{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Graphics.Vega.VegaLite.Transform
( Operation(..)
, Window(..)
, WOperation(..)
, BinProperty(..)
, WindowProperty(..)
, ImputeProperty(..)
, ImMethod(..)
, aggregate_
, op_
, binned_
, impute_
, bin
, binProperty
, operationSpec
, windowTS
, joinAggregateTS
, imputeTS
) where
import qualified Data.Aeson as A
import qualified Data.Text as T
import Data.Aeson ((.=), object, toJSON)
import Data.Maybe (mapMaybe)
#if !(MIN_VERSION_base(4, 12, 0))
import Data.Monoid ((<>))
#endif
import Graphics.Vega.VegaLite.Data
( DataValue
, DataValues
, dataValueSpec
, dataValuesSpecs
)
import Graphics.Vega.VegaLite.Foundation
( FieldName
, SortField
, sortFieldSpec
, field_
, fromT
, allowNull
)
import Graphics.Vega.VegaLite.Specification
( VLSpec
, LabelledSpec
, TransformSpec(..)
, SelectionLabel
)
data Operation
= ArgMax (Maybe FieldName)
| ArgMin (Maybe FieldName)
| CI0
| CI1
| Count
| Distinct
| Max
| Mean
| Median
| Min
| Missing
| Product
| Q1
| Q3
| Stderr
| Stdev
| StdevP
| Sum
| Valid
| Variance
| VarianceP
operationSpec :: Operation -> VLSpec
operationSpec :: Operation -> VLSpec
operationSpec (ArgMax Maybe FieldName
Nothing) = VLSpec
"argmax"
operationSpec (ArgMax (Just FieldName
s)) = [Pair] -> VLSpec
object [FieldName
"argmax" FieldName -> FieldName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= FieldName
s]
operationSpec (ArgMin Maybe FieldName
Nothing) = VLSpec
"argmin"
operationSpec (ArgMin (Just FieldName
s)) = [Pair] -> VLSpec
object [FieldName
"argmin" FieldName -> FieldName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= FieldName
s]
operationSpec Operation
CI0 = VLSpec
"ci0"
operationSpec Operation
CI1 = VLSpec
"ci1"
operationSpec Operation
Count = VLSpec
"count"
operationSpec Operation
Distinct = VLSpec
"distinct"
operationSpec Operation
Max = VLSpec
"max"
operationSpec Operation
Mean = VLSpec
"mean"
operationSpec Operation
Median = VLSpec
"median"
operationSpec Operation
Min = VLSpec
"min"
operationSpec Operation
Missing = VLSpec
"missing"
operationSpec Operation
Product = VLSpec
"product"
operationSpec Operation
Q1 = VLSpec
"q1"
operationSpec Operation
Q3 = VLSpec
"q3"
operationSpec Operation
Stderr = VLSpec
"stderr"
operationSpec Operation
Stdev = VLSpec
"stdev"
operationSpec Operation
StdevP = VLSpec
"stdevp"
operationSpec Operation
Sum = VLSpec
"sum"
operationSpec Operation
Valid = VLSpec
"valid"
operationSpec Operation
Variance = VLSpec
"variance"
operationSpec Operation
VarianceP = VLSpec
"variancep"
aggregate_ :: Operation -> LabelledSpec
aggregate_ :: Operation -> Pair
aggregate_ Operation
op = FieldName
"aggregate" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Operation -> VLSpec
operationSpec Operation
op
op_ :: Operation -> LabelledSpec
op_ :: Operation -> Pair
op_ Operation
op = FieldName
"op" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Operation -> VLSpec
operationSpec Operation
op
data Window
= WAggregateOp Operation
| WOp WOperation
| WParam Int
| WField FieldName
windowFieldProperty :: Window -> LabelledSpec
windowFieldProperty :: Window -> Pair
windowFieldProperty (WAggregateOp Operation
op) = FieldName
"op" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Operation -> VLSpec
operationSpec Operation
op
windowFieldProperty (WOp WOperation
op) = FieldName
"op" FieldName -> FieldName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= WOperation -> FieldName
wOperationLabel WOperation
op
windowFieldProperty (WParam Int
n) = FieldName
"param" FieldName -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Int
n
windowFieldProperty (WField FieldName
f) = FieldName -> Pair
field_ FieldName
f
data WOperation
= RowNumber
| Rank
| DenseRank
| PercentRank
| CumeDist
| Ntile
| Lag
| Lead
| FirstValue
| LastValue
| NthValue
wOperationLabel :: WOperation -> T.Text
wOperationLabel :: WOperation -> FieldName
wOperationLabel WOperation
RowNumber = FieldName
"row_number"
wOperationLabel WOperation
Rank = FieldName
"rank"
wOperationLabel WOperation
DenseRank = FieldName
"dense_rank"
wOperationLabel WOperation
PercentRank = FieldName
"percent_rank"
wOperationLabel WOperation
CumeDist = FieldName
"cume_dist"
wOperationLabel WOperation
Ntile = FieldName
"ntile"
wOperationLabel WOperation
Lag = FieldName
"lag"
wOperationLabel WOperation
Lead = FieldName
"lead"
wOperationLabel WOperation
FirstValue = FieldName
"first_value"
wOperationLabel WOperation
LastValue = FieldName
"last_value"
wOperationLabel WOperation
NthValue = FieldName
"nth_value"
data BinProperty
= AlreadyBinned Bool
| BinAnchor Double
| Base Double
| Divide [Double]
| Extent Double Double
| MaxBins Int
| MinStep Double
| Nice Bool
| SelectionExtent SelectionLabel
| Step Double
| Steps [Double]
binProperty :: BinProperty -> LabelledSpec
binProperty :: BinProperty -> Pair
binProperty (AlreadyBinned Bool
b) = FieldName
"binned" FieldName -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Bool
b
binProperty (BinAnchor Double
x) = FieldName
"anchor" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
x
binProperty (Base Double
x) = FieldName
"base" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
x
binProperty (Divide [Double]
xs) = FieldName
"divide" FieldName -> [Double] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= [Double]
xs
binProperty (Extent Double
mn Double
mx) = FieldName
"extent" FieldName -> [Double] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= [ Double
mn, Double
mx ]
binProperty (SelectionExtent FieldName
s) = FieldName
"extent" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= [Pair] -> VLSpec
object [ FieldName
"selection" FieldName -> FieldName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= FieldName
s ]
binProperty (MaxBins Int
n) = FieldName
"maxbins" FieldName -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Int
n
binProperty (MinStep Double
x) = FieldName
"minstep" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
x
binProperty (Nice Bool
b) = FieldName
"nice" FieldName -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Bool
b
binProperty (Step Double
x) = FieldName
"step" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
x
binProperty (Steps [Double]
xs) = FieldName
"steps" FieldName -> [Double] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= [Double]
xs
bin :: [BinProperty] -> LabelledSpec
bin :: [BinProperty] -> Pair
bin [] = FieldName
"bin" FieldName -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Bool
True
bin [BinProperty]
xs = FieldName
"bin" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= [Pair] -> VLSpec
object ((BinProperty -> Pair) -> [BinProperty] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map BinProperty -> Pair
binProperty [BinProperty]
xs)
binned_ :: LabelledSpec
binned_ :: Pair
binned_ = FieldName
"bin" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= FieldName -> VLSpec
fromT FieldName
"binned"
data WindowProperty
= WFrame (Maybe Int) (Maybe Int)
| WIgnorePeers Bool
| WGroupBy [FieldName]
| WSort [SortField]
wpFrame , wpIgnorePeers, wpGroupBy, wpSort :: WindowProperty -> Maybe VLSpec
wpFrame :: WindowProperty -> Maybe VLSpec
wpFrame (WFrame Maybe Int
m1 Maybe Int
m2) = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just ([VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Maybe Int -> VLSpec
allowNull Maybe Int
m1, Maybe Int -> VLSpec
allowNull Maybe Int
m2])
wpFrame WindowProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
wpIgnorePeers :: WindowProperty -> Maybe VLSpec
wpIgnorePeers (WIgnorePeers Bool
b) = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just (Bool -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Bool
b)
wpIgnorePeers WindowProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
wpGroupBy :: WindowProperty -> Maybe VLSpec
wpGroupBy (WGroupBy [FieldName]
fs) = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just ([FieldName] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
fs)
wpGroupBy WindowProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
wpSort :: WindowProperty -> Maybe VLSpec
wpSort (WSort [SortField]
sfs) = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just ([VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON ((SortField -> VLSpec) -> [SortField] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map SortField -> VLSpec
sortFieldSpec [SortField]
sfs))
wpSort WindowProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
windowTS ::
[([Window], FieldName)]
-> [WindowProperty]
-> TransformSpec
windowTS :: [([Window], FieldName)] -> [WindowProperty] -> TransformSpec
windowTS [([Window], FieldName)]
wss [WindowProperty]
wps =
let addField :: FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
n WindowProperty -> Maybe v
a = case (WindowProperty -> Maybe v) -> [WindowProperty] -> [v]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe WindowProperty -> Maybe v
a [WindowProperty]
wps of
[v
x] -> [FieldName
n FieldName -> v -> a
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= v
x]
[v]
_ -> []
winFieldDef :: ([Window], v) -> VLSpec
winFieldDef ([Window]
ws, v
out) = [Pair] -> VLSpec
object (FieldName
"as" FieldName -> v -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= v
out Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: (Window -> Pair) -> [Window] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map Window -> Pair
windowFieldProperty [Window]
ws)
fields :: [Pair]
fields = [ FieldName
"window" FieldName -> [VLSpec] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= (([Window], FieldName) -> VLSpec)
-> [([Window], FieldName)] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map ([Window], FieldName) -> VLSpec
forall v. ToJSON v => ([Window], v) -> VLSpec
winFieldDef [([Window], FieldName)]
wss ]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (WindowProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
"frame" WindowProperty -> Maybe VLSpec
wpFrame
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (WindowProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
"ignorePeers" WindowProperty -> Maybe VLSpec
wpIgnorePeers
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (WindowProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
"groupby" WindowProperty -> Maybe VLSpec
wpGroupBy
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (WindowProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
"sort" WindowProperty -> Maybe VLSpec
wpSort
in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
fields)
joinAggregateTS :: [VLSpec] -> [WindowProperty] -> TransformSpec
joinAggregateTS :: [VLSpec] -> [WindowProperty] -> TransformSpec
joinAggregateTS [VLSpec]
ops [WindowProperty]
wps =
let addField :: FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
n WindowProperty -> Maybe v
a = case (WindowProperty -> Maybe v) -> [WindowProperty] -> [v]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe WindowProperty -> Maybe v
a [WindowProperty]
wps of
[v
x] -> [FieldName
n FieldName -> v -> a
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= v
x]
[v]
_ -> []
fields :: [Pair]
fields = [ FieldName
"joinaggregate" FieldName -> [VLSpec] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= [VLSpec]
ops ]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (WindowProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
"frame" WindowProperty -> Maybe VLSpec
wpFrame
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (WindowProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
"ignorePeers" WindowProperty -> Maybe VLSpec
wpIgnorePeers
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (WindowProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
"groupby" WindowProperty -> Maybe VLSpec
wpGroupBy
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (WindowProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (WindowProperty -> Maybe v) -> [a]
addField FieldName
"sort" WindowProperty -> Maybe VLSpec
wpSort
in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
fields)
data ImputeProperty
= ImFrame (Maybe Int) (Maybe Int)
| ImKeyVals DataValues
| ImKeyValSequence Double Double Double
| ImMethod ImMethod
| ImGroupBy [FieldName]
| ImNewValue DataValue
imputeProperty :: ImputeProperty -> LabelledSpec
imputeProperty :: ImputeProperty -> Pair
imputeProperty (ImFrame Maybe Int
m1 Maybe Int
m2) = FieldName
"frame" FieldName -> [VLSpec] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= (Maybe Int -> VLSpec) -> [Maybe Int] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map Maybe Int -> VLSpec
allowNull [Maybe Int
m1, Maybe Int
m2]
imputeProperty (ImKeyVals DataValues
dVals) = FieldName
"keyvals" FieldName -> [VLSpec] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= DataValues -> [VLSpec]
dataValuesSpecs DataValues
dVals
imputeProperty (ImKeyValSequence Double
start Double
stop Double
step) =
FieldName
"keyvals" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= [Pair] -> VLSpec
object [FieldName
"start" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
start, FieldName
"stop" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
stop, FieldName
"step" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
step]
imputeProperty (ImMethod ImMethod
method) = FieldName
"method" FieldName -> FieldName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= ImMethod -> FieldName
imMethodLabel ImMethod
method
imputeProperty (ImNewValue DataValue
dVal) = FieldName
"value" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= DataValue -> VLSpec
dataValueSpec DataValue
dVal
imputeProperty (ImGroupBy [FieldName]
_) = FieldName
"groupby" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= VLSpec
A.Null
imputePropertySpecFrame, imputePropertySpecKeyVals,
imputePropertySpecKeyValSequence, imputePropertySpecGroupBy,
imputePropertySpecMethod, imputePropertySpecValue :: ImputeProperty -> Maybe VLSpec
imputePropertySpecFrame :: ImputeProperty -> Maybe VLSpec
imputePropertySpecFrame (ImFrame Maybe Int
m1 Maybe Int
m2) = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just ([VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON ((Maybe Int -> VLSpec) -> [Maybe Int] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map Maybe Int -> VLSpec
allowNull [Maybe Int
m1, Maybe Int
m2]))
imputePropertySpecFrame ImputeProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
imputePropertySpecKeyVals :: ImputeProperty -> Maybe VLSpec
imputePropertySpecKeyVals (ImKeyVals DataValues
dVals) = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just ([VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON (DataValues -> [VLSpec]
dataValuesSpecs DataValues
dVals))
imputePropertySpecKeyVals ImputeProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
imputePropertySpecKeyValSequence :: ImputeProperty -> Maybe VLSpec
imputePropertySpecKeyValSequence (ImKeyValSequence Double
start Double
stop Double
step) =
let obj :: [Pair]
obj = [FieldName
"start" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
start, FieldName
"stop" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
stop, FieldName
"step" FieldName -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= Double
step]
in VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just ([Pair] -> VLSpec
object [Pair]
obj)
imputePropertySpecKeyValSequence ImputeProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
imputePropertySpecGroupBy :: ImputeProperty -> Maybe VLSpec
imputePropertySpecGroupBy (ImGroupBy [FieldName]
fields) = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just ([FieldName] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
fields)
imputePropertySpecGroupBy ImputeProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
imputePropertySpecMethod :: ImputeProperty -> Maybe VLSpec
imputePropertySpecMethod (ImMethod ImMethod
method) = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just (FieldName -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON (ImMethod -> FieldName
imMethodLabel ImMethod
method))
imputePropertySpecMethod ImputeProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
imputePropertySpecValue :: ImputeProperty -> Maybe VLSpec
imputePropertySpecValue (ImNewValue DataValue
dVal) = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just (DataValue -> VLSpec
dataValueSpec DataValue
dVal)
imputePropertySpecValue ImputeProperty
_ = Maybe VLSpec
forall a. Maybe a
Nothing
impute_ :: [ImputeProperty] -> LabelledSpec
impute_ :: [ImputeProperty] -> Pair
impute_ [ImputeProperty]
ips = FieldName
"impute" FieldName -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= [Pair] -> VLSpec
object ((ImputeProperty -> Pair) -> [ImputeProperty] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map ImputeProperty -> Pair
imputeProperty [ImputeProperty]
ips)
imputeTS ::
FieldName
-> FieldName
-> [ImputeProperty]
-> TransformSpec
imputeTS :: FieldName -> FieldName -> [ImputeProperty] -> TransformSpec
imputeTS FieldName
field FieldName
key [ImputeProperty]
imProps =
let addField :: FieldName -> (ImputeProperty -> Maybe v) -> [a]
addField FieldName
n ImputeProperty -> Maybe v
a = case (ImputeProperty -> Maybe v) -> [ImputeProperty] -> [v]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ImputeProperty -> Maybe v
a [ImputeProperty]
imProps of
[v
x] -> [FieldName
n FieldName -> v -> a
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= v
x]
[v]
_ -> []
fields :: [Pair]
fields = [ FieldName
"impute" FieldName -> FieldName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= FieldName
field
, FieldName
"key" FieldName -> FieldName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => FieldName -> v -> kv
.= FieldName
key ]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (ImputeProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (ImputeProperty -> Maybe v) -> [a]
addField FieldName
"frame" ImputeProperty -> Maybe VLSpec
imputePropertySpecFrame
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (ImputeProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (ImputeProperty -> Maybe v) -> [a]
addField FieldName
"keyvals" ImputeProperty -> Maybe VLSpec
imputePropertySpecKeyVals
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (ImputeProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (ImputeProperty -> Maybe v) -> [a]
addField FieldName
"keyvals" ImputeProperty -> Maybe VLSpec
imputePropertySpecKeyValSequence
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (ImputeProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (ImputeProperty -> Maybe v) -> [a]
addField FieldName
"method" ImputeProperty -> Maybe VLSpec
imputePropertySpecMethod
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (ImputeProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (ImputeProperty -> Maybe v) -> [a]
addField FieldName
"groupby" ImputeProperty -> Maybe VLSpec
imputePropertySpecGroupBy
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> FieldName -> (ImputeProperty -> Maybe VLSpec) -> [Pair]
forall a v.
(KeyValue a, ToJSON v) =>
FieldName -> (ImputeProperty -> Maybe v) -> [a]
addField FieldName
"value" ImputeProperty -> Maybe VLSpec
imputePropertySpecValue
in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
fields)
data ImMethod
= ImMin
| ImMax
| ImMean
| ImMedian
| ImValue
imMethodLabel :: ImMethod -> T.Text
imMethodLabel :: ImMethod -> FieldName
imMethodLabel ImMethod
ImMin = FieldName
"min"
imMethodLabel ImMethod
ImMax = FieldName
"max"
imMethodLabel ImMethod
ImMean = FieldName
"mean"
imMethodLabel ImMethod
ImMedian = FieldName
"median"
imMethodLabel ImMethod
ImValue = FieldName
"value"