uhc-light-1.1.9.0: Part of UHC packaged as cabal/hackage installable library

Safe HaskellNone
LanguageHaskell98

UHC.Light.Compiler.CoreRun.API

Contents

Description

CoreRun Public API

Intended for constructing basic CoreRun Programs.

CoreRun is a simplified Core intended to be used for direct interpretation/execution. For semantics, see TBD

Synopsis

CoreRun AST

The datatypes making up a CoreRun program.

data Exp Source

Instances

data SExp Source

Instances

data Alt Source

Instances

type Bind = Exp Source

Bind, just an Exp, addressing is left implicit

data RRef Source

Identifier references for use during running CoreRun

data Import Source

Instances

data Meta Source

Instances

data DataCon Source

Instances

Utilities

type CRArray x = Vector x Source

Fast access sequence

Construction functions

References

mkLocLevRef :: Int -> Int -> RRef Source

RRef to local or outside scoped, using absolute level and offset (this is to be converted to a level difference + offset encoding for running, see mkLocDifRef)

mkLocDifRef :: Int -> Int -> RRef Source

RRef to local or outside scoped, using level difference (to a current) and offset

mkGlobRef :: Int -> Int -> RRef Source

RRef to global from module, using module nr and offset (will become obsolete, replaced by either Imp or Mod Ref

mkImpRef :: Int -> Int -> RRef Source

RRef to global from module, using module nr and offset

mkModRef :: Int -> RRef Source

RRef to global from current module, using offset

Expressions

mkExp :: SExp -> Exp Source

Lift SExp into Exp

mkVar :: RRef -> Exp Source

Var ref as Exp

mkVar' :: RRef -> SExp Source

Var ref as SExp

mkInt :: Int -> Exp Source

Int constant as Exp

mkInt' :: Int -> SExp Source

Int constant as SExp

mkChar :: Char -> Exp Source

Char constant as Exp

mkChar' :: Char -> SExp Source

Char constant as SExp

mkInteger :: Integer -> Exp Source

Integer constant as Exp

mkInteger' :: Integer -> SExp Source

Integer constant as SExp

mkString :: String -> Exp Source

String constant as Exp

mkString' :: String -> SExp Source

String constant as SExp

mkDbg :: String -> Exp Source

Debug info as Exp

mkDbg' :: String -> SExp Source

Debug info as SExp, will make an interpreter stop with displaying the message

mkApp :: Exp -> [SExp] -> Exp Source

Application

mkApp' :: Exp -> CRArray SExp -> Exp Source

Application

mkTup :: Int -> [SExp] -> Exp Source

Tuple, Node

mkTup' :: Int -> CRArray SExp -> Exp Source

Tuple, Node

mkEval :: Exp -> Exp Source

Force evaluation

mkTail :: Exp -> Exp Source

Set tail call context

mkCase :: SExp -> [Exp] -> Exp Source

Case

mkLam Source

Arguments

:: Int

nr of arguments, 0 encodes a thunk/CAF

-> Int

total stack size, including arguments, locals, expression calculation

-> Exp

body

-> Exp 

Lambda

mkLam' Source

Arguments

:: Maybe HsName

a name for this lambda, to be used for pretty printing

-> Int

nr of arguments, 0 encodes a thunk/CAF

-> Int

total stack size, including arguments, locals, expression calculation

-> Exp

body

-> Exp 

Lambda

mkLet Source

Arguments

:: Int

stackoffset to place bound value

-> [Exp]

bound terms

-> Exp

body

-> Exp 

Let

mkLet' Source

Arguments

:: Int

stackoffset to place bound value

-> CRArray Exp

bound terms

-> Exp

body

-> Exp 

Let

mkFFI Source

Arguments

:: String

name of foreign entity, if unknown results in debug expr

-> [SExp]

args

-> Exp 

FFI

mkFFI' Source

Arguments

:: String

name of foreign entity, if unknown results in debug expr

-> CRArray SExp

args

-> Exp 

FFI

Meta

mkMetaDataCon Source

Arguments

:: HsName

constructor name (without module qualifier, name must be globally unique)

-> Int

constructor tag

-> DataCon 

Meta: datatype constructor info

mkMetaDataType Source

Arguments

:: HsName

datatype name (fully qualified)

-> [DataCon]

constructor tag

-> Meta 

Meta: datatype constructor info

Modules

mkMod Source

Arguments

:: HsName

module name

-> Int

module number

-> Int

total stack size, including globals of module, their setup (see semantics), and the main startup part kicking of evaluation

-> [Bind]

bound expressions

-> Exp

body of main

-> Mod 

Module

mkMod' Source

Arguments

:: HsName

module name

-> Int

module number

-> Int

total stack size, including globals of module, their setup (see semantics), and the main startup part kicking of evaluation

-> CRArray Bind

bound expressions

-> Exp

body of main

-> Mod 

Module

mkModWithMetas Source

Arguments

:: HsName

module name

-> Int

module number

-> Int

total stack size, including globals of module, their setup (see semantics), and the main startup part kicking of evaluation

-> [Meta]

meta info

-> CRArray Bind

bound expressions

-> Exp

body of main

-> Mod 

Module, with meta info

mkModWithImportsMetas Source

Arguments

:: HsName

module name

-> Int

module number

-> Int

total stack size, including globals of module, their setup (see semantics), and the main startup part kicking of evaluation

-> [Import]

imports

-> [Meta]

meta info

-> CRArray Bind

bound expressions

-> Maybe Exp

body of main, absence of main indicated by Nothing

-> Mod 

Module, with imports, with meta info

mkImport Source

Arguments

:: HsName

name of imported module

-> Import 

Meta: datatype constructor info

Conversion

rrefToDif :: Int -> RRef -> RRef Source

Convert to RRef_Loc to RRef_LDf, i.e. absolute level to relative (to current) level

Parsing

parseModFromString :: String -> Either [String] Mod Source

Parses a module. TBD: integration with other parser utils from EHC driver...

Running

runCoreRunIO Source

Arguments

:: EHCOpts

options, e.g. for turning on tracing (if supported by runner)

-> Mod

the module to run

-> IO (Either Err RVal) 

Run CoreRun in IO TBD: fix dependence on whole program linked

Misc utils

printModule :: EHCOpts -> Mod -> PP_Doc Source

Pretty print Mod