{-# 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
newtype Query = Query T.Text deriving [Char] -> Query
([Char] -> Query) -> IsString Query
forall a. ([Char] -> a) -> IsString a
$cfromString :: [Char] -> Query
fromString :: [Char] -> Query
IsString
instance Show Query where
show :: Query -> [Char]
show (Query Text
q) = Text -> [Char]
forall a. Show a => a -> [Char]
show Text
q
data Server = Server
{ Server -> Text
_host :: !Text
, Server -> Int
_port :: !Int
, Server -> Bool
_ssl :: !Bool
} deriving (Int -> Server -> ShowS
[Server] -> ShowS
Server -> [Char]
(Int -> Server -> ShowS)
-> (Server -> [Char]) -> ([Server] -> ShowS) -> Show Server
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Server -> ShowS
showsPrec :: Int -> Server -> ShowS
$cshow :: Server -> [Char]
show :: Server -> [Char]
$cshowList :: [Server] -> ShowS
showList :: [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
$cfrom :: forall x. Server -> Rep Server x
from :: forall x. Server -> Rep Server x
$cto :: forall x. Rep Server x -> Server
to :: forall x. Rep Server x -> Server
Generic, Server -> Server -> Bool
(Server -> Server -> Bool)
-> (Server -> Server -> Bool) -> Eq Server
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Server -> Server -> Bool
== :: Server -> Server -> Bool
$c/= :: Server -> Server -> Bool
/= :: 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
$ccompare :: Server -> Server -> Ordering
compare :: Server -> Server -> Ordering
$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
>= :: Server -> Server -> Bool
$cmax :: Server -> Server -> Server
max :: Server -> Server -> Server
$cmin :: Server -> Server -> Server
min :: Server -> Server -> Server
Ord)
makeLensesWith (lensRules & generateSignatures .~ False) ''Server
host :: Lens' Server Text
port :: Lens' Server Int
ssl :: Lens' Server Bool
defaultServer :: Server
defaultServer :: Server
defaultServer = Server
{ _host :: Text
_host = Text
"localhost"
, _port :: Int
_port = Int
8086
, _ssl :: Bool
_ssl = Bool
False
}
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
data Credentials = Credentials
{ Credentials -> Text
_user :: !Text
, Credentials -> Text
_password :: !Text
} deriving Int -> Credentials -> ShowS
[Credentials] -> ShowS
Credentials -> [Char]
(Int -> Credentials -> ShowS)
-> (Credentials -> [Char])
-> ([Credentials] -> ShowS)
-> Show Credentials
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Credentials -> ShowS
showsPrec :: Int -> Credentials -> ShowS
$cshow :: Credentials -> [Char]
show :: Credentials -> [Char]
$cshowList :: [Credentials] -> ShowS
showList :: [Credentials] -> ShowS
Show
credentials
:: Text
-> Text
-> Credentials
credentials :: Text -> Text -> Credentials
credentials = Text -> Text -> Credentials
Credentials
makeLensesWith (lensRules & generateSignatures .~ False) ''Credentials
user :: Lens' Credentials Text
password :: Lens' Credentials Text
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
$c== :: Database -> Database -> Bool
== :: Database -> Database -> Bool
$c/= :: Database -> Database -> Bool
/= :: 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
$ccompare :: Database -> Database -> Ordering
compare :: Database -> Database -> Ordering
$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
>= :: Database -> Database -> Bool
$cmax :: Database -> Database -> Database
max :: Database -> Database -> Database
$cmin :: Database -> Database -> Database
min :: Database -> Database -> Database
Ord)
instance IsString Database where
fromString :: [Char] -> Database
fromString [Char]
xs = Text -> Database
Database (Text -> Database) -> Text -> Database
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> Text
identifier [Char]
"Database" [Char]
xs
instance Show Database where
show :: Database -> [Char]
show (Database Text
name) = Text -> [Char]
forall a. Show a => a -> [Char]
show Text
name
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
$c== :: Measurement -> Measurement -> Bool
== :: Measurement -> Measurement -> Bool
$c/= :: Measurement -> Measurement -> Bool
/= :: 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
$ccompare :: Measurement -> Measurement -> Ordering
compare :: Measurement -> Measurement -> Ordering
$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
>= :: Measurement -> Measurement -> Bool
$cmax :: Measurement -> Measurement -> Measurement
max :: Measurement -> Measurement -> Measurement
$cmin :: Measurement -> Measurement -> Measurement
min :: Measurement -> Measurement -> Measurement
Ord)
instance IsString Measurement where
fromString :: [Char] -> Measurement
fromString [Char]
xs = Text -> Measurement
Measurement (Text -> Measurement) -> Text -> Measurement
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> Text
identifier [Char]
"Measurement" [Char]
xs
instance Show Measurement where
show :: Measurement -> [Char]
show (Measurement Text
name) = Text -> [Char]
forall a. Show a => a -> [Char]
show Text
name
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
$c== :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
/= :: 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
$ccompare :: Key -> Key -> Ordering
compare :: Key -> Key -> Ordering
$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
>= :: Key -> Key -> Bool
$cmax :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
min :: Key -> Key -> Key
Ord)
instance IsString Key where
fromString :: [Char] -> Key
fromString [Char]
xs = Text -> Key
Key (Text -> Key) -> Text -> Key
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> Text
identifier [Char]
"Key" [Char]
xs
instance Show Key where
show :: Key -> [Char]
show (Key Text
name) = Text -> [Char]
forall a. Show a => a -> [Char]
show Text
name
identifier :: String -> String -> Text
identifier :: [Char] -> [Char] -> Text
identifier [Char]
ty [Char]
xs
| [Char] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
xs = [Char] -> Text
forall a. HasCallStack => [Char] -> a
error ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ [Char]
ty [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
" should never be empty"
| Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Char
'\n' [Char]
xs = [Char] -> Text
forall a. HasCallStack => [Char] -> a
error ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ [Char]
ty [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
" should not contain a new line"
| Bool
otherwise = [Char] -> Text
forall a. IsString a => [Char] -> a
fromString [Char]
xs
data Nullability = Nullable | NonNullable deriving Typeable
type QueryField = Field 'Nullable
type LineField = Field 'NonNullable
data Field (n :: Nullability) where
FieldInt :: !Int64 -> Field n
FieldFloat :: !Double -> Field n
FieldString :: !Text -> Field n
FieldBool :: !Bool -> Field n
FieldNull :: Field 'Nullable
deriving Typeable
deriving instance Eq (Field n)
deriving instance Show (Field n)
instance IsString (Field n) where
fromString :: [Char] -> Field n
fromString = Text -> Field n
forall (n :: Nullability). Text -> Field n
FieldString (Text -> Field n) -> ([Char] -> Text) -> [Char] -> Field n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack
data RequestType
= QueryRequest
| WriteRequest
deriving Int -> RequestType -> ShowS
[RequestType] -> ShowS
RequestType -> [Char]
(Int -> RequestType -> ShowS)
-> (RequestType -> [Char])
-> ([RequestType] -> ShowS)
-> Show RequestType
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestType -> ShowS
showsPrec :: Int -> RequestType -> ShowS
$cshow :: RequestType -> [Char]
show :: RequestType -> [Char]
$cshowList :: [RequestType] -> ShowS
showList :: [RequestType] -> ShowS
Show
data Precision (ty :: RequestType) where
Nanosecond :: Precision ty
Microsecond :: Precision ty
Millisecond :: Precision ty
Second :: Precision ty
Minute :: Precision ty
Hour :: Precision ty
RFC3339 :: Precision 'QueryRequest
deriving instance Show (Precision a)
deriving instance Eq (Precision a)
precisionName :: Precision ty -> Text
precisionName :: forall (ty :: RequestType). 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"
class Timestamp time where
roundTo :: Precision 'WriteRequest -> time -> Int64
scaleTo :: Precision 'WriteRequest -> time -> Int64
roundAt :: RealFrac a => a -> a -> a
roundAt :: forall a. RealFrac a => a -> a -> a
roundAt a
scale a
x = Int64 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Int64
forall b. Integral b => a -> b
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
precisionScale :: Fractional a => Precision ty -> a
precisionScale :: forall a (ty :: RequestType). Fractional a => 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
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
instance Timestamp NominalDiffTime where
roundTo :: Precision 'WriteRequest -> POSIXTime -> Int64
roundTo Precision 'WriteRequest
prec POSIXTime
time =
POSIXTime -> Int64
forall b. Integral b => POSIXTime -> b
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 b. Integral b => POSIXTime -> b
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
instance Timestamp TimeSpec where
roundTo :: Precision 'WriteRequest -> TimeSpec -> Int64
roundTo Precision 'WriteRequest
prec TimeSpec
t =
Double -> Int64
forall b. Integral b => Double -> b
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 b. Integral b => Double -> b
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 :: Int64
sec :: TimeSpec -> Int64
sec, Int64
nsec :: Int64
nsec :: TimeSpec -> 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)
data InfluxException
= ServerError String
| ClientError String Request
| UnexpectedResponse String Request BL.ByteString
| HTTPException HC.HttpException
deriving (Int -> InfluxException -> ShowS
[InfluxException] -> ShowS
InfluxException -> [Char]
(Int -> InfluxException -> ShowS)
-> (InfluxException -> [Char])
-> ([InfluxException] -> ShowS)
-> Show InfluxException
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InfluxException -> ShowS
showsPrec :: Int -> InfluxException -> ShowS
$cshow :: InfluxException -> [Char]
show :: InfluxException -> [Char]
$cshowList :: [InfluxException] -> ShowS
showList :: [InfluxException] -> ShowS
Show, Typeable)
instance Exception InfluxException
class HasServer a where
server :: Lens' a Server
class HasDatabase a where
database :: Lens' a Database
class HasPrecision (ty :: RequestType) a | a -> ty where
precision :: Lens' a (Precision ty)
class HasManager a where
manager :: Lens' a (Either ManagerSettings Manager)
class HasCredentials a where
authentication :: Lens' a (Maybe Credentials)