influxdb-1.6.0.7: Haskell client library for InfluxDB

Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB.Line

Contents

Synopsis

Documentation

The Line protocol implementation.

>>> :set -XOverloadedStrings
>>> import Database.InfluxDB
>>> import Data.Time
>>> import qualified Data.ByteString.Lazy.Char8 as BL8
>>> import System.IO (stdout)
>>> :{
let l1 = Line "cpu_usage"
      (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
:}

Types and accessors

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.

Serializers

buildLine :: (time -> Int64) -> Line time -> Builder Source #

Serialize a Line to a bytestring Buider

>>> B.hPutBuilder stdout $ buildLine (scaleTo Second) l1
cpu_usage,cpu=cpu-total idle=10.1,system=53.3,user=46.6 1497714100

buildLines :: Foldable f => (time -> Int64) -> f (Line time) -> Builder Source #

Serialize Lines to a bytestring Builder

>>> B.hPutBuilder stdout $ buildLines (scaleTo Second) [l1, l1]
cpu_usage,cpu=cpu-total idle=10.1,system=53.3,user=46.6 1497714100
cpu_usage,cpu=cpu-total idle=10.1,system=53.3,user=46.6 1497714100

encodeLine Source #

Arguments

:: (time -> Int64)

Function to convert time to an InfluxDB timestamp

Use scaleTo for HTTP writes and roundTo for UDP writes.

-> Line time 
-> ByteString 

Serialize a Line to a lazy bytestring

>>> BL8.putStrLn $ encodeLine (scaleTo Second) l1
cpu_usage,cpu=cpu-total idle=10.1,system=53.3,user=46.6 1497714100

encodeLines Source #

Arguments

:: Foldable f 
=> (time -> Int64)

Function to convert time to an InfluxDB timestamp

Use scaleTo for HTTP writes and roundTo for UDP writes.

-> f (Line time) 
-> ByteString 

Serialize Lines to a lazy bytestring

>>> BL8.putStr $ encodeLines (scaleTo Second) [l1, l1]
cpu_usage,cpu=cpu-total idle=10.1,system=53.3,user=46.6 1497714100
cpu_usage,cpu=cpu-total idle=10.1,system=53.3,user=46.6 1497714100

Other types

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

Defined in Database.InfluxDB.Types

Methods

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

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

Show (Field n) Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

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

show :: Field n -> String #

showList :: [Field n] -> ShowS #

IsString (Field n) Source # 
Instance details

Defined in Database.InfluxDB.Types

Methods

fromString :: String -> Field n #

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
Show (Precision a) Source # 
Instance details

Defined in Database.InfluxDB.Types