{-# LANGUAGE DeriveDataTypeable #-}
{-# OPTIONS_HADDOCK hide #-}
module Network.Simple.Internal
  ( HostPreference(..)
  , hpHostName
  , ipv4mapped_to_ipv4
  , isIPv4addr
  , isIPv6addr
  , prioritize
  , happyEyeballSort
  ) where
import           Data.Bits                     (shiftR, (.&.))
import qualified Data.List                     as List
import           Data.String                   (IsString (fromString))
import           Data.Word                     (byteSwap32)
import qualified Network.Socket as             NS
data HostPreference
  = HostAny          
  | HostIPv4         
  | HostIPv6         
  | Host NS.HostName 
  deriving (Eq, Ord, Show, Read)
instance IsString HostPreference where
  fromString "*"  = HostAny
  fromString "*4" = HostIPv4
  fromString "*6" = HostIPv6
  fromString s    = Host s
hpHostName:: HostPreference -> Maybe NS.HostName
hpHostName (Host s) = Just s
hpHostName _        = Nothing
ipv4mapped_to_ipv4:: NS.SockAddr -> NS.SockAddr
ipv4mapped_to_ipv4 (NS.SockAddrInet6 p _ (0, 0, 0xFFFF, h) _)
  = NS.SockAddrInet p (NS.tupleToHostAddress
      (fromIntegral (shiftR (h .&. 0xFF000000) 24),
       fromIntegral (shiftR (h .&. 0x00FF0000) 16),
       fromIntegral (shiftR (h .&. 0x0000FF00) 8),
       fromIntegral         (h .&. 0x000000FF)))
ipv4mapped_to_ipv4 sa = sa
happyEyeballSort :: [NS.AddrInfo] -> [NS.AddrInfo]
happyEyeballSort l =
    concat (List.transpose ((\(a,b) -> [a,b]) (List.partition isIPv6addr l)))
isIPv4addr :: NS.AddrInfo -> Bool
isIPv4addr x = NS.addrFamily x == NS.AF_INET
isIPv6addr :: NS.AddrInfo -> Bool
isIPv6addr x = NS.addrFamily x == NS.AF_INET6
prioritize :: (a -> Bool) -> [a] -> [a]
prioritize p = uncurry (++) . List.partition p