feldspar-compiler-0.3.1: Compiler for the Feldspar languageSource codeContentsIndex
Feldspar.Compiler.PluginArchitecture
Documentation
foldlist :: (Default a, Combine a) => [a] -> aSource
convertMaybeList :: Maybe [a] -> [a]Source
convertMaybe :: Maybe a -> [a]Source
type Walker t construction = TransformationPhase t => t -> Downwards t -> construction (From t) -> (construction (To t), Upwards t)Source
class TransformationPhase t => Plugin t whereSource
Associated Types
type ExternalInfo t Source
Methods
executePlugin :: t -> ExternalInfo t -> Procedure (From t) -> Procedure (To t)Source
show/hide Instances
class (SemanticInfo (From t), SemanticInfo (To t), ConvertAllInfos (From t) (To t), Combine (Upwards t), Default (Upwards t)) => TransformationPhase t whereSource
Associated Types
type From t Source
type To t Source
type Downwards t Source
type Upwards t Source
Methods
executeTransformationPhase :: Walker t ProcedureSource
downwardsProcedure :: t -> Downwards t -> Procedure (From t) -> Downwards tSource
transformProcedure :: t -> Downwards t -> Procedure (From t) -> InfoFromProcedureParts t -> Procedure (To t)Source
upwardsProcedure :: t -> Downwards t -> Procedure (From t) -> InfoFromProcedureParts t -> Procedure (To t) -> Upwards tSource
downwardsBlock :: t -> Downwards t -> Block (From t) -> Downwards tSource
transformBlock :: t -> Downwards t -> Block (From t) -> InfoFromBlockParts t -> Block (To t)Source
upwardsBlock :: t -> Downwards t -> Block (From t) -> InfoFromBlockParts t -> Block (To t) -> Upwards tSource
downwardsProgram :: t -> Downwards t -> Program (From t) -> Downwards tSource
transformProgram :: t -> Downwards t -> Program (From t) -> InfoFromProgramParts t -> Program (To t)Source
upwardsProgram :: t -> Downwards t -> Program (From t) -> InfoFromProgramParts t -> Program (To t) -> Upwards tSource
transformEmptyProgramInProgram :: t -> Downwards t -> Empty (From t) -> ProgramConstruction (To t)Source
upwardsEmptyProgramInProgram :: t -> Downwards t -> Empty (From t) -> ProgramConstruction (To t) -> Upwards tSource
downwardsPrimitiveProgramInProgram :: t -> Downwards t -> Primitive (From t) -> Downwards tSource
transformPrimitiveProgramInProgram :: t -> Downwards t -> Primitive (From t) -> InfoFromPrimitiveParts t -> ProgramConstruction (To t)Source
upwardsPrimitiveProgramInProgram :: t -> Downwards t -> Primitive (From t) -> InfoFromPrimitiveParts t -> ProgramConstruction (To t) -> Upwards tSource
downwardsSequenceProgramInProgram :: t -> Downwards t -> Sequence (From t) -> Downwards tSource
transformSequenceProgramInProgram :: t -> Downwards t -> Sequence (From t) -> InfoFromSequenceParts t -> ProgramConstruction (To t)Source
upwardsSequenceProgramInProgram :: t -> Downwards t -> Sequence (From t) -> InfoFromSequenceParts t -> ProgramConstruction (To t) -> Upwards tSource
downwardsBranchProgramInProgram :: t -> Downwards t -> Branch (From t) -> Downwards tSource
transformBranchProgramInProgram :: t -> Downwards t -> Branch (From t) -> InfoFromBranchParts t -> ProgramConstruction (To t)Source
upwardsBranchProgramInProgram :: t -> Downwards t -> Branch (From t) -> InfoFromBranchParts t -> ProgramConstruction (To t) -> Upwards tSource
downwardsSequentialLoopProgramInProgram :: t -> Downwards t -> SequentialLoop (From t) -> Downwards tSource
transformSequentialLoopProgramInProgram :: t -> Downwards t -> SequentialLoop (From t) -> InfoFromSequentialLoopParts t -> ProgramConstruction (To t)Source
upwardsSequentialLoopProgramInProgram :: t -> Downwards t -> SequentialLoop (From t) -> InfoFromSequentialLoopParts t -> ProgramConstruction (To t) -> Upwards tSource
downwardsParallelLoopProgramInProgram :: t -> Downwards t -> ParallelLoop (From t) -> Downwards tSource
transformParallelLoopProgramInProgram :: t -> Downwards t -> ParallelLoop (From t) -> InfoFromParallelLoopParts t -> ProgramConstruction (To t)Source
upwardsParallelLoopProgramInProgram :: t -> Downwards t -> ParallelLoop (From t) -> InfoFromParallelLoopParts t -> ProgramConstruction (To t) -> Upwards tSource
downwardsFormalParameter :: t -> Downwards t -> FormalParameter (From t) -> Downwards tSource
transformFormalParameter :: t -> Downwards t -> FormalParameter (From t) -> InfoFromFormalParameterParts t -> FormalParameter (To t)Source
upwardsFormalParameter :: t -> Downwards t -> FormalParameter (From t) -> InfoFromFormalParameterParts t -> FormalParameter (To t) -> Upwards tSource
downwardsLocalDeclaration :: t -> Downwards t -> LocalDeclaration (From t) -> Downwards tSource
transformLocalDeclaration :: t -> Downwards t -> LocalDeclaration (From t) -> InfoFromLocalDeclarationParts t -> LocalDeclaration (To t)Source
upwardsLocalDeclaration :: t -> Downwards t -> LocalDeclaration (From t) -> InfoFromLocalDeclarationParts t -> LocalDeclaration (To t) -> Upwards tSource
downwardsExpression :: t -> Downwards t -> Expression (From t) -> Downwards tSource
transformExpression :: t -> Downwards t -> Expression (From t) -> InfoFromExpressionParts t -> Expression (To t)Source
upwardsExpression :: t -> Downwards t -> Expression (From t) -> InfoFromExpressionParts t -> Expression (To t) -> Upwards tSource
downwardsLeftValueExpressionInExpression :: t -> Downwards t -> LeftValue (From t) -> Downwards tSource
transformLeftValueExpressionInExpression :: t -> Downwards t -> LeftValue (From t) -> InfoFromLeftValueParts t -> ExpressionData (To t)Source
upwardsLeftValueExpressionInExpression :: t -> Downwards t -> LeftValue (From t) -> InfoFromLeftValueParts t -> ExpressionData (To t) -> Upwards tSource
downwardsConstantExpressionInExpression :: t -> Downwards t -> Constant (From t) -> Downwards tSource
transformConstantExpressionInExpression :: t -> Downwards t -> Constant (From t) -> InfoFromConstantParts t -> ExpressionData (To t)Source
upwardsConstantExpressionInExpression :: t -> Downwards t -> Constant (From t) -> InfoFromConstantParts t -> ExpressionData (To t) -> Upwards tSource
downwardsFunctionCallExpressionInExpression :: t -> Downwards t -> FunctionCall (From t) -> Downwards tSource
transformFunctionCallExpressionInExpression :: t -> Downwards t -> FunctionCall (From t) -> InfoFromFunctionCallParts t -> ExpressionData (To t)Source
upwardsFunctionCallExpressionInExpression :: t -> Downwards t -> FunctionCall (From t) -> InfoFromFunctionCallParts t -> ExpressionData (To t) -> Upwards tSource
downwardsConstant :: t -> Downwards t -> Constant (From t) -> Downwards tSource
transformConstant :: t -> Downwards t -> Constant (From t) -> InfoFromConstantParts t -> Constant (To t)Source
upwardsConstant :: t -> Downwards t -> Constant (From t) -> InfoFromConstantParts t -> Constant (To t) -> Upwards tSource
transformIntConstantInConstant :: t -> Downwards t -> IntConstantType (From t) -> ConstantData (To t)Source
upwardsIntConstantInConstant :: t -> Downwards t -> IntConstantType (From t) -> ConstantData (To t) -> Upwards tSource
transformFloatConstantInConstant :: t -> Downwards t -> FloatConstantType (From t) -> ConstantData (To t)Source
upwardsFloatConstantInConstant :: t -> Downwards t -> FloatConstantType (From t) -> ConstantData (To t) -> Upwards tSource
transformBoolConstantInConstant :: t -> Downwards t -> BoolConstantType (From t) -> ConstantData (To t)Source
upwardsBoolConstantInConstant :: t -> Downwards t -> BoolConstantType (From t) -> ConstantData (To t) -> Upwards tSource
downwardsArrayConstantInConstant :: t -> Downwards t -> ArrayConstantType (From t) -> Downwards tSource
transformArrayConstantInConstant :: t -> Downwards t -> ArrayConstantType (From t) -> InfoFromArrayConstantParts t -> ConstantData (To t)Source
upwardsArrayConstantInConstant :: t -> Downwards t -> ArrayConstantType (From t) -> InfoFromArrayConstantParts t -> ConstantData (To t) -> Upwards tSource
downwardsLeftValue :: t -> Downwards t -> LeftValue (From t) -> Downwards tSource
transformLeftValue :: t -> Downwards t -> LeftValue (From t) -> InfoFromLeftValueParts t -> LeftValue (To t)Source
upwardsLeftValue :: t -> Downwards t -> LeftValue (From t) -> InfoFromLeftValueParts t -> LeftValue (To t) -> Upwards tSource
transformVariableLeftValueInLeftValue :: t -> Downwards t -> Variable (From t) -> LeftValueData (To t)Source
upwardsVariableLeftValueInLeftValue :: t -> Downwards t -> Variable (From t) -> LeftValueData (To t) -> Upwards tSource
downwardsArrayElemReferenceLeftValueInLeftValue :: t -> Downwards t -> ArrayElemReference (From t) -> Downwards tSource
transformArrayElemReferenceLeftValueInLeftValue :: t -> Downwards t -> ArrayElemReference (From t) -> InfoFromArrayElemReferenceParts t -> LeftValueData (To t)Source
upwardsArrayElemReferenceLeftValueInLeftValue :: t -> Downwards t -> ArrayElemReference (From t) -> InfoFromArrayElemReferenceParts t -> LeftValueData (To t) -> Upwards tSource
downwardsInstruction :: t -> Downwards t -> Instruction (From t) -> Downwards tSource
transformInstruction :: t -> Downwards t -> Instruction (From t) -> InfoFromInstructionParts t -> Instruction (To t)Source
upwardsInstruction :: t -> Downwards t -> Instruction (From t) -> InfoFromInstructionParts t -> Instruction (To t) -> Upwards tSource
downwardsAssignmentInstructionInInstruction :: t -> Downwards t -> Assignment (From t) -> Downwards tSource
transformAssignmentInstructionInInstruction :: t -> Downwards t -> Assignment (From t) -> InfoFromAssignmentParts t -> InstructionData (To t)Source
upwardsAssignmentInstructionInInstruction :: t -> Downwards t -> Assignment (From t) -> InfoFromAssignmentParts t -> InstructionData (To t) -> Upwards tSource
downwardsProcedureCallInstructionInInstruction :: t -> Downwards t -> ProcedureCall (From t) -> Downwards tSource
transformProcedureCallInstructionInInstruction :: t -> Downwards t -> ProcedureCall (From t) -> InfoFromProcedureCallParts t -> InstructionData (To t)Source
upwardsProcedureCallInstructionInInstruction :: t -> Downwards t -> ProcedureCall (From t) -> InfoFromProcedureCallParts t -> InstructionData (To t) -> Upwards tSource
downwardsActualParameter :: t -> Downwards t -> ActualParameter (From t) -> Downwards tSource
transformActualParameter :: t -> Downwards t -> ActualParameter (From t) -> InfoFromActualParameterParts t -> ActualParameter (To t)Source
upwardsActualParameter :: t -> Downwards t -> ActualParameter (From t) -> InfoFromActualParameterParts t -> ActualParameter (To t) -> Upwards tSource
downwardsInputActualParameterInActualParameter :: t -> Downwards t -> Expression (From t) -> Downwards tSource
transformInputActualParameterInActualParameter :: t -> Downwards t -> Expression (From t) -> InfoFromExpressionParts t -> ActualParameterData (To t)Source
upwardsInputActualParameterInActualParameter :: t -> Downwards t -> Expression (From t) -> InfoFromExpressionParts t -> ActualParameterData (To t) -> Upwards tSource
downwardsOutputActualParameterInActualParameter :: t -> Downwards t -> LeftValue (From t) -> Downwards tSource
transformOutputActualParameterInActualParameter :: t -> Downwards t -> LeftValue (From t) -> InfoFromLeftValueParts t -> ActualParameterData (To t)Source
upwardsOutputActualParameterInActualParameter :: t -> Downwards t -> LeftValue (From t) -> InfoFromLeftValueParts t -> ActualParameterData (To t) -> Upwards tSource
transformIntConstant :: t -> Downwards t -> IntConstantType (From t) -> IntConstantType (To t)Source
upwardsIntConstant :: t -> Downwards t -> IntConstantType (From t) -> IntConstantType (To t) -> Upwards tSource
transformFloatConstant :: t -> Downwards t -> FloatConstantType (From t) -> FloatConstantType (To t)Source
upwardsFloatConstant :: t -> Downwards t -> FloatConstantType (From t) -> FloatConstantType (To t) -> Upwards tSource
transformBoolConstant :: t -> Downwards t -> BoolConstantType (From t) -> BoolConstantType (To t)Source
upwardsBoolConstant :: t -> Downwards t -> BoolConstantType (From t) -> BoolConstantType (To t) -> Upwards tSource
transformVariable :: t -> Downwards t -> Variable (From t) -> Variable (To t)Source
upwardsVariable :: t -> Downwards t -> Variable (From t) -> Variable (To t) -> Upwards tSource
walkProcedure :: Walker t ProcedureSource
walkBlock :: Walker t BlockSource
walkProgram :: Walker t ProgramSource
walkEmptyProgramInProgram :: TransformationPhase t => t -> Downwards t -> Empty (From t) -> (ProgramConstruction (To t), Upwards t)Source
walkPrimitiveProgramInProgram :: TransformationPhase t => t -> Downwards t -> Primitive (From t) -> (ProgramConstruction (To t), Upwards t)Source
walkSequenceProgramInProgram :: TransformationPhase t => t -> Downwards t -> Sequence (From t) -> (ProgramConstruction (To t), Upwards t)Source
walkBranchProgramInProgram :: TransformationPhase t => t -> Downwards t -> Branch (From t) -> (ProgramConstruction (To t), Upwards t)Source
walkSequentialLoopProgramInProgram :: TransformationPhase t => t -> Downwards t -> SequentialLoop (From t) -> (ProgramConstruction (To t), Upwards t)Source
walkParallelLoopProgramInProgram :: TransformationPhase t => t -> Downwards t -> ParallelLoop (From t) -> (ProgramConstruction (To t), Upwards t)Source
walkFormalParameter :: Walker t FormalParameterSource
walkLocalDeclaration :: Walker t LocalDeclarationSource
walkExpression :: Walker t ExpressionSource
walkLeftValueExpressionInExpression :: TransformationPhase t => t -> Downwards t -> LeftValue (From t) -> (ExpressionData (To t), Upwards t)Source
walkConstantExpressionInExpression :: TransformationPhase t => t -> Downwards t -> Constant (From t) -> (ExpressionData (To t), Upwards t)Source
walkFunctionCallExpressionInExpression :: TransformationPhase t => t -> Downwards t -> FunctionCall (From t) -> (ExpressionData (To t), Upwards t)Source
walkConstant :: Walker t ConstantSource
walkIntConstantInConstant :: TransformationPhase t => t -> Downwards t -> IntConstantType (From t) -> (ConstantData (To t), Upwards t)Source
walkFloatConstantInConstant :: TransformationPhase t => t -> Downwards t -> FloatConstantType (From t) -> (ConstantData (To t), Upwards t)Source
walkBoolConstantInConstant :: TransformationPhase t => t -> Downwards t -> BoolConstantType (From t) -> (ConstantData (To t), Upwards t)Source
walkArrayConstantInConstant :: TransformationPhase t => t -> Downwards t -> ArrayConstantType (From t) -> (ConstantData (To t), Upwards t)Source
walkLeftValue :: Walker t LeftValueSource
walkVariableLeftValueInLeftValue :: TransformationPhase t => t -> Downwards t -> Variable (From t) -> (LeftValueData (To t), Upwards t)Source
walkArrayElemReferenceLeftValueInLeftValue :: TransformationPhase t => t -> Downwards t -> ArrayElemReference (From t) -> (LeftValueData (To t), Upwards t)Source
walkInstruction :: Walker t InstructionSource
walkAssignmentInstructionInInstruction :: TransformationPhase t => t -> Downwards t -> Assignment (From t) -> (InstructionData (To t), Upwards t)Source
walkProcedureCallInstructionInInstruction :: TransformationPhase t => t -> Downwards t -> ProcedureCall (From t) -> (InstructionData (To t), Upwards t)Source
walkActualParameter :: Walker t ActualParameterSource
walkInputActualParameterInActualParameter :: TransformationPhase t => t -> Downwards t -> Expression (From t) -> (ActualParameterData (To t), Upwards t)Source
walkOutputActualParameterInActualParameter :: TransformationPhase t => t -> Downwards t -> LeftValue (From t) -> (ActualParameterData (To t), Upwards t)Source
walkVariable :: Walker t VariableSource
show/hide Instances
data TransformationPhase t => InfoFromProcedureParts t Source
Constructors
InfoFromProcedureParts
recursivelyTransformedInParameters :: [FormalParameter (To t)]
upwardsInfoFromInParameters :: [Upwards t]
recursivelyTransformedOutParameters :: [FormalParameter (To t)]
upwardsInfoFromOutParameters :: [Upwards t]
recursivelyTransformedProcedureBody :: Block (To t)
upwardsInfoFromProcedureBody :: Upwards t
data TransformationPhase t => InfoFromBlockParts t Source
Constructors
InfoFromBlockParts
recursivelyTransformedBlockDeclarations :: [LocalDeclaration (To t)]
upwardsInfoFromBlockDeclarations :: [Upwards t]
recursivelyTransformedBlockInstructions :: Program (To t)
upwardsInfoFromBlockInstructions :: Upwards t
data TransformationPhase t => InfoFromProgramParts t Source
Constructors
InfoFromProgramParts
recursivelyTransformedProgramConstruction :: ProgramConstruction (To t)
upwardsInfoFromProgramConstruction :: Upwards t
data TransformationPhase t => InfoFromPrimitiveParts t Source
Constructors
InfoFromPrimitiveParts
recursivelyTransformedPrimitiveInstruction :: Instruction (To t)
upwardsInfoFromPrimitiveInstruction :: Upwards t
data TransformationPhase t => InfoFromSequenceParts t Source
Constructors
InfoFromSequenceParts
recursivelyTransformedSequenceProgramList :: [Program (To t)]
upwardsInfoFromSequenceProgramList :: [Upwards t]
data TransformationPhase t => InfoFromBranchParts t Source
Constructors
InfoFromBranchParts
recursivelyTransformedBranchConditionVariable :: Variable (To t)
upwardsInfoFromBranchConditionVariable :: Upwards t
recursivelyTransformedThenBlock :: Block (To t)
upwardsInfoFromThenBlock :: Upwards t
recursivelyTransformedElseBlock :: Block (To t)
upwardsInfoFromElseBlock :: Upwards t
data TransformationPhase t => InfoFromSequentialLoopParts t Source
Constructors
InfoFromSequentialLoopParts
recursivelyTransformedSequentialLoopCondition :: Expression (To t)
upwardsInfoFromSequentialLoopCondition :: Upwards t
recursivelyTransformedConditionCalculation :: Block (To t)
upwardsInfoFromConditionCalculation :: Upwards t
recursivelyTransformedSequentialLoopCore :: Block (To t)
upwardsInfoFromSequentialLoopCore :: Upwards t
data TransformationPhase t => InfoFromParallelLoopParts t Source
Constructors
InfoFromParallelLoopParts
recursivelyTransformedParallelLoopConditionVariable :: Variable (To t)
upwardsInfoFromParallelLoopConditionVariable :: Upwards t
recursivelyTransformedNumberOfIterations :: Expression (To t)
upwardsInfoFromNumberOfIterations :: Upwards t
recursivelyTransformedParallelLoopCore :: Block (To t)
upwardsInfoFromParallelLoopCore :: Upwards t
data TransformationPhase t => InfoFromFormalParameterParts t Source
Constructors
InfoFromFormalParameterParts
recursivelyTransformedFormalParameterVariable :: Variable (To t)
upwardsInfoFromFormalParameterVariable :: Upwards t
data TransformationPhase t => InfoFromLocalDeclarationParts t Source
Constructors
InfoFromLocalDeclarationParts
recursivelyTransformedLocalVariable :: Variable (To t)
upwardsInfoFromLocalVariable :: Upwards t
recursivelyTransformedLocalInitValue :: Maybe (Expression (To t))
upwardsInfoFromLocalInitValue :: Maybe (Upwards t)
data TransformationPhase t => InfoFromExpressionParts t Source
Constructors
InfoFromExpressionParts
recursivelyTransformedExpressionData :: ExpressionData (To t)
upwardsInfoFromExpressionData :: Upwards t
data TransformationPhase t => InfoFromConstantParts t Source
Constructors
InfoFromConstantParts
recursivelyTransformedConstantData :: ConstantData (To t)
upwardsInfoFromConstantData :: Upwards t
data TransformationPhase t => InfoFromFunctionCallParts t Source
Constructors
InfoFromFunctionCallParts
recursivelyTransformedActualParametersOfFunctionToCall :: [Expression (To t)]
upwardsInfoFromActualParametersOfFunctionToCall :: [Upwards t]
data TransformationPhase t => InfoFromLeftValueParts t Source
Constructors
InfoFromLeftValueParts
recursivelyTransformedLeftValueData :: LeftValueData (To t)
upwardsInfoFromLeftValueData :: Upwards t
data TransformationPhase t => InfoFromArrayElemReferenceParts t Source
Constructors
InfoFromArrayElemReferenceParts
recursivelyTransformedArrayName :: LeftValue (To t)
upwardsInfoFromArrayName :: Upwards t
recursivelyTransformedArrayIndex :: Expression (To t)
upwardsInfoFromArrayIndex :: Upwards t
data TransformationPhase t => InfoFromInstructionParts t Source
Constructors
InfoFromInstructionParts
recursivelyTransformedInstructionData :: InstructionData (To t)
upwardsInfoFromInstructionData :: Upwards t
data TransformationPhase t => InfoFromAssignmentParts t Source
Constructors
InfoFromAssignmentParts
recursivelyTransformedAssignmentLhs :: LeftValue (To t)
upwardsInfoFromAssignmentLhs :: Upwards t
recursivelyTransformedAssignmentRhs :: Expression (To t)
upwardsInfoFromAssignmentRhs :: Upwards t
data TransformationPhase t => InfoFromProcedureCallParts t Source
Constructors
InfoFromProcedureCallParts
recursivelyTransformedActualParametersOfProcedureToCall :: [ActualParameter (To t)]
upwardsInfoFromActualParametersOfProcedureToCall :: [Upwards t]
data TransformationPhase t => InfoFromActualParameterParts t Source
Constructors
InfoFromActualParameterParts
recursivelyTransformedActualParameterData :: ActualParameterData (To t)
upwardsInfoFromActualParameterData :: Upwards t
data TransformationPhase t => InfoFromArrayConstantParts t Source
Constructors
InfoFromArrayConstantParts
recursivelyTransformedArrayConstantValue :: [Constant (To t)]
upwardsInfoFromArrayConstantValue :: [Upwards t]
module Feldspar.Compiler.Imperative.Representation
module Feldspar.Compiler.Imperative.Semantics
module Feldspar.Compiler.PluginArchitecture.DefaultConvert
Produced by Haddock version 2.6.1