Skip to content

Commit

Permalink
Switch to Xilinx designs and remove dead code
Browse files Browse the repository at this point in the history
Let's keep the handwritten implementation in the history in case we need it
  • Loading branch information
martijnbastiaan committed Dec 5, 2024
1 parent bedfb61 commit 9ba7c19
Show file tree
Hide file tree
Showing 4 changed files with 3 additions and 120 deletions.
4 changes: 2 additions & 2 deletions bittide/src/Bittide/Transceiver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -368,13 +368,13 @@ transceiverPrbsN opts inputs@Inputs{clock, reset, refClock} =

txOutClk = (head outputs).txOutClock
-- see [NOTE: duplicate tx/rx domain]
txClockNw = Gth.gthUserClockNetwork @tx @tx txOutClk txUsrClkRst
txClockNw = Gth.xilinxGthUserClockNetworkTx @tx @tx txOutClk txUsrClkRst
(_txClk1s, txClock, _txClkActives) = txClockNw
txClocks = repeat txClock

rxOutClks = map (.rxOutClock) outputs
-- see [NOTE: duplicate tx/rx domain]
rxClockNws = map (flip (Gth.gthUserClockNetwork @rx @rx) rxUsrClkRst) rxOutClks
rxClockNws = map (flip (Gth.xilinxGthUserClockNetworkRx @rx @rx) rxUsrClkRst) rxOutClks
(_rxClk1s, rxClocks, _rxClkActives) = unzip3 rxClockNws

go (clockTx1, clockTx2, txActive) transceiverIndex channelName clockPath rxN rxP txData txReady rxReady (clockRx1, clockRx2, rxActive) =
Expand Down
2 changes: 1 addition & 1 deletion bittide/src/Clash/Cores/Xilinx/GTH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,4 +4,4 @@

module Clash.Cores.Xilinx.GTH (module X) where

import Clash.Cores.Xilinx.GTH.Internal as X hiding (unsafeBufgGt)
import Clash.Cores.Xilinx.GTH.Internal as X
46 changes: 0 additions & 46 deletions bittide/src/Clash/Cores/Xilinx/GTH/BlackBoxes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -305,49 +305,3 @@ ibufds_gte3BBTF bbCtx
(zip (fst <$> compOuts) outs)
pure outs
ibufds_gte3BBTF bbCtx = error ("ibufds_gte3BBTF, bad bbCtx: " <> show bbCtx)

{- | Template function for 'unsafeBufgGt'.
TODO: Upstream to @clash-cores@
-}
unsafeBufgGtTF :: TemplateFunction
unsafeBufgGtTF = TemplateFunction used valid go
where
used = [1, 2, 3]
valid = const True

go :: (Backend s) => BlackBoxContext -> State s Doc
go bbCtx
| [_knownDomOut, div0, clk, clr] <- map fst (DSL.tInputs bbCtx) =
do
instLabel <- Id.makeBasic "bufgGt_inst"

DSL.declarationReturn bbCtx "bufgGt_block" $ do
bufgGtOut <- DSL.declare "bufgGt_out" Bit
-- div1 <- DSL.pureToBVResized "div" 3 div0 -- TODO resize is currently VHDL only
let
compName = "BUFG_GT"
compInps =
[ ("I", Bit)
, ("CLR", Bit)
, ("DIV", BitVector 3)
, ("CE", Bit)
, ("CEMASK", Bit)
, ("CLRMASK", Bit)
]
compOuts = [("O", Bit)]
inps =
[ ("I", clk)
, ("CLR", clr)
, ("DIV", div0)
, ("CE", DSL.High)
, ("CEMASK", DSL.Low)
, ("CLRMASK", DSL.Low)
]
outs = [("O", bufgGtOut)]

DSL.compInBlock compName compInps compOuts
DSL.instDecl Empty (Id.unsafeMake compName) instLabel [] inps outs

