{-# LANGUAGE OverloadedStrings #-}
module Graphics.Vega.VegaLite.Configuration
( ConfigurationProperty(..)
, FieldTitleProperty(..)
, ViewConfig(..)
, FacetConfig(..)
, ConcatConfig(..)
, ScaleConfig(..)
, RangeConfig(..)
, AxisConfig(..)
, LegendConfig(..)
, TitleConfig(..)
, TitleFrame(..)
, configuration
, title
) where
import qualified Data.Aeson as A
import qualified Data.Text as T
import Data.Aeson ((.=), object)
import Graphics.Vega.VegaLite.Core
( schemeProperty
)
import Graphics.Vega.VegaLite.Foundation
( Angle
, Color
, CompositionAlignment
, DashStyle
, DashOffset
, APosition
, FontWeight
, Opacity
, Orientation
, OverlapStrategy
, Side
, StrokeCap
, StrokeJoin
, Symbol
, HAlign
, VAlign
, BandAlign
, Padding
, Autosize
, ZIndex
, HeaderProperty
, ViewBackground
, fromColor
, fromDS
, splitOnNewline
, header_
, anchorLabel
, fontWeightSpec
, orientationSpec
, hAlignLabel
, vAlignLabel
, bandAlignLabel
, strokeCapLabel
, strokeJoinLabel
, sideLabel
, overlapStrategyLabel
, symbolLabel
, compositionAlignmentSpec
, paddingSpec
, autosizeProperty
, viewBackgroundSpec
)
import Graphics.Vega.VegaLite.Geometry
( ProjectionProperty
, projectionProperty
)
import Graphics.Vega.VegaLite.Legend
( LegendLayout
, LegendOrientation
, legendOrientLabel
, legendLayoutSpec
)
import Graphics.Vega.VegaLite.Mark
( MarkProperty
, mprops_
)
import Graphics.Vega.VegaLite.Selection
( Selection
, SelectionProperty
, selectionProperties
, selectionLabel
)
import Graphics.Vega.VegaLite.Specification
( VLSpec
, VLProperty(VLTitle)
, ConfigureSpec(..)
, BuildConfigureSpecs
, LabelledSpec
, PropertySpec
)
data ConfigurationProperty
= AreaStyle [MarkProperty]
| Autosize [Autosize]
| Axis [AxisConfig]
| AxisBand [AxisConfig]
| AxisBottom [AxisConfig]
| AxisLeft [AxisConfig]
| AxisRight [AxisConfig]
| AxisTop [AxisConfig]
| AxisX [AxisConfig]
| AxisY [AxisConfig]
| Background Color
| BarStyle [MarkProperty]
| CircleStyle [MarkProperty]
| ConcatStyle [ConcatConfig]
| CountTitle T.Text
| FacetStyle [FacetConfig]
| FieldTitle FieldTitleProperty
| GeoshapeStyle [MarkProperty]
| HeaderStyle [HeaderProperty]
| Legend [LegendConfig]
| LineStyle [MarkProperty]
| MarkStyle [MarkProperty]
| NamedStyle T.Text [MarkProperty]
| NamedStyles [(T.Text, [MarkProperty])]
| NumberFormat T.Text
| Padding Padding
| PointStyle [MarkProperty]
| Projection [ProjectionProperty]
| Range [RangeConfig]
| RectStyle [MarkProperty]
| RuleStyle [MarkProperty]
| Scale [ScaleConfig]
| SelectionStyle [(Selection, [SelectionProperty])]
| SquareStyle [MarkProperty]
| TextStyle [MarkProperty]
| TickStyle [MarkProperty]
| TimeFormat T.Text
| TitleStyle [TitleConfig]
| TrailStyle [MarkProperty]
| View [ViewConfig]
configProperty :: ConfigurationProperty -> LabelledSpec
configProperty (Autosize aus) = "autosize" .= object (map autosizeProperty aus)
configProperty (Background bg) = "background" .= bg
configProperty (CountTitle ttl) = "countTitle" .= ttl
configProperty (ConcatStyle cps) = "concat" .= object (map concatConfigProperty cps)
configProperty (FieldTitle ftp) = "fieldTitle" .= fieldTitleLabel ftp
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) = mprops_ "mark" mps
configProperty (Projection pps) = "projection" .= object (map projectionProperty pps)
configProperty (AreaStyle mps) = mprops_ "area" mps
configProperty (BarStyle mps) = mprops_ "bar" mps
configProperty (CircleStyle mps) = mprops_ "circle" mps
configProperty (FacetStyle fps) = "facet" .= object (map facetConfigProperty fps)
configProperty (GeoshapeStyle mps) = mprops_ "geoshape" mps
configProperty (HeaderStyle hps) = header_ hps
configProperty (LineStyle mps) = mprops_ "line" mps
configProperty (PointStyle mps) = mprops_ "point" mps
configProperty (RectStyle mps) = mprops_ "rect" mps
configProperty (RuleStyle mps) = mprops_ "rule" mps
configProperty (SquareStyle mps) = mprops_ "square" mps
configProperty (TextStyle mps) = mprops_ "text" mps
configProperty (TickStyle mps) = mprops_ "tick" mps
configProperty (TitleStyle tcs) = "title" .= object (map titleConfigSpec tcs)
configProperty (NamedStyle nme mps) = "style" .= object [mprops_ nme mps]
configProperty (NamedStyles styles) =
let toStyle = uncurry mprops_
in "style" .= object (map toStyle styles)
configProperty (Scale scs) = scaleConfig_ scs
configProperty (Range rcs) = "range" .= object (map rangeConfigProperty rcs)
configProperty (SelectionStyle selConfig) =
let selProp (sel, sps) = selectionLabel sel .= object (concatMap selectionProperties sps)
in "selection" .= object (map selProp selConfig)
configProperty (TrailStyle mps) = mprops_ "trail" mps
configProperty (View vcs) = "view" .= object (concatMap viewConfigProperties vcs)
data ScaleConfig
= SCBandPaddingInner Double
| SCBandPaddingOuter Double
| SCBarBandPaddingInner Double
| SCBarBandPaddingOuter Double
| SCRectBandPaddingInner Double
| SCRectBandPaddingOuter Double
| SCClamp Bool
| SCMaxBandSize Double
| SCMinBandSize Double
| SCMaxFontSize Double
| SCMinFontSize Double
| SCMaxOpacity Opacity
| SCMinOpacity Opacity
| SCMaxSize Double
| SCMinSize Double
| SCMaxStrokeWidth Double
| SCMinStrokeWidth Double
| SCPointPadding Double
| SCRound Bool
| SCUseUnaggregatedDomain Bool
scaleConfig_ :: [ScaleConfig] -> LabelledSpec
scaleConfig_ scs = "scale" .= object (map scaleConfigProperty scs)
data FieldTitleProperty
= Verbal
| Function
| Plain
fieldTitleLabel :: FieldTitleProperty -> T.Text
fieldTitleLabel Verbal = "verbal"
fieldTitleLabel Function = "functional"
fieldTitleLabel Plain = "plain"
data LegendConfig
= LeClipHeight Double
| LeColumnPadding Double
| LeColumns Int
| LeCornerRadius Double
| LeFillColor Color
| LeGradientDirection Orientation
| LeGradientHorizontalMaxLength Double
| LeGradientHorizontalMinLength Double
| LeGradientLabelLimit Double
| LeGradientLabelOffset Double
| LeGradientLength Double
| LeGradientOpacity Opacity
| LeGradientStrokeColor Color
| LeGradientStrokeWidth Double
| LeGradientThickness Double
| LeGradientVerticalMaxLength Double
| LeGradientVerticalMinLength Double
| LeGridAlign CompositionAlignment
| LeLabelAlign HAlign
| LeLabelBaseline VAlign
| LeLabelColor Color
| LeLabelFont T.Text
| LeLabelFontSize Double
| LeLabelFontStyle T.Text
| LeLabelFontWeight FontWeight
| LeLabelLimit Double
| LeLabelOffset Double
| LeLabelOpacity Opacity
| LeLabelOverlap OverlapStrategy
| LeLabelPadding Double
| LeLabelSeparation Double
| LeLayout [LegendLayout]
| LeLeX Double
| LeLeY Double
| LeOffset Double
| LeOrient LegendOrientation
| LePadding Double
| LeRowPadding Double
| LeStrokeColor Color
| LeStrokeDash DashStyle
| LeStrokeWidth Double
| LeSymbolBaseFillColor Color
| LeSymbolBaseStrokeColor Color
| LeSymbolDash DashStyle
| LeSymbolDashOffset DashOffset
| LeSymbolDirection Orientation
| LeSymbolFillColor Color
| LeSymbolOffset Double
| LeSymbolOpacity Opacity
| LeSymbolSize Double
| LeSymbolStrokeColor Color
| LeSymbolStrokeWidth Double
| LeSymbolType Symbol
| LeTitle T.Text
| LeNoTitle
| LeTitleAlign HAlign
| LeTitleAnchor APosition
| LeTitleBaseline VAlign
| LeTitleColor Color
| LeTitleFont T.Text
| LeTitleFontSize Double
| LeTitleFontStyle T.Text
| LeTitleFontWeight FontWeight
| LeTitleLimit Double
| LeTitleOpacity Opacity
| LeTitleOrient Side
| LeTitlePadding Double
legendConfigProperty :: LegendConfig -> LabelledSpec
legendConfigProperty (LeClipHeight x) = "clipHeight" .= x
legendConfigProperty (LeColumnPadding x) = "columnPadding" .= x
legendConfigProperty (LeColumns n) = "columns" .= n
legendConfigProperty (LeCornerRadius x) = "cornerRadius" .= x
legendConfigProperty (LeFillColor s) = "fillColor" .= fromColor s
legendConfigProperty (LeGradientDirection o) = "gradientDirection" .= orientationSpec o
legendConfigProperty (LeGradientHorizontalMaxLength x) = "gradientHorizontalMaxLength" .= x
legendConfigProperty (LeGradientHorizontalMinLength x) = "gradientHorizontalMinLength" .= x
legendConfigProperty (LeGradientLabelLimit x) = "gradientLabelLimit" .= x
legendConfigProperty (LeGradientLabelOffset x) = "gradientLabelOffset" .= x
legendConfigProperty (LeGradientLength x) = "gradientLength" .= x
legendConfigProperty (LeGradientOpacity x) = "gradientOpacity" .= x
legendConfigProperty (LeGradientStrokeColor s) = "gradientStrokeColor" .= fromColor s
legendConfigProperty (LeGradientStrokeWidth x) = "gradientStrokeWidth" .= x
legendConfigProperty (LeGradientThickness x) = "gradientThickness" .= x
legendConfigProperty (LeGradientVerticalMaxLength x) = "gradientVerticalMaxLength" .= x
legendConfigProperty (LeGradientVerticalMinLength x) = "gradientVerticalMinLength" .= x
legendConfigProperty (LeGridAlign ga) = "gridAlign" .= compositionAlignmentSpec ga
legendConfigProperty (LeLabelAlign ha) = "labelAlign" .= hAlignLabel ha
legendConfigProperty (LeLabelBaseline va) = "labelBaseline" .= vAlignLabel va
legendConfigProperty (LeLabelColor s) = "labelColor" .= fromColor s
legendConfigProperty (LeLabelFont s) = "labelFont" .= s
legendConfigProperty (LeLabelFontSize x) = "labelFontSize" .= x
legendConfigProperty (LeLabelFontStyle s) = "labelFontStyle" .= s
legendConfigProperty (LeLabelFontWeight fw) = "labelFontWeight" .= fontWeightSpec fw
legendConfigProperty (LeLabelLimit x) = "labelLimit" .= x
legendConfigProperty (LeLabelOffset x) = "labelOffset" .= x
legendConfigProperty (LeLabelOpacity x) = "labelOpacity" .= x
legendConfigProperty (LeLabelOverlap olap) = "labelOverlap" .= overlapStrategyLabel olap
legendConfigProperty (LeLabelPadding x) = "labelPadding" .= x
legendConfigProperty (LeLabelSeparation x) = "labelSeparation" .= x
legendConfigProperty (LeLayout ll) = "layout" .= object (map legendLayoutSpec ll)
legendConfigProperty (LeLeX x) = "legendX" .= x
legendConfigProperty (LeLeY x) = "legendY" .= x
legendConfigProperty (LeOffset x) = "offset" .= x
legendConfigProperty (LeOrient orl) = "orient" .= legendOrientLabel orl
legendConfigProperty (LePadding x) = "padding" .= x
legendConfigProperty (LeRowPadding x) = "rowPadding" .= x
legendConfigProperty (LeStrokeColor s) = "strokeColor" .= fromColor s
legendConfigProperty (LeStrokeDash xs) = "strokeDash" .= fromDS xs
legendConfigProperty (LeStrokeWidth x) = "strokeWidth" .= x
legendConfigProperty (LeSymbolBaseFillColor s) = "symbolBaseFillColor" .= fromColor s
legendConfigProperty (LeSymbolBaseStrokeColor s) = "symbolBaseStrokeColor" .= fromColor s
legendConfigProperty (LeSymbolDash xs) = "symbolDash" .= fromDS xs
legendConfigProperty (LeSymbolDashOffset x) = "symbolDashOffset" .= x
legendConfigProperty (LeSymbolDirection o) = "symbolDirection" .= orientationSpec o
legendConfigProperty (LeSymbolFillColor s) = "symbolFillColor" .= fromColor s
legendConfigProperty (LeSymbolOffset x) = "symbolOffset" .= x
legendConfigProperty (LeSymbolOpacity x) = "symbolOpacity" .= x
legendConfigProperty (LeSymbolSize x) = "symbolSize" .= x
legendConfigProperty (LeSymbolStrokeColor s) = "symbolStrokeColor" .= fromColor s
legendConfigProperty (LeSymbolStrokeWidth x) = "symbolStrokeWidth" .= x
legendConfigProperty (LeSymbolType s) = "symbolType" .= symbolLabel s
legendConfigProperty (LeTitle s) = "title" .= s
legendConfigProperty LeNoTitle = "title" .= A.Null
legendConfigProperty (LeTitleAlign ha) = "titleAlign" .= hAlignLabel ha
legendConfigProperty (LeTitleAnchor anc) = "titleAnchor" .= anchorLabel anc
legendConfigProperty (LeTitleBaseline va) = "titleBaseline" .= vAlignLabel va
legendConfigProperty (LeTitleColor s) = "titleColor" .= fromColor s
legendConfigProperty (LeTitleFont s) = "titleFont" .= s
legendConfigProperty (LeTitleFontSize x) = "titleFontSize" .= x
legendConfigProperty (LeTitleFontStyle s) = "titleFontStyle" .= s
legendConfigProperty (LeTitleFontWeight fw) = "titleFontWeight" .= fontWeightSpec fw
legendConfigProperty (LeTitleLimit x) = "titleLimit" .= x
legendConfigProperty (LeTitleOpacity x) = "titleOpacity" .= x
legendConfigProperty (LeTitleOrient orient) = "titleOrient" .= sideLabel orient
legendConfigProperty (LeTitlePadding x) = "titlePadding" .= x
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 []]
scaleConfigProperty :: ScaleConfig -> LabelledSpec
scaleConfigProperty (SCBandPaddingInner x) = "bandPaddingInner" .= x
scaleConfigProperty (SCBandPaddingOuter x) = "bandPaddingOuter" .= x
scaleConfigProperty (SCBarBandPaddingInner x) = "barBandPaddingInner" .= x
scaleConfigProperty (SCBarBandPaddingOuter x) = "barBandPaddingOuter" .= x
scaleConfigProperty (SCRectBandPaddingInner x) = "rectBandPaddingInner" .= x
scaleConfigProperty (SCRectBandPaddingOuter x) = "rectBandPaddingOuter" .= 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 (SCRound b) = "round" .= b
scaleConfigProperty (SCUseUnaggregatedDomain b) = "useUnaggregatedDomain" .= b
{-# DEPRECATED ViewWidth "Please change ViewWidth to ViewContinuousWidth" #-}
{-# DEPRECATED ViewHeight "Please change ViewHeight to ViewContinuousHeight" #-}
data ViewConfig
= ViewBackgroundStyle [ViewBackground]
| ViewClip Bool
| ViewContinuousWidth Double
| ViewContinuousHeight Double
| ViewCornerRadius Double
| ViewDiscreteWidth Double
| ViewDiscreteHeight Double
| ViewFill (Maybe Color)
| ViewFillOpacity Opacity
| ViewOpacity Opacity
| ViewStep Double
| ViewStroke (Maybe Color)
| ViewStrokeCap StrokeCap
| ViewStrokeDash DashStyle
| ViewStrokeDashOffset DashOffset
| ViewStrokeJoin StrokeJoin
| ViewStrokeMiterLimit Double
| ViewStrokeOpacity Opacity
| ViewStrokeWidth Double
| ViewWidth Double
| ViewHeight Double
viewConfigProperties :: ViewConfig -> [LabelledSpec]
viewConfigProperties (ViewBackgroundStyle bs) = map viewBackgroundSpec bs
viewConfigProperties (ViewClip b) = ["clip" .= b]
viewConfigProperties (ViewWidth x) = ["continuousWidth" .= x]
viewConfigProperties (ViewHeight x) = ["continuousHeight" .= x]
viewConfigProperties (ViewContinuousWidth x) = ["continuousWidth" .= x]
viewConfigProperties (ViewContinuousHeight x) = ["continuousHeight" .= x]
viewConfigProperties (ViewCornerRadius x) = ["cornerRadius" .= x]
viewConfigProperties (ViewDiscreteWidth x) = ["discreteWidth" .= x]
viewConfigProperties (ViewDiscreteHeight x) = ["discreteHeight" .= x]
viewConfigProperties (ViewFill ms) = ["fill" .= maybe A.Null fromColor ms]
viewConfigProperties (ViewFillOpacity x) = ["fillOpacity" .= x]
viewConfigProperties (ViewOpacity x) = ["opacity" .= x]
viewConfigProperties (ViewStep x) = ["step" .= x]
viewConfigProperties (ViewStroke ms) = ["stroke" .= maybe A.Null fromColor ms]
viewConfigProperties (ViewStrokeCap sc) = ["strokeCap" .= strokeCapLabel sc]
viewConfigProperties (ViewStrokeDash xs) = ["strokeDash" .= fromDS xs]
viewConfigProperties (ViewStrokeDashOffset x) = ["strokeDashOffset" .= x]
viewConfigProperties (ViewStrokeJoin sj) = ["strokeJoin" .= strokeJoinLabel sj]
viewConfigProperties (ViewStrokeMiterLimit x) = ["strokeMiterLimit" .= x]
viewConfigProperties (ViewStrokeOpacity x) = ["strokeOpacity" .= x]
viewConfigProperties (ViewStrokeWidth x) = ["strokeWidth" .= x]
data AxisConfig
= BandPosition Double
| Domain Bool
| DomainColor Color
| DomainDash DashStyle
| DomainDashOffset DashOffset
| DomainOpacity Opacity
| DomainWidth Double
| Grid Bool
| GridColor Color
| GridDash DashStyle
| GridDashOffset DashOffset
| GridOpacity Opacity
| GridWidth Double
| Labels Bool
| LabelAlign HAlign
| LabelAngle Angle
| LabelBaseline VAlign
| LabelNoBound
| LabelBound
| LabelBoundValue Double
| LabelColor Color
| LabelNoFlush
| LabelFlush
| LabelFlushValue Double
| LabelFlushOffset Double
| LabelFont T.Text
| LabelFontSize Double
| LabelFontStyle T.Text
| LabelFontWeight FontWeight
| LabelLimit Double
| LabelOpacity Opacity
| LabelOverlap OverlapStrategy
| LabelPadding Double
| LabelSeparation Double
| MaxExtent Double
| MinExtent Double
| NoTitle
| Orient Side
| Ticks Bool
| TickBand BandAlign
| TickColor Color
| TickDash DashStyle
| TickDashOffset DashOffset
| TickExtra Bool
| TickOffset Double
| TickOpacity Opacity
| TickRound Bool
| TickSize Double
| TickWidth Double
| TitleAlign HAlign
| TitleAnchor APosition
| TitleAngle Angle
| TitleBaseline VAlign
| TitleColor Color
| TitleFont T.Text
| TitleFontSize Double
| TitleFontStyle T.Text
| TitleFontWeight FontWeight
| TitleLimit Double
| TitleLineHeight Double
| TitleOpacity Opacity
| TitlePadding Double
| TitleX Double
| TitleY Double
| TranslateOffset Double
axisConfigProperty :: AxisConfig -> LabelledSpec
axisConfigProperty (BandPosition x) = "bandPosition" .= x
axisConfigProperty (Domain b) = "domain" .= b
axisConfigProperty (DomainColor c) = "domainColor" .= fromColor c
axisConfigProperty (DomainDash ds) = "domainDash" .= fromDS ds
axisConfigProperty (DomainDashOffset x) = "domainDashOffset" .= x
axisConfigProperty (DomainOpacity x) = "domainOpacity" .= x
axisConfigProperty (DomainWidth w) = "domainWidth" .= w
axisConfigProperty (Grid b) = "grid" .= b
axisConfigProperty (GridColor c) = "gridColor" .= fromColor c
axisConfigProperty (GridDash ds) = "gridDash" .= fromDS ds
axisConfigProperty (GridDashOffset x) = "gridDashOffset" .= x
axisConfigProperty (GridOpacity o) = "gridOpacity" .= o
axisConfigProperty (GridWidth x) = "gridWidth" .= x
axisConfigProperty (LabelAlign ha) = "labelAlign" .= hAlignLabel ha
axisConfigProperty (LabelAngle angle) = "labelAngle" .= angle
axisConfigProperty (LabelBaseline va) = "labelBaseline" .= vAlignLabel va
axisConfigProperty LabelNoBound = "labelBound" .= False
axisConfigProperty LabelBound = "labelBound" .= True
axisConfigProperty (LabelBoundValue x) = "labelBound" .= x
axisConfigProperty (LabelColor c) = "labelColor" .= fromColor c
axisConfigProperty LabelNoFlush = "labelFlush" .= False
axisConfigProperty LabelFlush = "labelFlush" .= True
axisConfigProperty (LabelFlushValue x) = "labelFlush" .= x
axisConfigProperty (LabelFlushOffset x) = "labelFlushOffset" .= x
axisConfigProperty (LabelFont f) = "labelFont" .= f
axisConfigProperty (LabelFontSize x) = "labelFontSize" .= x
axisConfigProperty (LabelFontStyle s) = "labelFontStyle" .= s
axisConfigProperty (LabelFontWeight fw) = "labelFontWeight" .= fontWeightSpec fw
axisConfigProperty (LabelLimit x) = "labelLimit" .= x
axisConfigProperty (LabelOpacity x) = "labelOpacity" .= x
axisConfigProperty (LabelOverlap strat) = "labelOverlap" .= overlapStrategyLabel strat
axisConfigProperty (LabelPadding pad) = "labelPadding" .= pad
axisConfigProperty (LabelSeparation x) = "labelSeparation" .= x
axisConfigProperty (Labels b) = "labels" .= b
axisConfigProperty (MaxExtent n) = "maxExtent" .= n
axisConfigProperty (MinExtent n) = "minExtent" .= n
axisConfigProperty (Orient orient) = "orient" .= sideLabel orient
axisConfigProperty (TickBand band) = "tickBand" .= bandAlignLabel band
axisConfigProperty (TickColor c) = "tickColor" .= fromColor c
axisConfigProperty (TickDash ds) = "tickDash" .= fromDS ds
axisConfigProperty (TickDashOffset x) = "tickDashOffset" .= x
axisConfigProperty (TickExtra b) = "tickExtra" .= b
axisConfigProperty (TickOffset x) = "tickOffset" .= x
axisConfigProperty (TickOpacity x) = "tickOpacity" .= x
axisConfigProperty (TickRound b) = "tickRound" .= b
axisConfigProperty (TickSize x) = "tickSize" .= x
axisConfigProperty (TickWidth x) = "tickWidth" .= x
axisConfigProperty (Ticks b) = "ticks" .= b
axisConfigProperty NoTitle = "title" .= A.Null
axisConfigProperty (TitleAlign algn) = "titleAlign" .= hAlignLabel algn
axisConfigProperty (TitleAnchor a) = "titleAnchor" .= anchorLabel a
axisConfigProperty (TitleAngle x) = "titleAngle" .= x
axisConfigProperty (TitleBaseline va) = "titleBaseline" .= vAlignLabel va
axisConfigProperty (TitleColor c) = "titleColor" .= fromColor c
axisConfigProperty (TitleFont f) = "titleFont" .= f
axisConfigProperty (TitleFontSize x) = "titleFontSize" .= x
axisConfigProperty (TitleFontStyle s) = "titleFontStyle" .= s
axisConfigProperty (TitleFontWeight w) = "titleFontWeight" .= fontWeightSpec w
axisConfigProperty (TitleLimit x) = "titleLimit" .= x
axisConfigProperty (TitleLineHeight x) = "titleLineHeight" .= x
axisConfigProperty (TitleOpacity x) = "titleOpacity" .= x
axisConfigProperty (TitlePadding x) = "titlePadding" .= x
axisConfigProperty (TitleX x) = "titleX" .= x
axisConfigProperty (TitleY x) = "titleY" .= x
axisConfigProperty (TranslateOffset x) = "translate" .= x
data FacetConfig
= FColumns Int
| FSpacing Double
facetConfigProperty :: FacetConfig -> LabelledSpec
facetConfigProperty (FColumns n) = "columns" .= n
facetConfigProperty (FSpacing x) = "spacing" .= x
data TitleFrame
= FrBounds
| FrGroup
titleFrameSpec :: TitleFrame -> VLSpec
titleFrameSpec FrBounds = "bounds"
titleFrameSpec FrGroup = "group"
data TitleConfig
= TAlign HAlign
| TAnchor APosition
| TAngle Angle
| TBaseline VAlign
| TColor Color
| TdX Double
| TdY Double
| TFont T.Text
| TFontSize Double
| TFontStyle T.Text
| TFontWeight FontWeight
| TFrame TitleFrame
| TLimit Double
| TLineHeight Double
| TOffset Double
| TOrient Side
| TStyle [T.Text]
| TSubtitle T.Text
| TSubtitleColor Color
| TSubtitleFont T.Text
| TSubtitleFontSize Double
| TSubtitleFontStyle T.Text
| TSubtitleFontWeight FontWeight
| TSubtitleLineHeight Double
| TSubtitlePadding Double
| TZIndex ZIndex
titleConfigSpec :: TitleConfig -> LabelledSpec
titleConfigSpec (TAlign ha) = "align" .= hAlignLabel ha
titleConfigSpec (TAnchor an) = "anchor" .= anchorLabel an
titleConfigSpec (TAngle x) = "angle" .= x
titleConfigSpec (TBaseline va) = "baseline" .= vAlignLabel va
titleConfigSpec (TColor clr) = "color" .= fromColor clr
titleConfigSpec (TdX x) = "dx" .= x
titleConfigSpec (TdY x) = "dy" .= x
titleConfigSpec (TFont fnt) = "font" .= fnt
titleConfigSpec (TFontSize x) = "fontSize" .= x
titleConfigSpec (TFontStyle s) = "fontStyle" .= s
titleConfigSpec (TFontWeight w) = "fontWeight" .= fontWeightSpec w
titleConfigSpec (TFrame tf) = "frame" .= titleFrameSpec tf
titleConfigSpec (TLimit x) = "limit" .= x
titleConfigSpec (TLineHeight x) = "lineHeight" .= x
titleConfigSpec (TOffset x) = "offset" .= x
titleConfigSpec (TOrient sd) = "orient" .= sideLabel sd
titleConfigSpec (TStyle [style]) = "style" .= style
titleConfigSpec (TStyle styles) = "style" .= styles
titleConfigSpec (TSubtitle s) = "subtitle" .= splitOnNewline s
titleConfigSpec (TSubtitleColor s) = "subtitleColor" .= fromColor s
titleConfigSpec (TSubtitleFont s) = "subtitleFont" .= s
titleConfigSpec (TSubtitleFontSize x) = "subtitleFontSize" .= x
titleConfigSpec (TSubtitleFontStyle s) = "subtitleFontStyle" .= s
titleConfigSpec (TSubtitleFontWeight fw) = "subtitleFontWeight" .= fontWeightSpec fw
titleConfigSpec (TSubtitleLineHeight x) = "subtitleLineHeight" .= x
titleConfigSpec (TSubtitlePadding x) = "subtitlePadding" .= x
titleConfigSpec (TZIndex z) = "zindex" .= z
data ConcatConfig
= ConcatColumns Int
| ConcatSpacing Double
concatConfigProperty :: ConcatConfig -> LabelledSpec
concatConfigProperty (ConcatColumns n) = "columns" .= n
concatConfigProperty (ConcatSpacing x) = "spacing" .= x
configuration ::
ConfigurationProperty
-> BuildConfigureSpecs
configuration cfg ols = CS (configProperty cfg) : ols
title ::
T.Text
-> [TitleConfig]
-> PropertySpec
title s [] =
(VLTitle, splitOnNewline s)
title s topts =
(VLTitle,
object ("text" .= splitOnNewline s : map titleConfigSpec topts))