ivory-0.1.0.9: Safe embedded C programming.

Safe HaskellNone
LanguageHaskell2010

Ivory.Language.Syntax.AST

Contents

Synopsis

Documentation

type ModulePath = String Source #

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

Instances
Eq a => Eq (Visible a) Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

(==) :: Visible a -> Visible a -> Bool #

(/=) :: Visible a -> Visible a -> Bool #

Ord a => Ord (Visible a) Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

compare :: Visible a -> Visible a -> Ordering #

(<) :: Visible a -> Visible a -> Bool #

(<=) :: Visible a -> Visible a -> Bool #

(>) :: Visible a -> Visible a -> Bool #

(>=) :: Visible a -> Visible a -> Bool #

max :: Visible a -> Visible a -> Visible a #

min :: Visible a -> Visible a -> Visible a #

Show a => Show (Visible a) Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

show :: Visible a -> String #

showList :: [Visible a] -> ShowS #

Semigroup (Visible a) Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

(<>) :: Visible a -> Visible a -> Visible a #

sconcat :: NonEmpty (Visible a) -> Visible a #

stimes :: Integral b => b -> Visible a -> Visible a #

Monoid (Visible a) Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

mempty :: Visible a #

mappend :: Visible a -> Visible a -> Visible a #

mconcat :: [Visible a] -> Visible a #

Lift a => Lift (Visible a) Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Visible a -> Q Exp #

type ModuleName = String Source #

The name of a module defined in Ivory.

data Module Source #

Constructors

Module 

Fields

Instances
Eq Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Show Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Semigroup Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Monoid Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Lift Module Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Module -> Q Exp #

WriterM ModuleM Module Source # 
Instance details

Defined in Ivory.Language.Module

Methods

put :: Module -> ModuleM () #

data Import Source #

Functions that are defined in a c header.

Instances
Eq Import Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Import Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Show Import Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Lift Import Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Import -> Q Exp #

data Proc Source #

Functions defined in the language.

Constructors

Proc 
Instances
Eq Proc Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Proc Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

compare :: Proc -> Proc -> Ordering #

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

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

(>) :: Proc -> Proc -> Bool #

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

max :: Proc -> Proc -> Proc #

min :: Proc -> Proc -> Proc #

Show Proc Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

showsPrec :: Int -> Proc -> ShowS #

show :: Proc -> String #

showList :: [Proc] -> ShowS #

Lift Proc Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Proc -> Q Exp #

data Struct Source #

Instances
Eq Struct Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Struct Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Show Struct Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Lift Struct Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Struct -> Q Exp #

data Area Source #

Constructors

Area 
Instances
Eq Area Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Area Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

compare :: Area -> Area -> Ordering #

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

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

(>) :: Area -> Area -> Bool #

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

max :: Area -> Area -> Area #

min :: Area -> Area -> Area #

Show Area Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

showsPrec :: Int -> Area -> ShowS #

show :: Area -> String #

showList :: [Area] -> ShowS #

Lift Area Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Area -> Q Exp #

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 first (like memcopy). The type is the dereferenced value of the variables.

RefZero Type Expr

Ref zero. Zero out the memory associated with the reference. The type parameter is not a reference, but the referenced type.

AllocRef Type Var Name

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

Loop Integer Var Expr LoopIncr Block

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

Forever Block

Nonterminting loop

Break

Break out of a loop

Comment Comment

User comment, can be used to output a comment in the backend.

Instances
Eq Stmt Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Stmt Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

compare :: Stmt -> Stmt -> Ordering #

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

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

(>) :: Stmt -> Stmt -> Bool #

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

max :: Stmt -> Stmt -> Stmt #

min :: Stmt -> Stmt -> Stmt #

Show Stmt Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

showsPrec :: Int -> Stmt -> ShowS #

show :: Stmt -> String #

showList :: [Stmt] -> ShowS #

Lift Stmt Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Stmt -> Q Exp #

data LoopIncr Source #

Constructors

