Tag Engine Now Finished it seems #10

Merged
Yehowshua merged 12 commits from tag_engine_version_3 into main 2025-04-08 01:32:40 +00:00
5 changed files with 152 additions and 146 deletions

View file

@ -61,7 +61,7 @@ $(BDPI_OBJ): $(BDPI_SRC)
BSC_LINK_FLAGS += -keep-fires BSC_LINK_FLAGS += -keep-fires
BSC_PATHS = -p bs/:bsv/:+ BSC_PATHS = -p bs/:bs/Tests/:bsv/:+
.PHONY: help .PHONY: help
help: help:

View file

@ -57,9 +57,9 @@ interface BusMaster =
-- This has implications about for the implementor of BusMaster, namely, that it -- This has implications about for the implementor of BusMaster, namely, that it
-- should hold its request until it's request method gets called. -- should hold its request until it's request method gets called.
request :: BusRequest request :: BusRequest
-- From the masters's perspective, the response should not be called until -- From the masters's perspective, the response should not be called by the
-- the client is ready to accept the response. In other words, response -- arbiter until the master is ready to accept the response. In other words,
-- should be guarded by the client. -- response should be guarded by the client.
response :: BusResponse -> Action response :: BusResponse -> Action
type Token = UInt 5 type Token = UInt 5

View file

