{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Database.InfluxDB.Types where
import Control.Exception
import Data.Int (Int64)
import Data.String
import Data.Typeable (Typeable)
import GHC.Generics (Generic)

import Control.Lens
import Data.Text (Text)
import Data.Time.Clock
import Data.Time.Clock.POSIX
import Network.HTTP.Client (Manager, ManagerSettings, Request)
import System.Clock (TimeSpec(..))
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Network.HTTP.Client as HC

-- $setup
-- >>> :set -XOverloadedStrings
-- >>> import System.Clock (TimeSpec(..))
-- >>> import Database.InfluxDB
-- >>> import qualified Database.InfluxDB.Format as F

-- | An InfluxDB query.
--
-- A spec of the format is available at
-- <https://docs.influxdata.com/influxdb/v1.7/query_language/spec/>.
--
-- A 'Query' can be constructed using either
--
--   * the 'IsString' instance with @-XOverloadedStrings@
--   * or 'Database.InfluxDB.Format.formatQuery'.
--
-- >>> :set -XOverloadedStrings
-- >>> "SELECT * FROM series" :: Query
-- "SELECT * FROM series"
-- >>> import qualified Database.InfluxDB.Format as F
-- >>> formatQuery ("SELECT * FROM "%F.key) "series"
-- "SELECT * FROM \"series\""
--
-- NOTE: Currently this library doesn't support type-safe query construction.
newtype Query = Query T.Text deriving String -> Query
(String -> Query) -> IsString Query
forall a. (String -> a) -> IsString a
fromString :: String -> Query
$cfromString :: String -> Query
IsString

instance Show Query where
  show :: Query -> String
show (Query Text
q) = Text -> String
forall a. Show a => a -> String
show Text
q

-- | InfluxDB server to connect to.
--
-- Following lenses are available to access its fields:
--
-- * 'host': FQDN or IP address of the InfluxDB server
-- * 'port': Port number of the InfluxDB server
-- * 'ssl': Whether or not to use SSL
data Server = Server
  { Server -> Text
_host :: !Text
  , Server -> Int
_port :: !Int
  , Server -> Bool
_ssl :: !Bool
  } deriving (Int -> Server -> ShowS
[Server] -> ShowS
Server -> String
(Int -> Server -> ShowS)
-> (Server -> String) -> ([Server] -> ShowS) -> Show Server
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Server] -> ShowS
$cshowList :: [Server] -> ShowS
show :: Server -> String
$cshow :: Server -> String
showsPrec :: Int -> Server -> ShowS
$cshowsPrec :: Int -> Server -> ShowS
Show, (forall x. Server -> Rep Server x)
-> (forall x. Rep Server x -> Server) -> Generic Server
forall x. Rep Server x -> Server
forall x. Server -> Rep Server x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Server x -> Server
$cfrom :: forall x. Server -> Rep Server x
Generic, Server -> Server -> Bool
(Server -> Server -> Bool)
-> (Server -> Server -> Bool) -> Eq Server
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Server -> Server -> Bool
$c/= :: Server -> Server -> Bool
== :: Server -> Server -> Bool
$c== :: Server -> Server -> Bool
Eq, Eq Server
Eq Server
-> (Server -> Server -> Ordering)
-> (Server -> Server -> Bool)
-> (Server -> Server -> Bool)
-> (Server -> Server -> Bool)
-> (Server -> Server -> Bool)
-> (Server -> Server -> Server)
-> (Server -> Server -> Server)
-> Ord Server
Server -> Server -> Bool
Server -> Server -> Ordering
Server -> Server -> Server
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 :: Server -> Server -> Server
$cmin :: Server -> Server -> Server
max :: Server -> Server -> Server
$cmax :: Server -> Server -> Server
>= :: Server -> Server -> Bool
$c>= :: Server -> Server -> Bool
> :: Server -> Server -> Bool
$c> :: Server -> Server -> Bool
<= :: Server -> Server -> Bool
$c<= :: Server -> Server -> Bool
< :: Server -> Server -> Bool
$c< :: Server -> Server -> Bool
compare :: Server -> Server -> Ordering
$ccompare :: Server -> Server -> Ordering
$cp1Ord :: Eq Server
Ord)

