Skip to content

Commit

Permalink
Move EbTb out of Sgmii
Browse files Browse the repository at this point in the history
  • Loading branch information
jvnknvlgl committed Jun 21, 2024
1 parent ac38bab commit aed543e
Show file tree
Hide file tree
Showing 14 changed files with 50 additions and 48 deletions.
10 changes: 5 additions & 5 deletions clash-cores/clash-cores.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -126,20 +126,22 @@ library
Clash.Cores.Crc
Clash.Cores.Crc.Internal
Clash.Cores.Crc.Catalog
Clash.Cores.EbTb
Clash.Cores.EbTb.Decoder
Clash.Cores.EbTb.Encoder
Clash.Cores.LatticeSemi.ECP5.Blackboxes.IO
Clash.Cores.LatticeSemi.ECP5.IO
Clash.Cores.LatticeSemi.ICE40.Blackboxes.IO
Clash.Cores.LatticeSemi.ICE40.IO
Clash.Cores.Sgmii
Clash.Cores.Sgmii.AutoNeg
Clash.Cores.Sgmii.BitSlip
Clash.Cores.Sgmii.Common
Clash.Cores.Sgmii.EbTb
Clash.Cores.Sgmii.Gearbox
Clash.Cores.Sgmii.PcsReceive
Clash.Cores.Sgmii.PcsTransmit
Clash.Cores.Sgmii.PcsTransmit.CodeGroup
Clash.Cores.Sgmii.PcsTransmit.OrderedSet
Clash.Cores.Sgmii.Sgmii
Clash.Cores.Sgmii.Sync
Clash.Cores.SPI
Clash.Cores.UART
Expand Down Expand Up @@ -173,8 +175,6 @@ library
Clash.Cores.Xilinx.Xpm.Cdc.SyncRst

other-modules:
Clash.Cores.Sgmii.EbTb.Decoder
Clash.Cores.Sgmii.EbTb.Encoder
Data.Text.Extra

ghc-options:
Expand Down Expand Up @@ -207,12 +207,12 @@ test-suite unittests

