domain-core-0.1.0.3: Low-level API of "domain"
Safe HaskellSafe-Inferred
LanguageHaskell2010

DomainCore.Model

Description

High-level model of schema.

Synopsis

Documentation

data TypeDec Source #

Declaration of a type.

Constructors

TypeDec Text TypeDef

Name of the type and its definition.

Instances

Instances details
Generic TypeDec Source # 
Instance details

Defined in DomainCore.Model

Associated Types

type Rep TypeDec :: Type -> Type #

Methods

from :: TypeDec -> Rep TypeDec x #

to :: Rep TypeDec x -> TypeDec #

Show TypeDec Source # 
Instance details

Defined in DomainCore.Model

Eq TypeDec Source # 
Instance details

Defined in DomainCore.Model

Methods

(==) :: TypeDec -> TypeDec -> Bool #

(/=) :: TypeDec -> TypeDec -> Bool #

Ord TypeDec Source # 
Instance details

Defined in DomainCore.Model

Lift TypeDec Source # 
Instance details

Defined in DomainCore.Model

Methods

lift :: Quote m => TypeDec -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TypeDec -> Code m TypeDec #

type Rep TypeDec Source # 
Instance details

Defined in DomainCore.Model

type Rep TypeDec = D1 ('MetaData "TypeDec" "DomainCore.Model" "domain-core-0.1.0.3-4l3KoVOJPEQ3bbwSkn4nIf" 'False) (C1 ('MetaCons "TypeDec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TypeDef)))

data TypeDef Source #

Definition of a type.

Constructors

SumTypeDef [(Text, [Type])]

Sum. A list of pairs of names of its members (which will be mapped to constructors) and types which will populate the according constructors.

ProductTypeDef [(Text, Type)]

Product. Think of it as a record. Carries a list of associations of field names with types.

Instances

Instances details
Generic TypeDef Source # 
Instance details

Defined in DomainCore.Model

Associated Types

type Rep TypeDef :: Type -> Type #

Methods

from :: TypeDef -> Rep TypeDef x #

to :: Rep TypeDef x -> TypeDef #

Show TypeDef Source # 
Instance details

Defined in DomainCore.Model

Eq TypeDef Source # 
Instance details

Defined in DomainCore.Model

Methods

(==) :: TypeDef -> TypeDef -> Bool #

(/=) :: TypeDef -> TypeDef -> Bool #

Ord TypeDef Source # 
Instance details

Defined in DomainCore.Model

Lift TypeDef Source # 
Instance details

Defined in DomainCore.Model

Methods

lift :: Quote m => TypeDef -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TypeDef -> Code m TypeDef #

type Rep TypeDef Source # 
Instance details

Defined in DomainCore.Model

type Rep TypeDef = D1 ('MetaData "TypeDef" "DomainCore.Model" "domain-core-0.1.0.3-4l3KoVOJPEQ3bbwSkn4nIf" 'False) (C1 ('MetaCons "SumTypeDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(Text, [Type])])) :+: C1 ('MetaCons "ProductTypeDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(Text, Type)])))

data Type Source #

Type.

Constructors

TupleType [Type]

Fully applied tuple of the listed types.

AppType (NonEmpty Type)

List of type applications.

ListType Type

List type with the type of its element.

RefType Text

Possibly qualified reference to another type.

Instances

Instances details
Generic Type Source # 
Instance details

Defined in DomainCore.Model

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Show Type Source # 
Instance details

Defined in DomainCore.Model

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type Source # 
Instance details

Defined in DomainCore.Model

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Ord Type Source # 
Instance details

Defined in DomainCore.Model

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Lift Type Source # 
Instance details

Defined in DomainCore.Model

Methods

lift :: Quote m => Type -> m Exp #

liftTyped :: forall (m :: Type0 -> Type0). Quote m => Type -> Code m Type #

type Rep Type Source # 
Instance details

Defined in DomainCore.Model