influxdb-1.1.2.1: Haskell client library for InfluxDB

Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB

Contents

Description

 

Synopsis

Writing data

InfluxDB has two ways to write data into it, via HTTP and UDP. This module only exports functions for the HTTP API. For UDP, you can use a qualified import:

import qualified Database.InfluxDB.Write.UDP as UDP

write :: Timestamp time => WriteParams -> Line time -> IO () Source #

Write a Line

writeBatch :: (Timestamp time, Foldable f) => WriteParams -> f (Line time) -> IO () Source #

Write Lines in a batch

This is more efficient than write.

Write parameters

data WriteParams Source #

The full set of parameters for the HTTP writer.

Instances

HasCredentials WriteParams Source # 
HasManager WriteParams Source #
>>> let p = writeParams "foo"
>>> p & manager .~ Left HC.defaultManagerSettings
HasDatabase WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. database
"foo"
HasServer WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. server.host
"localhost"
HasPrecision WriteRequest WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. precision
Nanosecond

retentionPolicy :: Lens' WriteParams (Maybe Key) Source #

Target retention policy for the write.

InfluxDB writes to the default retention policy if this parameter is set to Nothing.

>>> let p = writeParams "foo"
>>> let p' = p & retentionPolicy .~ Just "two_hours"
>>> p' ^. retentionPolicy
Just "two_hours"

The Line protocol

data Line time Source #

Placeholder for the Line Protocol

See https://docs.influxdata.com/influxdb/v1.0/write_protocols/line_protocol_tutorial/ for the concrete syntax.

Constructors

Line !Key !(Map Key Text) !(Map Key FieldValue) !(Maybe time) 

measurement :: Lens' (Line time) Key Source #

Name of the measurement that you want to write your data to.

tagSet :: Lens' (Line time) (Map Key Text) Source #

Tag(s) that you want to include with your data point. Tags are optional in the Line Protocol, so you can set it empty.

fieldSet :: Lens' (Line time) (Map Key FieldValue) Source #

Field(s) for your data point. Every data point requires at least one field in the Line Protocol, so it shouldn't be empty.

timestamp :: Lens' (Line time) (Maybe time) Source #

Timestamp for your data point. You can put whatever type of timestamp that is an instance of the Timestamp class.

data FieldValue Source #

Instances

Eq FieldValue Source # 
Data FieldValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldValue -> c FieldValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldValue #

toConstr :: FieldValue -> Constr #

dataTypeOf :: FieldValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FieldValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldValue) #

gmapT :: (forall b. Data b => b -> b) -> FieldValue -> FieldValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldValue -> m FieldValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldValue -> m FieldValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldValue -> m FieldValue #

Show FieldValue Source # 
IsString FieldValue Source # 
Generic FieldValue Source # 

Associated Types

type Rep FieldValue :: * -> * #

type Rep FieldValue Source # 

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

Querying data

query :: QueryResults a => QueryParams -> Query -> IO (Vector a) Source #

Query data from InfluxDB.

It may throw InfluxException.

queryChunked Source #

Arguments

:: QueryResults a 
=> QueryParams 
-> Optional Int

Chunk size

By Default, InfluxDB chunks responses by series or by every 10,000 points, whichever occurs first. If it set to a Specific value, InfluxDB chunks responses by series or by that number of points.

-> Query 
-> FoldM IO (Vector a) r 
-> IO r 

Same as query but it instructs InfluxDB to stream chunked responses rather than returning a huge JSON object. This can be lot more efficient than query if the result is huge.

It may throw InfluxException.

Query constructor

(%) :: Format b c -> Format a b -> Format a c Source #

Query parameters

data QueryParams Source #

The full set of parameters for the query API

Instances

HasCredentials QueryParams Source # 
HasManager QueryParams Source #
>>> let p = queryParams "foo"
>>> p & manager .~ Left HC.defaultManagerSettings
HasDatabase QueryParams Source #
>>> let p = queryParams "foo"
>>> p ^. database
"foo"
HasServer QueryParams Source #
>>> let p = queryParams "foo"
>>> p ^. server.host
"localhost"
HasPrecision QueryRequest QueryParams Source #

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

