New.hs 1.69 KB
Newer Older
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20
{-|
Module      : Gargantext.API.Corpus.New
Description : New corpus API
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

New corpus means either:
- new corpus
- new data in existing corpus
-}

{-# LANGUAGE NoImplicitPrelude  #-}
{-# LANGUAGE TemplateHaskell    #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE DataKinds          #-}
{-# LANGUAGE TypeOperators      #-}
{-# LANGUAGE OverloadedStrings  #-}
21 22
{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE RankNTypes          #-}
23 24 25 26

module Gargantext.API.Corpus.New
      where

27 28 29 30 31 32 33
import Data.Aeson.TH (deriveJSON)
import Data.Swagger
import Data.Text (Text)
import GHC.Generics (Generic)
import Gargantext.Core (Lang(..))
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Flow (flowCorpusSearchInDatabase)
34
import Gargantext.Database.Types.Node (CorpusId)
35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56
import Gargantext.Prelude
import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import Gargantext.Database.Flow (FlowCmdM)

data Query = Query { query_query      :: Text
                   , query_corpus_id  :: Int
                   }
                   deriving (Eq, Show, Generic)

deriveJSON (unPrefix "query_") ''Query


instance Arbitrary Query where
    arbitrary = elements [ Query q n
                         | q <- ["a","b"]
                         , n <- [0..10]
                         ]

instance ToSchema Query

57 58 59 60 61 62

type Api = Summary "New Corpus endpoint"
         :> ReqBody '[JSON] Query
         :> Post '[JSON] CorpusId


63 64 65 66
api :: FlowCmdM env err m => Query -> m CorpusId
api (Query q _) = do
  cId <- flowCorpusSearchInDatabase "user1" EN q
  pure cId