on package:hvega

Vega event stream selector that triggers a selection, or the empty string (which sets the property to false).
The name of the field used for encoding with an order channel.
Remove the title.
No overlap strategy to be applied when there is not space to show all items on an axis.
Create a value with this number. For use with OSelectionCondition and ODataCondition.
Instead of layering one view on top of another (superposition), we can place them side by side in a row or column (juxtaposition). In Vega-Lite this is referred to as concatenation: Open this visualization in the Vega Editor
let enc field = encoding
. position X [ PName "Cluster", PmType Nominal ]
. position Y [ PName field, PmType Quantitative, PAggregate Median ]

parallaxes = [ mark Bar [], enc "plx" [] ]
magnitudes = [ mark Bar [], enc "Gmag" [] ]

specs = map asSpec [ parallaxes, magnitudes ]

in toVegaLite
[ gaiaData
, vConcat specs
]
The hConcat function would align the two plots horizontally, rather than vertically (and is used in concatenatedSkyPlot). Note that as the axes are identical apart from the field for the y axis, the encoding has been moved into a function to enforce this constraint (this ensures the x axis is the same, which makes it easier to visually compare the two plots). However, there is no requirement that the two plots be "compatible" (they could use different data sources).
The alignment of the plots can be adjusted with spacing, which we use here to remove the vertical gap between the two plots (the example is written so that we can see the only difference between the two plot specifications is the addition of PAxis [] to the parallax plot). Open this visualization in the Vega Editor
let enc field flag = encoding
. position X ([ PName "Cluster", PmType Nominal ] ++
if flag then [ PAxis [] ] else [])
. position Y [ PName field, PmType Quantitative, PAggregate Median ]

parallaxes = [ mark Bar [], enc "plx" True [] ]
magnitudes = [ mark Bar [], enc "Gmag" False [] ]

specs = map asSpec [ parallaxes, magnitudes ]

in toVegaLite
[ gaiaData
, spacing 0
, vConcat specs
]
Even though we set spacing to 0 there is still a small gap between the plots: this can be removed by using bounds Flush, but we'll leave using that until the grand finale.
In skyPlotWithGraticules I used the Mercator projection to display the stars on the sky, but promised I would also show you data using the Orthographic projection. The main specification (that is, the argument of toVegaLite) starts with a change to the plot defaults, using configure to ensure that no border is drawn around the plot (note that in combinedPlot I do the same thing, but by setting the stroke color to Just "transparent" rather than Nothing). The default data stream is set up, to ensure we have "longitude" and "DE_ICRS" values to display. It then has three versions of the same visualization, varying only on rotation angle and label, stacked horizontally with hConcat. Each plot - created with the rSpec helper function - defines a plot size, uses the Orthographic projection with the given rotation (the lambda term of PrRotate) to change the center of the display, and then the plot itself is formed from four layers:
  1. sphere is used to indicate the area of the plot covered by the sky (filled with a blue variant);
  2. graticules are drawn at every 30 degrees (longitude, so 2 hours in Right Ascension) and 15 degrees (latitude);
  3. the stars are drawn using color to encode the parallax of the star and the symbol shape the cluster membership (although the density of points is such that it can be hard to make the shapes out);
  4. and a label is added at the center of the plot to indicate the Right Ascension (the label could be determined automatically from the rotation angle, but it was easier to just specify it directly).
Since the data values have two different encodings - color and shape - there are two legends added. I place them in different locations using LOrient: the parallax goes to the right of the plots (which is the default) and the symbol shapes to the bottom. Both use larger-than-default font sizes for the text (title and label). Open this visualization in the Vega Editor (although the link is long, and may not work with Internet Explorer)
let trans = transform
. calculateAs
"datum.RA_ICRS > 180 ? datum.RA_ICRS - 360 : datum.RA_ICRS"
"longitude"

axOpts field = [ PName field, PmType Quantitative ]
legend ttl o = MLegend [ LTitle ttl
, LOrient o
, LTitleFontSize 16
, LLabelFontSize 14
]
enc = encoding
. position Longitude (axOpts "longitude")
. position Latitude (axOpts "DE_ICRS")
. color [ MName "plx"
, MmType Quantitative
, MScale [ SType ScLog
, SScheme "viridis" []
]
, legend "parallax" LORight
]
. shape [ MName "Cluster"
, MmType Nominal
, legend "cluster" LOBottom
]
. tooltip [ TName "Cluster", TmType Nominal ]

