Add automated testbench generation according to supplied test input
[matthijs/master-project/cλash.git] / HighOrdAlu.hs
index 6458f3c968958b8f265057b1fe173c534cdbe3cb..1ead210f0bb82dd85ceae098bdd3fb89380b5cf8 100644 (file)
@@ -1,3 +1,5 @@
+{-# LANGUAGE TemplateHaskell #-}
+
 module HighOrdAlu where
 
 import Prelude hiding (
@@ -7,29 +9,47 @@ import Bits
 import Types
 import Data.Param.TFVec
 import Data.RangedWord
+import CLasH.Translator.Annotations
 
 constant :: e -> Op D4 e
 constant e a b =
-  e +> (e +> (e +> (singleton e )))
-
-inv = hwnot
+  (e +> (e +> (e +> (singleton e))))
 
 invop :: Op n Bit
-invop a b = map inv a
-
-xand = hwand
+invop a b = map hwnot a
 
 andop :: Op n Bit
-andop a b = zipWith xand a b
+andop a b = zipWith hwand a b
+
+-- Is any bit set?
+--anyset :: (PositiveT n) => Op n Bit
+anyset :: (Bit -> Bit -> Bit) -> Op D4 Bit
+--anyset a b = copy undefined (a' `hwor` b')
+anyset f a b = constant (a' `hwor` b') a b
+  where 
+    a' = foldl f Low a
+    b' = foldl f Low b
+
+xhwor = hwor
 
 type Op n e = (TFVec n e -> TFVec n e -> TFVec n e)
 type Opcode = Bit
 
+{-# ANN sim_input TestInput#-}
+sim_input = [ (High,$(vectorTH [High,Low,Low,Low]),$(vectorTH [High,Low,Low,Low]))
+            , (High,$(vectorTH [High,High,High,High]),$(vectorTH [High,High,High,High]))
+            , (Low,$(vectorTH [High,Low,Low,High]),$(vectorTH [High,Low,High,Low]))]
+
+{-# ANN actual_alu InitState #-}
+initstate = High
+
 alu :: Op n e -> Op n e -> Opcode -> TFVec n e -> TFVec n e -> TFVec n e
 alu op1 op2 opc a b =
   case opc of
     Low -> op1 a b
     High -> op2 a b
 
-actual_alu :: Opcode -> TFVec D4 Bit -> TFVec D4 Bit -> TFVec D4 Bit
-actual_alu = alu (constant Low) andop
+{-# ANN actual_alu TopEntity #-}
+actual_alu :: (Opcode, TFVec D4 Bit, TFVec D4 Bit) -> TFVec D4 Bit
+--actual_alu = alu (constant Low) andop
+actual_alu (opc, a, b) = alu (anyset xhwor) (andop) opc a b