{-# LANGUAGE OverloadedStrings #-}
module Graphics.Vega.VegaLite.Legend
( LegendType(..)
, LegendOrientation(..)
, LegendLayout(..)
, BaseLegendLayout(..)
, LegendProperty(..)
, LegendValues(..)
, legendProp_
, legendOrientLabel
, legendLayoutSpec
) where
import qualified Data.Aeson as A
import qualified Data.Text as T
import Data.Aeson ((.=), object, toJSON)
import Data.Aeson.Types (Pair)
import Graphics.Vega.VegaLite.Foundation
( APosition
, Bounds
, Color
, CompositionAlignment
, DashStyle
, DashOffset
, FontWeight
, HAlign
, Opacity
, Orientation
, OverlapStrategy
, Side
, Symbol
, VAlign
, VegaExpr
, ZIndex
, anchorLabel
, boundsSpec
, compositionAlignmentSpec
, fontWeightSpec
, hAlignLabel
, orientationSpec
, overlapStrategyLabel
, sideLabel
, symbolLabel
, vAlignLabel
, fromT
, fromColor
, fromDS
, splitOnNewline
)
import Graphics.Vega.VegaLite.Scale
( ScaleNice
, scaleNiceSpec
)
import Graphics.Vega.VegaLite.Specification (VLSpec)
import Graphics.Vega.VegaLite.Time
( DateTime
, dateTimeSpec
)
data LegendType
= GradientLegend
| SymbolLegend
legendLabel :: LegendType -> T.Text
legendLabel :: LegendType -> Text
legendLabel LegendType
GradientLegend = Text
"gradient"
legendLabel LegendType
SymbolLegend = Text
"symbol"
data LegendOrientation
= LONone
| LOLeft
| LORight
| LOTop
| LOBottom
| LOTopLeft
| LOTopRight
| LOBottomLeft
| LOBottomRight
legendOrientLabel :: LegendOrientation -> T.Text
legendOrientLabel :: LegendOrientation -> Text
legendOrientLabel LegendOrientation
LONone = Text
"none"
legendOrientLabel LegendOrientation
LOLeft = Text
"left"
legendOrientLabel LegendOrientation
LORight = Text
"right"
legendOrientLabel LegendOrientation
LOTop = Text
"top"
legendOrientLabel LegendOrientation
LOBottom = Text
"bottom"
legendOrientLabel LegendOrientation
LOTopLeft = Text
"top-left"
legendOrientLabel LegendOrientation
LOTopRight = Text
"top-right"
legendOrientLabel LegendOrientation
LOBottomLeft = Text
"bottom-left"
legendOrientLabel LegendOrientation
LOBottomRight = Text
"bottom-right"
data LegendLayout
= LeLAnchor APosition
| LeLBottom [BaseLegendLayout]
| LeLBottomLeft [BaseLegendLayout]
| LeLBottomRight [BaseLegendLayout]
| LeLBounds Bounds
| LeLCenter Bool
| LeLDirection Orientation
| LeLLeft [BaseLegendLayout]
| LeLMargin Double
| LeLOffset Double
| LeLRight [BaseLegendLayout]
| LeLTop [BaseLegendLayout]
| LeLTopLeft [BaseLegendLayout]
| LeLTopRight [BaseLegendLayout]
legendLayoutSpec :: LegendLayout -> Pair
legendLayoutSpec :: LegendLayout -> Pair
legendLayoutSpec (LeLAnchor APosition
anc) = Key
"anchor" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= APosition -> Text
anchorLabel APosition
anc
legendLayoutSpec (LeLBottom [BaseLegendLayout]
bl) = Key
"bottom" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BaseLegendLayout] -> VLSpec
toBLSpec [BaseLegendLayout]
bl
legendLayoutSpec (LeLBottomLeft [BaseLegendLayout]
bl) = Key
"bottom-left" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BaseLegendLayout] -> VLSpec
toBLSpec [BaseLegendLayout]
bl
legendLayoutSpec (LeLBottomRight [BaseLegendLayout]
bl) = Key
"bottom-right" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BaseLegendLayout] -> VLSpec
toBLSpec [BaseLegendLayout]
bl
legendLayoutSpec (LeLBounds Bounds
bnds) = Key
"bounds" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bounds -> VLSpec
boundsSpec Bounds
bnds
legendLayoutSpec (LeLCenter Bool
b) = Key
"center" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
legendLayoutSpec (LeLDirection Orientation
o) = Key
"direction" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Orientation -> VLSpec
orientationSpec Orientation
o
legendLayoutSpec (LeLLeft [BaseLegendLayout]
bl) = Key
"left" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BaseLegendLayout] -> VLSpec
toBLSpec [BaseLegendLayout]
bl
legendLayoutSpec (LeLMargin Double
x) = Key
"margin" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendLayoutSpec (LeLOffset Double
x) = Key
"offset" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendLayoutSpec (LeLRight [BaseLegendLayout]
bl) = Key
"right" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BaseLegendLayout] -> VLSpec
toBLSpec [BaseLegendLayout]
bl
legendLayoutSpec (LeLTop [BaseLegendLayout]
bl) = Key
"top" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BaseLegendLayout] -> VLSpec
toBLSpec [BaseLegendLayout]
bl
legendLayoutSpec (LeLTopLeft [BaseLegendLayout]
bl) = Key
"top-left" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BaseLegendLayout] -> VLSpec
toBLSpec [BaseLegendLayout]
bl
legendLayoutSpec (LeLTopRight [BaseLegendLayout]
bl) = Key
"top-right" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BaseLegendLayout] -> VLSpec
toBLSpec [BaseLegendLayout]
bl
data BaseLegendLayout
= BLeLAnchor APosition
| BLeLBounds Bounds
| BLeLCenter Bool
| BLeLDirection Orientation
| BLeLMargin Double
| BLeLOffset Double
toBLSpec :: [BaseLegendLayout] -> VLSpec
toBLSpec :: [BaseLegendLayout] -> VLSpec
toBLSpec = [Pair] -> VLSpec
object ([Pair] -> VLSpec)
-> ([BaseLegendLayout] -> [Pair]) -> [BaseLegendLayout] -> VLSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BaseLegendLayout -> Pair) -> [BaseLegendLayout] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map BaseLegendLayout -> Pair
baseLegendLayoutSpec
baseLegendLayoutSpec :: BaseLegendLayout -> Pair
baseLegendLayoutSpec :: BaseLegendLayout -> Pair
baseLegendLayoutSpec (BLeLAnchor APosition
anc) = Key
"anchor" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= APosition -> Text
anchorLabel APosition
anc
baseLegendLayoutSpec (BLeLBounds Bounds
bnds) = Key
"bounds" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bounds -> VLSpec
boundsSpec Bounds
bnds
baseLegendLayoutSpec (BLeLCenter Bool
b) = Key
"center" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
baseLegendLayoutSpec (BLeLDirection Orientation
o) = Key
"direction" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Orientation -> VLSpec
orientationSpec Orientation
o
baseLegendLayoutSpec (BLeLMargin Double
x) = Key
"margin" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
baseLegendLayoutSpec (BLeLOffset Double
x) = Key
"offset" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
data LegendProperty
= LAria Bool
| LAriaDescription T.Text
| LClipHeight Double
| LColumnPadding Double
| LColumns Int
| LCornerRadius Double
| LDirection Orientation
| LFillColor Color
| LFormat T.Text
| LFormatAsNum
| LFormatAsTemporal
| LFormatAsCustom T.Text
| LGradientLength Double
| LGradientOpacity Opacity
| LGradientStrokeColor Color
| LGradientStrokeWidth Double
| LGradientThickness Double
| LGridAlign CompositionAlignment
| LLabelAlign HAlign
| LLabelBaseline VAlign
| LLabelColor Color
| LLabelExpr VegaExpr
| LLabelFont T.Text
| LLabelFontSize Double
| LLabelFontStyle T.Text
| LLabelFontWeight FontWeight
| LLabelLimit Double
| LLabelOffset Double
| LLabelOpacity Opacity
| LLabelOverlap OverlapStrategy
| LLabelPadding Double
| LLabelSeparation Double
| LOffset Double
| LOrient LegendOrientation
| LPadding Double
| LRowPadding Double
| LStrokeColor Color
| LSymbolDash DashStyle
| LSymbolDashOffset DashOffset
| LSymbolFillColor Color
| LSymbolLimit Int
| LSymbolOffset Double
| LSymbolOpacity Opacity
| LSymbolSize Double
| LSymbolStrokeColor Color
| LSymbolStrokeWidth Double
| LSymbolType Symbol
| LTickCount Double
| LTickCountTime ScaleNice
| LTickMinStep Double
| LTitle T.Text
| LNoTitle
| LTitleAlign HAlign
| LTitleAnchor APosition
| LTitleBaseline VAlign
| LTitleColor Color
| LTitleFont T.Text
| LTitleFontSize Double
| LTitleFontStyle T.Text
| LTitleFontWeight FontWeight
| LTitleLimit Double
| LTitleLineHeight Double
| LTitleOpacity Opacity
| LTitleOrient Side
| LTitlePadding Double
| LType LegendType
| LValues LegendValues
| LeX Double
| LeY Double
| LZIndex ZIndex
legendProperty :: LegendProperty -> Pair
legendProperty :: LegendProperty -> Pair
legendProperty (LAria Bool
b) = Key
"aria" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
legendProperty (LAriaDescription Text
t) = Key
"description" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
t
legendProperty (LClipHeight Double
x) = Key
"clipHeight" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LColumnPadding Double
x) = Key
"columnPadding" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LColumns Int
n) = Key
"columns" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
n
legendProperty (LCornerRadius Double
x) = Key
"cornerRadius" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LDirection Orientation
o) = Key
"direction" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Orientation -> VLSpec
orientationSpec Orientation
o
legendProperty (LFillColor Text
s) = Key
"fillColor" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromColor Text
s
legendProperty (LFormat Text
s) = Key
"format" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
legendProperty LegendProperty
LFormatAsNum = Key
"formatType" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"number"
legendProperty LegendProperty
LFormatAsTemporal = Key
"formatType" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"time"
legendProperty (LFormatAsCustom Text
c) = Key
"formatType" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
c
legendProperty (LGradientLength Double
x) = Key
"gradientLength" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LGradientOpacity Double
x) = Key
"gradientOpacity" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LGradientStrokeColor Text
s) = Key
"gradientStrokeColor" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromColor Text
s
legendProperty (LGradientStrokeWidth Double
x) = Key
"gradientStrokeWidth" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LGradientThickness Double
x) = Key
"gradientThickness" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LGridAlign CompositionAlignment
ga) = Key
"gridAlign" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
ga
legendProperty (LLabelAlign HAlign
ha) = Key
"labelAlign" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HAlign -> Text
hAlignLabel HAlign
ha
legendProperty (LLabelBaseline VAlign
va) = Key
"labelBaseline" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VAlign -> Text
vAlignLabel VAlign
va
legendProperty (LLabelColor Text
s) = Key
"labelColor" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromColor Text
s
legendProperty (LLabelExpr Text
s) = Key
"labelExpr" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
legendProperty (LLabelFont Text
s) = Key
"labelFont" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
legendProperty (LLabelFontSize Double
x) = Key
"labelFontSize" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LLabelFontStyle Text
s) = Key
"labelFontStyle" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
legendProperty (LLabelFontWeight FontWeight
fw) = Key
"labelFontWeight" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FontWeight -> VLSpec
fontWeightSpec FontWeight
fw
legendProperty (LLabelLimit Double
x) = Key
"labelLimit" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LLabelOffset Double
x) = Key
"labelOffset" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LLabelOpacity Double
x) = Key
"labelOpacity" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LLabelOverlap OverlapStrategy
strat) = Key
"labelOverlap" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= OverlapStrategy -> VLSpec
overlapStrategyLabel OverlapStrategy
strat
legendProperty (LLabelPadding Double
x) = Key
"labelPadding" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LLabelSeparation Double
x) = Key
"labelSeparation" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LOffset Double
x) = Key
"offset" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LOrient LegendOrientation
orl) = Key
"orient" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= LegendOrientation -> Text
legendOrientLabel LegendOrientation
orl
legendProperty (LPadding Double
x) = Key
"padding" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LRowPadding Double
x) = Key
"rowPadding" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LStrokeColor Text
s) = Key
"strokeColor" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromColor Text
s
legendProperty (LSymbolDash DashStyle
ds) = Key
"symbolDash" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DashStyle -> VLSpec
fromDS DashStyle
ds
legendProperty (LSymbolDashOffset Double
x) = Key
"symbolDashOffset" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LSymbolFillColor Text
s) = Key
"symbolFillColor" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromColor Text
s
legendProperty (LSymbolLimit Int
x) = Key
"symbolLimit" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
x
legendProperty (LSymbolOffset Double
x) = Key
"symbolOffset" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LSymbolOpacity Double
x) = Key
"symbolOpacity" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LSymbolSize Double
x) = Key
"symbolSize" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LSymbolStrokeColor Text
s) = Key
"symbolStrokeColor" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromColor Text
s
legendProperty (LSymbolStrokeWidth Double
x) = Key
"symbolStrokeWidth" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LSymbolType Symbol
sym) = Key
"symbolType" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Symbol -> Text
symbolLabel Symbol
sym
legendProperty (LTickCount Double
x) = Key
"tickCount" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LTickCountTime ScaleNice
sn) = Key
"tickCount" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ScaleNice -> VLSpec
scaleNiceSpec ScaleNice
sn
legendProperty (LTickMinStep Double
x) = Key
"tickMinStep" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LTitle Text
s) = Key
"title" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
splitOnNewline Text
s
legendProperty LegendProperty
LNoTitle = Key
"title" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null
legendProperty (LTitleAlign HAlign
ha) = Key
"titleAlign" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HAlign -> Text
hAlignLabel HAlign
ha
legendProperty (LTitleAnchor APosition
anc) = Key
"titleAnchor" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= APosition -> Text
anchorLabel APosition
anc
legendProperty (LTitleBaseline VAlign
va) = Key
"titleBaseline" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VAlign -> Text
vAlignLabel VAlign
va
legendProperty (LTitleColor Text
s) = Key
"titleColor" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromColor Text
s
legendProperty (LTitleFont Text
s) = Key
"titleFont" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
legendProperty (LTitleFontSize Double
x) = Key
"titleFontSize" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LTitleFontStyle Text
s) = Key
"titleFontStyle" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
legendProperty (LTitleFontWeight FontWeight
fw) = Key
"titleFontWeight" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FontWeight -> VLSpec
fontWeightSpec FontWeight
fw
legendProperty (LTitleLimit Double
x) = Key
"titleLimit" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LTitleLineHeight Double
x) = Key
"titleLineHeight" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LTitleOpacity Double
x) = Key
"titleOpacity" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LTitleOrient Side
orient) = Key
"titleOrient" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Side -> Text
sideLabel Side
orient
legendProperty (LTitlePadding Double
x) = Key
"titlePadding" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LType LegendType
lType) = Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= LegendType -> Text
legendLabel LegendType
lType
legendProperty (LValues LegendValues
vals) =
let ls :: [VLSpec]
ls = case LegendValues
vals of
LNumbers DashStyle
xs -> (Double -> VLSpec) -> DashStyle -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map Double -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON DashStyle
xs
LDateTimes [[DateTime]]
dts -> ([DateTime] -> VLSpec) -> [[DateTime]] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map [DateTime] -> VLSpec
dateTimeSpec [[DateTime]]
dts
LStrings [Text]
ss -> (Text -> VLSpec) -> [Text] -> [VLSpec]
forall a b. (a -> b) -> [a] -> [b]
map Text -> VLSpec
forall a. ToJSON a => a -> VLSpec
toJSON [Text]
ss
in Key
"values" Key -> [VLSpec] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [VLSpec]
ls
legendProperty (LeX Double
x) = Key
"legendX" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LeY Double
x) = Key
"legendY" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
legendProperty (LZIndex ZIndex
z) = Key
"zindex" Key -> ZIndex -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ZIndex
z
legendProp_ :: [LegendProperty] -> Pair
legendProp_ :: [LegendProperty] -> Pair
legendProp_ [] = Key
"legend" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null
legendProp_ [LegendProperty]
lps = Key
"legend" Key -> VLSpec -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object ((LegendProperty -> Pair) -> [LegendProperty] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map LegendProperty -> Pair
legendProperty [LegendProperty]
lps)
data LegendValues
= LDateTimes [[DateTime]]
| LNumbers [Double]
| LStrings [T.Text]