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 6b8b7b6d3ba26635ad94832659b9d41dc30615c9..b23e5f3117acc6481e37062d2816c28754365d46 100644 (file)
--- a/VHDL.hs
+++ b/VHDL.hs
@@ -3,9 +3,9 @@
 --
 module VHDL where
 
-import Data.Traversable
 import qualified Data.Foldable as Foldable
 import qualified Maybe
+import qualified Control.Monad as Monad
 
 import qualified Type
 import qualified Name
@@ -17,18 +17,19 @@ import qualified ForSyDe.Backend.VHDL.AST as AST
 import VHDLTypes
 import FlattenTypes
 import TranslatorTypes
+import Pretty
 
 -- | Create an entity for a given function
 createEntity ::
   HsFunction        -- | The function signature
   -> FuncData       -- | The function data collected so far
-  -> FuncData       -- | The modified function data
+  -> VHDLState ()
 
 createEntity hsfunc fdata = 
   let func = flatFunc fdata in
   case func of
     -- Skip (builtin) functions without a FlatFunction
-    Nothing -> fdata
+    Nothing -> do return ()
     -- Create an entity for all other functions
     Just flatfunc ->
       
@@ -39,9 +40,10 @@ 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
-        fdata { funcEntity = Just entity' }
+        setEntity hsfunc entity'
   where
     mkMap :: Eq id => [(id, SignalInfo)] -> id -> (AST.VHDLId, AST.TypeMark)
     mkMap sigmap id =
@@ -89,31 +91,30 @@ mkEntityId hsfunc =
 createArchitecture ::
   HsFunction        -- | The function signature
   -> FuncData       -- | The function data collected so far
-  -> FuncData       -- | The modified function data
+  -> VHDLState ()
 
 createArchitecture hsfunc fdata = 
   let func = flatFunc fdata in
   case func of
     -- Skip (builtin) functions without a FlatFunction
-    Nothing -> fdata
+    Nothing -> do return ()
     -- Create an architecture for all other functions
-    Just flatfunc ->
-      let 
-        sigs      = flat_sigs flatfunc
-        args      = flat_args flatfunc
-        res       = flat_res  flatfunc
-        apps      = flat_apps flatfunc
-        entity_id = Maybe.fromMaybe
+    Just flatfunc -> do
+      let sigs = flat_sigs flatfunc
+      let args = flat_args flatfunc
+      let res  = flat_res  flatfunc
+      let apps = flat_apps flatfunc
+      let entity_id = Maybe.fromMaybe
                       (error $ "Building architecture without an entity? This should not happen!")
                       (getEntityId fdata)
-        -- Create signal declarations for all signals that are not in args and
-        -- res
-        sig_decs = [mkSigDec info | (id, info) <- sigs, (all (id `Foldable.notElem`) (res:args)) ]
-        -- Create component instantiations for all function applications
-        insts    = map (AST.CSISm . mkCompInsSm) apps
-        arch     = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) insts
-      in
-        fdata { funcArch = Just arch }
+      -- Create signal declarations for all signals that are not in args and
+      -- 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 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
 
 mkSigDec :: SignalInfo -> AST.SigDec
 mkSigDec info =
@@ -126,15 +127,60 @@ mkSigDec info =
 
 -- | Transforms a flat function application to a VHDL component instantiation.
 mkCompInsSm ::
-  FApp UnnamedSignal  -- | The application to look at.
-  -> AST.CompInsSm    -- | The corresponding VHDL component instantiation.
-
-mkCompInsSm app =
-  AST.CompInsSm label (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
+  [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture
+  -> FApp UnnamedSignal         -- | The application to look at.
+  -> VHDLState AST.CompInsSm    -- | The corresponding VHDL component instantiation.
+
+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