influxdb-1.6.0.4: Haskell client library for InfluxDB

Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB

Contents

Description

 

Synopsis

Documentation

Getting started

This tutorial assumes the following language extensions and imports.

>>> :set -XOverloadedStrings
>>> :set -XRecordWildCards
>>> import Database.InfluxDB
>>> import qualified Database.InfluxDB.Format as F
>>> import Control.Lens
>>> import qualified Data.Map as Map
>>> import Data.Time
>>> import qualified Data.Vector as V

The examples below roughly follows the README in the official Go client library.

Creating a database

This library assumes the lens package in some APIs. Here we use ?~ to set the authentication parameters of type Maybe Credentials.

Also note that in order to construct a Query, we use formatQuery with the database formatter. There are many other formatters defined in Database.InfluxDB.Format.

>>> let db = "square_holes"
>>> let bubba = credentials "bubba" "bumblebeetuna"
>>> let p = queryParams db & authentication ?~ bubba
>>> manage p $ formatQuery ("DROP DATABASE "%F.database) db
>>> manage p $ formatQuery ("CREATE DATABASE "%F.database) db

Writing data

write or writeBatch can be used to write data. In general writeBatch should be used for efficiency when writing multiple data points.

>>> let wp = writeParams db & authentication ?~ bubba & precision .~ Second
>>> let cpuUsage = "cpu_usage"
>>> :{
writeBatch wp
  [ Line cpuUsage (Map.singleton "cpu" "cpu-total")
    (Map.fromList
      [ ("idle",   FieldFloat 10.1)
      , ("system", FieldFloat 53.3)
      , ("user",   FieldFloat 46.6)
      ])
    (Just $ parseTimeOrError False defaultTimeLocale
      "%F %T%Q %Z"
      "2017-06-17 15:41:40.42659044 UTC") :: Line UTCTime
  ]
:}

Note that the type signature of the timestamp is necessary. Otherwise it doesn't type check.

Querying data

Using an one-off tuple

If all the field types are an instance of FromJSON, we can use a tuple to store the results.

>>> :set -XDataKinds -XOverloadedStrings
>>> type CPUUsage = (Tagged "time" UTCTime, Tagged "idle" Double, Tagged "system" Double, Tagged "user" Double)
>>> v <- query p $ formatQuery ("SELECT * FROM "%F.measurement) cpuUsage :: IO (V.Vector CPUUsage)
>>> v
[(Tagged 2017-06-17 15:41:40 UTC,Tagged 10.1,Tagged 53.3,Tagged 46.6)]

Note that the type signature on query here is also necessary to type check. We can remove the tags using untag:

>>> V.map (\(a, b, c, d) -> (untag a, untag b, untag c, untag d)) v :: V.Vector (UTCTime, Double, Double, Double)
[(2017-06-17 15:41:40 UTC,10.1,53.3,46.6)]

Or even using coerce:

>>> import Data.Coerce
>>> coerce v :: V.Vector (UTCTime, Double, Double, Double)
[(2017-06-17 15:41:40 UTC,10.1,53.3,46.6)]

Using a custom data type

We can define our custom data type and write a QueryResults instance instead. getField, parseUTCTime and parseQueryField etc are avilable to make it easier to write a JSON decoder.

>>> :{
data CPUUsage = CPUUsage
  { time :: UTCTime
  , cpuIdle, cpuSystem, cpuUser :: Double
  } deriving Show
instance QueryResults CPUUsage where
  parseResults prec = parseResultsWithDecoder strictDecoder $ \_ _ columns fields -> do
    time <- getField "time" columns fields >>= parseUTCTime prec
    cpuIdle <- getField "idle" columns fields >>= parseJSON
    cpuSystem <- getField "system" columns fields >>= parseJSON
    cpuUser <- getField "user" columns fields >>= parseJSON
    return CPUUsage {..}
:}
>>> query p $ formatQuery ("SELECT * FROM "%F.measurement) cpuUsage :: IO (V.Vector CPUUsage)
[CPUUsage {time = 2017-06-17 15:41:40 UTC, cpuIdle = 10.1, cpuSystem = 53.3, cpuUser = 46.6}]

Writing data via HTTP

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.

>>> let p = writeParams "test-db"
>>> write p $ Line "room_temp" Map.empty (Map.fromList [("temp", FieldFloat 25.0)]) (Nothing :: Maybe UTCTime)

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

