| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Data.IP
Description
Data structures to express IPv4, IPv6 and IP range.
Synopsis
- data IP
- data IPv4
- toIPv4 :: [Int] -> IPv4
- toIPv4w :: Word32 -> IPv4
- fromIPv4 :: IPv4 -> [Int]
- fromIPv4w :: IPv4 -> Word32
- fromHostAddress :: HostAddress -> IPv4
- toHostAddress :: IPv4 -> HostAddress
- data IPv6
- toIPv6 :: [Int] -> IPv6
- toIPv6b :: [Int] -> IPv6
- toIPv6w :: (Word32, Word32, Word32, Word32) -> IPv6
- fromIPv6 :: IPv6 -> [Int]
- fromIPv6b :: IPv6 -> [Int]
- fromIPv6w :: IPv6 -> (Word32, Word32, Word32, Word32)
- fromHostAddress6 :: HostAddress6 -> IPv6
- toHostAddress6 :: IPv6 -> HostAddress6
- ipv4ToIPv6 :: IPv4 -> IPv6
- fromSockAddr :: SockAddr -> Maybe (IP, PortNumber)
- toSockAddr :: (IP, PortNumber) -> SockAddr
- data IPRange
- data AddrRange a
- class Eq a => Addr a where
- makeAddrRange :: Addr a => a -> Int -> AddrRange a
- (>:>) :: Addr a => AddrRange a -> AddrRange a -> Bool
- isMatchedTo :: Addr a => a -> AddrRange a -> Bool
- addrRangePair :: Addr a => AddrRange a -> (a, Int)
- ipv4RangeToIPv6 :: AddrRange IPv4 -> AddrRange IPv6
IP data
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
Instances
| Data IP Source # | |
| 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 # 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 :: forall r r'. (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 # | |
| IsString IP Source # | |
| Defined in Data.IP.Addr Methods fromString :: String -> IP # | |
| Enum IP Source # | |
| Generic IP Source # | |
| Read IP Source # | |
| Show IP Source # | |
| Eq IP Source # | Equality over IP addresses. Correctly compare IPv4 and IPv4-embedded-in-IPv6 addresses. 
 | 
| Ord IP Source # | |
| type Rep IP Source # | |
| Defined in Data.IP.Addr type Rep IP = D1 ('MetaData "IP" "Data.IP.Addr" "iproute-1.7.14-1zIIH75j1FAJJMN1nmSNNv" 'False) (C1 ('MetaCons "IPv4" 'PrefixI 'True) (S1 ('MetaSel ('Just "ipv4") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 IPv4)) :+: C1 ('MetaCons "IPv6" 'PrefixI 'True) (S1 ('MetaSel ('Just "ipv6") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 IPv6))) | |
IPv4
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" :: IPv4192.0.2.1
Instances
| Data IPv4 Source # | |
| 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 # 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 :: forall r r'. (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 # | |
| IsString IPv4 Source # | |
| Defined in Data.IP.Addr Methods fromString :: String -> IPv4 # | |
| Bounded IPv4 Source # | |
| Enum IPv4 Source # | |
| Generic IPv4 Source # | |
| Read IPv4 Source # | |
| Show IPv4 Source # | |
| Eq IPv4 Source # | |
| Ord IPv4 Source # | |
| Addr IPv4 Source # | |
| Routable IPv4 Source # | |
| IsString (AddrRange IPv4) Source # | |
| Defined in Data.IP.Range Methods fromString :: String -> AddrRange IPv4 # | |
| Read (AddrRange IPv4) Source # | |
| type Rep IPv4 Source # | |
| Defined in Data.IP.Addr | |
toIPv4 :: [Int] -> IPv4 Source #
The toIPv4 function returns the IP address corresponding to the given
  list of Int octets.  The function is strict in the four elements of the
  list.  An error is returned if the list has a differnet length.  The input
  elements are silently truncated to their 8 least-significant bits before they
  are combined to form the IPv4 address.
