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

Indigo.Internal.Var

Synopsis

Variables

data Var a Source #

A variable referring to an element in the stack.

Constructors

Var RefId 

Instances

Instances details
Show (Var a) Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

showsPrec :: Int -> Var a -> ShowS #

show :: Var a -> String #

showList :: [Var a] -> ShowS #

Generic (Var a) Source # 
Instance details

Defined in Indigo.Internal.Var

Associated Types

type Rep (Var a) :: Type -> Type #

Methods

from :: Var a -> Rep (Var a) x #

to :: Rep (Var a) x -> Var a #

Buildable (Var a) Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

build :: Var a -> Builder #

type Rep (Var a) Source # 
Instance details

Defined in Indigo.Internal.Var

type Rep (Var a) = D1 ('MetaData "Var" "Indigo.Internal.Var" "indigo-0.5.0-inplace" 'False) (C1 ('MetaCons "Var" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RefId)))

data RefId Source #

Reference id to a stack cell

Instances

Instances details
Bounded RefId Source # 
Instance details

Defined in Indigo.Internal.Var

Eq RefId Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

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

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

Num RefId Source # 
Instance details

Defined in Indigo.Internal.Var

Ord RefId Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

compare :: RefId -> RefId -> Ordering #

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

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

(>) :: RefId -> RefId -> Bool #

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

max :: RefId -> RefId -> RefId #

min :: RefId -> RefId -> RefId #

Real RefId Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

toRational :: RefId -> Rational #

Show RefId Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

showsPrec :: Int -> RefId -> ShowS #

show :: RefId -> String #

showList :: [RefId] -> ShowS #

Generic RefId Source # 
Instance details

Defined in Indigo.Internal.Var

Associated Types

type Rep RefId :: Type -> Type #

Methods

from :: RefId -> Rep RefId x #

to :: Rep RefId x -> RefId #

Buildable RefId Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

build :: RefId -> Builder #

type Rep RefId Source # 
Instance details

Defined in Indigo.Internal.Var

type Rep RefId = D1 ('MetaData "RefId" "Indigo.Internal.Var" "indigo-0.5.0-inplace" 'True) (C1 ('MetaCons "RefId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

data StackVars (stk :: [Type]) where Source #

Stack of the symbolic interpreter.

Constructors

StkElements :: Rec StkEl stk -> StackVars stk 
FailureStack :: StackVars stk 

Instances

Instances details
(KnownValue x, Default (StackVars xs)) => Default (StackVars (x ': xs)) Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

def :: StackVars (x ': xs) #

Default (StackVars ('[] :: [Type])) Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

def :: StackVars '[] #

type StackVars' stk = Rec StkEl stk Source #

data StkEl a where Source #

Stack element of the symbolic interpreter.

It holds either a reference index that refers to this element or just NoRef, indicating that there are no references to this element.

Constructors

NoRef :: KnownValue a => StkEl a 
Ref :: KnownValue a => RefId -> StkEl a 

Instances

Instances details
TestEquality StkEl Source # 
Instance details

Defined in Indigo.Internal.Var

Methods

testEquality :: forall (a :: k) (b :: k). StkEl a -> StkEl b -> Maybe (a :~: b) #

Stack operations

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

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

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

pushRef :: KnownValue a => Var a -> StackVars inp -> StackVars (a ': inp) Source #

Push a new stack element with a reference to it, given the variable.

pushNoRef :: KnownValue a => StackVars inp -> StackVars (a ': inp) Source #

Push a new stack element without a reference to it.

popNoRef :: StackVars (a ': inp) -> StackVars 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), KnownValue 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