Write multiple Lines in a batch.

This is more efficient than calling write multiple times.

>>> let p = writeParams "test-db"
>>> :{
writeBatch p
  [ Line "temp" (Map.singleton "city" "tokyo") (Map.fromList [("temp", FieldFloat 25.0)]) (Nothing :: Maybe UTCTime)
  , Line "temp" (Map.singleton "city" "osaka") (Map.fromList [("temp", FieldFloat 25.2)]) (Nothing :: Maybe UTCTime)
  ]
:}

Write parameters

data WriteParams Source #

The full set of parameters for the HTTP writer.

Instances

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"
HasManager WriteParams Source #
>>> let p = writeParams "foo" & 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" & 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.5/write_protocols/line_protocol_tutorial/ for the concrete syntax.

Constructors

Line !Measurement !(Map Key Key) !(Map Key LineField) !(Maybe time) 

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

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

tagSet :: Lens' (Line time) (Map Key Key) 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 LineField) 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 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 #

type LineField = Field NonNullable Source #

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

type QueryField = Field Nullable Source #

Field type for queries. Queries can contain null values.

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

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

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

Scale of the type precision.

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

precisionName :: Precision ty -> Text Source #

Name of the time precision.

>>> precisionName Nanosecond
"n"

Querying data

query and queryChunked can be used to query data. If your dataset fits your memory, query is easier to use. If it doesn't, use queryChunked to stream data.

data Query Source #

An InfluxDB query.

A spec of the format is available at https://docs.influxdata.com/influxdb/v1.5/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.

If you need a lower-level interface (e.g. to bypass the QueryResults constraint etc), see withQueryResponse.

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.

If you need a lower-level interface (e.g. to bypass the QueryResults constraint etc), see withQueryResponse.

Query construction

There are various utility functions available in Database.InfluxDB.Format. This module is designed to be imported as qualified:

import Database.InfluxDB
import qualified Database.InfluxDB.Format as F

formatQuery :: Format Query r -> r Source #

Format a Query.

>>> formatQuery "SELECT * FROM series"
"SELECT * FROM series"
>>> formatQuery ("SELECT * FROM "%key) "series"
"SELECT * FROM \"series\""

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

Format specific synonym of (.).

This is typically easier to use than (.) is because it doesn't conflict with Prelude.(.).

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

authentication :: HasCredentials a => Lens' a (Maybe Credentials) Source #

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

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
    levelDesc <- getField "level_description" columns fields >>= parseJSON
    location <- getField "location" columns fields >>= parseJSON
    waterLevel <- getField "water_level" columns fields >>= parseJSON
    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 # 
(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2) Source #

One-off tuple for sigle-field measurements

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3) Source #

One-off tuple for two-field measurements

(KnownSymbol k, FromJSON v) => QueryResults (Tagged Symbol k v) Source #

One-off type for non-timestamped measurements

>>> let p = queryParams "_internal"
>>> dbs <- query p "SHOW DATABASES" :: IO (V.Vector (Tagged "name" T.Text))
>>> find ((== "_internal") . untag) dbs
Just (Tagged "_internal")
(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4) Source #

One-off tuple for three-field measurements

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4, Tagged Symbol k5 v5) Source #

One-off tuple for four-field measurements

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5, KnownSymbol k6, FromJSON v6) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4, Tagged Symbol k5 v5, Tagged Symbol k6 v6) Source #

One-off tuple for five-field measurements

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5, KnownSymbol k6, FromJSON v6, KnownSymbol k7, FromJSON v7) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4, Tagged Symbol k5 v5, Tagged Symbol k6 v6, Tagged Symbol k7 v7) Source #

One-off tuple for six-field measurement

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5, KnownSymbol k6, FromJSON v6, KnownSymbol k7, FromJSON v7, KnownSymbol k8, FromJSON v8) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4, Tagged Symbol k5 v5, Tagged Symbol k6 v6, Tagged Symbol k7 v7, Tagged Symbol k8 v8) Source #

One-off tuple for seven-field measurements

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 with the lenientDecoder. This can be useful to implement the parseResults method.

parseResultsWithDecoder Source #

Arguments

