iproute-1.7.7: IP Routing Table

Safe HaskellNone
LanguageHaskell2010

Data.IP

Contents

Description

Data structures to express IPv4, IPv6 and IP range.

Synopsis

IP data

data IP Source #

A unified IP data for IP and IP. To create this, use the data constructors. Or use read "192.0.2.1" :: IP, for example. Also, "192.0.2.1" can be used as literal with OverloadedStrings.

>>> (read "192.0.2.1" :: IP) == IPv4 (read "192.0.2.1" :: IPv4)
True
>>> (read "2001:db8:00:00:00:00:00:01" :: IP) == IPv6 (read "2001:db8:00:00:00:00:00:01" :: IPv6)
True

Constructors

IPv4 

Fields

IPv6 

Fields

Instances
Enum IP Source # 
Instance details

Defined in Data.IP.Addr

Methods

succ :: IP -> IP #

pred :: IP -> IP #

toEnum :: Int -> IP #

fromEnum :: IP -> Int #

enumFrom :: IP -> [IP] #

enumFromThen :: IP -> IP -> [IP] #

enumFromTo :: IP -> IP -> [IP] #

enumFromThenTo :: IP -> IP -> IP -> [IP] #

Eq IP Source #

Equality over IP addresses. Correctly compare IPv4 and IPv4-embedded-in-IPv6 addresses.

>>> (read "2001:db8:00:00:00:00:00:01" :: IP) == (read "2001:db8:00:00:00:00:00:01" :: IP)
True
>>> (read "2001:db8:00:00:00:00:00:01" :: IP) == (read "2001:db8:00:00:00:00:00:05" :: IP)
False
>>> (read "127.0.0.1" :: IP) == (read "127.0.0.1" :: IP)
True
>>> (read "127.0.0.1" :: IP) == (read "10.0.0.1" :: IP)
False
>>> (read "::ffff:127.0.0.1" :: IP) == (read "127.0.0.1" :: IP)
True
>>> (read "::ffff:127.0.0.1" :: IP) == (read "127.0.0.9" :: IP)
False
>>> (read "::ffff:127.0.0.1" :: IP) >= (read "127.0.0.1" :: IP)
True
>>> (read "::ffff:127.0.0.1" :: IP) <= (read "127.0.0.1" :: IP)
True
Instance details

Defined in Data.IP.Addr

Methods

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

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

Data IP Source # 
Instance details

Defined in Data.IP.Addr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IP -> c IP #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IP #

toConstr :: IP -> Constr #

dataTypeOf :: IP -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IP) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IP) #

gmapT :: (forall b. Data b => b -> b) -> IP -> IP #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IP -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IP -> r #

gmapQ :: (forall d. Data d => d -> u) -> IP -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IP -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IP -> m IP #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IP -> m IP #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IP -> m IP #

Ord IP Source # 
Instance details

Defined in Data.IP.Addr

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

Defined in Data.IP.Addr

Show IP Source # 
Instance details

Defined in Data.IP.Addr

Methods

showsPrec :: Int -> IP -> ShowS #

show :: IP -> String #

showList :: [IP] -> ShowS #

IsString IP Source # 
Instance details

Defined in Data.IP.Addr

Methods

fromString :: String -> IP #

Generic IP Source # 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IP :: Type -> Type #

Methods

from :: IP -> Rep IP x #

to :: Rep IP x -> IP #

type Rep IP Source # 
Instance details

Defined in Data.IP.Addr

type Rep IP = D1 (MetaData "IP" "Data.IP.Addr" "iproute-1.7.7-Bl4bYsnCshE2skMbTxGToc" False) (C1 (MetaCons "IPv4" PrefixI True) (S1 (MetaSel (Just "ipv4") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IPv4)) :+: C1 (MetaCons "IPv6" PrefixI True) (S1 (MetaSel (Just "ipv6") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IPv6)))

IPv4

data IPv4 Source #

The abstract data type to express an IPv4 address. To create this, use toIPv4. Or use read "192.0.2.1" :: IP, for example. Also, "192.0.2.1" can be used as literal with OverloadedStrings.

>>> read "192.0.2.1" :: IPv4
192.0.2.1
Instances
Bounded IPv4 Source # 
Instance details

Defined in Data.IP.Addr

Enum IPv4 Source # 
Instance details

Defined in Data.IP.Addr

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 Data.IP.Addr

Methods

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

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

Data IPv4 Source # 
Instance details

Defined in Data.IP.Addr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPv4 -> c IPv4 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IPv4 #

toConstr :: IPv4 -> Constr #

dataTypeOf :: IPv4 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IPv4) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv4) #

gmapT :: (forall b. Data b => b -> b) -> IPv4 -> IPv4 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPv4 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPv4 -> r #

