biscuit-servant-0.2.1.0: Servant support for the Biscuit security token
Safe HaskellNone
LanguageHaskell2010

Auth.Biscuit.Servant

Synopsis

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 :: PublicKey -> Application
app 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.
  serveWithContext
    (Proxy :: Proxy API)
    (genBiscuitCtx publicKey)
    server

-- server :: Biscuit OpenOrSealed Verified -> Server ProtectedAPI
server :: Server API
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 #

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).

authHandler :: PublicKey -> AuthHandler Request (Biscuit OpenOrSealed Verified) Source #

Servant authorization handler. This extracts the biscuit from the request, checks its signature (but not the datalog part) and returns a Biscuit upon success.

genBiscuitCtx :: PublicKey -> Context '[AuthHandler Request (Biscuit OpenOrSealed Verified)] Source #

Helper function generating a servant context containing the authorization handler.

Supplying a authorizer for a single endpoint

The corresponding Server API value will be a Biscuit OpenOrSealed Verified -> Server ProtectedAPI. The next step is to provide a Authorizer so that the biscuit datalog can be verified. For that, you can use checkBiscuit (or checkBiscuitM for effectful checks).

server :: Server API
server biscuit = h1 biscuit
            :<|> h2 biscuit
            :<|> h3 biscuit

h1 :: Biscuit OpenOrSealed Verified -> Handler Int
h1 biscuit =
  checkBiscuit biscuit
    [authorizer|allow if right("one");|]
    -- ^ only allow biscuits granting access to the endpoint tagged "one"
    (pure 1)

h2 :: Biscuit OpenOrSealed Verified -> Int -> Handler Int
h2 biscuit value =
  let authorizer' = do
        now <- liftIO getCurrentTime
        pure [authorizer|
               // provide the current time so that TTL checks embedded in
               // the biscuit can decide if it's still valid
               // this show how to run an effectful check with
               // checkBiscuitM (getting the current time is an effect)
               time(${now});
               // only allow biscuits granting access to the endpoint tagged "two"
               // AND for the provided int value. This show how the checks can depend
               // on the http request contents.
               allow if right("two", ${value});
             |]
  checkBiscuitM biscuit authorizer
    (pure 2)

h3 :: Biscuit OpenOrSealed Verified -> Handler Int
h3 biscuit =
  checkBiscuit biscuit
    [authorizer|deny if true;|]
    -- ^ reject every biscuit
    (pure 3)

checkBiscuit :: (MonadIO m, MonadError ServerError m) => Biscuit OpenOrSealed Verified -> Authorizer -> m a -> m a Source #

Given a biscuit (provided by the servant authorization mechanism), verify its validity (with the provided Authorizer).

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 retrieve extra information needed to check the token), you can use checkBiscuitM instead.

If you don't want to pass the biscuit manually to all the endpoints or want to blanket apply authorizers on whole API trees, you can consider using withAuthorizer (on endpoints), withFallbackAuthorizer and withPriorityAuthorizer (on API sub-trees) and handleBiscuit (on the whole API).

checkBiscuitM :: (MonadIO m, MonadError ServerError m) => Biscuit OpenOrSealed Verified -> m Authorizer -> m a -> m a Source #