:: Decoder a 
-> (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 with the specified decoder settings.

data Decoder a Source #

Decoder settings

Constructors

Decoder 

Fields

lenientDecoder :: Decoder a Source #

A decoder that ignores parse failures and returns only successful results.

strictDecoder :: Decoder a Source #

A decoder that fails immediately if there's any parse failure.

getField Source #

Arguments

:: Monad m 
=> Text

Column name

-> Vector Text

Columns

-> Vector Value

Field values

-> m Value 

Get a field value from a column name

getTag Source #

Arguments

:: Monad m 
=> Text

Tag name

-> HashMap Text Value

Tags

-> m Value 

Get a tag value from a tag name

parseUTCTime :: Precision ty -> Value -> Parser UTCTime Source #

Parse either a POSIX timestamp or RFC3339 formatted timestamp as UTCTime.

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

Parse either a POSIX timestamp or RFC3339 formatted timestamp as POSIXTime.

parseQueryField :: Value -> Parser QueryField Source #

Deprecated: This function parses numbers in a misleading way. Use parseJSON instead.

Parse a QueryField.

Re-exports from tagged

newtype Tagged k (s :: k) b :: forall k. k -> * -> * #

A Tagged s b value is a value b with an attached phantom type s. This can be used in place of the more traditional but less safe idiom of passing in an undefined value with the type, because unlike an (s -> b), a Tagged s b can't try to use the argument s as a real value.

Moreover, you don't have to rely on the compiler to inline away the extra argument, because the newtype is "free"

Tagged has kind k -> * -> * if the compiler supports PolyKinds, therefore there is an extra k showing in the instance haddocks that may cause confusion.

Constructors

Tagged 

Fields

Instances

ToJSON2 (Tagged *) 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Tagged * a b -> Value #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Tagged * a b] -> Value #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Tagged * a b -> Encoding #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Tagged * a b] -> Encoding #

FromJSON2 (Tagged *) 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (Tagged * a b) #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [Tagged * a b] #

Bitraversable (Tagged *) 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Tagged * a b -> f (Tagged * c d) #

Bifoldable (Tagged *) 

Methods

bifold :: Monoid m => Tagged * m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Tagged * a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Tagged * a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Tagged * a b -> c #

Bifunctor (Tagged *) 

Methods

bimap :: (a -> b) -> (c -> d) -> Tagged * a c -> Tagged * b d #

first :: (a -> b) -> Tagged * a c -> Tagged * b c #

second :: (b -> c) -> Tagged * a b -> Tagged * a c #

Eq2 (Tagged *) 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Tagged * a c -> Tagged * b d -> Bool #

Ord2 (Tagged *) 

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Tagged * a c -> Tagged * b d -> Ordering #

Read2 (Tagged *) 

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Tagged * a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Tagged * a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Tagged * a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Tagged * a b] #

Show2 (Tagged *) 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Tagged * a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Tagged * a b] -> ShowS #

Corepresentable (Tagged *) 

Associated Types

type Corep (Tagged * :: * -> * -> *) :: * -> * #

Methods

cotabulate :: (Corep (Tagged *) d -> c) -> Tagged * d c #

Profunctor (Tagged *) 

Methods

dimap :: (a -> b) -> (c -> d) -> Tagged * b c -> Tagged * a d #

lmap :: (a -> b) -> Tagged * b c -> Tagged * a c #

rmap :: (b -> c) -> Tagged * a b -> Tagged * a c #

