Make application names unique.
[matthijs/master-project/cλash.git] / VHDL.hs
diff --git a/VHDL.hs b/VHDL.hs
index eac7079155bd8d0b89e02aa441b321e9be890874..9c130d4b93cdf4db6ec1c55f2353ba2a5f60ff0d 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,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 ::
@@ -39,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
@@ -97,23 +99,22 @@ createArchitecture hsfunc fdata =
     -- Skip (builtin) functions without a FlatFunction
     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
-        setArchitecture hsfunc 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 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,14 +127,22 @@ 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)
+  FApp UnnamedSignal            -- | The application to look at.
+  -> VHDLState AST.CompInsSm    -- | The corresponding VHDL component instantiation.
+
+mkCompInsSm 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)
+  return $ AST.CompInsSm (mkVHDLId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
   where
-    entity_id = mkVHDLId "foo"
-    label     = mkVHDLId "app"
     portmaps  = []
 
 -- | Extracts the generated entity id from the given funcdata