| Stability | experimental | 
|---|---|
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Database.InfluxDB
Contents
Description
Synopsis
- write :: Timestamp time => WriteParams -> Line time -> IO ()
- writeBatch :: (Timestamp time, Foldable f) => WriteParams -> f (Line time) -> IO ()
- writeByteString :: WriteParams -> ByteString -> IO ()
- data WriteParams
- writeParams :: Database -> WriteParams
- retentionPolicy :: Lens' WriteParams (Maybe Key)
- data Line time = Line !Measurement !(Map Key Key) !(Map Key LineField) !(Maybe time)
- measurement :: Lens' (Line time) Measurement
- tagSet :: Lens' (Line time) (Map Key Key)
- fieldSet :: Lens' (Line time) (Map Key LineField)
- timestamp :: Lens' (Line time) (Maybe time)
- data Field (n :: Nullability) where
- type LineField = Field NonNullable
- type QueryField = Field Nullable
- class Timestamp time where
- precisionScale :: Fractional a => Precision ty -> a
- precisionName :: Precision ty -> Text
- data Query
- query :: QueryResults a => QueryParams -> Query -> IO (Vector a)
- queryChunked :: QueryResults a => QueryParams -> Optional Int -> Query -> FoldM IO (Vector a) r -> IO r
- formatQuery :: Format Query r -> r
- (%) :: Format b c -> Format a b -> Format a c
- data QueryParams
- queryParams :: Database -> QueryParams
- authentication :: HasCredentials a => Lens' a (Maybe Credentials)
- class QueryResults a where
- parseResultsWith :: (Maybe Text -> HashMap Text Text -> Vector Text -> Array -> Parser a) -> Value -> Parser (Vector a)
- parseResultsWithDecoder :: Decoder a -> (Maybe Text -> HashMap Text Text -> Vector Text -> Array -> Parser a) -> Value -> Parser (Vector a)
- data Decoder a = Decoder {- decodeEach :: Parser a -> Parser b
- decodeFold :: Parser (Vector b) -> Parser (Vector a)
 
- lenientDecoder :: Decoder a
- strictDecoder :: Decoder a
- getField :: Monad m => Text -> Vector Text -> Vector Value -> m Value
- getTag :: Monad m => Text -> HashMap Text Value -> m Value
- parseJSON :: FromJSON a => Value -> Parser a
- parseUTCTime :: Precision ty -> Value -> Parser UTCTime
- parsePOSIXTime :: Precision ty -> Value -> Parser POSIXTime
- parseQueryField :: Value -> Parser QueryField
- newtype Tagged (s :: k) b :: forall k. k -> * -> * = Tagged {- unTagged :: b
 
- untag :: Tagged s b -> b
- manage :: QueryParams -> Query -> IO ()
- data Precision (ty :: RequestType) where- Nanosecond :: Precision ty
- Microsecond :: Precision ty
- Millisecond :: Precision ty
- Second :: Precision ty
- Minute :: Precision ty
- Hour :: Precision ty
- RFC3339 :: Precision QueryRequest
 
- data Database
- formatDatabase :: Format Database r -> r
- data Measurement
- formatMeasurement :: Format Measurement r -> r
- data Key
- formatKey :: Format Key r -> r
- data Server
- defaultServer :: Server
- host :: Lens' Server Text
- port :: Lens' Server Int
- ssl :: Lens' Server Bool
- data Credentials
- credentials :: Text -> Text -> Credentials
- user :: Lens' Credentials Text
- password :: Lens' Credentials Text
- data InfluxException
- class HasServer a where
- class HasDatabase a where
- class HasPrecision (ty :: RequestType) a | a -> ty where
- class HasManager a where
Documentation
Getting started
This tutorial assumes the following language extensions and imports.
>>>:set -XOverloadedStrings>>>:set -XRecordWildCards>>>import Database.InfluxDB>>>import qualified Database.InfluxDB.Format as F>>>import Control.Lens>>>import qualified Data.Map as Map>>>import Data.Time>>>import qualified Data.Vector as V
The examples below roughly follows the README in the official Go client library.
Creating a database
This library assumes the lens
package in some APIs. Here we use ?~ to set the authentication
parameters of type Maybe .Credentials
Also note that in order to construct a Query, we use formatQuery with the
database formatter. There are many other formatters defined in
Database.InfluxDB.Format.
>>>let db = "square_holes">>>let bubba = credentials "bubba" "bumblebeetuna">>>let p = queryParams db & authentication ?~ bubba>>>manage p $ formatQuery ("DROP DATABASE "%F.database) db>>>manage p $ formatQuery ("CREATE DATABASE "%F.database) db
Writing data
write or writeBatch can be used to write data. In general writeBatch
should be used for efficiency when writing multiple data points.
>>>let wp = writeParams db & authentication ?~ bubba & precision .~ Second>>>let cpuUsage = "cpu_usage">>>:{writeBatch wp [ Line cpuUsage (Map.singleton "cpu" "cpu-total") (Map.fromList [ ("idle", FieldFloat 10.1) , ("system", FieldFloat 53.3) , ("user", FieldFloat 46.6) ]) (Just $ parseTimeOrError False defaultTimeLocale "%F %T%Q %Z" "2017-06-17 15:41:40.42659044 UTC") :: Line UTCTime ] :}
Note that the type signature of the timestamp is necessary. Otherwise it doesn't type check.
Querying data
Using an one-off tuple
If all the field types are an instance of FromJSON, we can use a tuple to store
the results.
>>>:set -XDataKinds -XOverloadedStrings>>>type CPUUsage = (Tagged "time" UTCTime, Tagged "idle" Double, Tagged "system" Double, Tagged "user" Double)>>>v <- query p $ formatQuery ("SELECT * FROM "%F.measurement) cpuUsage :: IO (V.Vector CPUUsage)>>>v[(Tagged 2017-06-17 15:41:40 UTC,Tagged 10.1,Tagged 53.3,Tagged 46.6)]
Note that the type signature on query here is also necessary to type check.
We can remove the tags using untag:
>>>V.map (\(a, b, c, d) -> (untag a, untag b, untag c, untag d)) v :: V.Vector (UTCTime, Double, Double, Double)[(2017-06-17 15:41:40 UTC,10.1,53.3,46.6)]
Or even using coerce:
>>>import Data.Coerce>>>coerce v :: V.Vector (UTCTime, Double, Double, Double)[(2017-06-17 15:41:40 UTC,10.1,53.3,46.6)]
Using a custom data type
We can define our custom data type and write a QueryResults instance
instead. getField, parseUTCTime and parseJSON etc are avilable to
make it easier to write a JSON decoder.
>>>:{data CPUUsage = CPUUsage { time :: UTCTime , cpuIdle, cpuSystem, cpuUser :: Double } deriving Show instance QueryResults CPUUsage where parseResults prec = parseResultsWithDecoder strictDecoder $ \_ _ columns fields -> do time <- getField "time" columns fields >>= parseUTCTime prec cpuIdle <- getField "idle" columns fields >>= parseJSON cpuSystem <- getField "system" columns fields >>= parseJSON cpuUser <- getField "user" columns fields >>= parseJSON return CPUUsage {..} :}
>>>query p $ formatQuery ("SELECT * FROM "%F.measurement) cpuUsage :: IO (V.Vector CPUUsage)[CPUUsage {time = 2017-06-17 15:41:40 UTC, cpuIdle = 10.1, cpuSystem = 53.3, cpuUser = 46.6}]
Writing data via HTTP
InfluxDB has two ways to write data into it, via HTTP and UDP. This module only exports functions for the HTTP API. For UDP, you can use a qualified import:
import qualified Database.InfluxDB.Write.UDP as UDP
write :: Timestamp time => WriteParams -> Line time -> IO () Source #
Write a Line.
>>>let p = writeParams "test-db">>>write p $ Line "room_temp" Map.empty (Map.fromList [("temp", FieldFloat 25.0)]) (Nothing :: Maybe UTCTime)
writeBatch :: (Timestamp time, Foldable f) => WriteParams -> f (Line time) -> IO () Source #
Write multiple Lines in a batch.
This is more efficient than calling write multiple times.
>>>let p = writeParams "test-db">>>:{writeBatch p [ Line "temp" (Map.singleton "city" "tokyo") (Map.fromList [("temp", FieldFloat 25.0)]) (Nothing :: Maybe UTCTime) , Line "temp" (Map.singleton "city" "osaka") (Map.fromList [("temp", FieldFloat 25.2)]) (Nothing :: Maybe UTCTime) ] :}
writeByteString :: WriteParams -> ByteString -> IO () Source #
Write a raw ByteString
Write parameters
data WriteParams Source #
The full set of parameters for the HTTP writer.
Instances
| HasCredentials WriteParams Source # | Authentication info for the write 
 | 
| Defined in Database.InfluxDB.Write Methods authentication :: Lens' WriteParams (Maybe Credentials) Source # | |
| HasManager WriteParams Source # | 
 | 
| Defined in Database.InfluxDB.Write Methods manager :: Lens' WriteParams (Either ManagerSettings Manager) Source # | |
| HasDatabase WriteParams Source # | 
 | 
| Defined in Database.InfluxDB.Write | |
| HasServer WriteParams Source # | 
 | 
| Defined in Database.InfluxDB.Write | |
| HasPrecision WriteRequest WriteParams Source # | 
 | 
| Defined in Database.InfluxDB.Write Methods precision :: Lens' WriteParams (Precision WriteRequest) Source # | |
writeParams :: Database -> WriteParams Source #
Smart constructor for WriteParams
Default parameters:
retentionPolicy :: Lens' WriteParams (Maybe Key) Source #
Target retention policy for the write.
InfluxDB writes to the default retention policy if this parameter is set
 to Nothing.
>>>let p = writeParams "foo" & retentionPolicy .~ Just "two_hours">>>p ^. retentionPolicyJust "two_hours"
The Line protocol
Placeholder for the Line Protocol
See https://docs.influxdata.com/influxdb/v1.5/write_protocols/line_protocol_tutorial/ for the concrete syntax.
measurement :: Lens' (Line time) Measurement Source #
Name of the measurement that you want to write your data to.
tagSet :: Lens' (Line time) (Map Key Key) Source #
Tag(s) that you want to include with your data point. Tags are optional in
 the Line Protocol, so you can set it empty.
fieldSet :: Lens' (Line time) (Map Key LineField) Source #
Field(s) for your data point. Every data point requires at least one field
 in the Line Protocol, so it shouldn't be empty.
timestamp :: Lens' (Line time) (Maybe time) Source #
Timestamp for your data point. You can put whatever type of timestamp that
 is an instance of the Timestamp class.
data Field (n :: Nullability) where Source #
Constructors
| FieldInt :: !Int64 -> Field n | |
| FieldFloat :: !Double -> Field n | |
| FieldString :: !Text -> Field n | |
| FieldBool :: !Bool -> Field n | |
| FieldNull :: Field Nullable | 
type LineField = Field NonNullable Source #
Field type for the line protocol. The line protocol doesn't accept null values.
type QueryField = Field Nullable Source #
Field type for queries. Queries can contain null values.
class Timestamp time where Source #
A Timestamp is something that can be converted to a valid
 InfluxDB timestamp, which is represented as a 64-bit integer.
Methods
roundTo :: Precision WriteRequest -> time -> Int64 Source #
Round a time to the given precision and scale it to nanoseconds
scaleTo :: Precision WriteRequest -> time -> Int64 Source #
Scale a time to the given precision
Instances
| Timestamp UTCTime Source # | 
 | 
| Defined in Database.InfluxDB.Types | |
| Timestamp TimeSpec Source # | 
 | 
| Defined in Database.InfluxDB.Types | |
| Timestamp NominalDiffTime Source # | 
 | 
| Defined in Database.InfluxDB.Types Methods roundTo :: Precision WriteRequest -> NominalDiffTime -> Int64 Source # scaleTo :: Precision WriteRequest -> NominalDiffTime -> Int64 Source # | |
precisionScale :: Fractional a => Precision ty -> a Source #
Scale of the type precision.
>>>precisionScale RFC33391.0e-9>>>precisionScale Microsecond1.0e-6
precisionName :: Precision ty -> Text Source #
Name of the time precision.
>>>precisionName Nanosecond"n"
Querying data
query and queryChunked can be used to query data. If your dataset fits your
memory, query is easier to use. If it doesn't, use queryChunked to stream
data.
An InfluxDB query.
A spec of the format is available at https://docs.influxdata.com/influxdb/v1.5/query_language/spec/.
A Query can be constructed using either
- the IsStringinstance with-XOverloadedStrings
- or formatQuery.
>>>:set -XOverloadedStrings>>>"SELECT * FROM series" :: Query"SELECT * FROM series">>>import qualified Database.InfluxDB.Format as F>>>formatQuery ("SELECT * FROM "%F.key) "series""SELECT * FROM \"series\""
NOTE: Currently this library doesn't support type-safe query construction.
query :: QueryResults a => QueryParams -> Query -> IO (Vector a) Source #
Query data from InfluxDB.
It may throw InfluxException.
If you need a lower-level interface (e.g. to bypass the QueryResults
 constraint etc), see withQueryResponse.
Arguments
| :: QueryResults a | |
| => QueryParams | |
| -> Optional Int | Chunk size By  | 
| -> Query | |
| -> FoldM IO (Vector a) r | |
| -> IO r | 
Same as query but it instructs InfluxDB to stream chunked responses
 rather than returning a huge JSON object. This can be lot more efficient than
 query if the result is huge.
It may throw InfluxException.
If you need a lower-level interface (e.g. to bypass the QueryResults
 constraint etc), see withQueryResponse.
Query construction
There are various utility functions available in Database.InfluxDB.Format. This module is designed to be imported as qualified:
import Database.InfluxDB import qualified Database.InfluxDB.Format as F
formatQuery :: Format Query r -> r Source #
Format a Query.
>>>formatQuery "SELECT * FROM series""SELECT * FROM series">>>formatQuery ("SELECT * FROM "%key) "series""SELECT * FROM \"series\""
Query parameters
data QueryParams Source #
The full set of parameters for the query API
Instances
| HasCredentials QueryParams Source # | Authentication info for the query 
 | 
| Defined in Database.InfluxDB.Query Methods authentication :: Lens' QueryParams (Maybe Credentials) Source # | |
| HasManager QueryParams Source # | 
 | 
| Defined in Database.InfluxDB.Query Methods manager :: Lens' QueryParams (Either ManagerSettings Manager) Source # | |
| HasDatabase QueryParams Source # | 
 | 
| Defined in Database.InfluxDB.Query | |
| HasServer QueryParams Source # | 
 | 
| Defined in Database.InfluxDB.Query | |
| HasPrecision QueryRequest QueryParams Source # | Returning JSON responses contain timestamps in the specified precision/format. 
 | 
| Defined in Database.InfluxDB.Query Methods precision :: Lens' QueryParams (Precision QueryRequest) Source # | |
queryParams :: Database -> QueryParams Source #
Smart constructor for QueryParams
Default parameters:
authentication :: HasCredentials a => Lens' a (Maybe Credentials) Source #
User name and password to be used when sending requests to InfluxDB.
Parsing results
class QueryResults a where Source #
Types that can be converted from an JSON object returned by InfluxDB.
For example the h2o_feet series in
 the official document
 can be encoded as follows:
>>>:{data H2OFeet = H2OFeet { time :: UTCTime , levelDesc :: T.Text , location :: T.Text , waterLevel :: Double } instance QueryResults H2OFeet where parseResults prec = parseResultsWith $ \_ _ columns fields -> do time <- getField "time" columns fields >>= parseUTCTime prec levelDesc <- getField "level_description" columns fields >>= parseJSON location <- getField "location" columns fields >>= parseJSON waterLevel <- getField "water_level" columns fields >>= parseJSON return H2OFeet {..} :}
Minimal complete definition
Methods
parseResults :: Precision QueryRequest -> Value -> Parser (Vector a) Source #
Parse a JSON object as an array of values of expected type.
Instances
Arguments
| :: (Maybe Text -> HashMap Text Text -> Vector Text -> Array -> Parser a) | A parser that takes 
 to construct a value. | 
| -> Value | |
| -> Parser (Vector a) | 
Parse a JSON response with the lenientDecoder. This can be useful to
 implement the parseResults method.
parseResultsWithDecoder Source #
Arguments
| :: Decoder a | |
| -> (Maybe Text -> HashMap Text Text -> Vector Text -> Array -> Parser a) | A parser that takes 
 to construct a value. | 
| -> Value | |
| -> Parser (Vector a) | 
Parse a JSON response with the specified decoder settings.
Decoder settings
lenientDecoder :: Decoder a Source #
A decoder that ignores parse failures and returns only successful results.
strictDecoder :: Decoder a Source #
A decoder that fails immediately if there's any parse failure.
Get a field value from a column name
Get a tag value from a tag name
parseUTCTime :: Precision ty -> Value -> Parser UTCTime Source #
Parse either a POSIX timestamp or RFC3339 formatted timestamp as UTCTime.
parsePOSIXTime :: Precision ty -> Value -> Parser POSIXTime Source #
Parse either a POSIX timestamp or RFC3339 formatted timestamp as
 POSIXTime.
parseQueryField :: Value -> Parser QueryField Source #
Deprecated: This function parses numbers in a misleading way. Use parseJSON instead.
Parse a QueryField.
Re-exports from tagged
newtype Tagged (s :: k) b :: forall k. k -> * -> * #
A Tagged s bb with an attached phantom type s.
 This can be used in place of the more traditional but less safe idiom of
 passing in an undefined value with the type, because unlike an (s -> b),
 a Tagged s bs as a real value.
Moreover, you don't have to rely on the compiler to inline away the extra argument, because the newtype is "free"
Tagged has kind k -> * -> * if the compiler supports PolyKinds, therefore
 there is an extra k showing in the instance haddocks that may cause confusion.
Instances
| FunctorWithIndex () (Tagged a) | |
| FoldableWithIndex () (Tagged a) | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (() -> a0 -> m) -> Tagged a a0 -> m # ifolded :: (Indexable () p, Contravariant f, Applicative f) => p a0 (f a0) -> Tagged a a0 -> f (Tagged a a0) # ifoldr :: (() -> a0 -> b -> b) -> b -> Tagged a a0 -> b # ifoldl :: (() -> b -> a0 -> b) -> b -> Tagged a a0 -> b # | |
| TraversableWithIndex () (Tagged a) | |
| Defined in Control.Lens.Indexed Methods itraverse :: Applicative f => (() -> a0 -> f b) -> Tagged a a0 -> f (Tagged a b) # itraversed :: (Indexable () p, Applicative f) => p a0 (f b) -> Tagged a a0 -> f (Tagged a b) # | |
| ToJSON2 (Tagged :: * -> * -> *) | |
| Defined in Data.Aeson.Types.ToJSON Methods liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Tagged a b -> Value # liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Tagged a b] -> Value # liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Tagged a b -> Encoding # liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Tagged a b] -> Encoding # | |
| FromJSON2 (Tagged :: * -> * -> *) | |
| Defined in Data.Aeson.Types.FromJSON | |
| Bitraversable (Tagged :: * -> * -> *) | |
| Defined in Data.Tagged Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Tagged a b -> f (Tagged c d) # | |
| Bifoldable (Tagged :: * -> * -> *) | |
| Bifunctor (Tagged :: * -> * -> *) | |
| Eq2 (Tagged :: * -> * -> *) | |
| Ord2 (Tagged :: * -> * -> *) | |
| Defined in Data.Tagged | |
| Read2 (Tagged :: * -> * -> *) | |
| Defined in Data.Tagged Methods liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Tagged a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Tagged a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Tagged a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Tagged a b] # | |
| Show2 (Tagged :: * -> * -> *) | |
| Profunctor (Tagged :: * -> * -> *) | |
| Defined in Data.Profunctor.Unsafe | |
| Bitraversable1 (Tagged :: * -> * -> *) | |
| Defined in Data.Semigroup.Traversable.Class Methods bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Tagged a c -> f (Tagged b d) # bisequence1 :: Apply f => Tagged (f a) (f b) -> f (Tagged a b) # | |
| Corepresentable (Tagged :: * -> * -> *) | |
| Choice (Tagged :: * -> * -> *) | |
| Generic1 (Tagged s :: * -> *) | |
| Monad (Tagged s) | |
| Functor (Tagged s) | |
| Applicative (Tagged s) | |
| Foldable (Tagged s) | |
| Defined in Data.Tagged Methods fold :: Monoid m => Tagged s m -> m # foldMap :: Monoid m => (a -> m) -> Tagged s a -> m # foldr :: (a -> b -> b) -> b -> Tagged s a -> b # foldr' :: (a -> b -> b) -> b -> Tagged s a -> b # foldl :: (b -> a -> b) -> b -> Tagged s a -> b # foldl' :: (b -> a -> b) -> b -> Tagged s a -> b # foldr1 :: (a -> a -> a) -> Tagged s a -> a # foldl1 :: (a -> a -> a) -> Tagged s a -> a # elem :: Eq a => a -> Tagged s a -> Bool # maximum :: Ord a => Tagged s a -> a # minimum :: Ord a => Tagged s a -> a # | |
| Traversable (Tagged s) | |
| Representable (Tagged t) | |
| ToJSON1 (Tagged a) | |
| Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a0 -> Value) -> ([a0] -> Value) -> Tagged a a0 -> Value # liftToJSONList :: (a0 -> Value) -> ([a0] -> Value) -> [Tagged a a0] -> Value # liftToEncoding :: (a0 -> Encoding) -> ([a0] -> Encoding) -> Tagged a a0 -> Encoding # liftToEncodingList :: (a0 -> Encoding) -> ([a0] -> Encoding) -> [Tagged a a0] -> Encoding # | |
| FromJSON1 (Tagged a) | |
| Eq1 (Tagged s) | |
| Ord1 (Tagged s) | |
| Defined in Data.Tagged | |
| Read1 (Tagged s) | |
| Defined in Data.Tagged | |
| Show1 (Tagged s) | |
| Traversable1 (Tagged a) | |
| (KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2) => QueryResults (Tagged k1 v1, Tagged k2 v2) Source # | One-off tuple for sigle-field measurements | 
| Defined in Database.InfluxDB.Query Methods parseResults :: Precision QueryRequest -> Value -> Parser (Vector (Tagged k1 v1, Tagged k2 v2)) Source # | |
| Bounded b => Bounded (Tagged s b) | |
| Enum a => Enum (Tagged s a) | |
| Defined in Data.Tagged Methods succ :: Tagged s a -> Tagged s a # pred :: Tagged s a -> Tagged s a # fromEnum :: Tagged s a -> Int # enumFrom :: Tagged s a -> [Tagged s a] # enumFromThen :: Tagged s a -> Tagged s a -> [Tagged s a] # enumFromTo :: Tagged s a -> Tagged s a -> [Tagged s a] # enumFromThenTo :: Tagged s a -> Tagged s a -> Tagged s a -> [Tagged s a] # | |
| Eq b => Eq (Tagged s b) | |
| Floating a => Floating (Tagged s a) | |
| Defined in Data.Tagged Methods exp :: Tagged s a -> Tagged s a # log :: Tagged s a -> Tagged s a # sqrt :: Tagged s a -> Tagged s a # (**) :: Tagged s a -> Tagged s a -> Tagged s a # logBase :: Tagged s a -> Tagged s a -> Tagged s a # sin :: Tagged s a -> Tagged s a # cos :: Tagged s a -> Tagged s a # tan :: Tagged s a -> Tagged s a # asin :: Tagged s a -> Tagged s a # acos :: Tagged s a -> Tagged s a # atan :: Tagged s a -> Tagged s a # sinh :: Tagged s a -> Tagged s a # cosh :: Tagged s a -> Tagged s a # tanh :: Tagged s a -> Tagged s a # asinh :: Tagged s a -> Tagged s a # acosh :: Tagged s a -> Tagged s a # atanh :: Tagged s a -> Tagged s a # log1p :: Tagged s a -> Tagged s a # expm1 :: Tagged s a -> Tagged s a # | |
| Fractional a => Fractional (Tagged s a) | |
| Integral a => Integral (Tagged s a) | |
| Defined in Data.Tagged Methods quot :: Tagged s a -> Tagged s a -> Tagged s a # rem :: Tagged s a -> Tagged s a -> Tagged s a # div :: Tagged s a -> Tagged s a -> Tagged s a # mod :: Tagged s a -> Tagged s a -> Tagged s a # quotRem :: Tagged s a -> Tagged s a -> (Tagged s a, Tagged s a) # divMod :: Tagged s a -> Tagged s a -> (Tagged s a, Tagged s a) # | |
| (Data s, Data b) => Data (Tagged s b) | |
| Defined in Data.Tagged Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Tagged s b -> c (Tagged s b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tagged s b) # toConstr :: Tagged s b -> Constr # dataTypeOf :: Tagged s b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tagged s b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tagged s b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Tagged s b -> Tagged s b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tagged s b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tagged s b -> r # gmapQ :: (forall d. Data d => d -> u) -> Tagged s b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tagged s b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tagged s b -> m (Tagged s b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged s b -> m (Tagged s b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged s b -> m (Tagged s b) # | |
| Num a => Num (Tagged s a) | |
| Defined in Data.Tagged | |
| Ord b => Ord (Tagged s b) | |
| Read b => Read (Tagged s b) | |
| Real a => Real (Tagged s a) | |
| Defined in Data.Tagged Methods toRational :: Tagged s a -> Rational # | |
| RealFloat a => RealFloat (Tagged s a) | |
| Defined in Data.Tagged Methods floatRadix :: Tagged s a -> Integer # floatDigits :: Tagged s a -> Int # floatRange :: Tagged s a -> (Int, Int) # decodeFloat :: Tagged s a -> (Integer, Int) # encodeFloat :: Integer -> Int -> Tagged s a # exponent :: Tagged s a -> Int # significand :: Tagged s a -> Tagged s a # scaleFloat :: Int -> Tagged s a -> Tagged s a # isInfinite :: Tagged s a -> Bool # isDenormalized :: Tagged s a -> Bool # isNegativeZero :: Tagged s a -> Bool # | |
| RealFrac a => RealFrac (Tagged s a) | |
| Show b => Show (Tagged s b) | |
| Ix b => Ix (Tagged s b) | |
| Defined in Data.Tagged Methods range :: (Tagged s b, Tagged s b) -> [Tagged s b] # index :: (Tagged s b, Tagged s b) -> Tagged s b -> Int # unsafeIndex :: (Tagged s b, Tagged s b) -> Tagged s b -> Int inRange :: (Tagged s b, Tagged s b) -> Tagged s b -> Bool # rangeSize :: (Tagged s b, Tagged s b) -> Int # unsafeRangeSize :: (Tagged s b, Tagged s b) -> Int | |
| IsString a => IsString (Tagged s a) | |
| Defined in Data.Tagged Methods fromString :: String -> Tagged s a # | |
| Generic (Tagged s b) | |
| Semigroup a => Semigroup (Tagged s a) | |
| (Semigroup a, Monoid a) => Monoid (Tagged s a) | |
| ToJSON b => ToJSON (Tagged a b) | |
| Defined in Data.Aeson.Types.ToJSON | |
| ToJSONKey b => ToJSONKey (Tagged a b) | |
| Defined in Data.Aeson.Types.ToJSON Methods toJSONKey :: ToJSONKeyFunction (Tagged a b) # toJSONKeyList :: ToJSONKeyFunction [Tagged a b] # | |
| FromJSON b => FromJSON (Tagged a b) | |
| FromJSONKey b => FromJSONKey (Tagged a b) | |
| Defined in Data.Aeson.Types.FromJSON Methods fromJSONKey :: FromJSONKeyFunction (Tagged a b) # fromJSONKeyList :: FromJSONKeyFunction [Tagged a b] # | |
| Storable a => Storable (Tagged s a) | |
| Defined in Data.Tagged Methods alignment :: Tagged s a -> Int # peekElemOff :: Ptr (Tagged s a) -> Int -> IO (Tagged s a) # pokeElemOff :: Ptr (Tagged s a) -> Int -> Tagged s a -> IO () # peekByteOff :: Ptr b -> Int -> IO (Tagged s a) # pokeByteOff :: Ptr b -> Int -> Tagged s a -> IO () # | |
| Bits a => Bits (Tagged s a) | |
| Defined in Data.Tagged Methods (.&.) :: Tagged s a -> Tagged s a -> Tagged s a # (.|.) :: Tagged s a -> Tagged s a -> Tagged s a # xor :: Tagged s a -> Tagged s a -> Tagged s a # complement :: Tagged s a -> Tagged s a # shift :: Tagged s a -> Int -> Tagged s a # rotate :: Tagged s a -> Int -> Tagged s a # setBit :: Tagged s a -> Int -> Tagged s a # clearBit :: Tagged s a -> Int -> Tagged s a # complementBit :: Tagged s a -> Int -> Tagged s a # testBit :: Tagged s a -> Int -> Bool # bitSizeMaybe :: Tagged s a -> Maybe Int # bitSize :: Tagged s a -> Int # isSigned :: Tagged s a -> Bool # shiftL :: Tagged s a -> Int -> Tagged s a # unsafeShiftL :: Tagged s a -> Int -> Tagged s a # shiftR :: Tagged s a -> Int -> Tagged s a # unsafeShiftR :: Tagged s a -> Int -> Tagged s a # rotateL :: Tagged s a -> Int -> Tagged s a # | |
| FiniteBits a => FiniteBits (Tagged s a) | |
| Defined in Data.Tagged Methods finiteBitSize :: Tagged s a -> Int # countLeadingZeros :: Tagged s a -> Int # countTrailingZeros :: Tagged s a -> Int # | |
| NFData b => NFData (Tagged s b) | |
| Defined in Data.Tagged | |
| Wrapped (Tagged s a) | |
| (KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3) => QueryResults (Tagged k1 v1, Tagged k2 v2, Tagged k3 v3) Source # | One-off tuple for two-field measurements | 
| Defined in Database.InfluxDB.Query | |
| (KnownSymbol k, FromJSON v) => QueryResults (Tagged k v) Source # | One-off type for non-timestamped measurements 
 | 