makeLensesWith (lensRules & generateSignatures .~ False) ''Server

-- | Host name of the server
host :: Lens' Server Text

-- | Port number of the server
port :: Lens' Server Int

-- | If SSL is enabled
--
-- For secure connections (HTTPS), consider using one of the following packages:
--
--  * [http-client-tls](https://hackage.haskell.org/package/http-client-tls)
--  * [http-client-openssl](https://hackage.haskell.org/package/http-client-openssl)
ssl :: Lens' Server Bool

-- | Default InfluxDB server settings
--
-- Default parameters:
--
-- >>> defaultServer ^. host
-- "localhost"
-- >>> defaultServer ^. port
-- 8086
-- >>> defaultServer ^. ssl
-- False
defaultServer :: Server
defaultServer :: Server
defaultServer = Server :: Text -> Int -> Bool -> Server
Server
  { _host :: Text
_host = Text
"localhost"
  , _port :: Int
_port = Int
8086
  , _ssl :: Bool
_ssl = Bool
False
  }

-- | HTTPS-enabled InfluxDB server settings
secureServer :: Server
secureServer :: Server
secureServer = Server
defaultServer Server -> (Server -> Server) -> Server
forall a b. a -> (a -> b) -> b
& (Bool -> Identity Bool) -> Server -> Identity Server
Lens' Server Bool
ssl ((Bool -> Identity Bool) -> Server -> Identity Server)
-> Bool -> Server -> Server
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
True

-- | User credentials.
--
-- Following lenses are available to access its fields:
--
-- * 'user'
-- * 'password'
data Credentials = Credentials
  { Credentials -> Text
_user :: !Text
  , Credentials -> Text
_password :: !Text
  } deriving Int -> Credentials -> ShowS
[Credentials] -> ShowS
Credentials -> String
(Int -> Credentials -> ShowS)
-> (Credentials -> String)
-> ([Credentials] -> ShowS)
-> Show Credentials
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Credentials] -> ShowS
$cshowList :: [Credentials] -> ShowS
show :: Credentials -> String
$cshow :: Credentials -> String
showsPrec :: Int -> Credentials -> ShowS
$cshowsPrec :: Int -> Credentials -> ShowS
Show

-- | Smart constructor for 'Credentials'
credentials
    :: Text -- ^ User name
    -> Text -- ^ Password
    -> Credentials
credentials :: Text -> Text -> Credentials
credentials = Text -> Text -> Credentials
Credentials

makeLensesWith (lensRules & generateSignatures .~ False) ''Credentials

-- | User name to access InfluxDB.
--
-- >>> let creds = credentials "john" "passw0rd"
-- >>> creds ^. user
-- "john"
user :: Lens' Credentials Text

-- | Password to access InfluxDB
--
-- >>> let creds = credentials "john" "passw0rd"
-- >>> creds ^. password
-- "passw0rd"
password :: Lens' Credentials Text

-- | Database name.
--
-- 'Database.InfluxDB.formatDatabase' can be used to construct a
-- 'Database'.
--
-- >>> "test-db" :: Database
-- "test-db"
-- >>> formatDatabase "test-db"
-- "test-db"
-- >>> formatDatabase ("test-db-"%F.decimal) 0
-- "test-db-0"
newtype Database = Database { Database -> Text
databaseName :: Text } deriving (Database -> Database -> Bool
(Database -> Database -> Bool)
-> (Database -> Database -> Bool) -> Eq Database
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Database -> Database -> Bool
$c/= :: Database -> Database -> Bool
== :: Database -> Database -> Bool
$c== :: Database -> Database -> Bool
Eq, Eq Database
Eq Database
-> (Database -> Database -> Ordering)
-> (Database -> Database -> Bool)
-> (Database -> Database -> Bool)
-> (Database -> Database -> Bool)
-> (Database -> Database -> Bool)
-> (Database -> Database -> Database)
-> (Database -> Database -> Database)
-> Ord Database
Database -> Database -> Bool
Database -> Database -> Ordering
Database -> Database -> Database
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 :: Database -> Database -> Database
$cmin :: Database -> Database -> Database
max :: Database -> Database -> Database
$cmax :: Database -> Database -> Database
>= :: Database -> Database -> Bool
$c>= :: Database -> Database -> Bool
> :: Database -> Database -> Bool
$c> :: Database -> Database -> Bool
<= :: Database -> Database -> Bool
$c<= :: Database -> Database -> Bool
< :: Database -> Database -> Bool
$c< :: Database -> Database -> Bool
compare :: Database -> Database -> Ordering
$ccompare :: Database -> Database -> Ordering
$cp1Ord :: Eq Database
Ord)

instance IsString Database where
  fromString :: String -> Database
fromString String
xs = Text -> Database
Database (Text -> Database) -> Text -> Database
forall a b. (a -> b) -> a -> b
$ String -> String -> Text
identifier String
"Database" String
xs

instance Show Database where
  show :: Database -> String
show (Database Text
name) = Text -> String
forall a. Show a => a -> String
show Text
name

-- | String name that is used for measurements.
--
-- 'Database.InfluxDB.formatMeasurement' can be used to construct a
-- 'Measurement'.
--
-- >>> "test-series" :: Measurement
-- "test-series"
-- >>> formatMeasurement "test-series"
-- "test-series"
-- >>> formatMeasurement ("test-series-"%F.decimal) 0
-- "test-series-0"
newtype Measurement = Measurement Text deriving (Measurement -> Measurement -> Bool
(Measurement -> Measurement -> Bool)
-> (Measurement -> Measurement -> Bool) -> Eq Measurement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Measurement -> Measurement -> Bool
$c/= :: Measurement -> Measurement -> Bool
== :: Measurement -> Measurement -> Bool
$c== :: Measurement -> Measurement -> Bool
Eq, Eq Measurement
Eq Measurement
-> (Measurement -> Measurement -> Ordering)
-> (Measurement -> Measurement -> Bool)
-> (Measurement -> Measurement -> Bool)
-> (Measurement -> Measurement -> Bool)
-> (Measurement -> Measurement -> Bool)
-> (Measurement -> Measurement -> Measurement)
-> (Measurement -> Measurement -> Measurement)
-> Ord Measurement
Measurement -> Measurement -> Bool
Measurement -> Measurement -> Ordering
Measurement -> Measurement -> Measurement
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 :: Measurement -> Measurement -> Measurement
$cmin :: Measurement -> Measurement -> Measurement
max :: Measurement -> Measurement -> Measurement
$cmax :: Measurement -> Measurement -> Measurement
>= :: Measurement -> Measurement -> Bool
$c>= :: Measurement -> Measurement -> Bool
> :: Measurement -> Measurement -> Bool
$c> :: Measurement -> Measurement -> Bool
<= :: Measurement -> Measurement -> Bool
$c<= :: Measurement -> Measurement -> Bool
< :: Measurement -> Measurement -> Bool
$c< :: Measurement -> Measurement -> Bool
compare :: Measurement -> Measurement -> Ordering
$ccompare :: Measurement -> Measurement -> Ordering
$cp1Ord :: Eq Measurement
Ord)

instance IsString Measurement where
  fromString :: String -> Measurement
fromString String
xs = Text -> Measurement
Measurement (Text -> Measurement) -> Text -> Measurement
forall a b. (a -> b) -> a -> b
$ String -> String -> Text
identifier String
"Measurement" String
xs

instance Show Measurement where
  show :: Measurement -> String
show (Measurement Text
name) = Text -> String
forall a. Show a => a -> String
show Text
name

-- | String type that is used for tag keys/values and field keys.
--
-- 'Database.InfluxDB.formatKey' can be used to construct a 'Key'.
--
-- >>> "test-key" :: Key
-- "test-key"
-- >>> formatKey "test-key"
-- "test-key"
-- >>> formatKey ("test-key-"%F.decimal) 0
-- "test-key-0"
newtype Key = Key Text deriving (Key -> Key -> Bool
(Key -> Key -> Bool) -> (Key -> Key -> Bool) -> Eq Key
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c== :: Key -> Key -> Bool
Eq, Eq Key
Eq Key
-> (Key -> Key -> Ordering)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Key)
-> (Key -> Key -> Key)
-> Ord Key
Key -> Key -> Bool
Key -> Key -> Ordering
Key -> Key -> Key
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 :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmax :: Key -> Key -> Key
>= :: Key -> Key -> Bool
$c>= :: Key -> Key -> Bool
> :: Key -> Key -> Bool
$c> :: Key -> Key -> Bool
<= :: Key -> Key -> Bool
$c<= :: Key -> Key -> Bool
< :: Key -> Key -> Bool
$c< :: Key -> Key -> Bool
compare :: Key -> Key -> Ordering
$ccompare :: Key -> Key -> Ordering
$cp1Ord :: Eq Key
Ord)

