]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Count.hs
[MOCK] all routes completed, builds but need to be adapted to fite the practices.
[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 (permutations)
35 -----------------------------------------------------------------------
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 -----------------------------------------------------------------------
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
60 instance Arbitrary QueryBool where
61 arbitrary = elements queries
62
63 instance FromJSON QueryBool
64 instance ToJSON QueryBool
65
66
67
68 data Query = Query { query_query :: QueryBool
69 , query_name :: Maybe [Scraper]
70 }
71 deriving (Eq, Show, Generic)
72 instance FromJSON Query
73 instance ToJSON Query
74 instance Arbitrary Query where
75 arbitrary = elements [ Query q (Just n)
76 | q <- queries
77 , n <- take 10 $ permutations scrapers
78 ]
79
80 -----------------------------------------------------------------------
81 -----------------------------------------------------------------------
82 type Code = Integer
83 type Error = Text
84 type Errors = [Error]
85
86 data Message = Message Code Errors
87 deriving (Eq, Show, Generic)
88
89 toMessage :: [(Code, Errors)] -> [Message]
90 toMessage = map (\(c,err) -> Message c err)
91
92 messages :: [Message]
93 messages = toMessage $ [ (400, ["Ill formed query "])
94 , (300, ["API connexion error "])
95 , (300, ["Internal Gargantext Error "])
96 , (300, ["Connexion to Gargantext Error"])
97 , (300, ["Token has expired "])
98 ] -- <> take 10 ( repeat (200, [""]))
99
100 instance Arbitrary Message where
101 arbitrary = elements messages
102
103 instance FromJSON Message
104 instance ToJSON Message
105
106 -----------------------------------------------------------------------
107 -----------------------------------------------------------------------
108 data Counts = Counts [Count]
109 deriving (Eq, Show, Generic)
110
111 instance FromJSON Counts
112 instance ToJSON Counts
113
114 data Count = Count { count_name :: Scraper
115 , count_count :: Maybe Int
116 , count_message :: Maybe Message
117 }
118 deriving (Eq, Show, Generic)
119
120 instance FromJSON Count
121 instance ToJSON Count
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 -----------------------------------------------------------------------
136 count :: Query -> Handler Counts
137 count _ = undefined