| Defined in Database.InfluxDB.Query Methods parseResults :: Precision QueryRequest -> Value -> Parser (Vector (Tagged k v)) Source # | |
| t ~ Tagged s' a' => Rewrapped (Tagged s a) t | |
| Defined in Control.Lens.Wrapped | |
| (KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4) => QueryResults (Tagged k1 v1, Tagged k2 v2, Tagged k3 v3, Tagged k4 v4) Source # | One-off tuple for three-field measurements | 
| Defined in Database.InfluxDB.Query | |
| (KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5) => QueryResults (Tagged k1 v1, Tagged k2 v2, Tagged k3 v3, Tagged k4 v4, Tagged k5 v5) Source # | One-off tuple for four-field measurements | 
| Defined in Database.InfluxDB.Query | |
| (KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5, KnownSymbol k6, FromJSON v6) => QueryResults (Tagged k1 v1, Tagged k2 v2, Tagged k3 v3, Tagged k4 v4, Tagged k5 v5, Tagged k6 v6) Source # | One-off tuple for five-field measurements | 
| Defined in Database.InfluxDB.Query | |
| (KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5, KnownSymbol k6, FromJSON v6, KnownSymbol k7, FromJSON v7) => QueryResults (Tagged k1 v1, Tagged k2 v2, Tagged k3 v3, Tagged k4 v4, Tagged k5 v5, Tagged k6 v6, Tagged k7 v7) Source # | One-off tuple for six-field measurement | 
| (KnownSymbol k1, FromJSON v1, KnownSymbol k2, FromJSON v2, KnownSymbol k3, FromJSON v3, KnownSymbol k4, FromJSON v4, KnownSymbol k5, FromJSON v5, KnownSymbol k6, FromJSON v6, KnownSymbol k7, FromJSON v7, KnownSymbol k8, FromJSON v8) => QueryResults (Tagged k1 v1, Tagged k2 v2, Tagged k3 v3, Tagged k4 v4, Tagged k5 v5, Tagged k6 v6, Tagged k7 v7, Tagged k8 v8) Source # | One-off tuple for seven-field measurements | 
| type Corep (Tagged :: * -> * -> *) | |
| type Rep1 (Tagged s :: * -> *) | |
| Defined in Data.Tagged | |
| type Rep (Tagged t) | |
| Defined in Data.Functor.Rep | |
| type Rep (Tagged s b) | |
| Defined in Data.Tagged | |
| type Unwrapped (Tagged s a) | |
| Defined in Control.Lens.Wrapped | |
Database management
manage :: QueryParams -> Query -> IO () Source #
Send a database management query to InfluxDB.
>>>let db = "manage-test">>>let p = queryParams db>>>manage p $ F.formatQuery ("CREATE DATABASE "%F.database) db
Common data types and classes
data Precision (ty :: RequestType) where Source #
Predefined set of time precision.
RFC3339 is only available for QueryRequests.
Constructors
| Nanosecond :: Precision ty | POSIX time in ns | 
| Microsecond :: Precision ty | POSIX time in μs | 
| Millisecond :: Precision ty | POSIX time in ms | 
| Second :: Precision ty | POSIX time in s | 
| Minute :: Precision ty | POSIX time in minutes | 
| Hour :: Precision ty | POSIX time in hours | 
| RFC3339 :: Precision QueryRequest | Nanosecond precision time in a human readable format, like
  | 