stars = asSpec [ enc [], mark Point [] ]
grats = asSpec [ graticule [ GrStepMinor (30, 15) ]
, mark Geoshape [ MStroke "grey"
, MStrokeOpacity 0.5
, MStrokeWidth 0.5
]
]

lblData r h0 =
let r0 = -r
lbl = h0 <> "h"
in dataFromColumns []
. dataColumn "x" (Numbers [ r0 ])
. dataColumn "y" (Numbers [ 0 ])
. dataColumn "lbl" (Strings [ lbl ])

encLabels = encoding
. position Longitude (axOpts "x")
. position Latitude (axOpts "y")
. text [ TName "lbl", TmType Nominal ]
labels r h0 = asSpec [ lblData r h0 []
, encLabels []
, mark Text [ MAlign AlignCenter
, MBaseline AlignTop
, MdY 5
]
]

bg = asSpec [ sphere, mark Geoshape [ MFill "aliceblue" ] ]

rSpec r h0 = asSpec [ width 300
, height 300
, projection [ PrType Orthographic
, PrRotate r 0 0
]
, layer [ bg, grats, stars, labels r h0 ]
]

s1 = rSpec (-120) "8"
s2 = rSpec 0 "12"
s3 = rSpec 120 "4"

setup = configure . configuration (ViewStyle [ ViewNoStroke ])

in toVegaLite [ setup []
, gaiaData
, trans []
, hConcat [ s1, s2, s3 ] ]
The ability to determine the scale of a chart based on a selection is useful in implementing a common visualization design pattern, that of 'context and focus' (or sometimes referred to as 'overview and detail on demand'). We can achieve this by setting the scale of one view based on the selection in another. The detail view is updated whenever the selected region is changed through interaction: Open this visualization in the Vega Editor
let sel = selection . select "brush" Interval [ Encodings [ ChY ] ]

encContext = encoding
. position X [ PName "Gmag", PmType Quantitative, PScale [ SZero False ] ]
. position Y [ PName "plx", PmType Quantitative ]

specContext = asSpec [ width 400
, height 80
, sel []
, mark Point []
, encContext []
, title "Select a Y range to zoom in below" []
]

encDetail = encoding
. position X [ PName "Gmag"
, PmType Quantitative
, PScale [ SZero False ]
, PAxis [ AxNoTitle ]
]
. position Y [ PName "plx"
, PmType Quantitative
-- prior to 0.11.0.0 this was SDomain
, PScale [ SDomainOpt (DSelection "brush") ]
]
. color [ MName "Cluster", MmType Nominal ]

specDetail =
asSpec [ width 400, mark Point [], encDetail [] ]

in toVegaLite
[ gaiaData
, vConcat [ specContext, specDetail ]
]
Not shown here, but selecting a range of y-values in the top plot (specContext) will cause the second plot (specDetail) to zoom in on that range, as the selection is bound to the y axis of this plot via DSelection.
We can take advantage of browser event by using On to define which event to use, such as mouse movement over points: Open this visualization in the Vega Editor
let selLabel = "picked"
sel = selection
. select selLabel Multi [ On "mouseover" ]

in toVegaLite (sel [] : selectionProperties selLabel "Move the pointer to select a point")
The supported list of events is described in the Vega Event-Stream Selectors documentation. The addition of Nearest True to the list of properties sent to select would avoid the flickering, as the mouse moves between the stars.
The final BooleanOp value is Interval, which lets you drag a rectangle to select the interior points: Open this visualization in the Vega Editor
let selLabel = "naming is hard"
sel = selection
. select selLabel Interval [ ]

in toVegaLite (sel [] : selectionProperties selLabel "Drag a rectangle to select points")
The default interval option is to select a rectangle, but it can be restricted - such as to select all items within a range along a given axis using Encodings: Open this visualization in the Vega Editor
let selLabel = "naming is still hard"
sel = selection
. select selLabel Interval [ Encodings [ ChY ] ]

in toVegaLite (sel [] : selectionProperties selLabel "Drag to select points by parallax")
We'll come back to further things to do with interval selections when we get to interactive plots below (see bindScales).
This example is similar to layeredPlot but includes an x-axis encoding for the second layer. We use this to show the range of the data - so the minimum to maximum parallax range of each cluster - with the Rule type. The difference to the previous plot is that an extra positional encoding is added (Y2) to define the end point of each line (Y is used as the start point). Open this visualization in the Vega Editor
let plx op = position Y [ PName "plx", PmType Quantitative, PAggregate op ]
cluster = position X [ PName "Cluster", PmType Nominal ]

