{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Graphics.Vega.VegaLite.Foundation
( Angle
, Color
, DashStyle
, DashOffset
, FieldName
, Opacity
, StyleLabel
, VegaExpr
, ZIndex
, FontWeight(..)
, Measurement(..)
, Arrangement(..)
, APosition(..)
, Orientation(..)
, Position(..)
, HAlign(..)
, VAlign(..)
, BandAlign(..)
, StrokeCap(..)
, StrokeJoin(..)
, Scale(..)
, SortField(..)
, Cursor(..)
, OverlapStrategy(..)
, Side(..)
, Symbol(..)
, StackProperty(..)
, StackOffset(..)
, TooltipContent(..)
, Channel(..)
, Resolve(..)
, Resolution(..)
, Bounds(..)
, CompositionAlignment(..)
, Padding(..)
, Autosize(..)
, RepeatFields(..)
, CInterpolate(..)
, ViewBackground(..)
, HeaderProperty(..)
, fontWeightSpec
, measurementLabel
, arrangementLabel
, anchorLabel
, orientationSpec
, hAlignLabel
, vAlignLabel
, bandAlignLabel
, strokeCapLabel
, strokeJoinLabel
, scaleLabel
, positionLabel
, sortFieldSpec
, cursorLabel
, overlapStrategyLabel
, sideLabel
, symbolLabel
, stackPropertySpecSort
, stackPropertySpecOffset
, stackOffset
, ttContentLabel
, channelLabel
, resolveProperty
, boundsSpec
, compositionAlignmentSpec
, paddingSpec
, autosizeProperty
, repeatFieldsProperty
, cInterpolateSpec
, viewBackgroundSpec
, fromT
, fromColor
, fromDS
, splitOnNewline
, field_
, header_
, order_
, allowNull
, (.=~)
, toKey
, toKeys
, toObject
)
where
import qualified Data.Aeson as A
#if MIN_VERSION_aeson(2, 0, 0)
import qualified Data.Aeson.Key as Key
#endif
import qualified Data.Text as T
#if MIN_VERSION_aeson(2, 0, 0)
import Control.Arrow (first)
#endif
import Data.Aeson ((.=), object, toJSON)
import Data.Aeson.Types (Pair, ToJSON)
#if !(MIN_VERSION_base(4, 12, 0))
import Data.Monoid ((<>))
#endif
import Numeric.Natural (Natural)
import Graphics.Vega.VegaLite.Specification
( VLSpec
, LabelledSpec
, ResolveSpec(..)
)
(.=~) :: ToJSON a => T.Text -> a -> (T.Text, A.Value)
Text
a .=~ :: forall a. ToJSON a => Text -> a -> (Text, VLSpec)
.=~ a
b = (Text
a, forall a. ToJSON a => a -> VLSpec
toJSON a
b)
toKey :: LabelledSpec -> Pair
#if MIN_VERSION_aeson(2, 0, 0)
toKey :: (Text, VLSpec) -> Pair
toKey = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Text -> Key
Key.fromText
#else
toKey = id
#endif
toKeys :: [LabelledSpec] -> [Pair]
toKeys :: [(Text, VLSpec)] -> [Pair]
toKeys = forall a b. (a -> b) -> [a] -> [b]
map (Text, VLSpec) -> Pair
toKey
toObject :: [LabelledSpec] -> VLSpec
toObject :: [(Text, VLSpec)] -> VLSpec
toObject = [Pair] -> VLSpec
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Text, VLSpec)] -> [Pair]
toKeys
field_ :: FieldName -> Pair
field_ :: Text -> Pair
field_ Text
f = Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
f
header_ :: T.Text -> [HeaderProperty] -> LabelledSpec
Text
extra [HeaderProperty]
hps = (Text
"header" forall a. Semigroup a => a -> a -> a
<> Text
extra, [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map HeaderProperty -> Pair
headerProperty [HeaderProperty]
hps))
order_ :: T.Text -> Pair
order_ :: Text -> Pair
order_ Text
o = Key
"order" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
o
allowNull :: Maybe Int -> VLSpec
allowNull :: Maybe Int -> VLSpec
allowNull (Just Int
a) = forall a. ToJSON a => a -> VLSpec
toJSON Int
a
allowNull Maybe Int
Nothing = VLSpec
A.Null
type FieldName = T.Text
type Color = T.Text
fromColor :: Color -> VLSpec
fromColor :: Text -> VLSpec
fromColor = Text -> VLSpec
cleanT
cleanT :: T.Text -> VLSpec
cleanT :: Text -> VLSpec
cleanT Text
t =
let tout :: Text
tout = Text -> Text
T.strip Text
t
in if Text -> Bool
T.null Text
tout
then VLSpec
A.Null
else forall a. ToJSON a => a -> VLSpec
toJSON Text
tout
type DashStyle = [Double]
fromDS :: DashStyle -> VLSpec
fromDS :: DashStyle -> VLSpec
fromDS = forall a. ToJSON a => a -> VLSpec
toJSON
type DashOffset = Double
type Opacity = Double
type StyleLabel = T.Text
type Angle = Double
type ZIndex = Natural
type VegaExpr = T.Text
data FontWeight
= Bold
| Bolder
| Lighter
| Normal
| W100
| W200
| W300
| W400
| W500
| W600
| W700
| W800
| W900
fromF :: Double -> VLSpec
fromF :: Double -> VLSpec
fromF = forall a. ToJSON a => a -> VLSpec
toJSON
fromT :: T.Text -> VLSpec
fromT :: Text -> VLSpec
fromT = forall a. ToJSON a => a -> VLSpec
toJSON
splitOnNewline :: T.Text -> VLSpec
splitOnNewline :: Text -> VLSpec
splitOnNewline Text
ts =
case (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
== Char
'\n') Text
ts of
[] -> Text -> VLSpec
fromT Text
""
[Text
s] -> forall a. ToJSON a => a -> VLSpec
toJSON Text
s
[Text]
s -> forall a. ToJSON a => a -> VLSpec
toJSON [Text]
s
fontWeightSpec :: FontWeight -> VLSpec
fontWeightSpec :: FontWeight -> VLSpec
fontWeightSpec FontWeight
Bold = Text -> VLSpec
fromT Text
"bold"
fontWeightSpec FontWeight
Bolder = Text -> VLSpec
fromT Text
"bolder"
fontWeightSpec FontWeight
Lighter = Text -> VLSpec
fromT Text
"lighter"
fontWeightSpec FontWeight
Normal = Text -> VLSpec
fromT Text
"normal"
fontWeightSpec FontWeight
W100 = Double -> VLSpec
fromF Double
100
fontWeightSpec FontWeight
W200 = Double -> VLSpec
fromF Double
200
fontWeightSpec FontWeight
W300 = Double -> VLSpec
fromF Double
300
fontWeightSpec FontWeight
W400 = Double -> VLSpec
fromF Double
400
fontWeightSpec FontWeight
W500 = Double -> VLSpec
fromF Double
500
fontWeightSpec FontWeight
W600 = Double -> VLSpec
fromF Double
600
fontWeightSpec FontWeight
W700 = Double -> VLSpec
fromF Double
700
fontWeightSpec FontWeight
W800 = Double -> VLSpec
fromF Double
800
fontWeightSpec FontWeight
W900 = Double -> VLSpec
fromF Double
900
data Measurement
= Nominal
| Ordinal
| Quantitative
| Temporal
| GeoFeature
measurementLabel :: Measurement -> T.Text
measurementLabel :: Measurement -> Text
measurementLabel Measurement
Nominal = Text
"nominal"
measurementLabel Measurement
Ordinal = Text
"ordinal"
measurementLabel Measurement
Quantitative = Text
"quantitative"
measurementLabel Measurement
Temporal = Text
"temporal"
measurementLabel Measurement
GeoFeature = Text
"geojson"
data Arrangement
= Column
| Row
| Flow
| Layer
arrangementLabel :: Arrangement -> T.Text
arrangementLabel :: Arrangement -> Text
arrangementLabel Arrangement
Column = Text
"column"
arrangementLabel Arrangement
Row = Text
"row"
arrangementLabel Arrangement
Flow = Text
"repeat"
arrangementLabel Arrangement
Layer = Text
"layer"
data APosition
= AStart
| AMiddle
| AEnd
anchorLabel :: APosition -> T.Text
anchorLabel :: APosition -> Text
anchorLabel APosition
AStart = Text
"start"
anchorLabel APosition
AMiddle = Text
"middle"
anchorLabel APosition
AEnd = Text
"end"
data Orientation
= Horizontal
| Vertical
orientationSpec :: Orientation -> VLSpec
orientationSpec :: Orientation -> VLSpec
orientationSpec Orientation
Horizontal = VLSpec
"horizontal"
orientationSpec Orientation
Vertical = VLSpec
"vertical"
data Position
= X
| Y
| X2
| Y2
| Theta
| Theta2
| R
| R2
| XError
| XError2
| YError
| YError2
| Longitude
| Latitude
| Longitude2
| Latitude2
positionLabel :: Position -> T.Text
positionLabel :: Position -> Text
positionLabel Position
X = Text
"x"
positionLabel Position
Y = Text
"y"
positionLabel Position
X2 = Text
"x2"
positionLabel Position
Y2 = Text
"y2"
positionLabel Position
Theta = Text
"theta"
positionLabel Position
Theta2 = Text
"theta2"
positionLabel Position
R = Text
"radius"
positionLabel Position
R2 = Text
"radius2"
positionLabel Position
XError = Text
"xError"
positionLabel Position
YError = Text
"yError"
positionLabel Position
XError2 = Text
"xError2"
positionLabel Position
YError2 = Text
"yError2"
positionLabel Position
Longitude = Text
"longitude"
positionLabel Position
Latitude = Text
"latitude"
positionLabel Position
Longitude2 = Text
"longitude2"
positionLabel Position
Latitude2 = Text
"latitude2"
data HAlign
= AlignCenter
| AlignLeft
| AlignRight
data VAlign
= AlignTop
| AlignMiddle
| AlignBottom
| AlignBaseline
| AlignLineTop
| AlignLineBottom
hAlignLabel :: HAlign -> T.Text
hAlignLabel :: HAlign -> Text
hAlignLabel HAlign
AlignLeft = Text
"left"
hAlignLabel HAlign
AlignCenter = Text
"center"
hAlignLabel HAlign
AlignRight = Text
"right"
vAlignLabel :: VAlign -> T.Text
vAlignLabel :: VAlign -> Text
vAlignLabel VAlign
AlignTop = Text
"top"
vAlignLabel VAlign
AlignMiddle = Text
"middle"
vAlignLabel VAlign
AlignBottom = Text
"bottom"
vAlignLabel VAlign
AlignBaseline = Text
"alphabetic"
vAlignLabel VAlign
AlignLineTop = Text
"line-top"
vAlignLabel VAlign
AlignLineBottom = Text
"line-bottom"
data BandAlign
= BCenter
| BExtent
bandAlignLabel :: BandAlign -> T.Text
bandAlignLabel :: BandAlign -> Text
bandAlignLabel BandAlign
BCenter = Text
"center"
bandAlignLabel BandAlign
BExtent = Text
"extent"
data StrokeCap
= CButt
| CRound
| CSquare
strokeCapLabel :: StrokeCap -> T.Text
strokeCapLabel :: StrokeCap -> Text
strokeCapLabel StrokeCap
CButt = Text
"butt"
strokeCapLabel StrokeCap
CRound = Text
"round"
strokeCapLabel StrokeCap
CSquare = Text
"square"
data StrokeJoin
= JMiter
| JRound
| JBevel
strokeJoinLabel :: StrokeJoin -> T.Text
strokeJoinLabel :: StrokeJoin -> Text
strokeJoinLabel StrokeJoin
JMiter = Text
"miter"
strokeJoinLabel StrokeJoin
JRound = Text
"round"
strokeJoinLabel StrokeJoin
JBevel = Text
"bevel"
data Scale
= ScLinear
| ScLog
| ScPow
| ScSqrt
| ScSymLog
| ScTime
| ScUtc
| ScQuantile
| ScQuantize
| ScThreshold
| ScBinOrdinal
| ScOrdinal
| ScPoint
| ScBand
scaleLabel :: Scale -> T.Text
scaleLabel :: Scale -> Text
scaleLabel Scale
ScLinear = Text
"linear"
scaleLabel Scale
ScLog = Text
"log"
scaleLabel Scale
ScPow = Text
"pow"
scaleLabel Scale
ScSqrt = Text
"sqrt"
scaleLabel Scale
ScSymLog = Text
"symlog"
scaleLabel Scale
ScTime = Text
"time"
scaleLabel Scale
ScUtc = Text
"utc"
scaleLabel Scale
ScQuantile = Text
"quantile"
scaleLabel Scale
ScQuantize = Text
"quantize"
scaleLabel Scale
ScThreshold = Text
"threshold"
scaleLabel Scale
ScBinOrdinal = Text
"bin-ordinal"
scaleLabel Scale
ScOrdinal = Text
"ordinal"
scaleLabel Scale
ScPoint = Text
"point"
scaleLabel Scale
ScBand = Text
"band"
data SortField
= WAscending FieldName
| WDescending FieldName
sortFieldSpec :: SortField -> VLSpec
sortFieldSpec :: SortField -> VLSpec
sortFieldSpec (WAscending Text
f) = [Pair] -> VLSpec
object [Text -> Pair
field_ Text
f, Text -> Pair
order_ Text
"ascending"]
sortFieldSpec (WDescending Text
f) = [Pair] -> VLSpec
object [Text -> Pair
field_ Text
f, Text -> Pair
order_ Text
"descending"]
data Cursor
= CAuto
| CDefault
| CNone
|
| 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 :: Cursor -> Text
cursorLabel Cursor
CAuto = Text
"auto"
cursorLabel Cursor
CDefault = Text
"default"
cursorLabel Cursor
CNone = Text
"none"
cursorLabel Cursor
CContextMenu = Text
"context-menu"
cursorLabel Cursor
CHelp = Text
"help"
cursorLabel Cursor
CPointer = Text
"pointer"
cursorLabel Cursor
CProgress = Text
"progress"
cursorLabel Cursor
CWait = Text
"wait"
cursorLabel Cursor
CCell = Text
"cell"
cursorLabel Cursor
CCrosshair = Text
"crosshair"
cursorLabel Cursor
CText = Text
"text"
cursorLabel Cursor
CVerticalText = Text
"vertical-text"
cursorLabel Cursor
CAlias = Text
"alias"
cursorLabel Cursor
CCopy = Text
"copy"
cursorLabel Cursor
CMove = Text
"move"
cursorLabel Cursor
CNoDrop = Text
"no-drop"
cursorLabel Cursor
CNotAllowed = Text
"not-allowed"
cursorLabel Cursor
CAllScroll = Text
"all-scroll"
cursorLabel Cursor
CColResize = Text
"col-resize"
cursorLabel Cursor
CRowResize = Text
"row-resize"
cursorLabel Cursor
CNResize = Text
"n-resize"
cursorLabel Cursor
CEResize = Text
"e-resize"
cursorLabel Cursor
CSResize = Text
"s-resize"
cursorLabel Cursor
CWResize = Text
"w-resize"
cursorLabel Cursor
CNEResize = Text
"ne-resize"
cursorLabel Cursor
CNWResize = Text
"nw-resize"
cursorLabel Cursor
CSEResize = Text
"se-resize"
cursorLabel Cursor
CSWResize = Text
"sw-resize"
cursorLabel Cursor
CEWResize = Text
"ew-resize"
cursorLabel Cursor
CNSResize = Text
"ns-resize"
cursorLabel Cursor
CNESWResize = Text
"nesw-resize"
cursorLabel Cursor
CNWSEResize = Text
"nwse-resize"
cursorLabel Cursor
CZoomIn = Text
"zoom-in"
cursorLabel Cursor
CZoomOut = Text
"zoom-out"
cursorLabel Cursor
CGrab = Text
"grab"
cursorLabel Cursor
CGrabbing = Text
"grabbing"
data OverlapStrategy
= ONone
| OParity
| OGreedy
overlapStrategyLabel :: OverlapStrategy -> VLSpec
overlapStrategyLabel :: OverlapStrategy -> VLSpec
overlapStrategyLabel OverlapStrategy
ONone = forall a. ToJSON a => a -> VLSpec
toJSON Bool
False
overlapStrategyLabel OverlapStrategy
OParity = forall a. ToJSON a => a -> VLSpec
toJSON Bool
True
overlapStrategyLabel OverlapStrategy
OGreedy = Text -> VLSpec
fromT Text
"greedy"
data Side
= STop
| SBottom
| SLeft
| SRight
sideLabel :: Side -> T.Text
sideLabel :: Side -> Text
sideLabel Side
STop = Text
"top"
sideLabel Side
SBottom = Text
"bottom"
sideLabel Side
SLeft = Text
"left"
sideLabel Side
SRight = Text
"right"
data Symbol
= SymCircle
| SymSquare
| SymCross
| SymDiamond
| SymTriangleUp
| SymTriangleDown
| SymTriangleRight
| SymTriangleLeft
| SymStroke
| SymArrow
| SymTriangle
| SymWedge
| SymPath T.Text
symbolLabel :: Symbol -> T.Text
symbolLabel :: Symbol -> Text
symbolLabel Symbol
SymCircle = Text
"circle"
symbolLabel Symbol
SymSquare = Text
"square"
symbolLabel Symbol
SymCross = Text
"cross"
symbolLabel Symbol
SymDiamond = Text
"diamond"
symbolLabel Symbol
SymTriangleUp = Text
"triangle-up"
symbolLabel Symbol
SymTriangleDown = Text
"triangle-down"
symbolLabel Symbol
SymTriangleRight = Text
"triangle-right"
symbolLabel Symbol
SymTriangleLeft = Text
"triangle-left"
symbolLabel Symbol
SymStroke = Text
"stroke"
symbolLabel Symbol
SymArrow = Text
"arrow"
symbolLabel Symbol
SymTriangle = Text
"triangle"
symbolLabel Symbol
SymWedge = Text
"wedge"
symbolLabel (SymPath Text
svgPath) = Text
svgPath
data StackProperty
= StOffset StackOffset
| StSort [SortField]
data StackOffset
= StZero
| StNormalize
| StCenter
| NoStack
stackOffsetSpec :: StackOffset -> VLSpec
stackOffsetSpec :: StackOffset -> VLSpec
stackOffsetSpec StackOffset
StZero = VLSpec
"zero"
stackOffsetSpec StackOffset
StNormalize = VLSpec
"normalize"
stackOffsetSpec StackOffset
StCenter = VLSpec
"center"
stackOffsetSpec StackOffset
NoStack = VLSpec
A.Null
stackOffset :: StackOffset -> Pair
stackOffset :: StackOffset -> Pair
stackOffset StackOffset
so = Key
"stack" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StackOffset -> VLSpec
stackOffsetSpec StackOffset
so
stackPropertySpecOffset , stackPropertySpecSort:: StackProperty -> Maybe VLSpec
stackPropertySpecOffset :: StackProperty -> Maybe VLSpec
stackPropertySpecOffset (StOffset StackOffset
op) = forall a. a -> Maybe a
Just (StackOffset -> VLSpec
stackOffsetSpec StackOffset
op)
stackPropertySpecOffset StackProperty
_ = forall a. Maybe a
Nothing
stackPropertySpecSort :: StackProperty -> Maybe VLSpec
stackPropertySpecSort (StSort [SortField]
sfs) = forall a. a -> Maybe a
Just (forall a. ToJSON a => a -> VLSpec
toJSON (forall a b. (a -> b) -> [a] -> [b]
map SortField -> VLSpec
sortFieldSpec [SortField]
sfs))
stackPropertySpecSort StackProperty
_ = forall a. Maybe a
Nothing
data TooltipContent
= TTEncoding
| TTData
| TTNone
ttContentLabel :: TooltipContent -> T.Text
ttContentLabel :: TooltipContent -> Text
ttContentLabel TooltipContent
TTEncoding = Text
"encoding"
ttContentLabel TooltipContent
TTData = Text
"data"
ttContentLabel TooltipContent
TTNone = Text
"null"
data Channel
= ChX
| ChY
| ChX2
| ChY2
| ChLongitude
| ChLongitude2
| ChLatitude
| ChLatitude2
| ChAngle
| ChTheta
| ChTheta2
| ChRadius
| ChRadius2
| ChColor
| ChFill
| ChFillOpacity
| ChHref
| ChKey
| ChOpacity
| ChShape
| ChSize
| ChStroke
| ChStrokeDash
| ChStrokeOpacity
| ChStrokeWidth
| ChText
| ChDescription
| ChURL
channelLabel :: Channel -> T.Text
channelLabel :: Channel -> Text
channelLabel Channel
ChX = Text
"x"
channelLabel Channel
ChY = Text
"y"
channelLabel Channel
ChX2 = Text
"x2"
channelLabel Channel
ChY2 = Text
"y2"
channelLabel Channel
ChLongitude = Text
"longitude"
channelLabel Channel
ChLongitude2 = Text
"longitude2"
channelLabel Channel
ChLatitude = Text
"latitude"
channelLabel Channel
ChLatitude2 = Text
"latitude2"
channelLabel Channel
ChAngle = Text
"angle"
channelLabel Channel
ChTheta = Text
"theta"
channelLabel Channel
ChTheta2 = Text
"theta2"
channelLabel Channel
ChRadius = Text
"radius"
channelLabel Channel
ChRadius2 = Text
"radius2"
channelLabel Channel
ChColor = Text
"color"
channelLabel Channel
ChFill = Text
"fill"
channelLabel Channel
ChFillOpacity = Text
"fillOpacity"
channelLabel Channel
ChHref = Text
"href"
channelLabel Channel
ChKey = Text
"key"
channelLabel Channel
ChOpacity = Text
"opacity"
channelLabel Channel
ChShape = Text
"shape"
channelLabel Channel
ChSize = Text
"size"
channelLabel Channel
ChStroke = Text
"stroke"
channelLabel Channel
ChStrokeDash = Text
"strokeDash"
channelLabel Channel
ChStrokeOpacity = Text
"strokeOpacity"
channelLabel Channel
ChStrokeWidth = Text
"strokeWidth"
channelLabel Channel
ChText = Text
"text"
channelLabel Channel
ChDescription = Text
"description"
channelLabel Channel
ChURL = Text
"url"
data Resolution
= Shared
| Independent
resolutionLabel :: Resolution -> T.Text
resolutionLabel :: Resolution -> Text
resolutionLabel Resolution
Shared = Text
"shared"
resolutionLabel Resolution
Independent = Text
"independent"
data Resolve
= RAxis [(Channel, Resolution)]
| RLegend [(Channel, Resolution)]
| RScale [(Channel, Resolution)]
resolveProperty :: Resolve -> ResolveSpec
resolveProperty :: Resolve -> ResolveSpec
resolveProperty Resolve
res =
let (Text
nme, [(Channel, Resolution)]
rls) = case Resolve
res of
RAxis [(Channel, Resolution)]
chRules -> (Text
"axis", [(Channel, Resolution)]
chRules)
RLegend [(Channel, Resolution)]
chRules -> (Text
"legend", [(Channel, Resolution)]
chRules)
RScale [(Channel, Resolution)]
chRules -> (Text
"scale", [(Channel, Resolution)]
chRules)
ans :: [(Text, VLSpec)]
ans = forall a b. (a -> b) -> [a] -> [b]
map (\(Channel
ch, Resolution
rule) -> Channel -> Text
channelLabel Channel
ch forall a. ToJSON a => Text -> a -> (Text, VLSpec)
.=~ Resolution -> Text
resolutionLabel Resolution
rule) [(Channel, Resolution)]
rls
in (Text, VLSpec) -> ResolveSpec
RS (Text
nme, [(Text, VLSpec)] -> VLSpec
toObject [(Text, VLSpec)]
ans)
data Bounds
= Full
| Flush
boundsSpec :: Bounds -> VLSpec
boundsSpec :: Bounds -> VLSpec
boundsSpec Bounds
Full = VLSpec
"full"
boundsSpec Bounds
Flush = VLSpec
"flush"
data CompositionAlignment
= CANone
| CAEach
| CAAll
compositionAlignmentSpec :: CompositionAlignment -> VLSpec
compositionAlignmentSpec :: CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
CANone = VLSpec
"none"
compositionAlignmentSpec CompositionAlignment
CAEach = VLSpec
"each"
compositionAlignmentSpec CompositionAlignment
CAAll = VLSpec
"all"
data Padding
= PSize Double
| PEdges Double Double Double Double
paddingSpec :: Padding -> VLSpec
paddingSpec :: Padding -> VLSpec
paddingSpec (PSize Double
p) = forall a. ToJSON a => a -> VLSpec
toJSON Double
p
paddingSpec (PEdges Double
l Double
t Double
r Double
b) =
[Pair] -> VLSpec
object [ Key
"left" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
l
, Key
"top" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
t
, Key
"right" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
r
, Key
"bottom" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
b
]
data Autosize
= AContent
| AFit
| AFitX
| AFitY
| ANone
| APad
| APadding
| AResize
autosizeProperty :: Autosize -> Pair
autosizeProperty :: Autosize -> Pair
autosizeProperty Autosize
APad = Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"pad"
autosizeProperty Autosize
AFit = Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"fit"
autosizeProperty Autosize
AFitX = Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"fit-x"
autosizeProperty Autosize
AFitY = Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"fit-y"
autosizeProperty Autosize
ANone = Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"none"
autosizeProperty Autosize
AResize = Key
"resize" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
True
autosizeProperty Autosize
AContent = Key
"contains" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"content"
autosizeProperty Autosize
APadding = Key
"contains" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"padding"
data RepeatFields
= RowFields [FieldName]
| ColumnFields [FieldName]
| LayerFields [FieldName]
repeatFieldsProperty :: RepeatFields -> Pair
repeatFieldsProperty :: RepeatFields -> Pair
repeatFieldsProperty (RowFields [Text]
fs) = Key
"row" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
fs
repeatFieldsProperty (ColumnFields [Text]
fs) = Key
"column" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
fs
repeatFieldsProperty (LayerFields [Text]
fs) = Key
"layer" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
fs
data CInterpolate
= CubeHelix Double
| CubeHelixLong Double
| Hcl
| HclLong
| Hsl
| HslLong
| Lab
| Rgb Double
#if MIN_VERSION_aeson(2, 0, 0)
pairT :: Key.Key -> T.Text -> Pair
pairT :: Key -> Text -> Pair
pairT Key
a Text
b = Key
a forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
b
#else
pairT :: T.Text -> T.Text -> Pair
pairT a b = a .= b
#endif
cInterpolateSpec :: CInterpolate -> VLSpec
cInterpolateSpec :: CInterpolate -> VLSpec
cInterpolateSpec (Rgb Double
gamma) = [Pair] -> VLSpec
object [Key -> Text -> Pair
pairT Key
"type" Text
"rgb", Key
"gamma" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
gamma]
cInterpolateSpec CInterpolate
Hsl = [Pair] -> VLSpec
object [Key -> Text -> Pair
pairT Key
"type" Text
"hsl"]
cInterpolateSpec CInterpolate
HslLong = [Pair] -> VLSpec
object [Key -> Text -> Pair
pairT Key
"type" Text
"hsl-long"]
cInterpolateSpec CInterpolate
Lab = [Pair] -> VLSpec
object [Key -> Text -> Pair
pairT Key
"type" Text
"lab"]
cInterpolateSpec CInterpolate
Hcl = [Pair] -> VLSpec
object [Key -> Text -> Pair
pairT Key
"type" Text
"hcl"]
cInterpolateSpec CInterpolate
HclLong = [Pair] -> VLSpec
object [Key -> Text -> Pair
pairT Key
"type" Text
"hcl-long"]
cInterpolateSpec (CubeHelix Double
gamma) = [Pair] -> VLSpec
object [Key -> Text -> Pair
pairT Key
"type" Text
"cubehelix", Key
"gamma" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
gamma]
cInterpolateSpec (CubeHelixLong Double
gamma) = [Pair] -> VLSpec
object [Key -> Text -> Pair
pairT Key
"type" Text
"cubehelix-long", Key
"gamma" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
gamma]
data ViewBackground
= VBStyle [StyleLabel]
| VBCornerRadius Double
| VBFill Color
| VBNoFill
| VBFillOpacity Opacity
| VBOpacity Opacity
| VBStroke Color
| VBNoStroke
| VBStrokeOpacity Opacity
| VBStrokeWidth Double
| VBStrokeCap StrokeCap
| VBStrokeDash DashStyle
| VBStrokeDashOffset DashOffset
| VBStrokeJoin StrokeJoin
| VBStrokeMiterLimit Double
viewBackgroundSpec :: ViewBackground -> Pair
viewBackgroundSpec :: ViewBackground -> Pair
viewBackgroundSpec (VBStyle [Text
style]) = Key
"style" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
style
viewBackgroundSpec (VBStyle [Text]
styles) = Key
"style" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
styles
viewBackgroundSpec (VBCornerRadius Double
r) = Key
"cornerRadius" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
r
viewBackgroundSpec (VBFill Text
s) = Key
"fill" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
viewBackgroundSpec ViewBackground
VBNoFill = Key
"fill" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null
viewBackgroundSpec (VBFillOpacity Double
x) = Key
"fillOpacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBOpacity Double
x) = Key
"opacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBStroke Text
s) = Key
"stroke" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
viewBackgroundSpec ViewBackground
VBNoStroke = Key
"stroke" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null
viewBackgroundSpec (VBStrokeOpacity Double
x) = Key
"strokeOpacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBStrokeCap StrokeCap
cap) = Key
"strokeCap" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrokeCap -> Text
strokeCapLabel StrokeCap
cap
viewBackgroundSpec (VBStrokeJoin StrokeJoin
jn) = Key
"strokeJoin" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrokeJoin -> Text
strokeJoinLabel StrokeJoin
jn
viewBackgroundSpec (VBStrokeWidth Double
x) = Key
"strokeWidth" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBStrokeDash DashStyle
xs) = Key
"strokeDash" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DashStyle -> VLSpec
fromDS DashStyle
xs
viewBackgroundSpec (VBStrokeDashOffset Double
x) = Key
"strokeDashOffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBStrokeMiterLimit Double
x) = Key
"strokeMiterLimit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
data
= HFormat T.Text
| HFormatAsNum
| HFormatAsTemporal
| HFormatAsCustom T.Text
| HLabel Bool
| HLabelAlign HAlign
| HLabelAnchor APosition
| HLabelAngle Angle
| HLabelBaseline VAlign
| HLabelColor Color
| HLabelExpr VegaExpr
| HLabelFont T.Text
| HLabelFontSize Double
| HLabelFontStyle T.Text
| HLabelFontWeight FontWeight
| HLabelLimit Double
| HLabelLineHeight Double
| HLabelOrient Side
| HLabelPadding Double
| HOrient Side
| HTitle T.Text
| HNoTitle
| HTitleAlign HAlign
| HTitleAnchor APosition
| HTitleAngle Angle
| HTitleBaseline VAlign
| HTitleColor Color
| HTitleFont T.Text
| HTitleFontSize Double
| HTitleFontStyle T.Text
| HTitleFontWeight FontWeight
| HTitleLimit Double
| HTitleLineHeight Double
| HTitleOrient Side
| HTitlePadding Double
headerProperty :: HeaderProperty -> Pair
(HFormat Text
fmt) = Key
"format" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
fmt
headerProperty HeaderProperty
HFormatAsNum = Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"number"
headerProperty HeaderProperty
HFormatAsTemporal = Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromT Text
"time"
headerProperty (HFormatAsCustom Text
c) = Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
c
headerProperty (HTitle Text
ttl) = Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
splitOnNewline Text
ttl
headerProperty HeaderProperty
HNoTitle = Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null
headerProperty (HLabel Bool
b) = Key
"labels" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
headerProperty (HLabelAlign HAlign
ha) = Key
"labelAlign" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HAlign -> Text
hAlignLabel HAlign
ha
headerProperty (HLabelAnchor APosition
a) = Key
"labelAnchor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= APosition -> Text
anchorLabel APosition
a
headerProperty (HLabelAngle Double
x) = Key
"labelAngle" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HLabelBaseline VAlign
va) = Key
"labelBaseline" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VAlign -> Text
vAlignLabel VAlign
va
headerProperty (HLabelColor Text
s) = Key
"labelColor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromColor Text
s
headerProperty (HLabelExpr Text
s) = Key
"labelExpr" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HLabelFont Text
s) = Key
"labelFont" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HLabelFontSize Double
x) = Key
"labelFontSize" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HLabelFontStyle Text
s) = Key
"labelFontStyle" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HLabelFontWeight FontWeight
w) = Key
"labelFontWeight" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FontWeight -> VLSpec
fontWeightSpec FontWeight
w
headerProperty (HLabelLimit Double
x) = Key
"labelLimit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HLabelLineHeight Double
x) = Key
"labelLineHeight" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HLabelOrient Side
orient) = Key
"labelOrient" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Side -> Text
sideLabel Side
orient
headerProperty (HLabelPadding Double
x) = Key
"labelPadding" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HOrient Side
orient) = Key
"orient" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Side -> Text
sideLabel Side
orient
headerProperty (HTitleAlign HAlign
ha) = Key
"titleAlign" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HAlign -> Text
hAlignLabel HAlign
ha
headerProperty (HTitleAnchor APosition
a) = Key
"titleAnchor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= APosition -> Text
anchorLabel APosition
a
headerProperty (HTitleAngle Double
x) = Key
"titleAngle" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HTitleBaseline VAlign
va) = Key
"titleBaseline" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VAlign -> Text
vAlignLabel VAlign
va
headerProperty (HTitleColor Text
s) = Key
"titleColor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> VLSpec
fromColor Text
s
headerProperty (HTitleFont Text
s) = Key
"titleFont" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HTitleFontWeight FontWeight
fw) = Key
"titleFontWeight" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FontWeight -> VLSpec
fontWeightSpec FontWeight
fw
headerProperty (HTitleFontSize Double
x) = Key
"titleFontSize" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HTitleFontStyle Text
s) = Key
"titleFontStyle" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HTitleLimit Double
x) = Key
"titleLimit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HTitleLineHeight Double
x) = Key
"titleLineHeight" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HTitleOrient Side
orient) = Key
"titleOrient" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Side -> Text
sideLabel Side
orient
headerProperty (HTitlePadding Double
x) = Key
"titlePadding" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x