hostaddress-0.1.0.0: Network Host Addresses

CopyrightCopyright © 2020 Lars Kuhtz <lakuhtz@gmail.com>
LicenseMIT
MaintainerLars Kuhtz <lakuhtz@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Network.HostAddress

Contents

Description

Host addresses as described in RFC2396 section 3.2.2 with additional consideration of

  • RFC1123 (additional restrictions for hostnames),
  • RFC1034 (disambiguate domain names and IPv4 addresses),
  • RFC4291 (parsing of IPv6 addresses), and
  • RFC3986 and RFC5952 (IPv6 literals within host addresses).

Port numbers must be within the range [0,2^16-1].

All hostnames are considered fully qualified and thus the final dot is omitted.

For hostnames we follow the specification for "Server-based Naming Authority" for URIs from RFC2396 section 3.2.2.:

     hostport      = host [ ":" port ]
     host          = hostname | IPv4address
     hostname      = *( domainlabel "." ) toplabel [ "." ]
     domainlabel   = alphanum | alphanum *( alphanum | "-" ) alphanum
     toplabel      = alpha | alpha *( alphanum | "-" ) alphanum

     IPv4address   = 1*digit "." 1*digit "." 1*digit "." 1*digit
     port          = *digit

1*digit designates the decimal representation of an octet. The specification takes the form of hostnames from section 2.1 RFC1123, but limiting the rightmost (top-most) label to the from given in section 3 of RFC1034, which allows to disambiguate domain names and IPv4 addresses.

IPv6 Addresses are partially supported. IPv6 address are parsed as described in RFC4291, but embedding of IPv4 addresses is not supported. IPv6 addresses are printed exactly as they where parsed. No normalization is performed. In particular the recommendations from RFC5952 are not considered. For host addresses RFC3986 and RFC5952 are followed by requiring that IPv6 literals are enclosed in square brackets. Anything else from RFC3986, which is concerning URIs is ignored.

Additional restriction for hostname apply from RFC1123: labels must have not more than 63 octets, letters are case-insensitive. The maximum length must not exceed 254 octets, excluding the (optional) terminating dot.

See https://cs.uwaterloo.ca/twiki/view/CF/HostNamingRules for an extensive overview of different standards for host names.

Non-ascii characters are encoded via Punycode and are of no concern in this implementation.

Synopsis

Port Numbers

data Port Source #

Instances
Bounded Port Source # 
Instance details

Defined in Network.HostAddress

Enum Port Source # 
Instance details

Defined in Network.HostAddress

Methods

succ :: Port -> Port #

pred :: Port -> Port #

toEnum :: Int -> Port #

fromEnum :: Port -> Int #

enumFrom :: Port -> [Port] #

enumFromThen :: Port -> Port -> [Port] #

enumFromTo :: Port -> Port -> [Port] #

enumFromThenTo :: Port -> Port -> Port -> [Port] #

Eq Port Source # 
Instance details

Defined in Network.HostAddress

Methods

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

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

Integral Port Source # 
Instance details

Defined in Network.HostAddress

Methods

quot :: Port -> Port -> Port #

rem :: Port -> Port -> Port #

div :: Port -> Port -> Port #

mod :: Port -> Port -> Port #

quotRem :: Port -> Port -> (Port, Port) #

divMod :: Port -> Port -> (Port, Port) #

toInteger :: Port -> Integer #

Num Port Source # 
Instance details

Defined in Network.HostAddress

Methods

(+) :: Port -> Port -> Port #

(-) :: Port -> Port -> Port #

(*) :: Port -> Port -> Port #

negate :: Port -> Port #

abs :: Port -> Port #

signum :: Port -> Port #

fromInteger :: Integer -> Port #

Ord Port Source # 
Instance details

Defined in Network.HostAddress

Methods

compare :: Port -> Port -> Ordering #

(<) :: Port -> Port -> Bool #

(<=) :: Port -> Port -> Bool #

(>) :: Port -> Port -> Bool #

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

max :: Port -> Port -> Port #

min :: Port -> Port -> Port #

Real Port Source # 
Instance details

Defined in Network.HostAddress

Methods

toRational :: Port -> Rational #

Show Port Source # 
Instance details

Defined in Network.HostAddress

Methods

showsPrec :: Int -> Port -> ShowS #

show :: Port -> String #

showList :: [Port] -> ShowS #

Generic Port Source # 
Instance details

Defined in Network.HostAddress

Associated Types

type Rep Port :: Type -> Type #

Methods

from :: Port -> Rep Port x #

to :: Rep Port x -> Port #

NFData Port Source # 
Instance details

Defined in Network.HostAddress

Methods

rnf :: Port -> () #

Hashable Port Source # 
Instance details

Defined in Network.HostAddress

Methods

hashWithSalt :: Int -> Port -> Int #

hash :: Port -> Int #

type Rep Port Source # 
Instance details

Defined in Network.HostAddress

type Rep Port = D1 (MetaData "Port" "Network.HostAddress" "hostaddress-0.1.0.0-F3mdNZ0s3Us5jbXgpRWOxN" True) (C1 (MetaCons "Port" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16)))

Hostnames

data Hostname Source #

Instances
Eq Hostname Source # 
Instance details

Defined in Network.HostAddress

Ord Hostname Source # 
Instance details

Defined in Network.HostAddress

Show Hostname Source # 
Instance details

Defined in Network.HostAddress

Generic Hostname Source # 
Instance details

Defined in Network.HostAddress

Associated Types

type Rep Hostname :: Type -> Type #

Methods

from :: Hostname -> Rep Hostname x #

to :: Rep Hostname x -> Hostname #

NFData Hostname Source # 
Instance details

Defined in Network.HostAddress

Methods

rnf :: Hostname -> () #

Hashable Hostname Source # 
Instance details

Defined in Network.HostAddress

Methods

hashWithSalt :: Int -> Hostname -> Int #

hash :: Hostname -> Int #

type Rep Hostname Source # 
Instance details

Defined in Network.HostAddress

Special Host Names

localhostIPv4 :: Hostname Source #

Using explicit IP addresses and not to "localhost" greatly improves networking performance and Mac OS X.

localhostIPv6 :: Hostname Source #

Using explicit IP addresses and not to "localhost" greatly improves networking performance and Mac OS X.

HostAddresses

data HostAddress Source #

Instances
Eq HostAddress Source # 
Instance details

Defined in Network.HostAddress

Ord HostAddress Source # 
Instance details

Defined in Network.HostAddress

Show HostAddress Source # 
Instance details

Defined in Network.HostAddress

Generic HostAddress Source # 
Instance details

Defined in Network.HostAddress

Associated Types

type Rep HostAddress :: Type -> Type #

NFData HostAddress Source # 
Instance details

Defined in Network.HostAddress

Methods

rnf :: HostAddress -> () #

Hashable HostAddress Source # 
Instance details

Defined in Network.HostAddress

type Rep HostAddress Source # 
Instance details

Defined in Network.HostAddress

type Rep HostAddress = D1 (MetaData "HostAddress" "Network.HostAddress" "hostaddress-0.1.0.0-F3mdNZ0s3Us5jbXgpRWOxN" False) (C1 (MetaCons "HostAddress" PrefixI True) (S1 (MetaSel (Just "_hostAddressHost") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Hostname) :*: S1 (MetaSel (Just "_hostAddressPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Port)))

Special Host Addresses