Routes.hs 1.81 KB
{-|
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 TypeFamilies         #-}
{-# LANGUAGE UndecidableInstances #-}

module Gargantext.API.Routes
      where

import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Prelude (GargM)
import Gargantext.API.Routes.Named.Corpus qualified as Named
import Gargantext.API.Worker (serveWorkerAPI)
import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Worker.Jobs.Types qualified as Jobs
import Gargantext.Prelude
import Servant.Server.Generic (AsServerT)

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

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

addCorpusWithForm :: User -> Named.AddWithForm (AsServerT (GargM Env BackendInternalError))
addCorpusWithForm user =
  Named.AddWithForm {
    addWithFormEp = \cId -> serveWorkerAPI $ \p ->
      -- /NOTE(adinapoli)/ Track the initial steps outside 'addToCorpusWithForm', because it's
      -- called in a few places, and the job status might be different between invocations.
      -- markStarted 3 jHandle
      -- New.addToCorpusWithForm user cid i jHandle
      Jobs.AddCorpusFormAsync { Jobs._acf_args = p
                              , Jobs._acf_user = user
                              , Jobs._acf_cid = cId }
    }