Commit fd38823e authored by Alexandre Delanoë's avatar Alexandre Delanoë

[MOCK] More credible count.

parent e4cedde5
...@@ -11,11 +11,11 @@ Count API part of Gargantext. ...@@ -11,11 +11,11 @@ Count API part of Gargantext.
-} -}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveAnyClass #-}
module Gargantext.API.Count module Gargantext.API.Count
where where
...@@ -32,7 +32,7 @@ import Test.QuickCheck.Arbitrary ...@@ -32,7 +32,7 @@ import Test.QuickCheck.Arbitrary
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Data.List (repeat,permutations) import Data.List (repeat,permutations)
----------------------------------------------------------------------- -----------------------------------------------------------------------
type CountAPI = Post '[JSON] [Count] type CountAPI = Post '[JSON] Counts
----------------------------------------------------------------------- -----------------------------------------------------------------------
data Scraper = Pubmed | Hal | IsTex | Isidore data Scraper = Pubmed | Hal | IsTex | Isidore
...@@ -78,60 +78,59 @@ instance Arbitrary Query where ...@@ -78,60 +78,59 @@ instance Arbitrary Query where
----------------------------------------------------------------------- -----------------------------------------------------------------------
----------------------------------------------------------------------- -----------------------------------------------------------------------
data ErrorMessage = ErrorMessage Text
deriving (Eq, Show, Generic)
errorMessages :: [ErrorMessage]
errorMessages = map (\m -> ErrorMessage (pack m)) $ [ "Ill formed query "
, "API connexion error "
, "Internal Gargantext Error "
, "Connexion to Gargantext Error"
-- , "Token has expired "
] <> take 100 ( repeat ("No Error"))
instance Arbitrary ErrorMessage where type Error = Text
arbitrary = elements errorMessages type Errors = [Error]
instance FromJSON ErrorMessage data Message = Message Integer Errors
instance ToJSON ErrorMessage deriving (Eq, Show, Generic)
----------------------------------------------------------------------- toMessage :: [(Integer, [Text])] -> [Message]
data Error = Error { error_message :: ErrorMessage toMessage = map (\(c,es) -> Message c es)
, error_code :: Int
}
deriving (Eq, Show, Generic)
instance FromJSON Error
instance ToJSON Error
errorCodes :: [Int] messages :: [Message]
errorCodes = [200,300,400,500] messages = toMessage $ [ (400, ["Ill formed query "])
, (300, ["API connexion error "])
, (300, ["Internal Gargantext Error "])
, (300, ["Connexion to Gargantext Error"])
, (300, ["Token has expired "])
] <> take 10 ( repeat (200, [""]))
errors :: [Error] instance Arbitrary Message where
errors = [ Error m c | m <- errorMessages arbitrary = elements messages
, c <- errorCodes
]
instance Arbitrary Error where instance FromJSON Message
arbitrary = elements errors instance ToJSON Message
----------------------------------------------------------------------- -----------------------------------------------------------------------
----------------------------------------------------------------------- -----------------------------------------------------------------------
data Count = Count { count_name :: Scraper data Counts = Counts [Count]
, count_count :: Maybe Int deriving (Eq, Show, Generic)
, count_errors :: Maybe [Error]
} instance FromJSON Counts
instance ToJSON Counts
data Count = Count { count_name :: Scraper
, count_count :: Maybe Int
, count_message :: Maybe Message
}
deriving (Eq, Show, Generic) deriving (Eq, Show, Generic)
instance FromJSON Count instance FromJSON Count
instance ToJSON Count instance ToJSON Count
instance Arbitrary Count where instance Arbitrary Counts where
arbitrary = elements [ Count n (Just c) (Just [e]) | n <- scrapers arbitrary = elements $ select
, c <- [100..1000] $ map Counts
, e <- errors $ map (\xs -> zipWith (\s (c,m) -> Count s c m) scrapers xs)
] $ chunkAlong (length scrapers) 1 $ (map filter' countOrErrors)
where
select xs = (take 10 xs) <> (take 10 $ drop 100 xs)
countOrErrors = [ (c,e) | c <- [500..1000], e <- reverse messages]
filter' (c,e) = case e of
Message 200 _ -> (Just c , Nothing )
message -> (Nothing, Just message)
----------------------------------------------------------------------- -----------------------------------------------------------------------
count :: Query -> Handler [Count] count :: Query -> Handler Counts
count _ = undefined count _ = undefined
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment