tmp-proc-0.5.0.1: Run 'tmp' processes in integration tests
Copyright(c) 2020-2021 Tim Emiola
LicenseBSD3
MaintainerTim Emiola <adetokunbo@users.noreply.github.com>
Safe HaskellNone
LanguageHaskell2010

System.TmpProc.TypeLevel

Description

Defines type-level data structures and combinators used by System.TmpProc.Docker and System.TmpProc.Warp.

HList implements a heterogenous list used to define types that represent multiple concurrent tmp procs.

KV is intended for internal use within the tmp-proc package. It allows indexing and sorting of lists of tmp procs.

Synopsis

Heterogenous List

data HList :: [*] -> * where Source #

Defines a Heterogenous list.

Constructors

HNil :: HList '[] 
HCons :: anyTy -> HList manyTys -> HList (anyTy ': manyTys) infixr 5 

Instances

Instances details
(Eq x, Eq (HList xs)) => Eq (HList (x ': xs)) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

(==) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

(/=) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

Eq (HList ('[] :: [Type])) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

(==) :: HList '[] -> HList '[] -> Bool #

(/=) :: HList '[] -> HList '[] -> Bool #

(Show x, Show (HList xs)) => Show (HList (x ': xs)) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

showsPrec :: Int -> HList (x ': xs) -> ShowS #

show :: HList (x ': xs) -> String #

showList :: [HList (x ': xs)] -> ShowS #

Show (HList ('[] :: [Type])) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

showsPrec :: Int -> HList '[] -> ShowS #

show :: HList '[] -> String #

showList :: [HList '[]] -> ShowS #

(&:) :: x -> HList xs -> HList (x ': xs) infixr 5 Source #

An infix alias for HCons.

hHead :: HList (a ': as) -> a Source #

Obtain the first element of a HList.

hOf :: forall y xs. IsInProof y xs => Proxy y -> HList xs -> y Source #

Get an item in an HList given its type.

class ReorderH xs ys where Source #

Allows reordering of similar HLists.

Examples

Expand
>>> hReorder @_ @'[Bool, Int] ('c' &: (3 :: Int) &: True &: (3.1 :: Double) &: HNil)
True &: 3 &: HNil
>>> hReorder @_ @'[Double, Bool, Int] ('c' &: (3 :: Int) &: True &: (3.1 :: Double) &: HNil)
3.1 &: True &: 3 &: HNil

Methods

hReorder :: HList xs -> HList ys Source #

Instances

Instances details
ReorderH xs ('[] :: [Type]) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

hReorder :: HList xs -> HList '[] Source #

(IsInProof y xs, ReorderH xs ys) => ReorderH xs (y ': ys) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

hReorder :: HList xs -> HList (y ': ys) Source #

A type-level Key-Value

data KV :: Symbol -> * -> * where Source #

Use a type-level symbol as key type that indexes a value type.

Constructors

V :: a -> KV s a 

Instances

Instances details
ManyMemberKV ks ts kvs => ManyMemberKV ks ts (KV ok ot ': kvs) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

manyProof :: LookupMany ks ts (KV ok ot ': kvs) Source #

MemberKV k t kvs => MemberKV k t (KV ok ot ': kvs) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

lookupProof :: LookupKV k t (KV ok ot ': kvs) Source #

MemberKV k t (KV k t ': kvs) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

lookupProof :: LookupKV k t (KV k t ': kvs) Source #

MemberKV k t '[KV k t] Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

lookupProof :: LookupKV k t '[KV k t] Source #

ManyMemberKV ks ts kvs => ManyMemberKV (k ': ks) (t ': ts) (KV k t ': kvs) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

manyProof :: LookupMany (k ': ks) (t ': ts) (KV k t ': kvs) Source #

ManyMemberKV '[k] '[t] (KV k t ': ks) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

manyProof :: LookupMany '[k] '[t] (KV k t ': ks) Source #

select :: forall k t xs. MemberKV k t xs => HList xs -> t Source #

Select an item from an HList of KVs by key.

N.B Returns the first item. It assumes the keys in the KV HList are unique. TODO: enforce this rule using a constraint.

Examples

Expand
>>> select @"d" @Double  @'[KV "b" Bool, KV "d" Double] (V True &:  V (3.1 :: Double) &: HNil)
3.1

selectMany :: forall ks ts xs. ManyMemberKV ks ts xs => HList xs -> HList ts Source #

Select items with specified keys from an HList of KVs by key.

N.B. this this is an internal function.

The keys must be provided in the same order as they occur in the HList, any other order will likely result in an compiler error.

Examples

Expand
>>> selectMany @'["b"] @'[Bool] @'[KV "b" Bool, KV "d" Double] (V True &:  V (3.1 :: Double) &: HNil)
True &: HNil

data LookupKV (k :: Symbol) t (xs :: [*]) where Source #

Proves a symbol and its type occur as entry in a list of KV types.

Constructors

AtHead :: LookupKV k t (KV k t ': kvs) 
OtherKeys :: LookupKV k t kvs -> LookupKV k t (KV ok ot ': kvs) 

class MemberKV (k :: Symbol) (t :: *) (xs :: [*]) where Source #

Generate proof instances of LookupKV.

Methods

lookupProof :: LookupKV k t xs Source #

Instances

Instances details
MemberKV k t kvs => MemberKV k t (KV ok ot ': kvs) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

lookupProof :: LookupKV k t (KV ok ot ': kvs) Source #

MemberKV k t (KV k t ': kvs) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

lookupProof :: LookupKV k t (KV k t ': kvs) Source #

MemberKV k t '[KV k t] Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

lookupProof :: LookupKV k t '[KV k t] Source #

class ManyMemberKV (ks :: [Symbol]) (ts :: [*]) (kvs :: [*]) where Source #

Generate proof instances of LookupMany.

Methods

manyProof :: LookupMany ks ts kvs Source #

Instances

Instances details
ManyMemberKV ks ts kvs => ManyMemberKV ks ts (KV ok ot ': kvs) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

manyProof :: LookupMany ks ts (KV ok ot ': kvs) Source #

ManyMemberKV ks ts kvs => ManyMemberKV (k ': ks) (t ': ts) (KV k t ': kvs) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

manyProof :: LookupMany (k ': ks) (t ': ts) (KV k t ': kvs) Source #

ManyMemberKV '[k] '[t] (KV k t ': ks) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

manyProof :: LookupMany '[k] '[t] (KV k t ': ks) Source #

Other combinators

type family IsAbsent e r :: Constraint where ... Source #

A constraint that confirms that a type is not present in a type-level list.

Equations

IsAbsent e '[] = () 
IsAbsent e (e ': _) = TypeError (NotAbsentErr e) 
IsAbsent e (e' ': tail) = IsAbsent e tail 

class IsInProof t (tys :: [Type]) Source #

Generate proof instances of IsIn.

Minimal complete definition

provedIsIn

Instances

Instances details
IsInProof t tys => IsInProof t (a ': tys) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

provedIsIn :: IsIn t (a ': tys)

IsInProof t (t ': tys) Source # 
Instance details

Defined in System.TmpProc.TypeLevel

Methods

provedIsIn :: IsIn t (t ': tys)

Re-exports