influxdb-1.2.0: Haskell client library for InfluxDB

Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB.Query

Contents

Synopsis

Query interface

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

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 parameters

data QueryParams Source #

The full set of parameters for the query API

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"
HasManager QueryParams Source #
>>> let p = queryParams "foo" & 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
RFC3339

server :: HasServer a => Lens' a Server Source #

InfluxDB server address and port that to interact with.

database :: HasDatabase a => Lens' a Database Source #

Database name to work on.

precision :: HasPrecision ty a => Lens' a (Precision ty) Source #

Time precision parameter.

manager :: HasManager a => 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.

Parsing results

class QueryResults a where Source #

Types that can be converted from an JSON object returned by InfluxDB.

For example the h2o_feet series in the official document can be encoded as follows:

>>> :{
data H2OFeet = H2OFeet
  { time :: UTCTime
  , levelDesc :: T.Text
  , location :: T.Text
  , waterLevel :: Double
  }
instance QueryResults H2OFeet where
  parseResults prec = parseResultsWith $ \_ _ columns fields -> do
    time <- getField "time" columns fields >>= parseUTCTime prec
    String levelDesc <- getField "level_description" columns fields
    String location <- getField "location" columns fields
    FieldFloat waterLevel <-
      getField "water_level" columns fields >>= parseQueryField
    return H2OFeet {..}
:}

Minimal complete definition

parseResults

Methods

parseResults :: Precision QueryRequest -> Value -> Parser (Vector a) Source #

Parse a JSON object as an array of values of expected type.

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) 

A helper function to parse a JSON response in parseResults.

Low-level functions

withQueryResponse Source #

Arguments

:: QueryParams 
-> Maybe (Optional Int)

Chunk size

By Nothing, InfluxDB returns all matching data points at once. By Just 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 
-> (Request -> Response BodyReader -> IO r) 
-> IO r