]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Count.hs
Merge branch 'dev' into dev-doc-annotation-issue
[gargantext.git] / src / Gargantext / API / Count.hs
1 {-|
2 Module : Gargantext.API.Count
3 Description : Server API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Count API part of Gargantext.
11 -}
12
13 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
14
15 {-# LANGUAGE TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
17 {-# LANGUAGE DeriveAnyClass #-}
18
19 module Gargantext.API.Count
20 where
21
22
23 import GHC.Generics (Generic)
24 import Prelude (Bounded, Enum, minBound, maxBound)
25
26 import Data.Aeson hiding (Error)
27 import Data.Aeson.TH (deriveJSON)
28 import Data.Eq (Eq())
29 import Data.Either
30 import Data.List (repeat, permutations)
31 import Data.Swagger
32 import Data.Text (Text, pack)
33
34 import Servant
35 import Test.QuickCheck.Arbitrary
36 import Test.QuickCheck (elements)
37 -- import Control.Applicative ((<*>))
38
39 import Gargantext.Prelude
40 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
41
42 -----------------------------------------------------------------------
43 -- TODO-ACCESS: CanCount
44 -- TODO-EVENTS: No events as this is a read only query.
45 type CountAPI = Post '[JSON] Counts
46
47 -----------------------------------------------------------------------
48 data Scraper = Pubmed | Hal | IsTex | Isidore
49 deriving (Eq, Show, Generic, Enum, Bounded)
50
51 scrapers :: [Scraper]
52 scrapers = [minBound..maxBound]
53
54 instance FromJSON Scraper
55 instance ToJSON Scraper
56
57 instance Arbitrary Scraper where
58 arbitrary = elements scrapers
59
60 instance ToSchema Scraper
61
62 -----------------------------------------------------------------------
63 data QueryBool = QueryBool Text
64 deriving (Eq, Show, Generic)
65
66 queries :: [QueryBool]
67 queries = [QueryBool (pack "(X OR X') AND (Y OR Y') NOT (Z OR Z')")]
68 --queries = [QueryBool (pack "(X + X') * (Y + Y') - (Z + Z')")]
69
70 instance Arbitrary QueryBool where
71 arbitrary = elements queries
72
73 instance FromJSON QueryBool
74 instance ToJSON QueryBool
75
76 instance ToSchema QueryBool
77 -----------------------------------------------------------------------
78
79 data Query = Query { query_query :: QueryBool
80 , query_name :: Maybe [Scraper]
81 }
82 deriving (Eq, Show, Generic)
83 instance FromJSON Query
84 instance ToJSON Query
85
86 instance Arbitrary Query where
87 arbitrary = elements [ Query q (Just n)
88 | q <- queries
89 , n <- take 10 $ permutations scrapers
90 ]
91
92 instance ToSchema Query where
93 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "query_")
94
95 -----------------------------------------------------------------------
96 type Code = Integer
97 type Error = Text
98 type Errors = [Error]
99
100 -----------------------------------------------------------------------
101 data Message = Message Code Errors
102 deriving (Eq, Show, Generic)
103
104 toMessage :: [(Code, Errors)] -> [Message]
105 toMessage = map (\(c,err) -> Message c err)
106
107 messages :: [Message]
108 messages = toMessage $ [ (400, ["Ill formed query "])
109 , (300, ["API connexion error "])
110 , (300, ["Internal Gargantext Error "])
111 ] <> take 10 ( repeat (200, [""]))
112
113 instance Arbitrary Message where
114 arbitrary = elements messages
115
116 instance FromJSON Message
117 instance ToJSON Message
118
119 instance ToSchema Message
120 -----------------------------------------------------------------------
121 data Counts = Counts { results :: [Either Message Count]
122 } deriving (Eq, Show, Generic)
123
124
125 instance FromJSON Counts
126 instance ToJSON Counts
127
128 instance Arbitrary Counts where
129 arbitrary = elements [Counts [ Right (Count Pubmed (Just 20 ))
130 , Right (Count IsTex (Just 150))
131 , Right (Count Hal (Just 150))
132 ]
133 ]
134
135 instance ToSchema Counts
136
137 -----------------------------------------------------------------------
138 data Count = Count { count_name :: Scraper
139 , count_count :: Maybe Int
140 }
141 deriving (Eq, Show, Generic)
142
143 $(deriveJSON (unPrefix "count_") ''Count)
144
145 instance ToSchema Count where
146 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "count_")
147 --instance Arbitrary Count where
148 -- arbitrary = Count <$> arbitrary <*> arbitrary <*> arbitrary
149
150 -----------------------------------------------------------------------
151 count :: Monad m => Query -> m Counts
152 count _ = undefined