{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
#if __GLASGOW_HASKELL__ >= 800
{-# OPTIONS_GHC -Wno-missing-signatures #-}
#else
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
#endif
module Database.InfluxDB.Ping
(
ping
, PingParams
, pingParams
, server
, manager
, timeout
, Pong
, roundtripTime
, influxdbVersion
) where
import Control.Exception
import Control.Lens
import Data.Time.Clock (NominalDiffTime)
import System.Clock
import qualified Data.ByteString as BS
import qualified Data.Text.Encoding as TE
import qualified Network.HTTP.Client as HC
import Database.InfluxDB.Types as Types
data PingParams = PingParams
{ PingParams -> Server
pingServer :: !Server
, PingParams -> Either ManagerSettings Manager
pingManager :: !(Either HC.ManagerSettings HC.Manager)
, PingParams -> Maybe NominalDiffTime
pingTimeout :: !(Maybe NominalDiffTime)
}
pingParams :: PingParams
pingParams :: PingParams
pingParams = PingParams :: Server
-> Either ManagerSettings Manager
-> Maybe NominalDiffTime
-> PingParams
PingParams
{ pingServer :: Server
pingServer = Server
defaultServer
, pingManager :: Either ManagerSettings Manager
pingManager = ManagerSettings -> Either ManagerSettings Manager
forall a b. a -> Either a b
Left ManagerSettings
HC.defaultManagerSettings
, pingTimeout :: Maybe NominalDiffTime
pingTimeout = Maybe NominalDiffTime
forall a. Maybe a
Nothing
}
makeLensesWith
( lensRules
& generateSignatures .~ False
& lensField .~ lookingupNamer
[ ("pingServer", "_server")
, ("pingManager", "_manager")
, ("pingTimeout", "timeout")
]
)
''PingParams
instance HasServer PingParams where
server :: (Server -> f Server) -> PingParams -> f PingParams
server = (Server -> f Server) -> PingParams -> f PingParams
Lens' PingParams Server
_server
instance HasManager PingParams where
manager :: (Either ManagerSettings Manager
-> f (Either ManagerSettings Manager))
-> PingParams -> f PingParams
manager = (Either ManagerSettings Manager
-> f (Either ManagerSettings Manager))
-> PingParams -> f PingParams
Lens' PingParams (Either ManagerSettings Manager)
_manager
timeout :: Lens' PingParams (Maybe NominalDiffTime)
pingRequest :: PingParams -> HC.Request
pingRequest :: PingParams -> Request
pingRequest PingParams {Maybe NominalDiffTime
Either ManagerSettings Manager
Server
pingTimeout :: Maybe NominalDiffTime
pingManager :: Either ManagerSettings Manager
pingServer :: Server
pingTimeout :: PingParams -> Maybe NominalDiffTime
pingManager :: PingParams -> Either ManagerSettings Manager
pingServer :: PingParams -> Server
..} = Request
HC.defaultRequest
{ host :: ByteString
HC.host = Text -> ByteString
TE.encodeUtf8 Text
_host
, port :: Int
HC.port = Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
_port
, secure :: Bool
HC.secure = Bool
_ssl
, method :: ByteString
HC.method = ByteString
"GET"
, path :: ByteString
HC.path = ByteString
"/ping"
}
where
Server {Bool
Int
Text
_ssl :: Server -> Bool
_port :: Server -> Int
_host :: Server -> Text
_ssl :: Bool
_port :: Int
_host :: Text
..} = Server
pingServer
data Pong = Pong
{ Pong -> TimeSpec
_roundtripTime :: !TimeSpec
, Pong -> ByteString
_influxdbVersion :: !BS.ByteString
} deriving (Int -> Pong -> ShowS
[Pong] -> ShowS
Pong -> String
(Int -> Pong -> ShowS)
-> (Pong -> String) -> ([Pong] -> ShowS) -> Show Pong
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pong] -> ShowS
$cshowList :: [Pong] -> ShowS
show :: Pong -> String
$cshow :: Pong -> String
showsPrec :: Int -> Pong -> ShowS
$cshowsPrec :: Int -> Pong -> ShowS
Show, Pong -> Pong -> Bool
(Pong -> Pong -> Bool) -> (Pong -> Pong -> Bool) -> Eq Pong
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pong -> Pong -> Bool
$c/= :: Pong -> Pong -> Bool
== :: Pong -> Pong -> Bool
$c== :: Pong -> Pong -> Bool
Eq, Eq Pong
Eq Pong
-> (Pong -> Pong -> Ordering)
-> (Pong -> Pong -> Bool)
-> (Pong -> Pong -> Bool)
-> (Pong -> Pong -> Bool)
-> (Pong -> Pong -> Bool)
-> (Pong -> Pong -> Pong)
-> (Pong -> Pong -> Pong)
-> Ord Pong
Pong -> Pong -> Bool
Pong -> Pong -> Ordering
Pong -> Pong -> Pong
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Pong -> Pong -> Pong
$cmin :: Pong -> Pong -> Pong
max :: Pong -> Pong -> Pong
$cmax :: Pong -> Pong -> Pong
>= :: Pong -> Pong -> Bool
$c>= :: Pong -> Pong -> Bool
> :: Pong -> Pong -> Bool
$c> :: Pong -> Pong -> Bool
<= :: Pong -> Pong -> Bool
$c<= :: Pong -> Pong -> Bool
< :: Pong -> Pong -> Bool
$c< :: Pong -> Pong -> Bool
compare :: Pong -> Pong -> Ordering
$ccompare :: Pong -> Pong -> Ordering
$cp1Ord :: Eq Pong
Ord)
makeLensesWith (lensRules & generateSignatures .~ False) ''Pong
roundtripTime :: Lens' Pong TimeSpec
influxdbVersion :: Lens' Pong BS.ByteString
ping :: PingParams -> IO Pong
ping :: PingParams -> IO Pong
ping PingParams
params = do
Manager
manager' <- (ManagerSettings -> IO Manager)
-> (Manager -> IO Manager)
-> Either ManagerSettings Manager
-> IO Manager
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ManagerSettings -> IO Manager
HC.newManager Manager -> IO Manager
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ManagerSettings Manager -> IO Manager)
-> Either ManagerSettings Manager -> IO Manager
forall a b. (a -> b) -> a -> b
$ PingParams -> Either ManagerSettings Manager
pingManager PingParams
params
TimeSpec
startTime <- IO TimeSpec
getTimeMonotonic
Request -> Manager -> (Response BodyReader -> IO Pong) -> IO Pong
forall a.
Request -> Manager -> (Response BodyReader -> IO a) -> IO a
HC.withResponse Request
request Manager
manager' ((Response BodyReader -> IO Pong) -> IO Pong)
-> (Response BodyReader -> IO Pong) -> IO Pong
forall a b. (a -> b) -> a -> b
$ \Response BodyReader
response -> do
TimeSpec
endTime <- IO TimeSpec
getTimeMonotonic
case HeaderName -> [(HeaderName, ByteString)] -> Maybe ByteString
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
"X-Influxdb-Version" (Response BodyReader -> [(HeaderName, ByteString)]
forall body. Response body -> [(HeaderName, ByteString)]
HC.responseHeaders Response BodyReader
response) of
Just ByteString
version ->
Pong -> IO Pong
forall (m :: * -> *) a. Monad m => a -> m a
return (Pong -> IO Pong) -> Pong -> IO Pong
forall a b. (a -> b) -> a -> b
$! TimeSpec -> ByteString -> Pong
Pong (TimeSpec -> TimeSpec -> TimeSpec
diffTimeSpec TimeSpec
endTime TimeSpec
startTime) ByteString
version
Maybe ByteString
Nothing ->
InfluxException -> IO Pong
forall e a. Exception e => e -> IO a
throwIO (InfluxException -> IO Pong) -> InfluxException -> IO Pong
forall a b. (a -> b) -> a -> b
$ String -> Request -> ByteString -> InfluxException
UnexpectedResponse
String
"The X-Influxdb-Version header was missing in the response."
Request
request
ByteString
""
IO Pong -> (HttpException -> IO Pong) -> IO Pong
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (InfluxException -> IO Pong
forall e a. Exception e => e -> IO a
throwIO (InfluxException -> IO Pong)
-> (HttpException -> InfluxException) -> HttpException -> IO Pong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HttpException -> InfluxException
HTTPException)
where
request :: Request
request = (PingParams -> Request
pingRequest PingParams
params)
{ responseTimeout :: ResponseTimeout
HC.responseTimeout = case PingParams -> Maybe NominalDiffTime
pingTimeout PingParams
params of
Maybe NominalDiffTime
Nothing -> ResponseTimeout
HC.responseTimeoutNone
Just NominalDiffTime
sec -> Int -> ResponseTimeout
HC.responseTimeoutMicro (Int -> ResponseTimeout) -> Int -> ResponseTimeout
forall a b. (a -> b) -> a -> b
$
Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Int) -> Double -> Int
forall a b. (a -> b) -> a -> b
$ NominalDiffTime -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac NominalDiffTime
sec Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
10Double -> Double -> Double
forall a. Floating a => a -> a -> a
**(-Double
6) :: Double)
}
getTimeMonotonic :: IO TimeSpec
getTimeMonotonic = Clock -> IO TimeSpec
getTime Clock
Monotonic