Skip to content

Commit 63b90ce

Browse files
authored
clash-cores: Fix xpmCdcHandshake (#2610)
* The HDL generated incorrectly set DEST_EXT_HSK=0, configuring it to generate acks automatically. While the exposed API and simulation model assumed external handshaking. * The dstStages and srcStages settings were flipped. This also updates the test so it can detect that first error. And improves the haddock a bit to clarify what the settings do and relate them to the XPM documentation.
1 parent c8734ac commit 63b90ce

File tree

3 files changed

+43
-19
lines changed

3 files changed

+43
-19
lines changed

clash-cores/src/Clash/Cores/Xilinx/Xpm/Cdc/Handshake.hs

Lines changed: 24 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-|
2-
Copyright : (C) 2023, Google LLC
2+
Copyright : (C) 2023, Google LLC,
3+
2023, QBayLogic B.V.
34
License : BSD2 (see the file LICENSE)
45
Maintainer : QBayLogic B.V. <[email protected]>
56
-}
@@ -81,11 +82,28 @@ xpmCdcHandshake = xpmCdcHandshakeWith XpmCdcHandshakeConfig{..}
8182
{-# INLINE xpmCdcHandshake #-}
8283

8384
-- | Configuration for 'xpmCdcHandshakeWith'
85+
--
86+
-- Other attributes that are hardcoded:
87+
--
88+
-- +------------------+-------+
89+
-- | Attribute | Value |
90+
-- +==================+=======+
91+
-- | @DEST_EXT_HSK@ | 1 |
92+
-- +------------------+-------+
93+
-- | @SIM_ASSERT_CHK@ | 0 |
94+
-- +------------------+-------+
8495
data XpmCdcHandshakeConfig srcStages dstStages = XpmCdcHandshakeConfig
85-
{ -- | Number of synchronization stages in the source domain
96+
{ -- | Number of registers, clocked by the src clock, that are used to synchronize @dest_ack@ to @src_rcv@.
97+
--
98+
-- This is what [PG382](https://docs.xilinx.com/r/en-US/pg382-xpm-cdc-generator/XPM_CDC_HANDSHAKE)
99+
-- calls @SRC_SYNC_FF@.
86100
srcStages :: SNat srcStages
87101

88-
-- | Number of synchronization stages in the destination domain
102+
-- | Number of registers, clocked by the dst clock,
103+
-- that are used to synchronize between the input register of @src_send@ and the output register of @dest_req@.
104+
--
105+
-- This is what [PG382](https://docs.xilinx.com/r/en-US/pg382-xpm-cdc-generator/XPM_CDC_HANDSHAKE)
106+
-- calls @DEST_SYNC_FF@.
89107
, dstStages :: SNat dstStages
90108

91109
-- | Initialize registers used within the primitive to /0/. Note that
@@ -95,6 +113,9 @@ data XpmCdcHandshakeConfig srcStages dstStages = XpmCdcHandshakeConfig
95113
--
96114
-- This value is ignored in Clash simulation on domains configured to not
97115
-- support initial values.
116+
--
117+
-- This is what [PG382](https://docs.xilinx.com/r/en-US/pg382-xpm-cdc-generator/XPM_CDC_HANDSHAKE)
118+
-- calls @INIT_SYNC_FF@.
98119
, initialValues :: Bool
99120
}
100121

clash-cores/src/Clash/Cores/Xilinx/Xpm/Cdc/Handshake/Internal.hs

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-|
2-
Copyright : (C) 2023, Google LLC
2+
Copyright : (C) 2023, Google LLC,
3+
2023, QBayLogic B.V.
34
License : BSD2 (see the file LICENSE)
45
Maintainer : QBayLogic B.V. <[email protected]>
56
-}
@@ -111,11 +112,11 @@ xpmCdcHandshakeTF# bbCtx
111112
let
112113
generics :: [(Text, DSL.LitHDL)]
113114
generics =
114-
[ ("DEST_EXT_HSK", DSL.I 0)
115-
, ("DEST_SYNC_FF", DSL.I srcStages0)
115+
[ ("DEST_EXT_HSK", DSL.I 1)
116+
, ("DEST_SYNC_FF", DSL.I dstStages0)
116117
, ("INIT_SYNC_FF", if initValues0 then 1 else 0)
117118
, ("SIM_ASSERT_CHK", 0)
118-
, ("SRC_SYNC_FF", DSL.I dstStages0)
119+
, ("SRC_SYNC_FF", DSL.I srcStages0)
119120
, ("WIDTH", DSL.I width)
120121
]
121122

@@ -208,8 +209,8 @@ xpmCdcHandshake# initVals srcStages dstStages clkSrc clkDst srcIn srcSend dstAck
208209
, initialValues = initVals
209210
, registerInput = False }
210211

211-
srcSendFfSynced = xpmCdcSingleWith (defOpts srcStages) clkSrc clkDst srcSendFf
212-
srcRcv = xpmCdcSingleWith (defOpts dstStages) clkDst clkSrc dstAck
212+
srcSendFfSynced = xpmCdcSingleWith (defOpts dstStages) clkSrc clkDst srcSendFf
213+
srcRcv = xpmCdcSingleWith (defOpts srcStages) clkDst clkSrc dstAck
213214

214215
srcSendFf = delay clkSrc enableGen (initVal False) srcSend
215216
srcHsDataFf = delay clkSrc (toEnable (not <$> srcSendFf)) (initVal (unpack 0)) srcIn

tests/shouldwork/Cores/Xilinx/XpmCdcHandshakeTypes.hs

Lines changed: 12 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ createDomain vXilinxSystem{vName="D5", vPeriod=hzToPeriod 50e6}
1515
createDomain vXilinxSystem{vName="D10", vPeriod=hzToPeriod 100e6}
1616
createDomain vXilinxSystem{vName="D11", vPeriod=hzToPeriod 110e6}
1717

18-
data State = WaitForDeassert | WaitForAssert deriving (Generic, NFDataX)
18+
data State = WaitForDeassert | WaitForAssert (Index 2) deriving (Generic, NFDataX)
1919

2020
-- | Transfer 1, 2, 3, ... to destination domain
2121
srcFsm ::
@@ -29,10 +29,11 @@ srcFsm ::
2929
Signal src (a, Bool)
3030
srcFsm clk = mealy clk noReset enableGen go (0, WaitForDeassert)
3131
where
32-
go (n, WaitForDeassert) True = ((n, WaitForDeassert), (n, False))
33-
go (n, WaitForDeassert) False = ((n + 1, WaitForAssert), (n + 1, True))
34-
go (n, WaitForAssert) False = ((n, WaitForAssert), (n, True))
35-
go (n, WaitForAssert) True = ((n, WaitForDeassert), (n, False))
32+
go (n, WaitForDeassert) True = ((n, WaitForDeassert), (0, False))
33+
go (n, WaitForDeassert) False = ((n + 1, WaitForAssert maxBound), (n + 1, True))
34+
go (n, WaitForAssert _) False = ((n, WaitForAssert maxBound), (n, True))
35+
go (n, WaitForAssert 0) True = ((n, WaitForDeassert), (0, False))
36+
go (n, WaitForAssert w) True = ((n, WaitForAssert (w-1)), (n, True)) -- seen src_rcv, wait a little before dropping src_send
3637
{-# NOINLINE srcFsm #-}
3738

3839
-- | Receives data from source domain
@@ -42,12 +43,13 @@ dstFsm ::
4243
Clock dst ->
4344
Signal dst (Bool, a) ->
4445
Signal dst (Bool, Maybe a)
45-
dstFsm clk = mealy clk noReset enableGen go WaitForAssert
46+
dstFsm clk = mealy clk noReset enableGen go (WaitForAssert maxBound)
4647
where
47-
go WaitForAssert (False, _) = (WaitForAssert, (False, Nothing))
48-
go WaitForAssert (True, n) = (WaitForDeassert, (True, Just n))
49-
go WaitForDeassert (True, _) = (WaitForDeassert, (True, Nothing))
50-
go WaitForDeassert (False, _) = (WaitForAssert, (False, Nothing))
48+
go (WaitForAssert _) (False, _) = (WaitForAssert maxBound, (False, Nothing))
49+
go (WaitForAssert 0) (True, n) = (WaitForDeassert, (True, Just n))
50+
go (WaitForAssert w) (True, n) = (WaitForAssert (w-1), (False, Nothing)) -- seen dest_req, wait a little before asserting dest_ack
51+
go WaitForDeassert (True, _) = (WaitForDeassert, (True, Nothing))
52+
go WaitForDeassert (False, _) = (WaitForAssert maxBound, (False, Nothing))
5153
{-# NOINLINE dstFsm #-}
5254

5355
-- | Composition of 'srcFsm' and 'dstFsm'

0 commit comments

Comments
 (0)