>>>toIPv4 [192,0,2,1]192.0.2.1
toIPv4w :: Word32 -> IPv4 Source #
The toIPv4w function constructs the IP address corresponding to the
  given Word32 value.  Unlike the fromHostAddress function, it is strict in
  the input value, which here is in host byte order.
>>>toIPv4w 0xc0000201192.0.2.1
Since: 1.7.9
fromIPv4w :: IPv4 -> Word32 Source #
The fromIPv4w function returns a single Word32 value corresponding to the
  given the IP address.  Unlike the toHostAddress function, the returned
  value is strictly evaluated, and is not converted to network byte order.
>>>fromIPv4w (toIPv4 [0xc0,0,2,1]) == 0xc0000201True
Since: 1.7.9
fromHostAddress :: HostAddress -> IPv4 Source #
The fromHostAddress function converts HostAddress to IP.
toHostAddress :: IPv4 -> HostAddress Source #
The toHostAddress function converts IP to HostAddress.
IPv6
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" :: IPv62001:db8::1>>>read "2001:db8:11e:c00::101" :: IPv62001:db8:11e:c00::101>>>read "2001:db8:11e:c00:aa:bb:192.0.2.1" :: IPv62001:db8:11e:c00:aa:bb:c000:201>>>read "2001:db8::192.0.2.1" :: IPv62001: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
| Data IPv6 Source # | |
| 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 # 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 :: forall r r'. (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 # | |
| IsString IPv6 Source # | |
| Defined in Data.IP.Addr Methods fromString :: String -> IPv6 # | |
| Bounded IPv6 Source # | |
| Enum IPv6 Source # | |
| Generic IPv6 Source # | |
| Read IPv6 Source # | |
| Show IPv6 Source # | |
| Eq IPv6 Source # | |
| Ord IPv6 Source # | |
| Addr IPv6 Source # | |
| Routable IPv6 Source # | |
| IsString (AddrRange IPv6) Source # | |
| Defined in Data.IP.Range Methods fromString :: String -> AddrRange IPv6 # | |
| Read (AddrRange IPv6) Source # | |
| type Rep IPv6 Source # | |
| Defined in Data.IP.Addr | |
toIPv6 :: [Int] -> IPv6 Source #
The toIPv6 function returns the IP address corresponding to the given
  list of eight 16-bit Ints.  The function is strict in the eight elements of
  the list.  An error is returned if the list has a differnet length.  The
  input elements are in host byte order and are silently truncated to their 16
  least-signicant bits before they are combined to form the IPv6 address.
>>>toIPv6 [0x2001,0xDB8,0,0,0,0,0,1]2001:db8::1
toIPv6b :: [Int] -> IPv6 Source #
The toIPv6b function returns the IPv6 address corresponding to the given
  list of sixteen Int octets.  The function is strict in the sixteen elements
  of the list.  An error is returned if the list has a differnet length.  The
  input elements are silently truncated to their 8 least-signicant bits before
  they are combined to form the IPv6 address.
>>>toIPv6b [0x20,0x01,0xD,0xB8,0,0,0,0,0,0,0,0,0,0,0,1]2001:db8::1
toIPv6w :: (Word32, Word32, Word32, Word32) -> IPv6 Source #
The toIPv6w function constructs the IP address corresponding to the
  given four-tuple of host byte order Word32 values.  This function differs
  from the fromHostAddress6 function only in the fact that it is strict in
  the elements of the tuple.
>>>toIPv6w (0x20010DB8,0x0,0x0,0x1)2001:db8::1
Since: 1.7.9
fromIPv6w :: IPv6 -> (Word32, Word32, Word32, Word32) Source #
The fromIPv6w function returns a four-tuple of Word32 values in host byte
  order corresponding to the given IP address.  This is identical to the
  toHostAddress6 function, except that the elements of four-tuple are
  first strictly evaluated.
