{- - Copyright (c) 2009-2010, ERICSSON AB All rights reserved. - - Redistribution and use in source and binary forms, with or without - modification, are permitted provided that the following conditions - are met: - - * Redistributions of source code must retain the above copyright - notice, - this list of conditions and the following disclaimer. - * Redistributions in binary form must reproduce the above copyright - notice, this list of conditions and the following disclaimer - in the documentation and/or other materials provided with the - distribution. - * Neither the name of the ERICSSON AB nor the names of its - contributors - may be used to endorse or promote products derived from this - software without specific prior written permission. - - THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS - "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT - LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR - A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT - HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, - SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT - LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, - DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY - THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT - (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE - OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} {-# LANGUAGE TypeFamilies #-} module Feldspar.Compiler.Imperative.Representation where import Feldspar.Compiler.Imperative.Semantics -- =========================================================================== -- == Representation of imperative programs -- =========================================================================== -- ========================= [ Procedure ] =================================== data (SemanticInfo t) => Procedure t = Procedure { procedureName :: String, inParameters :: [FormalParameter t], outParameters :: [FormalParameter t], procedureBody :: Block t, procedureSemInf :: ProcedureInfo t } deriving (Eq,Show) -- ========================= [ Block ] ======================================= data (SemanticInfo t) => Block t = Block { blockData :: BlockData t, blockSemInf :: BlockInfo t } deriving (Eq,Show) data (SemanticInfo t) => BlockData t = BlockData { blockDeclarations :: [LocalDeclaration t], blockInstructions :: Program t } deriving (Eq,Show) -- ========================= [ Program ] ===================================== data (SemanticInfo t) => Program t = Program { programConstruction :: ProgramConstruction t, programSemInf :: ProgramInfo t } deriving (Eq,Show) data (SemanticInfo t) => ProgramConstruction t = EmptyProgram (Empty t) | PrimitiveProgram (Primitive t) | SequenceProgram (Sequence t) | BranchProgram (Branch t) | SequentialLoopProgram (SequentialLoop t) | ParallelLoopProgram (ParallelLoop t) deriving (Eq,Show) data (SemanticInfo t) => Empty t = Empty { emptySemInf :: EmptyInfo t } deriving (Eq,Show) data (SemanticInfo t) => Primitive t = Primitive { primitiveInstruction :: Instruction t, primitiveSemInf :: PrimitiveInfo t } deriving (Eq,Show) data (SemanticInfo t) => Sequence t = Sequence { sequenceProgramList :: [Program t], sequenceSemInf :: SequenceInfo t } deriving (Eq,Show) data (SemanticInfo t) => Branch t = Branch { branchData :: BranchData t, branchSemInf :: BranchInfo t } deriving (Eq,Show) data (SemanticInfo t) => BranchData t = BranchData { branchConditionVariable :: Variable t, -- ??? thenBlock :: Block t, elseBlock :: Block t } deriving (Eq, Show) data (SemanticInfo t) => SequentialLoop t = SequentialLoop { sequentialLoopData :: SequentialLoopData t, sequentialLoopSemInf :: SequentialLoopInfo t } deriving (Eq,Show) data (SemanticInfo t) => SequentialLoopData t = SequentialLoopData { sequentialLoopCondition :: Expression t, conditionCalculation :: Block t, -- ??? sequentialLoopCore :: Block t } deriving (Eq, Show) data (SemanticInfo t) => ParallelLoop t = ParallelLoop { parallelLoopData :: ParallelLoopData t, parallelLoopSemInf :: ParallelLoopInfo t } deriving (Eq,Show) data (SemanticInfo t) => ParallelLoopData t = ParallelLoopData { parallelLoopConditionVariable :: Variable t, numberOfIterations :: Expression t, -- ??? parallelLoopStep :: Int, -- ??? parallelLoopCore :: Block t } deriving (Eq, Show) -- ========================= [ FormalParameter ] ============================= data (SemanticInfo t) => FormalParameter t = FormalParameter { formalParameterVariable :: Variable t, formalParameterSemInf :: FormalParameterInfo t } deriving (Eq,Show) -- ========================= [ LocalDeclaration ] ============================ data (SemanticInfo t) => LocalDeclaration t = LocalDeclaration { localDeclarationData :: LocalDeclarationData t, localDeclarationSemInf :: LocalDeclarationInfo t } deriving (Eq,Show) data (SemanticInfo t) => LocalDeclarationData t = LocalDeclarationData { localVariable :: Variable t, localInitValue :: Maybe (Expression t) } deriving (Eq,Show) -- ========================= [ Expression ] ================================== data (SemanticInfo t) => Expression t = LeftValueExpression (LeftValueInExpression t) | ConstantExpression (Constant t) | FunctionCallExpression (FunctionCall t) deriving (Eq, Show) data (SemanticInfo t) => LeftValueInExpression t = LeftValueInExpression { leftValueExpressionContents :: LeftValue t, leftValueExpressionSemInf :: LeftValueExpressionInfo t } deriving (Eq, Show) data (SemanticInfo t) => FunctionCall t = FunctionCall { functionCallData :: FunctionCallData t, functionCallSemInf :: FunctionCallInfo t } deriving (Eq, Show) data (SemanticInfo t) => FunctionCallData t = FunctionCallData { roleOfFunctionToCall :: FunctionRole, typeOfFunctionToCall :: Type, nameOfFunctionToCall :: String, actualParametersOfFunctionToCall :: [Expression t] } deriving (Eq,Show) -- ========================= [ LeftValue ] =================================== data (SemanticInfo t) => LeftValue t = VariableLeftValue (VariableInLeftValue t) | ArrayElemReferenceLeftValue (ArrayElemReference t) deriving (Eq,Show) data (SemanticInfo t) => VariableInLeftValue t = VariableInLeftValue { variableLeftValueContents :: Variable t, variableLeftValueSemInf :: VariableInLeftValueInfo t } deriving (Eq,Show) data (SemanticInfo t) => ArrayElemReference t = ArrayElemReference { arrayElemReferenceData :: ArrayElemReferenceData t, arrayElemReferenceSemInf :: ArrayElemReferenceInfo t } deriving (Eq,Show) data (SemanticInfo t) => ArrayElemReferenceData t = ArrayElemReferenceData { arrayName :: LeftValue t, arrayIndex :: Expression t } deriving (Eq,Show) -- ========================= [ Instruction ] ================================= data (SemanticInfo t) => Instruction t = AssignmentInstruction (Assignment t) | ProcedureCallInstruction (ProcedureCall t) deriving (Eq,Show) data (SemanticInfo t) => Assignment t = Assignment { assignmentData :: AssignmentData t, assignmentSemInf :: AssignmentInfo t } deriving (Eq,Show) data (SemanticInfo t) => AssignmentData t = AssignmentData { assignmentLhs :: LeftValue t, assignmentRhs :: Expression t } deriving (Eq,Show) data (SemanticInfo t) => ProcedureCall t = ProcedureCall { procedureCallData :: ProcedureCallData t, procedureCallSemInf :: ProcedureCallInfo t } deriving (Eq,Show) data (SemanticInfo t) => ProcedureCallData t = ProcedureCallData { nameOfProcedureToCall :: String, actualParametersOfProcedureToCall :: [ActualParameter t] } deriving (Eq,Show) -- ========================= [ ActualParameter ] ============================= data (SemanticInfo t) => ActualParameter t = InputActualParameter (InputActualParameterType t) | OutputActualParameter (OutputActualParameterType t) deriving (Eq,Show) data (SemanticInfo t) => InputActualParameterType t = InputActualParameterType { inputActualParameterExpression :: Expression t, inputActualParameterSemInf :: InputActualParameterInfo t } deriving (Eq,Show) data (SemanticInfo t) => OutputActualParameterType t = OutputActualParameterType { outputActualParameterLeftValue :: LeftValue t, outputActualParameterSemInf :: OutputActualParameterInfo t } deriving (Eq,Show) -- ========================= [ Constant ] ==================================== data Constant t = IntConstant (IntConstantType t) | FloatConstant (FloatConstantType t) | BoolConstant (BoolConstantType t) | ArrayConstant (ArrayConstantType t) deriving (Eq,Show) data (SemanticInfo t) => IntConstantType t = IntConstantType { intConstantValue :: Int, intConstantSemInf :: IntConstantInfo t } deriving (Eq, Show) data (SemanticInfo t) => FloatConstantType t = FloatConstantType { floatConstantValue :: Float, floatConstantSemInf :: FloatConstantInfo t } deriving (Eq, Show) data (SemanticInfo t) => BoolConstantType t = BoolConstantType { boolConstantValue :: Bool, boolConstantSemInf :: BoolConstantInfo t } deriving (Eq, Show) data (SemanticInfo t) => ArrayConstantType t = ArrayConstantType { arrayConstantValue :: [Constant t], arrayConstantSemInf :: ArrayConstantInfo t } deriving (Eq, Show) -- ========================= [ Variable ] ==================================== data (SemanticInfo t) => Variable t = Variable { variableData :: VariableData, variableSemInf :: VariableInfo t } deriving (Eq,Show) data VariableData = VariableData { variableRole :: VariableRole, variableType :: Type, variableName :: String } deriving (Eq,Show) -- ========================= [ Basic structures ] ============================ data Length = Norm Int | Defined Int | Undefined deriving (Eq,Show) data Size = S8 | S16 | S32 | S64 deriving (Eq,Show) data Signedness = ImpSigned | ImpUnsigned deriving (Eq,Show) data Type = BoolType | FloatType | Numeric Signedness Size | ImpArrayType Length Type deriving (Eq,Show) data FunctionRole = SimpleFun | InfixOp | PrefixOp deriving (Eq,Show) data VariableRole = Value {- input of main & local -} | FunOut {- output of main -} deriving (Eq,Show)