-{-# 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
--- /dev/null
+{-# LANGUAGE TemplateHaskell, DeriveDataTypeable #-}
+
+module CLasH.HardwareTypes
+ ( module Types
+ , module Data.Param.TFVec
+ , module Data.RangedWord
+ , module Data.SizedInt
+ , module Data.SizedWord
+ , module Prelude
+ , Bit(..)
+ , 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 Data.Param.TFVec
+import Data.RangedWord
+import Data.SizedInt
+import Data.SizedWord
+
+import Language.Haskell.TH.Lift
+import Data.Typeable
+
+-- 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
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