{- - 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, EmptyDataDecls, FlexibleContexts #-} module Feldspar.Compiler.Imperative.Semantics where -- =========================================================================== -- == Semantic info class -- =========================================================================== class (Show (ProcedureInfo t), Show (BlockInfo t), Show (ProgramInfo t), Show (EmptyInfo t), Show (PrimitiveInfo t), Show (SequenceInfo t), Show (BranchInfo t), Show (SequentialLoopInfo t), Show (ParallelLoopInfo t), Show (FormalParameterInfo t), Show (LocalDeclarationInfo t), Show (FunctionCallInfo t), Show (LeftValueExpressionInfo t), Show (VariableInLeftValueInfo t), Show (ArrayElemReferenceInfo t), Show (InputActualParameterInfo t), Show (OutputActualParameterInfo t), Show (AssignmentInfo t), Show (ProcedureCallInfo t), Show (IntConstantInfo t), Show (FloatConstantInfo t), Show (BoolConstantInfo t), Show (ArrayConstantInfo t), Show (VariableInfo t), Eq (ProcedureInfo t), Eq (BlockInfo t), Eq (ProgramInfo t), Eq (EmptyInfo t), Eq (PrimitiveInfo t), Eq (SequenceInfo t), Eq (BranchInfo t), Eq (SequentialLoopInfo t), Eq (ParallelLoopInfo t), Eq (FormalParameterInfo t), Eq (LocalDeclarationInfo t), Eq (FunctionCallInfo t), Eq (LeftValueExpressionInfo t), Eq (VariableInLeftValueInfo t), Eq (ArrayElemReferenceInfo t), Eq (InputActualParameterInfo t), Eq (OutputActualParameterInfo t), Eq (AssignmentInfo t), Eq (ProcedureCallInfo t), Eq (IntConstantInfo t), Eq (FloatConstantInfo t), Eq (BoolConstantInfo t), Eq (ArrayConstantInfo t), Eq (VariableInfo t)) => SemanticInfo t where type ProcedureInfo t type BlockInfo t type ProgramInfo t type EmptyInfo t type PrimitiveInfo t type SequenceInfo t type BranchInfo t type SequentialLoopInfo t type ParallelLoopInfo t type FormalParameterInfo t type LocalDeclarationInfo t type LeftValueExpressionInfo t type VariableInLeftValueInfo t type ArrayElemReferenceInfo t type InputActualParameterInfo t type OutputActualParameterInfo t type AssignmentInfo t type ProcedureCallInfo t type FunctionCallInfo t type IntConstantInfo t type FloatConstantInfo t type BoolConstantInfo t type ArrayConstantInfo t type VariableInfo t -- =========================================================================== -- == Unit semantic info instance -- =========================================================================== instance SemanticInfo () where type ProcedureInfo () = () type BlockInfo () = () type ProgramInfo () = () type EmptyInfo () = () type PrimitiveInfo () = () type SequenceInfo () = () type BranchInfo () = () type SequentialLoopInfo () = () type ParallelLoopInfo () = () type FormalParameterInfo () = () type LocalDeclarationInfo () = () type LeftValueExpressionInfo () = () type VariableInLeftValueInfo () = () type ArrayElemReferenceInfo () = () type InputActualParameterInfo () = () type OutputActualParameterInfo () = () type AssignmentInfo () = () type ProcedureCallInfo () = () type FunctionCallInfo () = () type IntConstantInfo () = () type FloatConstantInfo () = () type BoolConstantInfo () = () type ArrayConstantInfo () = () type VariableInfo () = () -- =========================================================================== -- == Basic semantic info instance -- =========================================================================== data InitSemInf instance SemanticInfo InitSemInf where type ProcedureInfo InitSemInf = () type BlockInfo InitSemInf = () type ProgramInfo InitSemInf = () type EmptyInfo InitSemInf = () type PrimitiveInfo InitSemInf = Bool type SequenceInfo InitSemInf = () type BranchInfo InitSemInf = () type SequentialLoopInfo InitSemInf = () type ParallelLoopInfo InitSemInf = () type FormalParameterInfo InitSemInf = () type LocalDeclarationInfo InitSemInf = () type LeftValueExpressionInfo InitSemInf = () type VariableInLeftValueInfo InitSemInf = () type ArrayElemReferenceInfo InitSemInf = () type InputActualParameterInfo InitSemInf = () type OutputActualParameterInfo InitSemInf = () type AssignmentInfo InitSemInf = () type ProcedureCallInfo InitSemInf = () type FunctionCallInfo InitSemInf = () type IntConstantInfo InitSemInf = () type FloatConstantInfo InitSemInf = () type BoolConstantInfo InitSemInf = () type ArrayConstantInfo InitSemInf = () type VariableInfo InitSemInf = () -- =========================================================================== -- == PrettyPrint semantic info instance -- =========================================================================== data IsRestrict = Restrict | NoRestrict deriving (Show,Eq) data IsDefaultArraySize = DefaultArraySize | NoDefaultArraySize deriving (Show,Eq) data PrettyPrintSemanticInfo instance SemanticInfo PrettyPrintSemanticInfo where type ProcedureInfo PrettyPrintSemanticInfo = () type BlockInfo PrettyPrintSemanticInfo = () type ProgramInfo PrettyPrintSemanticInfo = () type EmptyInfo PrettyPrintSemanticInfo = () type PrimitiveInfo PrettyPrintSemanticInfo = () type SequenceInfo PrettyPrintSemanticInfo = () type BranchInfo PrettyPrintSemanticInfo = () type SequentialLoopInfo PrettyPrintSemanticInfo = () type ParallelLoopInfo PrettyPrintSemanticInfo = () type FormalParameterInfo PrettyPrintSemanticInfo = IsRestrict type LocalDeclarationInfo PrettyPrintSemanticInfo = () type LeftValueExpressionInfo PrettyPrintSemanticInfo = () type VariableInLeftValueInfo PrettyPrintSemanticInfo = () type ArrayElemReferenceInfo PrettyPrintSemanticInfo = () type InputActualParameterInfo PrettyPrintSemanticInfo = () type OutputActualParameterInfo PrettyPrintSemanticInfo = () type AssignmentInfo PrettyPrintSemanticInfo = () type ProcedureCallInfo PrettyPrintSemanticInfo = () type FunctionCallInfo PrettyPrintSemanticInfo = () type IntConstantInfo PrettyPrintSemanticInfo = () type FloatConstantInfo PrettyPrintSemanticInfo = () type BoolConstantInfo PrettyPrintSemanticInfo = () type ArrayConstantInfo PrettyPrintSemanticInfo = () type VariableInfo PrettyPrintSemanticInfo = ()