]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Count.hs
[MOCK] pushing for the meeting and tests with the team.
[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 Prelude (Bounded, Enum, minBound, maxBound)
27 import Data.Eq (Eq())
28 import Data.Text (Text, pack)
29 import Servant
30 import GHC.Generics (Generic)
31 import Data.Aeson hiding (Error)
32 import Test.QuickCheck.Arbitrary
33 import Test.QuickCheck (elements)
34 import Data.List (repeat, permutations)
35 -- import Control.Applicative ((<*>))
36
37 -----------------------------------------------------------------------
38 type CountAPI = Post '[JSON] Counts
39
40 -----------------------------------------------------------------------
41 data Scraper = Pubmed | Hal | IsTex | Isidore
42 deriving (Eq, Show, Generic, Enum, Bounded)
43
44 scrapers :: [Scraper]
45 scrapers = [minBound..maxBound]
46
47 instance FromJSON Scraper
48 instance ToJSON Scraper
49
50 instance Arbitrary Scraper where
51 arbitrary = elements scrapers
52
53 -----------------------------------------------------------------------
54 -----------------------------------------------------------------------
55
56 data QueryBool = QueryBool Text
57 deriving (Eq, Show, Generic)
58
59 queries :: [QueryBool]
60 queries = [QueryBool (pack "(X OR X') AND (Y OR Y') NOT (Z OR Z')")]
61
62 instance Arbitrary QueryBool where
63 arbitrary = elements queries
64
65 instance FromJSON QueryBool
66 instance ToJSON QueryBool
67
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 -----------------------------------------------------------------------
84 -----------------------------------------------------------------------
85 type Code = Integer
86 type Error = Text
87 type Errors = [Error]
88
89 data Message = Message Code Errors
90 deriving (Eq, Show, Generic)
91
92 toMessage :: [(Code, Errors)] -> [Message]
93 toMessage = map (\(c,err) -> Message c err)
94
95 messages :: [Message]
96 messages = toMessage $ [ (400, ["Ill formed query "])
97 , (300, ["API connexion error "])
98 , (300, ["Internal Gargantext Error "])
99 , (300, ["Connexion to Gargantext Error"])
100 , (300, ["Token has expired "])
101 ] <> take 10 ( repeat (200, [""]))
102
103 instance Arbitrary Message where
104 arbitrary = elements messages
105
106 instance FromJSON Message
107 instance ToJSON Message
108
109 -----------------------------------------------------------------------
110 -----------------------------------------------------------------------
111 data Counts = Counts [Count]
112 deriving (Eq, Show, Generic)
113
114 instance FromJSON Counts
115 instance ToJSON Counts
116
117 data Count = Count { count_name :: Scraper
118 , count_count :: Maybe Int
119 , count_message :: Maybe Message
120 }
121 deriving (Eq, Show, Generic)
122
123 instance FromJSON Count
124 instance ToJSON Count
125 --
126 --instance Arbitrary Count where
127 -- arbitrary = Count <$> arbitrary <*> arbitrary <*> arbitrary
128
129
130 instance Arbitrary Counts where
131 arbitrary = elements $ select
132 $ map Counts
133 $ map (\xs -> zipWith (\s (c,m) -> Count s c m) scrapers xs)
134 $ chunkAlong (length scrapers) 1 $ (map filter' countOrErrors)
135 where
136 select xs = (take 10 xs) <> (take 10 $ drop 100 xs)
137 countOrErrors = [ (c,e) | c <- [500..1000], e <- reverse messages]
138 filter' (c,e) = case e of
139 Message 200 _ -> (Just c , Nothing )
140 message -> (Nothing, Just message)
141
142 -----------------------------------------------------------------------
143 count :: Query -> Handler Counts
144 count _ = undefined