Skip to content

Commit

Permalink
Fixes for changed names in 8b10b
Browse files Browse the repository at this point in the history
  • Loading branch information
jvnknvlgl committed Jul 1, 2024
1 parent 554658e commit cae2505
Show file tree
Hide file tree
Showing 6 changed files with 100 additions and 89 deletions.
13 changes: 6 additions & 7 deletions clash-cores/src/Clash/Cores/Sgmii.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Clash.Cores.Sgmii where

import Clash.Cores.LineCoding8b10b
import Clash.Cores.Sgmii.AutoNeg
import Clash.Cores.Sgmii.BitSlip
-- import Clash.Cores.Sgmii.BitSlip
import Clash.Cores.Sgmii.Common
import Clash.Cores.Sgmii.PcsReceive
import Clash.Cores.Sgmii.PcsTransmit
Expand All @@ -28,15 +28,14 @@ sgmiiCdc ::
Signal txDom Bool ->
Signal txDom (BitVector 8) ->
Signal rxDom (BitVector 10) ->
( Signal rxDom (Bool, Bool, BitVector 8, BitVector 10)
( Signal rxDom (Bool, Bool, BitVector 8)
, Signal txDom (BitVector 10)
)
sgmiiCdc autoNegCdc rxClk txClk rxRst txRst txEn txEr dw1 cg1 =
( bundle
( exposeClockResetEnable regMaybe rxClk rxRst enableGen False rxDv
, exposeClockResetEnable regMaybe rxClk rxRst enableGen False rxEr
, exposeClockResetEnable regMaybe rxClk rxRst enableGen 0 dw4
, cg2
)
, cg4
)
Expand Down Expand Up @@ -64,12 +63,12 @@ sgmiiCdc autoNegCdc rxClk txClk rxRst txRst txEn txEr dw1 cg1 =
pcsReceive' = exposeClockResetEnable pcsReceive

(cg3, rd, dw2, rxEven, syncStatus) =
unbundle $ sync' rxClk rxRst enableGen cg2
unbundle $ sync' rxClk rxRst enableGen cg1
where
sync' = exposeClockResetEnable sync

(cg2, _) = unbundle $ bitSlip' rxClk rxRst enableGen cg1
where
bitSlip' = exposeClockResetEnable bitSlip
-- (cg2, _) = unbundle $ bitSlip' rxClk rxRst enableGen cg1
-- where
-- bitSlip' = exposeClockResetEnable bitSlip

{-# CLASH_OPAQUE sgmiiCdc #-}
20 changes: 10 additions & 10 deletions clash-cores/src/Clash/Cores/Sgmii/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,50 +47,50 @@ data Xmit = Conf | Data | Idle

-- | Data word corresponding to the decoded version of code group D00.0, used
-- for early-end detection
dwD00_0 :: DataWord
dwD00_0 :: Symbol8b10b
dwD00_0 = Dw 0b00000000

-- | Data word corresponding to the decoded version of code group D02.2, used
-- for alternating configuration transmission
dwD02_2 :: DataWord
dwD02_2 :: Symbol8b10b
dwD02_2 = Dw 0b01000010

-- | Data word corresponding to the decoded version of code group D05.6, used
-- for correcting idle transmission
dwD05_6 :: DataWord
dwD05_6 :: Symbol8b10b
dwD05_6 = Dw 0b11000101

-- | Data word corresponding to the decoded version of code group D16.2, used
-- for preserving idle transmission
dwD16_2 :: DataWord
dwD16_2 :: Symbol8b10b
dwD16_2 = Dw 0b01010000

-- | Data word corresponding to the decoded version of code group D21.5, used
-- for alternating configuration transmission
dwD21_5 :: DataWord
dwD21_5 :: Symbol8b10b
dwD21_5 = Dw 0b10110101

-- | Data word corresponding to the decoded version of code group K28.5, the
-- most commonly used comma value
cwK28_5 :: DataWord
cwK28_5 :: Symbol8b10b
cwK28_5 = Cw 0b10111100

-- | Data word corresponding to the decoded version of code group K23.7, used
-- for encapsulation of @Carrier_Extend@ (/R/)
cwR :: DataWord
cwR :: Symbol8b10b
cwR = Cw 0b11110111

-- | Data word corresponding to the decoded version of code group K27.7, used
-- for encapsulation of @Start_of_Packet@ (/S/)
cwS :: DataWord
cwS :: Symbol8b10b
cwS = Cw 0b11111011

-- | Data word corresponding to the decoded version of code group D29.7, used
-- for encapsulation of @End_of_Packet@ (/T/)
cwT :: DataWord
cwT :: Symbol8b10b
cwT = Cw 0b11111101

-- | Data word corresponding to the decoded version of code group K30.7, used
-- for encapsulation of @Error_Propagation@ (/V/)
cwV :: DataWord
cwV :: Symbol8b10b
cwV = Cw 0b11111110
32 changes: 22 additions & 10 deletions clash-cores/src/Clash/Cores/Sgmii/PcsReceive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,13 @@ data PcsReceiveState
| WaitForK {_rx :: Bool, _xmit :: Xmit}
| RxK {_rx :: Bool, _xmit :: Xmit}
| RxCB {_rx :: Bool, _xmit :: Xmit}
| RxCC {_rx :: Bool, _xmit :: Xmit, _hist :: DataWord}
| RxCD {_rx :: Bool, _xmit :: Xmit, _hist :: DataWord, _rxConfReg :: ConfReg}
| RxCC {_rx :: Bool, _xmit :: Xmit, _hist :: Symbol8b10b}
| RxCD
{ _rx :: Bool
, _xmit :: Xmit
, _hist :: Symbol8b10b
, _rxConfReg :: ConfReg
}
| RxInvalid {_rx :: Bool, _xmit :: Xmit}
| IdleD {_rx :: Bool, _xmit :: Xmit}
| FalseCarrier {_rx :: Bool, _xmit :: Xmit}
Expand All @@ -45,8 +50,8 @@ data PcsReceiveState
| PacketBurstRrs {_rx :: Bool, _xmit :: Xmit}
| ExtendErr {_rx :: Bool, _xmit :: Xmit}
| EarlyEndExt {_rx :: Bool, _xmit :: Xmit}
| RxData {_rx :: Bool, _xmit :: Xmit, _hist :: DataWord}
| RxDataError {_rx :: Bool, _xmit :: Xmit, _hist :: DataWord}
| RxData {_rx :: Bool, _xmit :: Xmit, _hist :: Symbol8b10b}
| RxDataError {_rx :: Bool, _xmit :: Xmit, _hist :: Symbol8b10b}
| LinkFailed {_rx :: Bool, _xmit :: Xmit}
deriving (Generic, NFDataX, Eq, Show)

Expand Down Expand Up @@ -103,7 +108,7 @@ carrierDetect cg rd rxEven
-- check whether they correspond to one of the specified end conditions
checkEnd ::
-- | Current and next 2 data words
Vec 3 DataWord ->
Vec 3 Symbol8b10b ->
-- | End condition
Maybe CheckEnd
checkEnd dws
Expand All @@ -128,13 +133,13 @@ pcsReceiveT ::
PcsReceiveState ->
-- | Input values, where @Vec 3 CodeGroup@ contains the current and next two
-- | data words
(BitVector 10, Bool, Vec 3 DataWord, Even, SyncStatus, Maybe Xmit) ->
(BitVector 10, Bool, Vec 3 Symbol8b10b, Even, SyncStatus, Maybe Xmit) ->
-- | Tuple with the new state and the output values
( PcsReceiveState
, ( PcsReceiveState
, Maybe Bool
, Maybe Bool
, Maybe DataWord
, Maybe Symbol8b10b
, Maybe Rudi
, Maybe ConfReg
)
Expand Down Expand Up @@ -460,16 +465,23 @@ pcsReceive ::
Signal dom (BitVector 10) ->
-- | Current running disparity from 'Sgmii.sync'
Signal dom Bool ->
-- | Input 'DataWord' from 'Sgmii.sync'
Signal dom (Vec 3 DataWord) ->
-- | Input 'Symbol8b10b' from 'Sgmii.sync'
Signal dom (Vec 3 Symbol8b10b) ->
-- | The 'Even' value from 'Sgmii.sync'
Signal dom Even ->
-- | The current 'SyncStatus' from 'Sgmii.sync'
Signal dom SyncStatus ->
-- | The 'Xmit' signal from 'Sgmii.autoNeg'
Signal dom (Maybe Xmit) ->
-- | Tuple containing the output values
Signal dom (Maybe Bool, Maybe Bool, Maybe DataWord, Maybe Rudi, Maybe ConfReg)
Signal
dom
( Maybe Bool
, Maybe Bool
, Maybe Symbol8b10b
, Maybe Rudi
, Maybe ConfReg
)
pcsReceive cg rd dw1 rxEven syncStatus xmit =
bundle (rxDv, rxEr, dw2, rudi, rxConfReg)
where
Expand Down
Loading

0 comments on commit cae2505

Please sign in to comment.