ip-1.4.2.1: Library for IP and MAC addresses

Safe HaskellNone
LanguageHaskell2010

Net.IPv6

Contents

Description

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

Synopsis

Convert

ipv6 :: Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> IPv6 Source #

Create an IPv6 address from the eight 16-bit fragments that make it up. This closely resembles the standard IPv6 notation, so is used for the Show instance. Note that this lacks the formatting feature for suppress zeroes in an IPv6 address, but it should be readable enough for hacking in GHCi.

>>> let addr = ipv6 0x3124 0x0 0x0 0xDEAD 0xCAFE 0xFF 0xFE00 0x1
>>> addr
ipv6 0x3124 0x0000 0x0000 0xdead 0xcafe 0x00ff 0xfe00 0x0001
>>> T.putStrLn (encode addr)
3124::dead:cafe:ff:fe00:1

fromOctets :: Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> IPv6 Source #

This could be useful for the rare occasion in which one could construct an IPv6 from octets.

Note that while Net.IPv4.fromOctets = Net.IPv4.ipv4, Net.IPv6.fromOctets /= Net.IPv6.ipv6. While this should be obvious from their types, it is worth mentioning since the similarity in naming might be confusing.

fromWord16s :: Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> IPv6 Source #

An alias for the ipv6 smart constructor.

fromWord32s :: Word32 -> Word32 -> Word32 -> Word32 -> IPv6 Source #

Build an IPv6 from four 32-bit words. The leftmost argument is the high word and the rightword is the low word.

toWord16s :: IPv6 -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) Source #

Convert an IPv6 to eight 16-bit words.

toWord32s :: IPv6 -> (Word32, Word32, Word32, Word32) Source #

Convert an IPv6 to four 32-bit words.

Special IP Addresses

any :: IPv6 Source #

The IP address representing any host.

>>> any
ipv6 0x0000 0x0000 0x0000 0x0000 0x0000 0x0000 0x0000 0x0000

loopback :: IPv6 Source #

The local loopback IP address.

>>> loopback
ipv6 0x0000 0x0000 0x0000 0x0000 0x0000 0x0000 0x0000 0x0001

localhost :: IPv6 Source #

A useful alias for loopback.

>>> localhost
ipv6 0x0000 0x0000 0x0000 0x0000 0x0000 0x0000 0x0000 0x0001

Textual Conversion

Text

encode :: IPv6 -> Text Source #

Encodes the IP, using zero-compression on the leftmost-longest string of zeroes in the address. Per RFC 5952 Section 5, this uses mixed notation when encoding an IPv4-mapped IPv6 address:

>>> T.putStrLn $ encode $ fromWord16s 0xDEAD 0xBEEF 0x0 0x0 0x0 0x0 0x0 0x1234
dead:beef::1234
>>> T.putStrLn $ encode $ fromWord16s 0x0 0x0 0x0 0x0 0x0 0xFFFF 0x6437 0xA5B4
::ffff:100.55.165.180
>>> T.putStrLn $ encode $ fromWord16s 0x0 0x0 0x0 0x0 0x0 0x0 0x0 0x0
::

decode :: Text -> Maybe IPv6 Source #

Decode an IPv6 address. This accepts both standard IPv6 notation (with zero compression) and mixed notation for IPv4-mapped IPv6 addresses.

parser :: Parser IPv6 Source #

Parse an IPv6 using Parser.

>>> ip = ipv6 0xDEAD 0xBEEF 0x3240 0xA426 0xBA68 0x1CD0 0x4263 0x109B
>>> Atto.parseOnly parser (Text.pack "dead:beef:3240:a426:ba68:1cd0:4263:109b")
Right (ipv6 0xdead 0xbeef 0x3240 0xa426 0xba68 0x1cd0 0x4263 0x109b)

Printing

print :: IPv6 -> IO () Source #

Print an IPv6 using the textual encoding.

IPv6 Ranges

Range functions

range :: IPv6 -> Word8 -> IPv6Range Source #

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

