Added +> function, started on map
authorChristiaan Baaij <christiaan.baaij@gmail.com>
Tue, 23 Jun 2009 11:38:13 +0000 (13:38 +0200)
committerChristiaan Baaij <christiaan.baaij@gmail.com>
Tue, 23 Jun 2009 11:38:13 +0000 (13:38 +0200)
Generate.hs
GlobalNameTable.hs

index d3c05ab23e2447794c3df66d5f74015017f33349..8053f9852a5653107e1f802842727214f14516fb 100644 (file)
@@ -1,7 +1,11 @@
 module Generate where
-  
+
+import qualified Control.Monad as Monad
+import qualified Maybe
+
 import qualified ForSyDe.Backend.VHDL.AST as AST
 import Constants
+import VHDLTypes
 
 -- | Generate a binary operator application. The first argument should be a
 -- constructor from the AST.Expr type, e.g. AST.And.
@@ -19,6 +23,33 @@ genExprFCall fName args =
    AST.PrimFCall $ AST.FCall (AST.NSimple fName)  $
              map (\exp -> Nothing AST.:=>: AST.ADExpr exp) args
 
+-- | Generate a generate statement for the builtin function "map"
+genMapCall :: 
+  Int -- | The length of the vector 
+  -> Entity -- | The entity to map
+  -> AST.VHDLId -- | The input vector
+  -> AST.VHDLId -- | The output vector
+  -> AST.GenerateSm -- | The resulting generate statement
+genMapCall len entity arg res = genSm
+  where
+    label = AST.unsafeVHDLBasicId "mapVector"
+    nPar  = AST.unsafeVHDLBasicId "n"
+    range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
+    genScheme = AST.ForGn nPar range
+    entity_id = ent_id entity
+    argport = map (Monad.liftM fst) (ent_args entity)
+    resport = (Monad.liftM fst) (ent_res entity)
+    inport = mkAssocElem (head argport) arg
+    outport = mkAssocElem resport res
+    portmaps = Maybe.catMaybes [inport,outport]
+    portmap = AST.CSISm $ AST.CompInsSm (AST.unsafeVHDLBasicId "map12") (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
+    genSm = AST.GenerateSm label genScheme [] [portmap]
+    -- | Create an VHDL port -> signal association
+    mkAssocElem :: Maybe AST.VHDLId -> AST.VHDLId -> Maybe AST.AssocElem
+    mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADName (AST.NIndexed (AST.IndexedName 
+                    (AST.NSimple signal) [AST.PrimName $ AST.NSimple nPar])))
+    mkAssocElem Nothing _ = Nothing
+
 genUnconsVectorFuns :: AST.TypeMark -- ^ type of the vector elements
                     -> AST.TypeMark -- ^ type of the vector
                     -> [AST.SubProgBody]
@@ -30,7 +61,8 @@ 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]     
   ]
   where 
     ixPar   = AST.unsafeVHDLBasicId "ix"
@@ -154,3 +186,18 @@ genUnconsVectorFuns elemTM vectorTM  =
                                   AST.AttribName (AST.NSimple vecPar) lengthId Nothing) 
                                                              AST.:-: AST.PrimLit "1"))
     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)
index 237a4bdc0e17dc46a6ad908bfde1b4dd73d2adc4..cf585ea50a88607ef146f7654f2510a7ace02765 100644 (file)
@@ -25,6 +25,7 @@ globalNameTable = mkGlobalNameTable
   , ("init"           , (1, genExprFCall initId                           ) )
   , ("take"           , (2, genExprFCall takeId                           ) )
   , ("drop"           , (2, genExprFCall dropId                           ) )
+  , ("+>"             , (2, genExprFCall plusgtId                         ) )
   , ("hwxor"          , (2, genExprOp2 AST.Xor                            ) )
   , ("hwand"          , (2, genExprOp2 AST.And                            ) )
   , ("hwor"           , (2, genExprOp2 AST.Or                             ) )