instance IsString Key where
  fromString :: String -> Key
fromString String
xs = Text -> Key
Key (Text -> Key) -> Text -> Key
forall a b. (a -> b) -> a -> b
$ String -> String -> Text
identifier String
"Key" String
xs

instance Show Key where
  show :: Key -> String
show (Key Text
name) = Text -> String
forall a. Show a => a -> String
show Text
name

identifier :: String -> String -> Text
identifier :: String -> String -> Text
identifier String
ty String
xs
  | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = String -> Text
forall a. HasCallStack => String -> a
error (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
ty String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" should never be empty"
  | Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Char
'\n' String
xs = String -> Text
forall a. HasCallStack => String -> a
error (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
ty String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" should not contain a new line"
  | Bool
otherwise = String -> Text
forall a. IsString a => String -> a
fromString String
xs

-- | Nullability of fields.
--
-- Queries can contain nulls but the line protocol cannot.
data Nullability = Nullable | NonNullable deriving Typeable

-- | Field type for queries. Queries can contain null values.
type QueryField = Field 'Nullable

-- | Field type for the line protocol. The line protocol doesn't accept null
-- values.
type LineField = Field 'NonNullable

data Field (n :: Nullability) where
  -- | Signed 64-bit integers (@-9,223,372,036,854,775,808@ to
  -- @9,223,372,036,854,775,807@).
  FieldInt :: !Int64 -> Field n
  -- | IEEE-754 64-bit floating-point numbers. This is the default numerical
  -- type.
  FieldFloat :: !Double -> Field n
  -- | String field. Its length is limited to 64KB, which is not enforced by
  -- this library.
  FieldString :: !Text -> Field n
  -- | Boolean field.
  FieldBool :: !Bool -> Field n
  -- | Null field.
  --
  -- Note that a field can be null only in queries. The line protocol doesn't
  -- allow null values.
  FieldNull :: Field 'Nullable
  deriving Typeable

deriving instance Eq (Field n)
deriving instance Show (Field n)

instance IsString (Field n) where
  fromString :: String -> Field n
fromString = Text -> Field n
forall (n :: Nullability). Text -> Field n
FieldString (Text -> Field n) -> (String -> Text) -> String -> Field n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack

-- | Type of a request
data RequestType
  = QueryRequest
  -- ^ Request for @/query@
  | WriteRequest
  -- ^ Request for @/write@
  deriving Int -> RequestType -> ShowS
[RequestType] -> ShowS
RequestType -> String
(Int -> RequestType -> ShowS)
-> (RequestType -> String)
-> ([RequestType] -> ShowS)
-> Show RequestType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestType] -> ShowS
$cshowList :: [RequestType] -> ShowS
show :: RequestType -> String
$cshow :: RequestType -> String
showsPrec :: Int -> RequestType -> ShowS
$cshowsPrec :: Int -> RequestType -> ShowS
Show

-- | Predefined set of time precision.
--
-- 'RFC3339' is only available for 'QueryRequest's.
data Precision (ty :: RequestType) where
  -- | POSIX time in ns
  Nanosecond :: Precision ty
  -- | POSIX time in μs
  Microsecond :: Precision ty
  -- | POSIX time in ms
  Millisecond :: Precision ty
  -- | POSIX time in s
  Second :: Precision ty
  -- | POSIX time in minutes
  Minute :: Precision ty
  -- | POSIX time in hours
  Hour :: Precision ty
  -- | Nanosecond precision time in a human readable format, like
  -- @2016-01-04T00:00:23.135623Z@. This is the default format for @/query@.
  RFC3339 :: Precision 'QueryRequest

deriving instance Show (Precision a)
deriving instance Eq (Precision a)

-- | Name of the time precision.
--
-- >>> precisionName Nanosecond
-- "n"
-- >>> precisionName Microsecond
-- "u"
-- >>> precisionName Millisecond
-- "ms"
-- >>> precisionName Second
-- "s"
-- >>> precisionName Minute
-- "m"
-- >>> precisionName Hour
-- "h"
-- >>> precisionName RFC3339
-- "rfc3339"
precisionName :: Precision ty -> Text
precisionName :: Precision ty -> Text
precisionName = \case
  Precision ty
Nanosecond -> Text
"n"
  Precision ty
Microsecond -> Text
"u"
  Precision ty
Millisecond -> Text
"ms"
  Precision ty
Second -> Text
"s"
  Precision ty
Minute -> Text
"m"
  Precision ty
Hour -> Text
"h"
  Precision ty
RFC3339 -> Text
"rfc3339"

-- | A 'Timestamp' is something that can be converted to a valid
-- InfluxDB timestamp, which is represented as a 64-bit integer.
class Timestamp time where
  -- | Round a time to the given precision and scale it to nanoseconds
  roundTo :: Precision 'WriteRequest -> time -> Int64
  -- | Scale a time to the given precision
  scaleTo :: Precision 'WriteRequest -> time -> Int64

roundAt :: RealFrac a => a -> a -> a
roundAt :: a -> a -> a
roundAt a
scale a
x = Int64 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
round (a
x a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
scale) :: Int64) a -> a -> a
forall a. Num a => a -> a -> a
* a
scale