IncrTo Expr 
DecrTo Expr 
Instances
Eq LoopIncr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Ord LoopIncr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Show LoopIncr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Lift LoopIncr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: LoopIncr -> Q Exp #

data Name Source #

Constructors

NameSym Sym 
NameVar Var 
Instances
Eq Name Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Name Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Lift Name Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Name -> Q Exp #

data Comment Source #

Instances
Eq Comment Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Comment Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Show Comment Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Lift Comment Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Comment -> Q Exp #

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
Eq Cond Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Cond Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

compare :: Cond -> Cond -> Ordering #

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

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

(>) :: Cond -> Cond -> Bool #

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

max :: Cond -> Cond -> Cond #

min :: Cond -> Cond -> Cond #

Show Cond Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

showsPrec :: Int -> Cond -> ShowS #

show :: Cond -> String #

showList :: [Cond] -> ShowS #

Lift Cond Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Cond -> Q Exp #

newtype Require Source #

Constructors

Require 

Fields

Instances
Eq Require Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Require Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Show Require Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Lift Require Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Require -> Q Exp #

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

Instances
Eq Ensure Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Ensure Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Show Ensure Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Lift Ensure Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Ensure -> Q Exp #

data Extern Source #

External Symbols.

Constructors

Extern 
Instances
Eq Extern Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Extern Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Show Extern Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Lift Extern Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Extern -> Q Exp #

data Expr Source #

Constructors

ExpSym Sym

Symbols

ExpExtern Extern

Imported 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.

ExpSizeOf Type

Return the allocation size of the given type.

Instances
Bounded Expr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Eq Expr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Floating Expr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

pi :: Expr #

exp :: Expr -> Expr #

log :: Expr -> Expr #

sqrt :: Expr -> Expr #

(**) :: Expr -> Expr -> Expr #

logBase :: Expr -> Expr -> Expr #

sin :: Expr -> Expr #

cos :: Expr -> Expr #

tan :: Expr -> Expr #

asin :: Expr -> Expr #

acos :: Expr -> Expr #

atan :: Expr -> Expr #

sinh :: Expr -> Expr #

cosh :: Expr -> Expr #

tanh :: Expr -> Expr #

asinh :: Expr -> Expr #

acosh :: Expr -> Expr #

atanh :: Expr -> Expr #

log1p :: Expr -> Expr #

expm1 :: Expr -> Expr #

log1pexp :: Expr -> Expr #

log1mexp :: Expr -> Expr #

Fractional Expr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

(/) :: Expr -> Expr -> Expr #

recip :: Expr -> Expr #

fromRational :: Rational -> Expr #

Num Expr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

(+) :: Expr -> Expr -> Expr #

(-) :: Expr -> Expr -> Expr #

(*) :: Expr -> Expr -> Expr #

negate :: Expr -> Expr #

abs :: Expr -> Expr #

signum :: Expr -> Expr #

fromInteger :: Integer -> Expr #

Ord Expr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

compare :: Expr -> Expr -> Ordering #

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

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

(>) :: Expr -> Expr -> Bool #

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

max :: Expr -> Expr -> Expr #

min :: Expr -> Expr -> Expr #

Show Expr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Lift Expr Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Expr -> Q Exp #

zeroInit :: Init Source #

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] Bool

{ i1, ..., in } Bool true if no unused initialization values.

Instances
Eq Init Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

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

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

Ord Init Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

compare :: Init -> Init -> Ordering #

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

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

(>) :: Init -> Init -> Bool #

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

max :: Init -> Init -> Init #

min :: Init -> Init -> Init #

Show Init Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

showsPrec :: Int -> Init -> ShowS #

show :: Init -> String #

showList :: [Init] -> ShowS #

Lift Init Source # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Init -> Q Exp #

Orphan instances

Lift Position Source # 
Instance details

Methods

lift :: Position -> Q Exp #

Lift Range Source # 
Instance details

Methods

lift :: Range -> Q Exp #

Lift SrcLoc Source # 
Instance details

Methods

lift :: SrcLoc -> Q Exp #