Compare commits

...

5 commits

3 changed files with 111 additions and 32 deletions

View file

@ -1,7 +1,55 @@
package Bus(a) where package Bus(mkBus) where
import Types import Types
import BusTypes import BusTypes
import TagEngine
import Vector
import Util
import Arbiter
a :: UInt 5 clientRequest :: Arbiter.ArbiterClient_IFC -> Action
a = 3 clientRequest ifc = ifc.request
busRequestToAddr :: BusRequest -> Addr
busRequestToAddr req = case req of
BusReadRequest (ReadRequest addr _) -> addr
WriteReadRequest (WriteRequest addr _) -> addr
mkBus :: (Addr -> Integer)
-> Vector numClients (BusClient inFlightTransactions)
-> Vector numServers (BusServer inFlightTransactions numClients)
-> Module Empty
mkBus addrToServerTranslation clientVec serverVec = do
tagEngineByClientVec :: Vector numClients (TagEngine inFlightTransactions)
tagEngineByClientVec <- replicateM mkTagEngine
arbiterByServer :: Vector numServers (Arbiter_IFC numClients)
arbiterByServer <- replicateM (mkArbiter False)
addRules |>
rules
"placeholder rule": when True ==> do
let selectedServerArbiter = (select arbiterByServer 0)
mapM_ clientRequest selectedServerArbiter.clients
"connect request client 0": when True ==> do
let
clientIdx :: Integer = 0
selectedClient ::(BusClient inFlightTransactions)
selectedClient = (select clientVec clientIdx)
selectedTagEngine = (select tagEngineByClientVec clientIdx)
tag <- selectedTagEngine.requestTag
busRequest :: BusRequest
busRequest <- selectedClient.dequeueRequest tag
let
addr = busRequestToAddr busRequest
targetServerIdx = addrToServerTranslation addr
targetServer = (select serverVec targetServerIdx)
-- targetServer
action {}
return $ interface Empty { }

View file

@ -1,12 +1,16 @@
package BusTypes( package BusTypes(
BusVal(..), MkClientTagType,
BusError(..), BusClient(..), BusServer(..),
TransactionSize(..), BusRequest(..), BusResponse(..),
ReadRequest(..), ReadRequest(..), ReadResponse(..), WriteRequest(..), WriteResponse(..),
WriteRequest(..) BusVal(..), BusError(..), TransactionSize(..)
) where ) where
import Types import Types
import Vector
import TagEngine
type MkClientTagType a = (UInt (TLog a))
data BusError data BusError
= UnMapped = UnMapped
@ -48,21 +52,47 @@ data BusResponse
| BusWriteResponse WriteResponse | BusWriteResponse WriteResponse
deriving (Bits, Eq, FShow) deriving (Bits, Eq, FShow)
interface BusMaster = -- # BusClient.dequeueRequest
-- The Bus arbiter will call the Bus Master's request method -- * The Bus arbiter will call the Bus Client's request method if it is
-- if and only if it's the Bus Master's turn to make a request, and the Bus Master -- the Bus Client's turn to make a request, or if another client forfits
-- has a request to make. -- its turn.
-- It is up to the BusMaster to guard it's request method such that calling -- * The BusClient must guard its request method such that calling its
-- it's request method is only valid when the BusMaster has a request to make. -- request method is only valid when the BusClient has a request to make.
-- This has implications about for the implementor of BusMaster, namely, that it -- * This has implications about for the implementor of BusClient,
-- should hold its request until it's request method gets called. -- namely, that it should hold its request until it's request method
request :: BusRequest -- gets called. The arbiter tags the request so that the client can
-- From the masters's perspective, the response should not be called by the -- later correctly correlate the response.
-- arbiter until the master is ready to accept the response. In other words, -- * Although the tag is technically passed in as an argument from the
-- response should be guarded by the client. -- arbiter to the client's request method, given that methods are
response :: BusResponse -> Action -- atomic in Bluespec, this is effectively equivalent to tagging the
-- transaction from the client's perspective. Thus, the client must
-- take care to appropiately store the tag.
-- # BusClient.enqueueResponse
-- * From the client's perspective, the response should not be called
-- by the arbiter until the client is ready to accept the response.
-- In other words, the response method should be guarded by the client.
interface (BusClient :: # -> *) inFlightTransactions =
dequeueRequest :: MkTagType inFlightTransactions
-> ActionValue BusRequest
enqueueResponse :: (BusResponse, MkTagType inFlightTransactions)
-> Action
type Token = UInt 5 -- # BusServer.dequeueResponse
-- * If the arbiter is able to successfully call `dequeueResponse`, then
a :: UInt 5 -- the BusServer's internal logic must update such that it understands
a = 3 -- the response has been handed off.
-- # BusServer.peekClientTagDestination
-- * The arbiter looks at (peekClientTagDestination :: MkClientTagType) to
-- determine whether or not it is currently safe whether to dequeue the
-- response as well as where to route the response should it dequeue the
-- response.
-- * `peekClientTagDestination` should be guarded on whether or not there is
-- a valid response available.
interface (BusServer :: # -> # -> *) inFlightTransactions numClients =
enqueueRequest :: (MkTagType inFlightTransactions, BusRequest)
-> Action
dequeueResponse :: ActionValue (
MkClientTagType numClients,
BusResponse, transactionTagType
)
peekClientTagDestination :: MkClientTagType numClients

View file

@ -1,4 +1,5 @@
package TagEngine( package TagEngine(
MkTagType,
TagEngine(..), TagEngine(..),
Util.BasicResult(..), Util.BasicResult(..),
mkTagEngine) where mkTagEngine) where
@ -9,11 +10,11 @@ import FIFO
import FIFOF import FIFOF
import SpecialFIFOs import SpecialFIFOs
#define UIntLog2N(n) (UInt (TLog n)) type MkTagType numTags = (UInt (TLog numTags))
interface (TagEngine :: # -> *) numTags = interface (TagEngine :: # -> *) numTags =
requestTag :: ActionValue UIntLog2N(numTags) requestTag :: ActionValue (MkTagType numTags)
retireTag :: UIntLog2N(numTags) -> Action retireTag :: (MkTagType 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
@ -44,7 +45,7 @@ mkTagEngine = do
debugOnce <- mkReg True debugOnce <- mkReg True
-- Rules -- Rules
addRules $ addRules |>
rules rules
"debug_initial_state": when debugOnce ==> do "debug_initial_state": when debugOnce ==> do
$display "tagUsage: " (fshow (readVReg tagUsage)) $display "tagUsage: " (fshow (readVReg tagUsage))
@ -77,9 +78,9 @@ mkTagEngine = do
(Nothing, Nothing) -> action {} (Nothing, Nothing) -> action {}
-- Interface -- Interface
return $ return |>
interface TagEngine interface TagEngine
requestTag :: ActionValue UIntLog2N(numTags) requestTag :: ActionValue (MkTagType numTags)
requestTag = do requestTag = do
case initialTagDistributor of case initialTagDistributor of
Just 0 -> do Just 0 -> do
@ -100,7 +101,7 @@ mkTagEngine = do
-- so it is advisable that the caller of `retireTag` only attempt to retire valid tags. -- so it is advisable that the caller of `retireTag` only attempt to retire valid tags.
-- Internally, the tagEngine will keep a correct and consistent state since TagEngine -- Internally, the tagEngine will keep a correct and consistent state since TagEngine
-- validates tags before attempting to retire them. -- validates tags before attempting to retire them.
retireTag :: UIntLog2N(numTags) -> Action retireTag :: (MkTagType numTags) -> Action
retireTag tag = retireTag tag =
do do
let let