influxdb-0.10.0: Haskell client library for InfluxDB

Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB

Contents

Synopsis

Series data types

data Series Source #

A series consists of name, columns and points. The columns and points are expressed in a separate type SeriesData.

Constructors

Series 

Fields

Instances

Generic Series Source # 

Associated Types

type Rep Series :: * -> * #

Methods

from :: Series -> Rep Series x #

to :: Rep Series x -> Series #

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

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 #

type Rep Series Source # 
type Rep Series = D1 (MetaData "Series" "Database.InfluxDB.Types" "influxdb-0.10.0-6UzQ1Q8vsoP9cn1oXjGOX1" False) (C1 (MetaCons "Series" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "seriesName") SourceUnpack SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "seriesData") SourceUnpack SourceStrict DecidedStrict) (Rec0 SeriesData))))

seriesColumns :: Series -> Vector Column Source #

Convenient accessor for columns.

seriesPoints :: Series -> [Vector Value] Source #

Convenient accessor for points.

data Value Source #

An InfluxDB value represented as a Haskell value.

Constructors

Int !Int64 
Float !Double 
String !Text 
Bool !Bool 
Null 

Instances

Eq Value Source # 

Methods

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

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

Data Value Source # 

Methods

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

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

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Value Source # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 

Associated Types

type Rep Value :: * -> * #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

ToJSON Value Source # 
FromJSON Value Source # 
ToValue Value Source # 

Methods

toValue :: Value -> Value Source #

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

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 #

type Rep Value Source # 

Encoding

class ToSeriesData a where Source #

A type that can be converted to a SeriesData. A typical implementation is as follows.

import qualified Data.Vector as V

data Event = Event Text EventType
data EventType = Login | Logout

instance ToSeriesData Event where
  toSeriesColumns _ = V.fromList ["user", "type"]
  toSeriesPoints (Event user ty) = V.fromList [toValue user, toValue ty]

instance ToValue EventType

Minimal complete definition

toSeriesColumns, toSeriesPoints

Methods

toSeriesColumns :: Proxy a -> Vector Column Source #

Column names. You can safely ignore the proxy agument.

toSeriesPoints :: a -> Vector Value Source #

Data points.

class ToValue a where Source #

A type that can be stored in InfluxDB.

Minimal complete definition

toValue

Methods

toValue :: a -> Value Source #

Decoding

class FromSeries a where Source #

A type that can be converted from a Series.

Minimal complete definition

parseSeries

fromSeries :: FromSeries a => Series -> Either String a Source #

Converte a value from a Series, failing if the types do not match.

class FromSeriesData a where Source #

A type that can be converted from a SeriesData. A typical implementation is as follows.

import Control.Applicative ((<$>), (<*>))
import qualified Data.Vector as V

data Event = Event Text EventType
data EventType = Login | Logout

instance FromSeriesData Event where
  parseSeriesData = withValues $ \values -> Event
    <$> values .: "user"
    <*> values .: "type"

instance FromValue EventType

Minimal complete definition

parseSeriesData

fromSeriesData :: FromSeriesData a => SeriesData -> Either String [a] Source #

Converte a value from a SeriesData, failing if the types do not match.

fromValue :: FromValue a => Value -> Either String a Source #

Converte a value from a Value, failing if the types do not match.

withValues :: (Vector Value -> ValueParser a) -> Vector Column -> Vector Value -> Parser a Source #

Helper function to define parseSeriesData from ValueParsers.

(.:) :: FromValue a => Vector Value -> Column -> ValueParser a Source #

Retrieve the value associated with the given column. The result is empty if the column is not present or the value cannot be converted to the desired type.

(.:?) :: FromValue a => Vector Value -> Column -> ValueParser (Maybe a) Source #

Retrieve the value associated with the given column. The result is Nothing if the column is not present or the value cannot be converted to the desired type.

(.!=) :: Parser (Maybe a) -> a -> Parser a Source #

Helper for use in combination with .:? to provide default values for optional columns.

HTTP API

Data types

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.

data ServerPool Source #

Non-empty set of server locations. The active server will always be used until any HTTP communications fail.

newServerPool :: Server -> [Server] -> IO (IORef ServerPool) Source #

Create a non-empty server pool. You must specify at least one server location to create a pool.

newtype Database Source #

Constructors

Database 

Fields

Instances

Show Database Source # 
Generic Database Source # 

Associated Types

type Rep Database :: * -> * #

Methods

from :: Database -> Rep Database x #

to :: Rep Database x -> Database #

FromJSON Database Source # 
type Rep Database Source # 
type Rep Database = D1 (MetaData "Database" "Database.InfluxDB.Types" "influxdb-0.10.0-6UzQ1Q8vsoP9cn1oXjGOX1" True) (C1 (MetaCons "Database" PrefixI True) (S1 (MetaSel (Just Symbol "databaseName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data User Source #

User

Constructors

User 

Fields

Instances

Show User Source # 

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Generic User Source # 

Associated Types

type Rep User :: * -> * #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

FromJSON User Source # 

Methods

parseJSON :: Value -> Parser User #

type Rep User Source # 
type Rep User = D1 (MetaData "User" "Database.InfluxDB.Types" "influxdb-0.10.0-6UzQ1Q8vsoP9cn1oXjGOX1" False) (C1 (MetaCons "User" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "userName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "userIsAdmin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

newtype Admin Source #

Administrator

Constructors

Admin 

Fields

Instances

Show Admin Source # 

Methods

showsPrec :: Int -> Admin -> ShowS #

show :: Admin -> String #

showList :: [Admin] -> ShowS #

Generic Admin Source # 

Associated Types

type Rep Admin :: * -> * #

Methods

from :: Admin -> Rep Admin x #

to :: Rep Admin x -> Admin #

FromJSON Admin Source # 
type Rep Admin Source # 
type Rep Admin = D1 (MetaData "Admin" "Database.InfluxDB.Types" "influxdb-0.10.0-6UzQ1Q8vsoP9cn1oXjGOX1" True) (C1 (MetaCons "Admin" PrefixI True) (S1 (MetaSel (Just Symbol "adminName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Ping Source #

Constructors

Ping 

Fields

Instances

Show Ping Source # 

Methods

showsPrec :: Int -> Ping -> ShowS #

show :: Ping -> String #

showList :: [Ping] -> ShowS #

Generic Ping Source # 

Associated Types

type Rep Ping :: * -> * #

Methods

from :: Ping -> Rep Ping x #

to :: Rep Ping x -> Ping #

FromJSON Ping Source # 

Methods

parseJSON :: Value -> Parser Ping #

type Rep Ping Source # 
type Rep Ping = D1 (MetaData "Ping" "Database.InfluxDB.Types" "influxdb-0.10.0-6UzQ1Q8vsoP9cn1oXjGOX1" True) (C1 (MetaCons "Ping" PrefixI True) (S1 (MetaSel (Just Symbol "pingStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data ShardSpace Source #

Exception

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