-
Notifications
You must be signed in to change notification settings - Fork 3
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Ethernet: support zero-byte transfers. (#19)
Only the padding inserter and frame check sequence inserter needed adjustments. The tests are adjusted to use the new packet generation method.
- Loading branch information
Showing
14 changed files
with
308 additions
and
278 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,2 @@ | ||
indentation: 2 | ||
column-limit: 90 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -2,31 +2,29 @@ | |
{-# LANGUAGE RecordWildCards #-} | ||
{-# OPTIONS_HADDOCK hide #-} | ||
|
||
{-| | ||
Module : Clash.Cores.Ethernet.Mac.FrameCheckSequence | ||
Description : Provides circuits to insert, validate and strip the FCS of an Ethernet frame. | ||
{- | | ||
Copyright : (C) 2024, QBayLogic B.V. | ||
License : BSD2 (see the file LICENSE) | ||
Maintainer : QBayLogic B.V. <[email protected]> | ||
Provides circuits to insert, validate and strip the FCS of Ethernet frames. | ||
-} | ||
module Clash.Cores.Ethernet.Mac.FrameCheckSequence ( | ||
fcsInserterC, | ||
fcsValidatorC, | ||
fcsStripperC, | ||
) where | ||
|
||
-- crc | ||
import Clash.Cores.Crc (crcEngine, crcValidator, HardwareCrc) | ||
import Clash.Cores.Crc.Catalog (Crc32_ethernet(..)) | ||
|
||
-- vector | ||
import Clash.Sized.Vector.Extra (appendVec) | ||
import Clash.Cores.Crc (HardwareCrc, crcEngine, crcValidator) | ||
import Clash.Cores.Crc.Catalog (Crc32_ethernet (..)) | ||
|
||
-- prelude | ||
import Clash.Prelude | ||
|
||
-- maybe | ||
import Clash.Sized.Vector.Extra (appendVec) | ||
|
||
import Data.Maybe | ||
import Data.Maybe.Extra | ||
import Data.Maybe.Extra (toMaybe) | ||
|
||
-- protocols | ||
import Protocols | ||
import Protocols.PacketStream | ||
|
||
|
@@ -40,106 +38,110 @@ toCrcInput :: | |
PacketStreamM2S dataWidth () -> | ||
Maybe (Bool, Index dataWidth, Vec dataWidth (BitVector 8)) | ||
toCrcInput en isFirst PacketStreamM2S{..} = | ||
toMaybe en (isFirst, fromMaybe maxBound _last, _data) | ||
|
||
fcsInserterT | ||
:: forall dataWidth | ||
. KnownNat dataWidth | ||
=> 1 <= dataWidth | ||
=> FcsInserterState dataWidth | ||
-> ( Vec 4 (BitVector 8) | ||
, Maybe (PacketStreamM2S dataWidth ()) | ||
, PacketStreamS2M) | ||
-> ( FcsInserterState dataWidth | ||
, ( Maybe (PacketStreamM2S dataWidth ()) | ||
, Bool)) | ||
fcsInserterT (FcsCopy Nothing) ( _, fwdIn, _) = (FcsCopy fwdIn, (Nothing, True)) | ||
|
||
fcsInserterT st@(FcsCopy (Just cache@(PacketStreamM2S{..}))) (ethCrcBytes, fwdIn, PacketStreamS2M readyIn) | ||
= (nextSt, (Just fwdOut, readyIn)) | ||
where | ||
(combined, leftover) = splitAtI $ appendVec (fromJust _last) _data ethCrcBytes | ||
|
||
nextLast i = case compareSNat d5 (SNat @dataWidth) of | ||
SNatLE -> toMaybe (i < natToNum @(dataWidth - 4)) $ i + 4 | ||
_ -> Nothing | ||
|
||
insertCrc = nextLast <$> _last | ||
|
||
fwdOut = case insertCrc of | ||
Just l -> cache { _data = combined, _last = l } | ||
Nothing -> cache | ||
|
||
nextStIfReady = if maybe True isJust insertCrc | ||
then FcsCopy fwdIn | ||
else FcsInsert | ||
{ _aborted = _abort | ||
, _cachedFwd = fwdIn | ||
-- Since we know we are in a case where we are not transmitting the entire CRC out | ||
-- it's guaranteed that dataWidth - 4 <= lastIdx <= dataWidth - 1 | ||
-- This means we don't need to look at entire state space of the index. | ||
-- Only the last 2 bits matter. But since dataWidth might not be 4 byte | ||
-- aligned we need to wrapping subtract Mod dataWidth 4 to align the index. | ||
-- Normally wrapping subtract is relatively expensive but since 4 | ||
-- is a power of two we get it for free. But it means we have to do | ||
-- arithmetic with BitVector/Unsigned type and not index. | ||
-- | ||
-- We could go even further beyond and just pass through the last 2 bits without | ||
-- correction and handle that in `FcsInsert`. | ||
, _valid = unpack $ resize (pack $ fromJustX _last) - natToNum @(Mod dataWidth 4) | ||
, _cachedCrc = leftover | ||
} | ||
|
||
nextSt = if readyIn then nextStIfReady else st | ||
|
||
fcsInserterT st@(FcsInsert{..}) (_, _, PacketStreamS2M readyIn) = (nextSt, (Just dataOut, False)) | ||
where | ||
finished = _valid <= natToNum @(Min (dataWidth - 1) 3) | ||
(outBytes, nextBytes) = splitAtI $ _cachedCrc ++ repeat 0 | ||
dataOut = PacketStreamM2S | ||
{ _data = outBytes | ||
, _last = toMaybe finished $ resize _valid | ||
, _meta = () | ||
, _abort = _aborted | ||
} | ||
|
||
nextStIfReady = | ||
if finished | ||
then FcsCopy _cachedFwd | ||
else st | ||
{ _valid = _valid - natToNum @dataWidth | ||
, _cachedCrc = nextBytes | ||
} | ||
|
||
nextSt = if readyIn then nextStIfReady else st | ||
toMaybe | ||
(en && _last /= Just 0) | ||
(isFirst, maybe maxBound (resize . (\i -> i - 1)) _last, _data) | ||
|
||
-- | States of the FcsInserter | ||
-- | State of 'fcsInserterT'. | ||
data FcsInserterState dataWidth | ||
= FcsCopy | ||
{ _cachedFwd :: Maybe (PacketStreamM2S dataWidth ()) } | ||
{_cachedFwd :: Maybe (PacketStreamM2S dataWidth ())} | ||
| FcsInsert | ||
{ _aborted :: Bool | ||
, _cachedFwd :: Maybe (PacketStreamM2S dataWidth ()) | ||
, _valid :: Index 4 | ||
, _valid :: Index 5 | ||
-- ^ how many bytes of _cachedCrc are valid | ||
, _cachedCrc :: Vec 4 (BitVector 8) | ||
} | ||
deriving (Show, Generic, NFDataX) | ||
|
||
-- | fcsInserter | ||
fcsInserter | ||
:: forall (dataWidth :: Nat) (dom :: Domain) | ||
. HiddenClockResetEnable dom | ||
=> KnownNat dataWidth | ||
=> HardwareCrc Crc32_ethernet 8 dataWidth | ||
=> ( Signal dom (Maybe (PacketStreamM2S dataWidth ())) | ||
, Signal dom PacketStreamS2M | ||
) | ||
-> ( Signal dom PacketStreamS2M | ||
, Signal dom (Maybe (PacketStreamM2S dataWidth ())) | ||
) | ||
fcsInserter (fwdIn, bwdIn) = (bwdOut, fwdOut) | ||
where | ||
-- | State transition function of 'fcsInserterC'. | ||
fcsInserterT :: | ||
forall dataWidth. | ||
(KnownNat dataWidth) => | ||
(1 <= dataWidth) => | ||
FcsInserterState dataWidth -> | ||
( Vec 4 (BitVector 8) | ||
, Maybe (PacketStreamM2S dataWidth ()) | ||
, PacketStreamS2M | ||
) -> | ||
( FcsInserterState dataWidth | ||
, ( Maybe (PacketStreamM2S dataWidth ()) | ||
, Bool | ||
) | ||
) | ||
fcsInserterT (FcsCopy Nothing) (_, fwdIn, _) = (FcsCopy fwdIn, (Nothing, True)) | ||
fcsInserterT st@(FcsCopy (Just cache@(PacketStreamM2S{..}))) (ethCrcBytes, fwdIn, bwdIn) = | ||
(nextStOut, (Just fwdOut, _ready bwdIn)) | ||
where | ||
(combined, leftover) = splitAtI $ appendVec (fromJust _last) _data ethCrcBytes | ||
|
||
nextLast :: Index (dataWidth + 1) -> Maybe (Index (dataWidth + 1)) | ||
nextLast i = case compareSNat d4 (SNat @dataWidth) of | ||
SNatLE -> toMaybe (i <= natToNum @(dataWidth - 4)) (i + 4) | ||
_ -> Nothing | ||
|
||
insertCrc = nextLast <$> _last | ||
|
||
fwdOut = case insertCrc of | ||
Just l -> cache{_data = combined, _last = l} | ||
Nothing -> cache | ||
|
||
nextSt = | ||
if maybe True isJust insertCrc | ||
then FcsCopy fwdIn | ||
else | ||
FcsInsert | ||
{ _aborted = _abort | ||
, _cachedFwd = fwdIn | ||
, _valid = 4 - resize (maxBound - fromJustX _last) | ||
, _cachedCrc = leftover | ||
} | ||
|
||
nextStOut = if _ready bwdIn then nextSt else st | ||
fcsInserterT st@(FcsInsert{..}) (_, _, bwdIn) = (nextStOut, (Just dataOut, False)) | ||
where | ||
finished = _valid <= natToNum @(Min dataWidth 4) | ||
(outBytes, nextBytes) = splitAtI $ _cachedCrc ++ repeat 0x00 | ||
dataOut = | ||
PacketStreamM2S | ||
{ _data = outBytes | ||
, _last = toMaybe finished (resize _valid) | ||
, _meta = () | ||
, _abort = _aborted | ||
} | ||
|
||
nextSt = | ||
if finished | ||
then FcsCopy _cachedFwd | ||
else | ||
st | ||
{ _valid = _valid - natToNum @dataWidth | ||
, _cachedCrc = nextBytes | ||
} | ||
|
||
nextStOut = if _ready bwdIn then nextSt else st | ||
|
||
{- | | ||
Computes the Ethernet CRC ('Crc32_ethernet') over each packet in the stream | ||
and appends this CRC to the corresponding packet in the output stream. | ||
__NB__: does not support zero-byte packets. Feeding a zero-byte packet to this | ||
component will result in /undefined behaviour/. | ||
-} | ||
fcsInserterC :: | ||
forall (dataWidth :: Nat) (dom :: Domain). | ||
(HiddenClockResetEnable dom) => | ||
(HardwareCrc Crc32_ethernet 8 dataWidth) => | ||
(KnownNat dataWidth) => | ||
-- | Ethernet FCS inserter circuit | ||
Circuit | ||
(PacketStream dom dataWidth ()) | ||
(PacketStream dom dataWidth ()) | ||
fcsInserterC = forceResetSanity |> fromSignals go | ||
where | ||
go (fwdIn, bwdIn) = (bwdOut, fwdOut) | ||
where | ||
fwdInX = fromJustX <$> fwdIn | ||
transferOccured = ready .&&. isJust <$> fwdIn | ||
crcIn = liftA3 toCrcInput transferOccured isFirst fwdInX | ||
|
@@ -152,21 +154,6 @@ fcsInserter (fwdIn, bwdIn) = (bwdOut, fwdOut) | |
|
||
(fwdOut, ready) = mealyB fcsInserterT (FcsCopy Nothing) (ethCrcBytes, fwdIn, bwdIn) | ||
|
||
{- | | ||
Computes the Ethernet CRC (4 bytes) of each packet in the input stream and | ||
appends this CRC to the corresponding packet in the output stream. | ||
-} | ||
fcsInserterC | ||
:: forall (dataWidth :: Nat) (dom :: Domain) | ||
. KnownDomain dom | ||
=> KnownNat dataWidth | ||
=> HiddenClockResetEnable dom | ||
=> HardwareCrc Crc32_ethernet 8 dataWidth | ||
=> Circuit | ||
(PacketStream dom dataWidth ()) | ||
(PacketStream dom dataWidth ()) | ||
fcsInserterC = forceResetSanity |> fromSignals fcsInserter | ||
|
||
-- | State of 'fcsValidatorT'. | ||
newtype FcsValidatorState dataWidth = FcsValidatorState | ||
{ _cachedFwd :: Maybe (PacketStreamM2S dataWidth ()) | ||
|
@@ -176,6 +163,7 @@ newtype FcsValidatorState dataWidth = FcsValidatorState | |
-- | State transition function of 'fcsValidator'. | ||
fcsValidatorT :: | ||
forall (dataWidth :: Nat). | ||
(KnownNat dataWidth) => | ||
FcsValidatorState dataWidth -> | ||
( Bool | ||
, Maybe (PacketStreamM2S dataWidth ()) | ||
|
@@ -204,7 +192,6 @@ fcsValidatorT st@FcsValidatorState{..} (valid, fwdIn, bwdIn) = | |
fcsValidator :: | ||
forall (dataWidth :: Nat) (dom :: Domain). | ||
(HiddenClockResetEnable dom) => | ||
(KnownNat dataWidth) => | ||
(HardwareCrc Crc32_ethernet 8 dataWidth) => | ||
( Signal dom (Maybe (PacketStreamM2S dataWidth ())) | ||
, Signal dom PacketStreamS2M | ||
|
@@ -233,12 +220,16 @@ did not match the last 4 bytes of the stream. | |
__NB__: does not remove the FCS field (last 4 bytes of the stream). | ||
Use 'fcsStripperC' for that. | ||
__NB__: does not support zero-byte packets. Feeding a zero-byte packet to this | ||
component will result in /undefined behaviour/. | ||
-} | ||
fcsValidatorC :: | ||
forall (dataWidth :: Nat) (dom :: Domain). | ||
(HiddenClockResetEnable dom) => | ||
(KnownNat dataWidth) => | ||
(HardwareCrc Crc32_ethernet 8 dataWidth) => | ||
-- | Ethernet FCS validator circuit | ||
Circuit | ||
(PacketStream dom dataWidth ()) | ||
(PacketStream dom dataWidth ()) | ||
|
@@ -255,6 +246,7 @@ fcsStripperC :: | |
(HiddenClockResetEnable dom) => | ||
(KnownNat dataWidth) => | ||
(1 <= dataWidth) => | ||
-- | Ethernet FCS stripper circuit | ||
Circuit | ||
(PacketStream dom dataWidth ()) | ||
(PacketStream dom dataWidth ()) | ||
|
Oops, something went wrong.