>>> let p = queryParams "foo"
>>> p ^. precision
Nanosecond

Parsing results

class QueryResults a where Source #

Minimal complete definition

parseResults

Instances

QueryResults Void Source # 
QueryResults ShowSeries Source # 
QueryResults ShowQuery Source # 
((~) * a Value, (~) * b Value) => QueryResults (a, b) Source # 
((~) * a Value, (~) * b Value, (~) * c Value) => QueryResults (a, b, c) Source # 
((~) * a Value, (~) * b Value, (~) * c Value, (~) * d Value) => QueryResults (a, b, c, d) Source # 

Methods

parseResults :: Precision QueryRequest -> Value -> Parser (Vector (a, b, c, d)) Source #

((~) * a Value, (~) * b Value, (~) * c Value, (~) * d Value, (~) * e Value) => QueryResults (a, b, c, d, e) Source # 

Methods

parseResults :: Precision QueryRequest -> Value -> Parser (Vector (a, b, c, d, e)) Source #

((~) * a Value, (~) * b Value, (~) * c Value, (~) * d Value, (~) * e Value, (~) * f Value) => QueryResults (a, b, c, d, e, f) Source # 

Methods

parseResults :: Precision QueryRequest -> Value -> Parser (Vector (a, b, c, d, e, f)) Source #

((~) * a Value, (~) * b Value, (~) * c Value, (~) * d Value, (~) * e Value, (~) * f Value, (~) * g Value) => QueryResults (a, b, c, d, e, f, g) Source # 

Methods

parseResults :: Precision QueryRequest -> Value -> Parser (Vector (a, b, c, d, e, f, g)) Source #

((~) * a Value, (~) * b Value, (~) * c Value, (~) * d Value, (~) * e Value, (~) * f Value, (~) * g Value, (~) * h Value) => QueryResults (a, b, c, d, e, f, g, h) Source # 

Methods

parseResults :: Precision QueryRequest -> Value -> Parser (Vector (a, b, c, d, e, f, g, h)) Source #

parseResultsWith Source #

Arguments

:: (Maybe Text -> HashMap Text Text -> Vector Text -> Array -> Parser a)

A parser that takes

  1. an optional name of the series
  2. a map of tags
  3. an array of field names
  4. an array of values

to construct a value.

-> Value 
-> Parser (Vector a) 

Parse a JSON response

getField Source #

Arguments

:: Text

Column name

-> Vector Text

Columns

-> Array

Fields

-> Parser Value 

Get a field value from a column name

getTag Source #

Arguments

:: Monad m 
=> Text

Tag name

-> HashMap Text Text

Tags

-> m Text 

Get a tag value from a tag name

parseTimestamp :: Precision ty -> Value -> Parser POSIXTime Source #

Parse either a POSIX timestamp or RFC3339 formatted timestamp.

Database management

manage :: QueryParams -> Query -> IO () Source #

Send a database management query to InfluxDB.

Common data types and classes

data Precision ty 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

data Key Source #

String type that is used for measurements, tag keys and field keys.

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 #

data Server Source #

Instances

Eq Server Source # 

Methods

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

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

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.1.2.1-IcTAjArwxmACO4QtBW5BBh" 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)))))

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

localServer :: Server Source #

Default server settings.

Default parameters:

data Credentials Source #

User credentials

user :: Lens' Credentials Text Source #

User name to access InfluxDB

password :: Lens' Credentials Text Source #

Password to access InfluxDB

Exception

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.

BadRequest String Request

Client side error.

You need to fix your query to get a successful response.

IllformedJSON String ByteString

Unexpected JSON response.

This can happen e.g. when the response from InfluxDB is incompatible with what this library expects due to an upstream format change etc.

class HasServer a where Source #

Minimal complete definition

server

Methods

server :: Lens' a Server Source #

Instances

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

class HasDatabase a where Source #

Minimal complete definition

database

Instances

HasDatabase WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. database
"foo"
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
["_internal"]

class HasPrecision ty a | a -> ty where Source #

Minimal complete definition

precision

Methods

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

Instances

HasPrecision QueryRequest QueryParams Source #

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

>>> let p = queryParams "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.

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

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