>>>fromIPv6w (toIPv6 [0x2001,0xDB8,0,0,0,0,0,1]) == (0x20010DB8, 0, 0, 1)True
Since: 1.7.9
fromHostAddress6 :: HostAddress6 -> IPv6 Source #
The fromHostAddress6 function converts HostAddress6 to IP.
toHostAddress6 :: IPv6 -> HostAddress6 Source #
The toHostAddress6 function converts IP to HostAddress6.
Converters
ipv4ToIPv6 :: IPv4 -> IPv6 Source #
Convert IPv4 address to IPv4-embedded-in-IPv6
fromSockAddr :: SockAddr -> Maybe (IP, PortNumber) Source #
toSockAddr :: (IP, PortNumber) -> SockAddr Source #
IP range data
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
Instances
| Data IPRange Source # | |
| 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 :: forall r r'. (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 # | |
| IsString IPRange Source # | |
| Defined in Data.IP.Range Methods fromString :: String -> IPRange # | |
| Generic IPRange Source # | |
| Read IPRange Source # | |
| Show IPRange Source # | |
| Eq IPRange Source # | |
| Ord IPRange Source # | |
| type Rep IPRange Source # | |
| Defined in Data.IP.Range type Rep IPRange = D1 ('MetaData "IPRange" "Data.IP.Range" "iproute-1.7.14-1zIIH75j1FAJJMN1nmSNNv" 'False) (C1 ('MetaCons "IPv4Range" 'PrefixI 'True) (S1 ('MetaSel ('Just "ipv4range") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (AddrRange IPv4))) :+: C1 ('MetaCons "IPv6Range" 'PrefixI 'True) (S1 ('MetaSel ('Just "ipv6range") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (AddrRange IPv6)))) | |
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 IPv4192.0.2.0/24>>>read "2001:db8:00:00:00:00:00:01/48" :: AddrRange IPv62001:db8::/48
Instances
| Data a => Data (AddrRange a) Source # | |
| 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 :: forall r r'. (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) # | |
| IsString (AddrRange IPv4) Source # | |
| Defined in Data.IP.Range Methods fromString :: String -> AddrRange IPv4 # | |
| IsString (AddrRange IPv6) Source # | |
| Defined in Data.IP.Range Methods fromString :: String -> AddrRange IPv6 # | |
| Generic (AddrRange a) Source # | |
| Read (AddrRange IPv4) Source # | |
| Read (AddrRange IPv6) Source # | |
| Show a => Show (AddrRange a) Source # | |
| Eq a => Eq (AddrRange a) Source # | |
| Ord a => Ord (AddrRange a) Source # | |
| Defined in Data.IP.Range | |
| type Rep (AddrRange a) Source # | |
| Defined in Data.IP.Range type Rep (AddrRange a) = D1 ('MetaData "AddrRange" "Data.IP.Range" "iproute-1.7.14-1zIIH75j1FAJJMN1nmSNNv" '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 7126.0.0.0
Methods
masked :: a -> a -> a Source #
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 :: IPv4255.255.0.0
>>>intToMask (-16) :: IPv40.0.255.255
>>>intToMask 16 :: IPv6ffff::
>>>intToMask (-16) :: IPv6::ffff
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]) 8127.0.0.0/8>>>makeAddrRange (toIPv6 [0x2001,0xDB8,0,0,0,0,0,1]) 82000::/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" 24True>>>makeAddrRange ("127.0.2.1" :: IPv4) 24 >:> makeAddrRange "127.0.2.1" 8False>>>makeAddrRange ("2001:DB8::1" :: IPv6) 16 >:> makeAddrRange "2001:DB8::1" 32True>>>makeAddrRange ("2001:DB8::1" :: IPv6) 32 >:> makeAddrRange "2001:DB8::1" 16False
isMatchedTo :: Addr a => a -> AddrRange a -> Bool Source #
The isMatchedTo 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" 24True>>>("127.0.2.0" :: IPv4) `isMatchedTo` makeAddrRange "127.0.2.1" 32False>>>("2001:DB8::1" :: IPv6) `isMatchedTo` makeAddrRange "2001:DB8::1" 32True>>>("2001:DB8::" :: IPv6) `isMatchedTo` makeAddrRange "2001:DB8::1" 128False