webgear-server-0.1.0: 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 that a value might posess. For example, a list containing totally ordered values might have a Maximum trait where the associated attribute is the maximum value. The trait exists only if the list is non-empty.

Traits help to access these attributes 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.

The check function validates the presence of the trait for a given value. Checking the presence of the trait can optionally modify the value as well.

Associated Types

type Val t a Source #

Type of the associated attribute

type Fail t a Source #

Type of check failures

Methods

check :: a -> m (CheckResult t a) Source #

Checks the presence of the associated attribute.

Instances

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

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

Instance details

Defined in WebGear.Trait

Associated Types

type Val '[] a Source #

type Fail '[] a Source #

Methods

check :: a -> m (CheckResult '[] a) Source #

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

Defined in WebGear.Trait.Method

Associated Types

type Val (Method t) Request Source #

type Fail (Method t) Request Source #

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

Defined in WebGear.Trait.Path

Associated Types

type Val (Path s) Request Source #

type Fail (Path s) Request Source #

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

Defined in WebGear.Trait.Body

(KnownSymbol s, KnownSymbol t, Monad m) => Trait (HeaderMatch s t :: Type) Request m Source # 
Instance details

Defined in WebGear.Trait.Header

Associated Types

type Val (HeaderMatch s t) Request Source #

type Fail (HeaderMatch s t) Request Source #

(KnownSymbol s, FromHttpApiData t, Monad m) => Trait (Header s t :: Type) Request m Source # 
Instance details

Defined in WebGear.Trait.Header

Associated Types

type Val (Header s t) Request Source #

type Fail (Header s t) Request Source #

Methods

check :: Request -> m (CheckResult (Header s t) Request) Source #

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

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

Instance details

Defined in WebGear.Trait

Associated Types

type Val (t ': ts) a2 Source #

type Fail (t ': ts) a2 Source #

Methods

check :: a2 -> m (CheckResult (t ': ts) a2) Source #

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

Defined in WebGear.Trait.Path

Associated Types

type Val (PathVar tag val) Request Source #

type Fail (PathVar tag val) Request Source #

Methods

check :: Request -> m (CheckResult (PathVar tag val) Request) Source #

data CheckResult t a Source #

Result of a check operation

Constructors

CheckSuccess a (Val t a) 
CheckFail (Fail t a) 

Instances

Instances details
(Eq a, Eq (Val t a), Eq (Fail t a)) => Eq (CheckResult t a) Source # 
Instance details

Defined in WebGear.Trait

Methods

(==) :: CheckResult t a -> CheckResult t a -> Bool #

(/=) :: CheckResult t a -> CheckResult t a -> Bool #

(Read a, Read (Val t a), Read (Fail t a)) => Read (CheckResult t a) Source # 
Instance details

Defined in WebGear.Trait

(Show a, Show (Val t a), Show (Fail t a)) => Show (CheckResult t a) Source # 
Instance details

Defined in WebGear.Trait

Methods

showsPrec :: Int -> CheckResult t a -> ShowS #

show :: CheckResult t a -> String #

showList :: [CheckResult t a] -> ShowS #

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

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

type family Traits ts a m :: Constraint where ... Source #

Constraint for functions that use multiple traits

Equations

Traits '[] a m = () 
Traits (t ': ts) a m = (Trait t a m, Traits ts a m) 

Linking values with traits

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

Link a value with the trivial trait

linkplus :: Trait t a m => Linked ts a -> m (Either (Fail t a) (Linked (t ': ts) a)) Source #

Attempt to link an additional trait with an already linked value

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

Remove the leading trait from the linked value

unlink :: Linked ts a -> a Source #

Retrive the value from a linked value

Retrive trait attributes from linked values

class Has t ts where Source #

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

Methods

traitValue :: Linked ts a -> Tagged t (Val t a) Source #

Instances

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

Defined in WebGear.Trait

Methods

traitValue :: Linked (t ': ts) a -> Tagged t (Val t a) Source #

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

Defined in WebGear.Trait

Methods

traitValue :: Linked (t' ': ts) a -> Tagged t (Val t a) Source #

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

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

Equations

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