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