Skip to content

Commit

Permalink
Apply reviewer comments
Browse files Browse the repository at this point in the history
  • Loading branch information
lmbollen committed Apr 23, 2024
1 parent 652e4b4 commit b5b84e7
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 48 deletions.
40 changes: 20 additions & 20 deletions clash-cores/src/Clash/Cores/Xilinx/Ethernet/Gmii.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,3 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fconstraint-solver-iterations=10 #-}
{-|
Copyright : (C) 2024, Google LLC
License : BSD2 (see the file LICENSE)
Expand All @@ -11,6 +7,12 @@
"LogiCORE IP Ethernet 1000BASE-X PCS/PMA or SGMII"
-}

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fconstraint-solver-iterations=10 #-}

module Clash.Cores.Xilinx.Ethernet.Gmii where

import Clash.Explicit.Prelude
Expand Down Expand Up @@ -40,23 +42,22 @@ gmiiSgmiiBridge ::
DiffClock sgmii625 ->
-- | Asynchronous reset for the bridge.
Reset asyncDom ->
-- | Link speed configuration.
Signal gmiiRx125 LinkSpeed ->
-- | Signal detect from the Phy.
Signal asyncDom SignalDetect ->
-- | 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.
Signal asyncDom Bool ->
-- | Configuration for the bridge.
Signal gmiiRx125 Config ->
-- | Auto negotiation configuration for the bridge.
Signal gmiiRx125 AutoNegConfig ->
-- | Restart auto negotiation.
Signal gmiiRx125 RestartAutoNeg ->
Signal gmiiRx125 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{..}
gmiiSgmiiBridge refClk refRst signalDetect bridgeConfig anConfig anRestart lvdsIn gmiiTx = BridgeOutput{..}
where
( lvdsOutP
, lvdsOutN
Expand All @@ -66,9 +67,9 @@ gmiiSgmiiBridge refClk refRst cLinkSpeed signalDetect bridgeConfig anConfig anRe
, bridgeClk125
, activeHighRxRst
, fmap fromStatusVector -> bridgeStatusVector
) = gmiiSgmiiBridgeBb clockP clockN activeHighRefRst (getSpeed100 <$> cLinkSpeed)
(getSpeed10_100 <$> cLinkSpeed) signalDetect (toConfigVector <$> bridgeConfig)
anConfig anRestart lvdsInP lvdsInN gmiiTxD gmiiTxEn gmiiTxEr
) = gmiiSgmiiBridgeBb clockP clockN activeHighRefRst signalDetect
(toConfigVector <$> bridgeConfig) anConfig anRestart lvdsInP lvdsInN gmiiTxD
gmiiTxEn gmiiTxEr

activeHighRefRst = unsafeToActiveHigh refRst
bridgeRst125 = unsafeFromActiveHigh activeHighRxRst
Expand All @@ -86,19 +87,17 @@ gmiiSgmiiBridgeBb ::
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 ->
-- Either connect to the Phy's signal detect or use a constant 'True`,
-- otherwise the link will never come up.
Signal asyncDom Bool ->
-- | Configuration for the bridge.
Signal gmiiRx125 ConfigVector ->
-- | Auto negotiation configuration for the bridge.
Signal gmiiRx125 AutoNegConfig ->

-- | Restart auto negotiation.
Signal gmiiRx125 RestartAutoNeg ->
Signal gmiiRx125 Bool ->
-- | P channel of the LVDS input from the Phy.
Signal sgmii625 Bit ->
-- | N channel of the LVDS input from the Phy.
Expand Down Expand Up @@ -128,7 +127,8 @@ gmiiSgmiiBridgeBb ::
, Signal gmiiRx125 StatusVector
)

gmiiSgmiiBridgeBb !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ =
-- Can't use `deepErrorX' because one of the results is a clock.
gmiiSgmiiBridgeBb !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ !_ =
(undefined, undefined, undefined, undefined, undefined, undefined, undefined, undefined)

{-# OPAQUE gmiiSgmiiBridgeBb #-}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,6 @@ veriBinaryPrim =
smiiClkP :<
smiiClkN :<
rst :<
speed100 :<
speed10_100 :<
signalDetect :<
pmaConfig :<
pmaAnAdvancedConfig :<
Expand Down Expand Up @@ -59,8 +57,8 @@ veriBinaryPrim =
.refclk625_p(~ARG[#{smiiClkP}]),
.refclk625_n(~ARG[#{smiiClkN}]),
.reset(~ARG[#{rst}]),
.speed_is_100(~ARG[#{speed100}]),
.speed_is_10_100(~ARG[#{speed10_100}]),
.speed_is_100(0),
.speed_is_10_100(0),
.signal_detect(~ARG[#{signalDetect}]),
.configuration_vector(~ARG[#{pmaConfig}]),
.an_adv_config_vector(~ARG[#{pmaAnAdvancedConfig}]),
Expand Down Expand Up @@ -100,7 +98,7 @@ veriBinaryPrim =
binaryTclTF :: TemplateFunction
binaryTclTF = TemplateFunction used valid tclTemplate
where
used = [0..13] -- use all arguments
used = [0..11] -- use all arguments
valid = const True -- There are no configuration options to check

tclTemplate :: Backend s => BlackBoxContext -> State s Doc
Expand Down
26 changes: 3 additions & 23 deletions clash-cores/src/Clash/Cores/Xilinx/Ethernet/Gmii/Types.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,16 @@
-- | Contains the types used in the implementation of the GMII to SGMII bridge wrapper.
-- LogiCORE IP Ethernet 1000BASE-X PCS/PMA or SGMII

{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fconstraint-solver-iterations=10 #-}
{-# LANGUAGE RecordWildCards #-}
-- | Contains the types used in the implementation of the GMII to SGMII bridge wrapper.
-- LogiCORE IP Ethernet 1000BASE-X PCS/PMA or SGMII
module Clash.Cores.Xilinx.Ethernet.Gmii.Types where

import Clash.Prelude

data Lvds = Lvds{lvdsP :: Bit, lvdsN :: Bit}
deriving (Generic, NFDataX, BitPack)

type Speed_10_100 = Bool
type Speed_100 = Bool

-- TODO: Incorporate in 'Clash.Prelude'?
-- | Gets time in 'Picoseconds' from time in 'Nanoseconds'.
type Nanoseconds (ns :: Nat) = Picoseconds (1000 * ns)
Expand All @@ -28,31 +26,13 @@ data Gmii = Gmii
, gmiiError :: Bit
} deriving (Generic, BitPack, NFDataX)

type SignalDetect = Bool
type RestartAutoNeg = Bool
type ConfigValid = Bool
type BridgeAnConfigValid = Bool
type MdioAddr = BitVector 5

data DuplexMode = HalfDuplex | FullDuplex
deriving (Generic, NFDataX, BitPack, Eq)

-- | Link speeds in Mega bits per second.
data LinkSpeed = Speed10 | Speed100 | Speed1000
deriving (Generic, NFDataX, BitPack)

getSpeed100 :: LinkSpeed -> Speed_100
getSpeed100 = \case
Speed10 -> False
Speed100 -> True
Speed1000 -> False

getSpeed10_100 :: LinkSpeed -> Speed_10_100
getSpeed10_100 = \case
Speed10 -> True
Speed100 -> True
Speed1000 -> False

-- | Whether the link partner supports pause frames.
data Pause = NoPause | SymmetricPause | AsymmetricPause | SymmetricAsymmetricPause
deriving (Generic, NFDataX, BitPack)
Expand Down

0 comments on commit b5b84e7

Please sign in to comment.