feldspar-compiler-0.3.1: Compiler for the Feldspar languageSource codeContentsIndex
Feldspar.Compiler.Imperative.Representation
Documentation
data SemanticInfo t => Procedure t Source
Constructors
Procedure
procedureName :: String
inParameters :: [FormalParameter t]
outParameters :: [FormalParameter t]
procedureBody :: Block t
procedureSemInf :: ProcedureInfo t
show/hide Instances
data SemanticInfo t => Block t Source
Constructors
Block
blockDeclarations :: [LocalDeclaration t]
blockInstructions :: Program t
blockSemInf :: BlockInfo t
show/hide Instances
data SemanticInfo t => Program t Source
Constructors
Program
programConstruction :: ProgramConstruction t
programSemInf :: ProgramInfo t
show/hide Instances
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)
show/hide Instances
data SemanticInfo t => Empty t Source
Constructors
Empty
emptySemInf :: EmptyInfo t
show/hide Instances
data SemanticInfo t => Primitive t Source
Constructors
Primitive
primitiveInstruction :: Instruction t
primitiveSemInf :: PrimitiveInfo t
show/hide Instances
data SemanticInfo t => Sequence t Source
Constructors
Sequence
sequenceProgramList :: [Program t]
sequenceSemInf :: SequenceInfo t
show/hide Instances
data SemanticInfo t => Branch t Source
Constructors
Branch
branchConditionVariable :: Variable t
thenBlock :: Block t
elseBlock :: Block t
branchSemInf :: BranchInfo t
show/hide Instances
data SemanticInfo t => SequentialLoop t Source
Constructors
SequentialLoop
sequentialLoopCondition :: Expression t
conditionCalculation :: Block t
sequentialLoopCore :: Block t
sequentialLoopSemInf :: SequentialLoopInfo t
show/hide Instances
data SemanticInfo t => ParallelLoop t Source
Constructors
ParallelLoop
parallelLoopConditionVariable :: Variable t
numberOfIterations :: Expression t
parallelLoopStep :: Int
parallelLoopCore :: Block t
parallelLoopSemInf :: ParallelLoopInfo t
show/hide Instances
data SemanticInfo t => FormalParameter t Source
Constructors
FormalParameter
formalParameterVariable :: Variable t
formalParameterSemInf :: FormalParameterInfo t
show/hide Instances
data SemanticInfo t => LocalDeclaration t Source
Constructors
LocalDeclaration
localVariable :: Variable t
localInitValue :: Maybe (Expression t)
localDeclarationSemInf :: LocalDeclarationInfo t
show/hide Instances
data SemanticInfo t => Expression t Source
Constructors
Expression
expressionData :: ExpressionData t
expressionSemInf :: ExpressionInfo t
show/hide Instances
data SemanticInfo t => ExpressionData t Source
Constructors
LeftValueExpression (LeftValue t)
ConstantExpression (Constant t)
FunctionCallExpression (FunctionCall t)
show/hide Instances
data SemanticInfo t => Constant t Source
Constructors
Constant
constantData :: ConstantData t
constantSemInf :: ConstantInfo t
show/hide Instances
data SemanticInfo t => FunctionCall t Source
Constructors
FunctionCall
roleOfFunctionToCall :: FunctionRole
typeOfFunctionToCall :: Type
nameOfFunctionToCall :: String
actualParametersOfFunctionToCall :: [Expression t]
functionCallSemInf :: FunctionCallInfo t
show/hide Instances
data SemanticInfo t => LeftValue t Source
Constructors
LeftValue
leftValueData :: LeftValueData t
leftValueSemInf :: LeftValueInfo t
show/hide Instances
data SemanticInfo t => LeftValueData t Source
Constructors
VariableLeftValue (Variable t)
ArrayElemReferenceLeftValue (ArrayElemReference t)
show/hide Instances
data SemanticInfo t => ArrayElemReference t Source
Constructors
ArrayElemReference
arrayName :: LeftValue t
arrayIndex :: Expression t
arrayElemReferenceSemInf :: ArrayElemReferenceInfo t
show/hide Instances
data SemanticInfo t => Instruction t Source
Constructors
Instruction
instructionData :: InstructionData t
instructionSemInf :: InstructionInfo t
show/hide Instances
data SemanticInfo t => InstructionData t Source
Constructors
AssignmentInstruction (Assignment t)
ProcedureCallInstruction (ProcedureCall t)
show/hide Instances
data SemanticInfo t => Assignment t Source
Constructors
Assignment
assignmentLhs :: LeftValue t
assignmentRhs :: Expression t
assignmentSemInf :: AssignmentInfo t
show/hide Instances
data SemanticInfo t => ProcedureCall t Source
Constructors
ProcedureCall
nameOfProcedureToCall :: String
actualParametersOfProcedureToCall :: [ActualParameter t]
procedureCallSemInf :: ProcedureCallInfo t
show/hide Instances
data SemanticInfo t => ActualParameter t Source
Constructors
ActualParameter
actualParameterData :: ActualParameterData t
actualParameterSemInf :: ActualParameterInfo t
show/hide Instances
data SemanticInfo t => ActualParameterData t Source
Constructors
InputActualParameter (Expression t)
OutputActualParameter (LeftValue t)
show/hide Instances
data SemanticInfo t => ConstantData t Source
Constructors
IntConstant (IntConstantType t)
FloatConstant (FloatConstantType t)
BoolConstant (BoolConstantType t)
ArrayConstant (ArrayConstantType t)
show/hide Instances
data SemanticInfo t => IntConstantType t Source
Constructors
IntConstantType
intConstantValue :: Int
intConstantSemInf :: IntConstantInfo t
show/hide Instances
data SemanticInfo t => FloatConstantType t Source
Constructors
FloatConstantType
floatConstantValue :: Float
floatConstantSemInf :: FloatConstantInfo t
show/hide Instances
data SemanticInfo t => BoolConstantType t Source
Constructors
BoolConstantType
boolConstantValue :: Bool
boolConstantSemInf :: BoolConstantInfo t
show/hide Instances
data SemanticInfo t => ArrayConstantType t Source
Constructors
ArrayConstantType
arrayConstantValue :: [Constant t]
arrayConstantSemInf :: ArrayConstantInfo t
show/hide Instances
data SemanticInfo t => Variable t Source
Constructors
Variable
variableRole :: VariableRole
variableType :: Type
variableName :: String
variableSemInf :: VariableInfo t
show/hide Instances
data Length Source
Constructors
Norm Int
Defined Int
Undefined
show/hide Instances
data Size Source
Constructors
S8
S16
S32
S40
S64
show/hide Instances
data Signedness Source
Constructors
ImpSigned
ImpUnsigned
show/hide Instances
data Type Source
Constructors
BoolType
FloatType
Numeric Signedness Size
ImpArrayType Length Type
UserType String
show/hide Instances
data FunctionRole Source
Constructors
SimpleFun
InfixOp
PrefixOp
show/hide Instances
data VariableRole Source
Constructors
Value
FunOut
show/hide Instances
Produced by Haddock version 2.6.1