>>> let addr = ipv6 0xDEAD 0xBEEF 0x3240 0xA426 0xBA68 0x1CD0 0x4263 0x109B
>>> printRange $ range addr 25
dead:be80::/25

fromBounds :: IPv6 -> IPv6 -> IPv6Range Source #

Given an inclusive lower and upper ip address, create the smallest IPv6Range that contains the two. This is helpful in situations where input is given as a range, like .

This makes the range broader if it cannot be represented in CIDR notation.

>>> addrLower = ipv6 0xDEAD 0xBE80 0x0000 0x0000 0x0000 0x0000 0x0000 0x0000
>>> addrUpper = ipv6 0xDEAD 0xBEFF 0xFFFF 0xFFFF 0xFFFF 0xFFFF 0xFFFF 0xFFFF
>>> printRange $ fromBounds addrLower addrUpper
dead:be80::/25

normalize :: IPv6Range -> IPv6Range Source #

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

>>> addr1 = ipv6 0x0192 0x0168 0x0001 0x0019 0x0000 0x0000 0x0000 0x0000
>>> addr2 = ipv6 0x0192 0x0168 0x0001 0x0163 0x0000 0x0000 0x0000 0x0000
>>> printRange $ normalize $ IPv6Range addr1 24
192:100::/24 
>>> printRange $ normalize $ IPv6Range addr2 28
192:160::/28

The second effect of this is that the mask length is lowered to be 128 or smaller. Working with IPv6Ranges 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 128).

Note that 'normalize is idempotent, that is:

normalize r == (normalize . normalize) r

contains :: IPv6Range -> IPv6 -> Bool Source #

Checks to see if an IPv6 address belongs in the IPv6Range.

