| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Feldspar.Compiler.Imperative.Representation
- data Module t = Module {}
- data Entity t
- data StructMember t = StructMember {}
- data Block t = Block {
- locals :: [Declaration t]
- blockBody :: Program t
- data Program t
- = Empty {
- | Comment { }
- | Assign {
- lhs :: Expression t
- rhs :: Expression t
- | ProcedureCall {
- procCallName :: String
- procCallParams :: [ActualParameter t]
- | Sequence {
- sequenceProgs :: [Program t]
- | Switch {
- scrutinee :: Expression t
- alts :: [(Pattern t, Block t)]
- | SeqLoop {
- sLoopCond :: Expression t
- sLoopCondCalc :: Block t
- sLoopBlock :: Block t
- | ParLoop {
- pParallel :: Bool
- pLoopCounter :: Variable t
- pLoopBound :: Expression t
- pLoopStep :: Expression t
- pLoopBlock :: Block t
- | BlockProgram {
- blockProgram :: Block t
- = Empty {
- data Pattern t
- = PatDefault
- | Pat (Expression t)
- data ActualParameter t
- = ValueParameter {
- valueParam :: Expression t
- | TypeParameter { }
- | FunParameter { }
- = ValueParameter {
- data Declaration t = Declaration {
- declVar :: Variable t
- initVal :: Maybe (Expression t)
- data Expression t
- = VarExpr { }
- | ArrayElem {
- array :: Expression t
- arrayIndex :: Expression t
- | StructField {
- struct :: Expression t
- fieldName :: String
- | ConstExpr { }
- | FunctionCall {
- function :: Function
- funCallParams :: [Expression t]
- | Cast {
- castType :: Type
- castExpr :: Expression t
- | AddrOf {
- addrExpr :: Expression t
- | SizeOf { }
- data Function = Function {
- funName :: String
- returnType :: Type
- funMode :: FunctionMode
- data Constant t
- = IntConst { }
- | DoubleConst { }
- | FloatConst {
- floatValue :: Float
- | BoolConst { }
- | ComplexConst { }
- | ArrayConst {
- arrayValues :: [Constant t]
- data Variable t = Variable {}
- data Size
- data Signedness
- data Type
- data FunctionMode
- class HasType a where
- reprError :: forall a. ErrorClass -> String -> a
- fv :: Expression t -> [Variable t]
- fv' :: Expression t -> [Variable t]
Documentation
Constructors
| StructDef | |
Fields
| |
| TypeDef | |
Fields
| |
| Proc | |
| ValueDef | |
Instances
| (Transformable1 t [] StructMember, Transformable1 t [] Variable, Transformable t Block, Transformable t Declaration, Transformable t Constant, Combine (Up t), Default (Up t), Transformation t) => DefaultTransformable t Entity | |
| Transformable IVarPlugin Entity | |
| Eq (Entity t) | |
| Show (Entity t) | |
| CodeGen (Entity ()) | |
| Typeable (* -> *) Entity |
data StructMember t Source
Constructors
| StructMember | |
Fields | |
Instances
| Default (Up t) => DefaultTransformable t StructMember | |
| Eq (StructMember t) | |
| Show (StructMember t) | |
| CodeGen (StructMember ()) | |
| Typeable (* -> *) StructMember |
Constructors
| Block | |
Fields
| |
Instances
| (Transformable1 t [] Declaration, Transformable t Program, Combine (Up t)) => DefaultTransformable t Block | |
| Eq (Block t) | |
| Show (Block t) | |
| Monoid (Block t) | |
| CodeGen (Block ()) | |
| Typeable (* -> *) Block |
Constructors
| Empty | |
| Comment | |
Fields
| |
| Assign | |
Fields
| |
| ProcedureCall | |
Fields
| |
| Sequence | |
Fields
| |
| Switch | |
Fields
| |
| SeqLoop | |
Fields
| |
| ParLoop | |
Fields
| |
| BlockProgram | |
Fields
| |
Instances
| (Transformable1 t [] Program, Transformable t Expression, Transformable1 t [] ActualParameter, Transformable t Block, Transformable t Variable, Combine (Up t), Default (Up t), Transformation t) => DefaultTransformable t Program | |
| Transformable IVarPlugin Program | |
| Eq (Program t) | |
| Show (Program t) | |
| Monoid (Program t) | |
| CodeGen (Program ()) | |
| Typeable (* -> *) Program |
Constructors
| PatDefault | |
| Pat (Expression t) |
Instances
| (Transformable t Constant, Transformable t Expression, Transformable1 t [] ActualParameter, Transformable t Block, Transformable t Variable, Combine (Up t), Default (Up t)) => DefaultTransformable t Pattern | |
| Eq (Pattern t) | |
| Show (Pattern t) | |
| CodeGen (Pattern ()) | |
| Typeable (* -> *) Pattern |
data ActualParameter t Source
Constructors
| ValueParameter | |
Fields
| |
| TypeParameter | |
| FunParameter | |
Fields | |
Instances
| (Transformable t Expression, Default (Up t)) => DefaultTransformable t ActualParameter | |
| Eq (ActualParameter t) | |
| Show (ActualParameter t) | |
| HasType (ActualParameter t) | |
| CodeGen (ActualParameter ()) | |
| Typeable (* -> *) ActualParameter | |
| type TypeOf (ActualParameter t) = Type |
data Declaration t Source
Constructors
| Declaration | |
Fields
| |
Instances
| (Transformable t Variable, Transformable1 t Maybe Expression, Combine (Up t)) => DefaultTransformable t Declaration | |
| Eq (Declaration t) | |
| Show (Declaration t) | |
| CodeGen (Declaration ()) | |
| Typeable (* -> *) Declaration |
data Expression t Source
Constructors
| VarExpr | |
| ArrayElem | |
Fields
| |
| StructField | |
Fields
| |
| ConstExpr | |
| FunctionCall | |
Fields
| |
| Cast | |
Fields
| |
| AddrOf | |
Fields
| |
| SizeOf | |
Instances
| (Transformable t Expression, Transformable t Variable, Transformable t Constant, Transformable1 t [] Expression, Combine (Up t), Default (Up t)) => DefaultTransformable t Expression | |
| Eq (Expression t) | |
| Show (Expression t) | |
| HasType (Expression t) | |
| CodeGen (Expression ()) | |
| Typeable (* -> *) Expression | |
| type TypeOf (Expression t) = Type |
Constructors
| Function | |
Fields
| |
Constructors
| IntConst | |
| DoubleConst | |
Fields | |
| FloatConst | |
Fields
| |
| BoolConst | |
| ComplexConst | |
Fields | |
| ArrayConst | |
Fields
| |
Instances
| HasType (Variable t) | |
| HasType (Constant t) | |
| HasType (Expression t) | |
| HasType (ActualParameter t) |
reprError :: forall a. ErrorClass -> String -> a Source
fv :: Expression t -> [Variable t] Source
Free variables of an expression.
fv' :: Expression t -> [Variable t] Source