webgear-server-0.2.1: Composable, type-safe library to build HTTP API servers
Copyright(c) Raghu Kaippully 2020
LicenseMPL-2.0
Maintainerrkaippully@gmail.com
Safe HaskellNone
LanguageHaskell2010

WebGear.Trait

Description

Traits are optional attributes associated with a value. For example, a list containing totally ordered values might have a Maximum trait where the associated attribute is the maximum value. This trait exists only if the list is non-empty. The Trait typeclass provides an interface to extract such trait attributes.

Traits help to link attributes with values in a type-safe manner.

Traits are somewhat similar to refinement types, but allow arbitrary attributes to be associated with a value instead of only a predicate.

Synopsis

Core Types

class Monad m => Trait t a m where Source #

A trait is an optional attribute t associated with a value a.

Associated Types

type Attribute t a :: Type Source #

Type of the associated attribute when the trait holds for a value

type Absence t a :: Type Source #

Type that indicates that the trait does not exist for a value. This could be an error message, parse error etc.

Methods

toAttribute :: a -> m (Result t a) Source #

Attempt to deduce the trait attribute from the value a. It is possible that deducing a trait's presence can alter the value, hence this function returns a possibly updated value along with the trait attribute on success.

Instances

Instances details
MonadState PathInfo m => Trait PathEnd Request m Source # 
Instance details

Defined in WebGear.Middlewares.Path

Monad m => Trait BasicAuth Request m Source # 
Instance details

Defined in WebGear.Middlewares.Auth.Basic

