Safe Haskell | None |
---|
- data Series = Series {
- seriesName :: !Text
- seriesData :: !SeriesData
- seriesColumns :: Series -> Vector Column
- seriesPoints :: Series -> [Vector Value]
- data SeriesData = SeriesData {}
- data Value
- class ToSeriesData a where
- toSeriesColumns :: Proxy a -> Vector Column
- toSeriesPoints :: a -> Vector Value
- class ToValue a where
- class FromSeries a where
- parseSeries :: Series -> Parser a
- fromSeries :: FromSeries a => Series -> Either String a
- class FromSeriesData a where
- fromSeriesData :: FromSeriesData a => SeriesData -> Either String [a]
- class FromValue a where
- parseValue :: Value -> Parser a
- fromValue :: FromValue a => Value -> Either String a
- withValues :: (Vector Value -> ValueParser a) -> Vector Column -> Vector Value -> Parser a
- (.:) :: FromValue a => Vector Value -> Column -> ValueParser a
- (.:?) :: FromValue a => Vector Value -> Column -> ValueParser (Maybe a)
- (.!=) :: Parser (Maybe a) -> a -> Parser a
- typeMismatch :: String -> Value -> Parser a
- data Config = Config {}
- data Credentials = Credentials {
- credsUser :: !Text
- credsPassword :: !Text
- rootCreds :: Credentials
- data TimePrecision
- data Server = Server {
- serverHost :: !Text
- serverPort :: !Int
- serverSsl :: !Bool
- localServer :: Server
- data ServerPool
- newServerPool :: Server -> [Server] -> IO (IORef ServerPool)
- newtype Database = Database {
- databaseName :: Text
- data User = User {
- userName :: Text
- userIsAdmin :: Bool
- newtype Admin = Admin {}
- 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 ()
- 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 ()
Series data types
A series consists of name, columns and points. The columns and points are
expressed in a separate type SeriesData
.
Series | |
|
seriesColumns :: Series -> Vector ColumnSource
Convenient accessor for columns.
seriesPoints :: Series -> [Vector Value]Source
Convenient accessor for points.
data SeriesData Source
SeriesData
consists of columns and points.
An InfluxDB value represented as a Haskell value.
Encoding
class ToSeriesData a whereSource
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 toSeriesColumn _ = V.fromList ["user", "type"] toSeriesPoints (Event user ty) = V.fromList [toValue user, toValue ty] instance ToValue EventType
toSeriesColumns :: Proxy a -> Vector ColumnSource
Column names. You can safely ignore the proxy agument.
toSeriesPoints :: a -> Vector ValueSource
Data points.
A type that can be stored in InfluxDB.
Decoding
class FromSeries a whereSource
A type that can be converted from a Series
.
parseSeries :: Series -> Parser aSource
fromSeries :: FromSeries a => Series -> Either String aSource
Converte a value from a Series
, failing if the types do not match.
class FromSeriesData a whereSource
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
fromSeriesData :: FromSeriesData a => SeriesData -> Either String [a]Source
Converte a value from a SeriesData
, failing if the types do not match.
A type that can be converted from a Value
.
parseValue :: Value -> Parser aSource
fromValue :: FromValue a => Value -> Either String aSource
Converte a value from a Value
, failing if the types do not match.
withValues :: (Vector Value -> ValueParser a) -> Vector Column -> Vector Value -> Parser aSource
Helper function to define parseSeriesData
from ValueParser
s.
(.:) :: FromValue a => Vector Value -> Column -> ValueParser aSource
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 aSource
Helper for use in combination with .:?
to provide default values for
optional columns.
typeMismatch :: String -> Value -> Parser aSource
HTTP API
Data types
Configurations for HTTP API client.
Config | |
|
rootCreds :: CredentialsSource
Default credentials.
Server location.
Server | |
|
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.
Writing Data
Updating Points
post :: Config -> Text -> SeriesT IO a -> IO aSource
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.
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.
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) |
:: (Monad m, ToSeriesData a) | |
=> Text | Series name |
-> a | Series data |
-> SeriesT m () |
Write a single series data.
:: forall m a . (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
One Time Deletes
Regularly Scheduled Deletes (not implemented)
Querying Data
:: 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
:: 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.
Security
Cluster admin
listClusterAdmins :: Config -> IO [Admin]Source
List cluster administrators.
authenticateClusterAdmin :: Config -> IO ()Source
Add a new cluster administrator. Requires cluster admin privilege.
updateClusterAdminPasswordSource
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.
updateDatabaseUserPasswordSource
Update password for the database user.
Delete an user from the database users.
Give admin privilege to the user.