{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Database.CQL.IO.Cluster.Host where
import Control.Lens ((^.), Lens')
import Data.ByteString.Lazy.Char8 (unpack)
import Database.CQL.Protocol (Response (..))
import Data.IP
import Data.Text (Text)
import Network.Socket (SockAddr (..), PortNumber)
import System.Logger.Message
data Host = Host
{ _hostAddr :: !InetAddr
, _dataCentre :: !Text
, _rack :: !Text
} deriving (Eq, Ord)
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 = unpack . eval . bytes
instance ToBytes Host where
bytes h = h^.dataCentre +++ val ":" +++ h^.rack +++ val ":" +++ h^.hostAddr
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
instance ToBytes InetAddr where
bytes (InetAddr (SockAddrInet p a)) =
let i = fromIntegral p :: Int in
show (fromHostAddress a) +++ val ":" +++ i
bytes (InetAddr (SockAddrInet6 p _ a _)) =
let i = fromIntegral p :: Int in
show (fromHostAddress6 a) +++ val ":" +++ i
bytes (InetAddr (SockAddrUnix unix)) = bytes unix
#if MIN_VERSION_network(2,6,1) && !MIN_VERSION_network(3,0,0)
bytes (InetAddr (SockAddrCan int32)) = bytes int32
#endif
ip2inet :: PortNumber -> IP -> InetAddr
ip2inet p (IPv4 a) = InetAddr $ SockAddrInet p (toHostAddress a)
ip2inet p (IPv6 a) = InetAddr $ SockAddrInet6 p 0 (toHostAddress6 a) 0
inet2ip :: InetAddr -> IP
inet2ip (InetAddr (SockAddrInet _ a)) = IPv4 (fromHostAddress a)
inet2ip (InetAddr (SockAddrInet6 _ _ a _)) = IPv6 (fromHostAddress6 a)
inet2ip _ = error "inet2Ip: not IP4/IP6 address"