Given a Biscuit (provided by the servant authorization mechanism), verify its validity (with the provided Authorizer, 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 authorizers on whole API trees, you can consider using withAuthorizer (on endpoints), withFallbackAuthorizer and withPriorityAuthorizer (on API sub-trees) and handleBiscuit (on the whole API).

Decorate regular handlers with composable authorizers

checkBiscuit allows you to describe validation rules endpoint by endpoint. If your application has a lot of endpoints with the same policies, it can become tedious to maintain.

'biscuit-servant' provides a way to apply authorizers on whole API trees, in a composable way, thanks to hoistServer. hoistServer is a mechanism provided by servant-server that lets apply a transformation function to whole API trees.

-- 'withAuthorizer' wraps a 'Handler' and lets you attach a authorizer to a
-- specific endoint. This authorizer may be combined with other authorizers
-- attached to the whole API tree
handler1 :: WithAuthorizer Handler Int
handler1 = withAuthorizer
  [authorizer|allow if right("one");|]
  (pure 1)

handler2 :: Int -> WithAuthorizer Handler Int
handler2 value = withAuthorizer
  [authorizer|allow if right("two", ${value});|]
  (pure 2)

handler3 :: WithAuthorizer Handler Int
handler3 = withAuthorizer
  [authorizer|allow if right("three");|]
  (pure 3)

server :: Biscuit OpenOrSealed Verified -> Server ProtectedAPI
server biscuit =
 let nowFact = do
       now <- liftIO getCurrentTime
       pure [authorizer|time(${now});|]
     handleAuth :: WithAuthorizer Handler x -> Handler x
     handleAuth =
         handleBiscuit biscuit
         -- ^ this runs datalog checks on the biscuit, based on authorizers attached to
         -- the handlers
       . withPriorityAuthorizerM nowFact
         -- ^ this provides the current time to the verification context so that biscuits with
         -- a TTL can check if they are still valid.
         -- Authorizers can be provided in a monadic context (it has to be the same monad as
         -- the handlers themselves, so here it's 'Handler').
       . withPriorityAuthorizer [authorizer|allow if right("admin");|]
         -- ^ this policy will be tried /before/ any endpoint policy, so `endpoint3` will be
         -- reachable with an admin biscuit
       . withFallbackAuthorizer [authorizer|allow if right("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.

data WithAuthorizer (m :: Type -> Type) (a :: Type) Source #

Wrapper for a servant handler, equipped with a biscuit Authorizer that will be used to authorize the request. If the authorization succeeds, the handler is ran. The handler itself is given access to the verified biscuit through a ReaderT (Biscuit OpenOrSealed Verified).

Constructors

WithAuthorizer 

Fields

handleBiscuit :: (MonadIO m, MonadError ServerError m) => Biscuit OpenOrSealed Verified -> WithAuthorizer m a -> m a Source #

Given a handler wrapped in a WithAuthorizer, use the attached Authorizer 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.

withAuthorizer :: Applicative m => Authorizer -> ReaderT (Biscuit OpenOrSealed Verified) m a -> WithAuthorizer m a Source #

Wraps an existing handler block, attaching a Authorizer. The handler has to be a @ReaderT (Biscuit OpenOrSealed Verified)' to be able to access the token. If you don't need to access the token from the handler block, you can use withAuthorizer_ instead.

If you need to perform effects to compute the authorizer (eg. to get the current date, or to query a database), you can use withAuthorizerM instead.

withAuthorizer_ :: Monad m => Authorizer -> m a -> WithAuthorizer m a Source #

Wraps an existing handler block, attaching a Authorizer. 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 withAuthorizer instead.

If you need to perform effects to compute the authorizer (eg. to get the current date, or to query a database), you can use withAuthorizerM_ instead.

withAuthorizerM :: m Authorizer -> ReaderT (Biscuit OpenOrSealed Verified) m a -> WithAuthorizer m a Source #

Wraps an existing handler block, attaching a Authorizer. The handler has to be a ReaderT (Biscuit OpenOrSealed Verified) to be able to access the token. If you don't need to access the token from the handler block, you can use withAuthorizer_ instead.

Here, the Authorizer can be computed effectfully. If you don't need to perform effects, you can use withAuthorizer instead.

withAuthorizerM_ :: Monad m => m Authorizer -> m a -> WithAuthorizer m a Source #

Wraps an existing handler block, attaching a Authorizer. 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 withAuthorizer instead.

Here, the Authorizer can be computed effectfully. If you don't need to perform effects, you can use withAuthorizer_ instead.

noAuthorizer :: Applicative m => ReaderT (Biscuit OpenOrSealed Verified) m a -> WithAuthorizer m a Source #

Wraps an existing handler block, attaching an empty Authorizer. The handler has to be a ReaderT (Biscuit OpenOrSealed Verified) to be able to access the token. If you don't need to access the token from the handler block, you can use noAuthorizer_ instead.

This function is useful when the endpoint does not have any specific authorizer context, and the authorizer context is applied on the whole API tree through withFallbackAuthorizer or withPriorityAuthorizer to apply policies on several handlers at the same time (with hoistServer for instance).

noAuthorizer_ :: Monad m => m a -> WithAuthorizer m a Source #

Wraps an existing handler block, attaching an empty Authorizer. 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 noAuthorizer instead.

This function is useful when the endpoint does not have any specific authorizer context, and the authorizer context is applied on the whole API tree through withFallbackAuthorizer or withPriorityAuthorizer to apply policies on several handlers at the same time (with hoistServer for instance).

withFallbackAuthorizer :: Functor m => Authorizer -> WithAuthorizer m a -> WithAuthorizer m a Source #

Combines the provided Authorizer to the Authorizer attached to the wrapped handler. facts, rules and checks are unordered, but policies have a specific order. withFallbackAuthorizer puts the provided policies at the bottom of the list (ie as fallback policies): these policies will be tried after the policies declared through withPriorityAuthorizer and after the policies declared by the endpoints.

If you want the policies to be tried before the ones of the wrapped handler, you can use withPriorityAuthorizer.

If you need to perform effects to compute the authorizer (eg. to get the current date, or to query a database), you can use withFallbackAuthorizerM instead.

withPriorityAuthorizer :: Functor m => Authorizer -> WithAuthorizer m a -> WithAuthorizer m a Source #

Combines the provided Authorizer to the Authorizer attached to the wrapped handler. facts, rules and checks are unordered, but policies have a specific order. withFallbackAuthorizer puts the provided policies at the top of the list (ie as priority policies): these policies will be tried after the policies declared through withPriorityAuthorizer and after the policies declared by the endpoints.

If you want the policies to be tried after the ones of the wrapped handler, you can use withFallbackAuthorizer.

If you need to perform effects to compute the authorizer (eg. to get the current date, or to query a database), you can use withPriorityAuthorizerM instead.

withFallbackAuthorizerM :: Applicative m => m Authorizer -> WithAuthorizer m a -> WithAuthorizer m a Source #

Combines the provided Authorizer to the Authorizer attached to the wrapped handler. facts, rules and checks are unordered, but policies have a specific order. withFallbackAuthorizer puts the provided policies at the bottom of the list (ie as fallback policies): these policies will be tried after the policies declared through withPriorityAuthorizer and after the policies declared by the endpoints.

If you want the policies to be tried before the ones of the wrapped handler, you can use withPriorityAuthorizer.

Here, the Authorizer can be computed effectfully. If you don't need to perform effects, you can use withFallbackAuthorizer instead.

withPriorityAuthorizerM :: Applicative m => m Authorizer -> WithAuthorizer m a -> WithAuthorizer m a Source #

Combines the provided Authorizer to the Authorizer attached to the wrapped handler. facts, rules and checks are unordered, but policies have a specific order. withFallbackAuthorizer puts the provided policies at the top of the list (ie as priority policies): these policies will be tried after the policies declared through withPriorityAuthorizer and after the policies declared by the endpoints.

If you want the policies to be tried after the ones of the wrapped handler, you can use withFallbackAuthorizer.

Here, the Authorizer can be computed effectfully. If you don't need to perform effects, you can use withFallbackAuthorizer instead.