ip-1.4.2.1: Library for IP and MAC addresses

Safe HaskellNone
LanguageHaskell2010

Net.IPv4

Contents

Description

This module provides the IPv4 data type and functions for working with it.

Synopsis

Conversion Functions

ipv4 :: Word8 -> Word8 -> Word8 -> Word8 -> IPv4 Source #

Create an IPv4 address from four octets. The first argument is the most significant octet. The last argument is the least significant. Since IP addresses are commonly written using dot-decimal notation, this is the recommended way to create an IP address. Additionally, it is used for the Show and Read instances of IPv4 to help keep things readable in GHCi.

>>> let addr = ipv4 192 168 1 1
>>> addr
ipv4 192 168 1 1
>>> getIPv4 addr
3232235777

fromOctets :: Word8 -> Word8 -> Word8 -> Word8 -> IPv4 Source #

An alias for the ipv4 smart constructor.

fromTupleOctets :: (Word8, Word8, Word8, Word8) -> IPv4 Source #

An uncurried variant of fromOctets.

toOctets :: IPv4 -> (Word8, Word8, Word8, Word8) Source #

Convert an IPv4 address into a quadruple of octets. The first element in the quadruple is the most significant octet. The last element is the least significant octet.

Special IP Addresses

any :: IPv4 Source #

The IP address representing any host.

>>> any
ipv4 0 0 0 0

loopback :: IPv4 Source #

The local loopback IP address.

>>> loopback
ipv4 127 0 0 1

localhost :: IPv4 Source #

A useful and common alias for loopback.

>>> localhost
ipv4 127 0 0 1

broadcast :: IPv4 Source #

The broadcast IP address.

>>> broadcast
ipv4 255 255 255 255

Range Predicates

private :: IPv4 -> Bool Source #

Checks to see if the IPv4 address belongs to a private network. The three private networks that are checked are 10.0.0.0/8, 172.16.0.0/12, and 192.168.0.0/16.

reserved :: IPv4 -> Bool Source #

Checks to see if the IPv4 address belongs to a reserved network. This includes the three private networks that private checks along with several other ranges that are not used on the public Internet.

public :: IPv4 -> Bool Source #

Checks to see if the IPv4 address is publicly routable.

public x == not (reserved x)

Textual Conversion

Text

encode :: IPv4 -> Text Source #

Encode an IPv4 address to Text using dot-decimal notation:

>>> T.putStrLn (encode (ipv4 192 168 2 47))
192.168.2.47

decode :: Text -> Maybe IPv4 Source #

Decode an IPv4 address.

>>> decode (Text.pack "192.168.2.47")
Just (ipv4 192 168 2 47)
>>> decode (Text.pack "10.100.256.256")
Nothing

builder :: IPv4 -> Builder Source #

Encode an IPv4 address to a text Builder.

>>> builder (ipv4 192 168 2 47)
"192.168.2.47"

reader :: Reader IPv4 Source #

Parse an IPv4 address using a Reader.

>>> reader (Text.pack "192.168.2.47")
Right (ipv4 192 168 2 47,"")
>>> reader (Text.pack "192.168.2.470")
Left "All octets in an IPv4 address must be between 0 and 255"

parser :: Parser IPv4 Source #

Parse an IPv4 address using a Parser.

>>> AT.parseOnly parser (Text.pack "192.168.2.47")
Right (ipv4 192 168 2 47)
>>> AT.parseOnly parser (Text.pack "192.168.2.470")
Left "Failed reading: All octets in an IPv4 address must be between 0 and 255"

UTF-8 ByteString

encodeUtf8 :: IPv4 -> ByteString Source #

Encode an IPv4 address to a UTF-8 encoded ByteString.

>>> encodeUtf8 (ipv4 192 168 2 47)
"192.168.2.47"

decodeUtf8 :: ByteString -> Maybe IPv4 Source #

Decode a UTF8-encoded ByteString into an IPv4.

>>> decodeUtf8 (BC8.pack "192.168.2.47")
Just (ipv4 192 168 2 47)

parserUtf8 :: Parser IPv4 Source #

Parse an IPv4 using a Parser.

>>> AB.parseOnly parserUtf8 (BC8.pack "192.168.2.47")
Right (ipv4 192 168 2 47)
>>> AB.parseOnly parserUtf8 (BC8.pack "192.168.2.470")
Left "Failed reading: All octets in an ipv4 address must be between 0 and 255"

String

These functions exist for the convenience of those who need a String representation of an IPv4 address. Using them is discouraged unless the end user is working with a library that can only use String to deal with textual data (such as pandoc, hxr, or network).

encodeString :: IPv4 -> String Source #

Encode an IPv4 as a String.

decodeString :: String -> Maybe IPv4 Source #

Decode an IPv4 from a String.

Printing

print :: IPv4 -> IO () Source #