pure [bufgGtOut]
go bbCtx = error ("unsafeBufgGt template:\n\n" <> ppShow bbCtx)
71 changes: 0 additions & 71 deletions bittide/src/Clash/Cores/Xilinx/GTH/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,11 +9,9 @@ module Clash.Cores.Xilinx.GTH.Internal where
import Clash.Explicit.Prelude

import Clash.Annotations.Primitive (
HDL (Verilog),
Primitive (InlineYamlPrimitive),
hasBlackBox,
)
import Clash.Annotations.SynthesisAttributes
import Data.String.Interpolate (__i)

import Clash.Cores.Xilinx.GTH.BlackBoxes
Expand Down Expand Up @@ -122,39 +120,6 @@ gthCore
)
#-}

{- | This mimics what PG182 calls the "[RX,TX] User Clocking Network Helper Block"
It has a hardcoded to do no division for @usrclk@ and divide by 2 for @usrclk2@.
So it'll only work when the external RX/TX GTH interfaces uses twice the width of the internal width.
See: https://docs.amd.com/r/en-US/pg182-gtwizard-ultrascale/Transmitter-User-Clocking-Network-Helper-Block-Ports
-}
gthUserClockNetwork ::
forall user user2.
(KnownDomain user, KnownDomain user2) =>
Clock user ->
Reset user2 ->
(Clock user, Clock user2, Signal user2 (BitVector 1))
gthUserClockNetwork clkIn rstIn =
(clk1, clk2, active)
where
rstIn1 :: Reset user
rstIn1 = unsafeSynchronizerReset clk2 clk1 rstIn
clk1 = bufgGt d0 clkIn rstIn1
clk2 :: Clock user2
clk2 = bufgGt d1 clkIn rstIn1
-- TODO: Use XPM syncer. Alternatively, instantiate Xilinx IP for this whole function
reg = annotate (StringAttr "ASYNC_REG" "TRUE" :> Nil) . register clk2 rstIn enableGen 0
active = reg $ reg (pure 1)
{-# NOINLINE gthUserClockNetwork #-}

unsafeSynchronizerReset ::
(KnownDomain dom1, KnownDomain dom2) =>
Clock dom1 ->
Clock dom2 ->
Reset dom1 ->
Reset dom2
unsafeSynchronizerReset clkIn clkOut rstIn = unsafeFromActiveHigh $ unsafeSynchronizer clkIn clkOut (unsafeToActiveHigh rstIn)

xilinxGthUserClockNetworkTx ::
forall user user2.
(KnownDomain user, KnownDomain user2) =>
Expand Down Expand Up @@ -213,39 +178,3 @@ ibufds_gte3 !_clk = clockGen
|]
)
#-}

{- | Clock Buffer Driven by Gigabit Transceiver. For more information see:
https://docs.xilinx.com/r/en-US/ug974-vivado-ultrascale-libraries/BUFG_GT
The actual divide value is the value provide in @SNat div@ plus 1.
So an @SNat 0@ gives you a division of 1
-}
bufgGt ::
(KnownDomain domIn, KnownDomain domOut, 0 <= div, div <= 7) =>
SNat div ->
Clock domIn ->
Reset domIn ->
Clock domOut
bufgGt = unsafeBufgGt

unsafeBufgGt ::
(KnownDomain domOut) => SNat div -> Clock domIn -> Reset domIn -> Clock domOut
unsafeBufgGt !_ !_ !_ = clockGen
{-# ANN unsafeBufgGt hasBlackBox #-}
{-# OPAQUE unsafeBufgGt #-}
{-# ANN
unsafeBufgGt
( let primName = 'unsafeBufgGt
tfName = 'unsafeBufgGtTF
in InlineYamlPrimitive
[Verilog]
[__i|
BlackBox:
name: #{primName}
kind: Declaration
format: Haskell
templateFunction: #{tfName}
|]
)
#-}

0 comments on commit 9ba7c19

Please sign in to comment.