-- | Scale of the type precision.
--
-- >>> precisionScale RFC3339
-- 1.0e-9
-- >>> precisionScale Microsecond
-- 1.0e-6
precisionScale :: Fractional a => Precision ty -> a
precisionScale :: Precision ty -> a
precisionScale = \case
  Precision ty
RFC3339 ->     a
10a -> Int -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^(-Int
9 :: Int)
  Precision ty
Nanosecond ->  a
10a -> Int -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^(-Int
9 :: Int)
  Precision ty
Microsecond -> a
10a -> Int -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^(-Int
6 :: Int)
  Precision ty
Millisecond -> a
10a -> Int -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^(-Int
3 :: Int)
  Precision ty
Second -> a
1
  Precision ty
Minute -> a
60
  Precision ty
Hour ->   a
60 a -> a -> a
forall a. Num a => a -> a -> a
* a
60

-- |
-- >>> import Data.Time.Calendar
-- >>> let t = UTCTime (fromGregorian 2018 04 14) 123.123456789
-- >>> t
-- 2018-04-14 00:02:03.123456789 UTC
-- >>> roundTo Nanosecond t
-- 1523664123123456789
-- >>> roundTo Microsecond t
-- 1523664123123457000
-- >>> roundTo Millisecond t
-- 1523664123123000000
-- >>> roundTo Second t
-- 1523664123000000000
-- >>> roundTo Minute t
-- 1523664120000000000
-- >>> roundTo Hour t
-- 1523664000000000000
-- >>> scaleTo Nanosecond t
-- 1523664123123456789
-- >>> scaleTo Microsecond t
-- 1523664123123457
-- >>> scaleTo Millisecond t
-- 1523664123123
-- >>> scaleTo Second t
-- 1523664123
-- >>> scaleTo Minute t
-- 25394402
-- >>> scaleTo Hour t
-- 423240
instance Timestamp UTCTime where
  roundTo :: Precision 'WriteRequest -> UTCTime -> Int64