Print an IPv4 using the textual encoding.

IPv4 Ranges

Range functions

range :: IPv4 -> Word8 -> IPv4Range Source #

Smart constructor for IPv4Range. Ensures the mask is appropriately sized and sets masked bits in the IPv4 to zero.

fromBounds :: IPv4 -> IPv4 -> IPv4Range Source #

Given an inclusive lower and upper ip address, create the smallest IPv4Range that contains the two. This is helpful in situations where input given as a range like 192.168.16.0-192.168.19.255 needs to be handled. This makes the range broader if it cannot be represented in CIDR notation.

>>> printRange $ fromBounds (fromOctets 192 168 16 0) (fromOctets 192 168 19 255)
192.168.16.0/22
>>> printRange $ fromBounds (fromOctets 10 0 5 7) (fromOctets 10 0 5 14)
10.0.5.0/28

normalize :: IPv4Range -> IPv4Range Source #

Normalize an IPv4Range. The first result of this is that the IPv4 inside the IPv4Range is changed so that the insignificant bits are zeroed out. For example:

>>> printRange $ normalize $ IPv4Range (fromOctets 192 168 1 19) 24
192.168.1.0/24
>>> printRange $ normalize $ IPv4Range (fromOctets 192 168 1 163) 28
192.168.1.160/28

The second effect of this is that the mask length is lowered to be 32 or smaller. Working with IPv4Ranges that have not been normalized does not cause any issues for this library, although other applications may reject such ranges (especially those with a mask length above 32).

Note that normalize is idempotent, that is:

normalize r == (normalize . normalize) r

contains :: IPv4Range -> IPv4 -> Bool Source #

Checks to see if an IPv4 address belongs in the IPv4Range.

>>> let ip = fromOctets 10 10 1 92
>>> contains (IPv4Range (fromOctets 10 0 0 0) 8) ip
True
>>> contains (IPv4Range (fromOctets 10 11 0 0) 16) ip
False

Typically, element-testing functions are written to take the element as the first argument and the set as the second argument. This is intentionally written the other way for better performance when iterating over a collection. For example, you might test elements in a list for membership like this:

>>> let r = IPv4Range (fromOctets 10 10 10 6) 31
>>> mapM_ (P.print . contains r) (take 5 $ iterate succ $ fromOctets 10 10 10 5)
False
True
True
False
False

The implementation of contains ensures that (with GHC), the bitmask creation and range normalization only occur once in the above example. They are reused as the list is iterated.

member :: IPv4 -> IPv4Range -> Bool Source #

This is provided to mirror the interface provided by Data.Set. It behaves just like contains but with flipped arguments.

member ip r == contains r ip

lowerInclusive :: IPv4Range -> IPv4 Source #

The inclusive lower bound of an IPv4Range. This is conventionally understood to be the broadcast address of a subnet. For example:

>>> T.putStrLn $ encode $ lowerInclusive $ IPv4Range (ipv4 10 10 1 160) 25
10.10.1.128

Note that the lower bound of a normalized IPv4Range is simply the ip address of the range:

lowerInclusive r == ipv4RangeBase (normalize r)

upperInclusive :: IPv4Range -> IPv4 Source #

The inclusive upper bound of an IPv4Range.

>>> T.putStrLn $ encode $ upperInclusive $ IPv4Range (ipv4 10 10 1 160) 25
10.10.1.255

Conversion to IPv4

toList :: IPv4Range -> [IPv4] Source #

Convert an IPv4Range into a list of the IPv4 addresses that are in it.

>>> let r = IPv4Range (fromOctets 192 168 1 8) 30
>>> mapM_ (T.putStrLn . encode) (toList r)
192.168.1.8
192.168.1.9
192.168.1.10
192.168.1.11

toGenerator :: MonadPlus m => IPv4Range -> m IPv4 Source #

A stream-polymorphic generator over an IPv4Range. For more information, see How to build library-agnostic streaming sources.

Private Ranges

private24 :: IPv4Range Source #

The RFC1918 24-bit block. Subnet mask: 10.0.0.0/8

private20 :: IPv4Range Source #

The RFC1918 20-bit block. Subnet mask: 172.16.0.0/12

private16 :: IPv4Range Source #

The RFC1918 16-bit block. Subnet mask: 192.168.0.0/16

Textual Conversion

Text

parserRange :: Parser IPv4Range Source #

Parse an IPv4Range using a 'AT.Parser.'

printRange :: IPv4Range -> IO () Source #

This exists mostly for testing purposes.

Types

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 # 
Instance details

Defined in Net.IPv4

Enum IPv4 Source # 
Instance details

Defined in Net.IPv4

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 # 
Instance details

Defined in Net.IPv4

Methods

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

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

Ord IPv4 Source # 
Instance details

Defined in Net.IPv4

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 # 
Instance details

Defined in Net.IPv4

