influxdb-1.6.1.3: Haskell client library for InfluxDB

Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB.Types

Synopsis

Documentation

>>> :set -XOverloadedStrings
>>> import Database.InfluxDB

newtype Query Source #

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

>>> :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.

Constructors

Query Text 
Instances
Show Query Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

IsString Query Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

fromString :: String -> Query #

data Server Source #

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

Constructors

Server 

Fields

Instances
Eq Server Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

(==) :: Server -> Server -> Bool #

(/=) :: Server -> Server -> Bool #

Ord Server Source # 
Instance details

Defined in Database.InfluxDB.Types

Show Server Source # 
Instance details

Defined in Database.InfluxDB.Types

Generic Server Source # 
Instance details

Defined in Database.InfluxDB.Types

Associated Types

type Rep Server :: Type -> Type #

Methods

from :: Server -> Rep Server x #

to :: Rep Server x -> Server #

type Rep Server Source # 
Instance details

Defined in Database.InfluxDB.Types

type Rep Server = D1 (MetaData "Server" "Database.InfluxDB.Types" "influxdb-1.6.1.3-6Uwr7LiLsQiKrXH1jlw1lM" False) (C1 (MetaCons "Server" PrefixI True) (S1 (MetaSel (Just "_host") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "_port") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_ssl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))))

host :: Lens' Server Text Source #

Host name of the server

port :: Lens' Server Int Source #

Port number of the server

ssl :: Lens' Server Bool Source #

If SSL is enabled

For secure connections (HTTPS), consider using one of the following packages:

defaultServer :: Server Source #

Default InfluxDB server settings

Default parameters:

>>> defaultServer ^. host
"localhost"
>>> defaultServer ^. port
8086
>>> defaultServer ^. ssl
False

secureServer :: Server Source #

HTTPS-enabled InfluxDB server settings

data Credentials Source #

User credentials.

Following lenses are available to access its fields:

Constructors

Credentials 

Fields

Instances
Show Credentials Source # 
Instance details

Defined in Database.InfluxDB.Types

credentials Source #

Arguments

:: Text

User name

-> Text

Password

-> Credentials 

Smart constructor for Credentials

user :: Lens' Credentials Text Source #

User name to access InfluxDB.

>>> let creds = credentials "john" "passw0rd"
>>> creds ^. user
"john"

password :: Lens' Credentials Text Source #

Password to access InfluxDB

>>> let creds = credentials "john" "passw0rd"
>>> creds ^. password
"passw0rd"

newtype Database Source #

Database name.

formatDatabase can be used to construct a Database.

Constructors

Database 

Fields

Instances
Eq Database Source # 
Instance details

Defined in Database.InfluxDB.Types

Ord Database Source # 
Instance details

Defined in Database.InfluxDB.Types

Show Database Source # 
Instance details

Defined in Database.InfluxDB.Types

IsString Database Source # 
Instance details

Defined in Database.InfluxDB.Types

newtype Measurement Source #

String name that is used for measurements.

formatMeasurement can be used to construct a Measurement.

Constructors

Measurement Text 

newtype Key Source #

String type that is used for tag keys/values and field keys.

formatKey can be used to construct a Key.

Constructors

Key Text 
Instances
Eq Key Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Ord Key Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

fromString :: String -> Key #

data Nullability Source #

Nullability of fields.

Queries can contain nulls but the line protocol cannot.

Constructors

Nullable 
NonNullable 

type QueryField = Field Nullable Source #

Field type for queries. Queries can contain null values.

type LineField = Field NonNullable Source #

Field type for the line protocol. The line protocol doesn't accept null values.

data Field (n :: Nullability) where Source #

Constructors

FieldInt :: !Int64 -> Field n

Signed 64-bit integers (-9,223,372,036,854,775,808 to 9,223,372,036,854,775,807).

FieldFloat :: !Double -> Field n

IEEE-754 64-bit floating-point numbers. This is the default numerical type.

FieldString :: !Text -> Field n

String field. Its length is limited to 64KB, which is not enforced by this library.

FieldBool :: !Bool -> Field n

Boolean field.

FieldNull :: Field Nullable

Null field.

Note that a field can be null only in queries. The line protocol doesn't allow null values.

Instances
Eq (Field n) Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

(==) :: Field n -> Field n -> Bool #

(/=) :: Field n -> Field n -> Bool #

Show (Field n) Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

showsPrec :: Int -> Field n -> ShowS #

show :: Field n -> String #

showList :: [Field n] -> ShowS #

IsString (Field n) Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

fromString :: String -> Field n #

data RequestType Source #

Type of a request

Constructors

QueryRequest

Request for /query

WriteRequest

Request for /write

Instances
Show RequestType Source # 
Instance details

Defined in Database.InfluxDB.Types

data Precision (ty :: RequestType) where Source #

Predefined set of time precision.

RFC3339 is only available for QueryRequests.

Constructors

Nanosecond :: Precision ty

POSIX time in ns

Microsecond :: Precision ty

POSIX time in μs

Millisecond :: Precision ty

POSIX time in ms

Second :: Precision ty

POSIX time in s

Minute :: Precision ty

POSIX time in minutes

Hour :: Precision ty

POSIX time in hours

RFC3339 :: Precision QueryRequest

Nanosecond precision time in a human readable format, like 2016-01-04T00:00:23.135623Z. This is the default format for /query.