gmapQ :: (forall d. Data d => d -> u) -> IPv4 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPv4 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPv4 -> m IPv4 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPv4 -> m IPv4 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPv4 -> m IPv4 #

Ord IPv4 Source # 
Instance details

Defined in Data.IP.Addr

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 Data.IP.Addr

Show IPv4 Source # 
Instance details

Defined in Data.IP.Addr

Methods

showsPrec :: Int -> IPv4 -> ShowS #

show :: IPv4 -> String #

showList :: [IPv4] -> ShowS #

IsString IPv4 Source # 
Instance details

Defined in Data.IP.Addr

Methods

fromString :: String -> IPv4 #

Generic IPv4 Source # 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IPv4 :: Type -> Type #

Methods

from :: IPv4 -> Rep IPv4 x #

to :: Rep IPv4 x -> IPv4 #

Addr IPv4 Source # 
Instance details

Defined in Data.IP.Op

Routable IPv4 Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Read (AddrRange IPv4) Source # 
Instance details

Defined in Data.IP.Range

IsString (AddrRange IPv4) Source # 
Instance details

Defined in Data.IP.Range

type Rep IPv4 Source # 
Instance details

Defined in Data.IP.Addr

type Rep IPv4 = D1 (MetaData "IPv4" "Data.IP.Addr" "iproute-1.7.7-Bl4bYsnCshE2skMbTxGToc" True) (C1 (MetaCons "IP4" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IPv4Addr)))

toIPv4 :: [Int] -> IPv4 Source #

The toIPv4 function takes a list of Int and returns IP.

>>> toIPv4 [192,0,2,1]
192.0.2.1

fromIPv4 :: IPv4 -> [Int] Source #

The fromIPv4 function converts IP to a list of Int.

>>> fromIPv4 (toIPv4 [192,0,2,1])
[192,0,2,1]

IPv6

data IPv6 Source #

The abstract data type to express an IPv6 address. To create this, use toIPv6. Or use read "2001:DB8::1" :: IP, for example. Also, "2001:DB8::1" can be used as literal with OverloadedStrings.

>>> read "2001:db8:00:00:00:00:00:01" :: IPv6
2001:db8::1
>>> read "2001:db8:11e:c00::101" :: IPv6
2001:db8:11e:c00::101
>>> read "2001:db8:11e:c00:aa:bb:192.0.2.1" :: IPv6
2001:db8:11e:c00:aa:bb:c000:201
>>> read "2001:db8::192.0.2.1" :: IPv6
2001:db8::c000:201
>>> read "0::ffff:192.0.2.1" :: IPv6
::ffff:192.0.2.1
>>> read "0::0:c000:201" :: IPv6
::192.0.2.1
>>> read "::0.0.0.1" :: IPv6
::1
Instances
Bounded IPv6 Source # 
Instance details

Defined in Data.IP.Addr

Enum IPv6 Source # 
Instance details

Defined in Data.IP.Addr

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 Data.IP.Addr

Methods

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

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

Data IPv6 Source # 
Instance details

Defined in Data.IP.Addr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPv6 -> c IPv6 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IPv6 #

toConstr :: IPv6 -> Constr #

dataTypeOf :: IPv6 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IPv6) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPv6) #

gmapT :: (forall b. Data b => b -> b) -> IPv6 -> IPv6 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPv6 -> r #

gmapQ :: (forall d. Data d => d -> u) -> IPv6 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPv6 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPv6 -> m IPv6 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPv6 -> m IPv6 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPv6 -> m IPv6 #

Ord IPv6 Source # 
Instance details

Defined in Data.IP.Addr

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 Data.IP.Addr

Show IPv6 Source # 
Instance details

Defined in Data.IP.Addr

Methods

showsPrec :: Int -> IPv6 -> ShowS #

show :: IPv6 -> String #

showList :: [IPv6] -> ShowS #

IsString IPv6 Source # 
Instance details

Defined in Data.IP.Addr

Methods

fromString :: String -> IPv6 #

Generic IPv6 Source # 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IPv6 :: Type -> Type #

Methods

from :: IPv6 -> Rep IPv6 x #

to :: Rep IPv6 x -> IPv6 #

Addr IPv6 Source # 
Instance details

Defined in Data.IP.Op

Routable IPv6 Source # 
Instance details

Defined in Data.IP.RouteTable.Internal

Read (AddrRange IPv6) Source # 
Instance details

Defined in Data.IP.Range

IsString (AddrRange IPv6) Source # 
Instance details

Defined in Data.IP.Range

type Rep IPv6 Source # 
Instance details

Defined in Data.IP.Addr

type Rep IPv6 = D1 (MetaData "IPv6" "Data.IP.Addr" "iproute-1.7.7-Bl4bYsnCshE2skMbTxGToc" True) (C1 (MetaCons "IP6" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IPv6Addr)))

toIPv6 :: [Int] -> IPv6 Source #

