We now output VHDL types in the correct order
[matthijs/master-project/cλash.git] / VHDL.hs
diff --git a/VHDL.hs b/VHDL.hs
index 76cb62f827d87c24faa2e48df4af4f7527566499..13a92942e171508e13ddffcf8287a04091422a5d 100644 (file)
--- a/VHDL.hs
+++ b/VHDL.hs
@@ -12,6 +12,7 @@ import qualified Control.Arrow as Arrow
 import qualified Control.Monad.Trans.State as State
 import qualified Data.Monoid as Monoid
 import Data.Accessor
+import Debug.Trace
 
 -- ForSyDe
 import qualified ForSyDe.Backend.VHDL.AST as AST
@@ -36,7 +37,6 @@ import Pretty
 import CoreTools
 import Constants
 import Generate
-import GlobalNameTable
 
 createDesignFiles ::
   [(CoreSyn.CoreBndr, CoreSyn.CoreExpr)]
@@ -47,12 +47,11 @@ createDesignFiles binds =
   map (Arrow.second $ AST.DesignFile full_context) units
   
   where
-    init_session = VHDLState Map.empty Map.empty Map.empty Map.empty
+    init_session = VHDLState Map.empty [] Map.empty Map.empty
     (units, final_session) = 
       State.runState (createLibraryUnits binds) init_session
     tyfun_decls = map snd $ Map.elems (final_session ^.vsTypeFuns)
-    ty_decls = map mktydecl $ Map.elems (final_session ^. vsTypes)
-    vec_decls = map (\(v_id, v_def) -> AST.PDITD $ AST.TypeDec v_id v_def) (Map.elems (final_session ^. vsElemTypes))
+    ty_decls = final_session ^.vsTypeDecls
     tfvec_index_decl = AST.PDISD $ AST.SubtypeDec tfvec_indexTM tfvec_index_def
     tfvec_range = AST.ConstraintRange $ AST.SubTypeRange (AST.PrimLit "-1") (AST.PrimName $ AST.NAttribute $ AST.AttribName (AST.NSimple integerTM) highId Nothing)
     tfvec_index_def = AST.SubtypeIn integerTM (Just tfvec_range)
@@ -65,13 +64,10 @@ createDesignFiles binds =
       mkUseAll ["work", "types"]
       : (mkUseAll ["work"]
       : ieee_context)
-    type_package_dec = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") ([tfvec_index_decl] ++ vec_decls ++ ty_decls ++ subProgSpecs)
+    type_package_dec = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") ([tfvec_index_decl] ++ ty_decls ++ subProgSpecs)
     type_package_body = AST.LUPackageBody $ AST.PackageBody typesId tyfun_decls
     subProgSpecs = map subProgSpec tyfun_decls
     subProgSpec = \(AST.SubProgBody spec _ _) -> AST.PDISS spec
-    mktydecl :: (AST.VHDLId, Either AST.TypeDef AST.SubtypeIn) -> AST.PackageDecItem
-    mktydecl (ty_id, Left ty_def) = AST.PDITD $ AST.TypeDec ty_id ty_def
-    mktydecl (ty_id, Right ty_def) = AST.PDISD $ AST.SubtypeDec ty_id ty_def
 
 -- Create a use foo.bar.all statement. Takes a list of components in the used
 -- name. Must contain at least two components
@@ -119,7 +115,7 @@ createEntity (fname, expr) = do
     mkMap ::
       --[(SignalId, SignalInfo)] 
       CoreSyn.CoreBndr 
-      -> VHDLSession VHDLSignalMapElement
+      -> VHDLSession Port
     -- We only need the vsTypes element from the state
     mkMap = (\bndr ->
       let
@@ -129,45 +125,36 @@ createEntity (fname, expr) = do
         --  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
-       )
+        error_msg = "\nVHDL.createEntity.mkMap: Can not create entity: " ++ pprString fname ++ "\nbecause no type can be created for port: " ++ pprString bndr 
+      in do
+        type_mark <- vhdl_ty error_msg 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
@@ -186,7 +173,7 @@ createArchitecture ::
 createArchitecture (fname, expr) = do
   signaturemap <- getA vsSignatures
   let signature = Maybe.fromMaybe 
