]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Count.hs
[STATIC+SWAGGER+MOCK] startGargantextMock 8008
[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 {-# LANGUAGE DataKinds #-}
15 {-# LANGUAGE TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
17 {-# LANGUAGE DeriveGeneric #-}
18 {-# LANGUAGE DeriveAnyClass #-}
19 {-# LANGUAGE OverloadedStrings #-}
20
21 module Gargantext.API.Count
22 where
23
24 import Gargantext.Prelude
25
26 import GHC.Generics (Generic)
27 import Prelude (Bounded, Enum, minBound, maxBound)
28
29 import Data.Eq (Eq())
30 import Data.Text (Text, pack)
31 import Data.Aeson hiding (Error)
32 import Data.List (repeat, permutations)
33 import Data.Swagger
34
35 import Servant
36 import Test.QuickCheck.Arbitrary
37 import Test.QuickCheck (elements)
38 -- import Control.Applicative ((<*>))
39
40 -----------------------------------------------------------------------
41 type CountAPI = Post '[JSON] Counts
42
43 -----------------------------------------------------------------------
44 data Scraper = Pubmed | Hal | IsTex | Isidore
45 deriving (Eq, Show, Generic, Enum, Bounded)
46
47 scrapers :: [Scraper]
48 scrapers = [minBound..maxBound]
49
50 instance FromJSON Scraper
51 instance ToJSON Scraper
52
53 instance Arbitrary Scraper where
54 arbitrary = elements scrapers
55
56 instance ToSchema Scraper
57
58 -----------------------------------------------------------------------
59
60 data QueryBool = QueryBool Text
61 deriving (Eq, Show, Generic)
62
63 queries :: [QueryBool]
64 queries = [QueryBool (pack "(X OR X') AND (Y OR Y') NOT (Z OR Z')")]
65
66 instance Arbitrary QueryBool where
67 arbitrary = elements queries
68
69 instance FromJSON QueryBool
70 instance ToJSON QueryBool
71
72 instance ToSchema QueryBool
73 -----------------------------------------------------------------------
74
75 data Query = Query { query_query :: QueryBool
76 , query_name :: Maybe [Scraper]
77 }
78 deriving (Eq, Show, Generic)
79 instance FromJSON Query
80 instance ToJSON Query
81
82 instance Arbitrary Query where
83 arbitrary = elements [ Query q (Just n)
84 | q <- queries
85 , n <- take 10 $ permutations scrapers
86 ]
87
88 instance ToSchema Query
89 -----------------------------------------------------------------------
90 type Code = Integer
91 type Error = Text
92 type Errors = [Error]
93
94 -----------------------------------------------------------------------
95 data Message = Message Code Errors
96 deriving (Eq, Show, Generic)
97
98 toMessage :: [(Code, Errors)] -> [Message]
99 toMessage = map (\(c,err) -> Message c err)
100
101 messages :: [Message]
102 messages = toMessage $ [ (400, ["Ill formed query "])
103 , (300, ["API connexion error "])
104 , (300, ["Internal Gargantext Error "])
105 , (300, ["Connexion to Gargantext Error"])
106 , (300, ["Token has expired "])
107 ] <> take 10 ( repeat (200, [""]))
108
109 instance Arbitrary Message where
110 arbitrary = elements messages
111
112 instance FromJSON Message
113 instance ToJSON Message
114
115 instance ToSchema Message
116 -----------------------------------------------------------------------
117 data Counts = Counts [Count]
118 deriving (Eq, Show, Generic)
119
120 instance FromJSON Counts
121 instance ToJSON Counts
122
123 instance Arbitrary Counts where
124 arbitrary = elements $ select
125 $ map Counts
126 $ map (\xs -> zipWith (\s (c,m) -> Count s c m) scrapers xs)
127 $ chunkAlong (length scrapers) 1 $ (map filter' countOrErrors)
128 where
129 select xs = (take 10 xs) <> (take 10 $ drop 100 xs)
130 countOrErrors = [ (c,e) | c <- [500..1000], e <- reverse messages]
131 filter' (c,e) = case e of
132 Message 200 _ -> (Just c , Nothing )
133 message -> (Nothing, Just message)
134
135 instance ToSchema Counts
136
137
138 -----------------------------------------------------------------------
139 data Count = Count { count_name :: Scraper
140 , count_count :: Maybe Int
141 , count_message :: Maybe Message
142 }
143 deriving (Eq, Show, Generic)
144
145 instance FromJSON Count
146 instance ToJSON Count
147
148 instance ToSchema Count
149 --instance Arbitrary Count where
150 -- arbitrary = Count <$> arbitrary <*> arbitrary <*> arbitrary
151
152 -----------------------------------------------------------------------
153 count :: Query -> Handler Counts
154 count _ = undefined