ip-1.2.0: 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

Conversion Functions

ipv4 :: 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 IP addresses are commonly written using dot-decimal notation, this is the recommended way to create an IP address. Additionally, it is used for the Show and Read instances of IPv4 to help keep things readable in GHCi.

>>> let addr = ipv4 192 168 1 1
>>> addr
ipv4 192 168 1 1
>>> getIPv4 addr
3232235777

fromOctets :: Word8 -> Word8 -> Word8 -> Word8 -> IPv4 Source #

An alias for the ipv4 smart constructor.

fromTupleOctets :: (Word8, Word8, Word8, Word8) -> IPv4 Source #

An uncurried variant of fromOctets.

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.

Special IP Addresses

any :: IPv4 Source #

The IP address representing any host: 0.0.0.0

loopback :: IPv4 Source #

The local loopback IP address: 127.0.0.1

broadcast :: IPv4 Source #

The broadcast IP address: 255.255.255.255

Range Predicates

private :: IPv4 -> Bool Source #

Checks to see if the IPv4 address belongs to a private network. The three private networks that are checked are 10.0.0.0/8, 172.16.0.0/12, and 192.168.0.0/16.

reserved :: IPv4 -> Bool Source #

Checks to see if the IPv4 address belongs to a reserved network. This includes the three private networks that private checks along with several other ranges that are not used on the public Internet.

public :: IPv4 -> Bool Source #

Checks to see if the IPv4 address is publicly routable.

public x == not (reserved x)

Textual Conversion

Text

encode :: IPv4 -> Text Source #

Encode an IPv4 address to Text using dot-decimal notation:

>>> T.putStrLn (encode (ipv4 192 168 2 47))
192.168.2.47

decode :: Text -> Maybe IPv4 Source #

Decode an IPv4 address.

builder :: IPv4 -> Builder Source #

Encode an IPv4 address to a text Builder.

UTF-8 ByteString

encodeUtf8 :: IPv4 -> ByteString Source #

Encode an IPv4 address to a UTF-8 encoded ByteString.

String

These functions exist for the convenience of those who need a String representation of an IPv4 address. Using them is discouraged unless the end user is working with a library that can only use String to deal with textual data (such as pandoc, hxr, or network).

Printing

print :: IPv4 -> IO () Source #

Types

newtype IPv4 Source #

A 32-bit Internet Protocol version 4 address. To use this with the network library, it is necessary to use Network.Socket.htonl to convert the underlying Word32 from host byte order to network byte order.

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 #

Hashable IPv4 Source # 

Methods

hashWithSalt :: Int -> IPv4 -> Int #

hash :: IPv4 -> Int #

ToJSON IPv4 Source # 
ToJSONKey IPv4 Source # 
FromJSON IPv4 Source # 
FromJSONKey IPv4 Source # 
Storable IPv4 Source # 

Methods

sizeOf :: IPv4 -> Int #

alignment :: IPv4 -> Int #

peekElemOff :: Ptr IPv4 -> Int -> IO IPv4 #

pokeElemOff :: Ptr IPv4 -> Int -> IPv4 -> IO () #

peekByteOff :: Ptr b -> Int -> IO IPv4 #

pokeByteOff :: Ptr b -> Int -> IPv4 -> IO () #

peek :: Ptr IPv4 -> IO IPv4 #

poke :: Ptr IPv4 -> IPv4 -> IO () #

Bits IPv4 Source #

Note: we use network order (big endian) as opposed to host order (little endian) which differs from the underlying IPv4 type representation.

FiniteBits IPv4 Source # 
Prim IPv4 Source # 
Unbox IPv4 Source # 
Vector Vector IPv4 Source # 
MVector MVector IPv4 Source # 
type Rep IPv4 Source # 
type Rep IPv4 = D1 * (MetaData "IPv4" "Net.IPv4" "ip-1.2.0-8CzvWTqY9MS39eJl8Vj0" True) (C1 * (MetaCons "IPv4" PrefixI True) (S1 * (MetaSel (Just Symbol "getIPv4") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32)))
data Vector IPv4 Source # 
data MVector s IPv4 Source # 

Interoperability

The network library is commonly used to open sockets and communicate over them. In the Network.Socket module, it provides a type synonym HostAddress that, like IPv4, is used to represent an IPv4 address. However, while IPv4 uses a big-endian representation for ip addresses, HostAddress has platform dependent endianness. Consequently, it is necessary to convert between the two as follows:

import Network.Socket (HostAddress,htonl,ntohl)

toHostAddr :: IPv4 -> HostAddress
toHostAddr (IPv4 w) = htonl w

fromHostAddr :: HostAddress -> IPv4
fromHostAddr w = IPv4 (ntohl w)

These functions are not included with this library since it would require picking up a dependency on network.