Copyright | (c) Douglas Burke 2018-2021 |
---|---|
License | BSD3 |
Maintainer | dburke.gw@gmail.com |
Stability | unstable |
Portability | CPP, OverloadedStrings, TupleSections |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
- Creating a Vega-Lite Specification
- Creating the Data Specification
- Creating the Transform Specification
- Creating the Mark Specification
- Creating the Encoding Specification
- Creating view compositions
- Creating Selections for Interaction
- Top-level Settings
- General Data types
- Update notes
This is a port of the
Elm Vega Lite module,
written by Jo Wood of the giCentre at the City
University of London. It was originally based on version 2.2.1
but
it has been updated to match later versions. This module allows users
to create a Vega-Lite specification, targeting version 4 of the
JSON schema.
Version 0.12 of hvega
supports version 4.15 of the Vega-Lite specification.
Although this was based on the Elm module, there have been a number of changes - on both sides.
Please see Graphics.Vega.Tutorials.VegaLite for an introduction
to using hvega
to create visualizations. The
ihaskell-hvega
package provides an easy way to embed Vega-Lite
visualizations in an IHaskell notebook (using
Vega-Embed).
Examples
Note that this module exports several symbols that are exported
by the Prelude, such as filter
, lookup
,
and repeat
; to avoid name clashes it's therefore advised
to either import the module qualified, for example:
import qualified Graphics.Vega.VegaLite as VL
or to hide the clashing names explicitly:
import Prelude hiding (filter, lookup, repeat)
In the following examples, we'll assume the latter.
Example: viewing columns from a file
The Vega-Lite example gallery contain a number of visualizations of the "cars.json" dataset (and many other datasets ;-), which has a number of columns to display, such as "Horsepower", "Miles_per_Gallon", and "Origin". The following code will create a visualization that plots the efficiency of the cars (the "mpg") as a function of its Horsepower, and color-code by the origin of the car:
let cars =dataFromUrl
"https://vega.github.io/vega-datasets/data/cars.json" [] enc =encoding
.position
X
[PName
"Horsepower",PmType
Quantitative
] .position
Y
[PName
"Miles_per_Gallon",PmType
Quantitative
,PTitle
"Miles per Gallon" ] .color
[MName
"Origin" ] bkg =background
"rgba(0, 0, 0, 0.05)" intoVegaLite
[ bkg, cars,mark
Circle
[MTooltip
TTEncoding
], enc [] ]
When viewed with a Vega-Lite viewer (normally some form of a browser), you can view the result. For instance:
- the
fromVL
function will create the JSON representation of the visualization, which can then be passed to a Vega-Lite viewer; - a routine like
toHtmlFile
can be used to create a HTML file that will display the visualization using the Vega-Embed Javascript library; - users of the
Jupyter notebook
environment can make use of the automatic display of theVegaLite
type, usingihaskell-hvega
, to view an in-browser version of the plot (generated via Vega-Embed); - and users of
Jupyter lab
can use thevlShow
method (fromihaskell-hvega
), but be aware that it is currently limited to only supporing features from Vega-Lite version 2.
The visualization can be viewed in the Vega Editor, which lets you interact with the plot and modify its contents, as shown for this example.
It can also be viewed as a PNG version:
Example: faceting, data transformation, and interaction
The following example is rather lengthy, as it includes data tranformation (sub-setting the data and creating a new column), automatic faceting (that is, creating separate plots for unique values of a data column), interactive elements (the ability to filter a plot by selecting a subset in another element), and some basic configuration and styling (primarily to change the text sizes). The Graphics.Vega.Tutorials.VegaLite tutorial should be reviewed to understand how the plot works!
It's aim is to show the recent community measurements of the
brightness of
the star Betelgeuse,
which caused much interest in the Astronomical world at the
start of 2020 as it became much fainter than normal
(although it is massive enough to go supernova, it is not
expected to happen for quite a while yet). The data shown
is based on data collated by the
AAVSO, and converted to JSON format,
with the primary columns of interest being "jd
" (the
date of the observation, in the
Julian day system),
"magnitude
" (the brightness of the star, reported
as an
apparent magnitude),
and "filterName"
(the filter through which the measurement was
made). For display purposes we are only going to use the
"Vis.
" and "V
" filters (the former is a by-eye estimate,
which is less accurate but has the advantage of having been used
for a long time, and the second is measured from a in image
taken by a CCD detector,
which is more accurate and repeatable, but more costly to obtain),
and the date field is going to be converted into the number of
days since the start of 2020 (via a little bit of subtraction).
For "historical reasons", the magnitude system used by Astronomers
to measure how bright a system is reversed, so that larger magnitudes
mean fainter systems. For this reason, the magnitude axis is reversed
in this visualization, so that as Betelgeuse dims the values drop.
{-# LANGUAGE OverloadedStrings #-} betelgeuse = let desc = "How has Betelgeuse's brightness varied, based on data collated by AAVSO (https://www.aavso.org/). " ++ "You should also look at https://twitter.com/betelbot and https://github.com/hippke/betelbot. " ++ "It was all the rage on social media at the start of 2020." titleStr = "Betelegeuse's magnitude measurements, collated by AAVSO" -- height and width of individual plots (in pixels) w =width
600 h =height
150 -- Define the properties used for the "position" channels. For this example -- it makes sense to define as functions since they are used several times. -- pos1Opts fld ttl = [PName
fld,PmType
Quantitative
,PTitle
ttl] x1Opts = pos1Opts "days" "Days since January 1, 2020" y1Opts = pos1Opts "magnitude" "Magnitude" ++ [PSort
[Descending
], y1Range] y1Range =PScale
[SDomain
(DNumbers
[-1, 3])] -- The filter name is used as a facet, but also to define the -- color and shape of the points. -- filtOpts = [MName
"filterName"] filtEnc =color
(MLegend
[LTitle
"Filter",LTitleFontSize
16,LLabelFontSize
14] : filtOpts) .shape
filtOpts -- In an attempt to make the V filter results visible, I have chosen -- to use open symbols. It doesn't really work out well. -- circle =mark
Point
[MOpacity
0.5,MFilled
False] -- What is plotted in the "overview" plot? -- encOverview =encoding
.position
X
x1Opts .position
Y
y1Opts . filtEnc -- Select roughly the last year's observations (roughly the length of -- time that Betelgeuse is visible) -- xlim = (Number
(-220),Number
100) ylim = (Number
(-0.5),Number
2.5) overview =asSpec
[ w , h , encOverview [] ,selection
.select
selNameInterval
[Encodings
[ChX
,ChY
] ,SInitInterval
(Just xlim) (Just ylim) ] $ [] , circle ] -- What is plotted in the "detail" plot? -- selName = "brush" pos2Opts fld = [PName
fld,PmType
Quantitative
,PNoTitle
,PScale
[SDomainOpt
(DSelectionField
selName fld)] ] x2Opts = pos2Opts "days" y2Opts = pos2Opts "magnitude" ++ [PSort
[Descending
]] encDetail =encoding
.position
X
x2Opts .position
Y
y2Opts . filtEnc detail =asSpec
[ w , h , encDetail [] , circle ] -- Control the labelling of the faceted plots. Here we move the -- label so that it appears at the top-right corner of each plot -- and remove the title. -- headerOpts = [HLabelFontSize
16 ,HLabelAlign
AlignRight
,HLabelAnchor
AEnd
,HLabelPadding
(-24) ,HNoTitle
,HLabelExpr
"'Filter: ' + datum.label" ] -- The "detail" plot has multiple rows, one for each filter. -- details =asSpec
[columns
1 ,facetFlow
[FName
"filterName" ,FHeader
headerOpts ] ,spacing
10 ,specification
detail ] intoVegaLite
[description
desc ,title
titleStr [TFontSize
18] ,dataFromUrl
"https://raw.githubusercontent.com/DougBurke/hvega/master/hvega/data/betelgeuse-2020-03-19.json" [] ,transform
-- concentrate on the two filters with a reasonable number of points .filter
(FExpr
"datum.filterName[0] === 'V'") -- remove some "outliers" .filter
(FExpr
"datum.magnitude < 4") -- subtract Jan 1 2020 (start of day, hence the .0 rather than .5) .calculateAs
"datum.jd - 2458849.0" "days" $ [] ,vConcat
[overview, details] ,configure
-- Change axis titles from bold- to normal-weight, -- and increase the size of the labels .configuration
(Axis
[TitleFontWeight
Normal
,TitleFontSize
16,LabelFontSize
14]) $ [] ]
The PNG version shows the basic features:
However this is missing the interactive elements of the visualization, primarily selection and zooming in the top plot changes the axis ranges of the bottom two plots. This interactivity requires a Vega-Lite viewer such as the Vega Editor.
Synopsis
- toVegaLite :: [PropertySpec] -> VegaLite
- toVegaLiteSchema :: Text -> [PropertySpec] -> VegaLite
- vlSchema2 :: Text
- vlSchema3 :: Text
- vlSchema4 :: Text
- vlSchema :: Natural -> Maybe Natural -> Maybe Natural -> Maybe Text -> Text
- fromVL :: VegaLite -> Value
- data VLProperty
- = VLAlign
- | VLAutosize
- | VLBackground
- | VLBounds
- | VLCenter
- | VLColumns
- | VLConcat
- | VLConfig
- | VLData
- | VLDatasets
- | VLDescription
- | VLEncoding
- | VLFacet
- | VLHConcat
- | VLHeight
- | VLLayer
- | VLMark
- | VLName
- | VLPadding
- | VLProjection
- | VLRepeat
- | VLResolve
- | VLSelection
- | VLSpacing
- | VLSpecification
- | VLTitle
- | VLTransform
- | VLUserMetadata
- | VLVConcat
- | VLViewBackground
- | VLWidth
- type VLSpec = Value
- data VegaLite
- type PropertySpec = (VLProperty, VLSpec)
- type LabelledSpec = (Text, VLSpec)
- data EncodingSpec
- toEncodingSpec :: Text -> VLSpec -> EncodingSpec
- fromEncodingSpec :: EncodingSpec -> (Text, VLSpec)
- data TransformSpec
- toTransformSpec :: VLSpec -> TransformSpec
- fromTransformSpec :: TransformSpec -> VLSpec
- data ResolveSpec
- toResolveSpec :: Text -> VLSpec -> ResolveSpec
- fromResolveSpec :: ResolveSpec -> (Text, VLSpec)
- data SelectSpec
- toSelectSpec :: SelectionLabel -> VLSpec -> SelectSpec
- fromSelectSpec :: SelectSpec -> (SelectionLabel, VLSpec)
- data ConfigureSpec
- toConfigureSpec :: Text -> VLSpec -> ConfigureSpec
- fromConfigureSpec :: ConfigureSpec -> (Text, VLSpec)
- type BuildEncodingSpecs = [EncodingSpec] -> [EncodingSpec]
- type BuildTransformSpecs = [TransformSpec] -> [TransformSpec]
- type BuildResolveSpecs = [ResolveSpec] -> [ResolveSpec]
- type BuildSelectSpecs = [SelectSpec] -> [SelectSpec]
- type BuildConfigureSpecs = [ConfigureSpec] -> [ConfigureSpec]
- type Angle = Double
- type Color = Text
- type DashStyle = [Double]
- type DashOffset = Double
- type FieldName = Text
- type GradientCoord = Double
- type GradientStops = [(GradientCoord, Color)]
- type Opacity = Double
- type SelectionLabel = Text
- type StyleLabel = Text
- type VegaExpr = Text
- type ZIndex = Natural
- toHtml :: VegaLite -> Text
- toHtmlFile :: FilePath -> VegaLite -> IO ()
- toHtmlWith :: Maybe Value -> VegaLite -> Text
- toHtmlFileWith :: Maybe Value -> FilePath -> VegaLite -> IO ()
- dataFromUrl :: Text -> [Format] -> Data
- dataFromColumns :: [Format] -> [DataColumn] -> Data
- dataFromRows :: [Format] -> [DataRow] -> Data
- dataFromJson :: VLSpec -> [Format] -> Data
- dataFromSource :: Text -> [Format] -> Data
- dataName :: Text -> Data -> Data
- datasets :: [(Text, Data)] -> Data
- dataColumn :: FieldName -> DataValues -> [DataColumn] -> [DataColumn]
- dataRow :: [(FieldName, DataValue)] -> [DataRow] -> [DataRow]
- noData :: Data
- type Data = (VLProperty, VLSpec)
- type DataColumn = [LabelledSpec]
- type DataRow = VLSpec
- geometry :: Geometry -> [(Text, DataValue)] -> VLSpec
- geoFeatureCollection :: [VLSpec] -> VLSpec
- geometryCollection :: [VLSpec] -> VLSpec
- data Geometry
- dataSequence :: Double -> Double -> Double -> Data
- dataSequenceAs :: Double -> Double -> Double -> FieldName -> Data
- sphere :: Data
- graticule :: [GraticuleProperty] -> Data
- data GraticuleProperty
- data Format
- data DataType
- transform :: [TransformSpec] -> PropertySpec
- projection :: [ProjectionProperty] -> PropertySpec
- data ProjectionProperty
- = PrType Projection
- | PrClipAngle (Maybe Double)
- | PrClipExtent ClipRect
- | PrCenter Double Double
- | PrScale Double
- | PrTranslate Double Double
- | PrRotate Double Double Double
- | PrPrecision Double
- | PrReflectX Bool
- | PrReflectY Bool
- | PrCoefficient Double
- | PrDistance Double
- | PrFraction Double
- | PrLobes Int
- | PrParallel Double
- | PrRadius Double
- | PrRatio Double
- | PrSpacing Double
- | PrTilt Double
- data Projection
- data ClipRect
- aggregate :: [VLSpec] -> [FieldName] -> BuildTransformSpecs
- joinAggregate :: [VLSpec] -> [WindowProperty] -> BuildTransformSpecs
- opAs :: Operation -> FieldName -> FieldName -> VLSpec
- timeUnitAs :: TimeUnit -> FieldName -> FieldName -> BuildTransformSpecs
- data Operation
- binAs :: [BinProperty] -> FieldName -> FieldName -> BuildTransformSpecs
- data BinProperty
- stack :: FieldName -> [FieldName] -> FieldName -> FieldName -> [StackProperty] -> BuildTransformSpecs
- data StackProperty
- data StackOffset
- = StZero
- | StNormalize
- | StCenter
- | NoStack
- calculateAs :: VegaExpr -> FieldName -> BuildTransformSpecs
- filter :: Filter -> BuildTransformSpecs
- data Filter
- = FEqual FieldName DataValue
- | FLessThan FieldName DataValue
- | FLessThanEq FieldName DataValue
- | FGreaterThan FieldName DataValue
- | FGreaterThanEq FieldName DataValue
- | FExpr VegaExpr
- | FCompose BooleanOp
- | FSelection SelectionLabel
- | FOneOf FieldName DataValues
- | FRange FieldName FilterRange
- | FValid FieldName
- data FilterRange
- flatten :: [FieldName] -> BuildTransformSpecs
- flattenAs :: [FieldName] -> [FieldName] -> BuildTransformSpecs
- fold :: [FieldName] -> BuildTransformSpecs
- foldAs :: [FieldName] -> FieldName -> FieldName -> BuildTransformSpecs
- pivot :: FieldName -> FieldName -> [PivotProperty] -> BuildTransformSpecs
- data PivotProperty
- lookup :: FieldName -> Data -> FieldName -> LookupFields -> BuildTransformSpecs
- lookupSelection :: FieldName -> SelectionLabel -> FieldName -> BuildTransformSpecs
- data LookupFields
- lookupAs :: FieldName -> Data -> FieldName -> FieldName -> BuildTransformSpecs
- impute :: FieldName -> FieldName -> [ImputeProperty] -> BuildTransformSpecs
- data ImputeProperty
- data ImMethod
- sample :: Int -> BuildTransformSpecs
- density :: FieldName -> [DensityProperty] -> BuildTransformSpecs
- data DensityProperty
- loess :: FieldName -> FieldName -> [LoessProperty] -> BuildTransformSpecs
- data LoessProperty
- regression :: FieldName -> FieldName -> [RegressionProperty] -> BuildTransformSpecs
- data RegressionProperty
- data RegressionMethod
- quantile :: FieldName -> [QuantileProperty] -> BuildTransformSpecs
- data QuantileProperty
- window :: [([Window], FieldName)] -> [WindowProperty] -> BuildTransformSpecs
- data Window
- data WOperation
- data WindowProperty
- mark :: Mark -> [MarkProperty] -> PropertySpec
- data Mark
- data MarkProperty
- = MAlign HAlign
- | MAngle Angle
- | MAria Bool
- | MAriaDescription Text
- | MAriaRole Text
- | MAriaRoleDescription Text
- | MAspect Bool
- | MBandSize Double
- | MBaseline VAlign
- | MBinSpacing Double
- | MBlend BlendMode
- | MBorders [MarkProperty]
- | MNoBorders
- | MBox [MarkProperty]
- | MNoBox
- | MClip Bool
- | MColor Color
- | MColorGradient ColorGradient GradientStops [GradientProperty]
- | MCornerRadius Double
- | MCornerRadiusEnd Double
- | MCornerRadiusTL Double
- | MCornerRadiusTR Double
- | MCornerRadiusBL Double
- | MCornerRadiusBR Double
- | MCursor Cursor
- | MDir TextDirection
- | MContinuousBandSize Double
- | MDiscreteBandSize Double
- | MdX Double
- | MdY Double
- | MEllipsis Text
- | MExtent MarkErrorExtent
- | MFill Color
- | MFilled Bool
- | MFillGradient ColorGradient GradientStops [GradientProperty]
- | MFillOpacity Opacity
- | MFont Text
- | MFontSize Double
- | MFontStyle Text
- | MFontWeight FontWeight
- | MHeight Double
- | MHRef Text
- | MInnerRadius Double
- | MInterpolate MarkInterpolation
- | MLimit Double
- | MLine LineMarker
- | MLineBreak Text
- | MLineHeight Double
- | MMedian [MarkProperty]
- | MNoMedian
- | MOpacity Opacity
- | MOrder Bool
- | MOrient Orientation
- | MOuterRadius Double
- | MOutliers [MarkProperty]
- | MNoOutliers
- | MPadAngle Double
- | MPoint PointMarker
- | MRadius Double
- | MRadius2 Double
- | MRadiusOffset Double
- | MRadius2Offset Double
- | MRemoveInvalid Bool
- | MRule [MarkProperty]
- | MNoRule
- | MShape Symbol
- | MSize Double
- | MStroke Color
- | MStrokeCap StrokeCap
- | MStrokeDash DashStyle
- | MStrokeDashOffset DashOffset
- | MStrokeGradient ColorGradient GradientStops [GradientProperty]
- | MStrokeJoin StrokeJoin
- | MStrokeMiterLimit Double
- | MStrokeOpacity Opacity
- | MStrokeWidth Double
- | MStyle [StyleLabel]
- | MTension Double
- | MText Text
- | MTexts [Text]
- | MTheta Double
- | MTheta2 Double
- | MThetaOffset Double
- | MTheta2Offset Double
- | MThickness Double
- | MTicks [MarkProperty]
- | MNoTicks
- | MTimeUnitBand Double
- | MTimeUnitBandPosition Double
- | MTooltip TooltipContent
- | MWidth Double
- | MX Double
- | MX2 Double
- | MXOffset Double
- | MX2Offset Double
- | MY Double
- | MY2 Double
- | MYOffset Double
- | MY2Offset Double
- | MXWidth
- | MX2Width
- | MYHeight
- | MY2Height
- data StrokeCap
- data StrokeJoin
- data Orientation
- data MarkInterpolation
- data Symbol
- data PointMarker
- data LineMarker
- = LMNone
- | LMMarker [MarkProperty]
- data MarkErrorExtent
- data TooltipContent
- = TTEncoding
- | TTData
- | TTNone
- data ColorGradient
- data GradientProperty
- data TextDirection
- data BlendMode
- 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
- encoding :: [EncodingSpec] -> PropertySpec
- data Measurement
- position :: Position -> [PositionChannel] -> BuildEncodingSpecs
- data Position
- data PositionChannel
- = PName FieldName
- | PHeight
- | PWidth
- | PDatum DataValue
- | PNumber Double
- | PRepeat Arrangement
- | PRepeatDatum Arrangement
- | PmType Measurement
- | PBin [BinProperty]
- | PBinned
- | PTimeUnit TimeUnit
- | PTitle Text
- | PNoTitle
- | PAggregate Operation
- | PScale [ScaleProperty]
- | PAxis [AxisProperty]
- | PSort [SortProperty]
- | PStack StackOffset
- | PImpute [ImputeProperty]
- | PBand Double
- data SortProperty
- data SortField
- data AxisProperty
- = AxAria Bool
- | AxAriaDescription Text
- | AxBandPosition Double
- | AxDataCondition BooleanOp ConditionalAxisProperty
- | AxDomain Bool
- | AxDomainCap StrokeCap
- | AxDomainColor Color
- | AxDomainDash DashStyle
- | AxDomainDashOffset DashOffset
- | AxDomainOpacity Opacity
- | AxDomainWidth Double
- | AxFormat Text
- | AxFormatAsNum
- | AxFormatAsTemporal
- | AxFormatAsCustom Text
- | AxGrid Bool
- | AxGridCap StrokeCap
- | AxGridColor Color
- | AxGridDash DashStyle
- | AxGridDashOffset DashOffset
- | AxGridOpacity Opacity
- | AxGridWidth Double
- | AxLabels Bool
- | AxLabelAlign HAlign
- | AxLabelAngle Angle
- | AxLabelBaseline VAlign
- | AxLabelNoBound
- | AxLabelBound
- | AxLabelBoundValue Double
- | AxLabelColor Color
- | AxLabelExpr VegaExpr
- | AxLabelNoFlush
- | AxLabelFlush
- | AxLabelFlushValue Double
- | AxLabelFlushOffset Double
- | AxLabelFont Text
- | AxLabelFontSize Double
- | AxLabelFontStyle Text
- | AxLabelFontWeight FontWeight
- | AxLabelLimit Double
- | AxLabelLineHeight Double
- | AxLabelOffset Double
- | AxLabelOpacity Opacity
- | AxLabelOverlap OverlapStrategy
- | AxLabelPadding Double
- | AxLabelSeparation Double
- | AxMaxExtent Double
- | AxMinExtent Double
- | AxOffset Double
- | AxOrient Side
- | AxPosition Double
- | AxStyle [StyleLabel]
- | AxTicks Bool
- | AxTickBand BandAlign
- | AxTickCap StrokeCap
- | AxTickColor Color
- | AxTickCount Int
- | AxTickCountTime ScaleNice
- | AxTickDash DashStyle
- | AxTickDashOffset DashOffset
- | AxTickExtra Bool
- | AxTickMinStep Double
- | AxTickOffset Double
- | AxTickOpacity Opacity
- | AxTickRound Bool
- | AxTickSize Double
- | AxTickWidth Double
- | AxTitle Text
- | AxNoTitle
- | AxTitleAlign HAlign
- | AxTitleAnchor APosition
- | AxTitleAngle Angle
- | AxTitleBaseline VAlign
- | AxTitleColor Color
- | AxTitleFont Text
- | AxTitleFontSize Double
- | AxTitleFontStyle Text
- | AxTitleFontWeight FontWeight
- | AxTitleLimit Double
- | AxTitleLineHeight Double
- | AxTitleOpacity Opacity
- | AxTitlePadding Double
- | AxTitleX Double
- | AxTitleY Double
- | AxTranslateOffset Double
- | AxValues DataValues
- | AxDates [[DateTime]]
- | AxZIndex ZIndex
- data ConditionalAxisProperty
- = CAxGridColor Color Color
- | CAxGridDash DashStyle DashStyle
- | CAxGridDashOffset DashOffset DashOffset
- | CAxGridOpacity Opacity Opacity
- | CAxGridWidth Double Double
- | CAxLabelAlign HAlign HAlign
- | CAxLabelBaseline VAlign VAlign
- | CAxLabelColor Color Color
- | CAxLabelFont Text Text
- | CAxLabelFontSize Double Double
- | CAxLabelFontStyle Text Text
- | CAxLabelFontWeight FontWeight FontWeight
- | CAxLabelOffset Double Double
- | CAxLabelOpacity Opacity Opacity
- | CAxLabelPadding Double Double
- | CAxTickColor Text Text
- | CAxTickDash DashStyle DashStyle
- | CAxTickDashOffset DashOffset DashOffset
- | CAxTickOpacity Opacity Opacity
- | CAxTickSize Double Double
- | CAxTickWidth Double Double
- data HAlign
- data VAlign
- data BandAlign
- data OverlapStrategy
- data Side
- angle :: [MarkChannel] -> BuildEncodingSpecs
- color :: [MarkChannel] -> BuildEncodingSpecs
- fill :: [MarkChannel] -> BuildEncodingSpecs
- fillOpacity :: [MarkChannel] -> BuildEncodingSpecs
- opacity :: [MarkChannel] -> BuildEncodingSpecs
- shape :: [MarkChannel] -> BuildEncodingSpecs
- size :: [MarkChannel] -> BuildEncodingSpecs
- stroke :: [MarkChannel] -> BuildEncodingSpecs
- strokeDash :: [MarkChannel] -> BuildEncodingSpecs
- strokeOpacity :: [MarkChannel] -> BuildEncodingSpecs
- strokeWidth :: [MarkChannel] -> BuildEncodingSpecs
- data MarkChannel
- = MName FieldName
- | MRepeat Arrangement
- | MRepeatDatum Arrangement
- | MmType Measurement
- | MScale [ScaleProperty]
- | MBin [BinProperty]
- | MBinned
- | MSort [SortProperty]
- | MTimeUnit TimeUnit
- | MTitle Text
- | MNoTitle
- | MAggregate Operation
- | MLegend [LegendProperty]
- | MSelectionCondition BooleanOp [MarkChannel] [MarkChannel]
- | MDataCondition [(BooleanOp, [MarkChannel])] [MarkChannel]
- | MPath Text
- | MDatum DataValue
- | MNumber Double
- | MString Text
- | MBoolean Bool
- | MNullValue
- | MSymbol Symbol
- data LegendType
- data LegendProperty
- = LAria Bool
- | LAriaDescription Text
- | LClipHeight Double
- | LColumnPadding Double
- | LColumns Int
- | LCornerRadius Double
- | LDirection Orientation
- | LFillColor Color
- | LFormat Text
- | LFormatAsNum
- | LFormatAsTemporal
- | LFormatAsCustom Text
- | LGradientLength Double
- | LGradientOpacity Opacity
- | LGradientStrokeColor Color
- | LGradientStrokeWidth Double
- | LGradientThickness Double
- | LGridAlign CompositionAlignment
- | LLabelAlign HAlign
- | LLabelBaseline VAlign
- | LLabelColor Color
- | LLabelExpr VegaExpr
- | LLabelFont Text
- | LLabelFontSize Double
- | LLabelFontStyle 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 Text
- | LNoTitle
- | LTitleAlign HAlign
- | LTitleAnchor APosition
- | LTitleBaseline VAlign
- | LTitleColor Color
- | LTitleFont Text
- | LTitleFontSize Double
- | LTitleFontStyle Text
- | LTitleFontWeight FontWeight
- | LTitleLimit Double
- | LTitleLineHeight Double
- | LTitleOpacity Opacity
- | LTitleOrient Side
- | LTitlePadding Double
- | LType LegendType
- | LValues LegendValues
- | LeX Double
- | LeY Double
- | LZIndex ZIndex
- data LegendOrientation
- data LegendValues
- text :: [TextChannel] -> BuildEncodingSpecs
- tooltip :: [TextChannel] -> BuildEncodingSpecs
- tooltips :: [[TextChannel]] -> BuildEncodingSpecs
- data TextChannel
- = TName FieldName
- | TRepeat Arrangement
- | TRepeatDatum Arrangement
- | TmType Measurement
- | TAggregate Operation
- | TBand Double
- | TBin [BinProperty]
- | TBinned
- | TDataCondition [(BooleanOp, [TextChannel])] [TextChannel]
- | TSelectionCondition BooleanOp [TextChannel] [TextChannel]
- | TDatum DataValue
- | TFormat Text
- | TFormatAsNum
- | TFormatAsTemporal
- | TFormatAsCustom Text
- | TLabelExpr VegaExpr
- | TString Text
- | TStrings [Text]
- | TTimeUnit TimeUnit
- | TTitle Text
- | TNoTitle
- data FontWeight
- hyperlink :: [HyperlinkChannel] -> BuildEncodingSpecs
- data HyperlinkChannel
- = HName FieldName
- | HRepeat Arrangement
- | HmType Measurement
- | HAggregate Operation
- | HyBand Double
- | HBin [BinProperty]
- | HBinned
- | HSelectionCondition BooleanOp [HyperlinkChannel] [HyperlinkChannel]
- | HDataCondition [(BooleanOp, [HyperlinkChannel])] [HyperlinkChannel]
- | HyFormat Text
- | HyFormatAsNum
- | HyFormatAsTemporal
- | HyFormatAsCustom Text
- | HyLabelExpr VegaExpr
- | HString Text
- | HTimeUnit TimeUnit
- | HyTitle Text
- | HyNoTitle
- url :: [HyperlinkChannel] -> BuildEncodingSpecs
- order :: [OrderChannel] -> BuildEncodingSpecs
- data OrderChannel
- = OName FieldName
- | ORepeat Arrangement
- | OAggregate Operation
- | OBand Double
- | OBin [BinProperty]
- | OSort [SortProperty]
- | OTimeUnit TimeUnit
- | OTitle Text
- | ONoTitle
- | OmType Measurement
- | ODataCondition [(BooleanOp, [OrderChannel])] [OrderChannel]
- | OSelectionCondition BooleanOp [OrderChannel] [OrderChannel]
- | ONumber Double
- row :: [FacetChannel] -> BuildEncodingSpecs
- column :: [FacetChannel] -> BuildEncodingSpecs
- detail :: [DetailChannel] -> BuildEncodingSpecs
- data DetailChannel
- ariaDescription :: [AriaDescriptionChannel] -> BuildEncodingSpecs
- data AriaDescriptionChannel
- = ADName FieldName
- | ADRepeat Arrangement
- | ADmType Measurement
- | ADAggregate Operation
- | ADBand Double
- | ADBin [BinProperty]
- | ADBinned
- | ADSelectionCondition BooleanOp [AriaDescriptionChannel] [AriaDescriptionChannel]
- | ADDataCondition [(BooleanOp, [AriaDescriptionChannel])] [AriaDescriptionChannel]
- | ADFormat Text
- | ADFormatAsNum
- | ADFormatAsTemporal
- | ADFormatAsCustom Text
- | ADLabelExpr VegaExpr
- | ADString Text
- | ADTimeUnit TimeUnit
- | ADTitle Text
- | ADNoTitle
- data ScaleProperty
- = SType Scale
- | SAlign Double
- | SBase Double
- | SBins [Double]
- | SClamp Bool
- | SConstant Double
- | SDomain DomainLimits
- | SDomainMid Double
- | SDomainOpt ScaleDomain
- | SExponent Double
- | SInterpolate CInterpolate
- | SNice ScaleNice
- | SPadding Double
- | SPaddingInner Double
- | SPaddingOuter Double
- | SRange ScaleRange
- | SReverse Bool
- | SRound Bool
- | SScheme Text [Double]
- | SZero Bool
- data Scale
- = ScLinear
- | ScLog
- | ScPow
- | ScSqrt
- | ScSymLog
- | ScTime
- | ScUtc
- | ScQuantile
- | ScQuantize
- | ScThreshold
- | ScBinOrdinal
- | ScOrdinal
- | ScPoint
- | ScBand
- categoricalDomainMap :: [(Text, Color)] -> [ScaleProperty]
- domainRangeMap :: (Double, Color) -> (Double, Color) -> [ScaleProperty]
- data ScaleDomain
- data DomainLimits
- data ScaleRange
- data ScaleNice
- data NTimeUnit
- data CInterpolate
- layer :: [VLSpec] -> PropertySpec
- vlConcat :: [VLSpec] -> PropertySpec
- columns :: Natural -> PropertySpec
- hConcat :: [VLSpec] -> PropertySpec
- vConcat :: [VLSpec] -> PropertySpec
- align :: CompositionAlignment -> PropertySpec
- alignRC :: CompositionAlignment -> CompositionAlignment -> PropertySpec
- spacing :: Double -> PropertySpec
- spacingRC :: Double -> Double -> PropertySpec
- center :: Bool -> PropertySpec
- centerRC :: Bool -> Bool -> PropertySpec
- bounds :: Bounds -> PropertySpec
- data Bounds
- data CompositionAlignment
- resolve :: [ResolveSpec] -> PropertySpec
- resolution :: Resolve -> BuildResolveSpecs
- data Resolve
- = RAxis [(Channel, Resolution)]
- | RLegend [(Channel, Resolution)]
- | RScale [(Channel, Resolution)]
- data Channel
- data Resolution
- repeat :: [RepeatFields] -> PropertySpec
- repeatFlow :: [FieldName] -> PropertySpec
- data RepeatFields
- = RowFields [FieldName]
- | ColumnFields [FieldName]
- | LayerFields [FieldName]
- facet :: [FacetMapping] -> PropertySpec
- facetFlow :: [FacetChannel] -> PropertySpec
- data FacetMapping
- = ColumnBy [FacetChannel]
- | RowBy [FacetChannel]
- data FacetChannel
- asSpec :: [PropertySpec] -> VLSpec
- specification :: VLSpec -> PropertySpec
- data Arrangement
- data HeaderProperty
- = HFormat Text
- | HFormatAsNum
- | HFormatAsTemporal
- | HFormatAsCustom Text
- | HLabel Bool
- | HLabelAlign HAlign
- | HLabelAnchor APosition
- | HLabelAngle Angle
- | HLabelBaseline VAlign
- | HLabelColor Color
- | HLabelExpr VegaExpr
- | HLabelFont Text
- | HLabelFontSize Double
- | HLabelFontStyle Text
- | HLabelFontWeight FontWeight
- | HLabelLimit Double
- | HLabelLineHeight Double
- | HLabelOrient Side
- | HLabelPadding Double
- | HOrient Side
- | HTitle Text
- | HNoTitle
- | HTitleAlign HAlign
- | HTitleAnchor APosition
- | HTitleAngle Angle
- | HTitleBaseline VAlign
- | HTitleColor Color
- | HTitleFont Text
- | HTitleFontSize Double
- | HTitleFontStyle Text
- | HTitleFontWeight FontWeight
- | HTitleLimit Double
- | HTitleLineHeight Double
- | HTitleOrient Side
- | HTitlePadding Double
- selection :: [SelectSpec] -> PropertySpec
- select :: SelectionLabel -> Selection -> [SelectionProperty] -> BuildSelectSpecs
- data Selection
- data SelectionProperty
- = Empty
- | BindScales
- | BindLegend BindLegendProperty
- | On Text
- | Clear Text
- | Translate Text
- | Zoom Text
- | Fields [FieldName]
- | Encodings [Channel]
- | SInit [(FieldName, DataValue)]
- | SInitInterval (Maybe (DataValue, DataValue)) (Maybe (DataValue, DataValue))
- | ResolveSelections SelectionResolution
- | SelectionMark [SelectionMarkProperty]
- | Bind [Binding]
- | Nearest Bool
- | Toggle Text
- data Binding
- = IRange Text [InputProperty]
- | ICheckbox Text [InputProperty]
- | IRadio Text [InputProperty]
- | ISelect Text [InputProperty]
- | IText Text [InputProperty]
- | INumber Text [InputProperty]
- | IDate Text [InputProperty]
- | ITime Text [InputProperty]
- | IMonth Text [InputProperty]
- | IWeek Text [InputProperty]
- | IDateTimeLocal Text [InputProperty]
- | ITel Text [InputProperty]
- | IColor Text [InputProperty]
- data BindLegendProperty
- data InputProperty
- data SelectionMarkProperty
- data SelectionResolution
- = Global
- | Union
- | Intersection
- data BooleanOp
- name :: Text -> PropertySpec
- description :: Text -> PropertySpec
- height :: Double -> PropertySpec
- heightOfContainer :: PropertySpec
- heightStep :: Double -> PropertySpec
- width :: Double -> PropertySpec
- widthOfContainer :: PropertySpec
- widthStep :: Double -> PropertySpec
- padding :: Padding -> PropertySpec
- autosize :: [Autosize] -> PropertySpec
- background :: Color -> PropertySpec
- usermetadata :: Object -> PropertySpec
- data Padding
- data Autosize
- title :: Text -> [TitleConfig] -> PropertySpec
- viewBackground :: [ViewBackground] -> PropertySpec
- 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
- configure :: [ConfigureSpec] -> PropertySpec
- configuration :: ConfigurationProperty -> BuildConfigureSpecs
- data ConfigurationProperty
- = ArcStyle [MarkProperty]
- | AreaStyle [MarkProperty]
- | AriaStyle Bool
- | AutosizeStyle [Autosize]
- | Axis [AxisConfig]
- | AxisBand AxisChoice [AxisConfig]
- | AxisBottom [AxisConfig]
- | AxisDiscrete AxisChoice [AxisConfig]
- | AxisLeft [AxisConfig]
- | AxisPoint AxisChoice [AxisConfig]
- | AxisQuantitative AxisChoice [AxisConfig]
- | AxisRight [AxisConfig]
- | AxisTemporal AxisChoice [AxisConfig]
- | AxisTop [AxisConfig]
- | AxisX [AxisConfig]
- | AxisY [AxisConfig]
- | AxisNamedStyles [(StyleLabel, [AxisProperty])]
- | BackgroundStyle Color
- | BarStyle [MarkProperty]
- | BoxplotStyle [MarkProperty]
- | CircleStyle [MarkProperty]
- | ConcatStyle [CompositionConfig]
- | CountTitleStyle Text
- | CustomFormatStyle Bool
- | ErrorBandStyle [MarkProperty]
- | ErrorBarStyle [MarkProperty]
- | FacetStyle [CompositionConfig]
- | FieldTitleStyle FieldTitleProperty
- | FontStyle Text
- | GeoshapeStyle [MarkProperty]
- | HeaderStyle [HeaderProperty]
- | HeaderColumnStyle [HeaderProperty]
- | HeaderFacetStyle [HeaderProperty]
- | HeaderRowStyle [HeaderProperty]
- | ImageStyle [MarkProperty]
- | LegendStyle [LegendConfig]
- | LineStyle [MarkProperty]
- | LineBreakStyle Text
- | MarkStyle [MarkProperty]
- | MarkNamedStyles [(StyleLabel, [MarkProperty])]
- | NumberFormatStyle Text
- | PaddingStyle Padding
- | PointStyle [MarkProperty]
- | ProjectionStyle [ProjectionProperty]
- | RangeStyle [RangeConfig]
- | RectStyle [MarkProperty]
- | RepeatStyle [CompositionConfig]
- | RuleStyle [MarkProperty]
- | ScaleStyle [ScaleConfig]
- | SelectionStyle [(Selection, [SelectionProperty])]
- | SquareStyle [MarkProperty]
- | TextStyle [MarkProperty]
- | TickStyle [MarkProperty]
- | TimeFormatStyle Text
- | TitleStyle [TitleConfig]
- | TrailStyle [MarkProperty]
- | ViewStyle [ViewConfig]
- | Autosize [Autosize]
- | Background Color
- | CountTitle Text
- | FieldTitle FieldTitleProperty
- | Legend [LegendConfig]
- | NumberFormat Text
- | Padding Padding
- | Projection [ProjectionProperty]
- | Range [RangeConfig]
- | Scale [ScaleConfig]
- | TimeFormat Text
- | View [ViewConfig]
- | NamedStyle StyleLabel [MarkProperty]
- | NamedStyles [(StyleLabel, [MarkProperty])]
- data AxisConfig
- = Aria Bool
- | AriaDescription Text
- | AStyle [StyleLabel]
- | BandPosition Double
- | Disable Bool
- | Domain Bool
- | DomainCap StrokeCap
- | DomainColor Color
- | DomainDash DashStyle
- | DomainDashOffset DashOffset
- | DomainOpacity Opacity
- | DomainWidth Double
- | Format Text
- | FormatAsNum
- | FormatAsTemporal
- | FormatAsCustom Text
- | Grid Bool
- | GridCap StrokeCap
- | 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 Text
- | LabelFontSize Double
- | LabelFontStyle Text
- | LabelFontWeight FontWeight
- | LabelLimit Double
- | LabelLineHeight Double
- | LabelOffset Double
- | LabelOpacity Opacity
- | LabelOverlap OverlapStrategy
- | LabelPadding Double
- | LabelSeparation Double
- | MaxExtent Double
- | MinExtent Double
- | NoTitle
- | Orient Side
- | Ticks Bool
- | TickBand BandAlign
- | TickCap StrokeCap
- | TickColor Color
- | TickCount Int
- | TickCountTime ScaleNice
- | 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 Text
- | TitleFontSize Double
- | TitleFontStyle Text
- | TitleFontWeight FontWeight
- | TitleLimit Double
- | TitleLineHeight Double
- | TitleOpacity Opacity
- | TitlePadding Double
- | TitleX Double
- | TitleY Double
- | TranslateOffset Double
- data AxisChoice
- data LegendConfig
- = LeAria Bool
- | LeAriaDescription Text
- | LeClipHeight Double
- | LeColumnPadding Double
- | LeColumns Int
- | LeCornerRadius Double
- | LeDirection Orientation
- | LeDisable Bool
- | 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 Text
- | LeLabelFontSize Double
- | LeLabelFontStyle 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
- | LeSymbolLimit Int
- | LeSymbolOffset Double
- | LeSymbolOpacity Opacity
- | LeSymbolSize Double
- | LeSymbolStrokeColor Color
- | LeSymbolStrokeWidth Double
- | LeSymbolType Symbol
- | LeTickCount Int
- | LeTickCountTime ScaleNice
- | LeNoTitle
- | LeTitleAlign HAlign
- | LeTitleAnchor APosition
- | LeTitleBaseline VAlign
- | LeTitleColor Color
- | LeTitleFont Text
- | LeTitleFontSize Double
- | LeTitleFontStyle Text
- | LeTitleFontWeight FontWeight
- | LeTitleLimit Double
- | LeTitleLineHeight Double
- | LeTitleOpacity Opacity
- | LeTitleOrient Side
- | LeTitlePadding Double
- | LeUnselectedOpacity Opacity
- | LeZIndex ZIndex
- 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]
- data BaseLegendLayout
- 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
- | SCXReverse Bool
- data RangeConfig
- data TitleConfig
- = TAlign HAlign
- | TAnchor APosition
- | TAngle Angle
- | TAria Bool
- | TBaseline VAlign
- | TColor Color
- | TdX Double
- | TdY Double
- | TFont Text
- | TFontSize Double
- | TFontStyle Text
- | TFontWeight FontWeight
- | TFrame TitleFrame
- | TLimit Double
- | TLineHeight Double
- | TOffset Double
- | TOrient Side
- | TStyle [StyleLabel]
- | TSubtitle Text
- | TSubtitleColor Color
- | TSubtitleFont Text
- | TSubtitleFontSize Double
- | TSubtitleFontStyle Text
- | TSubtitleFontWeight FontWeight
- | TSubtitleLineHeight Double
- | TSubtitlePadding Double
- | TZIndex ZIndex
- data TitleFrame
- data ViewConfig
- = ViewBackgroundStyle [ViewBackground]
- | ViewClip Bool
- | ViewContinuousWidth Double
- | ViewContinuousHeight Double
- | ViewCornerRadius Double
- | ViewCursor Cursor
- | ViewDiscreteWidth Double
- | ViewDiscreteHeight Double
- | ViewFill Color
- | ViewNoFill
- | ViewFillOpacity Opacity
- | ViewOpacity Opacity
- | ViewStep Double
- | ViewStroke Color
- | ViewNoStroke
- | ViewStrokeCap StrokeCap
- | ViewStrokeDash DashStyle
- | ViewStrokeDashOffset DashOffset
- | ViewStrokeJoin StrokeJoin
- | ViewStrokeMiterLimit Double
- | ViewStrokeOpacity Opacity
- | ViewStrokeWidth Double
- | ViewWidth Double
- | ViewHeight Double
- data APosition
- data FieldTitleProperty
- data CompositionConfig
- data DataValue
- data DataValues
- data DateTime
- data MonthName
- data DayName
- data TimeUnit
- data BaseTimeUnit
- = Year
- | Quarter
- | Month
- | Week
- | Date
- | Day
- | DayOfYear
- | Hours
- | Minutes
- | Seconds
- | Milliseconds
- | YearQuarter
- | YearQuarterMonth
- | YearMonth
- | YearMonthDate
- | YearMonthDateHours
- | YearMonthDateHoursMinutes
- | YearMonthDateHoursMinutesSeconds
- | YearWeek
- | YearWeekDay
- | YearWeekDayHours
- | YearWeekDayHoursMinutes
- | YearWeekDayHoursMinutesSeconds
- | YearDayOfYear
- | QuarterMonth
- | MonthDate
- | MonthDateHours
- | MonthDateHoursMinutes
- | MonthDateHoursMinutesSeconds
- | WeekDay
- | WeeksDayHours
- | WeeksDayHoursMinutes
- | WeeksDayHoursMinutesSeconds
- | DayHours
- | DayHoursMinutes
- | DayHoursMinutesSeconds
- | HoursMinutes
- | HoursMinutesSeconds
- | MinutesSeconds
- | SecondsMilliseconds
Creating a Vega-Lite Specification
toVegaLite :: [PropertySpec] -> VegaLite Source #
Convert a list of Vega-Lite specifications into a single JSON object that may be passed to Vega-Lite for graphics generation. Commonly these will include at least a data, mark, and encoding specification.
While simple properties like mark
may be provided directly, it is
usually clearer to label more complex ones such as encodings as
separate expressions. This becomes increasingly helpful for
visualizations that involve composition of layers, repeats and facets.
Specifications can be built up by chaining a series of functions (such
as dataColumn
or position
in the example below). Functional
composition using the .
operator allows this to be done compactly.
let dat =dataFromColumns
[] .dataColumn
"a" (Strings
[ "C", "C", "D", "D", "E", "E" ]) .dataColumn
"b" (Numbers
[ 2, 7, 1, 2, 6, 8 ]) enc =encoding
.position
X
[PName
"a",PmType
Nominal
] .position
Y
[PName
"b",PmType
Quantitative
,PAggregate
Mean
] intoVegaLite
[ dat [],mark
Bar
[], enc [] ]
The schema used is version 4 of Vega-Lite,
and please report an issue if
you find a problem with the output of hvega
. Use toVegaLiteSchema
if you
need to create a Vega-Lite specification which uses a different version of
the schema.
:: Text | The schema to use (e.g. There is no check that this schema represents Vega-Lite, and is just treated as a value added to the output JSON. |
-> [PropertySpec] | The visualization. |
-> VegaLite |
A version of toVegaLite
that allows you to change the Vega-Lite
schema version of the visualization.
toVegaLiteSchema
vlSchema3
props
Note that the schema is only used to fill in the "$schema"
field of the JSON structure. It does not change the JSON
encoding of the visualization.
The latest version 2 Vega-Lite schema (equivalent to
).vlSchema
2 Nothing Nothing Nothing
The latest version 3 Vega-Lite schema (equivalent to
).vlSchema
3 Nothing Nothing Nothing
The latest version 4 Vega-Lite schema (equivalent to
).vlSchema
4 Nothing Nothing Nothing
:: Natural | The major version |
-> Maybe Natural | The minor version |
-> Maybe Natural | The "micro" version |
-> Maybe Text | Anything beyond "major.minor.micro" (e.g. "-beta.0"). |
-> Text | The Vega-Lite Schema |
Create the Vega-Lite schema for an arbitrary version. See https://github.com/vega/schema for more information on naming and availability.
There is no validation of the input values.
Alpha and Beta releases can be specified by setting the last argument; for instance to get the "beta.0" version of version 4 you would use
vlSchema 4 (Just 0) (Just 0) (Just "-beta.0")
whereas
vlSchema 4 Nothing Nothing Nothing
refers to the latest release of version 4.
:: VegaLite | |
-> Value | Prior to version |
Obtain the Vega-Lite JSON (i.e. specification) for passing to a Vega-Lite visualizer.
let vlSpec = fromVL vl Data.ByteString.Lazy.Char8.putStrLn (Data.Aeson.Encode.Pretty.encodePretty vlSpec)
Note that there is no validation done to ensure that the output matches the Vega Lite schema. That is, it is possible to create an invalid visualization with this module (e.g. missing a data source or referring to an undefined field).
data VLProperty Source #
Top-level Vega-Lite properties. These are the ones that define the core of the visualization grammar. All properties are created by functions which can be arranged into seven broad groups:
- Data Properties
- These relate to the input data to be visualized. Generated by
dataFromColumns
,dataFromRows
,dataFromUrl
,dataFromSource
,dataFromJson
,dataSequence
,sphere
, andgraticule
. - Transform Properties
- These indicate that some transformation of input data should
be applied before encoding them visually. Generated by
transform
andprojection
they can include data transformations such asfilter
,binAs
andcalculateAs
and geo transformations of longitude, latitude coordinates used by marks such asGeoshape
,Point
, andLine
. - Mark Properties
- These relate to the symbols used to visualize data items. They
are generated by
mark
, and include types such asCircle
,Bar
, andLine
. - Encoding Properties
- These specify which data elements are mapped to which mark characteristics
(known as channels). Generated by
encoding
, they include encodings such asposition
,color
,size
,shape
,text
,hyperlink
, andorder
. - Composition Properties
- These allow visualization views to be combined to form more
complex visualizations. Generated by
layer
,repeat
,repeatFlow
,facet
,facetFlow
,vlConcat
,columns
,hConcat
,vConcat
,asSpec
, andresolve
. - Interaction Properties
- These allow interactions such as clicking, dragging and others
generated via a GUI or data stream to influence the visualization. Generated by
selection
. - Supplementary and Configuration Properties
- These provide a means to add metadata and
styling to one or more visualizations. Generated by
name
,title
,description
,background
,height
,heightStep
,width
,widthStep
,padding
,autosize
,viewBackground
, andconfigure
.
Prior to 0.4.0.0
this was an opaque data type, as the constructors
were not exported. It is suggested that you do not import the
constructors to VLProperty
unless you need to transform the
Vega-Lite code in some manner (e.g. because hvega
is missing needed
functionality or is buggy).
Note that there is only a very-limited attempt to enforce the Vega-Lite Schema (e.g. to ensure the required components are provided).
VLAlign | See Since: 0.4.0.0 |
VLAutosize | See |
VLBackground | See |
VLBounds | See Since: 0.4.0.0 |
VLCenter | Since: 0.4.0.0 |
VLColumns | See Since: 0.4.0.0 |
VLConcat | See Since: 0.4.0.0 |
VLConfig | See |
VLData | See |
VLDatasets | See |
VLDescription | See |
VLEncoding | See |
VLFacet | |
VLHConcat | See |
VLHeight | See |
VLLayer | See |
VLMark | See |
VLName | See |
VLPadding | See |
VLProjection | See |
VLRepeat | See |
VLResolve | See |
VLSelection | See |
VLSpacing | See Since: 0.4.0.0 |
VLSpecification | See |
VLTitle | See |
VLTransform | See |
VLUserMetadata | see Since: 0.4.0.0 |
VLVConcat | See |
VLViewBackground | See Since: 0.4.0.0 |
VLWidth |
A Vega Lite visualization, created by
toVegaLite
. The contents can be extracted with fromVL
.
type PropertySpec = (VLProperty, VLSpec) Source #
A convenience type-annotation label. It is the same as Data
.
Since: 0.4.0.0
type LabelledSpec = (Text, VLSpec) Source #
Represents a named Vega-Lite specification, usually generated by a
function in this module. You shouldn't need to create LabelledSpec
tuples directly, but they can be useful for type annotations.
data EncodingSpec Source #
Represent an encoding (input to encoding
).
It is expected that routines like position
and color
are used to create values with this
type, but they can also be constructed and deconstructed manually
with toEncodingSpec
and fromEncodingSpec
.
Since: 0.5.0.0
:: Text | The key to use for these settings (e.g. |
-> VLSpec | The value of the key. This is expected to be an object, but there is no check on the value. See the Vega-Lite schema for information on the supported values. |
-> EncodingSpec |
This function is provided in case there is any need to inject
JSON into the Vega-Lite document that hvega
does not support
(due to changes in the Vega-Lite specification or missing
functionality in this module). If you find yourself needing
to use this then please
report an issue.
See also fromEncodingSpec
.
Since: 0.5.0.0
:: EncodingSpec | |
-> (Text, VLSpec) | The key for the settings (e.g. "detail") and the value of the key. |
Extract the contents of an encoding specification. This may be
needed when the Vega-Lite specification adds or modifies settings
for a particular encoding, and hvega
has not been updated
to reflect this change. If you find yourself needing
to use this then please
report an issue.
See also toEncodingSpec
.
Since: 0.5.0.0
data TransformSpec Source #
Represent a transformation (input to transform
).
It is expected that routines like calculateAs
and filter
are used to create values with this
type, but they can also be constructed and deconstructed manually
with toTransformSpec
and fromTransformSpec
.
Since: 0.5.0.0
:: VLSpec | The tranform value, which is expected to be an object, but there is no check on this. See the Vega-Lite schema for information on the supported values. |
-> TransformSpec |
This function is provided in case there is any need to inject
JSON into the Vega-Lite document that hvega
does not support
(due to changes in the Vega-Lite specification or missing
functionality in this module). If you find yourself needing
to use this then please
report an issue.
See also fromTransformSpec
.
Since: 0.5.0.0
:: TransformSpec | |
-> VLSpec | The transformation data. |
Extract the contents of a transformation specification. This may be
needed when the Vega-Lite specification adds or modifies settings
for a particular encoding, and hvega
has not been updated
to reflect this change. If you find yourself needing
to use this then please
report an issue.
See also toTransformSpec
.
Since: 0.5.0.0
data ResolveSpec Source #
Represent a set of resolution properties
(input to resolve
).
It is expected that resolution
is used
to create values with this type, but they can also be constructed and
deconstructed manually with toResolveSpec
and fromResolveSpec
.
Since: 0.5.0.0
:: Text | The key to use for these settings (e.g. |
-> VLSpec | The value of the key. This is expected to be an object, but there is no check on the value. See the Vega-Lite schema for information on the supported values. |
-> ResolveSpec |
This function is provided in case there is any need to inject
JSON into the Vega-Lite document that hvega
does not support
(due to changes in the Vega-Lite specification or missing
functionality in this module). If you find yourself needing
to use this then please
report an issue.
See also fromResolveSpec
.
Since: 0.5.0.0
:: ResolveSpec | |
-> (Text, VLSpec) | The key for the settings (e.g. "legend") and the value of the key. |
Extract the contents of an resolve specification. This may be
needed when the Vega-Lite specification adds or modifies settings
for a particular resolve, and hvega
has not been updated
to reflect this change. If you find yourself needing
to use this then please
report an issue.
See also toResolveSpec
.
Since: 0.5.0.0
data SelectSpec Source #
Represent a set of resolution properties
(input to selection
).
It is expected that select
is used
to create values with this type, but they can also be constructed and
deconstructed manually with toSelectSpec
and fromSelectSpec
.
Since: 0.5.0.0
:: SelectionLabel | The name given to the selection. |
-> VLSpec | The value of the key. This is expected to be an object, but there is no check on the value. See the Vega-Lite schema for information on the supported values. |
-> SelectSpec |
This function is provided in case there is any need to inject
JSON into the Vega-Lite document that hvega
does not support
(due to changes in the Vega-Lite specification or missing
functionality in this module). If you find yourself needing
to use this then please
report an issue.
See also fromSelectSpec
.
Since: 0.5.0.0
:: SelectSpec | |
-> (SelectionLabel, VLSpec) | The name for the selection and its settings. |
Extract the contents of a select specification. This may be
needed when the Vega-Lite specification adds or modifies settings
for a particular select, and hvega
has not been updated
to reflect this change. If you find yourself needing
to use this then please
report an issue.
See also toSelectSpec
.
Since: 0.5.0.0
data ConfigureSpec Source #
Represent a set of configuration properties
(input to configuration
).
It is expected that configuration
is used
to create values with this type, but they can also be constructed and
deconstructed manually with toConfigureSpec
and fromConfigureSpec
.
Since: 0.5.0.0
:: Text | The key to use for these settings (e.g. |
-> VLSpec | The value of the key. See the Vega-Lite schema for information on the supported values. |
-> ConfigureSpec |
This function is provided in case there is any need to inject
JSON into the Vega-Lite document that hvega
does not support
(due to changes in the Vega-Lite specification or missing
functionality in this module). If you find yourself needing
to use this then please
report an issue.
See also fromConfigureSpec
.
Since: 0.5.0.0
:: ConfigureSpec | |
-> (Text, VLSpec) | The key for the settings (e.g. "numberFormat") and the value of the key. |
Extract the contents of a configuration specification. This may be
needed when the Vega-Lite specification adds or modifies settings
for a particular configure, and hvega
has not been updated
to reflect this change. If you find yourself needing
to use this then please
report an issue.
See also toConfigureSpec
.
Since: 0.5.0.0
type BuildEncodingSpecs = [EncodingSpec] -> [EncodingSpec] Source #
Represent the functions that can be chained together and sent to
encoding
.
Since: 0.5.0.0
type BuildTransformSpecs = [TransformSpec] -> [TransformSpec] Source #
Represent the functions that can be chained together and sent to
transform
.
Since: 0.5.0.0
type BuildResolveSpecs = [ResolveSpec] -> [ResolveSpec] Source #
Represent the functions that can be chained together and sent to
resolve
.
Since: 0.5.0.0
type BuildSelectSpecs = [SelectSpec] -> [SelectSpec] Source #
Represent the functions that can be chained together and sent to
selection
.
Since: 0.5.0.0
type BuildConfigureSpecs = [ConfigureSpec] -> [ConfigureSpec] Source #
Represent the functions that can be chained together and sent to
configure
.
Since: 0.5.0.0
Convenience type-annotation label to indicate an angle, which is measured in degrees from the horizontal (so anti-clockwise).
The value should be in the range 0 to 360, inclusive, but no attempt is made to enforce this.
Since: 0.4.0.0
Convenience type-annotation label to indicate a color value. There is no attempt to validate that the user-supplied input is a valid color.
Any supported HTML color specification can be used, such as:
"#eee" "#734FD8" "crimson" "rgb(255,204,210)" "hsl(180, 50%, 50%)"
A blank string is converted to the JSON null value (new in 0.5.0.0
).
Since: 0.4.0.0
type DashStyle = [Double] Source #
The dash style for a line. This is defined as a series of on and then
off lengths, in pixels. So [10, 4, 5, 2]
means a long line, followed
by a space, then a line half as long as the first segment, and then
a short space. This pattern is then repeated.
This is a convenience type annotation and there is no validation of the input.
Since: 0.5.0.0
type DashOffset = Double Source #
The offset at which to start drawing the line dash (given by a
DashStyle
argument), in pixels.
This is a convenience type annotation and there is no validation of the input.
Since: 0.5.0.0
type FieldName = Text Source #
The field name. This can include "dotted" notation, such as
"o.latitude"
.
There is no attempt to validate this value (e.g. check it is not empty, contains only valid characters, or remove excess whitespace).
Since: 0.5.0.0
type GradientCoord = Double Source #
Convenience type-annotation to label a normalized coordinate for color gradients. The value should be in the range 0 to 1, inclusive. There is no attempt to validate that the number lies within this range.
Since: 0.5.0.0
type GradientStops = [(GradientCoord, Color)] Source #
Convenience type-annotation label to indicate the color interpolation points - i.e. the colors to use at points along the normalized range 0 to 1 (inclusive).
The list does not have to be sorted. There is no check that the color is valid (i.e. not empty or a valid color specification).
Since: 0.5.0.0
type Opacity = Double Source #
Convenience type-annotation label to indicate an opacity value, which lies in the range 0 to 1 inclusive. There is no attempt to validate that the user-supplied value falls in this range.
A value of 0 indicates fully transparent (see through), and 1 is fully opaque (does not show anything it is on top of).
Since: 0.4.0.0
type SelectionLabel = Text Source #
Convenience type-annotation label to indicate the name, or label, of a selection. It is expected to be a non-empty string, but there is no attempt to validate this.
Since: 0.5.0.0
type StyleLabel = Text Source #
Convenience type-annotation to indicate a name, or label, that represents
a set of mark or axis styles. The styles are generated with
AxisNamedStyles
and
MarkNamedStyles
,
and used with constructs such as
AStyle
,
AxStyle
,
MStyle
, and
TStyle
.
Since: 0.6.0.0
Convenience type-annotation label to indicate a Vega Expression. There is no attempt to validate the expression.
Examples include:
"datum.IMDB_Rating != null" "datum.height / 1000" "if(datum.index % 2 == 1, datum.label, '')" "sampleLogNormal(2.3, 0.3)"
Since: 0.5.0.0
type ZIndex = Natural Source #
At what "depth" (z index) is the item to be drawn (a relative depth
for items in the visualization). The standard values are 0
for
back and 1
for front, but other values can be used if you want
to ensure a certain layering of items.
The following example is taken from a discussion with Jo Wood:
let dcols =dataFromColumns
[] .dataColumn
"x" (Numbers
[ 20, 10 ]) .dataColumn
"y" (Numbers
[ 10, 20 ]) .dataColumn
"cat" (Strings
[ "a", "b" ]) axis lbl z = [PName
lbl,PmType
Quantitative
,PAxis
[AxZIndex
z ] ] enc =encoding
.position
X
(axis "x" 2) .position
Y
(axis "y" 1) .color
[MName
"cat",MmType
Nominal
,MLegend
[] ] cfg =configure
.configuration
(Axis
[GridWidth
8 ]) .configuration
(AxisX
[GridColor
"red" ]) .configuration
(AxisY
[GridColor
"blue" ]) intoVegaLite
[ cfg [] , dcols [] , enc [] ,mark
Circle
[MSize
5000,MOpacity
1 ] ]
View the visualization in the Vega Editor
Since: 0.4.0.0
toHtml :: VegaLite -> Text Source #
Converts VegaLite to html Text. Uses Vega-Embed with the
default options. See toHtmlWith
for more control.
Since: 0.2.1.0
toHtmlFile :: FilePath -> VegaLite -> IO () Source #
Converts VegaLite to an html file. Uses Vega-Embed with the
default options. See toHtmlFileWith
for more control.
Since: 0.2.1.0
:: Maybe Value | The options to pass to the Vega-Embed |
-> VegaLite | The Vega-Lite specification to display. |
-> Text |
Converts VegaLite to html Text. Uses Vega-Embed and is for when
some control is needed over the output: toHtml
is a simpler
form which just uses the default Vega-Embed options.
The render you use to view the output file must support Javascript, since it is needed to create the visualization from the Vega-Lite specification. The Vega and Vega-Lite Javascript versions are pegged to 5 and 4, but no limit is applied to the Vega-Embed library.
Since: 0.4.0.0
:: Maybe Value | The options to pass to the Vega-Embed |
-> FilePath | The output file name (it will be over-written if it already exists). |
-> VegaLite | The Vega-Lite specification to display. |
-> IO () |
Converts VegaLite to an html file. Uses Vega-Embed and is for when
some control is needed over the output: toHtmlFile
is a simpler
form which just uses the default Vega-Embed options.
Since: 0.4.0.0
Creating the Data Specification
Functions and types for declaring the input data to the visualization. See the Vega-Lite documentation.
dataFromUrl :: Text -> [Format] -> Data Source #
Declare data source from a url. The url can be a local path on a web server or an external http(s) url. Used to create a data ( property, specification ) pair. An optional list of field formatting instructions can be provided as the second parameter or an empty list to use the default formatting. See the Vega-Lite documentation for details.
dataFromUrl
"data/weather.csv" [Parse
[ ( "date",FoDate
"%Y-%m-%d %H:%M" ) ] ]
:: [Format] | An optional list of formatting instructions for the columns. Simple numbers and strings do not normally need formatting, but it is good practice to explicitly declare date-time formats as handling of these values can vary between different viewers (e.g. browsers). See the Vega-Lite documentation for more details. |
-> [DataColumn] | The columns to add. This is expected to be created with one or more
calls to |
-> Data |
Declare a data source from a list of column values. Each column has a
specific type (e.g. Number
or String
), but different columns can have
different types.
Note that the columns are truncated to match the length of the shortest column.
dataFromColumns
[Parse
[ ( "Year",FoDate
"%Y" ) ] ] .dataColumn
"Animal" (Strings
[ "Fish", "Dog", "Cat" ]) .dataColumn
"Age" (Numbers
[ 28, 12, 6 ]) .dataColumn
"Year" (Strings
[ "2010", "2014", "2015" ])
:: [Format] | An optional list of formatting instructions for the rows. Simple numbers and strings do not normally need formatting, but it is good practice to explicitly declare date-time formats as handling of these values can vary between different viewers (e.g. browsers). See the Vega-Lite documentation for more details. |
-> [DataRow] | The rows to add. This is expected to be created with one or more
calls to |
-> Data |
Declare a data source from a provided list of row values. Each row contains a list of tuples where the first value is a string representing the column name, and the second the column value for that row. Each column can have a value of a different type but you must ensure that when subsequent rows are added, they match the types of previous values with shared column names.
Note though that generally if you are creating data inline (as opposed to reading from a file), adding data by column is more efficient and less error-prone.
dataFromRows [Parse
[ ( "Year",FoDate
"%Y" ) ] ] .dataRow
[ ( "Animal",Str
"Fish" ), ( "Age",Number
28 ), ( "Year",Str
"2010" ) ] .dataRow
[ ( "Animal",Str
"Dog" ), ( "Age",Number
12 ), ( "Year",Str
"2014" ) ] .dataRow
[ ( "Animal",Str
"Cat" ), ( "Age",Number
6 ), ( "Year",Str
"2015" ) ]
dataFromJson :: VLSpec -> [Format] -> Data Source #
Declare a data source from a provided json specification. The most likely use-case
for specifying json inline is when creating geojson objects,
when geometry
, geometryCollection
, and geoFeatureCollection
functions
may be used. For more general cases of json creation, consider encode
.
let geojson =geometry
(GeoPolygon
[ [ ( -3, 59 ), ( 4, 59 ), ( 4, 52 ), ( -3, 59 ) ] ]) [] intoVegaLite
[width
200 ,height
200 ,dataFromJson
geojson [] ,projection
[PrType
Orthographic
] ,mark
Geoshape
[] ]
dataFromSource :: Text -> [Format] -> Data Source #
Declare data from a named source. The source may be from named datasets
within
a specification or a named data source created via the
Vega View API.
An optional list of field formatting instructions can be provided as the second
parameter or an empty list to use the default formatting. See the
Vega-Lite documentation
for details.
toVegaLite
[datasets
[ ( "myData", dvals [] ), ( "myJson",dataFromJson
json [] ) ] ,dataFromSource
"myData" [] ,mark
Bar
[] , ... ]
:: Text | The name to give the data source |
-> Data | The data source to be named. |
-> Data | If the input |
Name to give a data source. Useful when a specification needs to reference a data source, such as one generated via an API call.
dvals =dataName
"myName" (dataFromUrl
"myData.json" [])
Since: 0.4.0.0
datasets :: [(Text, Data)] -> Data Source #
Create a dataset comprising a collection of named Data
items. Each data item
can be created with normal data generating functions such as dataFromRows
or
dataFromJson
. These can be later referred to using dataFromSource
.
let toJS = Data.Aeson.toJSON obj = Data.Aeson.object dvals =dataFromRows
[] .dataRow
[ ( "cat",Str
"a" ), ( "val",Number
10 ) ] .dataRow
[ ( "cat",Str
"b" ), ( "val",Number
18 ) ] json = toJS [ obj [ ( "cat", toJS "a" ), ( "val", toJS 120 ) ] , obj [ ( "cat", toJS "b" ), ( "val", toJS 180 ) ] ] enc = ... intoVegaLite
[datasets
[ ( "myData", dvals [] ), ( "myJson",dataFromJson
json [] ) ] ,dataFromSource
"myData" [] ,mark
Bar
[] , enc [] ]
dataColumn :: FieldName -> DataValues -> [DataColumn] -> [DataColumn] Source #
Create a column of data. A column has a name and a list of values. The final parameter is the list of any other columns to which this is added.
This is expected to be used with dataFromColumns
.
dataColumn
"Animal" (Strings
[ "Cat", "Dog", "Mouse"]) []
dataRow :: [(FieldName, DataValue)] -> [DataRow] -> [DataRow] Source #
Create a row of data. A row comprises a list of (columnName, value) pairs. The final parameter is the list of any other rows to which this is added.
This is expected to be used with dataFromRows
.
dataRow
[("Animal",Str
"Fish"), ("Age",Number
28), ("Year",Str
"2010")] []
This is for composed specifications, and it tells the visualization to ignore the data from the parent.
Since: 0.4.0.0
type Data = (VLProperty, VLSpec) Source #
Convenience type-annotation label for use with data generation functions.
myRegion : [DataColumn
] ->Data
myRegion =dataFromColumns
[] .dataColumn
"easting" (Numbers
[ -3, 4, 4, -3, -3 ]) .dataColumn
"northing" (Numbers
[ 52, 52, 45, 45, 52 ])
It is the same as PropertySpec
(which was added in 0.4.0.0
),
but kept separate to help better-document code.
type DataColumn = [LabelledSpec] Source #
Represents a single column of data. Used when generating inline data with
dataColumn
and dataFromColumns
.
type DataRow = VLSpec Source #
Represents a single row of data. Used when generating inline data with
dataRow
and dataFromRows
.
Geographic Data
geometry :: Geometry -> [(Text, DataValue)] -> VLSpec Source #
Specifies a geometric object to be used in a geoShape specification. The first parameter is the geometric type, the second an optional list of properties to be associated with the object.
geometry
(GeoPolygon
[ [ ( -3, 59 ), ( 4, 59 ), ( 4, 52 ), ( -3, 59 ) ] ]) []
geoFeatureCollection :: [VLSpec] -> VLSpec Source #
Specifies a list of geo features to be used in a geoShape specification.
Each feature object in this collection can be created with the geometry
function.
geoFeatureCollection
[geometry
(GeoPolygon
[ [ ( -3, 59 ), ( -3, 52 ), ( 4, 52 ), ( -3, 59 ) ] ]) [ ( "myRegionName",Str
"Northern region" ) ] ,geometry
(GeoPolygon
[ [ ( -3, 52 ), ( 4, 52 ), ( 4, 45 ), ( -3, 52 ) ] ]) [ ( "myRegionName",Str
"Southern region" ) ] ]
geometryCollection :: [VLSpec] -> VLSpec Source #
Specifies a list of geometry objects to be used in a geoShape specification.
Each geometry object in this collection can be created with the geometry
function.
geometryCollection
[geometry
(GeoPolygon
[ [ ( -3, 59 ), ( 4, 59 ), ( 4, 52 ), ( -3, 59 ) ] ]) [] ,geometry
(GeoPoint
-3.5 55.5) [] ]
Specifies the type and content of geometry specifications for programatically
creating GeoShapes. These can be mapped to the
GeoJson geometry object types
where the pluralised type names refer to their Multi
prefixed equivalent in the
GeoJSON specification.
GeoPoint Double Double | The GeoJson geometry |
GeoPoints [(Double, Double)] | The GeoJson geometry |
GeoLine [(Double, Double)] | The GeoJson geometry |
GeoLines [[(Double, Double)]] | The GeoJson geometry |
GeoPolygon [[(Double, Double)]] | The GeoJson geometry |
GeoPolygons [[[(Double, Double)]]] | The GeoJson geometry |
Data Generators
Functions that create new data sources.
:: Double | start of the sequence (inclusive) |
-> Double | end of the sequence (exclusive) |
-> Double | step size |
-> Data |
Generate a sequence of numbers as a data source. The resulting
sequence will have the name "data"
. To give it an alternative name use
dataSequenceAs
.
myData = dataSequence
0 6.28 0.1
Since: 0.4.0.0
:: Double | start of the sequence (inclusive) |
-> Double | end of the sequence (exclusive) |
-> Double | step size |
-> FieldName | The name of the data source |
-> Data |
Generate a sequence of numbers as a named data source. This extends
dataSequence
by allowing you to name the data source.
myTheta = dataSequenceAs
0 6.28 0.1 "theta"
Since: 0.4.0.0
Generate a data source that is a sphere for bounding global geographic data. The sphere will be subject to whatever projection is specified for the view.
toVegaLite
[sphere
,projection
[PrType
Orthographic
] ,mark
Geoshape
[MFill
"aliceblue" ] ]
Since: 0.4.0.0
:: [GraticuleProperty] | An empty list uses the default parameters |
-> Data |
Generate a grid of lines of longitude (meridians) and latitude (parallels).
let proj =projection
[PrType
Orthographic
] sphereSpec =asSpec
[sphere
,mark
Geoshape
[MFill
"aliceblue" ] ] gratSpec =asSpec
[graticule
[GrStep
(5, 5) ] ,mark
Geoshape
[MFilled
False,MStrokeWidth
0.3 ] ] intoVegaLite
[ proj,layer
[ sphereSpec, gratSpec ] ]
Since: 0.4.0.0
data GraticuleProperty Source #
Determine the properties of graticules. See the Vega-Lite documentation for details.
Since: 0.4.0.0
GrExtent (Double, Double) (Double, Double) | Define the extent of both the major and minor graticules. The range is given as longitude, latitude pairs of the minimum and then maximum extent. The units are degrees. |
GrExtentMajor (Double, Double) (Double, Double) | As |
GrExtentMinor (Double, Double) (Double, Double) | As |
GrStep (Double, Double) | The step angles for the graticule lines, given as a longitude, latitude pair defining the EW and NS intervals respectively. The units are degrees. By default major graticule lines extend to both poles but the minor lines stop at ±80 degrees latitude. |
GrStepMajor (Double, Double) | As The default is |
GrStepMinor (Double, Double) | As The default is |
GrPrecision Double | The precision of the graticule. The units are degrees. A smaller value reduces visual artifacts (steps) but takes longer to render. The default is |
Formatting Input Data
Specifies the type of format a data source uses. If the format is indicated by
the file name extension (".tsv"
, ".csv"
, ".json"
) there is no need to indicate the
format explicitly. However this can be useful if the filename extension does not
indicate type (e.g. ".txt"
) or you wish to customise the parsing of a file. For
example, when specifying the JSON
format, its parameter indicates the name of
property field containing the attribute data to extract. For details see the
Vega-Lite documentation.
JSON Text | Property to be extracted from some JSON when it has some surrounding structure.
e.g., specifying the property |
CSV | Comma-separated (CSV) data file format. |
TSV | Tab-separated (TSV) data file format |
DSV Char | The fields are separated by the given character (which must be a single 16-bit code unit). Since: 0.4.0.0 |
TopojsonFeature Text | A topoJSON feature format containing an object with the given name. For example:
|
TopojsonMesh Text | A topoJSON mesh format containing an object with the given name. Unlike
|
Parse [(FieldName, DataType)] | Parsing rules when processing some data text, specified as
a list of tuples in the form
|
Indicates the type of data to be parsed when reading input data. For FoDate
and FoUtc
, the formatting specification can be specified using
D3's formatting specifiers
or left as an empty string if default date formatting is to be applied. Care should
be taken when assuming default parsing of dates because different browsers can
parse dates differently. Being explicit about the date format is usually safer.
FoNumber | Indicate numeric data type to be parsed when reading input data. |
FoBoolean | Indicate Boolean data type to be parsed when reading input data. |
FoDate Text | Date format for parsing input data using D3's formatting specifiers or left as an empty string for default formatting. |
FoUtc Text | Similar to |
Creating the Transform Specification
Functions and types for declaring the transformation rules that are applied to data fields or geospatial coordinates before they are encoded visually.
In version 0.5.0.0
the TransformSpec
type was introduced to
make it clear what functions can be used with transform
.
:: [TransformSpec] | The transformations to apply. The order does matter. Prior to |
-> PropertySpec |
Create a single transform from a list of transformation
specifications. Note that the order of transformations can be
important, especially if labels created with calculateAs
,
timeUnitAs
, and binAs
are used in other transformations. Using
the functional composition pipeline idiom (as example below) allows
you to provide the transformations in the order intended in a clear
manner.
transform
.filter
(FExpr
"datum.year == 2010") .calculateAs
"datum.sex == 2 ? 'Female' : 'Male'" "gender"
The supported transformations are:
aggregate
, binAs
, calculateAs
, density
, filter
, flatten
,
flattenAs
, fold
, foldAs
, impute
, joinAggregate
, loess
,
lookup
, lookupAs
, lookupSelection
, pivot
, quantile
,
regression
, sample
, stack
, timeUnitAs
, and window
.
Map Projections
projection :: [ProjectionProperty] -> PropertySpec Source #
Sets the cartographic projection used for geospatial coordinates. A projection
defines the mapping from (longitude,latitude)
to an (x,y)
plane used for rendering.
This is useful when using the Geoshape
mark. For further details see the
Vega-Lite documentation.
projection
[PrType
Orthographic
,PrRotate
(-40) 0 0 ]
data ProjectionProperty Source #
Properties for customising a geospatial projection that converts longitude,latitude
pairs into planar (x,y)
coordinate pairs for rendering and query. For details see the
Vega-Lite documentation.
This type has been changed in the 0.4.0.0
release so that all constructors
start with Pr
rather than P
(and so provide some differentiation to the
PositionChannel
constructors).
PrType Projection | The type of the map projection. |
PrClipAngle (Maybe Double) | The clipping circle angle in degrees. A value of |
PrClipExtent ClipRect | Projection’s viewport clip extent to the specified bounds in pixels. |
PrCenter Double Double | Projection’s center as longitude and latitude in degrees. |
PrScale Double | The projection's zoom scale, which if set, overrides automatic scaling of a geo feature to fit within the viewing area. Since: 0.4.0.0 |
PrTranslate Double Double | A projection’s panning translation, which if set, overrides automatic positioning of a geo feature to fit within the viewing area Note that the prefix is Since: 0.4.0.0 |
PrRotate Double Double Double | A projection’s three-axis rotation angle. The order is |
PrPrecision Double | Threshold for the projection’s adaptive resampling in pixels, and corresponds to the Douglas–Peucker distance. If precision is not specified, the projection’s current resampling precision of 0.707 is used. Version 3.3.0 of the Vega-Lite spec claims this should be output as a string, but it is written out as a number since the spec is in error. |
PrReflectX Bool | Reflect the x-coordinates after performing an identity projection. This
creates a left-right mirror image of the geoshape marks when subject to an
identity projection with Since: 0.4.0.0 |
PrReflectY Bool | Reflect the y-coordinates after performing an identity projection. This
creates a left-right mirror image of the geoshape marks when subject to an
identity projection with Since: 0.4.0.0 |
PrCoefficient Double | The |
PrDistance Double | The |
PrFraction Double | The |
PrLobes Int | Number of lobes in lobed map projections such as the |
PrParallel Double | Parallel for map projections such as the |
PrRadius Double | Radius value for map projections such as the |
PrRatio Double | Ratio value for map projections such as the |
PrSpacing Double | Spacing value for map projections such as the |
PrTilt Double |
|
data Projection Source #
Types of geographic map projection. These are based on a subset of those provided by the d3-geo library. For details of available projections see the Vega-Lite documentation.
Albers | An Albers equal-area conic map projection. |
AlbersUsa | An Albers USA map projection that combines continental USA with
Alaska and Hawaii. Unlike other projection types, this remains
unaffected by |
AzimuthalEqualArea | An azimuthal equal area map projection. |
AzimuthalEquidistant | An azimuthal equidistant map projection. |
ConicConformal | A conformal conic map projection. |
ConicEqualArea | An equal area conic map projection. |
ConicEquidistant | An equidistant conic map projection. |
Custom Text | Specify the name of the custom D3 prohection to use. See the Vega API for more information. An example: |
EqualEarth | An Equal Earth map projection that provides a reasonable shape approximation while retaining relative areas. Since: 0.5.0.0 |
Equirectangular | An equirectangular map projection that maps longitude to x and latitude to y.
While showing less area distortion towards the poles than the default |
Gnomonic | A gnomonic map projection. |
Identity | The identiy projection. This can be combined with Since: 0.4.0.0 |
Mercator | A Mercator map projection. This is the default projection of longitude, latitude values if no projection is set explicitly. It preserves shape (local angle) and lines of equal angular bearing remain parallel straight lines. The area is significantly enlarged towards the poles. |
NaturalEarth1 | The Natural Earth projection is neither conformal nor equal-area, but is designed to be "appealing to the eye" for small-scale maps of the whole world. Since: 0.5.0.0 |
Orthographic | An orthographic map projection. |
Stereographic | A stereographic map projection. |
TransverseMercator | A transverse Mercator map projection. |
Specifies a clipping rectangle for defining the clip extent of a map projection.
Aggregation
See the Vega-Lite aggregate documentation.
:: [VLSpec] | The named aggregation operations to apply. |
-> [FieldName] | The "group by" fields. |
-> BuildTransformSpecs |
Defines a set of named aggregation transformations to be used when encoding channels. This is useful when, for example, you wish to apply the same transformation to a number of channels but do not want to define it each time. For further details see the Vega-Lite documentation.
transform
.aggregate
[opAs
Min
"people" "lowerBound" ,opAs
Max
"people" "upperBound" ] [ "age" ]
See also joinAggregate
.
joinAggregate :: [VLSpec] -> [WindowProperty] -> BuildTransformSpecs Source #
Aggregation transformations to be used when encoding channels. Unlike
aggregate
, this transformation joins the results to the input data.
Can be helpful for creating derived values that combine raw data with some aggregate
measure, such as percentages of group totals. The first parameter is a list
of the named aggregation operations to apply. The second is a list of possible
window aggregate field properties, such as a field to group by when aggregating.
The third parameter is a list of transformations to which this is added.
transform
.joinAggregate
[opAs
Mean
"rating" "avYearRating" ] [WGroupBy
[ "year" ] ] .filter
(FExpr
"(datum.rating - datum.avYearRating) > 3"))
For details, see the Vega-Lite join aggregate documentation.
See also aggregate
.
Since: 0.4.0.0
:: TimeUnit | The width of each bin. Prior to |
-> FieldName | The field to bin. |
-> FieldName | The name of the binned data created by this routine. |
-> BuildTransformSpecs |
Creates a new data field based on the given temporal binning. Unlike the direct encoding binning, this transformation is named and so can be referred to in multiple encodings. Note though that usually it is easer to apply the temporal binning directly as part of the encoding as this will automatically format the temporal axis. See the Vega-Lite documentation for further details.
The following example takes a temporal dataset and encodes daily totals from it grouping by month:
trans =transform
.timeUnitAs
(TU
Month
) "date" "monthly" enc =encoding
.position
X
[PName
"date",PmType
Temporal
,PTimeUnit
(TU
Day
) ] .position
Y
[PAggregate
Sum
,PmType
Quantitative
] .detail
[DName
"monthly",DmType
Temporal
]
Type of aggregation operation. See the Vega-Lite documentation for more details.
The Average
constructor was removed in version 0.4.0.0
; use Mean
instead.
ArgMax (Maybe FieldName) | An input data object containing the maximum field value to be used in an aggregation operation. If supplied as part of an encoding aggregation, the parameter
should be Encoding example, to find the production budget for the maximum US grossing film in each genre:
An example of its use as part of an
The optional field name was added in the |
ArgMin (Maybe FieldName) | An input data object containing the minimum field value to be used
in an aggregation operation. See The optional field name was added in the |
CI0 | Lower 95% confidence interval to be used in an aggregation operation. |
CI1 | Upper 95% confidence interval to be used in an aggregation operation. |
Count | Total count of data objects to be used in an aggregation operation. |
Distinct | Count of distinct data objects to be used in an aggregation operation. |
Max | Maximum field value to be used in an aggregation operation. |
Mean | Mean field value to be used in an aggregation operation. |
Median | Median field value to be used in an aggregation operation. |
Min | Minimum field value to be used in an aggregation operation. |
Missing | Count of |
Product | Product of field values to be used in an aggregate operation. This was added in Vega-Lite 4.6.0. Since: 0.7.0.0 |
Q1 | Lower quartile boundary of field values to be used in an aggregation operation. |
Q3 | Upper quartile boundary of field values to be used in an aggregation operation. |
Stderr | Standard error of field values to be used in an aggregate operation. |
Stdev | Sample standard deviation of field values to be used in an aggregate operation. |
StdevP | Population standard deviation of field values to be used in an aggregate operation. |
Sum | Sum of field values to be used in an aggregate operation. |
Valid | Count of values that are not |
Variance | Sample variance of field values to be used in an aggregate operation. |
VarianceP | Population variance of field values to be used in an aggregate operation. |
Binning
See the Vega-Lite binning documentation.
:: [BinProperty] | An empty list means that the default binning is used (that is, the
|
-> FieldName | The field to bin. |
-> FieldName | The label for the binned data. |
-> BuildTransformSpecs |
Create a named binning transformation that may be referenced in other Transformations or encodings. See the Vega-Lite documentation for more details. Note that usually, direct binning within an encoding is preferred over this form of bin transformation.
transform
.binAs
[MaxBins
3 ] "IMDB_Rating" "ratingGroup"
data BinProperty Source #
Type of binning property to customise. See the Vega-Lite documentation for more details.
This is used with: binAs
, DBin
, FBin
, HBin
, MBin
, OBin
,
PBin
, and TBin
.
AlreadyBinned Bool | Should the input data be treated as already binned? Since: 0.4.0.0 |
BinAnchor Double | A value in the binned domain at which to anchor the bins, shifting the bin boundaries if necessary to ensure that a boundary aligns with the anchor value. Since: 0.4.0.0 |
Base Double | The number base to use for automatic bin determination. Default is |
Divide [Double] | Scale factors indicating allowable subdivisions. Default is Prior to |
Extent Double Double | The range (minimum, maximum) of the desired bin values. |
MaxBins Int | The maxium number of bins. Default is |
MinStep Double | A minimum allowable step size. |
Nice Bool | If Default is |
SelectionExtent SelectionLabel | Set the range based on an interactive selection. The label must reference an interval selection, but this constraint is not enforced at compile or run time. sel = Since: 0.5.0.0 |
Step Double | The step size to use between bins. If specified, |
Steps [Double] | Pick the step size from this list. |
Stacking
See the Vega-Lite stack documentation.
:: FieldName | The field to be stacked. |
-> [FieldName] | The fields to group by. |
-> FieldName | The output field name (start). |
-> FieldName | The output field name (end). |
-> [StackProperty] | Offset and sort properties. |
-> BuildTransformSpecs |
Apply a stack transform for positioning multiple values. This is an alternative to specifying stacking directly when encoding position.
transform
.aggregate
[opAs
Count
"" "count_*" ] [ "Origin", "Cylinders" ] .stack
"count_*" [] "stack_count_Origin1" "stack_count_Origin2" [StOffset
StNormalize
,StSort
[WAscending
"Origin" ] ] .window
[ ( [WAggregateOp
Min
,WField
"stack_count_Origin1" ], "x" ) , ( [WAggregateOp
Max
,WField
"stack_count_Origin2" ], "x2" ) ] [WFrame
Nothing Nothing,WGroupBy
[ "Origin" ] ] .stack
"count_*" [ "Origin" ] "y" "y2" [StOffset
StNormalize
,StSort
[WAscending
"Cylinders" ] ]
Since: 0.4.0.0
data StackProperty Source #
How are stacks applied within a transform?
Prior to version 0.4.0.0
the StackProperty
type was
what is now StackOffset
.
StOffset StackOffset | Stack offset. Since: 0.4.0.0 |
StSort [SortField] | Ordering within a stack. Since: 0.4.0.0 |
data StackOffset Source #
Describes the type of stacking to apply to a bar chart.
In 0.4.0.0
this was renamed from StackProperty
to StackOffset
,
but the constructor names have not changed.
StZero | Offset a stacked layout using a baseline at the foot of the stack. |
StNormalize | Rescale a stacked layout to use a common height while preserving the relative size of stacked quantities. |
StCenter | Offset a stacked layout using a central stack baseline. |
NoStack | Do not stack marks, but create a layered plot. |
Data Calculation
See the Vega-Lite calculate documentation.
:: VegaExpr | The calculation to perform. |
-> FieldName | The field to assign the new values. |
-> BuildTransformSpecs |
Creates a new data field based on calculations from existing fields and values.
See the Vega-Lite documentation for further details.
transform
.calculateAs
"datum.sex == 2 ? 'F' : 'M'" "gender"
Filtering
See the Vega-Lite filter documentation.
filter :: Filter -> BuildTransformSpecs Source #
Adds the given filter operation a list of transformations that may be applied to a channel or field.
transform
.filter
(FEqual
"Animal" (Str
"Cat"))
Filter operations can combine selections and data predicates with BooleanOp
expressions (and as of 0.4.0.0
, FilterOp
and FilterOpTrans
can be used to lift the Filter
type into boolean expressions):
transform
.filter
(FCompose
(And
(Expr
"datum.Weight_in_lbs > 3000") (Selection
"brush")))
The Vega expression documentation
describes the supported format (e.g. the requirement to precede column names
with "datum."
).
Type of filtering operation. See the Vega-Lite documentation for details.
These can also be included into a BooleanOp
expression using FilterOp
and FilterOpTrans
(as of version 0.4.0.0
).
FEqual FieldName DataValue | Filter a data stream so that only data in a given field equal to the given value are used. |
FLessThan FieldName DataValue | Filter a data stream so that only data in a given field less than the given value are used. Since: 0.4.0.0 |
FLessThanEq FieldName DataValue | Filter a data stream so that only data in a given field less than, or equal to, the given value are used. Since: 0.4.0.0 |
FGreaterThan FieldName DataValue | Filter a data stream so that only data in a given field greater than the given value are used. Since: 0.4.0.0 |
FGreaterThanEq FieldName DataValue | Filter a data stream so that only data in a given field greater than, or equal to, the given value are used. Since: 0.4.0.0 |
FExpr VegaExpr | Filter a data stream so that only data that satisfy the given predicate expression are used. |
FCompose BooleanOp | Build up a filtering predicate through logical composition such
as The following fgragment will apply a filter to identify only those items selected interactively and that represent ages over 65: trans = |
FSelection SelectionLabel | Filter a data stream so that only data in a given field that are within the given interactive selection are used. sel = |
FOneOf FieldName DataValues | Filter a data stream so that only data in a given field contained in the given list of values are used. |
FRange FieldName FilterRange | Filter a data stream so that only data in a given field that are within the given range are used. For example:
See |
FValid FieldName | Filter a data stream so that only valid data (i.e. not null or NaN) in a given field are used. Since: 0.4.0.0 |
data FilterRange Source #
A pair of filter range data values, used with FRange
.
NumberRange Double Double | Select between these two values (both limits are inclusive). |
NumberRangeLL Double | A lower limit (inclusive). Since: 0.7.0.0 |
NumberRangeUL Double | An upper limit (inclusive). Since: 0.7.0.0 |
DateRange [DateTime] [DateTime] | Select between these two dates (both limits are inclusive). If a limit is the empty list then the filter is treated as
a limit only on the other value, so
|
Flattening
See the Vega-Lite flatten documentation.
flatten :: [FieldName] -> BuildTransformSpecs Source #
Map array-valued fields to a set of individual data objects, one per array entry.
See also flattenAs
.
Since: 0.4.0.0
:: [FieldName] | |
-> [FieldName] | The names of the output fields. |
-> BuildTransformSpecs |
Similar to flatten
but allows the new output fields to be named.
Since: 0.4.0.0
Folding and Pivoting
Data tidying operations that reshape the rows and columns of a dataset. See the Vega-Lite fold and pivot documentation.
:: [FieldName] | The data fields to fold. |
-> BuildTransformSpecs |
Perform a gather operation to tidy a table. Collapse multiple data fields
into two new data fields: key
containing the original data field names and
value
containing the corresponding data values.
It is the inverse of pivot
. See also foldAs
.
dvals =dataFromColumns
[] .dataColumn
"city" (Strings
[ "Bristol", "Sheffield", "Glasgow" ]) .dataColumn
"temp2017" (Numbers
[ 12, 11, 7 ]) .dataColumn
"temp2018" (Numbers
[ 14, 13, 10 ]) trans =transform
.fold
[ "temp2017", "temp2018" ] enc =encoding
.position
X
[PName
"key",PmType
Nominal
] .position
Y
[PName
"city",PmType
Nominal
] .size
[MName
"value",MmType
Quantitative
]
Since: 0.4.0.0
:: [FieldName] | The data fields to fold. |
-> FieldName | The name for the |
-> FieldName | The name for the |
-> BuildTransformSpecs |
A fold
where the key
and value
fields can be renamed.
Since: 0.4.0.0
:: FieldName | The key field. |
-> FieldName | The value field. |
-> [PivotProperty] | |
-> BuildTransformSpecs |
Perform a pivot operation on a table. Spreads a key-value pair of fields across multiple fields according to the data in the key field.
It is the inverse of fold
.
dvals =dataFromColumns
[] .dataColumn
"city" (Strings
[ "Bristol", "Bristol", "Sheffield", "Sheffield", "Glasgow", "Glasgow" ]) .dataColumn
"temperature" (Numbers
[ 12, 14, 11, 13, 7, 10 ]) .dataColumn
"year" (Numbers
[ 2017, 2018, 2017, 2018, 2017, 2018 ]) trans =transform
.pivot
"year" "temperature" [PiGroupBy
[ "city" ] ] enc =encoding
.position
X
[PName
"2017",PmType
Quantitative
] .position
Y
[PName
"city",PmType
Nominal
]
Since: 0.5.0.0
data PivotProperty Source #
Configure the pivot
operation.
Since: 0.5.0.0
PiGroupBy [FieldName] | The data fields to group by when pivoting. If unspecified then a single group containing all the data objects will be used. |
PiLimit Natural | The maximum number of fields to generate when pivoting. If 0 or unspecified all fields are pivoted. The pivot names are sorted into ascending order before the limit is applied. |
PiOp Operation | The aggregation operation to apply to grouped fields. |
Relational Joining (lookup)
Create lookups between data tables in order to join values from multiple sources. See the Vega-Lite lookup documentation.
:: FieldName | The field in the primary data structure acting as the key. |
-> Data | The secondary data source (e.g. the return from the data-generating
functions such as |
-> FieldName | The name of the field in the secondary data source to match against the primary key. |
-> LookupFields | The list of fields to store when the keys match. This was changed from |
-> BuildTransformSpecs |
Perform a lookup of named fields between two data sources. This allows you to find values in one data source based on the values in another (like a relational join).
Use lookupSelection
for linking data with interactive selections.
See the Vega-Lite documentation for further details.
The following would return the values in the age
and height
fields from
lookup_people.csv
for all rows where the value in the name
column in that
file matches the value of person
in the primary data source.
peopleData =dataFromUrl
"data/lookup_people.csv" [] lfields =LuFields
["age", "height"] trans =transform
.lookup
"person" peopleData "name" lfields
Note that the interface has changed in version 0.5.0.0
: the
output field names argument now uses the new LookupFields
type. This provides greater flexibility in naming and
default behaviour. The conversion from version 0.4 is
simple: change
lookup key1 dataSource key2 fields
to
lookup key1 dataSource key2 (LuFields fields)
:: FieldName | The field to lookup in the primary data source. |
-> SelectionLabel | The name of the selection (as set with |
-> FieldName | The name of the field in the selection to link with the primary data field. |
-> BuildTransformSpecs |
Attach the results of an interactive selection to a primary data source.
This is similar to lookup
except that the data in a selection are used
in place of the secondary data source.
See the Vega Lite lookup selection documentation.
sel =selection
.select
"mySel"Single
[On
"mouseover",Encodings
[ChX
] ] trans =transform
.lookupSelection
"country" "mySel" "country"
Since: 0.5.0.0
data LookupFields Source #
Configure the field selection in lookup
.
Since: 0.5.0.0
LuFields [FieldName] | The name of the fields to return from the secondary data source. |
LuFieldAs [(FieldName, FieldName)] | Select fields from the secondary data source (first argument) and allow them to be referred to with a new name (second argument). |
LuAs FieldName | Create a single name for all the fields in the secondary data source. The individual fields use dot notation to combine the given name with the field name. dvals = |
LuFieldsWithDefault [FieldName] Text | The name of the fields to return from the secondary data source, along with the default value to use if the lookup fails. |
LuFieldsAsWithDefault [(FieldName, FieldName)] Text | Allow fields to be renamed and provide a default for when the lookup fails. |
LuAsWithDefault FieldName Text | Create a single name for all the fields in the secondary data source, but the second parameter gives the default value for when the lookup fails. |
:: FieldName | The field in the primary data structure acting as the key. |
-> Data | The secondary data source (e.g. the return from the data-generating
functions such as |
-> FieldName | The name of the field in the secondary data source to match against the primary key. |
-> FieldName | The field name for the new data. |
-> BuildTransformSpecs |
Deprecated: Please change 'lookupAs ... alias' to 'lookup ... (LuAs alias)'
This routine is deprecated (as of version 0.5.0.0
) in favor
of lookup
, as
lookupAs "key1" dataSource "key2" "matchName"
can be written as
lookup "key1" dataSource "key2" (LuAs "matchName")
Data Imputation
Impute missing data. See the Vega-Lite impute documentation.
:: FieldName | The data field to process. |
-> FieldName | The key field to uniquely identify data objects within a group. |
-> [ImputeProperty] | Define how the imputation works. |
-> BuildTransformSpecs |
Impute missing data values.
The following example creates a value for b
, set to the
mean of existing b
values with c=1
, for the "missing" coordinate
of (a=30
, c=1
):
let dvals =dataFromColumns
[] .dataColumn
"a" (Numbers
[0, 0, 10, 10, 20, 20, 30]) .dataColumn
"b" (Numbers
[28, 91, 43, 55, 81, 53, 19]) .dataColumn
"c" (Numbers
[0, 1, 0, 1, 0, 1, 0]) trans =transform
.impute
"b" "a" [ImMethod
ImMean
,ImGroupBy
["c"]] enc =encoding
.position
X
[PName
"a",PmType
Quantitative
] .position
Y
[PName
"b",PmType
Quantitative
] .color
[MName
"c",MmType
Nominal
] intoVegaLite
[dvals [], trans [], enc [],mark
Line
[]]
Since: 0.4.0.0
data ImputeProperty Source #
ImFrame (Maybe Int) (Maybe Int) | 1d window over which data imputation values are generated. The two
parameters should either be |
ImKeyVals DataValues | Key values to be considered for imputation. |
ImKeyValSequence Double Double Double | Key values to be considered for imputation as a sequence of numbers between a start (first parameter), to less than an end (second parameter) in steps of the third parameter. |
ImMethod ImMethod | How is the imputed value constructed. When using |
ImGroupBy [FieldName] | Allow imputing of missing values on a per-group basis. For use with the impute transform only and not a channel encoding. |
ImNewValue DataValue | The replacement value (when using |
Imputation method to use when replacing values.
Since: 0.4.0.0
Data sampling
See the Vega-Lite sample documentation.
sample :: Int -> BuildTransformSpecs Source #
Randomly sample rows from a data source up to a given maximum.
For example, the following randomly samples 50 values from a sine curve:
dvals =dataSequenceAs
0 13 0.001 "x" trans =transform
.calculateAs
"sin(datum.x)" "y" .sample
50
Since: 0.4.0.0
Density Estimation
See the Vega-Lite density documentation.
:: FieldName | The field used for the KDE. |
-> [DensityProperty] | Configure the calculation. |
-> BuildTransformSpecs |
Apply Kernel Density Estimation to a data stream to generate a new stream of samples of the estimated density. This is useful for representing probability distributions and generating continuous distributions from discrete samples.
The following example creates a faceted display of the smoothed length and width distributions from the iris dataset.
dvals =dataFromUrl
"https://vega.github.io/vega-lite/data/iris.json" [] colNames = [ "petalWidth", "petalLength", "sepalWidth", "sepalLength" ] trans =transform
.foldAs
colNames "measurement" "value" .density
"value" [DnGroupBy
[ "measurement" ] ] enc =encoding
.position
X
[PName
"value",PmType
Quantitative
] .position
Y
[PName
"density",PmType
Quantitative
] .row
[FName
"measurement",FmType
Nominal
] layer =asSpec
[ trans [], enc [],mark
Area
[MOpacity
0.7 ] ]
Since: 0.5.0.0
data DensityProperty Source #
Configure the kernel density estimation process. Used by density
.
Since: 0.5.0.0
DnAs FieldName FieldName | Name the outputs of a density transform. The first argument is the name of the field containing the samples and the second the name for the field containing the density estimates. The defaults are |
DnBandwidth Double | The bandwidth (standard deviation) of the Gaussian kernel to be used in the KDE. If not given, or set to 0, then Scott's method is used. |
DnCounts Bool | If The default is probabilities. |
DnCumulative Bool | Should the density estimates be cumulative? The default is |
DnExtent Double Double | The domain (minimum to maximum) from which to sample a distribution for the density estimation. The default is to use the full extent of the input values. |
DnGroupBy [FieldName] | The data fields to group by. The default is to use a single group containing all the data objects. |
DnMaxSteps Natural | The maximum number of samples to take from the extent domain. The default is 200. |
DnMinSteps Natural | The minimum number of samples to take from the extent domain. The default is 25. |
DnSteps Natural | This overrides the It can be used with |
Loess Trend Calculation
See the Vega-Lite loess documentation.
:: FieldName | The field representing the dependent variable (often displayed on the y axis). |
-> FieldName | The field representing the independent variable (often the x axis). |
-> [LoessProperty] | Customize the trend fitting. |
-> BuildTransformSpecs |
Generate a loess (locally-estimated scatterplot smoothing) trendline through a pair of data fields.
See also regression
.
The following example overlays the trendline generated by loess
(the "xsm", "ysm" points) on the raw points (assuming the data
source has fields called "xraw" and "yraw" for the independent
and dependent fields, respectively).
transLS =transform
.loess
"yraw" "xraw" [LsAs
"xsm" "ysm" ] encRaw =encoding
.position
X
[PName
"xraw",PmType
Quantitative
] .position
Y
[PName
"yraw",PmType
Quantitative
] encLS =encoding
.position
X
[PName
"xsm",PmType
Quantitative
] .position
Y
[PName
"ysm",PmType
Quantitative
] layers =layer
[asSpec
[ encRaw [],mark
Point
[MOpacity
0.5 ] ] ,asSpec
[ transLS [], encLS [],mark
Line
[MColor
"firebrick" ] ] ]
Since: 0.5.0.0
data LoessProperty Source #
Configure the trend fitting used by the loess
encoding.
Since: 0.5.0.0
LsAs FieldName FieldName | Name the outputs of a loess transform. The first argument is the name of the field containing the smoothed independent variable and the second the name for the field containing the smoothed dependent variable. If not specified the original field names will be used. |
LsBandwidth Double | The amount of smoothing. The value should be in the range 0 to 1, inclusive. The default is 0.3. |
LsGroupBy [FieldName] | The data fields to group by. The default is to use a single group containing all the data objects. |
Regression Calculation
See the Vega-Lite regression documentation.
:: FieldName | The field representing the dependent variable (often displayed on the y axis). |
-> FieldName | The field representing the independent variable (often the x axis). |
-> [RegressionProperty] | Customize the regression. |
-> BuildTransformSpecs |
Generate a 2d regression model for smoothing and predicting data.
See also loess
.
The following example overlays the points generated by regression
(the "xrg", "yrg" points) on the raw points (assuming the data
source has fields called "xraw" and "yraw" for the independent
and dependent fields, respectively).
transLS =transform
.regression
"yraw" "xraw" [RgAs
"xrg" "yrg" ] encRaw =encoding
.position
X
[PName
"xraw",PmType
Quantitative
] .position
Y
[PName
"yraw",PmType
Quantitative
] encLS =encoding
.position
X
[PName
"xrg",PmType
Quantitative
] .position
Y
[PName
"yrg",PmType
Quantitative
] layers =layer
[asSpec
[ encRaw [],mark
Point
[MOpacity
0.5 ] ] ,asSpec
[ transLS [], encLS [],mark
Line
[MColor
"firebrick" ] ] ]
Since: 0.5.0.0
data RegressionProperty Source #
Configure the regression process (used by regression
).
Since: 0.5.0.0
RgAs FieldName FieldName | Name the outputs of the regression analysis. The first argument is the name of the field containing the independent variable, the second the dependent variable. If not specified the original field names will be used. |
RgExtent Double Double | The domain (minimum to maximum) over which to estimate the dependent variable in the regression. The default is to use the full extent of the input values. |
RgGroupBy [FieldName] | The data fields to group by. The default is to use a single group containing all the data objects. |
RgMethod RegressionMethod | The type of regression model to use. |
RgOrder Natural | The order of the polynomial model. |
RgParams Bool | Should the transform return the regression model parameters, one object per group, rather than the trend line points. If set, the returned objects include a The default is |
data RegressionMethod Source #
The functional form of the regression analysis. Used by RgMethod
.
Since: 0.5.0.0
Qualtile Calculation
See the Vega-Lite quantile documentation.
:: FieldName | The field to analyse. |
-> [QuantileProperty] | Configure the quantile analysis |
-> BuildTransformSpecs |
Calculate quantile values from an input data stream. This can be useful for examining distributional properties of a data stream, and for creating Q-Q plots.
As an example:
let dvals =dataFromUrl
"data/normal-2d.json" [] trans =transform
.quantile
"u" [QtStep
0.01,QtAs
"p" "v" ] .calculateAs
"quantileUniform(datum.p)" "unif" .calculateAs
"quantileNormal(datum.p)" "norm" enc x y =encoding
.position
X
[PName
x,PmType
Quantitative
] .position
Y
[PName
y,PmType
Quantitative
] leftSpec =asSpec
[mark
Point
[], enc "unif" "v" [] ] rightSpec =asSpec
[mark
Point
[], enc "norm" "v" [] ] intoVegaLite
[ dvals, trans [],hConcat
[ leftSpec, rightSpec ] ]
Since: 0.5.0.0
data QuantileProperty Source #
Configure the quantile analysis performed by quantile
.
Since: 0.5.0.0
QtAs FieldName FieldName | Name the fields used to store the calculated probability and associated quantile values. The defaults are |
QtGroupBy [FieldName] | The data fields to group by. The default is to use a single group containing all the data objects. |
QtProbs [Double] | The probabilites (measured in the range 0-1) for which to compute quantile values. The default is to use a step size of 0.01, or the
|
QtStep Double | The interval between probabilities when performing a quantile transformation. All value from half the given step size to 1 will be sampled,
and is only used if |
Window Transformations
See the Vega-Lite window transform field and window transform documentation.
:: [([Window], FieldName)] | The window-transform definition and associated output name. |
-> [WindowProperty] | The window transform. |
-> BuildTransformSpecs |
Window transformations.
Since: 0.4.0.0
WAggregateOp Operation | An aggregrate operation to be used in a window transformation. |
WOp WOperation | Window-specific operation to be used in a window transformation. |
WParam Int | Numeric parameter for window-only operations that can be parameterised
( |
WField FieldName | Field for which to compute a window operation. Not needed for operations
that do not apply to fields such as |
data WOperation Source #
Window-specific operation for transformations (for use with WOp
).
Since: 0.4.0.0
RowNumber | Assign consecutive row number to values in a data object to be applied in a window transform. |
Rank | Rank function to be applied in a window transform. |
DenseRank | Dense rank function to be applied in a window transform. |
PercentRank | Percentile of values in a sliding window to be applied in a window transform. |
CumeDist | Cumulative distribution function to be applied in a window transform. |
Ntile | Value preceding the current object in a sliding window to be applied in a window transform. |
Lag | Value preceding the current object in a sliding window to be applied in a window transform. |
Lead | Value following the current object in a sliding window to be applied in a window transform. |
FirstValue | First value in a sliding window to be applied in a window transform. |
LastValue | Last value in a sliding window to be applied in a window transform. |
NthValue | Nth value in a sliding window to be applied in a window transform. |
data WindowProperty Source #
Properties for a window transform.
Since: 0.4.0.0
WFrame (Maybe Int) (Maybe Int) | Moving window for use by a window transform. When a number is
given, via |
WIgnorePeers Bool | Should the sliding window in a window transform ignore peer values (those considered identical by the sort criteria). |
WGroupBy [FieldName] | The fields for partitioning data objects in a window transform into separate windows. If not specified, all points will be in a single group. |
WSort [SortField] | Comparator for sorting data objects within a window transform. |
Creating the Mark Specification
Types and functions for declaring the type of visual marks used in the visualization.
mark :: Mark -> [MarkProperty] -> PropertySpec Source #
Create a mark specification. All marks must have a type (first parameter) and can optionally be customised with a list of mark properties such as interpolation style for lines. To keep the default style for the mark, just provide an empty list for the second parameter.
mark
Circle
[]mark
Line
[MInterpolate
StepAfter
]
let dvals =dataFromUrl
"city.json" [TopojsonFeature
"boroughs"] [] markOpts =mark
Geoshape
[MFill
"lightgrey",MStroke
"white"] intoVegaLite
[dvals, markOpts]
Type of visual mark used to represent data in the visualization.
The properties of the mark can be changed with the MarkProperty
constructors - such as MHeight
and MWidth
- although not all
properties apply to all marks.
Arc | An arc mark. Since: 0.9.0.0 |
Area | An area mark for representing a series of data elements, such as in a stacked area chart or streamgraph. |
Bar | Bar mark for histograms, bar charts etc. |
Boxplot | Boxplot composite mark for showing summaries of statistical distributions. Tick marks can be added using
The range of the box plot is controlled with Since: 0.4.0.0 |
Circle | Circle mark for representing points. |
ErrorBar | Errorbar composite mark for showing summaries of variation along a signal. By default
no ticks are drawn. To add ticks with default properties use
Since: 0.4.0.0 |
ErrorBand | Errorband composite mark for showing summaries of variation along a signal. By default
no border is drawn. To add a border with default properties use
Since: 0.4.0.0 |
Geoshape | Geoshape determined by geographically referenced coordinates. |
Image | Vega Lite image mark,
where the image to display is given via the
Since: 0.5.0.0 |
Line | Line mark for symbolising a sequence of values. |
Point | Point mark for symbolising a data point with a symbol. |
Rect | |
Rule | Rule line connecting two vertices. |
Square | Square mark for symbolising points. |
Text | Text mark to be displayed at some point location. |
Tick | Short line - tick - mark for symbolising point locations. |
Trail | Trail mark (line with variable width along its length). Since: 0.4.0.0 |
Mark properties
See the Vega-Lite general mark, area mark, bar mark, boxplot, circle mark, error band, error bar, hyperlink mark, line mark, point mark, square mark, text mark and tick mark property documentation.
data MarkProperty Source #
Properties for customising the appearance of a mark. For details see the Vega-Lite documentation.
Not all properties are valid for each mark type.
Some properties which take a list - such as MBox
- will
create a true
value if the list is empty, and false
if the
"No"
variant of the constructor is used (e.g. MNoBox
).
In version 0.5.0.0
the MRemoveInvalid
constructor was added, which
replaces the RemoveInvalid
constructor of ConfigurationProperty
, and the
MShortTimeLabels
constuctor was removed.
MAlign HAlign | Horizontal alignment of a text mark. |
MAngle Angle | Rotation angle of a text, point, or square marks. |
MAria Bool | Should ARIA attributes be included (SVG output only). If False, the "aria-hidden" attribute will be set on the output SVG element, removing the mark item from the ARIA accessibility tree. Since: 0.9.0.0 |
MAriaDescription Text | A text description of the mark item for ARIA accessibility (SVG output only). If specified, this property determines the "aria-label" attribute. Since: 0.9.0.0 |
MAriaRole Text | Sets the type of user interface element of the mark item for ARIA accessibility (SVG output only). If specified, this property determines the "role" attribute. Warning: this property is experimental and may be changed in the future. Since: 0.9.0.0 |
MAriaRoleDescription Text | A human-readable, author-localized description for the role of the mark item for ARIA accessibility (SVG output only). If specified, this property determines the "aria-roledescription" attribute. Warning: this property is experimental and may be changed in the future. Since: 0.9.0.0 |
MAspect Bool | Should the aspect ratio of an Since: 0.5.0.0 |
MBandSize Double | Band size of a bar mark. |
MBaseline VAlign | Vertical alignment of a text mark. |
MBinSpacing Double | Offset between bars for a binned field using a bar mark. The ideal value for this is either |
MBlend BlendMode | How should the item be blended with its background? Added in Vega-Lite 4.6.0. Since: 0.7.0.0 |
MBorders [MarkProperty] | Border properties for an Since: 0.4.0.0 |
MNoBorders | Do not draw a border for an Since: 0.6.0.0 |
MBox [MarkProperty] | Box-symbol properties for a Since: 0.4.0.0 |
MNoBox | Do not draw outliers with the Since: 0.6.0.0 |
MClip Bool | Should a mark be clipped to the enclosing group's dimensions. |
MColor Color | Default color of a mark. Note that |
MColorGradient ColorGradient GradientStops [GradientProperty] | The color gradient to apply to a mark. The first argument determines its type, the second is the list of color interpolation points, and the third allows for customization.
Since: 0.5.0.0 |
MCornerRadius Double | Corner radius of all corners of a rectangular mark, in pixels. The default is 0. This value is over-ridden by any of
Since: 0.5.0.0 |
MCornerRadiusEnd Double | The radius used for bars, in pixels. For vertical bars it defines the top-left and top-right radius, and for horizontal bars it is the top-right and bottom-right. For an example, see the Vega-Lite documentation. Since: 0.6.0.0 |
MCornerRadiusTL Double | Top-left corner radius of a rectangular mark, in pixels. The default is 0. Since: 0.5.0.0 |
MCornerRadiusTR Double | Top-right corner radius of a rectangular mark, in pixels. The default is 0. Since: 0.5.0.0 |
MCornerRadiusBL Double | Bottom-left corner radius of a rectangular mark, in pixels. The default is 0. Since: 0.5.0.0 |
MCornerRadiusBR Double | Bottom-right corner radius of a rectangular mark, in pixels. The default is 0. Since: 0.5.0.0 |
MCursor Cursor | Cursor to be associated with a hyperlink mark. |
MDir TextDirection | Direction of the text. This property determines which side of the
label is truncated by the The default is Since: 0.5.0.0 |
MContinuousBandSize Double | Continuous band size of a bar mark. |
MDiscreteBandSize Double | Discrete band size of a bar mark. |
MdX Double | Horizontal offset between a text mark and its anchor. |
MdY Double | Vertical offset between a text mark and its anchor. |
MEllipsis Text | The ellipsis string for text truncated in response to
The default is Since: 0.5.0.0 |
MExtent MarkErrorExtent | Extent of whiskers used with Since: 0.4.0.0 |
MFill Color | Default fill color of a mark. This was changed to use the |
MFilled Bool | Should a mark's color should be used as the fill color instead of stroke color. |
MFillGradient ColorGradient GradientStops [GradientProperty] | The color gradient to apply to the interior of a mark. The first argument determines its type, the second is the list of color interpolation points, and the third allows for customization.
Since: 0.5.0.0 |
MFillOpacity Opacity | Fill opacity of a mark. |
MFont Text | Font of a text mark. Can be any font name made accessible via a css file (or a generic font like "serif", "monospace" etc.). |
MFontSize Double | Font size, in pixels, used by a text mark. |
MFontStyle Text | Font style (e.g. "italic") used by a text mark. |
MFontWeight FontWeight | Font weight used by a text mark. |
MHeight Double | Explicitly set the height of a mark. See also Since: 0.4.0.0 |
MHRef Text | Hyperlink to be associated with a mark making it a clickable hyperlink. Since: 0.4.0.0 |
MInnerRadius Double | The inner radius, in pixels, of arc marks. It is an alias for
Since: 0.9.0.0 |
MInterpolate MarkInterpolation | Interpolation method used by line and area marks. |
MLimit Double | The maximum length of the text mark in pixels. If the text is
larger then it will be truncated, with the truncation controlled
by The default value is Since: 0.5.0.0 |
MLine LineMarker | How should the vertices of an area mark be joined? Since: 0.4.0.0 |
MLineBreak Text | A delimeter, such as a newline character, upon which to break text strings into multiple lines. Note that Since: 0.5.0.0 |
MLineHeight Double | The height, in pixels, of each line of text in a multi-line text mark. Since: 0.5.0.0 |
MMedian [MarkProperty] | Median-line properties for the Since: 0.4.0.0 |
MNoMedian | Do not draw the median of the Since: 0.6.0.0 |
MOpacity Opacity | Overall opacity of a mark in the range 0 to 1. |
MOrder Bool | Ordering of vertices in a line or area mark. If Since: 0.4.0.0 |
MOrient Orientation | Orientation of a non-stacked bar, tick, area or line mark. |
MOuterRadius Double | The outer radius, in pixels, of arc marks. It is an alias for Since: 0.9.0.0 |
MOutliers [MarkProperty] | Outlier symbol properties for the Since: 0.4.0.0 |
MNoOutliers | Do not draw outliers with the Since: 0.4.0.0 |
MPadAngle Double | The angular padding apploed to sides of the arc, in radians. Since: 0.9.0.0 |
MPoint PointMarker | Appearance of a point marker joining the vertices of a line or area mark. Since: 0.4.0.0 |
MRadius Double | Polar coordinate radial offset of a text mark, in pixels, from its origin. For an arc mark this defines the outer radius, in pixels. |
MRadius2 Double | The inner radius, in pixels, of an arc mark. Since: 0.9.0.0 |
MRadiusOffset Double | The offset for Since: 0.9.0.0 |
MRadius2Offset Double | The offset for Since: 0.9.0.0 |
MRemoveInvalid Bool | The default handling of invalid ( This replaces Since: 0.5.0.0 |
MRule [MarkProperty] | Rule (main line) properties for the Since: 0.4.0.0 |
MNoRule | Do not draw the rule for Since: 0.6.0.0 |
MShape Symbol | Shape of a point mark. |
MSize Double | Size of a mark. |
MStroke Color | Default stroke color of a mark. This was changed to use the |
MStrokeCap StrokeCap | Cap style of a mark's stroke. Since: 0.4.0.0 |
MStrokeDash DashStyle | The stroke dash pattern used by a mark. |
MStrokeDashOffset DashOffset | The offset for the dash pattern. |
MStrokeGradient ColorGradient GradientStops [GradientProperty] | The color gradient to apply to the boundary of a mark. The first argument determines its type, the second is the list of color interpolation points, and the third allows for customization.
Since: 0.5.0.0 |
MStrokeJoin StrokeJoin | Line segment join style of a mark's stroke. Since: 0.4.0.0 |
MStrokeMiterLimit Double | Mitre limit at which to bevel a join between line segments of a mark's stroke. Since: 0.4.0.0 |
MStrokeOpacity Opacity | Stroke opacity of a mark in the range 0 to 1. |
MStrokeWidth Double | Stroke width of a mark in pixels. |
MStyle [StyleLabel] | Names of custom styles to apply to a mark. Each should refer to a named style
defined in a separate style configuration (using
|
MTension Double | Interpolation tension used when interpolating line and area marks. |
MText Text | Placeholder text for a text mark for when a text channel is not specified. See |
MTexts [Text] | Placeholder text for a text mark for when a text channel is not specified. See Since: 0.6.0.0 |
MTheta Double | Polar coordinate angle (clockwise from north in radians) of a text mark from the origin (determined by its x and y properties). For arc marks, the arc length in radians if theta2 is not specified, otherwise the start arc angle, where a value of 0 refers to "up" or "north", and increases clockwise). |
MTheta2 Double | The end angle of arc marks, in radians. A value of 0 indicated "up" or "north", and increases clockwise. Since: 0.9.0.0 |
MThetaOffset Double | Offset for Since: 0.9.0.0 |
MTheta2Offset Double | Offset for Since: 0.9.0.0 |
MThickness Double | Thickness of a tick mark. |
MTicks [MarkProperty] | Tick properties for the Since: 0.4.0.0 |
MNoTicks | Do not draw ticks for The default behavior for ticks is for them to not be drawn, so
Since: 0.6.0.0 |
MTimeUnitBand Double | The default relative band size for a time unit. If set to 1 the bandwidth of the marks will be equal to the time unit band step, and if set to 0.5 they will be half that. Since: 0.5.0.0 |
MTimeUnitBandPosition Double | The default relative band position for a time unit. If set to 0 the marks will be positioned at the start of the band, and if set to 0.5 they will be in the middle. Since: 0.5.0.0 |
MTooltip TooltipContent | The tooltip content for a mark. Since: 0.4.0.0 |
MWidth Double | Explicitly set the width of a mark (e.g. the bar width). See also
Since: 0.4.0.0 |
MX Double | X position of a mark. See also Since: 0.4.0.0 |
MX2 Double | X2 position of a mark. This is the secondary position for
lines and area marks). See also Since: 0.4.0.0 |
MXOffset Double | X position offset of a mark. Since: 0.4.0.0 |
MX2Offset Double | X2 position offset of a mark. Since: 0.4.0.0 |
MY Double | Y position of a mark. See also Since: 0.4.0.0 |
MY2 Double | Y2 position of a mark. This is the secondary position for
lines and area marks). See also Since: 0.4.0.0 |
MYOffset Double | Y position offset of a mark. Since: 0.4.0.0 |
MY2Offset Double | Y2 position offset of a mark. Since: 0.4.0.0 |
MXWidth | Specify the X coordinate as the "width" of the plot. Since: 0.9.0.0 |
MX2Width | Specify the X2 coordinate as the "width" of the plot. Since: 0.9.0.0 |
MYHeight | Specify the Y coordinate as the "height" of the plot. Since: 0.9.0.0 |
MY2Height | Specify the Y2 coordinate as the "height" of the plot. Since: 0.9.0.0 |
How are strokes capped? This is used with MStrokeCap
, VBStrokeCap
,
and ViewStrokeCap
.
Since: 0.4.0.0
data StrokeJoin Source #
How are strokes joined? This is used with MStrokeJoin
, VBStrokeJoin
,
and ViewStrokeJoin
.
Since: 0.4.0.0
Used by Mark Properties
data Orientation Source #
The orientation of an item. This is used with:
BLeLDirection
, LDirection
,
LeDirection
, LeGradientDirection
,
LeLDirection
, LeSymbolDirection
,
and MOrient
.
In 0.4.0.0
this was renamed from MarkOrientation
to Orientation
.
Horizontal | Display horizontally. |
Vertical | Display vertically. |
data MarkInterpolation Source #
Indicates the mark interpolation style. See the Vega-Lite documentation for details.
Basis | A B-spline interpolation between points anchored at the first and last points. |
BasisClosed | Closed B-spline interpolation between points forming a polygon. |
BasisOpen | Open B-spline interpolation between points, which may not intersect the first and last points. |
Bundle | Bundle curve interpolation between points. This is equivalent to |
Cardinal | Cardinal spline interpolation between points anchored at the first and last points. |
CardinalClosed | Closed Cardinal spline interpolation between points forming a polygon. |
CardinalOpen | Open Cardinal spline interpolation between points, which may not intersect the first and last points. |
Linear | Linear interpolation between points. |
LinearClosed | Closed linear interpolaiton between points forming a polygon. |
Monotone | Cubic spline interpolation that preserves monotonicity between points. |
StepAfter | Piecewise (stepped) constant interpolation function after each point in a sequence. |
StepBefore | Piecewise (stepped) constant interpolation function before each point in a sequence. |
Stepwise | Piecewise (stepped) constant interpolation function centred on each point in a sequence. |
Identifies the type of symbol used with the Point
mark type.
It is used with MShape
, LeSymbolType
, and LSymbolType
.
In version 0.4.0.0
all constructors were changed to start
with Sym
.
SymCircle | Specify a circular symbol for a shape mark. |
SymSquare | Specify a square symbol for a shape mark. |
SymCross | Specify a cross symbol for a shape mark. |
SymDiamond | Specify a diamond symbol for a shape mark. |
SymTriangleUp | Specify an upward-triangular symbol for a shape mark. |
SymTriangleDown | Specify a downward-triangular symbol for a shape mark. |
SymTriangleRight | Specify an right-facing triangular symbol for a shape mark. Since: 0.4.0.0 |
SymTriangleLeft | Specify an left-facing triangular symbol for a shape mark. Since: 0.4.0.0 |
SymStroke | The line symbol. Since: 0.4.0.0 |
SymArrow | Centered directional shape. Since: 0.4.0.0 |
SymTriangle | Centered directional shape. It is not clear what difference
this is to Since: 0.4.0.0 |
SymWedge | Centered directional shape. Since: 0.4.0.0 |
SymPath Text | A custom symbol shape as an SVG path description. For correct sizing, the path should be defined within a square bounding box, defined on an axis of -1 to 1 for both dimensions. |
data PointMarker Source #
The properties of a point marker on a line or area mark.
For use with MPoint
.
Since: 0.4.0.0
PMTransparent | A transparent marker is used, which can be useful for interactive selections. |
PMNone | No marker to be shown. |
PMMarker [MarkProperty] | The properties of the marks to be shown at the points. Use an empty list to use a filled point with default properties. |
data LineMarker Source #
Appearance of a line marker that is overlaid on an area mark.
For use with MLine
.
Since: 0.4.0.0
LMNone | No line marker. |
LMMarker [MarkProperty] | The properties of a line marker overlain on an area mark. Use an empty list to use a filled point with default properties. |
data MarkErrorExtent Source #
Indicates the extent of the rule used for the error bar. See Vega-Lite documentation for details.
Note that not all options are valid for all mark types.
This is called SummaryExtent
in Elm and the constructors also have
different names.
Since: 0.4.0.0
ConfidenceInterval | Band extent between the 95% confidence intervals of a distribution. |
StdErr | Band extent as the standard error about the mean of a distribution. |
StdDev | Band extent as the standard deviation of a distribution. |
Iqr | Band extent between the lower and upper quartiles of a distribution (the inter-quartile range, q1 to q3). |
ExRange | Band extent between the minimum and maximum values in a distribution. |
IqrScale Double | A scaling of the interquartile range to be used as whiskers in a
|
data TooltipContent Source #
TTEncoding | When enabled, tooltips are generated by the encoding (this is the default). For example:
|
TTData | Tooltips are generated by all fields in the underlying data. For example:
|
TTNone | Disable tooltips. This is the default behavior in Vega-Lite 4,
and can also be achieved by adding an encoding of
For example:
|
data ColorGradient Source #
Define the form of the
color gradient
(for use with MColorGradient
and MFillGradient
).
Since: 0.5.0.0
data GradientProperty Source #
Control the appearance of the gradient. Used by MColorGradient
,
MFillGradient
, and MStrokeGradient
.
Since: 0.5.0.0
GrX1 GradientCoord | The start of the color gradient (X axis); for radial gradients it represents the center of the inner circle. The default for linear gradients is 0, and for radial gradients it is 0.5. |
GrY1 GradientCoord | The start of the color gradient (Y axis); for radial gradients it represents the center of the inner circle. The default for linear gradients is 0, and for radial gradients it is 0.5. |
GrX2 GradientCoord | The end of the color gradient (X axis); for radial gradients it represents the center of the outer circle. The default for linear gradients is 1, and for radial gradients it is 0.5. |
GrY2 GradientCoord | The end of the color gradient (Y axis); for radial gradients it represents the center of the outer circle. The default for linear gradients is 1, and for radial gradients it is 0.5. |
GrR1 GradientCoord | The radius of the inner circle (radial color gradients only). The default is 0. |
GrR2 GradientCoord | The radius of the outer circle (radial color gradients only). The default is 0.5. |
data TextDirection Source #
The blend mode for drawing an item on its background. This is used with MBlend
.
This is based on CSS mix-blend-mode
and the default is BMNormal
.
Added in Vega-Lite 4.6.0.
Since: 0.7.0.0
BMNormal | The default behavior for Vega-Lite, which is the |
BMMultiply |
|
BMScreen |
|
BMOverlay |
|
BMDarken |
|
BMLighten |
|
BMColorDodge |
|
BMColorBurn |
|
BMHardLight |
|
BMSoftLight |
|
BMDifference |
|
BMExclusion |
|
BMHue |
|
BMSaturation |
|
BMColor |
|
BMLuminosity |
|
Cursors
See the CSS cursor documentation
Represents the type of cursor to display. For an explanation of each type, see the CSS documentation.
Creating the Encoding Specification
Types and functions for declaring which data fields are mapped to which
channels. Channels can include: position on screen (e.g. X
, Y
); visual
mark properties (color
, size
, stroke
, shape
); text
; hyperlink
;
ordering (order
); level of detail
; and facets for composed
visualizations (facet
). All can be further customised via a series of
properties that determine how the encoding is implemented (such as
scaling, sorting, and spacing).
In version 0.5.0.0
the EncodingSpec
type was introduced to
make it clear what functions can be used with encoding
.
:: [EncodingSpec] | The channel encodings (the order does not matter). Prior to |
-> PropertySpec |
Create an encoding specification from a list of channel encodings.
enc =encoding
.position
X
[PName
"Animal",PmType
Ordinal
] .position
Y
[PName
"Age",PmType
Quantitative
] .shape
[MName
"Species",MmType
Nominal
] .size
[MName
"Population",MmType
Quantitative
]
The type of enc
in this example is [EncodingSpec] -> PropertySpec
,
so it can either be used to add further encoding specifications or as
enc []
to create a specification.
The supported encodings are:
ariaDescription
, angle
, color
, column
, detail
, fill
, fillOpacity
,
hyperlink
, opacity
, order
, position
, row
, shape
, size
,
stroke
, strokeDash
, strokeOpacity
, strokeWidth
, text
, tooltip
,
tooltips
, and url
.
There is currently no support for encoding by key.
data Measurement Source #
Type of measurement to be associated with some channel.
Nominal | Data are categories identified by name alone and which have no intrinsic order. |
Ordinal | Data are also categories, but ones which have some natural order. |
Quantitative | Data are numeric measurements typically on a continuous scale. |
Temporal | Data represents time in some manner. |
GeoFeature | Geospatial position encoding ( |
Position Channels
Control where items appear in the visualization. See the Vega-Lite position documentation.
:: Position | The channel to encode. |
-> [PositionChannel] | The options for the channel; this will usually include the name ( |
-> BuildEncodingSpecs |
Encode a position channel.
enc =encoding
.position
X
[PName
"Animal",PmType
Ordinal
]
Encoding by position will generate an axis by default. To prevent the axis from
appearing, simply provide an empty list of axis properties to PAxis
:
enc =encoding
.position
X
[PName
"Animal",PmType
Ordinal
,PAxis
[] ]
Type of position channel, X
and Y
represent horizontal and vertical axis
dimensions on a plane and X2
and Y2
represent secondary axis dimensions where
two scales are overlaid in the same space. Geographic positions represented by
longitude and latiutude values are identified with Longitude
, Latitude
and
their respective secondary equivalents. Such geographic position channels are
subject to a map projection (set using projection
) before being placed graphically.
X | |
Y | |
X2 | The secondary coordinate for ranged |
Y2 | The secondary coordinate for ranged |
Theta | The start angle of an arc. Since: 0.9.0.0 |
Theta2 | The end angle of an arc. Since: 0.9.0.0 |
R | The outer radius of an arc. Since: 0.9.0.0 |
R2 | The inner radius of an arc. Since: 0.9.0.0 |
XError | Indicates that the Since: 0.4.0.0 |
XError2 | Used to support asymmetric error ranges defined as Since: 0.4.0.0 |
YError | Indicates that the Since: 0.4.0.0 |
YError2 | Used to support asymmetric error ranges defined as Since: 0.4.0.0 |
Longitude | The longitude value for projections. |
Latitude | The latitude value for projections. |
Longitude2 | A second longitude coordinate. |
Latitude2 | A second longitude coordinate. |
Position channel properties
data PositionChannel Source #
Position channel properties used for creating a position channel encoding.
PName FieldName | Name of the field used for encoding with a position channel. |
PHeight | Set the position to the height of the enclosing data space. Useful for placing a mark relative to the bottom edge of a view. Since: 0.4.0.0 |
PWidth | Set the position to the width of the enclosing data space. Useful for justifying a mark to the right hand edge of a view. e.g. to position a mark at the right of the data rectangle: enc = Since: 0.4.0.0 |
PDatum DataValue | Set a position to an arbitrary data value. Useful for placing items at a
specific point in the data space. To place in data screen space use
Since: 0.9.0.0 |
PNumber Double | Set a position to an arbitrary value. Useful for placing items at the top of
a plot area ( Use Since: 0.4.0.0 |
PRepeat Arrangement | Reference in a position channel to a field name generated by For example: enc = |
PRepeatDatum Arrangement | Reference in a position channel to a datum value generated by Since: 0.9.0.0 |
PmType Measurement | Level of measurement when encoding with a position channel. |
PBin [BinProperty] | Discretize numeric values into bins when encoding with a position channel. For example, to encode a frequency histogram with bins every 5 units: enc = |
PBinned | Indicate that the data encoded with position is already binned. Since: 0.4.0.0 |
PTimeUnit TimeUnit | Form of time unit aggregation of field values when encoding with a position channel. |
PTitle Text | Title of a field when encoding with a position channel. Since: 0.4.0.0 |
PNoTitle | Draw no title. Since: 0.4.0.0 |
PAggregate Operation | Compute some aggregate summary statistics for a field to be encoded with a position channel. enc = |
PScale [ScaleProperty] | Scaling applied to a field when encoding with a position channel. The scale will transform a field's value into a position along one axis. For example, the following will scale the bars positioned along a horizontal axis to have an inner spacing of 50% (0.5) of the total space allocated to each bar: enc = |
PAxis [AxisProperty] | Axis properties used when encoding with a position channel. For no axis, provide an empty list. |
PSort [SortProperty] | Sort order for field when encoding with a position channel. |
PStack StackOffset | Type of stacking offset for the field when encoding with a position channel. For example, stacking areas away from a centreline can be used to create a streamgraph: enc = Changed from |
PImpute [ImputeProperty] | Set the imputation rules for a position channel. See the Vega-Lite impute documentation. Since: 0.4.0.0 |
PBand Double | Specify the mark position or size relative to the band size. The value is in the range 0 to 1, inclusive. For rectangular-based marks ( For non-rectangular marks, the relative position on a band of a stacked, binned, time unit, or band scale is used. A value of 0 positions the band at the beginning of the band, and 1 at the end. Since: 0.5.0.0 |
Sorting properties
See the Vega-Lite sort documentation.
data SortProperty Source #
Allow type of sorting to be customised. For details see the Vega-Lite documentation.
The constructors have been changed in version 0.4.0.0
, with
Op
, ByField
, and ByRepeat
removed, and their functionality
replaced with ByRepeatOp
, ByFieldOp
, and ByChannel
.
Ascending | Sorting is from low to high. |
Descending | Sorting is from high to low. |
CustomSort DataValues | Custom sort order listing data values explicitly. Since: 0.4.0.0 |
ByRepeatOp Arrangement Operation | Sort by the aggregated summaries of the given fields (referenced by a repeat iterator) using an aggregation operation. Since: 0.4.0.0 |
ByFieldOp FieldName Operation | Sort by the aggregated summary of a field using an aggregation
operation. The following example sorts the categorical data field
Since: 0.4.0.0 |
ByChannel Channel | Sort by another channel.
Since: 0.4.0.0 |
How should the field be sorted when performing a window transform.
Since: 0.4.0
WAscending FieldName | Sort the field into ascending order. |
WDescending FieldName | Sort the field into descending order. |
Axis properties
See the Vega-Lite axis property documentation](https:/vega.github.iovega-litedocsaxis.html#axis-properties).
data AxisProperty Source #
Axis customisation properties. These are used for customising individual axes.
To configure all axes, use AxisConfig
with a configuration
instead. See the
Vega-Lite documentation
for more details.
The AxTitleMaxLength
constructor was removed in release 0.4.0.0
. The
AxTitleLimit
constructor should be used instead.
AxAria Bool | A boolean flag indicating if ARIA attributes should be included (SVG output only). If False, the "aria-hidden" attribute will be set on the output SVG group, removing the axis from the ARIA accessibility tree. Default value: True Since: 0.9.0.0 |
AxAriaDescription Text | A text description of this axis for ARIA accessibility (SVG output only). If the If the description is unspecified it will be automatically generated. Since: 0.9.0.0 |
AxBandPosition Double | An interpolation fraction indicating where, for Since: 0.4.0.0 |
AxDataCondition BooleanOp ConditionalAxisProperty | Set conditions on an axis property. The first argument is the test to apply, and the second is the pair of properties to set if the condition holds or not. The test parameter has access to the axis
Inline aggregation can be performed (before the test)
using
Since: 0.5.0.0 |
AxDomain Bool | Should the axis domain (the baseline) be displayed? |
AxDomainCap StrokeCap | The stroke cap for the domain lines' ending style. Since: 0.9.0.0 |
AxDomainColor Color | The axis domain color. Since: 0.4.0.0 |
AxDomainDash DashStyle | The dash pattern of the domain. Since: 0.4.0.0 |
AxDomainDashOffset DashOffset | The offset for the dash pattern. Since: 0.4.0.0 |
AxDomainOpacity Opacity | The axis domain opacity. Since: 0.4.0.0 |
AxDomainWidth Double | The width of the axis domain. Since: 0.4.0.0 |
AxFormat Text | Formatting pattern for
axis values. To distinguish between formatting as numeric values
and data/time values, additionally use When used with a custom formatType, this value will be passed as "format" alongside "datum.value" to the registered function. |
AxFormatAsNum | Facet headers should be formatted as numbers. Use a
d3 numeric format string
with Since: 0.4.0.0 |
AxFormatAsTemporal | Facet headers should be formatted as dates or times. Use a
d3 date/time format string
with Since: 0.4.0.0 |
AxFormatAsCustom Text | The custom format type
for use with with Since: 0.9.0.0 |
AxGrid Bool | Should an axis grid be displayed? |
AxGridCap StrokeCap | The stroke cap for the grid lines' ending style. Since: 0.9.0.0 |
AxGridColor Color | The color for the grid. Since: 0.4.0.0 |
AxGridDash DashStyle | The dash pattern of the grid. Since: 0.4.0.0 |
AxGridDashOffset DashOffset | The offset for the dash pattern. Since: 0.4.0.0 |
AxGridOpacity Opacity | The opacity of the grid. Since: 0.4.0.0 |
AxGridWidth Double | The width of the grid lines. Since: 0.4.0.0 |
AxLabels Bool | Should labels be added to an axis? |
AxLabelAlign HAlign | The horizontal alignment for labels. Since: 0.4.0.0 |
AxLabelAngle Angle | The angle at which to draw labels. |
AxLabelBaseline VAlign | The vertical alignment for labels. Since: 0.4.0.0 |
AxLabelNoBound | No boundary overlap check is applied to labels. This is the default behavior. See also Since: 0.4.0.0 |
AxLabelBound | Labels are hidden if they exceed the axis range by more than 1 pixel. See also Since: 0.4.0.0 |
AxLabelBoundValue Double | Labels are hidden if they exceed the axis range by more than the given number of pixels. See also Since: 0.4.0.0 |
AxLabelColor Color | The label color. Since: 0.4.0.0 |
AxLabelExpr VegaExpr | Provide the expression used to generate axis labels. The expression can use The following example uses four digit years for decades and two-digit years for other years: AxLabelExpr "if(year(datum.value) % 10 == 0, utcFormat(datum.value,'%Y'), utcFormat(datum.value,'%y'))" Since: 0.5.0.0 |
AxLabelNoFlush | The labels are not aligned flush to the scale. This is the default for non-continuous X scales. See also Since: 0.4.0.0 |
AxLabelFlush | The first and last axis labels are aligned flush to the scale range. See also Since: 0.4.0.0 |
AxLabelFlushValue Double | The labels are aligned flush, and the parameter determines the extra offset, in pixels, to apply to the first and last labels. This can help the labels better group (visually) with the corresponding axis ticks. See also Since: 0.4.0.0 |
AxLabelFlushOffset Double | The number of pixels to offset flush-adjusted labels. Since: 0.4.0.0 |
AxLabelFont Text | The font for the label. Since: 0.4.0.0 |
AxLabelFontSize Double | The font size of the label. Since: 0.4.0.0 |
AxLabelFontStyle Text | The font style of the label. Since: 0.4.0.0 |
AxLabelFontWeight FontWeight | The font weight of the label. Since: 0.4.0.0 |
AxLabelLimit Double | The maximum width of a label, in pixels. Since: 0.4.0.0 |
AxLabelLineHeight Double | The line height, in pixels, for multi-line label text. Added in Vega-Lite 4.6.0. Since: 0.7.0.0 |
AxLabelOffset Double | The pixel offset for labels, in addition to Since: 0.6.0.0 |
AxLabelOpacity Opacity | The opacity of the label. Since: 0.4.0.0 |
AxLabelOverlap OverlapStrategy | How should overlapping labels be displayed? |
AxLabelPadding Double | The padding, in pixels, between the label and the axis. |
AxLabelSeparation Double | The minimum separation, in pixels, between label bounding boxes
for them to be considered non-overlapping. This is ignored if
the Since: 0.4.0.0 |
AxMaxExtent Double | The maximum extent, in pixels, that axis ticks and labels should use. This determines a maxmium offset value for axis titles. |
AxMinExtent Double | The minimum extent, in pixels, that axis ticks and labels should use. This determines a minmium offset value for axis titles. |
AxOffset Double | The offset, in pixels, between the axis and the edge of the enclosing group or data rectangle. |
AxOrient Side | The orientation of the axis. |
AxPosition Double | The anchor position of the axis in pixels. |
AxStyle [StyleLabel] | The named styles - generated with Since: 0.6.0.0 |
AxTicks Bool | Should tick marks be drawn on an axis? |
AxTickBand BandAlign | For band scales, indicates if ticks and grid lines should be placed at the center of a band (the default) or at the band extents to indicate intervals. Since: 0.5.0.0 |
AxTickCap StrokeCap | The stroke cap for the grid lines' ending style. Since: 0.9.0.0 |
AxTickColor Color | The color of the ticks. Since: 0.4.0.0 |
AxTickCount Int | The desired number of ticks for axes visualizing quantitative scales. This is a hint to the system, and the actual number used will be adjusted to be "nice" (multiples of 2, 5, or 10) and lie within the underlying scale's range. The |
AxTickCountTime ScaleNice | A specialised version of The Since: 0.9.0.0 |
AxTickDash DashStyle | The dash pattern of the ticks. Since: 0.4.0.0 |
AxTickDashOffset DashOffset | The offset for the dash pattern. Since: 0.4.0.0 |
AxTickExtra Bool | Should an extra axis tick mark be added for the initial position of the axis? Since: 0.4.0.0 |
AxTickMinStep Double | The minimum desired step between axis ticks, in terms of the scale domain values. Since: 0.4.0.0 |
AxTickOffset Double | The position offset, in pixels, to apply to ticks, labels, and grid lines. See also Since: 0.4.0.0 |
AxTickOpacity Opacity | The opacity of the ticks. Since: 0.4.0.0 |
AxTickRound Bool | Should pixel position values be rounded to the nearest integer? Since: 0.4.0.0 |
AxTickSize Double | The size of the tick marks in pixels. |
AxTickWidth Double | The width of the tick marks in pixels. Since: 0.4.0.0 |
AxTitle Text | The axis title. |
AxNoTitle | Draw no title for the axis. Since: 0.4.0.0 |
AxTitleAlign HAlign | The horizontal alignment of the axis title. |
AxTitleAnchor APosition | The text anchor position for placing axis titles. Since: 0.4.0.0 |
AxTitleAngle Angle | The angle of the axis title. |
AxTitleBaseline VAlign | The vertical alignment of the axis title. Since: 0.4.0.0 |
AxTitleColor Color | The color of the axis title. Since: 0.4.0.0 |
AxTitleFont Text | The font for the axis title. Since: 0.4.0.0 |
AxTitleFontSize Double | The font size of the axis title. Since: 0.4.0.0 |
AxTitleFontStyle Text | The font style of the axis title. Since: 0.4.0.0 |
AxTitleFontWeight FontWeight | The font weight of the axis title. Since: 0.4.0.0 |
AxTitleLimit Double | The maximum allowed width of the axis title, in pixels. Since: 0.4.0.0 |
AxTitleLineHeight Double | Line height, in pixels, for multi-line title text. Since: 0.5.0.0 |
AxTitleOpacity Opacity | The opacity of the axis title. Since: 0.4.0.0 |
AxTitlePadding Double | The padding, in pixels, between title and axis. |
AxTitleX Double | The X coordinate of the axis title, relative to the axis group. Since: 0.4.0.0 |
AxTitleY Double | The Y coordinate of the axis title, relative to the axis group. Since: 0.4.0.0 |
AxTranslateOffset Double | The translation offset in pixels applied to the axis group mark x and y. If specified it overrides the default value of a 0.5 offset to pixel-align stroked lines. Since: 0.5.0.0 |
AxValues DataValues | Set the explicit tick, grid, and label values along an axis. The following three examples are for an axis displaying a quantitative, categorical, and temporal field respectively.
Changed in |
AxDates [[DateTime]] | Deprecated: Please change AxDates to AxValues The dates or times to appear along the axis. As of version |
AxZIndex ZIndex | The z-index of the axis, relative to the chart marks. |
data ConditionalAxisProperty Source #
For use with AxDataCondition
, and defines those axis properties
which can be conditioned on their position (or label).
The constuctor determines the axis property (a label, tick, or
grid element), and the two arguments are the value to set if the condition
is True
(first), and for when it is False
(second).
Since: 0.5.0.0
CAxGridColor Color Color | The color for the axis grid. |
CAxGridDash DashStyle DashStyle | The dash pattern for the axis grid. |
CAxGridDashOffset DashOffset DashOffset | The offset for the dash pattern. |
CAxGridOpacity Opacity Opacity | The opacity of the axis grid. |
CAxGridWidth Double Double | The width of the axis grid. |
CAxLabelAlign HAlign HAlign | Axis label horizontal alignment. |
CAxLabelBaseline VAlign VAlign | Axis label vertical alignment. |
CAxLabelColor Color Color | Axis label color. |
CAxLabelFont Text Text | Axis label font. |
CAxLabelFontSize Double Double | Axis label font. |
CAxLabelFontStyle Text Text | Axis label font style. |
CAxLabelFontWeight FontWeight FontWeight | Axis label font weight. |
CAxLabelOffset Double Double | Axis label offset. Since: 0.6.0.0 |
CAxLabelOpacity Opacity Opacity | Axis label opacity. |
CAxLabelPadding Double Double | Axis label padding. Since: 0.6.0.0 |
CAxTickColor Text Text | Tick color for the axis. |
CAxTickDash DashStyle DashStyle | The dash pattern for the axis ticks. |
CAxTickDashOffset DashOffset DashOffset | The offset for the dash pattern. |
CAxTickOpacity Opacity Opacity | Opacity of the axis tick marks. |
CAxTickSize Double Double | Size, in pixels, of the axis tick marks. Since: 0.6.0.0 |
CAxTickWidth Double Double | Width, in pixels, of the axis tick marks. |
Positioning Constants
Alignment
Indicates the horizontal alignment of text such as on an axis or legend.
Indicates the vertical alignment of text that may be attached to a mark.
AlignTop | The position refers to the top of the text, calculated relative to
the font size. Also see |
AlignMiddle | The middle of the text. |
AlignBottom | The position refers to the bottom of the text, including
descenders, like g. This is calculated relative to the
font size. Also see |
AlignBaseline | The position refers to the baseline of the text (so it does
not include descenders). This maps to the Vega-Lite
Since: 0.6.0.0 |
AlignLineTop | Similar to This was added in Vega-Lite 4.6.0. Since: 0.7.0.0 |
AlignLineBottom | Similar to This was added in Vega-Lite 4.6.0. Since: 0.7.0.0 |
Where should tick marks and grid lines be placed. This is used with
AxTickBand
and TickBand
.
Since: 0.5.0.0
Overlapping text
data OverlapStrategy Source #
Type of overlap strategy to be applied when there is not space to show all items
on an axis, and is used by
AxLabelOverlap
,
LabelOverlap
,
LLabelOverlap
,
and LeLabelOverlap
.
See the
Vega-Lite documentation
for more details.
ONone | No overlap strategy to be applied when there is not space to show all items on an axis. |
OParity | Give all items equal weight in overlap strategy to be applied when there is not space to show them all on an axis. |
OGreedy | Greedy overlap strategy to be applied when there is not space to show all items on an axis. |
Legends
Represents one side of a rectangular space.
Used by
AxOrient
,
HLabelOrient
,
HTitleOrient
,
LTitleOrient
,
LeTitleOrient
,
Orient
,
and
TOrient
.
Mark channels
:: [MarkChannel] | The color-encoding options. |
-> BuildEncodingSpecs |
Encode an angle (orientation) channel, which allows for data-driven rotation of text, point, and square marks.
Since: 0.9.0.0
:: [MarkChannel] | The color-encoding options. |
-> BuildEncodingSpecs |
:: [MarkChannel] | Configure the fill. |
-> BuildEncodingSpecs |
fillOpacity :: [MarkChannel] -> BuildEncodingSpecs Source #
opacity :: [MarkChannel] -> BuildEncodingSpecs Source #
Encode an opacity channel. The first parameter is a list of mark channel properties that characterise the way a data field is encoded by opacity. The second parameter is a list of any previous channels to which this opacity channel should be added.
opacity
[MName
"Age",MmType
Quantitative
] []
See also fillOpacity
.
:: [MarkChannel] | What data values are used to control the shape parameters of the mark. |
-> BuildEncodingSpecs |
:: [MarkChannel] | What data values are used to control the size parameters of the mark. |
-> BuildEncodingSpecs |
Encode a size channel.
size
[MName
"Age",MmType
Quantitative
] []
:: [MarkChannel] | What data values are used to control the stoke parameters of the mark. |
-> BuildEncodingSpecs |
:: [MarkChannel] | What data values are used to control the stoke opacity parameters of the mark. |
-> BuildEncodingSpecs |
Encode a stroke-dash channel.
The following will use a different dash style for each value in the "symbol" field (a multi-series line chart):
toVegaLite
[dataFromUrl
"data/stocks.csv" [] ,mark
Line
[] ,encoding
.position
X
[PName
"date",PmType
Temporal
] .position
Y
[PName
"price",PmType
Quantitative
] . strokeDash [MName
"symbol",MmType
Nominal
] $ [] ]
It can also be used to change the line style for connected
points (e.g. to indicate where the data changes its "predicted"
value, noting that there are two points at "a"
equal to "E"
):
toVegaLite
[dataFromColumns
[] .dataColumn
"a" (Strings
[ "A", "B", "D", "E", "E", "G", "H"]) .dataColumn
"b" (Numbers
[ 28, 55, 91, 81, 81, 19, 87 ]) .dataColumn
"predicted" (Booleans
[False, False, False, False, True, True, True]) $ [] ,mark
Line
[] ,encoding
.position
X
[PName
"a",PmType
Ordinal
] .position
Y
[PName
"b",PmType
Quantitative
] . strokeDash [MName
"predicted",MmType
Nominal
] $ [] ]
Since: 0.6.0.0
:: [MarkChannel] | What data values are used to control the stoke opacity parameters of the mark. |
-> BuildEncodingSpecs |
:: [MarkChannel] | What data values are used to control the stoke width parameters of the mark. |
-> BuildEncodingSpecs |
Encode a stroke width channel.
Since: 0.4.0.0
Mark Channel properties
data MarkChannel Source #
Mark channel properties used for creating a mark channel encoding.
MName FieldName | Field used for encoding with a mark property channel. |
MRepeat Arrangement | Reference in a mark channel to a field name generated by |
MRepeatDatum Arrangement | Reference in a mark channel to a datum value generated by Since: 0.9.0.0 |
MmType Measurement | Level of measurement when encoding with a mark property channel. |
MScale [ScaleProperty] | Scaling applied to a field when encoding with a mark property channel. The scale will transform a field's value into a color, shape, size etc. Use an empty list to remove the scale. |
MBin [BinProperty] | Discretize numeric values into bins when encoding with a mark property channel. |
MBinned | Indicate that data encoding with a mark are already binned. Since: 0.4.0.0 |
MSort [SortProperty] | Sort order. Since: 0.4.0.0 |
MTimeUnit TimeUnit | Time unit aggregation of field values when encoding with a mark property channel. |
MTitle Text | Title of a field when encoding with a mark property channel. Since: 0.4.0.0 |
MNoTitle | Draw no title. Since: 0.4.0.0 |
MAggregate Operation | Compute aggregate summary statistics for a field to be encoded with a mark property channel. |
MLegend [LegendProperty] | Properties of a legend that describes a mark's encoding. For no legend, provide an empty list. |
MSelectionCondition BooleanOp [MarkChannel] [MarkChannel] | Make a mark channel conditional on interactive selection. The first parameter is a selection condition to evaluate; the second the encoding to apply if that selection is true; the third parameter is the encoding if the selection is false.
|
MDataCondition [(BooleanOp, [MarkChannel])] [MarkChannel] | Make a text channel conditional on one or more predicate expressions. The first
parameter is a list of tuples each pairing an expression to evaluate with the encoding
if that expression is
The arguments to this constructor have changed in |
MPath Text | SVG path string used when encoding with a mark property channel. Useful for providing custom shapes. |
MDatum DataValue | Name of a literal data item used for encoding with a mark property channel.
Unlike Since: 0.9.0.0 |
MNumber Double | Literal numeric value when encoding with a mark property channel. |
MString Text | Literal string value when encoding with a mark property channel. |
MBoolean Bool | Boolean value when encoding with a mark property channel. |
MNullValue | A null value. Since: 0.11.0.0 |
MSymbol Symbol | A symbol literal. This can be useful when making a symbol dependent on some data or
selection condition (e.g. For example:
Since: 0.6.0.0 |
Mark Legends
data LegendType Source #
Indicates the type of legend to create. It is used with LType
.
Prior to version 0.4.0.0.0
this was called Legend
and the
constructors did not end in Legend
.
GradientLegend | Typically used for continuous quantitative data. |
SymbolLegend | Typically used for categorical data. |
data LegendProperty Source #
Legend properties, set with MLegend
. For more detail see the
Vega-Lite documentation.
The LEntryPadding
constructor was removed in 0.4.0.0
.
LAria Bool | A boolean flag indicating if ARIA attributes should be included (SVG output only). If False, the "aria-hidden" attribute will be set on the output SVG group, removing the legend from the ARIA accessibility tree. Default value: True Since: 0.9.0.0 |
LAriaDescription Text | A text description of this legend for ARIA accessibility (SVG output only). If the If the description is unspecified it will be automatically generated. Since: 0.9.0.0 |
LClipHeight Double | The height, in pixels, to clip symbol legend entries. Since: 0.4.0.0 |
LColumnPadding Double | The horizontal padding, in pixels, between symbol legend entries. Since: 0.4.0.0 |
LColumns Int | The number of columns in which to arrange symbol legend entries.
A value of Since: 0.4.0.0 |
LCornerRadius Double | The corner radius for the full legend. Since: 0.4.0.0 |
LDirection Orientation | The direction of the legend. Since: 0.4.0.0 |
LFillColor Color | The background fill color for the full legend. Since: 0.4.0.0 |
LFormat Text | Formatting pattern for
legend values. To distinguish between formatting as numeric values
and data/time values, additionally use |
LFormatAsNum | Legends should be formatted as numbers. Use a
d3 numeric format string
with Since: 0.4.0.0 |
LFormatAsTemporal | Legends should be formatted as dates or times. Use a
d3 date/time format string
with Since: 0.4.0.0 |
LFormatAsCustom Text | The custom format type
for use with with Since: 0.9.0.0 |
LGradientLength Double | The length in pixels of the primary axis of the color gradient. Since: 0.4.0.0 |
LGradientOpacity Opacity | The opacity of the color gradient. Since: 0.4.0.0 |
LGradientStrokeColor Color | The color of the gradient stroke. Since: 0.4.0.0 |
LGradientStrokeWidth Double | The width, in pixels, of the gradient stroke. Since: 0.4.0.0 |
LGradientThickness Double | The thickness, in pixels, of the color gradient. Since: 0.4.0.0 |
LGridAlign CompositionAlignment | The grid layout for the symbol legends. Since: 0.4.0.0 |
LLabelAlign HAlign | Since: 0.4.0.0 |
LLabelBaseline VAlign | Since: 0.4.0.0 |
LLabelColor Color | The color of the legend label. Since: 0.4.0.0 |
LLabelExpr VegaExpr | Customize the legend label. The default text and value can be accessed
with the LLabelExpr "'<' + datum.label + '>'" Since: 0.8.0.0 |
LLabelFont Text | Since: 0.4.0.0 |
LLabelFontSize Double | Since: 0.4.0.0 |
LLabelFontStyle Text | Since: 0.4.0.0 |
LLabelFontWeight FontWeight | Since: 0.4.0.0 |
LLabelLimit Double | Since: 0.4.0.0 |
LLabelOffset Double | Since: 0.4.0.0 |
LLabelOpacity Opacity | Since: 0.4.0.0 |
LLabelOverlap OverlapStrategy | Since: 0.4.0.0 |
LLabelPadding Double | Since: 0.4.0.0 |
LLabelSeparation Double | Since: 0.4.0.0 |
LOffset Double | The offset in pixels by which to displace the legend from the data rectangle and axes. |
LOrient LegendOrientation | The legend orientation. |
LPadding Double | The padding, in pixels, between the border and content of the legend group. |
LRowPadding Double | The vertical padding, in pixels, between symbol legend entries. Since: 0.4.0.0 |
LStrokeColor Color | The border stroke color for the full legend. Since: 0.4.0.0 |
LSymbolDash DashStyle | The dash pattern for symbols. Since: 0.4.0.0 |
LSymbolDashOffset DashOffset | The offset for the dash pattern. Since: 0.4.0.0 |
LSymbolFillColor Color | The fill color of the legend symbol. Since: 0.4.0.0 |
LSymbolLimit Int | The maximum numbed of entries to show in the legend. Additional entries are dropped. Since: 0.8.0.0 |
LSymbolOffset Double | The horizontal pixel offset for legend symbols. Since: 0.4.0.0 |
LSymbolOpacity Opacity | The opacity of the legend symbols. Since: 0.4.0.0 |
LSymbolSize Double | The size of the legend symbol, in pixels. Since: 0.4.0.0 |
LSymbolStrokeColor Color | The edge color of the legend symbol. Since: 0.4.0.0 |
LSymbolStrokeWidth Double | The width of the sumbol's stroke. Since: 0.4.0.0 |
LSymbolType Symbol | Since: 0.4.0.0 |
LTickCount Double | The desired number of tick values for quantitative legends. The |
LTickCountTime ScaleNice | A specialised version of The Since: 0.9.0.0 |
LTickMinStep Double | The minimum desired step between legend ticks, in terms of the scale domain values. Since: 0.4.0.0 |
LTitle Text | |
LNoTitle | Draw no title. Since: 0.4.0.0 |
LTitleAlign HAlign | Since: 0.4.0.0 |
LTitleAnchor APosition | Since: 0.4.0.0 |
LTitleBaseline VAlign | Since: 0.4.0.0 |
LTitleColor Color | Since: 0.4.0.0 |
LTitleFont Text | Since: 0.4.0.0 |
LTitleFontSize Double | Since: 0.4.0.0 |
LTitleFontStyle Text | Since: 0.4.0.0 |
LTitleFontWeight FontWeight | Since: 0.4.0.0 |
LTitleLimit Double | The maximum allowed pixel width of the legend title. Since: 0.4.0.0 |
LTitleLineHeight Double | The line height, in pixels, for multi-line title text. Since: 0.8.0.0 |
LTitleOpacity Opacity | Opacity of the legend title. Since: 0.4.0.0 |
LTitleOrient Side | Orientation of the legend title. Since: 0.4.0.0 |
LTitlePadding Double | The padding, in pixels, between title and legend. Since: 0.4.0.0 |
LType LegendType | The type of the legend. |
LValues LegendValues | Explicitly set the visible legend values. |
LeX Double | Custom x position, in pixels, for the legend when Since: 0.4.0.0 |
LeY Double | Custom y position, in pixels, for the legend when Since: 0.4.0.0 |
LZIndex ZIndex | The z-index at which to draw the legend. |
data LegendOrientation Source #
Indicates the legend orientation. See the Vega-Lite documentation for more details.
LONone | |
LOLeft | |
LORight | |
LOTop | Since: 0.4.0.0 |
LOBottom | Since: 0.4.0.0 |
LOTopLeft | |
LOTopRight | |
LOBottomLeft | |
LOBottomRight |
data LegendValues Source #
A list of data values suitable for setting legend values, used with
LValues
.
Text Channels
Control the appearance of the text and tooltip elements in the visualization.
:: [TextChannel] | What data values are used to control the text parameters. |
-> BuildEncodingSpecs |
Encode a text channel. See the Vega-Lite documentation for further details on the text and tooltip channels and Vega-Lite formatting documentation for formatting the appearance of the text.
encoding
.position
X
[PName
"miles",PmType
Quantitative
] .position
Y
[PName
"gas",PmType
Quantitative
] .text
[TName
"miles",TmType
Quantitative
]
:: [TextChannel] | The properties for the channel. If the list is empty then this turns off tooltip support for
this channel. This is new to |
-> BuildEncodingSpecs |
Encode a tooltip channel. See the Vega-Lite documentation for further details on the text and tooltip channels and Vega-Lite formatting documentation for formatting the appearance of the text.
enc =encoding
.position
X
[PName
"Horsepower",PmType
Quantitative
] .position
Y
[PName
"Miles_per_Gallon",PmType
Quantitative
] .tooltip
[TName
"Year",TmType
Temporal
,TFormat
"%Y" ]
To encode multiple tooltip values with a mark, use tooltips
.
:: [[TextChannel]] | A separate list of properties for each channel. |
-> BuildEncodingSpecs |
Encode a tooltip channel using multiple data fields.
encoding
.position
X
[PName
"Horsepower",PmType
Quantitative
] .position
Y
[PName
"Miles_per_Gallon",PmType
Quantitative
] .tooltips
[ [TName
"Year",TmType
Temporal
,TFormat
"%Y" ] , [TName
"Month",TmType
Temporal
,TFormat
"%Y" ] ]
Since: 0.3.0.0
data TextChannel Source #
Types of text channel property used for displaying text as part of the visualization.
TName FieldName | Name of the field used for encoding with a text channel. |
TRepeat Arrangement | Reference in a text channel to a field name generated by |
TRepeatDatum Arrangement | Reference in a text channel to a datum value generated by Since: 0.9.0.0 |
TmType Measurement | Level of measurement when encoding with a text channel. |
TAggregate Operation | Compute some aggregate summary statistics for a field to be encoded with a text channel. The type of aggregation is determined by the given operation parameter. |
TBand Double | Specify the mark position or size relative to the band size. The value is in the range 0 to 1, inclusive. Since: 0.9.0.0 |
TBin [BinProperty] | Discretize numeric values into bins when encoding with a text channel. |
TBinned | Indicate that data encoded with a text channel are already binned. Since: 0.4.0.0 |
TDataCondition [(BooleanOp, [TextChannel])] [TextChannel] | Make a text channel conditional on one or more predicate expressions. The first
parameter is a list of tuples each pairing an expression to evaluate with the encoding
if that expression is The arguments to this constructor have changed in |
TSelectionCondition BooleanOp [TextChannel] [TextChannel] | Make a text channel conditional on interactive selection. The first parameter is a selection condition to evaluate; the second the encoding to apply if that selection is true; the third parameter is the encoding if the selection is false. |
TDatum DataValue | A constant value in the data domain. Since: 0.9.0.0 |
TFormat Text | Formatting pattern for text marks. To distinguish between formatting as numeric values and data/time
values, additionally use |
TFormatAsNum | The text marks should be formatted as numbers. Use a
d3 numeric format string
with Since: 0.4.0.0 |
TFormatAsTemporal | The text marks should be formatted as dates or times. Use a
d3 date/time format string
with Since: 0.4.0.0 |
TFormatAsCustom Text | The custom format type
for use with with Since: 0.9.0.0 |
TLabelExpr VegaExpr | Provide the expression used to generate labels. Since: 0.9.0.0 |
TString Text | A literal value for encoding a text property channel. See also This can be useful for a text annotation, such as:
Since: 0.5.0.0 |
TStrings [Text] | A multi-line value. See also Since: 0.7.0.0 |
TTimeUnit TimeUnit | Time unit aggregation of field values when encoding with a text channel. |
TTitle Text | Title of a field when encoding with a text or tooltip channel. Since: 0.4.0.0 |
TNoTitle | Display no title. Since: 0.4.0.0 |
data FontWeight Source #
Indicates the weight options for a font.
Hyperlink Channels
Channels which offer a clickable URL destination. Unlike most other channels, the hyperlink channel has no direct visual expression other than the option of changing the cursor style when hovering, so an encoding will usually pair hyperlinks with other visual channels such as marks or texts.
:: [HyperlinkChannel] | The properties for the hyperlink channel. |
-> BuildEncodingSpecs |
data HyperlinkChannel Source #
Types of hyperlink channel property used for linking marks or text to URLs.
Unfortunately there is a split between H
and Hy
as the prefix.
HName FieldName | Field used for encoding with a hyperlink channel. |
HRepeat Arrangement | Reference in a hyperlink channel to a field name generated by |
HmType Measurement | Level of measurement when encoding with a hyperlink channel. |
HAggregate Operation | Compute aggregate summary statistics for a field to be encoded with a hyperlink channel. |
HyBand Double | Specify the mark position or size relative to the band size. The value is in the range 0 to 1, inclusive. Since: 0.9.0.0 |
HBin [BinProperty] | Discretize numeric values into bins when encoding with a hyperlink channel. |
HBinned | Indicate that data encoded with a hyperlink channel are already binned. Since: 0.4.0.0 |
HSelectionCondition BooleanOp [HyperlinkChannel] [HyperlinkChannel] | Make a hyperlink channel conditional on interactive selection. The first parameter provides the selection to evaluate, the second the encoding to apply if the hyperlink has been selected, the third the encoding if it is not selected. |
HDataCondition [(BooleanOp, [HyperlinkChannel])] [HyperlinkChannel] | Make a hyperlink channel conditional on one or more predicate expressions. The first
parameter is a list of tuples each pairing an expression to evaluate with the encoding
if that expression is The arguments to this constructor have changed in |
HyFormat Text | Formatting pattern for hyperlink properties. To distinguish between formatting as numeric values and data/time
values, additionally use Since: 0.9.0.0 |
HyFormatAsNum | The marks should be formatted as numbers. Use a
d3 numeric format string
with Since: 0.9.0.0 |
HyFormatAsTemporal | The marks should be formatted as dates or times. Use a
d3 date/time format string
with Since: 0.9.0.0 |
HyFormatAsCustom Text | The custom format type
for use with with Since: 0.9.0.0 |
HyLabelExpr VegaExpr | Provide the expression used to generate labels. Since: 0.9.0.0 |
HString Text | Literal string value when encoding with a hyperlink channel. |
HTimeUnit TimeUnit | Time unit aggregation of field values when encoding with a hyperlink channel. |
HyTitle Text | Title of a field when encoding with a hyperlink channel. Since: 0.9.0.0 |
HyNoTitle | Display no title. Since: 0.9.0.0 |
URL Channel
Data-driven URL used for Image
specification: a data field can contain
URL strings defining the location of image files, or the URL can be
given directly.
url :: [HyperlinkChannel] -> BuildEncodingSpecs Source #
Encode a URL for use with the Image
mark type.
The URL can be encoded directly:
let axVals =Numbers
[ 0.5, 1.5, 2.5 ] dvals =dataFromColumns
[] .dataColumn
"x" axVals .dataColumn
"y" axVals enc =encoding
.position
X
[PName
"x",PmType
Quantitative
] .position
Y
[PName
"y",PmType
Quantitative
] .url
[HString
"wonderful-image.png" ] imMark =mark
Image
[MWidth
50,MHeight
25 ] intoVegaLite
[ dvals [], enc [], imMark ]
or by referencing a data field containing the URL values:
...dataColumn
"img" (Strings
[ "i1.png", "i2.png", "i4.png" ]) ...url
[HName
"img",HmType
Nominal
]
Since: 0.5.0.0
Order Channel
Channels that relate to the order of data fields such as for sorting stacking order or order of data points in a connected scatterplot. See the Vega-Lite documentation for further details.
:: [OrderChannel] | The order-encoding options. |
-> BuildEncodingSpecs |
Encode an order channel.
encoding
.position
X
[PName
"miles",PmType
Quantitative
] .position
Y
[PName
"gas",PmType
Quantitative
] .order
[OName
"year",OmType
Temporal
,OSort
[Descending
] ]
Conditional values
can be set with OSelectionCondition
, such as
order
[OSelectionCondition
('SelectionName "highlight") [ONumber
1] [ONumber
0]
data OrderChannel Source #
Properties of an ordering channel used for sorting data fields.
OName FieldName | The name of the field used for encoding with an order channel. |
ORepeat Arrangement | Reference in an order channel to a field name generated by |
OAggregate Operation | Compute some aggregate summary statistics for a field to be encoded with an order channel. |
OBand Double | For rect-based marks, define the mark size relative to the bandwidth of band scales, bins, or time units: a value of 1 uses the range and 0.5 half the range. For other marks it defines the relative position in a band of a stacked, binned, time unit, or band scale: if 0 the marks will be positioned at the beginning of the band and 0.5 gives the middle of the band. The argument must be in the range 0 to 1, inclusive, but there is no check on this. Since: 0.11.0.0 |
OBin [BinProperty] | Discretize numeric values into bins when encoding with an order channel. |
OSort [SortProperty] | Sort order for field when encoding with an order channel. |
OTimeUnit TimeUnit | Form of time unit aggregation of field values when encoding with an order channel. |
OTitle Text | The title for the field. Note that if both the field and axis, header, or legend titles are defined than the latter (axis, header, or legend) will be used. Since: 0.11.0.0 |
ONoTitle | Remove the title. Since: 0.11.0.0 |
OmType Measurement | The level of measurement when encoding with an order channel. |
ODataCondition [(BooleanOp, [OrderChannel])] [OrderChannel] | Make an order channel conditional on one or more predicate expressions. The first
parameter is a list of tuples each pairing an expression to evaluate with the encoding
if that expression is Since: 0.11.0.0 |
OSelectionCondition BooleanOp [OrderChannel] [OrderChannel] | Make an order channel conditional on interactive selection. The first parameter is a selection condition to evaluate; the second the encoding to apply if that selection is true; the third parameter is the encoding if the selection is false. An example:
Since: 0.11.0.0 |
ONumber Double | Create a value with this number. For use with Since: 0.11.0.0 |
Facet Channel
Channels for faceting single plots into small multiples. Can be used to create trellis plots or other arrangements in rows and columns. See the Vega-Lite documentation for further details. See also, faceted views for a more flexible (but more verbose) way of defining faceted views.
:: [FacetChannel] | The facet properties for the channel; this should include the name of
the field ( |
-> BuildEncodingSpecs |
Encode a new facet to be arranged in rows.
See the Vega-Lite row documentation.
Note that when faceting, dimensions specified with width
and height
refer to the individual faceted plots, not the whole visualization.
let dvals =dataFromUrl
"crimeData.csv" enc =encoding
.position
X
[PName
"month",PmType
Temporal
] .position
Y
[PName
"reportedCrimes" ,PmType
Quantitative
,PAggregate
Sum
,PAxis
[AxNoTitle
] ] .row
[FName
"crimeType",FmType
Nominal
] intoVegaLite
[height
80, dvals [],mark
Bar
[], enc []]
:: [FacetChannel] | The list of properties that define the faceting channel. At a minimum
this should include the data field ( |
-> BuildEncodingSpecs |
Encodes a new facet to be arranged in columns. See the Vega-Lite column documentation.
Note that when faceting, dimensions specified with width
and height
refer to the individual faceted plots, not the overall visualization.
let dvals =dataFromUrl
"crimeData.csv" enc =encoding
.position
X
[PName
"month",PmType
Temporal
] .position
Y
[PName
"reportedCrimes",PmType
Quantitative
,PAggregate
Sum
] .column
[FName
"crimeType",FmType
Nominal
] intoVegaLite
[width
100, dvals [],mark
Bar
[], enc [] ]
Level of detail Channel
Used for grouping data but without changing the visual appearance of a mark. When, for example, a field is encoded by color, all data items with the same value for that field are given the same color. When a detail channel encodes a field, all data items with the same value are placed in the same group. This allows, for example a line chart with multiple lines to be created – one for each group. See the Vega-Lite documentation for more information.
:: [DetailChannel] | The field to group. |
-> BuildEncodingSpecs |
data DetailChannel Source #
Level of detail channel properties used for creating a grouped channel encoding.
DName FieldName | The name of the field. |
DmType Measurement | The measurement type of the field. |
DBin [BinProperty] | How to convert discrete numeric values into bins. |
DTimeUnit TimeUnit | The form of time unit aggregation. |
DAggregate Operation | How should the detail field be aggregated? |
Aria Description Channel
:: [AriaDescriptionChannel] | The properties for the channel. |
-> BuildEncodingSpecs |
Encode an Aria description.
Since: 0.9.0.0
data AriaDescriptionChannel Source #
A text description of this mark for ARIA accessibility.
Since: 0.9.0.0
ADName FieldName | Field used for encoding with an Aria description. |
ADRepeat Arrangement | Reference in an Aria description channel to a field name generated by |
ADmType Measurement | Level of measurement. |
ADAggregate Operation | Compute aggregate summary statistics for a field to be encoded. |
ADBand Double | Specify the mark position or size relative to the band size. The value is in the range 0 to 1, inclusive. |
ADBin [BinProperty] | Discretize numeric values into bins. |
ADBinned | Indicate that data encoded are already binned. |
ADSelectionCondition BooleanOp [AriaDescriptionChannel] [AriaDescriptionChannel] | Make the channel conditional on interactive selection. The first parameter provides the selection to evaluate, the second the encoding to apply if the description has been selected, the third the encoding if it is not selected. |
ADDataCondition [(BooleanOp, [AriaDescriptionChannel])] [AriaDescriptionChannel] | Make the channel conditional on one or more predicate expressions. The first
parameter is a list of tuples each pairing an expression to evaluate with the encoding
if that expression is |
ADFormat Text | Formatting pattern for descriptions. To distinguish between formatting as numeric values and data/time
values, additionally use |
ADFormatAsNum | The marks should be formatted as numbers. Use a
d3 numeric format string
with |
ADFormatAsTemporal | The marks should be formatted as dates or times. Use a
d3 date/time format string
with |
ADFormatAsCustom Text | The custom format type
for use with with |
ADLabelExpr VegaExpr | Provide the expression used to generate labels. |
ADString Text | Literal string value. |
ADTimeUnit TimeUnit | Time unit aggregation of field values when encoding with an Aria description channel. |
ADTitle Text | Title of a field when encoding with an Aria description channel. |
ADNoTitle | Display no title. |
Scaling
Used to specify how the encoding of a data field should be applied. See the Vega-Lite scale documentation.
data ScaleProperty Source #
Individual scale property. These are used to customise an individual scale
transformation. To customise all scales use configure
and supply relevant
ScaleConfig
values. For more details see the
Vega-Lite documentation.
There are two utility routines for constructing a list of scale
properties: categoricalDomainMap
and domainRangeMap
.
The SRangeStep
constructor was removed in version 0.5.0.0
. Users
should use the heightStep
and widthStep
functions instead.
The SReverse
constructor was removed in version 0.4.0.0
, as it
represented a Vega, rather than Vega-Lite, property. The order of
a scale can be changed with the PSort
constructor.
SType Scale | Type of scaling to apply. |
SAlign Double | Alignment of the steps within the scale range. A value of
The input is clamped so that values less than 0 are mapped to 0 and greater than 1 to 1. Since: 0.4.0.0 |
SBase Double | The base to use for log scaling ( Default is Since: 0.4.0.0 |
SBins [Double] | An array of bin boundaries over the scale domain. If give, axes and legends will use these boundaries to inform the choice of tick marks and text labels. Since: 0.4.0.0 |
SClamp Bool | Should values outside the data domain be clamped (to the minimum or maximum value)? |
SConstant Double | The desired slope of the The default is Since: 0.4.0.0 |
SDomain DomainLimits | Custom scaling domain. See also In verson |
SDomainMid Double | Set the mid-point of a continuous diverging domain. This is deprecated as of 0.11.0.0 and Since: 0.6.0.0 |
SDomainOpt ScaleDomain | Custom scaling domain. See also Since: 0.11.0.0 |
SExponent Double | The exponent to use for power scaling ( Since: 0.4.0.0 |
SInterpolate CInterpolate | Interpolation method for scaling range values. |
SNice ScaleNice | "Nice" minimum and maximum values in a scaling (e.g. multiples of 10). |
SPadding Double | Padding in pixels to apply to a scaling. |
SPaddingInner Double | Inner padding to apply to a band scaling. |
SPaddingOuter Double | Outer padding to apply to a band scaling. |
SRange ScaleRange | Range of a scaling. The type of range depends on the encoding channel. |
SReverse Bool | Should the order of the scale range be reversed? Since: 0.6.0.0 |
SRound Bool | Are numeric values in a scaling rounded to integers? The default is |
SScheme Text [Double] | Color scheme used by a color scaling. The first parameter is the name of the scheme (e.g. "viridis") and the second an optional specification, which can contain 1, 2, or 3 numbers:
For the full list of supported schemes, please refer to the Vega Scheme reference. The number of colors was broken prior to |
SZero Bool | Should a numeric scaling be forced to include a zero value? Not all scales support |
Used to indicate the type of scale transformation to apply. The Vega-Lite scale documentation defines which of these are for continuous or discrete distributions, and what the defaults are for the combination of data type and encoding channel.
The Scale
type is used with the SType
constructor to set up the scaling properties of an encoding.
Examples:
PScale
[SType
ScTime ]color
[MName
"Acceleration" ,MmType
Quantitative
,MScale
[SType
ScLog,SRange
(RStrings
["yellow", "red"]) ] ]
The ScBinLinear
constructor was removed in 0.8.0.0
because
it was not used by Vega-Lite.
The 0.4.0.0
release removed the ScSequential
constructor, as
ScLinear
should be used instead.
ScLinear | A linear scale. |
ScLog | A log scale. Defaults to log of base 10, but can be customised with
|
ScPow | A power scale. The exponent to use for scaling is specified with
|
ScSqrt | A square-root scale. |
ScSymLog | A symmetrical log (PDF link)
scale. Similar to a log scale but supports zero and negative values. The slope
of the function at zero can be set with | ScIdentity added in Vega-Lite 4.4, no documentation | ScSequential added in Vega-Lite 4.4, no documentation, not clear if any different from linear Since: 0.4.0.0 |
ScTime | A temporal scale. |
ScUtc | A temporal scale, in UTC. |
ScQuantile | A quantile scale. Since: 0.4.0.0 |
ScQuantize | A quantizing scale. Since: 0.4.0.0 |
ScThreshold | A threshold scale. Since: 0.4.0.0 |
ScBinOrdinal | An ordinal band scale. |
ScOrdinal | An ordinal scale. |
ScPoint | A point scale. |
ScBand | A band scale. |
categoricalDomainMap :: [(Text, Color)] -> [ScaleProperty] Source #
Create a set of discrete domain to color mappings suitable for customising categorical
scales. The first item in each tuple should be a domain value and the second the
color value with which it should be associated. It is a convenience function equivalent
to specifying separate SDomain
and SRange
lists and is safer as it guarantees
a one-to-one correspondence between domain and range values.
color
[MName
"weather" ,MmType
Nominal ,MScale
( categoricalDomainMap [ ( "sun", "yellow" ) , ( "rain", "blue" ) , ( "fog", "grey" ) ] ) ]
domainRangeMap :: (Double, Color) -> (Double, Color) -> [ScaleProperty] Source #
Create a pair of continuous domain to color mappings suitable for customising
ordered scales. The first parameter is a tuple representing the mapping of the lowest
numeric value in the domain to its equivalent color; the second tuple the mapping
of the highest numeric value to color. If the domain contains any values between
these lower and upper bounds they are interpolated according to the scale's interpolation
function. This is a convenience function equivalent to specifying separate SDomain
and SRange
lists and is safer as it guarantees a one-to-one correspondence between
domain and range values.
color
[MName
"year" ,MmType
Ordinal
,MScale
(domainRangeMap (1955, "rgb(230,149,156)") (2000, "rgb(145,26,36)")) ]
data ScaleDomain Source #
Describes the scale domain (type of data in scale). For full details see the Vega-Lite documentation.
In 0.11.0.0
the functionality has been split into ScaleDomain
and
DomainLimits
.
DMax Double | Sets the maximum value in the scale domain. It is only intended for scales with a continuous domain. It is supported in Vega-Lite 4.14 and later. Since: 0.11.0.0 |
DMaxTime [DateTime] |
It is supported in Vega-Lite 4.14 and later. Since: 0.11.0.0 |
DMid Double | Sets the mid-point of a continuous diverging domain. It replaces Since: 0.11.0.0 |
DMin Double | Sets the minimum value in the scale domain. It is only intended for scales with a continuous domain. It is supported in Vega-Lite 4.14 and later. Since: 0.11.0.0 |
DMinTime [DateTime] |
It is supported in Vega-Lite 4.14 and later. Since: 0.11.0.0 |
DSelection SelectionLabel | Scale domain based on a named interactive selection.
See also In |
DSelectionField SelectionLabel FieldName | Use the given selection and associated field, when the selection is projected over multiple fields or encodings. Since: 0.7.0.0 |
DSelectionChannel SelectionLabel Channel | Use the given selection and associated encoding, when the selection is projected over multiple fields or encodings. Since: 0.7.0.0 |
DUnionWith DomainLimits | Combine the domain of the data with the provided domain. The following example will use a range of at least 0 to 100, but this will be increased if the data (either initially or via any updates to the Vege-Lite visualization) exceeds this:
Since: 0.6.0.0 |
Unaggregated | Indicate that a domain of aggregated data should be scaled to the domain of the data prior to aggregation. |
data DomainLimits Source #
Represent the range of the domain, which is used by SDomain
and DUnionWith
.
Prior to 0.11.0.0
this was part of ScaleDomain
.
Since: 0.11.0.0
DNumbers [Double] | Numeric values that define a scale domain. It is expected that this contains two values (minimum and maximum), but more can be given for piecewise quantitative scales. |
DStrings [Text] | String values that define a scale domain |
DDateTimes [[DateTime]] | Date-time values that define a scale domain. |
data ScaleRange Source #
Describes a scale range of scale output values. For full details see the Vega-Lite documentation.
For color scales you can also specify a color scheme instead of range.
Any directly specified range for x
and y
channels will be ignored. Range can be customized
via the view's corresponding size
(width
and height
) or via range steps and paddings properties (e.g. SCRangeStep
)
for band and point scales.
RField FieldName | For discrete and discretizing scales, the name if the field to use. For example. if the field "color" contains CSS color names, we can say
It is supported in Vega-Lite 4.14 and later. Since: 0.11.0.0 |
RMax Double | Sets the maximum value in the scale range. It is only intended for scales with a continuous range. It is supported in Vega-Lite 4.14 and later. Since: 0.11.0.0 |
RMin Double | Sets the minimum value in the scale range. It is only intended for scales with a continuous range. It is supported in Vega-Lite 4.14 and later. Since: 0.11.0.0 |
RPair Double Double | The minimum and maximum values. Since: 0.9.0.0 |
RHeight Double | Specify the width as a number and height as the string Since: 0.9.0.0 |
RWidth Double | Specify the height as a number and width as the string Since: 0.9.0.0 |
RNumbers [Double] | For continuous scales, a two-element array indicating minimum and maximum values, or an array with more than two entries for specifying a piecewise scale. Support for the two-element version may be removed (ie this left only for piecewise scales). |
RNumberLists [[Double]] | A scale range comprising of numeric lists, such as custom dash styles for
the Since: 0.6.0.0 |
RStrings [Text] | Text scale range for discrete scales. |
RName Text | Name of a pre-defined named scale range (e.g. "symbol" or "diverging"). |
Describes the way a scale can be rounded to "nice" numbers. For full details see the Vega-Lite documentation.
Prior to version 0.10.0.0
the time units were included in the constructors
for ScaleNice
.
The time intervals that can be rounded to "nice" numbers.
Prior to 0.10.0.0
these were part of ScaleNice
.
NMillisecond | Nice time intervals that try to align with rounded milliseconds. |
NSecond | Nice time intervals that try to align with whole or rounded seconds. |
NMinute | Nice time intervals that try to align with whole or rounded minutes. |
NHour | Nice time intervals that try to align with whole or rounded hours. |
NDay | Nice time intervals that try to align with whole or rounded days. |
NWeek | Nice time intervals that try to align with whole or rounded weeks. |
NMonth | Nice time intervals that try to align with whole or rounded months. |
NYear | Nice time intervals that try to align with whole or rounded years. |
Color scaling
For color interpolation types, see the Vega-Lite continuous scale documentation.
data CInterpolate Source #
Indicates the type of color interpolation to apply, when mapping a data field onto a color scale.
For details see the Vega-Lite documentation.
CubeHelix Double | Cube helix color interpolation for continuous color scales using the given gamma value (anchored at 1). |
CubeHelixLong Double | Long-path cube helix color interpolation for continuous color scales using the given gamma value (anchored at 1). |
Hcl | HCL color interpolation for continuous color scales. |
HclLong | HCL color interpolation in polar coordinate space for continuous color scales. |
Hsl | HSL color interpolation for continuous color scales. |
HslLong | HSL color interpolation in polar coordinate space for continuous color scales. |
Lab | Lab color interpolation for continuous color scales. |
Rgb Double | RGB color interpolation for continuous color scales using the given gamma value (anchored at 1). |
Creating view compositions
Views can be combined to create more complex multiview displays. This may involve
layering views on top of each other (superposition) or laying them out in adjacent
spaces (juxtaposition using repeat
, repeatFlow
, facet
, facetFlow
,
vlConcat
, hConcat
, or vConcat
). Where different views have potentially conflicting
channels (for example, two position scales in a layered visualization) the rules for
resolving them can be defined with resolve
. For details of creating composite views see the
Vega-Lite documentation.
layer :: [VLSpec] -> PropertySpec Source #
Assigns a list of specifications to superposed layers in a visualization.
toVegaLite
[dataFromUrl
"data/driving.json" [], layer [spec1, spec2]]
A complete example showing layer
in use:
let dvals =dataFromColumns
[] .dataColumn
"x" (Numbers
[1, 2, 3, 4, 5]) .dataColumn
"a" (Numbers
[28, 91, 43, 55, 81]) enc =encoding
.position
X
[PName
"x",PmType
Ordinal
] .position
Y
[PName
"a",PmType
Quantitative
] .text
[TName
"a",TmType
Nominal
] intoVegaLite
[ dvals [] , enc [] ,layer
[asSpec
[mark
Bar
[]] ,asSpec
[mark
Text
[MdY
(-8)]] ] ]
vlConcat :: [VLSpec] -> PropertySpec Source #
The list of specifications to be juxtaposed horizontally in a flow
layout of views.
See also hConcat
and vConcat
.
The number of columns in the flow layout can be set with columns
and, if not specified, will default to a single row of unlimited columns.
let dvals =dataSequenceAs
0 6.28 0.1 "x" trans =transform
.calculateAs
"sin(datum.x)" "sinX" .calculateAs
"cos(datum.x)" "cosX" enc =encoding
.position
X
[PName
"x",PmType
Quantitative
] encCos = enc .position
Y
[PName
"cosX",PmType
Quantitative
] encSin = enc .position
Y
[PName
"sinX",PmType
Quantitative
] in toVegaLite [ dvals , trans [] ,vlConcat
[asSpec
[encCos [],mark
Line
[]] ,asSpec
[encSin [],mark
Line
[]] ] ]
This is named concat
in Elm VegaLite but has been renamed here
to avoid conflicting with the Prelude.
Since: 0.4.0.0
:: Natural | A value of 0 means that a single row will be used (which is also the default behavior). |
-> PropertySpec |
The maximum number of columns to include in a view composition flow
layout. If the number of faceted small multiples exceeds this number,
flow moves to the next row. Only applies to flow layouts generated by
vlConcat
, facetFlow
, and repeatFlow
.
Since: 0.4.0.0
hConcat :: [VLSpec] -> PropertySpec Source #
Assigns a list of specifications to be juxtaposed horizontally in a visualization.
See also vConcat
and vlConcat
.
toVegaLite
[dataFromUrl
"data/driving.json" [] , hConcat [ spec1, spec2 ] ]
vConcat :: [VLSpec] -> PropertySpec Source #
Assigns a list of specifications to be juxtaposed vertically in a visualization.
See also hConcat
and vlConcat
.
toVegaLite
[dataFromUrl
"data/driving.json" [] ,vConcat
[ spec1, spec2 ] ]
align :: CompositionAlignment -> PropertySpec Source #
Alignment to apply to grid rows and columns generated by a composition operator. This version sets the same alignment for rows and columns.
See also alignRC
.
Since: 0.4.0.0
:: CompositionAlignment | Row alignment |
-> CompositionAlignment | Column alignment |
-> PropertySpec |
:: Double | Spacing in pixels. |
-> PropertySpec |
:: Double | Spacing between rows (in pixels). |
-> Double | Spacing between columns (in pixels). |
-> PropertySpec |
center :: Bool -> PropertySpec Source #
Are sub-views in a composition operator centred relative to their respective rows and columns?
See also centerRC
.
Since: 0.4.0.0
:: Bool | Are rows to be centered? |
-> Bool | Are columns to be centered? |
-> PropertySpec |
Are sub-views in a composition operator centred relative to their respective rows and columns?
See also center
.
Since: 0.4.0.0
bounds :: Bounds -> PropertySpec Source #
Bounds calculation method to use for determining the extent of a sub-plot in a composed view.
Since: 0.4.0.0
This is used with bounds
to define the extent of a sub plot.
Since: 0.4.0.0
data CompositionAlignment Source #
Specifies the alignment of compositions. It is used with:
align
, alignRC
,
LeGridAlign
, LGridAlign
,
and FAlign
.
Since: 0.4.0.0
Resolution
Control the independence between composed views.
See the Vega-Lite resolve documentation.
:: [ResolveSpec] | The arguments created by Prior to |
-> PropertySpec |
Determine whether scales, axes or legends in composite views should share channel encodings. This allows, for example, two different color encodings to be created in a layered view, which otherwise by default would share color channels between layers. Each resolution rule should be in a tuple pairing the channel to which it applies and the rule type.
let res =resolve
.resolution
(RLegend
[(ChColor
,Independent
)]) intoVegaLite
[dataFromUrl
"data/movies.json" [] ,vConcat
[heatSpec, barSpec] , res [] ]
For more information see the Vega-Lite documentation.
let dvals =dataFromColumns
[] .dataColumn
"x" (Numbers
[1, 2, 3, 4, 5]) .dataColumn
"a" (Numbers
[28, 91, 43, 55, 81]) .dataColumn
"b" (Numbers
[17, 22, 28, 30, 40]) encBar =encoding
.position
X
[PName
"x",PmType
Quantitative
] .position
Y
[PName
"a",PmType
Quantitative
] specBar =asSpec
[mark
Bar
[], encBar []] encLine =encoding
.position
X
[PName
"x",PmType
Quantitative
] .position
Y
[PName
"b",PmType
Quantitative
] specLine =asSpec
[mark
Line
[MColor
"firebrick"], encLine []] res =resolve
.resolution
(RScale
[(ChY
,Independent
)]) intoVegaLite
[dvals [], res [],layer
[specBar, specLine]]
:: Resolve | |
-> BuildResolveSpecs | Prior to |
Define a single resolution option to be applied when scales, axes or legends in composite views share channel encodings. This allows, for example, two different color encodings to be created in a layered view, which otherwise by default would share color channels between layers. Each resolution rule should be in a tuple pairing the channel to which it applies and the rule type.
resolve
. resolution (RScale
[ (ChY
,Independent
) ])
Used to determine how a channel's axis, scale or legend domains should be resolved if defined in more than one view in a composite visualization. See the Vega-Lite documentation for details.
RAxis [(Channel, Resolution)] | |
RLegend [(Channel, Resolution)] | |
RScale [(Channel, Resolution)] |
Indicates a channel type to be used in a resolution specification.
Used with the Resolve
type and the
BLChannel
, BLChannelEvent
,
ByChannel
, and Encodings
constructors.
Changed in 0.7.0.0
: the ChTooltip
channel was removed as it was
dropped in Vega-Lite 4.0.
ChX | |
ChY | |
ChX2 | |
ChY2 | |
ChLongitude | Since: 0.4.0.0 |
ChLongitude2 | Since: 0.4.0.0 |
ChLatitude | Since: 0.4.0.0 |
ChLatitude2 | Since: 0.4.0.0 |
ChAngle | Since: 0.9.0.0 |
ChTheta | Since: 0.9.0.0 |
ChTheta2 | Since: 0.9.0.0 |
ChRadius | Since: 0.9.0.0 |
ChRadius2 | Since: 0.9.0.0 |
ChColor | |
ChFill | Since: 0.3.0.0 |
ChFillOpacity | Since: 0.4.0.0 |
ChHref | Since: 0.4.0.0 |
ChKey | Since: 0.4.0.0 |
ChOpacity | |
ChShape | |
ChSize | |
ChStroke | Since: 0.3.0.0 |
ChStrokeDash | Since: 0.6.0.0 |
ChStrokeOpacity | Since: 0.4.0.0 |
ChStrokeWidth | Since: 0.4.0.0 |
ChText | Since: 0.4.0.0 |
ChDescription | Since: 0.9.0.0 |
ChURL | Since: 0.9.0.0 |
data Resolution Source #
Indicates whether or not a scale domain should be independent of others in a composite visualization. See the Vega-Lite documentation for details.
For use with Resolve
.
Faceted views
These are small multiples each of which show subsets of the same dataset. The specification determines which field should be used to determine subsets along with their spatial arrangement (in rows or columns). For details see the Vega-Lite documentation.
repeat :: [RepeatFields] -> PropertySpec Source #
Define the fields that will be used to compose rows and columns of a
set of small multiples. This is used where the encoding of the
visualization in small multiples is largely identical, but the data
field used in each might vary. When a list of fields is identified
with repeat
you also need to define a full specification to apply to
each of those fields using asSpec
.
Unlike faceting, which creates multiple charts based on different values of a single field, repeating uses a different field for each chart.
See the Vega-Lite documentation for further details.
toVegaLite
[repeat
[ColumnFields
["Cat", "Dog", "Fish"]] ,specification
(asSpec
spec) ]
See also repeatFlow
.
repeatFlow :: [FieldName] -> PropertySpec Source #
Define the fields that will be used to compose a flow layout of a set of
small multiples. Used when the encoding is largely identical, but the data field
used in each might vary. When a list of fields is identified with repeatFlow
you also
need to define a full specification to apply to each of those fields using asSpec
.
Small multiples will be laid out from left to right, moving on to new rows only
if the number of plots exceeds an optional column limit (specified via columns
).
toVegaLite
[repeatFlow
[ "Cat", "Dog", "Fish" ] ,specification
(asSpec
spec) ]
See also repeat
.
Since: 0.4.0.0
data RepeatFields Source #
Create a list of fields to use in set of repeated small multiples. The list of
fields named here can be referenced in an encoding with
or PRepeat
Column
.PRepeat
Row
RowFields [FieldName] | |
ColumnFields [FieldName] | |
LayerFields [FieldName] | Since: 0.9.0.0 |
facet :: [FacetMapping] -> PropertySpec Source #
Defines the fields that will be used to facet a view in rows or columns to create
a set of small multiples. This is used where the encoding of the visualization in small
multiples is identical, but data for each is grouped by the given fields. When
creating a faceted view in this way you also need to define a full specification
to apply to each of those facets using asSpec
.
See the Vega-Lite documentation for further details.
toVegaLite
[ facet [RowBy
[FName
"Month",FmType
Ordinal
] ,ColumnBy
[FName
"Week",FmType
Ordinal
] ] ,specification
spec ]
See also facetFlow
.
facetFlow :: [FacetChannel] -> PropertySpec Source #
Facet a view to create small multiples in a flow layout. Used when the encoding
of the visualization in small multiples is identical, but data for each is grouped
by the given fields. When creating a faceted view in this way you also need to
define a full specification to apply to each of those facets using asSpec
.
Small multiples will be laid out from left to right, moving on to new rows only
if the number of plots exceeds an optional column limit (specified via columns
).
toVegaLite
[ facetFlow [FName
"Origin",FmType
Nominal
] ,specification
spec ]
See also facet
.
Since: 0.4.0.0
data FacetMapping Source #
Provides details of the mapping between a row or column and its field definitions in a set of faceted small multiples. For details see the Vega-Lite documentation.
data FacetChannel Source #
Types of facet channel property used for creating a composed facet view of small multiples.
FName FieldName | The name of the field from which to pull a data value. |
FmType Measurement | The encoded field's type of measurement. |
FAggregate Operation | Aggregation function for the field. |
FAlign CompositionAlignment | The alignment to apply to the row- or column- facet's subplot. Since: 0.6.0.0 |
FBin [BinProperty] | Describe how to bin quantitative fields, or whether the channels are already binned. |
FCenter Bool | Should sub-views be centered relative to their respective rows or columns. Since: 0.6.0.0 |
FHeader [HeaderProperty] | The properties of a facet's header. |
FSort [SortProperty] | Sort order for the encoded field. Since: 0.4.0.0 |
FSpacing Double | The pixel spacing between sub-views. If you have code from a version of Since: 0.6.0.0 |
FTimeUnit TimeUnit | The time-unit for a temporal field. |
FTitle Text | The title for the field. Since: 0.4.0.0 |
FNoTitle | Draw no title. Since: 0.4.0.0 |
asSpec :: [PropertySpec] -> VLSpec Source #
Create a specification sufficient to define an element in a composed visualization such as a superposed layer or juxtaposed facet. Typically a layer will contain a full set of specifications that define a visualization with the exception of the data specification which is usually defined outside of any one layer. Whereas for repeated and faceted specs, the entire specification is provided.
spec1 = asSpec [ enc1 [],mark
Line
[] ]
specification :: VLSpec -> PropertySpec Source #
Defines a specification object for use with faceted and repeated small multiples.
toVegaLite
[facet
[RowBy
[FName
"Origin",FmType
Nominal
] ] ,specification
spec ]
data Arrangement Source #
Facet Headers
See the Vega-Lite header documentation.
data HeaderProperty Source #
Represents a facet header property. For details, see the Vega-Lite documentation.
Labels refer to the title of each sub-plot in a faceted view and title is the overall title of the collection.
HFormat Text | Formatting pattern for
facet header (title) values. To distinguish between formatting as numeric values
and data/time values, additionally use |
HFormatAsNum | Facet headers should be formatted as numbers. Use a
d3 numeric format string
with Since: 0.4.0.0 |
HFormatAsTemporal | Facet headers should be formatted as dates or times. Use a
d3 date/time format string
with Since: 0.4.0.0 |
HFormatAsCustom Text | The custom format type
for use with with Since: 0.9.0.0 |
HLabel Bool | Should labels be included as part of the header. The default is Since: 0.6.0.0 |
HLabelAlign HAlign | The horizontal alignment of the labels. Since: 0.4.0.0 |
HLabelAnchor APosition | The anchor position for the labels. Since: 0.4.0.0 |
HLabelAngle Angle | The angle to draw the labels. The default is 0 for column headers and -90 for row headers. Since: 0.4.0.0 |
HLabelBaseline VAlign | The vertical text baseline for header labels. The default is
Added in Vega-Lite 4.8.0. Since: 0.8.0.0 |
HLabelColor Color | The color of the labels. Since: 0.4.0.0 |
HLabelExpr VegaExpr | The expression used to generate header labels. The expression can use Since: 0.6.0.0 |
HLabelFont Text | The font for the labels. Since: 0.4.0.0 |
HLabelFontSize Double | The font size for the labels. Since: 0.4.0.0 |
HLabelFontStyle Text | The font style for the labels. Since: 0.6.0.0 |
HLabelFontWeight FontWeight | The font weight for the header label. Added in Vega-Lite 4.8.0. Since: 0.8.0.0 |
HLabelLimit Double | The maximum length of each label. Since: 0.4.0.0 |
HLabelLineHeight Double | The line height, in pixels, for multi-line header labels, or
title text with baselines of Added in Vega-Lite 4.8.0. Since: 0.8.0.0 |
HLabelOrient Side | The position of the label relative to its sub-plot. See also
Since: 0.4.0.0 |
HLabelPadding Double | The spacing in pixels between the label and its sub-plot. Since: 0.4.0.0 |
HOrient Side | A shortcut for setting both Since Vega-Lite 4.8. Since: 0.8.0.0 |
HTitle Text | The title for the facets. |
HNoTitle | Draw no title for the facets. Since: 0.4.0.0 |
HTitleAlign HAlign | The horizontal alignment of the title. Since: 0.4.0.0 |
HTitleAnchor APosition | The anchor position for the title. Since: 0.4.0.0 |
HTitleAngle Angle | The angle to draw the title. Since: 0.4.0.0 |
HTitleBaseline VAlign | The vertical alignment of the title. Since: 0.4.0.0 |
HTitleColor Color | The color of the title. Since: 0.4.0.0 |
HTitleFont Text | The font for the title. Since: 0.4.0.0 |
HTitleFontSize Double | The font size for the title. Since: 0.4.0.0 |
HTitleFontStyle Text | The font style for the title. Since: 0.6.0.0 |
HTitleFontWeight FontWeight | The font weight for the title. The argument changed from Since: 0.4.0.0 |
HTitleLimit Double | The maximum length of the title. Since: 0.4.0.0 |
HTitleLineHeight Double | The line height, in pixels, for multi-line header title text, or
title text with baselines of Since: 0.6.0.0 |
HTitleOrient Side | The position of the title relative to the sub-plots. See also Since: 0.4.0.0 |
HTitlePadding Double | The spacing in pixels between the title and the labels. Since: 0.4.0.0 |
Creating Selections for Interaction
Selections are the way in which interactions (such as clicking or dragging) can be responded to in a visualization. They transform interactions into data queries. For details, see the Vega-Lite documentation.
:: [SelectSpec] | The arguments created by Prior to |
-> PropertySpec |
:: SelectionLabel | The name given to the selection. |
-> Selection | The type of the selection. |
-> [SelectionProperty] | What options are applied to the selection. |
-> BuildSelectSpecs | Prior to |
Indicates the type of selection to be generated by the user.
data SelectionProperty Source #
Properties for customising the nature of the selection. See the Vega-Lite documentation for details.
For use with select
and SelectionStyle
.
Empty | Make a selection empty by default when nothing selected. |
BindScales | Enable two-way binding between a selection and the scales used in the same view. This is commonly used for zooming and panning by binding selection to position scaling: sel = |
BindLegend BindLegendProperty | Enable binding between a legend selection and the item it references. This is only applicable to categorical (symbol) legends. The following will allow the "crimeType" legend to be selected:
Use
Since: 0.5.0.0 |
On Text | Vega event stream selector that triggers a selection, or the empty string (which sets the property to |
Clear Text | Vega event stream selector that can clear a selection. For example, to allow a zoomed/panned view to be reset on shift-click:
To remove the default clearing behaviour of a selection, provide an empty string rather than an event stream selector. Since: 0.4.0.0 |
Translate Text | Translation selection transformation used for panning a view. See the Vega-Lite translate documentation. |
Zoom Text | Zooming selection transformation used for zooming a view. See the Vega-Lite zoom documentation. |
Fields [FieldName] | Field names for projecting a selection. |
Encodings [Channel] | Encoding channels that form a named selection. For example, to project a selection across all items that share the same value in the color channel: sel = |
SInit [(FieldName, DataValue)] | Initialise one or more selections with values from bound fields.
See also For example,
Since: 0.4.0.0 |
SInitInterval (Maybe (DataValue, DataValue)) (Maybe (DataValue, DataValue)) | Initialize the domain extent of an interval selection. See
also The parameters refer to the x and y axes, given in the order
Since: 0.4.0.0 |
ResolveSelections SelectionResolution | Strategy that determines how selections' data queries are resolved when applied in a filter transform, conditional encoding rule, or scale domain. |
SelectionMark [SelectionMarkProperty] | Appearance of an interval selection mark (dragged rectangle). |
Bind [Binding] | Binding to some input elements as part of a named selection. The followig example allows a selection to be based on a drop-down list of options: sel = |
Nearest Bool | Whether or not a selection should capture nearest marks to a pointer rather than an exact position match. |
Toggle Text | Predicate expression that determines a toggled selection. See the Vega-Lite toggle documentation. |
Describes the binding property of a selection based on some HTML input element such as a checkbox or radio button. For details see the Vega-Lite documentation and the Vega input binding documentation.
IRange Text [InputProperty] | Range slider input element that can bound to a named field value. |
ICheckbox Text [InputProperty] | Checkbox input element that can bound to a named field value. |
IRadio Text [InputProperty] | Radio box input element that can bound to a named field value. |
ISelect Text [InputProperty] | Select input element that can bound to a named field value. |
IText Text [InputProperty] | Text input element that can bound to a named field value. |
INumber Text [InputProperty] | Number input element that can bound to a named field value. |
IDate Text [InputProperty] | Date input element that can bound to a named field value. |
ITime Text [InputProperty] | Time input element that can bound to a named field value. |
IMonth Text [InputProperty] | Month input element that can bound to a named field value. |
IWeek Text [InputProperty] | Week input element that can bound to a named field value. |
IDateTimeLocal Text [InputProperty] | Local time input element that can bound to a named field value. |
ITel Text [InputProperty] | Telephone number input element that can bound to a named field value. |
IColor Text [InputProperty] | Color input element that can bound to a named field value. |
data BindLegendProperty Source #
Control the interactivity of the legend. This is used with BindLegend
.
Since: 0.5.0.0
BLField FieldName | The data field which should be made interactive in the legend on a single click. |
BLChannel Channel | Which channel should be made interactive in a legend on a single click. |
BLFieldEvent FieldName Text | The data field which should be made interactive in the legend and the Vega event stream that should trigger the selection. |
BLChannelEvent Channel Text | Which channel should be made interactive in a legend and the Vega event stream that should trigger the selection. |
data InputProperty Source #
GUI Input properties. The type of relevant property will depend on the type of
input element selected. For example an InRange
(slider) can have numeric min,
max and step values; InSelect
(selector) has a list of selection label options.
For details see the
Vega input element binding documentation.
Debounce Double | The delay to introduce when processing input events to avoid unnescessary event broadcasting. |
Element Text | CSS selector indicating the parent element to which an input element should be added. This allows for interacting with elements outside the visualization container. |
InOptions [Text] | The options for a radio or select input element. |
InMin Double | The minimum slider value for a range input element. |
InMax Double | The maximum slider value for a range input element. |
InName Text | Custom label for a radio or select input element. |
InStep Double | The minimum increment for a range sliders. |
InPlaceholder Text | The initial text for input elements such as text fields. |
data SelectionMarkProperty Source #
Properties for customising the appearance of an interval selection mark (a dragged rectangle). For details see the Vega-Lite documentation.
SMCursor Cursor | Cursor type to appear when pointer is over an interval selection mark (dragged rectangular area). Since: 0.6.0.0 |
SMFill Color | Fill color. |
SMFillOpacity Opacity | Fill opacity. |
SMStroke Color | The stroke color. |
SMStrokeOpacity Opacity | The stroke opacity. |
SMStrokeWidth Double | The line width of the stroke. |
SMStrokeDash DashStyle | The dash pattern for the stroke. |
SMStrokeDashOffset DashOffset | The offset at which to start the dash pattern. |
Selection Resolution
Determines how selections are made across multiple views. See the Vega-lite resolve selection documentation.
data SelectionResolution Source #
Determines how selections in faceted or repeated views are resolved. See the Vega-Lite documentation for details.
For use with ResolveSelections
.
Global | One selection available across all subviews (default). |
Union | Each subview contains its own brush and marks are selected if they lie within any of these individual selections. |
Intersection | Each subview contains its own brush and marks are selected if they lie within all of these individual selections. |
Making conditional channel encodings
To make channel encoding conditional on the result of some interaction, use
MSelectionCondition
, TSelectionCondition
, or HSelectionCondition
. Similarly
MDataCondition
, TDataCondition
, or HDataCondition
will encode a mark
conditionally depending on some data properties such as whether a datum is null
or an outlier.
For interaction, once a selection has been defined and named, supplying a set of
encodings allow mark encodings to become dependent on that selection.
MSelectionCondition
is followed firstly a (Boolean) selection and then an
encoding if that selection is true and another encoding to be applied if it is false.
The color specification below states "whenever data marks are selected with an
interval mouse drag, encode the cylinder field with an ordinal color scheme,
otherwise make them grey":
sel =selection
.select
"myBrush"Interval
[] enc =encoding
.position
X
[PName
"Horsepower",PmType
Quantitative
] .position
Y
[PName
"Miles_per_Gallon",PmType
Quantitative ] .color
[MSelectionCondition
(SelectionName
"myBrush") [MName
"Cylinders",MmType
Ordinal
] [MString
"grey" ] ]
In a similar way, MDataCondition
will encode a mark depending on whether any
predicate tests are satisfied. Unlike selections, multiple conditions and associated
encodings can be specified. Each test condition is evaluated in order and only on
failure of the test does encoding proceed to the next test. If no tests are true,
the encoding in the final parameter is applied in a similar way to case of
expressions:
enc =encoding
.position
X
[PName
"value",PmType
Quantitative
] .color
[MDataCondition
[ (Expr
"datum.value < 40", [MString
"blue" ] ) , (Expr
"datum.value < 50", [MString
"red" ] ) , (Expr
"datum.value < 60", [MString
"yellow" ] ) ] [MString
"black" ] ]
For more details, see the Vega-Lite documentation.
Used for creating logical compositions. For example
color
[MSelectionCondition
(Or (SelectionName
"alex") (SelectionName "morgan")) [MAggregate
Count
,MName
"*",MmType
Quantitative
] [MString
"gray"] ]
Logical compositions can be nested to any level as shown in this example
Not
(And
(Expr
"datum.IMDB_Rating === null") (Expr
"datum.Rotten_Tomatoes_Rating === null") )
Expr VegaExpr | Expression that should evaluate to either true or false. |
FilterOp Filter | Convert a For example (using trans = Since: 0.4.0.0 |
FilterOpTrans MarkChannel Filter | Combine a data-transformation operation with a filter before
converting into a boolean operation. This can be useful when
working with dates, such as the following exampe, which aggregates
a set of dates into years, and filters only those years between
2010 and 2017 (inclusive). The final expression is converted
back into a
Since: 0.4.0.0 |
Selection SelectionLabel | Interactive selection that will be true or false as part of a logical composition. For example: to filter a dataset so that only items selected interactively and that have a weight of more than 30:
|
SelectionName SelectionLabel | Name a selection that is used as part of a conditional encoding.
|
And BooleanOp BooleanOp | Apply an 'and' Boolean operation as part of a logical composition.
|
Or BooleanOp BooleanOp | Apply an 'or' Boolean operation as part of a logical composition. |
Not BooleanOp | Negate the given expression.
|
Top-level Settings
These are in addition to the data and transform options described above, and are described in the Vega-Lite top-level spec documentation.
name :: Text -> PropertySpec Source #
Provides an optional name to be associated with the visualization.
toVegaLite
[name
"PopGrowth" ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] , enc [] ]
description :: Text -> PropertySpec Source #
Provides an optional description to be associated with the visualization.
toVegaLite
[description
"Population change of key regions since 1900" ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] , enc [] ]
height :: Double -> PropertySpec Source #
Overrides the default height of the visualization. If not specified the height
will be calculated based on the content of the visualization. See
autosize
for customization of the content sizing relative to this
setting, heightOfContainer
for setting the height to that of
the surrounding container,
and heightStep
for setting the height of discrete fields.
toVegaLite
[height
300 ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] , enc [] ]
heightOfContainer :: PropertySpec Source #
Set the height of the view to that of the surrounding container, to allow for responsive sizing.
Please see the Vega Lite responsive sizing documentation for caveats and limitations.
Since: 0.5.0.0
heightStep :: Double -> PropertySpec Source #
Set the height of the discrete y-field (e.g. individual bars in a horizontal bar chart). The total height is then calculated based on the number of discrete fields (e.g. bars).
toVegaLite
[heightStep
17 , data [] , enc [] ,mark
Bar
[] ]
This replaces the use of SRangeStep
from ScaleProperty
.
Since: 0.5.0.0
width :: Double -> PropertySpec Source #
Override the default width of the visualization. If not specified the width
will be calculated based on the content of the visualization. See
autosize
for customization of the content sizing relative to this
setting, widthOfContainer
for setting the width to that of
the surrounding container,
and widthStep
for setting the width of discrete fields.
toVegaLite
[width
500 ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] , enc [] ]
widthOfContainer :: PropertySpec Source #
Set the width of the view to that of the surrounding container, to allow for responsive sizing.
Please see the Vega Lite responsive sizing documentation for caveats and limitations.
Since: 0.5.0.0
widthStep :: Double -> PropertySpec Source #
Set the width of the discrete x-field (e.g. individual bars in a bar chart). The total width is then calculated based on the number of discrete fields (e.g. bars).
toVegaLite
[widthStep
17 , data [] , enc [] ,mark
Bar
[] ]
This replaces the use of SRangeStep
from ScaleProperty
.
Since: 0.5.0.0
padding :: Padding -> PropertySpec Source #
Set the padding around the visualization in pixel units. The way padding is
interpreted will depend on the autosize
properties. See the
Vega-Lite documentation
for details.
toVegaLite
[width
500 ,padding
(PEdges
20 10 5 15) ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] , enc [] ]
autosize :: [Autosize] -> PropertySpec Source #
Declare the way the view is sized. See the Vega-Lite documentation for details.
toVegaLite
[width
250 ,height
300 ,autosize
[AFit
,APadding
,AResize
] ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] , enc [] ]
:: Color | The background color. For example, This was changed to use the |
-> PropertySpec |
Set the background color of the visualization. If not specified the background will be white.
toVegaLite
[background
"rgb(251,247,238)" ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] , enc [] ]
:: Object | The metadata is passed around but ignored by VegaLite. |
-> PropertySpec |
Optional metadata.
Since: 0.4.0.0
Specify the padding dimensions in pixel units.
Indicates the auto-sizing characteristics of the visualization such as amount of padding, whether it should fill the parent container etc. For more details see the Vega-Lite documentation.
AContent | Interpret visualization dimensions to be for the data rectangle (external padding added to this size). |
AFit | Interpret visualization dimensions to be for the entire visualization (data rectangle is shrunk to accommodate external decorations padding). |
AFitX | Interpret visualization width to be for the entire visualization width (data rectangle width is shrunk to accommodate external decorations padding). Since: 0.5.0.0 |
AFitY | Interpret visualization height to be for the entire visualization height (data rectangle height is shrunk to accommodate external decorations padding). Since: 0.5.0.0 |
ANone | No autosizing is applied. |
APad | Automatically expand size of visualization from the given dimensions in order to fit in all supplementary decorations (legends etc.). |
APadding | Interpret visualization width to be for the entire visualization (data rectangle is shrunk to accommodate external padding). |
AResize | Recalculate autosizing on every view update. |
Title
Per-title settings. Use TitleStyle
to change the appearance of all
titles in a multi-view specification.
:: Text | The title. Any In version |
-> [TitleConfig] | Configure the appearance of the title. Since: 0.4.0.0 |
-> PropertySpec |
Provide an optional title to be displayed in the visualization.
toVegaLite
[title
"Population Growth" [TColor
"orange"] ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] ,encoding
... ]
Prior to 0.4.0.0
there was no way to set the title options
(other than using configuration
with TitleStyle
).
View Backgroud
The background of a single view in a view composition can be styled independently of other views. For more details see the Vega-Lite view background documentation.
viewBackground :: [ViewBackground] -> PropertySpec Source #
The background style of a single view or layer in a view composition.
Since: 0.4.0.0
data ViewBackground Source #
The properties for a single view or layer background.
Used with viewBackground
and
ViewBackgroundStyle
.
In version 0.6.0.0
the constructors that used to take an optional color,
namely VBFill
and VBStroke
, were split out, so that they
now take a Color
argument and new constructors - VBNoFill
and
VBNoStroke
- were added to replace the Nothing
versions.
Since: 0.4.0.0
VBStyle [StyleLabel] | A list of named styles to apply. A named style can be specified
via |
VBCornerRadius Double | The radius in pixels of rounded corners. |
VBFill Color | Fill color. See also This was changed to use the |
VBNoFill | Do not use a fill. See also Since: 0.6.0.0 |
VBFillOpacity Opacity | Fill opacity. |
VBOpacity Opacity | Overall opacity. |
VBStroke Color | The stroke color for a line around the background. See also This was changed to use the |
VBNoStroke | Do not use a stroke. See also Since: 0.6.0.0 |
VBStrokeOpacity Opacity | The opacity of the line around the background, if drawn. |
VBStrokeWidth Double | The width of the line around the background, if drawn. |
VBStrokeCap StrokeCap | The cap line-ending for the line around the background, if drawn. |
VBStrokeDash DashStyle | The dash pattern of the line around the background, if drawn. |
VBStrokeDashOffset DashOffset | The offset of the dash pattern for the line around the background, if drawn. |
VBStrokeJoin StrokeJoin | The line-joining style of the line around the background, if drawn. |
VBStrokeMiterLimit Double | The mitre limit at which to bevel the line around the background, if drawn. |
Style Setting
In version 0.5.0.0
the ConfigureSpec
type was introduced to
make it clear that only configuration
should be used with
configure
.
:: [ConfigureSpec] | The configuration options, created with Prior to version |
-> PropertySpec |
Create a single global configuration from a list of configuration specifications. Configurations are applied to all relevant items in the specification. See the Vega-Lite documentation for more details.
The following example would make axis lines (domain) 2 pixels wide, remove the border rectangle and require interactive selection of items to use a double-click:
config =configure
.configuration
(Axis
[DomainWidth
1 ]) .configuration
(ViewStyle
[ViewStroke
"transparent" ]) .configuration
(SelectionStyle
[ (Single
, [On
"dblclick" ] ) ])
:: ConfigurationProperty | |
-> BuildConfigureSpecs | Prior to version |
Defines a single configuration option to be applied globally across the visualization. The first parameter identifies the type of configuration, the second a list of previous configurations to which this one may be added.
The result should be used with configure
.
configuration
(Axis
[DomainWidth
4 ]) []
data ConfigurationProperty Source #
Type of configuration property to customise. See the Vega-Lite documentation for details. There are multiple ways to configure the properties of an axis, as discussed in the Vega-Lite axis configuration documentation.
Used by configuration
.
In version 0.7.0.0
, the AxisBand
, AxisDiscrete
, AxisPoint
,
AxisQuantitative
, and AxisTemporal
were changed to accept an
additional argument (AxisChoice
), to define which axis the configuration
should be applied to.
In version 0.6.0.0
:
- the
Autosize
,Background
,CountTitle
,FieldTitle
,Legend
,NumberFormat
,Padding
,Projection
,Range
,Scale
.TimeFormat
, andView
constructors have been deprecated, and should be replaced byAutosizeStyle
,BackgroundStyle
,CountTitleStyle
,FieldTitleStyle
,LegendStyle
,NumberFormatStyle
,PaddingStyle
,ProjectionStyle
,RangeStyle
,ScaleStyle
,TimeFormatStyle
, andViewStyle
respectively. The axis configuration options have not been updated to this system. - new constructors have been added:
AxisDiscrete
,AxisPoint
,AxisQuantitative
,AxisTemporal
,BoxplotStyle
,ErrorBandStyle
,ErrorBarStyle
,HeaderColumnStyle
,HeaderFacetStyle
,HeaderRowStyle
,ImageStyle
, andRepeatStyle
. ConcatStyle
andFacetStyle
now take a common type,CompositionConfig
, rather thanConcatConfig
andFacetStyle
.
In version 0.5.0.0
:
- the
RemoveInvalid
constructor was removed, as the newMRemoveInvalid
constructor for theMarkProperty
type should be used instead (so
changes toconfiguration
(RemoveInvalid b)
.configuration
(MarkStyle
[MRemoveInvalid
b]) - the
Stack
constructor (which was calledStackProperty
prior to version0.4.0.0
) was removed.
ArcStyle [MarkProperty] | The default appearance of arc marks. Since: 0.9.0.0 |
AreaStyle [MarkProperty] | The default appearance of area marks. |
AriaStyle Bool | A boolean flag indicating if ARIA default attributes should be included for marks and guides (SVG output only). If False, the "aria-hidden" attribute will be set for all guides, removing them from the ARIA accessibility tree and Vega-Lite will not generate default descriptions for marks. Default value: True Since: 0.9.0.0 |
AutosizeStyle [Autosize] | The default sizing of visualizations. This was renamed from Since: 0.6.0.0 |
Axis [AxisConfig] | The default appearance of axes. |
AxisBand AxisChoice [AxisConfig] | The default appearance of axes with band scaling. See also |
AxisBottom [AxisConfig] | The default appearance of the bottom-side axes. |
AxisDiscrete AxisChoice [AxisConfig] | The default appearance of axes with point or band scales. See also Since: 0.6.0.0 |
AxisLeft [AxisConfig] | The default appearance of the left-side axes. |
AxisPoint AxisChoice [AxisConfig] | The default appearance of axes with point scales. See also Since: 0.6.0.0 |
AxisQuantitative AxisChoice [AxisConfig] | The default appearance of quantitative axes. Since: 0.6.0.0 |
AxisRight [AxisConfig] | The default appearance of the right-side axes. |
AxisTemporal AxisChoice [AxisConfig] | The default appearance of temporal axes. Since: 0.6.0.0 |
AxisTop [AxisConfig] | The default appearance of the top-side axes. |
AxisX [AxisConfig] | The default appearance of the X axes. |
AxisY [AxisConfig] | The default appearance of the Y axes. |
AxisNamedStyles [(StyleLabel, [AxisProperty])] | Assign a set of axis styles to a label. These labels can then be referred
to when configuring an axis with To customize the style for guides (axes, headers, and legends), Vega-Lite includes the following built-in style names:
Since: 0.6.0.0 |
BackgroundStyle Color | The default background color of visualizations. This was changed to use the This was renamed from Since: 0.6.0.0 |
BarStyle [MarkProperty] | The default appearance of bar marks. |
BoxplotStyle [MarkProperty] | The default appearance for box plots. Since: 0.6.0.0 |
CircleStyle [MarkProperty] | The default appearance of circle marks. |
ConcatStyle [CompositionConfig] | The default appearance for all concatenation and repeat view
composition operators ( In Vega-Lite 4.8 changed this field to also control repeat-view
operators (which previously had used Since: 0.4.0.0 |
CountTitleStyle Text | The default axis and legend title for count fields. The default is
This was renamed from Since: 0.6.0.0 |
CustomFormatStyle Bool | Allow the "formatType" property for text marks and guides to accept a custom formatter function registered as a Vega Expression. Since: 0.9.0.0 |
ErrorBandStyle [MarkProperty] | The default appearance for error bands. Since: 0.6.0.0 |
ErrorBarStyle [MarkProperty] | The default appearance for error bars. Since: 0.6.0.0 |
FacetStyle [CompositionConfig] | The default appearance of facet layouts. In Since: 0.4.0.0 |
FieldTitleStyle FieldTitleProperty | The default title-generation style for fields. This was renamed from Since: 0.6.0.0 |
FontStyle Text | The default font for all text marks, titles, and labels. The naming scheme used here is somewhat unfortunate, as this
is for the name of the font (such as Since: 0.6.0.0 |
GeoshapeStyle [MarkProperty] | The default appearance of geoshape marks. Since: 0.4.0.0 |
HeaderStyle [HeaderProperty] | The default appearance of all headers. Since: 0.4.0.0 |
HeaderColumnStyle [HeaderProperty] | The default appearance for column headers. Since: 0.6.0.0 |
HeaderFacetStyle [HeaderProperty] | The default appearance for non-row and non-column facet headers. Since: 0.6.0.0 |
HeaderRowStyle [HeaderProperty] | The default appearance for row headers. Since: 0.6.0.0 |
ImageStyle [MarkProperty] | The default appearance for images. Since: 0.6.0.0 |
LegendStyle [LegendConfig] | The default appearance of legends. This was renamed from Since: 0.6.0.0 |
LineStyle [MarkProperty] | The default appearance of line marks. |
LineBreakStyle Text | The delimiter, such as a newline character, upon which to break text strings into multiple lines. This can be over-ridden by mark or style configuration settings. Added in Vega-Lite 4.6.0. Since: 0.7.0.0 |
MarkStyle [MarkProperty] | The default mark appearance. |
MarkNamedStyles [(StyleLabel, [MarkProperty])] | Assign a set of mark styles to a label. These labels can then be referred
to when configuring a mark, such as with Since: 0.6.0.0 |
NumberFormatStyle Text | The default number formatting for axis and text labels, using D3's number format pattern. As an example This was renamed from Since: 0.6.0.0 |
PaddingStyle Padding | The default padding in pixels from the edge of the of visualization to the data rectangle. This was renamed from Since: 0.6.0.0 |
PointStyle [MarkProperty] | The default appearance of point marks. |
ProjectionStyle [ProjectionProperty] | The default style of map projections. This was renamed from Since: 0.6.0.0 |
RangeStyle [RangeConfig] | The default range properties used when scaling. This was renamed from Since: 0.6.0.0 |
RectStyle [MarkProperty] | The default appearance of rectangle marks. |
RepeatStyle [CompositionConfig] | The default appearance for the Support for this setting was removed in Vega-Lite 4.8. This
constructor is currently still supported, but will be removed
in a future release. The Since: 0.6.0.0 |
RuleStyle [MarkProperty] | The default appearance of rule marks. |
ScaleStyle [ScaleConfig] | The default properties used when scaling. This was renamed from Since: 0.6.0.0 |
SelectionStyle [(Selection, [SelectionProperty])] | The default appearance of selection marks. |
SquareStyle [MarkProperty] | the default appearance of square marks |
TextStyle [MarkProperty] | The default appearance of text marks. |
TickStyle [MarkProperty] | The default appearance of tick marks. |
TimeFormatStyle Text | The default time format for raw time values (without time units) in text marks, legend labels, and header labels. This does not control the appearance of axis labels. The default is This was renamed from Since: 0.6.0.0 |
TitleStyle [TitleConfig] | The default appearance of visualization titles. |
TrailStyle [MarkProperty] | The default style of trail marks. Since: 0.4.0.0 |
ViewStyle [ViewConfig] | The default properties for single view plots. This was renamed from Since: 0.6.0.0 |
Autosize [Autosize] | Deprecated: Please change Autosize to AutosizeStyle As of version |
Background Color | Deprecated: Please change Background to BackgroundStyle As of version |
CountTitle Text | Deprecated: Please change CountTitle to CountTitleStyle As of version |
FieldTitle FieldTitleProperty | Deprecated: Please change FieldTitle to FieldTitleStyle As of version |
Legend [LegendConfig] | Deprecated: Please change Legend to LegendStyle As of version |
NumberFormat Text | Deprecated: Please change NumberFormat to NumberFormatStyle As of version |
Padding Padding | Deprecated: Please change Padding to PaddingStyle As of version |
Projection [ProjectionProperty] | Deprecated: Please change Projection to ProjectionStyle As of version |
Range [RangeConfig] | Deprecated: Please change Range to RangeStyle As of version |
Scale [ScaleConfig] | Deprecated: Please change Scale to ScaleStyle As of version |
TimeFormat Text | Deprecated: Please change TimeFormat to TimeFormatStyle As of version |
View [ViewConfig] | Deprecated: Please change View to ViewStyle As of version |
NamedStyle StyleLabel [MarkProperty] | Deprecated: Please change Legend to MarkNamedStyles As of version |
NamedStyles [(StyleLabel, [MarkProperty])] | Deprecated: Please change Legend to MarkNamedStyles As of version |
Axis Configuration Options
See the Vega-Lite axis config documentation.
data AxisConfig Source #
Axis configuration options for customising all axes. See the Vega-Lite documentation for more details.
This is used by ConfigurationProperty
.
In 0.5.0.0
the ShortTimeLabels
constructor was removed.
The TitleMaxLength
constructor was removed in release 0.4.0.0
. The
TitleLimit
constructor should be used instead.
Aria Bool | A boolean flag indicating if ARIA attributes should be included (SVG output only). If False, the "aria-hidden" attribute will be set on the output SVG group, removing the axis from the ARIA accessibility tree. Default value: True Since: 0.9.0.0 |
AriaDescription Text | A text description of this axis for ARIA accessibility (SVG output only). If the If the description is unspecified it will be automatically generated. Since: 0.9.0.0 |
AStyle [StyleLabel] | The named styles - generated with Added in Vega-Lite 4.7.0 (although accidentally supported in Since: 0.6.0.0 |
BandPosition Double | The default axis band position. |
Disable Bool | Disable the axis? Added in Vega-Lite 4.8.0. Since: 0.8.0.0 |
Domain Bool | Should the axis domain be displayed? |
DomainCap StrokeCap | The stroke cap for the domain lines' ending style. Since: 0.9.0.0 |
DomainColor Color | The axis domain color. |
DomainDash DashStyle | The dash pattern of the domain. Since: 0.4.0.0 |
DomainDashOffset DashOffset | The offset for the dash pattern. Since: 0.4.0.0 |
DomainOpacity Opacity | The axis domain opacity. Since: 0.4.0.0 |
DomainWidth Double | The width of the axis domain. |
Format Text | Formatting pattern for
axis values. To distinguish between formatting as numeric values
and data/time values, additionally use When used with a custom formatType, this value will be passed as "format" alongside "datum.value" to the registered function. Since: 0.9.0.0 |
FormatAsNum | Facet headers should be formatted as numbers. Use a
d3 numeric format string
with Since: 0.9.0.0 |
FormatAsTemporal | Facet headers should be formatted as dates or times. Use a
d3 date/time format string
with Since: 0.9.0.0 |
FormatAsCustom Text | The custom format type
for use with with Since: 0.9.0.0 |
Grid Bool | Should an axis grid be displayed? |
GridCap StrokeCap | The stroke cap for the grid lines' ending style. Since: 0.9.0.0 |
GridColor Color | The color for the grid. |
GridDash DashStyle | The dash pattern of the grid. |
GridDashOffset DashOffset | The offset for the dash pattern. Since: 0.4.0.0 |
GridOpacity Opacity | The opacity of the grid. |
GridWidth Double | The width of the grid lines. |
Labels Bool | Should labels be added to an axis? |
LabelAlign HAlign | The horizontal alignment for labels. Since: 0.4.0.0 |
LabelAngle Angle | The angle at which to draw labels. |
LabelBaseline VAlign | The vertical alignment for labels. Since: 0.4.0.0 |
LabelNoBound | No boundary overlap check is applied to labels. This is the default behavior. See also Since: 0.4.0.0 |
LabelBound | Labels are hidden if they exceed the axis range by more than 1 pixel. See also Since: 0.4.0.0 |
LabelBoundValue Double | Labels are hidden if they exceed the axis range by more than the given number of pixels. See also Since: 0.4.0.0 |
LabelColor Color | The label color. |
LabelNoFlush | The labels are not aligned flush to the scale. This is the default for non-continuous X scales. See also Since: 0.4.0.0 |
LabelFlush | The first and last axis labels are aligned flush to the scale range. See also Since: 0.4.0.0 |
LabelFlushValue Double | The labels are aligned flush, and the parameter determines the extra offset, in pixels, to apply to the first and last labels. This can help the labels better group (visually) with the corresponding axis ticks. See also Since: 0.4.0.0 |
LabelFlushOffset Double | The number of pixels to offset flush-adjusted labels. Since: 0.4.0.0 |
LabelFont Text | The font for the label. |
LabelFontSize Double | The font size of the label. |
LabelFontStyle Text | The font style of the label. Since: 0.4.0.0 |
LabelFontWeight FontWeight | The font weight of the label. Since: 0.4.0.0 |
LabelLimit Double | The maximum width of a label, in pixels. |
LabelLineHeight Double | The line height, in pixels, for multi-line label text. Added in Vega-Lite 4.6.0. Since: 0.7.0.0 |
LabelOffset Double | The pixel offset for labels, in addition to Since: 0.6.0.0 |
LabelOpacity Opacity | The opacity of the label. Since: 0.4.0.0 |
LabelOverlap OverlapStrategy | How should overlapping labels be displayed? |
LabelPadding Double | The padding, in pixels, between the label and the axis. |
LabelSeparation Double | The minimum separation, in pixels, between label bounding boxes
for them to be considered non-overlapping. This is ignored if
the Since: 0.4.0.0 |
MaxExtent Double | The maximum extent, in pixels, that axis ticks and labels should use. This determines a maxmium offset value for axis titles. |
MinExtent Double | The minimum extent, in pixels, that axis ticks and labels should use. This determines a minmium offset value for axis titles. |
NoTitle | Do not draw a title for this axis. Since: 0.4.0.0 |
Orient Side | The orientation of the axis. Since: 0.4.0.0 |
Ticks Bool | Should tick marks be drawn on an axis? |
TickBand BandAlign | For band scales, indicates if ticks and grid lines should be placed at the center of a band (the default) or at the band extents to indicate intervals. Since: 0.5.0.0 |
TickCap StrokeCap | The stroke cap for the grid lines' ending style. Since: 0.9.0.0 |
TickColor Color | The color of the ticks. |
TickCount Int | The desired number of ticks for axes visualizing quantitative scales. This is a hint to the system, and the actual number used will be adjusted to be "nice" (multiples of 2, 5, or 10) and lie within the underlying scale's range. The Since: 0.9.0.0 |
TickCountTime ScaleNice | A specialised version of The Since: 0.9.0.0 |
TickDash DashStyle | The dash pattern of the ticks. |
TickDashOffset DashOffset | The offset for the dash pattern. Since: 0.4.0.0 |
TickExtra Bool | Should an extra axis tick mark be added for the initial position of the axis? Since: 0.4.0.0 |
TickOffset Double | The position offset, in pixels, to apply to ticks, labels, and grid lines. See also Since: 0.4.0.0 |
TickOpacity Opacity | The opacity of the ticks. Since: 0.4.0.0 |
TickRound Bool | Should pixel position values be rounded to the nearest integer? |
TickSize Double | The size of the tick marks in pixels. |
TickWidth Double | The width of the tick marks in pixels. |
TitleAlign HAlign | The horizontal alignment of the axis title. |
TitleAnchor APosition | The text anchor position for placing axis titles. Since: 0.4.0.0 |
TitleAngle Angle | The angle of the axis title. |
TitleBaseline VAlign | The vertical alignment of the axis title. |
TitleColor Color | The color of the axis title. |
TitleFont Text | The font for the axis title. |
TitleFontSize Double | The font size of the axis title. |
TitleFontStyle Text | The font style of the axis title. Since: 0.4.0.0 |
TitleFontWeight FontWeight | The font weight of the axis title. |
TitleLimit Double | The maximum allowed width of the axis title, in pixels. |
TitleLineHeight Double | Line height, in pixels, for multi-line title text. Since: 0.5.0.0 |
TitleOpacity Opacity | The opacity of the axis title. Since: 0.4.0.0 |
TitlePadding Double | The padding, in pixels, between title and axis. |
TitleX Double | The X coordinate of the axis title, relative to the axis group. |
TitleY Double | The Y coordinate of the axis title, relative to the axis group. |
TranslateOffset Double | The translation offset in pixels applied to the axis group mark x and y. If specified it overrides the default value of a 0.5 offset to pixel-align stroked lines. Since: 0.5.0.0 |
data AxisChoice Source #
Which axis should the configuration be applied to?
Added in Vega-Lite 4.7.0.
Since: 0.7.0.0
Legend Configuration Options
data LegendConfig Source #
Legend configuration options, set with the LegendStyle
constructor.
For more detail see the
Vega-Lite documentation.
In 0.9.0.0
the LeTickCountTime
constructor was added.
In 0.8.0.0
the LeTitle
constructor was removed as there is no way
to set the default text for a legend title in Vega-Lite (LeNoTitle
remains as this is used to turn off legend titles).
In 0.6.0.0
the following constructors were added (all from Vega-Lite 4.0):
LeSymbolLimit
, LeTickCount
, LeTitleLineHeight
, and
LeUnselectedOpacity
.
In 0.5.0.0
the LeShortTimeLabels
constructor was removed (Vega-Lite 4.0).
This data type has seen significant changes in the 0.4.0.0
release:
- the
EntryPadding
,GradientHeight
,GradientLabelBaseline
,GradientWidth
andSymbolColor
constructors were removed; - the constructors were removed;
- the remaining constructors that did not begin with
Le
were renamed (for exampleOrient
was changed toLeOrient
); - and new constructors were added.
LeAria Bool | A boolean flag indicating if ARIA attributes should be included (SVG output only). If False, the "aria-hidden" attribute will be set on the output SVG group, removing the legend from the ARIA accessibility tree. Default value: True Since: 0.9.0.0 |
LeAriaDescription Text | A text description of this legend for ARIA accessibility (SVG output only). If the If the description is unspecified it will be automatically generated. Since: 0.9.0.0 |
LeClipHeight Double | The height in pixels at which to clip symbol legend entries. Since: 0.4.0.0 |
LeColumnPadding Double | The horizontal padding, in pixels, between symbol legend entries. Since: 0.4.0.0 |
LeColumns Int | The number of columns in which to arrange symbol legend entries. A value
of Since: 0.4.0.0 |
LeCornerRadius Double | The corner radius for the full legend. |
LeDirection Orientation | The direction for the legend. Since: 0.8.0.0 |
LeDisable Bool | Disable the legend by default? Added in Vega-Lite 4.8. Since: 0.8.0.0 |
LeFillColor Color | The background fill color for the full legend. |
LeGradientDirection Orientation | The default direction for gradient legends. Since: 0.4.0.0 |
LeGradientHorizontalMaxLength Double | The maximum legend length for a horizontal gradient. Since: 0.4.0.0 |
LeGradientHorizontalMinLength Double | The minimum legend length for a horizontal gradient. Since: 0.4.0.0 |
LeGradientLabelLimit Double | The maximum allowed length, in pixels, of color-ramp gradient labels. |
LeGradientLabelOffset Double | The vertical offset in pixels for color-ramp gradient labels. |
LeGradientLength Double | The length in pixels of the primary axis of a color gradient.
See also Since: 0.4.0.0 |
LeGradientOpacity Opacity | The opacity of the color gradient. Since: 0.4.0.0 |
LeGradientStrokeColor Color | The color of the gradient stroke. |
LeGradientStrokeWidth Double | The width of the gradient stroke, in pixels. |
LeGradientThickness Double | The thickness in pixels of the color gradient. See also Since: 0.4.0.0 |
LeGradientVerticalMaxLength Double | The maximum legend length for a vertical gradient. Since: 0.4.0.0 |
LeGradientVerticalMinLength Double | The minimum legend length for a vertical gradient. Since: 0.4.0.0 |
LeGridAlign CompositionAlignment | The alignment to apply to symbol legends rows and columns. Since: 0.4.0.0 |
LeLabelAlign HAlign | The alignment of the legend label. |
LeLabelBaseline VAlign | The position of the baseline of the legend label. |
LeLabelColor Color | The color of the legend label. |
LeLabelFont Text | The font of the legend label. |
LeLabelFontSize Double | The font of the legend label. |
LeLabelFontStyle Text | The font style of the legend label. Since: 0.4.0.0 |
LeLabelFontWeight FontWeight | The font weight of the legend label. Since: 0.4.0.0 |
LeLabelLimit Double | The maxumum allowed pixel width of the legend label. |
LeLabelOffset Double | The offset of the legend label. |
LeLabelOpacity Opacity | The opacity of the legend label. Since: 0.4.0.0 |
LeLabelOverlap OverlapStrategy | How to resolve overlap of labels in gradient legends. Since: 0.4.0.0 |
LeLabelPadding Double | The passing in pixels between the legend and legend labels. Since: 0.4.0.0 |
LeLabelSeparation Double | The minimum separation between label bounding boxes for them
to be considered non-overlapping (ignored if Since: 0.4.0.0 |
LeLayout [LegendLayout] | Layout parameters for the legend orient group. It is not clear if this is used in Vega Lite 4.2 or later. Since: 0.4.0.0 |
LeLeX Double | Custom x position for a legend with orientation Since: 0.4.0.0 |
LeLeY Double | Custom y position for a legend with orientation Since: 0.4.0.0 |
LeOffset Double | The offset in pixels between the legend and the data rectangle and axes. |
LeOrient LegendOrientation | The orientation of the legend, which determines how the legend is positioned within the scene. |
LePadding Double | The padding between the border and content of the legend group. |
LeRowPadding Double | The vertical padding in pixels between symbol legend entries. Since: 0.4.0.0 |
LeStrokeColor Color | The border stoke color for the full legend. |
LeStrokeDash DashStyle | The border stroke dash pattern for the full legend. |
LeStrokeWidth Double | The border stroke width for the full legend. |
LeSymbolBaseFillColor Color | The fill color for legend symbols. This is only applied if there is no "fill" scale color encoding for the legend. Since: 0.4.0.0 |
LeSymbolBaseStrokeColor Color | The stroke color for legend symbols. This is only applied if there is no "fill" scale color encoding for the legend. Since: 0.4.0.0 |
LeSymbolDash DashStyle | The pattern for dashed symbol strokes. Since: 0.4.0.0 |
LeSymbolDashOffset DashOffset | The offset at which to start drawing the symbol dash pattern. Since: 0.4.0.0 |
LeSymbolDirection Orientation | The default direction for symbol legends. Since: 0.4.0.0 |
LeSymbolFillColor Color | The color of the legend symbol. Since: 0.4.0.0 |
LeSymbolLimit Int | The maximum number of allowed entries for a symbol legend. Any additional entries will be dropped. Since: 0.6.0.0 |
LeSymbolOffset Double | The horizontal pixel offset for legend symbols. Since: 0.4.0.0 |
LeSymbolOpacity Opacity | The opacity of the legend symbols. Since: 0.4.0.0 |
LeSymbolSize Double | The size of the legend symbol, in pixels. |
LeSymbolStrokeColor Color | The stroke color for legend symbols. Since: 0.4.0.0 |
LeSymbolStrokeWidth Double | The width of the symbol's stroke. |
LeSymbolType Symbol | The default shape type for legend symbols. |
LeTickCount Int | The desired number of tick values for quantitative legends. The Since: 0.6.0.0 |
LeTickCountTime ScaleNice | A specialised version of The Since: 0.9.0.0 |
LeNoTitle | Do not add a title for the legend. Since: 0.4.0.0 |
LeTitleAlign HAlign | The horizontal text alignment for legend titles. |
LeTitleAnchor APosition | The text anchor position for legend titles. Since: 0.4.0.0 |
LeTitleBaseline VAlign | The vertical text alignment for legend titles. |
LeTitleColor Color | The color of the legend title. |
LeTitleFont Text | The font of the legend title. |
LeTitleFontSize Double | The font size of the legend title. |
LeTitleFontStyle Text | The font style for the legend title. Since: 0.4.0.0 |
LeTitleFontWeight FontWeight | The font weight of the legend title. |
LeTitleLimit Double | The maxmimum pixel width of the legend title. |
LeTitleLineHeight Double | The line height, in pixels, for multi-line title text. Since: 0.6.0.0 |
LeTitleOpacity Opacity | The opacity of the legend title. Since: 0.4.0.0 |
LeTitleOrient Side | The orientation of the legend title. Since: 0.4.0.0 |
LeTitlePadding Double | The padding, in pixels, between title and legend. |
LeUnselectedOpacity Opacity | The opacity of unselected legend entries. The default is 0.35. Since: 0.6.0.0 |
LeZIndex ZIndex | The z-index indicating the layering of the legend group relative to the other axis, mark, and legend groups. Since: 0.9.0.0 |
data LegendLayout Source #
Highly experimental and used with LeLayout
.
Since: 0.4.0.0
LeLAnchor APosition | The anchor point for legend orient group layout. |
LeLBottom [BaseLegendLayout] | |
LeLBottomLeft [BaseLegendLayout] | |
LeLBottomRight [BaseLegendLayout] | |
LeLBounds Bounds | The bounds calculation to use for legend orient group layout. |
LeLCenter Bool | A flag to center legends within a shared orient group. |
LeLDirection Orientation | The layout firection for legend orient group layout. |
LeLLeft [BaseLegendLayout] | |
LeLMargin Double | The margin, in pixels, between legends within an orient group. |
LeLOffset Double | The offset, in pixels, from the chart body for a legend orient group. |
LeLRight [BaseLegendLayout] | |
LeLTop [BaseLegendLayout] | |
LeLTopLeft [BaseLegendLayout] | |
LeLTopRight [BaseLegendLayout] |
data BaseLegendLayout Source #
Highly experimental and used with constructors from LegendLayout
.
Since: 0.4.0.0
BLeLAnchor APosition | The anchor point for legend orient group layout. |
BLeLBounds Bounds | The bounds calculation to use for legend orient group layout. |
BLeLCenter Bool | A flag to center legends within a shared orient group. |
BLeLDirection Orientation | The layout direction for legend orient group layout. |
BLeLMargin Double | The margin, in pixels, between legends within an orient group. |
BLeLOffset Double | The offset, in pixels, from the chart body for a legend orient group. |
Scale Configuration Options
data ScaleConfig Source #
Scale configuration property. These are used to configure all scales
with ScaleStyle
. For more details see the
Vega-Lite documentation.
Version 0.5.0.0
removed the SCRangeStep
and SCTextXRangeStep
constructors. The new ViewStep
constructor of ViewConfig
should
be used instead.
SCBandPaddingInner Double | Default inner padding for x and y band-ordinal scales. |
SCBandPaddingOuter Double | Default outer padding for x and y band-ordinal scales. |
SCBarBandPaddingInner Double | Default inner padding for x and y band-ordinal scales of Since: 0.4.0.0 |
SCBarBandPaddingOuter Double | Default outer padding for x and y band-ordinal scales of Since: 0.4.0.0 |
SCRectBandPaddingInner Double | Default inner padding for x and y band-ordinal scales of Since: 0.4.0.0 |
SCRectBandPaddingOuter Double | Default outer padding for x and y band-ordinal scales of Since: 0.4.0.0 |
SCClamp Bool | Whether or not by default values that exceed the data domain are clamped to the min/max range value. |
SCMaxBandSize Double | Default maximum value for mapping quantitative fields to a bar's size/bandSize. |
SCMinBandSize Double | Default minimum value for mapping quantitative fields to a bar's size/bandSize. |
SCMaxFontSize Double | Default maximum value for mapping a quantitative field to a text mark's size. |
SCMinFontSize Double | Default minimum value for mapping a quantitative field to a text mark's size. |
SCMaxOpacity Opacity | Default maximum opacity for mapping a field to opacity. |
SCMinOpacity Opacity | Default minimum opacity for mapping a field to opacity. |
SCMaxSize Double | Default maximum size for point-based scales. |
SCMinSize Double | Default minimum size for point-based scales. |
SCMaxStrokeWidth Double | Default maximum stroke width for rule, line and trail marks. |
SCMinStrokeWidth Double | Default minimum stroke width for rule, line and trail marks. |
SCPointPadding Double | Default padding for point-ordinal scales. |
SCRound Bool | Are numeric values are rounded to integers when scaling? Useful for snapping to the pixel grid. |
SCUseUnaggregatedDomain Bool | Whether or not to use the source data range before aggregation. |
SCXReverse Bool | Reverse the X scale (useful for right-to-left charts). Since: 0.6.0.0 |
Scale Range Configuration Options
data RangeConfig Source #
Properties for customising the colors of a range. The parameter should be a
named color scheme such as "accent"
or "purpleorange-11"
. For details see the
Vega-Lite documentation.
Used by RangeStyle
.
Title Configuration Options
Unlike title
, these options apply to all titles if multiple views
are created. See the
Vega-Lite title configuration documentation.
data TitleConfig Source #
Title configuration properties. These are used to configure the default style
of all titles within a visualization with title
or TitleStyle
.
For further details see the Vega-Lite documentation.
TAlign HAlign | The horizontal text alignment for title text. Since: 0.5.0.0 |
TAnchor APosition | The anchor position when placing titles. |
TAngle Angle | The angle when orientating titles. |
TAria Bool | A boolean flag indicating if ARIA attributes should be included (SVG output only). If False, the "aria-hidden" attribute will be set on the output SVG group, removing the title from the ARIA accessibility tree. Default value: True Since: 0.9.0.0 |
TBaseline VAlign | The vertical alignment when placing titles. |
TColor Color | The color of title text. |
TdX Double | The offset, in pixels, for the x coordinate of title and subtitle text. Since: 0.5.0.0 |
TdY Double | The offset, in pixels, for the x coordinate of title and subtitle text. Since: 0.5.0.0 |
TFont Text | Default font when showing titles. |
TFontSize Double | Default font size when showing titles. |
TFontStyle Text | Defaylt font style when showing titles. Since: 0.4.0.0 |
TFontWeight FontWeight | Default font weight when showing titles. |
TFrame TitleFrame | Default title position anchor. Since: 0.4.0.0 |
TLimit Double | The maximum length, in pixels, of title and subtitle text. |
TLineHeight Double | Line height, in pixels, for multi-line title text. Since: 0.5.0.0 |
TOffset Double | Default offset, in pixels, of titles relative to the chart body. |
TOrient Side | Default placement of titles relative to the chart body. |
TStyle [StyleLabel] | A list of named styles to apply. A named style can be specified
via Since: 0.4.0.0 |
TSubtitle Text | Subtitle text. This is placed below the title text. Use n to insert line breaks into the subtitle. This should only be used with Since: 0.5.0.0 |
TSubtitleColor Color | Subtitle color. Since: 0.5.0.0 |
TSubtitleFont Text | Subtitle font. Since: 0.5.0.0 |
TSubtitleFontSize Double | Subtitle font size, in pixels. Since: 0.5.0.0 |
TSubtitleFontStyle Text | Subtitle font style. Since: 0.5.0.0 |
TSubtitleFontWeight FontWeight | Subtitle font weight. Since: 0.5.0.0 |
TSubtitleLineHeight Double | Subtitle line height, in pixels. Since: 0.5.0.0 |
TSubtitlePadding Double | Padding, in pixels, between the title and Subtitle. Since: 0.5.0.0 |
TZIndex ZIndex | Drawing order of a title relative to the other chart elements. Since: 0.4.0.0 |
data TitleFrame Source #
Specifies how the title anchor is positioned relative to the frame.
Since: 0.4.0.0
View Configuration Options
data ViewConfig Source #
View configuration property. These are used to configure the style of a single
view within a visualization (via ViewStyle
) such as its size and default fill and stroke colors.
For further details see the
Vega-Lite documentation.
In version 0.6.0.0
the constructors that used to take an optional color,
namely ViewFill
and ViewStroke
, were split out, so that they
now take a Color
argument and new constructors - ViewNoFill
and
ViewNoStroke
- were added to replace the Nothing
versions.
In version 0.5.0.0
the ViewWidth
and ViewHeight
constructors have
been deprecated, and replaced by
ViewContinuousWidth
, ViewContinuousHeight
,
ViewDiscreteWidth
, and ViewDiscreteHeight
. The ViewBackgroundStyle
constructor has been added.
This type has been changed in the 0.4.0.0
release to use a consistent
naming scheme for the constructors (everything starts with View
). Prior to
this release only ViewWidth
and ViewHeight
were named this way. There
are also five new constructors.
ViewBackgroundStyle [ViewBackground] | The default single-view style. Since: 0.5.0.0 |
ViewClip Bool | Should the view be clipped? |
ViewContinuousWidth Double | The default width of single views when the visualization has a continuous x field. Since: 0.5.0.0 |
ViewContinuousHeight Double | The default height of single views when the visualization has a continuous y field. Since: 0.5.0.0 |
ViewCornerRadius Double | The radius, in pixels, of rounded rectangle corners. The default is Since: 0.4.0.0 |
ViewCursor Cursor | The default cursor for single views. Since: 0.6.0.0 |
ViewDiscreteWidth Double | The default width of single views when the visualization has a discrete x field. Since: 0.5.0.0 |
ViewDiscreteHeight Double | The default height of single views when the visualization has a discrete y field. Since: 0.5.0.0 |
ViewFill Color | The fill color. See also This was changed to use the |
ViewNoFill | Do not use a fill. See also Since: 0.6.0.0 |
ViewFillOpacity Opacity | The fill opacity. |
ViewOpacity Opacity | The overall opacity. The default is Since: 0.4.0.0 |
ViewStep Double | Default step size for discrete fields. This replaces Since: 0.5.0.0 |
ViewStroke Color | The stroke color. See also This was changed to use the |
ViewNoStroke | Do not use a stroke color. See also Since: 0.6.0.0 |
ViewStrokeCap StrokeCap | The stroke cap for line-ending style. Since: 0.4.0.0 |
ViewStrokeDash DashStyle | The stroke dash pattern. |
ViewStrokeDashOffset DashOffset | The offset for the dash pattern. |
ViewStrokeJoin StrokeJoin | The stroke line-join method. Since: 0.4.0.0 |
ViewStrokeMiterLimit Double | The miter limit at which to bevel a line join. Since: 0.4.0.0 |
ViewStrokeOpacity Opacity | The stroke opacity. |
ViewStrokeWidth Double | The stroke width, in pixels. |
ViewWidth Double | Deprecated: Please change ViewWidth to ViewContinuousWidth As of version |
ViewHeight Double | Deprecated: Please change ViewHeight to ViewContinuousHeight As of version |
Indicates the anchor position for text.
data FieldTitleProperty Source #
Indicates the style in which field names are displayed.
Composition Configuration Options
data CompositionConfig Source #
Configuration options for composition views, used with
ConcatStyle
, FacetStyle
, and RepeatStyle
.
Prior to 0.6.0.0
this information was made available in
two types - ConcatConfig
and FacetConfig
- which had
the same meaning.
Since: 0.6.0.0
CompColumns Int | The number of columns to use. The default is to use a single row (an infinite number of columns). Prior to |
CompSpacing Double | The spacing in pixels between sub-views. The default is 20. Prior to |
General Data types
In addition to more general data types like integers and string, the following types can carry data used in specifications.
A single data value. This is used when a function or constructor
can accept values of different types (e.g. either a number or a string),
such as:
dataRow
, geometry
, many constructors of the Filter
type,
ImNewValue
, and SInit
.
Boolean Bool | |
DateTime [DateTime] | |
Number Double | |
Str Text | |
NullValue | Create a JavaScript
For more-complex data sources - such as lists of defined
and un-specified values, it is suggested that Since: 0.4.0.0 |
data DataValues Source #
A list of data values. This is used when a function or constructor
can accept lists of different types (e.g. either a list of numbers
or a list of strings), such as:
dataColumn
, CustomSort
, FOneOf
, or ImKeyVals
.
If your data contains undefined values then it is suggested that
you convert it to JSON (e.g. Value
) and then use dataFromJson
.
Temporal data
See the Vega-Lite dateTime documentation and the Vega-Lite time unit documentation.
Allows a date or time to be represented. This is typically part of a list of
DateTime
items to provide a specific point in time. For details see the
Vega-Lite documentation.
There is no check that the provided Int
values lie within the
required bounds.
A DateTime
value of DTDay
or DTDayNum
should not be combined with
DTYear
, DTQuarter
, DTMonth
, DTMonthNum
, or DTDate
.
DTYear Int | |
DTQuarter Int | The quarter of the year (1 to 4, inclusive). |
DTMonth MonthName | |
DTMonthNum Int | The month number (1 to 12, inclusive). Since: 0.5.0.0 |
DTWeek Int | The week number. Each week begins on Sunday, which means that days before the first Sunday of the year are considered to be in week 0, as the first Sunday of the year is the start of week 1. Since: 0.10.0.0 |
DTDay DayName | |
DTDayNum Int | The day number (1 represents Monday, 7 is Sunday). Since: 0.5.0.0 |
DTDayOfYear Int | The day of the year (1 to 366). Since: 0.10.0.0 |
DTDate Int | Day of the month (1 to 31, inclusive). |
DTHours Int | Hour of the day, where 0 is midnight, 1 is 1am, and 23 is 11pm. |
DTMinutes Int | The minute of an hour (0 to 59, inclusive). |
DTSeconds Int | The second of a minute (0 to 59, inclusive). |
DTMilliseconds Int | The milliseconds of a second (0 to 999, inclusive). |
Identifies a month of the year.
Describes a unit of time. Useful for encoding and transformations. See the Vega-Lite documentation for further details.
encoding
.position
X
[PName
"date",PmType
Temporal
,PTimeUnit
(Utc
YearMonthDateHours
) ]
Prior to version 0.10.0.0
the field was a combination of what is now
BaseTimeUnit
and the "option" fields (e.g. encode as UTC or the
maximum nuber of bins).
TU BaseTimeUnit | Encode a time as local time. |
Utc BaseTimeUnit | Encode a time as UTC (coordinated universal time, independent of local time zones or daylight saving). |
TUMaxBins Natural | The maximum number of bins to use when discretising time values.
This can be useful as an algternative to explicitly providing the
time unit to bin by, as it will be inferred from the temporal
extent and the number of bins. As an example, Since: 0.6.0.0 |
TUStep Double BaseTimeUnit | The number of steps between time-unit bins, in terms of the
least-significant unit provided. So Since: 0.6.0.0 |
UtcStep Double BaseTimeUnit | The number of steps between time-unit bins, in terms of the
least-significant unit provided for UTC times.
So Since: 0.10.0.0 |
data BaseTimeUnit Source #
Define the time unit, either as a base unit - such as Hours
- or
as a composite type, for example WeeksDayHours
.
Since: 0.10.0.0
Year | Year. |
Quarter | Quarter of the year. |
Month | Month of the year. |
Week | Sunday-based week number. Days before the first Sunday of the year are considered to be in week 0, and the first Sunday of the year is the start of week 1, Since: 0.10.0.0 |
Date | Day of the month (1 to 31). |
Day | Day of the week. |
DayOfYear | Day of the year (starting at 1). Since: 0.10.0.0 |
Hours | Hour of the day. |
Minutes | Minutes of the hour. |
Seconds | Seconds of the minute. |
Milliseconds | Milliseconds. |
YearQuarter | Year and quarter. |
YearQuarterMonth | Year, quarter, and month. |
YearMonth | Year and month. |
YearMonthDate | Year, month, and day of month. |
YearMonthDateHours | Year, month, day of month, and hour of day. |
YearMonthDateHoursMinutes | Year, month, day of month, hour of day, and minutes. |
YearMonthDateHoursMinutesSeconds | Year, month, day of month, hour of day, minutes, and seconds. |
YearWeek | Year and week. Since: 0.10.0 |
YearWeekDay | Year, week, and day. Since: 0.10.0 |
YearWeekDayHours | Year, week, day, and hour of day. Since: 0.10.0 |
YearWeekDayHoursMinutes | Year, week, day, hour of day, and minutes. Since: 0.10.0 |
YearWeekDayHoursMinutesSeconds | Year, week, day, hour of day, minutes, and seconds. Since: 0.10.0 |
YearDayOfYear | Year and day of year. Since: 0.10.0 |
QuarterMonth | Quarter of the year and month. |
MonthDate | Month of the year and day of the month. |
MonthDateHours | Month, day of the month, and hours. Since: 0.10.0.0 |
MonthDateHoursMinutes | Month, day of the month, hours, and minutes. Since: 0.10.0.0 |
MonthDateHoursMinutesSeconds | Month, day of the month, hours, minutes, and seconds. Since: 0.10.0.0 |
WeekDay | Week and day of month. Since: 0.10.0.0 |
WeeksDayHours | Week, day of month, and hours. Since: 0.10.0.0 |
WeeksDayHoursMinutes | Week, day of month, hours, and minutes. Since: 0.10.0.0 |
WeeksDayHoursMinutesSeconds | Week, day of month, hours, minutes, and seconds. Since: 0.10.0.0 |
DayHours | Day of the week and hours. Since: 0.10.0.0 |
DayHoursMinutes | Day of the week, hours, and minutes. Since: 0.10.0.0 |
DayHoursMinutesSeconds | Day of the week, hours, minutes, and seconds. Since: 0.10.0.0 |
HoursMinutes | Hour of the day and minutes. |
HoursMinutesSeconds | Hour of the day, minutes, and seconds. |
MinutesSeconds | Minutes of the hour and seconds. |
SecondsMilliseconds | Seconds of the minute and milliseconds. |
Update notes
The following section describes how to update code that used
an older version of hvega
.
Version 0.12
The 0.12.0.2
release adds support for version 2.0 of the text package.
There are no changes to the code.
The 0.12.0.1
release is purely to support bytestring 0.11 when
running the tests. There are no changes to the code.
The 0.12.0.0
release allows hvega
to be built with version 2.0 of the
aeson package. There are
no changes to the API of hvega
, but it does mean that you may need
to update code that directly creates JSON, such as dataFromJson
.
It is likely that LabelledSpec
type and the related
toXXXSpec/fromXXXSpec
functions, such as fromSelectSpec
and
toSelectSpec
, will be updated once we can drop
support for versions of aeson
prior to 2.0.
Version 0.11
The 0.11.0.1
release is purely to support testing with hashable
0.3.1.0.
There are no changes to the module.
The 0.11.0.0
release updates hvega
to support version 4.15 of
the Vega-Lite schema.
Note that hvega
does not provide any information to help users
take advantage of the (new to 4.14) ability to
omit the type of a field when
it can be inferred.
As the type is currently optional in hvega
users can just
not give a type. The example IHaskell notebooks
have been updated to show off the optional support.
Similarly, Vega-Lite 4.14 allows you to share the type, scale, axis,
and legend in a shared encoding. There is no explicit support added in
0.11.0.0
because hvega
already allowed you to create the specification.
New constructors
The OrderChannel
type has gained OBand
, OTitle
/ONoTitle
,
and conditional-predicate support with ODataCondition
,
OSelectionCondition
, and ONumber
constructors.
The MarkChannel
type has gained the MNullValue
constructor.
The ScaleRange
type has gained RField
, RMax
, and RMin
constructors.
Breaking Changes
Domain settings in ScaleProperty
and associated types have been
changed to better match the Vega-Lite schema: SDomain
now takes
a new type (DomainLimits
) which actually contains many of the
orignal symbols (so hopefully will require no changes), and a new
constructor has been added (SDomainOpt
) which takes the
ScaleDomain
type, which has seen new constructors - DMax
,
DMaxTime
, DMid
, DMin
, and DMinTime
- as well as
some constructors moving to DomainLimits
.
Deprecated symbols:
The SDomainMid
constructor of ScaleProperty
will be removed in a
future release as it has been replaced by the DMid
constructor
in ScaleDomain
.
Version 0.10
The 0.10.0.0
release updates hvega
to support version 4.13 of
the Vega-Lite schema.
Breaking Changes
The handling of time units (for both TimeUnit
and ScaleNice
) has
changed. The contents of these types have been split into two parts:
a "time unit" and the options that get applied to it (rather than having
a single type that combines both functions). This does mean that setting
time units has now become more verbose, but it has stopped some
problem cases (and, in the case of ScaleNice
, fixed a logical error
on my part). The new time units are BaseTimeUnit
and NTimeUnit
,
and contain the "basic" constructors for the time units. The
TimeUnit
and ScaleNice
constructors now reference these
types rather than include them in their definition, so that
PTimeUnit Month
has been changed to
and
PTimeUnit
(TU
Month
)SNice NMinute
has changed to
.SNice
(NTU
NMinute
)
The BaseTimeUnit
type has seen a number of additions: the Week
and
DayOfYear
time units added in Vega-Lite 4.13.0, along with the
associated composite units (such as YearWeek
), and a number of
composite types that were missing (such as MonthDateHours
).
The DataValue
type has added the DTWeek
and DTDayOfYear
constructors.
Version 0.9
The tutorial has been expanded to add a section with pie charts.
The 0.9.0.0
release updates hvega
to support version 4.12 of
the Vega-Lite schema.
New constructors
Support for arcs has been added: the Arc
type has been added
to Mark
; Theta
, Theta2
, R
, and R2
have
been added to Position
; and MInnerRadius
,
MOuterRadius
, MPadAngle
, MRadius2
,
MRadiusOffset
, MRadius2Offset
, MTheta2
,
MThetaOffset
, and MTheta2Offset
added to
MarkProperty
. ArcStyle
has been added to
ConfigurationProperty
.
Support for ARIA attributes has been added to a number of features
(e.g. Aria
and AriaDescription
for AxisConfig
and
MAria
, MAriaDescription
, MAriaRole
, MAriaRoleDescription
for MarkProperty
, AriaStyle
for ConfigurationProperty
).
The ariaDescrption
encoding has been added, along with the
AriaDescriptionChannel
.
The angle
encoding channel has been added for text and point marks.
The Channel
type has gained ChAngle
, ChTheta
, ChTheta2
,
ChRadius
, ChRadius2
, ChDescription
, and ChURL
.
Layers have been added to Arrangement
(Layer
) and to
RepeatFields
(LayerFields
).
The MRepeatDatum
and MDatum
, PRepeatDatum
and
PDatum
, and TRepeatDatum
and TDatum
pairs have been
added to MarkChannel
, PositionChannel
, and
TextChannel
respectively.
The MarkProperty
now has support for labelling the X (or X2)
coordinate as the "width" of the plot and Y (or Y2)
as the "height" of the plot. See MXWidth
, MX2Width
,
MYHeight
, and MY2Height
.
Improved support for tick scales: TickCount
and
TickCountTime
have been added to AxisConfig
,
AxTickCountTime
has been added to AxisProperty
,
LTickCountTime
has been added to LegendProperty
, and
LeTickCountTime
has been added to LegendConfig
.
The ScaleRange
type has now gained three new versions:
(experimental) RPair
for defining the axis range,
and RHeight
and RWidth
for specifying the height
or width as a signal.
AxisProperty
has gained AxFormatAsCustom
. AxisConfig
has gained AxisConfig
, FormatAsNum
, FormatAsTemporal
,
and FormatAsCustom
. LegendProperty
has gained
LFormatAsCustom
. HeaderProperty
has gained
HFormatAsCustom
. TextChannel
has gained
TFormatAsCustom
. The ConfigurationProperty
type has a new
option to configure support for custom format types
(CustomFormatStyle
).
AxisConfig
and AxisProperty
have gained new cap styles:
DomainCap
, GridCap
, TickCap
and
AxDomainCap
, AxGridCap
, AxTickCap
respectively.
The TZIndex
option of TitleConfig
can now be used with
TitleStyle
(prior to Vega-Lite 4.12 it was only supported
when used with title
). The LeZIndex
type has been added
to LegendConfig
.
The HyperlinkChannel
has gained a number of constructors it was
missing: HyBand
, HyFormat
, HyFormatAsNum
,
HyFormatAsTemporal
, HyFormatAsCustom
, HyLabelExpr
,
HyTitle
, and HyNoTitle
. A similar update has been made
to TextChannel
, which has gained TBand
and TLabelExpr
.
Version 0.8
The 0.8.0.0
release updates hvega
to support version 4.8 of
the Vega-Lite schema.
The RepeatStyle
constructor for ConfigurationProperty
should not
be used, as its functionality has been moved to ConcatStyle
in
Vega-Lite 4.8. This constructor will be removed at some point in the
future but is still available (as support for Vega-Lite 4.8 is
limited).
Breaking Changes
The HTitleFontWeight
constructor (a member of HeaderProperty
)
now takes a FontWeight
argument rather than Text
.
The LeTitle
constructor from LegendConfig
was removed as it
is not supported in Vega-Lite (LeNoTitle
remains, as it is used
to remove legend titles from a visualization).
ScBinLinear
was removed from ConfigurationProperty
as it is
not used by Vega-Lite.
New constructors
The HeaderProperty
type has gained the following constructors
from Vega-Lite 4.8: HLabelBaseline
, HLabelFontWeight
,
HLabelLineHeight
, and HOrient
.
The AxisConfig
type has gained the Disable
constructor from
Vega-Lite 4.8.
The LegendConfig
type has gained the LeDirection
and
(from Vega-Lite 4.8) LeDisable
constructors. The LegendProperty
type has gained LLabelExpr
, LSymbolLimit
, and
LTitleLineHeight
constructors.
Version 0.7
The 0.7.0.0
release updates hvega
to support version 4.7 of
the Vega-Lite schema. The 0.7.0.1
update fixes several minor
documentation issues.
New functionality
The BlendMode
type has been added for controlling how marks blend
with their background. This is used with the new MBlend
constructor
for marks.
Breaking Change
The axis style options for specific data- or mark- types
(AxisBand
, AxisDiscrete
, AxisPoint
,
AxisQuantitative
, and AxisTemporal
) have been changed to
accept an additional argument (the new AxisChoice
type)
which defines which axis (X, Y, or both) the configuration should be
applied to. This is to support new axis configuration options added
in Vega-Lite 4.7.0.
The ChTooltip
Channel
constructor has been removed as support
for this channel type was dropped in Vega-Lite 4.
New constructors
The ScaleDomain
type has gained DSelectionField
and DSelectionChannel
constructors, which allow you to link a scale (e.g. an axis) to a selection that
is projected over multiple fields or encodings.
The Operation
type has gained the Product
specifier from Vega-Lite
4.6.0.
The TextChannel
has gained TStrings
to support multi-line labels.
The VAlign
type has gained AlignLineTop
and AlignLineBottom
(Vega-Lite 4.6.0).
LineBreakStyle
has been added to ConfigurationProperty
.
The height of multi-line axis labels can now be set with the
LabelLineHeight
and AxLabelLineHeight
properties of the
AxisConfig
and AxisProperty
types (Vega-Lite 4.6.0).
Numeric filter ranges, specified with FRange
,
can now be lower- or upper-limits -
NumberRangeLL
and NumberRangeUL
respectively -
added to the FilterRange
type.
Version 0.6
The 0.6.0.0
release updates hvega
to support version 4.5 of
the Vega-Lite schema.
New functionality
New function for use with encoding
: strokeDash
. The ChStrokeDash
constructor has been added to the Channel
type, and RNumberLists
(Vega-Lite 4.4) to ScaleRange
.
Named styles have been added for axes as well as marks. As mentioned below,
this involves deprecating the previous constructors for naming styles,
as there are now separate configuration options: AxisNamedStyles
and MarkNamedStyles
. The AStyle
and AxStyle
options have been
added to AxisConfig
and AxisProperty
respectively.
The StyleLabel
type alias has been added to help the documentation, but
provides no extra type safety.
Breaking Change
The ConcatStyle
and FacetStyle
constructors for
ConfigurationProperty
now accept a common type,
CompositionConfig
, rather than having separate
ConcatConfig
and FacetConfig
types with the same meaning.
So ConcatColumns
and FColumns
have been replaced by CompColumns
,
and CompSpacing
and FSpacing
by CompSpacing
.
The ViewFill
and ViewStroke
constructors of ViewConfig
no longer take an optional Color
argument. The Nothing
case has been replaced by new constructors: ViewNoFill
and ViewNoStroke
.
The VBFill
and VBStroke
constructors of ViewBackground
no longer take an optional Color
argument. The Nothing
case has been replaced by new constructors: VBNoFill
and VBNoStroke
.
New constructors:
FacetChannel
has gained the following constructors:
FAlign
, FCenter
, and FSpacing
. The last one
would have collided with the FacetStyle
option,
but this has fortuitously been renamed to CompSpacing
.
MSymbol
has been added to MarkChannel
which can be
used to make the shape
encoding conditional on a data
or selection condition.
The TUStep
and TUMaxBins
constructors have been added to
TimeUnit
for controlling how time values are binned.
The MarkProperty
type has gained the MCornerRadiusEnd
constructor, which is used to draw rounded histogram bars, and
MTexts
for specifying multiple text values.
Error box and band properties (constructors in MarkProperty
) can now
be turned off with explicit No
variants: MNoBorders
, MNoBox
,
MNoMedian
, MNoRule
, and MNoTicks
. These join the MNoOutliers
constructor.
The ScaleProperty
type has gained SDomainMid
, useful
for asymmetric diverging color scales, and SReverse
from
Vega-Lite v4.5. The ScaleDomain
type has gained the
DUnionWith
option from Vega-Lite v4.3. The ScaleConfig
type has gained SCXReverse
from Vega-Lite v4.5.
Labels can now be vertically aligned to their baseline with the
AlignBaseline
constructor of the VAlign
type.
Headers (HeaderProperty
) have gained the following constructors:
HLabel
, HLabelExpr
, HLabelFontStyle
, HTitleFontStyle
,
and HTitleLineHeight
.
Conditional axis (ConditionalAxisProperty
) has gained the following
constructors for features added in Vega-Lite v4.2 and v4.5:
CAxLabelOffset
, CAxLabelPadding
, and CAxTickSize
.
Cursor handling has been enhanced (to match Vega-Lite 4.1):
ViewCursor
has been added to ViewConfig
and SMCursor
to
SelectionMarkProperty
.
The legend configuration has been updated (to match Vega-Lite 4.0)
with the addition of LeSymbolLimit
, LeTickCount
, LeTitleLineHeight
,
and LeUnselectedOpacity
constructors.
The axis configuration and property types (AxisConfig
and AxisProperty
)
have gained the Vega-Lite 4.4 LabelOffset
and AxLabelOffset
constructors.
Note that version 4.4.0 of the Vega-Lite specification has these fields
as strings but this is fixed in version 4.5.0.
ConfigurationProperty
has added new constructors:
AxisDiscrete
and AxisPoint
from Vega-Lite 4.5,
AxisQuantitative
and AxisTemporal
from Vega-Lite 4.4,
BoxplotStyle
, ErrorBandStyle
, ErrorBarStyle
,
FontStyle
(Vega-Lite 4.3), HeaderColumnStyle
,
HeaderFacetStyle
, HeaderRowStyle
,
ImageStyle
, and RepeatStyle
.
Deprecated symbols:
ConfigurationProperty
has seen a large number of deprecations,
as a number of constructors have been renamed:
NamedStyle
andNamedStyles
have been replaced byMarkNamedStyles
;Autosize
,Background
,CountTitle
,FieldTitle
,Legend
,NumberFormat
,Padding
,Projection
,Range
,Scale
,TimeFormat
, andView
constructors have been replaced byAutosizeStyle
,BackgroundStyle
,CountTitleStyle
,FieldTitleStyle
,LegendStyle
,NumberFormatStyle
,PaddingStyle
,ProjectionStyle
,RangeStyle
,ScaleStyle
,TimeFormatStyle
, andViewStyle
respectively.
Version 0.5
The 0.5.0.0
release now creates specifications using version 4
of the Vega-Lite schema (version 0.4 of hvega
used version 3).
The toVegaLiteSchema
function can be used along with the
vlSchema3
to use version 3 for the output.
There is more-extensive use of type aliases, such as Color
,
and the introduction of several more (e.g. DashStyle
and
FieldName
). These do not add any type safety, but help the
documentation (as they provide a single place to explain the meaning
and any constraints on a particular value). There are some
changes that do improve type safety, discussed in the
"Breaking changes" section below.
Documentation improvements, including a new section in the tutorial on choropleths contributed by Adam Conner-Sax, and plots using an Aitoff projection contributed by Jo Wood.
Changes in Vega-Lite 4:
- The background of a visualization is now white by default whereas in
previous versions it was transparent. If you
need a transparent background then add the following configuration
to the visualization:
.configuration
(BackgroundStyle
"rgba(0,0,0,0)") - Tooltips are now disabled by default. To enable, either use the
tooltip
channel or by setting
.MTooltip
TTEncoding
- Title (and subtitle) strings can now be split across multiple lines:
use
'n'
to indicate where line breaks should occur.
Note that the behavior of a Vega-Lite visualization seems to depend on both the version of the schema it is using, and the version of the visualization software used to display it (e.g. Vega-Embed).
New functionality:
This does not include new configuration options listed in the "new constructors" section below.
- Colors are now cleaned of extraneous whitespace and, if empty, converted to the JSON null value. This should not change the behavior of any existing visualization.
- The
pivot
transform has been added, along with thePivotProperty
preferences type. This is the inverse offold
. - The
density
transform has been added, along with theDensityProperty
type, to support kernel density estimation (such as generating a continuous distribution from a discrete one). - The
loess
transform has been added, along with theLoessProperty
type, to support estimating a trend (scatterplot smoothing). - The
regression
transform has been added, along with theRegressionProperty
andRegressionMethod
types, to support regression analysis. - The
quantile
transform has been added, along with theQuantileProperty
type, to support quantile analysis. - The
url
encoding has been added for displaying images (via the newImage
mark type. - The
lookupSelection
transform has been added to support joining data via a selection. TheSelectionLabel
type alias has been added as a guide for the documentation. - The
heightOfContainer
andwidthOfContainer
functions have been added to support responsive sizing, although I have not had much success in getting them to work! - The
tooltip
encoding will now turn off tooltips if given an empty list (although note that tooltips are now off by default in Vega-Lite 4).
Breaking changes:
- The
combineSpecs
function has been removed. - In an attempt to provide some type safety, the
encoding
,transform
,resolve
,selection
, andconfigure
functions now take specialised types -EncodingSpec
,TransformSpec
,ResolveSpec
,SelectSpec
, andConfigureSpec
respectively - rather than the genericLabelledSpec
type. Simple visualizations should remain unchanged, but helper functions may need to have their type signatures updated. - The
lookup
function now takes the newLookupFields
type rather than a list of field names. ThelookupAs
function is deprecated, as its functionality is now possible withlookup
. - The
RemoveInvalid
constructor has been removed fromConfigurationProperty
. To indicate how missing values should be handled use the newMRemoveInvalid
constructor fromMarkProperty
instead. This means changing
toconfiguration
(RemoveInvalid b)
.configuration
(MarkStyle
[MRemoveInvalid
b]) - The
Stack
constructor has been removed fromConfigurationProperty
. - The
SRangeStep
constructor fromScaleProperty
has been removed. ThewidthStep
andheightStep
functions should be used instead. - The
ViewWidth
andViewHeight
constructors fromViewConfig
have been replaced byViewContinuousWidth
,ViewContinuousHeight
,ViewDiscreteWidth
, andViewDiscreteHeight
constructors (actually, they remain but are now deprecated and the continuous-named versions should be used instead). - The
SCRangeStep
andSCTextXRangeStep
constructors ofScaleConfig
have been removed. The newViewStep
constructor ofViewConfig
should be used instead. That is, users should change
toconfiguration
(ConfigurationProperty
[SCRangeStep (Just x)])
.configuration
(View
[ViewStep
x]) - The
ShortTimeLabels
,LeShortTimeLabels
, andMShortTImeLabels
constructors have been removed fromAxisConfig
,LegendConfig
, andMarkProperty
respectively.
New constructors:
Note that some new constructors have been described in the "breaking changes" section above and so are not repeated here.
AxisProperty
has gained theAxDataCondition
constructor for marking a subset of axis properties as being conditional on their position, and theConditionalAxisProperty
for defining which properties (grid, label, and tick) can be used in this way. It has also gained theAxLabelExpr
constructor, which allows you to change the content of axis labels,AxTickBand
for positioning the labels for band scales (and the associatedBandAlign
type),AxTitleLineHeight
to specify the line height, andAxTranslateOffset
for applying a translation offset to the axis group mark.AxisConfig
has gainedTickBand
,TitleLineHeight
, andTranslateOffset
, matching the additions toAxisProperty
.- The
ViewBackgroundStyle
constructor has been added toViewConfig
. - The
TitleConfig
type gained the following constructors:TAlign
,TdX
,TdY
,TLineHeight
,TSubtitle
,TSubtitleColor
,TSubtitleFont
,TSubtitleFontSize
,TSubtitleFontStyle
,TSubtitleFontWeight
,TSubtitleLineHeight
, andTSubtitlePadding
. - The
AFitX
andAFitY
constructors have been added to theAutosize
type. - The
SelectionProperty
type has gained theBindLegend
constructor - and associatedBindLegendProperty
type - to allow selection of legend items (for categorical data only). - The
TextChannel
type has gainedTString
, which lets you specify the text content as a literal. - Two new projections -
EqualEarth
andNaturalEarth1
- have been added to theConfigurationProperty
type. - Support for color gradients has been added for marks via the
MColorGradient
,MFillGradient
, andMStrokeGradient
constructors ofMarkProperty
, along with the newColorGradient
andGradientProperty
types for defining the appearance of the gradient. TheGradientCoord
andGradientStops
type aliases have also been added (although they provides no type safety). - The
Image
constructor has been added toMark
, for use with the newurl
encoding, andMAspect
toMarkProperty
. - The
MCornerRadius
constructor has been added toMarkProperty
to set the corner radius of rectangular marks. If that's not enough, you can change individual corners with one of:MCornerRadiusTL
,MCornerRadiusTR
,MCornerRadiusBL
, andMCornerRadiusBR
. - The
MDir
,MEllipsis
, andMLimit
constructors have been added toMarkProperty
to control how text is truncated. TheTextDirection
type has been added for use withMDir
. - The
MarkProperty
type has gainedMLineBreak
andMLineHeight
constructors for controlling how multi-line labels are displayed. Note thathvega
will always split on the newline character (\n
), which will over-ride theMLineBreak
setting. - The
DTMonthNum
andDTDayNum
constructors have been added toDateTime
. - The
BinProperty
type has gained theSelectionExtent
constructor, which defines the bin range as an interval selection. - The
PositionChannel
type has gainedPBand
, for defining the size of a mark relative to a band, andMarkProperty
has addedMTimeUnitBand
andMTimeUnitBandPosition
.
Bug Fixes in this release:
- The selection property
is now a no-op (as it does nothing), rather than generating invalid JSON.SInitInterval
Nothing Nothing - The following options or symbols generated incorrect JSON output:
ONone
,LSymbolStrokeWidth
,LeLabelOpacity
.
Version 0.4
The 0.4.0.0
release added a large number of functions, types, and
constructors, including:
toVegaLiteSchema
has been added to allow you to specify a
different Vega-Lite schema. toVegaLite
uses version 3 but
version 4 is being worked on as I type this. The vlSchema
function has been added, along with vlSchema4
, vlSchema3
,
and vlSchema2
values. The toHtmlWith
and toHtmlFileWith
functions have been added to support more control over the
embedding of the Vega-Lite visualizations, and the versions of
the required Javascript libraries used by the toHtmlXXX
routines
has been updated.
The VLProperty
type now exports its constructors, to support users
who may need to tweak or augment the JSON Vega-Lite specification
created by hvega
: see issue
17. It has also gained
several new constructors and associated functions, which are given in
brackets after the constructor: VLAlign
(align
); VLBounds
(bounds
); VLCenter
(center
, centerRC
); VLColumns
(columns
); VLConcat
(vlConcat
); VLSpacing
(alignRC
,
spacing
, spacingRC
); VLUserMetadata
(usermetadata
); and
VLViewBackground
(viewBackground
). It is expected that you will be
using the functions rather the constructors!
Four new type aliases have been added: Angle
, Color
, Opacity
,
and ZIndex
. These do not provide any new functionality but do
document intent.
The noData
function has been added to let compositions define the
source of the data (whether it is from the parent or not), and data
sources can be named with dataName
. Data can be created with
dataSequence
, dataSequenceAs
, and sphere
. Graticules can be
created with graticule
. The NullValue
type has been added to
DataValue
to support data sources that are missing elements, but for
more-complex cases it is suggested that you create your data as an
Aeson Value and then use dataFromJson
. Support for data imputation
(creating new values based on existing data) has been added, as
discussed below.
The alignment, size, and composition of plots can be defined and
changed with align
, alignRC
, bounds
, center
, centerRC
,
columns
, spacing
, and spacingRC
.
Plots can be combined and arranged with: facet
, facetFlow
,
repeat
, repeatFlow
, and vlConcat
New functions for use in a transform
: flatten
, flattenAs
,
fold
, foldAs
, impute
, and stack
.
New functions for use with encoding
: fillOpacity
, strokeOpacity
,
strokeWidth
,
The ability to arrange specifications has added the "flow" option
(aka "repeat"). This is seen in the addition of the Flow
constructor
to the Arrangement
type - which is used with ByRepeatOp
,
HRepeat
, MRepeat
, ORepeat
, PRepeat
, and TRepeat
.
The Mark
type has gained Boxplot
, ErrorBar
, ErrorBand
, and
Trail
constructors. The MarkProperty
type has gained MBorders
,
MBox
, MExtent
, MHeight
, MHRef
, MLine
, MMedian
, MOrder
,
MOutliers
, MNoOutliers
, MPoint
, MRule
, MStrokeCap
, MStrokeJoin
,
MStrokeMiterLimit
, MTicks
, MTooltip
, MWidth
, MX
, MX2
,
MXOffset
, MX2Offset
, MY
, MY2
, MYOffset
, and MY2Offset
constructors.
The Position
type has added XError
, XError2
, YError
, and
YError2
constructors.
The MarkErrorExtent
type was added.
The BooleanOp
type has gained the FilterOp
and FilterOpTrans
constructors which lets you use Filter
expressions as part of a
boolean operation. The Filter
type has also gained expresiveness,
with the FLessThan
, FLessThanEq
, FGreaterThan
, FGreaterThanEq
,
and FValid
.
The AxisConfig
type has gained the DSV
constructor, which allow you
to specify the separator character for column data.
The MarkChannel type has been expanded to include: MBinned
, MSort
,
MTitle
, and MNoTitle
. The PositionChannel type has added
PHeight
, PWidth
, PNumber
, PBinned
, PImpute
, PTitle
, and
PNoTitle
constructors.
The LineMarker and PointMarker types have been added for use with
MLine
and MPoint
respectively (both from MarkProperty
).
The ability to define the binning property with
binAs
, DBin
, FBin
, HBin
, MBin
, OBin
, PBin
, and TBin
has
been expanded by adding the AlreadyBinned
and BinAnchor
constructors to BinProperty
, as well as changing the Divide
constructor (as described below).
The StrokeCap
and StrokeJoin
types has been added. These are used
with MStrokeCap
, VBStrokeCap
, and ViewStrokeCap
and
MStrokeJoin
, VBStrokeJoin
, and ViewStrokeJoin
respectively.
The StackProperty
constructor has been added with the StOffset
and StSort
constructors. As discussed below this is a breaking change
since the old StackProperty type has been renamed to StackOffset
.
The ScaleProperty
type has seen significant enhancement, by adding
the constructors: SAlign
, SBase
, SBins
, SConstant
and
SExponent
. The ConfigurationProperty
tye has added ScSymLog
ScQuantile
,
ScQuantize
, and ScThreshold
.
The SortProperty
type has new constructors: CustomSort
,
ByRepeatOp
, ByFieldOp
, and ByChannel
. See the breaking-changes
section below for the constructors that were removed.
The AxisProperty
type has seen significant additions, including:
AxBandPosition
, AxDomainColor
, AxDomainDash
,
AxDomainDashOffset
, AxDomainOpacity
, AxDomainWidth
,
AxFormatAsNum
, AxFormatAsTemporal
, AxGridColor
, AxGridDash
,
AxGridDashOffset
, AxGridOpacity
, AxGridWidth
, AxLabelAlign
,
AxLabelBaseline
, AxLabelNoBound
, AxLabelBound
, AxLabelBoundValue
,
AxLabelColor
, AxLabelNoFlush
, AxLabelFlush
, AxLabelFlushValue
,
AxLabelFlushOffset
, AxLabelFont
, AxLabelFontSize
,
AxLabelFontStyle
, AxLabelFontWeight
, AxLabelLimit
,
AxLabelOpacity
, AxLabelSeparation
, AxTickColor
, AxTickDash
,
AxTickDashOffset
, AxTickExtra
, AxTickMinStep
, AxTickOffset
,
AxTickOpacity
, AxTickRound
, AxTickWidth
, AxNoTitle
,
AxTitleAnchor
, AxTitleBaseline
, AxTitleColor
, AxTitleFont
,
AxTitleFontSize
, AxTitleFontStyle
, AxTitleFontWeight
,
AxTitleLimit
, AxTitleOpacity
, AxTitleX
, and AxTitleY
.
The AxisConfig
has seen a similar enhancement, and looks similar
to the above apart from the constructors do not start with Ax
.
The LegendConfig
type has been significantly expanded and, as
discussed in the Breaking Changes section, changed. It has gained:
LeClipHeight
, LeColumnPadding
, LeColumns
, LeGradientDirection
,
LeGradientHorizontalMaxLength
, LeGradientHorizontalMinLength
,
LeGradientLength
, LeGradientOpacity
, LeGradientThickness
,
LeGradientVerticalMaxLength
, LeGradientVerticalMinLength
,
LeGridAlign
, LeLabelFontStyle
, LeLabelFontWeight
,
LeLabelOpacity
, LeLabelOverlap
, LeLabelPadding
,
LeLabelSeparation
, LeLayout
, LeLeX
, LeLeY
, LeRowPadding
,
LeSymbolBaseFillColor
, LeSymbolBaseStrokeColor
, LeSymbolDash
,
LeSymbolDashOffset
, LeSymbolDirection
, LeSymbolFillColor
,
LeSymbolOffset
, LeSymbolOpacity
, LeSymbolStrokeColor
, LeTitle
,
LeNoTitle
, LeTitleAnchor
, LeTitleFontStyle
, LeTitleOpacity
,
and LeTitleOrient
.
The LegendOrientation
type has gained LOTop
and LOBottom
.
The LegendLayout
and BaseLegendLayout
types are new, and used
with LeLayout
to define the legent orient group.
The LegendProperty
type gained: LClipHeight
, LColumnPadding
,
LColumns
, LCornerRadius
, LDirection
, LFillColor
,
LFormatAsNum
, LFormatAsTemporal
, LGradientLength
,
LGradientOpacity
, LGradientStrokeColor
, LGradientStrokeWidth
,
LGradientThickness
, LGridAlign
, LLabelAlign
, LLabelBaseline
,
LLabelColor
, LLabelFont
, LLabelFontSize
, LLabelFontStyle
,
LLabelFontWeight
, LLabelLimit
, LLabelOffset
, LLabelOpacity
,
LLabelOverlap
, LLabelPadding
, LLabelSeparation
, LRowPadding
,
LStrokeColor
, LSymbolDash
, LSymbolDashOffset
,
LSymbolFillColor
, LSymbolOffset
, LSymbolOpacity
, LSymbolSize
,
LSymbolStrokeColor
, LSymbolStrokeWidth
, LSymbolType
,
LTickMinStep
, LNoTitle
, LTitleAlign
, LTitleAnchor
,
LTitleBaseline
, LTitleColor
, LTitleFont
, LTitleFontSize
,
LTitleFontStyle
, LTitleFontWeight
, LTitleLimit
, LTitleOpacity
,
LTitleOrient
, LTitlePadding
, LeX
, and LeY
.
ConfigurationProperty
has gained the Identity
constructor. The
ProjectionProperty
type has gained PrScale
, PrTranslate
,
PrReflectX
, and PrReflectY
. The GraticuleProperty
type was
added to configure the appearance of graticules created with
graticule
.
The CompositionAlignment
type was added and is used with align
,
alignRC
, LeGridAlign
, and LGridAlign
.
The Bounds
type was added for use with bounds
.
The ImputeProperty
and ImputeProperty
types were added for use with
impute
and PImpute
.
The ScaleConfig
type has gained SCBarBandPaddingInner
,
SCBarBandPaddingOuter
, SCRectBandPaddingInner
, and
SCRectBandPaddingOuter
.
The SelectionProperty
type has gained Clear
, SInit
, and
SInitInterval
.
The Channel type has gained: ChLongitude
, ChLongitude2
,
ChLatitude
, ChLatitude2
, ChFill
, ChFillOpacity
, ChHref
,
ChKey
, ChStroke
, ChStrokeOpacity
. ChStrokeWidth
, ChText
,
and ChTooltip
.
The TitleConfig
type has gained: TFontStyle
, TFrame
, TStyle
,
and TZIndex
.
The TitleFrame
type is new and used with TFrame
from TitleConfig
.
The ViewBackground
type is new and used with viewBackground
.
The ViewConfig
type has gained ViewCornerRadius
, ViewOpacity
,
ViewStrokeCap
, ViewStrokeJoin
, and ViewStrokeMiterLimit
.
The ConfigurationProperty
type, used with configuration
, has
gained ConcatStyle
, FacetStyle
, GeoshapeStyle
, HeaderStyle
,
NamedStyles
(renamed to MarkNamedStyles
in 0.6.0.0),
and TrailStyle
constructors.
The ConcatConfig
type was added for use with the ConcatStyle
,
and the FacetConfig
type for the FacetStyle
configuration settings.
The HeaderProperty
type has gained: HFormatAsNum
,
HFormatAsTemporal
, HNoTitle
, HLabelAlign
, HLabelAnchor
,
HLabelAngle
, HLabelColor
, HLabelFont
, HLabelFontSize
,
HLabelLimit
, HLabelOrient
, HLabelPadding
, HTitleAlign
,
HTitleAnchor
, HTitleAngle
, HTitleBaseline
, HTitleColor
,
HTitleFont
, HTitleFontSize
, HTitleFontWeight
, HTitleLimit
,
HTitleOrient
, and HTitlePadding
.
The HyperlinkChannel
type has gained HBinned
.
The FacetChannel
type has gained FSort
, FTitle
, and FNoTitle
.
The TextChannel
type has gained TBinned
, TFormatAsNum
,
TFormatAsTemporal
, TTitle
, and TNoTitle
.
The TooltipContent
type was added, for use with MTooltip
.
The Symbol
type has gained: SymArrow
, SymStroke
,
SymTriangle
, SymTriangleLeft
, SymTriangleRight
, and
SymWedge
.
There are a number of breaking changes in this release (some of which were mentioned above):
- The
title
function now takes a second argument, a list ofTitleConfig
values for configuring the appearance of the title. - The
SReverse
constructor was removed fromScaleProperty
as it represented a Vega, rather than Vega-Lite, property. ThexSort
constructors are used to change the order of an item (e.g.PSort
,MSort
). - The
ScSequential
constructor was removed fromConfigurationProperty
asScLinear
should be used. - The
SortProperty
type has had a number of changes: theOp
,ByField
, andByRepeat
constructors have been removed, andByRepeatOp
,ByFieldOp
, andByChannel
constructors have been added. - The
AxTitleMaxLength
andTitleMaxLength
constructors have been removed (fromAxisProperty
andAxisConfig
respectively) as they are invalid. TheAxTitleLimit
(new in this release) andTitleLimit
constructors should be used instead. AxisProperty
: theAxValues
constructor has been changed from accepting a list of doubles toDataValues
. TheAxDates
constructor has been deprecated andAxValues
should be used instead.- There have been significant changes to the
LegendConfig
type: theEntryPadding
,GradientHeight
,GradientLabelBaseline
,GradientWidth
, andSymbolColor
constructors have been removed; the renaming constructors have been renamed so they all begin withLe
(e.g.Orient
is nowLeOrient
, andOrient
has been added toAxisConfig
); and new constructors have been added. - The
StackProperty
type has been renamed toStackOffset
and its constructors have changed, and a newStackProperty
type has been added (that references theStackOffset
type). - The
Average
constructor ofOperation
was removed, andMean
should be used instead. - The
LEntryPadding
constructor ofLegendProperty
was removed. - The arguments to the
MDataCondition
,TDataCondition
, andHDataCondition
constructors - ofMarkChannel
,TextChannel
, andHyperlinkChannel
respectively - have changed to support accepting multiple expressions. - The
MarkOrientation
type has been renamedOrientation
. - The constructors of the
ViewConfig
type have been renamed so they all begin withView
(to matchViewWidth
andViewHeight
). - The constructors of the
ProjectionProperty
type have been renamed so that they begin withPr
rather thanP
(to avoid conflicts with thePositionChannel
type). - The
Divide
constructor ofBinProperty
now takes a list of Doubles rather than two. - The
TitleConfig
type has gained the following constructors:TFontStyle
,TFrame
,TStyle
, andTZIndex
. TheTitleFrame
type was added for use withTFrame
. - The
ArgMax
andArgMin
constructors ofOperation
now take an optional field name, to allow them to be used as part of an encoding aggregation (e.g. withPAggregate
). - The "z index" value has changed from an
Int
to theZIndex
type. - The constructors for the
Symbol
type now all start withSym
, soCross
,Diamond
,TriangleUp
,TriangleDown
, andPath
have been renamed toSymCross
,SymDiamond
,SymTriangleUp
,SymTriangleDown
, andSymPath
, respectively. - The
Legend
type has been renamedLegendType
and its constructors have been renamedGradientLegend
andSymbolLegend
.