The toIPv6 function takes a list of Int and returns IP.

>>> toIPv6 [0x2001,0xDB8,0,0,0,0,0,1]
2001:db8::1

toIPv6b :: [Int] -> IPv6 Source #

The toIPv6b function takes a list of Int where each member repserents a single byte and returns IP.

>>> toIPv6b [0x20,0x01,0xD,0xB8,0,0,0,0,0,0,0,0,0,0,0,1]
2001:db8::1

fromIPv6 :: IPv6 -> [Int] Source #

The toIPv6 function converts IP to a list of Int.

>>> fromIPv6 (toIPv6 [0x2001,0xDB8,0,0,0,0,0,1])
[8193,3512,0,0,0,0,0,1]

fromIPv6b :: IPv6 -> [Int] Source #

The fromIPv6b function converts IP to a list of Int where each member represents a single byte.

>>> fromIPv6b (toIPv6b [0x20,0x01,0xD,0xB8,0,0,0,0,0,0,0,0,0,0,0,1])
[32,1,13,184,0,0,0,0,0,0,0,0,0,0,0,1]

Converters

ipv4ToIPv6 :: IPv4 -> IPv6 Source #

Convert IPv4 address to IPv4-embedded-in-IPv6

fromSockAddr :: SockAddr -> Maybe (IP, PortNumber) Source #

Convert SockAddr to IP.

Since: 1.7.4.

IP range data

data IPRange Source #

A unified data for AddrRange IP and AddrRange IP. To create this, use read "192.0.2.0/24" :: IPRange. Also, "192.0.2.0/24" can be used as literal with OverloadedStrings.

>>> (read "192.0.2.1/24" :: IPRange) == IPv4Range (read "192.0.2.0/24" :: AddrRange IPv4)
True
>>> (read "2001:db8:00:00:00:00:00:01/48" :: IPRange) == IPv6Range (read "2001:db8:00:00:00:00:00:01/48" :: AddrRange IPv6)
True

Constructors

IPv4Range 
IPv6Range 
Instances
Eq IPRange Source # 
Instance details

Defined in Data.IP.Range

Methods

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

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

Data IPRange Source # 
Instance details

Defined in Data.IP.Range

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPRange -> c IPRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IPRange #

toConstr :: IPRange -> Constr #

dataTypeOf :: IPRange -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IPRange) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IPRange) #

gmapT :: (forall b. Data b => b -> b) -> IPRange -> IPRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPRange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> IPRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPRange -> m IPRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPRange -> m IPRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPRange -> m IPRange #

Ord IPRange Source # 
Instance details

Defined in Data.IP.Range

Read IPRange Source # 
Instance details

Defined in Data.IP.Range

Show IPRange Source # 
Instance details

Defined in Data.IP.Range

IsString IPRange Source # 
Instance details

Defined in Data.IP.Range

Methods

fromString :: String -> IPRange #

Generic IPRange Source # 
Instance details

Defined in Data.IP.Range

Associated Types

type Rep IPRange :: Type -> Type #

Methods

from :: IPRange -> Rep IPRange x #

to :: Rep IPRange x -> IPRange #

type Rep IPRange Source # 
Instance details

Defined in Data.IP.Range

type Rep IPRange = D1 (MetaData "IPRange" "Data.IP.Range" "iproute-1.7.7-Bl4bYsnCshE2skMbTxGToc" False) (C1 (MetaCons "IPv4Range" PrefixI True) (S1 (MetaSel (Just "ipv4range") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AddrRange IPv4))) :+: C1 (MetaCons "IPv6Range" PrefixI True) (S1 (MetaSel (Just "ipv6range") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AddrRange IPv6))))

data AddrRange a Source #

The Addr range consists of an address, a contiguous mask, and mask length. The contiguous mask and the mask length are essentially same information but contained for pre calculation.

To create this, use makeAddrRange or read "192.0.2.0/24" :: AddrRange IP. Also, "192.0.2.0/24" can be used as literal with OverloadedStrings.

>>> read "192.0.2.1/24" :: AddrRange IPv4
192.0.2.0/24
>>> read "2001:db8:00:00:00:00:00:01/48" :: AddrRange IPv6
2001:db8::/48
Instances
Eq a => Eq (AddrRange a) Source # 
Instance details

Defined in Data.IP.Range

Methods

(==) :: AddrRange a -> AddrRange a -> Bool #

(/=) :: AddrRange a -> AddrRange a -> Bool #

Data a => Data (AddrRange a) Source # 
Instance details

Defined in Data.IP.Range

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddrRange a -> c (AddrRange a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AddrRange a) #

toConstr :: AddrRange a -> Constr #

dataTypeOf :: AddrRange a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AddrRange a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AddrRange a)) #

