]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Count.hs
Merge branch 'dev-phylo' of ssh://gitlab.iscpif.fr:20022/gargantext/haskell-gargantex...
[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
25 import Data.Aeson hiding (Error)
26 import Data.Aeson.TH (deriveJSON)
27 import Data.Either
28 import Data.List (permutations)
29 import Data.Swagger
30 import Data.Text (Text, pack)
31
32 import Servant
33 import Test.QuickCheck.Arbitrary
34 import Test.QuickCheck (elements)
35 -- import Control.Applicative ((<*>))
36
37 import Gargantext.Prelude
38 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
39
40 -----------------------------------------------------------------------
41 -- TODO-ACCESS: CanCount
42 -- TODO-EVENTS: No events as this is a read only query.
43 type CountAPI = Post '[JSON] Counts
44
45 -----------------------------------------------------------------------
46 data Scraper = Pubmed | Hal | IsTex | Isidore
47 deriving (Eq, Show, Generic, Enum, Bounded)
48
49 scrapers :: [Scraper]
50 scrapers = [minBound..maxBound]
51
52 instance FromJSON Scraper
53 instance ToJSON Scraper
54
55 instance Arbitrary Scraper where
56 arbitrary = elements scrapers
57
58 instance ToSchema Scraper
59
60 -----------------------------------------------------------------------
61 data QueryBool = QueryBool Text
62 deriving (Eq, Show, Generic)
63
64 queries :: [QueryBool]
65 queries = [QueryBool (pack "(X OR X') AND (Y OR Y') NOT (Z OR Z')")]
66 --queries = [QueryBool (pack "(X + X') * (Y + Y') - (Z + Z')")]
67
68 instance Arbitrary QueryBool where
69 arbitrary = elements queries
70
71 instance FromJSON QueryBool
72 instance ToJSON QueryBool
73
74 instance ToSchema QueryBool
75 -----------------------------------------------------------------------
76
77 data Query = Query { query_query :: QueryBool
78 , query_name :: Maybe [Scraper]
79 }
80 deriving (Eq, Show, Generic)
81 instance FromJSON Query
82 instance ToJSON Query
83
84 instance Arbitrary Query where
85 arbitrary = elements [ Query q (Just n)
86 | q <- queries
87 , n <- take 10 $ permutations scrapers
88 ]
89
90 instance ToSchema Query where
91 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "query_")
92
93 -----------------------------------------------------------------------
94 type Code = Integer
95 type Error = Text
96 type Errors = [Error]
97
98 -----------------------------------------------------------------------
99 data Message = Message Code Errors
100 deriving (Eq, Show, Generic)
101
102 toMessage :: [(Code, Errors)] -> [Message]
103 toMessage = map (\(c,err) -> Message c err)
104
105 messages :: [Message]
106 messages = toMessage $ [ (400, ["Ill formed query "])
107 , (300, ["API connexion error "])
108 , (300, ["Internal Gargantext Error "])
109 ] <> take 10 ( repeat (200, [""]))
110
111 instance Arbitrary Message where
112 arbitrary = elements messages
113
114 instance FromJSON Message
115 instance ToJSON Message
116
117 instance ToSchema Message
118 -----------------------------------------------------------------------
119 data Counts = Counts { results :: [Either Message Count]
120 } deriving (Eq, Show, Generic)
121
122
123 instance FromJSON Counts
124 instance ToJSON Counts
125
126 instance Arbitrary Counts where
127 arbitrary = elements [Counts [ Right (Count Pubmed (Just 20 ))
128 , Right (Count IsTex (Just 150))
129 , Right (Count Hal (Just 150))
130 ]
131 ]
132
133 instance ToSchema Counts
134
135 -----------------------------------------------------------------------
136 data Count = Count { count_name :: Scraper
137 , count_count :: Maybe Int
138 }
139 deriving (Eq, Show, Generic)
140
141 $(deriveJSON (unPrefix "count_") ''Count)
142
143 instance ToSchema Count where
144 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "count_")
145 --instance Arbitrary Count where
146 -- arbitrary = Count <$> arbitrary <*> arbitrary <*> arbitrary
147
148 -----------------------------------------------------------------------
149 count :: Monad m => Query -> m Counts
150 count _ = undefined