Skip to content

Commit

Permalink
Add top-level MAC module and improve its documentation
Browse files Browse the repository at this point in the history
  • Loading branch information
t-wallet committed Aug 28, 2024
1 parent 0c59cff commit 9cf12fd
Show file tree
Hide file tree
Showing 8 changed files with 169 additions and 98 deletions.
1 change: 1 addition & 0 deletions clash-cores.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -141,6 +141,7 @@ library
Clash.Cores.Ethernet.IP.InternetChecksum
Clash.Cores.Ethernet.IP.IPPacketizers
Clash.Cores.Ethernet.IP.IPv4Types
Clash.Cores.Ethernet.Mac
Clash.Cores.Ethernet.Mac.EthernetTypes
Clash.Cores.Ethernet.Mac.FrameCheckSequence
Clash.Cores.Ethernet.Mac.InterpacketGapInserter
Expand Down
29 changes: 29 additions & 0 deletions src/Clash/Cores/Ethernet/Mac.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
{- |
Copyright : (C) 2024, QBayLogic B.V.
License : BSD2 (see the file LICENSE)
Maintainer : QBayLogic B.V. <devops@qbaylogic.com>
Provides various components to handle the Ethernet protocol, both the physical-
and link-layer.
-}
module Clash.Cores.Ethernet.Mac (
-- * Data types and constants
module Clash.Cores.Ethernet.Mac.EthernetTypes,
-- * Frame check sequence
module Clash.Cores.Ethernet.Mac.FrameCheckSequence,
-- * Interpacket gap
module Clash.Cores.Ethernet.Mac.InterpacketGapInserter,
-- * MAC header
module Clash.Cores.Ethernet.Mac.MacPacketizers,
-- * Padding
module Clash.Cores.Ethernet.Mac.PaddingInserter,
-- * Preamble
module Clash.Cores.Ethernet.Mac.Preamble,
) where

