Store a use for each signal in a flattened function.
[matthijs/master-project/cλash.git] / VHDL.hs
diff --git a/VHDL.hs b/VHDL.hs
index 8c0a2ec93835605f964ea0745159b86a59739fd2..b23e5f3117acc6481e37062d2816c28754365d46 100644 (file)
--- a/VHDL.hs
+++ b/VHDL.hs
@@ -5,6 +5,7 @@ module VHDL where
 
 import qualified Data.Foldable as Foldable
 import qualified Maybe
+import qualified Control.Monad as Monad
 
 import qualified Type
 import qualified Name
@@ -16,6 +17,7 @@ import qualified ForSyDe.Backend.VHDL.AST as AST
 import VHDLTypes
 import FlattenTypes
 import TranslatorTypes
+import Pretty
 
 -- | Create an entity for a given function
 createEntity ::
@@ -38,7 +40,8 @@ createEntity hsfunc fdata =
         args'   = map (fmap (mkMap sigs)) args
         res'    = fmap (mkMap sigs) res
         ent_decl' = createEntityAST hsfunc args' res'
-        entity' = Entity args' res' (Just ent_decl')
+        AST.EntityDec entity_id _ = ent_decl' 
+        entity' = Entity entity_id args' res' (Just ent_decl')
       in
         setEntity hsfunc entity'
   where
@@ -108,7 +111,7 @@ createArchitecture hsfunc fdata =
       -- res
       let sig_decs = [mkSigDec info | (id, info) <- sigs, (all (id `Foldable.notElem`) (res:args)) ]
       -- Create component instantiations for all function applications
-      insts <- mapM mkCompInsSm apps
+      insts <- mapM (mkCompInsSm sigs) apps
       let insts' = map AST.CSISm insts
       let arch = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) insts'
       setArchitecture hsfunc arch
@@ -124,15 +127,60 @@ mkSigDec info =
 
 -- | Transforms a flat function application to a VHDL component instantiation.
 mkCompInsSm ::
-  FApp UnnamedSignal            -- | The application to look at.
+  [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture
+  -> FApp UnnamedSignal         -- | The application to look at.
   -> VHDLState AST.CompInsSm    -- | The corresponding VHDL component instantiation.
 
-mkCompInsSm app = do
-  return $ AST.CompInsSm label (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
+mkCompInsSm sigs app = do
+  let hsfunc = appFunc app
+  fdata_maybe <- getFunc hsfunc
+  let fdata = Maybe.fromMaybe
+        (error $ "Using function '" ++ (prettyShow hsfunc) ++ "' that is not in the session? This should not happen!")
+        fdata_maybe
+  let entity = Maybe.fromMaybe
+        (error $ "Using function '" ++ (prettyShow hsfunc) ++ "' without entity declaration? This should not happen!")
+        (funcEntity fdata)
+  let entity_id = ent_id entity
+  label <- uniqueName (AST.fromVHDLId entity_id)
+  let portmaps = mkAssocElems sigs app entity
+  return $ AST.CompInsSm (mkVHDLId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
+
+mkAssocElems :: 
+  [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture
+  -> FApp UnnamedSignal         -- | The application to look at.
+  -> Entity                     -- | The entity to map against.
+  -> [AST.AssocElem]            -- | The resulting port maps
+
+mkAssocElems sigmap app entity =
+    -- Create the actual AssocElems
+    zipWith mkAssocElem ports sigs
   where
-    entity_id = mkVHDLId "foo"
-    label     = mkVHDLId "app"
-    portmaps  = []
+    -- 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
+    -- the similar form?
+    arg_ports = concat (map Foldable.toList (ent_args entity))
+    res_ports = Foldable.toList (ent_res entity)
+    arg_sigs  = (concat (map Foldable.toList (appArgs app)))
+    res_sigs  = Foldable.toList (appRes app)
+    -- Extract the id part from the (id, type) tuple
+    ports     = (map fst (arg_ports ++ res_ports)) 
+    -- Translate signal numbers into names
+    sigs      = (map (lookupSigName sigmap) (arg_sigs ++ res_sigs))
+
+-- | Look up a signal in the signal name map
+lookupSigName :: [(UnnamedSignal, SignalInfo)] -> UnnamedSignal -> String
+lookupSigName sigs sig = name
+  where
+    info = Maybe.fromMaybe
+      (error $ "Unknown signal " ++ (show sig) ++ " used? This should not happen!")
+      (lookup sig sigs)
+    name = Maybe.fromMaybe
+      (error $ "Unnamed signal " ++ (show sig) ++ " used? This should not happen!")
+      (sigName info)
+
+-- | Create an VHDL port -> signal association
+mkAssocElem :: AST.VHDLId -> String -> AST.AssocElem
+mkAssocElem port signal = Just port AST.:=>: (AST.ADName (AST.NSimple (mkVHDLId signal))) 
 
 -- | Extracts the generated entity id from the given funcdata
 getEntityId :: FuncData -> Maybe AST.VHDLId