influxdb-1.9.0: Haskell client library for InfluxDB

Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB.Write

Contents

Synopsis

Writers

The code snippets in this module assume the following imports.

import qualified Data.Map as Map
import Data.Time

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

Write a Line.

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

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 @UTCTime "temp" (Map.singleton "city" "tokyo") (Map.fromList [("temp", FieldFloat 25.0)]) Nothing
  , Line @UTCTime "temp" (Map.singleton "city" "osaka") (Map.fromList [("temp", FieldFloat 25.2)]) Nothing
  ]
:}

Writer parameters

data WriteParams Source #

The full set of parameters for the HTTP writer.

Following lenses are available to access its fields:

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

Defined in Database.InfluxDB.Write

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

Defined in Database.InfluxDB.Write

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

Defined in Database.InfluxDB.Write

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

Defined in Database.InfluxDB.Write

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

Defined in Database.InfluxDB.Write

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.

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"

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.