-- -- 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 data InitSemInf data PrettyPrintSemanticInfo data IsRestrict = Restrict | NoRestrict deriving (Show,Eq) data IsDefaultArraySize = DefaultArraySize | NoDefaultArraySize deriving (Show,Eq) -- ==================================================================================================== -- == Semantic info class -- ==================================================================================================== class ( Show(ProcedureInfo t), Eq(ProcedureInfo t), Show(BlockInfo t), Eq(BlockInfo t), Show(ProgramInfo t), Eq(ProgramInfo t), Show(EmptyInfo t), Eq(EmptyInfo t), Show(PrimitiveInfo t), Eq(PrimitiveInfo t), Show(SequenceInfo t), Eq(SequenceInfo t), Show(BranchInfo t), Eq(BranchInfo t), Show(SequentialLoopInfo t), Eq(SequentialLoopInfo t), Show(ParallelLoopInfo t), Eq(ParallelLoopInfo t), Show(FormalParameterInfo t), Eq(FormalParameterInfo t), Show(LocalDeclarationInfo t), Eq(LocalDeclarationInfo t), Show(ExpressionInfo t), Eq(ExpressionInfo t), Show(ConstantInfo t), Eq(ConstantInfo t), Show(FunctionCallInfo t), Eq(FunctionCallInfo t), Show(LeftValueInfo t), Eq(LeftValueInfo t), Show(ArrayElemReferenceInfo t), Eq(ArrayElemReferenceInfo t), Show(InstructionInfo t), Eq(InstructionInfo t), Show(AssignmentInfo t), Eq(AssignmentInfo t), Show(ProcedureCallInfo t), Eq(ProcedureCallInfo t), Show(ActualParameterInfo t), Eq(ActualParameterInfo t), Show(IntConstantInfo t), Eq(IntConstantInfo t), Show(FloatConstantInfo t), Eq(FloatConstantInfo t), Show(BoolConstantInfo t), Eq(BoolConstantInfo t), Show(ArrayConstantInfo t), Eq(ArrayConstantInfo t), Show(VariableInfo 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 ExpressionInfo t type ConstantInfo t type FunctionCallInfo t type LeftValueInfo t type ArrayElemReferenceInfo t type InstructionInfo t type AssignmentInfo t type ProcedureCallInfo t type ActualParameterInfo t type IntConstantInfo t type FloatConstantInfo t type BoolConstantInfo t type ArrayConstantInfo t type VariableInfo t 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 ExpressionInfo () = () type ConstantInfo () = () type FunctionCallInfo () = () type LeftValueInfo () = () type ArrayElemReferenceInfo () = () type InstructionInfo () = () type AssignmentInfo () = () type ProcedureCallInfo () = () type ActualParameterInfo () = () type IntConstantInfo () = () type FloatConstantInfo () = () type BoolConstantInfo () = () type ArrayConstantInfo () = () type VariableInfo () = () 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 ExpressionInfo InitSemInf = () type ConstantInfo InitSemInf = () type FunctionCallInfo InitSemInf = () type LeftValueInfo InitSemInf = () type ArrayElemReferenceInfo InitSemInf = () type InstructionInfo InitSemInf = () type AssignmentInfo InitSemInf = () type ProcedureCallInfo InitSemInf = () type ActualParameterInfo InitSemInf = () type IntConstantInfo InitSemInf = () type FloatConstantInfo InitSemInf = () type BoolConstantInfo InitSemInf = () type ArrayConstantInfo InitSemInf = () type VariableInfo InitSemInf = () 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 ExpressionInfo PrettyPrintSemanticInfo = () type ConstantInfo PrettyPrintSemanticInfo = () type FunctionCallInfo PrettyPrintSemanticInfo = () type LeftValueInfo PrettyPrintSemanticInfo = () type ArrayElemReferenceInfo PrettyPrintSemanticInfo = () type InstructionInfo PrettyPrintSemanticInfo = () type AssignmentInfo PrettyPrintSemanticInfo = () type ProcedureCallInfo PrettyPrintSemanticInfo = () type ActualParameterInfo PrettyPrintSemanticInfo = () type IntConstantInfo PrettyPrintSemanticInfo = () type FloatConstantInfo PrettyPrintSemanticInfo = () type BoolConstantInfo PrettyPrintSemanticInfo = () type ArrayConstantInfo PrettyPrintSemanticInfo = () type VariableInfo PrettyPrintSemanticInfo = ()