ip-1.7.3: Library for IP and MAC addresses
Safe HaskellNone
LanguageHaskell2010

Net.IP

Description

An IP data type representing either an IPv4 address or an IPv6 address. The user can think of this as though it were a sum type. However, to minimize indirections, it is actually implemented as an IPv6 address, with IPv4 addresses being represented as an IPv4-mapped IPv6 addresses:

+---------+---------+--------------+
| 80 bits | 16 bits | 32 bits      |
+---------+---------+--------------+
| 00...00 | FFFF    | IPv4 address |
+---------+---------+--------------+

All functions and instance methods that deal with textual conversion will encode an IP using either dot-decimal notation (for IPv4) or RFC 5952 (for IPv6). They will decode an IP from either format as well. The Show instance presents an address in as valid haskell code that resembles the formatted address:

>>> decode "192.168.3.100"
Just (ipv4 192 168 3 100)
>>> decode "A3F5:12:F26::1466:8B91"
Just (ipv6 0xa3f5 0x0012 0x0f26 0x0000 0x0000 0x0000 0x1466 0x8b91)
Synopsis

Pattern Matching

case_ :: (IPv4 -> a) -> (IPv6 -> a) -> IP -> a Source #

Run a function over an IP depending on its status as an IPv4 or IPv6.

>>> case_ IPv4.encode IPv6.encode (ipv4 192 168 2 47)
"192.168.2.47"
>>> addr = ipv6 0x2001 0x0db8 0x0000 0x0000 0x0000 0x0000 0x0000 0x0001
>>> case_ IPv4.encode IPv6.encode addr
"2001:db8::1"

isIPv4 :: IP -> Bool Source #

Is the IP an IPv4 address?

>>> isIPv4 (ipv4 10 0 0 25)
True
>>> isIPv4 (ipv6 0x3124 0x0 0x0 0xDEAD 0xCAFE 0xFF 0xFE00 0x1)
False

isIPv6 :: IP -> Bool Source #

Is the IP an IPv6 address?

>>> isIPv6 (ipv4 10 0 0 25)
False
>>> isIPv6 (ipv6 0x3124 0x0 0x0 0xDEAD 0xCAFE 0xFF 0xFE00 0x1)
True

Construction

ipv4 :: Word8 -> Word8 -> Word8 -> Word8 -> IP Source #

Construct an IP address from the four octets of an IPv4 address.

ipv6 :: Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> Word16 -> IP Source #

Construct an IP address from the eight 16-bit chunks of an IPv6 address.

fromIPv4 :: IPv4 -> IP Source #

Turn an IPv4 into an IP.

fromIPv6 :: IPv6 -> IP Source #

Turn an IPv6 into an IP.

Textual Conversion

Text

encode :: IP -> Text Source #

Encode an IP as Text.

>>> encode (ipv4 10 0 0 25)
"10.0.0.25"
>>> encode (ipv6 0x3124 0x0 0x0 0xDEAD 0xCAFE 0xFF 0xFE00 0x1)
"3124::dead:cafe:ff:fe00:1"

encodeShort :: IP -> ShortText Source #

Encode an IP as ShortText.

>>> encodeShort (ipv4 10 0 1 26)
"10.0.1.26"
>>> encodeShort (ipv6 0x3124 0x0 0x0 0xDEAD 0xCAFE 0xFF 0xFE01 0x0000)
"3124::dead:cafe:ff:fe01:0"

decode :: Text -> Maybe IP Source #

Decode an IP from Text.

>>> decode "10.0.0.25"
Just (ipv4 10 0 0 25)
>>> fmap isIPv4 (decode "10.0.0.25")
Just True
>>> decode "3124::dead:cafe:ff:fe00:1"
Just (ipv6 0x3124 0x0000 0x0000 0xdead 0xcafe 0x00ff 0xfe00 0x0001)
>>> fmap isIPv6 (decode "3124::dead:cafe:ff:fe00:1")
Just True

decodeShort :: ShortText -> Maybe IP Source #

Decode an IP from ShortText.

>>> decodeShort "10.0.0.25"
Just (ipv4 10 0 0 25)
>>> decodeShort "::dead:cafe"
Just (ipv6 0x0000 0x0000 0x0000 0x0000 0x0000 0x0000 0xdead 0xcafe)

boundedBuilderUtf8 :: IP -> Builder 39 Source #

Encode an IP as a bounded bytearray builder.

>>> BB.run Nat.constant (boundedBuilderUtf8 (ipv4 192 168 2 14))
[0x31, 0x39, 0x32, 0x2e, 0x31, 0x36, 0x38, 0x2e, 0x32, 0x2e, 0x31, 0x34]

Bytes

parserUtf8Bytes :: e -> Parser e s IP Source #

Parse UTF-8-encoded Bytes as an IP address.

Printing

print :: IP -> IO () Source #

Print an IP using the textual encoding. This exists mostly for debugging purposes.

>>> print (ipv4 10 0 0 25)
10.0.0.25
>>> print (ipv6 0x3124 0x0 0x0 0xDEAD 0xCAFE 0xFF 0xFE00 0x1)
3124::dead:cafe:ff:fe00:1

Types

newtype IP Source #

A 32-bit IPv4 address or a 128-bit IPv6 address. Internally, this is just represented as an IPv6 address. The functions provided in Net.IP help simulate constructing and pattern matching on values of this type. All functions and typeclass methods that convert IP values to text will display it as an IPv4 address if possible.

Constructors

IP 

Fields

Instances

Instances details
Eq IP Source # 
Instance details

Defined in Net.IP

Methods

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

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

Data IP Source # 
Instance details

Defined in Net.IP

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 :: 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 #

Ord IP Source # 
Instance details

Defined in Net.IP

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 Net.IP

Show IP Source # 
Instance details

Defined in Net.IP

Methods

showsPrec :: Int -> IP -> ShowS #

show :: IP -> String #

showList :: [IP] -> ShowS #

Ix IP Source # 
Instance details

Defined in Net.IP

Methods

range :: (IP, IP) -> [IP] #

index :: (IP, IP) -> IP -> Int #

unsafeIndex :: (IP, IP) -> IP -> Int #

inRange :: (IP, IP) -> IP -> Bool #

rangeSize :: (IP, IP) -> Int #

unsafeRangeSize :: (IP, IP) -> Int #

Generic IP Source # 
Instance details

Defined in Net.IP

Associated Types

type Rep IP :: Type -> Type #

Methods

from :: IP -> Rep IP x #

to :: Rep IP x -> IP #

ToJSON IP Source # 
Instance details

Defined in Net.IP

FromJSON IP Source # 
Instance details

Defined in Net.IP

NFData IP Source # 
Instance details

Defined in Net.IP

Methods

rnf :: IP -> () #

type Rep IP Source # 
Instance details

Defined in Net.IP

type Rep IP = D1 ('MetaData "IP" "Net.IP" "ip-1.7.3-55ZwDgM4labHVZFLHwdgFh" 'True) (C1 ('MetaCons "IP" 'PrefixI 'True) (S1 ('MetaSel ('Just "getIP") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IPv6)))