influxdb-1.1.2: Haskell client library for InfluxDB

Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB.Types

Synopsis

Documentation

newtype Query Source #

Constructors

Query Text 

data Server Source #

Constructors

Server 

Fields

Instances

Eq Server Source # 

Methods

(==) :: Server -> Server -> Bool #

(/=) :: Server -> Server -> Bool #

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.1.2-eCsD6I1ufwCmOwVM7BHZs" 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)))))

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

Constructors

Credentials 

Fields

user :: Lens' Credentials Text Source #

User name to access InfluxDB

password :: Lens' Credentials Text Source #

Password to access InfluxDB

newtype Key Source #

String type that is used for measurements, tag keys and field keys.

Constructors

Key Text 

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 #

data FieldValue Source #

Instances

Eq FieldValue Source # 
Data FieldValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldValue -> c FieldValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldValue #

toConstr :: FieldValue -> Constr #

dataTypeOf :: FieldValue -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> FieldValue -> FieldValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldValue -> m FieldValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldValue -> m FieldValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldValue -> m FieldValue #

Show FieldValue Source # 
IsString FieldValue Source # 
Generic FieldValue Source # 

Associated Types

type Rep FieldValue :: * -> * #

type Rep FieldValue Source # 

data RequestType Source #

Type of a request

Constructors

QueryRequest

Request for /query

WriteRequest

Request for /write

data Precision ty 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

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

roundAt :: RealFrac a => a -> a -> a Source #

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.

BadRequest String Request

Client side error.

You need to fix your query to get a successful response.

IllformedJSON String ByteString

Unexpected JSON response.

This can happen e.g. when the response from InfluxDB is incompatible with what this library expects due to an upstream format change etc.

class HasServer a where Source #

Minimal complete definition

server

Methods

server :: Lens' a Server Source #

Instances

HasServer PingParams Source # 
HasServer WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. server.host
"localhost"
HasServer QueryParams Source #
>>> let p = queryParams "foo"
>>> p ^. server.host
"localhost"

class HasDatabase a where Source #

Minimal complete definition

database

Instances

HasDatabase WriteParams Source #
>>> let p = writeParams "foo"
>>> p ^. database
"foo"
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
["_internal"]

class HasPrecision ty a | a -> ty where Source #

Minimal complete definition

precision

Methods

precision :: Lens' a (Precision ty) Source #

Instances

HasPrecision QueryRequest QueryParams Source #

Returning JSON responses contain timestamps in the specified precision/format.

>>> let p = queryParams "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.

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

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 # 
HasManager WriteParams Source #
>>> let p = writeParams "foo"
>>> p & manager .~ Left HC.defaultManagerSettings
HasManager QueryParams Source #
>>> let p = queryParams "foo"
>>> p & manager .~ Left HC.defaultManagerSettings