roundTo Precision 'WriteRequest
prec = Precision 'WriteRequest -> POSIXTime -> Int64
forall time.
Timestamp time =>
Precision 'WriteRequest -> time -> Int64
roundTo Precision 'WriteRequest
prec (POSIXTime -> Int64) -> (UTCTime -> POSIXTime) -> UTCTime -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> POSIXTime
utcTimeToPOSIXSeconds
  scaleTo :: Precision 'WriteRequest -> UTCTime -> Int64
scaleTo Precision 'WriteRequest
prec = Precision 'WriteRequest -> POSIXTime -> Int64
forall time.
Timestamp time =>
Precision 'WriteRequest -> time -> Int64
scaleTo Precision 'WriteRequest
prec (POSIXTime -> Int64) -> (UTCTime -> POSIXTime) -> UTCTime -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> POSIXTime
utcTimeToPOSIXSeconds

-- |
-- >>> let dt = 123.123456789 :: NominalDiffTime
-- >>> roundTo Nanosecond dt
-- 123123456789
-- >>> roundTo Microsecond dt
-- 123123457000
-- >>> roundTo Millisecond dt
-- 123123000000
-- >>> roundTo Second dt
-- 123000000000
-- >>> roundTo Minute dt
-- 120000000000
-- >>> roundTo Hour dt
-- 0
-- >>> scaleTo Nanosecond dt
-- 123123456789
-- >>> scaleTo Microsecond dt
-- 123123457
-- >>> scaleTo Millisecond dt
-- 123123
-- >>> scaleTo Second dt
-- 123
-- >>> scaleTo Minute dt
-- 2
-- >>> scaleTo Hour dt
-- 0
instance Timestamp NominalDiffTime where
  roundTo :: Precision 'WriteRequest -> POSIXTime -> Int64
