Compare commits

..

No commits in common. "e6b002f70e76050eb60a6176f63a9a242306b6d8" and "8e27ca877f653480de10cb757d0c593255e429bc" have entirely different histories.

2 changed files with 63 additions and 39 deletions

View file

@ -7,27 +7,55 @@ import Util
#define UIntLog2N(n) (UInt (TLog n)) #define UIntLog2N(n) (UInt (TLog n))
data Tag numTags
= Next UIntLog2N(numTags)
| Freed
| Tail
deriving (Bits, Eq, FShow)
data TagPtr numTags
= SomeTagPtr UIntLog2N(numTags)
| None
deriving (Bits, Eq, FShow)
interface (TagEngine :: # -> *) numTags = interface (TagEngine :: # -> *) numTags =
requestTag :: ActionValue UIntLog2N(numTags) requestTag :: ActionValue UIntLog2N(numTags)
retireTag :: UIntLog2N(numTags) -> Action retireTag :: UIntLog2N(numTags) -> Action
-- The tag engine returns a tag that is unique for the duration of instance FShow (Reg (Tag numTags)) where
-- the lifetime of the tag. Useful when you need to tag transactions fshow value = fshow (readReg value)
-- on a bus for example.
-- This implementation is stack based. initTagNext :: Integer -> Module(Reg (Tag numTags))
initTagNext i = do
t :: Reg (Tag numTags)
t <- mkReg (Next (fromInteger i))
return t
initTagTail :: Module(Reg (Tag numTags))
initTagTail = do
t :: Reg (Tag numTags)
t <- mkReg Tail
return t
initTagVec :: Module(Vector numTags (Reg (Tag numTags)))
initTagVec =
let
lastIdx :: Integer = (fromInteger |> valueOf numTags) - 1
initByIdx currIdx =
if (currIdx < lastIdx)
then initTagNext (currIdx + 1)
else initTagTail
in
mapM initByIdx genVector
mkTagEngine :: Module (TagEngine numTags) mkTagEngine :: Module (TagEngine numTags)
mkTagEngine = mkTagEngine =
do do
let reifiedNumTags = fromInteger |> valueOf numTags tagVec :: Vector numTags (Reg (Tag numTags))
tagVec <- initTagVec
freeStackVec :: Vector numTags (Reg UIntLog2N(numTags)) head :: Reg(TagPtr(numTags)) <- mkReg(SomeTagPtr(0))
freeStackVec <- mapM (\i -> mkReg |> fromInteger i) genVector tail :: Reg(TagPtr(numTags)) <- mkReg(SomeTagPtr(lastIdx))
inUseVec :: Vector numTags (Reg Bool)
inUseVec <- replicateM |> mkReg False
stackPtr :: (Reg (Maybe(UIntLog2N(numTags))))
stackPtr <- mkReg |> Just |> reifiedNumTags - 1
debugOnce <- mkReg True debugOnce <- mkReg True
@ -35,37 +63,35 @@ mkTagEngine =
rules rules
"display": when (debugOnce == True) ==> "display": when (debugOnce == True) ==>
do do
$display "freeStackVec : " (fshow |> readVReg freeStackVec) $display (fshow tagVec)
$display "inUseVec : " (fshow |> readVReg inUseVec)
$display "stackPtr : " (fshow stackPtr)
debugOnce := False debugOnce := False
counter <- mkReg(0 :: UIntLog2N(numTags)) counter <- mkReg(0 :: UIntLog2N(numTags))
return $ return $
interface TagEngine interface TagEngine
requestTag :: ActionValue UIntLog2N(numTags) requestTag :: ActionValue UIntLog2N(numTags)
requestTag = requestTag =
do do
stackPtr := let currHeadPtr :: UIntLog2N(numTags) =
if sampledStackPtr == 0 case head of
then Nothing SomeTagPtr ptr -> ptr
else Just |> sampledStackPtr - 1 -- we technically will never hit this arm
(select inUseVec sampledStackPtr) := True -- due to when guard `SomeTagPtr ptr <- head`
return |> readReg (select freeStackVec sampledStackPtr) None -> 0
let currHead :: (Reg (Tag numTags)) = (select tagVec currHeadPtr)
let nextHeadPtr :: UIntLog2N(numTags) =
case currHead of
Next ptr -> ptr
-- TODO : handle tail correctly
Tail -> 0
currHead := Freed
head := SomeTagPtr(nextHeadPtr)
return nextHeadPtr
when when
Just sampledStackPtr <- stackPtr SomeTagPtr ptr <- head
retireTag :: UIntLog2N(numTags) -> Action retireTag :: UIntLog2N(numTags) -> Action
retireTag tag = retireTag tag = do
do -- placeholder
let nextStackPtrUint = counter := 0
case stackPtr of where
Nothing -> 0 lastIdx :: UIntLog2N(numTags) = (fromInteger |> valueOf numTags) - 1
Just n -> n + 1
(select inUseVec tag) := False
(select freeStackVec nextStackPtrUint) := tag
stackPtr := Just nextStackPtrUint
-- when
-- tag < (reifiedNumTags - 1),
-- readReg (select inUseVec tag)

View file

@ -1,7 +1,5 @@
package Util((|>), simulate_for) where package Util((|>), simulate_for) where
infixr 0 |>
(|>) :: (a -> b) -> a -> b (|>) :: (a -> b) -> a -> b
f |> x = f x; f |> x = f x;