Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- write :: Timestamp time => WriteParams -> Line time -> IO ()
- writeBatch :: (Timestamp time, Foldable f) => WriteParams -> f (Line time) -> IO ()
- writeByteString :: WriteParams -> ByteString -> IO ()
- data WriteParams
- writeParams :: Database -> WriteParams
- retentionPolicy :: Lens' WriteParams (Maybe Key)
- data Line time = Line !Measurement !(Map Key Key) !(Map Key LineField) !(Maybe time)
- measurement :: Lens' (Line time) Measurement
- tagSet :: Lens' (Line time) (Map Key Key)
- fieldSet :: Lens' (Line time) (Map Key LineField)
- timestamp :: Lens' (Line time) (Maybe time)
- data Field (n :: Nullability) where
- type LineField = Field 'NonNullable
- type QueryField = Field 'Nullable
- class Timestamp time where
- roundTo :: Precision 'WriteRequest -> time -> Int64
- scaleTo :: Precision 'WriteRequest -> time -> Int64
- precisionScale :: Fractional a => Precision ty -> a
- precisionName :: Precision ty -> Text
- data Query
- query :: forall a. QueryResults a => QueryParams -> Query -> IO (Vector a)
- queryChunked :: QueryResults a => QueryParams -> Optional Int -> Query -> FoldM IO (Vector a) r -> IO r
- formatQuery :: Format Query r -> r
- (%) :: Format b c -> Format a b -> Format a c
- data QueryParams
- queryParams :: Database -> QueryParams
- authentication :: HasCredentials a => Lens' a (Maybe Credentials)
- decoder :: Lens' QueryParams Decoder
- class QueryResults a where
- parseMeasurement :: Precision 'QueryRequest -> Maybe Text -> HashMap Text Text -> Vector Text -> Array -> Parser a
- coerceDecoder :: proxy a -> Maybe Decoder
- data Decoder
- lenientDecoder :: Decoder
- strictDecoder :: Decoder
- data Ignored
- data Empty
- newtype Tagged (s :: k) b = Tagged {
- unTagged :: b
- untag :: forall k (s :: k) b. Tagged s b -> b
- getField :: MonadFail m => Text -> Vector Text -> Vector Value -> m Value
- getTag :: MonadFail m => Text -> HashMap Text Value -> m Value
- parseJSON :: FromJSON a => Value -> Parser a
- parseUTCTime :: Precision ty -> Value -> Parser UTCTime
- parsePOSIXTime :: Precision ty -> Value -> Parser POSIXTime
- manage :: QueryParams -> Query -> IO ()
- data Precision (ty :: RequestType) where
- Nanosecond :: Precision ty
- Microsecond :: Precision ty
- Millisecond :: Precision ty
- Second :: Precision ty
- Minute :: Precision ty
- Hour :: Precision ty
- RFC3339 :: Precision 'QueryRequest
- data Database
- formatDatabase :: Format Database r -> r
- data Measurement
- formatMeasurement :: Format Measurement r -> r
- data Key
- formatKey :: Format Key r -> r
- data Server
- defaultServer :: Server
- secureServer :: Server
- host :: Lens' Server Text
- port :: Lens' Server Int
- ssl :: Lens' Server Bool
- data Credentials
- credentials :: Text -> Text -> Credentials
- user :: Lens' Credentials Text
- password :: Lens' Credentials Text
- data InfluxException
- class HasServer a where
- class HasDatabase a where
- class HasPrecision (ty :: RequestType) a | a -> ty where
- class HasManager a where
- manager :: Lens' a (Either ManagerSettings Manager)
Documentation
Getting started
This tutorial assumes the following language extensions and imports.
>>>
:set -XOverloadedStrings
>>>
:set -XRecordWildCards
>>>
:set -XTypeApplications
>>>
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 @UTCTime 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") ] :}
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 -XTypeOperators
>>>
type CPUUsage = (Tagged "time" UTCTime, Tagged "idle" Double, Tagged "system" Double, Tagged "user" Double)
>>>
v <- query @CPUUsage p $ formatQuery ("SELECT * FROM "%F.measurement) 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 parseJSON
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 parseMeasurement prec _name _tags 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 @CPUUsage p $ formatQuery ("SELECT * FROM "%F.measurement) 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, see Database.InfluxDB.Write.UDP.
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 Line
s 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 ] :}
writeByteString :: WriteParams -> ByteString -> IO () Source #
Write a raw ByteString
Write 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
|
Defined in Database.InfluxDB.Write | |
HasManager WriteParams Source # |
|
Defined in Database.InfluxDB.Write | |
HasDatabase WriteParams Source # |
|
Defined in Database.InfluxDB.Write | |
HasServer WriteParams Source # |
|
Defined in Database.InfluxDB.Write | |
HasPrecision 'WriteRequest WriteParams Source # |
|
Defined in Database.InfluxDB.Write |
writeParams :: Database -> WriteParams Source #
Smart constructor for WriteParams
Default parameters:
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
Placeholder for the Line Protocol
See https://docs.influxdata.com/influxdb/v1.7/write_protocols/line_protocol_tutorial/ for the concrete syntax.
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 #
FieldInt :: !Int64 -> Field n | Signed 64-bit integers ( |
FieldFloat :: !Double -> Field n | IEEE-754 64-bit floating-point numbers. This is the default numerical type. |
FieldString :: !Text -> Field n | String field. Its length is limited to 64KB, which is not enforced by this library. |
FieldBool :: !Bool -> Field n | Boolean field. |
FieldNull :: Field 'Nullable | Null field. Note that a field can be null only in queries. The line protocol doesn't allow null values. |
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.
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 # |
|
Defined in Database.InfluxDB.Types | |
Timestamp TimeSpec Source # |
|
Defined in Database.InfluxDB.Types | |
Timestamp NominalDiffTime Source # |
|
Defined in Database.InfluxDB.Types roundTo :: Precision 'WriteRequest -> NominalDiffTime -> Int64 Source # scaleTo :: Precision 'WriteRequest -> NominalDiffTime -> Int64 Source # |
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">>>
precisionName Microsecond
"u">>>
precisionName Millisecond
"ms">>>
precisionName Second
"s">>>
precisionName Minute
"m">>>
precisionName Hour
"h">>>
precisionName RFC3339
"rfc3339"
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.
An InfluxDB query.
A spec of the format is available at https://docs.influxdata.com/influxdb/v1.7/query_language/spec/.
A Query
can be constructed using either
- the
IsString
instance with-XOverloadedStrings
- or
formatQuery
.
>>>
: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 :: forall a. 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
.
:: QueryResults a | |
=> QueryParams | |
-> Optional Int | Chunk size By |
-> 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
.
>>>
F.formatQuery "SELECT * FROM series"
"SELECT * FROM series">>>
F.formatQuery ("SELECT * FROM "%F.key) "series"
"SELECT * FROM \"series\""
Query parameters
data QueryParams Source #
The full set of parameters for the query API
Following lenses are available to access its fields:
Instances
HasCredentials QueryParams Source # | Authentication info for the query
|
Defined in Database.InfluxDB.Query | |
HasManager QueryParams Source # |
|
Defined in Database.InfluxDB.Query | |
HasDatabase QueryParams Source # |
|
Defined in Database.InfluxDB.Query | |
HasServer QueryParams Source # |
|
Defined in Database.InfluxDB.Query | |
HasPrecision 'QueryRequest QueryParams Source # | Returning JSON responses contain timestamps in the specified precision/format.
|
Defined in Database.InfluxDB.Query |
queryParams :: Database -> QueryParams Source #
Smart constructor for QueryParams
Default parameters:
authentication :: HasCredentials a => Lens' a (Maybe Credentials) Source #
User name and password to be used when sending requests to InfluxDB.
decoder :: Lens' QueryParams Decoder Source #
Decoder settings
>>>
let p = queryParams "foo"
>>>
let _ = p & decoder .~ strictDecoder
>>>
let _ = p & decoder .~ lenientDecoder
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 parseMeasurement prec _name _tags 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 {..} :}
:: Precision 'QueryRequest | Timestamp precision |
-> Maybe Text | Optional series name |
-> HashMap Text Text | Tag set |
-> Vector Text | Field keys |
-> Array | Field values |
-> Parser a |
Parse a single measurement in a JSON object.
coerceDecoder :: proxy a -> Maybe Decoder Source #
Always use this Decoder
when decoding this type.
means Just
decdecoder
in QueryParams
will be ignored and be
replaced with the dec
. Nothing
means decoder
in QueryParams
will
be used.
Instances
A decoder to use when parsing a JSON response.
Use strictDecoder
if you want to fail the entire decoding process if
there's any failure. Use lenientDecoder
if you want the decoding process
to collect only successful results.
lenientDecoder :: Decoder Source #
A decoder that ignores parse failures and returns only successful results.
strictDecoder :: Decoder Source #
A decoder that fails immediately if there's any parse failure.
strictDecoder
is defined as follows:
strictDecoder :: Decoder strictDecoder = Decoder $ SomeDecoder { decodeEach = id , decodeFold = id }
Helper types and functions
Ignored
can be used in the result type of query
when the result values
are not needed.
>>>
v <- query @Ignored (queryParams "dummy") "SHOW DATABASES"
>>>
v
[]
Instances
Show Ignored Source # | |
QueryResults Ignored Source # |
|
Empty
can be used in the result type of query
when the expected results
are always empty. Note that if the results are not empty, the decoding
process will fail:
>>>
let p = queryParams "empty"
>>>
Database.InfluxDB.Manage.manage p "CREATE DATABASE empty"
>>>
v <- query @Empty p "SELECT * FROM empty" -- query an empty series
>>>
v
[]
Instances
Show Empty Source # | |
QueryResults Empty Source # |
|
A
value is a value Tagged
s bb
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
can't try to use the argument Tagged
s bs
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.
Instances
Get a field value from a column name
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
.
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 QueryRequest
s.
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
|
Database name.
formatDatabase
can be used to construct a
Database
.
>>>
"test-db" :: Database
"test-db">>>
formatDatabase "test-db"
"test-db">>>
formatDatabase ("test-db-"%F.decimal) 0
"test-db-0"
formatDatabase :: Format Database r -> r Source #
Format a Database
.
>>>
F.formatDatabase "test-db"
"test-db">>>
F.formatDatabase ("test-db-"%F.decimal) 0
"test-db-0"
data Measurement Source #
String name that is used for measurements.
formatMeasurement
can be used to construct a
Measurement
.
>>>
"test-series" :: Measurement
"test-series">>>
formatMeasurement "test-series"
"test-series">>>
formatMeasurement ("test-series-"%F.decimal) 0
"test-series-0"
Instances
Eq Measurement Source # | |
Defined in Database.InfluxDB.Types (==) :: Measurement -> Measurement -> Bool # (/=) :: Measurement -> Measurement -> Bool # | |
Ord Measurement Source # | |
Defined in Database.InfluxDB.Types compare :: Measurement -> Measurement -> Ordering # (<) :: Measurement -> Measurement -> Bool # (<=) :: Measurement -> Measurement -> Bool # (>) :: Measurement -> Measurement -> Bool # (>=) :: Measurement -> Measurement -> Bool # max :: Measurement -> Measurement -> Measurement # min :: Measurement -> Measurement -> Measurement # | |
Show Measurement Source # | |
Defined in Database.InfluxDB.Types showsPrec :: Int -> Measurement -> ShowS # show :: Measurement -> String # showList :: [Measurement] -> ShowS # | |
IsString Measurement Source # | |
Defined in Database.InfluxDB.Types fromString :: String -> Measurement # |
formatMeasurement :: Format Measurement r -> r Source #
Format a Measurement
.
>>>
F.formatMeasurement "test-series"
"test-series">>>
F.formatMeasurement ("test-series-"%F.decimal) 0
"test-series-0"
String type that is used for tag keys/values and field keys.
formatKey
can be used to construct a Key
.
>>>
"test-key" :: Key
"test-key">>>
formatKey "test-key"
"test-key">>>
formatKey ("test-key-"%F.decimal) 0
"test-key-0"
formatKey :: Format Key r -> r Source #
Format a Key
.
>>>
F.formatKey "test-key"
"test-key">>>
F.formatKey ("test-key-"%F.decimal) 0
"test-key-0"
InfluxDB server to connect to.
Following lenses are available to access its fields:
Instances
Eq Server Source # | |
Ord Server Source # | |
Show Server Source # | |
Generic Server Source # | |
type Rep Server Source # | |
Defined in Database.InfluxDB.Types type Rep Server = D1 ('MetaData "Server" "Database.InfluxDB.Types" "influxdb-1.9.2-CIOZ9787HYkMsaTrowotD" 'False) (C1 ('MetaCons "Server" 'PrefixI 'True) (S1 ('MetaSel ('Just "_host") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "_port") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "_ssl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))) |
defaultServer :: Server Source #
Default InfluxDB server settings
Default parameters:
>>>
defaultServer ^. host
"localhost">>>
defaultServer ^. port
8086>>>
defaultServer ^. ssl
False
secureServer :: Server Source #
HTTPS-enabled InfluxDB server settings
ssl :: Lens' Server Bool Source #
If SSL is enabled
For secure connections (HTTPS), consider using one of the following packages:
data Credentials Source #
Instances
Show Credentials Source # | |
Defined in Database.InfluxDB.Types showsPrec :: Int -> Credentials -> ShowS # show :: Credentials -> String # showList :: [Credentials] -> ShowS # |
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
>>>
let creds = credentials "john" "passw0rd"
>>>
creds ^. password
"passw0rd"
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.
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 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 |
Instances
Show InfluxException Source # | |
Defined in Database.InfluxDB.Types showsPrec :: Int -> InfluxException -> ShowS # show :: InfluxException -> String # showList :: [InfluxException] -> ShowS # | |
Exception InfluxException Source # | |
Defined in Database.InfluxDB.Types |
class HasServer a where Source #
Class of data types that have a server field
Instances
HasServer PingParams Source # |
|
Defined in Database.InfluxDB.Ping | |
HasServer QueryParams Source # |
|
Defined in Database.InfluxDB.Query | |
HasServer WriteParams Source # |
|
Defined in Database.InfluxDB.Write |
class HasDatabase a where Source #
Class of data types that have a database field
Instances
HasDatabase QueryParams Source # |
|
Defined in Database.InfluxDB.Query | |
HasDatabase ShowQuery Source # |
|
HasDatabase WriteParams Source # |
|
Defined in Database.InfluxDB.Write |
class HasPrecision (ty :: RequestType) a | a -> ty where Source #
Class of data types that have a precision field
Instances
HasPrecision 'QueryRequest QueryParams Source # | Returning JSON responses contain timestamps in the specified precision/format.
|
Defined in Database.InfluxDB.Query | |
HasPrecision 'WriteRequest WriteParams Source # |
|
Defined in Database.InfluxDB.Write | |
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. |
Defined in Database.InfluxDB.Write.UDP |
class HasManager a where Source #
Class of data types that have a manager field
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 # |
|
Defined in Database.InfluxDB.Ping | |
HasManager QueryParams Source # |
|
Defined in Database.InfluxDB.Query | |
HasManager WriteParams Source # |
|
Defined in Database.InfluxDB.Write |