(#.) :: Coercible * c b => (b -> c) -> Tagged * a b -> Tagged * a c #

(.#) :: Coercible * b a => Tagged * b c -> (a -> b) -> Tagged * a c #

Generic1 * (Tagged k s) 

Associated Types

type Rep1 (Tagged k s) (f :: Tagged k s -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Tagged k s) f a #

to1 :: Rep1 (Tagged k s) f a -> f a #

Monad (Tagged k s) 

Methods

(>>=) :: Tagged k s a -> (a -> Tagged k s b) -> Tagged k s b #

(>>) :: Tagged k s a -> Tagged k s b -> Tagged k s b #

return :: a -> Tagged k s a #

fail :: String -> Tagged k s a #

Functor (Tagged k s) 

Methods

fmap :: (a -> b) -> Tagged k s a -> Tagged k s b #

(<$) :: a -> Tagged k s b -> Tagged k s a #

Applicative (Tagged k s) 

Methods

pure :: a -> Tagged k s a #

(<*>) :: Tagged k s (a -> b) -> Tagged k s a -> Tagged k s b #

liftA2 :: (a -> b -> c) -> Tagged k s a -> Tagged k s b -> Tagged k s c #

(*>) :: Tagged k s a -> Tagged k s b -> Tagged k s b #

(<*) :: Tagged k s a -> Tagged k s b -> Tagged k s a #

Foldable (Tagged k s) 

Methods

fold :: Monoid m => Tagged k s m -> m #

foldMap :: Monoid m => (a -> m) -> Tagged k s a -> m #

foldr :: (a -> b -> b) -> b -> Tagged k s a -> b #

foldr' :: (a -> b -> b) -> b -> Tagged k s a -> b #

foldl :: (b -> a -> b) -> b -> Tagged k s a -> b #

foldl' :: (b -> a -> b) -> b -> Tagged k s a -> b #

foldr1 :: (a -> a -> a) -> Tagged k s a -> a #

foldl1 :: (a -> a -> a) -> Tagged k s a -> a #

toList :: Tagged k s a -> [a] #

null :: Tagged k s a -> Bool #

length :: Tagged k s a -> Int #

elem :: Eq a => a -> Tagged k s a -> Bool #

maximum :: Ord a => Tagged k s a -> a #

minimum :: Ord a => Tagged k s a -> a #

sum :: Num a => Tagged k s a -> a #

product :: Num a => Tagged k s a -> a #

Traversable (Tagged k s) 

Methods

traverse :: Applicative f => (a -> f b) -> Tagged k s a -> f (Tagged k s b) #

sequenceA :: Applicative f => Tagged k s (f a) -> f (Tagged k s a) #

mapM :: Monad m => (a -> m b) -> Tagged k s a -> m (Tagged k s b) #

sequence :: Monad m => Tagged k s (m a) -> m (Tagged k s a) #

Representable (Tagged * t) 

Associated Types

type Rep (Tagged * t :: * -> *) :: * #

Methods

tabulate :: (Rep (Tagged * t) -> a) -> Tagged * t a #

index :: Tagged * t a -> Rep (Tagged * t) -> a #

ToJSON1 (Tagged k a) 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Tagged k a a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Tagged k a a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Tagged k a a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Tagged k a a] -> Encoding #

FromJSON1 (Tagged k a) 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Tagged k a a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Tagged k a a] #

Eq1 (Tagged k s) 

Methods

liftEq :: (a -> b -> Bool) -> Tagged k s a -> Tagged k s b -> Bool #

Ord1 (Tagged k s) 

Methods

liftCompare :: (a -> b -> Ordering) -> Tagged k s a -> Tagged k s b -> Ordering #

Read1 (Tagged k s) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Tagged k s a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Tagged k s a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Tagged k s a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Tagged k s a] #

Show1 (Tagged k s) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Tagged k s a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Tagged k s a] -> ShowS #

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2) Source #

One-off tuple for sigle-field measurements

Bounded b => Bounded (Tagged k s b) 

Methods

minBound :: Tagged k s b #

maxBound :: Tagged k s b #

Enum a => Enum (Tagged k s a) 

Methods

succ :: Tagged k s a -> Tagged k s a #

pred :: Tagged k s a -> Tagged k s a #

toEnum :: Int -> Tagged k s a #

fromEnum :: Tagged k s a -> Int #

enumFrom :: Tagged k s a -> [Tagged k s a] #

enumFromThen :: Tagged k s a -> Tagged k s a -> [Tagged k s a] #

enumFromTo :: Tagged k s a -> Tagged k s a -> [Tagged k s a] #

enumFromThenTo :: Tagged k s a -> Tagged k s a -> Tagged k s a -> [Tagged k s a] #

Eq b => Eq (Tagged k s b) 

Methods

(==) :: Tagged k s b -> Tagged k s b -> Bool #

(/=) :: Tagged k s b -> Tagged k s b -> Bool #

Floating a => Floating (Tagged k s a) 

Methods

pi :: Tagged k s a #

exp :: Tagged k s a -> Tagged k s a #

log :: Tagged k s a -> Tagged k s a #

sqrt :: Tagged k s a -> Tagged k s a #

(**) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

logBase :: Tagged k s a -> Tagged k s a -> Tagged k s a #

sin :: Tagged k s a -> Tagged k s a #

cos :: Tagged k s a -> Tagged k s a #

