{-| Module : Gargantext.API.Routes Description : Copyright : (c) CNRS, 2017-Present License : AGPL + CECILL v3 Maintainer : team@gargantext.org Stability : experimental Portability : POSIX -} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} module Gargantext.API.Routes where import Data.ByteString.Base64 qualified as BSB64 import Data.Text qualified as T import Data.Text.Encoding qualified as TE import Database.PostgreSQL.Simple.LargeObjects qualified as PSQL import Gargantext.API.Admin.Auth.Types (AuthenticatedUser, auth_user_id) import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Errors.Types (BackendInternalError) import Gargantext.API.Node.Corpus.New.Types ( FileFormat(..) ) import Gargantext.API.Node.Types (NewWithForm(..), NewWithTempFile(..)) import Gargantext.API.Prelude (GargServer, GargM) import Gargantext.API.Routes.Named.Annuaire qualified as Named import Gargantext.API.Routes.Named.Corpus qualified as Named import Gargantext.API.Worker (serveWorkerAPI, serveWorkerAPIM) import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Worker.Jobs.Types qualified as Jobs import Gargantext.Database.Prelude (createLargeObject) import Gargantext.Prelude import Gargantext.System.Logging ( logLocM, LogLevel(..) ) import Servant (Get, JSON) import Servant.Server.Generic (AsServerT) ---------------------------------------------------------------------- -- For Tests type WaitAPI = Get '[JSON] Text waitAPI :: Int -> GargServer WaitAPI waitAPI n = do let m = (10 :: Int) ^ (6 :: Int) _ <- liftBase $ threadDelay ( m * n) pure $ "Waited: " <> show n ---------------------------------------- -- addCorpusWithQuery :: User -> Named.AddWithQuery (AsServerT (GargM Env BackendInternalError)) -- addCorpusWithQuery user = Named.AddWithQuery $ \cid -> AsyncJobs $ -- serveJobsAPI AddCorpusQueryJob $ \_jHandle q -> do -- -- limit <- view $ hasConfig . gc_jobs . jc_max_docs_scrapers -- -- New.addToCorpusWithQuery user cid q (Just $ fromIntegral limit) jHandle -- void $ Jobs.sendJob $ Jobs.AddCorpusWithQuery { Jobs._acq_args = q -- , Jobs._acq_user = user -- , Jobs._acq_cid = cid } {- let log' x = do printDebug "addToCorpusWithQuery" x liftBase $ log x -} addCorpusWithQuery :: User -> Named.AddWithQuery (AsServerT (GargM Env BackendInternalError)) addCorpusWithQuery user = Named.AddWithQuery { addWithQueryEp = \cId -> serveWorkerAPI $ \p -> Jobs.AddCorpusWithQuery { Jobs._acq_args = p , Jobs._acq_user = user , Jobs._acq_cid = cId } } -- | Uses temporary file stored in postgres to add that file to a corpus addWithTempFileApi :: AuthenticatedUser -> Named.AddWithTempFile (AsServerT (GargM Env BackendInternalError)) addWithTempFileApi authenticatedUser = Named.AddWithTempFile { addWithTempFileEp = \cId -> serveWorkerAPIM $ \(NewWithForm { .. }) -> do let bs = case _wf_fileformat of Plain -> cs _wf_data ZIP -> case BSB64.decode $ TE.encodeUtf8 _wf_data of Left err -> panicTrace $ T.pack "[addWithTempFileApi] error decoding base64: " <> T.pack err Right decoded -> decoded (PSQL.Oid oId) <- createLargeObject bs $(logLocM) DEBUG $ "[addWithTempFileApi] oId': " <> show oId let args = NewWithTempFile { _wtf_filetype = _wf_filetype , _wtf_fileformat = _wf_fileformat , _wtf_file_oid = fromIntegral oId , _wtf_lang = _wf_lang , _wtf_name = _wf_name , _wtf_selection = _wf_selection } pure $ Jobs.AddCorpusTempFileAsync { _actf_args = args , _actf_cid = cId , _actf_user = userId } } where userId = UserDBId $ authenticatedUser ^. auth_user_id addAnnuaireWithForm :: Named.AddAnnuaireWithForm (AsServerT (GargM Env BackendInternalError)) addAnnuaireWithForm = Named.AddAnnuaireWithForm { addWithFormEp = \aId -> serveWorkerAPI $ \i -> Jobs.AddToAnnuaireWithForm { _aawf_annuaire_id = aId , _aawf_args = i } }