Skip to content

Commit

Permalink
Add ReqResp Protocol
Browse files Browse the repository at this point in the history
A simple protocol for request-response transactions
  • Loading branch information
lmbollen committed Jun 28, 2024
1 parent 5e8ad7a commit ee63617
Show file tree
Hide file tree
Showing 2 changed files with 47 additions and 0 deletions.
1 change: 1 addition & 0 deletions clash-protocols.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -177,6 +177,7 @@ library
Protocols.Internal.Units.TH
Protocols.Plugin
Protocols.Plugin.Internal
Protocols.ReqResp
Protocols.Wishbone
Protocols.Wishbone.Standard
Protocols.Wishbone.Standard.Hedgehog
Expand Down
46 changes: 46 additions & 0 deletions src/Protocols/ReqResp.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
{- |
Simple protocol for request-response communication.
The forward channel channel has type @Signal dom (Maybe req)@ and is used to send requests.
The backward channel has type @Signal dom (Maybe resp)@ and is used to send responses.
The protocol must obey the following rules:
* When the forward channel is @Just a@, it must not change until the transaction is completed.
* The forward channel can not depend on the backward channel.
* When the forward channel is @Nothing@, the backward channel may be undefined.
-}
module Protocols.ReqResp where

import qualified Clash.Prelude as C
import Data.Kind (Type)
import Protocols
import Protocols.Internal.Classes
import Prelude as P

{- | For simple request-response protocols. The forward channel is used to send requests
and the backward channel is used to send responses.
Rules:
* When the forward channel is @Just a@, it must not change until the transaction
is completed.
* The forward channel can not depend on the backward channel.
* When the forward channel is @Nothing@, the backward channel may be undefined.
-}
data ReqResp (dom :: C.Domain) (req :: Type) (resp :: Type)

instance Protocol (ReqResp dom req resp) where
-- \| Forward channel for ReqResp protocol:
type Fwd (ReqResp dom req resp) = C.Signal dom (Maybe req)

-- \| Backward channel for ReqResp protocol:
type Bwd (ReqResp dom req resp) = C.Signal dom (Maybe resp)

instance IdleCircuit (ReqResp dom req resp) where
idleFwd _ = pure Nothing
idleBwd _ = pure Nothing

{- | Force a @Nothing@ on the backward channel and @Nothing@ on the forward
channel if reset is asserted.
-}
forceResetSanity ::
forall dom req resp.
(C.HiddenReset dom) =>
Circuit (ReqResp dom req resp) (ReqResp dom req resp)
forceResetSanity = forceResetSanityGeneric

0 comments on commit ee63617

Please sign in to comment.