Commit 8524a635 authored by Grégoire Locqueville's avatar Grégoire Locqueville

Renamed `DbCmd'` -> `IsDBCmd`

parent 18ae58ab
...@@ -62,7 +62,7 @@ import Gargantext.Core.Types.Individu (User(..), Username, GargPassword(..)) ...@@ -62,7 +62,7 @@ import Gargantext.Core.Types.Individu (User(..), Username, GargPassword(..))
import Gargantext.Core.Worker.Jobs.Types qualified as Jobs import Gargantext.Core.Worker.Jobs.Types qualified as Jobs
import Gargantext.Database.Action.User.New (guessUserName) import Gargantext.Database.Action.User.New (guessUserName)
import Gargantext.Database.Admin.Types.Node (NodeId(..), UserId) import Gargantext.Database.Admin.Types.Node (NodeId(..), UserId)
import Gargantext.Database.Prelude (Cmd', IsDBEnvExtra, DbCmd') import Gargantext.Database.Prelude (Cmd', IsDBEnvExtra, IsDBCmd)
import Gargantext.Database.Query.Table.User import Gargantext.Database.Query.Table.User
import Gargantext.Database.Query.Tree (isDescendantOf, isIn) import Gargantext.Database.Query.Tree (isDescendantOf, isIn)
import Gargantext.Database.Query.Tree.Root (getRoot) import Gargantext.Database.Query.Tree.Root (getRoot)
...@@ -89,7 +89,7 @@ makeTokenForUser nodeId userId = do ...@@ -89,7 +89,7 @@ makeTokenForUser nodeId userId = do
either (authenticationError . LoginFailed nodeId userId) (pure . toStrict . LE.decodeUtf8) e either (authenticationError . LoginFailed nodeId userId) (pure . toStrict . LE.decodeUtf8) e
-- TODO not sure about the encoding... -- TODO not sure about the encoding...
checkAuthRequest :: ( HasJWTSettings env, HasAuthenticationError err, DbCmd' env err m ) checkAuthRequest :: ( HasJWTSettings env, HasAuthenticationError err, IsDBCmd env err m )
=> Username => Username
-> GargPassword -> GargPassword
-> m CheckAuth -> m CheckAuth
...@@ -114,7 +114,7 @@ checkAuthRequest couldBeEmail (GargPassword p) = do ...@@ -114,7 +114,7 @@ checkAuthRequest couldBeEmail (GargPassword p) = do
token <- makeTokenForUser nodeId userLight_id token <- makeTokenForUser nodeId userLight_id
pure $ Valid token nodeId userLight_id pure $ Valid token nodeId userLight_id
auth :: (HasJWTSettings env, HasAuthenticationError err, DbCmd' env err m) auth :: (HasJWTSettings env, HasAuthenticationError err, IsDBCmd env err m)
=> AuthRequest -> m AuthResponse => AuthRequest -> m AuthResponse
auth (AuthRequest u p) = do auth (AuthRequest u p) = do
checkAuthRequest' <- checkAuthRequest u p checkAuthRequest' <- checkAuthRequest u p
...@@ -138,7 +138,7 @@ authCheck _env (BasicAuthData login password) = pure $ ...@@ -138,7 +138,7 @@ authCheck _env (BasicAuthData login password) = pure $
maybe Indefinite Authenticated $ TODO maybe Indefinite Authenticated $ TODO
-} -}
withAccessM :: ( DbCmd' env err m ) withAccessM :: ( IsDBCmd env err m )
=> AuthenticatedUser => AuthenticatedUser
-> PathId -> PathId
-> m a -> m a
......
...@@ -10,13 +10,13 @@ import Gargantext.Core.Text.Corpus (makeSubcorpusFromQuery) ...@@ -10,13 +10,13 @@ import Gargantext.Core.Text.Corpus (makeSubcorpusFromQuery)
import Gargantext.Core.Text.Corpus.Query (RawQuery(..), parseQuery) import Gargantext.Core.Text.Corpus.Query (RawQuery(..), parseQuery)
import Gargantext.Core.Types (UserId) import Gargantext.Core.Types (UserId)
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Prelude (DbCmd') import Gargantext.Database.Prelude (IsDBCmd)
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
makeSubcorpus :: ( HasNodeStoryEnv env makeSubcorpus :: ( HasNodeStoryEnv env
, HasNLPServer env , HasNLPServer env
, DbCmd' env BackendInternalError m , IsDBCmd env BackendInternalError m
) )
=> UserId => UserId
-> MakeSubcorpusAPI (AsServerT m) -> MakeSubcorpusAPI (AsServerT m)
......
...@@ -19,7 +19,7 @@ import Control.Lens (over) ...@@ -19,7 +19,7 @@ import Control.Lens (over)
import Gargantext.Core (Lang) import Gargantext.Core (Lang)
import Gargantext.Database.Admin.Types.Hyperdata.Corpus (HyperdataCorpus, _hc_lang) import Gargantext.Database.Admin.Types.Hyperdata.Corpus (HyperdataCorpus, _hc_lang)
import Gargantext.Database.Admin.Types.Node (CorpusId) import Gargantext.Database.Admin.Types.Node (CorpusId)
import Gargantext.Database.Prelude (DbCmd') import Gargantext.Database.Prelude (IsDBCmd)
import Gargantext.Database.Query.Table.Node (getNodeWith) import Gargantext.Database.Query.Table.Node (getNodeWith)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError) import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
...@@ -29,7 +29,7 @@ import Gargantext.Utils.Jobs.Monad (MonadJobStatus) ...@@ -29,7 +29,7 @@ import Gargantext.Utils.Jobs.Monad (MonadJobStatus)
-- | Updates the 'HyperdataCorpus' with the input 'Lang'. -- | Updates the 'HyperdataCorpus' with the input 'Lang'.
addLanguageToCorpus :: (HasNodeError err, DbCmd' env err m, MonadJobStatus m) addLanguageToCorpus :: (HasNodeError err, IsDBCmd env err m, MonadJobStatus m)
=> CorpusId => CorpusId
-> Lang -> Lang
-> m () -> m ()
......
...@@ -41,7 +41,7 @@ import Gargantext.Core.Types.Query (Offset, Limit) ...@@ -41,7 +41,7 @@ import Gargantext.Core.Types.Query (Offset, Limit)
import Gargantext.Database.Action.Learn (FavOrTrash(..), moreLike) import Gargantext.Database.Action.Learn (FavOrTrash(..), moreLike)
import Gargantext.Database.Action.Search (searchCountInCorpus, searchInCorpus) import Gargantext.Database.Action.Search (searchCountInCorpus, searchInCorpus)
import Gargantext.Database.Admin.Types.Node (ContactId, CorpusId, NodeId) import Gargantext.Database.Admin.Types.Node (ContactId, CorpusId, NodeId)
import Gargantext.Database.Prelude (CmdM, DbCmd', DBCmd) import Gargantext.Database.Prelude (CmdM, IsDBCmd, DBCmd)
import Gargantext.Database.Query.Facet (FacetDoc , runViewDocuments, runCountDocuments, OrderBy(..), runViewAuthorsDoc) import Gargantext.Database.Query.Facet (FacetDoc , runViewDocuments, runCountDocuments, OrderBy(..), runViewAuthorsDoc)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError) import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Prelude import Gargantext.Prelude
...@@ -107,7 +107,7 @@ getTableHashApi cId tabType = do ...@@ -107,7 +107,7 @@ getTableHashApi cId tabType = do
HashedResponse { hash = h } <- getTableApi cId tabType Nothing Nothing Nothing Nothing Nothing HashedResponse { hash = h } <- getTableApi cId tabType Nothing Nothing Nothing Nothing Nothing
pure h pure h
searchInCorpus' :: (DbCmd' env err m, MonadLogger m) searchInCorpus' :: (IsDBCmd env err m, MonadLogger m)
=> CorpusId => CorpusId
-> Bool -> Bool
-> RawQuery -> RawQuery
......
...@@ -58,7 +58,7 @@ import Gargantext.Database.Admin.Types.Node ( NodeId(..) ) ...@@ -58,7 +58,7 @@ import Gargantext.Database.Admin.Types.Node ( NodeId(..) )
import Gargantext.Core.Text.Ngrams qualified as Ngrams import Gargantext.Core.Text.Ngrams qualified as Ngrams
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Admin.Config () import Gargantext.Database.Admin.Config ()
import Gargantext.Database.Prelude (DbCmd') import Gargantext.Database.Prelude (IsDBCmd)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError()) import Gargantext.Database.Query.Table.Node.Error (HasNodeError())
import Gargantext.Prelude hiding (to) import Gargantext.Prelude hiding (to)
import Opaleye (DefaultFromField(..), SqlJsonb, fromPGSFromField) import Opaleye (DefaultFromField(..), SqlJsonb, fromPGSFromField)
...@@ -197,7 +197,7 @@ data NodeStoryEnv = NodeStoryEnv ...@@ -197,7 +197,7 @@ data NodeStoryEnv = NodeStoryEnv
} }
deriving (Generic) deriving (Generic)
type HasNodeStory env err m = ( DbCmd' env err m type HasNodeStory env err m = ( IsDBCmd env err m
, MonadReader env m , MonadReader env m
, MonadError err m , MonadError err m
, HasNodeStoryEnv env , HasNodeStoryEnv env
......
...@@ -94,7 +94,7 @@ import Gargantext.Database.Admin.Types.Hyperdata.Contact ( HyperdataContact ) ...@@ -94,7 +94,7 @@ import Gargantext.Database.Admin.Types.Hyperdata.Contact ( HyperdataContact )
import Gargantext.Database.Admin.Types.Hyperdata.Corpus ( HyperdataAnnuaire, HyperdataCorpus(_hc_lang) ) import Gargantext.Database.Admin.Types.Hyperdata.Corpus ( HyperdataAnnuaire, HyperdataCorpus(_hc_lang) )
import Gargantext.Database.Admin.Types.Hyperdata.Document ( ToHyperdataDocument(toHyperdataDocument) ) import Gargantext.Database.Admin.Types.Hyperdata.Document ( ToHyperdataDocument(toHyperdataDocument) )
import Gargantext.Database.Admin.Types.Node hiding (DEBUG) -- (HyperdataDocument(..), NodeType(..), NodeId, UserId, ListId, CorpusId, RootId, MasterCorpusId, MasterUserId) import Gargantext.Database.Admin.Types.Node hiding (DEBUG) -- (HyperdataDocument(..), NodeType(..), NodeId, UserId, ListId, CorpusId, RootId, MasterCorpusId, MasterUserId)
import Gargantext.Database.Prelude (DbCmd', DBCmd') import Gargantext.Database.Prelude (IsDBCmd, DBCmd')
import Gargantext.Database.Query.Table.ContextNodeNgrams2 ( ContextNodeNgrams2Poly(..), insertContextNodeNgrams2 ) import Gargantext.Database.Query.Table.ContextNodeNgrams2 ( ContextNodeNgrams2Poly(..), insertContextNodeNgrams2 )
import Gargantext.Database.Query.Table.Node ( MkCorpus, insertDefaultNodeIfNotExists, getOrMkList, getNodeWith ) import Gargantext.Database.Query.Table.Node ( MkCorpus, insertDefaultNodeIfNotExists, getOrMkList, getNodeWith )
import Gargantext.Database.Query.Table.Node.Document.Add qualified as Doc (add) import Gargantext.Database.Query.Table.Node.Document.Add qualified as Doc (add)
...@@ -161,7 +161,7 @@ getDataText_Debug a l q li = do ...@@ -161,7 +161,7 @@ getDataText_Debug a l q li = do
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
flowDataText :: forall env err m. flowDataText :: forall env err m.
( DbCmd' env err m ( IsDBCmd env err m
, HasNodeStory env err m , HasNodeStory env err m
, MonadLogger m , MonadLogger m
, HasNLPServer env , HasNLPServer env
...@@ -191,7 +191,7 @@ flowDataText u (DataNew (mLen, txtC)) tt cid mfslw jobHandle = do ...@@ -191,7 +191,7 @@ flowDataText u (DataNew (mLen, txtC)) tt cid mfslw jobHandle = do
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO use proxy -- TODO use proxy
flowAnnuaire :: ( DbCmd' env err m flowAnnuaire :: ( IsDBCmd env err m
, HasNodeStory env err m , HasNodeStory env err m
, MonadLogger m , MonadLogger m
, HasNLPServer env , HasNLPServer env
...@@ -210,7 +210,7 @@ flowAnnuaire mkCorpusUser l filePath jobHandle = do ...@@ -210,7 +210,7 @@ flowAnnuaire mkCorpusUser l filePath jobHandle = do
flow (Nothing :: Maybe HyperdataAnnuaire) mkCorpusUser l Nothing (fromIntegral $ length docs, yieldMany docs) jobHandle flow (Nothing :: Maybe HyperdataAnnuaire) mkCorpusUser l Nothing (fromIntegral $ length docs, yieldMany docs) jobHandle
------------------------------------------------------------------------ ------------------------------------------------------------------------
flowCorpusFile :: ( DbCmd' env err m flowCorpusFile :: ( IsDBCmd env err m
, HasNodeStory env err m , HasNodeStory env err m
, MonadLogger m , MonadLogger m
, HasNLPServer env , HasNLPServer env
...@@ -239,7 +239,7 @@ flowCorpusFile mkCorpusUser _l la ft ff fp mfslw jobHandle = do ...@@ -239,7 +239,7 @@ flowCorpusFile mkCorpusUser _l la ft ff fp mfslw jobHandle = do
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | TODO improve the needed type to create/update a corpus -- | TODO improve the needed type to create/update a corpus
-- (For now, Either is enough) -- (For now, Either is enough)
flowCorpus :: ( DbCmd' env err m flowCorpus :: ( IsDBCmd env err m
, HasNodeStory env err m , HasNodeStory env err m
, MonadLogger m , MonadLogger m
, HasNLPServer env , HasNLPServer env
...@@ -258,7 +258,7 @@ flowCorpus = flow (Nothing :: Maybe HyperdataCorpus) ...@@ -258,7 +258,7 @@ flowCorpus = flow (Nothing :: Maybe HyperdataCorpus)
flow :: forall env err m a c. flow :: forall env err m a c.
( DbCmd' env err m ( IsDBCmd env err m
, HasNodeStory env err m , HasNodeStory env err m
, MonadLogger m , MonadLogger m
, HasNLPServer env , HasNLPServer env
...@@ -300,7 +300,7 @@ flow c mkCorpusUser la mfslw (count, docsC) jobHandle = do ...@@ -300,7 +300,7 @@ flow c mkCorpusUser la mfslw (count, docsC) jobHandle = do
-- | Given a list of corpus documents and a 'NodeId' identifying the 'CorpusId', adds -- | Given a list of corpus documents and a 'NodeId' identifying the 'CorpusId', adds
-- the given documents to the corpus. Returns the Ids of the inserted documents. -- the given documents to the corpus. Returns the Ids of the inserted documents.
addDocumentsToHyperCorpus :: ( DbCmd' env err m addDocumentsToHyperCorpus :: ( IsDBCmd env err m
, HasNodeError err , HasNodeError err
, FlowCorpus document , FlowCorpus document
, MkCorpus corpus , MkCorpus corpus
...@@ -317,7 +317,7 @@ addDocumentsToHyperCorpus ncs mb_hyper la corpusId docs = do ...@@ -317,7 +317,7 @@ addDocumentsToHyperCorpus ncs mb_hyper la corpusId docs = do
pure ids pure ids
------------------------------------------------------------------------ ------------------------------------------------------------------------
createNodes :: ( DbCmd' env err m, HasNodeError err createNodes :: ( IsDBCmd env err m, HasNodeError err
, MkCorpus c , MkCorpus c
, HasCentralExchangeNotification env , HasCentralExchangeNotification env
) )
...@@ -410,7 +410,7 @@ buildSocialList l user userCorpusId listId ctype mfslw = do ...@@ -410,7 +410,7 @@ buildSocialList l user userCorpusId listId ctype mfslw = do
pure () pure ()
insertMasterDocs :: ( DbCmd' env err m insertMasterDocs :: ( IsDBCmd env err m
, HasNodeError err , HasNodeError err
, FlowCorpus a , FlowCorpus a
, MkCorpus c , MkCorpus c
...@@ -443,7 +443,7 @@ insertMasterDocs ncs c lang hs = do ...@@ -443,7 +443,7 @@ insertMasterDocs ncs c lang hs = do
-- _cooc <- insertDefaultNode NodeListCooc lId masterUserId -- _cooc <- insertDefaultNode NodeListCooc lId masterUserId
pure $ map contextId2NodeId ids' pure $ map contextId2NodeId ids'
saveDocNgramsWith :: (DbCmd' env err m) saveDocNgramsWith :: (IsDBCmd env err m)
=> ListId => ListId
-> HashMap.HashMap ExtractedNgrams (Map NgramsType (Map NodeId (Int, TermsCount))) -> HashMap.HashMap ExtractedNgrams (Map NgramsType (Map NodeId (Int, TermsCount)))
-> m () -> m ()
......
...@@ -33,7 +33,7 @@ import Gargantext.Data.HashMap.Strict.Utils qualified as HashMap ...@@ -33,7 +33,7 @@ import Gargantext.Data.HashMap.Strict.Utils qualified as HashMap
import Gargantext.Database.Action.Flow.Types (DocumentIdWithNgrams(..), FlowInsertDB) import Gargantext.Database.Action.Flow.Types (DocumentIdWithNgrams(..), FlowInsertDB)
import Gargantext.Database.Admin.Types.Hyperdata.Document ( HyperdataDocument, hd_abstract, hd_title ) import Gargantext.Database.Admin.Types.Hyperdata.Document ( HyperdataDocument, hd_abstract, hd_title )
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude (DBCmd, DbCmd') import Gargantext.Database.Prelude (DBCmd, IsDBCmd)
import Gargantext.Database.Query.Table.ContextNodeNgrams ( ContextNodeNgramsPoly(..), insertContextNodeNgrams ) import Gargantext.Database.Query.Table.ContextNodeNgrams ( ContextNodeNgramsPoly(..), insertContextNodeNgrams )
import Gargantext.Database.Query.Table.Node.Document.Add qualified as Doc (add) import Gargantext.Database.Query.Table.Node.Document.Add qualified as Doc (add)
import Gargantext.Database.Query.Table.Node.Document.Insert (ReturnId, addUniqId, insertDb, reId, reInserted, reUniqId) import Gargantext.Database.Query.Table.Node.Document.Insert (ReturnId, addUniqId, insertDb, reId, reInserted, reUniqId)
...@@ -119,7 +119,7 @@ mapNodeIdNgrams = HashMap.unionsWith (DM.unionWith (DM.unionWith addTuples)) . f ...@@ -119,7 +119,7 @@ mapNodeIdNgrams = HashMap.unionsWith (DM.unionWith (DM.unionWith addTuples)) . f
-- TODO Type NodeDocumentUnicised -- TODO Type NodeDocumentUnicised
insertDocs :: ( DbCmd' env err m insertDocs :: ( IsDBCmd env err m
-- , FlowCorpus a -- , FlowCorpus a
, FlowInsertDB a , FlowInsertDB a
, HasNodeError err , HasNodeError err
......
...@@ -97,13 +97,13 @@ type Cmd'' env err a = forall m. CmdM'' env err m => m a ...@@ -97,13 +97,13 @@ type Cmd'' env err a = forall m. CmdM'' env err m => m a
type Cmd' env err a = forall m. IsCmd env err m => m a type Cmd' env err a = forall m. IsCmd env err m => m a
type Cmd err a = forall m env. CmdM env err m => m a type Cmd err a = forall m env. CmdM env err m => m a
type CmdR err a = forall m env. CmdRandom env err m => m a type CmdR err a = forall m env. CmdRandom env err m => m a
type DBCmd' env err a = forall m. DbCmd' env err m => m a type DBCmd' env err a = forall m. IsDBCmd env err m => m a
type DBCmd err a = forall m env. DbCmd' env err m => m a type DBCmd err a = forall m env. IsDBCmd env err m => m a
-- | Only the /minimum/ amount of class constraints required -- | Only the /minimum/ amount of class constraints required
-- to use the Gargantext Database. It's important, to ease testability, -- to use the Gargantext Database. It's important, to ease testability,
-- that these constraints stays as few as possible. -- that these constraints stays as few as possible.
type DbCmd' env err m = ( type IsDBCmd env err m = (
IsCmd env err m IsCmd env err m
, IsDBEnv env , IsDBEnv env
) )
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment