clash-lib-1.0.0: CAES Language for Synchronous Hardware - As a Library
Copyright(C) 2017 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Core.Evaluator

Description

Call-by-need evaluator based on the evaluator described in:

Maximilian Bolingbroke, Simon Peyton Jones, "Supercompilation by evaluation", Haskell '10, Baltimore, Maryland, USA.

Synopsis

Documentation

newtype GPureHeap Source #

Constructors

GPureHeap 

type GlobalHeap = (IntMap Term, Int) Source #

Global heap

type Stack = [StackFrame] Source #

The stack

data Value Source #

Constructors

Lambda Id Term

Functions

TyLambda TyVar Term

Type abstractions

DC DataCon [Either Term Type]

Data constructors

Lit Literal

Literals

PrimVal Text 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

Instances

Instances details
Show Value Source # 
Instance details

Defined in Clash.Core.Evaluator

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

type State = (Heap, Stack, Term) Source #

State of the evaluator

type PrimEvaluator = Bool -> TyConMap -> Heap -> Stack -> Text -> PrimInfo -> [Type] -> [Value] -> Maybe State Source #

Function that can evaluator primitives, i.e., perform delta-reduction

whnf' :: PrimEvaluator -> BindingMap -> TyConMap -> GlobalHeap -> Supply -> InScopeSet -> Bool -> Term -> (GlobalHeap, PureHeap, Term) Source #

Evaluate to WHNF starting with an empty Heap and Stack

whnf :: PrimEvaluator -> TyConMap -> Bool -> State -> State Source #

Evaluate to WHNF given an existing Heap and Stack

isScrut :: Stack -> Bool Source #

Are we in a context where special primitives must be forced.

See [Note: forcing special primitives]

unwindStack :: State -> Maybe State Source #

Completely unwind the stack to get back the complete term

step :: PrimEvaluator -> TyConMap -> State -> Maybe State Source #

Small-step operational semantics.

force :: Heap -> Stack -> Id -> Maybe State Source #

Force the evaluation of a variable.

unwind :: PrimEvaluator -> TyConMap -> Heap -> Stack -> Value -> Maybe State Source #

Unwind the stack by 1

update :: Heap -> Stack -> Id -> Value -> State Source #

Update the Heap with the evaluated term

gupdate :: Heap -> Stack -> Id -> Value -> State Source #

Update the Globals with the evaluated term

apply :: Heap -> Stack -> Value -> Id -> State Source #

Apply a value to a function

instantiate :: Heap -> Stack -> Value -> Type -> State Source #

Instantiate a type-abstraction

primop Source #

Arguments

:: PrimEvaluator 
-> TyConMap 
-> Heap 
-> Stack 
-> Text

Name of the primitive

-> PrimInfo

Type of the primitive

-> [Type]

Applied types

-> [Value]

Applied values

-> Value

The current value

-> [Term]

The remaining terms which must be evaluated to a value

-> Maybe State 

Evaluation of primitive operations

scrutinise :: Heap -> Stack -> Value -> [Alt] -> State Source #

Evaluate a case-expression

substAlt :: DataCon -> [TyVar] -> [Id] -> [Either Term Type] -> Term -> Term Source #

allocate :: Heap -> Stack -> [LetBinding] -> Term -> State Source #

Allocate let-bindings on the heap

letSubst :: PureHeap -> Supply -> Id -> (Supply, (Id, (Id, Term))) Source #

Create a unique name and substitution for a let-binder

uniqueInHeap :: PureHeap -> Supply -> Id -> (Supply, Id) Source #

Create a name that's unique in the heap