Monad m => Trait ('[] :: [k]) a m Source #

A trivial derivable trait that is always present and whose attribute does not carry any meaningful information.

Instance details

Defined in WebGear.Trait

Associated Types

type Attribute '[] a Source #

type Absence '[] a Source #

Methods

toAttribute :: a -> m (Result '[] a) Source #

(IsStdMethod t, Monad m) => Trait (Method t :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Method

Associated Types

type Attribute (Method t) Request Source #

type Absence (Method t) Request Source #

(KnownSymbol s, MonadState PathInfo m) => Trait (Path s :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Path

Associated Types

type Attribute (Path s) Request Source #

type Absence (Path s) Request Source #

(FromJSON t, MonadIO m) => Trait (JSONRequestBody t :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Body

(Trait t a2 m, Trait ts a2 m, Monad m) => Trait (t ': ts :: [a1]) a2 m Source #

Combination of many derivable traits all of which are present for a value.

Instance details

Defined in WebGear.Trait

Associated Types

type Attribute (t ': ts) a2 Source #

type Absence (t ': ts) a2 Source #

Methods

toAttribute :: a2 -> m (Result (t ': ts) a2) Source #

(KnownSymbol name, KnownSymbol val, Monad m) => Trait (HeaderMatch' 'Required name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (HeaderMatch' 'Required name val) Request Source #

type Absence (HeaderMatch' 'Required name val) Request Source #

(KnownSymbol name, KnownSymbol val, Monad m) => Trait (HeaderMatch' 'Optional name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (HeaderMatch' 'Optional name val) Request Source #

type Absence (HeaderMatch' 'Optional name val) Request Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (Header' 'Required 'Strict name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (Header' 'Required 'Strict name val) Request Source #

type Absence (Header' 'Required 'Strict name val) Request Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (Header' 'Required 'Lenient name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (Header' 'Required 'Lenient name val) Request Source #

type Absence (Header' 'Required 'Lenient name val) Request Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (Header' 'Optional 'Strict name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (Header' 'Optional 'Strict name val) Request Source #

type Absence (Header' 'Optional 'Strict name val) Request Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (Header' 'Optional 'Lenient name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (Header' 'Optional 'Lenient name val) Request Source #

type Absence (Header' 'Optional 'Lenient name val) Request Source #

(FromHttpApiData val, MonadState PathInfo m) => Trait (PathVar tag val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Path

Associated Types

type Attribute (PathVar tag val) Request Source #

type Absence (PathVar tag val) Request Source #

Methods

toAttribute :: Request -> m (Result (PathVar tag val) Request) Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (Header' 'Required 'Strict name val :: Type) (Response a) m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (Header' 'Required 'Strict name val) (Response a) Source #

type Absence (Header' 'Required 'Strict name val) (Response a) Source #

Methods

toAttribute :: Response a -> m (Result (Header' 'Required 'Strict name val) (Response a)) Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (Header' 'Required 'Lenient name val :: Type) (Response a) m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (Header' 'Required 'Lenient name val) (Response a) Source #

type Absence (Header' 'Required 'Lenient name val) (Response a) Source #

Methods

toAttribute :: Response a -> m (Result (Header' 'Required 'Lenient name val) (Response a)) Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (Header' 'Optional 'Strict name val :: Type) (Response a) m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (Header' 'Optional 'Strict name val) (Response a) Source #

type Absence (Header' 'Optional 'Strict name val) (Response a) Source #

Methods

toAttribute :: Response a -> m (Result (Header' 'Optional 'Strict name val) (Response a)) Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (Header' 'Optional 'Lenient name val :: Type) (Response a) m Source # 
Instance details

Defined in WebGear.Middlewares.Header

Associated Types

type Attribute (Header' 'Optional 'Lenient name val) (Response a) Source #

type Absence (Header' 'Optional 'Lenient name val) (Response a) Source #

Methods

toAttribute :: Response a -> m (Result (Header' 'Optional 'Lenient name val) (Response a)) Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (QueryParam' 'Required 'Strict name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Params

Associated Types

type Attribute (QueryParam' 'Required 'Strict name val) Request Source #

type Absence (QueryParam' 'Required 'Strict name val) Request Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (QueryParam' 'Required 'Lenient name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Params

Associated Types

type Attribute (QueryParam' 'Required 'Lenient name val) Request Source #

type Absence (QueryParam' 'Required 'Lenient name val) Request Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (QueryParam' 'Optional 'Strict name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Params

Associated Types

type Attribute (QueryParam' 'Optional 'Strict name val) Request Source #

type Absence (QueryParam' 'Optional 'Strict name val) Request Source #

(KnownSymbol name, FromHttpApiData val, Monad m) => Trait (QueryParam' 'Optional 'Lenient name val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Params

Associated Types

type Attribute (QueryParam' 'Optional 'Lenient name val) Request Source #

type Absence (QueryParam' 'Optional 'Lenient name val) Request Source #

data Result t a Source #

The result of toAttribute - either a successful deduction of an attribute or an error.

Constructors

NotFound (Absence t a) 
Found (Attribute t a) 

data Linked (ts :: [Type]) a Source #

A value linked with a type-level list of traits.

Linking values with attributes

link :: a -> Linked '[] a Source #

Wrap a value with an empty list of traits.

unlink :: Linked ts a -> a Source #

Retrive the value from a linked value

probe :: forall t ts a m. Trait t a m => Linked ts a -> m (Either (Absence t a) (Linked (t ': ts) a)) Source #

Attempt to link an additional trait with an already linked value via the toAttribute operation. This can fail indicating an Absence of the trait.

remove :: Linked (t ': ts) a -> Linked ts a Source #

Remove the leading trait from the type-level list of traits

Retrive trait attributes from linked values

class Has t ts where Source #

Constraint that proves that the trait t is present in the list of traits ts.

Methods

get :: Proxy t -> Linked ts a -> Attribute t a Source #

Get the attribute associated with t from a linked value

Instances

Instances details
(TypeError (MissingTrait t) :: Constraint) => Has (t :: k) ('[] :: [Type]) Source # 
Instance details

Defined in WebGear.Trait

Methods

get :: Proxy t -> Linked '[] a -> Attribute t a Source #

Has (t :: Type) (t ': ts) Source # 
Instance details

Defined in WebGear.Trait

Methods

get :: Proxy t -> Linked (t ': ts) a -> Attribute t a Source #

Has t ts => Has (t :: k) (t' ': ts) Source # 
Instance details

Defined in WebGear.Trait

Methods

get :: Proxy t -> Linked (t' ': ts) a -> Attribute t a Source #

type family Have ts qs :: Constraint where ... Source #

Constraint that proves that all the traits in the list ts are also present in the list qs.

Equations

Have '[] qs = () 
Have (t ': ts) qs = (Has t qs, Have ts qs) 

type MissingTrait t = ((((((((Text "The request doesn't have the trait \8216" :<>: ShowType t) :<>: Text "\8217.") :$$: Text "") :$$: Text "Did you use a wrong trait type?") :$$: Text "For e.g., \8216PathVar \"foo\" Int\8217 instead of \8216PathVar \"foo\" String\8217?") :$$: Text "") :$$: Text "Or did you forget to apply an appropriate middleware?") :$$: Text "For e.g. The trait \8216JSONRequestBody Foo\8217 can be used with \8216jsonRequestBody @Foo\8217 middleware.") :$$: Text "" Source #

Type error for nicer UX of missing traits