| Copyright | (C) 2020 QBayLogic B.V. |
|---|---|
| License | BSD2 (see the file LICENSE) |
| Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
| Safe Haskell | None |
| Language | Haskell2010 |
Clash.Core.Evaluator.Types
Description
Types for the Partial Evaluator
Synopsis
- type PrimStep = TyConMap -> Bool -> PrimInfo -> [Type] -> [Value] -> Machine -> Maybe Machine
- type PrimUnwind = TyConMap -> PrimInfo -> [Type] -> [Value] -> Value -> [Term] -> Machine -> Maybe Machine
- type PrimEvaluator = (PrimStep, PrimUnwind)
- data Machine = Machine {}
- type PrimHeap = (IntMap Term, Int)
- type PureHeap = VarEnv Term
- type Stack = [StackFrame]
- data StackFrame
- data Value
- valToTerm :: Value -> Term
- collectValueTicks :: Value -> (Value, [TickInfo])
- forcePrims :: Machine -> Bool
- primCount :: Machine -> Int
- primLookup :: Int -> Machine -> Maybe Term
- primInsert :: Int -> Term -> Machine -> Machine
- primUpdate :: Int -> Term -> Machine -> Machine
- heapLookup :: IdScope -> Id -> Machine -> Maybe Term
- heapContains :: IdScope -> Id -> Machine -> Bool
- heapInsert :: IdScope -> Id -> Term -> Machine -> Machine
- heapDelete :: IdScope -> Id -> Machine -> Machine
- stackPush :: StackFrame -> Machine -> Machine
- stackPop :: Machine -> Maybe (Machine, StackFrame)
- stackClear :: Machine -> Machine
- stackNull :: Machine -> Bool
- getTerm :: Machine -> Term
- setTerm :: Term -> Machine -> Machine
Documentation
type PrimStep = TyConMap -> Bool -> PrimInfo -> [Type] -> [Value] -> Machine -> Maybe Machine Source #
type PrimUnwind = TyConMap -> PrimInfo -> [Type] -> [Value] -> Value -> [Term] -> Machine -> Maybe Machine Source #
type PrimEvaluator = (PrimStep, PrimUnwind) Source #
Constructors
| Machine | |
Fields
| |
type Stack = [StackFrame] Source #
data StackFrame Source #
Constructors
| Update IdScope Id | |
| Apply Id | |
| Instantiate Type | |
| PrimApply PrimInfo [Type] [Value] [Term] | |
| Scrutinise Type [Alt] | |
| Tickish TickInfo |
Instances
| Show StackFrame Source # | |
Defined in Clash.Core.Evaluator.Types Methods showsPrec :: Int -> StackFrame -> ShowS # show :: StackFrame -> String # showList :: [StackFrame] -> ShowS # | |
| ClashPretty StackFrame Source # | |
Defined in Clash.Core.Evaluator.Types Methods clashPretty :: StackFrame -> Doc () Source # | |
Constructors
| Lambda Id Term | Functions |
| TyLambda TyVar Term | Type abstractions |
| DC DataCon [Either Term Type] | Data constructors |
| Lit Literal | Literals |
| PrimVal PrimInfo [Type] [Value] | Clash's number types are represented by their "fromInteger#" primitive function. So some primitives are values. |
| Suspend Term | Used by lazy primitives |
| TickValue TickInfo Value | Preserve ticks from Terms in Values |
| CastValue Value Type Type | Preserve casts from Terms in Values |
forcePrims :: Machine -> Bool Source #
Are we in a context where special primitives must be forced.
See [Note: forcing special primitives]
stackClear :: Machine -> Machine Source #