ip-1.3.0: Library for IP and MAC addresses

Safe HaskellNone
LanguageHaskell2010

Net.Types

Synopsis

Documentation

newtype IPv4 Source #

A 32-bit Internet Protocol version 4 address. To use this with the network library, it is necessary to use Network.Socket.htonl to convert the underlying Word32 from host byte order to network byte order.

Constructors

IPv4 

Fields

Instances

Bounded IPv4 Source # 
Enum IPv4 Source # 

Methods

succ :: IPv4 -> IPv4 #

pred :: IPv4 -> IPv4 #

toEnum :: Int -> IPv4 #

fromEnum :: IPv4 -> Int #

enumFrom :: IPv4 -> [IPv4] #

enumFromThen :: IPv4 -> IPv4 -> [IPv4] #

enumFromTo :: IPv4 -> IPv4 -> [IPv4] #

enumFromThenTo :: IPv4 -> IPv4 -> IPv4 -> [IPv4] #

Eq IPv4 Source # 

Methods

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

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

Ord IPv4 Source # 

Methods

compare :: IPv4 -> IPv4 -> Ordering #

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

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

(>) :: IPv4 -> IPv4 -> Bool #

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

max :: IPv4 -> IPv4 -> IPv4 #

min :: IPv4 -> IPv4 -> IPv4 #

Read IPv4 Source # 
Show IPv4 Source # 

Methods

showsPrec :: Int -> IPv4 -> ShowS #

show :: IPv4 -> String #

showList :: [IPv4] -> ShowS #

Generic IPv4 Source # 

Associated Types

type Rep IPv4 :: * -> * #

Methods

from :: IPv4 -> Rep IPv4 x #

to :: Rep IPv4 x -> IPv4 #

Hashable IPv4 Source # 

Methods

hashWithSalt :: Int -> IPv4 -> Int #

hash :: IPv4 -> Int #

ToJSON IPv4 Source # 
ToJSONKey IPv4 Source # 
FromJSON IPv4 Source # 
FromJSONKey IPv4 Source # 
Storable IPv4 Source # 

Methods

sizeOf :: IPv4 -> Int #

alignment :: IPv4 -> Int #

peekElemOff :: Ptr IPv4 -> Int -> IO IPv4 #

pokeElemOff :: Ptr IPv4 -> Int -> IPv4 -> IO () #

peekByteOff :: Ptr b -> Int -> IO IPv4 #

pokeByteOff :: Ptr b -> Int -> IPv4 -> IO () #

peek :: Ptr IPv4 -> IO IPv4 #

poke :: Ptr IPv4 -> IPv4 -> IO () #

Bits IPv4 Source #

Note: we use network order (big endian) as opposed to host order (little endian) which differs from the underlying IPv4 type representation.

FiniteBits IPv4 Source # 
Prim IPv4 Source # 
Unbox IPv4 Source # 
Vector Vector IPv4 Source # 
MVector MVector IPv4 Source # 
type Rep IPv4 Source # 
type Rep IPv4 = D1 * (MetaData "IPv4" "Net.IPv4" "ip-1.3.0-8akPoClmXX6CvMDevW5iZ7" True) (C1 * (MetaCons "IPv4" PrefixI True) (S1 * (MetaSel (Just Symbol "getIPv4") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32)))
data Vector IPv4 Source # 
data MVector s IPv4 Source # 

data IPv6 Source #

A 128-bit Internet Protocol version 6 address.

Constructors

IPv6 

Fields

Instances

Eq IPv6 Source # 

Methods

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

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

Ord IPv6 Source # 

Methods

compare :: IPv6 -> IPv6 -> Ordering #

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

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

(>) :: IPv6 -> IPv6 -> Bool #

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

max :: IPv6 -> IPv6 -> IPv6 #

min :: IPv6 -> IPv6 -> IPv6 #

Read IPv6 Source # 
Show IPv6 Source # 

Methods

showsPrec :: Int -> IPv6 -> ShowS #

show :: IPv6 -> String #

showList :: [IPv6] -> ShowS #

ToJSON IPv6 Source # 
FromJSON IPv6 Source # 
Prim IPv6 Source # 

newtype IP Source #

A 32-bit IPv4 address or a 128-bit IPv6 address. Internally, this is just represented as an IPv6 address. The functions provided in Net.IP help simulate constructing and pattern matching on values of this type. All functions and typeclass methods that convert IP values to text will display it as an IPv4 address if possible.

Constructors

IP 

Fields

Instances

Eq IP Source # 

Methods

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

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

Ord IP Source # 

Methods

compare :: IP -> IP -> Ordering #

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

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

(>) :: IP -> IP -> Bool #

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

max :: IP -> IP -> IP #

min :: IP -> IP -> IP #

Read IP Source # 
Show IP Source # 

Methods

showsPrec :: Int -> IP -> ShowS #