gmapT :: (forall b. Data b => b -> b) -> AddrRange a -> AddrRange a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddrRange a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddrRange a -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddrRange a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddrRange a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddrRange a -> m (AddrRange a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddrRange a -> m (AddrRange a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddrRange a -> m (AddrRange a) #

Ord a => Ord (AddrRange a) Source # 
Instance details

Defined in Data.IP.Range

Read (AddrRange IPv6) Source # 
Instance details

Defined in Data.IP.Range

Read (AddrRange IPv4) Source # 
Instance details

Defined in Data.IP.Range

Show a => Show (AddrRange a) Source # 
Instance details

Defined in Data.IP.Range

IsString (AddrRange IPv6) Source # 
Instance details

Defined in Data.IP.Range

IsString (AddrRange IPv4) Source # 
Instance details

Defined in Data.IP.Range

Generic (AddrRange a) Source # 
Instance details

Defined in Data.IP.Range

Associated Types

type Rep (AddrRange a) :: Type -> Type #

Methods

from :: AddrRange a -> Rep (AddrRange a) x #

to :: Rep (AddrRange a) x -> AddrRange a #

type Rep (AddrRange a) Source # 
Instance details

Defined in Data.IP.Range

type Rep (AddrRange a) = D1 (MetaData "AddrRange" "Data.IP.Range" "iproute-1.7.7-Bl4bYsnCshE2skMbTxGToc" False) (C1 (MetaCons "AddrRange" PrefixI True) (S1 (MetaSel (Just "addr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: (S1 (MetaSel (Just "mask") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "mlen") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int))))

Address class

class Eq a => Addr a where Source #

>>> toIPv4 [127,0,2,1] `masked` intToMask 7
126.0.0.0

Methods

masked :: a -> a -> a Source #

The masked function takes an Addr and a contiguous mask and returned a masked Addr.

intToMask :: Int -> a Source #

The intToMask function takes an Int representing the number of bits to be set in the returned contiguous mask. When this integer is positive the bits will be starting from the MSB and from the LSB otherwise.

>>> intToMask 16 :: IPv4
255.255.0.0
>>> intToMask (-16) :: IPv4
0.0.255.255
>>> intToMask 16 :: IPv6
ffff::
>>> intToMask (-16) :: IPv6
::ffff
Instances
Addr IPv6 Source # 
Instance details

Defined in Data.IP.Op

Addr IPv4 Source # 
Instance details

Defined in Data.IP.Op

makeAddrRange :: Addr a => a -> Int -> AddrRange a Source #

The makeAddrRange functions takes an Addr address and a mask length. It creates a bit mask from the mask length and masks the Addr address, then returns AddrRange made of them.

>>> makeAddrRange (toIPv4 [127,0,2,1]) 8
127.0.0.0/8
>>> makeAddrRange (toIPv6 [0x2001,0xDB8,0,0,0,0,0,1]) 8
2000::/8

(>:>) :: Addr a => AddrRange a -> AddrRange a -> Bool Source #

The >:> operator takes two AddrRange. It returns True if the first AddrRange contains the second AddrRange. Otherwise, it returns False.

>>> makeAddrRange ("127.0.2.1" :: IPv4) 8 >:> makeAddrRange "127.0.2.1" 24
True
>>> makeAddrRange ("127.0.2.1" :: IPv4) 24 >:> makeAddrRange "127.0.2.1" 8
False
>>> makeAddrRange ("2001:DB8::1" :: IPv6) 16 >:> makeAddrRange "2001:DB8::1" 32
True
>>> makeAddrRange ("2001:DB8::1" :: IPv6) 32 >:> makeAddrRange "2001:DB8::1" 16
False

isMatchedTo :: Addr a => a -> AddrRange a -> Bool Source #

The toMatchedTo function take an Addr address and an AddrRange, and returns True if the range contains the address.

>>> ("127.0.2.0" :: IPv4) `isMatchedTo` makeAddrRange "127.0.2.1" 24
True
>>> ("127.0.2.0" :: IPv4) `isMatchedTo` makeAddrRange "127.0.2.1" 32
False
>>> ("2001:DB8::1" :: IPv6) `isMatchedTo` makeAddrRange "2001:DB8::1" 32
True
>>> ("2001:DB8::" :: IPv6) `isMatchedTo` makeAddrRange "2001:DB8::1" 128
False

addrRangePair :: Addr a => AddrRange a -> (a, Int) Source #

The unmakeAddrRange functions take a AddrRange and returns the network address and a mask length.

>>> addrRangePair ("127.0.0.0/8" :: AddrRange IPv4)
(127.0.0.0,8)
>>> addrRangePair ("2000::/8" :: AddrRange IPv6)
(2000::,8)

ipv4RangeToIPv6 :: AddrRange IPv4 -> AddrRange IPv6 Source #

Convert IPv4 range to IPV4-embedded-in-IPV6 range