Database name.
formatDatabase can be used to construct a
 Database.
formatDatabase :: Format Database r -> r Source #
Format a Database.
>>>formatDatabase "test-db""test-db"
data Measurement Source #
String name that is used for measurements.
formatMeasurement can be used to construct a
 Measurement.
Instances
| Eq Measurement Source # | |
| Defined in Database.InfluxDB.Types | |
| Ord Measurement Source # | |
| Defined in Database.InfluxDB.Types Methods compare :: Measurement -> Measurement -> Ordering # (<) :: Measurement -> Measurement -> Bool # (<=) :: Measurement -> Measurement -> Bool # (>) :: Measurement -> Measurement -> Bool # (>=) :: Measurement -> Measurement -> Bool # max :: Measurement -> Measurement -> Measurement # min :: Measurement -> Measurement -> Measurement # | |
| Show Measurement Source # | |
| Defined in Database.InfluxDB.Types Methods showsPrec :: Int -> Measurement -> ShowS # show :: Measurement -> String # showList :: [Measurement] -> ShowS # | |
| IsString Measurement Source # | |
| Defined in Database.InfluxDB.Types Methods fromString :: String -> Measurement # | |
formatMeasurement :: Format Measurement r -> r Source #
Format a Measurement.
>>>formatMeasurement "test-series""test-series"
String type that is used for tag keys/values and field keys.
Instances
| Eq Server Source # | |
| Ord Server Source # | |
| Show Server Source # | |
| Generic Server Source # | |
| type Rep Server Source # | |
| Defined in Database.InfluxDB.Types type Rep Server = D1 (MetaData "Server" "Database.InfluxDB.Types" "influxdb-1.6.0.7-JQhSEyKMeUhLPmcsxdxKP5" False) (C1 (MetaCons "Server" PrefixI True) (S1 (MetaSel (Just "_host") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "_port") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_ssl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)))) | |
data Credentials Source #
User credentials
Instances
| Show Credentials Source # | |
| Defined in Database.InfluxDB.Types Methods showsPrec :: Int -> Credentials -> ShowS # show :: Credentials -> String # showList :: [Credentials] -> ShowS # | |
Arguments
| :: Text | User name | 
| -> Text | Password | 
| -> Credentials | 
user :: Lens' Credentials Text Source #
User name to access InfluxDB.
>>>let creds = credentials "john" "passw0rd">>>creds ^. user"john"
Exception
data InfluxException Source #
Exceptions used in this library.
In general, the library tries to convert exceptions from the dependent libraries to the following types of errors.
Constructors
| ServerError String | Server side error. You can expect to get a successful response once the issue is resolved on the server side. | 
| ClientError String Request | Client side error. You need to fix your query to get a successful response. | 
| UnexpectedResponse String Request ByteString | Received an unexpected response. The  This can happen e.g. when the response from InfluxDB is incompatible with what this library expects due to an upstream format change or when the JSON response doesn't have expected fields etc. | 
| HTTPException HttpException | HTTP communication error. Typical HTTP errors (4xx and 5xx) are covered by  | 
Instances
| Show InfluxException Source # | |
| Defined in Database.InfluxDB.Types Methods showsPrec :: Int -> InfluxException -> ShowS # show :: InfluxException -> String # showList :: [InfluxException] -> ShowS # | |
| Exception InfluxException Source # | |
| Defined in Database.InfluxDB.Types Methods toException :: InfluxException -> SomeException # | |
class HasServer a where Source #
Minimal complete definition
Instances
| HasServer PingParams Source # | 
 | 
