Reflect moving TFVec and TFP Integers into clash in sourcefiles related to builtin...
authorchristiaanb <christiaan.baaij@gmail.com>
Tue, 1 Jun 2010 14:20:33 +0000 (16:20 +0200)
committerchristiaanb <christiaan.baaij@gmail.com>
Tue, 1 Jun 2010 14:20:33 +0000 (16:20 +0200)
cλash/CLasH/HardwareTypes.hs
cλash/CLasH/VHDL/Constants.hs
cλash/CLasH/VHDL/Generate.hs
cλash/CLasH/VHDL/VHDLTools.hs

index 3b746aa242b702a9239b4dbcabd6d0fb34df0a4d..2912e50fe75bf98ab63bb4f31ba6ab421581656c 100644 (file)
@@ -2,14 +2,13 @@
 
 module CLasH.HardwareTypes
   ( module Types
-  , module Data.Param.TFVec
-  , module Data.RangedWord
-  , module Data.SizedInt
-  , module Data.SizedWord
+  , module Data.Param.Vector
+  , module Data.Param.Index
+  , module Data.Param.Signed
+  , module Data.Param.Unsigned
   , module Prelude
   , Bit(..)
   , State(..)
-  , Vector
   , resizeInt
   , resizeWord
   , hwand
@@ -26,32 +25,29 @@ import Prelude hiding (
   null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr,
   zipWith, zip, unzip, concat, reverse, iterate )
 import Types
-import qualified Data.Param.TFVec as TFVec
-import Data.Param.TFVec hiding (TFVec)
-import Data.RangedWord
-import qualified Data.SizedInt as SizedInt
-import Data.SizedInt hiding (resize)
-import qualified Data.SizedWord as SizedWord
-import Data.SizedWord hiding (resize) 
+import Data.Param.Vector
+import Data.Param.Index
+import qualified Data.Param.Signed as Signed
+import Data.Param.Signed hiding (resize)
+import qualified Data.Param.Unsigned as Unsigned
+import Data.Param.Unsigned hiding (resize) 
 
 import Language.Haskell.TH.Lift
 import Data.Typeable
 
 newtype State s = State s deriving (P.Show)
 
-type Vector = TFVec.TFVec
+resizeInt :: (NaturalT nT, NaturalT nT') => Signed nT -> Signed nT'
+resizeInt = Signed.resize
 
-resizeInt :: (NaturalT nT, NaturalT nT') => SizedInt nT -> SizedInt nT'
-resizeInt = SizedInt.resize
-
-resizeWord :: (NaturalT nT, NaturalT nT') => SizedWord nT -> SizedWord nT'
-resizeWord = SizedWord.resize
+resizeWord :: (NaturalT nT, NaturalT nT') => Unsigned nT -> Unsigned nT'
+resizeWord = Unsigned.resize
 
 -- The plain Bit type
 data Bit = High | Low
   deriving (P.Show, P.Eq, P.Read, Typeable)
 
-deriveLift1 ''Bit
+deriveLift ''Bit
 
 hwand :: Bit -> Bit -> Bit
 hwor  :: Bit -> Bit -> Bit
@@ -82,8 +78,8 @@ blockRAM ::
   ,((s :+: D1) :>: s) ~ True ) =>
   (MemState s a) -> 
   a ->
-  RangedWord s ->
-  RangedWord s ->
+  Index s ->
+  Index s ->
   Bool -> 
   ((MemState s a), a )
 blockRAM (State mem) data_in rdaddr wraddr wrenable = 
index 6051d9b3168e8cb132b3b66ed04fa33bc8676b78..c70ca71a04258b589b76798815a9a509ec4c9bb3 100644 (file)
@@ -301,10 +301,10 @@ minusId = "-"
 
 -- | convert sizedword to ranged
 fromSizedWordId :: String
-fromSizedWordId = "fromSizedWord"
+fromSizedWordId = "fromUnsigned"
 
 fromRangedWordId :: String
-fromRangedWordId = "fromRangedWord"
+fromRangedWordId = "fromIndex"
 
 toIntegerId :: String
 toIntegerId = "to_integer"
@@ -331,10 +331,10 @@ smallIntegerId :: String
 smallIntegerId = "smallInteger"
 
 sizedIntId :: String
-sizedIntId = "SizedInt"
+sizedIntId = "Signed"
 
 tfvecId :: String
-tfvecId = "TFVec"
+tfvecId = "Vector"
 
 blockRAMId :: String
 blockRAMId = "blockRAM"
index 83404334e01d8c4c1c26e3f067b32bf5142e16b8..3d31529a86cc3c7b46b0930a4dc0aa748283c2cf 100644 (file)
@@ -383,7 +383,7 @@ genNegation' _ f [arg] = do
   let (tycon, args) = Type.splitTyConApp ty
   let name = Name.getOccString (TyCon.tyConName tycon)
   case name of
-    "SizedInt" -> return $ AST.Neg arg1
+    "Signed" -> return $ AST.Neg arg1
     otherwise -> error $ "\nGenerate.genNegation': Negation not allowed for type: " ++ show name 
 
 -- | Generate a function call from the destination binder, function name and a
@@ -432,8 +432,8 @@ genResize' (Left res) f [arg] = do {
         ; name = Name.getOccString (TyCon.tyConName tycon)
         } ;
   ; len <- case name of
-      "SizedInt" -> MonadState.lift tsType $ tfp_to_int (sized_int_len_ty ty)
-      "SizedWord" -> MonadState.lift tsType $ tfp_to_int (sized_word_len_ty ty)
+      "Signed" -> MonadState.lift tsType $ tfp_to_int (sized_int_len_ty ty)
+      "Unsigned" -> MonadState.lift tsType $ tfp_to_int (sized_word_len_ty ty)
   ; return $ AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLBasicId resizeId))
              [Nothing AST.:=>: AST.ADExpr arg, Nothing AST.:=>: AST.ADExpr( AST.PrimLit (show len))]
   }
