Skip to content

Commit

Permalink
Apply reviewer comments
Browse files Browse the repository at this point in the history
  • Loading branch information
lmbollen committed Jun 14, 2024
1 parent 652e4b4 commit a8cdb95
Show file tree
Hide file tree
Showing 8 changed files with 521 additions and 424 deletions.

This file was deleted.

5 changes: 3 additions & 2 deletions clash-cores/clash-cores.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -142,8 +142,7 @@ library
Clash.Cores.Xilinx.Floating.Explicit
Clash.Cores.Xilinx.Floating.Internal
Clash.Cores.Xilinx.Ethernet.Gmii
Clash.Cores.Xilinx.Ethernet.Gmii.BlackBoxes
Clash.Cores.Xilinx.Ethernet.Gmii.Types
Clash.Cores.Xilinx.Ethernet.Gmii.Internal
Clash.Cores.Xilinx.Ila
Clash.Cores.Xilinx.Ila.Internal
Clash.Cores.Xilinx.Internal
Expand Down Expand Up @@ -199,6 +198,7 @@ test-suite unittests
Test.Cores.Xilinx.BlockRam
Test.Cores.Xilinx.DcFifo
Test.Cores.Xilinx.DnaPortE2
Test.Cores.Xilinx.Ethernet.Gmii

build-depends:
clash-cores,
Expand All @@ -210,6 +210,7 @@ test-suite unittests
tasty-quickcheck,
tasty-th,
hedgehog,
HUnit,
tasty-hedgehog >= 1.2.0,
infinite-list

Expand Down
187 changes: 78 additions & 109 deletions clash-cores/src/Clash/Cores/Xilinx/Ethernet/Gmii.hs
Original file line number Diff line number Diff line change
@@ -1,136 +1,105 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fconstraint-solver-iterations=10 #-}
{-|
Copyright : (C) 2024, Google LLC
License : BSD2 (see the file LICENSE)
Maintainer : QBayLogic B.V. <devops@qbaylogic.com>
Contains a wrapper for the Xilinx GMII to SGMII PMA core :
"LogiCORE IP Ethernet 1000BASE-X PCS/PMA or SGMII"
https://www.xilinx.com/xsw/gig_ethernet_pcs_pma
-}
module Clash.Cores.Xilinx.Ethernet.Gmii where

import Clash.Explicit.Prelude
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}

module Clash.Cores.Xilinx.Ethernet.Gmii
(
--- Types
AutoNegConfig(..),
BridgeOutput(..),
Config(..),
DuplexMode(..),
Gmii(..),
LinkSpeed(..),
Lvds(..),
Nanoseconds,
Pause(..),
Picoseconds,
Status(..),

--- Gmii to Sgmii bridge
gmiiSgmiiBridge,
)
where

import Clash.Annotations.Primitive
import Clash.Cores.Xilinx.Ethernet.Gmii.BlackBoxes
import Clash.Cores.Xilinx.Ethernet.Gmii.Types
import Clash.Explicit.Prelude
import Clash.Signal.Internal(ClockN, DiffClock(..))

-- | Wrapper for the LogiCORE IP Ethernet 1000BASE-X PCS/PMA or SGMII.
-- Configured to function as a GMII to SGMII bridge.
import Clash.Cores.Xilinx.Ethernet.Gmii.Internal
import Clash.Signal.Internal (DiffClock(..))

-- | A subset of the relevant output signals of the GMII to SGMII bridge
data BridgeOutput gmii125 sgmii625 = BridgeOutput
{ bridgeLvdsOut :: Signal sgmii625 Lvds
, bridgeGmiiRx :: Signal gmii125 Gmii
, bridgeClk125 :: Clock gmii125
, bridgeRst125 :: Reset gmii125
, bridgeStatus :: Signal gmii125 Status
}

