Merge git://github.com/darchon/clash into cλash
[matthijs/master-project/cλash.git] / VHDL.hs
diff --git a/VHDL.hs b/VHDL.hs
index f838cbafcf5a4f9ee30a1ec73673543e84800c56..13a92942e171508e13ddffcf8287a04091422a5d 100644 (file)
--- a/VHDL.hs
+++ b/VHDL.hs
@@ -4,18 +4,14 @@
 module VHDL where
 
 -- Standard modules
-import qualified Data.Foldable as Foldable
 import qualified Data.List as List
 import qualified Data.Map as Map
 import qualified Maybe
 import qualified Control.Monad as Monad
 import qualified Control.Arrow as Arrow
 import qualified Control.Monad.Trans.State as State
-import qualified Data.Traversable as Traversable
 import qualified Data.Monoid as Monoid
 import Data.Accessor
-import qualified Data.Accessor.MonadState as MonadState
-import Text.Regex.Posix
 import Debug.Trace
 
 -- ForSyDe
@@ -23,25 +19,24 @@ import qualified ForSyDe.Backend.VHDL.AST as AST
 
 -- GHC API
 import CoreSyn
-import qualified Type
+--import qualified Type
 import qualified Name
-import qualified OccName
 import qualified Var
+import qualified Id
+import qualified IdInfo
 import qualified TyCon
 import qualified DataCon
+--import qualified CoreSubst
+import qualified CoreUtils
 import Outputable ( showSDoc, ppr )
 
 -- Local imports
 import VHDLTypes
-import Flatten
-import FlattenTypes
-import TranslatorTypes
-import HsValueMap
+import VHDLTools
 import Pretty
 import CoreTools
 import Constants
 import Generate
-import GlobalNameTable
 
 createDesignFiles ::
   [(CoreSyn.CoreBndr, CoreSyn.CoreExpr)]
@@ -52,12 +47,14 @@ createDesignFiles binds =
   map (Arrow.second $ AST.DesignFile full_context) units
   
   where
-    init_session = VHDLSession Map.empty Map.empty Map.empty builtin_funcs globalNameTable
+    init_session = VHDLState Map.empty [] Map.empty Map.empty
     (units, final_session) = 
       State.runState (createLibraryUnits binds) init_session
-    ty_decls = Map.elems (final_session ^. vsTypes)
-    subty_decls = Map.elems (final_session ^. vsSubTypes)
-    tyfun_decls = Map.elems (final_session ^.vsTypeFuns)
+    tyfun_decls = map snd $ Map.elems (final_session ^.vsTypeFuns)
+    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)
     ieee_context = [
         AST.Library $ mkVHDLBasicId "IEEE",
         mkUseAll ["IEEE", "std_logic_1164"],
@@ -65,13 +62,12 @@ createDesignFiles binds =
       ]
     full_context =
       mkUseAll ["work", "types"]
-      : ieee_context
-    type_package_dec = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") (packageTypeDecs ++ packageSubtypeDecs ++ subProgSpecs)
-    type_package_body = AST.LUPackageBody $ AST.PackageBody typesId (concat tyfun_decls)
-    packageTypeDecs = map (AST.PDITD . snd) ty_decls
-    packageSubtypeDecs = map (AST.PDISD . snd) subty_decls
-    subProgSpecs = concat (map subProgSpec tyfun_decls)
-    subProgSpec = map (\(AST.SubProgBody spec _ _) -> AST.PDISS spec)
+      : (mkUseAll ["work"]
+      : ieee_context)
+    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
 
 -- Create a use foo.bar.all statement. Takes a list of components in the used
 -- name. Must contain at least two components
@@ -85,7 +81,7 @@ mkUseAll ss =
       
 createLibraryUnits ::
   [(CoreSyn.CoreBndr, CoreSyn.CoreExpr)]
-  -> VHDLState [(AST.VHDLId, [AST.LibraryUnit])]
+  -> VHDLSession [(AST.VHDLId, [AST.LibraryUnit])]
 
 createLibraryUnits binds = do
   entities <- Monad.mapM createEntity binds
