indigo-0.2.2: Convenient imperative eDSL over Lorentz.
Safe HaskellNone
LanguageHaskell2010

Indigo.Internal.Object

Synopsis

Documentation

data IndigoObjectF f a where Source #

A object that can be either stored in the single stack cell or split into fields. Fields are identified by their names.

f is a functor to be applied to each of field names.

Constructors

Cell :: KnownValue a => ~RefId -> IndigoObjectF f a

Value stored on the stack, it might be either complex product type, like (a, b), Storage, etc, or sum type like Either, or primitive like Int, Operation, etc.

Laziness of RefId is needed here to make possible to put error in a variable. This is used as a workaround in Indigo.Compilation.Lambda.

Decomposed :: ComplexObjectC a => Rec f (ConstructorFieldNames a) -> IndigoObjectF f a

Decomposed product type, which is NOT stored as one cell on the stack.

Instances

Instances details
(name ~ AppendSymbol "c" ctor, KnownValue x) => CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))) Source # 
Instance details

Defined in Indigo.Backend.Case

Methods

(/->) :: Label name -> (Var x -> IndigoAnyOut x ret) -> IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x)) #

data NamedFieldVar a name where Source #

Auxiliary datatype to define a variable. Keeps field name as type param

Constructors

NamedFieldVar 

Fields

Instances

Instances details
(name ~ AppendSymbol "c" ctor, KnownValue x) => CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))) Source # 
Instance details

Defined in Indigo.Backend.Case

Methods

(/->) :: Label name -> (Var x -> IndigoAnyOut x ret) -> IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x)) #

data TypedFieldVar a where Source #

Like NamedFieldVar, but this one doesn't keep name of a field

Constructors

TypedFieldVar :: IsObject a => Var a -> TypedFieldVar a 

type Var a = IndigoObjectF (NamedFieldVar a) a Source #

Variable exposed to a user.

Var represents the tree of fields. Each field is Var itself: either a value on the stack or Rec of its direct fields.

namedToTypedRec :: forall a f g. (forall name. f name -> g (GetFieldType a name)) -> Rec f (ConstructorFieldNames a) -> Rec g (FieldTypes a) Source #

Convert a list of fields from name-based list to type-based one

typedToNamedRec :: forall a f g. KnownList (ConstructorFieldNames a) => (forall name. f (GetFieldType a name) -> g name) -> Rec f (FieldTypes a) -> Rec g (ConstructorFieldNames a) Source #

Convert a list of fields from type-based list to named-based one

class IsObject' (TypeDecision a) a => IsObject a Source #

Instances

Instances details
IsObject' (TypeDecision a) a => IsObject a Source # 
Instance details

Defined in Indigo.Internal.Object

complexObjectDict :: forall a. IsObject a => Maybe (Dict (ComplexObjectC a)) Source #

type ComplexObjectC a = (ToDeconstructC a, ToConstructC a, AllConstrained IsObject (FieldTypes a)) Source #

Stack operations

withVarAt :: (KnownValue a, a ~ At n inp, RequireLongerThan inp n) => MetaData inp -> Sing n -> (MetaData inp, Var a) Source #

Given a MetaData and a Peano singleton for a depth, it puts a new Var at that depth (0-indexed) and returns it with the updated MetaData.

If there is a Var there already it is used and the MetaData not changed.

makeTopVar :: KnownValue x => IndigoState (x & inp) (x & inp) (Var x) Source #

Create a variable referencing the element on top of the stack.

pushRefMd :: KnownValue x => MetaData stk -> (Var x, MetaData (x & stk)) Source #

Push a new stack element with a reference to it. Return the variable referencing this element.

pushNoRefMd :: KnownValue a => MetaData inp -> MetaData (a & inp) Source #

Push a new stack element without a reference to it.

popNoRefMd :: MetaData (a & inp) -> MetaData inp Source #

Remove the top element of the stack. It's supposed that no variable refers to this element.

Operations/Storage variables

type HasSideEffects = Given (Var Ops) Source #

Allows to get a variable with operations

operationsVar :: HasSideEffects => Var Ops Source #

Return a variable which refers to a stack cell with operations

type HasStorage st = Given (Var st) Source #

Allows to get a variable with storage

storageVar :: HasStorage st => Var st Source #

Return a variable which refers to a stack cell with storage