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