{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
module Graphics.Vega.VegaLite.Core
( transform
, aggregate
, joinAggregate
, opAs
, timeUnitAs
, binAs
, stack
, calculateAs
, filter
, Filter(..)
, FilterRange(..)
, flatten
, flattenAs
, fold
, foldAs
, pivot
, PivotProperty(..)
, lookup
, lookupSelection
, LookupFields(..)
, lookupAs
, impute
, sample
, density
, DensityProperty(..)
, loess
, LoessProperty(..)
, regression
, RegressionProperty(..)
, RegressionMethod(..)
, quantile
, QuantileProperty(..)
, window
, mark
, encoding
, position
, PositionChannel(..)
, SortProperty(..)
, AxisProperty(..)
, ConditionalAxisProperty(..)
, angle
, color
, fill
, fillOpacity
, opacity
, shape
, size
, stroke
, strokeDash
, strokeOpacity
, strokeWidth
, MarkChannel(..)
, text
, tooltip
, tooltips
, TextChannel(..)
, hyperlink
, url
, HyperlinkChannel(..)
, order
, OrderChannel(..)
, row
, column
, detail
, DetailChannel(..)
, ariaDescription
, AriaDescriptionChannel(..)
, ScaleProperty(..)
, categoricalDomainMap
, domainRangeMap
, layer
, vlConcat
, columns
, hConcat
, vConcat
, align
, alignRC
, spacing
, spacingRC
, center
, centerRC
, bounds
, resolve
, resolution
, repeat
, repeatFlow
, facet
, facetFlow
, FacetMapping(..)
, FacetChannel(..)
, BooleanOp(..)
, name
, description
, height
, heightOfContainer
, heightStep
, width
, widthOfContainer
, widthStep
, padding
, autosize
, background
, usermetadata
, viewBackground
, configure
, autosizeProperty
, axisProperty
, paddingSpec
, schemeProperty
)
where
import Prelude hiding (filter, lookup, repeat)
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 Numeric.Natural (Natural)
import Graphics.Vega.VegaLite.Data
( DataValue(..)
, DataValues(..)
, dataValueSpec
, dataValuesSpecs
)
import Graphics.Vega.VegaLite.Foundation
( Angle
, Color
, DashStyle
, DashOffset
, FieldName
, Opacity
, StyleLabel
, VegaExpr
, ZIndex
, FontWeight
, Measurement
, Arrangement
, APosition
, Position
, HAlign
, VAlign
, BandAlign
, Scale
, OverlapStrategy
, Side
, StackProperty
, StackOffset
, StrokeCap
, Channel
, Resolve
, Bounds
, CompositionAlignment
, Padding
, Autosize
, RepeatFields
, CInterpolate
, ViewBackground
, HeaderProperty
, Symbol
, fromT
, fromColor
, fromDS
, splitOnNewline
, field_
, header_
, order_
, fontWeightSpec
, measurementLabel
, arrangementLabel
, anchorLabel
, hAlignLabel
, vAlignLabel
, bandAlignLabel
, scaleLabel
, strokeCapLabel
, positionLabel
, overlapStrategyLabel
, sideLabel
, stackPropertySpecSort
, stackPropertySpecOffset
, stackOffset
, channelLabel
, resolveProperty
, boundsSpec
, compositionAlignmentSpec
, paddingSpec
, autosizeProperty
, repeatFieldsProperty
, cInterpolateSpec
, viewBackgroundSpec
, symbolLabel
)
import Graphics.Vega.VegaLite.Input
( Data
)
import Graphics.Vega.VegaLite.Legend
( LegendProperty
, legendProp_
)
import Graphics.Vega.VegaLite.Mark
( Mark
, MarkProperty
, markLabel
, markProperty
)
import Graphics.Vega.VegaLite.Scale
( ScaleDomain(..)
, DomainLimits(..)
, ScaleRange(..)
, ScaleNice
, scaleDomainProperty
, domainLimitsSpec
, scaleNiceSpec
)
import Graphics.Vega.VegaLite.Specification
( VLProperty(..)
, VLSpec
, PropertySpec
, LabelledSpec
, EncodingSpec(..)
, BuildEncodingSpecs
, TransformSpec(..)
, BuildTransformSpecs
, ConfigureSpec(..)
, ResolveSpec(..)
, BuildResolveSpecs
, SelectionLabel
)
import Graphics.Vega.VegaLite.Time
( DateTime
, TimeUnit
, dateTimeSpec
, timeUnitSpec
)
import Graphics.Vega.VegaLite.Transform
( Operation(Count)
, Window
, BinProperty
, WindowProperty
, ImputeProperty
, aggregate_
, op_
, binned_
, impute_
, bin
, binProperty
, operationSpec
, windowTS
, joinAggregateTS
, imputeTS
)
clamped ::
Double
-> Double
-> Double
-> Double
clamped :: Double -> Double -> Double -> Double
clamped Double
xmin Double
xmax Double
x = Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
xmin (Double -> Double -> Double
forall a. Ord a => a -> a -> a
min Double
xmax Double
x)
repeat_ :: Arrangement -> LabelledSpec
repeat_ :: Arrangement -> LabelledSpec
repeat_ Arrangement
arr = Text
"repeat" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Arrangement -> Text
arrangementLabel Arrangement
arr
sort_ :: [SortProperty] -> LabelledSpec
sort_ :: [SortProperty] -> LabelledSpec
sort_ [SortProperty]
ops = Text
"sort" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [SortProperty] -> VLSpec
sortPropertySpec [SortProperty]
ops
mchan_ :: T.Text -> [MarkChannel] -> EncodingSpec
mchan_ :: Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
f [MarkChannel]
ms = LabelledSpec -> EncodingSpec
ES (Text
f Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object ((MarkChannel -> [LabelledSpec]) -> [MarkChannel] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap MarkChannel -> [LabelledSpec]
markChannelProperty [MarkChannel]
ms))
mtype_ :: Measurement -> LabelledSpec
mtype_ :: Measurement -> LabelledSpec
mtype_ Measurement
m = Text
"type" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Measurement -> Text
measurementLabel Measurement
m
timeUnit_ :: TimeUnit -> LabelledSpec
timeUnit_ :: TimeUnit -> LabelledSpec
timeUnit_ TimeUnit
tu = Text
"timeUnit" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= TimeUnit -> VLSpec
timeUnitSpec TimeUnit
tu
scaleProp_ :: [ScaleProperty] -> LabelledSpec
scaleProp_ :: [ScaleProperty] -> LabelledSpec
scaleProp_ [] = Text
"scale" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null
scaleProp_ [ScaleProperty]
sps = Text
"scale" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object ((ScaleProperty -> LabelledSpec)
-> [ScaleProperty] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map ScaleProperty -> LabelledSpec
scaleProperty [ScaleProperty]
sps)
value_ :: T.Text -> LabelledSpec
value_ :: Text -> LabelledSpec
value_ Text
v = Text
"value" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
v
selCond_ :: (a -> [LabelledSpec]) -> BooleanOp -> [a] -> [a] -> [LabelledSpec]
selCond_ :: (a -> [LabelledSpec]) -> BooleanOp -> [a] -> [a] -> [LabelledSpec]
selCond_ a -> [LabelledSpec]
getProps BooleanOp
selName [a]
ifClause [a]
elseClause =
let h :: LabelledSpec
h = (Text
"condition", VLSpec
hkey)
toProps :: [a] -> [LabelledSpec]
toProps = (a -> [LabelledSpec]) -> [a] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap a -> [LabelledSpec]
getProps
hkey :: VLSpec
hkey = [LabelledSpec] -> VLSpec
object ((Text
"selection", BooleanOp -> VLSpec
booleanOpSpec BooleanOp
selName) LabelledSpec -> [LabelledSpec] -> [LabelledSpec]
forall a. a -> [a] -> [a]
: [a] -> [LabelledSpec]
toProps [a]
ifClause)
hs :: [LabelledSpec]
hs = [a] -> [LabelledSpec]
toProps [a]
elseClause
in LabelledSpec
h LabelledSpec -> [LabelledSpec] -> [LabelledSpec]
forall a. a -> [a] -> [a]
: [LabelledSpec]
hs
dataCond_ :: (a -> [LabelledSpec]) -> [(BooleanOp, [a])] -> [a] -> [LabelledSpec]
dataCond_ :: (a -> [LabelledSpec])
-> [(BooleanOp, [a])] -> [a] -> [LabelledSpec]
dataCond_ a -> [LabelledSpec]
getProps [(BooleanOp, [a])]
tests [a]
elseClause =
let h :: LabelledSpec
h = (Text
"condition", VLSpec
condClause)
condClause :: VLSpec
condClause = case [VLSpec]
conds of
[VLSpec
cond] -> VLSpec
cond
[VLSpec]
_ -> [VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
conds
conds :: [VLSpec]
conds = ((BooleanOp, [a]) -> VLSpec) -> [(BooleanOp, [a])] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map (BooleanOp, [a]) -> VLSpec
testClause [(BooleanOp, [a])]
tests
testClause :: (BooleanOp, [a]) -> VLSpec
testClause (Selection Text
sel, [a]
ifClause) =
[LabelledSpec] -> VLSpec
object ((Text
"selection" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
sel) LabelledSpec -> [LabelledSpec] -> [LabelledSpec]
forall a. a -> [a] -> [a]
: [a] -> [LabelledSpec]
toProps [a]
ifClause)
testClause (BooleanOp
predicate, [a]
ifClause) =
[LabelledSpec] -> VLSpec
object ((Text
"test", BooleanOp -> VLSpec
booleanOpSpec BooleanOp
predicate) LabelledSpec -> [LabelledSpec] -> [LabelledSpec]
forall a. a -> [a] -> [a]
: [a] -> [LabelledSpec]
toProps [a]
ifClause)
toProps :: [a] -> [LabelledSpec]
toProps = (a -> [LabelledSpec]) -> [a] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap a -> [LabelledSpec]
getProps
hs :: [LabelledSpec]
hs = [a] -> [LabelledSpec]
toProps [a]
elseClause
in LabelledSpec
h LabelledSpec -> [LabelledSpec] -> [LabelledSpec]
forall a. a -> [a] -> [a]
: [LabelledSpec]
hs
opAs ::
Operation
-> FieldName
-> FieldName
-> VLSpec
opAs :: Operation -> Text -> Text -> VLSpec
opAs Operation
Count Text
_ Text
label =
[LabelledSpec] -> VLSpec
object [ Operation -> LabelledSpec
op_ Operation
Count, Text
"as" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
label ]
opAs Operation
op Text
field Text
label =
[LabelledSpec] -> VLSpec
object [ Operation -> LabelledSpec
op_ Operation
op, Text -> LabelledSpec
field_ Text
field, Text
"as" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
label ]
mark :: Mark -> [MarkProperty] -> PropertySpec
mark :: Mark -> [MarkProperty] -> PropertySpec
mark Mark
mrk [MarkProperty]
props =
let jsName :: VLSpec
jsName = Text -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON (Mark -> Text
markLabel Mark
mrk)
vals :: VLSpec
vals = if [MarkProperty] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [MarkProperty]
props
then VLSpec
jsName
else [LabelledSpec] -> VLSpec
object ((Text
"type" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
jsName) LabelledSpec -> [LabelledSpec] -> [LabelledSpec]
forall a. a -> [a] -> [a]
: (MarkProperty -> LabelledSpec) -> [MarkProperty] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map MarkProperty -> LabelledSpec
markProperty [MarkProperty]
props)
in (VLProperty
VLMark, VLSpec
vals)
data MarkChannel
= MName FieldName
| MRepeat Arrangement
| MRepeatDatum Arrangement
| MmType Measurement
| MScale [ScaleProperty]
| MBin [BinProperty]
| MBinned
| MSort [SortProperty]
| MTimeUnit TimeUnit
| MTitle T.Text
| MNoTitle
| MAggregate Operation
| MLegend [LegendProperty]
| MSelectionCondition BooleanOp [MarkChannel] [MarkChannel]
| MDataCondition [(BooleanOp, [MarkChannel])] [MarkChannel]
| MPath T.Text
| MDatum DataValue
| MNumber Double
| MString T.Text
| MBoolean Bool
| MNullValue
| MSymbol Symbol
markChannelProperty :: MarkChannel -> [LabelledSpec]
markChannelProperty :: MarkChannel -> [LabelledSpec]
markChannelProperty (MName Text
s) = [Text -> LabelledSpec
field_ Text
s]
markChannelProperty (MRepeat Arrangement
arr) = [Text
"field" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr]]
markChannelProperty (MRepeatDatum Arrangement
arr) = [Text
"datum" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr]]
markChannelProperty (MmType Measurement
t) = [Measurement -> LabelledSpec
mtype_ Measurement
t]
markChannelProperty (MScale [ScaleProperty]
sps) = [[ScaleProperty] -> LabelledSpec
scaleProp_ [ScaleProperty]
sps]
markChannelProperty (MLegend [LegendProperty]
lps) = [[LegendProperty] -> LabelledSpec
legendProp_ [LegendProperty]
lps]
markChannelProperty (MBin [BinProperty]
bps) = [[BinProperty] -> LabelledSpec
bin [BinProperty]
bps]
markChannelProperty MarkChannel
MBinned = [LabelledSpec
binned_]
markChannelProperty (MSort [SortProperty]
ops) = [[SortProperty] -> LabelledSpec
sort_ [SortProperty]
ops]
markChannelProperty (MSelectionCondition BooleanOp
selName [MarkChannel]
ifClause [MarkChannel]
elseClause) =
(MarkChannel -> [LabelledSpec])
-> BooleanOp -> [MarkChannel] -> [MarkChannel] -> [LabelledSpec]
forall a.
(a -> [LabelledSpec]) -> BooleanOp -> [a] -> [a] -> [LabelledSpec]
selCond_ MarkChannel -> [LabelledSpec]
markChannelProperty BooleanOp
selName [MarkChannel]
ifClause [MarkChannel]
elseClause
markChannelProperty (MDataCondition [(BooleanOp, [MarkChannel])]
tests [MarkChannel]
elseClause) =
(MarkChannel -> [LabelledSpec])
-> [(BooleanOp, [MarkChannel])] -> [MarkChannel] -> [LabelledSpec]
forall a.
(a -> [LabelledSpec])
-> [(BooleanOp, [a])] -> [a] -> [LabelledSpec]
dataCond_ MarkChannel -> [LabelledSpec]
markChannelProperty [(BooleanOp, [MarkChannel])]
tests [MarkChannel]
elseClause
markChannelProperty (MTimeUnit TimeUnit
tu) = [TimeUnit -> LabelledSpec
timeUnit_ TimeUnit
tu]
markChannelProperty (MAggregate Operation
op) = [Operation -> LabelledSpec
aggregate_ Operation
op]
markChannelProperty (MPath Text
s) = [Text
"value" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s]
markChannelProperty (MDatum DataValue
d) = [Text
"datum" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= DataValue -> VLSpec
dataValueSpec DataValue
d]
markChannelProperty (MNumber Double
x) = [Text
"value" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x]
markChannelProperty (MString Text
s) = [Text
"value" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s]
markChannelProperty (MBoolean Bool
b) = [Text
"value" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b]
markChannelProperty (MSymbol Symbol
s) = [Text
"value" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Symbol -> Text
symbolLabel Symbol
s]
markChannelProperty MarkChannel
MNullValue = [Text
"value" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null]
markChannelProperty (MTitle Text
s) = [Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
splitOnNewline Text
s]
markChannelProperty MarkChannel
MNoTitle = [Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null]
encoding ::
[EncodingSpec]
-> PropertySpec
encoding :: [EncodingSpec] -> PropertySpec
encoding [EncodingSpec]
channels = (VLProperty
VLEncoding, [LabelledSpec] -> VLSpec
object ((EncodingSpec -> LabelledSpec) -> [EncodingSpec] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map EncodingSpec -> LabelledSpec
unES [EncodingSpec]
channels))
ariaDescription ::
[AriaDescriptionChannel]
-> BuildEncodingSpecs
ariaDescription :: [AriaDescriptionChannel] -> BuildEncodingSpecs
ariaDescription [AriaDescriptionChannel]
ads [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"description", [LabelledSpec] -> VLSpec
object ((AriaDescriptionChannel -> [LabelledSpec])
-> [AriaDescriptionChannel] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap AriaDescriptionChannel -> [LabelledSpec]
ariaDescriptionChannelProperty [AriaDescriptionChannel]
ads)) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
stack ::
FieldName
-> [FieldName]
-> FieldName
-> FieldName
-> [StackProperty]
-> BuildTransformSpecs
stack :: Text
-> [Text] -> Text -> Text -> [StackProperty] -> BuildTransformSpecs
stack Text
f [Text]
grp Text
start Text
end [StackProperty]
sProps [TransformSpec]
ols =
let addField :: Text -> [v] -> [a]
addField Text
n [v
x] = [Text
n Text -> v -> a
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= v
x]
addField Text
_ [v]
_ = []
mOffset :: [VLSpec]
mOffset = (StackProperty -> Maybe VLSpec) -> [StackProperty] -> [VLSpec]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe StackProperty -> Maybe VLSpec
stackPropertySpecOffset [StackProperty]
sProps
mSort :: [VLSpec]
mSort = (StackProperty -> Maybe VLSpec) -> [StackProperty] -> [VLSpec]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe StackProperty -> Maybe VLSpec
stackPropertySpecSort [StackProperty]
sProps
fields :: [LabelledSpec]
fields = [ Text
"stack" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
f
, Text
"groupby" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
grp
, Text
"as" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [ Text
start, Text
end ] ]
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> [VLSpec] -> [LabelledSpec]
forall a v. (KeyValue a, ToJSON v) => Text -> [v] -> [a]
addField Text
"offset" [VLSpec]
mOffset
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> [VLSpec] -> [LabelledSpec]
forall a v. (KeyValue a, ToJSON v) => Text -> [v] -> [a]
addField Text
"sort" [VLSpec]
mSort
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
fields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
data ScaleProperty
= SType Scale
| SAlign Double
| SBase Double
| SBins [Double]
| SClamp Bool
| SConstant Double
| SDomain DomainLimits
| SDomainMid Double
| SDomainOpt ScaleDomain
| SExponent Double
| SInterpolate CInterpolate
| SNice ScaleNice
| SPadding Double
| SPaddingInner Double
| SPaddingOuter Double
| SRange ScaleRange
| SReverse Bool
| SRound Bool
| SScheme T.Text [Double]
| SZero Bool
scaleProperty :: ScaleProperty -> LabelledSpec
scaleProperty :: ScaleProperty -> LabelledSpec
scaleProperty (SType Scale
sType) = Text
"type" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Scale -> Text
scaleLabel Scale
sType
scaleProperty (SAlign Double
c) = Text
"align" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double -> Double -> Double -> Double
clamped Double
0 Double
1 Double
c
scaleProperty (SBase Double
x) = Text
"base" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
scaleProperty (SBins [Double]
xs) = Text
"bins" Text -> [Double] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Double]
xs
scaleProperty (SClamp Bool
b) = Text
"clamp" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
scaleProperty (SConstant Double
x) = Text
"constant" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
scaleProperty (SDomain DomainLimits
dl) = Text
"domain" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= DomainLimits -> VLSpec
domainLimitsSpec DomainLimits
dl
scaleProperty (SDomainMid Double
x) = Text
"domainMid" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
scaleProperty (SDomainOpt ScaleDomain
sd) = ScaleDomain -> LabelledSpec
scaleDomainProperty ScaleDomain
sd
scaleProperty (SExponent Double
x) = Text
"exponent" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
scaleProperty (SInterpolate CInterpolate
interp) = Text
"interpolate" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= CInterpolate -> VLSpec
cInterpolateSpec CInterpolate
interp
scaleProperty (SNice ScaleNice
ni) = Text
"nice" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ScaleNice -> VLSpec
scaleNiceSpec ScaleNice
ni
scaleProperty (SPadding Double
x) = Text
"padding" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
scaleProperty (SPaddingInner Double
x) = Text
"paddingInner" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
scaleProperty (SPaddingOuter Double
x) = Text
"paddingOuter" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
scaleProperty (SRange (RField Text
f)) = Text
"range" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Text
"field" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
f]
scaleProperty (SRange (RMax Double
x)) = Text
"rangeMax" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
scaleProperty (SRange (RMin Double
x)) = Text
"rangeMin" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
scaleProperty (SRange (RPair Double
lo Double
hi)) = Text
"range" Text -> [Double] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Double
lo, Double
hi]
scaleProperty (SRange (RHeight Double
w)) = Text
"range" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text -> VLSpec
fromT Text
"height", Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
w]
scaleProperty (SRange (RWidth Double
h)) = Text
"range" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
h, Text -> VLSpec
fromT Text
"width"]
scaleProperty (SRange (RNumbers [Double]
xs)) = Text
"range" Text -> [Double] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Double]
xs
scaleProperty (SRange (RNumberLists [[Double]]
xss)) = Text
"range" Text -> [[Double]] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [[Double]]
xss
scaleProperty (SRange (RStrings [Text]
ss)) = Text
"range" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
ss
scaleProperty (SRange (RName Text
s)) = Text
"range" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s
scaleProperty (SReverse Bool
b) = Text
"reverse" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
scaleProperty (SRound Bool
b) = Text
"round" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
scaleProperty (SScheme Text
nme [Double]
extent) = Text -> [Double] -> LabelledSpec
schemeProperty Text
nme [Double]
extent
scaleProperty (SZero Bool
b) = Text
"zero" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
schemeProperty :: T.Text -> [Double] -> LabelledSpec
schemeProperty :: Text -> [Double] -> LabelledSpec
schemeProperty Text
nme [Double
n] = Text
"scheme" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Text
"name" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
nme, Text
"count" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
n]
schemeProperty Text
nme [Double
mn, Double
mx] = Text
"scheme" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Text
"name" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
nme, Text
"extent" Text -> [Double] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Double
mn, Double
mx]]
schemeProperty Text
nme [Double
n, Double
mn, Double
mx] = Text
"scheme" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Text
"name" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
nme, Text
"count" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
n, Text
"extent" Text -> [Double] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Double
mn, Double
mx]]
schemeProperty Text
nme [Double]
_ = Text
"scheme" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
nme
data SortProperty
= Ascending
| Descending
| CustomSort DataValues
| ByRepeatOp Arrangement Operation
| ByFieldOp FieldName Operation
| ByChannel Channel
sortProperty :: SortProperty -> [LabelledSpec]
sortProperty :: SortProperty -> [LabelledSpec]
sortProperty SortProperty
Ascending = [Text -> LabelledSpec
order_ Text
"ascending"]
sortProperty SortProperty
Descending = [Text -> LabelledSpec
order_ Text
"descending"]
sortProperty (ByChannel Channel
ch) = [Text
"encoding" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Channel -> Text
channelLabel Channel
ch]
sortProperty (ByFieldOp Text
field Operation
op) = [Text -> LabelledSpec
field_ Text
field, Operation -> LabelledSpec
op_ Operation
op]
sortProperty (ByRepeatOp Arrangement
arr Operation
op) = [Text
"field" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr], Operation -> LabelledSpec
op_ Operation
op]
sortProperty (CustomSort DataValues
_) = []
sortPropertySpec :: [SortProperty] -> VLSpec
sortPropertySpec :: [SortProperty] -> VLSpec
sortPropertySpec [] = VLSpec
A.Null
sortPropertySpec [SortProperty
Ascending] = Text -> VLSpec
fromT Text
"ascending"
sortPropertySpec [SortProperty
Descending] = Text -> VLSpec
fromT Text
"descending"
sortPropertySpec [CustomSort DataValues
dvs] = [VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON (DataValues -> [VLSpec]
dataValuesSpecs DataValues
dvs)
sortPropertySpec [SortProperty]
sps = [LabelledSpec] -> VLSpec
object ((SortProperty -> [LabelledSpec])
-> [SortProperty] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap SortProperty -> [LabelledSpec]
sortProperty [SortProperty]
sps)
data PositionChannel
= PName FieldName
| PHeight
| PWidth
| PDatum DataValue
| PNumber Double
| PRepeat Arrangement
| PRepeatDatum Arrangement
| PmType Measurement
| PBin [BinProperty]
| PBinned
| PTimeUnit TimeUnit
| PTitle T.Text
| PNoTitle
| PAggregate Operation
| PScale [ScaleProperty]
| PAxis [AxisProperty]
| PSort [SortProperty]
| PStack StackOffset
| PImpute [ImputeProperty]
| PBand Double
positionChannelProperty :: PositionChannel -> LabelledSpec
positionChannelProperty :: PositionChannel -> LabelledSpec
positionChannelProperty (PName Text
s) = Text -> LabelledSpec
field_ Text
s
positionChannelProperty (PmType Measurement
m) = Measurement -> LabelledSpec
mtype_ Measurement
m
positionChannelProperty (PBin [BinProperty]
b) = [BinProperty] -> LabelledSpec
bin [BinProperty]
b
positionChannelProperty PositionChannel
PBinned = LabelledSpec
binned_
positionChannelProperty (PAggregate Operation
op) = Operation -> LabelledSpec
aggregate_ Operation
op
positionChannelProperty (PTimeUnit TimeUnit
tu) = TimeUnit -> LabelledSpec
timeUnit_ TimeUnit
tu
positionChannelProperty (PTitle Text
s) = Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
splitOnNewline Text
s
positionChannelProperty PositionChannel
PNoTitle = Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null
positionChannelProperty (PSort [SortProperty]
ops) = [SortProperty] -> LabelledSpec
sort_ [SortProperty]
ops
positionChannelProperty (PScale [ScaleProperty]
sps) = [ScaleProperty] -> LabelledSpec
scaleProp_ [ScaleProperty]
sps
positionChannelProperty (PAxis [AxisProperty]
aps) =
let js :: VLSpec
js = if [AxisProperty] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [AxisProperty]
aps
then VLSpec
A.Null
else [LabelledSpec] -> VLSpec
object ((AxisProperty -> LabelledSpec) -> [AxisProperty] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map AxisProperty -> LabelledSpec
axisProperty [AxisProperty]
aps)
in Text
"axis" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
js
positionChannelProperty (PStack StackOffset
so) = StackOffset -> LabelledSpec
stackOffset StackOffset
so
positionChannelProperty (PRepeat Arrangement
arr) = Text
"field" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr]
positionChannelProperty (PRepeatDatum Arrangement
arr) = Text
"datum" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr]
positionChannelProperty PositionChannel
PHeight = Text -> LabelledSpec
value_ Text
"height"
positionChannelProperty PositionChannel
PWidth = Text -> LabelledSpec
value_ Text
"width"
positionChannelProperty (PDatum DataValue
d) = Text
"datum" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= DataValue -> VLSpec
dataValueSpec DataValue
d
positionChannelProperty (PNumber Double
x) = Text
"value" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
positionChannelProperty (PImpute [ImputeProperty]
ips) = [ImputeProperty] -> LabelledSpec
impute_ [ImputeProperty]
ips
positionChannelProperty (PBand Double
x) = Text
"band" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
background ::
Color
-> PropertySpec
background :: Text -> PropertySpec
background Text
colour = (VLProperty
VLBackground, Text -> VLSpec
fromColor Text
colour)
description :: T.Text -> PropertySpec
description :: Text -> PropertySpec
description Text
s = (VLProperty
VLDescription, Text -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Text
s)
usermetadata ::
A.Object
-> PropertySpec
usermetadata :: Object -> PropertySpec
usermetadata Object
o = (VLProperty
VLUserMetadata, Object -> VLSpec
A.Object Object
o)
{-# DEPRECATED AxDates "Please change AxDates to AxValues" #-}
data AxisProperty
= AxAria Bool
| AxAriaDescription T.Text
| AxBandPosition Double
| AxDataCondition BooleanOp ConditionalAxisProperty
| AxDomain Bool
| AxDomainCap StrokeCap
| AxDomainColor Color
| AxDomainDash DashStyle
| AxDomainDashOffset DashOffset
| AxDomainOpacity Opacity
| AxDomainWidth Double
| AxFormat T.Text
| AxFormatAsNum
| AxFormatAsTemporal
| AxFormatAsCustom T.Text
| AxGrid Bool
| AxGridCap StrokeCap
| AxGridColor Color
| AxGridDash DashStyle
| AxGridDashOffset DashOffset
| AxGridOpacity Opacity
| AxGridWidth Double
| AxLabels Bool
| AxLabelAlign HAlign
| AxLabelAngle Angle
| AxLabelBaseline VAlign
| AxLabelNoBound
| AxLabelBound
| AxLabelBoundValue Double
| AxLabelColor Color
| AxLabelExpr VegaExpr
| AxLabelNoFlush
| AxLabelFlush
| AxLabelFlushValue Double
| AxLabelFlushOffset Double
| AxLabelFont T.Text
| AxLabelFontSize Double
| AxLabelFontStyle T.Text
| AxLabelFontWeight FontWeight
| AxLabelLimit Double
| AxLabelLineHeight Double
| AxLabelOffset Double
| AxLabelOpacity Opacity
| AxLabelOverlap OverlapStrategy
| AxLabelPadding Double
| AxLabelSeparation Double
| AxMaxExtent Double
| AxMinExtent Double
| AxOffset Double
| AxOrient Side
| AxPosition Double
| AxStyle [StyleLabel]
| AxTicks Bool
| AxTickBand BandAlign
| AxTickCap StrokeCap
| AxTickColor Color
| AxTickCount Int
| AxTickCountTime ScaleNice
| AxTickDash DashStyle
| AxTickDashOffset DashOffset
| Bool
| AxTickMinStep Double
| AxTickOffset Double
| AxTickOpacity Opacity
| AxTickRound Bool
| AxTickSize Double
| AxTickWidth Double
| AxTitle T.Text
| AxNoTitle
| AxTitleAlign HAlign
| AxTitleAnchor APosition
| AxTitleAngle Angle
| AxTitleBaseline VAlign
| AxTitleColor Color
| AxTitleFont T.Text
| AxTitleFontSize Double
| AxTitleFontStyle T.Text
| AxTitleFontWeight FontWeight
| AxTitleLimit Double
| AxTitleLineHeight Double
| AxTitleOpacity Opacity
| AxTitlePadding Double
| AxTitleX Double
| AxTitleY Double
| AxTranslateOffset Double
| AxValues DataValues
| AxDates [[DateTime]]
| AxZIndex ZIndex
axisProperty :: AxisProperty -> LabelledSpec
axisProperty :: AxisProperty -> LabelledSpec
axisProperty (AxStyle [Text
s]) = Text
"style" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s
axisProperty (AxStyle [Text]
s) = Text
"style" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
s
axisProperty (AxAria Bool
b) = Text
"aria" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
axisProperty (AxAriaDescription Text
t) = Text
"description" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
t
axisProperty (AxBandPosition Double
x) = Text
"bandPosition" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxDataCondition BooleanOp
predicate ConditionalAxisProperty
cap) =
let (AxisProperty
ifAxProp, AxisProperty
elseAxProp) = ConditionalAxisProperty -> (AxisProperty, AxisProperty)
conditionalAxisProperty ConditionalAxisProperty
cap
(Text
axKey, VLSpec
ifProp) = AxisProperty -> LabelledSpec
axisProperty AxisProperty
ifAxProp
(Text
_, VLSpec
elseProp) = AxisProperty -> LabelledSpec
axisProperty AxisProperty
elseAxProp
in Text
axKey Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [ Text
"condition" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [ Text
"test" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= BooleanOp -> VLSpec
booleanOpSpec BooleanOp
predicate
, Text
"value" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
ifProp
]
, Text
"value" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
elseProp]
axisProperty (AxDomain Bool
b) = Text
"domain" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
axisProperty (AxDomainCap StrokeCap
c) = Text
"domainCap" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= StrokeCap -> Text
strokeCapLabel StrokeCap
c
axisProperty (AxDomainColor Text
s) = Text
"domainColor" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromColor Text
s
axisProperty (AxDomainDash [Double]
ds) = Text
"domainDash" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Double] -> VLSpec
fromDS [Double]
ds
axisProperty (AxDomainDashOffset Double
x) = Text
"domainDashOffset" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxDomainOpacity Double
x) = Text
"domainOpacity" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxDomainWidth Double
x) = Text
"domainWidth" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxFormat Text
fmt) = Text
"format" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
fmt
axisProperty AxisProperty
AxFormatAsNum = Text
"formatType" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromT Text
"number"
axisProperty AxisProperty
AxFormatAsTemporal = Text
"formatType" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromT Text
"time"
axisProperty (AxFormatAsCustom Text
c) = Text
"formatType" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
c
axisProperty (AxGrid Bool
b) = Text
"grid" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
axisProperty (AxGridCap StrokeCap
c) = Text
"gridCap" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= StrokeCap -> Text
strokeCapLabel StrokeCap
c
axisProperty (AxGridColor Text
s) = Text
"gridColor" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromColor Text
s
axisProperty (AxGridDash [Double]
ds) = Text
"gridDash" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Double] -> VLSpec
fromDS [Double]
ds
axisProperty (AxGridDashOffset Double
x) = Text
"gridDashOffset" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxGridOpacity Double
x) = Text
"gridOpacity" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxGridWidth Double
x) = Text
"gridWidth" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabels Bool
b) = Text
"labels" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
axisProperty (AxLabelAlign HAlign
ha) = Text
"labelAlign" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= HAlign -> Text
hAlignLabel HAlign
ha
axisProperty (AxLabelAngle Double
a) = Text
"labelAngle" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
a
axisProperty (AxLabelBaseline VAlign
va) = Text
"labelBaseline" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VAlign -> Text
vAlignLabel VAlign
va
axisProperty AxisProperty
AxLabelNoBound = Text
"labelBound" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
False
axisProperty AxisProperty
AxLabelBound = Text
"labelBound" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
True
axisProperty (AxLabelBoundValue Double
x) = Text
"labelBound" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabelColor Text
s) = Text
"labelColor" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromColor Text
s
axisProperty (AxLabelExpr Text
e) = Text
"labelExpr" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
e
axisProperty AxisProperty
AxLabelNoFlush = Text
"labelFlush" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
False
axisProperty AxisProperty
AxLabelFlush = Text
"labelFlush" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
True
axisProperty (AxLabelFlushValue Double
x) = Text
"labelFlush" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabelFlushOffset Double
x) = Text
"labelFlushOffset" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabelFont Text
s) = Text
"labelFont" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s
axisProperty (AxLabelFontSize Double
x) = Text
"labelFontSize" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabelFontStyle Text
s) = Text
"labelFontStyle" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s
axisProperty (AxLabelFontWeight FontWeight
fw) = Text
"labelFontWeight" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= FontWeight -> VLSpec
fontWeightSpec FontWeight
fw
axisProperty (AxLabelLimit Double
x) = Text
"labelLimit" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabelLineHeight Double
x) = Text
"labelLineHeight" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabelOffset Double
x) = Text
"labelOffset" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabelOpacity Double
x) = Text
"labelOpacity" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabelOverlap OverlapStrategy
s) = Text
"labelOverlap" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= OverlapStrategy -> VLSpec
overlapStrategyLabel OverlapStrategy
s
axisProperty (AxLabelPadding Double
x) = Text
"labelPadding" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxLabelSeparation Double
x) = Text
"labelSeparation" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxMaxExtent Double
n) = Text
"maxExtent" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
n
axisProperty (AxMinExtent Double
n) = Text
"minExtent" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
n
axisProperty (AxOffset Double
n) = Text
"offset" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
n
axisProperty (AxOrient Side
side) = Text
"orient" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Side -> Text
sideLabel Side
side
axisProperty (AxPosition Double
n) = Text
"position" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
n
axisProperty (AxTicks Bool
b) = Text
"ticks" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
axisProperty (AxTickBand BandAlign
bnd) = Text
"tickBand" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= BandAlign -> Text
bandAlignLabel BandAlign
bnd
axisProperty (AxTickCap StrokeCap
c) = Text
"tickCap" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= StrokeCap -> Text
strokeCapLabel StrokeCap
c
axisProperty (AxTickColor Text
s) = Text
"tickColor" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromColor Text
s
axisProperty (AxTickCount Int
n) = Text
"tickCount" Text -> Int -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Int
n
axisProperty (AxTickCountTime ScaleNice
sn) = Text
"tickCount" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ScaleNice -> VLSpec
scaleNiceSpec ScaleNice
sn
axisProperty (AxTickDash [Double]
ds) = Text
"tickDash" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Double] -> VLSpec
fromDS [Double]
ds
axisProperty (AxTickDashOffset Double
x) = Text
"tickDashOffset" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTickExtra Bool
b) = Text
"tickExtra" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
axisProperty (AxTickMinStep Double
x) = Text
"tickMinStep" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTickOffset Double
x) = Text
"tickOffset" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTickOpacity Double
x) = Text
"tickOpacity" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTickRound Bool
b) = Text
"tickRound" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
axisProperty (AxTickSize Double
x) = Text
"tickSize" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTickWidth Double
x) = Text
"tickWidth" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTitle Text
ttl) = Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
splitOnNewline Text
ttl
axisProperty AxisProperty
AxNoTitle = Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null
axisProperty (AxTitleAlign HAlign
ha) = Text
"titleAlign" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= HAlign -> Text
hAlignLabel HAlign
ha
axisProperty (AxTitleAnchor APosition
a) = Text
"titleAnchor" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= APosition -> Text
anchorLabel APosition
a
axisProperty (AxTitleAngle Double
x) = Text
"titleAngle" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTitleBaseline VAlign
va) = Text
"titleBaseline" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VAlign -> Text
vAlignLabel VAlign
va
axisProperty (AxTitleColor Text
s) = Text
"titleColor" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromColor Text
s
axisProperty (AxTitleFont Text
s) = Text
"titleFont" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s
axisProperty (AxTitleFontSize Double
x) = Text
"titleFontSize" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTitleFontStyle Text
s) = Text
"titleFontStyle" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s
axisProperty (AxTitleFontWeight FontWeight
fw) = Text
"titleFontWeight" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= FontWeight -> VLSpec
fontWeightSpec FontWeight
fw
axisProperty (AxTitleLimit Double
x) = Text
"titleLimit" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTitleLineHeight Double
x) = Text
"titleLineHeight" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTitleOpacity Double
x) = Text
"titleOpacity" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTitlePadding Double
pad) = Text
"titlePadding" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
pad
axisProperty (AxTitleX Double
x) = Text
"titleX" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTitleY Double
x) = Text
"titleY" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxTranslateOffset Double
x) = Text
"translate" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
axisProperty (AxValues DataValues
vals) = Text
"values" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= DataValues -> [VLSpec]
dataValuesSpecs DataValues
vals
axisProperty (AxDates [[DateTime]]
dtss) = Text
"values" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ([DateTime] -> VLSpec) -> [[DateTime]] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map [DateTime] -> VLSpec
dateTimeSpec [[DateTime]]
dtss
axisProperty (AxZIndex ZIndex
z) = Text
"zindex" Text -> ZIndex -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ZIndex
z
data ConditionalAxisProperty
= CAxGridColor Color Color
| CAxGridDash DashStyle DashStyle
| CAxGridDashOffset DashOffset DashOffset
| CAxGridOpacity Opacity Opacity
| CAxGridWidth Double Double
| CAxLabelAlign HAlign HAlign
| CAxLabelBaseline VAlign VAlign
| CAxLabelColor Color Color
| CAxLabelFont T.Text T.Text
| CAxLabelFontSize Double Double
| CAxLabelFontStyle T.Text T.Text
| CAxLabelFontWeight FontWeight FontWeight
| CAxLabelOffset Double Double
| CAxLabelOpacity Opacity Opacity
| CAxLabelPadding Double Double
| CAxTickColor T.Text T.Text
| CAxTickDash DashStyle DashStyle
| CAxTickDashOffset DashOffset DashOffset
| CAxTickOpacity Opacity Opacity
| CAxTickSize Double Double
| CAxTickWidth Double Double
conditionalAxisProperty :: ConditionalAxisProperty -> (AxisProperty, AxisProperty)
conditionalAxisProperty :: ConditionalAxisProperty -> (AxisProperty, AxisProperty)
conditionalAxisProperty (CAxGridColor Text
t Text
f) = (Text -> AxisProperty
AxGridColor Text
t, Text -> AxisProperty
AxGridColor Text
f)
conditionalAxisProperty (CAxGridDash [Double]
t [Double]
f) = ([Double] -> AxisProperty
AxGridDash [Double]
t, [Double] -> AxisProperty
AxGridDash [Double]
f)
conditionalAxisProperty (CAxGridDashOffset Double
t Double
f) = (Double -> AxisProperty
AxGridDashOffset Double
t, Double -> AxisProperty
AxGridDashOffset Double
f)
conditionalAxisProperty (CAxGridOpacity Double
t Double
f) = (Double -> AxisProperty
AxGridOpacity Double
t, Double -> AxisProperty
AxGridOpacity Double
f)
conditionalAxisProperty (CAxGridWidth Double
t Double
f) = (Double -> AxisProperty
AxGridWidth Double
t, Double -> AxisProperty
AxGridWidth Double
f)
conditionalAxisProperty (CAxLabelAlign HAlign
t HAlign
f) = (HAlign -> AxisProperty
AxLabelAlign HAlign
t, HAlign -> AxisProperty
AxLabelAlign HAlign
f)
conditionalAxisProperty (CAxLabelBaseline VAlign
t VAlign
f) = (VAlign -> AxisProperty
AxLabelBaseline VAlign
t, VAlign -> AxisProperty
AxLabelBaseline VAlign
f)
conditionalAxisProperty (CAxLabelColor Text
t Text
f) = (Text -> AxisProperty
AxLabelColor Text
t, Text -> AxisProperty
AxLabelColor Text
f)
conditionalAxisProperty (CAxLabelFont Text
t Text
f) = (Text -> AxisProperty
AxLabelFont Text
t, Text -> AxisProperty
AxLabelFont Text
f)
conditionalAxisProperty (CAxLabelFontSize Double
t Double
f) = (Double -> AxisProperty
AxLabelFontSize Double
t, Double -> AxisProperty
AxLabelFontSize Double
f)
conditionalAxisProperty (CAxLabelFontStyle Text
t Text
f) = (Text -> AxisProperty
AxLabelFontStyle Text
t, Text -> AxisProperty
AxLabelFontStyle Text
f)
conditionalAxisProperty (CAxLabelFontWeight FontWeight
t FontWeight
f) = (FontWeight -> AxisProperty
AxLabelFontWeight FontWeight
t, FontWeight -> AxisProperty
AxLabelFontWeight FontWeight
f)
conditionalAxisProperty (CAxLabelOffset Double
t Double
f) = (Double -> AxisProperty
AxLabelOffset Double
t, Double -> AxisProperty
AxLabelOffset Double
f)
conditionalAxisProperty (CAxLabelOpacity Double
t Double
f) = (Double -> AxisProperty
AxLabelOpacity Double
t, Double -> AxisProperty
AxLabelOpacity Double
f)
conditionalAxisProperty (CAxLabelPadding Double
t Double
f) = (Double -> AxisProperty
AxLabelPadding Double
t, Double -> AxisProperty
AxLabelPadding Double
f)
conditionalAxisProperty (CAxTickColor Text
t Text
f) = (Text -> AxisProperty
AxTickColor Text
t, Text -> AxisProperty
AxTickColor Text
f)
conditionalAxisProperty (CAxTickDash [Double]
t [Double]
f) = ([Double] -> AxisProperty
AxTickDash [Double]
t, [Double] -> AxisProperty
AxTickDash [Double]
f)
conditionalAxisProperty (CAxTickDashOffset Double
t Double
f) = (Double -> AxisProperty
AxTickDashOffset Double
t, Double -> AxisProperty
AxTickDashOffset Double
f)
conditionalAxisProperty (CAxTickOpacity Double
t Double
f) = (Double -> AxisProperty
AxTickOpacity Double
t, Double -> AxisProperty
AxTickOpacity Double
f)
conditionalAxisProperty (CAxTickSize Double
t Double
f) = (Double -> AxisProperty
AxTickSize Double
t, Double -> AxisProperty
AxTickSize Double
f)
conditionalAxisProperty (CAxTickWidth Double
t Double
f) = (Double -> AxisProperty
AxTickWidth Double
t, Double -> AxisProperty
AxTickWidth Double
f)
autosize :: [Autosize] -> PropertySpec
autosize :: [Autosize] -> PropertySpec
autosize [Autosize]
aus = (VLProperty
VLAutosize, [LabelledSpec] -> VLSpec
object ((Autosize -> LabelledSpec) -> [Autosize] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map Autosize -> LabelledSpec
autosizeProperty [Autosize]
aus))
viewBackground :: [ViewBackground] -> PropertySpec
viewBackground :: [ViewBackground] -> PropertySpec
viewBackground [ViewBackground]
vbs = (VLProperty
VLViewBackground, [LabelledSpec] -> VLSpec
object ((ViewBackground -> LabelledSpec)
-> [ViewBackground] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map ViewBackground -> LabelledSpec
viewBackgroundSpec [ViewBackground]
vbs))
data BooleanOp
= Expr VegaExpr
| FilterOp Filter
| FilterOpTrans MarkChannel Filter
| Selection SelectionLabel
| SelectionName SelectionLabel
| And BooleanOp BooleanOp
| Or BooleanOp BooleanOp
| Not BooleanOp
booleanOpSpec :: BooleanOp -> VLSpec
booleanOpSpec :: BooleanOp -> VLSpec
booleanOpSpec (Expr Text
expr) = Text -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Text
expr
booleanOpSpec (FilterOp Filter
f) = Filter -> VLSpec
filterSpec Filter
f
booleanOpSpec (FilterOpTrans MarkChannel
tr Filter
f) = MarkChannel -> Filter -> VLSpec
trFilterSpec MarkChannel
tr Filter
f
booleanOpSpec (SelectionName Text
selName) = Text -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Text
selName
booleanOpSpec (Selection Text
sel) = [LabelledSpec] -> VLSpec
object [Text
"selection" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
sel]
booleanOpSpec (And BooleanOp
operand1 BooleanOp
operand2) = [LabelledSpec] -> VLSpec
object [Text
"and" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand1, BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand2]]
booleanOpSpec (Or BooleanOp
operand1 BooleanOp
operand2) = [LabelledSpec] -> VLSpec
object [Text
"or" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand1, BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand2]]
booleanOpSpec (Not BooleanOp
operand) = [LabelledSpec] -> VLSpec
object [Text
"not" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand]
data Filter
= FEqual FieldName DataValue
| FLessThan FieldName DataValue
| FLessThanEq FieldName DataValue
| FGreaterThan FieldName DataValue
| FGreaterThanEq FieldName DataValue
| FExpr VegaExpr
| FCompose BooleanOp
| FSelection SelectionLabel
| FOneOf FieldName DataValues
| FRange FieldName FilterRange
| FValid FieldName
fop_ :: FieldName -> T.Text -> DataValue -> [LabelledSpec]
fop_ :: Text -> Text -> DataValue -> [LabelledSpec]
fop_ Text
field Text
label DataValue
val = [Text -> LabelledSpec
field_ Text
field, Text
label Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= DataValue -> VLSpec
dataValueSpec DataValue
val]
filterProperty :: Filter -> [LabelledSpec]
filterProperty :: Filter -> [LabelledSpec]
filterProperty (FEqual Text
field DataValue
val) = Text -> Text -> DataValue -> [LabelledSpec]
fop_ Text
field Text
"equal" DataValue
val
filterProperty (FLessThan Text
field DataValue
val) = Text -> Text -> DataValue -> [LabelledSpec]
fop_ Text
field Text
"lt" DataValue
val
filterProperty (FLessThanEq Text
field DataValue
val) = Text -> Text -> DataValue -> [LabelledSpec]
fop_ Text
field Text
"lte" DataValue
val
filterProperty (FGreaterThan Text
field DataValue
val) = Text -> Text -> DataValue -> [LabelledSpec]
fop_ Text
field Text
"gt" DataValue
val
filterProperty (FGreaterThanEq Text
field DataValue
val) = Text -> Text -> DataValue -> [LabelledSpec]
fop_ Text
field Text
"gte" DataValue
val
filterProperty (FSelection Text
selName) = [Text
"selection" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
selName]
filterProperty (FRange Text
field FilterRange
vals) =
let ans :: [VLSpec]
ans = case FilterRange
vals of
NumberRange Double
mn Double
mx -> (Double -> VLSpec) -> [Double] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Double
mn, Double
mx]
NumberRangeLL Double
mn -> [Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
mn, VLSpec
A.Null]
NumberRangeUL Double
mx -> [VLSpec
A.Null, Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
mx]
DateRange [DateTime]
dMin [DateTime]
dMax -> [[DateTime] -> VLSpec
process [DateTime]
dMin, [DateTime] -> VLSpec
process [DateTime]
dMax]
process :: [DateTime] -> VLSpec
process [] = VLSpec
A.Null
process [DateTime]
dts = [DateTime] -> VLSpec
dateTimeSpec [DateTime]
dts
in [Text -> LabelledSpec
field_ Text
field, Text
"range" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [VLSpec]
ans]
filterProperty (FOneOf Text
field DataValues
vals) =
let ans :: [VLSpec]
ans = case DataValues
vals of
Numbers [Double]
xs -> (Double -> VLSpec) -> [Double] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Double]
xs
DateTimes [[DateTime]]
dts -> ([DateTime] -> VLSpec) -> [[DateTime]] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map [DateTime] -> VLSpec
dateTimeSpec [[DateTime]]
dts
Strings [Text]
ss -> (Text -> VLSpec) -> [Text] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map Text -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
ss
Booleans [Bool]
bs -> (Bool -> VLSpec) -> [Bool] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map Bool -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Bool]
bs
in [Text -> LabelledSpec
field_ Text
field, Text
"oneOf" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [VLSpec]
ans]
filterProperty (FValid Text
field) = [Text -> LabelledSpec
field_ Text
field, Text
"valid" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
True]
filterProperty Filter
_ = []
filterSpec :: Filter -> VLSpec
filterSpec :: Filter -> VLSpec
filterSpec (FExpr Text
expr) = Text -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Text
expr
filterSpec (FCompose BooleanOp
boolExpr) = BooleanOp -> VLSpec
booleanOpSpec BooleanOp
boolExpr
filterSpec Filter
f = [LabelledSpec] -> VLSpec
object (Filter -> [LabelledSpec]
filterProperty Filter
f)
trFilterSpec :: MarkChannel -> Filter -> VLSpec
trFilterSpec :: MarkChannel -> Filter -> VLSpec
trFilterSpec MarkChannel
_ (FExpr Text
expr) = Text -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Text
expr
trFilterSpec MarkChannel
_ (FCompose BooleanOp
boolExpr) = BooleanOp -> VLSpec
booleanOpSpec BooleanOp
boolExpr
trFilterSpec MarkChannel
mchan Filter
fi = [LabelledSpec] -> VLSpec
object (MarkChannel -> [LabelledSpec]
markChannelProperty MarkChannel
mchan [LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Filter -> [LabelledSpec]
filterProperty Filter
fi)
data FilterRange
= NumberRange Double Double
| NumberRangeLL Double
| NumberRangeUL Double
| DateRange [DateTime] [DateTime]
data HyperlinkChannel
= HName FieldName
| HRepeat Arrangement
| HmType Measurement
| HAggregate Operation
| HyBand Double
| HBin [BinProperty]
| HBinned
| HSelectionCondition BooleanOp [HyperlinkChannel] [HyperlinkChannel]
| HDataCondition [(BooleanOp, [HyperlinkChannel])] [HyperlinkChannel]
| HyFormat T.Text
| HyFormatAsNum
| HyFormatAsTemporal
| HyFormatAsCustom T.Text
| HyLabelExpr VegaExpr
| HString T.Text
| HTimeUnit TimeUnit
| HyTitle T.Text
| HyNoTitle
hyperlinkChannelProperty :: HyperlinkChannel -> [LabelledSpec]
hyperlinkChannelProperty :: HyperlinkChannel -> [LabelledSpec]
hyperlinkChannelProperty (HName Text
s) = [Text -> LabelledSpec
field_ Text
s]
hyperlinkChannelProperty (HRepeat Arrangement
arr) = [Text
"field" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr]]
hyperlinkChannelProperty (HmType Measurement
t) = [Measurement -> LabelledSpec
mtype_ Measurement
t]
hyperlinkChannelProperty (HAggregate Operation
op) = [Operation -> LabelledSpec
aggregate_ Operation
op]
hyperlinkChannelProperty (HyBand Double
x) = [Text
"band" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x]
hyperlinkChannelProperty (HBin [BinProperty]
bps) = [[BinProperty] -> LabelledSpec
bin [BinProperty]
bps]
hyperlinkChannelProperty HyperlinkChannel
HBinned = [LabelledSpec
binned_]
hyperlinkChannelProperty (HSelectionCondition BooleanOp
selName [HyperlinkChannel]
ifClause [HyperlinkChannel]
elseClause) =
(HyperlinkChannel -> [LabelledSpec])
-> BooleanOp
-> [HyperlinkChannel]
-> [HyperlinkChannel]
-> [LabelledSpec]
forall a.
(a -> [LabelledSpec]) -> BooleanOp -> [a] -> [a] -> [LabelledSpec]
selCond_ HyperlinkChannel -> [LabelledSpec]
hyperlinkChannelProperty BooleanOp
selName [HyperlinkChannel]
ifClause [HyperlinkChannel]
elseClause
hyperlinkChannelProperty (HDataCondition [(BooleanOp, [HyperlinkChannel])]
tests [HyperlinkChannel]
elseClause) =
(HyperlinkChannel -> [LabelledSpec])
-> [(BooleanOp, [HyperlinkChannel])]
-> [HyperlinkChannel]
-> [LabelledSpec]
forall a.
(a -> [LabelledSpec])
-> [(BooleanOp, [a])] -> [a] -> [LabelledSpec]
dataCond_ HyperlinkChannel -> [LabelledSpec]
hyperlinkChannelProperty [(BooleanOp, [HyperlinkChannel])]
tests [HyperlinkChannel]
elseClause
hyperlinkChannelProperty (HyFormat Text
fmt) = [Text
"format" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
fmt]
hyperlinkChannelProperty HyperlinkChannel
HyFormatAsNum = [Text
"formatType" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromT Text
"number"]
hyperlinkChannelProperty HyperlinkChannel
HyFormatAsTemporal = [Text
"formatType" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromT Text
"time"]
hyperlinkChannelProperty (HyFormatAsCustom Text
c) = [Text
"formatType" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
c]
hyperlinkChannelProperty (HyLabelExpr Text
lbl) = [Text
"labelExpr" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
lbl]
hyperlinkChannelProperty (HString Text
s) = [Text -> LabelledSpec
value_ Text
s]
hyperlinkChannelProperty (HTimeUnit TimeUnit
tu) = [TimeUnit -> LabelledSpec
timeUnit_ TimeUnit
tu]
hyperlinkChannelProperty (HyTitle Text
t) = [Text
"title" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
t]
hyperlinkChannelProperty HyperlinkChannel
HyNoTitle = [Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null]
data AriaDescriptionChannel
= ADName FieldName
| ADRepeat Arrangement
| ADmType Measurement
| ADAggregate Operation
| ADBand Double
| ADBin [BinProperty]
| ADBinned
| ADSelectionCondition BooleanOp [AriaDescriptionChannel] [AriaDescriptionChannel]
| ADDataCondition [(BooleanOp, [AriaDescriptionChannel])] [AriaDescriptionChannel]
| ADFormat T.Text
| ADFormatAsNum
| ADFormatAsTemporal
| ADFormatAsCustom T.Text
| ADLabelExpr VegaExpr
| ADString T.Text
| ADTimeUnit TimeUnit
| ADTitle T.Text
| ADNoTitle
ariaDescriptionChannelProperty :: AriaDescriptionChannel -> [LabelledSpec]
ariaDescriptionChannelProperty :: AriaDescriptionChannel -> [LabelledSpec]
ariaDescriptionChannelProperty (ADName Text
s) = [Text -> LabelledSpec
field_ Text
s]
ariaDescriptionChannelProperty (ADRepeat Arrangement
arr) = [Text
"field" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr]]
ariaDescriptionChannelProperty (ADmType Measurement
t) = [Measurement -> LabelledSpec
mtype_ Measurement
t]
ariaDescriptionChannelProperty (ADAggregate Operation
op) = [Operation -> LabelledSpec
aggregate_ Operation
op]
ariaDescriptionChannelProperty (ADBand Double
x) = [Text
"band" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x]
ariaDescriptionChannelProperty (ADBin [BinProperty]
bps) = [[BinProperty] -> LabelledSpec
bin [BinProperty]
bps]
ariaDescriptionChannelProperty AriaDescriptionChannel
ADBinned = [LabelledSpec
binned_]
ariaDescriptionChannelProperty (ADSelectionCondition BooleanOp
selName [AriaDescriptionChannel]
ifClause [AriaDescriptionChannel]
elseClause) =
(AriaDescriptionChannel -> [LabelledSpec])
-> BooleanOp
-> [AriaDescriptionChannel]
-> [AriaDescriptionChannel]
-> [LabelledSpec]
forall a.
(a -> [LabelledSpec]) -> BooleanOp -> [a] -> [a] -> [LabelledSpec]
selCond_ AriaDescriptionChannel -> [LabelledSpec]
ariaDescriptionChannelProperty BooleanOp
selName [AriaDescriptionChannel]
ifClause [AriaDescriptionChannel]
elseClause
ariaDescriptionChannelProperty (ADDataCondition [(BooleanOp, [AriaDescriptionChannel])]
tests [AriaDescriptionChannel]
elseClause) =
(AriaDescriptionChannel -> [LabelledSpec])
-> [(BooleanOp, [AriaDescriptionChannel])]
-> [AriaDescriptionChannel]
-> [LabelledSpec]
forall a.
(a -> [LabelledSpec])
-> [(BooleanOp, [a])] -> [a] -> [LabelledSpec]
dataCond_ AriaDescriptionChannel -> [LabelledSpec]
ariaDescriptionChannelProperty [(BooleanOp, [AriaDescriptionChannel])]
tests [AriaDescriptionChannel]
elseClause
ariaDescriptionChannelProperty (ADFormat Text
fmt) = [Text
"format" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
fmt]
ariaDescriptionChannelProperty AriaDescriptionChannel
ADFormatAsNum = [Text
"formatType" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromT Text
"number"]
ariaDescriptionChannelProperty AriaDescriptionChannel
ADFormatAsTemporal = [Text
"formatType" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromT Text
"time"]
ariaDescriptionChannelProperty (ADFormatAsCustom Text
c) = [Text
"formatType" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
c]
ariaDescriptionChannelProperty (ADLabelExpr Text
lbl) = [Text
"labelExpr" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
lbl]
ariaDescriptionChannelProperty (ADString Text
s) = [Text -> LabelledSpec
value_ Text
s]
ariaDescriptionChannelProperty (ADTimeUnit TimeUnit
tu) = [TimeUnit -> LabelledSpec
timeUnit_ TimeUnit
tu]
ariaDescriptionChannelProperty (ADTitle Text
t) = [Text
"title" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
t]
ariaDescriptionChannelProperty AriaDescriptionChannel
ADNoTitle = [Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null]
domainRangeMap :: (Double, Color) -> (Double, Color) -> [ScaleProperty]
domainRangeMap :: (Double, Text) -> (Double, Text) -> [ScaleProperty]
domainRangeMap (Double, Text)
lowerMap (Double, Text)
upperMap =
let ([Double]
domain, [Text]
range) = [(Double, Text)] -> ([Double], [Text])
forall a b. [(a, b)] -> ([a], [b])
unzip [(Double, Text)
lowerMap, (Double, Text)
upperMap]
in [DomainLimits -> ScaleProperty
SDomain ([Double] -> DomainLimits
DNumbers [Double]
domain), ScaleRange -> ScaleProperty
SRange ([Text] -> ScaleRange
RStrings [Text]
range)]
categoricalDomainMap :: [(T.Text, Color)] -> [ScaleProperty]
categoricalDomainMap :: [(Text, Text)] -> [ScaleProperty]
categoricalDomainMap [(Text, Text)]
scaleDomainPairs =
let ([Text]
domain, [Text]
range) = [(Text, Text)] -> ([Text], [Text])
forall a b. [(a, b)] -> ([a], [b])
unzip [(Text, Text)]
scaleDomainPairs
in [DomainLimits -> ScaleProperty
SDomain ([Text] -> DomainLimits
DStrings [Text]
domain), ScaleRange -> ScaleProperty
SRange ([Text] -> ScaleRange
RStrings [Text]
range)]
data FacetChannel
= FName FieldName
| FmType Measurement
| FAggregate Operation
| FAlign CompositionAlignment
| FBin [BinProperty]
| FCenter Bool
| [HeaderProperty]
| FSort [SortProperty]
| FSpacing Double
| FTimeUnit TimeUnit
| FTitle T.Text
| FNoTitle
facetChannelProperty :: FacetChannel -> LabelledSpec
facetChannelProperty :: FacetChannel -> LabelledSpec
facetChannelProperty (FName Text
s) = Text -> LabelledSpec
field_ Text
s
facetChannelProperty (FmType Measurement
measure) = Measurement -> LabelledSpec
mtype_ Measurement
measure
facetChannelProperty (FAlign CompositionAlignment
algn) = Text
"align" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
algn
facetChannelProperty (FAggregate Operation
op) = Operation -> LabelledSpec
aggregate_ Operation
op
facetChannelProperty (FBin [BinProperty]
bps) = [BinProperty] -> LabelledSpec
bin [BinProperty]
bps
facetChannelProperty (FCenter Bool
b) = Text
"center" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
b
facetChannelProperty (FHeader [HeaderProperty]
hps) = Text -> [HeaderProperty] -> LabelledSpec
header_ Text
"" [HeaderProperty]
hps
facetChannelProperty (FSort [SortProperty]
sps) = [SortProperty] -> LabelledSpec
sort_ [SortProperty]
sps
facetChannelProperty (FSpacing Double
x) = Text
"spacing" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x
facetChannelProperty (FTitle Text
s) = Text
"title" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s
facetChannelProperty FacetChannel
FNoTitle = Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null
facetChannelProperty (FTimeUnit TimeUnit
tu) = TimeUnit -> LabelledSpec
timeUnit_ TimeUnit
tu
data TextChannel
= TName FieldName
| TRepeat Arrangement
| TRepeatDatum Arrangement
| TmType Measurement
| TAggregate Operation
| TBand Double
| TBin [BinProperty]
| TBinned
| TDataCondition [(BooleanOp, [TextChannel])] [TextChannel]
| TSelectionCondition BooleanOp [TextChannel] [TextChannel]
| TDatum DataValue
| TFormat T.Text
| TFormatAsNum
| TFormatAsTemporal
| TFormatAsCustom T.Text
| TLabelExpr VegaExpr
| TString T.Text
| TStrings [T.Text]
| TTimeUnit TimeUnit
| TTitle T.Text
| TNoTitle
textChannelProperty :: TextChannel -> [LabelledSpec]
textChannelProperty :: TextChannel -> [LabelledSpec]
textChannelProperty (TName Text
s) = [Text -> LabelledSpec
field_ Text
s]
textChannelProperty (TRepeat Arrangement
arr) = [Text
"field" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr]]
textChannelProperty (TRepeatDatum Arrangement
arr) = [Text
"datum" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr]]
textChannelProperty (TmType Measurement
measure) = [Measurement -> LabelledSpec
mtype_ Measurement
measure]
textChannelProperty (TAggregate Operation
op) = [Operation -> LabelledSpec
aggregate_ Operation
op]
textChannelProperty (TBand Double
x) = [Text
"band" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x]
textChannelProperty (TBin [BinProperty]
bps) = [[BinProperty] -> LabelledSpec
bin [BinProperty]
bps]
textChannelProperty TextChannel
TBinned = [LabelledSpec
binned_]
textChannelProperty (TDataCondition [(BooleanOp, [TextChannel])]
tests [TextChannel]
elseClause) =
(TextChannel -> [LabelledSpec])
-> [(BooleanOp, [TextChannel])] -> [TextChannel] -> [LabelledSpec]
forall a.
(a -> [LabelledSpec])
-> [(BooleanOp, [a])] -> [a] -> [LabelledSpec]
dataCond_ TextChannel -> [LabelledSpec]
textChannelProperty [(BooleanOp, [TextChannel])]
tests [TextChannel]
elseClause
textChannelProperty (TSelectionCondition BooleanOp
selName [TextChannel]
ifClause [TextChannel]
elseClause) =
(TextChannel -> [LabelledSpec])
-> BooleanOp -> [TextChannel] -> [TextChannel] -> [LabelledSpec]
forall a.
(a -> [LabelledSpec]) -> BooleanOp -> [a] -> [a] -> [LabelledSpec]
selCond_ TextChannel -> [LabelledSpec]
textChannelProperty BooleanOp
selName [TextChannel]
ifClause [TextChannel]
elseClause
textChannelProperty (TDatum DataValue
dv) = [Text
"datum" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= DataValue -> VLSpec
dataValueSpec DataValue
dv]
textChannelProperty (TFormat Text
fmt) = [Text
"format" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
fmt]
textChannelProperty TextChannel
TFormatAsNum = [Text
"formatType" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromT Text
"number"]
textChannelProperty TextChannel
TFormatAsTemporal = [Text
"formatType" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
fromT Text
"time"]
textChannelProperty (TFormatAsCustom Text
c) = [Text
"formatType" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
c]
textChannelProperty (TLabelExpr Text
e) = [Text
"labelExpr" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
e]
textChannelProperty (TString Text
s) = [Text
"value" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s]
textChannelProperty (TStrings [Text]
xs) = [Text
"value" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
xs]
textChannelProperty (TTimeUnit TimeUnit
tu) = [TimeUnit -> LabelledSpec
timeUnit_ TimeUnit
tu]
textChannelProperty (TTitle Text
s) = [Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> VLSpec
splitOnNewline Text
s]
textChannelProperty TextChannel
TNoTitle = [Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null]
data OrderChannel
= OName FieldName
| ORepeat Arrangement
| OAggregate Operation
| OBand Double
| OBin [BinProperty]
| OSort [SortProperty]
| OTimeUnit TimeUnit
| OTitle T.Text
| ONoTitle
| OmType Measurement
| ODataCondition [(BooleanOp, [OrderChannel])] [OrderChannel]
| OSelectionCondition BooleanOp [OrderChannel] [OrderChannel]
| ONumber Double
orderChannelProperty :: OrderChannel -> [LabelledSpec]
orderChannelProperty :: OrderChannel -> [LabelledSpec]
orderChannelProperty (OAggregate Operation
op) = [Operation -> LabelledSpec
aggregate_ Operation
op]
orderChannelProperty (OBand Double
x) = [Text
"band" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
x]
orderChannelProperty (OBin [BinProperty]
bps) = [[BinProperty] -> LabelledSpec
bin [BinProperty]
bps]
orderChannelProperty (OName Text
s) = [Text -> LabelledSpec
field_ Text
s]
orderChannelProperty (ORepeat Arrangement
arr) = [Text
"field" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [Arrangement -> LabelledSpec
repeat_ Arrangement
arr]]
orderChannelProperty (OSort [SortProperty]
ops) = [[SortProperty] -> LabelledSpec
sort_ [SortProperty]
ops]
orderChannelProperty (OTimeUnit TimeUnit
tu) = [TimeUnit -> LabelledSpec
timeUnit_ TimeUnit
tu]
orderChannelProperty (OTitle Text
s) = [Text
"title" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
s]
orderChannelProperty OrderChannel
ONoTitle = [Text
"title" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
A.Null]
orderChannelProperty (OmType Measurement
measure) = [Measurement -> LabelledSpec
mtype_ Measurement
measure]
orderChannelProperty (ODataCondition [(BooleanOp, [OrderChannel])]
tests [OrderChannel]
elseClause) =
(OrderChannel -> [LabelledSpec])
-> [(BooleanOp, [OrderChannel])]
-> [OrderChannel]
-> [LabelledSpec]
forall a.
(a -> [LabelledSpec])
-> [(BooleanOp, [a])] -> [a] -> [LabelledSpec]
dataCond_ OrderChannel -> [LabelledSpec]
orderChannelProperty [(BooleanOp, [OrderChannel])]
tests [OrderChannel]
elseClause
orderChannelProperty (OSelectionCondition BooleanOp
selName [OrderChannel]
ifClause [OrderChannel]
elseClause) =
(OrderChannel -> [LabelledSpec])
-> BooleanOp -> [OrderChannel] -> [OrderChannel] -> [LabelledSpec]
forall a.
(a -> [LabelledSpec]) -> BooleanOp -> [a] -> [a] -> [LabelledSpec]
selCond_ OrderChannel -> [LabelledSpec]
orderChannelProperty BooleanOp
selName [OrderChannel]
ifClause [OrderChannel]
elseClause
orderChannelProperty (ONumber Double
n) = [Text
"value" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
n]
data DetailChannel
= DName FieldName
| DmType Measurement
| DBin [BinProperty]
| DTimeUnit TimeUnit
| DAggregate Operation
detailChannelProperty :: DetailChannel -> LabelledSpec
detailChannelProperty :: DetailChannel -> LabelledSpec
detailChannelProperty (DName Text
s) = Text -> LabelledSpec
field_ Text
s
detailChannelProperty (DmType Measurement
t) = Measurement -> LabelledSpec
mtype_ Measurement
t
detailChannelProperty (DBin [BinProperty]
bps) = [BinProperty] -> LabelledSpec
bin [BinProperty]
bps
detailChannelProperty (DTimeUnit TimeUnit
tu) = TimeUnit -> LabelledSpec
timeUnit_ TimeUnit
tu
detailChannelProperty (DAggregate Operation
op) = Operation -> LabelledSpec
aggregate_ Operation
op
data FacetMapping
= ColumnBy [FacetChannel]
| RowBy [FacetChannel]
facetMappingProperty :: FacetMapping -> LabelledSpec
facetMappingProperty :: FacetMapping -> LabelledSpec
facetMappingProperty (RowBy [FacetChannel]
fFields) =
Text
"row" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object ((FacetChannel -> LabelledSpec) -> [FacetChannel] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> LabelledSpec
facetChannelProperty [FacetChannel]
fFields)
facetMappingProperty (ColumnBy [FacetChannel]
fFields) =
Text
"column" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object ((FacetChannel -> LabelledSpec) -> [FacetChannel] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> LabelledSpec
facetChannelProperty [FacetChannel]
fFields)
configure ::
[ConfigureSpec]
-> PropertySpec
configure :: [ConfigureSpec] -> PropertySpec
configure [ConfigureSpec]
configs = (VLProperty
VLConfig, [LabelledSpec] -> VLSpec
object ((ConfigureSpec -> LabelledSpec)
-> [ConfigureSpec] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map ConfigureSpec -> LabelledSpec
unCS [ConfigureSpec]
configs))
align :: CompositionAlignment -> PropertySpec
align :: CompositionAlignment -> PropertySpec
align CompositionAlignment
algn = (VLProperty
VLAlign, CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
algn)
alignRC ::
CompositionAlignment
-> CompositionAlignment
-> PropertySpec
alignRC :: CompositionAlignment -> CompositionAlignment -> PropertySpec
alignRC CompositionAlignment
alRow CompositionAlignment
alCol =
(VLProperty
VLSpacing, [LabelledSpec] -> VLSpec
object [ Text
"row" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
alRow
, Text
"col" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
alCol
])
spacing ::
Double
-> PropertySpec
spacing :: Double -> PropertySpec
spacing Double
sp = (VLProperty
VLSpacing, Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
sp)
spacingRC ::
Double
-> Double
-> PropertySpec
spacingRC :: Double -> Double -> PropertySpec
spacingRC Double
spRow Double
spCol = (VLProperty
VLSpacing, [LabelledSpec] -> VLSpec
object [Text
"row" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
spRow, Text
"column" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
spCol])
center :: Bool -> PropertySpec
center :: Bool -> PropertySpec
center Bool
c = (VLProperty
VLCenter, Bool -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Bool
c)
centerRC ::
Bool
-> Bool
-> PropertySpec
centerRC :: Bool -> Bool -> PropertySpec
centerRC Bool
cRow Bool
cCol = (VLProperty
VLCenter, [LabelledSpec] -> VLSpec
object [Text
"row" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
cRow, Text
"col" Text -> Bool -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
cCol])
bounds :: Bounds -> PropertySpec
bounds :: Bounds -> PropertySpec
bounds Bounds
bnds = (VLProperty
VLBounds, Bounds -> VLSpec
boundsSpec Bounds
bnds)
vlConcat :: [VLSpec] -> PropertySpec
vlConcat :: [VLSpec] -> PropertySpec
vlConcat [VLSpec]
specs = (VLProperty
VLConcat, [VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
specs)
facet :: [FacetMapping] -> PropertySpec
facet :: [FacetMapping] -> PropertySpec
facet [FacetMapping]
fMaps = (VLProperty
VLFacet, [LabelledSpec] -> VLSpec
object ((FacetMapping -> LabelledSpec) -> [FacetMapping] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map FacetMapping -> LabelledSpec
facetMappingProperty [FacetMapping]
fMaps))
facetFlow :: [FacetChannel] -> PropertySpec
facetFlow :: [FacetChannel] -> PropertySpec
facetFlow [FacetChannel]
fFields = (VLProperty
VLFacet, [LabelledSpec] -> VLSpec
object ((FacetChannel -> LabelledSpec) -> [FacetChannel] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> LabelledSpec
facetChannelProperty [FacetChannel]
fFields))
height :: Double -> PropertySpec
height :: Double -> PropertySpec
height Double
h = (VLProperty
VLHeight, Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
h)
heightOfContainer :: PropertySpec
heightOfContainer :: PropertySpec
heightOfContainer = (VLProperty
VLHeight, Text -> VLSpec
fromT Text
"container")
heightStep :: Double -> PropertySpec
heightStep :: Double -> PropertySpec
heightStep Double
s = (VLProperty
VLHeight, [LabelledSpec] -> VLSpec
object [ Text
"step" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
s ])
hConcat :: [VLSpec] -> PropertySpec
hConcat :: [VLSpec] -> PropertySpec
hConcat [VLSpec]
specs = (VLProperty
VLHConcat, [VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
specs)
layer :: [VLSpec] -> PropertySpec
layer :: [VLSpec] -> PropertySpec
layer [VLSpec]
specs = (VLProperty
VLLayer, [VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
specs)
name :: T.Text -> PropertySpec
name :: Text -> PropertySpec
name Text
s = (VLProperty
VLName, Text -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Text
s)
padding :: Padding -> PropertySpec
padding :: Padding -> PropertySpec
padding Padding
pad = (VLProperty
VLPadding, Padding -> VLSpec
paddingSpec Padding
pad)
repeat :: [RepeatFields] -> PropertySpec
repeat :: [RepeatFields] -> PropertySpec
repeat [RepeatFields]
fields = (VLProperty
VLRepeat, [LabelledSpec] -> VLSpec
object ((RepeatFields -> LabelledSpec) -> [RepeatFields] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map RepeatFields -> LabelledSpec
repeatFieldsProperty [RepeatFields]
fields))
repeatFlow ::
[FieldName]
-> PropertySpec
repeatFlow :: [Text] -> PropertySpec
repeatFlow [Text]
fields = (VLProperty
VLRepeat, [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
fields)
resolve ::
[ResolveSpec]
-> PropertySpec
resolve :: [ResolveSpec] -> PropertySpec
resolve [ResolveSpec]
res = (VLProperty
VLResolve, [LabelledSpec] -> VLSpec
object ((ResolveSpec -> LabelledSpec) -> [ResolveSpec] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map ResolveSpec -> LabelledSpec
unRS [ResolveSpec]
res))
transform ::
[TransformSpec]
-> PropertySpec
transform :: [TransformSpec] -> PropertySpec
transform [TransformSpec]
transforms =
let js :: VLSpec
js = if [TransformSpec] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TransformSpec]
transforms then VLSpec
A.Null else [VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON ((TransformSpec -> VLSpec) -> [TransformSpec] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map TransformSpec -> VLSpec
unTS [TransformSpec]
transforms)
in (VLProperty
VLTransform, VLSpec
js)
vConcat :: [VLSpec] -> PropertySpec
vConcat :: [VLSpec] -> PropertySpec
vConcat [VLSpec]
specs = (VLProperty
VLVConcat, [VLSpec] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
specs)
width :: Double -> PropertySpec
width :: Double -> PropertySpec
width Double
w = (VLProperty
VLWidth, Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
w)
widthOfContainer :: PropertySpec
widthOfContainer :: PropertySpec
widthOfContainer = (VLProperty
VLWidth, Text -> VLSpec
fromT Text
"container")
widthStep :: Double -> PropertySpec
widthStep :: Double -> PropertySpec
widthStep Double
s = (VLProperty
VLWidth, [LabelledSpec] -> VLSpec
object [ Text
"step" Text -> Double -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Double
s ])
aggregate ::
[VLSpec]
-> [FieldName]
-> BuildTransformSpecs
aggregate :: [VLSpec] -> [Text] -> BuildTransformSpecs
aggregate [VLSpec]
ops [Text]
groups [TransformSpec]
ols =
let fields :: [LabelledSpec]
fields = [ Text
"aggregate" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [VLSpec]
ops
, Text
"groupby" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
groups ]
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
fields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
joinAggregate ::
[VLSpec]
-> [WindowProperty]
-> BuildTransformSpecs
joinAggregate :: [VLSpec] -> [WindowProperty] -> BuildTransformSpecs
joinAggregate [VLSpec]
ops [WindowProperty]
wProps [TransformSpec]
ols = [VLSpec] -> [WindowProperty] -> TransformSpec
joinAggregateTS [VLSpec]
ops [WindowProperty]
wProps TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
window ::
[([Window], FieldName)]
-> [WindowProperty]
-> BuildTransformSpecs
window :: [([Window], Text)] -> [WindowProperty] -> BuildTransformSpecs
window [([Window], Text)]
wss [WindowProperty]
wProps [TransformSpec]
ols = [([Window], Text)] -> [WindowProperty] -> TransformSpec
windowTS [([Window], Text)]
wss [WindowProperty]
wProps TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
sample :: Int -> BuildTransformSpecs
sample :: Int -> BuildTransformSpecs
sample Int
maxSize [TransformSpec]
ols = VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [ Text
"sample" Text -> Int -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Int
maxSize ]) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
data DensityProperty
= DnAs FieldName FieldName
| DnBandwidth Double
| DnCounts Bool
| DnCumulative Bool
| DnExtent Double Double
| DnGroupBy [FieldName]
| DnMaxSteps Natural
| DnMinSteps Natural
| DnSteps Natural
data DensityPropertyLabel =
DPLGroupby | DPLCumulative | DPLCounts | DPLBandwidth | DPLExtent |
DPLMinsteps | DPLMaxsteps | DPLSteps | DPLAs
densityPropertySpec :: DensityPropertyLabel -> [DensityProperty] -> VLSpec
densityPropertySpec :: DensityPropertyLabel -> [DensityProperty] -> VLSpec
densityPropertySpec DensityPropertyLabel
DPLGroupby [DensityProperty]
ps =
let wanted :: DensityProperty -> Maybe [Text]
wanted (DnGroupBy [Text]
xs) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
xs
wanted DensityProperty
_ = Maybe [Text]
forall a. Maybe a
Nothing
in case (DensityProperty -> Maybe [Text]) -> [DensityProperty] -> [[Text]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe [Text]
wanted [DensityProperty]
ps of
[[Text]
x] -> [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
x
[[Text]]
_ -> VLSpec
A.Null
densityPropertySpec DensityPropertyLabel
DPLCumulative [DensityProperty]
ps =
let wanted :: DensityProperty -> Maybe Bool
wanted (DnCumulative Bool
xs) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs
wanted DensityProperty
_ = Maybe Bool
forall a. Maybe a
Nothing
in case (DensityProperty -> Maybe Bool) -> [DensityProperty] -> [Bool]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe Bool
wanted [DensityProperty]
ps of
[Bool
x] -> Bool -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Bool
x
[Bool]
_ -> VLSpec
A.Null
densityPropertySpec DensityPropertyLabel
DPLCounts [DensityProperty]
ps =
let wanted :: DensityProperty -> Maybe Bool
wanted (DnCounts Bool
xs) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs
wanted DensityProperty
_ = Maybe Bool
forall a. Maybe a
Nothing
in case (DensityProperty -> Maybe Bool) -> [DensityProperty] -> [Bool]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe Bool
wanted [DensityProperty]
ps of
[Bool
x] -> Bool -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Bool
x
[Bool]
_ -> VLSpec
A.Null
densityPropertySpec DensityPropertyLabel
DPLBandwidth [DensityProperty]
ps =
let wanted :: DensityProperty -> Maybe Double
wanted (DnBandwidth Double
xs) = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
xs
wanted DensityProperty
_ = Maybe Double
forall a. Maybe a
Nothing
in case (DensityProperty -> Maybe Double) -> [DensityProperty] -> [Double]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe Double
wanted [DensityProperty]
ps of
[Double
x] -> Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
x
[Double]
_ -> VLSpec
A.Null
densityPropertySpec DensityPropertyLabel
DPLExtent [DensityProperty]
ps =
let wanted :: DensityProperty -> Maybe [Double]
wanted (DnExtent Double
xs Double
ys) = [Double] -> Maybe [Double]
forall a. a -> Maybe a
Just [Double
xs, Double
ys]
wanted DensityProperty
_ = Maybe [Double]
forall a. Maybe a
Nothing
in case (DensityProperty -> Maybe [Double])
-> [DensityProperty] -> [[Double]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe [Double]
wanted [DensityProperty]
ps of
[[Double]
x] -> [Double] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Double]
x
[[Double]]
_ -> VLSpec
A.Null
densityPropertySpec DensityPropertyLabel
DPLMinsteps [DensityProperty]
ps =
let wanted :: DensityProperty -> Maybe ZIndex
wanted (DnMinSteps ZIndex
xs) = ZIndex -> Maybe ZIndex
forall a. a -> Maybe a
Just ZIndex
xs
wanted DensityProperty
_ = Maybe ZIndex
forall a. Maybe a
Nothing
in case (DensityProperty -> Maybe ZIndex) -> [DensityProperty] -> [ZIndex]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe ZIndex
wanted [DensityProperty]
ps of
[ZIndex
x] -> ZIndex -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON ZIndex
x
[ZIndex]
_ -> VLSpec
A.Null
densityPropertySpec DensityPropertyLabel
DPLMaxsteps [DensityProperty]
ps =
let wanted :: DensityProperty -> Maybe ZIndex
wanted (DnMaxSteps ZIndex
xs) = ZIndex -> Maybe ZIndex
forall a. a -> Maybe a
Just ZIndex
xs
wanted DensityProperty
_ = Maybe ZIndex
forall a. Maybe a
Nothing
in case (DensityProperty -> Maybe ZIndex) -> [DensityProperty] -> [ZIndex]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe ZIndex
wanted [DensityProperty]
ps of
[ZIndex
x] -> ZIndex -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON ZIndex
x
[ZIndex]
_ -> VLSpec
A.Null
densityPropertySpec DensityPropertyLabel
DPLSteps [DensityProperty]
ps =
let wanted :: DensityProperty -> Maybe ZIndex
wanted (DnSteps ZIndex
xs) = ZIndex -> Maybe ZIndex
forall a. a -> Maybe a
Just ZIndex
xs
wanted DensityProperty
_ = Maybe ZIndex
forall a. Maybe a
Nothing
in case (DensityProperty -> Maybe ZIndex) -> [DensityProperty] -> [ZIndex]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe ZIndex
wanted [DensityProperty]
ps of
[ZIndex
x] -> ZIndex -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON ZIndex
x
[ZIndex]
_ -> VLSpec
A.Null
densityPropertySpec DensityPropertyLabel
DPLAs [DensityProperty]
ps =
let wanted :: DensityProperty -> Maybe [Text]
wanted (DnAs Text
xs Text
ys) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text
xs, Text
ys]
wanted DensityProperty
_ = Maybe [Text]
forall a. Maybe a
Nothing
in case (DensityProperty -> Maybe [Text]) -> [DensityProperty] -> [[Text]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe [Text]
wanted [DensityProperty]
ps of
[[Text]
x] -> [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
x
[[Text]]
_ -> VLSpec
A.Null
density ::
FieldName
-> [DensityProperty]
-> BuildTransformSpecs
density :: Text -> [DensityProperty] -> BuildTransformSpecs
density Text
field [DensityProperty]
dps [TransformSpec]
ols =
let addField :: Text -> DensityPropertyLabel -> [a]
addField Text
n DensityPropertyLabel
p = case DensityPropertyLabel -> [DensityProperty] -> VLSpec
densityPropertySpec DensityPropertyLabel
p [DensityProperty]
dps of
VLSpec
A.Null -> []
VLSpec
x -> [ Text
n Text -> VLSpec -> a
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
x ]
ofields :: [LabelledSpec]
ofields = [ Text
"density" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
field ]
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> DensityPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> DensityPropertyLabel -> [a]
addField Text
"groupby" DensityPropertyLabel
DPLGroupby
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> DensityPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> DensityPropertyLabel -> [a]
addField Text
"cumulative" DensityPropertyLabel
DPLCumulative
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> DensityPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> DensityPropertyLabel -> [a]
addField Text
"counts" DensityPropertyLabel
DPLCounts
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> DensityPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> DensityPropertyLabel -> [a]
addField Text
"bandwidth" DensityPropertyLabel
DPLBandwidth
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> DensityPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> DensityPropertyLabel -> [a]
addField Text
"extent" DensityPropertyLabel
DPLExtent
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> DensityPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> DensityPropertyLabel -> [a]
addField Text
"minsteps" DensityPropertyLabel
DPLMinsteps
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> DensityPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> DensityPropertyLabel -> [a]
addField Text
"maxsteps" DensityPropertyLabel
DPLMaxsteps
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> DensityPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> DensityPropertyLabel -> [a]
addField Text
"steps" DensityPropertyLabel
DPLSteps
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> DensityPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> DensityPropertyLabel -> [a]
addField Text
"as" DensityPropertyLabel
DPLAs
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
ofields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
data LoessProperty
= LsAs FieldName FieldName
| LsBandwidth Double
| LsGroupBy [FieldName]
data LoessPropertyLabel = LLAs | LLBandwidth | LLGroupBy
loessPropertySpec :: LoessPropertyLabel -> [LoessProperty] -> VLSpec
loessPropertySpec :: LoessPropertyLabel -> [LoessProperty] -> VLSpec
loessPropertySpec LoessPropertyLabel
LLAs [LoessProperty]
ps =
let wanted :: LoessProperty -> Maybe [Text]
wanted (LsAs Text
xs Text
ys) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text
xs, Text
ys]
wanted LoessProperty
_ = Maybe [Text]
forall a. Maybe a
Nothing
in case (LoessProperty -> Maybe [Text]) -> [LoessProperty] -> [[Text]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe LoessProperty -> Maybe [Text]
wanted [LoessProperty]
ps of
[[Text]
x] -> [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
x
[[Text]]
_ -> VLSpec
A.Null
loessPropertySpec LoessPropertyLabel
LLBandwidth [LoessProperty]
ps =
let wanted :: LoessProperty -> Maybe Double
wanted (LsBandwidth Double
xs) = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
xs
wanted LoessProperty
_ = Maybe Double
forall a. Maybe a
Nothing
in case (LoessProperty -> Maybe Double) -> [LoessProperty] -> [Double]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe LoessProperty -> Maybe Double
wanted [LoessProperty]
ps of
[Double
x] -> Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
x
[Double]
_ -> VLSpec
A.Null
loessPropertySpec LoessPropertyLabel
LLGroupBy [LoessProperty]
ps =
let wanted :: LoessProperty -> Maybe [Text]
wanted (LsGroupBy [Text]
xs) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
xs
wanted LoessProperty
_ = Maybe [Text]
forall a. Maybe a
Nothing
in case (LoessProperty -> Maybe [Text]) -> [LoessProperty] -> [[Text]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe LoessProperty -> Maybe [Text]
wanted [LoessProperty]
ps of
[[Text]
x] -> [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
x
[[Text]]
_ -> VLSpec
A.Null
loess ::
FieldName
-> FieldName
-> [LoessProperty]
-> BuildTransformSpecs
loess :: Text -> Text -> [LoessProperty] -> BuildTransformSpecs
loess Text
depField Text
indField [LoessProperty]
lsp [TransformSpec]
ols =
let addField :: Text -> LoessPropertyLabel -> [a]
addField Text
n LoessPropertyLabel
p = case LoessPropertyLabel -> [LoessProperty] -> VLSpec
loessPropertySpec LoessPropertyLabel
p [LoessProperty]
lsp of
VLSpec
A.Null -> []
VLSpec
x -> [ Text
n Text -> VLSpec -> a
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
x ]
ofields :: [LabelledSpec]
ofields = [ Text
"loess" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
depField
, Text
"on" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
indField ]
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> LoessPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> LoessPropertyLabel -> [a]
addField Text
"groupby" LoessPropertyLabel
LLGroupBy
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> LoessPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> LoessPropertyLabel -> [a]
addField Text
"bandwidth" LoessPropertyLabel
LLBandwidth
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> LoessPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> LoessPropertyLabel -> [a]
addField Text
"as" LoessPropertyLabel
LLAs
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
ofields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
data RegressionMethod
= RgLinear
| RgLog
| RgExp
| RgPow
| RgQuad
| RgPoly
regressionMethodSpec :: RegressionMethod -> VLSpec
regressionMethodSpec :: RegressionMethod -> VLSpec
regressionMethodSpec RegressionMethod
RgLinear = Text -> VLSpec
fromT Text
"linear"
regressionMethodSpec RegressionMethod
RgLog = Text -> VLSpec
fromT Text
"log"
regressionMethodSpec RegressionMethod
RgExp = Text -> VLSpec
fromT Text
"exp"
regressionMethodSpec RegressionMethod
RgPow = Text -> VLSpec
fromT Text
"pow"
regressionMethodSpec RegressionMethod
RgQuad = Text -> VLSpec
fromT Text
"quad"
regressionMethodSpec RegressionMethod
RgPoly = Text -> VLSpec
fromT Text
"poly"
data RegressionProperty
= RgAs FieldName FieldName
| RgExtent Double Double
| RgGroupBy [FieldName]
| RgMethod RegressionMethod
| RgOrder Natural
| RgParams Bool
data RegressionPropertyLabel =
RPLAs | RPLExtent | RPLGroupBy | RPLMethod | RPLOrder | RPLParams
regressionPropertySpec :: RegressionPropertyLabel -> [RegressionProperty] -> VLSpec
regressionPropertySpec :: RegressionPropertyLabel -> [RegressionProperty] -> VLSpec
regressionPropertySpec RegressionPropertyLabel
RPLAs [RegressionProperty]
ps =
let wanted :: RegressionProperty -> Maybe [Text]
wanted (RgAs Text
xs Text
ys) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text
xs, Text
ys]
wanted RegressionProperty
_ = Maybe [Text]
forall a. Maybe a
Nothing
in case (RegressionProperty -> Maybe [Text])
-> [RegressionProperty] -> [[Text]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe [Text]
wanted [RegressionProperty]
ps of
[[Text]
x] -> [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
x
[[Text]]
_ -> VLSpec
A.Null
regressionPropertySpec RegressionPropertyLabel
RPLExtent [RegressionProperty]
ps =
let wanted :: RegressionProperty -> Maybe [Double]
wanted (RgExtent Double
xs Double
ys) = [Double] -> Maybe [Double]
forall a. a -> Maybe a
Just [Double
xs, Double
ys]
wanted RegressionProperty
_ = Maybe [Double]
forall a. Maybe a
Nothing
in case (RegressionProperty -> Maybe [Double])
-> [RegressionProperty] -> [[Double]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe [Double]
wanted [RegressionProperty]
ps of
[[Double]
x] -> [Double] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Double]
x
[[Double]]
_ -> VLSpec
A.Null
regressionPropertySpec RegressionPropertyLabel
RPLGroupBy [RegressionProperty]
ps =
let wanted :: RegressionProperty -> Maybe [Text]
wanted (RgGroupBy [Text]
xs) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
xs
wanted RegressionProperty
_ = Maybe [Text]
forall a. Maybe a
Nothing
in case (RegressionProperty -> Maybe [Text])
-> [RegressionProperty] -> [[Text]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe [Text]
wanted [RegressionProperty]
ps of
[[Text]
x] -> [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
x
[[Text]]
_ -> VLSpec
A.Null
regressionPropertySpec RegressionPropertyLabel
RPLMethod [RegressionProperty]
ps =
let wanted :: RegressionProperty -> Maybe RegressionMethod
wanted (RgMethod RegressionMethod
xs) = RegressionMethod -> Maybe RegressionMethod
forall a. a -> Maybe a
Just RegressionMethod
xs
wanted RegressionProperty
_ = Maybe RegressionMethod
forall a. Maybe a
Nothing
in case (RegressionProperty -> Maybe RegressionMethod)
-> [RegressionProperty] -> [RegressionMethod]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe RegressionMethod
wanted [RegressionProperty]
ps of
[RegressionMethod
x] -> RegressionMethod -> VLSpec
regressionMethodSpec RegressionMethod
x
[RegressionMethod]
_ -> VLSpec
A.Null
regressionPropertySpec RegressionPropertyLabel
RPLOrder [RegressionProperty]
ps =
let wanted :: RegressionProperty -> Maybe ZIndex
wanted (RgOrder ZIndex
xs) = ZIndex -> Maybe ZIndex
forall a. a -> Maybe a
Just ZIndex
xs
wanted RegressionProperty
_ = Maybe ZIndex
forall a. Maybe a
Nothing
in case (RegressionProperty -> Maybe ZIndex)
-> [RegressionProperty] -> [ZIndex]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe ZIndex
wanted [RegressionProperty]
ps of
[ZIndex
x] -> ZIndex -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON ZIndex
x
[ZIndex]
_ -> VLSpec
A.Null
regressionPropertySpec RegressionPropertyLabel
RPLParams [RegressionProperty]
ps =
let wanted :: RegressionProperty -> Maybe Bool
wanted (RgParams Bool
xs) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs
wanted RegressionProperty
_ = Maybe Bool
forall a. Maybe a
Nothing
in case (RegressionProperty -> Maybe Bool)
-> [RegressionProperty] -> [Bool]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe Bool
wanted [RegressionProperty]
ps of
[Bool
x] -> Bool -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Bool
x
[Bool]
_ -> VLSpec
A.Null
regression ::
FieldName
-> FieldName
-> [RegressionProperty]
-> BuildTransformSpecs
regression :: Text -> Text -> [RegressionProperty] -> BuildTransformSpecs
regression Text
depField Text
indField [RegressionProperty]
rps [TransformSpec]
ols =
let addField :: Text -> RegressionPropertyLabel -> [a]
addField Text
n RegressionPropertyLabel
p = case RegressionPropertyLabel -> [RegressionProperty] -> VLSpec
regressionPropertySpec RegressionPropertyLabel
p [RegressionProperty]
rps of
VLSpec
A.Null -> []
VLSpec
x -> [ Text
n Text -> VLSpec -> a
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
x ]
ofields :: [LabelledSpec]
ofields = [ Text
"regression" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
depField
, Text
"on" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
indField ]
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> RegressionPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> RegressionPropertyLabel -> [a]
addField Text
"groupby" RegressionPropertyLabel
RPLGroupBy
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> RegressionPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> RegressionPropertyLabel -> [a]
addField Text
"method" RegressionPropertyLabel
RPLMethod
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> RegressionPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> RegressionPropertyLabel -> [a]
addField Text
"order" RegressionPropertyLabel
RPLOrder
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> RegressionPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> RegressionPropertyLabel -> [a]
addField Text
"extent" RegressionPropertyLabel
RPLExtent
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> RegressionPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> RegressionPropertyLabel -> [a]
addField Text
"params" RegressionPropertyLabel
RPLParams
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> RegressionPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> RegressionPropertyLabel -> [a]
addField Text
"as" RegressionPropertyLabel
RPLAs
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
ofields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
data QuantileProperty
= QtAs FieldName FieldName
| QtGroupBy [FieldName]
| QtProbs [Double]
| QtStep Double
data QuantilePropertyLabel =
QPLAs | QPLGroupBy | QPLProbs | QPLStep
quantilePropertySpec :: QuantilePropertyLabel -> [QuantileProperty] -> VLSpec
quantilePropertySpec :: QuantilePropertyLabel -> [QuantileProperty] -> VLSpec
quantilePropertySpec QuantilePropertyLabel
QPLAs [QuantileProperty]
ps =
let wanted :: QuantileProperty -> Maybe [Text]
wanted (QtAs Text
xs Text
ys) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text
xs, Text
ys]
wanted QuantileProperty
_ = Maybe [Text]
forall a. Maybe a
Nothing
in case (QuantileProperty -> Maybe [Text])
-> [QuantileProperty] -> [[Text]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe QuantileProperty -> Maybe [Text]
wanted [QuantileProperty]
ps of
[[Text]
x] -> [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
x
[[Text]]
_ -> VLSpec
A.Null
quantilePropertySpec QuantilePropertyLabel
QPLGroupBy [QuantileProperty]
ps =
let wanted :: QuantileProperty -> Maybe [Text]
wanted (QtGroupBy [Text]
xs) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
xs
wanted QuantileProperty
_ = Maybe [Text]
forall a. Maybe a
Nothing
in case (QuantileProperty -> Maybe [Text])
-> [QuantileProperty] -> [[Text]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe QuantileProperty -> Maybe [Text]
wanted [QuantileProperty]
ps of
[[Text]
x] -> [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
x
[[Text]]
_ -> VLSpec
A.Null
quantilePropertySpec QuantilePropertyLabel
QPLProbs [QuantileProperty]
ps =
let wanted :: QuantileProperty -> Maybe [Double]
wanted (QtProbs [Double]
xs) = [Double] -> Maybe [Double]
forall a. a -> Maybe a
Just [Double]
xs
wanted QuantileProperty
_ = Maybe [Double]
forall a. Maybe a
Nothing
in case (QuantileProperty -> Maybe [Double])
-> [QuantileProperty] -> [[Double]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe QuantileProperty -> Maybe [Double]
wanted [QuantileProperty]
ps of
[[Double]
x] -> [Double] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Double]
x
[[Double]]
_ -> VLSpec
A.Null
quantilePropertySpec QuantilePropertyLabel
QPLStep [QuantileProperty]
ps =
let wanted :: QuantileProperty -> Maybe Double
wanted (QtStep Double
xs) = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
xs
wanted QuantileProperty
_ = Maybe Double
forall a. Maybe a
Nothing
in case (QuantileProperty -> Maybe Double)
-> [QuantileProperty] -> [Double]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe QuantileProperty -> Maybe Double
wanted [QuantileProperty]
ps of
[Double
x] -> Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Double
x
[Double]
_ -> VLSpec
A.Null
quantile ::
FieldName
-> [QuantileProperty]
-> BuildTransformSpecs
quantile :: Text -> [QuantileProperty] -> BuildTransformSpecs
quantile Text
field [QuantileProperty]
qps [TransformSpec]
ols =
let addField :: Text -> QuantilePropertyLabel -> [a]
addField Text
n QuantilePropertyLabel
p = case QuantilePropertyLabel -> [QuantileProperty] -> VLSpec
quantilePropertySpec QuantilePropertyLabel
p [QuantileProperty]
qps of
VLSpec
A.Null -> []
VLSpec
x -> [ Text
n Text -> VLSpec -> a
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
x ]
ofields :: [LabelledSpec]
ofields = [ Text
"quantile" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
field ]
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> QuantilePropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> QuantilePropertyLabel -> [a]
addField Text
"groupby" QuantilePropertyLabel
QPLGroupBy
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> QuantilePropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> QuantilePropertyLabel -> [a]
addField Text
"probs" QuantilePropertyLabel
QPLProbs
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> QuantilePropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> QuantilePropertyLabel -> [a]
addField Text
"step" QuantilePropertyLabel
QPLStep
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> QuantilePropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> QuantilePropertyLabel -> [a]
addField Text
"as" QuantilePropertyLabel
QPLAs
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
ofields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
binAs ::
[BinProperty]
-> FieldName
-> FieldName
-> BuildTransformSpecs
binAs :: [BinProperty] -> Text -> Text -> BuildTransformSpecs
binAs [BinProperty]
bProps Text
field Text
label [TransformSpec]
ols =
let fields :: [LabelledSpec]
fields = [ Text
"bin" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= if [BinProperty] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [BinProperty]
bProps then Bool -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON Bool
True else VLSpec
binObj
, Text
"field" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
field
, Text
"as" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
label ]
binObj :: VLSpec
binObj = [LabelledSpec] -> VLSpec
object ((BinProperty -> LabelledSpec) -> [BinProperty] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map BinProperty -> LabelledSpec
binProperty [BinProperty]
bProps)
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
fields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
calculateAs ::
VegaExpr
-> FieldName
-> BuildTransformSpecs
calculateAs :: Text -> Text -> BuildTransformSpecs
calculateAs Text
expr Text
label [TransformSpec]
ols =
let fields :: [LabelledSpec]
fields = [ Text
"calculate" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
expr, Text
"as" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
label ]
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
fields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
angle ::
[MarkChannel]
-> BuildEncodingSpecs
angle :: [MarkChannel] -> BuildEncodingSpecs
angle [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"angle" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
color ::
[MarkChannel]
-> BuildEncodingSpecs
color :: [MarkChannel] -> BuildEncodingSpecs
color [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"color" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
column ::
[FacetChannel]
-> BuildEncodingSpecs
column :: [FacetChannel] -> BuildEncodingSpecs
column [FacetChannel]
fFields [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"column", [LabelledSpec] -> VLSpec
object ((FacetChannel -> LabelledSpec) -> [FacetChannel] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> LabelledSpec
facetChannelProperty [FacetChannel]
fFields)) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
columns ::
Natural
-> PropertySpec
columns :: ZIndex -> PropertySpec
columns ZIndex
cols = (VLProperty
VLColumns, ZIndex -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON ZIndex
cols)
detail ::
[DetailChannel]
-> BuildEncodingSpecs
detail :: [DetailChannel] -> BuildEncodingSpecs
detail [DetailChannel]
detailProps [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"detail", [LabelledSpec] -> VLSpec
object ((DetailChannel -> LabelledSpec)
-> [DetailChannel] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map DetailChannel -> LabelledSpec
detailChannelProperty [DetailChannel]
detailProps)) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
fill ::
[MarkChannel]
-> BuildEncodingSpecs
fill :: [MarkChannel] -> BuildEncodingSpecs
fill [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"fill" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
fillOpacity :: [MarkChannel] -> BuildEncodingSpecs
fillOpacity :: [MarkChannel] -> BuildEncodingSpecs
fillOpacity [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"fillOpacity" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
filter :: Filter -> BuildTransformSpecs
filter :: Filter -> BuildTransformSpecs
filter Filter
f [TransformSpec]
ols = VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [ Text
"filter" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Filter -> VLSpec
filterSpec Filter
f ]) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
flatten :: [FieldName] -> BuildTransformSpecs
flatten :: [Text] -> BuildTransformSpecs
flatten [Text]
fields [TransformSpec]
ols = VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [ Text
"flatten" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
fields ]) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
flattenAs ::
[FieldName]
-> [FieldName]
-> BuildTransformSpecs
flattenAs :: [Text] -> [Text] -> BuildTransformSpecs
flattenAs [Text]
fields [Text]
names [TransformSpec]
ols =
let ofields :: [LabelledSpec]
ofields = [ Text
"flatten" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
fields, Text
"as" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
names ]
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
ofields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
fold ::
[FieldName]
-> BuildTransformSpecs
fold :: [Text] -> BuildTransformSpecs
fold [Text]
fields [TransformSpec]
ols = VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [ Text
"fold" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
fields ]) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
foldAs ::
[FieldName]
-> FieldName
-> FieldName
-> BuildTransformSpecs
foldAs :: [Text] -> Text -> Text -> BuildTransformSpecs
foldAs [Text]
fields Text
keyName Text
valName [TransformSpec]
ols =
let ofields :: [LabelledSpec]
ofields = [ Text
"fold" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
fields
, Text
"as" Text -> [Text] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [ Text
keyName, Text
valName ]
]
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
ofields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
pivot ::
FieldName
-> FieldName
-> [PivotProperty]
-> BuildTransformSpecs
pivot :: Text -> Text -> [PivotProperty] -> BuildTransformSpecs
pivot Text
field Text
valField [PivotProperty]
pProps [TransformSpec]
ols =
let addField :: Text -> PivotPropertyLabel -> [a]
addField Text
n PivotPropertyLabel
p = case PivotPropertyLabel -> [PivotProperty] -> VLSpec
pivotPropertySpec PivotPropertyLabel
p [PivotProperty]
pProps of
VLSpec
A.Null -> []
VLSpec
x -> [Text
n Text -> VLSpec -> a
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
x]
ofields :: [LabelledSpec]
ofields = [ Text
"pivot" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
field
, Text
"value" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
valField ]
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> PivotPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> PivotPropertyLabel -> [a]
addField Text
"groupby" PivotPropertyLabel
PPLGroupBy
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> PivotPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> PivotPropertyLabel -> [a]
addField Text
"limit" PivotPropertyLabel
PPLLimit
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> PivotPropertyLabel -> [LabelledSpec]
forall a. KeyValue a => Text -> PivotPropertyLabel -> [a]
addField Text
"op" PivotPropertyLabel
PPLOp
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
ofields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
data PivotProperty
= PiGroupBy [FieldName]
| PiLimit Natural
| PiOp Operation
data PivotPropertyLabel = PPLGroupBy | PPLLimit | PPLOp
pivotPropertySpec ::
PivotPropertyLabel
-> [PivotProperty]
-> VLSpec
pivotPropertySpec :: PivotPropertyLabel -> [PivotProperty] -> VLSpec
pivotPropertySpec PivotPropertyLabel
PPLGroupBy [PivotProperty]
ps =
let wanted :: PivotProperty -> Maybe [Text]
wanted (PiGroupBy [Text]
xs) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
xs
wanted PivotProperty
_ = Maybe [Text]
forall a. Maybe a
Nothing
in case (PivotProperty -> Maybe [Text]) -> [PivotProperty] -> [[Text]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe PivotProperty -> Maybe [Text]
wanted [PivotProperty]
ps of
[[Text]
x] -> [Text] -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
x
[[Text]]
_ -> VLSpec
A.Null
pivotPropertySpec PivotPropertyLabel
PPLLimit [PivotProperty]
ps =
let wanted :: PivotProperty -> Maybe ZIndex
wanted (PiLimit ZIndex
xs) = ZIndex -> Maybe ZIndex
forall a. a -> Maybe a
Just ZIndex
xs
wanted PivotProperty
_ = Maybe ZIndex
forall a. Maybe a
Nothing
in case (PivotProperty -> Maybe ZIndex) -> [PivotProperty] -> [ZIndex]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe PivotProperty -> Maybe ZIndex
wanted [PivotProperty]
ps of
[ZIndex
x] -> ZIndex -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON ZIndex
x
[ZIndex]
_ -> VLSpec
A.Null
pivotPropertySpec PivotPropertyLabel
PPLOp [PivotProperty]
ps =
let wanted :: PivotProperty -> Maybe Operation
wanted (PiOp Operation
xs) = Operation -> Maybe Operation
forall a. a -> Maybe a
Just Operation
xs
wanted PivotProperty
_ = Maybe Operation
forall a. Maybe a
Nothing
in case (PivotProperty -> Maybe Operation)
-> [PivotProperty] -> [Operation]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe PivotProperty -> Maybe Operation
wanted [PivotProperty]
ps of
[Operation
x] -> Operation -> VLSpec
operationSpec Operation
x
[Operation]
_ -> VLSpec
A.Null
url :: [HyperlinkChannel] -> BuildEncodingSpecs
url :: [HyperlinkChannel] -> BuildEncodingSpecs
url [HyperlinkChannel]
hPs [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"url", [LabelledSpec] -> VLSpec
object ((HyperlinkChannel -> [LabelledSpec])
-> [HyperlinkChannel] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap HyperlinkChannel -> [LabelledSpec]
hyperlinkChannelProperty [HyperlinkChannel]
hPs)) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
hyperlink ::
[HyperlinkChannel]
-> BuildEncodingSpecs
hyperlink :: [HyperlinkChannel] -> BuildEncodingSpecs
hyperlink [HyperlinkChannel]
hyperProps [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"href", [LabelledSpec] -> VLSpec
object ((HyperlinkChannel -> [LabelledSpec])
-> [HyperlinkChannel] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap HyperlinkChannel -> [LabelledSpec]
hyperlinkChannelProperty [HyperlinkChannel]
hyperProps)) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
lookup ::
FieldName
-> Data
-> FieldName
-> LookupFields
-> BuildTransformSpecs
lookup :: Text -> PropertySpec -> Text -> LookupFields -> BuildTransformSpecs
lookup Text
key1 (VLProperty
_, VLSpec
spec) Text
key2 LookupFields
lfields [TransformSpec]
ols =
let get1 :: [(Text, b)] -> Maybe VLSpec
get1 = [Text] -> Maybe VLSpec
forall a. ToJSON a => a -> Maybe VLSpec
jj ([Text] -> Maybe VLSpec)
-> ([(Text, b)] -> [Text]) -> [(Text, b)] -> Maybe VLSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text, b) -> Text) -> [(Text, b)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text, b) -> Text
forall a b. (a, b) -> a
fst
get2 :: [(a, Text)] -> Maybe VLSpec
get2 = [Text] -> Maybe VLSpec
forall a. ToJSON a => a -> Maybe VLSpec
jj ([Text] -> Maybe VLSpec)
-> ([(a, Text)] -> [Text]) -> [(a, Text)] -> Maybe VLSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, Text) -> Text) -> [(a, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (a, Text) -> Text
forall a b. (a, b) -> b
snd
jj :: A.ToJSON a => a -> Maybe A.Value
jj :: a -> Maybe VLSpec
jj = VLSpec -> Maybe VLSpec
forall a. a -> Maybe a
Just (VLSpec -> Maybe VLSpec) -> (a -> VLSpec) -> a -> Maybe VLSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON
res :: (Maybe VLSpec, Maybe VLSpec, Maybe VLSpec)
res = case LookupFields
lfields of
LuFields [Text]
fs -> ( [Text] -> Maybe VLSpec
forall a. ToJSON a => a -> Maybe VLSpec
jj [Text]
fs, Maybe VLSpec
forall a. Maybe a
Nothing, Maybe VLSpec
forall a. Maybe a
Nothing )
LuFieldAs [(Text, Text)]
fas -> ( [(Text, Text)] -> Maybe VLSpec
forall b. [(Text, b)] -> Maybe VLSpec
get1 [(Text, Text)]
fas, [(Text, Text)] -> Maybe VLSpec
forall a. [(a, Text)] -> Maybe VLSpec
get2 [(Text, Text)]
fas, Maybe VLSpec
forall a. Maybe a
Nothing )
LuAs Text
s -> ( Maybe VLSpec
forall a. Maybe a
Nothing, Text -> Maybe VLSpec
forall a. ToJSON a => a -> Maybe VLSpec
jj Text
s, Maybe VLSpec
forall a. Maybe a
Nothing )
LuFieldsWithDefault [Text]
fs Text
def
-> ( [Text] -> Maybe VLSpec
forall a. ToJSON a => a -> Maybe VLSpec
jj [Text]
fs, Maybe VLSpec
forall a. Maybe a
Nothing , Text -> Maybe VLSpec
forall a. ToJSON a => a -> Maybe VLSpec
jj Text
def )
LuFieldsAsWithDefault [(Text, Text)]
fas Text
def
-> ( [(Text, Text)] -> Maybe VLSpec
forall b. [(Text, b)] -> Maybe VLSpec
get1 [(Text, Text)]
fas, [(Text, Text)] -> Maybe VLSpec
forall a. [(a, Text)] -> Maybe VLSpec
get2 [(Text, Text)]
fas, Text -> Maybe VLSpec
forall a. ToJSON a => a -> Maybe VLSpec
jj Text
def )
LuAsWithDefault Text
s Text
def -> ( Maybe VLSpec
forall a. Maybe a
Nothing, Text -> Maybe VLSpec
forall a. ToJSON a => a -> Maybe VLSpec
jj Text
s, Text -> Maybe VLSpec
forall a. ToJSON a => a -> Maybe VLSpec
jj Text
def )
(Maybe VLSpec
mfields, Maybe VLSpec
mas, Maybe VLSpec
mdefault) = (Maybe VLSpec, Maybe VLSpec, Maybe VLSpec)
res
addField :: a -> Maybe b -> [(a, b)]
addField a
n (Just b
x) = [ (a
n, b
x) ]
addField a
_ Maybe b
_ = []
fromFields :: [LabelledSpec]
fromFields = [ Text
"data" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= VLSpec
spec
, Text
"key" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
key2
]
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe VLSpec -> [LabelledSpec]
forall a b. a -> Maybe b -> [(a, b)]
addField Text
"fields" Maybe VLSpec
mfields
ofields :: [LabelledSpec]
ofields = [ Text
"lookup" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
key1
, Text
"from" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [LabelledSpec]
fromFields
]
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe VLSpec -> [LabelledSpec]
forall a b. a -> Maybe b -> [(a, b)]
addField Text
"as" Maybe VLSpec
mas
[LabelledSpec] -> [LabelledSpec] -> [LabelledSpec]
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe VLSpec -> [LabelledSpec]
forall a b. a -> Maybe b -> [(a, b)]
addField Text
"default" Maybe VLSpec
mdefault
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
ofields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
lookupSelection ::
FieldName
-> SelectionLabel
-> FieldName
-> BuildTransformSpecs
lookupSelection :: Text -> Text -> Text -> BuildTransformSpecs
lookupSelection Text
key1 Text
selName Text
key2 [TransformSpec]
ols =
let ofields :: [LabelledSpec]
ofields = [ Text
"lookup" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
key1
, Text
"from" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [LabelledSpec] -> VLSpec
object [ Text
"selection" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
selName
, Text
"key" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
key2 ]
]
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
ofields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
data LookupFields
= LuFields [FieldName]
| LuFieldAs [(FieldName, FieldName)]
| LuAs FieldName
| LuFieldsWithDefault [FieldName] T.Text
| LuFieldsAsWithDefault [(FieldName, FieldName)] T.Text
| LuAsWithDefault FieldName T.Text
{-# DEPRECATED lookupAs "Please change 'lookupAs ... alias' to 'lookup ... (LuAs alias)'" #-}
lookupAs ::
FieldName
-> Data
-> FieldName
-> FieldName
-> BuildTransformSpecs
lookupAs :: Text -> PropertySpec -> Text -> Text -> BuildTransformSpecs
lookupAs Text
key1 PropertySpec
sData Text
key2 Text
asName =
Text -> PropertySpec -> Text -> LookupFields -> BuildTransformSpecs
lookup Text
key1 PropertySpec
sData Text
key2 (Text -> LookupFields
LuAs Text
asName)
impute ::
FieldName
-> FieldName
-> [ImputeProperty]
-> BuildTransformSpecs
impute :: Text -> Text -> [ImputeProperty] -> BuildTransformSpecs
impute Text
fields Text
keyField [ImputeProperty]
imProps [TransformSpec]
ols = Text -> Text -> [ImputeProperty] -> TransformSpec
imputeTS Text
fields Text
keyField [ImputeProperty]
imProps TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
opacity :: [MarkChannel] -> BuildEncodingSpecs
opacity :: [MarkChannel] -> BuildEncodingSpecs
opacity [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"opacity" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
order ::
[OrderChannel]
-> BuildEncodingSpecs
order :: [OrderChannel] -> BuildEncodingSpecs
order [OrderChannel]
oDefs [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"order", [LabelledSpec] -> VLSpec
object ((OrderChannel -> [LabelledSpec])
-> [OrderChannel] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap OrderChannel -> [LabelledSpec]
orderChannelProperty [OrderChannel]
oDefs)) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
position ::
Position
-> [PositionChannel]
-> BuildEncodingSpecs
position :: Position -> [PositionChannel] -> BuildEncodingSpecs
position Position
pos [PositionChannel]
pDefs [EncodingSpec]
ols =
let defs :: VLSpec
defs = [LabelledSpec] -> VLSpec
object ((PositionChannel -> LabelledSpec)
-> [PositionChannel] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map PositionChannel -> LabelledSpec
positionChannelProperty [PositionChannel]
pDefs)
in LabelledSpec -> EncodingSpec
ES (Position -> Text
positionLabel Position
pos, VLSpec
defs) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
resolution ::
Resolve
-> BuildResolveSpecs
resolution :: Resolve -> BuildResolveSpecs
resolution Resolve
res [ResolveSpec]
ols = Resolve -> ResolveSpec
resolveProperty Resolve
res ResolveSpec -> BuildResolveSpecs
forall a. a -> [a] -> [a]
: [ResolveSpec]
ols
row ::
[FacetChannel]
-> BuildEncodingSpecs
row :: [FacetChannel] -> BuildEncodingSpecs
row [FacetChannel]
fFields [EncodingSpec]
ols = LabelledSpec -> EncodingSpec
ES (Text
"row", [LabelledSpec] -> VLSpec
object ((FacetChannel -> LabelledSpec) -> [FacetChannel] -> [LabelledSpec]
forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> LabelledSpec
facetChannelProperty [FacetChannel]
fFields)) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
shape ::
[MarkChannel]
-> BuildEncodingSpecs
shape :: [MarkChannel] -> BuildEncodingSpecs
shape [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"shape" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
size ::
[MarkChannel]
-> BuildEncodingSpecs
size :: [MarkChannel] -> BuildEncodingSpecs
size [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"size" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
stroke ::
[MarkChannel]
-> BuildEncodingSpecs
stroke :: [MarkChannel] -> BuildEncodingSpecs
stroke [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"stroke" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
strokeDash ::
[MarkChannel]
-> BuildEncodingSpecs
strokeDash :: [MarkChannel] -> BuildEncodingSpecs
strokeDash [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"strokeDash" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
strokeOpacity ::
[MarkChannel]
-> BuildEncodingSpecs
strokeOpacity :: [MarkChannel] -> BuildEncodingSpecs
strokeOpacity [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"strokeOpacity" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
strokeWidth ::
[MarkChannel]
-> BuildEncodingSpecs
strokeWidth :: [MarkChannel] -> BuildEncodingSpecs
strokeWidth [MarkChannel]
markProps [EncodingSpec]
ols = Text -> [MarkChannel] -> EncodingSpec
mchan_ Text
"strokeWidth" [MarkChannel]
markProps EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
text ::
[TextChannel]
-> BuildEncodingSpecs
text :: [TextChannel] -> BuildEncodingSpecs
text [TextChannel]
tDefs [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"text", [LabelledSpec] -> VLSpec
object ((TextChannel -> [LabelledSpec]) -> [TextChannel] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TextChannel -> [LabelledSpec]
textChannelProperty [TextChannel]
tDefs)) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
timeUnitAs ::
TimeUnit
-> FieldName
-> FieldName
-> BuildTransformSpecs
timeUnitAs :: TimeUnit -> Text -> Text -> BuildTransformSpecs
timeUnitAs TimeUnit
tu Text
field Text
label [TransformSpec]
ols =
let fields :: [LabelledSpec]
fields = [ Text
"timeUnit" Text -> VLSpec -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= TimeUnit -> VLSpec
timeUnitSpec TimeUnit
tu
, Text
"field" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
field
, Text
"as" Text -> Text -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
label ]
in VLSpec -> TransformSpec
TS ([LabelledSpec] -> VLSpec
object [LabelledSpec]
fields) TransformSpec -> BuildTransformSpecs
forall a. a -> [a] -> [a]
: [TransformSpec]
ols
tooltip ::
[TextChannel]
-> BuildEncodingSpecs
tooltip :: [TextChannel] -> BuildEncodingSpecs
tooltip [] [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"tooltip", VLSpec
A.Null) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
tooltip [TextChannel]
tDefs [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"tooltip", [LabelledSpec] -> VLSpec
object ((TextChannel -> [LabelledSpec]) -> [TextChannel] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TextChannel -> [LabelledSpec]
textChannelProperty [TextChannel]
tDefs)) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
tooltips ::
[[TextChannel]]
-> BuildEncodingSpecs
tooltips :: [[TextChannel]] -> BuildEncodingSpecs
tooltips [[TextChannel]]
tDefs [EncodingSpec]
ols =
LabelledSpec -> EncodingSpec
ES (Text
"tooltip" Text -> [VLSpec] -> LabelledSpec
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ([TextChannel] -> VLSpec) -> [[TextChannel]] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map ([LabelledSpec] -> VLSpec
object ([LabelledSpec] -> VLSpec)
-> ([TextChannel] -> [LabelledSpec]) -> [TextChannel] -> VLSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextChannel -> [LabelledSpec]) -> [TextChannel] -> [LabelledSpec]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TextChannel -> [LabelledSpec]
textChannelProperty) [[TextChannel]]
tDefs) EncodingSpec -> BuildEncodingSpecs
forall a. a -> [a] -> [a]
: [EncodingSpec]
ols