Skip to content

Commit

Permalink
Explicitly make sync a Moore machine
Browse files Browse the repository at this point in the history
  • Loading branch information
jvnknvlgl committed Jun 21, 2024
1 parent d56b3a9 commit 90f4649
Show file tree
Hide file tree
Showing 2 changed files with 44 additions and 59 deletions.
95 changes: 40 additions & 55 deletions clash-cores/src/Clash/Cores/Sgmii/Sync.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}

Expand Down Expand Up @@ -95,16 +96,15 @@ commas =

-- | State transition function for 'sync'. Takes the state as defined in
-- 'SyncState', a the new incoming code group from the SerDes-block and
-- returns a tuple containing the next state and the outputs as defined in
-- Clause 36 of IEEE 802.3
-- returns the next state as defined in Clause 36 of IEEE 802.3.
syncT ::
-- | Current state
SyncState ->
-- | New input codegroup
BitVector 10 ->
-- | New state and output tuple
(SyncState, (SyncState, BitVector 10, Bool, DataWord, Even, SyncStatus))
syncT self@LossOfSync{..} cg = (nextState, out)
SyncState
syncT LossOfSync{..} cg = nextState
where
nextState
| cg `notElem` commas = LossOfSync cg rd dw rxEven
Expand All @@ -113,10 +113,7 @@ syncT self@LossOfSync{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Fail

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@CommaDetect1{..} cg = (nextState, out)
syncT CommaDetect1{..} cg = nextState
where
nextState
| not (isDw dw) = LossOfSync cg rd dw rxEven
Expand All @@ -125,10 +122,7 @@ syncT self@CommaDetect1{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = Even
syncStatus = Fail

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@AcquireSync1{..} cg = (nextState, out)
syncT AcquireSync1{..} cg = nextState
where
nextState
| not (isValidDw dw) = LossOfSync cg rd dw rxEven
Expand All @@ -139,10 +133,7 @@ syncT self@AcquireSync1{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Fail

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@CommaDetect2{..} cg = (nextState, out)
syncT CommaDetect2{..} cg = nextState
where
nextState
| not (isDw dw) = LossOfSync cg rd dw rxEven
Expand All @@ -151,10 +142,7 @@ syncT self@CommaDetect2{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = Even
syncStatus = Fail

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@AcquireSync2{..} cg = (nextState, out)
syncT AcquireSync2{..} cg = nextState
where
nextState
| not (isValidDw dw) = LossOfSync cg rd dw rxEven
Expand All @@ -165,10 +153,7 @@ syncT self@AcquireSync2{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Fail

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@CommaDetect3{..} cg = (nextState, out)
syncT CommaDetect3{..} cg = nextState
where
nextState
| not (isDw dw) = LossOfSync cg rd dw rxEven
Expand All @@ -177,10 +162,7 @@ syncT self@CommaDetect3{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = Even
syncStatus = Fail

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@SyncAcquired1{..} cg = (nextState, out)
syncT SyncAcquired1{..} cg = nextState
where
nextState
| not (isValidDw dw) = SyncAcquired2 cg rd dw rxEven
Expand All @@ -191,10 +173,7 @@ syncT self@SyncAcquired1{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Ok

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@SyncAcquired2{..} cg = (nextState, out)
syncT SyncAcquired2{..} cg = nextState
where
nextState
| not (isValidDw dw) = SyncAcquired3 cg rd dw rxEven
Expand All @@ -205,11 +184,8 @@ syncT self@SyncAcquired2{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Ok
goodCgs = 0

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@SyncAcquired2A{..} cg = (nextState, out)
syncT SyncAcquired2A{..} cg = nextState
where
nextState
| not (isValidDw dw) = SyncAcquired3 cg rd dw rxEven
Expand All @@ -224,11 +200,8 @@ syncT self@SyncAcquired2A{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Ok
goodCgs = _goodCgs + 1

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@SyncAcquired3{..} cg = (nextState, out)
syncT SyncAcquired3{..} cg = nextState
where
nextState
| not (isValidDw dw) = SyncAcquired4 cg rd dw rxEven
Expand All @@ -239,11 +212,8 @@ syncT self@SyncAcquired3{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Ok
goodCgs = 0

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@SyncAcquired3A{..} cg = (nextState, out)
syncT SyncAcquired3A{..} cg = nextState
where
nextState
| not (isValidDw dw) = SyncAcquired4 cg rd dw rxEven
Expand All @@ -258,11 +228,8 @@ syncT self@SyncAcquired3A{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Ok
goodCgs = _goodCgs + 1

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@SyncAcquired4{..} cg = (nextState, out)
syncT SyncAcquired4{..} cg = nextState
where
nextState
| not (isValidDw dw) = LossOfSync cg rd dw rxEven
Expand All @@ -273,11 +240,8 @@ syncT self@SyncAcquired4{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Ok
goodCgs = 0

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
syncT self@SyncAcquired4A{..} cg = (nextState, out)
syncT SyncAcquired4A{..} cg = nextState
where
nextState
| not (isValidDw dw) = LossOfSync cg rd dw rxEven
Expand All @@ -292,10 +256,31 @@ syncT self@SyncAcquired4A{..} cg = (nextState, out)

(rd, dw) = ebTbDecode _rd cg
rxEven = nextEven _rxEven
syncStatus = Ok
goodCgs = _goodCgs + 1

out = (self, _cg, _rd, _dw, rxEven, syncStatus)
-- | Output function for 'sync'. Takes the state as defined in 'SyncState' and
-- returns a tuple containing the outputs as defined in Clause 36 of IEEE
-- 802.3
syncO ::
-- | Current state
SyncState ->
-- | New state and output tuple
(SyncState, BitVector 10, Bool, DataWord, Even, SyncStatus)
syncO self@LossOfSync{..} = (self, _cg, _rd, _dw, rxEven, Fail)
where
rxEven = nextEven _rxEven
syncO self@CommaDetect1{..} = (self, _cg, _rd, _dw, Even, Fail)
syncO self@AcquireSync1{..} = (self, _cg, _rd, _dw, rxEven, Fail)
where
rxEven = nextEven _rxEven
syncO self@CommaDetect2{..} = (self, _cg, _rd, _dw, Even, Fail)
syncO self@AcquireSync2{..} = (self, _cg, _rd, _dw, rxEven, Fail)
where
rxEven = nextEven _rxEven
syncO self@CommaDetect3{..} = (self, _cg, _rd, _dw, Even, Fail)
syncO self = (self, self._cg, self._rd, self._dw, rxEven, Ok)
where
rxEven = nextEven self._rxEven

-- | Transition function for the inputs of 'Sgmii.pcsReceive'. This is used to
-- keep a small list of "future" values for 'DataWord', such that these can
Expand Down Expand Up @@ -342,4 +327,4 @@ sync cg1 = out
$ bundle (cg2, rd, dw, rxEven, syncStatus)

(_, cg2, rd, dw, rxEven, syncStatus) =
mealyB syncT (LossOfSync 0 False (Dw 0) Even) cg1
mooreB syncT syncO (LossOfSync 0 False (Dw 0) Even) cg1
8 changes: 4 additions & 4 deletions clash-cores/test/Test/Cores/Sgmii/Sgmii.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,14 +50,14 @@ syncSim ::
SyncState ->
C.Signal dom (C.BitVector 10) ->
C.Signal dom (C.BitVector 10, Bool, C.Vec 3 DataWord, Even, SyncStatus)
syncSim s i = o
syncSim s cg1 = o
where
o =
C.moore outputQueueT outputQueueO (C.repeat (0, False, Dw 0, Odd, Ok)) $
C.bundle (cg, rd, dw, rxEven, syncStatus)
C.bundle (cg2, rd, dw, rxEven, syncStatus)

(_, cg, rd, dw, rxEven, syncStatus) =
C.mealyB syncT s i
(_, cg2, rd, dw, rxEven, syncStatus) =
C.mooreB syncT syncO s cg1

-- | Version of 'pcsReceive' that allows the initial state to be set via an
-- input variable
Expand Down

0 comments on commit 90f4649

Please sign in to comment.