other-Modules:
Test.Cores.Crc
Test.Cores.EbTb
Test.Cores.Internal.SampleSPI
Test.Cores.Internal.Signals
Test.Cores.Sgmii.AutoNeg
Test.Cores.Sgmii.BitSlip
Test.Cores.Sgmii.Common
Test.Cores.Sgmii.EbTb
Test.Cores.Sgmii.Gearbox
Test.Cores.Sgmii.PcsReceive
Test.Cores.Sgmii.PcsTransmit
Expand Down
Original file line number Diff line number Diff line change
@@ -1,12 +1,38 @@
{-# LANGUAGE CPP #-}

module Clash.Cores.Sgmii.EbTb where
module Clash.Cores.EbTb where

import Clash.Cores.Sgmii.Common
import qualified Clash.Cores.Sgmii.EbTb.Decoder as Dec
import qualified Clash.Cores.Sgmii.EbTb.Encoder as Enc
import qualified Clash.Cores.EbTb.Decoder as Dec
import qualified Clash.Cores.EbTb.Encoder as Enc
import Clash.Prelude

-- | Data type that contains a 'BitVector 8' with the corresponding error
-- condition of the decode function
data DataWord
= Dw (BitVector 8)
| Cw (BitVector 8)
| DwError (BitVector 8)
| RdError (BitVector 8)
deriving (Generic, NFDataX, Eq, Show)

-- | Function to check whether a 'DataWord' results in a data word
isDw :: DataWord -> Bool
isDw (Dw _) = True
isDw _ = False

-- | Function to check whether a 'DataWord' results in a data word or
-- control word
isValidDw :: DataWord -> Bool
isValidDw (Cw _) = True
isValidDw dw = isDw dw

-- | Function to convert a 'DataWord' to a plain 'BitVector 8'
fromDw :: DataWord -> BitVector 8
fromDw dw = case dw of
Dw _dw -> _dw
Cw _dw -> _dw
_ -> 0

-- | Take the running disparity and the current code group, and return a tuple
-- containing the new running disparity and a 'DataWord' containing the
-- decoded value. This function uses a 'MemBlob' to store the decoder lookup
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Clash.Cores.Sgmii.EbTb.Decoder where
module Clash.Cores.EbTb.Decoder where

import Clash.Prelude

Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Clash.Cores.Sgmii.EbTb.Encoder where
module Clash.Cores.EbTb.Encoder where

import Clash.Prelude

Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module Clash.Cores.Sgmii.Sgmii where
module Clash.Cores.Sgmii where

import Clash.Cores.EbTb
import Clash.Cores.Sgmii.AutoNeg
import Clash.Cores.Sgmii.BitSlip
import Clash.Cores.Sgmii.Common
Expand Down
28 changes: 1 addition & 27 deletions clash-cores/src/Clash/Cores/Sgmii/Common.hs
Original file line number Diff line number Diff line change
@@ -1,37 +1,11 @@
module Clash.Cores.Sgmii.Common where

import Clash.Cores.EbTb
import Clash.Prelude

-- | Format of rxConfReg and txConfReg, size of two data words
type ConfReg = BitVector 16

-- | Data type that contains a 'BitVector 8' with the corresponding error
-- condition of the decode function
data DataWord
= Dw (BitVector 8)
| Cw (BitVector 8)
| DwError (BitVector 8)
| RdError (BitVector 8)
deriving (Generic, NFDataX, Eq, Show)

-- | Function to check whether a 'DataWord' results in a data word
isDw :: DataWord -> Bool
isDw (Dw _) = True
isDw _ = False

-- | Function to check whether a 'DataWord' results in a data word or
-- control word
isValidDw :: DataWord -> Bool
isValidDw (Cw _) = True
isValidDw dw = isDw dw

-- | Function to convert a 'DataWord' to a plain 'BitVector 8'
fromDw :: DataWord -> BitVector 8
fromDw dw = case dw of
Dw _dw -> _dw
Cw _dw -> _dw
_ -> 0

-- | Defines the possible values for the RUDI output signal of the PCS Receive
-- block as defined in IEEE 802.3 Clause 36
data Rudi = C | I | Invalid
Expand Down
1 change: 1 addition & 0 deletions clash-cores/src/Clash/Cores/Sgmii/PcsReceive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@

module Clash.Cores.Sgmii.PcsReceive where

import Clash.Cores.EbTb
import Clash.Cores.Sgmii.Common
import Clash.Prelude

Expand Down
2 changes: 1 addition & 1 deletion clash-cores/src/Clash/Cores/Sgmii/PcsTransmit/CodeGroup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,8 @@

module Clash.Cores.Sgmii.PcsTransmit.CodeGroup where

import Clash.Cores.EbTb
import Clash.Cores.Sgmii.Common
import Clash.Cores.Sgmii.EbTb
import Clash.Prelude

-- | State type of 'codeGroupT' as defined in IEEE 802.3 Clause 36, with the
Expand Down
2 changes: 1 addition & 1 deletion clash-cores/src/Clash/Cores/Sgmii/Sync.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@

module Clash.Cores.Sgmii.Sync where

import Clash.Cores.EbTb
import Clash.Cores.Sgmii.Common
import Clash.Cores.Sgmii.EbTb
import Clash.Prelude

-- | State type of the output queue for 'sync'
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Test.Cores.Sgmii.EbTb where
module Test.Cores.EbTb where

import Clash.Cores.EbTb
import Clash.Cores.Sgmii.Common
import Clash.Cores.Sgmii.EbTb
import Clash.Hedgehog.Sized.BitVector
import qualified Hedgehog as H
import qualified Hedgehog.Gen as Gen
Expand Down
2 changes: 1 addition & 1 deletion clash-cores/test/Test/Cores/Sgmii/PcsReceive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,8 @@

module Test.Cores.Sgmii.PcsReceive where

import Clash.Cores.EbTb
import Clash.Cores.Sgmii.Common
import Clash.Cores.Sgmii.EbTb
import Clash.Cores.Sgmii.PcsReceive
import Clash.Hedgehog.Sized.BitVector
import qualified Clash.Prelude as C
Expand Down
1 change: 1 addition & 0 deletions clash-cores/test/Test/Cores/Sgmii/Sgmii.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@

module Test.Cores.Sgmii.Sgmii where

import Clash.Cores.EbTb
import Clash.Cores.Sgmii.AutoNeg
import Clash.Cores.Sgmii.BitSlip
import Clash.Cores.Sgmii.Common
Expand Down
2 changes: 1 addition & 1 deletion clash-cores/test/Test/Cores/Sgmii/Sync.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Test.Cores.Sgmii.Sync where

import Clash.Cores.EbTb
import Clash.Cores.Sgmii.Common
import Clash.Cores.Sgmii.EbTb
import Clash.Cores.Sgmii.Sync
import Clash.Hedgehog.Sized.BitVector
import qualified Clash.Prelude as C
Expand Down
5 changes: 2 additions & 3 deletions clash-cores/test/unittests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,9 @@ import Prelude
import Test.Tasty

import qualified Test.Cores.Crc
import qualified Test.Cores.EbTb
import qualified Test.Cores.Sgmii.AutoNeg
import qualified Test.Cores.Sgmii.BitSlip
import qualified Test.Cores.Sgmii.EbTb
import qualified Test.Cores.Sgmii.Gearbox
import qualified Test.Cores.Sgmii.PcsReceive
import qualified Test.Cores.Sgmii.PcsTransmit
Expand All @@ -29,10 +29,9 @@ import qualified Test.Cores.Xilinx.DnaPortE2
tests :: TestTree
tests = testGroup "Unittests"
[ Test.Cores.Crc.tests
, Test.Cores.Sgmii.EbTb.tests
, Test.Cores.EbTb.tests
, Test.Cores.Sgmii.AutoNeg.tests
, Test.Cores.Sgmii.BitSlip.tests
, Test.Cores.Sgmii.EbTb.tests
, Test.Cores.Sgmii.Gearbox.tests
, Test.Cores.Sgmii.PcsReceive.tests
, Test.Cores.Sgmii.PcsTransmit.tests
Expand Down

0 comments on commit aed543e

Please sign in to comment.