Compare commits

..

No commits in common. "f6d44f12776d7c116dd208570af0d2ef9de6149c" and "2d5cf48c54bd502274deaa50e71d6e055fc411a8" have entirely different histories.

3 changed files with 32 additions and 111 deletions

View file

@ -1,55 +1,7 @@
package Bus(mkBus) where package Bus(a) where
import Types import Types
import BusTypes import BusTypes
import TagEngine
import Vector
import Util
import Arbiter
clientRequest :: Arbiter.ArbiterClient_IFC -> Action a :: UInt 5
clientRequest ifc = ifc.request a = 3
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,16 +1,12 @@
package BusTypes( package BusTypes(
MkClientTagType, BusVal(..),
BusClient(..), BusServer(..), BusError(..),
BusRequest(..), BusResponse(..), TransactionSize(..),
ReadRequest(..), ReadResponse(..), WriteRequest(..), WriteResponse(..), ReadRequest(..),
BusVal(..), BusError(..), TransactionSize(..) WriteRequest(..)
) where ) where
import Types import Types
import Vector
import TagEngine
type MkClientTagType a = (UInt (TLog a))
data BusError data BusError
= UnMapped = UnMapped
@ -52,47 +48,21 @@ data BusResponse
| BusWriteResponse WriteResponse | BusWriteResponse WriteResponse
deriving (Bits, Eq, FShow) deriving (Bits, Eq, FShow)
-- # BusClient.dequeueRequest interface BusMaster =
-- * The Bus arbiter will call the Bus Client's request method if it is -- The Bus arbiter will call the Bus Master's request method
-- the Bus Client's turn to make a request, or if another client forfits -- if and only if it's the Bus Master's turn to make a request, and the Bus Master
-- its turn. -- has a request to make.
-- * The BusClient must guard its request method such that calling its -- It is up to the BusMaster to guard it's request method such that calling
-- request method is only valid when the BusClient has a request to make. -- it's request method is only valid when the BusMaster has a request to make.
-- * This has implications about for the implementor of BusClient, -- This has implications about for the implementor of BusMaster, namely, that it
-- namely, that it should hold its request until it's request method -- should hold its request until it's request method gets called.
-- gets called. The arbiter tags the request so that the client can request :: BusRequest
-- later correctly correlate the response. -- From the masters's perspective, the response should not be called by the
-- * Although the tag is technically passed in as an argument from the -- arbiter until the master is ready to accept the response. In other words,
-- arbiter to the client's request method, given that methods are -- response should be guarded by the client.
-- atomic in Bluespec, this is effectively equivalent to tagging the response :: BusResponse -> Action
-- 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
-- # BusServer.dequeueResponse type Token = UInt 5
-- * If the arbiter is able to successfully call `dequeueResponse`, then
-- the BusServer's internal logic must update such that it understands a :: UInt 5
-- the response has been handed off. a = 3
-- # 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,5 +1,4 @@
package TagEngine( package TagEngine(
MkTagType,
TagEngine(..), TagEngine(..),
Util.BasicResult(..), Util.BasicResult(..),
mkTagEngine) where mkTagEngine) where
@ -10,11 +9,11 @@ import FIFO
import FIFOF import FIFOF
import SpecialFIFOs import SpecialFIFOs
type MkTagType numTags = (UInt (TLog numTags)) #define UIntLog2N(n) (UInt (TLog n))
interface (TagEngine :: # -> *) numTags = interface (TagEngine :: # -> *) numTags =
requestTag :: ActionValue (MkTagType numTags) requestTag :: ActionValue UIntLog2N(numTags)
retireTag :: (MkTagType numTags) -> Action 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
@ -45,7 +44,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))
@ -78,9 +77,9 @@ mkTagEngine = do
(Nothing, Nothing) -> action {} (Nothing, Nothing) -> action {}
-- Interface -- Interface
return |> return $
interface TagEngine interface TagEngine
requestTag :: ActionValue (MkTagType numTags) requestTag :: ActionValue UIntLog2N(numTags)
requestTag = do requestTag = do
case initialTagDistributor of case initialTagDistributor of
Just 0 -> do Just 0 -> do
@ -101,7 +100,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 :: (MkTagType numTags) -> Action retireTag :: UIntLog2N(numTags) -> Action
retireTag tag = retireTag tag =
do do
let let