{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
module Database.InfluxDB.Line
(
Line(Line)
, measurement
, tagSet
, fieldSet
, timestamp
, buildLine
, buildLines
, encodeLine
, encodeLines
, LineField
, Field(..)
, Precision(..)
) where
import Data.List (intersperse)
import Data.Int (Int64)
import Data.Monoid
import Prelude
import Control.Lens
import Data.Map (Map)
import Data.Text (Text)
import qualified Data.ByteString.Builder as B
import qualified Data.ByteString.Lazy as L
import qualified Data.Map.Strict as Map
import qualified Data.Text.Encoding as TE
import Database.InfluxDB.Internal.Text
import Database.InfluxDB.Types
data Line time = Line
{ forall time. Line time -> Measurement
_measurement :: !Measurement
, forall time. Line time -> Map Key Key
_tagSet :: !(Map Key Key)
, forall time. Line time -> Map Key LineField
_fieldSet :: !(Map Key LineField)
, forall time. Line time -> Maybe time
_timestamp :: !(Maybe time)
} deriving Int -> Line time -> ShowS
forall time. Show time => Int -> Line time -> ShowS
forall time. Show time => [Line time] -> ShowS
forall time. Show time => Line time -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Line time] -> ShowS
$cshowList :: forall time. Show time => [Line time] -> ShowS
show :: Line time -> String
$cshow :: forall time. Show time => Line time -> String
showsPrec :: Int -> Line time -> ShowS
$cshowsPrec :: forall time. Show time => Int -> Line time -> ShowS
Show
encodeLine
:: (time -> Int64)
-> Line time
-> L.ByteString
encodeLine :: forall time. (time -> Int64) -> Line time -> ByteString
encodeLine time -> Int64
toTimestamp = Builder -> ByteString
B.toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall time. (time -> Int64) -> Line time -> Builder
buildLine time -> Int64
toTimestamp
encodeLines
:: Foldable f
=> (time -> Int64)
-> f (Line time)
-> L.ByteString
encodeLines :: forall (f :: * -> *) time.
Foldable f =>
(time -> Int64) -> f (Line time) -> ByteString
encodeLines time -> Int64
toTimestamp = Builder -> ByteString
B.toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) time.
Foldable f =>
(time -> Int64) -> f (Line time) -> Builder
buildLines time -> Int64
toTimestamp
buildLine
:: (time -> Int64)
-> Line time
-> B.Builder
buildLine :: forall time. (time -> Int64) -> Line time -> Builder
buildLine time -> Int64
toTimestamp Line {Maybe time
Map Key LineField
Map Key Key
Measurement
_timestamp :: Maybe time
_fieldSet :: Map Key LineField
_tagSet :: Map Key Key
_measurement :: Measurement
_timestamp :: forall time. Line time -> Maybe time
_fieldSet :: forall time. Line time -> Map Key LineField
_tagSet :: forall time. Line time -> Map Key Key
_measurement :: forall time. Line time -> Measurement
..} =
Builder
key forall a. Semigroup a => a -> a -> a
<> Builder
" " forall a. Semigroup a => a -> a -> a
<> Builder
fields forall a. Semigroup a => a -> a -> a
<> forall b a. b -> (a -> b) -> Maybe a -> b
maybe Builder
"" (Builder
" " forall a. Semigroup a => a -> a -> a
<>) Maybe Builder
timestamp
where
measurement :: Builder
measurement = Text -> Builder
TE.encodeUtf8Builder forall a b. (a -> b) -> a -> b
$ Measurement -> Text
escapeMeasurement Measurement
_measurement
tags :: Builder
tags = forall {t}. (t -> Builder) -> Map Key t -> Builder
buildMap (Text -> Builder
TE.encodeUtf8Builder forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Text
escapeKey) Map Key Key
_tagSet
key :: Builder
key = if forall k a. Map k a -> Bool
Map.null Map Key Key
_tagSet
then Builder
measurement
else Builder
measurement forall a. Semigroup a => a -> a -> a
<> Builder
"," forall a. Semigroup a => a -> a -> a
<> Builder
tags
fields :: Builder
fields = forall {t}. (t -> Builder) -> Map Key t -> Builder
buildMap LineField -> Builder
buildFieldValue Map Key LineField
_fieldSet
timestamp :: Maybe Builder
timestamp = Int64 -> Builder
B.int64Dec forall b c a. (b -> c) -> (a -> b) -> a -> c
. time -> Int64
toTimestamp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe time
_timestamp
buildMap :: (t -> Builder) -> Map Key t -> Builder
buildMap t -> Builder
encodeVal =
forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> [a] -> [a]
intersperse Builder
"," forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (Key, t) -> Builder
encodeKeyVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
Map.toList
where
encodeKeyVal :: (Key, t) -> Builder
encodeKeyVal (Key
name, t
val) = forall a. Monoid a => [a] -> a
mconcat
[ Text -> Builder
TE.encodeUtf8Builder forall a b. (a -> b) -> a -> b
$ Key -> Text
escapeKey Key
name
, Builder
"="
, t -> Builder
encodeVal t
val
]
escapeKey :: Key -> Text
escapeKey :: Key -> Text
escapeKey (Key Text
text) = Text -> Text
escapeCommas forall a b. (a -> b) -> a -> b
$ Text -> Text
escapeEqualSigns forall a b. (a -> b) -> a -> b
$ Text -> Text
escapeSpaces Text
text
escapeMeasurement :: Measurement -> Text
escapeMeasurement :: Measurement -> Text
escapeMeasurement (Measurement Text
text) = Text -> Text
escapeCommas forall a b. (a -> b) -> a -> b
$ Text -> Text
escapeSpaces Text
text
escapeStringField :: Text -> Text
escapeStringField :: Text -> Text
escapeStringField = Text -> Text
escapeDoubleQuotes forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
escapeBackslashes
buildFieldValue :: LineField -> B.Builder
buildFieldValue :: LineField -> Builder
buildFieldValue = \case
FieldInt Int64
i -> Int64 -> Builder
B.int64Dec Int64
i forall a. Semigroup a => a -> a -> a
<> Builder
"i"
FieldFloat Double
d -> Double -> Builder
B.doubleDec Double
d
FieldString Text
t -> Builder
"\"" forall a. Semigroup a => a -> a -> a
<> Text -> Builder
TE.encodeUtf8Builder (Text -> Text
escapeStringField Text
t) forall a. Semigroup a => a -> a -> a
<> Builder
"\""
FieldBool Bool
b -> if Bool
b then Builder
"true" else Builder
"false"
buildLines
:: Foldable f
=> (time -> Int64)
-> f (Line time)
-> B.Builder
buildLines :: forall (f :: * -> *) time.
Foldable f =>
(time -> Int64) -> f (Line time) -> Builder
buildLines time -> Int64
toTimestamp = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((forall a. Semigroup a => a -> a -> a
<> Builder
"\n") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall time. (time -> Int64) -> Line time -> Builder
buildLine time -> Int64
toTimestamp)
makeLensesWith (lensRules & generateSignatures .~ False) ''Line
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)