tan :: Tagged k s a -> Tagged k s a #

asin :: Tagged k s a -> Tagged k s a #

acos :: Tagged k s a -> Tagged k s a #

atan :: Tagged k s a -> Tagged k s a #

sinh :: Tagged k s a -> Tagged k s a #

cosh :: Tagged k s a -> Tagged k s a #

tanh :: Tagged k s a -> Tagged k s a #

asinh :: Tagged k s a -> Tagged k s a #

acosh :: Tagged k s a -> Tagged k s a #

atanh :: Tagged k s a -> Tagged k s a #

log1p :: Tagged k s a -> Tagged k s a #

expm1 :: Tagged k s a -> Tagged k s a #

log1pexp :: Tagged k s a -> Tagged k s a #

log1mexp :: Tagged k s a -> Tagged k s a #

Fractional a => Fractional (Tagged k s a) 

Methods

(/) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

recip :: Tagged k s a -> Tagged k s a #

fromRational :: Rational -> Tagged k s a #

Integral a => Integral (Tagged k s a) 

Methods

quot :: Tagged k s a -> Tagged k s a -> Tagged k s a #

rem :: Tagged k s a -> Tagged k s a -> Tagged k s a #

div :: Tagged k s a -> Tagged k s a -> Tagged k s a #

mod :: Tagged k s a -> Tagged k s a -> Tagged k s a #

quotRem :: Tagged k s a -> Tagged k s a -> (Tagged k s a, Tagged k s a) #

divMod :: Tagged k s a -> Tagged k s a -> (Tagged k s a, Tagged k s a) #

toInteger :: Tagged k s a -> Integer #

(Data s, Data b) => Data (Tagged * s b) 

Methods

gfoldl :: (forall d a. Data d => c (d -> a) -> d -> c a) -> (forall g. g -> c g) -> Tagged * s b -> c (Tagged * s b) #

