|
1 |
| -{-# language RecordWildCards #-} |
| 1 | +{-# LANGUAGE RecordWildCards #-} |
| 2 | +{-# OPTIONS_GHC -fplugin Protocols.Plugin #-} |
2 | 3 | {-# OPTIONS_HADDOCK hide #-}
|
3 | 4 |
|
4 |
| -module Clash.Cores.Ethernet.IP.EthernetStream |
5 |
| - (toEthernetStreamC) where |
| 5 | +module Clash.Cores.Ethernet.IP.EthernetStream ( |
| 6 | + toEthernetStreamC, |
| 7 | +) where |
6 | 8 |
|
7 | 9 | import Clash.Cores.Ethernet.Arp.ArpTypes
|
8 | 10 | import Clash.Cores.Ethernet.IP.IPv4Types
|
9 | 11 | import Clash.Cores.Ethernet.Mac.EthernetTypes
|
| 12 | + |
10 | 13 | import Clash.Prelude
|
11 |
| -import qualified Data.Bifunctor as B |
12 |
| -import Data.Maybe ( isJust ) |
| 14 | + |
| 15 | +import Data.Maybe (isJust) |
| 16 | + |
13 | 17 | import Protocols
|
14 | 18 | import Protocols.PacketStream
|
15 | 19 |
|
16 |
| --- | State of 'toEthernetStreamC'. |
| 20 | +-- | State of 'toEthernetStreamT'. |
17 | 21 | data EthernetStreamState
|
18 | 22 | = Idle
|
19 |
| - | DropPkt |
| 23 | + | DropPacket |
20 | 24 | | Forward {_mac :: MacAddress}
|
21 | 25 | deriving (Generic, NFDataX, Show, ShowX)
|
22 | 26 |
|
23 |
| --- | Takes our IPv4 address (as a signal), a packet stream with IPv4 addresses in the metadata, |
24 |
| --- performs an ARP lookup from a user-given ARP service, and |
25 |
| --- outputs the packet with a completed ethernet header containing |
26 |
| --- the IPv4 ether type, our IPv4 address and the looked up destination MAC. |
27 |
| --- If the ARP service gave an ArpEntryNotFound, then this circuit drops the |
28 |
| --- entire packet. It does not time out, instead expects the ARP service to send |
29 |
| --- an ArpEntryNotFound after an appropriate timeout. |
30 |
| -toEthernetStreamC |
31 |
| - :: forall (dom :: Domain) (dataWidth :: Nat) |
32 |
| - . HiddenClockResetEnable dom |
33 |
| - => KnownNat dataWidth |
34 |
| - => Signal dom MacAddress |
35 |
| - -- ^ My Mac address |
36 |
| - -> Circuit |
37 |
| - (PacketStream dom dataWidth IPv4Address) |
38 |
| - (PacketStream dom dataWidth EthernetHeader, ArpLookup dom) |
39 |
| -toEthernetStreamC myMac = fromSignals ckt |
40 |
| - where |
41 |
| - ckt |
42 |
| - :: (Signal dom (Maybe (PacketStreamM2S dataWidth IPv4Address)) |
43 |
| - , (Signal dom PacketStreamS2M, Signal dom (Maybe ArpResponse))) |
44 |
| - -> (Signal dom PacketStreamS2M |
45 |
| - , (Signal dom (Maybe (PacketStreamM2S dataWidth EthernetHeader)),Signal dom (Maybe IPv4Address))) |
46 |
| - ckt (packetInS, (ackInS, arpInS)) = (B.second unbundle . mealyB go Idle . B.second bundle) (myMac, packetInS, (ackInS, arpInS)) |
47 |
| - where |
48 |
| - go |
49 |
| - :: EthernetStreamState |
50 |
| - -> (MacAddress, Maybe (PacketStreamM2S dataWidth IPv4Address) |
51 |
| - , (PacketStreamS2M, Maybe ArpResponse)) |
52 |
| - -> (EthernetStreamState, (PacketStreamS2M |
53 |
| - , (Maybe (PacketStreamM2S dataWidth EthernetHeader), Maybe IPv4Address))) |
54 |
| - go Idle (_, pktIn, (_, arpResponse)) = (newSt, (PacketStreamS2M False, (Nothing, fmap _meta pktIn))) |
55 |
| - where |
56 |
| - newSt = case arpResponse of |
57 |
| - Nothing -> Idle |
58 |
| - Just ArpEntryNotFound -> DropPkt |
59 |
| - Just (ArpEntryFound ma) -> Forward{_mac = ma} |
60 |
| - go DropPkt (_, pktIn, (_, _)) |
61 |
| - = (nextSt, (PacketStreamS2M True, (Nothing, Nothing))) |
62 |
| - where |
63 |
| - pktInX = fromJustX pktIn |
64 |
| - nextSt = |
65 |
| - if isJust pktIn && isJust (_last pktInX) |
66 |
| - then Idle |
67 |
| - else DropPkt |
68 |
| - go st@Forward{..} (mac, pktIn, (PacketStreamS2M ack, _)) |
69 |
| - = (nextSt, (PacketStreamS2M ack, (pktOut, Nothing))) |
70 |
| - where |
71 |
| - pktInX = fromJustX pktIn |
72 |
| - nextSt = |
73 |
| - if isJust pktIn && isJust (_last pktInX) && ack |
74 |
| - then Idle |
75 |
| - else st |
76 |
| - hdr = EthernetHeader _mac mac 0x0800 |
77 |
| - pktOut = fmap (hdr <$) pktIn |
| 27 | +-- | State transition function of 'toEthernetStreamC'. |
| 28 | +toEthernetStreamT :: |
| 29 | + forall (dataWidth :: Nat). |
| 30 | + (KnownNat dataWidth) => |
| 31 | + EthernetStreamState -> |
| 32 | + ( Maybe (PacketStreamM2S dataWidth IPv4Address) |
| 33 | + , PacketStreamS2M |
| 34 | + , Maybe ArpResponse |
| 35 | + ) -> |
| 36 | + ( EthernetStreamState |
| 37 | + , ( PacketStreamS2M |
| 38 | + , Maybe (PacketStreamM2S dataWidth MacAddress) |
| 39 | + , Maybe IPv4Address |
| 40 | + ) |
| 41 | + ) |
| 42 | +toEthernetStreamT Idle (transferInM, _, arpResp) = |
| 43 | + (nextSt, (PacketStreamS2M False, Nothing, _meta <$> transferInM)) |
| 44 | + where |
| 45 | + nextSt = case arpResp of |
| 46 | + Nothing -> Idle |
| 47 | + Just ArpEntryNotFound -> DropPacket |
| 48 | + Just (ArpEntryFound mac) -> Forward{_mac = mac} |
| 49 | +toEthernetStreamT DropPacket (Just transferIn, _, _) = |
| 50 | + (nextSt, (PacketStreamS2M True, Nothing, Nothing)) |
| 51 | + where |
| 52 | + nextSt = if isJust (_last transferIn) then Idle else DropPacket |
| 53 | +toEthernetStreamT st@Forward{..} (Just transferIn, PacketStreamS2M readyIn, _) = |
| 54 | + (nextSt, (PacketStreamS2M readyIn, Just (_mac <$ transferIn), Nothing)) |
| 55 | + where |
| 56 | + nextSt = if isJust (_last transferIn) && readyIn then Idle else st |
| 57 | +toEthernetStreamT st (Nothing, _, _) = (st, (PacketStreamS2M True, Nothing, Nothing)) |
| 58 | + |
| 59 | +{- | |
| 60 | +Bridges the gap between the IPv4 and MAC layer by transforming packets directed |
| 61 | +to an IPv4 address (in the metadata) to packets directed to a MAC address. |
| 62 | +It does so by sending the IPv4 address in the metadata to the ARP service, |
| 63 | +for each packet in the stream. If the ARP service responds with 'ArpEntryNotFound', |
| 64 | +the packet is dropped to avoid stalling the network stack. |
| 65 | +
|
| 66 | +The maximum latency per packet depends on the configuration of the ARP service, |
| 67 | +there are no timers in this component. |
| 68 | +-} |
| 69 | +toEthernetStreamC :: |
| 70 | + forall (dataWidth :: Nat) (dom :: Domain). |
| 71 | + (HiddenClockResetEnable dom) => |
| 72 | + (KnownNat dataWidth) => |
| 73 | + -- | Our MAC address |
| 74 | + Signal dom MacAddress -> |
| 75 | + Circuit |
| 76 | + (PacketStream dom dataWidth IPv4Address) |
| 77 | + (PacketStream dom dataWidth EthernetHeader, ArpLookup dom) |
| 78 | +toEthernetStreamC ourMacS = circuit $ \transferIn -> do |
| 79 | + (withDstMac, req) <- fromSignals resolver -< transferIn |
| 80 | + withEthernetHeader <- |
| 81 | + mapMetaS ((\src dst -> EthernetHeader dst src 0x0800) <$> ourMacS) -< withDstMac |
| 82 | + idC -< (withEthernetHeader, req) |
| 83 | + where |
| 84 | + resolver (transferIn, (readyIn, respIn)) = (readyOut, (transferOut, reqOut)) |
| 85 | + where |
| 86 | + (readyOut, transferOut, reqOut) = |
| 87 | + mealyB toEthernetStreamT Idle (transferIn, readyIn, respIn) |
0 commit comments