roundTo Precision 'WriteRequest
prec POSIXTime
time =
    POSIXTime -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
round (POSIXTime -> Int64) -> POSIXTime -> Int64
forall a b. (a -> b) -> a -> b
$ POSIXTime
10POSIXTime -> Int -> POSIXTime
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
9 :: Int) POSIXTime -> POSIXTime -> POSIXTime
forall a. Num a => a -> a -> a
* POSIXTime -> POSIXTime -> POSIXTime
forall a. RealFrac a => a -> a -> a
roundAt (Precision 'WriteRequest -> POSIXTime
forall a (ty :: RequestType). Fractional a => Precision ty -> a
precisionScale Precision 'WriteRequest
prec) POSIXTime
time
  scaleTo :: Precision 'WriteRequest -> POSIXTime -> Int64
scaleTo Precision 'WriteRequest
prec POSIXTime
time = POSIXTime -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
round (POSIXTime -> Int64) -> POSIXTime -> Int64
forall a b. (a -> b) -> a -> b
$ POSIXTime
time POSIXTime -> POSIXTime -> POSIXTime
forall a. Fractional a => a -> a -> a
/ Precision 'WriteRequest -> POSIXTime
forall a (ty :: RequestType). Fractional a => Precision ty -> a
precisionScale Precision 'WriteRequest
prec

-- |
-- >>> let timespec = TimeSpec 123 123456789
-- >>> roundTo Nanosecond timespec
-- 123123456789
-- >>> roundTo Microsecond timespec
-- 123123457000
-- >>> roundTo Millisecond timespec
-- 123123000000
-- >>> roundTo Second timespec
-- 123000000000
-- >>> roundTo Minute timespec
-- 120000000000
-- >>> roundTo Hour timespec
-- 0
-- >>> scaleTo Nanosecond timespec
-- 123123456789
-- >>> scaleTo Microsecond timespec
-- 123123457
-- >>> scaleTo Millisecond timespec
-- 123123
-- >>> scaleTo Second timespec
-- 123
-- >>> scaleTo Minute timespec
-- 2
-- >>> scaleTo Hour timespec
-- 0
instance Timestamp TimeSpec where
  roundTo :: Precision 'WriteRequest -> TimeSpec -> Int64
roundTo Precision 'WriteRequest
prec TimeSpec
t =
    Double -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Int64) -> Double -> Int64
