influxdb-0.10.0: Haskell client library for InfluxDB

Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB.Types

Contents

Synopsis

Series, columns and data points

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 # 

Data types for HTTP API

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))))

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)))))

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 #

Server pool

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.

activeServer :: IORef ServerPool -> IO Server Source #

Get a server from the pool.

failover :: IORef ServerPool -> IO () Source #

Move the current server to the backup pool and pick one of the backup server as the new active server. Currently the scheduler works in round-robin fashion.

Exceptions