Merge branch 'master' of git://github.com/christiaanb/clash into cλash
[matthijs/master-project/cλash.git] / HighOrdAlu.hs
index 6458f3c968958b8f265057b1fe173c534cdbe3cb..6b11350ca951e059be3593298ae82d2b83853585 100644 (file)
@@ -1,35 +1,63 @@
+{-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-}
+
 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
+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.Translator.Annotations
 
-constant :: e -> Op D4 e
-constant e a b =
-  e +> (e +> (e +> (singleton e )))
-
-inv = hwnot
+constant :: NaturalT n => e -> Op n e
+constant e a b = copy e
 
 invop :: Op n Bit
-invop a b = map inv a
+invop a b = map hwnot a
+
+andop :: (e -> e -> e) -> Op n e
+andop f a b = zipWith f a b
 
-xand = hwand
+-- Is any bit set?
+--anyset :: (PositiveT n) => Op n Bit
+anyset :: NaturalT n => (e -> e -> e) -> e -> Op n e
+--anyset a b = copy undefined (a' `hwor` b')
+anyset f s a b = constant (f a' b') a b
+  where 
+    a' = foldl f s a
+    b' = foldl f s b
 
-andop :: Op n Bit
-andop a b = zipWith xand a 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 :: [(Opcode, TFVec D4 (SizedInt D8), TFVec 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]))) ]
+
+{-# 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 (SizedInt D8), TFVec D4 (SizedInt D8)) -> TFVec D4 (SizedInt D8)
+--actual_alu = alu (constant Low) andop
+actual_alu (opc, a, b) = alu (anyset (+) (0 :: SizedInt D8)) (andop (-)) opc a b
+
+runalu = P.map actual_alu sim_input
\ No newline at end of file