Added subtype declarations to TypeMap, removed SubtypeMap.
authorChristiaan Baaij <christiaan.baaij@gmail.com>
Mon, 22 Jun 2009 10:22:31 +0000 (12:22 +0200)
committerChristiaan Baaij <christiaan.baaij@gmail.com>
Mon, 22 Jun 2009 10:25:56 +0000 (12:25 +0200)
Merge branch 'cλash' of http://git.stderr.nl/matthijs/projects/master-project

* 'cλash' of http://git.stderr.nl/matthijs/projects/master-project: (32 commits)
  Support application of dataconstructors.
  Make mkAssign support assigning to a VHDLName as well.
  Split off record field selection AST construction.
  Only try to generate builtin functions for global binders.
  Never try to normalize global binders.
  Split off assignment generating code.
  Support single-alt selector case expressions.
  Add pprString convenience method.
  Support single-constructor algebraic types.
  Move type registration out of construct_vhdl_ty.
  Split off the VHDL type generating code.
  Actually use the introduced let from a few commits back...
  Error out when normalizing polymorphic functions.
  Add an empty let before starting normalization.
  Add and use a mkFunction utility function.
  Make beta reduction of Case expressions work for type arguments.
  Add function propagation transform.
  Improve debug output timing.
  Don't propagate types with free tyvars.
  Add is_applicable predicate.
  ...

Conflicts:
VHDL.hs

Adders.hs
CoreTools.hs
Generate.hs
GlobalNameTable.hs
VHDL.hs
VHDLTypes.hs

