Skip to content

Commit 391df03

Browse files
Add XPM_CDC_GRAY to clash-cores
1 parent 8ce162e commit 391df03

File tree

9 files changed

+454
-0
lines changed

9 files changed

+454
-0
lines changed

clash-cores/clash-cores.cabal

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -101,6 +101,10 @@ library
101101
Clash.Cores.Xilinx.Floating.BlackBoxes
102102
Clash.Cores.Xilinx.Floating.Explicit
103103
Clash.Cores.Xilinx.Floating.Internal
104+
Clash.Cores.Xilinx.Xpm
105+
Clash.Cores.Xilinx.Xpm.Cdc
106+
Clash.Cores.Xilinx.Xpm.Cdc.Gray
107+
Clash.Cores.Xilinx.Xpm.Cdc.Gray.Internal
104108
Clash.Cores.SPI
105109
Clash.Cores.UART
106110
Clash.Cores.LatticeSemi.ICE40.IO
@@ -116,6 +120,7 @@ library
116120
clash-lib,
117121
infinite-list ^>= 0.1,
118122
mtl >= 2.1.1 && < 2.3,
123+
pretty-show,
119124
prettyprinter >= 1.2.0.1 && < 1.8,
120125
prettyprinter-interp ^>= 0.2,
121126
reducers >= 3.12.2 && < 4.0,
@@ -147,6 +152,7 @@ test-suite unittests
147152
tasty >= 1.2 && < 1.5,
148153
tasty-hunit,
149154
tasty-quickcheck,
155+
tasty-th,
150156
hedgehog,
151157
tasty-hedgehog >= 1.2.0
152158

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
{-|
2+
Copyright : (C) 2023, Google LLC
3+
License : BSD2 (see the file LICENSE)
4+
Maintainer : QBayLogic B.V. <[email protected]>
5+
-}
6+
7+
module Clash.Cores.Xilinx.Xpm
8+
( module Clash.Cores.Xilinx.Xpm.Cdc
9+
) where
10+
11+
import Clash.Cores.Xilinx.Xpm.Cdc
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
{-|
2+
Copyright : (C) 2023, Google LLC
3+
License : BSD2 (see the file LICENSE)
4+
Maintainer : QBayLogic B.V. <[email protected]>
5+
-}
6+
7+
module Clash.Cores.Xilinx.Xpm.Cdc
8+
( module Clash.Cores.Xilinx.Xpm.Cdc.Gray
9+
) where
10+
11+
import Clash.Cores.Xilinx.Xpm.Cdc.Gray
Lines changed: 99 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,99 @@
1+
{-|
2+
Copyright : (C) 2023, Google LLC
3+
License : BSD2 (see the file LICENSE)
4+
Maintainer : QBayLogic B.V. <[email protected]>
5+
-}
6+
{-# LANGUAGE NamedFieldPuns #-}
7+
{-# LANGUAGE RecordWildCards #-}
8+
9+
module Clash.Cores.Xilinx.Xpm.Cdc.Gray
10+
( xpmCdcGray
11+
, XpmCdcGrayConfig(..)
12+
, xpmCdcGrayWith
13+
) where
14+
15+
import GHC.Stack (HasCallStack)
16+
17+
import Clash.Explicit.Prelude
18+
19+
import Clash.Cores.Xilinx.Xpm.Cdc.Gray.Internal (xpmCdcGray#)
20+
21+
-- | Synchronizes an 'Unsigned' from the source clock domain to the destination
22+
-- clock domain using Gray code. It instantiates Xilinx's @XPM_CDC_GRAY@, so no
23+
-- additional constraint definitions are needed. In order to synchronize data
24+
-- from the source domain to the destination domain, consecutive inputs need to
25+
-- be unchanged, successors (+1), or predecessors (-1). Overflows are okay. That is,
26+
-- 'maxBound' can be followed by zero, and vice versa. If this invariant is
27+
-- violated, the component might not transfer data correctly until the invariant
28+
-- is upheld again and the source clock has sampled the input once, followed by
29+
-- /4/ samples in the destination domain.
30+
--
31+
-- If you need all data to be transferred from the source domain to the destination
32+
-- domain, make sure the destination domain samples the input domain at least
33+
-- twice. Alternatively, use a FIFO.
34+
--
35+
-- Read more in [PG382](https://docs.xilinx.com/r/en-US/pg382-xpm-cdc-generator/XPM_CDC_GRAY).
36+
--
37+
-- __N.B.__: The simulation model does not detect invariant violations.
38+
--
39+
-- __N.B.__: In order to simulate initial values, both the source and destination
40+
-- domain need to support them. If the source and destination domain
41+
-- disagree on this property, use of this function will fail to
42+
-- simulate and translate to HDL.
43+
--
44+
xpmCdcGray ::
45+
forall n src dst.
46+
( 2 <= n, n <= 32
47+
, KnownNat n
48+
, KnownDomain src
49+
, KnownDomain dst
50+
, HasCallStack
51+
) =>
52+
Clock src ->
53+
Clock dst ->
54+
Signal src (Unsigned n) ->
55+
Signal dst (Unsigned n)
56+
xpmCdcGray = xpmCdcGrayWith XpmCdcGrayConfig{..}
57+
where
58+
stages = d4
59+
initialValues =
60+
case (initBehavior @src, initBehavior @dst) of
61+
(SDefined, SDefined) -> True
62+
(SUnknown, SUnknown) -> False
63+
_ -> clashCompileError $ "xpmCdcGray: domains need to agree on initial value "
64+
<> "behavior. To set initial value usage explicitly, "
65+
<> "consider using 'xpmCdcGrayWith'."
66+
{-# INLINE xpmCdcGray #-}
67+
68+
-- | Configuration for 'xpmCdcGrayWith'
69+
data XpmCdcGrayConfig stages = XpmCdcGrayConfig
70+
{ -- | Number of synchronization stages. I.e., number of registers in the
71+
-- destination domain. Note that there is always a register in the source
72+
-- domain.
73+
stages :: SNat stages
74+
75+
-- | Initialize registers used within the primitive to /0/. Note that
76+
-- 'xpmCdcGray' will set this to 'True' if both domains support initial
77+
-- values, to 'False' if neither domain does, and will otherwise emit an
78+
-- error.
79+
, initialValues :: Bool
80+
}
81+
82+
-- | Like 'xpmCdcGray', but with a configurable number of stages. Also see
83+
-- 'XpmCdcGrayConfig'.
84+
xpmCdcGrayWith ::
85+
forall stages n src dst.
86+
( 2 <= n, n <= 32
87+
, 2 <= stages, stages <= 10
88+
, KnownNat n
89+
, KnownDomain src
90+
, KnownDomain dst
91+
, HasCallStack
92+
) =>
93+
XpmCdcGrayConfig stages ->
94+
Clock src ->
95+
Clock dst ->
96+
Signal src (Unsigned n) ->
97+
Signal dst (Unsigned n)
98+
xpmCdcGrayWith XpmCdcGrayConfig{..} = xpmCdcGray# initialValues stages
99+
{-# INLINE xpmCdcGrayWith #-}
Lines changed: 178 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,178 @@
1+
{-|
2+
Copyright : (C) 2023, Google LLC
3+
License : BSD2 (see the file LICENSE)
4+
Maintainer : QBayLogic B.V. <[email protected]>
5+
-}
6+
{-# LANGUAGE LambdaCase #-}
7+
{-# LANGUAGE NumericUnderscores #-}
8+
{-# LANGUAGE OverloadedStrings #-}
9+
{-# LANGUAGE QuasiQuotes #-}
10+
{-# LANGUAGE ViewPatterns #-}
11+
12+
module Clash.Cores.Xilinx.Xpm.Cdc.Gray.Internal where
13+
14+
import Prelude
15+
import Clash.Explicit.Prelude
16+
( type (<=), KnownNat, SNat, Unsigned, Clock, KnownDomain, errorX
17+
, unsafeSynchronizer )
18+
19+
import Clash.Annotations.Primitive (Primitive(..), HDL(..), hasBlackBox)
20+
import Clash.Backend (Backend)
21+
import Clash.Netlist.Types (TemplateFunction(..), BlackBoxContext)
22+
import Clash.Promoted.Nat (snatToNum)
23+
import Clash.Signal.Internal (Signal((:-)))
24+
25+
import Control.Monad.State (State)
26+
import Data.List.Infinite (Infinite(..), (...))
27+
import Data.String.Interpolate (__i)
28+
import Data.Text (Text)
29+
import Data.Text.Prettyprint.Doc.Extra (Doc)
30+
import GHC.Stack (HasCallStack)
31+
import Text.Show.Pretty (ppShow)
32+
33+
import qualified Clash.Netlist.Id as Id
34+
import qualified Clash.Netlist.Types as N
35+
import qualified Clash.Primitives.DSL as DSL
36+
37+
xpmCdcGrayTF :: TemplateFunction
38+
xpmCdcGrayTF =
39+
TemplateFunction
40+
[initBehavior, stages, clkSrc, clkDst, input]
41+
(const True)
42+
xpmCdcGrayTF#
43+
where
44+
_2LteN
45+
:< _nLte32
46+
:< _2LteStages
47+
:< _stagesLte10
48+
:< _knownNatN
49+
:< _knownDomainSrc
50+
:< _knownDomainDst
51+
:< _hasCallStack
52+
:< initBehavior
53+
:< stages
54+
:< clkSrc
55+
:< clkDst
56+
:< input
57+
:< _ = (0...)
58+
59+
xpmCdcGrayTF# :: Backend backend => BlackBoxContext -> State backend Doc
60+
xpmCdcGrayTF# bbCtx
61+
| [ _2LteN
62+
, _nLte32
63+
, _2LteStages
64+
, _stagesLte10
65+
, _knownNatN
66+
, _knownDomainSrc
67+
, _knownDomainDst
68+
, _hasCallStack
69+
, DSL.getBool -> Just initValues
70+
, DSL.tExprToInteger -> Just stages
71+
, clkSrc
72+
, clkDst
73+
, input
74+
] <- map fst (DSL.tInputs bbCtx)
75+
, [resultTy] <- map DSL.ety (DSL.tResults bbCtx)
76+
= do
77+
78+
let
79+
compName :: Text
80+
compName = "xpm_cdc_gray"
81+
82+
width :: Integral a => a
83+
width = DSL.tySize resultTy
84+
85+
instName <- Id.make (compName <> "_inst")
86+
DSL.declarationReturn bbCtx (compName <> "_block") $ do
87+
inputBv <- DSL.toBV "src_in_bin_bv" input
88+
resultBv <- DSL.declare "dest_out_bin_bv" (N.BitVector width)
89+
result <- DSL.fromBV "dest_out_bin" resultTy resultBv
90+
91+
let
92+
generics :: [(Text, DSL.LitHDL)]
93+
generics =
94+
[ ("DEST_SYNC_FF", DSL.I stages)
95+
, ("INIT_SYNC_FF", if initValues then 1 else 0)
96+
, ("REG_OUTPUT", 0)
97+
, ("SIM_ASSERT_CHK", 0)
98+
, ("SIM_LOSSLESS_GRAY_CHK", 0)
99+
, ("WIDTH", DSL.I width)
100+
]
101+
102+
inps :: [(Text, DSL.TExpr)]
103+
inps =
104+
[ ("src_clk", clkSrc)
105+
, ("dest_clk", clkDst)
106+
, ("src_in_bin", inputBv)
107+
]
108+
109+
outs :: [(Text, DSL.TExpr)]
110+
outs =
111+
[ ("dest_out_bin", resultBv)
112+
]
113+
114+
DSL.instDecl
115+
N.Empty
116+
(Id.unsafeMake compName)
117+
instName
118+
generics
119+
inps
120+
outs
121+
122+
pure [result]
123+
124+
xpmCdcGrayTF# bbCtx = error (ppShow bbCtx)
125+
126+
{-# NOINLINE xpmCdcGray# #-}
127+
{-# ANN xpmCdcGray# hasBlackBox #-}
128+
{-# ANN xpmCdcGray#
129+
let
130+
primName = show 'xpmCdcGray#
131+
tfName = show 'xpmCdcGrayTF
132+
in InlineYamlPrimitive [VHDL] [__i|
133+
BlackBox:
134+
name: #{primName}
135+
kind: Declaration
136+
format: Haskell
137+
libraries: ["xpm"]
138+
imports: ["xpm.vcomponents.all"]
139+
templateFunction: #{tfName}
140+
|] #-}
141+
{-# ANN xpmCdcGray#
142+
let
143+
primName = show 'xpmCdcGray#
144+
tfName = show 'xpmCdcGrayTF
145+
in InlineYamlPrimitive [Verilog, SystemVerilog] [__i|
146+
BlackBox:
147+
name: #{primName}
148+
kind: Declaration
149+
format: Haskell
150+
templateFunction: #{tfName}
151+
|] #-}
152+
-- | Primitive used in 'Clash.Cores.Xilinx.Xpm.Cdc.Gray.xpmCdcGray'
153+
xpmCdcGray# ::
154+
forall stages n src dst.
155+
( 2 <= n, n <= 32
156+
, 2 <= stages, stages <= 10
157+
, KnownNat n
158+
, KnownDomain src
159+
, KnownDomain dst
160+
, HasCallStack
161+
) =>
162+
-- | Initial values supported
163+
Bool ->
164+
SNat stages ->
165+
Clock src ->
166+
Clock dst ->
167+
Signal src (Unsigned n) ->
168+
Signal dst (Unsigned n)
169+
xpmCdcGray# initValuesSupported stages clkSrc clkDst input =
170+
go (snatToNum stages) (initVal :- input)
171+
where
172+
initVal
173+
| initValuesSupported = 0
174+
| otherwise = errorX "xpmCdcGray: initial values undefined"
175+
176+
go :: Word -> Signal src (Unsigned n) -> Signal dst (Unsigned n)
177+
go 0 src = unsafeSynchronizer clkSrc clkDst src
178+
go n src = initVal :- go (n - 1) src

tests/Main.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -497,6 +497,12 @@ runClashTest = defaultMain $ clashTestRoot
497497
]
498498
}
499499
in runTest "Floating" _opts
500+
, runTest "XpmCdcGray" $ def
501+
{ hdlTargets=[VHDL, Verilog]
502+
, hdlLoad=[]
503+
, hdlSim=[Vivado]
504+
, buildTargets=BuildSpecific ["tb" <> show n | n <- [(1::Int)..7]]
505+
}
500506
, clashTestGroup "DcFifo"
501507
[ let _opts =
502508
def{ hdlTargets=[VHDL, Verilog]

0 commit comments

Comments
 (0)