module Network.IP.Addr
(
IP4(..)
, anIP4
, ip4ToOctets
, ip4ToOctetList
, ip4FromOctets
, ip4FromOctetList
, anyIP4
, loopbackIP4
, broadcastIP4
, Range4(..)
, ip4Range
, IP6(..)
, anIP6
, ip6ToWords
, ip6ToWordList
, ip6FromWords
, ip6FromWordList
, anyIP6
, loopbackIP6
, Range6(..)
, ip6Range
, IP46(..)
, anIP46
, anIP46Of
, IP
, anIP
, IsNetAddr(..)
, Net4Addr
, Net6Addr
, NetAddr
, aNetAddr
, aNetAddrOf
, aNet4Addr
, aNet6Addr
, aNetAddrIP
, net4Addr
, net6Addr
, toNetAddr46
, fromNetAddr46
, printNetAddr
, net4Parser
, net6Parser
, netParser
, putNetAddr
, getNetAddr
, InetPort(..)
, anInetPort
, InetAddr(..)
, Inet4Addr
, Inet6Addr
, anInetAddr
, anInetAddrOf
, anInet4Addr
, anInet6Addr
, anInetAddrIP
, toInetAddr46
, fromInetAddr46
) where
import Prelude hiding (print)
import Data.Typeable (Typeable)
#if !MIN_VERSION_base(4,10,0)
import Data.Typeable (Typeable1)
#endif
import Data.Data (Data)
import Data.Word
import Data.Bits
import Data.DoubleWord (BinaryWord(..), DoubleWord(..), Word128)
import Data.Ix (Ix)
import Data.Endian
import Data.Default.Class
import Data.Hashable
import Data.Serializer (Serializer, Serializable, SizedSerializable)
import qualified Data.Serializer as S
import Data.Deserializer (Deserializer, Deserializable)
import qualified Data.Deserializer as D
import Text.Printer (Printer, (<>))
import qualified Text.Printer as P
import qualified Text.Printer.Integral as P
import Data.Textual
import Data.Textual.Integral hiding (Binary)
import Text.Parser.Combinators ((<?>), try)
import Text.Parser.Char (CharParsing)
import qualified Text.Parser.Char as PC
import Text.Printf (printf)
import Type.Hint
import Control.Applicative
import Control.Monad (void, when)
import Foreign.Ptr (castPtr)
import Foreign.Storable (Storable(..))
newtype IP4 = IP4 { unIP4 ∷ Word32 }
deriving (Typeable, Data, Eq, Ord, Bounded, Enum, Ix, Num, Bits, Hashable)
anIP4 ∷ Proxy IP4
anIP4 = Proxy
instance Show IP4 where
showsPrec p a = showParen (p > 10)
$ showString "ip4FromOctets "
. showsPrec 11 o1
. showString " "
. showsPrec 11 o2
. showString " "
. showsPrec 11 o3
. showString " "
. showsPrec 11 o4
where (o1, o2, o3, o4) = ip4ToOctets a
instance Read IP4 where
readsPrec p = readParen (p > 10) $ \i →
[ (ip4FromOctets o1 o2 o3 o4, i4)
| ("ip4FromOctets", i') ← lex i
, (o1, i1) ← readsPrec 11 i'
, (o2, i2) ← readsPrec 11 i1
, (o3, i3) ← readsPrec 11 i2
, (o4, i4) ← readsPrec 11 i3 ]
instance Printable IP4 where
print = P.fsep (P.char7 '.') . (P.nonNegative Decimal <$>) . ip4ToOctetList
instance Textual IP4 where
textual = (<?> "IPv4 address")
$ ip4FromOctets
<$> (octet <* PC.char '.')
<*> (octet <* PC.char '.')
<*> (octet <* PC.char '.')
<*> octet
where octet = (<?> "IPv4 octet") $ do
o ← nnUpTo Decimal 3
if o > 255
then fail "out of bounds"
else return $ fromIntegral (o ∷ Int)
instance Storable IP4 where
alignment _ = alignment (undefined ∷ Word32)
sizeOf _ = 4
peek p = IP4 . fromBigEndian <$> peek (castPtr p)
poke p = poke (castPtr p) . toBigEndian . unIP4
instance Serializable IP4 where
put = S.word32B . unIP4
instance SizedSerializable IP4 where
size _ = 4
instance Deserializable IP4 where
get = IP4 <$> D.word32B <?> "IPv4 address"
ip4ToOctets ∷ IP4 → (Word8, Word8, Word8, Word8)
ip4ToOctets (IP4 w) = ( fromIntegral $ w `shiftR` 24
, fromIntegral $ w `shiftR` 16
, fromIntegral $ w `shiftR` 8
, fromIntegral w
)
ip4ToOctetList ∷ IP4 → [Word8]
ip4ToOctetList (IP4 w) = fromIntegral <$>
[w `shiftR` 24, w `shiftR` 16, w `shiftR` 8, w]
ip4FromOctets ∷ Word8 → Word8 → Word8 → Word8 → IP4
ip4FromOctets o1 o2 o3 o4 =
IP4 $ fromIntegral o1 `shiftL` 24
.|. fromIntegral o2 `shiftL` 16
.|. fromIntegral o3 `shiftL` 8
.|. fromIntegral o4
ip4FromOctetList ∷ [Word8] → Maybe IP4
ip4FromOctetList [o1, o2, o3, o4] = Just $ ip4FromOctets o1 o2 o3 o4
ip4FromOctetList _ = Nothing
anyIP4 ∷ IP4
anyIP4 = IP4 0
instance Default IP4 where
def = anyIP4
loopbackIP4 ∷ IP4
loopbackIP4 = IP4 0x7F000001
broadcastIP4 ∷ IP4
broadcastIP4 = IP4 0xFFFFFFFF
data Range4 = GeneralIP4
| ThisHostIP4
| PrivateUseIP4
| SharedSpaceIP4
| LoopbackIP4
| LinkLocalIP4
| ReservedIP4
| DSLiteIP4
| DocumentationIP4
| IP6To4IP4
| BenchmarkingIP4
| MulticastIP4
| FutureUseIP4
| BroadcastIP4
deriving (Typeable, Data, Show, Read, Eq, Ord, Enum)
ip4Range ∷ IP4 → Range4
ip4Range addr = case w1 of
0 → ThisHostIP4
10 → PrivateUseIP4
100 → if w2 .&. 0xC0 == 0x40 then SharedSpaceIP4 else GeneralIP4
127 → LoopbackIP4
169 → if w2 == 254 then LinkLocalIP4 else GeneralIP4
172 → if w2 .&. 0xF0 == 0x10 then PrivateUseIP4 else GeneralIP4
192 → case w2 of
0 → case w3 of
0 → if w4 <= 7 then DSLiteIP4 else ReservedIP4
2 → DocumentationIP4
_ → GeneralIP4
88 → if w3 == 99 then IP6To4IP4 else GeneralIP4
168 → PrivateUseIP4
_ → GeneralIP4
198 → case w2 of
18 → BenchmarkingIP4
19 → BenchmarkingIP4
51 → if w3 == 100 then DocumentationIP4 else GeneralIP4
_ → GeneralIP4
203 → if w2 == 0 && w3 == 113 then DocumentationIP4 else GeneralIP4
_ | addr == broadcastIP4 → BroadcastIP4
_ → case w1 .&. 0xF0 of
224 → MulticastIP4
240 → FutureUseIP4
_ → GeneralIP4
where (w1, w2, w3, w4) = ip4ToOctets addr
newtype IP6 = IP6 { unIP6 ∷ Word128 }
deriving (Typeable, Data, Eq, Ord, Bounded, Enum, Ix, Num, Bits, Hashable)
anIP6 ∷ Proxy IP6
anIP6 = Proxy
instance Show IP6 where
showsPrec p a
= showParen (p > 10)
$ showString
$ printf "ip6FromWords 0x%x 0x%x 0x%x 0x%x 0x%x 0x%x 0x%x 0x%x"
w1 w2 w3 w4 w5 w6 w7 w8
where
(w1, w2, w3, w4, w5, w6, w7, w8) = ip6ToWords a
instance Read IP6 where
readsPrec p = readParen (p > 10) $ \i →
[ (ip6FromWords w1 w2 w3 w4 w5 w6 w7 w8, i8)
| ("ip6FromWords", i') ← lex i
, (w1, i1) ← readsPrec 11 i'
, (w2, i2) ← readsPrec 11 i1
, (w3, i3) ← readsPrec 11 i2
, (w4, i4) ← readsPrec 11 i3
, (w5, i5) ← readsPrec 11 i4
, (w6, i6) ← readsPrec 11 i5
, (w7, i7) ← readsPrec 11 i6
, (w8, i8) ← readsPrec 11 i7 ]
instance Printable IP6 where
print addr = case addrZeroes of
Nothing → P.fsep (P.char7 ':') $ hex <$> addrWords
Just (i, n) → P.fsep (P.char7 ':') (hex <$> take i addrWords)
<> P.string7 "::"
<> P.fsep (P.char7 ':') (hex <$> drop (i + n) addrWords)
where hex = P.nonNegative LowHex
addrWords = ip6ToWordList addr
addrZeroes = go 0 0 0 addrWords
go !i zi zn = \case
[] → if zn <= 1 then Nothing else Just (zi, zn)
(0 : words') → inZeroes (i + 1) zi zn i 1 words'
(_ : words') → go (i + 1) zi zn words'
inZeroes !i zi zn zi' !zn' = \case
[] | zn' <= 1 → if zn <= 1 then Nothing else Just (zi, zn)
| zn <= 1 → Just (zi', zn')
| otherwise → Just $ if zn >= zn' then (zi, zn) else (zi', zn')
(0 : words') → inZeroes (i + 1) zi zn zi' (zn' + 1) words'
(_ : words') | zn' > zn → go (i + 1) zi' zn' words'
| otherwise → go (i + 1) zi zn words'
instance Textual IP6 where
textual = (<?> "IPv6 address") $ optional (PC.char ':') >>= \case
Just _ → do
void $ PC.char ':'
optional word >>= \case
Just w → after 6 0 (fromIntegral w)
Nothing → return anyIP6
Nothing → do
w ← word
before 7 (fromIntegral w)
where
word = nnUpTo Hexadecimal 4 `hintTypeArg` aWord16 <?> "word"
before 0 w = return $ IP6 w
before 1 w = do
void $ PC.char ':'
optional (PC.char ':') >>= \case
Just _ →
return $ IP6 $ w `shiftL` 16
Nothing → do
w' ← word
return $ IP6 $ (w `shiftL` 16) .|. fromIntegral w'
before upTo w = do
void $ PC.char ':'
optional (PC.char ':') >>= \case
Just _ → optional word >>= \case
Just w' →
after (upTo 2) (w `shiftL` (upTo * 16)) (fromIntegral w')
Nothing →
return $ IP6 $ w `shiftL` (upTo * 16)
Nothing → do
w' ← word
before (upTo 1) ((w `shiftL` 16) .|. fromIntegral w')
after 0 w1 w2 = return $ IP6 $ w1 .|. w2
after upTo w1 w2 = optional (PC.char ':') >>= \case
Just _ → do
w ← word
after (upTo 1) w1 ((w2 `shiftL` 16) .|. fromIntegral w)
Nothing →
return $ IP6 $ w1 .|. w2
instance Storable IP6 where
alignment _ = alignment (undefined ∷ Word64)
sizeOf _ = 16
peek p = fmap IP6
$ fromHiAndLo <$> (fromBigEndian <$> peek (castPtr p))
<*> (fromBigEndian <$> peek (castPtr p))
poke p (IP6 w) = do
poke (castPtr p) $ toBigEndian $ hiWord w
poke (castPtr p) $ toBigEndian $ loWord w
instance Serializable IP6 where
put (IP6 w) = S.word64B (hiWord w) <> S.word64B (loWord w)
instance SizedSerializable IP6 where
size _ = 16
instance Deserializable IP6 where
get = fmap IP6 $ fromHiAndLo <$> D.get <*> D.get <?> "IPv6 address"
ip6ToWords ∷ IP6 → (Word16, Word16, Word16, Word16,
Word16, Word16, Word16, Word16)
ip6ToWords (IP6 w) =
( fromIntegral $ hi `shiftR` 48
, fromIntegral $ hi `shiftR` 32
, fromIntegral $ hi `shiftR` 16
, fromIntegral hi
, fromIntegral $ lo `shiftR` 48
, fromIntegral $ lo `shiftR` 32
, fromIntegral $ lo `shiftR` 16
, fromIntegral lo
)
where hi = hiWord w
lo = loWord w
ip6ToWordList ∷ IP6 → [Word16]
ip6ToWordList (IP6 w) = fromIntegral <$>
[ hi `shiftR` 48
, hi `shiftR` 32
, hi `shiftR` 16
, hi
, lo `shiftR` 48
, lo `shiftR` 32
, lo `shiftR` 16
, lo
]
where hi = hiWord w
lo = loWord w
ip6FromWords ∷ Word16 → Word16 → Word16 → Word16
→ Word16 → Word16 → Word16 → Word16
→ IP6
ip6FromWords w1 w2 w3 w4 w5 w6 w7 w8 = IP6 $ fromHiAndLo hi lo
where hi = fromIntegral w1 `shiftL` 48
.|. fromIntegral w2 `shiftL` 32
.|. fromIntegral w3 `shiftL` 16
.|. fromIntegral w4
lo = fromIntegral w5 `shiftL` 48
.|. fromIntegral w6 `shiftL` 32
.|. fromIntegral w7 `shiftL` 16
.|. fromIntegral w8
ip6FromWordList ∷ [Word16] → Maybe IP6
ip6FromWordList [w1, w2, w3, w4, w5, w6, w7, w8] =
Just $ ip6FromWords w1 w2 w3 w4 w5 w6 w7 w8
ip6FromWordList _ = Nothing
anyIP6 ∷ IP6
anyIP6 = IP6 0
instance Default IP6 where
def = anyIP6
loopbackIP6 ∷ IP6
loopbackIP6 = IP6 1
data Range6 = GeneralIP6
| AnyIP6
| LoopbackIP6
| IP4MappedIP6
| IP4EmbeddedIP6
| DiscardIP6
| ReservedIP6
| TeredoIP6
| BenchmarkingIP6
| DocumentationIP6
| OrchidIP6
| IP6To4IP6
| UniqueLocalIP6
| LinkLocalIP6
| MulticastIP6
deriving (Typeable, Data, Show, Read, Eq, Ord, Enum)
ip6Range ∷ IP6 → Range6
ip6Range (IP6 w) = case hi of
0 → case lo of
0 → AnyIP6
1 → LoopbackIP6
_ → GeneralIP6
0x000000000000FFFF → if q3 == 0 then IP4MappedIP6 else GeneralIP6
0x0064FF9B00000000 → if q3 == 0 then IP4EmbeddedIP6 else GeneralIP6
0x0100000000000000 → DiscardIP6
_ → case w1 of
0x2001 → case w2 of
0 → TeredoIP6
2 → if w3 == 0 then BenchmarkingIP6 else GeneralIP6
0xDB8 → DocumentationIP6
_ | w2 .&. 0xFFF0 == 0x10 → OrchidIP6
| w2 .&. 0xFE00 == 0 → ReservedIP6
| otherwise → GeneralIP6
0x2002 → IP6To4IP6
_ | w1 .&. 0xFE00 == 0xFC00 → UniqueLocalIP6
| w1 .&. 0xFFC0 == 0xFE80 → LinkLocalIP6
| w1 >= 0xFF00 → MulticastIP6
| otherwise → GeneralIP6
where hi = hiWord w
lo = loWord w
q1 = hiWord hi
q2 = loWord hi
q3 = hiWord lo
w1 = hiWord q1
w2 = loWord q1
w3 = hiWord q2
data IP46 t₄ t₆ = IPv4 t₄
| IPv6 t₆
deriving (Typeable, Data, Eq, Ord, Show, Read)
anIP46 ∷ Proxy IP46
anIP46 = Proxy
anIP46Of ∷ Proxy t₄ → Proxy t₆ → Proxy (IP46 t₄ t₆)
anIP46Of _ _ = Proxy
type IP = IP46 IP4 IP6
anIP ∷ Proxy IP
anIP = Proxy
instance Printable IP where
print (IPv4 a) = print a
print (IPv6 a) = print a
instance Textual IP where
textual = try (IPv4 <$> textual) <|> (IPv6 <$> textual)
instance Serializable IP where
put (IPv4 a) = S.put (Left a ∷ Either IP4 IP6)
put (IPv6 a) = S.put (Right a ∷ Either IP4 IP6)
instance Deserializable IP where
get = D.get >>= return . either IPv4 IPv6 <?> "IP address"
class IsNetAddr n where
type NetHost n
netHost ∷ n → NetHost n
netHostIx ∷ n → NetHost n
netPrefix ∷ n → NetHost n
netMask ∷ n → NetHost n
netLength ∷ n → Word8
netAddr ∷ NetHost n
→ Word8
→ n
inNetwork ∷ NetHost n
→ n
→ Bool
data NetAddr a = NetAddr a !Word8
deriving Eq
#if !MIN_VERSION_base(4,10,0)
deriving instance Typeable1 NetAddr
#endif
deriving instance Data a ⇒ Data (NetAddr a)
type Net4Addr = NetAddr IP4
type Net6Addr = NetAddr IP6
aNetAddr ∷ Proxy NetAddr
aNetAddr = Proxy
aNetAddrOf ∷ Proxy a → Proxy (NetAddr a)
aNetAddrOf _ = Proxy
aNet4Addr ∷ Proxy Net4Addr
aNet4Addr = Proxy
aNet6Addr ∷ Proxy Net6Addr
aNet6Addr = Proxy
aNetAddrIP ∷ Proxy (NetAddr IP)
aNetAddrIP = Proxy
instance Show a ⇒ Show (NetAddr a) where
showsPrec p (NetAddr a w) = showParen (p > 10)
$ showString "netAddr "
. showsPrec 11 a
. showString " "
. showsPrec 11 w
instance Read Net4Addr where
readsPrec p = readParen (p > 10) $ \i →
[ (netAddr a w, i2)
| ("netAddr", i') ← lex i
, (a, i1) ← readsPrec 11 i'
, (w, i2) ← readsPrec 11 i1 ]
instance Read Net6Addr where
readsPrec p = readParen (p > 10) $ \i →
[ (netAddr a w, i2)
| ("netAddr", i') ← lex i
, (a, i1) ← readsPrec 11 i'
, (w, i2) ← readsPrec 11 i1 ]
instance Read (NetAddr IP) where
readsPrec p = readParen (p > 10) $ \i →
[ (netAddr a w, i2)
| ("netAddr", i') ← lex i
, (a, i1) ← readsPrec 11 i'
, (w, i2) ← readsPrec 11 i1 ]
instance Printable a ⇒ Printable (NetAddr a) where
print (NetAddr a m) = print a <> P.char7 '/' <> print m
instance Textual Net4Addr where
textual = net4Parser
instance Textual Net6Addr where
textual = net6Parser
instance Textual (NetAddr IP) where
textual = netParser
instance Serializable a ⇒ Serializable (NetAddr a) where
put (NetAddr a w) = S.put a <> S.put w
instance SizedSerializable a ⇒ SizedSerializable (NetAddr a) where
size _ = S.size (Proxy ∷ Proxy a) + 1
instance Deserializable Net4Addr where
get = getNetAddr <?> "IPv4 network address"
instance Deserializable Net6Addr where
get = getNetAddr <?> "IPv6 network address"
instance Deserializable (NetAddr IP) where
get = getNetAddr <?> "IP network address"
instance IsNetAddr Net4Addr where
type NetHost Net4Addr = IP4
netHost (NetAddr a _) = a
netHostIx (NetAddr a w) = (a `shiftL` l) `shiftR` l
where l = fromIntegral w
netPrefix (NetAddr a w) = (a `shiftR` l) `shiftL` l
where l = 32 fromIntegral w
netMask (NetAddr _ w) = IP4 $ (allOnes `shiftR` l) `shiftL` l
where l = 32 fromIntegral w
netLength (NetAddr _ w) = w
netAddr a w = NetAddr a (w `min` 32)
inNetwork h (NetAddr a w) = h `shiftR` l == a `shiftR` l
where l = 32 fromIntegral w
instance IsNetAddr Net6Addr where
type NetHost Net6Addr = IP6
netHost (NetAddr a _) = a
netHostIx (NetAddr a w) = (a `shiftL` l) `shiftR` l
where l = fromIntegral w
netPrefix (NetAddr a w) = (a `shiftR` l) `shiftL` l
where l = 128 fromIntegral w
netMask (NetAddr _ w) = IP6 $ (allOnes `shiftR` l) `shiftL` l
where l = 128 fromIntegral w
netLength (NetAddr _ w) = w
netAddr a w = NetAddr a (w `min` 128)
inNetwork h (NetAddr a w) = h `shiftR` l == a `shiftR` l
where l = 128 fromIntegral w
instance IsNetAddr (NetAddr IP) where
type NetHost (NetAddr IP) = IP
netHost (NetAddr a _) = a
netHostIx (NetAddr a w) = case a of
IPv4 a1 → IPv4 $ (a1 `shiftL` l) `shiftR` l
IPv6 a1 → IPv6 $ (a1 `shiftL` l) `shiftR` l
where l = fromIntegral w
netPrefix (NetAddr a w) = case a of
IPv4 a1 → IPv4 $ (a1 `shiftR` l) `shiftL` l
where l = 32 fromIntegral w
IPv6 a1 → IPv6 $ (a1 `shiftR` l) `shiftL` l
where l = 128 fromIntegral w
netMask (NetAddr a w) = case a of
IPv4 _ → IPv4 $ IP4 $ (allOnes `shiftR` l) `shiftL` l
where l = 32 fromIntegral w
IPv6 _ → IPv6 $ IP6 $ (allOnes `shiftR` l) `shiftL` l
where l = 128 fromIntegral w
netLength (NetAddr _ w) = w
netAddr a w = NetAddr a (w `min` m)
where m = case a of
IPv4 _ → 32
IPv6 _ → 128
inNetwork (IPv4 h) (NetAddr (IPv4 a) w) = h `shiftR` l == a `shiftR` l
where l = 32 fromIntegral w
inNetwork (IPv6 h) (NetAddr (IPv6 a) w) = h `shiftR` l == a `shiftR` l
where l = 128 fromIntegral w
inNetwork _ _ = False
net4Addr ∷ IP4 → Word8 → Net4Addr
net4Addr = netAddr
net6Addr ∷ IP6 → Word8 → Net6Addr
net6Addr = netAddr
toNetAddr46 ∷ NetAddr IP → IP46 (NetAddr IP4) (NetAddr IP6)
toNetAddr46 (NetAddr (IPv4 a) w) = IPv4 (NetAddr a w)
toNetAddr46 (NetAddr (IPv6 a) w) = IPv6 (NetAddr a w)
fromNetAddr46 ∷ IP46 (NetAddr IP4) (NetAddr IP6) → NetAddr IP
fromNetAddr46 (IPv4 (NetAddr a w)) = NetAddr (IPv4 a) w
fromNetAddr46 (IPv6 (NetAddr a w)) = NetAddr (IPv6 a) w
printNetAddr ∷ (IsNetAddr n, Printable (NetHost n), Printer p) ⇒ n → p
printNetAddr n = print (netHost n) <> P.char7 '/' <> print (netLength n)
ip4Mask ∷ (CharParsing μ, Monad μ) ⇒ μ Word8
ip4Mask = (<?> "network prefix length") $ do
m ← nncUpTo Decimal 2
when (m > 32) $ fail "out of bounds"
return m
net4Parser ∷ (CharParsing μ, Monad μ, IsNetAddr n, NetHost n ~ IP4) ⇒ μ n
net4Parser = netAddr <$> textual <*> (PC.char '/' *> ip4Mask)
<?> "IPv4 network address"
ip6Mask ∷ (CharParsing μ, Monad μ) ⇒ μ Word8
ip6Mask = (<?> "network prefix length") $ do
m ← nncUpTo Decimal 3
when (m > (128 ∷ Int)) $ fail "out of bounds"
return $ fromIntegral m
net6Parser ∷ (CharParsing μ, Monad μ, IsNetAddr n, NetHost n ~ IP6) ⇒ μ n
net6Parser = netAddr <$> textual <*> (PC.char '/' *> ip6Mask)
<?> "IPv6 network address"
netParser ∷ (IsNetAddr n, NetHost n ~ IP, CharParsing μ, Monad μ) ⇒ μ n
netParser = (<?> "IP network address") $ do
a ← textual
void $ PC.char '/'
m ← mask a
return $ netAddr a m
where
mask (IPv4 _) = ip4Mask
mask (IPv6 _) = ip6Mask
putNetAddr ∷ (IsNetAddr n, Serializable (NetHost n), Serializer s) ⇒ n → s
putNetAddr n = S.put (netHost n) <> S.put (netPrefix n)
getNetAddr ∷ (IsNetAddr n, Deserializable (NetHost n), Deserializer μ) ⇒ μ n
getNetAddr = netAddr <$> D.get <*> D.get
newtype InetPort = InetPort { unInetPort ∷ Word16 }
deriving (Typeable, Data, Eq, Ord, Bounded, Enum, Ix, Num, Real, Integral,
Bits, Hashable, Printable)
anInetPort ∷ Proxy InetPort
anInetPort = Proxy
instance Show InetPort where
showsPrec p (InetPort w) = showsPrec p w
instance Read InetPort where
readsPrec p = fmap (\(w, s) → (InetPort w, s)) . readsPrec p
instance Textual InetPort where
textual = InetPort <$> nncBounded Decimal <?> "port number"
instance Storable InetPort where
alignment _ = alignment (undefined ∷ Word16)
sizeOf _ = 2
peek p = InetPort . fromBigEndian <$> peek (castPtr p)
poke p = poke (castPtr p) . toBigEndian . unInetPort
instance Serializable InetPort where
put = S.word16B . unInetPort
instance SizedSerializable InetPort where
size _ = 2
instance Deserializable InetPort where
get = InetPort <$> D.word16B <?> "port number"
data InetAddr a = InetAddr { inetHost ∷ a
, inetPort ∷ !InetPort
} deriving (Eq, Ord, Show, Read)
#if !MIN_VERSION_base(4,10,0)
deriving instance Typeable1 InetAddr
#endif
deriving instance Data a ⇒ Data (InetAddr a)
type Inet4Addr = InetAddr IP4
type Inet6Addr = InetAddr IP6
anInetAddr ∷ Proxy InetAddr
anInetAddr = Proxy
anInetAddrOf ∷ Proxy a → Proxy (InetAddr a)
anInetAddrOf _ = Proxy
anInet4Addr ∷ Proxy Inet4Addr
anInet4Addr = Proxy
anInet6Addr ∷ Proxy Inet6Addr
anInet6Addr = Proxy
anInetAddrIP ∷ Proxy (InetAddr IP)
anInetAddrIP = Proxy
instance Functor InetAddr where
fmap f (InetAddr a p) = InetAddr (f a) p
instance Printable Inet4Addr where
print (InetAddr a p) = print a <> P.char7 ':' <> print p
instance Printable Inet6Addr where
print (InetAddr a p) = P.brackets (print a) <> P.char7 ':' <> print p
instance Printable (InetAddr IP) where
print (InetAddr (IPv4 a) p) = print (InetAddr a p)
print (InetAddr (IPv6 a) p) = print (InetAddr a p)
instance Textual Inet4Addr where
textual = InetAddr <$> textual <*> (PC.char ':' *> textual)
<?> "IPv4 socket address"
instance Textual Inet6Addr where
textual = InetAddr <$> (PC.char '[' *> textual <* PC.char ']')
<*> (PC.char ':' *> textual)
<?> "IPv6 socket address"
instance Textual (InetAddr IP) where
textual = InetAddr
<$> (optional (PC.char '[') >>= \case
Nothing → IPv4 <$> textual
Just _ → IPv6 <$> textual <* PC.char ']')
<*> (PC.char ':' *> textual)
<?> "IP socket address"
instance Hashable a ⇒ Hashable (InetAddr a) where
#if MIN_VERSION_hashable(1,2,0)
hashWithSalt s (InetAddr a p) = s `hashWithSalt` a `hashWithSalt` p
#else
hash (InetAddr a p) = hash a `combine` hash p
#endif
instance Serializable a ⇒ Serializable (InetAddr a) where
put (InetAddr a p) = S.put a <> S.put p
instance SizedSerializable a ⇒ SizedSerializable (InetAddr a) where
size _ = S.size (Proxy ∷ Proxy a) + 2
instance Deserializable a ⇒ Deserializable (InetAddr a) where
get = InetAddr <$> (D.get <?> "host address") <*> D.get <?> "socket address"
toInetAddr46 ∷ InetAddr IP → IP46 (InetAddr IP4) (InetAddr IP6)
toInetAddr46 (InetAddr (IPv4 a) w) = IPv4 (InetAddr a w)
toInetAddr46 (InetAddr (IPv6 a) w) = IPv6 (InetAddr a w)
fromInetAddr46 ∷ IP46 (InetAddr IP4) (InetAddr IP6) → InetAddr IP
fromInetAddr46 (IPv4 (InetAddr a w)) = InetAddr (IPv4 a) w
fromInetAddr46 (IPv6 (InetAddr a w)) = InetAddr (IPv6 a) w