Make application names unique.
[matthijs/master-project/cλash.git] / VHDL.hs
diff --git a/VHDL.hs b/VHDL.hs
index 8c2fe0315b525a96fa1585b14b11b0b9b9051ef1..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,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,28 +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
-        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)) ]
-        arch     = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) []
-      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 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 =
@@ -120,7 +124,27 @@ mkSigDec info =
       (error $ "Unnamed signal? This should not happen!")
       (sigName info)
     ty = sigTy info
-    
+
+-- | Transforms a flat function application to a VHDL component instantiation.
+mkCompInsSm ::
+  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
+    portmaps  = []
+
 -- | Extracts the generated entity id from the given funcdata
 getEntityId :: FuncData -> Maybe AST.VHDLId
 getEntityId fdata =