{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
module Graphics.Vega.VegaLite
(
toVegaLite
, fromVL
, VLProperty
, VLSpec
, VegaLite
, LabelledSpec
, BuildLabelledSpecs
, combineSpecs
, dataFromUrl
, dataFromColumns
, dataFromRows
, dataFromJson
, dataFromSource
, datasets
, dataColumn
, dataRow
, geometry
, geoFeatureCollection
, geometryCollection
, Data
, DataColumn
, DataRow
, Format(..)
, Geometry(..)
, DataType(..)
, transform
, projection
, ProjectionProperty(..)
, Projection(..)
, ClipRect(..)
, aggregate
, Operation(..)
, opAs
, timeUnitAs
, binAs
, BinProperty(..)
, calculateAs
, filter
, Filter(..)
, FilterRange(..)
, lookup
, lookupAs
, mark
, Mark(..)
, MarkProperty(..)
, MarkOrientation(..)
, MarkInterpolation(..)
, Symbol(..)
, Cursor(..)
, encoding
, Measurement(..)
, position
, PositionChannel(..)
, Position(..)
, SortProperty(..)
, StackProperty(..)
, AxisProperty(..)
, OverlapStrategy(..)
, Side(..)
, HAlign(..)
, VAlign(..)
, FontWeight(..)
, TimeUnit(..)
, size
, color
, fill
, stroke
, opacity
, shape
, MarkChannel(..)
, LegendProperty(..)
, Legend(..)
, LegendOrientation(..)
, LegendValues(..)
, text
, tooltip
, TextChannel(..)
, hyperlink
, HyperlinkChannel(..)
, order
, OrderChannel(..)
, row
, column
, detail
, DetailChannel(..)
, ScaleProperty(..)
, Scale(..)
, categoricalDomainMap
, domainRangeMap
, ScaleDomain(..)
, ScaleRange(..)
, ScaleNice(..)
, CInterpolate(..)
, layer
, hConcat
, vConcat
, resolve
, resolution
, Resolve(..)
, Channel(..)
, Resolution(..)
, repeat
, RepeatFields(..)
, facet
, FacetMapping(..)
, FacetChannel(..)
, asSpec
, specification
, Arrangement(..)
, HeaderProperty(..)
, selection
, select
, Selection(..)
, SelectionProperty(..)
, Binding(..)
, InputProperty(..)
, SelectionResolution(..)
, SelectionMarkProperty(..)
, BooleanOp(..)
, name
, title
, description
, height
, width
, padding
, autosize
, background
, configure
, configuration
, ConfigurationProperty(..)
, Autosize(..)
, Padding(..)
, AxisConfig(..)
, LegendConfig(..)
, ScaleConfig(..)
, TitleConfig(..)
, APosition(..)
, ViewConfig(..)
, RangeConfig(..)
, FieldTitleProperty(..)
, DataValue(..)
, DataValues(..)
, DateTime(..)
, MonthName(..)
, DayName(..)
)
where
import Prelude hiding (filter, lookup, repeat)
import qualified Data.Aeson as A
import qualified Data.Text as T
import qualified Data.Vector as V
import Control.Arrow (first, second)
import Data.Aeson ((.=), Value, decode, encode, object, toJSON)
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Monoid ((<>))
aggregate_ :: Operation -> LabelledSpec
aggregate_ op = "aggregate" .= operationLabel op
field_ :: T.Text -> LabelledSpec
field_ f = "field" .= f
op_ :: Operation -> LabelledSpec
op_ op = "op" .= operationLabel op
repeat_ :: Arrangement -> LabelledSpec
repeat_ arr = "repeat" .= arrangementLabel arr
sort_ :: [SortProperty] -> LabelledSpec
sort_ ops = "sort" .= sortPropertySpec ops
timeUnit_ :: TimeUnit -> LabelledSpec
timeUnit_ tu = "timeUnit" .= timeUnitLabel tu
type_ :: Measurement -> LabelledSpec
type_ m = "type" .= measurementLabel m
value_ :: T.Text -> LabelledSpec
value_ v = "value" .= v
fromT :: T.Text -> VLSpec
fromT = toJSON
fromF :: Double -> VLSpec
fromF = toJSON
newtype VegaLite =
VL {
fromVL :: VLSpec
}
type VLSpec = Value
vlSchemaName :: T.Text
vlSchemaName = "https://vega.github.io/schema/vega-lite/v2.json"
toVegaLite :: [(VLProperty, VLSpec)] -> VegaLite
toVegaLite vals =
let kvals = ("$schema" .= vlSchemaName)
: map toProp vals
toProp = first vlPropertyLabel
in VL { fromVL = object kvals }
combineSpecs :: [LabelledSpec] -> VLSpec
combineSpecs = object
asSpec :: [(VLProperty, VLSpec)] -> VLSpec
asSpec = object . map (first vlPropertyLabel)
geoFeatureCollection :: [VLSpec] -> VLSpec
geoFeatureCollection geoms =
object [ "type" .= ("FeatureCollection" :: T.Text)
, "features" .= geoms
]
geometryCollection :: [VLSpec] -> VLSpec
geometryCollection geoms =
object [ "type" .= ("GeometryCollection" :: T.Text)
, "geometries" .= geoms
]
opAs ::
Operation
-> T.Text
-> T.Text
-> VLSpec
opAs op field label =
object [ op_ op
, field_ field
, "as" .= label
]
data VLProperty
= VLName
| VLDescription
| VLTitle
| VLWidth
| VLHeight
| VLAutosize
| VLPadding
| VLBackground
| VLData
| VLDatasets
| VLMark
| VLTransform
| VLProjection
| VLEncoding
| VLLayer
| VLHConcat
| VLVConcat
| VLRepeat
| VLFacet
| VLSpec
| VLResolve
| VLConfig
| VLSelection
vlPropertyLabel :: VLProperty -> T.Text
vlPropertyLabel VLName = "name"
vlPropertyLabel VLDescription = "description"
vlPropertyLabel VLTitle = "title"
vlPropertyLabel VLWidth = "width"
vlPropertyLabel VLHeight = "height"
vlPropertyLabel VLPadding = "padding"
vlPropertyLabel VLAutosize = "autosize"
vlPropertyLabel VLBackground = "background"
vlPropertyLabel VLData = "data"
vlPropertyLabel VLDatasets = "datasets"
vlPropertyLabel VLProjection = "projection"
vlPropertyLabel VLMark = "mark"
vlPropertyLabel VLTransform = "transform"
vlPropertyLabel VLEncoding = "encoding"
vlPropertyLabel VLConfig = "config"
vlPropertyLabel VLSelection = "selection"
vlPropertyLabel VLHConcat = "hconcat"
vlPropertyLabel VLVConcat = "vconcat"
vlPropertyLabel VLLayer = "layer"
vlPropertyLabel VLRepeat = "repeat"
vlPropertyLabel VLFacet = "facet"
vlPropertyLabel VLSpec = "spec"
vlPropertyLabel VLResolve = "resolve"
data DataType
= FoNumber
| FoBoolean
| FoDate T.Text
| FoUtc T.Text
data Format
= JSON T.Text
| CSV
| TSV
| TopojsonFeature T.Text
| TopojsonMesh T.Text
| Parse [(T.Text, DataType)]
type LabelledSpec = (T.Text, VLSpec)
type BuildLabelledSpecs = [LabelledSpec] -> [LabelledSpec]
type DataColumn = [LabelledSpec]
type DataRow = VLSpec
type Data = (VLProperty, VLSpec)
formatProperty :: Format -> [LabelledSpec]
formatProperty (JSON js) =
let ps = [("type", "json")]
<> if T.null (T.strip js) then [] else [("property", js)]
in map (second toJSON) ps
formatProperty CSV = [("type", "csv")]
formatProperty TSV = [("type", "tsv")]
formatProperty (TopojsonFeature os) = [ ("type", "topojson")
, ("feature", toJSON os) ]
formatProperty (TopojsonMesh os) = [ ("type", "topojson")
, ("mesh", toJSON os) ]
formatProperty (Parse fmts) =
let pObj = object (map (second dataTypeSpec) fmts)
in [("parse", pObj)]
dataTypeSpec :: DataType -> VLSpec
dataTypeSpec dType =
let s = case dType of
FoNumber -> "number"
FoBoolean -> "boolean"
FoDate fmt | T.null fmt -> "date"
| otherwise -> "date:'" <> fmt <> "'"
FoUtc fmt | T.null fmt -> "utc"
| otherwise -> "utc:'" <> fmt <> "'"
in toJSON s
dataRow :: [(T.Text, DataValue)] -> [DataRow] -> [DataRow]
dataRow rw = (object (map (second dataValueSpec) rw) :)
datasets :: [(T.Text, Data)] -> Data
datasets namedData =
let convert = extract . snd
specs = map (second convert) namedData
extract din =
let extract' :: [(T.Text, Value)] -> Value
extract' [(_, v)] = v
extract' _ = din
in maybe din extract' (decode (encode din))
in (VLDatasets, object specs)
dataFromColumns :: [Format] -> [DataColumn] -> Data
dataFromColumns fmts cols =
let dataArray = map object (transpose cols)
vals = [("values", toJSON dataArray)]
<> if null fmts
then []
else [("format", toJSON fmtObject)]
fmtObject = object (concatMap formatProperty fmts)
in (VLData, object vals)
transpose :: [[a]] -> [[a]]
transpose [] = []
transpose ([]:xss) = transpose xss
transpose ((x:xs) : xss) =
let heads = filterMap elmHead xss
tails = filterMap elmTail xss
elmHead (h:_) = Just h
elmHead [] = Nothing
elmTail [] = Nothing
elmTail (_:ts) = Just ts
filterMap = mapMaybe
in (x : heads) : transpose (xs : tails)
dataFromJson :: VLSpec -> [Format] -> Data
dataFromJson vlspec fmts =
let js = if null fmts
then object [("values", vlspec)]
else object [ ("values", vlspec)
, ("format",
object (concatMap formatProperty fmts)) ]
in (VLData, js)
data DataValue
= Boolean Bool
| DateTime [DateTime]
| Number Double
| Str T.Text
dataValueSpec :: DataValue -> VLSpec
dataValueSpec (Boolean b) = toJSON b
dataValueSpec (DateTime dt) = object (map dateTimeProperty dt)
dataValueSpec (Number x) = toJSON x
dataValueSpec (Str t) = toJSON t
data DataValues
= Booleans [Bool]
| DateTimes [[DateTime]]
| Numbers [Double]
| Strings [T.Text]
dataColumn :: T.Text -> DataValues -> [DataColumn] -> [DataColumn]
dataColumn colName dVals xs =
let col = case dVals of
Booleans cs -> map toJSON cs
DateTimes cs -> map dtToJSON cs
Numbers cs -> map toJSON cs
Strings cs -> map toJSON cs
dtToJSON = object . map dateTimeProperty
x = map (colName,) col
in x : xs
dataFromRows :: [Format] -> [DataRow] -> Data
dataFromRows fmts rows =
let kvs = ("values", toJSON rows)
: if null fmts
then []
else [("format", object (concatMap formatProperty fmts))]
in (VLData, object kvs)
dataFromSource :: T.Text -> [Format] -> Data
dataFromSource sourceName fmts =
let kvs = ("name" .= sourceName)
: if null fmts
then []
else [("format", object (concatMap formatProperty fmts))]
in (VLData, object kvs)
dataFromUrl :: T.Text -> [Format] -> Data
dataFromUrl url fmts =
let kvs = ("url" .= url)
: if null fmts
then []
else [("format", object (concatMap formatProperty fmts))]
in (VLData, object kvs)
data Mark
= Area
| Bar
| Circle
| Geoshape
| Line
| Point
| Rect
| Rule
| Square
| Text
| Tick
markLabel :: Mark -> T.Text
markLabel Area = "area"
markLabel Bar = "bar"
markLabel Circle = "circle"
markLabel Line = "line"
markLabel Geoshape = "geoshape"
markLabel Point = "point"
markLabel Rect = "rect"
markLabel Rule = "rule"
markLabel Square = "square"
markLabel Text = "text"
markLabel Tick = "tick"
mark :: Mark -> [MarkProperty] -> (VLProperty, VLSpec)
mark mrk props =
let jsName = toJSON (markLabel mrk)
vals = if null props
then jsName
else object (("type" .= jsName) : map markProperty props)
in (VLMark, vals)
data MarkChannel
= MName T.Text
| MRepeat Arrangement
| MmType Measurement
| MScale [ScaleProperty]
| MBin [BinProperty]
| MTimeUnit TimeUnit
| MAggregate Operation
| MLegend [LegendProperty]
| MSelectionCondition BooleanOp [MarkChannel] [MarkChannel]
| MDataCondition BooleanOp [MarkChannel] [MarkChannel]
| MPath T.Text
| MNumber Double
| MString T.Text
| MBoolean Bool
markChannelProperty :: MarkChannel -> [LabelledSpec]
markChannelProperty (MName s) = [field_ s]
markChannelProperty (MRepeat arr) = ["field" .= object [repeat_ arr]]
markChannelProperty (MmType t) = [type_ t]
markChannelProperty (MScale sps) =
[("scale", if null sps then A.Null else object (map scaleProperty sps))]
markChannelProperty (MLegend lps) =
[("legend", if null lps then A.Null else object (map legendProperty lps))]
markChannelProperty (MBin bps) = [bin bps]
markChannelProperty (MSelectionCondition selName ifClause elseClause) =
let h = ("condition", hkey)
toProps = concatMap markChannelProperty
hkey = object (("selection", booleanOpSpec selName) : toProps ifClause)
hs = toProps elseClause
in h : hs
markChannelProperty (MDataCondition predicate ifClause elseClause) =
let h = ("condition", hkey)
toProps = concatMap markChannelProperty
hkey = object (("test", booleanOpSpec predicate) : toProps ifClause)
hs = toProps elseClause
in h : hs
markChannelProperty (MTimeUnit tu) = [timeUnit_ tu]
markChannelProperty (MAggregate op) = [aggregate_ op]
markChannelProperty (MPath s) = ["value" .= s]
markChannelProperty (MNumber x) = ["value" .= x]
markChannelProperty (MString s) = ["value" .= s]
markChannelProperty (MBoolean b) = ["value" .= b]
data MarkProperty
= MAlign HAlign
| MAngle Double
| MBandSize Double
| MBaseline VAlign
| MBinSpacing Double
| MClip Bool
| MColor T.Text
| MCursor Cursor
| MContinuousBandSize Double
| MDiscreteBandSize Double
| MdX Double
| MdY Double
| MFill T.Text
| MFilled Bool
| MFillOpacity Double
| MFont T.Text
| MFontSize Double
| MFontStyle T.Text
| MFontWeight FontWeight
| MInterpolate MarkInterpolation
| MOpacity Double
| MOrient MarkOrientation
| MRadius Double
| MShape Symbol
| MShortTimeLabels Bool
| MSize Double
| MStroke T.Text
| MStrokeDash [Double]
| MStrokeDashOffset Double
| MStrokeOpacity Double
| MStrokeWidth Double
| MStyle [T.Text]
| MTension Double
| MText T.Text
| MTheta Double
| MThickness Double
markProperty :: MarkProperty -> LabelledSpec
markProperty (MFilled b) = ("filled", toJSON b)
markProperty (MClip b) = ("clip", toJSON b)
markProperty (MColor col) = ("color", toJSON col)
markProperty (MCursor cur) = ("cursor", toJSON (cursorLabel cur))
markProperty (MFill col) = ("fill", toJSON col)
markProperty (MStroke t) = ("stroke", toJSON t)
markProperty (MStrokeOpacity x) = ("strokeOpacity", toJSON x)
markProperty (MStrokeWidth w) = ("strokeWidth", toJSON w)
markProperty (MStrokeDash xs) = ("strokeDash", toJSON (map toJSON xs))
markProperty (MStrokeDashOffset x) = ("strokeDashOffset", toJSON x)
markProperty (MOpacity x) = ("opacity", toJSON x)
markProperty (MFillOpacity x) = ("fillOpacity", toJSON x)
markProperty (MStyle styles) = ("style", toJSON (map toJSON styles))
markProperty (MInterpolate interp) = ("interpolate", toJSON (markInterpolationLabel interp))
markProperty (MTension x) = ("tension", toJSON x)
markProperty (MOrient orient) = ("orient", toJSON (markOrientationLabel orient))
markProperty (MShape sym) = ("shape", toJSON (symbolLabel sym))
markProperty (MSize x) = ("size", toJSON x)
markProperty (MAngle x) = ("angle", toJSON x)
markProperty (MAlign align) = ("align", toJSON (hAlignLabel align))
markProperty (MBaseline va) = ("baseline", toJSON (vAlignLabel va))
markProperty (MdX dx) = ("dx", toJSON dx)
markProperty (MdY dy) = ("dy", toJSON dy)
markProperty (MFont fnt) = ("font", toJSON fnt)
markProperty (MFontSize x) = ("fontSize", toJSON x)
markProperty (MFontStyle fSty) = ("fontStyle", toJSON fSty)
markProperty (MFontWeight w) = ("fontWeight", fontWeightSpec w)
markProperty (MRadius x) = ("radius", toJSON x)
markProperty (MText txt) = ("text", toJSON txt)
markProperty (MTheta x) = ("theta", toJSON x)
markProperty (MBinSpacing x) = ("binSpacing", toJSON x)
markProperty (MContinuousBandSize x) = ("continuousBandSize", toJSON x)
markProperty (MDiscreteBandSize x) = ("discreteBandSize", toJSON x)
markProperty (MShortTimeLabels b) = ("shortTimeLabels", toJSON b)
markProperty (MBandSize x) = ("bandSize", toJSON x)
markProperty (MThickness x) = ("thickness", toJSON x)
encoding :: [LabelledSpec] -> (VLProperty, VLSpec)
encoding channels = (VLEncoding, object channels)
data Position
= X
| Y
| X2
| Y2
| Longitude
| Latitude
| Longitude2
| Latitude2
data Measurement
= Nominal
| Ordinal
| Quantitative
| Temporal
| GeoFeature
data BinProperty
= Base Double
| Divide Double Double
| Extent Double Double
| MaxBins Int
| MinStep Double
| Nice Bool
| Step Double
| Steps [Double]
binProperty :: BinProperty -> LabelledSpec
binProperty (MaxBins n) = ("maxbins", toJSON n)
binProperty (Base x) = ("base", toJSON x)
binProperty (Step x) = ("step", toJSON x)
binProperty (Steps xs) = ("steps", toJSON (map toJSON xs))
binProperty (MinStep x) = ("minstep", toJSON x)
binProperty (Divide x y) = ("divide", toJSON [ toJSON x, toJSON y ])
binProperty (Extent mn mx) = ("extent", toJSON [ toJSON mn, toJSON mx ])
binProperty (Nice b) = ("nice", toJSON b)
bin :: [BinProperty] -> LabelledSpec
bin bProps =
let ans = if null bProps
then toJSON True
else object (map binProperty bProps)
in ("bin", ans)
data Operation
= ArgMax
| ArgMin
| Average
| CI0
| CI1
| Count
| Distinct
| Max
| Mean
| Median
| Min
| Missing
| Q1
| Q3
| Stderr
| Stdev
| StdevP
| Sum
| Valid
| Variance
| VarianceP
operationLabel :: Operation -> T.Text
operationLabel ArgMax = "argmax"
operationLabel ArgMin = "argmin"
operationLabel Average = "average"
operationLabel CI0 = "ci0"
operationLabel CI1 = "ci1"
operationLabel Count = "count"
operationLabel Distinct = "distinct"
operationLabel Max = "max"
operationLabel Mean = "mean"
operationLabel Median = "median"
operationLabel Min = "min"
operationLabel Missing = "missing"
operationLabel Q1 = "q1"
operationLabel Q3 = "q3"
operationLabel Stderr = "stderr"
operationLabel Stdev = "stdev"
operationLabel StdevP = "stdevp"
operationLabel Sum = "sum"
operationLabel Valid = "valid"
operationLabel Variance = "variance"
operationLabel VarianceP = "variancep"
data Arrangement
= Column
| Row
arrangementLabel :: Arrangement -> T.Text
arrangementLabel Column = "column"
arrangementLabel Row = "row"
data StackProperty
= StZero
| StNormalize
| StCenter
| NoStack
stackProperty :: StackProperty -> LabelledSpec
stackProperty StZero = ("stack", "zero")
stackProperty StNormalize = ("stack", "normalize")
stackProperty StCenter = ("stack", "center")
stackProperty NoStack = ("stack", A.Null)
data ScaleProperty
= SType Scale
| SDomain ScaleDomain
| SRange ScaleRange
| SScheme T.Text [Double]
| SPadding Double
| SPaddingInner Double
| SPaddingOuter Double
| SRangeStep (Maybe Double)
| SRound Bool
| SClamp Bool
| SInterpolate CInterpolate
| SNice ScaleNice
| SZero Bool
| SReverse Bool
scaleProperty :: ScaleProperty -> LabelledSpec
scaleProperty (SType sType) = ("type", toJSON (scaleLabel sType))
scaleProperty (SDomain sdType) = ("domain", scaleDomainSpec sdType)
scaleProperty (SRange range) =
let js = case range of
RNumbers xs -> toJSON (map toJSON xs)
RStrings ss -> toJSON (map toJSON ss)
RName s -> toJSON s
in ("range", js)
scaleProperty (SScheme nme extent) = schemeProperty nme extent
scaleProperty (SPadding x) = ("padding", toJSON x)
scaleProperty (SPaddingInner x) = ("paddingInner", toJSON x)
scaleProperty (SPaddingOuter x) = ("paddingOuter", toJSON x)
scaleProperty (SRangeStep numOrNull) = ("rangeStep", maybe A.Null toJSON numOrNull)
scaleProperty (SRound b) = ("round", toJSON b)
scaleProperty (SClamp b) = ("clamp", toJSON b)
scaleProperty (SInterpolate interp) = ("interpolate", cInterpolateSpec interp)
scaleProperty (SNice ni) = ("nice", scaleNiceSpec ni)
scaleProperty (SZero b) = ("zero", toJSON b)
scaleProperty (SReverse b) = ("reverse", toJSON b)
schemeProperty :: T.Text -> [Double] -> LabelledSpec
schemeProperty nme extent =
let js = case extent of
[mn, mx] -> object ["name" .= nme, "extent" .= [mn, mx]]
_ -> toJSON nme
in ("scheme", js)
data Scale
= ScLinear
| ScPow
| ScSqrt
| ScLog
| ScTime
| ScUtc
| ScSequential
| ScOrdinal
| ScBand
| ScPoint
| ScBinLinear
| ScBinOrdinal
scaleLabel :: Scale -> T.Text
scaleLabel ScLinear = "linear"
scaleLabel ScPow = "pow"
scaleLabel ScSqrt = "sqrt"
scaleLabel ScLog = "log"
scaleLabel ScTime = "time"
scaleLabel ScUtc = "utc"
scaleLabel ScSequential = "sequential"
scaleLabel ScOrdinal = "ordinal"
scaleLabel ScBand = "band"
scaleLabel ScPoint = "point"
scaleLabel ScBinLinear = "bin-linear"
scaleLabel ScBinOrdinal = "bin-ordinal"
data ScaleDomain
= DNumbers [Double]
| DStrings [T.Text]
| DDateTimes [[DateTime]]
| DSelection T.Text
| Unaggregated
scaleDomainSpec :: ScaleDomain -> VLSpec
scaleDomainSpec (DNumbers nums) = toJSON (map toJSON nums)
scaleDomainSpec (DDateTimes dts) = toJSON (map (object . map dateTimeProperty) dts)
scaleDomainSpec (DStrings cats) = toJSON (map toJSON cats)
scaleDomainSpec (DSelection selName) = object ["selection" .= selName]
scaleDomainSpec Unaggregated = "unaggregated"
data ScaleNice
= NMillisecond
| NSecond
| NMinute
| NHour
| NDay
| NWeek
| NMonth
| NYear
| NInterval TimeUnit Int
| IsNice Bool
| NTickCount Int
scaleNiceSpec :: ScaleNice -> VLSpec
scaleNiceSpec NMillisecond = fromT "millisecond"
scaleNiceSpec NSecond = fromT "second"
scaleNiceSpec NMinute = fromT "minute"
scaleNiceSpec NHour = fromT "hour"
scaleNiceSpec NDay = fromT "day"
scaleNiceSpec NWeek = fromT "week"
scaleNiceSpec NMonth = fromT "month"
scaleNiceSpec NYear = fromT "year"
scaleNiceSpec (NInterval tu step) =
object ["interval" .= timeUnitLabel tu, "step" .= step]
scaleNiceSpec (IsNice b) = toJSON b
scaleNiceSpec (NTickCount n) = toJSON n
data ScaleRange
= RNumbers [Double]
| RStrings [T.Text]
| RName T.Text
data CInterpolate
= CubeHelix Double
| CubeHelixLong Double
| Hcl
| HclLong
| Hsl
| HslLong
| Lab
| Rgb Double
pairT :: T.Text -> T.Text -> (T.Text, Value)
pairT a b = a .= b
cInterpolateSpec :: CInterpolate -> VLSpec
cInterpolateSpec (Rgb gamma) = object [pairT "type" "rgb", "gamma" .= gamma]
cInterpolateSpec Hsl = object [pairT "type" "hsl"]
cInterpolateSpec HslLong = object [pairT "type" "hsl-long"]
cInterpolateSpec Lab = object [pairT "type" "lab"]
cInterpolateSpec Hcl = object [pairT "type" "hcl"]
cInterpolateSpec HclLong = object [pairT "type" "hcl-long"]
cInterpolateSpec (CubeHelix gamma) = object [pairT "type" "cubehelix", "gamma" .= gamma]
cInterpolateSpec (CubeHelixLong gamma) = object [pairT "type" "cubehelix-long", "gamma" .= gamma]
data SortProperty
= Ascending
| Descending
| Op Operation
| ByField T.Text
| ByRepeat Arrangement
sortProperty :: SortProperty -> LabelledSpec
sortProperty Ascending = "order" .= fromT "ascending"
sortProperty Descending = "order" .= fromT "descending"
sortProperty (ByField field) = field_ field
sortProperty (Op op) = op_ op
sortProperty (ByRepeat arr) = ("field", object [repeat_ arr])
sortPropertySpec :: [SortProperty] -> VLSpec
sortPropertySpec [] = A.Null
sortPropertySpec [Ascending] = fromT "ascending"
sortPropertySpec [Descending] = fromT "descending"
sortPropertySpec ops = object (map sortProperty ops)
data PositionChannel
= PName T.Text
| PRepeat Arrangement
| PmType Measurement
| PBin [BinProperty]
| PTimeUnit TimeUnit
| PAggregate Operation
| PScale [ScaleProperty]
| PAxis [AxisProperty]
| PSort [SortProperty]
| PStack StackProperty
positionChannelProperty :: PositionChannel -> LabelledSpec
positionChannelProperty (PName s) = field_ s
positionChannelProperty (PRepeat arr) = "field" .= object [repeat_ arr]
positionChannelProperty (PmType m) = type_ m
positionChannelProperty (PBin b) = bin b
positionChannelProperty (PTimeUnit tu) = timeUnit_ tu
positionChannelProperty (PAggregate op) = aggregate_ op
positionChannelProperty (PScale sps) =
let js = if null sps
then A.Null
else object (map scaleProperty sps)
in "scale" .= js
positionChannelProperty (PAxis aps) =
let js = if null aps
then A.Null
else object (map axisProperty aps)
in "axis" .= js
positionChannelProperty (PSort ops) = sort_ ops
positionChannelProperty (PStack sp) = stackProperty sp
measurementLabel :: Measurement -> T.Text
measurementLabel Nominal = "nominal"
measurementLabel Ordinal = "ordinal"
measurementLabel Quantitative = "quantitative"
measurementLabel Temporal = "temporal"
measurementLabel GeoFeature = "geojson"
positionLabel :: Position -> T.Text
positionLabel X = "x"
positionLabel Y = "y"
positionLabel X2 = "x2"
positionLabel Y2 = "y2"
positionLabel Longitude = "longitude"
positionLabel Latitude = "latitude"
positionLabel Longitude2 = "longitude2"
positionLabel Latitude2 = "latitude2"
background :: T.Text -> (VLProperty, VLSpec)
background colour = (VLBackground, toJSON colour)
description :: T.Text -> (VLProperty, VLSpec)
description s = (VLDescription, toJSON s)
title :: T.Text -> (VLProperty, VLSpec)
title s = (VLTitle, toJSON s)
data AxisProperty
= AxDomain Bool
| AxFormat T.Text
| AxGrid Bool
| AxLabelAngle Double
| AxLabelOverlap OverlapStrategy
| AxLabelPadding Double
| AxLabels Bool
| AxMaxExtent Double
| AxMinExtent Double
| AxOffset Double
| AxOrient Side
| AxPosition Double
| AxTicks Bool
| AxTickCount Int
| AxTickSize Double
| AxTitle T.Text
| AxTitleAlign HAlign
| AxTitleAngle Double
| AxTitleMaxLength Double
| AxTitlePadding Double
| AxValues [Double]
| AxDates [[DateTime]]
| AxZIndex Int
axisProperty :: AxisProperty -> LabelledSpec
axisProperty (AxFormat fmt) = "format" .= fmt
axisProperty (AxLabels b) = "labels" .= b
axisProperty (AxLabelAngle a) = "labelAngle" .= a
axisProperty (AxLabelOverlap s) = "labelOverlap" .= overlapStrategyLabel s
axisProperty (AxLabelPadding pad) = "labelPadding" .= pad
axisProperty (AxDomain b) = "domain" .= b
axisProperty (AxGrid b) = "grid" .= b
axisProperty (AxMaxExtent n) = "maxExtent" .= n
axisProperty (AxMinExtent n) = "minExtent" .= n
axisProperty (AxOrient side) = "orient" .= sideLabel side
axisProperty (AxOffset n) = "offset" .= n
axisProperty (AxPosition n) = "position" .= n
axisProperty (AxZIndex n) = "zindex" .= n
axisProperty (AxTicks b) = "ticks" .= b
axisProperty (AxTickCount n) = "tickCount" .= n
axisProperty (AxTickSize sz) = "tickSize" .= sz
axisProperty (AxValues vals) = "values" .= map toJSON vals
axisProperty (AxDates dtss) = "values" .= map (object . map dateTimeProperty) dtss
axisProperty (AxTitle ttl) = "title" .= ttl
axisProperty (AxTitleAlign align) = "titleAlign" .= hAlignLabel align
axisProperty (AxTitleAngle angle) = "titleAngle" .= angle
axisProperty (AxTitleMaxLength len) = "titleMaxLength" .= len
axisProperty (AxTitlePadding pad) = "titlePadding" .= pad
data HAlign
= AlignCenter
| AlignLeft
| AlignRight
data VAlign
= AlignTop
| AlignMiddle
| AlignBottom
hAlignLabel :: HAlign -> T.Text
hAlignLabel AlignLeft = "left"
hAlignLabel AlignCenter = "center"
hAlignLabel AlignRight = "right"
vAlignLabel :: VAlign -> T.Text
vAlignLabel AlignTop = "top"
vAlignLabel AlignMiddle = "middle"
vAlignLabel AlignBottom = "bottom"
data Side
= STop
| SBottom
| SLeft
| SRight
sideLabel :: Side -> T.Text
sideLabel STop = "top"
sideLabel SBottom = "bottom"
sideLabel SLeft = "left"
sideLabel SRight = "right"
data OverlapStrategy
= ONone
| OParity
| OGreedy
overlapStrategyLabel :: OverlapStrategy -> T.Text
overlapStrategyLabel ONone = "false"
overlapStrategyLabel OParity = "parity"
overlapStrategyLabel OGreedy = "greedy"
data DateTime
= DTYear Int
| DTQuarter Int
| DTMonth MonthName
| DTDate Int
| DTDay DayName
| DTHours Int
| DTMinutes Int
| DTSeconds Int
| DTMilliseconds Int
data DayName
= Mon
| Tue
| Wed
| Thu
| Fri
| Sat
| Sun
data MonthName
= Jan
| Feb
| Mar
| Apr
| May
| Jun
| Jul
| Aug
| Sep
| Oct
| Nov
| Dec
data TimeUnit
= Year
| YearQuarter
| YearQuarterMonth
| YearMonth
| YearMonthDate
| YearMonthDateHours
| YearMonthDateHoursMinutes
| YearMonthDateHoursMinutesSeconds
| Quarter
| QuarterMonth
| Month
| MonthDate
| Date
| Day
| Hours
| HoursMinutes
| HoursMinutesSeconds
| Minutes
| MinutesSeconds
| Seconds
| SecondsMilliseconds
| Milliseconds
| Utc TimeUnit
dateTimeProperty :: DateTime -> LabelledSpec
dateTimeProperty (DTYear y) = "year" .= y
dateTimeProperty (DTQuarter q) = "quarter" .= q
dateTimeProperty (DTMonth mon) = "month" .= monthNameLabel mon
dateTimeProperty (DTDate dt) = "date" .= dt
dateTimeProperty (DTDay day) = "day" .= dayLabel day
dateTimeProperty (DTHours h) = "hours" .= h
dateTimeProperty (DTMinutes m) = "minutes" .= m
dateTimeProperty (DTSeconds s) = "seconds" .= s
dateTimeProperty (DTMilliseconds ms) = "milliseconds" .= ms
dayLabel :: DayName -> T.Text
dayLabel Mon = "Mon"
dayLabel Tue = "Tue"
dayLabel Wed = "Wed"
dayLabel Thu = "Thu"
dayLabel Fri = "Fri"
dayLabel Sat = "Sat"
dayLabel Sun = "Sun"
monthNameLabel :: MonthName -> T.Text
monthNameLabel Jan = "Jan"
monthNameLabel Feb = "Feb"
monthNameLabel Mar = "Mar"
monthNameLabel Apr = "Apr"
monthNameLabel May = "May"
monthNameLabel Jun = "Jun"
monthNameLabel Jul = "Jul"
monthNameLabel Aug = "Aug"
monthNameLabel Sep = "Sep"
monthNameLabel Oct = "Oct"
monthNameLabel Nov = "Nov"
monthNameLabel Dec = "Dec"
timeUnitLabel :: TimeUnit -> T.Text
timeUnitLabel Year = "year"
timeUnitLabel YearQuarter = "yearquarter"
timeUnitLabel YearQuarterMonth = "yearquartermonth"
timeUnitLabel YearMonth = "yearmonth"
timeUnitLabel YearMonthDate = "yearmonthdate"
timeUnitLabel YearMonthDateHours = "yearmonthdatehours"
timeUnitLabel YearMonthDateHoursMinutes = "yearmonthdatehoursminutes"
timeUnitLabel YearMonthDateHoursMinutesSeconds = "yearmonthdatehoursminutesseconds"
timeUnitLabel Quarter = "quarter"
timeUnitLabel QuarterMonth = "quartermonth"
timeUnitLabel Month = "month"
timeUnitLabel MonthDate = "monthdate"
timeUnitLabel Date = "date"
timeUnitLabel Day = "day"
timeUnitLabel Hours = "hours"
timeUnitLabel HoursMinutes = "hoursminutes"
timeUnitLabel HoursMinutesSeconds = "hoursminutesseconds"
timeUnitLabel Minutes = "minutes"
timeUnitLabel MinutesSeconds = "minutesseconds"
timeUnitLabel Seconds = "seconds"
timeUnitLabel SecondsMilliseconds = "secondsmilliseconds"
timeUnitLabel Milliseconds = "milliseconds"
timeUnitLabel (Utc tu) = "utc" <> timeUnitLabel tu
data Cursor
= CAuto
| CDefault
| CNone
| CContextMenu
| CHelp
| CPointer
| CProgress
| CWait
| CCell
| CCrosshair
| CText
| CVerticalText
| CAlias
| CCopy
| CMove
| CNoDrop
| CNotAllowed
| CAllScroll
| CColResize
| CRowResize
| CNResize
| CEResize
| CSResize
| CWResize
| CNEResize
| CNWResize
| CSEResize
| CSWResize
| CEWResize
| CNSResize
| CNESWResize
| CNWSEResize
| CZoomIn
| CZoomOut
| CGrab
| CGrabbing
cursorLabel :: Cursor -> T.Text
cursorLabel CAuto = "auto"
cursorLabel CDefault = "default"
cursorLabel CNone = "none"
cursorLabel CContextMenu = "context-menu"
cursorLabel CHelp = "help"
cursorLabel CPointer = "pointer"
cursorLabel CProgress = "progress"
cursorLabel CWait = "wait"
cursorLabel CCell = "cell"
cursorLabel CCrosshair = "crosshair"
cursorLabel CText = "text"
cursorLabel CVerticalText = "vertical-text"
cursorLabel CAlias = "alias"
cursorLabel CCopy = "copy"
cursorLabel CMove = "move"
cursorLabel CNoDrop = "no-drop"
cursorLabel CNotAllowed = "not-allowed"
cursorLabel CAllScroll = "all-scroll"
cursorLabel CColResize = "col-resize"
cursorLabel CRowResize = "row-resize"
cursorLabel CNResize = "n-resize"
cursorLabel CEResize = "e-resize"
cursorLabel CSResize = "s-resize"
cursorLabel CWResize = "w-resize"
cursorLabel CNEResize = "ne-resize"
cursorLabel CNWResize = "nw-resize"
cursorLabel CSEResize = "se-resize"
cursorLabel CSWResize = "sw-resize"
cursorLabel CEWResize = "ew-resize"
cursorLabel CNSResize = "ns-resize"
cursorLabel CNESWResize = "nesw-resize"
cursorLabel CNWSEResize = "nwse-resize"
cursorLabel CZoomIn = "zoom-in"
cursorLabel CZoomOut = "zoom-out"
cursorLabel CGrab = "grab"
cursorLabel CGrabbing = "grabbing"
data FontWeight
= Bold
| Bolder
| Lighter
| Normal
| W100
| W200
| W300
| W400
| W500
| W600
| W700
| W800
| W900
fontWeightSpec :: FontWeight -> VLSpec
fontWeightSpec Bold = fromT "bold"
fontWeightSpec Bolder = fromT "bolder"
fontWeightSpec Lighter = fromT "lighter"
fontWeightSpec Normal = fromT "normal"
fontWeightSpec W100 = fromF 100
fontWeightSpec W200 = fromF 200
fontWeightSpec W300 = fromF 300
fontWeightSpec W400 = fromF 400
fontWeightSpec W500 = fromF 500
fontWeightSpec W600 = fromF 600
fontWeightSpec W700 = fromF 700
fontWeightSpec W800 = fromF 800
fontWeightSpec W900 = fromF 900
data MarkInterpolation
= Basis
| BasisClosed
| BasisOpen
| Bundle
| Cardinal
| CardinalClosed
| CardinalOpen
| Linear
| LinearClosed
| Monotone
| StepAfter
| StepBefore
| Stepwise
markInterpolationLabel :: MarkInterpolation -> T.Text
markInterpolationLabel Linear = "linear"
markInterpolationLabel LinearClosed = "linear-closed"
markInterpolationLabel Stepwise = "step"
markInterpolationLabel StepBefore = "step-before"
markInterpolationLabel StepAfter = "step-after"
markInterpolationLabel Basis = "basis"
markInterpolationLabel BasisOpen = "basis-open"
markInterpolationLabel BasisClosed = "basis-closed"
markInterpolationLabel Cardinal = "cardinal"
markInterpolationLabel CardinalOpen = "cardinal-open"
markInterpolationLabel CardinalClosed = "cardinal-closed"
markInterpolationLabel Bundle = "bundle"
markInterpolationLabel Monotone = "monotone"
data MarkOrientation
= Horizontal
| Vertical
markOrientationLabel :: MarkOrientation -> T.Text
markOrientationLabel Horizontal = "horizontal"
markOrientationLabel Vertical = "vertical"
data Symbol
= SymCircle
| SymSquare
| Cross
| Diamond
| TriangleUp
| TriangleDown
| Path T.Text
symbolLabel :: Symbol -> T.Text
symbolLabel SymCircle = "circle"
symbolLabel SymSquare = "square"
symbolLabel Cross = "cross"
symbolLabel Diamond = "diamond"
symbolLabel TriangleUp = "triangle-up"
symbolLabel TriangleDown = "triangle-down"
symbolLabel (Path svgPath) = svgPath
data Autosize
= AContent
| AFit
| ANone
| APad
| APadding
| AResize
autosizeProperty :: Autosize -> LabelledSpec
autosizeProperty APad = ("type", fromT "pad")
autosizeProperty AFit = ("type", fromT "fit")
autosizeProperty ANone = ("type", fromT "none")
autosizeProperty AResize = "resize".= True
autosizeProperty AContent = ("contains", fromT "content")
autosizeProperty APadding = ("contains", fromT "padding")
autosize :: [Autosize] -> (VLProperty, VLSpec)
autosize aus = (VLAutosize, object (map autosizeProperty aus))
data FieldTitleProperty
= Verbal
| Function
| Plain
fieldTitleLabel :: FieldTitleProperty -> T.Text
fieldTitleLabel Verbal = "verbal"
fieldTitleLabel Function = "function"
fieldTitleLabel Plain = "plain"
data Legend
= Gradient
| Symbol
legendLabel :: Legend -> T.Text
legendLabel Gradient = "gradient"
legendLabel Symbol = "symbol"
data LegendConfig
= CornerRadius Double
| FillColor T.Text
| Orient LegendOrientation
| Offset Double
| StrokeColor T.Text
| LeStrokeDash [Double]
| LeStrokeWidth Double
| LePadding Double
| GradientLabelBaseline VAlign
| GradientLabelLimit Double
| GradientLabelOffset Double
| GradientStrokeColor T.Text
| GradientStrokeWidth Double
| GradientHeight Double
| GradientWidth Double
| LeLabelAlign HAlign
| LeLabelBaseline VAlign
| LeLabelColor T.Text
| LeLabelFont T.Text
| LeLabelFontSize Double
| LeLabelLimit Double
| LeLabelOffset Double
| LeShortTimeLabels Bool
| EntryPadding Double
| SymbolColor T.Text
| SymbolType Symbol
| SymbolSize Double
| SymbolStrokeWidth Double
| LeTitleAlign HAlign
| LeTitleBaseline VAlign
| LeTitleColor T.Text
| LeTitleFont T.Text
| LeTitleFontSize Double
| LeTitleFontWeight FontWeight
| LeTitleLimit Double
| LeTitlePadding Double
legendConfigProperty :: LegendConfig -> LabelledSpec
legendConfigProperty (CornerRadius r) = "cornerRadius" .= r
legendConfigProperty (FillColor s) = "fillColor" .= s
legendConfigProperty (Orient orl) = "orient" .= legendOrientLabel orl
legendConfigProperty (Offset x) = "offset" .= x
legendConfigProperty (StrokeColor s) = "strokeColor" .= s
legendConfigProperty (LeStrokeDash xs) = "strokeDash" .= map toJSON xs
legendConfigProperty (LeStrokeWidth x) = "strokeWidth" .= x
legendConfigProperty (LePadding x) = "padding" .= x
legendConfigProperty (GradientLabelBaseline va) = "gradientLabelBaseline" .= vAlignLabel va
legendConfigProperty (GradientLabelLimit x) = "gradientLabelLimit" .= x
legendConfigProperty (GradientLabelOffset x) = "gradientLabelOffset" .= x
legendConfigProperty (GradientStrokeColor s) = "gradientStrokeColor" .= s
legendConfigProperty (GradientStrokeWidth x) = "gradientStrokeWidth" .= x
legendConfigProperty (GradientHeight x) = "gradientHeight" .= x
legendConfigProperty (GradientWidth x) = "gradientWidth" .= x
legendConfigProperty (LeLabelAlign ha) = "labelAlign" .= hAlignLabel ha
legendConfigProperty (LeLabelBaseline va) = "labelBaseline" .= vAlignLabel va
legendConfigProperty (LeLabelColor s) = "labelColor" .= s
legendConfigProperty (LeLabelFont s) = "labelFont" .= s
legendConfigProperty (LeLabelFontSize x) = "labelFontSize" .= x
legendConfigProperty (LeLabelLimit x) = "labelLimit" .= x
legendConfigProperty (LeLabelOffset x) = "labelOffset" .= x
legendConfigProperty (LeShortTimeLabels b) = "shortTimeLabels" .= b
legendConfigProperty (EntryPadding x) = "entryPadding" .= x
legendConfigProperty (SymbolColor s) = "symbolColor" .= s
legendConfigProperty (SymbolType s) = "symbolType" .= symbolLabel s
legendConfigProperty (SymbolSize x) = "symbolSize" .= x
legendConfigProperty (SymbolStrokeWidth x) = "symbolStrokeWidth" .= x
legendConfigProperty (LeTitleAlign ha) = "titleAlign" .= hAlignLabel ha
legendConfigProperty (LeTitleBaseline va) = "titleBaseline" .= vAlignLabel va
legendConfigProperty (LeTitleColor s) = "titleColor" .= s
legendConfigProperty (LeTitleFont s) = "titleFont" .= s
legendConfigProperty (LeTitleFontSize x) = "titleFontSize" .= x
legendConfigProperty (LeTitleFontWeight fw) = "titleFontWeight" .= fontWeightSpec fw
legendConfigProperty (LeTitleLimit x) = "titleLimit" .= x
legendConfigProperty (LeTitlePadding x) = "titlePadding" .= x
data LegendOrientation
= LOBottomLeft
| LOBottomRight
| LOLeft
| LONone
| LORight
| LOTopLeft
| LOTopRight
legendOrientLabel :: LegendOrientation -> T.Text
legendOrientLabel LOLeft = "left"
legendOrientLabel LOBottomLeft = "bottom-left"
legendOrientLabel LOBottomRight = "bottom-right"
legendOrientLabel LORight = "right"
legendOrientLabel LOTopLeft = "top-left"
legendOrientLabel LOTopRight = "top-right"
legendOrientLabel LONone = "none"
data LegendProperty
= LEntryPadding Double
| LFormat T.Text
| LOffset Double
| LOrient LegendOrientation
| LPadding Double
| LTickCount Double
| LTitle T.Text
| LType Legend
| LValues LegendValues
| LZIndex Int
legendProperty :: LegendProperty -> LabelledSpec
legendProperty (LType lType) = "type" .= legendLabel lType
legendProperty (LEntryPadding x) = "entryPadding" .= x
legendProperty (LFormat s) = "format" .= s
legendProperty (LOffset x) = "offset" .= x
legendProperty (LOrient orl) = "orient" .= legendOrientLabel orl
legendProperty (LPadding x) = "padding" .= x
legendProperty (LTickCount x) = "tickCount" .= x
legendProperty (LTitle ttl) = "title" .= if T.null ttl then A.Null else fromT ttl
legendProperty (LValues vals) =
let ls = case vals of
LNumbers xs -> map toJSON xs
LDateTimes dts -> map (object . map dateTimeProperty) dts
LStrings ss -> map toJSON ss
in "values" .= ls
legendProperty (LZIndex n) = "zindex" .= n
data LegendValues
= LDateTimes [[DateTime]]
| LNumbers [Double]
| LStrings [T.Text]
data Padding
= PSize Double
| PEdges Double Double Double Double
paddingSpec :: Padding -> VLSpec
paddingSpec (PSize p) = toJSON p
paddingSpec (PEdges l t r b) =
object [ "left" .= l
, "top" .= t
, "right" .= r
, "bottom" .= b
]
data Projection
= Albers
| AlbersUsa
| AzimuthalEqualArea
| AzimuthalEquidistant
| ConicConformal
| ConicEqualArea
| ConicEquidistant
| Custom T.Text
| Equirectangular
| Gnomonic
| Mercator
| Orthographic
| Stereographic
| TransverseMercator
projectionLabel :: Projection -> T.Text
projectionLabel Albers = "albers"
projectionLabel AlbersUsa = "albersUsa"
projectionLabel AzimuthalEqualArea = "azimuthalEqualArea"
projectionLabel AzimuthalEquidistant = "azimuthalEquidistant"
projectionLabel ConicConformal = "conicConformal"
projectionLabel ConicEqualArea = "conicEqualarea"
projectionLabel ConicEquidistant = "conicEquidistant"
projectionLabel (Custom pName) = pName
projectionLabel Equirectangular = "equirectangular"
projectionLabel Gnomonic = "gnomonic"
projectionLabel Mercator = "mercator"
projectionLabel Orthographic = "orthographic"
projectionLabel Stereographic = "stereographic"
projectionLabel TransverseMercator = "transverseMercator"
data ClipRect
= NoClip
| LTRB Double Double Double Double
data ProjectionProperty
= PType Projection
| PClipAngle (Maybe Double)
| PClipExtent ClipRect
| PCenter Double Double
| PRotate Double Double Double
| PPrecision Double
| PCoefficient Double
| PDistance Double
| PFraction Double
| PLobes Int
| PParallel Double
| PRadius Double
| PRatio Double
| PSpacing Double
| PTilt Double
projectionProperty :: ProjectionProperty -> LabelledSpec
projectionProperty (PType proj) = "type" .= projectionLabel proj
projectionProperty (PClipAngle numOrNull) = "clipAngle" .= maybe A.Null toJSON numOrNull
projectionProperty (PClipExtent rClip) =
("clipExtent", case rClip of
NoClip -> A.Null
LTRB l t r b -> toJSON (map toJSON [l, t, r, b])
)
projectionProperty (PCenter lon lat) = "center" .= map toJSON [lon, lat]
projectionProperty (PRotate lambda phi gamma) = "rotate" .= map toJSON [lambda, phi, gamma]
projectionProperty (PPrecision pr) = "precision" .= pr
projectionProperty (PCoefficient x) = "coefficient" .= x
projectionProperty (PDistance x) = "distance" .= x
projectionProperty (PFraction x) = "fraction" .= x
projectionProperty (PLobes n) = "lobes" .= n
projectionProperty (PParallel x) = "parallel" .= x
projectionProperty (PRadius x) = "radius" .= x
projectionProperty (PRatio x) = "ratio" .= x
projectionProperty (PSpacing x) = "spacing" .= x
projectionProperty (PTilt x) = "tilt" .= x
projection :: [ProjectionProperty] -> (VLProperty, VLSpec)
projection pProps = (VLProjection, object (map projectionProperty pProps))
data RangeConfig
= RCategory T.Text
| RDiverging T.Text
| RHeatmap T.Text
| ROrdinal T.Text
| RRamp T.Text
| RSymbol T.Text
rangeConfigProperty :: RangeConfig -> LabelledSpec
rangeConfigProperty rangeCfg =
let (l, n) = case rangeCfg of
RCategory nme -> ("category", nme)
RDiverging nme -> ("diverging", nme)
RHeatmap nme -> ("heatmap", nme)
ROrdinal nme -> ("ordinal", nme)
RRamp nme -> ("ramp", nme)
RSymbol nme -> ("symbol", nme)
in l .= object [schemeProperty n []]
data ScaleConfig
= SCBandPaddingInner Double
| SCBandPaddingOuter Double
| SCClamp Bool
| SCMaxBandSize Double
| SCMinBandSize Double
| SCMaxFontSize Double
| SCMinFontSize Double
| SCMaxOpacity Double
| SCMinOpacity Double
| SCMaxSize Double
| SCMinSize Double
| SCMaxStrokeWidth Double
| SCMinStrokeWidth Double
| SCPointPadding Double
| SCRangeStep (Maybe Double)
| SCRound Bool
| SCTextXRangeStep Double
| SCUseUnaggregatedDomain Bool
scaleConfigProperty :: ScaleConfig -> LabelledSpec
scaleConfigProperty (SCBandPaddingInner x) = "bandPaddingInner" .= x
scaleConfigProperty (SCBandPaddingOuter x) = "bandPaddingOuter" .= x
scaleConfigProperty (SCClamp b) = "clamp" .= b
scaleConfigProperty (SCMaxBandSize x) = "maxBandSize" .= x
scaleConfigProperty (SCMinBandSize x) = "minBandSize" .= x
scaleConfigProperty (SCMaxFontSize x) = "maxFontSize" .= x
scaleConfigProperty (SCMinFontSize x) = "minFontSize" .= x
scaleConfigProperty (SCMaxOpacity x) = "maxOpacity" .= x
scaleConfigProperty (SCMinOpacity x) = "minOpacity" .= x
scaleConfigProperty (SCMaxSize x) = "maxSize" .= x
scaleConfigProperty (SCMinSize x) = "minSize" .= x
scaleConfigProperty (SCMaxStrokeWidth x) = "maxStrokeWidth" .= x
scaleConfigProperty (SCMinStrokeWidth x) = "minStrokeWidth" .= x
scaleConfigProperty (SCPointPadding x) = "pointPadding" .= x
scaleConfigProperty (SCRangeStep numOrNull) = "rangeStep" .= maybe A.Null toJSON numOrNull
scaleConfigProperty (SCRound b) = "round" .= b
scaleConfigProperty (SCTextXRangeStep x) = "textXRangeStep" .= x
scaleConfigProperty (SCUseUnaggregatedDomain b) = "useUnaggregatedDomain" .= b
data Selection
= Single
| Multi
| Interval
selectionLabel :: Selection -> T.Text
selectionLabel Single = "single"
selectionLabel Multi = "multi"
selectionLabel Interval = "interval"
data SelectionProperty
= On T.Text
| Translate T.Text
| Zoom T.Text
| Fields [T.Text]
| Encodings [Channel]
| Empty
| ResolveSelections SelectionResolution
| SelectionMark [SelectionMarkProperty]
| BindScales
| Bind [Binding]
| Nearest Bool
| Toggle T.Text
selectionProperty :: SelectionProperty -> LabelledSpec
selectionProperty (Fields fNames) = "fields" .= map toJSON fNames
selectionProperty (Encodings channels) = "encodings" .= map (toJSON . channelLabel) channels
selectionProperty (On e) = "on" .= e
selectionProperty Empty = "empty" .= ("none" :: T.Text)
selectionProperty (ResolveSelections res) = "resolve" .= selectionResolutionLabel res
selectionProperty (SelectionMark markProps) = "mark" .= object (map selectionMarkProperty markProps)
selectionProperty BindScales = "bind" .= ("scales" :: T.Text)
selectionProperty (Bind binds) = "bind" .= object (map bindingSpec binds)
selectionProperty (Nearest b) = "nearest" .= b
selectionProperty (Toggle expr) = "toggle" .= expr
selectionProperty (Translate e) = "translate" .= if T.null e then toJSON False else toJSON e
selectionProperty (Zoom e) = "zoom" .= if T.null e then toJSON False else toJSON e
data Channel
= ChX
| ChY
| ChX2
| ChY2
| ChColor
| ChOpacity
| ChShape
| ChSize
channelLabel :: Channel -> T.Text
channelLabel ChX = "x"
channelLabel ChY = "y"
channelLabel ChX2 = "x2"
channelLabel ChY2 = "y2"
channelLabel ChColor = "color"
channelLabel ChOpacity = "opacity"
channelLabel ChShape = "shape"
channelLabel ChSize = "size"
data SelectionResolution
= Global
| Union
| Intersection
selectionResolutionLabel :: SelectionResolution -> T.Text
selectionResolutionLabel Global = "global"
selectionResolutionLabel Union = "union"
selectionResolutionLabel Intersection = "intersect"
data SelectionMarkProperty
= SMFill T.Text
| SMFillOpacity Double
| SMStroke T.Text
| SMStrokeOpacity Double
| SMStrokeWidth Double
| SMStrokeDash [Double]
| SMStrokeDashOffset Double
selectionMarkProperty :: SelectionMarkProperty -> LabelledSpec
selectionMarkProperty (SMFill colour) = "fill" .= colour
selectionMarkProperty (SMFillOpacity x) = "fillOpacity" .= x
selectionMarkProperty (SMStroke colour) = "stroke" .= colour
selectionMarkProperty (SMStrokeOpacity x) = "strokeOpacity" .= x
selectionMarkProperty (SMStrokeWidth x) = "strokeWidth" .= x
selectionMarkProperty (SMStrokeDash xs) = "strokeDash" .= map toJSON xs
selectionMarkProperty (SMStrokeDashOffset x) = "strokeDashOffset" .= x
data InputProperty
= Debounce Double
| Element T.Text
| InOptions [T.Text]
| InMin Double
| InMax Double
| InName T.Text
| InStep Double
| InPlaceholder T.Text
inputProperty :: InputProperty -> LabelledSpec
inputProperty (InMin x) = "min".= x
inputProperty (InMax x) = "max".= x
inputProperty (InStep x) = "step".= x
inputProperty (Debounce x) = "debounce".= x
inputProperty (InName s) = "name" .= s
inputProperty (InOptions opts) = "options" .= map toJSON opts
inputProperty (InPlaceholder el) = "placeholder" .= toJSON el
inputProperty (Element el) = "element" .= toJSON el
data Binding
= IRange T.Text [InputProperty]
| ICheckbox T.Text [InputProperty]
| IRadio T.Text [InputProperty]
| ISelect T.Text [InputProperty]
| IText T.Text [InputProperty]
| INumber T.Text [InputProperty]
| IDate T.Text [InputProperty]
| ITime T.Text [InputProperty]
| IMonth T.Text [InputProperty]
| IWeek T.Text [InputProperty]
| IDateTimeLocal T.Text [InputProperty]
| ITel T.Text [InputProperty]
| IColor T.Text [InputProperty]
bindingSpec :: Binding -> LabelledSpec
bindingSpec bnd =
let (lbl, input, ps) = case bnd of
IRange label props -> (label, "range" :: T.Text, props)
ICheckbox label props -> (label, "checkbox", props)
IRadio label props -> (label, "radio", props)
ISelect label props -> (label, "select", props)
IText label props -> (label, "text", props)
INumber label props -> (label, "number", props)
IDate label props -> (label, "date", props)
ITime label props -> (label, "time", props)
IMonth label props -> (label, "month", props)
IWeek label props -> (label, "week", props)
IDateTimeLocal label props -> (label, "datetimelocal", props)
ITel label props -> (label, "tel", props)
IColor label props -> (label, "color", props)
in (lbl, object (("input" .= input) : map inputProperty ps))
data APosition
= AStart
| AMiddle
| AEnd
anchorLabel :: APosition -> T.Text
anchorLabel AStart = "start"
anchorLabel AMiddle = "middle"
anchorLabel AEnd = "end"
data TitleConfig
= TAnchor APosition
| TAngle Double
| TBaseline VAlign
| TColor T.Text
| TFont T.Text
| TFontSize Double
| TFontWeight FontWeight
| TLimit Double
| TOffset Double
| TOrient Side
titleConfigSpec :: TitleConfig -> LabelledSpec
titleConfigSpec (TAnchor an) = "anchor" .= anchorLabel an
titleConfigSpec (TAngle x) = "angle" .= x
titleConfigSpec (TBaseline va) = "baseline" .= vAlignLabel va
titleConfigSpec (TColor clr) = "color" .= clr
titleConfigSpec (TFont fnt) = "font" .= fnt
titleConfigSpec (TFontSize x) = "fontSize" .= x
titleConfigSpec (TFontWeight w) = "fontWeight" .= fontWeightSpec w
titleConfigSpec (TLimit x) = "limit" .= x
titleConfigSpec (TOffset x) = "offset" .= x
titleConfigSpec (TOrient sd) = "orient" .= sideLabel sd
data ViewConfig
= ViewWidth Double
| ViewHeight Double
| Clip Bool
| Fill (Maybe T.Text)
| FillOpacity Double
| Stroke (Maybe T.Text)
| StrokeOpacity Double
| StrokeWidth Double
| StrokeDash [Double]
| StrokeDashOffset Double
viewConfigProperty :: ViewConfig -> LabelledSpec
viewConfigProperty (ViewWidth x) = "width" .= x
viewConfigProperty (ViewHeight x) = "height" .= x
viewConfigProperty (Clip b) = "clip" .= b
viewConfigProperty (Fill ms) = "fill" .= fromMaybe "" ms
viewConfigProperty (FillOpacity x) = "fillOpacity" .= x
viewConfigProperty (Stroke ms) = "stroke" .= fromMaybe "" ms
viewConfigProperty (StrokeOpacity x) = "strokeOpacity" .= x
viewConfigProperty (StrokeWidth x) = "strokeWidth" .= x
viewConfigProperty (StrokeDash xs) = "strokeDash" .= map toJSON xs
viewConfigProperty (StrokeDashOffset x) = "strokeDashOffset" .= x
data ConfigurationProperty
= AreaStyle [MarkProperty]
| Autosize [Autosize]
| Axis [AxisConfig]
| AxisX [AxisConfig]
| AxisY [AxisConfig]
| AxisLeft [AxisConfig]
| AxisRight [AxisConfig]
| AxisTop [AxisConfig]
| AxisBottom [AxisConfig]
| AxisBand [AxisConfig]
| Background T.Text
| BarStyle [MarkProperty]
| CircleStyle [MarkProperty]
| CountTitle T.Text
| FieldTitle FieldTitleProperty
| Legend [LegendConfig]
| LineStyle [MarkProperty]
| MarkStyle [MarkProperty]
| NamedStyle T.Text [MarkProperty]
| NumberFormat T.Text
| Padding Padding
| PointStyle [MarkProperty]
| Projection [ProjectionProperty]
| Range [RangeConfig]
| RectStyle [MarkProperty]
| RemoveInvalid Bool
| RuleStyle [MarkProperty]
| Scale [ScaleConfig]
| SelectionStyle [(Selection, [SelectionProperty])]
| SquareStyle [MarkProperty]
| Stack StackProperty
| TextStyle [MarkProperty]
| TickStyle [MarkProperty]
| TitleStyle [TitleConfig]
| TimeFormat T.Text
| View [ViewConfig]
configProperty :: ConfigurationProperty -> LabelledSpec
configProperty (Autosize aus) = "autosize" .= object (map autosizeProperty aus)
configProperty (Background bg) = "background" .= bg
configProperty (CountTitle ttl) = "countTitle" .= ttl
configProperty (FieldTitle ftp) = "fieldTitle" .= fieldTitleLabel ftp
configProperty (RemoveInvalid b) = "invalidValues" .= if b then "filter" else A.Null
configProperty (NumberFormat fmt) = "numberFormat" .= fmt
configProperty (Padding pad) = "padding" .= paddingSpec pad
configProperty (TimeFormat fmt) = "timeFormat" .= fmt
configProperty (Axis acs) = "axis" .= object (map axisConfigProperty acs)
configProperty (AxisX acs) = "axisX" .= object (map axisConfigProperty acs)
configProperty (AxisY acs) = "axisY" .= object (map axisConfigProperty acs)
configProperty (AxisLeft acs) = "axisLeft" .= object (map axisConfigProperty acs)
configProperty (AxisRight acs) = "axisRight" .= object (map axisConfigProperty acs)
configProperty (AxisTop acs) = "axisTop" .= object (map axisConfigProperty acs)
configProperty (AxisBottom acs) = "axisBottom" .= object (map axisConfigProperty acs)
configProperty (AxisBand acs) = "axisBand" .= object (map axisConfigProperty acs)
configProperty (Legend lcs) = "legend" .= object (map legendConfigProperty lcs)
configProperty (MarkStyle mps) = "mark" .= object (map markProperty mps)
configProperty (Projection pps) = "projection" .= object (map projectionProperty pps)
configProperty (AreaStyle mps) = "area" .= object (map markProperty mps)
configProperty (BarStyle mps) = "bar" .= object (map markProperty mps)
configProperty (CircleStyle mps) = "circle" .= object (map markProperty mps)
configProperty (LineStyle mps) = "line" .= object (map markProperty mps)
configProperty (PointStyle mps) = "point" .= object (map markProperty mps)
configProperty (RectStyle mps) = "rect" .= object (map markProperty mps)
configProperty (RuleStyle mps) = "rule" .= object (map markProperty mps)
configProperty (SquareStyle mps) = "square" .= object (map markProperty mps)
configProperty (TextStyle mps) = "text" .= object (map markProperty mps)
configProperty (TickStyle mps) = "tick" .= object (map markProperty mps)
configProperty (TitleStyle tcs) = "title" .= object (map titleConfigSpec tcs)
configProperty (NamedStyle nme mps) = "style" .= object [nme .= object (map markProperty mps)]
configProperty (Scale scs) = "scale" .= object (map scaleConfigProperty scs)
configProperty (Stack sp) = stackProperty sp
configProperty (Range rcs) = "range" .= object (map rangeConfigProperty rcs)
configProperty (SelectionStyle selConfig) =
let selProp (sel, sps) = selectionLabel sel .= object (map selectionProperty sps)
in "selection" .= object (map selProp selConfig)
configProperty (View vcs) = "view" .= object (map viewConfigProperty vcs)
data AxisConfig
= BandPosition Double
| Domain Bool
| DomainColor T.Text
| DomainWidth Double
| MaxExtent Double
| MinExtent Double
| Grid Bool
| GridColor T.Text
| GridDash [Double]
| GridOpacity Double
| GridWidth Double
| Labels Bool
| LabelAngle Double
| LabelColor T.Text
| LabelFont T.Text
| LabelFontSize Double
| LabelLimit Double
| LabelOverlap OverlapStrategy
| LabelPadding Double
| ShortTimeLabels Bool
| Ticks Bool
| TickColor T.Text
| TickRound Bool
| TickSize Double
| TickWidth Double
| TitleAlign HAlign
| TitleAngle Double
| TitleBaseline VAlign
| TitleColor T.Text
| TitleFont T.Text
| TitleFontWeight FontWeight
| TitleFontSize Double
| TitleLimit Double
| TitleMaxLength Double
| TitlePadding Double
| TitleX Double
| TitleY Double
axisConfigProperty :: AxisConfig -> LabelledSpec
axisConfigProperty (BandPosition x) = ("bandPosition", toJSON x)
axisConfigProperty (Domain b) = ("domain", toJSON b)
axisConfigProperty (DomainColor c) = ("domainColor", fromT c)
axisConfigProperty (DomainWidth w) = ("domainWidth", toJSON w)
axisConfigProperty (MaxExtent n) = ("maxExtent", toJSON n)
axisConfigProperty (MinExtent n) = ("minExtent", toJSON n)
axisConfigProperty (Grid b) = ("grid", toJSON b)
axisConfigProperty (GridColor c) = ("gridColor", fromT c)
axisConfigProperty (GridDash ds) = ("gridDash", toJSON (map toJSON ds))
axisConfigProperty (GridOpacity o) = ("gridOpacity", toJSON o)
axisConfigProperty (GridWidth x) = ("gridWidth", toJSON x)
axisConfigProperty (Labels b) = ("labels", toJSON b)
axisConfigProperty (LabelAngle angle) = ("labelAngle", toJSON angle)
axisConfigProperty (LabelColor c) = ("labelColor", fromT c)
axisConfigProperty (LabelFont f) = ("labelFont", fromT f)
axisConfigProperty (LabelFontSize x) = ("labelFontSize", toJSON x)
axisConfigProperty (LabelLimit x) = ("labelLimit", toJSON x)
axisConfigProperty (LabelOverlap strat) = ("labelOverlap", fromT (overlapStrategyLabel strat))
axisConfigProperty (LabelPadding pad) = ("labelPadding", toJSON pad)
axisConfigProperty (ShortTimeLabels b) = ("shortTimeLabels", toJSON b)
axisConfigProperty (Ticks b) = ("ticks", toJSON b)
axisConfigProperty (TickColor c) = ("tickColor", fromT c)
axisConfigProperty (TickRound b) = ("tickRound", toJSON b)
axisConfigProperty (TickSize x) = ("tickSize", toJSON x)
axisConfigProperty (TickWidth x) = ("tickWidth", toJSON x)
axisConfigProperty (TitleAlign align) = ("titleAlign", fromT (hAlignLabel align))
axisConfigProperty (TitleAngle angle) = ("titleAngle", toJSON angle)
axisConfigProperty (TitleBaseline va) = ("titleBaseline", fromT (vAlignLabel va))
axisConfigProperty (TitleColor c) = ("titleColor", fromT c)
axisConfigProperty (TitleFont f) = ("titleFont", fromT f)
axisConfigProperty (TitleFontWeight w) = ("titleFontWeight", fontWeightSpec w)
axisConfigProperty (TitleFontSize x) = ("titleFontSize", toJSON x)
axisConfigProperty (TitleLimit x) = ("titleLimit", toJSON x)
axisConfigProperty (TitleMaxLength x) = ("titleMaxLength", toJSON x)
axisConfigProperty (TitlePadding x) = ("titlePadding", toJSON x)
axisConfigProperty (TitleX x) = ("titleX", toJSON x)
axisConfigProperty (TitleY y) = ("titleY", toJSON y)
data BooleanOp
= Expr T.Text
| Selection T.Text
| SelectionName T.Text
| And BooleanOp BooleanOp
| Or BooleanOp BooleanOp
| Not BooleanOp
booleanOpSpec :: BooleanOp -> VLSpec
booleanOpSpec (Expr expr) = toJSON expr
booleanOpSpec (SelectionName selName) = toJSON selName
booleanOpSpec (Selection sel) = object ["selection" .= sel]
booleanOpSpec (And operand1 operand2) = object ["and" .= [booleanOpSpec operand1, booleanOpSpec operand2]]
booleanOpSpec (Or operand1 operand2) = object ["or" .= [booleanOpSpec operand1, booleanOpSpec operand2]]
booleanOpSpec (Not operand) = object ["not" .= booleanOpSpec operand]
data Filter
= FEqual T.Text DataValue
| FExpr T.Text
| FCompose BooleanOp
| FSelection T.Text
| FOneOf T.Text DataValues
| FRange T.Text FilterRange
data FilterRange
= NumberRange Double Double
| DateRange [DateTime] [DateTime]
data Geometry
= GeoPoint Double Double
| GeoPoints [(Double, Double)]
| GeoLine [(Double, Double)]
| GeoLines [[(Double, Double)]]
| GeoPolygon [[(Double, Double)]]
| GeoPolygons [[[(Double, Double)]]]
geometry :: Geometry -> [(T.Text, DataValue)] -> VLSpec
geometry gType properties =
object ([ ("type", fromT "Feature")
, ("geometry", geometryTypeSpec gType) ]
<> if null properties
then []
else [("properties",
object (map (second dataValueSpec) properties))]
)
geometryTypeSpec :: Geometry -> VLSpec
geometryTypeSpec gType =
let toCoords :: [(Double, Double)] -> VLSpec
toCoords = toJSON
toCoordList :: [[(Double, Double)]] -> VLSpec
toCoordList = toJSON . map toCoords
(ptype, cs) = case gType of
GeoPoint x y -> ("Point", toJSON [x, y])
GeoPoints coords -> ("MultiPoint", toCoords coords)
GeoLine coords -> ("LineString", toCoords coords)
GeoLines coords -> ("MultiLineString", toCoordList coords)
GeoPolygon coords -> ("Polygon", toCoordList coords)
GeoPolygons ccoords -> ("MultiPolygon", toJSON (map toCoordList ccoords))
in object [("type", ptype), ("coordinates", cs)]
data Resolution
= Shared
| Independent
resolutionLabel :: Resolution -> T.Text
resolutionLabel Shared = "shared"
resolutionLabel Independent = "independent"
data Resolve
= RAxis [(Channel, Resolution)]
| RLegend [(Channel, Resolution)]
| RScale [(Channel, Resolution)]
resolveProperty :: Resolve -> LabelledSpec
resolveProperty res =
let (nme, rls) = case res of
RAxis chRules -> ("axis", chRules)
RLegend chRules -> ("legend", chRules)
RScale chRules -> ("scale", chRules)
ans = map (\(ch, rule) -> (channelLabel ch .= resolutionLabel rule)) rls
in (nme, object ans)
data HeaderProperty
= HFormat T.Text
| HTitle T.Text
headerProperty :: HeaderProperty -> LabelledSpec
headerProperty (HFormat fmt) = "format" .= fmt
headerProperty (HTitle ttl) = "title" .= ttl
data HyperlinkChannel
= HName T.Text
| HRepeat Arrangement
| HmType Measurement
| HBin [BinProperty]
| HAggregate Operation
| HTimeUnit TimeUnit
| HSelectionCondition BooleanOp [HyperlinkChannel] [HyperlinkChannel]
| HDataCondition BooleanOp [HyperlinkChannel] [HyperlinkChannel]
| HString T.Text
hyperlinkChannelProperty :: HyperlinkChannel -> [LabelledSpec]
hyperlinkChannelProperty (HName s) = [field_ s]
hyperlinkChannelProperty (HRepeat arr) = ["field" .= object [repeat_ arr]]
hyperlinkChannelProperty (HmType t) = [type_ t]
hyperlinkChannelProperty (HBin bps) = [bin bps]
hyperlinkChannelProperty (HSelectionCondition selName ifClause elseClause) =
let h = ("condition", hkey)
toProps = concatMap hyperlinkChannelProperty
hkey = object (("selection", booleanOpSpec selName) : toProps ifClause)
hs = toProps elseClause
in h : hs
hyperlinkChannelProperty (HDataCondition predicate ifClause elseClause) =
let h = ("condition", hkey)
toProps = concatMap hyperlinkChannelProperty
hkey = object (("test", booleanOpSpec predicate) : toProps ifClause)
hs = toProps elseClause
in h : hs
hyperlinkChannelProperty (HTimeUnit tu) = [timeUnit_ tu]
hyperlinkChannelProperty (HAggregate op) = [aggregate_ op]
hyperlinkChannelProperty (HString s) = [value_ s]
domainRangeMap :: (Double, T.Text) -> (Double, T.Text) -> [ScaleProperty]
domainRangeMap lowerMap upperMap =
let (domain, range) = unzip [lowerMap, upperMap]
in [SDomain (DNumbers domain), SRange (RStrings range)]
categoricalDomainMap :: [(T.Text, T.Text)] -> [ScaleProperty]
categoricalDomainMap scaleDomainPairs =
let (domain, range) = unzip scaleDomainPairs
in [SDomain (DStrings domain), SRange (RStrings range)]
data RepeatFields
= RowFields [T.Text]
| ColumnFields [T.Text]
repeatFieldsProperty :: RepeatFields -> LabelledSpec
repeatFieldsProperty rfs =
let (nme, vs) = case rfs of
RowFields fields -> ("row", fields)
ColumnFields fields -> ("column", fields)
in nme .= map toJSON vs
data FacetChannel
= FName T.Text
| FmType Measurement
| FBin [BinProperty]
| FAggregate Operation
| FTimeUnit TimeUnit
| FHeader [HeaderProperty]
facetChannelProperty :: FacetChannel -> LabelledSpec
facetChannelProperty (FName s) = field_ s
facetChannelProperty (FmType measure) = type_ measure
facetChannelProperty (FBin bps) = bin bps
facetChannelProperty (FAggregate op) = aggregate_ op
facetChannelProperty (FTimeUnit tu) = timeUnit_ tu
facetChannelProperty (FHeader hProps) = "header" .= object (map headerProperty hProps)
data TextChannel
= TName T.Text
| TRepeat Arrangement
| TmType Measurement
| TBin [BinProperty]
| TAggregate Operation
| TTimeUnit TimeUnit
| TSelectionCondition BooleanOp [TextChannel] [TextChannel]
| TDataCondition BooleanOp [TextChannel] [TextChannel]
| TFormat T.Text
textChannelProperty :: TextChannel -> [LabelledSpec]
textChannelProperty (TName s) = [field_ s]
textChannelProperty (TRepeat arr) = ["field" .= object [repeat_ arr]]
textChannelProperty (TmType measure) = [type_ measure]
textChannelProperty (TBin bps) = [bin bps]
textChannelProperty (TAggregate op) = [aggregate_ op]
textChannelProperty (TTimeUnit tu) = [timeUnit_ tu]
textChannelProperty (TFormat fmt) = ["format" .= fmt]
textChannelProperty (TSelectionCondition selName ifClause elseClause) =
let h = ("condition", hkey)
toProps = concatMap textChannelProperty
hkey = object (("selection", booleanOpSpec selName) : toProps ifClause)
hs = toProps elseClause
in h : hs
textChannelProperty (TDataCondition predicate ifClause elseClause) =
let h = ("condition", hkey)
toProps = concatMap textChannelProperty
hkey = object (("test", booleanOpSpec predicate) : toProps ifClause)
hs = toProps elseClause
in h : hs
data OrderChannel
= OName T.Text
| ORepeat Arrangement
| OmType Measurement
| OBin [BinProperty]
| OAggregate Operation
| OTimeUnit TimeUnit
| OSort [SortProperty]
orderChannelProperty :: OrderChannel -> LabelledSpec
orderChannelProperty (OName s) = field_ s
orderChannelProperty (ORepeat arr) = "field" .= object [repeat_ arr]
orderChannelProperty (OmType measure) = type_ measure
orderChannelProperty (OBin bps) = bin bps
orderChannelProperty (OAggregate op) = aggregate_ op
orderChannelProperty (OTimeUnit tu) = timeUnit_ tu
orderChannelProperty (OSort ops) = sort_ ops
data DetailChannel
= DName T.Text
| DmType Measurement
| DBin [BinProperty]
| DTimeUnit TimeUnit
| DAggregate Operation
detailChannelProperty :: DetailChannel -> LabelledSpec
detailChannelProperty (DName s) = field_ s
detailChannelProperty (DmType t) = type_ t
detailChannelProperty (DBin bps) = bin bps
detailChannelProperty (DTimeUnit tu) = timeUnit_ tu
detailChannelProperty (DAggregate op) = aggregate_ op
data FacetMapping
= ColumnBy [FacetChannel]
| RowBy [FacetChannel]
facetMappingProperty :: FacetMapping -> LabelledSpec
facetMappingProperty (RowBy fFields) =
"row" .= object (map facetChannelProperty fFields)
facetMappingProperty (ColumnBy fFields) =
"column" .= object (map facetChannelProperty fFields)
configure :: [LabelledSpec] -> (VLProperty, VLSpec)
configure configs = (VLConfig, object configs)
facet :: [FacetMapping] -> (VLProperty, VLSpec)
facet fMaps = (VLFacet, object (map facetMappingProperty fMaps))
height :: Double -> (VLProperty, VLSpec)
height h = (VLHeight, toJSON h)
hConcat :: [VLSpec] -> (VLProperty, VLSpec)
hConcat specs = (VLHConcat, toJSON specs)
layer :: [VLSpec] -> (VLProperty, VLSpec)
layer specs = (VLLayer, toJSON specs)
name :: T.Text -> (VLProperty, VLSpec)
name s = (VLName, toJSON s)
padding :: Padding -> (VLProperty, VLSpec)
padding pad = (VLPadding, paddingSpec pad)
repeat :: [RepeatFields] -> (VLProperty, VLSpec)
repeat fields = (VLRepeat, object (map repeatFieldsProperty fields))
resolve :: [LabelledSpec] -> (VLProperty, VLSpec)
resolve res = (VLResolve, object res)
selection :: [LabelledSpec] -> (VLProperty, VLSpec)
selection sels = (VLSelection, object sels)
specification :: VLSpec -> (VLProperty, VLSpec)
specification spec = (VLSpec, spec)
transform :: [LabelledSpec] -> (VLProperty, VLSpec)
transform transforms =
let js = if null transforms then A.Null else toJSON (map assemble transforms)
assemble :: LabelledSpec -> VLSpec
assemble (str, val) =
let dval = decode (encode val)
in case str of
"aggregate" ->
case dval of
Just (A.Array vs) | V.length vs == 2 -> object [ ("aggregate", vs V.! 0)
, ("groupby", vs V.! 1) ]
_ -> A.Null
"bin" ->
case dval of
Just (A.Array vs) | V.length vs == 3 -> object [ ("bin", vs V.! 0)
, ("field", vs V.! 1)
, ("as", vs V.! 2) ]
_ -> A.Null
"calculate" ->
case dval of
Just (A.Array vs) | V.length vs == 2 -> object [ ("calculate", vs V.! 0)
, ("as", vs V.! 1) ]
_ -> A.Null
"lookup" ->
case dval of
Just (A.Array vs) | V.length vs == 4 -> object [ ("lookup", vs V.! 0)
, ("from",
object [ ("data", vs V.! 1)
, ("key", vs V.! 2)
, ("fields", vs V.! 3) ] )
]
_ -> A.Null
"lookupAs" ->
case dval of
Just (A.Array vs) | V.length vs == 4 -> object [ ("lookup", vs V.! 0)
, ("from",
object [ ("data", vs V.! 1)
, ("key", vs V.! 2) ] )
, ("as", vs V.! 3) ]
_ -> A.Null
"timeUnit" ->
case dval of
Just (A.Array vs) | V.length vs == 3 -> object [ ("timeUnit", vs V.! 0)
, ("field", vs V.! 1)
, ("as", vs V.! 2) ]
_ -> A.Null
_ -> object [(str, val)]
in (VLTransform, js)
vConcat :: [VLSpec] -> (VLProperty, VLSpec)
vConcat specs = (VLVConcat, toJSON specs)
width :: Double -> (VLProperty, VLSpec)
width w = (VLWidth, toJSON w)
aggregate ::
[VLSpec]
-> [T.Text]
-> BuildLabelledSpecs
aggregate ops groups ols =
let ags = toJSON [toJSON ops, toJSON (map toJSON groups)]
in ("aggregate", ags) : ols
binAs ::
[BinProperty]
-> T.Text
-> T.Text
-> BuildLabelledSpecs
binAs bProps field label ols =
let js = if null bProps
then [toJSON True, toJSON field, toJSON label]
else [object (map binProperty bProps), toJSON field, toJSON label]
in ("bin" .= js) : ols
calculateAs ::
T.Text
-> T.Text
-> BuildLabelledSpecs
calculateAs expr label ols = ("calculate" .= [expr, label]) : ols
color ::
[MarkChannel]
-> BuildLabelledSpecs
color markProps ols =
let cs = object (concatMap markChannelProperty markProps)
in ("color", cs) : ols
column ::
[FacetChannel]
-> BuildLabelledSpecs
column fFields ols =
("column" .= object (map facetChannelProperty fFields)) : ols
configuration :: ConfigurationProperty -> BuildLabelledSpecs
configuration cfg ols = configProperty cfg : ols
detail :: [DetailChannel] -> BuildLabelledSpecs
detail detailProps ols =
("detail" .= object (map detailChannelProperty detailProps)) : ols
fill :: [MarkChannel] -> BuildLabelledSpecs
fill markProps ols =
("fill" .= object (concatMap markChannelProperty markProps)) : ols
filter :: Filter -> BuildLabelledSpecs
filter f ols =
let js = case f of
FExpr expr -> toJSON expr
FCompose boolExpr -> booleanOpSpec boolExpr
FEqual field val -> object [field_ field, "equal" .= dataValueSpec val]
FSelection selName -> object ["selection" .= selName]
FRange field vals ->
let ans = case vals of
NumberRange mn mx -> map toJSON [mn, mx]
DateRange dMin dMax ->
[ object (map dateTimeProperty dMin)
, object (map dateTimeProperty dMax)
]
in object [field_ field, "range" .= ans]
FOneOf field vals ->
let ans = case vals of
Numbers xs -> map toJSON xs
DateTimes dts -> map (object . map dateTimeProperty) dts
Strings ss -> map toJSON ss
Booleans bs -> map toJSON bs
in object [field_ field, "oneOf" .= ans]
in ("filter", js) : ols
hyperlink :: [HyperlinkChannel] -> BuildLabelledSpecs
hyperlink hyperProps ols =
("href" .= object (concatMap hyperlinkChannelProperty hyperProps)) : ols
lookup ::
T.Text
-> Data
-> T.Text
-> [T.Text]
-> BuildLabelledSpecs
lookup key1 (_, spec) key2 fields ols =
let js = [toJSON key1, spec, toJSON key2, toJSON (map toJSON fields)]
in ("lookup" .= js) : ols
lookupAs ::
T.Text
-> Data
-> T.Text
-> T.Text
-> BuildLabelledSpecs
lookupAs key1 (_, spec) key2 asName ols =
("lookupAs" .= [toJSON key1, spec, toJSON key2, toJSON asName]) : ols
opacity :: [MarkChannel] -> BuildLabelledSpecs
opacity markProps ols =
("opacity" .= object (concatMap markChannelProperty markProps)) : ols
order :: [OrderChannel] -> BuildLabelledSpecs
order oDefs ols =
("order" .= object (map orderChannelProperty oDefs)) : ols
position ::
Position
-> [PositionChannel]
-> BuildLabelledSpecs
position pos pDefs ols =
let defs = object (map positionChannelProperty pDefs)
in (positionLabel pos, defs) : ols
resolution :: Resolve -> BuildLabelledSpecs
resolution res ols = resolveProperty res : ols
row ::
[FacetChannel]
-> BuildLabelledSpecs
row fFields ols = ("row" .= object (map facetChannelProperty fFields)) : ols
select ::
T.Text
-> Selection
-> [SelectionProperty]
-> BuildLabelledSpecs
select nme sType options ols =
let selProps = ("type" .= selectionLabel sType) : map selectionProperty options
in (nme .= object selProps) : ols
shape ::
[MarkChannel]
-> BuildLabelledSpecs
shape markProps ols = ("shape" .= object (concatMap markChannelProperty markProps)) : ols
size ::
[MarkChannel]
-> BuildLabelledSpecs
size markProps ols = ("size" .= object (concatMap markChannelProperty markProps)) : ols
stroke ::
[MarkChannel]
-> BuildLabelledSpecs
stroke markProps ols =
("stroke" .= object (concatMap markChannelProperty markProps)) : ols
text ::
[TextChannel]
-> BuildLabelledSpecs
text tDefs ols =
("text" .= object (concatMap textChannelProperty tDefs)) : ols
timeUnitAs ::
TimeUnit
-> T.Text
-> T.Text
-> BuildLabelledSpecs
timeUnitAs tu field label ols =
("timeUnit" .= [timeUnitLabel tu, field, label]) : ols
tooltip ::
[TextChannel]
-> BuildLabelledSpecs
tooltip tDefs ols =
("tooltip" .= object (concatMap textChannelProperty tDefs)) : ols