{-# LANGUAGE CPP               #-}
{-# LANGUAGE OverloadedStrings #-}
module Database.CQL.IO.Cluster.Host where
import Control.Lens (Lens')
import Database.CQL.Protocol (Response (..))
import Database.CQL.IO.Cluster.Discovery
import Data.IP
import Data.Text (Text, unpack)
import Network.Socket (SockAddr (..), PortNumber)
data Host = Host
    { _hostAddr   :: !InetAddr
    , _dataCentre :: !Text
    , _rack       :: !Text
    }
instance Eq Host where
    a == b = _hostAddr a == _hostAddr b
instance Ord Host where
    compare a b = compare (_hostAddr a) (_hostAddr b)
peer2Host :: PortNumber -> Peer -> Host
peer2Host i p = Host (ip2inet i (peerRPC p)) (peerDC p) (peerRack p)
updateHost :: Host -> Maybe (Text, Text) -> Host
updateHost h (Just (dc, rk)) = h { _dataCentre = dc, _rack = rk }
updateHost h Nothing         = h
data HostResponse k a b = HostResponse
    { hrHost     :: !Host
    , hrResponse :: !(Response k a b)
    } deriving (Show)
data HostEvent
    = HostNew  !Host     
    | HostGone !InetAddr 
    | HostUp   !InetAddr 
    | HostDown !InetAddr 
hostAddr :: Lens' Host InetAddr
hostAddr f ~(Host a c r) = fmap (\x -> Host x c r) (f a)
{-# INLINE hostAddr #-}
dataCentre :: Lens' Host Text
dataCentre f ~(Host a c r) = fmap (\x -> Host a x r) (f c)
{-# INLINE dataCentre #-}
rack :: Lens' Host Text
rack f ~(Host a c r) = fmap (\x -> Host a c x) (f r)
{-# INLINE rack #-}
instance Show Host where
    show h = showString (unpack (_dataCentre h))
           . showString ":"
           . showString (unpack (_rack h))
           . showString ":"
           . shows (_hostAddr h)
           $ ""
newtype InetAddr = InetAddr { sockAddr :: SockAddr }
    deriving (Eq, Ord)
instance Show InetAddr where
    show (InetAddr (SockAddrInet p a)) =
        let i = fromIntegral p :: Int in
        shows (fromHostAddress a) . showString ":" . shows i $ ""
    show (InetAddr (SockAddrInet6 p _ a _)) =
        let i = fromIntegral p :: Int in
        shows (fromHostAddress6 a) . showString ":" . shows i $ ""
    show (InetAddr (SockAddrUnix unix)) = unix
#if MIN_VERSION_network(2,6,1) && !MIN_VERSION_network(3,0,0)
    show (InetAddr (SockAddrCan int32)) = show int32
#endif
sock2inet :: PortNumber -> SockAddr -> InetAddr
sock2inet i (SockAddrInet _ a)      = InetAddr (SockAddrInet i a)
sock2inet i (SockAddrInet6 _ f a b) = InetAddr (SockAddrInet6 i f a b)
sock2inet _ unix                    = InetAddr unix
ip2inet :: PortNumber -> IP -> InetAddr
ip2inet p (IPv4 a) = InetAddr $ SockAddrInet p (toHostAddress a)
ip2inet p (IPv6 a) = InetAddr $ SockAddrInet6 p 0 (toHostAddress6 a) 0