genScheme = AST.ForGn nPar range
-- Get the entity name and port names
entity_id = ent_id entity
- argports = map (Monad.liftM fst) (ent_args entity)
- resport = (Monad.liftM fst) (ent_res entity)
+ argports = map fst (ent_args entity)
+ resport = fst (ent_res entity)
-- Assign the ports
inport = mkAssocElemIndexed (argports!!0) (varToVHDLId arg) nPar
outport = mkAssocElemIndexed resport (varToVHDLId res) nPar
- portassigns = Maybe.catMaybes [inport,outport]
+ portassigns = [inport,outport]
-- Generate the portmap
mapLabel = "map" ++ (AST.fromVHDLId entity_id)
compins = mkComponentInst mapLabel entity_id portassigns
genScheme = AST.ForGn nPar range
-- Get the entity name and port names
entity_id = ent_id entity
- argports = map (Monad.liftM fst) (ent_args entity)
- resport = (Monad.liftM fst) (ent_res entity)
+ argports = map fst (ent_args entity)
+ resport = fst (ent_res entity)
-- Assign the ports
inport1 = mkAssocElemIndexed (argports!!0) (varToVHDLId arg1) nPar
inport2 = mkAssocElemIndexed (argports!!1) (varToVHDLId arg2) nPar
outport = mkAssocElemIndexed resport (varToVHDLId res) nPar
- portassigns = Maybe.catMaybes [inport1,inport2,outport]
+ portassigns = [inport1,inport2,outport]
-- Generate the portmap
mapLabel = "zipWith" ++ (AST.fromVHDLId entity_id)
compins = mkComponentInst mapLabel entity_id portassigns
mkMap ::
--[(SignalId, SignalInfo)]
CoreSyn.CoreBndr
- -> VHDLSession VHDLSignalMapElement
+ -> VHDLSession Port
-- We only need the vsTypes element from the state
mkMap = (\bndr ->
let
-- Assume the bndr has a valid VHDL id already
id = varToVHDLId bndr
ty = Var.varType bndr
- in
- if True -- isPortSigUse $ sigUse info
- then do
- type_mark <- vhdl_ty ty
- return $ Just (id, type_mark)
- else
- return $ Nothing
- )
+ in do
+ type_mark <- vhdl_ty ty
+ return (id, type_mark)
+ )
-- | Create the VHDL AST for an entity
createEntityAST ::
AST.VHDLId -- | The name of the function
- -> [VHDLSignalMapElement] -- | The entity's arguments
- -> VHDLSignalMapElement -- | The entity's result
+ -> [Port] -- | The entity's arguments
+ -> Port -- | The entity's result
-> AST.EntityDec -- | The entity with the ent_decl filled in as well
createEntityAST vhdl_id args res =
AST.EntityDec vhdl_id ports
where
-- Create a basic Id, since VHDL doesn't grok filenames with extended Ids.
- ports = Maybe.catMaybes $
- map (mkIfaceSigDec AST.In) args
+ ports = map (mkIfaceSigDec AST.In) args
++ [mkIfaceSigDec AST.Out res]
++ [clk_port]
-- Add a clk port if we have state
- clk_port = if True -- hasState hsfunc
- then
- Just $ AST.IfaceSigDec (mkVHDLExtId "clk") AST.In std_logicTM
- else
- Nothing
+ clk_port = AST.IfaceSigDec (mkVHDLExtId "clk") AST.In std_logicTM
-- | Create a port declaration
mkIfaceSigDec ::
AST.Mode -- | The mode for the port (In / Out)
- -> Maybe (AST.VHDLId, AST.TypeMark) -- | The id and type for the port
- -> Maybe AST.IfaceSigDec -- | The resulting port declaration
+ -> (AST.VHDLId, AST.TypeMark) -- | The id and type for the port
+ -> AST.IfaceSigDec -- | The resulting port declaration
-mkIfaceSigDec mode (Just (id, ty)) = Just $ AST.IfaceSigDec id mode ty
-mkIfaceSigDec _ Nothing = Nothing
+mkIfaceSigDec mode (id, ty) = AST.IfaceSigDec id mode ty
{-
-- | Generate a VHDL entity name for the given hsfunc
-> [AST.AssocElem] -- | The resulting port maps
mkAssocElems args res entity =
-- Create the actual AssocElems
- Maybe.catMaybes $ zipWith mkAssocElem ports sigs
+ zipWith mkAssocElem ports sigs
where
-- Turn the ports and signals from a map into a flat list. This works,
-- since the maps must have an identical form by definition. TODO: Check
arg_ports = ent_args entity
res_port = ent_res entity
-- Extract the id part from the (id, type) tuple
- ports = map (Monad.liftM fst) (res_port : arg_ports)
+ ports = map fst (res_port : arg_ports)
-- Translate signal numbers into names
sigs = (vhdlNameToVHDLExpr res : args)
-- | Create an VHDL port -> signal association
-mkAssocElem :: Maybe AST.VHDLId -> AST.Expr -> Maybe AST.AssocElem
-mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADExpr signal)
-mkAssocElem Nothing _ = Nothing
+mkAssocElem :: AST.VHDLId -> AST.Expr -> AST.AssocElem
+mkAssocElem port signal = Just port AST.:=>: (AST.ADExpr signal)
-- | Create an VHDL port -> signal association
-mkAssocElemIndexed :: Maybe AST.VHDLId -> AST.VHDLId -> AST.VHDLId -> Maybe AST.AssocElem
-mkAssocElemIndexed (Just port) signal index = Just $ Just port AST.:=>: (AST.ADName (AST.NIndexed (AST.IndexedName
+mkAssocElemIndexed :: AST.VHDLId -> AST.VHDLId -> AST.VHDLId -> AST.AssocElem
+mkAssocElemIndexed port signal index = Just port AST.:=>: (AST.ADName (AST.NIndexed (AST.IndexedName
(AST.NSimple signal) [AST.PrimName $ AST.NSimple index])))
-mkAssocElemIndexed Nothing _ _ = Nothing
mkComponentInst ::
String -- ^ The portmap label
mkComponentInst label entity_id portassigns = AST.CSISm compins
where
-- We always have a clock port, so no need to map it anywhere but here
- clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLExtId "clk") (idToVHDLExpr $ mkVHDLExtId "clk")
+ clk_port = mkAssocElem (mkVHDLExtId "clk") (idToVHDLExpr $ mkVHDLExtId "clk")
compins = AST.CompInsSm (mkVHDLExtId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect (portassigns ++ [clk_port]))
-----------------------------------------------------------------------------
import qualified ForSyDe.Backend.VHDL.AST as AST
-- Local imports
-import FlattenTypes
-import HsValueMap
-type VHDLSignalMapElement = (Maybe (AST.VHDLId, AST.TypeMark))
--- | A mapping from a haskell structure to the corresponding VHDL port
--- signature, or Nothing for values that do not translate to a port.
-type VHDLSignalMap = HsValueMap VHDLSignalMapElement
+-- A description of a port of an entity
+type Port = (AST.VHDLId, AST.TypeMark)
-- A description of a VHDL entity. Contains both the entity itself as well as
-- info on how to map a haskell value (argument / result) on to the entity's
-- ports.
data Entity = Entity {
ent_id :: AST.VHDLId, -- The id of the entity
- ent_args :: [VHDLSignalMapElement], -- A mapping of each function argument to port names
- ent_res :: VHDLSignalMapElement -- A mapping of the function result to port names
+ ent_args :: [Port], -- A mapping of each function argument to port names
+ ent_res :: Port -- A mapping of the function result to port names
} deriving (Show);
-- A orderable equivalent of CoreSyn's Type for use as a map key