influxdb-1.5.1: 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.2/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 

data Server Source #

Constructors

Server 

Fields

Instances

Eq Server Source # 

Methods

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

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

Ord Server Source # 
Show Server Source # 
Generic Server Source # 

Associated Types

type Rep Server :: * -> * #

Methods

from :: Server -> Rep Server x #

to :: Rep Server x -> Server #

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

defaultServer :: Server Source #

Default server settings.

Default parameters:

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

data Credentials Source #

User credentials

Constructors

Credentials 

Fields

credentials Source #

Arguments

:: Text

User name

-> Text

Password

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

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 # 

Methods

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

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

Ord Key Source # 

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 # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key Source # 

Methods

fromString :: String -> Key #

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 
FieldFloat :: !Double -> Field n 
FieldString :: !Text -> Field n 
FieldBool :: !Bool -> Field n 
FieldNull :: Field Nullable 

Instances

Eq (Field n) Source # 

Methods

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

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

Show (Field n) Source # 

Methods

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

show :: Field n -> String #

showList :: [Field n] -> ShowS #

IsString (Field n) Source # 

Methods

fromString :: String -> Field n #

data RequestType Source #

Type of a request

Constructors

QueryRequest

Request for /query

WriteRequest

Request for /write

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

precisionName :: Precision ty -> Text Source #

Name of the time precision.

>>> precisionName Nanosecond
"n"

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.

Minimal complete definition

roundTo, scaleTo

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

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 #

Minimal complete definition

server

Methods

server :: Lens' a Server Source #

InfluxDB server address and port that to interact with.

Instances

HasServer PingParams Source #
>>> pingParams ^. server.host
"localhost"
HasServer QueryParams Source #
>>> let p = queryParams "foo"
>>> p ^. server.host
"localhost"
HasServer WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. server.host
"localhost"

class HasDatabase a where Source #

Minimal complete definition

database

Methods

database :: Lens' a Database Source #

Database name to work on.

Instances

HasDatabase QueryParams Source #
>>> let p = queryParams "foo"
>>> p ^. database
"foo"
HasDatabase ShowQuery Source #
>>> v <- query (queryParams "_internal") "SHOW QUERIES" :: IO (V.Vector ShowQuery)
>>> v ^.. each.database
...
HasDatabase WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. database
"foo"

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

Minimal complete definition

precision

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
HasPrecision WriteRequest WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. precision
Nanosecond
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.

class HasManager a where Source #

Minimal complete definition

manager

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
HasManager QueryParams Source #
>>> let p = queryParams "foo" & manager .~ Left HC.defaultManagerSettings
HasManager WriteParams Source #
>>> let p = writeParams "foo" & manager .~ Left HC.defaultManagerSettings

class HasCredentials a where Source #

Minimal complete definition

authentication

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"
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"