gunfold :: (forall a r. Data a => c (a -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tagged * s b) #

toConstr :: Tagged * s b -> Constr #

dataTypeOf :: Tagged * s b -> DataType #

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

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

gmapT :: (forall a. Data a => a -> a) -> Tagged * s b -> Tagged * s b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tagged * s b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tagged * s b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tagged * s b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tagged * s b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tagged * s b -> m (Tagged * s b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged * s b -> m (Tagged * s b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged * s b -> m (Tagged * s b) #

Num a => Num (Tagged k s a) 

Methods

(+) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

(-) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

(*) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

negate :: Tagged k s a -> Tagged k s a #

abs :: Tagged k s a -> Tagged k s a #

signum :: Tagged k s a -> Tagged k s a #

fromInteger :: Integer -> Tagged k s a #

Ord b => Ord (Tagged k s b) 

Methods

compare :: Tagged k s b -> Tagged k s b -> Ordering #

(<) :: Tagged k s b -> Tagged k s b -> Bool #

(<=) :: Tagged k s b -> Tagged k s b -> Bool #

(>) :: Tagged k s b -> Tagged k s b -> Bool #

(>=) :: Tagged k s b -> Tagged k s b -> Bool #

max :: Tagged k s b -> Tagged k s b -> Tagged k s b #

min :: Tagged k s b -> Tagged k s b -> Tagged k s b #

Read b => Read (Tagged k s b) 

Methods

readsPrec :: Int -> ReadS (Tagged k s b) #

readList :: ReadS [Tagged k s b] #

readPrec :: ReadPrec (Tagged k s b) #

readListPrec :: ReadPrec [Tagged k s b] #

Real a => Real (Tagged k s a) 

Methods

toRational :: Tagged k s a -> Rational #

RealFloat a => RealFloat (Tagged k s a) 

Methods

floatRadix :: Tagged k s a -> Integer #

floatDigits :: Tagged k s a -> Int #

floatRange :: Tagged k s a -> (Int, Int) #

decodeFloat :: Tagged k s a -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Tagged k s a #

exponent :: Tagged k s a -> Int #

significand :: Tagged k s a -> Tagged k s a #

scaleFloat :: Int -> Tagged k s a -> Tagged k s a #

isNaN :: Tagged k s a -> Bool #

isInfinite :: Tagged k s a -> Bool #

isDenormalized :: Tagged k s a -> Bool #

isNegativeZero :: Tagged k s a -> Bool #

isIEEE :: Tagged k s a -> Bool #

atan2 :: Tagged k s a -> Tagged k s a -> Tagged k s a #

RealFrac a => RealFrac (Tagged k s a) 

Methods

properFraction :: Integral b => Tagged k s a -> (b, Tagged k s a) #

truncate :: Integral b => Tagged k s a -> b #

round :: Integral b => Tagged k s a -> b #

ceiling :: Integral b => Tagged k s a -> b #

floor :: Integral b => Tagged k s a -> b #

Show b => Show (Tagged k s b) 

Methods

showsPrec :: Int -> Tagged k s b -> ShowS #

show :: Tagged k s b -> String #

showList :: [Tagged k s b] -> ShowS #

Ix b => Ix (Tagged k s b) 

Methods

range :: (Tagged k s b, Tagged k s b) -> [Tagged k s b] #

index :: (Tagged k s b, Tagged k s b) -> Tagged k s b -> Int #

unsafeIndex :: (Tagged k s b, Tagged k s b) -> Tagged k s b -> Int

inRange :: (Tagged k s b, Tagged k s b) -> Tagged k s b -> Bool #

rangeSize :: (Tagged k s b, Tagged k s b) -> Int #

unsafeRangeSize :: (Tagged k s b, Tagged k s b) -> Int

IsString a => IsString (Tagged k s a) 

Methods

fromString :: String -> Tagged k s a #

Generic (Tagged k s b) 

Associated Types

type Rep (Tagged k s b) :: * -> * #

Methods

from :: Tagged k s b -> Rep (Tagged k s b) x #

to :: Rep (Tagged k s b) x -> Tagged k s b #

Semigroup a => Semigroup (Tagged k s a) 

Methods

(<>) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

sconcat :: NonEmpty (Tagged k s a) -> Tagged k s a #

stimes :: Integral b => b -> Tagged k s a -> Tagged k s a #

(Semigroup a, Monoid a) => Monoid (Tagged k s a) 

Methods

mempty :: Tagged k s a #

mappend :: Tagged k s a -> Tagged k s a -> Tagged k s a #

mconcat :: [Tagged k s a] -> Tagged k s a #

ToJSON b => ToJSON (Tagged k a b) 

Methods

toJSON :: Tagged k a b -> Value #

toEncoding :: Tagged k a b -> Encoding #

toJSONList :: [Tagged k a b] -> Value #

toEncodingList :: [Tagged k a b] -> Encoding #

ToJSONKey b => ToJSONKey (Tagged k a b) 
FromJSON b => FromJSON (Tagged k a b) 

Methods

parseJSON :: Value -> Parser (Tagged k a b) #

parseJSONList :: Value -> Parser [Tagged k a b] #

FromJSONKey b => FromJSONKey (Tagged k a b) 
Storable a => Storable (Tagged k s a) 

Methods

sizeOf :: Tagged k s a -> Int #

alignment :: Tagged k s a -> Int #

peekElemOff :: Ptr (Tagged k s a) -> Int -> IO (Tagged k s a) #

pokeElemOff :: Ptr (Tagged k s a) -> Int -> Tagged k s a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Tagged k s a) #

pokeByteOff :: Ptr b -> Int -> Tagged k s a -> IO () #

peek :: Ptr (Tagged k s a) -> IO (Tagged k s a) #

poke :: Ptr (Tagged k s a) -> Tagged k s a -> IO () #

Bits a => Bits (Tagged k s a) 

Methods

(.&.) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

(.|.) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

xor :: Tagged k s a -> Tagged k s a -> Tagged k s a #

complement :: Tagged k s a -> Tagged k s a #

shift :: Tagged k s a -> Int -> Tagged k s a #

rotate :: Tagged k s a -> Int -> Tagged k s a #

zeroBits :: Tagged k s a #

bit :: Int -> Tagged k s a #

setBit :: Tagged k s a -> Int -> Tagged k s a #

clearBit :: Tagged k s a -> Int -> Tagged k s a #

complementBit :: Tagged k s a -> Int -> Tagged k s a #

testBit :: Tagged k s a -> Int -> Bool #

bitSizeMaybe :: Tagged k s a -> Maybe Int #

bitSize :: Tagged k s a -> Int #

isSigned :: Tagged k s a -> Bool #

shiftL :: Tagged k s a -> Int -> Tagged k s a #

unsafeShiftL :: Tagged k s a -> Int -> Tagged k s a #

shiftR :: Tagged k s a -> Int -> Tagged k s a #

unsafeShiftR :: Tagged k s a -> Int -> Tagged k s a #

rotateL :: Tagged k s a -> Int -> Tagged k s a #

rotateR :: Tagged k s a -> Int -> Tagged k s a #

popCount :: Tagged k s a -> Int #

FiniteBits a => FiniteBits (Tagged k s a) 

Methods

finiteBitSize :: Tagged k s a -> Int #

countLeadingZeros :: Tagged k s a -> Int #

countTrailingZeros :: Tagged k s a -> Int #

NFData b => NFData (Tagged k s b) 

Methods

rnf :: Tagged k s b -> () #

Wrapped (Tagged k s a) 

Associated Types

type Unwrapped (Tagged k s a) :: * #

Methods

_Wrapped' :: Iso' (Tagged k s a) (Unwrapped (Tagged k s a)) #

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3) Source #

One-off tuple for two-field measurements

(KnownSymbol k, FromJSON v) => QueryResults (Tagged Symbol k v) Source #

One-off type for non-timestamped measurements

>>> let p = queryParams "_internal"
>>> dbs <- query p "SHOW DATABASES" :: IO (V.Vector (Tagged "name" T.Text))
>>> find ((== "_internal") . untag) dbs
Just (Tagged "_internal")
(~) * t (Tagged k2 s' a') => Rewrapped (Tagged k1 s a) t 
(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4) Source #

One-off tuple for three-field measurements

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4, Tagged Symbol k5 v5) Source #

