Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
WebGear.Core.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.
Traits help to associate attributes with values in a type-safe
manner. WebGear associates traits with Request
s and Response
s to
ensure certian attributes are present in them and access those with
safety.
Traits are somewhat similar to refinement types, but allow arbitrary attributes to be associated with a value instead of only a predicate.
A value a
associated with traits ts
is referred to as a witnessed
value, represented by the type a `
where With
` tsts
is a
type-level list. You can extract a trait attribute from a witnessed
value with:
pick
@t (from
witnessedValue)
The above expression will result in a compile-time error if t
is
not present in the type-level list of the witnessed value's type.
You can create a witnessed value in a number of ways:
First, you can use wzero
to lift a regular value to a witnessed
value with no associated traits.
Second, you can use probe
to search for the presence of a trait and
add it to the witnessed value; this will adjust the type-level list
accordingly. This is used in cases where the regular value already
contains the trait attribute which can be extracted using the Get
typeclass.
Third, you can use plant
to add a trait attribute to a witnessed
value, thereby extending its type-level list with one more
trait. This is used in cases where you want to modify the witnessed
value. This operation requires an implementation of the Set
typeclass.
Synopsis
- type family Attribute t a :: Type
- type family Absence t :: Type
- type family Prerequisite (t :: Type) (ts :: [Type]) :: Constraint
- class Arrow h => Get h t where
- type family Gets h ts :: Constraint where ...
- class Arrow h => Set h (t :: Type) where
- type family Sets h ts :: Constraint where ...
- data With a (ts :: [Type])
- wzero :: a -> a `With` '[]
- wminus :: (a `With` (t : ts)) -> a `With` ts
- unwitness :: With a ts -> a
- probe :: forall t ts h. (Get h t, Prerequisite t ts) => t -> h (Request `With` ts) (Either (Absence t) (Request `With` (t : ts)))
- plant :: forall t ts h. Set h t => t -> h (Response `With` ts, Attribute t Response) (Response `With` (t : ts))
- class HasTrait t ts where
- type family HaveTraits ts qs :: Constraint where ...
- pick :: Tagged t a -> a
- type MissingTrait t = ((((((((Text "The value doesn't have the \8216" :<>: ShowType t) :<>: Text "\8217 trait.") :$$: Text "") :$$: Text "Did you forget to apply an appropriate middleware?") :$$: Text "For e.g. The trait \8216Body JSON t\8217 requires \8216requestBody @t JSON\8217 middleware.") :$$: Text "") :$$: Text "or did you use a wrong trait type?") :$$: Text "For e.g., \8216RequiredQueryParam \"foo\" Int\8217 instead of \8216RequiredQueryParam \"foo\" String\8217?") :$$: Text ""
Core Types
type family Attribute t a :: Type Source #
Type of the associated attribute when the trait t
holds for a
value a
.
Instances
type family Absence t :: Type Source #
Type that indicates that the trait does not exist on a request. This could be an error message, exception etc.
Instances
type family Prerequisite (t :: Type) (ts :: [Type]) :: Constraint Source #
Indicates the constraints a trait depends upon as a
prerequisite. This is used to assert that a trait t
can be
extracted from a request only if one or more other traits are
present in the trait list ts
associated with it.
If a trait does not depend on other traits this can be set to the
empty contraint ()
.
Instances
type Prerequisite Method ts Source # | |
Defined in WebGear.Core.Trait.Method | |
type Prerequisite Path ts Source # | |
Defined in WebGear.Core.Trait.Path | |
type Prerequisite PathEnd ts Source # | |
Defined in WebGear.Core.Trait.Path | |
type Prerequisite (Body mt t) ts Source # | |
Defined in WebGear.Core.Trait.Body | |
type Prerequisite (PathVar tag val) ts Source # | |
Defined in WebGear.Core.Trait.Path | |
type Prerequisite (Cookie e name val) ts Source # | |
Defined in WebGear.Core.Trait.Cookie | |
type Prerequisite (RequestHeader e p name val) ts Source # | |
Defined in WebGear.Core.Trait.Header | |
type Prerequisite (QueryParam e p name val) ts Source # | |
Defined in WebGear.Core.Trait.QueryParam | |
type Prerequisite (BasicAuth' x scheme m e a) ts Source # | |
Defined in WebGear.Core.Trait.Auth.Basic | |
type Prerequisite (JWTAuth' x scheme m e a) ts Source # | |
Defined in WebGear.Core.Trait.Auth.JWT |
type family Gets h ts :: Constraint where ... Source #
Gets h ts
is equivalent to (Get h t1, Get h t2, ..., Get h tn)
where ts = [t1, t2, ..., tn]
.
class Arrow h => Set h (t :: Type) where Source #
Associate a trait attribute on a response
Methods
Arguments
:: t | The trait to set |
-> ((Response `With` ts) -> Response -> Attribute t Response -> Response `With` (t : ts)) | A function to generate a witnessed response. This function
must be called by the |
-> h (Response `With` ts, Attribute t Response) (Response `With` (t : ts)) | An arrow that attaches a new trait attribute to a witnessed value. |
Set a trait attribute t
on the value Response `With` ts
.
type family Sets h ts :: Constraint where ... Source #
Sets h ts
is equivalent to (Set h t1, Set h t2, ..., Set h tn)
where ts = [t1, t2, ..., tn]
.
data With a (ts :: [Type]) Source #
A value associated with a list of traits, referred to as a witnessed value. Typically, this is used as an infix type constructor:
a `With` ts
where a
is a value and ts
is a list of traits associated with
that value.
If t
is a type present in the list of types ts
, it is possible to
extract its attribute from a witnessed value:
let witnessedValue :: a `With` ts witnessedValue = ... let attr ::Attribute
t a attr =pick
@t (from
witnessedValue)
Associating values with attributes
probe :: forall t ts h. (Get h t, Prerequisite t ts) => t -> h (Request `With` ts) (Either (Absence t) (Request `With` (t : ts))) Source #
Attempt to witness an additional trait with a witnessed
request. This can fail indicating an Absence
of the trait.
plant :: forall t ts h. Set h t => t -> h (Response `With` ts, Attribute t Response) (Response `With` (t : ts)) Source #
Set a trait attribute on witnessed response to produce another witnessed response with the additional trait attached to it.
Retrieve trait attributes from witnessed values
class HasTrait t ts where Source #
Constraint that proves that the trait t
is present in the list
of traits ts
.
Methods
from :: (a `With` ts) -> Tagged t (Attribute t a) Source #
Get the attribute associated with t
from a witnessed
value. See also: pick
.
type family HaveTraits ts qs :: Constraint where ... Source #
Constraint that proves that all the traits in the list ts
are
also present in the list qs
.
Equations
HaveTraits '[] qs = () | |
HaveTraits (t : ts) qs = (HasTrait t qs, HaveTraits ts qs) |
type MissingTrait t = ((((((((Text "The value doesn't have the \8216" :<>: ShowType t) :<>: Text "\8217 trait.") :$$: Text "") :$$: Text "Did you forget to apply an appropriate middleware?") :$$: Text "For e.g. The trait \8216Body JSON t\8217 requires \8216requestBody @t JSON\8217 middleware.") :$$: Text "") :$$: Text "or did you use a wrong trait type?") :$$: Text "For e.g., \8216RequiredQueryParam \"foo\" Int\8217 instead of \8216RequiredQueryParam \"foo\" String\8217?") :$$: Text "" Source #
Type error for nicer UX of missing traits