Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data IndigoObjectF f a where
- Cell :: KnownValue a => ~RefId -> IndigoObjectF f a
- Decomposed :: ComplexObjectC a => Rec f (ConstructorFieldNames a) -> IndigoObjectF f a
- data NamedFieldVar a name where
- NamedFieldVar :: IsObject (GetFieldType a name) => {..} -> NamedFieldVar a name
- data TypedFieldVar a where
- TypedFieldVar :: IsObject a => Var a -> TypedFieldVar a
- type FieldTypes a = MapGFT a (ConstructorFieldNames a)
- type Var a = IndigoObjectF (NamedFieldVar a) a
- namedToTypedRec :: forall a f g. (forall name. f name -> g (GetFieldType a name)) -> Rec f (ConstructorFieldNames a) -> Rec g (FieldTypes a)
- typedToNamedRec :: forall a f g. KnownList (ConstructorFieldNames a) => (forall name. f (GetFieldType a name) -> g name) -> Rec f (FieldTypes a) -> Rec g (ConstructorFieldNames a)
- namedToTypedFieldVar :: forall a name. NamedFieldVar a name -> TypedFieldVar (GetFieldType a name)
- typedToNamedFieldVar :: forall a name. TypedFieldVar (GetFieldType a name) -> NamedFieldVar a name
- class IsObject' (TypeDecision a) a => IsObject a
- complexObjectDict :: forall a. IsObject a => Maybe (Dict (ComplexObjectC a))
- type ComplexObjectC a = (ToDeconstructC a, ToConstructC a, AllConstrained IsObject (FieldTypes a))
- castFieldConstructors :: forall a st. CastFieldConstructors (FieldTypes a) (ConstructorFieldTypes a) => Rec (FieldConstructor st) (FieldTypes a) -> Rec (FieldConstructor st) (ConstructorFieldTypes a)
- withVarAt :: (KnownValue a, a ~ At n inp, RequireLongerThan inp n) => MetaData inp -> Sing n -> (MetaData inp, Var a)
- makeTopVar :: KnownValue x => IndigoState (x & inp) (x & inp) (Var x)
- pushRefMd :: KnownValue x => MetaData stk -> (Var x, MetaData (x & stk))
- pushNoRefMd :: KnownValue a => MetaData inp -> MetaData (a & inp)
- popNoRefMd :: MetaData (a & inp) -> MetaData inp
- type Ops = [Operation]
- type HasSideEffects = Given (Var Ops)
- operationsVar :: HasSideEffects => Var Ops
- type HasStorage st = Given (Var st)
- storageVar :: HasStorage st => Var st
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.
Cell :: KnownValue a => ~RefId -> IndigoObjectF f a | Value stored on the stack, it might be
either complex product type, like Laziness of |
Decomposed :: ComplexObjectC a => Rec f (ConstructorFieldNames a) -> IndigoObjectF f a | Decomposed product type, which is NOT stored as one cell on the stack. |
Instances
(name ~ AppendSymbol "c" ctor, KnownValue x) => CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))) Source # | |
Defined in Indigo.Backend.Case (/->) :: 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
NamedFieldVar | |
|
Instances
(name ~ AppendSymbol "c" ctor, KnownValue x) => CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))) Source # | |
Defined in Indigo.Backend.Case (/->) :: 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
TypedFieldVar :: IsObject a => Var a -> TypedFieldVar a |
type FieldTypes a = MapGFT a (ConstructorFieldNames a) Source #
type Var a = IndigoObjectF (NamedFieldVar a) a Source #
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
namedToTypedFieldVar :: forall a name. NamedFieldVar a name -> TypedFieldVar (GetFieldType a name) Source #
typedToNamedFieldVar :: forall a name. TypedFieldVar (GetFieldType a name) -> NamedFieldVar a name Source #
class IsObject' (TypeDecision a) a => IsObject a Source #
Instances
IsObject' (TypeDecision a) a => IsObject a Source # | |
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 #
castFieldConstructors :: forall a st. CastFieldConstructors (FieldTypes a) (ConstructorFieldTypes a) => Rec (FieldConstructor st) (FieldTypes a) -> Rec (FieldConstructor st) (ConstructorFieldTypes a) Source #
Stack operations
withVarAt :: (KnownValue a, a ~ At n inp, RequireLongerThan inp n) => MetaData inp -> Sing n -> (MetaData inp, Var a) Source #
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