forall a b. (a -> b) -> a -> b
$ Double
10Double -> Int -> Double
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
9 :: Int) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double -> Double
forall a. RealFrac a => a -> a -> a
roundAt (Precision 'WriteRequest -> Double
forall a (ty :: RequestType). Fractional a => Precision ty -> a
precisionScale Precision 'WriteRequest
prec) (TimeSpec -> Double
timeSpecToSeconds TimeSpec
t)
  scaleTo :: Precision 'WriteRequest -> TimeSpec -> Int64
scaleTo Precision 'WriteRequest
prec TimeSpec
t = Double -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Int64) -> Double -> Int64
forall a b. (a -> b) -> a -> b
$ TimeSpec -> Double
timeSpecToSeconds TimeSpec
t Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Precision 'WriteRequest -> Double
forall a (ty :: RequestType). Fractional a => Precision ty -> a
precisionScale Precision 'WriteRequest
prec

timeSpecToSeconds :: TimeSpec -> Double
timeSpecToSeconds :: TimeSpec -> Double
timeSpecToSeconds TimeSpec { Int64
sec :: TimeSpec -> Int64
sec :: Int64
sec, Int64
nsec :: TimeSpec -> Int64
nsec :: Int64
nsec } =
  Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
sec Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
nsec Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
10Double -> Int -> Double
forall a b. (Fractional a, Integral b) => a -> b -> a
^^(-Int
9 :: Int)

-- | Exceptions used in this library.
--
-- In general, the library tries to convert exceptions from the dependent
-- libraries to the following types of errors.
data InfluxException
  = ServerError String
  -- ^ Server side error.
  --
  -- You can expect to get a successful response once the issue is resolved on
  -- the server side.
  | ClientError String Request
  -- ^ Client side error.
  --
  -- You need to fix your query to get a successful response.
  | UnexpectedResponse String Request BL.ByteString
  -- ^ Received an unexpected response. The 'String' field is a message and the
  -- 'BL.ByteString' field is a possibly-empty relevant payload of the response.
  --
  -- This can happen e.g. when the response from InfluxDB is incompatible with
  -- what this library expects due to an upstream format change or when the JSON
  -- response doesn't have expected fields etc.
  | HTTPException HC.HttpException
  -- ^ HTTP communication error.
  --
  -- Typical HTTP errors (4xx and 5xx) are covered by 'ClientError' and
  -- 'ServerError'. So this exception means something unusual happened. Note
  -- that if 'HC.checkResponse' is overridden to throw an 'HC.HttpException' on
  -- an unsuccessful HTTP code, this exception is thrown instead of
  -- 'ClientError' or 'ServerError'.
  deriving (Int -> InfluxException -> ShowS
[InfluxException] -> ShowS
InfluxException -> String
(Int -> InfluxException -> ShowS)
-> (InfluxException -> String)
-> ([InfluxException] -> ShowS)
-> Show InfluxException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InfluxException] -> ShowS
$cshowList :: [InfluxException] -> ShowS
show :: InfluxException -> String
$cshow :: InfluxException -> String
showsPrec :: Int -> InfluxException -> ShowS
$cshowsPrec :: Int -> InfluxException -> ShowS
Show, Typeable)

instance Exception InfluxException

-- | Class of data types that have a server field
class HasServer a where
  -- | InfluxDB server address and port that to interact with.
  server :: Lens' a Server

-- | Class of data types that have a database field
class HasDatabase a where
  -- | Database name to work on.
  database :: Lens' a Database

-- | Class of data types that have a precision field
class HasPrecision (ty :: RequestType) a | a -> ty where
  -- | Time precision parameter.
  precision :: Lens' a (Precision ty)

-- | Class of data types that have a manager field
class HasManager a where
  -- | HTTP manager settings or a manager itself.
  --
  -- If it's set to 'ManagerSettings', the library will create a 'Manager' from
  -- the settings for you.
  manager :: Lens' a (Either ManagerSettings Manager)

-- | Class of data types that has an authentication field
class HasCredentials a where
  -- | User name and password to be used when sending requests to InfluxDB.
  authentication :: Lens' a (Maybe Credentials)