Quick hack implementation of FSVec literals, needs to be fixed
[matthijs/master-project/cλash.git] / HighOrdAlu.hs
1 {-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-}
2
3 module HighOrdAlu where
4
5 import qualified Prelude as P
6 import Prelude hiding (
7   null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr,
8   zipWith, zip, unzip, concat, reverse, iterate )
9 import Bits
10 -- import Types
11 import Types.Data.Num.Ops
12 import Types.Data.Num.Decimal.Digits
13 import Types.Data.Num.Decimal.Ops
14 import Types.Data.Num.Decimal.Literals
15 import Data.Param.TFVec
16 import Data.RangedWord
17 import Data.SizedInt
18 import CLasH.Translator.Annotations
19
20 constant :: NaturalT n => e -> Op n e
21 constant e a b = copy e
22
23 invop :: Op n Bit
24 invop a b = map hwnot a
25
26 andop :: (e -> e -> e) -> Op n e
27 andop f a b = zipWith f a b
28
29 -- Is any bit set?
30 --anyset :: (PositiveT n) => Op n Bit
31 anyset :: NaturalT n => (e -> e -> e) -> e -> Op n e
32 --anyset a b = copy undefined (a' `hwor` b')
33 anyset f s a b = constant (f a' b') a b
34   where 
35     a' = foldl f s a
36     b' = foldl f s b
37
38 xhwor = hwor
39
40 type Op n e = (TFVec n e -> TFVec n e -> TFVec n e)
41 type Opcode = Bit
42
43 {-# ANN sim_input TestInput#-}
44 sim_input :: [(Opcode, TFVec D4 (SizedInt D8), TFVec D4 (SizedInt D8))]
45 sim_input = [ (High,  $(vectorTH ([4,3,2,1]::[SizedInt D8])), $(vectorTH ([1,2,3,4]::[SizedInt D8])))
46             , (High,  $(vectorTH ([4,3,2,1]::[SizedInt D8])), $(vectorTH ([1,2,3,4]::[SizedInt D8])))
47             , (Low,   $(vectorTH ([4,3,2,1]::[SizedInt D8])), $(vectorTH ([1,2,3,4]::[SizedInt D8]))) ]
48
49 {-# ANN actual_alu InitState #-}
50 initstate = High
51
52 alu :: Op n e -> Op n e -> Opcode -> TFVec n e -> TFVec n e -> TFVec n e
53 alu op1 op2 opc a b =
54   case opc of
55     Low -> op1 a b
56     High -> op2 a b
57
58 {-# ANN actual_alu TopEntity #-}
59 actual_alu :: (Opcode, TFVec D4 (SizedInt D8), TFVec D4 (SizedInt D8)) -> TFVec D4 (SizedInt D8)
60 --actual_alu = alu (constant Low) andop
61 actual_alu (opc, a, b) = alu (anyset (+) (0 :: SizedInt D8)) (andop (-)) opc a b
62
63 runalu = P.map actual_alu sim_input