servant-server-0.16.2: A family of combinators for defining webservices APIs and serving them

Safe HaskellNone
LanguageHaskell2010

Servant.Server.Internal.BasicAuth

Contents

Synopsis

Basic Auth

data BasicAuthResult usr Source #

servant-server's current implementation of basic authentication is not immune to certian kinds of timing attacks. Decoding payloads does not take a fixed amount of time.

The result of authentication/authorization

Instances
Functor BasicAuthResult Source # 
Instance details

Defined in Servant.Server.Internal.BasicAuth

Methods

fmap :: (a -> b) -> BasicAuthResult a -> BasicAuthResult b #

(<$) :: a -> BasicAuthResult b -> BasicAuthResult a #

Eq usr => Eq (BasicAuthResult usr) Source # 
Instance details

Defined in Servant.Server.Internal.BasicAuth

Read usr => Read (BasicAuthResult usr) Source # 
Instance details

Defined in Servant.Server.Internal.BasicAuth

Show usr => Show (BasicAuthResult usr) Source # 
Instance details

Defined in Servant.Server.Internal.BasicAuth

Generic (BasicAuthResult usr) Source # 
Instance details

Defined in Servant.Server.Internal.BasicAuth

Associated Types

type Rep (BasicAuthResult usr) :: Type -> Type #

Methods

from :: BasicAuthResult usr -> Rep (BasicAuthResult usr) x #

to :: Rep (BasicAuthResult usr) x -> BasicAuthResult usr #

type Rep (BasicAuthResult usr) Source # 
Instance details

Defined in Servant.Server.Internal.BasicAuth

type Rep (BasicAuthResult usr) = D1 (MetaData "BasicAuthResult" "Servant.Server.Internal.BasicAuth" "servant-server-0.16.2-DTgh0agHmG52UNzNHy0xfW" False) ((C1 (MetaCons "Unauthorized" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BadPassword" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NoSuchUser" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Authorized" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 usr))))

newtype BasicAuthCheck usr Source #

Datatype wrapping a function used to check authentication.

Instances
Functor BasicAuthCheck Source # 
Instance details

Defined in Servant.Server.Internal.BasicAuth

Methods

fmap :: (a -> b) -> BasicAuthCheck a -> BasicAuthCheck b #

(<$) :: a -> BasicAuthCheck b -> BasicAuthCheck a #

Generic (BasicAuthCheck usr) Source # 
Instance details

Defined in Servant.Server.Internal.BasicAuth

Associated Types

type Rep (BasicAuthCheck usr) :: Type -> Type #

Methods

from :: BasicAuthCheck usr -> Rep (BasicAuthCheck usr) x #

to :: Rep (BasicAuthCheck usr) x -> BasicAuthCheck usr #

type Rep (BasicAuthCheck usr) Source # 
Instance details

Defined in Servant.Server.Internal.BasicAuth

type Rep (BasicAuthCheck usr) = D1 (MetaData "BasicAuthCheck" "Servant.Server.Internal.BasicAuth" "servant-server-0.16.2-DTgh0agHmG52UNzNHy0xfW" True) (C1 (MetaCons "BasicAuthCheck" PrefixI True) (S1 (MetaSel (Just "unBasicAuthCheck") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (BasicAuthData -> IO (BasicAuthResult usr)))))

mkBAChallengerHdr :: ByteString -> Header Source #

Internal method to make a basic-auth challenge

decodeBAHdr :: Request -> Maybe BasicAuthData Source #

Find and decode an Authorization header from the request as Basic Auth

runBasicAuth :: Request -> ByteString -> BasicAuthCheck usr -> DelayedIO usr Source #

Run and check basic authentication, returning the appropriate http error per the spec.