module Feldspar.Compiler.Imperative.Frontend where import Feldspar.Compiler.Imperative.Representation import qualified Feldspar.Compiler.Imperative.Representation as Representation import Feldspar.Core.Types -- =========================================================================== -- == Program generator tools -- =========================================================================== emptyPrg :: Program () emptyPrg = Representation.Empty { emptyLabel = () , programLabel = () } genCopy :: Expression () -> Expression () -> Program () genCopy lhs rhs = ProcedureCall { procCallName = copy , procCallParams = [ In { inParam = rhs , actParamLabel = () } , Out { outParam = lhs , actParamLabel = () } ] , procCallLabel = () , programLabel = () } createConstantExpression c = ConstExpr { constExpr = c , exprLabel = () } createLoopVariable :: String -> Representation.Variable () createLoopVariable name = Representation.Variable { varName = name , varType = NumType Signed S32 , varRole = Representation.Value , varLabel = () } createVariable :: String -> Representation.Type -> Representation.Variable () createVariable name typ = Representation.Variable { varName = name , varType = typ -- compileTypeRep typ , varRole = Representation.Value , varLabel = () } createVariableLeftValue :: String -> Representation.Type -> Expression () createVariableLeftValue name typ = VarExpr { var = createVariable name typ , exprLabel = () } createProgramSequence :: [Program ()] -> Program () createProgramSequence programs = Sequence { sequenceProgs = programs , sequenceLabel = () , programLabel = () } createDeclaration :: String -> Representation.Type -> Declaration () createDeclaration name typ = Declaration { declVar = createVariable name typ , initVal = Nothing , declLabel = () } programToBlock :: Program () -> Block () programToBlock p = Block { locals = [] , blockBody = p , blockLabel = () } procedure symbol inArgs outArgs block = Procedure symbol inArgs outArgs block () () procedureCall symbol inArgs outArgs = ProcedureCall symbol (inArgs ++ outArgs) () () seqLoop cond condcalcblock core = SeqLoop cond condcalcblock core () () condBranch cond bt be = Branch cond bt be () () switch cond cases = Switch cond cases () () switchCase pattern impl = SwitchCase pattern impl () parLoop index length step block = ParLoop index length step block () () comment isblockcomment str = Comment isblockcomment str () () globalVar decl = GlobalVar decl () () intConstExpr :: Integer -> Expression () intConstExpr val = ConstExpr (intConst val) () intConstExprConv :: Int -> Expression () intConstExprConv val = ConstExpr (intConstConv val) () intConst :: Integer -> Constant () intConst val = IntConst val () () intConstConv :: Int -> Constant () intConstConv val = IntConst (toInteger val) () () functionCall :: String -> Representation.Type -> [Expression ()] -> Expression () functionCall symbol typ args = FunctionCall symbol typ SimpleFun args () () arrayElem :: Expression () -> Expression () -> Expression () arrayElem lv ix = ArrayElem lv ix () () blockProgram :: Block () -> Program () blockProgram = flip BlockProgram () declaration :: Variable () -> Maybe (Expression ()) -> Declaration () declaration var initval = Declaration var initval () varExpr :: Variable () -> Expression () varExpr var = VarExpr var () varActualParam :: Variable () -> (Expression () -> () -> ActualParameter ()) -> ActualParameter () varActualParam v role = role (varExpr v) () block :: [Declaration ()] -> [Program ()] -> Block () block decls actions = Block decls prog () where prog = case actions of [] -> Empty () () _ -> Sequence (concatMap act actions) () () act (Empty _ _) = [] act (Sequence seq _ _) = seq act a = [a] variable :: String -> Representation.Type -> Variable () variable name typ = Variable name typ Value () -- Using 'Value' for all variables; the correct role will be set in a later -- stage copy :: String copy = "copy" setLength :: Expression () -> Expression () -> Program () setLength arr len = procedureCall "setLength" [Out arr ()] [In len ()] increaseLength :: Expression () -> Expression () -> Program () increaseLength arr len = procedureCall "increaseLength" [Out arr ()] [In len ()] copyProg :: Expression () -> Expression () -> Program () copyProg outExp inExp = ProcedureCall copy [Out outExp (), In inExp ()] () () copyProgPos :: Expression () -> Expression () -> Expression () -> Program () copyProgPos outExp shift inExp = ProcedureCall "copyArrayPos" [Out outExp (), In shift (), In inExp ()] () () copyProgLen :: Expression () -> Expression () -> Expression () -> Program () copyProgLen outExp inExp len = ProcedureCall "copyArrayLen" [Out outExp (), In inExp (), In len ()] () ()