servant-auth-token-0.1.1.0: Servant based API and server for token based authorisation

Copyright(c) Anton Gushcha, 2016
LicenseMIT
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Servant.Server.Auth.Token

Contents

Description

The module is server side implementation of Servant.API.Auth.Token API and intended to be used as drop in module for user servers or as external micro service.

To use the server as constituent part, you need to provide customised AuthConfig for authServer function and implement AuthMonad instance for your handler monad.

import Servant.Server.Auth.Token as Auth

-- | Example of user side configuration
data Config = Config {
  -- | Authorisation specific configuration
  authConfig :: AuthConfig
  -- other fields
  -- ...
}

-- | Example of user side handler monad
newtype App a = App { 
    runApp :: ReaderT Config (ExceptT ServantErr IO) a
  } deriving ( Functor, Applicative, Monad, MonadReader Config,
               MonadError ServantErr, MonadIO)

-- | Now you can use authorisation API in your handler
instance AuthMonad App where 
  getAuthConfig = asks authConfig
  liftAuthAction = App . lift

-- | Include auth migrateAll function into your migration code
doMigrations :: SqlPersistT IO ()
doMigrations = runMigrationUnsafe $ do 
  migrateAll -- other user migrations
  Auth.migrateAll -- creation of authorisation entities
  -- optional creation of default admin if db is empty
  ensureAdmin 17 "admin" "123456" "admin@localhost" 

Now you can use guardAuthToken to check authorisation headers in endpoints of your server:

-- | Read a single customer from DB
customerGet :: CustomerId -- ^ Customer unique id
  -> MToken '["customer-read"] -- ^ Required permissions for auth token
  -> App Customer -- ^ Customer data
customerGet i token = do
  guardAuthToken token 
  runDB404 "customer" $ getCustomer i 

Synopsis

Implementation

authServer :: AuthConfig -> Server AuthAPI Source

Implementation of AuthAPI

Server API

class Monad m => AuthMonad m where Source

The interface your application should implement to be able to use token aurhorisation API.

Helpers

guardAuthToken :: forall perms m. (PermsList perms, AuthMonad m) => MToken perms -> m () Source

If the token is missing or the user of the token doesn't have needed permissions, throw 401 response

ensureAdmin :: Int -> Login -> Password -> Email -> SqlPersistT IO () Source

Ensures that DB has at leas one admin, if not, creates a new one with specified info.

authUserByToken :: AuthMonad m => MToken `[]` -> m UserImplId Source

Getting user id by token