Skip to content

Commit

Permalink
Add top level IPv4 module, move InternetChecksum out of IP module
Browse files Browse the repository at this point in the history
  • Loading branch information
t-wallet committed Sep 16, 2024
1 parent 3b031f2 commit 52a3f2d
Show file tree
Hide file tree
Showing 11 changed files with 36 additions and 12 deletions.
5 changes: 3 additions & 2 deletions clash-cores.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -136,8 +136,9 @@ library
Clash.Cores.Ethernet.Examples.RxStacks
Clash.Cores.Ethernet.Examples.TxStacks
Clash.Cores.Ethernet.Icmp
Clash.Cores.Ethernet.InternetChecksum
Clash.Cores.Ethernet.IPv4
Clash.Cores.Ethernet.IP.EthernetStream
Clash.Cores.Ethernet.IP.InternetChecksum
Clash.Cores.Ethernet.IP.IPPacketizers
Clash.Cores.Ethernet.IP.IPv4Types
Clash.Cores.Ethernet.Mac
Expand Down Expand Up @@ -225,9 +226,9 @@ test-suite unittests
Test.Cores.Ethernet
Test.Cores.Ethernet.Arp.ArpManager
Test.Cores.Ethernet.Base
Test.Cores.Ethernet.InternetChecksum
Test.Cores.Ethernet.Icmp
Test.Cores.Ethernet.IP.EthernetStream
Test.Cores.Ethernet.IP.InternetChecksum
Test.Cores.Ethernet.IP.IPPacketizers
Test.Cores.Ethernet.Mac.FrameCheckSequence
Test.Cores.Ethernet.Mac.InterpacketGapInserter
Expand Down
2 changes: 2 additions & 0 deletions src/Clash/Cores/Ethernet/IP/EthernetStream.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
{-# language RecordWildCards #-}
{-# OPTIONS_HADDOCK hide #-}

module Clash.Cores.Ethernet.IP.EthernetStream
(toEthernetStreamC) where

Expand Down
3 changes: 2 additions & 1 deletion src/Clash/Cores/Ethernet/IP/IPPacketizers.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_HADDOCK hide #-}

{-|
Module : Clash.Cores.Ethernet.IP.IPPacketizers
Expand All @@ -17,7 +18,7 @@ import Clash.Prelude
import Protocols
import Protocols.PacketStream

import Clash.Cores.Ethernet.IP.InternetChecksum
import Clash.Cores.Ethernet.InternetChecksum
import Clash.Cores.Ethernet.IP.IPv4Types
import Clash.Cores.Ethernet.Mac.EthernetTypes

Expand Down
1 change: 1 addition & 0 deletions src/Clash/Cores/Ethernet/IP/IPv4Types.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# language RecordWildCards #-}
{-# OPTIONS_HADDOCK hide #-}

{-|
Module : Clash.Cores.Ethernet.IP.IPv4Types
Expand Down
19 changes: 19 additions & 0 deletions src/Clash/Cores/Ethernet/IPv4.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
{- |
Copyright : (C) 2024, QBayLogic B.V.
License : BSD2 (see the file LICENSE)
Maintainer : QBayLogic B.V. <[email protected]>
Provides various components to handle the IPv4 protocol.
-}
module Clash.Cores.Ethernet.IPv4 (
-- * Data types, constants and simple utilities
module Clash.Cores.Ethernet.IP.IPv4Types,
-- * Querying the ARP subsystem
module Clash.Cores.Ethernet.IP.EthernetStream,
-- * (De)packetizing IPv4 headers
module Clash.Cores.Ethernet.IP.IPPacketizers,
) where

import Clash.Cores.Ethernet.IP.EthernetStream
import Clash.Cores.Ethernet.IP.IPv4Types
import Clash.Cores.Ethernet.IP.IPPacketizers
2 changes: 1 addition & 1 deletion src/Clash/Cores/Ethernet/Icmp.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Protocols (Circuit, (|>))
import Protocols.PacketStream

import Clash.Cores.Ethernet.IP.IPv4Types (IPv4Address (..), IPv4HeaderLite (..))
import Clash.Cores.Ethernet.IP.InternetChecksum (onesComplementAdd)
import Clash.Cores.Ethernet.InternetChecksum (onesComplementAdd)

-- | Full ICMP header.
data IcmpHeader = IcmpHeader
Expand Down
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
{-# LANGUAGE ViewPatterns #-}

{-|
Module : Clash.Cores.Ethernet.IP.InternetChecksum
Module : Clash.Cores.Ethernet.InternetChecksum
Description : Functions for computing the RFC1071 internet checksum.
-}
module Clash.Cores.Ethernet.IP.InternetChecksum
module Clash.Cores.Ethernet.InternetChecksum
( internetChecksum
, reduceToInternetChecksum
, pipelinedInternetChecksum
Expand Down
4 changes: 2 additions & 2 deletions test/Test/Cores/Ethernet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@ module Test.Cores.Ethernet (
import Test.Tasty
import qualified Test.Cores.Ethernet.Arp.ArpManager
import qualified Test.Cores.Ethernet.Icmp
import qualified Test.Cores.Ethernet.InternetChecksum
import qualified Test.Cores.Ethernet.IP.EthernetStream
import qualified Test.Cores.Ethernet.IP.InternetChecksum
import qualified Test.Cores.Ethernet.IP.IPPacketizers
import qualified Test.Cores.Ethernet.Mac.FrameCheckSequence
import qualified Test.Cores.Ethernet.Mac.InterpacketGapInserter
Expand All @@ -19,8 +19,8 @@ tests =
"Ethernet"
[ Test.Cores.Ethernet.Arp.ArpManager.tests
, Test.Cores.Ethernet.Icmp.tests
, Test.Cores.Ethernet.InternetChecksum.tests
, Test.Cores.Ethernet.IP.EthernetStream.tests
, Test.Cores.Ethernet.IP.InternetChecksum.tests
, Test.Cores.Ethernet.IP.IPPacketizers.tests
, Test.Cores.Ethernet.Mac.FrameCheckSequence.tests
, Test.Cores.Ethernet.Mac.InterpacketGapInserter.tests
Expand Down
2 changes: 1 addition & 1 deletion test/Test/Cores/Ethernet/IP/IPPacketizers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ import Protocols.PacketStream
import Protocols.PacketStream.Hedgehog

import Test.Cores.Ethernet.Base
import Test.Cores.Ethernet.IP.InternetChecksum (pureInternetChecksum)
import Test.Cores.Ethernet.InternetChecksum (pureInternetChecksum)

import Test.Tasty
import Test.Tasty.Hedgehog (HedgehogTestLimit (HedgehogTestLimit))
Expand Down
2 changes: 1 addition & 1 deletion test/Test/Cores/Ethernet/Icmp.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import Protocols.PacketStream (PacketStreamM2S(_meta))
import Protocols.PacketStream.Hedgehog

import Test.Cores.Ethernet.Base (genIPv4HeaderLite)
import Test.Cores.Ethernet.IP.InternetChecksum (calculateChecksum)
import Test.Cores.Ethernet.InternetChecksum (calculateChecksum)

import Test.Tasty
import Test.Tasty.Hedgehog (HedgehogTestLimit (HedgehogTestLimit))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
{-# language RecordWildCards #-}
{-# LANGUAGE TupleSections #-}

module Test.Cores.Ethernet.IP.InternetChecksum where
module Test.Cores.Ethernet.InternetChecksum where

-- base
import Data.Maybe
Expand All @@ -26,7 +26,7 @@ import Test.Tasty.Hedgehog.Extra ( testProperty )
import Test.Tasty.TH ( testGroupGenerator )

-- ethernet
import Clash.Cores.Ethernet.IP.InternetChecksum
import Clash.Cores.Ethernet.InternetChecksum

import Protocols.PacketStream
import Protocols.PacketStream.Hedgehog
Expand Down

0 comments on commit 52a3f2d

Please sign in to comment.