influxdb-0.10.0: Haskell client library for InfluxDB

Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB.Http

Contents

Synopsis

Documentation

data Config Source #

Configurations for HTTP API client.

data Credentials Source #

User credentials.

Constructors

Credentials 

Fields

Instances

Show Credentials Source # 
Generic Credentials Source # 

Associated Types

type Rep Credentials :: * -> * #

type Rep Credentials Source # 
type Rep Credentials = D1 (MetaData "Credentials" "Database.InfluxDB.Types" "influxdb-0.10.0-6UzQ1Q8vsoP9cn1oXjGOX1" False) (C1 (MetaCons "Credentials" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "credsUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "credsPassword") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

rootCreds :: Credentials Source #

Default credentials.

data Server Source #

Server location.

Constructors

Server 

Fields

Instances

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-0.10.0-6UzQ1Q8vsoP9cn1oXjGOX1" False) (C1 (MetaCons "Server" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "serverHost") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "serverPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Just Symbol "serverSsl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)))))

localServer :: Server Source #

Default server location.

Writing Data

Updating Points

post :: Config -> Text -> SeriesT IO a -> IO a Source #

Post a bunch of writes for (possibly multiple) series into a database.

postWithPrecision Source #

Arguments

:: Config 
-> Text

Database name

-> TimePrecision 
-> SeriesT IO a 
-> IO a 

Post a bunch of writes for (possibly multiple) series into a database like post but with time precision.

data SeriesT m a Source #

Monad transformer to batch up multiple writes of series to speed up insertions.

Instances

MonadTrans SeriesT Source # 

Methods

lift :: Monad m => m a -> SeriesT m a #

Monad m => Monad (SeriesT m) Source # 

Methods

(>>=) :: SeriesT m a -> (a -> SeriesT m b) -> SeriesT m b #

(>>) :: SeriesT m a -> SeriesT m b -> SeriesT m b #

return :: a -> SeriesT m a #

fail :: String -> SeriesT m a #

Functor m => Functor (SeriesT m) Source # 

Methods

fmap :: (a -> b) -> SeriesT m a -> SeriesT m b #

(<$) :: a -> SeriesT m b -> SeriesT m a #

Applicative m => Applicative (SeriesT m) Source # 

Methods

pure :: a -> SeriesT m a #

(<*>) :: SeriesT m (a -> b) -> SeriesT m a -> SeriesT m b #

(*>) :: SeriesT m a -> SeriesT m b -> SeriesT m b #

(<*) :: SeriesT m a -> SeriesT m b -> SeriesT m a #

MonadIO m => MonadIO (SeriesT m) Source # 

Methods

liftIO :: IO a -> SeriesT m a #

Monad m => MonadWriter (DList Series) (SeriesT m) Source # 

Methods

writer :: (a, DList Series) -> SeriesT m a #

tell :: DList Series -> SeriesT m () #

listen :: SeriesT m a -> SeriesT m (a, DList Series) #

pass :: SeriesT m (a, DList Series -> DList Series) -> SeriesT m a #

data PointT p m a Source #

Monad transformer to batch up multiple writes of points to speed up insertions.

Instances

MonadTrans (PointT p) Source # 

Methods

lift :: Monad m => m a -> PointT p m a #

Monad m => MonadWriter (DList (Vector Value)) (PointT p m) Source # 

Methods

writer :: (a, DList (Vector Value)) -> PointT p m a #

tell :: DList (Vector Value) -> PointT p m () #

listen :: PointT p m a -> PointT p m (a, DList (Vector Value)) #

pass :: PointT p m (a, DList (Vector Value) -> DList (Vector Value)) -> PointT p m a #

Monad m => Monad (PointT p m) Source # 

Methods

(>>=) :: PointT p m a -> (a -> PointT p m b) -> PointT p m b #

(>>) :: PointT p m a -> PointT p m b -> PointT p m b #

return :: a -> PointT p m a #

fail :: String -> PointT p m a #

Functor m => Functor (PointT p m) Source # 

Methods

fmap :: (a -> b) -> PointT p m a -> PointT p m b #

(<$) :: a -> PointT p m b -> PointT p m a #

Applicative m => Applicative (PointT p m) Source # 

Methods

pure :: a -> PointT p m a #

(<*>) :: PointT p m (a -> b) -> PointT p m a -> PointT p m b #

(*>) :: PointT p m a -> PointT p m b -> PointT p m b #

(<*) :: PointT p m a -> PointT p m b -> PointT p m a #

MonadIO m => MonadIO (PointT p m) Source # 

Methods

liftIO :: IO a -> PointT p m a #

writeSeries Source #

Arguments

:: (Monad m, ToSeriesData a) 
=> Text

Series name

-> a

Series data

-> SeriesT m () 

Write a single series data.

writeSeriesData Source #

Arguments

:: Monad m 
=> Text

Series name

-> SeriesData

Series data

-> SeriesT m () 

Write a single series data.

withSeries Source #

Arguments

:: (Monad m, ToSeriesData a) 
=> Text

Series name

-> PointT a m () 
-> SeriesT m () 

Write a bunch of data for a single series. Columns for the points don't need to be specified because they can be inferred from the type of a.

writePoints :: (Monad m, ToSeriesData a) => a -> PointT a m () Source #

Write a data into a series.

Deleting Points

deleteSeries Source #

Arguments

:: Config 
-> Text

Database name

-> Text

Series name

-> IO () 

Querying Data

query Source #

Arguments

:: FromSeries a 
=> Config 
-> Text

Database name

-> Text

Query text

-> IO [a] 

Query a specified database.

The query format is specified in the InfluxDB Query Language.

data Stream m a Source #

Effectful stream

Constructors

Yield a (m (Stream m a))

Yield a value. The stream will be continued.

Done

The end of the stream.

queryChunked Source #

Arguments

:: FromSeries a 
=> Config 
-> Text

Database name

-> Text

Query text

-> (Stream IO a -> IO b)

Action to handle the resulting stream of series

-> IO b 

Query a specified database like query but in a streaming fashion.

Administration & Security

Creating and Dropping Databases

listDatabases :: Config -> IO [Database] Source #

List existing databases.

createDatabase :: Config -> Text -> IO () Source #

Create a new database. Requires cluster admin privileges.

dropDatabase Source #

Arguments

:: Config 
-> Text

Database name

-> IO () 

Drop a database. Requires cluster admin privileges.

configureDatabase Source #

Arguments

:: Config 
-> Text

Database name

-> DatabaseRequest 
-> IO () 

Security

Shard spaces

listShardSpaces :: Config -> IO [ShardSpace] Source #

List shard spaces.

createShardSpace Source #

Arguments

:: Config 
-> Text

Database

-> ShardSpaceRequest 
-> IO () 

Create a shard space.

dropShardSpace Source #

Arguments

:: Config 
-> Text

Database name

-> Text

Shard space name

-> IO () 

Cluster admin

listClusterAdmins :: Config -> IO [Admin] Source #

List cluster administrators.

addClusterAdmin Source #

Arguments

:: Config 
-> Text

Admin name

-> Text

Password

-> IO Admin 

Add a new cluster administrator. Requires cluster admin privilege.

updateClusterAdminPassword Source #

Arguments

:: Config 
-> Admin 
-> Text

New password

-> IO () 

Update a cluster administrator's password. Requires cluster admin privilege.

deleteClusterAdmin :: Config -> Admin -> IO () Source #

Delete a cluster administrator. Requires cluster admin privilege.

Database user

listDatabaseUsers :: Config -> Text -> IO [User] Source #

List database users.

authenticateDatabaseUser Source #

Arguments

:: Config 
-> Text

Database name

-> IO () 

addDatabaseUser Source #

Arguments

:: Config 
-> Text

Database name

-> Text

User name

-> Text

Password

-> IO () 

Add an user to the database users.

updateDatabaseUserPassword Source #

Arguments

:: Config 
-> Text

Database name

-> Text

User name

-> Text

New password

-> IO () 

Update password for the database user.

deleteDatabaseUser Source #

Arguments

:: Config 
-> Text

Database name

-> Text

User name

-> IO () 

Delete an user from the database users.

grantAdminPrivilegeTo Source #

Arguments

:: Config 
-> Text

Database name

-> Text

User name

-> IO () 

Give admin privilege to the user.

revokeAdminPrivilegeFrom Source #

Arguments

:: Config 
-> Text

Database name

-> Text

User name

-> IO () 

Remove admin privilege from the user.

Other API