show :: IP -> String #

showList :: [IP] -> ShowS #

ToJSON IP Source # 
FromJSON IP Source # 

data IPv4Range Source #

The length should be between 0 and 32. These bounds are inclusive. This expectation is not in any way enforced by this library because it does not cause errors. A mask length greater than 32 will be treated as if it were 32.

Constructors

IPv4Range 

Instances

Eq IPv4Range Source # 
Ord IPv4Range Source # 
Read IPv4Range Source # 
Show IPv4Range Source # 
Generic IPv4Range Source # 

Associated Types

type Rep IPv4Range :: * -> * #

Hashable IPv4Range Source # 
ToJSON IPv4Range Source # 
FromJSON IPv4Range Source # 
Bits IPv4Range Source #

Notes:

  • bit operations use network order (big endian),
  • do not operate on host bits,
  • return a normalized range dropping host bits,
  • and "promote operands" by extending the length to the larger of two ranges.
FiniteBits IPv4Range Source #

Note: the size is determined by the range length

Unbox IPv4Range Source # 
Vector Vector IPv4Range Source # 
MVector MVector IPv4Range Source # 
type Rep IPv4Range Source # 
type Rep IPv4Range = D1 * (MetaData "IPv4Range" "Net.IPv4.Range" "ip-1.3.0-8akPoClmXX6CvMDevW5iZ7" False) (C1 * (MetaCons "IPv4Range" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "ipv4RangeBase") SourceUnpack SourceStrict DecidedStrict) (Rec0 * IPv4)) (S1 * (MetaSel (Just Symbol "ipv4RangeLength") SourceUnpack SourceStrict DecidedStrict) (Rec0 * Word8))))
data Vector IPv4Range Source # 
data MVector s IPv4Range Source # 

newtype Mac Source #

A 48-bit MAC address. Do not use the data constructor for this type. It is not considered part of the stable API, and it allows you to construct invalid MAC addresses.

Constructors

Mac Word64 

Instances

Eq Mac Source # 

Methods

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

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

Ord Mac Source # 

Methods

compare :: Mac -> Mac -> Ordering #

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

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

(>) :: Mac -> Mac -> Bool #

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

max :: Mac -> Mac -> Mac #

min :: Mac -> Mac -> Mac #

Read Mac Source # 
Show Mac Source # 

Methods

showsPrec :: Int -> Mac -> ShowS #

show :: Mac -> String #

showList :: [Mac] -> ShowS #

Generic Mac Source # 

Associated Types

type Rep Mac :: * -> * #

Methods

from :: Mac -> Rep Mac x #

to :: Rep Mac x -> Mac #

Hashable Mac Source # 

Methods

hashWithSalt :: Int -> Mac -> Int #

hash :: Mac -> Int #

ToJSON Mac Source # 
ToJSONKey Mac Source # 
FromJSON Mac Source # 
FromJSONKey Mac Source # 
Prim Mac Source #

This only preserves the lower 6 bytes of the 8-byte word that backs a mac address. It runs slower than it would if it used a full 8-byte word, but it consumes less space. When storing millions of mac addresses, this is a good trade to make. When storing a small number of mac address, it might be preferable to make a primitive array of Word64 instead and use the mac address data constructor to coerce between the two.

type Rep Mac Source # 
type Rep Mac = D1 * (MetaData "Mac" "Net.Mac" "ip-1.3.0-8akPoClmXX6CvMDevW5iZ7" True) (C1 * (MetaCons "Mac" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word64)))

data MacGrouping Source #

The format expected by the mac address parser. The Word8 taken by some of these constructors is the ascii value of the character to be used as the separator. This is typically a colon, a hyphen, or a space character. All decoding functions are case insensitive.

Constructors

MacGroupingPairs !Char

Two-character groups, FA:2B:40:09:8C:11

MacGroupingTriples !Char

Three-character groups, 24B-F0A-025-829

MacGroupingQuadruples !Char

Four-character groups, A220.0745.CAC7

MacGroupingNoSeparator

No separator, 24AF4B5B0780

Instances

Eq MacGrouping Source # 
Ord MacGrouping Source # 
Read MacGrouping Source # 
Show MacGrouping Source # 
Generic MacGrouping Source # 

Associated Types

type Rep MacGrouping :: * -> * #

type Rep MacGrouping Source # 
type Rep MacGrouping = D1 * (MetaData "MacGrouping" "Net.Mac" "ip-1.3.0-8akPoClmXX6CvMDevW5iZ7" False) ((:+:) * ((:+:) * (C1 * (MetaCons "MacGroupingPairs" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Char))) (C1 * (MetaCons "MacGroupingTriples" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Char)))) ((:+:) * (C1 * (MetaCons "MacGroupingQuadruples" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Char))) (C1 * (MetaCons "MacGroupingNoSeparator" PrefixI False) (U1 *))))