Skip to content

Commit

Permalink
Remove reverseBV from BitSlip
Browse files Browse the repository at this point in the history
  • Loading branch information
jvnknvlgl committed Aug 26, 2024
1 parent 336724e commit d14276b
Show file tree
Hide file tree
Showing 4 changed files with 27 additions and 29 deletions.
30 changes: 16 additions & 14 deletions clash-cores/src/Clash/Cores/Sgmii/BitSlip.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,11 +27,11 @@ import Data.Maybe (fromJust)
-- for 'BSFail'.
data BitSlipState
= BSFail
{ _rx :: BitVector 20
{ _rx :: (CodeGroup, CodeGroup)
, _commaLocs :: Vec 8 (Index 10)
, _hist :: Vec 10 (BitVector 10)
, _hist :: Vec 10 CodeGroup
}
| BSOk {_rx :: BitVector 20, _commaLoc :: Index 10}
| BSOk {_rx :: (CodeGroup, CodeGroup), _commaLoc :: Index 10}
deriving (Generic, NFDataX, Show)

-- | State transition function for 'bitSlip', where the initial state is the
Expand All @@ -46,20 +46,22 @@ bitSlipT ::
-- | New state
BitSlipState
bitSlipT BSFail{..} (cg, _)
| Just i <- n, _commaLocs == repeat (fromJust n) = BSOk rx i
| otherwise = BSFail rx ns hist
| Just i <- commaLoc, _commaLocs == repeat (fromJust commaLoc) = BSOk rx i
| otherwise = BSFail rx commaLocs hist
where
rx = resize $ _rx ++# reverseBV cg
ns = maybe _commaLocs (_commaLocs <<+) n
hist = map pack $ take d10 $ windows1d d10 $ bv2v rx
n = elemIndex True $ map f _hist
rx = (snd _rx, cg)
commaLocs = maybe _commaLocs (_commaLocs <<+) commaLoc

hist = map pack b
where
f a = a == reverseBV cgK28_5N || a == reverseBV cgK28_5P
b = take d10 (windows1d d10 (bitCoerce rx)) :: (Vec 10 (Vec 10 Bit))

commaLoc = elemIndex True $ map (`elem` commas) _hist
bitSlipT BSOk{..} (cg, syncStatus)
| syncStatus == Fail = BSFail rx (repeat _commaLoc) (repeat 0)
| otherwise = BSOk rx _commaLoc
where
rx = resize $ _rx ++# reverseBV cg
rx = (snd _rx, cg)

-- | Output function for 'bitSlip' that takes the calculated index value and
-- rotates the state vector to create the new output value, or outputs the
Expand All @@ -69,9 +71,9 @@ bitSlipO ::
BitSlipState ->
-- | New output value
(BitSlipState, BitVector 10, Status)
bitSlipO s = (s, reverseBV $ resize $ rotateR (_rx s) (10 - n), bsStatus)
bitSlipO s = (s, resize (rotateR (pack (_rx s)) (10 - commaLoc)), bsStatus)
where
(n, bsStatus) = case s of
(commaLoc, bsStatus) = case s of
BSFail{} -> (fromEnum $ last (_commaLocs s), Fail)
BSOk{} -> (fromEnum $ _commaLoc s, Ok)

Expand All @@ -93,7 +95,7 @@ bitSlip cg1 syncStatus = (register 0 cg2, register Fail bsStatus)
mooreB
bitSlipT
bitSlipO
(BSFail 0 (repeat 0) (repeat 0))
(BSFail (0, 0) (repeat 0) (repeat 0))
(cg1, syncStatus)

{-# CLASH_OPAQUE bitSlip #-}
14 changes: 10 additions & 4 deletions clash-cores/src/Clash/Cores/Sgmii/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,10 +78,6 @@ orNothing :: Bool -> a -> Maybe a
orNothing True a = Just a
orNothing False _ = Nothing

-- | Reverse the bits of a 'BitVector'
reverseBV :: (KnownNat n) => BitVector n -> BitVector n
reverseBV = v2bv . reverse . bv2v

-- | Code group that corresponds to K28.5 with negative disparity
cgK28_5N :: CodeGroup
cgK28_5N = 0b0101111100
Expand All @@ -90,6 +86,16 @@ cgK28_5N = 0b0101111100
cgK28_5P :: CodeGroup
cgK28_5P = 0b1010000011

-- | Vector containing the two alternative forms (with opposite running
-- disparity) of K28.5. This is the only relevant comma, as the other commas
-- are set as "reserved" in the list of control words. The order of the commas
-- in this is important, as the first comma returns the negative running
-- disparity when it is decoded and the second comma returns the positive
-- running disparity when it is decoded. This is used in 'Sync.LossOfSync' to
-- recover the correct running disparity from a received comma.
commas :: Vec 2 CodeGroup
commas = cgK28_5N :> cgK28_5P :> Nil

-- | Data word corresponding to the decoded version of code group D00.0, used
-- for early-end detection
dwD00_0 :: Symbol8b10b
Expand Down
10 changes: 0 additions & 10 deletions clash-cores/src/Clash/Cores/Sgmii/Sync.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,16 +58,6 @@ data SyncState
}
deriving (Generic, NFDataX, Show)

-- | Vector containing the two alternative forms (with opposite running
-- disparity) of K28.5. This is the only relevant comma, as the other commas
-- are set as "reserved" in the list of control words. The order of the commas
-- in this is important, as the first comma returns the negative running
-- disparity when it is decoded and the second comma returns the positive
-- running disparity when it is decoded. This is used in 'LossOfSync' to
-- recover the correct running disparity from a received comma.
commas :: Vec 2 CodeGroup
commas = cgK28_5N :> cgK28_5P :> Nil

-- | State transition function for 'sync'. Takes the state as defined in
-- 'SyncState', a the new incoming code group from the deserialization block
-- and returns the next state as defined in Clause 36 of IEEE 802.3. As is
Expand Down
2 changes: 1 addition & 1 deletion clash-cores/test/Test/Cores/Sgmii/BitSlip.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ bitSlipSim cg =
C.mooreB
bitSlipT
bitSlipO
(BSFail 0 (C.repeat 0) (C.repeat 0))
(BSFail (0, 0) (C.repeat 0) (C.repeat 0))
(cg, pure Ok)

-- | Check that if 'bitSlip' moves into 'BSOk', the index is non-zero as it
Expand Down

0 comments on commit d14276b

Please sign in to comment.