ip-0.7: Library for IP and MAC addresses

Safe HaskellNone
LanguageHaskell2010

Net.IPv4

Contents

Description

An IPv4 data type

This module provides the IPv4 data type and functions for working with it. There are also encoding and decoding functions provided in this module, but they should be imported from Net.IPv4.Text and Net.IPv4.ByteString.Char8 instead. They are defined here so that the FromJSON and ToJSON instances can use them.

At some point, a highly efficient IPv4-to-ByteString function needs to be added to this module to take advantage of aeson's new toEncoding method.

Synopsis

Types

newtype IPv4 Source #

A 32-bit Internet Protocol address.

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 #

ToJSON IPv4 Source # 
FromJSON IPv4 Source # 

Methods

parseJSON :: Value -> Parser IPv4 #

Hashable IPv4 Source # 

Methods

hashWithSalt :: Int -> IPv4 -> Int #

hash :: IPv4 -> Int #

MVector MVector IPv4 Source # 
type Rep IPv4 Source # 
type Rep IPv4 = D1 (MetaData "IPv4" "Net.IPv4" "ip-0.7-7yBoAFAa1Q77CKvp7MdxXp" True) (C1 (MetaCons "IPv4" PrefixI True) (S1 (MetaSel (Just Symbol "getIPv4") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))
data MVector s IPv4 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 :: * -> * #

ToJSON IPv4Range Source # 
FromJSON IPv4Range Source # 
Hashable IPv4Range Source # 
type Rep IPv4Range Source # 
type Rep IPv4Range = D1 (MetaData "IPv4Range" "Net.IPv4" "ip-0.7-7yBoAFAa1Q77CKvp7MdxXp" 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))))

Range functions

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:

>>> prRange $ normalize $ IPv4Range (fromOctets 192 168 1 19) 24
192.168.1.0/24
>>> prRange $ 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

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

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

Conversion Functions

fromOctets :: 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 the Show and Read instances for IPv4 are not generally usefully, this function is the recommened way to create IPv4 addresses. For example:

>>> fromOctets 192 168 1 1
IPv4 {getIPv4 = 3232235777}

fromOctets' :: Word32 -> Word32 -> Word32 -> Word32 -> IPv4 Source #

This is sort of a misnomer. It takes Word32 to make dotDecimalParser probably perform better. This is mostly for internal use.

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.

Internal Functions

prAddr :: IPv4 -> IO () Source #

$internal Everything below here is not part of the stable API. Many of these functions must live here because they are needed for the ToJSON and FromJSON instances. Hopefully, at some point, these can be removed from this module.

This only exists for doctests. Do not use it.

prRange :: IPv4Range -> IO () Source #

This only exists for doctests. Do not use it.

dotDecimalParser :: Parser IPv4 Source #

This does not do an endOfInput check because it is reused in the range parser implementation.