Add ty_has_free_tyvars predicate.
[matthijs/master-project/cλash.git] / reducer.hs
index 7c224f2a8903870b8477a55a154859c9f9f75f7b..2dba485a5be7c3dd10f31dda03bca90fabdc4c56 100644 (file)
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeOperators, TemplateHaskell #-}
+{-# LANGUAGE TypeOperators, TemplateHaskell, FlexibleContexts, TypeFamilies #-}
 module Reducer where
 
 import System.Random
@@ -18,8 +18,6 @@ type DataInt        = SizedWord DataSize
 type ArrayIndex     = SizedWord IndexSize
 type Discr          = RangedWord DiscrRange
 
-type RAM a          = Vector (DiscrRange :+: D1) a
-
 type ReducerState   = State ( DiscrState
                       , InputState
                       , FpAdderState
@@ -30,8 +28,6 @@ type ReducerSignal  = ( ( DataInt
                         )
                       , Bit
                       )
-
-type MemState a      = State (RAM a)
                       
 type OutputSignal   = ( (DataInt
                         , ArrayIndex
@@ -49,9 +45,10 @@ type InputState     = State ( Vector (AdderDepth :+: D1) ReducerSignal
 
 type FpAdderState   = State (Vector AdderDepth ReducerSignal)
 
-type OutputState    = State ( MemState DataInt
-                            , RAM ArrayIndex
-                            , RAM Bit
+type OutputState    = State ( MemState DiscrRange DataInt
+                            , MemState DiscrRange DataInt
+                            , RAM DiscrRange ArrayIndex
+                            , RAM DiscrRange Bit
                       )
 {-
 Discriminator adds a discriminator to each input value
@@ -176,39 +173,6 @@ fpAdder (State state) (input1, input2, grant, mem_out) = (State state', output)
               | otherwise         = High
     -- Shift addition of the two operants into the pipeline
     state'    = (((operant1 + operant2),discr),valid) +> (init state)
-    
-
-{- 
-first attempt at BlockRAM
-
-State:
-mem: content of the RAM
-
-Input:
-data_in: input value to be written to 'mem' at location 'wraddr'
-rdaddr: read address
-wraddr: write address
-wrenable: write enable flag
-
-Output:
-data_out: value of 'mem' at location 'rdaddr'
--}
-blockRAM :: (MemState a) -> 
-            ( a
-            , Discr
-            , Discr
-            , Discr
-            , Bit
-            ) -> 
-            (MemState a, (a, a) )
-blockRAM (State mem) (data_in, rdaddr1, rdaddr2, wraddr, wrenable) = 
-  ((State mem'), (data_out1,data_out2))
-  where
-    data_out1               = mem!rdaddr1 
-    data_out2               = mem!rdaddr2
-    -- Only write data_in to memory if write is enabled
-    mem'  | wrenable == Low = mem
-          | otherwise       = replace mem wraddr data_in
 
 {-
 Output logic - Determines when values are released from blockram to the output
@@ -241,9 +205,9 @@ outputter ::  OutputState ->
               , Bit
               ) -> 
               (OutputState, (ReducerSignal, OutputSignal))                 
-outputter (State (mem lut, valid))
+outputter (State (mem1, mem2, lut, valid))
   (discr, index, new_discr, data_in, rdaddr, wraddr, wrenable) = 
-  ((State (mem', lut', valid')), (data_out, output))
+  ((State (mem1', mem2', lut', valid')), (data_out, output))
   where
     -- Lut is updated when new discriminator/index combination enters system        
     lut'    | new_discr /= Low  = replace lut discr index
@@ -255,20 +219,16 @@ outputter (State (mem,  lut, valid))
     -- Location becomes invalid when it is fed back into the pipeline
     valid'  | wrenable == Low   = replace valid'' rdaddr Low
             | otherwise         = replace valid'' wraddr High
-    (mem', mem_out)             = blockRAM mem ( data_in
-                                                , rdaddr
-                                                , discr
-                                                , wraddr
-                                                , wrenable
-                                                )
-    data_out                    = ( ( (fst mem_out)
+    (mem1', mem_out1)           = blockRAM mem1 data_in rdaddr wraddr wrenable
+    (mem2', mem_out2)           = blockRAM mem2 data_in discr wraddr wrenable
+    data_out                    = ( ( (mem_out1)
                                     , rdaddr
                                     )
                                   , (valid!rdaddr)
                                   )
     -- Reduced row is released when new discriminator enters system
     -- And the position at the discriminator holds a valid value
-    output                      = ( ( (snd mem_out)
+    output                      = ( ( (mem_out2)
                                     , (lut!discr)
                                     )
                                   , (new_discr `hwand` (valid!discr))
@@ -478,6 +438,7 @@ initstate = State
     )
   , State (copy ((0::DataInt,0::Discr),Low))
   , State ( State (copy (0::DataInt))
+          , State (copy (0::DataInt))
           , (copy (0::ArrayIndex))
           , (copy Low)
           )