-        (error $ "Generating architecture for function " ++ (pprString fname) ++ "without signature? This should not happen!")
+        (error $ "\nVHDL.createArchitecture: Generating architecture for function \n" ++ (pprString fname) ++ "\nwithout signature? This should not happen!")
         (Map.lookup fname signaturemap)
   let entity_id = ent_id signature
   -- Strip off lambda's, these will be arguments
@@ -249,7 +236,8 @@ getSignalId info =
 mkSigDec :: CoreSyn.CoreBndr -> VHDLSession (Maybe AST.SigDec)
 mkSigDec bndr =
   if True then do --isInternalSigUse use || isStateSigUse use then do
-    type_mark <- vhdl_ty $ Var.varType bndr
+    let error_msg = "\nVHDL.mkSigDec: Can not make signal declaration for type: \n" ++ pprString bndr 
+    type_mark <- (vhdl_ty error_msg) $ Var.varType bndr
     return $ Just (AST.SigDec (varToVHDLId bndr) type_mark Nothing)
   else
     return Nothing
@@ -272,69 +260,8 @@ mkConcSm (bndr, Var v) = return $ [mkUncondAssign (Left bndr) (varToVHDLExpr v)]
 
 mkConcSm (bndr, app@(CoreSyn.App _ _))= do
   let (CoreSyn.Var f, args) = CoreSyn.collectArgs app
-  let valargs' = filter isValArg args
-  let valargs = filter (\(CoreSyn.Var bndr) -> not (Id.isDictId bndr)) valargs'
-  case Var.globalIdVarDetails f of
-    IdInfo.DataConWorkId dc ->
-        -- It's a datacon. Create a record from its arguments.
-        -- First, filter out type args. TODO: Is this the best way to do this?
-        -- The types should already have been taken into acocunt when creating
-        -- the signal, so this should probably work...
-        --let valargs = filter isValArg args in
-        if all is_var valargs then do
-          labels <- getFieldLabels (CoreUtils.exprType app)
-          return $ zipWith mkassign labels valargs
-        else
-          error $ "VHDL.mkConcSm Not in normal form: One ore more complex arguments: " ++ pprString args
-      where
-        mkassign :: AST.VHDLId -> CoreExpr -> AST.ConcSm
-        mkassign label (Var arg) =
-          let sel_name = mkSelectedName bndr label in
-          mkUncondAssign (Right sel_name) (varToVHDLExpr arg)
-    IdInfo.VanillaGlobal -> do
-      -- It's a global value imported from elsewhere. These can be builtin
-      -- functions.
-      signatures <- getA vsSignatures
-      case (Map.lookup (varToString f) globalNameTable) of
-        Just (arg_count, builder) ->
-          if length valargs == arg_count then
-            case builder of
-              Left funBuilder -> do
-                let sigs = map (varToVHDLExpr.exprToVar) valargs
-                func <- funBuilder bndr sigs
-                let src_wform = AST.Wform [AST.WformElem func Nothing]
-                let dst_name = AST.NSimple (mkVHDLExtId (varToString bndr))
-                let assign = dst_name AST.:<==: (AST.ConWforms [] src_wform Nothing)
-                return [AST.CSSASm assign]
-              Right genBuilder -> do
-                let sigs = map exprToVar valargs
-                let signature = Maybe.fromMaybe
-                      (error $ "Using function '" ++ (varToString (head sigs)) ++ "' without signature? This should not happen!") 
-                      (Map.lookup (head sigs) signatures)
-                let arg = tail sigs
-                genSm <- genBuilder signature (arg ++ [bndr])  
-                return [AST.CSGSm genSm]
-          else
-            error $ "VHDL.mkConcSm Incorrect number of arguments to builtin function: " ++ pprString f ++ " Args: " ++ pprString valargs
-        Nothing -> error $ "Using function from another module that is not a known builtin: " ++ pprString f
-    IdInfo.NotGlobalId -> do
-      signatures <- getA vsSignatures
-      -- This is a local id, so it should be a function whose definition we
-      -- have and which can be turned into a component instantiation.
-      let  
-        signature = Maybe.fromMaybe 
-          (error $ "Using function '" ++ (varToString f) ++ "' without signature? This should not happen!") 
-          (Map.lookup f signatures)
-        entity_id = ent_id signature
-        label = "comp_ins_" ++ varToString bndr
-        -- Add a clk port if we have state
-        --clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLExtId "clk") "clk"
-        clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLExtId "clk") "clk"
-        --portmaps = mkAssocElems sigs args res signature ++ (if hasState hsfunc then [clk_port] else [])
-        portmaps = clk_port : mkAssocElems args bndr signature
-        in
-          return [mkComponentInst label entity_id portmaps]
-    details -> error $ "Calling unsupported function " ++ pprString f ++ " with GlobalIdDetails " ++ pprString details
+  let valargs = get_val_args (Var.varType f) args
+  genApplication (Left bndr) f (map Left valargs)
 
 -- A single alt case must be a selector. This means thee scrutinee is a simple
 -- variable, the alternative is a dataalt with a single non-wild binder that
