webgear-core-1.0.3: Composable, type-safe library to build HTTP APIs
Safe HaskellNone
LanguageHaskell2010

WebGear.Core.Trait.Auth.Basic

Description

HTTP basic authentication support.

Middlewares defined in this module add basic authentication support to handlers. In most cases, you just need to use BasicAuth trait and basicAuth middleware. The table below describes when to use other traits and middlewares.

TypeAuth SchemeTraitMiddleware
RequiredBasicBasicAuthbasicAuth
OptionalBasicBasicAuth' OptionaloptionalBasicAuth
RequiredAny schemeBasicAuth' RequiredbasicAuth'
OptionalAny schemeBasicAuth' OptionaloptionalBasicAuth'

For example, given this handler:

myHandler :: (Handler h IO, HasTrait (BasicAuth IO () Credentials) req) => RequestHandler h req
myHandler = ....

and the following definitions:

authConfig :: BasicAuth IO () Credentials
authConfig = BasicAuth' { toBasicAttribute = pure . Right }

type ErrorTraits = [Status, RequiredHeader "Content-Type" Text, RequiredHeader "WWW-Authenticate" Text, Body Text]

errorHandler :: (Handler h IO, Sets h ErrorTraits Response)
             => h (Linked req Request, BasicAuthError e) Response
errorHandler = respondUnauthorized "Basic" "MyRealm"

we can add basic authentication to myHandler:

myHandlerWithAuth :: (Handler h IO, Get h (BasicAuth IO () Credentials) Request, Sets h ErrorTraits Response)
                  => RequestHandler h req
myHandlerWithAuth = basicAuth authConfig errorHandler myHandler

The middlewares defined below take a BasicAuth' parameter which is a newtype wrapper over a function of type Credentials -> m (Either e a). This is used to convert the user supplied credentials to a value of type a or fail with an error of type e. The next handler is invoked after this conversion and can access a as a trait attribute.

Middlewares marked as Required take an additional error handling arrow as a parameter. This arrow is used when an error is encountered in authentication. This arrow receives the original request and a BasicAuthError as inputs and must produce a response as the output.

Middlewares marked as Optional do not have this additional error handling arrow. Instead, the trait attribute is of type Either (BasicAuthError e) a. The next handler will get the errors in this trait attribute and must handle it.

Synopsis

Documentation

newtype BasicAuth' (x :: Existence) (scheme :: Symbol) m e a Source #

Trait for HTTP basic authentication: https://tools.ietf.org/html/rfc7617

Constructors

BasicAuth' 

Fields

Instances

Instances details
TraitAbsence (BasicAuth' 'Required scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Basic

Associated Types

type Absence (BasicAuth' 'Required scheme m e a) Request Source #

TraitAbsence (BasicAuth' 'Optional scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Basic

Associated Types

type Absence (BasicAuth' 'Optional scheme m e a) Request Source #

Trait (BasicAuth' 'Required scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Basic

Associated Types

type Attribute (BasicAuth' 'Required scheme m e a) Request Source #

Trait (BasicAuth' 'Optional scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Basic

Associated Types

type Attribute (BasicAuth' 'Optional scheme m e a) Request Source #

type Absence (BasicAuth' 'Required scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Basic

type Absence (BasicAuth' 'Optional scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Basic

type Absence (BasicAuth' 'Optional scheme m e a) Request = Void
type Attribute (BasicAuth' 'Required scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Basic

type Attribute (BasicAuth' 'Required scheme m e a) Request = a
type Attribute (BasicAuth' 'Optional scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Basic

type BasicAuth = BasicAuth' Required "Basic" Source #

Trait for HTTP basic authentication with the Basic scheme.

newtype Realm Source #

The protection space for authentication

Constructors

Realm ByteString 

Instances

Instances details
Eq Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Methods

(==) :: Realm -> Realm -> Bool #

(/=) :: Realm -> Realm -> Bool #

Ord Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Methods

compare :: Realm -> Realm -> Ordering #

(<) :: Realm -> Realm -> Bool #

(<=) :: Realm -> Realm -> Bool #

(>) :: Realm -> Realm -> Bool #

(>=) :: Realm -> Realm -> Bool #

max :: Realm -> Realm -> Realm #

min :: Realm -> Realm -> Realm #

Read Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Show Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Methods

showsPrec :: Int -> Realm -> ShowS #

show :: Realm -> String #

showList :: [Realm] -> ShowS #

IsString Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Methods

fromString :: String -> Realm #

newtype Username Source #

Username for basic authentication. Valid usernames cannot contain ':' characters.

Constructors

Username ByteString 

newtype Password Source #

Password for basic authentication.

Constructors

Password ByteString 

basicAuth Source #

Arguments

:: forall m e t h req. (Get h (BasicAuth' Required "Basic" m e t) Request, ArrowChoice h) 
=> BasicAuth m e t

Authentication configuration

-> h (Linked req Request, BasicAuthError e) Response

Error handler

-> Middleware h req (BasicAuth m e t ': req) 

Middleware to add basic authentication protection for a handler.

Example usage:

basicAuth cfg errorHandler nextHandler

The errorHandler is invoked if the credentials are invalid or missing. The nextHandler is invoked if the credentials were retrieved successfully.

basicAuth' Source #

Arguments

:: forall scheme m e t h req. (Get h (BasicAuth' Required scheme m e t) Request, ArrowChoice h) 
=> BasicAuth' Required scheme m e t

Authentication configuration

-> h (Linked req Request, BasicAuthError e) Response

Error handler

-> Middleware h req (BasicAuth' Required scheme m e t ': req) 

Similar to basicAuth but supports a custom authentication scheme.

Example usage:

basicAuth' @"scheme" cfg errorHandler nextHandler

optionalBasicAuth Source #

Arguments

:: forall m e t h req. (Get h (BasicAuth' Optional "Basic" m e t) Request, ArrowChoice h) 
=> BasicAuth' Optional "Basic" m e t

Authentication configuration

-> Middleware h req (BasicAuth' Optional "Basic" m e t ': req) 

Middleware to add optional basic authentication protection for a handler.

Example usage:

optionalBasicAuth cfg nextHandler

This middleware will not fail if credentials are invalid or missing. Instead the trait attribute is of type Either (BasicAuthError e) t so that the handler can process the authentication error appropriately.

optionalBasicAuth' Source #

Arguments

:: forall scheme m e t h req. (Get h (BasicAuth' Optional scheme m e t) Request, ArrowChoice h) 
=> BasicAuth' Optional scheme m e t

Authentication configuration

-> Middleware h req (BasicAuth' Optional scheme m e t ': req) 

Similar to optionalBasicAuth but supports a custom authentication scheme.

Example usage:

optionalBasicAuth' @"scheme" cfg nextHandler