morley-0.3.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.ADT

Contents

Synopsis

Documentation

type HasField dt fname = (InstrGetFieldC dt fname, InstrSetFieldC dt fname) Source #

Allows field access and modification.

type HasFieldOfType dt fname fieldTy = (HasField dt fname, GetFieldType dt fname ~ fieldTy) Source #

Like HasField, but allows constrainting field type.

type family HasFieldsOfType (dt :: Type) (fs :: [NamedField]) :: Constraint where ... Source #

Shortcut for multiple HasFieldOfType constraints.

Equations

HasFieldsOfType _ '[] = () 
HasFieldsOfType dt ((n := ty) ': fs) = (HasFieldOfType dt n ty, HasFieldsOfType dt fs) 

data NamedField Source #

A pair of field name and type.

Constructors

NamedField Symbol Type 

type (:=) n ty = NamedField n ty Source #

toField :: forall dt name st. InstrGetFieldC dt name => Label name -> (dt & st) :-> (GetFieldType dt name & st) Source #

Extract a field of a datatype replacing the value of this datatype with the extracted field.

For this and the following functions you have to specify field name which is either record name or name attached with (:!) operator.

toFieldNamed :: forall dt name st. InstrGetFieldC dt name => Label name -> (dt & st) :-> ((name :! GetFieldType dt name) & st) Source #

Like toField, but leaves field named.

getField :: forall dt name st. InstrGetFieldC dt name => Label name -> (dt & st) :-> (GetFieldType dt name & (dt ': st)) Source #

Extract a field of a datatype, leaving the original datatype on stack.

getFieldNamed :: forall dt name st. InstrGetFieldC dt name => Label name -> (dt & st) :-> ((name :! GetFieldType dt name) & (dt ': st)) Source #

Like getField, but leaves field named.

setField :: forall dt name st. InstrSetFieldC dt name => Label name -> (GetFieldType dt name ': (dt ': st)) :-> (dt ': st) Source #

Set a field of a datatype.

modifyField :: forall dt name st. (InstrGetFieldC dt name, InstrSetFieldC dt name) => Label name -> (forall st0. (GetFieldType dt name ': st0) :-> (GetFieldType dt name ': st0)) -> (dt & st) :-> (dt & st) Source #

Apply given modifier to a datatype field.

construct :: forall dt st. (InstrConstructC dt, RMap (ConstructorFieldTypes dt)) => Rec (FieldConstructor st) (ConstructorFieldTypes dt) -> st :-> (dt & st) Source #

Make up a datatype. You provide a pack of individual fields constructors.

Each element of the accepted record should be an instruction wrapped with fieldCtor function. This instruction will have access to the stack at the moment of calling construct. Instructions have to output fields of the built datatype, one per instruction; instructions order is expected to correspond to the order of fields in the datatype.

constructT :: forall dt fctors st. (InstrConstructC dt, RMap (ConstructorFieldTypes dt), fctors ~ Rec (FieldConstructor st) (ConstructorFieldTypes dt), RecFromTuple fctors) => IsoRecTuple fctors -> st :-> (dt & st) Source #

Version of construct which accepts tuple of field constructors.

fieldCtor :: (st :-> (f & st)) -> FieldConstructor st f Source #

Lift an instruction to field constructor.

wrap_ :: forall dt name st. InstrWrapC dt name => Label name -> AppendCtorField (GetCtorField dt name) st :-> (dt & st) Source #

Wrap entry in constructor. Useful for sum types.

case_ :: forall dt out inp. (InstrCaseC dt inp out, RMap (CaseClauses dt)) => Rec (CaseClauseL inp out) (CaseClauses dt) -> (dt & inp) :-> out Source #

Pattern match on the given sum type.

You have to provide a Rec containing case branches. To construct a case branch use /-> operator.

caseT :: forall dt out inp clauses. (InstrCaseC dt inp out, RMap (CaseClauses dt), RecFromTuple clauses, clauses ~ Rec (CaseClauseL inp out) (CaseClauses dt)) => IsoRecTuple clauses -> (dt & inp) :-> out Source #

Like case_, accepts a tuple of clauses, which may be more convenient.

(/->) :: Label ("c" `AppendSymbol` ctor) -> (AppendCtorField x inp :-> out) -> CaseClauseL inp out (CaseClauseParam ctor x) infixr 0 Source #

Lift an instruction to case clause.

You should write out constructor name corresponding to the clause explicitly. Prefix constructor name with "c" letter, otherwise your label will not be recognized by Haskell parser. Passing constructor name can be circumvented but doing so is not recomended as mentioning contructor name improves readability and allows avoiding some mistakes.

Useful re-exports

data Rec (a :: u -> Type) (b :: [u]) :: forall u. (u -> Type) -> [u] -> Type where #

A record is parameterized by a universe u, an interpretation f and a list of rows rs. The labels or indices of the record are given by inhabitants of the kind u; the type of values at any label r :: u is given by its interpretation f r :: *.

Constructors

RNil :: forall u (a :: u -> Type) (b :: [u]). Rec a ([] :: [u]) 
(:&) :: forall u (a :: u -> Type) (b :: [u]) (r :: u) (rs :: [u]). !(a r) -> !(Rec a rs) -> Rec a (r ': rs) infixr 7 
Instances
RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) Z 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f :: Constraint #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (r ': rs) -> g (Rec f (r' ': rs)) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (r ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (r ': rs) -> Rec f (r' ': rs) #

(RIndex r (s ': rs) ~ S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) (S i) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f :: Constraint #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (s ': rs) -> g (Rec f (s ': rs')) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (s ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (s ': rs) -> Rec f (s ': rs') #

RecSubset (Rec :: (k -> Type) -> [k] -> Type) ([] :: [k]) (ss :: [k]) ([] :: [Nat]) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f :: Constraint #

Methods

rsubsetC :: (Functor g, RecSubsetFCtx Rec f) => (Rec f [] -> g (Rec f [])) -> Rec f ss -> g (Rec f ss) #

rcastC :: RecSubsetFCtx Rec f => Rec f ss -> Rec f [] #

rreplaceC :: RecSubsetFCtx Rec f => Rec f [] -> Rec f ss -> Rec f ss #

(RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f :: Constraint #

Methods

rsubsetC :: (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) #

rcastC :: RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) #

rreplaceC :: RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss #

TestCoercion f => TestCoercion (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testCoercion :: Rec f a -> Rec f b -> Maybe (Coercion a b) #

TestEquality f => TestEquality (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testEquality :: Rec f a -> Rec f b -> Maybe (a :~: b) #

Eq (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f [] -> Rec f [] -> Bool #

(/=) :: Rec f [] -> Rec f [] -> Bool #

(Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(/=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

Ord (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f [] -> Rec f [] -> Ordering #

(<) :: Rec f [] -> Rec f [] -> Bool #

(<=) :: Rec f [] -> Rec f [] -> Bool #

(>) :: Rec f [] -> Rec f [] -> Bool #

(>=) :: Rec f [] -> Rec f [] -> Bool #

max :: Rec f [] -> Rec f [] -> Rec f [] #

min :: Rec f [] -> Rec f [] -> Rec f [] #

(Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering #

(<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Instance details

Defined in Data.Vinyl.Core

Methods

showsPrec :: Int -> Rec f rs -> ShowS #

show :: Rec f rs -> String #

showList :: [Rec f rs] -> ShowS #

Generic (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f []) :: Type -> Type #

Methods

from :: Rec f [] -> Rep (Rec f []) x #

to :: Rep (Rec f []) x -> Rec f [] #

Generic (Rec f rs) => Generic (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f (r ': rs)) :: Type -> Type #

Methods

from :: Rec f (r ': rs) -> Rep (Rec f (r ': rs)) x #

to :: Rep (Rec f (r ': rs)) x -> Rec f (r ': rs) #

Semigroup (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f [] -> Rec f [] -> Rec f [] #

sconcat :: NonEmpty (Rec f []) -> Rec f [] #

stimes :: Integral b => b -> Rec f [] -> Rec f [] #

(Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

sconcat :: NonEmpty (Rec f (r ': rs)) -> Rec f (r ': rs) #

stimes :: Integral b => b -> Rec f (r ': rs) -> Rec f (r ': rs) #

Monoid (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f [] #

mappend :: Rec f [] -> Rec f [] -> Rec f [] #

mconcat :: [Rec f []] -> Rec f [] #

(Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f (r ': rs) #

mappend :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

mconcat :: [Rec f (r ': rs)] -> Rec f (r ': rs) #

Storable (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f [] -> Int #

alignment :: Rec f [] -> Int #

peekElemOff :: Ptr (Rec f []) -> Int -> IO (Rec f []) #

pokeElemOff :: Ptr (Rec f []) -> Int -> Rec f [] -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f []) #

pokeByteOff :: Ptr b -> Int -> Rec f [] -> IO () #

peek :: Ptr (Rec f []) -> IO (Rec f []) #

poke :: Ptr (Rec f []) -> Rec f [] -> IO () #

(Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f (r ': rs) -> Int #

alignment :: Rec f (r ': rs) -> Int #

peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) #

pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) #

pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () #

peek :: Ptr (Rec f (r ': rs)) -> IO (Rec f (r ': rs)) #

poke :: Ptr (Rec f (r ': rs)) -> Rec f (r ': rs) -> IO () #

RecFromTuple (Rec f ([] :: [u])) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f []) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f []) -> Rec f [] Source #

RecFromTuple (Rec f (x ': ([] :: [u]))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x ': [])) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x ': [])) -> Rec f (x ': []) Source #

RecFromTuple (Rec f (x1 ': (x2 ': ([] :: [u])))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': []))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': []))) -> Rec f (x1 ': (x2 ': [])) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': ([] :: [u]))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': [])))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': [])))) -> Rec f (x1 ': (x2 ': (x3 ': []))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': ([] :: [u])))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': []))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': []))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': [])))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': ([] :: [u]))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': [])))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': [])))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': []))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': ([] :: [u])))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': []))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': []))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': [])))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': ([] :: [u]))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': [])))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': [])))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': []))))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': ([] :: [u])))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': []))))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': []))))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': [])))))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': ([] :: [u]))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': [])))))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': [])))))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': []))))))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': ([] :: [u])))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': []))))))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': []))))))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': [])))))))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': ([] :: [u]))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': [])))))))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': [])))))))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': []))))))))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': ([] :: [u])))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': []))))))))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': []))))))))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': [])))))))))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': ([] :: [u]))))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': [])))))))))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': [])))))))))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': []))))))))))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': ([] :: [u])))))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': []))))))))))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': []))))))))))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': [])))))))))))))) Source #

RecFromTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': (x15 ': ([] :: [u]))))))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

Associated Types

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': (x15 ': [])))))))))))))))) :: Type Source #

Methods

recFromTuple :: IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': (x15 ': [])))))))))))))))) -> Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': (x15 ': []))))))))))))))) Source #

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type Rep (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

type Rep (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': (x15 ': ([] :: [u]))))))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': (x15 ': ([] :: [u]))))))))))))))))) = (f x1, f x2, f x3, f x4, f x5, f x6, f x7, f x8, f x9, f x10, f x11, f x12, f x13, f x14, f x15)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': ([] :: [u])))))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': (x14 ': ([] :: [u])))))))))))))))) = (f x1, f x2, f x3, f x4, f x5, f x6, f x7, f x8, f x9, f x10, f x11, f x12, f x13, f x14)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': ([] :: [u]))))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': (x13 ': ([] :: [u]))))))))))))))) = (f x1, f x2, f x3, f x4, f x5, f x6, f x7, f x8, f x9, f x10, f x11, f x12, f x13)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': ([] :: [u])))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': (x12 ': ([] :: [u])))))))))))))) = (f x1, f x2, f x3, f x4, f x5, f x6, f x7, f x8, f x9, f x10, f x11, f x12)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': ([] :: [u]))))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': (x11 ': ([] :: [u]))))))))))))) = (f x1, f x2, f x3, f x4, f x5, f x6, f x7, f x8, f x9, f x10, f x11)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': ([] :: [u])))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': (x10 ': ([] :: [u])))))))))))) = (f x1, f x2, f x3, f x4, f x5, f x6, f x7, f x8, f x9, f x10)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': ([] :: [u]))))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': (x9 ': ([] :: [u]))))))))))) = (f x1, f x2, f x3, f x4, f x5, f x6, f x7, f x8, f x9)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': ([] :: [u])))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': (x8 ': ([] :: [u])))))))))) = (f x1, f x2, f x3, f x4, f x5, f x6, f x7, f x8)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': ([] :: [u]))))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': (x7 ': ([] :: [u]))))))))) = (f x1, f x2, f x3, f x4, f x5, f x6, f x7)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': ([] :: [u])))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': (x6 ': ([] :: [u])))))))) = (f x1, f x2, f x3, f x4, f x5, f x6)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': ([] :: [u]))))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': (x5 ': ([] :: [u]))))))) = (f x1, f x2, f x3, f x4, f x5)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': ([] :: [u])))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': (x4 ': ([] :: [u])))))) = (f x1, f x2, f x3, f x4)
type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': ([] :: [u]))))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': (x3 ': ([] :: [u]))))) = (f x1, f x2, f x3)
type IsoRecTuple (Rec f (x1 ': (x2 ': ([] :: [u])))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x1 ': (x2 ': ([] :: [u])))) = (f x1, f x2)
type IsoRecTuple (Rec f (x ': ([] :: [u]))) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f (x ': ([] :: [u]))) = f x
type IsoRecTuple (Rec f ([] :: [u])) Source # 
Instance details

Defined in Util.TypeTuple.Instances

type IsoRecTuple (Rec f ([] :: [u])) = ()

type (:!) (name :: Symbol) a = NamedF Identity a name #

Infix notation for the type of a named parameter.

type (:?) (name :: Symbol) a = NamedF Maybe a name #

Infix notation for the type of an optional named parameter.

arg :: Name name -> (name :! a) -> a #

arg unwraps a named parameter with the specified name. One way to use it is to match on arguments with -XViewPatterns:

fn (arg #t -> t) (arg #f -> f) = ...

This way, the names of parameters can be inferred from the patterns: no type signature for fn is required. In case a type signature for fn is provided, the parameters must come in the same order:

fn :: "t" :! Integer -> "f" :! Integer -> ...
fn (arg #t -> t) (arg #f -> f) = ... -- ok
fn (arg #f -> f) (arg #t -> t) = ... -- does not typecheck