diff --git a/clash-cores/src/Clash/Cores/Sgmii/Common.hs b/clash-cores/src/Clash/Cores/Sgmii/Common.hs index 27c12216f4..f4867f215a 100644 --- a/clash-cores/src/Clash/Cores/Sgmii/Common.hs +++ b/clash-cores/src/Clash/Cores/Sgmii/Common.hs @@ -5,24 +5,6 @@ import Clash.Prelude -- | Format of rxConfReg and txConfReg, size of two data words type ConfReg = BitVector 16 --- | Data type that contains a 'BitVector 10' with the corresponding error --- condition of the encode function -data CodeGroup - = Cg (BitVector 10) - | CgError (BitVector 10) - deriving (Generic, NFDataX, Eq, Show) - --- | Function to check whether a 'CodeGroup' results in a code group -isCg :: CodeGroup -> Bool -isCg (Cg _) = True -isCg _ = False - --- | Function to convert a 'CodeGroup' to a plain 'BitVector 10' -fromCg :: CodeGroup -> BitVector 10 -fromCg cg = case cg of - Cg _cg -> _cg - _ -> 0 - -- | Data type that contains a 'BitVector 8' with the corresponding error -- condition of the decode function data DataWord diff --git a/clash-cores/src/Clash/Cores/Sgmii/EbTb.hs b/clash-cores/src/Clash/Cores/Sgmii/EbTb.hs index 98d6362060..451a32018c 100644 --- a/clash-cores/src/Clash/Cores/Sgmii/EbTb.hs +++ b/clash-cores/src/Clash/Cores/Sgmii/EbTb.hs @@ -41,24 +41,17 @@ ebTbDecode rd cg = (rdNew, dw) {-# CLASH_OPAQUE ebTbDecode #-} -- | Take the running disparity and the current 'DataWord', and return a tuple --- containing the new running disparity and a 'CodeGroup' containing the +-- containing the new running disparity and a 'BitVector' containing the -- encoded value. This function uses a 'MemBlob' to store the encoder lookup -- table. --- --- Remarks: --- - I don't completely know yet if it is useful to have a specific type for --- CodeGroup, as a codegroup is always connected to the outside world and --- so it might be more relevant to have it a plain 'BitVector 10'. --- - The same goes for whether it is relevant to return an error for an input --- error, see the second case of 'ebTbEncode'. ebTbEncode :: -- | Running disparity Bool -> -- | Data word DataWord -> - -- | Tuple containing the new running disparity and the 'CodeGroup' - (Bool, CodeGroup) -ebTbEncode rd (Dw dw) = (rdNew, Cg $ pack $ reverse cg) + -- | Tuple containing the new running disparity and the code group + (Bool, BitVector 10) +ebTbEncode rd (Dw dw) = (rdNew, pack $ reverse cg) where (statusBits, cg) = splitAt d2 @@ -68,13 +61,9 @@ ebTbEncode rd (Dw dw) = (rdNew, Cg $ pack $ reverse cg) $ unpack (0 ++# bitCoerce rd ++# dw) rdNew = bitCoerce $ last statusBits -ebTbEncode rd (Cw dw) = (rdNew, cg) +ebTbEncode rd (Cw dw) = (rdNew, if cgEr then 0 else pack $ reverse cg) where - cg - | cgEr = CgError $ pack $ reverse _cg - | otherwise = Cg $ pack $ reverse _cg - - (statusBits, _cg) = + (statusBits, cg) = splitAt d2 $ bv2v $ asyncRomBlobPow2 @@ -83,6 +72,6 @@ ebTbEncode rd (Cw dw) = (rdNew, cg) cgEr = bitCoerce $ head statusBits rdNew = bitCoerce $ last statusBits -ebTbEncode rd _ = (rd, CgError 0) +ebTbEncode rd _ = (rd, 0) {-# CLASH_OPAQUE ebTbEncode #-} diff --git a/clash-cores/src/Clash/Cores/Sgmii/PcsReceive.hs b/clash-cores/src/Clash/Cores/Sgmii/PcsReceive.hs index 29324118af..c3de7d10ac 100644 --- a/clash-cores/src/Clash/Cores/Sgmii/PcsReceive.hs +++ b/clash-cores/src/Clash/Cores/Sgmii/PcsReceive.hs @@ -97,7 +97,7 @@ carrierDetect rd dw rxEven cgK28_5N = 0b0011111010 cgK28_5P = 0b1100000101 cgK28_5 = if rd then cgK28_5P else cgK28_5N - cg = fromCg $ snd $ ebTbEncode rd dw + cg = snd $ ebTbEncode rd dw -- | Take the running disparity, the current and next two input data words and -- check whether they correspond to one of the specified end conditions diff --git a/clash-cores/src/Clash/Cores/Sgmii/PcsTransmit.hs b/clash-cores/src/Clash/Cores/Sgmii/PcsTransmit.hs index 557b2c4b91..ab9cd2417e 100644 --- a/clash-cores/src/Clash/Cores/Sgmii/PcsTransmit.hs +++ b/clash-cores/src/Clash/Cores/Sgmii/PcsTransmit.hs @@ -12,11 +12,11 @@ pcsTransmit :: Signal dom (BitVector 8) -> Signal dom Xmit -> Signal dom ConfReg -> - Signal dom CodeGroup + Signal dom (BitVector 10) pcsTransmit txEn txEr dw xmit txConfReg = cg where (_, cg, txEven, cgSent) = - mealyB codeGroupT Init (txOSet, dw, txConfReg) + mealyB codeGroupT (SpecialGo False Even) (txOSet, dw, txConfReg) (_, txOSet) = mealyB diff --git a/clash-cores/src/Clash/Cores/Sgmii/PcsTransmit/CodeGroup.hs b/clash-cores/src/Clash/Cores/Sgmii/PcsTransmit/CodeGroup.hs index 36381ef699..7589de395e 100644 --- a/clash-cores/src/Clash/Cores/Sgmii/PcsTransmit/CodeGroup.hs +++ b/clash-cores/src/Clash/Cores/Sgmii/PcsTransmit/CodeGroup.hs @@ -7,8 +7,7 @@ import Clash.Cores.Sgmii.EbTb import Clash.Prelude data CodeGroupState - = Init - | SpecialGo {_rd :: Bool, _txEven :: Even} + = SpecialGo {_rd :: Bool, _txEven :: Even} | DataGo {_rd :: Bool, _txEven :: Even} | IdleDisparityWrong {_rd :: Bool} | IdleI1B {_rd :: Bool} @@ -27,24 +26,7 @@ data CodeGroupState codeGroupT :: CodeGroupState -> (DataWord, BitVector 8, ConfReg) -> - (CodeGroupState, (CodeGroupState, CodeGroup, Even, Bool)) -codeGroupT self@Init (txOSet, _, _) = (nextState, out) - where - nextState - | fromDw txOSet == dwV = SpecialGo rd txEven - | fromDw txOSet == dwS = SpecialGo rd txEven - | fromDw txOSet == dwT = SpecialGo rd txEven - | fromDw txOSet == dwR = SpecialGo rd txEven - | isDw txOSet = DataGo rd txEven - | fromDw txOSet == dwI && rd = IdleDisparityWrong rd - | fromDw txOSet == dwI && not rd = IdleDisparityOk rd - | fromDw txOSet == dwC = ConfigurationC1A rd - | otherwise = self - - rd = False - txEven = Even - - out = (self, Cg 0, txEven, False) + (CodeGroupState, (CodeGroupState, BitVector 10, Even, Bool)) codeGroupT self@SpecialGo{..} (txOSet, _, _) = (nextState, out) where nextState diff --git a/clash-cores/test/Test/Cores/Sgmii/EbTb.hs b/clash-cores/test/Test/Cores/Sgmii/EbTb.hs index ba767d3680..ca72d7b3f0 100644 --- a/clash-cores/test/Test/Cores/Sgmii/EbTb.hs +++ b/clash-cores/test/Test/Cores/Sgmii/EbTb.hs @@ -18,8 +18,8 @@ prop_ebTbDecodeCheckNothing = H.property $ do inp <- H.forAll (Gen.filterT checkBitSequence genDefinedBitVector) let out = isValidDw dw1 && isValidDw dw2 where - (_, dw1) = ebTbDecode False $ fromCg $ snd $ ebTbEncode False (Dw inp) - (_, dw2) = ebTbDecode True $ fromCg $ snd $ ebTbEncode True (Dw inp) + (_, dw1) = ebTbDecode False $ snd $ ebTbEncode False (Dw inp) + (_, dw2) = ebTbDecode True $ snd $ ebTbEncode True (Dw inp) H.assert out @@ -28,7 +28,7 @@ prop_ebTbDecodeCheckNothing = H.property $ do prop_ebTbEncodeCheckNothing :: H.Property prop_ebTbEncodeCheckNothing = H.property $ do inp <- H.forAll genDefinedBitVector - let out = isCg $ snd $ ebTbEncode False (Dw inp) + let out = 0 /= snd (ebTbEncode False (Dw inp)) H.assert out @@ -42,11 +42,7 @@ prop_ebTbEncodeDecode = H.property $ do inp <- H.forAll genDefinedBitVector let out = if isValidDw dw then fromDw dw else inp where - cg = snd $ ebTbEncode False (Dw inp) - - (_, dw) = case cg of - Cg _cg -> ebTbDecode False _cg - CgError _ -> (False, Dw inp) + dw = snd $ ebTbDecode False $ snd $ ebTbEncode False (Dw inp) expected = inp @@ -67,10 +63,9 @@ prop_ebTbDecodeEncode = H.property $ do where o = g False inp - g rd i = fromCg cg + g rd i = if isValidDw dw then snd $ ebTbEncode rd dw else i where dw = snd $ ebTbDecode rd i - cg = if isValidDw dw then snd $ ebTbEncode rd dw else Cg i expected = inp