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

Count API part of Gargantext.
-}

{-# LANGUAGE TemplateHaskell    #-}
{-# LANGUAGE TypeOperators      #-}
{-# LANGUAGE DeriveAnyClass     #-}

module Gargantext.API.Search
      where

20
import Data.Aeson hiding (defaultTaggedObject)
21
import Data.Maybe (fromMaybe)
22
import Data.Swagger hiding (fieldLabelModifier, Contact)
23
import Data.Text (Text)
24
import Data.Time (UTCTime)
25
import GHC.Generics (Generic)
26
import Gargantext.API.Prelude (GargServer)
27 28
import Gargantext.Core.Utils.Prefix (unPrefixSwagger, unCapitalize, dropPrefix)
import Gargantext.Database.Action.Flow.Pairing (isPairedWith)
29
import Gargantext.Database.Action.Search
30
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataContact(..), HyperdataDocument(..), ContactWho(..))
31
import Gargantext.Database.Admin.Types.Hyperdata.Contact (_cw_organization)
32
import Gargantext.Database.Admin.Types.Node
33
import Gargantext.Database.Query.Facet
34
import Gargantext.Prelude
35
import Gargantext.Utils.Aeson (defaultTaggedObject)
36 37 38
import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
39
import qualified Data.Text as Text
40

41 42 43 44 45 46 47 48 49 50
-----------------------------------------------------------------------
-- TODO-ACCESS: CanSearch? or is it part of CanGetNode
-- TODO-EVENTS: No event, this is a read-only query.
type API results = Summary "Search endpoint"
                 :> ReqBody '[JSON] SearchQuery
                 :> QueryParam "offset" Int
                 :> QueryParam "limit"  Int
                 :> QueryParam "order"  OrderBy
                 :> Post '[JSON] results
-----------------------------------------------------------------------
Alexandre Delanoë's avatar
Alexandre Delanoë committed
51
-- | Api search function
52
api :: NodeId -> GargServer (API SearchResult)
Alexandre Delanoë's avatar
Alexandre Delanoë committed
53

54
api nId (SearchQuery q SearchDoc) o l order =
Alexandre Delanoë's avatar
Alexandre Delanoë committed
55 56 57 58
  SearchResult <$> SearchResultDoc
               <$> map (toRow nId)
               <$> searchInCorpus nId False q o l order

59
api nId (SearchQuery q SearchContact) o l order = do
60 61
  printDebug "isPairedWith" nId
  aIds <- isPairedWith nId NodeAnnuaire
62 63
  -- TODO if paired with several corpus
  case head aIds of
Alexandre Delanoë's avatar
Alexandre Delanoë committed
64 65 66 67 68 69
    Nothing  -> pure $ SearchResult
              $ SearchNoResult "[G.A.Search] pair corpus with an Annuaire"
    Just aId -> SearchResult
            <$> SearchResultContact
            <$> map (toRow aId)
            <$> searchInCorpusWithContacts nId aId q o l order
70

71 72 73
-----------------------------------------------------------------------
-----------------------------------------------------------------------
-- | Main Types
74 75 76
-----------------------------------------------------------------------
data SearchType = SearchDoc | SearchContact
  deriving (Generic)
77 78 79 80
instance FromJSON SearchType where
  parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToJSON SearchType where
  toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
81 82 83 84
instance ToSchema SearchType
instance Arbitrary SearchType where
  arbitrary = elements [SearchDoc, SearchContact]

85
-----------------------------------------------------------------------
86 87 88
data SearchQuery =
  SearchQuery { query    :: ![Text]
              , expected :: !SearchType
89 90
              }
    deriving (Generic)
91 92 93 94
instance FromJSON SearchQuery where
  parseJSON = genericParseJSON defaultOptions
instance ToJSON SearchQuery where
  toJSON = genericToJSON defaultOptions
95 96 97 98 99
instance ToSchema SearchQuery
{-
  where
    declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
-}
100 101

instance Arbitrary SearchQuery where
102
  arbitrary = elements [SearchQuery ["electrodes"] SearchDoc]
103
  -- arbitrary = elements [SearchQuery "electrodes" 1 ] --SearchDoc]
104
-----------------------------------------------------------------------
105
data SearchResult =
106
  SearchResult { result :: !SearchResultTypes}
107
    deriving (Generic)
108

109 110
instance FromJSON SearchResult where
  parseJSON = genericParseJSON defaultOptions
111

112 113
instance ToJSON SearchResult where
  toJSON = genericToJSON defaultOptions
114 115 116 117 118

instance ToSchema SearchResult
{-
  where
    declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
119
-}
120

121
instance Arbitrary SearchResult where
122 123 124
  arbitrary = SearchResult <$> arbitrary


125 126 127 128
data SearchResultTypes =
    SearchResultDoc { docs     :: ![Row] }
  | SearchResultContact  { contacts :: ![Row] }
  | SearchNoResult      { message  :: !Text }
129
  deriving (Generic)
130 131 132 133
instance FromJSON SearchResultTypes where
  parseJSON = genericParseJSON (defaultOptions { sumEncoding = defaultTaggedObject })
instance ToJSON SearchResultTypes where
  toJSON = genericToJSON (defaultOptions { sumEncoding = defaultTaggedObject })
134 135
 
instance Arbitrary SearchResultTypes where
136 137
  arbitrary = do
    srd <- SearchResultDoc     <$> arbitrary
138 139 140 141 142 143 144 145 146 147 148
    src <- SearchResultContact <$> arbitrary
    srn <- pure $ SearchNoResult "No result because.."
    elements [srd, src, srn]

instance ToSchema SearchResultTypes where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")


--------------------------------------------------------------------

data Row =
149 150 151 152 153 154 155
    Document { id         :: !NodeId
             , created    :: !UTCTime
             , title      :: !Text
             , hyperdata  :: !HyperdataRow
             , category   :: !Int
             , score      :: !Int
             }
156 157 158 159
  | Contact  { c_id         :: !Int
             , c_created    :: !UTCTime
             , c_hyperdata  :: !HyperdataRow
             , c_score      :: !Int
Alexandre Delanoë's avatar
Alexandre Delanoë committed
160
             , c_annuaireId :: !NodeId
161
             }
162 163 164
  deriving (Generic)
instance FromJSON  Row
  where
165
    parseJSON = genericParseJSON 
166
                 ( defaultOptions { sumEncoding = defaultTaggedObject } )
167 168
instance ToJSON  Row
  where
169
    toJSON = genericToJSON (defaultOptions { sumEncoding = defaultTaggedObject })
170 171 172 173 174 175
instance Arbitrary Row where
  arbitrary = arbitrary

instance ToSchema Row where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")

176
class ToRow a where
Alexandre Delanoë's avatar
Alexandre Delanoë committed
177
  toRow :: NodeId -> a -> Row
178

179
instance ToRow FacetDoc where
180 181 182 183 184 185 186
  toRow _ (FacetDoc { .. }) =
    Document { id = facetDoc_id
             , created = facetDoc_created
             , title = facetDoc_title
             , hyperdata = toHyperdataRow facetDoc_hyperdata
             , category = fromMaybe 0 facetDoc_category
             , score = round $ fromMaybe 0 facetDoc_score }
187

188 189 190 191
-- | TODO rename FacetPaired
type FacetContact = FacetPaired Int UTCTime HyperdataContact Int

instance ToRow FacetContact where
Alexandre Delanoë's avatar
Alexandre Delanoë committed
192
  toRow annuaireId (FacetPaired nId utc h s) = Contact nId utc (toHyperdataRow h) s annuaireId
193 194 195


--------------------------------------------------------------------
196
data HyperdataRow =
197
  HyperdataRowDocument { _hr_abstract           :: !Text
198
                       , _hr_authors            :: !Text
199 200
                       , _hr_bdd                :: !Text
                       , _hr_doi                :: !Text
201
                       , _hr_institutes         :: !Text
202 203
                       , _hr_language_iso2      :: !Text
                       , _hr_page               :: !Int
204 205 206 207
                       , _hr_publication_date   :: !Text
                       , _hr_publication_day    :: !Int
                       , _hr_publication_hour   :: !Int
                       , _hr_publication_minute :: !Int
208
                       , _hr_publication_month  :: !Int
209
                       , _hr_publication_second :: !Int
210 211 212 213 214 215
                       , _hr_publication_year   :: !Int
                       , _hr_source             :: !Text
                       , _hr_title              :: !Text
                       , _hr_url                :: !Text
                       , _hr_uniqId             :: !Text
                       , _hr_uniqIdBdd          :: !Text
216
                       }
217 218 219 220
  | HyperdataRowContact { _hr_firstname :: !Text
                        , _hr_lastname  :: !Text
                        , _hr_labs      :: !Text
                        }
221 222 223 224 225
  deriving (Generic)
instance FromJSON  HyperdataRow
  where
    parseJSON = genericParseJSON
              ( defaultOptions
226
                { sumEncoding = defaultTaggedObject
227
                , fieldLabelModifier = unCapitalize . dropPrefix "_hr_"
228
                , omitNothingFields = False
229 230 231 232 233 234
                }
              )
instance ToJSON  HyperdataRow
  where
    toJSON = genericToJSON
               ( defaultOptions
235
                { sumEncoding = defaultTaggedObject
236
                , fieldLabelModifier = unCapitalize . dropPrefix "_hr_"
237
                , omitNothingFields = False
238 239 240 241 242
                }
              )

instance Arbitrary HyperdataRow where
  arbitrary = arbitrary
243

244 245
instance ToSchema HyperdataRow where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_hr_")
246

247 248 249 250
class ToHyperdataRow a where
  toHyperdataRow :: a -> HyperdataRow

instance ToHyperdataRow HyperdataDocument where
251
  toHyperdataRow (HyperdataDocument { .. }) =
252
    HyperdataRowDocument
253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271
      { _hr_abstract = fromMaybe "" _hd_abstract
      , _hr_authors = fromMaybe "" _hd_authors
      , _hr_bdd = fromMaybe "" _hd_bdd
      , _hr_doi = fromMaybe "" _hd_doi
      , _hr_institutes = fromMaybe "" _hd_institutes
      , _hr_language_iso2 = fromMaybe "EN" _hd_language_iso2
      , _hr_page = fromMaybe 0 _hd_page
      , _hr_publication_date = fromMaybe "" _hd_publication_date
      , _hr_publication_day = fromMaybe 1 _hd_publication_day
      , _hr_publication_hour = fromMaybe 1 _hd_publication_hour
      , _hr_publication_minute = fromMaybe 1 _hd_publication_minute
      , _hr_publication_month = fromMaybe 1 _hd_publication_month
      , _hr_publication_second = fromMaybe 1 _hd_publication_second
      , _hr_publication_year = fromMaybe 2020 _hd_publication_year
      , _hr_source = fromMaybe "" _hd_source
      , _hr_title = fromMaybe "Title" _hd_title
      , _hr_url = fromMaybe "" _hd_url
      , _hr_uniqId = fromMaybe "" _hd_uniqId
      , _hr_uniqIdBdd = fromMaybe "" _hd_uniqIdBdd }
272 273

instance ToHyperdataRow HyperdataContact where
274
  toHyperdataRow (HyperdataContact { _hc_who = Just (ContactWho _ fn ln _ _), _hc_where = ou} ) =
275 276
    HyperdataRowContact (fromMaybe "FirstName" fn) (fromMaybe "LastName" ln) ou'
      where
277
        ou' = maybe "CNRS" (Text.intercalate " " . _cw_organization) (head ou)
278
  toHyperdataRow (HyperdataContact {}) =
279
    HyperdataRowContact "FirstName" "LastName" "Labs"