2 Module : Gargantext.API.Count
3 Description : Server API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Count API part of Gargantext.
13 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
15 {-# LANGUAGE TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
17 {-# LANGUAGE DeriveAnyClass #-}
19 module Gargantext.API.Search
22 import Data.Aeson.TH (deriveJSON)
24 import Data.Text (Text)
25 import Data.Time (UTCTime)
26 import GHC.Generics (Generic)
27 import Gargantext.API.Prelude (GargServer)
28 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
29 import Gargantext.Database.Query.Facet
30 import Gargantext.Database.Action.Search
31 import Gargantext.Database.Admin.Types.Node
32 import Gargantext.Prelude
34 import Test.QuickCheck (elements)
35 import Test.QuickCheck.Arbitrary
37 -----------------------------------------------------------------------
38 data SearchQuery = SearchQuery
42 $(deriveJSON (unPrefix "sq_") ''SearchQuery)
44 instance ToSchema SearchQuery where
45 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "sq_")
47 instance Arbitrary SearchQuery where
48 arbitrary = elements [SearchQuery ["electrodes"]]
50 -----------------------------------------------------------------------
51 data SearchDocResults = SearchDocResults { sdr_results :: [FacetDoc]}
53 $(deriveJSON (unPrefix "sdr_") ''SearchDocResults)
55 instance Arbitrary SearchDocResults where
56 arbitrary = SearchDocResults <$> arbitrary
58 instance ToSchema SearchDocResults where
59 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "sdr_")
61 data SearchPairedResults =
62 SearchPairedResults { spr_results :: [FacetPaired Int UTCTime HyperdataDocument Int [Pair Int Text]] }
64 $(deriveJSON (unPrefix "spr_") ''SearchPairedResults)
66 instance Arbitrary SearchPairedResults where
67 arbitrary = SearchPairedResults <$> arbitrary
69 instance ToSchema SearchPairedResults where
70 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "spr_")
72 -----------------------------------------------------------------------
73 -- TODO-ACCESS: CanSearch? or is it part of CanGetNode
74 -- TODO-EVENTS: No event, this is a read-only query.
75 type SearchAPI results = Summary "Search endpoint"
76 :> ReqBody '[JSON] SearchQuery
77 :> QueryParam "offset" Int
78 :> QueryParam "limit" Int
79 :> QueryParam "order" OrderBy
80 :> Post '[JSON] results
82 type SearchDocsAPI = SearchAPI SearchDocResults
83 searchDocs :: NodeId -> GargServer SearchDocsAPI
84 searchDocs nId (SearchQuery q) o l order =
85 SearchDocResults <$> searchInCorpus nId False q o l order
86 --SearchResults <$> searchInCorpusWithContacts nId q o l order
88 -----------------------------------------------------------------------
89 type SearchPairsAPI = Summary ""
91 :> Capture "list" ListId
92 :> SearchAPI SearchPairedResults
93 searchPairs :: NodeId -> GargServer SearchPairsAPI
95 searchPairs pId lId (SearchQuery q) o l order =
96 SearchPairedResults <$> searchInCorpusWithContacts pId lId q o l order
98 -----------------------------------------------------------------------