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

Protect the TreeAPI

parent 4e054277
...@@ -31,6 +31,7 @@ And you have the main viz ...@@ -31,6 +31,7 @@ And you have the main viz
module Gargantext.API.Admin.Auth module Gargantext.API.Admin.Auth
( auth ( auth
, withPolicy , withPolicy
, withPolicyT
, forgotPassword , forgotPassword
, forgotPasswordAsync , forgotPasswordAsync
, withAccess , withAccess
...@@ -177,6 +178,22 @@ withPolicy ur checks m mgr = case mgr of ...@@ -177,6 +178,22 @@ withPolicy ur checks m mgr = case mgr of
Allow -> m Allow -> m
Deny err -> throwError $ GargServerError $ err Deny err -> throwError $ GargServerError $ err
withPolicyT :: forall env m api. (
GargServerC env GargError m
, HasServer api '[]
)
=> Proxy api
-> Proxy m
-> AuthenticatedUser
-> BoolExpr AccessCheck
-> ServerT api m
-> AccessPolicyManager
-> ServerT api m
withPolicyT p _ ur checks m0 mgr = hoistServer p f m0
where
f :: forall a. m a -> m a
f m = withPolicy ur checks m mgr
{- | Collaborative Schema {- | Collaborative Schema
User at his root can create Teams Folder User at his root can create Teams Folder
User can create Team in Teams Folder. User can create Team in Teams Folder.
......
...@@ -14,6 +14,7 @@ Portability : POSIX ...@@ -14,6 +14,7 @@ Portability : POSIX
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeApplications #-}
module Gargantext.API.Routes module Gargantext.API.Routes
where where
...@@ -27,7 +28,7 @@ import Servant.Auth as SA ...@@ -27,7 +28,7 @@ import Servant.Auth as SA
import Servant.Auth.Swagger () import Servant.Auth.Swagger ()
import Servant.Swagger.UI import Servant.Swagger.UI
import Gargantext.API.Admin.Auth (ForgotPasswordAPI, ForgotPasswordAsyncAPI, withAccess) import Gargantext.API.Admin.Auth (ForgotPasswordAPI, ForgotPasswordAsyncAPI, withAccess, withPolicyT)
import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..)) import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..))
import Gargantext.API.Admin.EnvTypes (Env, GargJob(..)) import Gargantext.API.Admin.EnvTypes (Env, GargJob(..))
import Gargantext.API.Admin.FrontEnd (FrontEndAPI) import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
...@@ -55,6 +56,7 @@ import qualified Gargantext.API.Node.Corpus.New as New ...@@ -55,6 +56,7 @@ import qualified Gargantext.API.Node.Corpus.New as New
import qualified Gargantext.API.Node.Document.Export as DocumentExport import qualified Gargantext.API.Node.Document.Export as DocumentExport
import qualified Gargantext.API.Node.Document.Export.Types as DocumentExport import qualified Gargantext.API.Node.Document.Export.Types as DocumentExport
import qualified Gargantext.API.Public as Public import qualified Gargantext.API.Public as Public
import Gargantext.API.Auth.PolicyCheck
type GargAPI = MkGargAPI (GargAPIVersion GargAPI') type GargAPI = MkGargAPI (GargAPIVersion GargAPI')
...@@ -170,7 +172,7 @@ type GargPrivateAPI' = ...@@ -170,7 +172,7 @@ type GargPrivateAPI' =
-- Tree endpoint -- Tree endpoint
:<|> "tree" :> Summary "Tree endpoint" :<|> "tree" :> Summary "Tree endpoint"
:> Capture "tree_id" NodeId :> Capture "tree_id" NodeId
:> TreeAPI :> PolicyChecked TreeAPI
-- Flat tree endpoint -- Flat tree endpoint
:<|> "treeflat" :> Summary "Flat tree endpoint" :<|> "treeflat" :> Summary "Flat tree endpoint"
:> Capture "tree_id" NodeId :> Capture "tree_id" NodeId
...@@ -262,8 +264,7 @@ serverPrivateGargAPI' authenticatedUser@(AuthenticatedUser (NodeId uid)) ...@@ -262,8 +264,7 @@ serverPrivateGargAPI' authenticatedUser@(AuthenticatedUser (NodeId uid))
:<|> withAccess (Proxy :: Proxy GraphAPI) Proxy authenticatedUser :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy authenticatedUser
<$> PathNode <*> graphAPI uid -- TODO: mock <$> PathNode <*> graphAPI uid -- TODO: mock
:<|> withAccess (Proxy :: Proxy TreeAPI) Proxy authenticatedUser :<|> (\nodeId -> withPolicyT (Proxy @TreeAPI) Proxy authenticatedUser (nodeChecks nodeId) (treeAPI nodeId))
<$> PathNode <*> treeAPI
:<|> withAccess (Proxy :: Proxy TreeFlatAPI) Proxy authenticatedUser :<|> withAccess (Proxy :: Proxy TreeFlatAPI) Proxy authenticatedUser
<$> PathNode <*> treeFlatAPI <$> PathNode <*> treeFlatAPI
......
...@@ -143,4 +143,4 @@ tests = sequential $ aroundAll withTestDBAndPort $ do ...@@ -143,4 +143,4 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
withApplication app $ do withApplication app $ do
withValidLogin port "alice" (GargPassword "alice") $ \token -> do withValidLogin port "alice" (GargPassword "alice") $ \token -> do
protected token "GET" (mkUrl port "/tree/1") "" protected token "GET" (mkUrl port "/tree/1") ""
`shouldRespondWith` [json| {} |] `shouldRespondWith` 403
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