index d4c43ca173450c14892dbfe92b57b478bcf8db63..6cf3be5d97ddafff47bd158e4d38a8e7cdaea73d 100644 (file)
--- a/Adders.hs
+++ b/Adders.hs
@@ -10,6 +10,7 @@ import Prelude hiding (
 import Language.Haskell.Syntax
 import Types
 import Data.Param.TFVec
+import Data.RangedWord
 
 mainIO f = Sim.simulateIO (Sim.stateless f) ()
 
@@ -171,8 +172,8 @@ highordtest = \x ->
              in
                 \c d -> op' d c
 
-functiontest :: TFVec D4 Bit -> Bit
-functiontest = \v -> let r = head v in r
+functiontest :: TFVec D4 Bit -> RangedWord D3 -> Bit
+functiontest = \v i -> let r = v!i in r
 
 highordtest2 = \a b ->
          case a of
index 73904b935f7b266b8be6e84c7553287d91a60c22..85c398ab7c2777bb920c749033f28caa2594d6c4 100644 (file)
@@ -63,6 +63,14 @@ sized_word_len ty =
   where 
     (tycon, args) = Type.splitTyConApp ty
     [len] = args
+    
+-- | Get the upperbound of a RangedWord type
+ranged_word_bound :: Type.Type -> Int
+ranged_word_bound ty =
+  eval_tfp_int len
+  where
+    (tycon, args) = Type.splitTyConApp ty
+    [len]         = args
 
 -- | Evaluate a core Type representing type level int from the TypeLevel
 -- library to a real int.
index 97d94882206ad81701ca39b8e583a6884753326f..2beacb8d5616e7c9014f3fef35a6644d02773a49 100644 (file)
@@ -26,12 +26,12 @@ genUnconsVectorFuns :: AST.TypeMark -- ^ type of the vector elements
 genUnconsVectorFuns elemTM vectorTM  = 
   [ AST.SubProgBody exSpec      []                  [exExpr]                    
   , AST.SubProgBody replaceSpec [AST.SPVD replaceVar] [replaceExpr,replaceRet]   
-    , AST.SubProgBody headSpec    []                  [headExpr]                  
-    , AST.SubProgBody lastSpec    []                  [lastExpr]                  
-    , AST.SubProgBody initSpec    [AST.SPVD initVar]  [initExpr, initRet]         
-    , AST.SubProgBody tailSpec    [AST.SPVD tailVar]  [tailExpr, tailRet]         
-    , AST.SubProgBody takeSpec    [AST.SPVD takeVar]  [takeExpr, takeRet]         
-    , AST.SubProgBody dropSpec    [AST.SPVD dropVar]  [dropExpr, dropRet]         
+  , AST.SubProgBody headSpec    []                  [headExpr]                  
+  , AST.SubProgBody lastSpec    []                  [lastExpr]                  
+  , AST.SubProgBody initSpec    [AST.SPVD initVar]  [initExpr, initRet]         
+  , AST.SubProgBody tailSpec    [AST.SPVD tailVar]  [tailExpr, tailRet]         
+  , AST.SubProgBody takeSpec    [AST.SPVD takeVar]  [takeExpr, takeRet]         
+  , AST.SubProgBody dropSpec    [AST.SPVD dropVar]  [dropExpr, dropRet]         
   ]
   where 
     ixPar   = AST.unsafeVHDLBasicId "ix"
index ef4b25ed986d542c79465bc46793f3c0de9a21e8..c860dcb437e5732c50968168d770bc10aca075ef 100644 (file)
@@ -17,6 +17,6 @@ mkGlobalNameTable = Map.fromList
 
 globalNameTable :: NameTable
 globalNameTable = mkGlobalNameTable
-  [ (show ('(V.!))           , (2, genExprFCall2L exId                           ) )
-  , ("head"          , (1, genExprFCall1L headId                         ) )
+  [ ("!"    , (2, genExprFCall2L exId                           ) )
+  , ("head"           , (1, genExprFCall1L headId                         ) )
   ]
\ No newline at end of file
diff --git a/VHDL.hs b/VHDL.hs
index f0bd3c4cca75a4a1314a87e2cb47a3b02c67ecf3..fcfd91171376aff196e9f2514e5dacf1ad927d39 100644 (file)
--- a/VHDL.hs
+++ b/VHDL.hs
@@ -52,14 +52,15 @@ createDesignFiles ::
   -> [(AST.VHDLId, AST.DesignFile)]
 
 createDesignFiles binds =
-  (mkVHDLBasicId "types", AST.DesignFile ieee_context [type_package]) :
+  (mkVHDLBasicId "types", AST.DesignFile ieee_context [type_package_dec, type_package_body]) :
   map (Arrow.second $ AST.DesignFile full_context) units
   
   where
     init_session = VHDLSession Map.empty Map.empty builtin_funcs globalNameTable
     (units, final_session) = 
       State.runState (createLibraryUnits binds) init_session
-    ty_decls = map (uncurry AST.TypeDec) $ Map.elems (final_session ^. vsTypes)
+    tyfun_decls = Map.elems (final_session ^.vsTypeFuns)
+    ty_decls = map mktydecl $ Map.elems (final_session ^. vsTypes)
     ieee_context = [
         AST.Library $ mkVHDLBasicId "IEEE",
         mkUseAll ["IEEE", "std_logic_1164"],
@@ -68,7 +69,13 @@ createDesignFiles binds =
     full_context =
       mkUseAll ["work", "types"]
       : ieee_context
-    type_package = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") (map AST.PDITD ty_decls)
+    type_package_dec = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") (ty_decls ++ subProgSpecs)
+    type_package_body = AST.LUPackageBody $ AST.PackageBody typesId (concat tyfun_decls)
+    subProgSpecs = concat (map subProgSpec tyfun_decls)
+    subProgSpec = map (\(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
@@ -403,7 +410,7 @@ getFieldLabels ty = do
   -- Get the types map, lookup and unpack the VHDL TypeDef
   types <- getA vsTypes
   case Map.lookup (OrdType ty) types of
-    Just (_, AST.TDR (AST.RecordTypeDef elems)) -> return $ map (\(AST.ElementDec id _) -> id) elems
+    Just (_, Left (AST.TDR (AST.RecordTypeDef elems))) -> return $ map (\(AST.ElementDec id _) -> id) elems
     _ -> error $ "VHDL.getFieldLabels Type not found or not a record type? This should not happen! Type: " ++ (show ty)
 
 -- Turn a variable reference into a AST expression
@@ -550,7 +557,7 @@ vhdl_ty ty = do
         Nothing -> error $ "Unsupported Haskell type: " ++ (showSDoc $ ppr ty)
 
 -- Construct a new VHDL type for the given Haskell type.
-construct_vhdl_ty :: Type.Type -> VHDLState (Maybe (AST.TypeMark, AST.TypeDef))
+construct_vhdl_ty :: Type.Type -> VHDLState (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
 construct_vhdl_ty ty = do
   case Type.splitTyConApp_maybe ty of
     Just (tycon, args) -> do
@@ -558,16 +565,19 @@ construct_vhdl_ty ty = do
       case name of
         "TFVec" -> do
           res <- mk_vector_ty (tfvec_len ty) ty
-          return $ Just res
+          return $ Just $ (Arrow.second Left) res
         "SizedWord" -> do
           res <- mk_vector_ty (sized_word_len ty) ty
-          return $ Just res
+          return $ Just $ (Arrow.second Left) res
+        "RangedWord" -> do 
+          res <- mk_natural_ty 0 (ranged_word_bound ty) ty
+          return $ Just $ (Arrow.second Right) res
         -- Create a custom type from this tycon
         otherwise -> mk_tycon_ty tycon args
     Nothing -> return $ Nothing
 
 -- | Create VHDL type for a custom tycon
-mk_tycon_ty :: TyCon.TyCon -> [Type.Type] -> VHDLState (Maybe (AST.TypeMark, AST.TypeDef))
+mk_tycon_ty :: TyCon.TyCon -> [Type.Type] -> VHDLState (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
 mk_tycon_ty tycon args =
   case TyCon.tyConDataCons tycon of
     -- Not an algebraic type
@@ -586,7 +596,7 @@ mk_tycon_ty tycon args =
       -- TODO: Special handling for tuples?
       let ty_id = mkVHDLExtId $ nameToString (TyCon.tyConName tycon)
       let ty_def = AST.TDR $ AST.RecordTypeDef elems
-      return $ Just (ty_id, ty_def)
+      return $ Just (ty_id, Left ty_def)
     dcs -> error $ "Only single constructor datatypes supported: " ++  (showSDoc $ ppr tycon)
   where
     -- Create a subst that instantiates all types passed to the tycon
@@ -610,6 +620,16 @@ mk_vector_ty len ty = do
   modA vsTypeFuns (Map.insert (OrdType ty) (genUnconsVectorFuns std_logic_ty ty_id))
   return (ty_id, ty_def)
 
+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, AST.SubtypeIn) -- 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)
+  return (ty_id, ty_def)
+
 
 builtin_types = 
   Map.fromList [
index 5b6807bdbc5a1864db4e636f9626007322982b44..cc842897a873f28416974c98fc212be9609eca85 100644 (file)
@@ -43,7 +43,7 @@ instance Ord OrdType where
   compare (OrdType a) (OrdType b) = Type.tcCmpType a b
 
 -- A map of a Core type to the corresponding type name
-type TypeMap = Map.Map OrdType (AST.VHDLId, AST.TypeDef)
+type TypeMap = Map.Map OrdType (AST.VHDLId, Either AST.TypeDef AST.SubtypeIn)
 
 -- A map of a vector Core type to the coressponding VHDL functions
 type TypeFunMap = Map.Map OrdType [AST.SubProgBody]