Commit cb7acfd6 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Split NodeAPIEndpoint

This commit splits the old `NodeAPIEndpoint` type into three;

* `NodeAPIEndpoint`, which will also contain the freeze endpoint;
* `AnnuaireAPIEndpoint`, which is the plain old node API without extra
  features;
* `CorpusAPIEndpoint`, which will also contain the publishin endpoint.

This split ensures that we don't add endpoints which do not belong to
all three categories, like before.
parent a4e5b84d
...@@ -200,22 +200,22 @@ moveNode _u n p = update (Move n p) ...@@ -200,22 +200,22 @@ moveNode _u n p = update (Move n p)
------------------------------------------------------------- -------------------------------------------------------------
annuaireNodeAPI :: AuthenticatedUser annuaireNodeAPI :: AuthenticatedUser
-> Named.NodeAPIEndpoint HyperdataAnnuaire (AsServerT (GargM Env BackendInternalError)) -> Named.AnnuaireAPIEndpoint (AsServerT (GargM Env BackendInternalError))
annuaireNodeAPI authenticatedUser = Named.NodeAPIEndpoint $ \targetNode -> annuaireNodeAPI authenticatedUser = Named.AnnuaireAPIEndpoint $ \targetNode ->
withNamedAccess authenticatedUser (PathNode targetNode) (concreteAPI targetNode) withNamedAccess authenticatedUser (PathNode targetNode) (concreteAPI targetNode)
where where
concreteAPI = genericNodeAPI' (Proxy :: Proxy HyperdataAnnuaire) authenticatedUser concreteAPI = genericNodeAPI' (Proxy :: Proxy HyperdataAnnuaire) authenticatedUser
corpusNodeAPI :: AuthenticatedUser corpusNodeAPI :: AuthenticatedUser
-> Named.NodeAPIEndpoint HyperdataCorpus (AsServerT (GargM Env BackendInternalError)) -> Named.CorpusAPIEndpoint (AsServerT (GargM Env BackendInternalError))
corpusNodeAPI authenticatedUser = Named.NodeAPIEndpoint $ \targetNode -> corpusNodeAPI authenticatedUser = Named.CorpusAPIEndpoint $ \targetNode ->
withNamedAccess authenticatedUser (PathNode targetNode) (concreteAPI targetNode) withNamedAccess authenticatedUser (PathNode targetNode) (concreteAPI targetNode)
where where
concreteAPI = genericNodeAPI' (Proxy :: Proxy HyperdataCorpus) authenticatedUser concreteAPI = genericNodeAPI' (Proxy :: Proxy HyperdataCorpus) authenticatedUser
------------------------------------------------------------------------ ------------------------------------------------------------------------
nodeAPI :: AuthenticatedUser nodeAPI :: AuthenticatedUser
-> Named.NodeAPIEndpoint HyperdataAny (AsServerT (GargM Env BackendInternalError)) -> Named.NodeAPIEndpoint (AsServerT (GargM Env BackendInternalError))
nodeAPI authenticatedUser = Named.NodeAPIEndpoint $ \targetNode -> nodeAPI authenticatedUser = Named.NodeAPIEndpoint $ \targetNode ->
withNamedAccess authenticatedUser (PathNode targetNode) (concreteAPI targetNode) withNamedAccess authenticatedUser (PathNode targetNode) (concreteAPI targetNode)
where where
......
...@@ -11,14 +11,13 @@ module Gargantext.API.Routes.Named.Private ( ...@@ -11,14 +11,13 @@ module Gargantext.API.Routes.Named.Private (
, GargAdminAPI(..) , GargAdminAPI(..)
, NodeAPIEndpoint(..) , NodeAPIEndpoint(..)
, MembersAPI(..) , MembersAPI(..)
, IsGenericNodeRoute(..) , AnnuaireAPIEndpoint(..)
, CorpusAPIEndpoint(..)
) where ) where
import Data.Kind
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
import GHC.TypeLits
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Auth.PolicyCheck import Gargantext.API.Auth.PolicyCheck
import Gargantext.API.Routes.Named.Contact import Gargantext.API.Routes.Named.Contact
...@@ -49,11 +48,11 @@ newtype GargPrivateAPI mode = GargPrivateAPI ...@@ -49,11 +48,11 @@ newtype GargPrivateAPI mode = GargPrivateAPI
data GargPrivateAPI' mode = GargPrivateAPI' data GargPrivateAPI' mode = GargPrivateAPI'
{ gargAdminAPI :: mode :- NamedRoutes GargAdminAPI { gargAdminAPI :: mode :- NamedRoutes GargAdminAPI
, nodeEp :: mode :- NamedRoutes (NodeAPIEndpoint HyperdataAny) , nodeEp :: mode :- NamedRoutes NodeAPIEndpoint
, contextEp :: mode :- "context" :> Summary "Context endpoint" , contextEp :: mode :- "context" :> Summary "Context endpoint"
:> Capture "node_id" ContextId :> Capture "node_id" ContextId
:> NamedRoutes (ContextAPI HyperdataAny) :> NamedRoutes (ContextAPI HyperdataAny)
, corpusNodeAPI :: mode :- NamedRoutes (NodeAPIEndpoint HyperdataCorpus) , corpusNodeAPI :: mode :- NamedRoutes CorpusAPIEndpoint
, corpusNodeNodeAPI :: mode :- "corpus" :> Summary "Corpus endpoint" , corpusNodeNodeAPI :: mode :- "corpus" :> Summary "Corpus endpoint"
:> Capture "node1_id" NodeId :> Capture "node1_id" NodeId
:> "document" :> "document"
...@@ -61,7 +60,7 @@ data GargPrivateAPI' mode = GargPrivateAPI' ...@@ -61,7 +60,7 @@ data GargPrivateAPI' mode = GargPrivateAPI'
:> NamedRoutes (NodeNodeAPI HyperdataAny) :> NamedRoutes (NodeNodeAPI HyperdataAny)
, corpusExportAPI :: mode :- "corpus" :> Capture "node_id" CorpusId , corpusExportAPI :: mode :- "corpus" :> Capture "node_id" CorpusId
:> NamedRoutes CorpusExportAPI :> NamedRoutes CorpusExportAPI
, annuaireEp :: mode :- NamedRoutes (NodeAPIEndpoint HyperdataAnnuaire) , annuaireEp :: mode :- NamedRoutes AnnuaireAPIEndpoint
, contactAPI :: mode :- "annuaire" :> Summary "Contact endpoint" , contactAPI :: mode :- "annuaire" :> Summary "Contact endpoint"
:> Capture "annuaire_id" NodeId :> Capture "annuaire_id" NodeId
:> NamedRoutes ContactAPI :> NamedRoutes ContactAPI
...@@ -102,31 +101,29 @@ data GargAdminAPI mode = GargAdminAPI ...@@ -102,31 +101,29 @@ data GargAdminAPI mode = GargAdminAPI
:> NamedRoutes NodesAPI :> NamedRoutes NodesAPI
} deriving Generic } deriving Generic
class IsGenericNodeRoute a where -- | The 'Node' API, unlike the ones for annuaire and corpus,
type family TyToSubPath (a :: Type) :: Symbol -- have other endpoints which should not be shared in the hierarchy,
type family TyToCapture (a :: Type) :: Symbol -- like the /freeze/ one. Similarly, a 'Corpus' API will have a
type family TyToSummary (a :: Type) :: Type -- '/publish' endpoint that doesn't generalise to everything.
data NodeAPIEndpoint mode = NodeAPIEndpoint
instance IsGenericNodeRoute HyperdataAny where { nodeEndpointAPI :: mode :- "node"
type instance TyToSubPath HyperdataAny = "node" :> Summary "Node endpoint"
type instance TyToCapture HyperdataAny = "node_id" :> Capture "node_id" NodeId
type instance TyToSummary HyperdataAny = Summary "Node endpoint" :> NamedRoutes (NodeAPI HyperdataAny)
} deriving Generic
instance IsGenericNodeRoute HyperdataCorpus where
type instance TyToSubPath HyperdataCorpus = "corpus" newtype AnnuaireAPIEndpoint mode = AnnuaireAPIEndpoint
type instance TyToCapture HyperdataCorpus = "corpus_id" { annuaireEndpointAPI :: mode :- "annuaire"
type instance TyToSummary HyperdataCorpus = Summary "Corpus endpoint" :> Summary "Annuaire endpoint"
:> Capture "annuaire_id" NodeId
instance IsGenericNodeRoute HyperdataAnnuaire where :> NamedRoutes (NodeAPI HyperdataAnnuaire)
type instance TyToSubPath HyperdataAnnuaire = "annuaire" } deriving Generic
type instance TyToCapture HyperdataAnnuaire = "annuaire_id"
type instance TyToSummary HyperdataAnnuaire = Summary "Annuaire endpoint" newtype CorpusAPIEndpoint mode = CorpusAPIEndpoint
{ corpusEndpointAPI :: mode :- "corpus"
newtype NodeAPIEndpoint a mode = NodeAPIEndpoint :> Summary "Corpus endpoint"
{ nodeEndpointAPI :: mode :- TyToSubPath a :> Capture "corpus_id" NodeId
:> TyToSummary a :> NamedRoutes (NodeAPI HyperdataCorpus)
:> Capture (TyToCapture a) NodeId
:> NamedRoutes (NodeAPI a)
} deriving Generic } deriving Generic
newtype MembersAPI mode = MembersAPI newtype MembersAPI mode = MembersAPI
......
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