]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Corpus/New.hs
[FACTO] Type Class and some Instances : Flow Corpus.
[gargantext.git] / src / Gargantext / API / Corpus / New.hs
1 {-|
2 Module : Gargantext.API.Corpus.New
3 Description : New corpus 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 New corpus means either:
11 - new corpus
12 - new data in existing corpus
13 -}
14
15 {-# LANGUAGE NoImplicitPrelude #-}
16 {-# LANGUAGE TemplateHaskell #-}
17 {-# LANGUAGE DeriveGeneric #-}
18 {-# LANGUAGE DataKinds #-}
19 {-# LANGUAGE TypeOperators #-}
20 {-# LANGUAGE OverloadedStrings #-}
21 {-# LANGUAGE FlexibleContexts #-}
22 {-# LANGUAGE RankNTypes #-}
23
24 module Gargantext.API.Corpus.New
25 where
26
27 import Data.Aeson.TH (deriveJSON)
28 import Data.Swagger
29 import Data.Text (Text)
30 import GHC.Generics (Generic)
31 import Gargantext.Core (Lang(..))
32 import Gargantext.Core.Utils.Prefix (unPrefix)
33 import Gargantext.Database.Flow (flowCorpusSearchInDatabase)
34 import Gargantext.Database.Types.Node (CorpusId)
35 import Gargantext.Prelude
36 import Servant
37 import Test.QuickCheck (elements)
38 import Test.QuickCheck.Arbitrary
39 import Gargantext.Database.Flow (FlowCmdM)
40 import qualified Gargantext.Text.Corpus.API as API
41 import Gargantext.Database.Types.Node (UserId)
42
43 data Query = Query { query_query :: Text
44 , query_corpus_id :: Int
45 , query_databases :: [API.ExternalAPIs]
46 }
47 deriving (Eq, Show, Generic)
48
49 deriveJSON (unPrefix "query_") 'Query
50
51
52 instance Arbitrary Query where
53 arbitrary = elements [ Query q n fs
54 | q <- ["a","b"]
55 , n <- [0..10]
56 , fs <- take 3 $ repeat API.externalAPIs
57 ]
58
59 instance ToSchema Query where
60 declareNamedSchema =
61 genericDeclareNamedSchema
62 defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 6 fieldLabel}
63
64 type Api = Summary "New Corpus endpoint"
65 :> ReqBody '[JSON] Query
66 :> Post '[JSON] CorpusId
67 :<|> Get '[JSON] ApiInfo
68
69 -- | TODO manage several apis
70 api :: FlowCmdM env err m => Query -> m CorpusId
71 api (Query q _ as) = do
72 cId <- case head as of
73 Nothing -> flowCorpusSearchInDatabase "user1" EN q
74 Just API.All -> flowCorpusSearchInDatabase "user1" EN q
75 Just _ -> undefined
76
77 pure cId
78
79 ------------------------------------------------
80 data ApiInfo = ApiInfo { api_info :: [API.ExternalAPIs]}
81 deriving (Generic)
82 instance Arbitrary ApiInfo where
83 arbitrary = ApiInfo <$> arbitrary
84
85 deriveJSON (unPrefix "") 'ApiInfo
86
87 instance ToSchema ApiInfo
88
89 info :: FlowCmdM env err m => UserId -> m ApiInfo
90 info _u = pure $ ApiInfo API.externalAPIs
91
92
93