Merge branch 'cλash' of http://git.stderr.nl/matthijs/projects/master-project
authorChristiaan Baaij <christiaan.baaij@gmail.com>
Mon, 22 Jun 2009 13:17:07 +0000 (15:17 +0200)
committerChristiaan Baaij <christiaan.baaij@gmail.com>
Mon, 22 Jun 2009 13:17:07 +0000 (15:17 +0200)
* 'cλash' of http://git.stderr.nl/matthijs/projects/master-project:
  Append the Unique to generated VHDL entity id's.
  Generate the VHDLId of an entity in a single place.
  Remove the old builtin function support.
  Add error message to mkConcSm for unsupported expressions.
  Fix definition of hwor builtin operator.

GlobalNameTable.hs
VHDL.hs
VHDLTypes.hs

index 756c6113c932e978e29a7bccd52d84669250e0e0..6317ebcee9a5125ef01519728edc8f8de05d700f 100644 (file)
@@ -21,6 +21,6 @@ globalNameTable = mkGlobalNameTable
   , ("head"           , (1, genExprFCall headId                           ) )
   , ("hwxor"          , (2, genExprOp2 AST.Xor                            ) )
   , ("hwand"          , (2, genExprOp2 AST.And                            ) )
-  , ("hwor"           , (2, genExprOp2 AST.And                            ) )
+  , ("hwor"           , (2, genExprOp2 AST.Or                             ) )
   , ("hwnot"          , (1, genExprOp1 AST.Not                            ) )
   ]
diff --git a/VHDL.hs b/VHDL.hs
index 5603f8c8a21c14ea70f0bd0c531197cb41bda2e4..ecf6406f95e3f3f621b835d74497eb4feb5b2110 100644 (file)
--- a/VHDL.hs
+++ b/VHDL.hs
@@ -57,7 +57,7 @@ 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 = VHDLSession Map.empty Map.empty Map.empty Map.empty globalNameTable
     (units, final_session) = 
       State.runState (createLibraryUnits binds) init_session
     tyfun_decls = Map.elems (final_session ^.vsTypeFuns)
@@ -115,13 +115,14 @@ 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 $ bndrToString 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
@@ -145,16 +146,15 @@ createEntity (fname, expr) = do
 
   -- | Create the VHDL AST for an entity
 createEntityAST ::
-  CoreSyn.CoreBndr             -- | The name of the function
+  AST.VHDLId                   -- | The name of the function
   -> [VHDLSignalMapElement]    -- | The entity's arguments
   -> VHDLSignalMapElement      -- | 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
               ++ [mkIfaceSigDec AST.Out res]
@@ -188,11 +188,11 @@ createArchitecture ::
   -> VHDLState 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 $ "Generating architecture for function " ++ (pprString fname) ++ "without 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 
@@ -308,7 +308,7 @@ mkConcSm (bndr, app@(CoreSyn.App _ _))= do
       let  
         signature = Maybe.fromMaybe 
           (error $ "Using function '" ++ (bndrToString f) ++ "' without signature? This should not happen!") 
-          (Map.lookup (bndrToString f) signatures)
+          (Map.lookup f signatures)
         entity_id = ent_id signature
         label = bndrToString bndr
         -- Add a clk port if we have state
@@ -354,6 +354,7 @@ mkConcSm (bndr, (Case (Var scrut) b ty [(_, _, Var false), (con, _, Var true)]))
     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
 
 -- Create an unconditional assignment statement
 mkUncondAssign ::
@@ -697,35 +698,15 @@ bndrToVHDLId = mkVHDLExtId . OccName.occNameString . Name.nameOccName . Var.varN
 bndrToString ::
   CoreSyn.CoreBndr
   -> String
-
 bndrToString = OccName.occNameString . Name.nameOccName . Var.varName
 
+-- Get the string version a Var's unique
+varToStringUniq = show . Var.varUnique
+
 -- Extracts the string version of the name
 nameToString :: Name.Name -> String
 nameToString = OccName.occNameString . Name.nameOccName
 
--- | 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)
-  ]
-
 recordlabels = map (\c -> mkVHDLBasicId [c]) ['A'..'Z']
 
 -- | Map a port specification of a builtin function to a VHDL Signal to put in
index 95e9ce02d9d239fa888e0727a0d3aa77ee1dd77a..6f6625b9727b5f497d14aba7d99c6eefef91b5af 100644 (file)
@@ -52,7 +52,7 @@ type ElemTypeMap = Map.Map OrdType (AST.VHDLId, AST.TypeDef)
 type TypeFunMap = Map.Map OrdType [AST.SubProgBody]
 
 -- A map of a Haskell function to a hardware signature
-type SignatureMap = Map.Map String Entity
+type SignatureMap = Map.Map CoreSyn.CoreBndr Entity
 
 -- A map of a builtin function to VHDL function builder 
 type NameTable = Map.Map String (Int, [AST.Expr] -> AST.Expr )