Show IPv4 Source # 
Instance details

Defined in Net.IPv4

Methods

showsPrec :: Int -> IPv4 -> ShowS #

show :: IPv4 -> String #

showList :: [IPv4] -> ShowS #

Generic IPv4 Source # 
Instance details

Defined in Net.IPv4

Associated Types

type Rep IPv4 :: Type -> Type #

Methods

from :: IPv4 -> Rep IPv4 x #

to :: Rep IPv4 x -> IPv4 #

Hashable IPv4 Source # 
Instance details

Defined in Net.IPv4

Methods

hashWithSalt :: Int -> IPv4 -> Int #

hash :: IPv4 -> Int #

ToJSON IPv4 Source # 
Instance details

Defined in Net.IPv4

ToJSONKey IPv4 Source # 
Instance details

Defined in Net.IPv4

FromJSON IPv4 Source # 
Instance details

Defined in Net.IPv4

FromJSONKey IPv4 Source # 
Instance details

Defined in Net.IPv4

Storable IPv4 Source # 
Instance details

Defined in Net.IPv4

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.

Instance details

Defined in Net.IPv4

FiniteBits IPv4 Source # 
Instance details

Defined in Net.IPv4

NFData IPv4 Source # 
Instance details

Defined in Net.IPv4

Methods

rnf :: IPv4 -> () #

Prim IPv4 Source # 
Instance details

Defined in Net.IPv4

Unbox IPv4 Source # 
Instance details

Defined in Net.IPv4

Vector Vector IPv4 Source # 
Instance details

Defined in Net.IPv4

MVector MVector IPv4 Source # 
Instance details

Defined in Net.IPv4

type Rep IPv4 Source # 
Instance details

Defined in Net.IPv4

type Rep IPv4 = D1 (MetaData "IPv4" "Net.IPv4" "ip-1.4.2.1-1kdobq8onQp8hYPnvSg0GR" True) (C1 (MetaCons "IPv4" PrefixI True) (S1 (MetaSel (Just "getIPv4") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))
newtype Vector IPv4 Source # 
Instance details

Defined in Net.IPv4

newtype MVector s IPv4 Source # 
Instance details

Defined in Net.IPv4

newtype MVector s IPv4 = MV_IPv4 (MVector s IPv4)

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 # 
Instance details

Defined in Net.IPv4

Ord IPv4Range Source # 
Instance details

Defined in Net.IPv4

Read IPv4Range Source # 
Instance details

Defined in Net.IPv4

Show IPv4Range Source # 
Instance details

Defined in Net.IPv4

Generic IPv4Range Source # 
Instance details

Defined in Net.IPv4

Associated Types

type Rep IPv4Range :: Type -> Type #

Hashable IPv4Range Source # 
Instance details

Defined in Net.IPv4

ToJSON IPv4Range Source # 
Instance details

Defined in Net.IPv4

FromJSON IPv4Range Source # 
Instance details

Defined in Net.IPv4

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.
Instance details

Defined in Net.IPv4

FiniteBits IPv4Range Source #

Note: the size is determined by the range length

Instance details

Defined in Net.IPv4

NFData IPv4Range Source # 
Instance details

Defined in Net.IPv4

Methods

rnf :: IPv4Range -> () #

Unbox IPv4Range Source # 
Instance details

Defined in Net.IPv4

Vector Vector IPv4Range Source # 
Instance details

Defined in Net.IPv4

MVector MVector IPv4Range Source # 
Instance details

Defined in Net.IPv4

type Rep IPv4Range Source # 
Instance details

Defined in Net.IPv4

type Rep IPv4Range = D1 (MetaData "IPv4Range" "Net.IPv4" "ip-1.4.2.1-1kdobq8onQp8hYPnvSg0GR" False) (C1 (MetaCons "IPv4Range" PrefixI True) (S1 (MetaSel (Just "ipv4RangeBase") SourceUnpack SourceStrict DecidedStrict) (Rec0 IPv4) :*: S1 (MetaSel (Just "ipv4RangeLength") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word8)))
data Vector IPv4Range Source # 
Instance details

Defined in Net.IPv4

data MVector s IPv4Range Source # 
Instance details

Defined in Net.IPv4

Interoperability

The network library is commonly used to open sockets and communicate over them. In the Network.Socket module, it provides a type synonym HostAddress that, like IPv4, is used to represent an IPv4 address. However, while IPv4 uses a big-endian representation for ip addresses, HostAddress has platform dependent endianness. Consequently, it is necessary to convert between the two as follows:

import Network.Socket (HostAddress,htonl,ntohl)

toHostAddr :: IPv4 -> HostAddress
toHostAddr (IPv4 w) = htonl w

fromHostAddr :: HostAddress -> IPv4
fromHostAddr w = IPv4 (ntohl w)

These functions are not included with this library since it would require picking up a dependency on network.