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
10 New corpus means either:
12 - new data in existing corpus
15 {-# LANGUAGE NoImplicitPrelude #-}
16 {-# LANGUAGE TemplateHaskell #-}
17 {-# LANGUAGE DeriveGeneric #-}
18 {-# LANGUAGE DataKinds #-}
19 {-# LANGUAGE TypeOperators #-}
20 {-# LANGUAGE OverloadedStrings #-}
21 {-# LANGUAGE FlexibleContexts #-}
22 {-# LANGUAGE RankNTypes #-}
24 module Gargantext.API.Corpus.New
27 import Data.Aeson.TH (deriveJSON)
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)
38 import Test.QuickCheck (elements)
39 import Test.QuickCheck.Arbitrary
40 import Gargantext.Database.Flow (FlowCmdM)
42 data Query = Query { query_query :: Text
43 , query_corpus_id :: Int
44 , query_files_id :: [Text]
46 deriving (Eq, Show, Generic)
48 deriveJSON (unPrefix "query_") ''Query
51 instance Arbitrary Query where
52 arbitrary = elements [ Query q n fs
55 , fs <- map (map hash) [["a","b"], ["c","d"]]
58 instance ToSchema Query
61 type Api = Summary "New Corpus endpoint"
62 :> ReqBody '[JSON] Query
63 :> Post '[JSON] CorpusId
66 api :: FlowCmdM env err m => Query -> m CorpusId
67 api (Query q _ _) = do
68 cId <- flowCorpusSearchInDatabase "user1" EN q