| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ivory.Language.Syntax.AST
Contents
Synopsis
- type ModulePath = String
- data Visible a = Visible {}
- type ModuleName = String
- data Module = Module {
- modName :: ModuleName
- modHeaders :: [FilePath]
- modDepends :: [ModuleName]
- modExterns :: [Extern]
- modImports :: [Import]
- modProcs :: Visible Proc
- modStructs :: Visible Struct
- modAreas :: Visible Area
- modAreaImports :: [AreaImport]
- data Import = Import {
- importSym :: Sym
- importFile :: ModulePath
- importRetTy :: Type
- importArgs :: [Typed Var]
- importRequires :: [Require]
- importEnsures :: [Ensure]
- data Proc = Proc {}
- data Struct
- structName :: Struct -> String
- data Area = Area {}
- data AreaImport = AreaImport {}
- type Block = [Stmt]
- data Stmt
- = IfTE Expr Block Block
- | Assert Expr
- | CompilerAssert Expr
- | Assume Expr
- | Return (Typed Expr)
- | ReturnVoid
- | Deref Type Var Expr
- | Store Type Expr Expr
- | Assign Type Var Expr
- | Call Type (Maybe Var) Name [Typed Expr]
- | Local Type Var Init
- | RefCopy Type Expr Expr
- | RefZero Type Expr
- | AllocRef Type Var Name
- | Loop Integer Var Expr LoopIncr Block
- | Forever Block
- | Break
- | Comment Comment
- data LoopIncr
- data Name
- data Comment
- data Cond
- newtype Require = Require {
- getRequire :: Cond
- newtype Ensure = Ensure {}
- data Extern = Extern {
- externSym :: Sym
- externFile :: ModulePath
- externType :: Type
- data Expr
- data ExpOp
- = ExpEq Type
- | ExpNeq Type
- | ExpCond
- | ExpGt Bool Type
- | ExpLt Bool Type
- | ExpNot
- | ExpAnd
- | ExpOr
- | ExpMul
- | ExpAdd
- | ExpSub
- | ExpNegate
- | ExpAbs
- | ExpSignum
- | ExpDiv
- | ExpMod
- | ExpRecip
- | ExpFExp
- | ExpFSqrt
- | ExpFLog
- | ExpFPow
- | ExpFLogBase
- | ExpFSin
- | ExpFTan
- | ExpFCos
- | ExpFAsin
- | ExpFAtan
- | ExpFAtan2
- | ExpFAcos
- | ExpFSinh
- | ExpFTanh
- | ExpFCosh
- | ExpFAsinh
- | ExpFAtanh
- | ExpFAcosh
- | ExpIsNan Type
- | ExpIsInf Type
- | ExpRoundF
- | ExpCeilF
- | ExpFloorF
- | ExpBitAnd
- | ExpBitOr
- | ExpBitXor
- | ExpBitComplement
- | ExpBitShiftL
- | ExpBitShiftR
- data Literal
- zeroInit :: Init
- data Init
Documentation
type ModulePath = String Source #
An external module that defines an imported resource. A header file in C is an example of this.
Instances
| Eq a => Eq (Visible a) Source # | |
| Ord a => Ord (Visible a) Source # | |
| Show a => Show (Visible a) Source # | |
| Semigroup (Visible a) Source # | |
| Monoid (Visible a) Source # | |
| Lift a => Lift (Visible a) Source # | |
type ModuleName = String Source #
The name of a module defined in Ivory.
Constructors
| Module | |
Fields
| |
Functions that are defined in a c header.
Constructors
| Import | |
Fields
| |
Functions defined in the language.
Constructors
| Proc | |
structName :: Struct -> String Source #
data AreaImport Source #
Constructors
| AreaImport | |
Instances
| Eq AreaImport Source # | |
Defined in Ivory.Language.Syntax.AST | |
| Ord AreaImport Source # | |
Defined in Ivory.Language.Syntax.AST Methods compare :: AreaImport -> AreaImport -> Ordering # (<) :: AreaImport -> AreaImport -> Bool # (<=) :: AreaImport -> AreaImport -> Bool # (>) :: AreaImport -> AreaImport -> Bool # (>=) :: AreaImport -> AreaImport -> Bool # max :: AreaImport -> AreaImport -> AreaImport # min :: AreaImport -> AreaImport -> AreaImport # | |
| Show AreaImport Source # | |
Defined in Ivory.Language.Syntax.AST Methods showsPrec :: Int -> AreaImport -> ShowS # show :: AreaImport -> String # showList :: [AreaImport] -> ShowS # | |
| Lift AreaImport Source # | |
Defined in Ivory.Language.Syntax.AST Methods lift :: AreaImport -> Q Exp # | |
Constructors
| IfTE Expr Block Block | If-then-else statement. The |
| Assert Expr | Boolean-valued assertions. The |
| 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 |
| 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 |
| 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. |
Constructors
| UserComment String | |
| SourcePos SrcLoc |
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. |
Constructors
| Require | |
Fields
| |
Ensure statements describe properties of the return value for the function they annotate. The return value is referenced through the special internal variable, "retval".
External Symbols.
Constructors
| Extern | |
Fields
| |
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. |
Constructors
Constructors
| LitInteger Integer | |
| LitFloat Float | |
| LitDouble Double | |
| LitChar Char | |
| LitBool Bool | |
| LitNull | |
| LitString String |
Constructors
| InitZero | {} |
| InitExpr Type Expr | expr |
| InitStruct [(String, Init)] | { .f1 = i1, ..., .fn = in } |
| InitArray [Init] Bool |
|