-- | Wrapper for the LogiCORE IP Ethernet 1000BASE-X PCS/PMA or SGMII,
-- configured to function as a GMII to SGMII bridge.
gmiiSgmiiBridge ::
forall asyncDom sgmii625 gmiiRx125 gmiiTx125 .
( KnownDomain asyncDom
, KnownDomain sgmii625
, KnownDomain gmiiRx125
, KnownDomain gmiiTx125
forall sgmii625 gmii125 .
( KnownDomain sgmii625
, KnownDomain gmii125
, DomainPeriod sgmii625 ~ Picoseconds 1600
, DomainPeriod gmiiRx125 ~ Nanoseconds 8
, DomainPeriod gmiiTx125 ~ Nanoseconds 8
, DomainActiveEdge sgmii625 ~ Rising
, DomainActiveEdge gmiiRx125 ~ Rising
, DomainActiveEdge gmiiTx125 ~ Rising
, DomainPeriod gmii125 ~ Nanoseconds 8
, DomainActiveEdge sgmii625 ~ 'Rising
, DomainActiveEdge gmii125 ~ 'Rising
, HasAsynchronousReset sgmii625
, HasSynchronousReset gmii125
, DomainResetPolarity sgmii625 ~ 'ActiveHigh
, DomainResetPolarity gmii125 ~ 'ActiveHigh
) =>
-- | Reference clock coming from the Phy.
-- | Reference clock coming from the PHY
DiffClock sgmii625 ->
-- | Asynchronous reset for the bridge.
Reset asyncDom ->
-- | Link speed configuration.
Signal gmiiRx125 LinkSpeed ->
-- | Signal detect from the Phy.
Signal asyncDom SignalDetect ->
-- | Configuration for the bridge.
Signal gmiiRx125 Config ->
-- | Auto negotiation configuration for the bridge.
Signal gmiiRx125 AutoNegConfig ->
-- | Restart auto negotiation.
Signal gmiiRx125 RestartAutoNeg ->
-- | LVDS input from the Phy.
-- | Asynchronous reset for the bridge
Reset sgmii625 ->
-- | Signal detect from the PHY. Either connect to the PHY's signal detect or use
-- a constant @True@, otherwise the link will never come up. The IP core considers this
-- an asynchronous signal, so synchronisation logic is not needed.
Signal sgmii625 Bool ->
-- | Configuration for the bridge
Signal gmii125 Config ->
-- | Auto negotiation configuration for the bridge
Signal gmii125 AutoNegConfig ->
-- | Restart auto negotiation
Signal gmii125 Bool ->
-- | LVDS input from the PHY
Signal sgmii625 Lvds ->
-- | GMII input from the MAC.
Signal gmiiTx125 Gmii ->
-- | Output record, see 'BridgeOutput'.
BridgeOutput gmiiRx125 sgmii625
gmiiSgmiiBridge refClk refRst cLinkSpeed signalDetect bridgeConfig anConfig anRestart lvdsIn gmiiTx = BridgeOutput{..}
-- | GMII input from the MAC
Signal gmii125 Gmii ->
-- | Output record, see @BridgeOutput@
BridgeOutput gmii125 sgmii625
gmiiSgmiiBridge refClk refRst signalDetect bridgeConfig anConfig anRestart lvdsIn gmiiTx = BridgeOutput{..}
where
( lvdsOutP
( bridgeClk125
, activeHighRxRst
, lvdsOutP
, lvdsOutN
, gmiiRxD
, gmiiRxDv
, gmiiRxEr
, bridgeClk125
, activeHighRxRst
, fmap fromStatusVector -> bridgeStatusVector
) = gmiiSgmiiBridgeBb clockP clockN activeHighRefRst (getSpeed100 <$> cLinkSpeed)
(getSpeed10_100 <$> cLinkSpeed) signalDetect (toConfigVector <$> bridgeConfig)
anConfig anRestart lvdsInP lvdsInN gmiiTxD gmiiTxEn gmiiTxEr
, fmap fromStatusVector -> bridgeStatus
) = gmiiSgmiiBridgePrim clockP clockN refRst signalDetect bridgeConfig
(toAutoNegConfigVector <$> anConfig) anRestart lvdsInP lvdsInN gmiiTxD gmiiTxEn
gmiiTxEr

activeHighRefRst = unsafeToActiveHigh refRst
bridgeRst125 = unsafeFromActiveHigh activeHighRxRst
bridgeLvdsOut = Lvds <$> lvdsOutP <*> lvdsOutN
(DiffClock clockP clockN) = refClk
(lvdsInP, lvdsInN) = (fmap lvdsP lvdsIn, fmap lvdsN lvdsIn)
(gmiiTxD, gmiiTxEn, gmiiTxEr) = unbundle $ fmap (\Gmii{..} -> (gmiiData, gmiiValid, gmiiError)) gmiiTx
lvdsInP = pChannel <$> lvdsIn
lvdsInN = nChannel <$> lvdsIn
gmiiTxD = gmiiData <$> gmiiTx
gmiiTxEn = gmiiValid <$> gmiiTx
gmiiTxEr = gmiiError <$> gmiiTx
bridgeGmiiRx = Gmii <$> gmiiRxD <*> gmiiRxDv <*> gmiiRxEr

-- | Black box for the GMII to SGMII bridge.
gmiiSgmiiBridgeBb ::
-- | P channel of the reference clock coming from the Phy.
Clock sgmii625 ->
-- | N channel of the reference clock coming from the Phy.
ClockN sgmii625 ->
-- | Asynchronous active high reset for the bridge.
Signal asyncDom Bool->
-- | Whether the link should be configured for 100 Mbit/s.
Signal gmiiRx125 Speed_100 ->
-- | Whether the link should be configured for 10 or 100 Mbit/s.
Signal gmiiRx125 Speed_10_100 ->
-- | Signal detect from the Phy.
Signal asyncDom SignalDetect ->
-- | Configuration for the bridge.
Signal gmiiRx125 ConfigVector ->
-- | Auto negotiation configuration for the bridge.
Signal gmiiRx125 AutoNegConfig ->

-- | Restart auto negotiation.
Signal gmiiRx125 RestartAutoNeg ->
-- | P channel of the LVDS input from the Phy.
Signal sgmii625 Bit ->
-- | N channel of the LVDS input from the Phy.
Signal sgmii625 Bit ->
-- | GMII data input from the MAC.
Signal gmiiTx125 (BitVector 8) ->
-- | GMII valid input from the MAC.
Signal gmiiTx125 Bit ->
-- | GMII error input from the MAC.
Signal gmiiTx125 Bit ->
-- |
-- 1. P channel of the LVDS output to the Phy.
-- 2. N channel of the LVDS output to the Phy.
-- 3. GMII data output to the MAC.
-- 4. GMII valid output to the MAC.
-- 5. GMII error output to the MAC.
-- 6. Clock output for the 125 MHz domain.
-- 7. Active high reset output for the 125 MHz domain.
-- 8. Status vector.
( Signal sgmii625 Bit
, Signal sgmii625 Bit
, Signal gmiiRx125 (BitVector 8)
, Signal gmiiRx125 Bit
, Signal gmiiRx125 Bit
, Clock gmiiRx125
, Signal gmiiRx125 Bool
, Signal gmiiRx125 StatusVector
)

gmiiSgmiiBridgeBb !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ =
(undefined, undefined, undefined, undefined, undefined, undefined, undefined, undefined)

{-# OPAQUE gmiiSgmiiBridgeBb #-}
{-# ANN gmiiSgmiiBridgeBb hasBlackBox #-}
{-# ANN gmiiSgmiiBridgeBb (veriBinaryPrim) #-}
131 changes: 0 additions & 131 deletions clash-cores/src/Clash/Cores/Xilinx/Ethernet/Gmii/BlackBoxes.hs

This file was deleted.

Loading

0 comments on commit a8cdb95

Please sign in to comment.