vectorTH works now, but you will need the latest version of TFVec
+{-# LANGUAGE TemplateHaskell #-}
+
module Adders where
import Bits
import qualified Sim
xand a b = hwand a b
-functiontest :: TFVec D4 (TFVec D3 Bit) -> (TFVec D12 Bit, TFVec D3 Bit, TFVec D3 (TFVec D3 Bit))
-functiontest = \v -> let r = (concat v, head v, tail v) in r
+functiontest :: TFVec D4 Bit -> TFVec D8 Bit
+functiontest = \v -> let r = v ++ $(vectorTH ([High,Low,High,Low] :: [Bit])) in r
xhwnot x = hwnot x
-{-# LANGUAGE FlexibleContexts,GADTs,ExistentialQuantification,LiberalTypeSynonyms #-}
+{-# LANGUAGE FlexibleContexts,GADTs,ExistentialQuantification,LiberalTypeSynonyms,TemplateHaskell #-}
module Bits where
import qualified Data.Param.TFVec as TFVec
import qualified Types
+import Language.Haskell.TH.Lift
--class Signal a where
-- hwand :: a -> a -> a
data Bit = High | Low
deriving (Show, Eq, Read)
+$(deriveLift1 ''Bit)
+
-- A function to prettyprint a bitvector
--displaysigs :: (Signal s) => [s] -> String