{-|
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.
-}

{-# OPTIONS_GHC -fno-warn-deprecations #-}

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

module Gargantext.API.Search
      where

import Data.Text qualified as T
import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Search qualified as Named
import Gargantext.API.Search.Types
import Gargantext.Core.Text.Corpus.Query (RawQuery (..), parseQuery)
import Gargantext.Core.Types.Search
import Gargantext.Database.Action.Flow.Pairing (isPairedWith)
import Gargantext.Database.Action.Search
import Gargantext.Database.Admin.Types.Node hiding (DEBUG)
import Gargantext.Prelude
import Gargantext.System.Logging
import Servant.Server.Generic (AsServerT)

-----------------------------------------------------------------------
-- TODO-ACCESS: CanSearch? or is it part of CanGetNode
-- TODO-EVENTS: No event, this is a read-only query.
-- | Api search function
api :: IsGargServer env err m => NodeId -> Named.SearchAPI SearchResult (AsServerT m)
api nId = Named.SearchAPI $ \query o l order -> case query of
  (SearchQuery rawQuery SearchDoc) -> case parseQuery rawQuery of
    Left  err -> pure $ SearchResult $ SearchNoResult (T.pack err)
    Right q   -> do
      $(logLocM) DEBUG $ T.pack "New search started with query = " <> (getRawQuery rawQuery)
      SearchResult <$> SearchResultDoc
                   <$> map (toRow nId)
                   <$> searchInCorpus nId False q o l order
  (SearchQuery rawQuery SearchContact) -> case parseQuery rawQuery of
    Left  err -> pure $ SearchResult $ SearchNoResult (T.pack err)
    Right q   -> do
      -- printDebug "isPairedWith" nId
      aIds <- isPairedWith nId NodeAnnuaire
      -- TODO if paired with several corpus
      case head aIds of
        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
  (SearchQuery _q SearchDocWithNgrams) -> panicTrace "unimplemented"