{-# 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
forall a. ([Char] -> a) -> IsString a
fromString :: [Char] -> Query
$cfromString :: [Char] -> Query
IsString
instance Show Query where
show :: Query -> [Char]
show (Query Text
q) = 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]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Server] -> ShowS
$cshowList :: [Server] -> ShowS
show :: Server -> [Char]
$cshow :: Server -> [Char]
showsPrec :: Int -> Server -> ShowS
$cshowsPrec :: Int -> Server -> ShowS
Show, 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
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
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
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 forall a b. a -> (a -> b) -> b
& Lens' Server Bool
ssl 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]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Credentials] -> ShowS
$cshowList :: [Credentials] -> ShowS
show :: Credentials -> [Char]
$cshow :: Credentials -> [Char]
showsPrec :: Int -> Credentials -> ShowS
$cshowsPrec :: Int -> 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
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
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
Ord)
instance IsString Database where
fromString :: [Char] -> Database
fromString [Char]
xs = Text -> Database
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) = forall a. Show a => a -> [Char]
show Text
name
newtype Measurement = Measurement Text deriving (Measurement -> Measurement -> Bool
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
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
Ord)
instance IsString Measurement where
fromString :: [Char] -> Measurement
fromString [Char]
xs = Text -> Measurement
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) = forall a. Show a => a -> [Char]
show Text
name
newtype Key = Key Text deriving (Key -> Key -> Bool
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
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
Ord)
instance IsString Key where
fromString :: [Char] -> Key
fromString [Char]
xs = Text -> Key
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) = forall a. Show a => a -> [Char]
show Text
name
identifier :: String -> String -> Text
identifier :: [Char] -> [Char] -> Text
identifier [Char]
ty [Char]
xs
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
xs = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
ty forall a. [a] -> [a] -> [a]
++ [Char]
" should never be empty"
| forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Char
'\n' [Char]
xs = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
ty forall a. [a] -> [a] -> [a]
++ [Char]
" should not contain a new line"
| Bool
otherwise = 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 = forall (n :: Nullability). Text -> Field n
FieldString 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]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [RequestType] -> ShowS
$cshowList :: [RequestType] -> ShowS
show :: RequestType -> [Char]
$cshow :: RequestType -> [Char]
showsPrec :: Int -> RequestType -> ShowS
$cshowsPrec :: Int -> 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 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. (RealFrac a, Integral b) => a -> b
round (a
x forall a. Fractional a => a -> a -> a
/ a
scale) :: Int64) 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
10forall a b. (Fractional a, Integral b) => a -> b -> a
^^(-Int
9 :: Int)
Precision ty
Nanosecond -> a
10forall a b. (Fractional a, Integral b) => a -> b -> a
^^(-Int
9 :: Int)
Precision ty
Microsecond -> a
10forall a b. (Fractional a, Integral b) => a -> b -> a
^^(-Int
6 :: Int)
Precision ty
Millisecond -> a
10forall 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 forall a. Num a => a -> a -> a
* a
60
instance Timestamp UTCTime where
roundTo :: Precision 'WriteRequest -> UTCTime -> Int64
roundTo Precision 'WriteRequest
prec = forall time.
Timestamp time =>
Precision 'WriteRequest -> time -> Int64
roundTo Precision 'WriteRequest
prec forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> POSIXTime
utcTimeToPOSIXSeconds
scaleTo :: Precision 'WriteRequest -> UTCTime -> Int64
scaleTo Precision 'WriteRequest
prec = forall time.
Timestamp time =>
Precision 'WriteRequest -> time -> Int64
scaleTo Precision 'WriteRequest
prec 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 =
forall a b. (RealFrac a, Integral b) => a -> b
round forall a b. (a -> b) -> a -> b
$ POSIXTime
10forall a b. (Num a, Integral b) => a -> b -> a
^(Int
9 :: Int) forall a. Num a => a -> a -> a
* forall a. RealFrac a => a -> a -> a
roundAt (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 = forall a b. (RealFrac a, Integral b) => a -> b
round forall a b. (a -> b) -> a -> b
$ POSIXTime
time forall a. Fractional a => a -> a -> a
/ 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 =
forall a b. (RealFrac a, Integral b) => a -> b
round forall a b. (a -> b) -> a -> b
$ Double
10forall a b. (Num a, Integral b) => a -> b -> a
^(Int
9 :: Int) forall a. Num a => a -> a -> a
* forall a. RealFrac a => a -> a -> a
roundAt (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 = forall a b. (RealFrac a, Integral b) => a -> b
round forall a b. (a -> b) -> a -> b
$ TimeSpec -> Double
timeSpecToSeconds TimeSpec
t forall a. Fractional a => a -> a -> a
/ 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 } =
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
sec forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
nsec forall a. Num a => a -> a -> a
* Double
10forall 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]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [InfluxException] -> ShowS
$cshowList :: [InfluxException] -> ShowS
show :: InfluxException -> [Char]
$cshow :: InfluxException -> [Char]
showsPrec :: Int -> InfluxException -> ShowS
$cshowsPrec :: Int -> 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)