Skip to content

Commit 2b933bb

Browse files
committed
Add ReqResp Protocol
A simple protocol for request-response transactions
1 parent 5e8ad7a commit 2b933bb

File tree

2 files changed

+44
-0
lines changed

2 files changed

+44
-0
lines changed

clash-protocols.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -177,6 +177,7 @@ library
177177
Protocols.Internal.Units.TH
178178
Protocols.Plugin
179179
Protocols.Plugin.Internal
180+
Protocols.ReqResp
180181
Protocols.Wishbone
181182
Protocols.Wishbone.Standard
182183
Protocols.Wishbone.Standard.Hedgehog

src/Protocols/ReqResp.hs

Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
-- |
2+
-- Simple protocol for request-response communication.
3+
-- The forward channel channel has type @Signal dom (Maybe req)@ and is used to send requests.
4+
-- The backward channel has type @Signal dom (Maybe resp)@ and is used to send responses.
5+
-- The protocol must obey the following rules:
6+
-- * When the forward channel is @Just a@, it must not change until the transaction is completed.
7+
-- * The forward channel can not depend on the backward channel.
8+
-- * When the forward channel is @Nothing@, the backward channel may be undefined.
9+
module Protocols.ReqResp where
10+
11+
import qualified Clash.Prelude as C
12+
import Data.Kind (Type)
13+
import Protocols
14+
import Protocols.Internal.Classes
15+
import Prelude as P
16+
17+
-- | For simple request-response protocols. The forward channel is used to send requests
18+
-- and the backward channel is used to send responses.
19+
-- Rules:
20+
-- * When the forward channel is @Just a@, it must not change until the transaction
21+
-- is completed.
22+
-- * The forward channel can not depend on the backward channel.
23+
-- * When the forward channel is @Nothing@, the backward channel may be undefined.
24+
data ReqResp (dom :: C.Domain) (req :: Type) (resp :: Type)
25+
26+
instance Protocol (ReqResp dom req resp) where
27+
-- \| Forward channel for ReqResp protocol:
28+
type Fwd (ReqResp dom req resp) = C.Signal dom (Maybe req)
29+
30+
-- \| Backward channel for ReqResp protocol:
31+
type Bwd (ReqResp dom req resp) = C.Signal dom (Maybe resp)
32+
33+
instance IdleCircuit (ReqResp dom req resp) where
34+
idleFwd _ = pure Nothing
35+
idleBwd _ = pure Nothing
36+
37+
-- | Force a @Nothing@ on the backward channel and @Nothing@ on the forward
38+
-- channel if reset is asserted.
39+
forceResetSanity ::
40+
forall dom req resp.
41+
(C.HiddenReset dom) =>
42+
Circuit (ReqResp dom req resp) (ReqResp dom req resp)
43+
forceResetSanity = forceResetSanityGeneric

0 commit comments

Comments
 (0)