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