Feldspar.Compiler.Imperative.Representation
Documentation
data SemanticInfo t => Procedure t Source
Constructors
Procedure | |
Fields
|
Instances
SemanticInfo t => Eq (Procedure t) | |
SemanticInfo t => Show (Procedure t) | |
ToC (Procedure PrettyPrintSemanticInfo) |
data SemanticInfo t => Block t Source
Constructors
Block | |
Fields
|
Instances
SemanticInfo t => Eq (Block t) | |
SemanticInfo t => Show (Block t) | |
ToC (Block PrettyPrintSemanticInfo) |
data SemanticInfo t => Program t Source
Constructors
Program | |
Fields |
Instances
SemanticInfo t => Eq (Program t) | |
SemanticInfo t => Show (Program t) | |
ToC (Program PrettyPrintSemanticInfo) |
data SemanticInfo t => ProgramConstruction t Source
Constructors
EmptyProgram (Empty t) | |
PrimitiveProgram (Primitive t) | |
SequenceProgram (Sequence t) | |
BranchProgram (Branch t) | |
SequentialLoopProgram (SequentialLoop t) | |
ParallelLoopProgram (ParallelLoop t) |
Instances
SemanticInfo t => Eq (ProgramConstruction t) | |
SemanticInfo t => Show (ProgramConstruction t) |
data SemanticInfo t => Empty t Source
Constructors
Empty | |
Fields
|
Instances
SemanticInfo t => Eq (Empty t) | |
SemanticInfo t => Show (Empty t) |
data SemanticInfo t => Primitive t Source
Constructors
Primitive | |
Fields |
Instances
SemanticInfo t => Eq (Primitive t) | |
SemanticInfo t => Show (Primitive t) |
data SemanticInfo t => Sequence t Source
Constructors
Sequence | |
Fields
|
Instances
SemanticInfo t => Eq (Sequence t) | |
SemanticInfo t => Show (Sequence t) |
data SemanticInfo t => Branch t Source
Constructors
Branch | |
Fields
|
Instances
SemanticInfo t => Eq (Branch t) | |
SemanticInfo t => Show (Branch t) | |
OccurrenceDownwards (Branch t) |
data SemanticInfo t => SequentialLoop t Source
Constructors
SequentialLoop | |
Fields |
Instances
SemanticInfo t => Eq (SequentialLoop t) | |
SemanticInfo t => Show (SequentialLoop t) | |
OccurrenceDownwards (SequentialLoop t) |
data SemanticInfo t => ParallelLoop t Source
Constructors
ParallelLoop | |
Fields |
Instances
SemanticInfo t => Eq (ParallelLoop t) | |
SemanticInfo t => Show (ParallelLoop t) | |
OccurrenceDownwards (ParallelLoop t) |
data SemanticInfo t => FormalParameter t Source
Constructors
FormalParameter | |
Fields |
Instances
SemanticInfo t => Eq (FormalParameter t) | |
SemanticInfo t => Show (FormalParameter t) | |
OccurrenceDownwards (FormalParameter t) | |
ToC (FormalParameter PrettyPrintSemanticInfo) |
data SemanticInfo t => LocalDeclaration t Source
Constructors
LocalDeclaration | |
Fields
|
Instances
data SemanticInfo t => Expression t Source
Constructors
Expression | |
Fields |
Instances
SemInfUtils Expression | |
SemanticInfo t => Eq (Expression t) | |
SemanticInfo t => Show (Expression t) | |
OccurrenceDownwards (Expression t) | |
SemanticInfo t => HasType (Expression t) | |
ToC (Expression PrettyPrintSemanticInfo) |
data SemanticInfo t => ExpressionData t Source
Constructors
LeftValueExpression (LeftValue t) | |
ConstantExpression (Constant t) | |
FunctionCallExpression (FunctionCall t) |
Instances
SemInfUtils ExpressionData | |
SemanticInfo t => Eq (ExpressionData t) | |
SemanticInfo t => Show (ExpressionData t) | |
SemanticInfo t => HasType (ExpressionData t) | |
ToC (ExpressionData PrettyPrintSemanticInfo) |
data SemanticInfo t => Constant t Source
Constructors
Constant | |
Fields
|
Instances
SemInfUtils Constant | |
SemanticInfo t => Eq (Constant t) | |
SemanticInfo t => Show (Constant t) | |
SemanticInfo t => HasType (Constant t) | |
ToC (Constant PrettyPrintSemanticInfo) |
data SemanticInfo t => FunctionCall t Source
Constructors
FunctionCall | |
Instances
SemInfUtils FunctionCall | |
SemanticInfo t => Eq (FunctionCall t) | |
SemanticInfo t => Show (FunctionCall t) |
data SemanticInfo t => LeftValue t Source
Constructors
LeftValue | |
Fields |
Instances
SemInfUtils LeftValue | |
SemanticInfo t => Eq (LeftValue t) | |
SemanticInfo t => Show (LeftValue t) | |
SemanticInfo t => HasType (LeftValue t) | |
ToC (LeftValue PrettyPrintSemanticInfo) |
data SemanticInfo t => LeftValueData t Source
Constructors
VariableLeftValue (Variable t) | |
ArrayElemReferenceLeftValue (ArrayElemReference t) |
Instances
SemInfUtils LeftValueData | |
SemanticInfo t => Eq (LeftValueData t) | |
SemanticInfo t => Show (LeftValueData t) | |
Default [(VariableData, LeftValueData ())] | |
Default [(VariableData, LeftValueData (), Bool)] | |
Default (Maybe (VariableData, LeftValueData (), Bool)) | |
SemanticInfo t => HasType (LeftValueData t) | |
ToC (LeftValueData PrettyPrintSemanticInfo) | |
Combine (VarStatBck, [(VariableData, LeftValueData (), Bool)]) |
data SemanticInfo t => ArrayElemReference t Source
Constructors
ArrayElemReference | |
Fields |
Instances
SemInfUtils ArrayElemReference | |
SemanticInfo t => Eq (ArrayElemReference t) | |
SemanticInfo t => Show (ArrayElemReference t) |
data SemanticInfo t => Instruction t Source
Constructors
Instruction | |
Fields |
Instances
SemanticInfo t => Eq (Instruction t) | |
SemanticInfo t => Show (Instruction t) | |
ToC (Instruction PrettyPrintSemanticInfo) |
data SemanticInfo t => InstructionData t Source
Constructors
AssignmentInstruction (Assignment t) | |
ProcedureCallInstruction (ProcedureCall t) |
Instances
SemanticInfo t => Eq (InstructionData t) | |
SemanticInfo t => Show (InstructionData t) | |
ToC (InstructionData PrettyPrintSemanticInfo) |
data SemanticInfo t => Assignment t Source
Constructors
Assignment | |
Fields
|
Instances
SemanticInfo t => Eq (Assignment t) | |
SemanticInfo t => Show (Assignment t) | |
OccurrenceDownwards (Assignment t) |
data SemanticInfo t => ProcedureCall t Source
Constructors
ProcedureCall | |
Instances
SemanticInfo t => Eq (ProcedureCall t) | |
SemanticInfo t => Show (ProcedureCall t) |
data SemanticInfo t => ActualParameterData t Source
Constructors
InputActualParameter (Expression t) | |
OutputActualParameter (LeftValue t) |
Instances
data SemanticInfo t => ConstantData t Source
Constructors
IntConstant (IntConstantType t) | |
FloatConstant (FloatConstantType t) | |
BoolConstant (BoolConstantType t) | |
ArrayConstant (ArrayConstantType t) |
Instances
SemInfUtils ConstantData | |
SemanticInfo t => Eq (ConstantData t) | |
SemanticInfo t => Show (ConstantData t) | |
SemanticInfo t => HasType (ConstantData t) | |
ToC (ConstantData PrettyPrintSemanticInfo) |
data SemanticInfo t => IntConstantType t Source
Constructors
IntConstantType | |
Fields |
Instances
SemInfUtils IntConstantType | |
SemanticInfo t => Eq (IntConstantType t) | |
SemanticInfo t => Show (IntConstantType t) |
data SemanticInfo t => FloatConstantType t Source
Constructors
FloatConstantType | |
Fields |
Instances
SemInfUtils FloatConstantType | |
SemanticInfo t => Eq (FloatConstantType t) | |
SemanticInfo t => Show (FloatConstantType t) |
data SemanticInfo t => BoolConstantType t Source
Constructors
BoolConstantType | |
Fields |
Instances
SemInfUtils BoolConstantType | |
SemanticInfo t => Eq (BoolConstantType t) | |
SemanticInfo t => Show (BoolConstantType t) |
data SemanticInfo t => ArrayConstantType t Source
Constructors
ArrayConstantType | |
Fields |
Instances
SemInfUtils ArrayConstantType | |
SemanticInfo t => Eq (ArrayConstantType t) | |
SemanticInfo t => Show (ArrayConstantType t) |
data SemanticInfo t => Variable t Source
Constructors
Variable | |
Fields
|
Instances
SemInfUtils Variable | |
SemanticInfo t => Eq (Variable t) | |
SemanticInfo t => Show (Variable t) | |
SemanticInfo t => HasType (Variable t) | |
ToC (Variable PrettyPrintSemanticInfo) |
Constructors
BoolType | |
FloatType | |
Numeric Signedness Size | |
ImpArrayType Length Type | |
UserType String |
data FunctionRole Source
Instances