]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Corpus/New.hs
add branching
[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 Gargantext.Prelude.Utils (hash)
37 import Servant
38 import Test.QuickCheck (elements)
39 import Test.QuickCheck.Arbitrary
40 import Gargantext.Database.Flow (FlowCmdM)
41 import qualified Gargantext.Text.Corpus.API as API
42 import Gargantext.Database.Types.Node (UserId)
43
44 data Query = Query { query_query :: Text
45 , query_corpus_id :: Int
46 , query_files_id :: [Text]
47 }
48 deriving (Eq, Show, Generic)
49
50 deriveJSON (unPrefix "query_") 'Query
51
52
53 instance Arbitrary Query where
54 arbitrary = elements [ Query q n fs
55 | q <- ["a","b"]
56 , n <- [0..10]
57 , fs <- map (map hash) [["a","b"], ["c","d"]]
58 ]
59
60 instance ToSchema Query where
61 declareNamedSchema =
62 genericDeclareNamedSchema
63 defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 6 fieldLabel}
64
65
66
67 type Api = Summary "New Corpus endpoint"
68 :> ReqBody '[JSON] Query
69 :> Post '[JSON] CorpusId
70 :<|> Get '[JSON] ApiInfo
71
72
73 api :: FlowCmdM env err m => Query -> m CorpusId
74 api (Query q _ _) = do
75 cId <- flowCorpusSearchInDatabase "user1" EN q
76 pure cId
77
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