import Clash.Cores.Ethernet.Mac.EthernetTypes
import Clash.Cores.Ethernet.Mac.FrameCheckSequence
import Clash.Cores.Ethernet.Mac.InterpacketGapInserter
import Clash.Cores.Ethernet.Mac.MacPacketizers
import Clash.Cores.Ethernet.Mac.PaddingInserter
import Clash.Cores.Ethernet.Mac.Preamble
81 changes: 45 additions & 36 deletions src/Clash/Cores/Ethernet/Mac/EthernetTypes.hs
Original file line number Diff line number Diff line change
@@ -1,58 +1,67 @@
{-# OPTIONS_HADDOCK hide #-}

{-|
Module : Clash.Cores.Ethernet.Mac.EthernetTypes
Description : Provides various data types, aliases and constants for the Ethernet protocol.
-}
module Clash.Cores.Ethernet.Mac.EthernetTypes
( MacAddress(..)
, EthernetHeader(..)
, broadcastMac
, constToEthernetC
) where

import Clash.Prelude
module Clash.Cores.Ethernet.Mac.EthernetTypes (
MacAddress (..),
EthernetHeader (..),
broadcastMac,
constToEthernetC,
) where

import Protocols
import Protocols.PacketStream
import Control.DeepSeq (NFData)

import Control.DeepSeq ( NFData )
import Clash.Prelude

import Protocols (Circuit)
import Protocols.PacketStream (PacketStream, mapMetaS)

-- | Stores a MAC address, which is always 6 bytes long.
newtype MacAddress = MacAddress (Vec 6 (BitVector 8))
deriving (BitPack, Eq, Generic, NFData, NFDataX, Show, ShowX)

-- | Stores a link-layer Ethernet header, that is, a destination MAC address,
-- a source MAC address, and an EtherType.
data EthernetHeader = EthernetHeader {
_macDst :: MacAddress,
_macSrc :: MacAddress,
_etherType :: BitVector 16
} deriving (BitPack, Eq, Generic, NFData, NFDataX, Show, ShowX)
-- | Stores a link-layer Ethernet header.
data EthernetHeader = EthernetHeader
{ _macDst :: MacAddress
-- ^ Destination MAC address
, _macSrc :: MacAddress
-- ^ Source MAC address
, _etherType :: BitVector 16
-- ^ EtherType
}
deriving (BitPack, Eq, Generic, NFData, NFDataX, Show, ShowX)

-- | Broadcast MAC address.
broadcastMac :: MacAddress
broadcastMac = MacAddress (repeat 0xFF)

{- |
Convert an arbitrary stream to an Ethernet stream with a hardcoded destination
MAC address.
Convert an arbitrary packet stream to an Ethernet stream with a hardcoded
destination MAC address.
Runs at full throughput and provides zero latency.
-}
constToEthernetC ::
HiddenClockResetEnable dom
(HiddenClockResetEnable dom) =>
-- | EtherType
=> BitVector 16
-- | Hardcoded Target MAC address
-> MacAddress
BitVector 16 ->
-- | Hardcoded destination MAC address
MacAddress ->
-- | Our MAC address
-> Signal dom MacAddress
-> Circuit
(PacketStream dom dataWidth meta)
(PacketStream dom dataWidth EthernetHeader)
constToEthernetC etherType macDst ourMac = mapMetaS (const <$> hdr)
where
hdr = (\src -> EthernetHeader
{
_macDst = macDst,
_macSrc = src,
_etherType = etherType
}) <$> ourMac
Signal dom MacAddress ->
Circuit
(PacketStream dom dataWidth meta)
(PacketStream dom dataWidth EthernetHeader)
constToEthernetC etherType macDst ourMacS = mapMetaS (const <$> hdr)
where
hdr =
( \ourMac ->
EthernetHeader
{ _macDst = macDst
, _macSrc = ourMac
, _etherType = etherType
}
)
<$> ourMacS
7 changes: 5 additions & 2 deletions src/Clash/Cores/Ethernet/Mac/FrameCheckSequence.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
{-# language MultiParamTypeClasses #-}
{-# language RecordWildCards #-}
{-# language ScopedTypeVariables #-}
{-# OPTIONS_HADDOCK hide #-}

{-|
Module : Clash.Cores.Ethernet.Mac.FrameCheckSequence
Expand Down Expand Up @@ -151,8 +152,10 @@ fcsInserter (fwdIn, bwdIn) = (bwdOut, fwdOut)
(fwdOut, ready) = mealyB fcsInserterT (FcsCopy Nothing) (ethCrcBytes, fwdIn, bwdIn)


-- | Computes the Crc-32 of the packets in the stream and inserts these as four (4) bytes at the end of each
-- packet in the stream.
{- |
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 (dom :: Domain) (dataWidth :: Nat)
. KnownDomain dom
Expand Down
25 changes: 13 additions & 12 deletions src/Clash/Cores/Ethernet/Mac/InterpacketGapInserter.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,19 @@
{-# OPTIONS_HADDOCK hide #-}

{-|
Module : Clash.Cores.Ethernet.Mac.InterpacketGapInserter
Description : Provides a circuit which inserts a configurable-length interpacket gap between packets.
-}
module Clash.Cores.Ethernet.Mac.InterpacketGapInserter
( interpacketGapInserterC
) where
module Clash.Cores.Ethernet.Mac.InterpacketGapInserter (
interpacketGapInserterC,
) where

import Clash.Prelude

import Protocols (Circuit, fromSignals)
import Protocols.PacketStream
import Protocols ( Circuit, fromSignals )

import Data.Maybe

import Data.Maybe (isJust)

data InterpacketGapInserterState gapSize
= -- | Assert backpressure for @gapSize@ cycles.
Expand All @@ -24,12 +25,12 @@ data InterpacketGapInserterState gapSize
-- | State transition function of the interpacket gap inserter, in mealy form.
gapInserterT ::
forall (gapSize :: Nat).
1 <= gapSize =>
KnownNat gapSize =>
(KnownNat gapSize) =>
(1 <= gapSize) =>
InterpacketGapInserterState gapSize ->
(Maybe (PacketStreamM2S 1 ()), PacketStreamS2M) ->
( InterpacketGapInserterState gapSize,
(PacketStreamS2M, Maybe (PacketStreamM2S 1 ()))
( InterpacketGapInserterState gapSize
, (PacketStreamS2M, Maybe (PacketStreamM2S 1 ()))
)
gapInserterT Insert{_counter = c} _ = (nextSt, (PacketStreamS2M False, Nothing))
where
Expand All @@ -48,8 +49,8 @@ with `_last` set. During these cycles, the output of this component is
-}
interpacketGapInserterC ::
forall (gapSize :: Nat) (dom :: Domain).
HiddenClockResetEnable dom =>
1 <= gapSize =>
(HiddenClockResetEnable dom) =>
(1 <= gapSize) =>
-- | The amount of clock cycles this component will stall after each packet boundary
SNat gapSize ->
Circuit (PacketStream dom 1 ()) (PacketStream dom 1 ())
Expand Down
44 changes: 28 additions & 16 deletions src/Clash/Cores/Ethernet/Mac/MacPacketizers.hs
Original file line number Diff line number Diff line change
@@ -1,37 +1,49 @@
{-# OPTIONS_HADDOCK hide #-}

{-|
Module : Clash.Cores.Ethernet.Mac.MacPacketizers
Description : Specialized packetizers for ethernet headers.
Description : Specialized (de)packetizers for Ethernet headers.
-}
module Clash.Cores.Ethernet.Mac.MacPacketizers
( macPacketizerC
, macDepacketizerC
) where
module Clash.Cores.Ethernet.Mac.MacPacketizers (
macPacketizerC,
macDepacketizerC,
) where

import Clash.Prelude

import Protocols
import Protocols.PacketStream
import Protocols (Circuit)
import Protocols.PacketStream (depacketizerC, packetizerC, PacketStream)

import Clash.Cores.Ethernet.Mac.EthernetTypes
import Clash.Cores.Ethernet.Mac.EthernetTypes (EthernetHeader)

{- |
Prepends the `EthernetHeader` in the metadata to the packet stream,
for each packet.
-- | Prepends an `EthernetHeader` in the metadata to the packet stream, for each packet.
Inherits latency and throughput from `packetizerC`.
-}
macPacketizerC ::
forall dataWidth dom.
HiddenClockResetEnable dom =>
KnownNat dataWidth =>
1 <= dataWidth =>
(HiddenClockResetEnable dom) =>
(KnownNat dataWidth) =>
(1 <= dataWidth) =>
Circuit
(PacketStream dom dataWidth EthernetHeader)
(PacketStream dom dataWidth ())
macPacketizerC = packetizerC (const ()) id

-- | Parses the first 14 bytes of the incoming PacketStream into an `EthernetHeader`.
{- |
Parses the first 14 bytes of each packet in the incoming packet stream into an
`EthernetHeader`, puts that in the metadata of the packet and strips those
bytes from the stream.
Inherits latency and throughput from `depacketizerC`.
-}
macDepacketizerC ::
forall dataWidth dom.
HiddenClockResetEnable dom =>
KnownNat dataWidth =>
1 <= dataWidth =>
(HiddenClockResetEnable dom) =>
(KnownNat dataWidth) =>
(1 <= dataWidth) =>
Circuit
(PacketStream dom dataWidth ())
(PacketStream dom dataWidth EthernetHeader)
Expand Down
15 changes: 10 additions & 5 deletions src/Clash/Cores/Ethernet/Mac/PaddingInserter.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# OPTIONS_HADDOCK hide #-}

{-|
Module : Clash.Cores.Ethernet.Mac.PaddingInserter
Description : Provides paddingInserterC for padding ethernet frames to a customizable amount of bytes.
Expand All @@ -17,8 +19,8 @@ import Data.Maybe.Extra ( toMaybe )


-- | State of the paddingInserter circuit.
-- Counts up to ceil(`padBytes`/`dataWidth`) packets, which is
-- the amount of packets needed to fill `padBytes` bytes.
-- Counts up to @ceil(padBytes / dataWidth)@ packets, which is
-- the amount of packets needed to fill @padBytes@ bytes.
data PaddingInserterState (dataWidth :: Nat) (padBytes :: Nat)
= Filling { count :: Index (DivRU padBytes dataWidth) }
| Full
Expand Down Expand Up @@ -77,16 +79,19 @@ paddingInserter _ = mealyB go (Filling 0)
-- and the _last of fwdIn
fwdOut = fwdIn {_last = guard done >> max lastIdx <$> _last fwdIn}

-- | Pads ethernet frames to a minimum of `padBytes` bytes.
-- Assumes that all invalid bytes are set to 0.
-- Sends bytes the same clock cycle as they are received.
{- |
Pads ethernet frames to a minimum of @padBytes@ bytes.
Requires that all invalid bytes are set to 0x00, otherwise
Sends bytes the same clock cycle as they are received.
-}
paddingInserterC
:: forall (dataWidth :: Nat) (padBytes :: Nat) (dom :: Domain)
. HiddenClockResetEnable dom
=> 1 <= dataWidth
=> 1 <= padBytes
=> KnownNat dataWidth
=> KnownNat padBytes
-- | The minimum size out output packets
=> SNat padBytes
-> Circuit (PacketStream dom dataWidth ()) (PacketStream dom dataWidth ())
paddingInserterC padBytes = fromSignals (paddingInserter padBytes)
Loading

0 comments on commit 9cf12fd

Please sign in to comment.