Commit f7a8e3d5 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API] Annuaire / contact done

parent a53c3ad2
Pipeline #976 failed with stage
...@@ -55,7 +55,6 @@ instance ToJSON a => MimeRender HTML a where ...@@ -55,7 +55,6 @@ instance ToJSON a => MimeRender HTML a where
mimeRender _ = encode mimeRender _ = encode
------------------------------------------------------------------------ ------------------------------------------------------------------------
get :: RepoCmdM env err m => get :: RepoCmdM env err m =>
ListId -> m (Headers '[Header "Content-Disposition" Text] NgramsList) ListId -> m (Headers '[Header "Content-Disposition" Text] NgramsList)
get lId = do get lId = do
...@@ -74,7 +73,6 @@ get' lId = fromList ...@@ -74,7 +73,6 @@ get' lId = fromList
<$> mapM (getNgramsTableMap lId) ngramsTypes <$> mapM (getNgramsTableMap lId) ngramsTypes
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO : purge list -- TODO : purge list
post :: FlowCmdM env err m post :: FlowCmdM env err m
=> ListId => ListId
...@@ -88,7 +86,6 @@ post l m = do ...@@ -88,7 +86,6 @@ post l m = do
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------ ------------------------------------------------------------------------
type PostAPI = Summary "Update List" type PostAPI = Summary "Update List"
:> "add" :> "add"
:> "form" :> "form"
......
...@@ -9,10 +9,17 @@ Portability : POSIX ...@@ -9,10 +9,17 @@ Portability : POSIX
-} -}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Gargantext.API.Node.Contact module Gargantext.API.Node.Contact
where where
...@@ -24,13 +31,14 @@ import Data.Text (Text) ...@@ -24,13 +31,14 @@ import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..)) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..))
import Gargantext.API.Admin.Settings (HasSettings) import Gargantext.API.Admin.Settings (HasSettings)
import Gargantext.API.Node
import Gargantext.API.Node.Corpus.New (AsyncJobs) import Gargantext.API.Node.Corpus.New (AsyncJobs)
import Gargantext.API.Prelude (GargServer, simuLogs) import Gargantext.API.Prelude (GargServer, simuLogs)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Action.Flow (flow) import Gargantext.Database.Action.Flow (flow)
import Gargantext.Database.Action.Flow.Types (FlowCmdM) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataAnnuaire(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataAnnuaire(..), HyperdataContact)
import Gargantext.Database.Admin.Types.Hyperdata.Contact (hyperdataContact) import Gargantext.Database.Admin.Types.Hyperdata.Contact (hyperdataContact)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Prelude (($), liftBase, (.), printDebug, pure) import Gargantext.Prelude (($), liftBase, (.), printDebug, pure)
...@@ -41,9 +49,17 @@ import Test.QuickCheck (elements) ...@@ -41,9 +49,17 @@ import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
------------------------------------------------------------------------ ------------------------------------------------------------------------
type API = Summary " Add Contact to Annuaire" type API = "contact" :> Summary "Contact endpoint"
:> AsyncJobs JobLog '[JSON] AddContactParams JobLog :> API_Async
:<|> Capture "contact_id" NodeId
:> NodeNodeAPI HyperdataContact
api :: UserId -> CorpusId -> GargServer API
api uid cid = (api_async (RootId (NodeId uid)) cid)
:<|> (nodeNodeAPI (Proxy :: Proxy HyperdataContact) uid cid)
type API_Async = AsyncJobs JobLog '[JSON] AddContactParams JobLog
------------------------------------------------------------------------ ------------------------------------------------------------------------
data AddContactParams = AddContactParams { firstname :: !Text, lastname :: !Text } data AddContactParams = AddContactParams { firstname :: !Text, lastname :: !Text }
| AddContactParamsAdvanced { firstname :: !Text | AddContactParamsAdvanced { firstname :: !Text
...@@ -53,8 +69,8 @@ data AddContactParams = AddContactParams { firstname :: !Text, lastname ...@@ -53,8 +69,8 @@ data AddContactParams = AddContactParams { firstname :: !Text, lastname
deriving (Generic) deriving (Generic)
---------------------------------------------------------------------- ----------------------------------------------------------------------
api :: User -> NodeId -> GargServer API api_async :: User -> NodeId -> GargServer API_Async
api u nId = api_async u nId =
serveJobsAPI $ serveJobsAPI $
JobFunction (\p log -> JobFunction (\p log ->
let let
......
...@@ -7,7 +7,6 @@ Maintainer : team@gargantext.org ...@@ -7,7 +7,6 @@ Maintainer : team@gargantext.org
Stability : experimental Stability : experimental
Portability : POSIX Portability : POSIX
-} -}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
...@@ -51,7 +50,7 @@ import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire ...@@ -51,7 +50,7 @@ import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
import qualified Gargantext.API.Node.Corpus.Export as Export import qualified Gargantext.API.Node.Corpus.Export as Export
import qualified Gargantext.API.Node.Corpus.New as New import qualified Gargantext.API.Node.Corpus.New as New
import qualified Gargantext.API.Public as Public import qualified Gargantext.API.Public as Public
import qualified Gargantext.API.Node.Contact as Contact
type GargAPI = "api" :> Summary "API " :> GargAPIVersion type GargAPI = "api" :> Summary "API " :> GargAPIVersion
-- | TODO :<|> Summary "Latest API" :> GargAPI' -- | TODO :<|> Summary "Latest API" :> GargAPI'
...@@ -116,9 +115,7 @@ type GargPrivateAPI' = ...@@ -116,9 +115,7 @@ type GargPrivateAPI' =
:<|> "annuaire" :> Summary "Contact endpoint" :<|> "annuaire" :> Summary "Contact endpoint"
:> Capture "annuaire_id" NodeId :> Capture "annuaire_id" NodeId
:> "contact" :> Contact.API
:> Capture "contact_id" NodeId
:> NodeNodeAPI HyperdataContact
-- Document endpoint -- Document endpoint
:<|> "document" :> Summary "Document endpoint" :<|> "document" :> Summary "Document endpoint"
...@@ -208,7 +205,7 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid)) ...@@ -208,7 +205,7 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
:<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
:<|> Export.getCorpus -- uid :<|> Export.getCorpus -- uid
:<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
:<|> nodeNodeAPI (Proxy :: Proxy HyperdataContact) uid :<|> Contact.api uid
:<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
<$> PathNode <*> apiNgramsTableDoc <$> PathNode <*> apiNgramsTableDoc
...@@ -246,7 +243,6 @@ waitAPI n = do ...@@ -246,7 +243,6 @@ waitAPI n = do
pure $ "Waited: " <> (cs $ show n) pure $ "Waited: " <> (cs $ show n)
---------------------------------------- ----------------------------------------
addCorpusWithQuery :: User -> GargServer New.AddWithQuery addCorpusWithQuery :: User -> GargServer New.AddWithQuery
addCorpusWithQuery user cid = addCorpusWithQuery user cid =
serveJobsAPI $ serveJobsAPI $
......
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