| Defined in Database.InfluxDB.Ping | |
| HasServer QueryParams Source # | 
 | 
| Defined in Database.InfluxDB.Query | |
| HasServer WriteParams Source # | 
 | 
| Defined in Database.InfluxDB.Write | |
class HasDatabase a where Source #
Minimal complete definition
Instances
| HasDatabase QueryParams Source # | 
 | 
| Defined in Database.InfluxDB.Query | |
| HasDatabase ShowQuery Source # | 
 | 
| HasDatabase WriteParams Source # | 
 | 
| Defined in Database.InfluxDB.Write | |
class HasPrecision (ty :: RequestType) a | a -> ty where Source #
Minimal complete definition
Instances
| HasPrecision QueryRequest QueryParams Source # | Returning JSON responses contain timestamps in the specified precision/format. 
 | 
| Defined in Database.InfluxDB.Query Methods precision :: Lens' QueryParams (Precision QueryRequest) Source # | |
| HasPrecision WriteRequest WriteParams Source # | 
 | 
| Defined in Database.InfluxDB.Write Methods precision :: Lens' WriteParams (Precision WriteRequest) Source # | |
| HasPrecision WriteRequest WriteParams Source # | Timestamp precision. In the UDP API, all timestamps are sent in nanosecond but you can specify lower precision. The writer just rounds timestamps to the specified precision. | 
| Defined in Database.InfluxDB.Write.UDP Methods precision :: Lens' WriteParams (Precision WriteRequest) Source # | |
class HasManager a where Source #
Minimal complete definition
Methods
manager :: Lens' a (Either ManagerSettings Manager) Source #
HTTP manager settings or a manager itself.
If it's set to ManagerSettings, the library will create a Manager from
 the settings for you.
Instances
| HasManager PingParams Source # | 
 | 
| Defined in Database.InfluxDB.Ping Methods manager :: Lens' PingParams (Either ManagerSettings Manager) Source # | |
| HasManager QueryParams Source # | 
 | 
| Defined in Database.InfluxDB.Query Methods manager :: Lens' QueryParams (Either ManagerSettings Manager) Source # | |
| HasManager WriteParams Source # | 
 | 
| Defined in Database.InfluxDB.Write Methods manager :: Lens' WriteParams (Either ManagerSettings Manager) Source # | |