Merge branch 'master' of git://github.com/christiaanb/clash into cλash
authorMatthijs Kooijman <m.kooijman@student.utwente.nl>
Thu, 6 Aug 2009 17:22:09 +0000 (19:22 +0200)
committerMatthijs Kooijman <m.kooijman@student.utwente.nl>
Thu, 6 Aug 2009 17:22:09 +0000 (19:22 +0200)
* 'master' of git://github.com/christiaanb/clash:
  Add the type-alias Vector for TFVec to HardwareTypes, and don't export TFVec.TFVec anymore
  Add the module hardware types, that exports all builtin types.
  Add new modules to cabal file

HighOrdAlu.hs
cλash/CLasH/HardwareTypes.hs [new file with mode: 0644]
cλash/clash.cabal

index 6b11350ca951e059be3593298ae82d2b83853585..e5dcbfddfd22eb96021e03315b462d41c16dcef6 100644 (file)
@@ -1,20 +1,9 @@
-{-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-}
+{-# LANGUAGE TemplateHaskell, ScopedTypeVariables, NoImplicitPrelude #-}
 
 module HighOrdAlu where
 
 import qualified Prelude as P
-import Prelude hiding (
-  null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr,
-  zipWith, zip, unzip, concat, reverse, iterate )
-import Bits
--- import Types
-import Types.Data.Num.Ops
-import Types.Data.Num.Decimal.Digits
-import Types.Data.Num.Decimal.Ops
-import Types.Data.Num.Decimal.Literals
-import Data.Param.TFVec
-import Data.RangedWord
-import Data.SizedInt
+import CLasH.HardwareTypes
 import CLasH.Translator.Annotations
 
 constant :: NaturalT n => e -> Op n e
@@ -37,11 +26,11 @@ anyset f s a b = constant (f a' b') a b
 
 xhwor = hwor
 
-type Op n e = (TFVec n e -> TFVec n e -> TFVec n e)
+type Op n e = (Vector n e -> Vector n e -> Vector n e)
 type Opcode = Bit
 
 {-# ANN sim_input TestInput#-}
-sim_input :: [(Opcode, TFVec D4 (SizedInt D8), TFVec D4 (SizedInt D8))]
+sim_input :: [(Opcode, Vector D4 (SizedInt D8), Vector D4 (SizedInt D8))]
 sim_input = [ (High,  $(vectorTH ([4,3,2,1]::[SizedInt D8])), $(vectorTH ([1,2,3,4]::[SizedInt D8])))
             , (High,  $(vectorTH ([4,3,2,1]::[SizedInt D8])), $(vectorTH ([1,2,3,4]::[SizedInt D8])))
             , (Low,   $(vectorTH ([4,3,2,1]::[SizedInt D8])), $(vectorTH ([1,2,3,4]::[SizedInt D8]))) ]
@@ -49,14 +38,14 @@ sim_input = [ (High,  $(vectorTH ([4,3,2,1]::[SizedInt D8])), $(vectorTH ([1,2,3
 {-# ANN actual_alu InitState #-}
 initstate = High
 
-alu :: Op n e -> Op n e -> Opcode -> TFVec n e -> TFVec n e -> TFVec n e
+alu :: Op n e -> Op n e -> Opcode -> Vector n e -> Vector n e -> Vector n e
 alu op1 op2 opc a b =
   case opc of
     Low -> op1 a b
     High -> op2 a b
 
 {-# ANN actual_alu TopEntity #-}
-actual_alu :: (Opcode, TFVec D4 (SizedInt D8), TFVec D4 (SizedInt D8)) -> TFVec D4 (SizedInt D8)
+actual_alu :: (Opcode, Vector D4 (SizedInt D8), Vector D4 (SizedInt D8)) -> Vector D4 (SizedInt D8)
 --actual_alu = alu (constant Low) andop
 actual_alu (opc, a, b) = alu (anyset (+) (0 :: SizedInt D8)) (andop (-)) opc a b
 
diff --git a/cλash/CLasH/HardwareTypes.hs b/cλash/CLasH/HardwareTypes.hs
new file mode 100644 (file)
index 0000000..9209086
--- /dev/null
@@ -0,0 +1,57 @@
+{-# LANGUAGE TemplateHaskell, DeriveDataTypeable #-}
+
+module CLasH.HardwareTypes
+  ( module Types
+  , module Data.Param.TFVec
+  , module Data.RangedWord
+  , module Data.SizedInt
+  , module Data.SizedWord
+  , module Prelude
+  , Bit(..)
+  , Vector
+  , hwand
+  , hwor
+  , hwxor
+  , hwnot
+  ) where
+
+import qualified Prelude as P
+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 Data.SizedInt
+import Data.SizedWord 
+
+import Language.Haskell.TH.Lift
+import Data.Typeable
+
+type Vector = TFVec.TFVec
+
+-- The plain Bit type
+data Bit = High | Low
+  deriving (P.Show, P.Eq, P.Read, Typeable)
+
+$(deriveLift1 ''Bit)
+
+hwand :: Bit -> Bit -> Bit
+hwor  :: Bit -> Bit -> Bit
+hwxor :: Bit -> Bit -> Bit
+hwnot :: Bit -> Bit
+
+High `hwand` High = High
+_ `hwand` _ = Low
+
+High `hwor` _  = High
+_ `hwor` High  = High
+Low `hwor` Low = Low
+
+High `hwxor` Low = High
+Low `hwxor` High = High
+_ `hwxor` _      = Low
+
+hwnot High = Low
+hwnot Low  = High
\ No newline at end of file
index 459be313ebe343b217787e31aac51792e031d14b..1797f28e596e17abeafdb997e471810621b65b33 100644 (file)
@@ -20,9 +20,10 @@ Library
   build-depends:    ghc >= 6.11, pretty, vhdl > 0.1, haskell98, syb,
                     data-accessor, containers, base >= 4, transformers,
                     filepath, template-haskell, data-accessor-template,
-                    prettyclass, directory
+                    prettyclass, directory, th-lift-ng, tfp, tfvec
                     
-  exposed-modules:  CLasH.Translator
+  exposed-modules:  CLasH.HardwareTypes
+                    CLasH.Translator
                     CLasH.Translator.Annotations
                     CLasH.Utils
                     
@@ -33,11 +34,13 @@ Library
                     CLasH.VHDL
                     CLasH.VHDL.Constants
                     CLasH.VHDL.Generate
+                    CLasH.VHDL.Testbench
                     CLasH.VHDL.VHDLTools
                     CLasH.VHDL.VHDLTypes
                     CLasH.Utils.GhcTools
                     CLasH.Utils.HsTools
                     CLasH.Utils.Pretty
+                    CLasH.Utils.Core.BinderTools
                     CLasH.Utils.Core.CoreShow
                     CLasH.Utils.Core.CoreTools