Skip to content

Commit cfb3059

Browse files
committed
Add ReqResp Protocol
A simple protocol for request-response transactions
1 parent 623ecd9 commit cfb3059

File tree

2 files changed

+54
-0
lines changed

2 files changed

+54
-0
lines changed

clash-protocols.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -179,6 +179,7 @@ library
179179
Protocols.Internal.Units.TH
180180
Protocols.Plugin
181181
Protocols.Plugin.Internal
182+
Protocols.ReqResp
182183
Protocols.Wishbone
183184
Protocols.Wishbone.Standard
184185
Protocols.Wishbone.Standard.Hedgehog

src/Protocols/ReqResp.hs

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

0 commit comments

Comments
 (0)