@@ -448,9 +448,9 @@ genTimes' (Left res) f [arg1,arg2] = do {
         ; name = Name.getOccString (TyCon.tyConName tycon)
         } ;
   ; len <- case name of
-      "SizedInt" -> MonadState.lift tsType $ tfp_to_int (sized_int_len_ty ty)
-      "SizedWord" -> MonadState.lift tsType $ tfp_to_int (sized_word_len_ty ty)
-      "RangedWord" -> do {  ubound <- MonadState.lift tsType $ tfp_to_int (ranged_word_bound_ty ty)
+      "Signed" -> MonadState.lift tsType $ tfp_to_int (sized_int_len_ty ty)
+      "Unsigned" -> MonadState.lift tsType $ tfp_to_int (sized_word_len_ty ty)
+      "Index" -> do {  ubound <- MonadState.lift tsType $ tfp_to_int (ranged_word_bound_ty ty)
                          ;  let bitsize = floor (logBase 2 (fromInteger (toInteger ubound)))
                          ;  return bitsize
                          }
@@ -470,12 +470,12 @@ genFromInteger' (Left res) f args = do
   let (tycon, tyargs) = Type.splitTyConApp ty
   let name = Name.getOccString (TyCon.tyConName tycon)
   len <- case name of
-    "SizedInt" -> MonadState.lift tsType $ tfp_to_int (sized_int_len_ty ty)
-    "SizedWord" -> MonadState.lift tsType $ tfp_to_int (sized_word_len_ty ty)
-    "RangedWord" -> do
+    "Signed" -> MonadState.lift tsType $ tfp_to_int (sized_int_len_ty ty)
+    "Unsigned" -> MonadState.lift tsType $ tfp_to_int (sized_word_len_ty ty)
+    "Index" -> do
       bound <- MonadState.lift tsType $ tfp_to_int (ranged_word_bound_ty ty)
       return $ floor (logBase 2 (fromInteger (toInteger (bound)))) + 1
-  let fname = case name of "SizedInt" -> toSignedId ; "SizedWord" -> toUnsignedId ; "RangedWord" -> toUnsignedId
+  let fname = case name of "Signed" -> toSignedId ; "Unsigned" -> toUnsignedId ; "Index" -> toUnsignedId
   case args of
     [integer] -> do -- The type and dictionary arguments are removed by genApplication
       literal <- getIntegerLiteral integer
index 716663025e9698753f3a3ce55be5c366f74fba7d..165b1ef655710195d244dd13ade22cd243be218d 100644 (file)
@@ -322,7 +322,7 @@ mkHTypeEither' ty | ty_has_free_tyvars ty = return $ Left $ "\nVHDLTools.mkHType
         (Just x) -> return $ Right $ BuiltinType name
         Nothing ->
           case name of
-                "TFVec" -> do
+                "Vector" -> do
                   let el_ty = tfvec_elem ty
                   elem_htype_either <- mkHTypeEither el_ty
                   case elem_htype_either of
@@ -333,13 +333,13 @@ mkHTypeEither' ty | ty_has_free_tyvars ty = return $ Left $ "\nVHDLTools.mkHType
                     -- Could not create element type
                     Left err -> return $ Left $ 
                       "\nVHDLTools.mkHTypeEither': Can not construct vectortype for elementtype: " ++ pprString el_ty ++ err
-                "SizedWord" -> do
+                "Unsigned" -> do
                   len <- tfp_to_int (sized_word_len_ty ty)
                   return $ Right $ SizedWType len
-                "SizedInt" -> do
+                "Signed" -> do
                   len <- tfp_to_int (sized_word_len_ty ty)
                   return $ Right $ SizedIType len
-                "RangedWord" -> do
+                "Index" -> do
                   bound <- tfp_to_int (ranged_word_bound_ty ty)
                   return $ Right $ RangedWType bound
                 otherwise ->