influxdb-1.9.2: InfluxDB client library for Haskell
Safe HaskellNone
LanguageHaskell2010

Database.InfluxDB.Format

Synopsis

Documentation

This module is desined to be imported qualified:

>>> :set -XOverloadedStrings
>>> import qualified Data.ByteString as B
>>> import qualified Database.InfluxDB.Format as F

The Format type and associated functions

data Format a r Source #

A typed format string. Format a r means that a is the type of formatted string, and r is the type of the formatter.

>>> :t F.formatQuery
F.formatQuery :: F.Format Query r -> r
>>> :t F.key
F.key :: F.Format r (Key -> r)
>>> :t "SELECT * FROM "%F.key
"SELECT * FROM "%F.key :: F.Format a (Key -> a)
>>> :t F.formatQuery ("SELECT * FROM "%F.key)
F.formatQuery ("SELECT * FROM "%F.key) :: Key -> Query
>>> F.formatQuery ("SELECT * FROM "%F.key) "series"
"SELECT * FROM \"series\""

Instances

Instances details
Category Format Source #

Formats can be composed using (.) from Control.Category.

>>> import Control.Category ((.))
>>> import Prelude hiding ((.))
>>> F.formatQuery ("SELECT * FROM " . F.key) "series"
"SELECT * FROM \"series\""
Instance details

Defined in Database.InfluxDB.Format

Methods

id :: forall (a :: k). Format a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Format b c -> Format a b -> Format a c #

a ~ r => IsString (Format a r) Source #

With the OverloadedStrings exension, string literals can be used to write queries.

>>> "SELECT * FROM series" :: Query
"SELECT * FROM series"
Instance details

Defined in Database.InfluxDB.Format

Methods

fromString :: String -> Format a r #

makeFormat :: (a -> Builder) -> Format r (a -> r) Source #

Convenience function to make a custom formatter.

(%) :: Format b c -> Format a b -> Format a c Source #

Format specific synonym of (.).

This is typically easier to use than (.) is because it doesn't conflict with Prelude.(.).

Formatting functions

formatQuery :: Format Query r -> r Source #

Format a Query.

>>> F.formatQuery "SELECT * FROM series"
"SELECT * FROM series"
>>> F.formatQuery ("SELECT * FROM "%F.key) "series"
"SELECT * FROM \"series\""

formatDatabase :: Format Database r -> r Source #

Format a Database.

>>> F.formatDatabase "test-db"
"test-db"
>>> F.formatDatabase ("test-db-"%F.decimal) 0
"test-db-0"

formatMeasurement :: Format Measurement r -> r Source #

Format a Measurement.

>>> F.formatMeasurement "test-series"
"test-series"
>>> F.formatMeasurement ("test-series-"%F.decimal) 0
"test-series-0"

formatKey :: Format Key r -> r Source #

Format a Key.

>>> F.formatKey "test-key"
"test-key"
>>> F.formatKey ("test-key-"%F.decimal) 0
"test-key-0"

Formatters for various types

database :: Format r (Database -> r) Source #

Format a database name.

>>> F.formatQuery ("CREATE DATABASE "%F.database) "test-db"
"CREATE DATABASE \"test-db\""

key :: Format r (Key -> r) Source #

Format an identifier (e.g. field names, tag names, etc).

Identifiers in InfluxDB protocol are surrounded with double quotes.

>>> F.formatQuery ("SELECT "%F.key%" FROM series") "field"
"SELECT \"field\" FROM series"
>>> F.formatQuery ("SELECT "%F.key%" FROM series") "foo\"bar"
"SELECT \"foo\\\"bar\" FROM series"

keys :: Format r ([Key] -> r) Source #

Format multiple keys.

>>> F.formatQuery ("SELECT "%F.keys%" FROM series") ["field1", "field2"]
"SELECT \"field1\",\"field2\" FROM series"

measurement :: Format r (Measurement -> r) Source #

Format a measurement.

>>> F.formatQuery ("SELECT * FROM "%F.measurement) "test-series"
"SELECT * FROM \"test-series\""

measurements :: Format r ([Measurement] -> r) Source #

Format a measurement.

>>> F.formatQuery ("SELECT * FROM "%F.measurements) ["series1", "series2"]
"SELECT * FROM \"series1\",\"series2\""

field :: Format r (QueryField -> r) Source #

Format an InfluxDB value. Good for field and tag values.

>>> F.formatQuery ("SELECT * FROM series WHERE "%F.key%" = "%F.field) "location" "tokyo"
"SELECT * FROM series WHERE \"location\" = 'tokyo'"

decimal :: Integral a => Format r (a -> r) Source #

Format a decimal number.

>>> F.formatQuery ("SELECT * FROM series WHERE time < now() - "%F.decimal%"h") 1
"SELECT * FROM series WHERE time < now() - 1h"

realFloat :: RealFloat a => Format r (a -> r) Source #

Format a floating-point number.

>>> F.formatQuery ("SELECT * FROM series WHERE value > "%F.realFloat) 0.1
"SELECT * FROM series WHERE value > 0.1"

text :: Format r (Text -> r) Source #

Format a text.

Note that this doesn't escape the string. Use formatKey to format field values in a query.

>>> :t F.formatKey F.text
F.formatKey F.text :: T.Text -> Key

string :: Format r (String -> r) Source #

Format a string.

Note that this doesn't escape the string. Use formatKey to format field values in a query.

>>> :t F.formatKey F.string
F.formatKey F.string :: String -> Key

byteString8 :: Format r (ByteString -> r) Source #

Format a UTF-8 encoded byte string.

Note that this doesn't escape the string. Use formatKey to format field values in a query.

>>> :t F.formatKey F.byteString8
F.formatKey F.byteString8 :: B.ByteString -> Key

time :: FormatTime time => Format r (time -> r) Source #

Format a time.

>>> import Data.Time
>>> let Just t = parseTimeM False defaultTimeLocale "%s" "0" :: Maybe UTCTime
>>> F.formatQuery ("SELECT * FROM series WHERE time >= "%F.time) t
"SELECT * FROM series WHERE time >= '1970-01-01 00:00:00'"

Utility functions