Copyright | (c) Raghu Kaippully 2020 |
---|---|
License | MPL-2.0 |
Maintainer | rkaippully@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
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
- class Monad m => Trait t a m where
- data Result t a
- data Linked (ts :: [Type]) a
- link :: a -> Linked '[] a
- unlink :: Linked ts a -> a
- probe :: forall t ts a m. Trait t a m => Linked ts a -> m (Either (Absence t a) (Linked (t ': ts) a))
- remove :: Linked (t ': ts) a -> Linked ts a
- class Has t ts where
- type family Have ts qs :: Constraint where ...
- 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 ""
Core Types
class Monad m => Trait t a m where Source #
A trait is an optional attribute t
associated with a value
a
.
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.
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
The result of toAttribute
- either a successful deduction of an
attribute or an error.
Linking values with attributes
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
Constraint that proves that the trait t
is present in the list
of traits ts
.
get :: Proxy t -> Linked ts a -> Attribute t a Source #
Get the attribute associated with t
from a linked value
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
.
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