X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=Generate.hs;h=654dc8625cbc864ce49c15a9c7963d05419bda80;hb=597f1b6823417f2c4cc54549f2a9d1b9f131893c;hp=2beacb8d5616e7c9014f3fef35a6644d02773a49;hpb=91914df9b344ccf0bc3242dc28ce74a8d6721944;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/Generate.hs b/Generate.hs index 2beacb8..654dc86 100644 --- a/Generate.hs +++ b/Generate.hs @@ -1,7 +1,30 @@ module Generate where - + +-- Standard modules +import qualified Control.Monad as Monad +import qualified Maybe + +-- ForSyDe import qualified ForSyDe.Backend.VHDL.AST as AST + +-- GHC API +import CoreSyn +import qualified Var + +-- Local imports import Constants +import VHDLTypes +import VHDLTools +import CoreTools + +-- | Generate a binary operator application. The first argument should be a +-- constructor from the AST.Expr type, e.g. AST.And. +genExprOp2 :: (AST.Expr -> AST.Expr -> AST.Expr) -> [AST.Expr] -> AST.Expr +genExprOp2 op [arg1, arg2] = op arg1 arg2 + +-- | Generate a unary operator application +genExprOp1 :: (AST.Expr -> AST.Expr) -> [AST.Expr] -> AST.Expr +genExprOp1 op [arg] = op arg -- | Generate a function call from the Function Name and a list of expressions -- (its arguments) @@ -10,15 +33,33 @@ genExprFCall fName args = AST.PrimFCall $ AST.FCall (AST.NSimple fName) $ map (\exp -> Nothing AST.:=>: AST.ADExpr exp) args --- | List version of genExprFCall1 -genExprFCall1L :: AST.VHDLId -> [AST.Expr] -> AST.Expr -genExprFCall1L fName [arg] = genExprFCall fName [arg] -genExprFCall1L _ _ = error "Generate.genExprFCall1L incorrect length" - --- | List version of genExprFCall2 -genExprFCall2L :: AST.VHDLId -> [AST.Expr] -> AST.Expr -genExprFCall2L fName [arg1, arg2] = genExprFCall fName [arg1,arg2] -genExprFCall2L _ _ = error "Generate.genExprFCall2L incorrect length" +-- | Generate a generate statement for the builtin function "map" +genMapCall :: + Entity -- | The entity to map + -> [CoreSyn.CoreBndr] -- | The vectors + -> AST.GenerateSm -- | The resulting generate statement +genMapCall entity [arg, res] = genSm + where + -- Setup the generate scheme + len = (tfvec_len . Var.varType) res + label = mkVHDLExtId ("mapVector" ++ (varToString res)) + nPar = AST.unsafeVHDLBasicId "n" + range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1)) + genScheme = AST.ForGn nPar range + -- Get the entity name and port names + entity_id = ent_id entity + argport = map (Monad.liftM fst) (ent_args entity) + resport = (Monad.liftM fst) (ent_res entity) + -- Assign the ports + inport = mkAssocElemIndexed (head argport) (varToString arg) nPar + outport = mkAssocElemIndexed resport (varToString res) nPar + clk_port = mkAssocElem (Just $ mkVHDLExtId "clk") "clk" + portassigns = Maybe.catMaybes [inport,outport,clk_port] + -- Generate the portmap + mapLabel = "map" ++ (AST.fromVHDLId entity_id) + compins = mkComponentInst mapLabel entity_id portassigns + -- Return the generate functions + genSm = AST.GenerateSm label genScheme [] [compins] genUnconsVectorFuns :: AST.TypeMark -- ^ type of the vector elements -> AST.TypeMark -- ^ type of the vector @@ -31,7 +72,11 @@ genUnconsVectorFuns elemTM vectorTM = , AST.SubProgBody initSpec [AST.SPVD initVar] [initExpr, initRet] , AST.SubProgBody tailSpec [AST.SPVD tailVar] [tailExpr, tailRet] , AST.SubProgBody takeSpec [AST.SPVD takeVar] [takeExpr, takeRet] - , AST.SubProgBody dropSpec [AST.SPVD dropVar] [dropExpr, dropRet] + , AST.SubProgBody dropSpec [AST.SPVD dropVar] [dropExpr, dropRet] + , AST.SubProgBody plusgtSpec [AST.SPVD plusgtVar] [plusgtExpr, plusgtRet] + , AST.SubProgBody emptySpec [AST.SPVD emptyVar] [emptyExpr] + , AST.SubProgBody singletonSpec [AST.SPVD singletonVar] [singletonRet] + , AST.SubProgBody copySpec [AST.SPVD copyVar] [copyExpr] ] where ixPar = AST.unsafeVHDLBasicId "ix" @@ -54,7 +99,7 @@ genUnconsVectorFuns elemTM vectorTM = replaceVar = AST.VarDec resId (AST.SubtypeIn vectorTM - (Just $ AST.IndexConstraint + (Just $ AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimName (AST.NAttribute $ AST.AttribName (AST.NSimple vecPar) lengthId Nothing) AST.:-: @@ -89,7 +134,7 @@ genUnconsVectorFuns elemTM vectorTM = initVar = AST.VarDec resId (AST.SubtypeIn vectorTM - (Just $ AST.IndexConstraint + (Just $ AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimName (AST.NAttribute $ AST.AttribName (AST.NSimple vecPar) lengthId Nothing) AST.:-: @@ -107,7 +152,7 @@ genUnconsVectorFuns elemTM vectorTM = tailVar = AST.VarDec resId (AST.SubtypeIn vectorTM - (Just $ AST.IndexConstraint + (Just $ AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimName (AST.NAttribute $ AST.AttribName (AST.NSimple vecPar) lengthId Nothing) AST.:-: @@ -126,7 +171,7 @@ genUnconsVectorFuns elemTM vectorTM = takeVar = AST.VarDec resId (AST.SubtypeIn vectorTM - (Just $ AST.IndexConstraint + (Just $ AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") ((AST.PrimName (AST.NSimple nPar)) AST.:-: (AST.PrimLit "1")) ])) @@ -142,7 +187,7 @@ genUnconsVectorFuns elemTM vectorTM = dropVar = AST.VarDec resId (AST.SubtypeIn vectorTM - (Just $ AST.IndexConstraint + (Just $ AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimName (AST.NAttribute $ AST.AttribName (AST.NSimple vecPar) lengthId Nothing) AST.:-: @@ -154,4 +199,53 @@ genUnconsVectorFuns elemTM vectorTM = (AST.PrimName (AST.NAttribute $ AST.AttribName (AST.NSimple vecPar) lengthId Nothing) AST.:-: AST.PrimLit "1")) - dropRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId) \ No newline at end of file + dropRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId) + plusgtSpec = AST.Function plusgtId [AST.IfaceVarDec aPar elemTM, + AST.IfaceVarDec vecPar vectorTM] vectorTM + -- variable res : fsvec_x (0 to vec'length); + plusgtVar = + AST.VarDec resId + (AST.SubtypeIn vectorTM + (Just $ AST.ConstraintIndex $ AST.IndexConstraint + [AST.ToRange (AST.PrimLit "0") + (AST.PrimName (AST.NAttribute $ + AST.AttribName (AST.NSimple vecPar) lengthId Nothing))])) + Nothing + plusgtExpr = AST.NSimple resId AST.:= + ((AST.PrimName $ AST.NSimple aPar) AST.:&: + (AST.PrimName $ AST.NSimple vecPar)) + plusgtRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId) + emptySpec = AST.Function emptyId [] vectorTM + emptyVar = + AST.VarDec resId + (AST.SubtypeIn vectorTM + (Just $ AST.ConstraintIndex $ AST.IndexConstraint + [AST.ToRange (AST.PrimLit "0") + (AST.PrimLit "-1")])) + Nothing + emptyExpr = AST.ReturnSm (Just $ AST.PrimName (AST.NSimple resId)) + singletonSpec = AST.Function singletonId [AST.IfaceVarDec aPar elemTM ] + vectorTM + -- variable res : fsvec_x (0 to 0) := (others => a); + singletonVar = + AST.VarDec resId + (AST.SubtypeIn vectorTM + (Just $ AST.ConstraintIndex $ AST.IndexConstraint + [AST.ToRange (AST.PrimLit "0") (AST.PrimLit "0")])) + (Just $ AST.Aggregate [AST.ElemAssoc (Just AST.Others) + (AST.PrimName $ AST.NSimple aPar)]) + singletonRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId) + copySpec = AST.Function copyId [AST.IfaceVarDec nPar naturalTM, + AST.IfaceVarDec aPar elemTM ] vectorTM + -- variable res : fsvec_x (0 to n-1) := (others => a); + copyVar = + AST.VarDec resId + (AST.SubtypeIn vectorTM + (Just $ AST.ConstraintIndex $ AST.IndexConstraint + [AST.ToRange (AST.PrimLit "0") + ((AST.PrimName (AST.NSimple nPar)) AST.:-: + (AST.PrimLit "1")) ])) + (Just $ AST.Aggregate [AST.ElemAssoc (Just AST.Others) + (AST.PrimName $ AST.NSimple aPar)]) + -- return res + copyExpr = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)