Instances
Eq (Precision a) Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

(==) :: Precision a -> Precision a -> Bool #

(/=) :: Precision a -> Precision a -> Bool #

Show (Precision a) Source # 
Instance details

Defined in Database.InfluxDB.Types

precisionName :: Precision ty -> Text Source #

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"

class Timestamp time where Source #

A Timestamp is something that can be converted to a valid InfluxDB timestamp, which is represented as a 64-bit integer.

Methods

roundTo :: Precision WriteRequest -> time -> Int64 Source #

Round a time to the given precision and scale it to nanoseconds

scaleTo :: Precision WriteRequest -> time -> Int64 Source #

Scale a time to the given precision

Instances
Timestamp UTCTime Source #
>>> 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 details

Defined in Database.InfluxDB.Types

Timestamp TimeSpec Source #
>>> 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 details

Defined in Database.InfluxDB.Types

Timestamp NominalDiffTime Source #
>>> 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 details

Defined in Database.InfluxDB.Types

roundAt :: RealFrac a => a -> a -> a Source #

precisionScale :: Fractional a => Precision ty -> a Source #

Scale of the type precision.

>>> precisionScale RFC3339
1.0e-9
>>> precisionScale Microsecond
1.0e-6

data InfluxException Source #

Exceptions used in this library.

In general, the library tries to convert exceptions from the dependent libraries to the following types of errors.

Constructors

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 ByteString

Received an unexpected response. The String field is a message and the 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 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 checkResponse is overridden to throw an HttpException on an unsuccessful HTTP code, this exception is thrown instead of ClientError or ServerError.

class HasServer a where Source #

Class of data types that have a server field

Methods

server :: Lens' a Server Source #

InfluxDB server address and port that to interact with.

Instances
HasServer PingParams Source #
>>> pingParams ^. server.host
"localhost"
Instance details

Defined in Database.InfluxDB.Ping

HasServer QueryParams Source #
>>> let p = queryParams "foo"
>>> p ^. server.host
"localhost"
Instance details

Defined in Database.InfluxDB.Query

HasServer WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. server.host
"localhost"
Instance details

Defined in Database.InfluxDB.Write

class HasDatabase a where Source #

Class of data types that have a database field

Methods

database :: Lens' a Database Source #

Database name to work on.

Instances
HasDatabase QueryParams Source #
>>> let p = queryParams "foo"
>>> p ^. database
"foo"
Instance details

Defined in Database.InfluxDB.Query

HasDatabase ShowQuery Source #
>>> v <- query (queryParams "_internal") "SHOW QUERIES" :: IO (V.Vector ShowQuery)
>>> v ^.. each.database
...
Instance details

Defined in Database.InfluxDB.Manage

HasDatabase WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. database
"foo"
Instance details

Defined in Database.InfluxDB.Write

class HasPrecision (ty :: RequestType) a | a -> ty where Source #

Class of data types that have a precision field

Methods

precision :: Lens' a (Precision ty) Source #

Time precision parameter.

Instances
HasPrecision QueryRequest QueryParams Source #

Returning JSON responses contain timestamps in the specified precision/format.

>>> let p = queryParams "foo"
>>> p ^. precision
RFC3339
Instance details

Defined in Database.InfluxDB.Query

HasPrecision WriteRequest WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. precision
Nanosecond
Instance details

Defined in Database.InfluxDB.Write

HasPrecision WriteRequest WriteParams Source #

Timestamp precision.

In the UDP API, all timestamps are sent in nanosecond but you can specify lower precision. The writer just rounds timestamps to the specified precision.

Instance details

Defined in Database.InfluxDB.Write.UDP

class HasManager a where Source #

Class of data types that have a manager field

Methods

manager :: Lens' a (Either ManagerSettings Manager) Source #

HTTP manager settings or a manager itself.

If it's set to ManagerSettings, the library will create a Manager from the settings for you.

Instances
HasManager PingParams Source #
>>> let p = pingParams & manager .~ Left HC.defaultManagerSettings
Instance details

Defined in Database.InfluxDB.Ping

HasManager QueryParams Source #
>>> let p = queryParams "foo" & manager .~ Left HC.defaultManagerSettings
Instance details

Defined in Database.InfluxDB.Query

HasManager WriteParams Source #
>>> let p = writeParams "foo" & manager .~ Left HC.defaultManagerSettings
Instance details

Defined in Database.InfluxDB.Write

class HasCredentials a where Source #

Class of data types that has an authentication field

Methods

authentication :: Lens' a (Maybe Credentials) Source #

User name and password to be used when sending requests to InfluxDB.

Instances
HasCredentials QueryParams Source #

Authentication info for the query

>>> let p = queryParams "foo"
>>> p ^. authentication
Nothing
>>> let p' = p & authentication ?~ credentials "john" "passw0rd"
>>> p' ^. authentication.traverse.user
"john"
Instance details

Defined in Database.InfluxDB.Query

HasCredentials WriteParams Source #

Authentication info for the write

>>> let p = writeParams "foo"
>>> p ^. authentication
Nothing
>>> let p' = p & authentication ?~ credentials "john" "passw0rd"
>>> p' ^. authentication . traverse . user
"john"
Instance details

Defined in Database.InfluxDB.Write