median = [ mark Circle [ MSize 20 ]
, encoding (plx Median [])
]
range = [ mark Rule [ ]
, encoding
. plx Min
. position Y2 [ PName "plx", PAggregate Max ]
$ []
]

in toVegaLite
[ gaiaData
, encoding (cluster [])
, layer (map asSpec [ median, range ])
, width 300
, height 300
]
The MSize option is used to change the size of the circles so that they do not drown out the lines (the size value indicates the area of the mark, and so for circles the radius is proportional to the square root of this size value; in practical terms I adjusted the value until I got something that looked sensible). Note that the y axis is automatically labelled with the different operation types that were applied - median, minimum, and maximum - although there is no indication of what marks map to these operations.
New in Vega Lite 4 is the ability to interact with the legend via the BindLegend option. In this case selecting on a cluster in the legend will highlight that cluster in the visualization (but not vice versa). Notice how the legend now also follows the MSelectionCondition rules (that is, the unselected items in the image below are also drawn in grey and are partially transparent). Open this visualization in the Vega Editor
let sel = selection
. select "pick" Single [ BindLegend
(BLField "Cluster")
]

in toVegaLite (sel [] : selectionProperties "pick" "Select a legend item")
The selection can easily be changed to allow multiple stars to be selected, using shift-click, by swapping from Single to Multi. Open this visualization in the Vega Editor
let selLabel = "this is just a label"
sel = selection
. select selLabel Multi []

in toVegaLite (sel [] : selectionProperties selLabel "Shift click to select points")
The only change here is to add a property to the selection - that is Nearest True - which means that the nearest point to the click will be highlighted. Open this visualization in the Vega Editor
let selLabel = "picked"
sel = selection
. select selLabel Single [ Nearest True ]

in toVegaLite (sel [] : selectionProperties selLabel "Select nearest point")
One consequence of this change is that once a point has been selected you can not remove this (i.e. un-select the point). This is in contrast to singleSelection, where clicking on an area with no stars would remove the previous selection. The Clear property can be added to the list to define a way to clear the selection.
This is the same data as loessExample, but using a linear regression model to try and explain the data. Practically, the only things that have changed are switching from loess to regression, and displaying all the data in a single visualization. Open this visualization in the Vega Editor
let simplify = transform
. filter (FExpr "(datum.DE_ICRS >= 0) & (datum.DE_ICRS <= 40)")

axis pos lbl = position pos [ PName lbl
, PmType Quantitative
, PScale [ SZero False ]
]
enc = encoding
. axis X "Gmag"
. axis Y "plx"
. color [ MName "Cluster" ]

rawLayer = asSpec [ enc [], mark Point [] ]

trans = transform
. regression "plx" "Gmag" [ RgGroupBy [ "Cluster" ] ]

trendLayer = asSpec [ trans []
, enc []
, mark Line [ MStroke "black"
, MStrokeWidth 2
]
]

in toVegaLite
[ width 300
, height 300
, gaiaData
, simplify []
, layer [ rawLayer, trendLayer ]
]
In this example I used the default method - RgLinear - but other options are possible (set with the RgMethod option).
The next several plots show different types of selection - select a single point, a range of plots, or follow the mouse - and all have the same basic structure. To avoid repetition, and mistakes, I am going to introduce a helper function which creates the plot structure but without the selection definition, and then use that to build up the plots. The helper function, selectionProperties, takes two arguments, which are the selection name and the plot title. The selection name is used to identify the selection, as a visualization can support multiple selections, and the plot title has been added mainly to show some minor customization (the use of TOrient to move the title to the bottom). The definition of this helper function is:
selectionProps selName label =
let posOpts field = [ PName field
, PmType Quantitative
, PScale [ SZero False ]
]

enc = encoding
. position X (posOpts "Gmag")
. position Y (posOpts "plx")

. color [ MSelectionCondition (SelectionName selName)
[ MName "Cluster", MmType Nominal ]
[ MString "grey" ]
]

. opacity [ MSelectionCondition (SelectionName selName)
[ MNumber 1.0 ]
[ MNumber 0.3 ]
]

