Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.InfluxDB.Http
Contents
- data Config = Config {}
- data Credentials = Credentials {
- credsUser :: !Text
- credsPassword :: !Text
- rootCreds :: Credentials
- data Server = Server {
- serverHost :: !Text
- serverPort :: !Int
- serverSsl :: !Bool
- localServer :: Server
- data TimePrecision
- post :: Config -> Text -> SeriesT IO a -> IO a
- postWithPrecision :: Config -> Text -> TimePrecision -> SeriesT IO a -> IO a
- data SeriesT m a
- data PointT p m a
- writeSeries :: (Monad m, ToSeriesData a) => Text -> a -> SeriesT m ()
- withSeries :: forall m a. (Monad m, ToSeriesData a) => Text -> PointT a m () -> SeriesT m ()
- writePoints :: (Monad m, ToSeriesData a) => a -> PointT a m ()
- deleteSeries :: Config -> Text -> Text -> IO ()
- query :: FromSeries a => Config -> Text -> Text -> IO [a]
- data Stream m a
- queryChunked :: FromSeries a => Config -> Text -> Text -> (Stream IO a -> IO b) -> IO b
- listDatabases :: Config -> IO [Database]
- createDatabase :: Config -> Text -> IO ()
- dropDatabase :: Config -> Text -> IO ()
- data DatabaseRequest = DatabaseRequest {}
- configureDatabase :: Config -> Text -> DatabaseRequest -> IO ()
- data ShardSpaceRequest = ShardSpaceRequest {}
- listShardSpaces :: Config -> IO [ShardSpace]
- createShardSpace :: Config -> Text -> ShardSpaceRequest -> IO ()
- dropShardSpace :: Config -> Text -> Text -> IO ()
- listClusterAdmins :: Config -> IO [Admin]
- authenticateClusterAdmin :: Config -> IO ()
- addClusterAdmin :: Config -> Text -> Text -> IO Admin
- updateClusterAdminPassword :: Config -> Admin -> Text -> IO ()
- deleteClusterAdmin :: Config -> Admin -> IO ()
- listDatabaseUsers :: Config -> Text -> IO [User]
- authenticateDatabaseUser :: Config -> Text -> IO ()
- addDatabaseUser :: Config -> Text -> Text -> Text -> IO ()
- updateDatabaseUserPassword :: Config -> Text -> Text -> Text -> IO ()
- deleteDatabaseUser :: Config -> Text -> Text -> IO ()
- grantAdminPrivilegeTo :: Config -> Text -> Text -> IO ()
- revokeAdminPrivilegeFrom :: Config -> Text -> Text -> IO ()
- ping :: Config -> IO Ping
- isInSync :: Config -> IO Bool
Documentation
Configurations for HTTP API client.
Constructors
Config | |
Fields
|
data Credentials Source
User credentials.
Constructors
Credentials | |
Fields
|
Instances
rootCreds :: Credentials Source
Default credentials.
Server location.
Constructors
Server | |
Fields
|
Default server location.
data TimePrecision Source
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.
Post a bunch of writes for (possibly multiple) series into a database like
post
but with time precision.
Monad transformer to batch up multiple writes of series to speed up insertions.
Instances
MonadTrans SeriesT | |
Monad m => Monad (SeriesT m) | |
Functor m => Functor (SeriesT m) | |
Applicative m => Applicative (SeriesT m) | |
MonadIO m => MonadIO (SeriesT m) | |
Monad m => MonadWriter (DList Series) (SeriesT m) |
Monad transformer to batch up multiple writes of points to speed up insertions.
Instances
MonadTrans (PointT p) | |
Monad m => MonadWriter (DList (Vector Value)) (PointT p m) | |
Monad m => Monad (PointT p m) | |
Functor m => Functor (PointT p m) | |
Applicative m => Applicative (PointT p m) | |
MonadIO m => MonadIO (PointT p m) |
Arguments
:: (Monad m, ToSeriesData a) | |
=> Text | Series name |
-> a | Series data |
-> SeriesT m () |
Write a single series data.
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
Querying Data
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.
Effectful stream
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.
Drop a database. Requires cluster admin privileges.
Arguments
:: Config | |
-> Text | Database name |
-> DatabaseRequest | |
-> IO () |
Security
Shard spaces
listShardSpaces :: Config -> IO [ShardSpace] Source
List shard spaces.
Arguments
:: Config | |
-> Text | Database |
-> ShardSpaceRequest | |
-> IO () |
Create a shard space.
Cluster admin
listClusterAdmins :: Config -> IO [Admin] Source
List cluster administrators.
authenticateClusterAdmin :: Config -> IO () Source
Add a new cluster administrator. Requires cluster admin privilege.
updateClusterAdminPassword Source
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
Add an user to the database users.
updateDatabaseUserPassword Source
Update password for the database user.
Delete an user from the database users.
Give admin privilege to the user.
revokeAdminPrivilegeFrom Source
Remove admin privilege from the user.