-- | Converting an address in 'SockAddr'.

module Network.SockAddr (
    showSockAddr
  , showSockAddrBS
  ) where

import Data.Bits (shift, (.&.))
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS (pack)
import Network.Socket (SockAddr(..), HostAddress, HostAddress6)
import System.ByteOrder
import Text.Printf

isReversed :: Bool
isReversed :: Bool
isReversed = ByteOrder
byteOrder ByteOrder -> ByteOrder -> Bool
forall a. Eq a => a -> a -> Bool
== ByteOrder
LittleEndian

----------------------------------------------------------------

-- | Convert 'SockAddr' to 'String'. If the address is
--   an IPv4-embedded IPv6 address, the IPv4 is extracted.
--
-- >>> import Network.Socket
-- >>> as <- getAddrInfo (Just defaultHints) (Just "example.org") (Just "http")
-- >>> map (showSockAddr.addrAddress) as
-- ["93.184.216.119","93.184.216.119","2606:2800:220:6d:26bf:1447:1097:aa7","2606:2800:220:6d:26bf:1447:1097:aa7"]
showSockAddr :: SockAddr -> String
showSockAddr :: SockAddr -> String
showSockAddr (SockAddrInet PortNumber
_ HostAddress
addr4)                       = HostAddress -> Bool -> String
showIPv4 HostAddress
addr4 Bool
isReversed
showSockAddr (SockAddrInet6 PortNumber
_ HostAddress
_ (HostAddress
0,HostAddress
0,HostAddress
0x0000ffff,HostAddress
addr4) HostAddress
_) = HostAddress -> Bool -> String
showIPv4 HostAddress
addr4 Bool
False
showSockAddr (SockAddrInet6 PortNumber
_ HostAddress
_ (HostAddress
0,HostAddress
0,HostAddress
0,HostAddress
1) HostAddress
_)              = String
"::1"
showSockAddr (SockAddrInet6 PortNumber
_ HostAddress
_ (HostAddress, HostAddress, HostAddress, HostAddress)
addr6 HostAddress
_)                  = (HostAddress, HostAddress, HostAddress, HostAddress) -> String
showIPv6 (HostAddress, HostAddress, HostAddress, HostAddress)
addr6
showSockAddr SockAddr
_                                            = String
"unknownSocket"

----------------------------------------------------------------

-- HostAddress is network byte order.
showIPv4 :: HostAddress -> Bool-> String
showIPv4 :: HostAddress -> Bool -> String
showIPv4 HostAddress
w32 Bool
reversed
  | Bool
reversed  = HostAddress -> String
forall a. Show a => a -> String
show HostAddress
b1 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ HostAddress -> String
forall a. Show a => a -> String
show HostAddress
b2 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ HostAddress -> String
forall a. Show a => a -> String
show HostAddress
b3 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ HostAddress -> String
forall a. Show a => a -> String
show HostAddress
b4
  | Bool
otherwise = HostAddress -> String
forall a. Show a => a -> String
show HostAddress
b4 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ HostAddress -> String
forall a. Show a => a -> String
show HostAddress
b3 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ HostAddress -> String
forall a. Show a => a -> String
show HostAddress
b2 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ HostAddress -> String
forall a. Show a => a -> String
show HostAddress
b1
  where
    t1 :: HostAddress
t1 = HostAddress
w32
    t2 :: HostAddress
t2 = HostAddress -> Int -> HostAddress
forall a. Bits a => a -> Int -> a
shift HostAddress
t1 (-Int
8)
    t3 :: HostAddress
t3 = HostAddress -> Int -> HostAddress
forall a. Bits a => a -> Int -> a
shift HostAddress
t2 (-Int
8)
    t4 :: HostAddress
t4 = HostAddress -> Int -> HostAddress
forall a. Bits a => a -> Int -> a
shift HostAddress
t3 (-Int
8)
    b1 :: HostAddress
b1 = HostAddress
t1 HostAddress -> HostAddress -> HostAddress
forall a. Bits a => a -> a -> a
.&. HostAddress
0x000000ff
    b2 :: HostAddress
b2 = HostAddress
t2 HostAddress -> HostAddress -> HostAddress
forall a. Bits a => a -> a -> a
.&. HostAddress
0x000000ff
    b3 :: HostAddress
b3 = HostAddress
t3 HostAddress -> HostAddress -> HostAddress
forall a. Bits a => a -> a -> a
.&. HostAddress
0x000000ff
    b4 :: HostAddress
b4 = HostAddress
t4 HostAddress -> HostAddress -> HostAddress
forall a. Bits a => a -> a -> a
.&. HostAddress
0x000000ff

-- HostAddress6 is host byte order.
showIPv6 :: HostAddress6 -> String
showIPv6 :: (HostAddress, HostAddress, HostAddress, HostAddress) -> String
showIPv6 (HostAddress
w1,HostAddress
w2,HostAddress
w3,HostAddress
w4) =
    String
-> HostAddress
-> HostAddress
-> HostAddress
-> HostAddress
-> HostAddress
-> HostAddress
-> HostAddress
-> HostAddress
-> String
forall r. PrintfType r => String -> r
printf String
"%x:%x:%x:%x:%x:%x:%x:%x" HostAddress
s1 HostAddress
s2 HostAddress
s3 HostAddress
s4 HostAddress
s5 HostAddress
s6 HostAddress
s7 HostAddress
s8
  where
    (HostAddress
s1,HostAddress
s2) = HostAddress -> (HostAddress, HostAddress)
forall a. (Bits a, Num a) => a -> (a, a)
split16 HostAddress
w1
    (HostAddress
s3,HostAddress
s4) = HostAddress -> (HostAddress, HostAddress)
forall a. (Bits a, Num a) => a -> (a, a)
split16 HostAddress
w2
    (HostAddress
s5,HostAddress
s6) = HostAddress -> (HostAddress, HostAddress)
forall a. (Bits a, Num a) => a -> (a, a)
split16 HostAddress
w3
    (HostAddress
s7,HostAddress
s8) = HostAddress -> (HostAddress, HostAddress)
forall a. (Bits a, Num a) => a -> (a, a)
split16 HostAddress
w4
    split16 :: a -> (a, a)
split16 a
w = (a
h1,a
h2)
      where
        h1 :: a
h1 = a -> Int -> a
forall a. Bits a => a -> Int -> a
shift a
w (-Int
16) a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
0x0000ffff
        h2 :: a
h2 = a
w a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
0x0000ffff

----------------------------------------------------------------

-- | Convert 'SockAddr' to 'ByteString'. If the address is
--   an IPv4-embedded IPv6 address, the IPv4 is extracted.
--
-- >>> import Network.Socket
-- >>> as <- getAddrInfo (Just defaultHints) (Just "localhost") (Just "http")
-- >>> map (showSockAddrBS.addrAddress) as
-- ["127.0.0.1","::1","fe80:0:0:0:0:0:0:1"]

showSockAddrBS :: SockAddr -> ByteString
showSockAddrBS :: SockAddr -> ByteString
showSockAddrBS = String -> ByteString
BS.pack (String -> ByteString)
-> (SockAddr -> String) -> SockAddr -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SockAddr -> String
showSockAddr