hans-3.0.2: Network Stack

Safe HaskellNone
LanguageHaskell2010

Hans.IP4.Packet

Synopsis

Documentation

newtype IP4 Source #

Constructors

IP4 Word32 

Instances

Eq IP4 Source # 

Methods

(==) :: IP4 -> IP4 -> Bool #

(/=) :: IP4 -> IP4 -> Bool #

Ord IP4 Source # 

Methods

compare :: IP4 -> IP4 -> Ordering #

(<) :: IP4 -> IP4 -> Bool #

(<=) :: IP4 -> IP4 -> Bool #

(>) :: IP4 -> IP4 -> Bool #

(>=) :: IP4 -> IP4 -> Bool #

max :: IP4 -> IP4 -> IP4 #

min :: IP4 -> IP4 -> IP4 #

Read IP4 Source # 
Show IP4 Source # 

Methods

showsPrec :: Int -> IP4 -> ShowS #

show :: IP4 -> String #

showList :: [IP4] -> ShowS #

Generic IP4 Source # 

Associated Types

type Rep IP4 :: * -> * #

Methods

from :: IP4 -> Rep IP4 x #

to :: Rep IP4 x -> IP4 #

Serialize IP4 Source # 

Methods

put :: Putter IP4 #

get :: Get IP4 #

Hashable IP4 Source # 

Methods

hashWithSalt :: Int -> IP4 -> Int #

hash :: IP4 -> Int #

Checksum IP4 Source # 
CodecAtom IP4 Source # 
Option IP4 Source # 
NetworkAddr IP4 Source # 
Network IP4 Source # 
type Rep IP4 Source # 
type Rep IP4 = D1 (MetaData "IP4" "Hans.IP4.Packet" "hans-3.0.2-GPIpvDF0acQKMmo8PFxkX0" True) (C1 (MetaCons "IP4" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))

pattern WildcardIP4 :: IP4 Source #

ip4PseudoHeader :: IP4 -> IP4 -> NetworkProtocol -> Int -> PartialChecksum Source #

source address | +--------+--------+--------+--------+ | destination address | +--------+--------+--------+--------+ | zero |protocol| length | +--------+--------+--------+--------+

ip4FragmentOffset :: Lens' IP4Header Word16 Source #

The fragment offset, in bytes.

ip4PacketSize :: IP4Header -> ByteString -> Int Source #

Calculate the size of an IP4 packet

ip4HeaderSize :: IP4Header -> Int Source #

Calculate the size of an IP4 header

splitPacket :: Int -> IP4Header -> ByteString -> [(IP4Header, ByteString)] Source #

Fragment a single IP packet into one or more, given an MTU to fit into.

fragmentPacket :: Int64 -> IP4Header -> ByteString -> [(IP4Header, ByteString)] Source #

Given a fragment size and a packet, fragment the packet into multiple smaller ones.

ip4VersionIHL :: Int -> Word8 Source #

Compute the value of the version/header length byte.

getIP4Packet :: Get (IP4Header, Int, Int) Source #

Version| IHL |Type of Service| Total Length | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Identification |Flags| Fragment Offset | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Time to Live | Protocol | Header Checksum | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Source Address | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Destination Address | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+

data ArpPacket Source #

Arp packets, specialized to IP4 and Mac addresses.

Constructors

ArpPacket 

Fields

getArpPacket :: Get ArpPacket Source #

Parse an Arp packet, given a way to parse hardware and protocol addresses.

putArpPacket :: Putter ArpPacket Source #

Render an Arp packet, given a way to render hardware and protocol addresses.

pattern ArpRequest :: forall a. (Num a, Eq a) => a Source #

pattern ArpReply :: forall a. (Num a, Eq a) => a Source #

getArpOper :: Get ArpOper Source #

Parse an Arp operation.

putArpOper :: Putter ArpOper Source #

Render an Arp operation.