One-off tuple for four-field measurements

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5, KnownSymbol k6, FromJSON v6) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4, Tagged Symbol k5 v5, Tagged Symbol k6 v6) Source #

One-off tuple for five-field measurements

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5, KnownSymbol k6, FromJSON v6, KnownSymbol k7, FromJSON v7) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4, Tagged Symbol k5 v5, Tagged Symbol k6 v6, Tagged Symbol k7 v7) Source #

One-off tuple for six-field measurement

(KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5, KnownSymbol k6, FromJSON v6, KnownSymbol k7, FromJSON v7, KnownSymbol k8, FromJSON v8) => QueryResults (Tagged Symbol k1 v1, Tagged Symbol k2 v2, Tagged Symbol k3 v3, Tagged Symbol k4 v4, Tagged Symbol k5 v5, Tagged Symbol k6 v6, Tagged Symbol k7 v7, Tagged Symbol k8 v8) Source #

One-off tuple for seven-field measurements

type Corep (Tagged *) 
type Corep (Tagged *) = Proxy *
type Rep1 * (Tagged k s) 
type Rep1 * (Tagged k s) = D1 * (MetaData "Tagged" "Data.Tagged" "tagged-0.8.5-2qJpg58g4ecDU6EbzROhsl" True) (C1 * (MetaCons "Tagged" PrefixI True) (S1 * (MetaSel (Just Symbol "unTagged") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Tagged * t) 
type Rep (Tagged * t) = ()
type Rep (Tagged k s b) 
type Rep (Tagged k s b) = D1 * (MetaData "Tagged" "Data.Tagged" "tagged-0.8.5-2qJpg58g4ecDU6EbzROhsl" True) (C1 * (MetaCons "Tagged" PrefixI True) (S1 * (MetaSel (Just Symbol "unTagged") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * b)))
type Unwrapped (Tagged k s a) 
type Unwrapped (Tagged k s a) = a

untag :: Tagged k s b -> b #

Alias for unTagged

Database management

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

Send a database management query to InfluxDB.

>>> let db = "manage-test"
>>> let p = queryParams db
>>> manage p $ F.formatQuery ("CREATE DATABASE "%F.database) db

Common data types and classes

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

formatDatabase :: Format Database r -> r Source #

Format a Database.

>>> formatDatabase "test-db"
"test-db"

formatMeasurement :: Format Measurement r -> r Source #

Format a Measurement.

>>> formatMeasurement "test-series"
"test-series"

data Key Source #

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

formatKey can be used to construct a Key.

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 #

formatKey :: Format Key r -> r Source #

Format a Key.

>>> formatKey "test-key"
"test-key"

data Server Source #

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.6.0.4-8OJTSEdt5qlEt2cfqDuFnJ" 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

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

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.

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