Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type RequireBiscuit = AuthProtect "biscuit"
- data CheckedBiscuit = CheckedBiscuit PublicKey Biscuit
- authHandler :: PublicKey -> AuthHandler Request CheckedBiscuit
- genBiscuitCtx :: PublicKey -> Context '[AuthHandler Request CheckedBiscuit]
- checkBiscuit :: (MonadIO m, MonadError ServerError m) => CheckedBiscuit -> Verifier -> m a -> m a
- checkBiscuitM :: (MonadIO m, MonadError ServerError m) => CheckedBiscuit -> m Verifier -> m a -> m a
- data WithVerifier m a = WithVerifier {}
- handleBiscuit :: (MonadIO m, MonadError ServerError m) => CheckedBiscuit -> WithVerifier m a -> m a
- withVerifier :: Applicative m => Verifier -> ReaderT Biscuit m a -> WithVerifier m a
- withVerifier_ :: Monad m => Verifier -> m a -> WithVerifier m a
- withVerifierM :: m Verifier -> ReaderT Biscuit m a -> WithVerifier m a
- withVerifierM_ :: Monad m => m Verifier -> m a -> WithVerifier m a
- noVerifier :: Applicative m => ReaderT Biscuit m a -> WithVerifier m a
- noVerifier_ :: Monad m => m a -> WithVerifier m a
- withFallbackVerifier :: Functor m => Verifier -> WithVerifier m a -> WithVerifier m a
- withPriorityVerifier :: Functor m => Verifier -> WithVerifier m a -> WithVerifier m a
- withFallbackVerifierM :: Applicative m => m Verifier -> WithVerifier m a -> WithVerifier m a
- withPriorityVerifierM :: Applicative m => m Verifier -> WithVerifier m a -> WithVerifier m a
Protecting a servant API with biscuits
Biscuit are bearer tokens that can be used to protect API endpoints. This package provides utilities to protect servant endpoints with such tokens.
The token will be extracted from the Authorization
header, and must
be base64-encoded, prefixed with the Bearer
string.
Annotating servant API types
To protect and endpoint (or a whole API tree), you can use RequireBiscuit
like so:
type API = RequireBiscuit :> ProtectedAPI type ProtectedAPI = "endpoint1" :> Get '[JSON] Int :<|> "endpoint2" :> Capture "int" Int :> Get '[JSON] Int :<|> "endpoint3" :> Get '[JSON] Int app :: Application app = serveWithContext (Proxy :: Proxy API) (genBiscuitCtx publicKey) -- servant needs access to the biscuit /public/ -- key to be able to check biscuit signatures. -- The public key can be read from the environment -- and parsed using 'parsePublicKeyHex' for instance. server server :: Server API -- CheckedBiscuit -> Server ProtectedAPI server biscuit = … -- this will be detailed later
This will instruct servant to extract the biscuit from the requests and check its signature. *It will not*, however, run any datalog check (as the checks typically depend on the request contents).
type RequireBiscuit = AuthProtect "biscuit" Source #
data CheckedBiscuit Source #
A biscuit which signature has already been verified.
Since the biscuit lib checks the signature while verifying the datalog
part, the public key is needed. CheckedBiscuit
carries the public key
used for verifying the signature so that the datalog verification part
can use it.
authHandler :: PublicKey -> AuthHandler Request CheckedBiscuit Source #
Servant authorization handler. This extracts the biscuit from the request,
checks its signature (but not the datalog part) and returns a CheckedBiscuit
upon success.
genBiscuitCtx :: PublicKey -> Context '[AuthHandler Request CheckedBiscuit] Source #
Helper function generating a servant context containing the authorization handler.
Supplying a verifier for a single endpoint
The corresponding Server API
value will be a CheckedBiscuit -> Server ProtectedAPI
.
The next step is to provide a Verifier
so that the biscuit datalog can be
verified. For that, you can use checkBiscuit
(or checkBiscuitM
).
server :: Server API server biscuit = h1 biscuit :<|> h2 biscuit :<|> h3 biscuit h1 :: CheckedBiscuit -> Handler Int h1 biscuit = checkBiscuit biscuit [verifier|allow if right(#authority,#one);|] -- ^ only allow biscuits granting access to the endpoint tagged `#one` (pure 1) h2 :: CheckedBiscuit -> Int -> Handler Int h2 biscuit value = checkBiscuit biscuit [verifier|allow if right(#authority,#two, ${value});|] -- ^ only allow biscuits granting access to the endpoint tagged `#two` -- AND for the provided int value. (pure 2) h3 :: CheckedBiscuit -> Handler Int h3 biscuit = checkBiscuit biscuit [verifier|deny if true;|] -- ^ reject every biscuit (pure 3)
checkBiscuit :: (MonadIO m, MonadError ServerError m) => CheckedBiscuit -> Verifier -> m a -> m a Source #
Given a CheckedBiscuit
(provided by the servant authorization mechanism),
verify its validity (with the provided Verifier
).
If you need to perform effects in the verification phase (eg to get the current time,
or if you need to issue a DB query to get context), you can use checkBiscuitM
instead.
If you don't want to pass the biscuit manually to all the endpoints or want to
blanket apply verifiers on whole API trees, you can consider using withVerifier
(on endpoints), withFallbackVerifier
and withPriorityVerifier
(on API sub-trees)
and handleBiscuit
(on the whole API).
checkBiscuitM :: (MonadIO m, MonadError ServerError m) => CheckedBiscuit -> m Verifier -> m a -> m a Source #
Given a CheckedBiscuit
(provided by the servant authorization mechanism),
verify its validity (with the provided Verifier
, which can be effectful).
If you don't need to run any effects in the verifying phase, you can use checkBiscuit
instead.
If you don't want to pass the biscuit manually to all the endpoints or want to blanket apply
verifiers on whole API trees, you can consider using withVerifier
(on endpoints),
withFallbackVerifier
and withPriorityVerifier
(on API sub-trees) and handleBiscuit
(on the whole API).
Decorate regular handlers with composable verifiers
checkBiscuit
allows you to describe validation rules endpoint by endpoint. Since Verifier
has a Monoid
instance, you can avoid duplication by extracting common rules, but that still
requires some boilerplate (and it won't prevent you from forgetting to add them on some endpoints).
'biscuit-servant' provides a way to apply verifiers on whole API trees, in a composable way, thanks
to hoistServer
:
-- 'withVerifier' wraps a 'Handler' and lets you attach a verifier handler1 :: WithVerifier Handler Int handler1 = withVerifier [verifier|allow if right(#authority, #one);|] (pure 1) handler2 :: Int -> WithVerifier Handler Int handler2 value = withVerifier [verifier|allow if right(#authority, #two, ${value});|] (pure 2) handler3 :: WithVerifier Handler Int handler3 = withVerifier [verifier|allow if right(#authority, #three);|] (pure 3) server :: Server API server = let nowFact = do now <- liftIO getCurrentTime pure [verifier|now(#ambient, ${now});|] handleAuth :: WithVerifier Handler x -> Handler x handleAuth = handleBiscuit b -- ^ this runs datalog checks on the biscuit, based on verifiers attached to -- the handlers . withPriorityVerifierM nowFact -- ^ this provides the current time to the verification context so that biscuits with -- a TTL can verify if they are still valid. -- Verifiers can be provided in a monadic context (it just has to be the same as -- the handlers themselves, so here it's 'Handler'). . withPriorityVerifier [verifier|allow if right(#authority, #admin);|] -- ^ this policy will be tried /before/ any endpoint policy, so `endpoint3` will be -- reachable with an admin biscuit . withFallbackVerifier [verifier|allow if right(#authority, #anon);|] -- ^ this policy will be tried /after/ the endpoints policies, so `endpoint3` will -- *not* be reachable with an anon macaroon. handlers = handler1 :<|> handler2 :<|> handler3 in hoistServer @ProtectedAPI Proxy handleAuth handlers -- ^ this will apply `handleAuth` on all 'ProtectedAPI' endpoints.
| Type used to protect and API tree, requiring a biscuit token
to be attached to requests. The associated auth handler will
only check the biscuit signature. Checking the datalog part
usually requires endpoint-specific information, and has to
be performed separately with either checkBiscuit
(for simple
use-cases) or handleBiscuit
(for more complex use-cases).
data WithVerifier m a Source #
handleBiscuit :: (MonadIO m, MonadError ServerError m) => CheckedBiscuit -> WithVerifier m a -> m a Source #
Given a handler wrapped in a WithVerifier
, use the attached Verifier
to
verify the provided biscuit and return an error as needed.
For simpler use cases, consider using checkBiscuit
instead, which works on regular
servant handlers.
withVerifier :: Applicative m => Verifier -> ReaderT Biscuit m a -> WithVerifier m a Source #
Wraps an existing handler block, attaching a Verifier
. The handler has
to be a ReaderT
Biscuit
to be able to access the token.
If you don't need to access the token from the handler block, you can use
withVerifier_
instead.
If you need to perform effects to compute the verifier (eg. to get the current date,
or to query a database), you can use withVerifierM
instead.
withVerifier_ :: Monad m => Verifier -> m a -> WithVerifier m a Source #
Wraps an existing handler block, attaching a Verifier
. The handler can be
any monad, but won't be able to access the Biscuit
.
If you want to read the biscuit token from the handler block, you can use withVerifier
instead.
If you need to perform effects to compute the verifier (eg. to get the current date,
or to query a database), you can use withVerifierM_
instead.
withVerifierM :: m Verifier -> ReaderT Biscuit m a -> WithVerifier m a Source #
Wraps an existing handler block, attaching a Verifier
. The handler has
to be a ReaderT
Biscuit
to be able to access the token.
If you don't need to access the token from the handler block, you can use
withVerifier_
instead.
Here, the Verifier
can be computed effectfully. If you don't need to perform effects,
you can use withVerifier
instead.
withVerifierM_ :: Monad m => m Verifier -> m a -> WithVerifier m a Source #
Wraps an existing handler block, attaching a Verifier
. The handler can be
any monad, but won't be able to access the Biscuit
.
If you want to read the biscuit token from the handler block, you can use withVerifier
instead.
Here, the Verifier
can be computed effectfully. If you don't need to perform effects,
you can use withVerifier_
instead.
noVerifier :: Applicative m => ReaderT Biscuit m a -> WithVerifier m a Source #
Wraps an existing handler block, attaching an empty Verifier
. The handler has
to be a ReaderT
Biscuit
to be able to access the token. If you don't need
to access the token from the handler block, you can use noVerifier_
instead.
This function can be used together with withFallbackVerifier
or withPriorityVerifier
to apply policies on several handlers at the same time (with hoistServer
for instance).
noVerifier_ :: Monad m => m a -> WithVerifier m a Source #
Wraps an existing handler block, attaching an empty Verifier
. The handler can be
any monad, but won't be able to access the Biscuit
. If you want to read the
biscuit token from the handler block, you can use noVerifier
instead.
This function can be used together with withFallbackVerifier
or withPriorityVerifier
to apply policies on several handlers at the same time (with hoistServer
for instance).
withFallbackVerifier :: Functor m => Verifier -> WithVerifier m a -> WithVerifier m a Source #
Combines the provided Verifier
to the Verifier
attached to the wrapped
handler. facts, rules and checks are unordered, but policies have a
specific order. withFallbackVerifier
puts the provided policies at the bottom
of the list (ie as fallback policies).
If you want the policies to be tried before the ones of the wrapped handler, you
can use withPriorityVerifier
.
If you need to perform effects to compute the verifier (eg. to get the current date,
or to query a database), you can use withFallbackVerifierM
instead.
withPriorityVerifier :: Functor m => Verifier -> WithVerifier m a -> WithVerifier m a Source #
Combines the provided Verifier
to the Verifier
attached to the wrapped
handler. facts, rules and checks are unordered, but policies have a
specific order. withFallbackVerifier
puts the provided policies at the top
of the list (ie as priority policies).
If you want the policies to be tried after the ones of the wrapped handler, you
can use withFallbackVerifier
.
If you need to perform effects to compute the verifier (eg. to get the current date,
or to query a database), you can use withPriorityVerifierM
instead.
withFallbackVerifierM :: Applicative m => m Verifier -> WithVerifier m a -> WithVerifier m a Source #
Combines the provided Verifier
to the Verifier
attached to the wrapped
handler. facts, rules and checks are unordered, but policies have a
specific order. withFallbackVerifier
puts the provided policies at the bottom
of the list (ie as fallback policies).
If you want the policies to be tried before the ones of the wrapped handler, you
can use withPriorityVerifier
.
Here, the Verifier
can be computed effectfully. If you don't need to perform effects,
you can use withFallbackVerifier
instead.
withPriorityVerifierM :: Applicative m => m Verifier -> WithVerifier m a -> WithVerifier m a Source #
Combines the provided Verifier
to the Verifier
attached to the wrapped
handler. facts, rules and checks are unordered, but policies have a
specific order. withFallbackVerifier
puts the provided policies at the top
of the list (ie as priority policies).
If you want the policies to be tried after the ones of the wrapped handler, you
can use withFallbackVerifier
.
Here, the Verifier
can be computed effectfully. If you don't need to perform effects,
you can use withFallbackVerifier
instead.