ivory-0.1.0.0: Safe embedded C programming.

Safe HaskellNone

Ivory.Language.Syntax.AST

Synopsis

Documentation

type ModulePath = StringSource

An external module that defines an imported resource. A header file in C is an example of this.

data Visible a Source

Constructors

Visible 

Fields

public :: [a]
 
private :: [a]
 

Instances

Eq a => Eq (Visible a) 
Ord a => Ord (Visible a) 
Show a => Show (Visible a) 
Monoid (Visible a) 
Lift a0 => Lift (Visible a0) 

type ModuleName = StringSource

The name of a module defined in Ivory.

data Extern Source

Functions not defined in a header, but are available to the linker.

Constructors

Extern 

data Import Source

Functions that are defined in a c header.

Constructors

Import 

data Proc Source

Functions defined in the language.

Constructors

Proc 

Instances

data Area Source

Constructors

Area 

Instances

type Block = [Stmt]Source

data Stmt Source

Constructors

IfTE Expr Block Block

If-then-else statement. The Expr argument will be typed as an IBool.

Assert Expr

Boolean-valued assertions. The Expr argument will be typed as an IBool.

CompilerAssert Expr

Compiler-inserted assertion (as opposed to user-level assertions). These are expected to be correct (e.g., no overflow, etc). Not exported.

Assume Expr

Boolean-valued assumptions. The Expr argument will be typed as an IBool.

Return (Typed Expr)

Returning a value.

ReturnVoid

Returning void.

Deref Type Var Expr

Reference dereferencing. The type parameter refers to the type of the referenced value, not the reference itself; the expression to be dereferenced is assumed to always be a reference.

Store Type Expr Expr

Storing to a reference. The type parameter refers to the type of the referenced value, not the reference itself; the expression to be dereferenced is assumed to always be a reference.

Assign Type Var Expr

Simple assignment.

Call Type (Maybe Var) Name [Typed Expr]

Function call. The optional variable is where to store the result. It is expected that the Expr passed for the function symbol will have the same type as the combination of the types for the arguments, and the return type.

Local Type Var Init

Stack allocation. The type parameter is not a reference at this point; references are allocated separately to the stack-allocated data.

RefCopy Type Expr Expr

Ref copy. Copy the second variable reference to the fist (like memcopy). The type is the dereferenced value of the variables.

AllocRef Type Var Name

Reference allocation. The type parameter is not a reference, but the referenced type.

Loop Var Expr LoopIncr Block

Looping: arguments are the loop variable, start value, break condition (for increment or decrement), and block.

Forever Block

Nonterminting loop

Break

Break out of a loop

Instances

data Name Source

Constructors

NameSym Sym 
NameVar Var 

Instances

data Cond Source

Constructors

CondBool Expr

Boolean Expressions

CondDeref Type Expr Var Cond

Dereference introduction. The type is the type of the dereferenced thing, not the reference itself.

Instances

newtype Require Source

Constructors

Require 

Fields

getRequire :: Cond
 

newtype Ensure Source

Ensure statements describe properties of the return value for the function they annotate. The return value is referenced through the special internal variable, retval.

Constructors

Ensure 

Fields

getEnsure :: Cond
 

data Expr Source

Constructors

ExpSym Sym

Symbols

ExpVar Var

Variables

ExpLit Literal

Literals

ExpLabel Type Expr String

Struct label indexing.

ExpIndex Type Expr Type Expr

Array indexing. The type is the type of the array being indexed, it's implied that the expression with the array in it is a reference.

ExpToIx Expr Integer

Cast from an expression to an index (Ix) used in loops and array indexing. The Integer is the maximum bound.

ExpSafeCast Type Expr

Type-safe casting. The type is the type casted from.

ExpOp ExpOp [Expr]

Primitive expression operators

ExpAddrOfGlobal Sym

Take the address of a global memory area, introduced through a MemArea *only*.

ExpMaxMin Bool

True is max value, False is min value for the type.

zeroInit :: InitSource

An initializer with no InitExpr fields corresponds to {0}.

data Init Source

Constructors

InitZero
 {}
InitExpr Type Expr
 expr
InitStruct [(String, Init)]
 { .f1 = i1, ..., .fn = in }
InitArray [Init]
 { i1, ..., in }

Instances