@@ -346,12 +273,12 @@ mkConcSm (bndr, expr@(Case (Var scrut) b ty [alt])) =
         Just i -> do
           labels <- getFieldLabels (Id.idType scrut)
           let label = labels!!i
-          let sel_name = mkSelectedName scrut label
+          let sel_name = mkSelectedName (varToVHDLName scrut) label
           let sel_expr = AST.PrimName sel_name
           return [mkUncondAssign (Left bndr) sel_expr]
-        Nothing -> error $ "VHDL.mkConcSM Not in normal form: Not a selector case:\n" ++ (pprString expr)
+        Nothing -> error $ "\nVHDL.mkConcSM: Not in normal form: Not a selector case:\n" ++ (pprString expr)
       
-    _ -> error $ "VHDL.mkConcSM Not in normal form: Not a selector case:\n" ++ (pprString expr)
+    _ -> error $ "\nVHDL.mkConcSM: Not in normal form: Not a selector case:\n" ++ (pprString expr)
 
 -- Multiple case alt are be conditional assignments and have only wild
 -- binders in the alts and only variables in the case values and a variable
@@ -364,6 +291,6 @@ mkConcSm (bndr, (Case (Var scrut) b ty [(_, _, Var false), (con, _, Var true)]))
     false_expr  = (varToVHDLExpr false)
   in
     return [mkCondAssign (Left bndr) cond_expr true_expr false_expr]
-mkConcSm (_, (Case (Var _) _ _ alts)) = error "VHDL.mkConcSm Not in normal form: Case statement with more than two alternatives"
-mkConcSm (_, Case _ _ _ _) = error "VHDL.mkConcSm Not in normal form: Case statement has does not have a simple variable as scrutinee"
-mkConcSm (bndr, expr) = error $ "VHDL.mkConcSM Unsupported binding in let expression: " ++ pprString bndr ++ " = " ++ pprString expr
+mkConcSm (_, (Case (Var _) _ _ alts)) = error "\nVHDL.mkConcSm: Not in normal form: Case statement with more than two alternatives"
+mkConcSm (_, Case _ _ _ _) = error "\nVHDL.mkConcSm: Not in normal form: Case statement has does not have a simple variable as scrutinee"
+mkConcSm (bndr, expr) = error $ "\nVHDL.mkConcSM: Unsupported binding in let expression: " ++ pprString bndr ++ " = " ++ pprString expr