@ -5,77 +5,109 @@ package TagEngine(
import Vector import Vector
import Util import Util
import FIFO
import FIFOF
import SpecialFIFOs
#define UIntLog2N(n) (UInt (TLog n)) #define UIntLog2N(n) (UInt (TLog n))
interface (TagEngine :: # -> *) numTags = interface (TagEngine :: # -> *) numTags =
requestTag :: ActionValue UIntLog2N(numTags) requestTag :: ActionValue UIntLog2N(numTags)
retireTag :: UIntLog2N(numTags) -> ActionValue BasicResult retireTag :: UIntLog2N(numTags) -> Action
-- The tag engine returns a tag that is unique for the duration of -- The tag engine returns a tag that is unique for the duration of
-- the lifetime of the tag. Useful when you need to tag transactions -- the lifetime of the tag. Useful when you need to tag transactions
-- on a bus for example. -- on a bus for example.
-- This implementation is stack based. -- This implementation is FIFO based.
mkTagEngine :: Module (TagEngine numTags) mkTagEngine :: Module (TagEngine numTags)
mkTagEngine = mkTagEngine = do
do -- Constants
let reifiedNumTags = fromInteger |> valueOf numTags let maxTagCount = fromInteger (valueOf numTags)
freeStackVec :: Vector numTags (Reg UIntLog2N(numTags)) tagUsage :: Vector numTags (Reg Bool) <- replicateM (mkReg False) -- Tracks which tags are in use
freeStackVec <- mapM (\i -> mkReg |> fromInteger i) genVector
inUseVec :: Vector numTags (Reg Bool) -- Since Bluespec doesn't allow us to initialize FIFOs with values at
inUseVec <- replicateM |> mkReg False -- reset, we can pretend as if the buffer within our freeTagQueue is populated
-- with sequentially incrementing values(starting from 0) on reset
-- by having our tag engine effectively return the value of a decrementing
-- counter initialized to (maxTagCount - 1) for the first n tag requests made
-- to TagEngine where `n := maxTagCount`.
initialTagDistributor <- mkReg (Just (maxTagCount - 1)) -- Distributes initial tags
retireQueue <- mkBypassFIFO -- Queue for tags being retired
freeTagQueue <- mkSizedFIFOF maxTagCount -- Queue of available tags
stackPtr :: (Reg (Maybe(UIntLog2N(numTags)))) -- Signals
stackPtr <- mkReg |> Just |> reifiedNumTags - 1 retireSignal <- mkRWire -- Signals a tag retirement
requestSignal <- mkRWire -- Signals a tag request
-- Debug
debugOnce <- mkReg True debugOnce <- mkReg True
-- Rules
addRules $ addRules $
rules rules
"display": when (debugOnce == True) ==> "debug_initial_state": when debugOnce ==> do
do $display "tagUsage: " (fshow (readVReg tagUsage))
$display "freeStackVec : " (fshow |> readVReg freeStackVec)
$display "inUseVec : " (fshow |> readVReg inUseVec)
$display "stackPtr : " (fshow stackPtr)
debugOnce := False debugOnce := False
counter <- mkReg(0 :: UIntLog2N(numTags)) "retire_tag": when True ==> do
let tag = retireQueue.first
$display "Retiring tag: " (fshow tag)
retireQueue.deq
freeTagQueue.enq tag
retireSignal.wset tag
-- Combined update rules (simplified below)
"update_usage": when True ==> do
let mRetireTag = retireSignal.wget
mRequestTag = requestSignal.wget
case (mRetireTag, mRequestTag) of
(Just retireTag, Just requestTag) -> do
let usage = readVReg tagUsage
usage' = update usage requestTag True
usage'' = update usage' retireTag False
writeVReg tagUsage usage''
$display $time " Updated usage (request + retire): " (fshow |> readVReg tagUsage)
(Just retireTag, Nothing) -> do
(select tagUsage retireTag) := False
$display $time " Updated usage (retire): " (fshow (readVReg tagUsage))
(Nothing, Just requestTag) -> do
(select tagUsage requestTag) := True
$display $time " Updated usage (request): " (fshow (readVReg tagUsage))
(Nothing, Nothing) -> action {}
-- Interface
return $ return $
interface TagEngine interface TagEngine
requestTag :: ActionValue UIntLog2N(numTags) requestTag :: ActionValue UIntLog2N(numTags)
requestTag = requestTag = do
do case initialTagDistributor of
stackPtr := Just 0 -> do
if sampledStackPtr == 0 initialTagDistributor := Nothing
then Nothing requestSignal.wset 0
else Just |> sampledStackPtr - 1 return 0
(select inUseVec sampledStackPtr) := True Just tag -> do
return |> readReg (select freeStackVec sampledStackPtr) initialTagDistributor := Just (tag - 1)
when requestSignal.wset tag
Just sampledStackPtr <- stackPtr return tag
Nothing -> do
let tag = freeTagQueue.first
freeTagQueue.deq
requestSignal.wset tag
return tag
-- retireTag isn't guarded so its up to external module to only attempt to -- `retireTag` isn't guarded on tag validity(this would break Bluespec's safety model)
-- retire valid tags... At any rate, we can notify the requestor of failures -- so it is advisable that the caller of `retireTag` only attempt to retire valid tags.
-- to retire tags - although the requestor can merely ignore this -- Internally, the tagEngine will keep a correct and consistent state since TagEngine
-- notification. -- validates tags before attempting to retire them.
retireTag :: UIntLog2N(numTags) -> ActionValue BasicResult retireTag :: UIntLog2N(numTags) -> Action
retireTag tag = retireTag tag =
do do
let let
tagValid = tag < reifiedNumTags tagValid = tag < maxTagCount
tagInUse = readReg (select inUseVec tag) tagInUse = readReg (select tagUsage tag)
nextStackPtrUint =
case stackPtr of
Nothing -> 0
Just n -> n + 1
if (tagValid && tagInUse) if (tagValid && tagInUse)
then do then do
(select inUseVec tag) := False retireQueue.enq tag
(select freeStackVec nextStackPtrUint) := tag
stackPtr := Just nextStackPtrUint
return Success
else do else do
return Failure action {}

View file

@ -0,0 +1,64 @@
package TagEngineTester(mkTagEngineTester) where
import TagEngine
import ActionSeq
mkTagEngineTester :: Module Empty
mkTagEngineTester = do
tagEngine :: TagEngine 5 <- mkTagEngine
runOnce :: Reg Bool <- mkReg False
s :: ActionSeq
s <-
let
requestTagAction :: Action
requestTagAction =
do
tag <- tagEngine.requestTag
$display $time " got tag : " (fshow tag)
retireTagAction :: UInt 3 -> Action
retireTagAction tag =
do
res <- tagEngine.retireTag tag
$display $time " retiring tag : " (fshow tag) " " (fshow res)
action {}
in
actionSeq $
do requestTagAction
|> do requestTagAction
|> do requestTagAction
|> do requestTagAction
|> do requestTagAction
|> do retireTagAction 2
-- |> do $display "BEGIN TRY SIMULTANEOUS RETIRE and REQUEST"
|> do
retireTagAction 4
requestTagAction
-- |> do $display "END TRY SIMULTANEOUS RETIRE and REQUEST"
-- |> do $display "BEGIN TRY SIMULTANEOUS RETIRE and REQUEST"
|> do
retireTagAction 4
requestTagAction
-- |> do $display "END TRY SIMULTANEOUS RETIRE and REQUEST"
|> do $finish
-- |> do retireTagAction 4
-- |> do retireTagAction 4
-- |> do retireTagAction 0
-- |> do requestTagAction
-- |> do requestTagAction
-- |> do retireTagAction 1
-- |> do requestTagAction
-- |> do $finish
addRules $
rules
-- "counter": when True ==>
-- do
-- count := count + 1
-- $display "count : " (fshow count)
"testIncrement": when (runOnce == False) ==>
do
s.start
runOnce := True

View file

@ -10,6 +10,8 @@ import TagEngine
import List import List
import ActionSeq import ActionSeq
import TagEngineTester
type FCLK = 25000000 type FCLK = 25000000
type BAUD = 9600 type BAUD = 9600
@ -19,44 +21,6 @@ interface ITop = {
;ftdi_txd :: Bit 1 -> Action {-# always_ready , always_enabled #-} ;ftdi_txd :: Bit 1 -> Action {-# always_ready , always_enabled #-}
}; };
interface BusClient =
request :: Bit 1
response :: Bit 1 -> Action
mkBusClient :: Module BusClient
mkBusClient = module
reqReg :: Reg (Bit 1) <- mkReg 0
return $
interface BusClient
request = reqReg
response resp = do
reqReg := 0 -- Reset request after receiving response
interface Bus =
request :: Bit 1 -> Action
response :: Bit 1
mkBus :: Module Bus
mkBus = module
respReg :: Reg (Bit 1) <- mkReg 0
return $
interface Bus
request req = do
respReg := req -- Simple pass-through for this example
response = respReg
-- -- Function to connect Bus to BusClient
connectBusToClient :: Bus -> BusClient -> Rules
connectBusToClient bus client =
rules
"busConnection": when True ==> do
bus.request client.request
client.response bus.response
-- need to implement mkBus
-- need function that can connect Bus to BusClient
mkTop :: Module ITop mkTop :: Module ITop
mkTop = do mkTop = do
fileHandle :: Handle <- openFile "compile.log" WriteMode fileHandle :: Handle <- openFile "compile.log" WriteMode
@ -64,17 +28,9 @@ mkTop = do
serializer :: ISerializer FCLK BAUD <- mkSerialize fileHandle serializer :: ISerializer FCLK BAUD <- mkSerialize fileHandle
core :: Core FCLK <- mkCore core :: Core FCLK <- mkCore
bus :: Bus <- mkBus
busClient :: BusClient <- mkBusClient
let a :: List Integer = 1 :> 2 :> Nil
b = length a
persistLed :: Reg (Bit 8) <- mkReg 0 persistLed :: Reg (Bit 8) <- mkReg 0
messageM $ "Hallo!!" + (realToString 5) messageM $ "Hallo!!" + (realToString 5)
-- need to instantiate a Bus and BusClient
addRules $ connectBusToClient bus busClient
addRules $ addRules $
rules rules
-- need new rule that always connects Bus to BusClient -- need new rule that always connects Bus to BusClient
@ -100,58 +56,12 @@ mkTop = do
mkSim :: Module Empty mkSim :: Module Empty
mkSim = do mkSim = do
let cfg :: BRAM_Configure = defaultValue _ :: Empty <- mkTagEngineTester
tagEngine :: TagEngine 5 <- mkTagEngine
count :: Reg (UInt 4) <- mkReg 0;
initCFunctions :: Reg Bool <- mkReg False; initCFunctions :: Reg Bool <- mkReg False;
core :: Core FCLK <- mkCore; core :: Core FCLK <- mkCore;
s :: ActionSeq
s <- actionSeq
$ do
$display "got tag : " tagEngine.requestTag
|> do
$display "got tag : " tagEngine.requestTag
|> do
$display "got tag : " tagEngine.requestTag
|> do
res <- tagEngine.retireTag 3
$display "retiring tag : 3 " (fshow res)
action {}
|> do
$display "got tag : " tagEngine.requestTag
|> do
$display "got tag : " tagEngine.requestTag
|> do
res <- tagEngine.retireTag 4
$display "retiring tag : 4 " (fshow res)
action {}
|> do
res <- tagEngine.retireTag 4
$display "retiring tag : 4 " (fshow res)
action {}
|> do
res <- tagEngine.retireTag 0
$display "retiring tag : 0 " (fshow res)
action {}
|> do
$display "got tag : " tagEngine.requestTag
|> do
$display "got tag : " tagEngine.requestTag
|> do
res <- tagEngine.retireTag 1
$display "retiring tag : 1 " (fshow res)
action {}
|> do
$display "got tag : " tagEngine.requestTag
addRules $ addRules $
rules rules
"testIncrement": when (count < 10) ==>
do
count := count + 1
s.start
"initCFunctionsOnce": when not initCFunctions ==> "initCFunctionsOnce": when not initCFunctions ==>
do do
initTerminal initTerminal