>>> let ip = ipv6 0x2001 0x0db8 0x0db8 0x1094 0x2051 0x0000 0x0000 0x0001
>>> let iprange mask = IPv6Range (ipv6 0x2001 0x0db8 0x0000 0x0000 0x0000 0x0000 0x0000 0x0001) mask
>>> contains (iprange 8) ip
True
>>> contains (iprange 48) 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 = IPv6Range (ipv6 0x2001 0x0db8 0x0000 0x0000 0x0000 0x0000 0x0000 0x0001) 64
>>> fmap (contains r) (take 5 $ iterate succ $ ipv6 0x2001 0x0db8 0x0000 0x0000 0xffff 0xffff 0xffff 0xfffe)
[True,True,False,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 :: IPv6 -> IPv6Range -> 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 :: IPv6Range -> IPv6 Source #

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

>>> T.putStrLn $ encode $ lowerInclusive $ IPv6Range (ipv6 0x2001 0x0db8 0x0000 0x0000 0x0000 0x0000 0x0000 0x0001) 25
2001:d80::

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

lowerInclusive r == ipv6RangeBase (normalize r)

upperInclusive :: IPv6Range -> IPv6 Source #

The inclusive upper bound of an IPv6Range.

>>> let addr = ipv6 0xDEAD 0xBEEF 0x3240 0xA426 0xBA68 0x1CD0 0x4263 0x109B
>>> T.putStrLn $ encode $ upperInclusive $ IPv6Range addr 25
dead:beff:ffff:ffff:ffff:ffff:ffff:ffff

Textual Conversion

Text

encodeRange :: IPv6Range -> Text Source #

Encode an IPv6Range as Text.

>>> addr = ipv6 0xDEAD 0xBEEF 0x3240 0xA426 0xBA68 0x1CD0 0x4263 0x109B
>>> T.putStrLn $ encodeRange $ IPv6Range addr 28
dead:beef:3240:a426:ba68:1cd0:4263:109b/28

decodeRange :: Text -> Maybe IPv6Range Source #

Decode an IPv6Range from Text.

>>> addr = ipv6 0xDEAD 0xBEEF 0x3240 0xA426 0xBA68 0x1CD0 0x4263 0x109B
>>> fmap encodeRange $ decodeRange (Text.pack "dead:beef:3240:a426:ba68:1cd0:4263:109b/28")
Just "dead:bee0::/28"

printRange :: IPv6Range -> IO () Source #

Print an IPv6Range using the textual encoding.

Types

data IPv6 Source #

A 128-bit Internet Protocol version 6 address.

Constructors

IPv6 

Fields

Instances
Bounded IPv6 Source # 
Instance details

Defined in Net.IPv6

Enum IPv6 Source #

Since IPv6 has more inhabitants than Int, the implementation of fromEnum discards information. Currently, enumFromThen and enumFromThenTo emit an error, but this could be remedied if someone wants to provide an implementation of them.

Instance details

Defined in Net.IPv6

Methods

succ :: IPv6 -> IPv6 #

pred :: IPv6 -> IPv6 #

toEnum :: Int -> IPv6 #

fromEnum :: IPv6 -> Int #

enumFrom :: IPv6 -> [IPv6] #

enumFromThen :: IPv6 -> IPv6 -> [IPv6] #

enumFromTo :: IPv6 -> IPv6 -> [IPv6] #

enumFromThenTo :: IPv6 -> IPv6 -> IPv6 -> [IPv6] #

Eq IPv6 Source # 
Instance details

Defined in Net.IPv6

Methods

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

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

Ord IPv6 Source # 
Instance details

Defined in Net.IPv6

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

Defined in Net.IPv6

Show IPv6 Source # 
Instance details

Defined in Net.IPv6

Methods

showsPrec :: Int -> IPv6 -> ShowS #

show :: IPv6 -> String #

showList :: [IPv6] -> ShowS #

Generic IPv6 Source # 
Instance details

Defined in Net.IPv6

Associated Types

type Rep IPv6 :: Type -> Type #

Methods

from :: IPv6 -> Rep IPv6 x #

to :: Rep IPv6 x -> IPv6 #

ToJSON IPv6 Source # 
Instance details

Defined in Net.IPv6

FromJSON IPv6 Source # 
Instance details

Defined in Net.IPv6

NFData IPv6 Source # 
Instance details

Defined in Net.IPv6

Methods

rnf :: IPv6 -> () #

Prim IPv6 Source # 
Instance details

Defined in Net.IPv6

type Rep IPv6 Source # 
Instance details

Defined in Net.IPv6

type Rep IPv6 = D1 (MetaData "IPv6" "Net.IPv6" "ip-1.4.2.1-1kdobq8onQp8hYPnvSg0GR" False) (C1 (MetaCons "IPv6" PrefixI True) (S1 (MetaSel (Just "ipv6A") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64) :*: S1 (MetaSel (Just "ipv6B") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64)))

data IPv6Range Source #

An IPv6Range. It is made up of the first IPv6 in the range and its length.

Constructors

IPv6Range 
Instances
Eq IPv6Range Source # 
Instance details

Defined in Net.IPv6

Ord IPv6Range Source # 
Instance details

Defined in Net.IPv6

Read IPv6Range Source # 
Instance details

Defined in Net.IPv6

Show IPv6Range Source # 
Instance details

Defined in Net.IPv6

Generic IPv6Range Source # 
Instance details

Defined in Net.IPv6

Associated Types

type Rep IPv6Range :: Type -> Type #

NFData IPv6Range Source # 
Instance details

Defined in Net.IPv6

Methods

rnf :: IPv6Range -> () #

type Rep IPv6Range Source # 
Instance details

Defined in Net.IPv6

type Rep IPv6Range = D1 (MetaData "IPv6Range" "Net.IPv6" "ip-1.4.2.1-1kdobq8onQp8hYPnvSg0GR" False) (C1 (MetaCons "IPv6Range" PrefixI True) (S1 (MetaSel (Just "ipv6RangeBase") SourceUnpack SourceStrict DecidedStrict) (Rec0 IPv6) :*: S1 (MetaSel (Just "ipv6RangeLength") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word8)))