@@ -100,7 +96,7 @@ createLibraryUnits binds = do
 -- | Create an entity for a given function
 createEntity ::
   (CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- | The function
-  -> VHDLState AST.EntityDec -- | The resulting entity
+  -> VHDLSession AST.EntityDec -- | The resulting entity
 
 createEntity (fname, expr) = do
       -- Strip off lambda's, these will be arguments
@@ -109,16 +105,17 @@ createEntity (fname, expr) = do
       -- There must be a let at top level 
       let (CoreSyn.Let binds (CoreSyn.Var res)) = letexpr
       res' <- mkMap res
-      let ent_decl' = createEntityAST fname args' res'
+      let vhdl_id = mkVHDLBasicId $ varToString fname ++ "_" ++ varToStringUniq fname
+      let ent_decl' = createEntityAST vhdl_id args' res'
       let AST.EntityDec entity_id _ = ent_decl' 
       let signature = Entity entity_id args' res'
-      modA vsSignatures (Map.insert (bndrToString fname) signature)
+      modA vsSignatures (Map.insert fname signature)
       return ent_decl'
   where
-    mkMap :: 
+    mkMap ::
       --[(SignalId, SignalInfo)] 
       CoreSyn.CoreBndr 
-      -> VHDLState VHDLSignalMapElement
+      -> VHDLSession Port
     -- We only need the vsTypes element from the state
     mkMap = (\bndr ->
       let
@@ -126,84 +123,80 @@ createEntity (fname, expr) = do
         --  (error $ "Signal not found in the name map? This should not happen!")
         --  (lookup id sigmap)
         --  Assume the bndr has a valid VHDL id already
-        id = bndrToVHDLId bndr
+        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 ::
-  CoreSyn.CoreBndr             -- | The name of the function
-  -> [VHDLSignalMapElement]    -- | The entity's arguments
-  -> VHDLSignalMapElement      -- | The entity's result
+  AST.VHDLId                   -- | The name of the function
+  -> [Port]                    -- | The entity's arguments
+  -> Port                      -- | The entity's result
   -> AST.EntityDec             -- | The entity with the ent_decl filled in as well
 
-createEntityAST name args res =
+createEntityAST vhdl_id args res =
   AST.EntityDec vhdl_id ports
   where
     -- Create a basic Id, since VHDL doesn't grok filenames with extended Ids.
-    vhdl_id = mkVHDLBasicId $ bndrToString name
-    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 VHDL.std_logic_ty
-      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
 mkEntityId hsfunc =
   -- TODO: This doesn't work for functions with multiple signatures!
   -- Use a Basic Id, since using extended id's for entities throws off
   -- precision and causes problems when generating filenames.
   mkVHDLBasicId $ hsFuncName hsfunc
+-}
 
 -- | Create an architecture for a given function
 createArchitecture ::
   (CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- ^ The function
-  -> VHDLState AST.ArchBody -- ^ The architecture for this function
+  -> VHDLSession AST.ArchBody -- ^ The architecture for this function
 
 createArchitecture (fname, expr) = do
-  --signaturemap <- getA vsSignatures
-  --let signature = Maybe.fromMaybe 
-  --      (error $ "Generating architecture for function " ++ (prettyShow hsfunc) ++ "without signature? This should not happen!")
-  --      (Map.lookup hsfunc signaturemap)
-  let entity_id = mkVHDLBasicId $ bndrToString fname
+  signaturemap <- getA vsSignatures
+  let signature = Maybe.fromMaybe 
+        (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
   let (args, letexpr) = CoreSyn.collectBinders expr
   -- There must be a let at top level 
-  let (CoreSyn.Let (CoreSyn.Rec binds) res) = letexpr
+  let (CoreSyn.Let (CoreSyn.Rec binds) (Var res)) = letexpr
 
-  -- Create signal declarations for all internal and state signals
-  sig_dec_maybes <- mapM (mkSigDec' . fst) binds
+  -- Create signal declarations for all binders in the let expression, except
+  -- for the output port (that will already have an output port declared in
+  -- the entity).
+  sig_dec_maybes <- mapM (mkSigDec' . fst) (filter ((/=res).fst) binds)
   let sig_decs = Maybe.catMaybes $ sig_dec_maybes
 
-  statements <- Monad.mapM mkConcSm binds
+  statementss <- Monad.mapM mkConcSm binds
+  let statements = concat statementss
   return $ AST.ArchBody (mkVHDLBasicId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) (statements ++ procs')
   where
-    procs = map mkStateProcSm [] -- (makeStatePairs flatfunc)
+    procs = [] --map mkStateProcSm [] -- (makeStatePairs flatfunc)
     procs' = map AST.CSPSm procs
     -- mkSigDec only uses vsTypes from the state
     mkSigDec' = mkSigDec
 
+{-
 -- | Looks up all pairs of old state, new state signals, together with
 --   the state id they represent.
 makeStatePairs :: FlatFunction -> [(StateId, SignalInfo, SignalInfo)]
@@ -231,63 +224,61 @@ mkStateProcSm (num, old, new) =
     rising_edge_clk = AST.PrimFCall $ AST.FCall rising_edge [Nothing AST.:=>: (AST.ADName $ AST.NSimple clk)]
     statement   = AST.IfSm rising_edge_clk [assign] [] Nothing
 
-mkSigDec :: CoreSyn.CoreBndr -> VHDLState (Maybe AST.SigDec)
-mkSigDec bndr =
-  if True then do --isInternalSigUse use || isStateSigUse use then do
-    type_mark <- vhdl_ty $ Var.varType bndr
-    return $ Just (AST.SigDec (bndrToVHDLId bndr) type_mark Nothing)
-  else
-    return Nothing
-
 -- | Creates a VHDL Id from a named SignalInfo. Errors out if the SignalInfo
 --   is not named.
 getSignalId :: SignalInfo -> AST.VHDLId
 getSignalId info =
-    mkVHDLExtId $ Maybe.fromMaybe
-      (error $ "Unnamed signal? This should not happen!")
-      (sigName info)
+  mkVHDLExtId $ Maybe.fromMaybe
+    (error $ "Unnamed signal? This should not happen!")
+    (sigName info)
+-}
+   
+mkSigDec :: CoreSyn.CoreBndr -> VHDLSession (Maybe AST.SigDec)
+mkSigDec bndr =
+  if True then do --isInternalSigUse use || isStateSigUse use then do
+    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
 
 -- | Transforms a core binding into a VHDL concurrent statement
 mkConcSm ::
   (CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- ^ The binding to process
-  -> VHDLState AST.ConcSm  -- ^ The corresponding VHDL component instantiation.
+  -> VHDLSession [AST.ConcSm] -- ^ The corresponding VHDL component instantiations.
 
-mkConcSm (bndr, app@(CoreSyn.App _ _))= do
-  signatures <- getA vsSignatures
-  funSignatures <- getA vsNameTable
-  let (CoreSyn.Var f, args) = CoreSyn.collectArgs app
-  case (Map.lookup (bndrToString f) funSignatures) of
-    Just funSignature ->
-      let
-        sigs = map (bndrToString.varBndr) args
-        sigsNames = map (\signal -> (AST.PrimName (AST.NSimple (mkVHDLExtId signal)))) sigs
-        func = (snd funSignature) sigsNames
-        src_wform = AST.Wform [AST.WformElem func Nothing]
-        dst_name = AST.NSimple (mkVHDLExtId (bndrToString bndr))
-        assign = dst_name AST.:<==: (AST.ConWforms [] src_wform Nothing)
-      in
-        return $ AST.CSSASm assign
-    Nothing ->
-      let  
-        signature = Maybe.fromMaybe 
-          (error $ "Using function '" ++ (bndrToString f) ++ "' without signature? This should not happen!") 
-          (Map.lookup (bndrToString f) signatures)
-        entity_id = ent_id signature
-        label = bndrToString bndr
-      -- Add a clk port if we have state
-      --clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLExtId "clk") "clk"
-      --portmaps = mkAssocElems sigs args res signature ++ (if hasState hsfunc then [clk_port] else [])
-        portmaps = mkAssocElems args bndr signature
-      in
-        return $ AST.CSISm $ AST.CompInsSm (mkVHDLExtId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
 
--- GHC generates some funny "r = r" bindings in let statements before
--- simplification. This outputs some dummy ConcSM for these, so things will at
--- least compile for now.
-mkConcSm (bndr, CoreSyn.Var _) = return $ AST.CSPSm $ AST.ProcSm (mkVHDLBasicId "unused") [] []
+-- Ignore Cast expressions, they should not longer have any meaning as long as
+-- the type works out.
+mkConcSm (bndr, Cast expr ty) = mkConcSm (bndr, expr)
+
+-- For simple a = b assignments, just generate an unconditional signal
+-- assignment. This should only happen for dataconstructors without arguments.
+-- TODO: Integrate this with the below code for application (essentially this
+-- is an application without arguments)
+mkConcSm (bndr, Var v) = return $ [mkUncondAssign (Left bndr) (varToVHDLExpr v)]
 
--- A single alt case must be a selector
-mkConcSm (bndr, (Case (Var scrut) b ty [alt])) = error "Single case alt not supported yet"
+mkConcSm (bndr, app@(CoreSyn.App _ _))= do
+  let (CoreSyn.Var f, args) = CoreSyn.collectArgs app
+  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
+-- is also returned.
+mkConcSm (bndr, expr@(Case (Var scrut) b ty [alt])) =
+  case alt of
+    (DataAlt dc, bndrs, (Var sel_bndr)) -> do
+      case List.elemIndex sel_bndr bndrs of
+        Just i -> do
+          labels <- getFieldLabels (Id.idType scrut)
+          let label = labels!!i
+          let sel_name = mkSelectedName (varToVHDLName scrut) label
+          let sel_expr = AST.PrimName sel_name
+          return [mkUncondAssign (Left bndr) sel_expr]
+        Nothing -> error $ "\nVHDL.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
@@ -295,275 +286,11 @@ mkConcSm (bndr, (Case (Var scrut) b ty [alt])) = error "Single case alt not supp
 -- first is the default case, if there is any.
 mkConcSm (bndr, (Case (Var scrut) b ty [(_, _, Var false), (con, _, Var true)])) =
   let
-    cond_expr = (varToVHDLExpr scrut) AST.:=: (conToVHDLExpr con)
+    cond_expr = (varToVHDLExpr scrut) AST.:=: (altconToVHDLExpr con)
     true_expr  = (varToVHDLExpr true)
     false_expr  = (varToVHDLExpr false)
-    false_wform = AST.Wform [AST.WformElem false_expr Nothing]
-    true_wform = AST.Wform [AST.WformElem true_expr Nothing]
-    whenelse = AST.WhenElse true_wform cond_expr
-    dst_name  = AST.NSimple (bndrToVHDLId bndr)
-    assign    = dst_name AST.:<==: (AST.ConWforms [whenelse] false_wform Nothing)
   in
-    return $ AST.CSSASm assign
-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"
-
--- Turn a variable reference into a AST expression
-varToVHDLExpr :: Var.Var -> AST.Expr
-varToVHDLExpr var = AST.PrimName $ AST.NSimple $ bndrToVHDLId var
-
--- Turn a constructor into an AST expression. For dataconstructors, this is
--- only the constructor itself, not any arguments it has. Should not be called
--- with a DEFAULT constructor.
-conToVHDLExpr :: CoreSyn.AltCon -> AST.Expr
-conToVHDLExpr (DataAlt dc) = AST.PrimLit lit
-  where
-    tycon = DataCon.dataConTyCon dc
-    tyname = TyCon.tyConName tycon
-    dcname = DataCon.dataConName dc
-    lit = case Name.getOccString tyname of
-      -- TODO: Do something more robust than string matching
-      "Bit"      -> case Name.getOccString dcname of "High" -> "'1'"; "Low" -> "'0'"
-      "Bool" -> case Name.getOccString dcname of "True" -> "true"; "False" -> "false"
-conToVHDLExpr (LitAlt _) = error "VHDL.conToVHDLExpr Literals not support in case alternatives yet"
-conToVHDLExpr DEFAULT = error "VHDL.conToVHDLExpr DEFAULT alternative should not occur here!"
-
-
-
-{-
-mkConcSm sigs (UncondDef src dst) _ = do
-  src_expr <- vhdl_expr src
-  let src_wform = AST.Wform [AST.WformElem src_expr Nothing]
-  let dst_name  = AST.NSimple (getSignalId $ signalInfo sigs dst)
-  let assign    = dst_name AST.:<==: (AST.ConWforms [] src_wform Nothing)
-  return $ AST.CSSASm assign
-  where
-    vhdl_expr (Left id) = return $ mkIdExpr sigs id
-    vhdl_expr (Right expr) =
-      case expr of
-        (EqLit id lit) ->
-          return $ (mkIdExpr sigs id) AST.:=: (AST.PrimLit lit)
-        (Literal lit Nothing) ->
-          return $ AST.PrimLit lit
-        (Literal lit (Just ty)) -> do
-          -- Create a cast expression, which is just a function call using the
-          -- type name as the function name.
-          let litexpr = AST.PrimLit lit
-          ty_id <- vhdl_ty ty
-          let ty_name = AST.NSimple ty_id
-          let args = [Nothing AST.:=>: (AST.ADExpr litexpr)] 
-          return $ AST.PrimFCall $ AST.FCall ty_name args
-        (Eq a b) ->
-         return $  (mkIdExpr sigs a) AST.:=: (mkIdExpr sigs b)
-
-mkConcSm sigs (CondDef cond true false dst) _ =
-  let
-    cond_expr  = mkIdExpr sigs cond
-    true_expr  = mkIdExpr sigs true
-    false_expr  = mkIdExpr sigs false
-    false_wform = AST.Wform [AST.WformElem false_expr Nothing]
-    true_wform = AST.Wform [AST.WformElem true_expr Nothing]
-    whenelse = AST.WhenElse true_wform cond_expr
-    dst_name  = AST.NSimple (getSignalId $ signalInfo sigs dst)
-    assign    = dst_name AST.:<==: (AST.ConWforms [whenelse] false_wform Nothing)
-  in
-    return $ AST.CSSASm assign
--}
--- | Turn a SignalId into a VHDL Expr
-mkIdExpr :: [(SignalId, SignalInfo)] -> SignalId -> AST.Expr
-mkIdExpr sigs id =
-  let src_name  = AST.NSimple (getSignalId $ signalInfo sigs id) in
-  AST.PrimName src_name
-
-mkAssocElems :: 
-  [CoreSyn.CoreExpr]            -- | The argument that are applied to function
-  -> CoreSyn.CoreBndr           -- | The binder in which to store the result
-  -> Entity                     -- | The entity to map against.
-  -> [AST.AssocElem]            -- | The resulting port maps
-
-mkAssocElems args res entity =
-    -- Create the actual AssocElems
-    Maybe.catMaybes $ zipWith mkAssocElem ports sigs
-  where
-    -- 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 = ent_args entity
-    res_port  = ent_res entity
-    -- Extract the id part from the (id, type) tuple
-    ports     = map (Monad.liftM fst) (res_port : arg_ports)
-    -- Translate signal numbers into names
-    sigs      = (bndrToString res : map (bndrToString.varBndr) args)
-
--- Turns a Var CoreExpr into the Id inside it. Will of course only work for
--- simple Var CoreExprs, not complexer ones.
-varBndr :: CoreSyn.CoreExpr -> Var.Id
-varBndr (CoreSyn.Var id) = id
-
--- | Look up a signal in the signal name map
-lookupSigName :: [(SignalId, SignalInfo)] -> SignalId -> 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 :: Maybe AST.VHDLId -> String -> Maybe AST.AssocElem
-mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADName (AST.NSimple (mkVHDLExtId signal))) 
-mkAssocElem Nothing _ = Nothing
-
--- | The VHDL Bit type
-bit_ty :: AST.TypeMark
-bit_ty = AST.unsafeVHDLBasicId "Bit"
-
--- | The VHDL Boolean type
-bool_ty :: AST.TypeMark
-bool_ty = AST.unsafeVHDLBasicId "Boolean"
-
--- | The VHDL std_logic
-std_logic_ty :: AST.TypeMark
-std_logic_ty = AST.unsafeVHDLBasicId "std_logic"
-
--- Translate a Haskell type to a VHDL type
-vhdl_ty :: Type.Type -> VHDLState AST.TypeMark
-vhdl_ty ty = do
-  typemap <- getA vsTypes
-  let builtin_ty = do -- See if this is a tycon and lookup its name
-        (tycon, args) <- Type.splitTyConApp_maybe ty
-        let name = Name.getOccString (TyCon.tyConName tycon)
-        Map.lookup name builtin_types
-  -- If not a builtin type, try the custom types
-  let existing_ty = (fmap fst) $ Map.lookup (OrdType ty) typemap
-  case Monoid.getFirst $ Monoid.mconcat (map Monoid.First [builtin_ty, existing_ty]) of
-    -- Found a type, return it
-    Just t -> return t
-    -- No type yet, try to construct it
-    Nothing -> do
-      let new_ty = do
-            -- Use the Maybe Monad for failing when one of these fails
-            (tycon, args) <- Type.splitTyConApp_maybe ty
-            let name = Name.getOccString (TyCon.tyConName tycon)
-            case name of
-              "TFVec" -> Just $ mk_vector_ty (tfvec_len ty) ty
-              "SizedWord" -> Just $ mk_vector_ty (sized_word_len ty) ty
-              "RangedWord" -> Just $ mk_natural_ty 0 (ranged_word_bound ty) ty
-              otherwise -> Nothing
-      -- Return new_ty when a new type was successfully created
-      Maybe.fromMaybe 
-        (error $ "Unsupported Haskell type: " ++ (showSDoc $ ppr ty))
-        new_ty
-
--- | Create a VHDL vector type
-mk_vector_ty ::
-  Int -- ^ The length of the vector
-  -> Type.Type -- ^ The Haskell type to create a VHDL type for
-  -> VHDLState AST.TypeMark -- The typemark created.
-
-mk_vector_ty len ty = do
-  -- Assume there is a single type argument
-  let ty_id = mkVHDLExtId $ "vector_" ++ (show len)
-  -- TODO: Use el_ty
-  let range = AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len - 1))]
-  let ty_def = AST.TDA $ AST.ConsArrayDef range std_logic_ty
-  let ty_dec = AST.TypeDec ty_id ty_def
-  -- TODO: Check name uniqueness
-  --State.modify (Map.insert (OrdType ty) (ty_id, ty_dec))
-  modA vsTypes (Map.insert (OrdType ty) (ty_id, ty_dec))
-  modA vsTypeFuns (Map.insert (OrdType ty) (genUnconsVectorFuns std_logic_ty ty_id))
-  return ty_id
-
-mk_natural_ty ::
-  Int -- ^ The minimum bound (> 0)
-  -> Int -- ^ The maximum bound (> minimum bound)
-  -> Type.Type -- ^ The Haskell type to create a VHDL type for
-  -> VHDLState AST.TypeMark -- The typemark created.
-mk_natural_ty min_bound max_bound ty = do
-  let ty_id = mkVHDLExtId $ "nat_" ++ (show min_bound) ++ "_to_" ++ (show max_bound)
-  let ty_def = AST.SubtypeIn naturalTM (Nothing)
-  let ty_dec = AST.SubtypeDec ty_id ty_def
-  modA vsSubTypes (Map.insert (OrdType ty) (ty_id, ty_dec))
-  return ty_id
-
-
-builtin_types = 
-  Map.fromList [
-    ("Bit", std_logic_ty),
-    ("Bool", bool_ty) -- TysWiredIn.boolTy
-  ]
-
--- Shortcut for 
--- Can only contain alphanumerics and underscores. The supplied string must be
--- a valid basic id, otherwise an error value is returned. This function is
--- not meant to be passed identifiers from a source file, use mkVHDLExtId for
--- that.
-mkVHDLBasicId :: String -> AST.VHDLId
-mkVHDLBasicId s = 
-  AST.unsafeVHDLBasicId $ (strip_multiscore . strip_leading . strip_invalid) s
-  where
-    -- Strip invalid characters.
-    strip_invalid = filter (`elem` ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ "_.")
-    -- Strip leading numbers and underscores
-    strip_leading = dropWhile (`elem` ['0'..'9'] ++ "_")
-    -- Strip multiple adjacent underscores
-    strip_multiscore = concat . map (\cs -> 
-        case cs of 
-          ('_':_) -> "_"
-          _ -> cs
-      ) . List.group
-
--- Shortcut for Extended VHDL Id's. These Id's can contain a lot more
--- different characters than basic ids, but can never be used to refer to
--- basic ids.
--- Use extended Ids for any values that are taken from the source file.
-mkVHDLExtId :: String -> AST.VHDLId
-mkVHDLExtId s = 
-  AST.unsafeVHDLExtId $ strip_invalid s
-  where 
-    -- Allowed characters, taken from ForSyde's mkVHDLExtId
-    allowed = ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ " \"#&\\'()*+,./:;<=>_|!$%@?[]^`{}~-"
-    strip_invalid = filter (`elem` allowed)
-
--- Creates a VHDL Id from a binder
-bndrToVHDLId ::
-  CoreSyn.CoreBndr
-  -> AST.VHDLId
-
-bndrToVHDLId = mkVHDLExtId . OccName.occNameString . Name.nameOccName . Var.varName
-
--- Extracts the binder name as a String
-bndrToString ::
-  CoreSyn.CoreBndr
-  -> String
-
-bndrToString = OccName.occNameString . Name.nameOccName . Var.varName
-
--- | A consise representation of a (set of) ports on a builtin function
---type PortMap = HsValueMap (String, AST.TypeMark)
--- | A consise representation of a builtin function
-data BuiltIn = BuiltIn String [(String, AST.TypeMark)] (String, AST.TypeMark)
-
--- | Translate a list of concise representation of builtin functions to a
---   SignatureMap
-mkBuiltins :: [BuiltIn] -> SignatureMap
-mkBuiltins = Map.fromList . map (\(BuiltIn name args res) ->
-    (name,
-     Entity (VHDL.mkVHDLBasicId name) (map toVHDLSignalMapElement args) (toVHDLSignalMapElement res))
-  )
-
-builtin_hsfuncs = Map.keys builtin_funcs
-builtin_funcs = mkBuiltins
-  [ 
-    BuiltIn "hwxor" [("a", VHDL.bit_ty), ("b", VHDL.bit_ty)] ("o", VHDL.bit_ty),
-    BuiltIn "hwand" [("a", VHDL.bit_ty), ("b", VHDL.bit_ty)] ("o", VHDL.bit_ty),
-    BuiltIn "hwor" [("a", VHDL.bit_ty), ("b", VHDL.bit_ty)] ("o", VHDL.bit_ty),
-    BuiltIn "hwnot" [("a", VHDL.bit_ty)] ("o", VHDL.bit_ty)
-  ]
-
--- | Map a port specification of a builtin function to a VHDL Signal to put in
---   a VHDLSignalMap
-toVHDLSignalMapElement :: (String, AST.TypeMark) -> VHDLSignalMapElement
-toVHDLSignalMapElement (name, ty) = Just (mkVHDLBasicId name, ty)
+    return [mkCondAssign (Left bndr) cond_expr true_expr false_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