. size [ MSelectionCondition (SelectionName selName)
[ MNumber 40 ]
[ MNumber 5 ]
]

trans = transform
. filter (FExpr "datum.DE_ICRS < -20")

in [ gaiaData
, trans []
, mark Point []
, enc []
, title label [ TOrient SBottom ]
]
The three non-selection-related features added here are that SZero is used to tell Vega Lite that we do not need 0 displayed on either axis, which leads to a "tight" bounding box around the data, a filter is used to select a subset of rows, namely only those with a declination less than -20 (via FExpr), and the plot title is moved to the bottom with TOrient. The main change is that the selection is used in the encoding section, identified by name, using SelectionName and the supplied argument. It is used as a filter for the encoding section, where MSelectionCondition defines the properties to use when the selection occurs (the first list of properties) and when it does not (the second list). This is used for three different encodings:
  • color, where the selected star is labelled by its cluster color, and all the other are grey;
  • opacity, so that the selected star is fully opaque whereas un-selected stars are partially transparent;
  • and size, so that the selected star is much bigger than the others.
When no selection has been made - such as when the visualization is first created - then all points are encoded with the "selected" case (so colorful, fully opaque, and large in this case).
The actual plot just requires the selection information to be defined and then added to the plot properties: Open this visualization in the Vega Editor
let selLabel = "picked"
sel = selection
. select selLabel Single []

in toVegaLite (sel [] : selectionProperties selLabel "Select a point")
The selection function is used to define the selection, via one or more applications of the select function. The form of select is that the selection is named, in this case we use "picked", and the type is given (a Single click), and then options, which in our case there aren't any, so an empty list is used. Note that hvega does not track the selection names, and will allow you to use a name that you have not defined.
For example, we can adjust the visualization to select all stars in the same cluster, which is useful in this case since the Blanco1 and IC2391 clusters occupy the same space in the magnitude-parallax plane. This is invoked simply by adding the Fields constructor to the select parameters naming the fields onto which we wish to project our selection. Additionally, we have set the default selection with Empty so that if nothing is selected, the selection is empty (as we have previously seen, without this the default selection is the entire encoded dataset). Open this visualization in the Vega Editor
let sel = selection
. select "pick" Single [ Fields [ "Cluster" ]
, Empty
, Nearest True
]

in toVegaLite (sel [] : selectionProperties "pick" "Select a point, select a cluster")
The Elm Vega-Lite walkthrough uses a dataset which has a column for which a range-slider makes sense. The dataset I'm using is less rich, and so I am going to use a HTML select widget - a drop-down list of values - instead. This lets the user select all stars from a given cluster, and is introduced with the Bind and ISelect constructors. The InOptions list is given the values of the Cluster column that can be selected: I start with a value not in the list (none) just to indicate that no values are selected, and then the list of clusters in this sub-sample (remembering that selectionProperties applies a declination cut off). Eagle-eyed readers will note that the cluster names in this list (the clusters variable) end in spaces: this is because the input data file has the cluster names stored in an eight-character field, even though it is a tab-separated file. This surprised me when I first tried this visualization, and using the value "Blanco1" did not select anything! Isn't working with data so much fun! Open this visualization in the Vega Editor
let picked = "picked"

clusters = [ "none", "Blanco1 ", "IC2391  ", "IC2602  ", "NGC2451 " ]
sel = selection
. select picked Single [ Fields [ "Cluster" ]
, Bind [ ISelect "Cluster" [ InOptions clusters ] ]
, Empty
]

conf = configure
. configuration (BackgroundStyle "beige")

in toVegaLite (conf [] :
sel [] :
selectionProperties picked "Please select a cluster")
Originally this example had the selection working both ways - that is the HTML widget can be used to select a cluster and clicking on a point on the visualization updated the HTML widget. However, this no-longer happens and I don't know whether it is a change in Vega-Lite or I changed something in the visualization! Unlike the other plots shown in the tutorial, this is a screen grab rather than a PNG file created by Vega Embed. The background color was changed - following the approach used in stripPlotWithBackground - to show where the visualization "ends" and the HTML select element starts. It also shows the Vega Embed "drop-down" menu in the top-right corner, namely the three dots in a circle.
Interpret visualization dimensions to be for the data rectangle (external padding added to this size).
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 True. The second is the encoding if none of the expressions evaluate as True.
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.
No autosizing is applied.