Copyright | (c) Douglas Burke 2018-2019 |
---|---|
License | BSD3 |
Maintainer | dburke.gw@gmail.com |
Stability | unstable |
Portability | CPP, OverloadedStrings, TupleSections |
Safe Haskell | None |
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
- Selection Resolution
- Making conditional channel encodings
- Top-level Settings
- Style Setting
- Axis Configuration Options
- Legend Configuration Options
- Scale Configuration Options
- Scale Range Configuration Options
- Title Configuration Options
- View Configuration Options
- Facet Configuration Options
- Concatenated View Configuration Options
- 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 3 of the
JSON schema. The
ihaskell-hvega module provides an easy way to embed Vega-Lite
visualizations in an IHaskell notebook (using
Vega-Embed).
Although this is based on the Elm module, there are differences, such
as using type constructors rather than functions for many properties -
such as PName "HorsePower"
rather than pName "HorsePower"
-
and the return value of toVegaLite
. The intention is to keep close
to the Elm module, but it is more a guide than an absolute
requirement!
Please see Graphics.Vega.Tutorials.VegaLite for an introduction
to using hvega
to create visualizations.
Example
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 example, we'll assume the latter.
Let's say we have the following plot declaration in a module:
{-# language OverloadedStrings #-} vl1 = let desc = "A very exciting bar chart" dat =dataFromRows
[Parse
[("start",FoDate
"%Y-%m-%d")]] .dataRow
[("start",Str
"2011-03-25"), ("count",Number
23)] .dataRow
[("start",Str
"2011-04-02"), ("count",Number
45)] .dataRow
[("start",Str
"2011-04-12"), ("count",Number
3)] barOpts = [MOpacity
0.4,MColor
"teal"] enc =encoding
.position
X
[PName
"start",PmType
Temporal
,PAxis
[AxTitle
"Inception date"]] .position
Y
[PName
"count",PmType
Quantitative
] intoVegaLite
[description
desc,background
"white" , dat [],mark
Bar
barOpts, enc []]
We can inspect how the encoded JSON looks like in an GHCi session:
>encode
$fromVL
vl1 > "{"mark":{"color":"teal","opacity":0.4,"type":"bar"},"data":{"values":[{"start":"2011-03-25","count":23},{"start":"2011-04-02","count":45},{"start":"2011-04-12","count":3}],"format":{"parse":{"start":"date:'%Y-%m-%d'"}}},"$schema":"https:/vega.github.ioschemavega-litev3.json","encoding":{"x":{"field":"start","type":"temporal","axis":{"title":"Inception date"}},"y":{"field":"count","type":"quantitative"}},"background":"white","description":"A very exciting bar chart"}"
The produced JSON can then be processed with vega-lite, which renders the following image:
which can also be displayed in the Vega Editor.
Output can be achieved in a Jupyter Lab session with the vlShow
function,
provided by ihaskell-vega
, or toHtmlFile
can be used to write out a page of
HTML that includes pointer to JavaScript files which will display a Vega-Lite
specification (there are also functions which provide more control over
the embedding).
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 -> VLSpec
- 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)
- type BuildLabelledSpecs = [LabelledSpec] -> [LabelledSpec]
- type Angle = Double
- type Color = Text
- type Opacity = Double
- type ZIndex = Natural
- combineSpecs :: [LabelledSpec] -> VLSpec
- 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 :: Text -> DataValues -> [DataColumn] -> [DataColumn]
- dataRow :: [(Text, 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 -> Text -> Data
- sphere :: Data
- graticule :: [GraticuleProperty] -> Data
- data GraticuleProperty
- data Format
- data DataType
- transform :: [LabelledSpec] -> 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] -> [Text] -> BuildLabelledSpecs
- joinAggregate :: [VLSpec] -> [WindowProperty] -> BuildLabelledSpecs
- opAs :: Operation -> Text -> Text -> VLSpec
- timeUnitAs :: TimeUnit -> Text -> Text -> BuildLabelledSpecs
- data Operation
- binAs :: [BinProperty] -> Text -> Text -> BuildLabelledSpecs
- data BinProperty
- stack :: Text -> [Text] -> Text -> Text -> [StackProperty] -> BuildLabelledSpecs
- data StackProperty
- data StackOffset
- = StZero
- | StNormalize
- | StCenter
- | NoStack
- calculateAs :: Text -> Text -> BuildLabelledSpecs
- filter :: Filter -> BuildLabelledSpecs
- data Filter
- data FilterRange
- flatten :: [Text] -> BuildLabelledSpecs
- flattenAs :: [Text] -> [Text] -> BuildLabelledSpecs
- fold :: [Text] -> BuildLabelledSpecs
- foldAs :: [Text] -> Text -> Text -> BuildLabelledSpecs
- lookup :: Text -> Data -> Text -> [Text] -> BuildLabelledSpecs
- lookupAs :: Text -> Data -> Text -> Text -> BuildLabelledSpecs
- impute :: Text -> Text -> [ImputeProperty] -> BuildLabelledSpecs
- data ImputeProperty
- data ImMethod
- sample :: Int -> BuildLabelledSpecs
- window :: [([Window], Text)] -> [WindowProperty] -> BuildLabelledSpecs
- data Window
- data WOperation
- data WindowProperty
- mark :: Mark -> [MarkProperty] -> PropertySpec
- data Mark
- data MarkProperty
- = MAlign HAlign
- | MAngle Angle
- | MBandSize Double
- | MBaseline VAlign
- | MBinSpacing Double
- | MBorders [MarkProperty]
- | MBox [MarkProperty]
- | MClip Bool
- | MColor Color
- | MCursor Cursor
- | MContinuousBandSize Double
- | MDiscreteBandSize Double
- | MdX Double
- | MdY Double
- | MExtent MarkErrorExtent
- | MFill Text
- | MFilled Bool
- | MFillOpacity Opacity
- | MFont Text
- | MFontSize Double
- | MFontStyle Text
- | MFontWeight FontWeight
- | MHeight Double
- | MHRef Text
- | MInterpolate MarkInterpolation
- | MLine LineMarker
- | MMedian [MarkProperty]
- | MOpacity Opacity
- | MOrder Bool
- | MOrient Orientation
- | MOutliers [MarkProperty]
- | MNoOutliers
- | MPoint PointMarker
- | MRadius Double
- | MRule [MarkProperty]
- | MShape Symbol
- | MShortTimeLabels Bool
- | MSize Double
- | MStroke Text
- | MStrokeCap StrokeCap
- | MStrokeDash [Double]
- | MStrokeDashOffset Double
- | MStrokeJoin StrokeJoin
- | MStrokeMiterLimit Double
- | MStrokeOpacity Opacity
- | MStrokeWidth Double
- | MStyle [Text]
- | MTension Double
- | MText Text
- | MTheta Double
- | MThickness Double
- | MTicks [MarkProperty]
- | MTooltip TooltipContent
- | MWidth Double
- | MX Double
- | MX2 Double
- | MXOffset Double
- | MX2Offset Double
- | MY Double
- | MY2 Double
- | MYOffset Double
- | MY2Offset Double
- 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 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 :: [LabelledSpec] -> PropertySpec
- data Measurement
- position :: Position -> [PositionChannel] -> BuildLabelledSpecs
- data Position
- data PositionChannel
- data SortProperty
- data SortField
- data AxisProperty
- = AxBandPosition Double
- | AxDomain Bool
- | AxDomainColor Color
- | AxDomainDash [Double]
- | AxDomainDashOffset Double
- | AxDomainOpacity Opacity
- | AxDomainWidth Double
- | AxFormat Text
- | AxFormatAsNum
- | AxFormatAsTemporal
- | AxGrid Bool
- | AxGridColor Color
- | AxGridDash [Double]
- | AxGridDashOffset Double
- | AxGridOpacity Opacity
- | AxGridWidth Double
- | AxLabels Bool
- | AxLabelAlign HAlign
- | AxLabelAngle Angle
- | AxLabelBaseline VAlign
- | AxLabelNoBound
- | AxLabelBound
- | AxLabelBoundValue Double
- | AxLabelColor Color
- | AxLabelNoFlush
- | AxLabelFlush
- | AxLabelFlushValue Double
- | AxLabelFlushOffset Double
- | AxLabelFont Text
- | AxLabelFontSize Double
- | AxLabelFontStyle Text
- | AxLabelFontWeight FontWeight
- | AxLabelLimit Double
- | AxLabelOpacity Opacity
- | AxLabelOverlap OverlapStrategy
- | AxLabelPadding Double
- | AxLabelSeparation Double
- | AxMaxExtent Double
- | AxMinExtent Double
- | AxOffset Double
- | AxOrient Side
- | AxPosition Double
- | AxTicks Bool
- | AxTickColor Color
- | AxTickCount Int
- | AxTickDash [Double]
- | AxTickDashOffset Double
- | 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
- | AxTitleOpacity Opacity
- | AxTitlePadding Double
- | AxTitleX Double
- | AxTitleY Double
- | AxValues DataValues
- | AxDates [[DateTime]]
- | AxZIndex ZIndex
- data HAlign
- data VAlign
- data OverlapStrategy
- data Side
- size :: [MarkChannel] -> BuildLabelledSpecs
- color :: [MarkChannel] -> BuildLabelledSpecs
- fill :: [MarkChannel] -> BuildLabelledSpecs
- stroke :: [MarkChannel] -> BuildLabelledSpecs
- strokeWidth :: [MarkChannel] -> BuildLabelledSpecs
- opacity :: [MarkChannel] -> BuildLabelledSpecs
- fillOpacity :: [MarkChannel] -> BuildLabelledSpecs
- strokeOpacity :: [MarkChannel] -> BuildLabelledSpecs
- shape :: [MarkChannel] -> BuildLabelledSpecs
- data MarkChannel
- = MName Text
- | MRepeat 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
- | MNumber Double
- | MString Text
- | MBoolean Bool
- data LegendType
- data LegendProperty
- = LClipHeight Double
- | LColumnPadding Double
- | LColumns Int
- | LCornerRadius Double
- | LDirection Orientation
- | LFillColor Color
- | LFormat Text
- | LFormatAsNum
- | LFormatAsTemporal
- | LGradientLength Double
- | LGradientOpacity Opacity
- | LGradientStrokeColor Color
- | LGradientStrokeWidth Double
- | LGradientThickness Double
- | LGridAlign CompositionAlignment
- | LLabelAlign HAlign
- | LLabelBaseline VAlign
- | LLabelColor Color
- | 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 [Double]
- | LSymbolDashOffset Double
- | LSymbolFillColor Color
- | LSymbolOffset Double
- | LSymbolOpacity Opacity
- | LSymbolSize Double
- | LSymbolStrokeColor Color
- | LSymbolStrokeWidth Double
- | LSymbolType Symbol
- | LTickCount Double
- | LTickMinStep Double
- | LTitle Text
- | LNoTitle
- | LTitleAlign HAlign
- | LTitleAnchor APosition
- | LTitleBaseline VAlign
- | LTitleColor Color
- | LTitleFont Text
- | LTitleFontSize Double
- | LTitleFontStyle Text
- | LTitleFontWeight FontWeight
- | LTitleLimit Double
- | LTitleOpacity Opacity
- | LTitleOrient Side
- | LTitlePadding Double
- | LType LegendType
- | LValues LegendValues
- | LeX Double
- | LeY Double
- | LZIndex ZIndex
- data LegendOrientation
- data LegendValues
- text :: [TextChannel] -> BuildLabelledSpecs
- tooltip :: [TextChannel] -> BuildLabelledSpecs
- tooltips :: [[TextChannel]] -> BuildLabelledSpecs
- data TextChannel
- = TName Text
- | TAggregate Operation
- | TBin [BinProperty]
- | TBinned
- | TDataCondition [(BooleanOp, [TextChannel])] [TextChannel]
- | TFormat Text
- | TFormatAsNum
- | TFormatAsTemporal
- | TmType Measurement
- | TRepeat Arrangement
- | TSelectionCondition BooleanOp [TextChannel] [TextChannel]
- | TTitle Text
- | TNoTitle
- | TTimeUnit TimeUnit
- data FontWeight
- hyperlink :: [HyperlinkChannel] -> BuildLabelledSpecs
- data HyperlinkChannel
- order :: [OrderChannel] -> BuildLabelledSpecs
- data OrderChannel
- row :: [FacetChannel] -> BuildLabelledSpecs
- column :: [FacetChannel] -> BuildLabelledSpecs
- detail :: [DetailChannel] -> BuildLabelledSpecs
- data DetailChannel
- data ScaleProperty
- = SType Scale
- | SAlign Double
- | SBase Double
- | SBins [Double]
- | SClamp Bool
- | SConstant Double
- | SDomain ScaleDomain
- | SExponent Double
- | SInterpolate CInterpolate
- | SNice ScaleNice
- | SPadding Double
- | SPaddingInner Double
- | SPaddingOuter Double
- | SRange ScaleRange
- | SRangeStep (Maybe Double)
- | SRound Bool
- | SScheme Text [Double]
- | SZero Bool
- data Scale
- = ScLinear
- | ScPow
- | ScSqrt
- | ScLog
- | ScSymLog
- | ScTime
- | ScUtc
- | ScOrdinal
- | ScBand
- | ScPoint
- | ScBinLinear
- | ScBinOrdinal
- | ScQuantile
- | ScQuantize
- | ScThreshold
- categoricalDomainMap :: [(Text, Text)] -> [ScaleProperty]
- domainRangeMap :: (Double, Text) -> (Double, Text) -> [ScaleProperty]
- data ScaleDomain
- = DNumbers [Double]
- | DStrings [Text]
- | DDateTimes [[DateTime]]
- | DSelection Text
- | Unaggregated
- data ScaleRange
- data ScaleNice
- 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 :: [LabelledSpec] -> PropertySpec
- resolution :: Resolve -> BuildLabelledSpecs
- data Resolve
- = RAxis [(Channel, Resolution)]
- | RLegend [(Channel, Resolution)]
- | RScale [(Channel, Resolution)]
- data Channel
- = ChX
- | ChY
- | ChX2
- | ChY2
- | ChLongitude
- | ChLongitude2
- | ChLatitude
- | ChLatitude2
- | ChColor
- | ChFill
- | ChFillOpacity
- | ChHref
- | ChKey
- | ChStroke
- | ChStrokeOpacity
- | ChStrokeWidth
- | ChOpacity
- | ChShape
- | ChSize
- | ChText
- | ChTooltip
- data Resolution
- repeat :: [RepeatFields] -> PropertySpec
- repeatFlow :: [Text] -> PropertySpec
- data RepeatFields
- = RowFields [Text]
- | ColumnFields [Text]
- 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
- | HTitle Text
- | HNoTitle
- | HLabelAlign HAlign
- | HLabelAnchor APosition
- | HLabelAngle Angle
- | HLabelColor Color
- | HLabelFont Text
- | HLabelFontSize Double
- | HLabelLimit Double
- | HLabelOrient Side
- | HLabelPadding Double
- | HTitleAlign HAlign
- | HTitleAnchor APosition
- | HTitleAngle Angle
- | HTitleBaseline VAlign
- | HTitleColor Color
- | HTitleFont Text
- | HTitleFontSize Double
- | HTitleFontWeight Text
- | HTitleLimit Double
- | HTitleOrient Side
- | HTitlePadding Double
- selection :: [LabelledSpec] -> PropertySpec
- select :: Text -> Selection -> [SelectionProperty] -> BuildLabelledSpecs
- data Selection
- data SelectionProperty
- = Empty
- | BindScales
- | On Text
- | Clear Text
- | Translate Text
- | Zoom Text
- | Fields [Text]
- | Encodings [Channel]
- | SInit [(Text, 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 InputProperty
- data SelectionMarkProperty
- data SelectionResolution
- = Global
- | Union
- | Intersection
- data BooleanOp
- name :: Text -> PropertySpec
- description :: Text -> PropertySpec
- height :: Double -> PropertySpec
- width :: Double -> PropertySpec
- padding :: Padding -> PropertySpec
- autosize :: [Autosize] -> PropertySpec
- background :: Text -> PropertySpec
- usermetadata :: Object -> PropertySpec
- data Padding
- data Autosize
- title :: Text -> [TitleConfig] -> PropertySpec
- viewBackground :: [ViewBackground] -> PropertySpec
- data ViewBackground
- configure :: [LabelledSpec] -> PropertySpec
- configuration :: ConfigurationProperty -> BuildLabelledSpecs
- data ConfigurationProperty
- = AreaStyle [MarkProperty]
- | Autosize [Autosize]
- | Axis [AxisConfig]
- | AxisBand [AxisConfig]
- | AxisBottom [AxisConfig]
- | AxisLeft [AxisConfig]
- | AxisRight [AxisConfig]
- | AxisTop [AxisConfig]
- | AxisX [AxisConfig]
- | AxisY [AxisConfig]
- | Background Text
- | BarStyle [MarkProperty]
- | CircleStyle [MarkProperty]
- | ConcatStyle [ConcatConfig]
- | CountTitle Text
- | FacetStyle [FacetConfig]
- | FieldTitle FieldTitleProperty
- | GeoshapeStyle [MarkProperty]
- | HeaderStyle [HeaderProperty]
- | Legend [LegendConfig]
- | LineStyle [MarkProperty]
- | MarkStyle [MarkProperty]
- | NamedStyle Text [MarkProperty]
- | NamedStyles [(Text, [MarkProperty])]
- | NumberFormat Text
- | Padding Padding
- | PointStyle [MarkProperty]
- | Projection [ProjectionProperty]
- | Range [RangeConfig]
- | RectStyle [MarkProperty]
- | RemoveInvalid Bool
- | RuleStyle [MarkProperty]
- | Scale [ScaleConfig]
- | SelectionStyle [(Selection, [SelectionProperty])]
- | SquareStyle [MarkProperty]
- | Stack StackOffset
- | TextStyle [MarkProperty]
- | TickStyle [MarkProperty]
- | TimeFormat Text
- | TitleStyle [TitleConfig]
- | TrailStyle [MarkProperty]
- | View [ViewConfig]
- data AxisConfig
- = BandPosition Double
- | Domain Bool
- | DomainColor Color
- | DomainDash [Double]
- | DomainDashOffset Double
- | DomainOpacity Opacity
- | DomainWidth Double
- | Grid Bool
- | GridColor Color
- | GridDash [Double]
- | GridDashOffset Double
- | 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
- | LabelOpacity Opacity
- | LabelOverlap OverlapStrategy
- | LabelPadding Double
- | LabelSeparation Double
- | MaxExtent Double
- | MinExtent Double
- | NoTitle
- | Orient Side
- | ShortTimeLabels Bool
- | Ticks Bool
- | TickColor Color
- | TickDash [Double]
- | TickDashOffset Double
- | 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
- | TitleOpacity Opacity
- | TitlePadding Double
- | TitleX Double
- | TitleY Double
- data LegendConfig
- = LeClipHeight Double
- | LeColumnPadding Double
- | LeColumns Int
- | LeCornerRadius Double
- | LeFillColor Color
- | LeGradientDirection Orientation
- | LeGradientHorizontalMaxLength Double
- | LeGradientHorizontalMinLength Double
- | LeGradientLabelLimit Double
- | LeGradientLabelOffset Double
- | LeGradientLength Double
- | LeGradientOpacity Opacity
- | LeGradientStrokeColor Color
- | LeGradientStrokeWidth Double
- | LeGradientThickness Double
- | LeGradientVerticalMaxLength Double
- | LeGradientVerticalMinLength Double
- | LeGridAlign CompositionAlignment
- | LeLabelAlign HAlign
- | LeLabelBaseline VAlign
- | LeLabelColor Color
- | LeLabelFont 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
- | LeShortTimeLabels Bool
- | LeStrokeColor Color
- | LeStrokeDash [Double]
- | LeStrokeWidth Double
- | LeSymbolBaseFillColor Color
- | LeSymbolBaseStrokeColor Color
- | LeSymbolDash [Double]
- | LeSymbolDashOffset Double
- | LeSymbolDirection Orientation
- | LeSymbolFillColor Color
- | LeSymbolOffset Double
- | LeSymbolOpacity Opacity
- | LeSymbolSize Double
- | LeSymbolStrokeColor Color
- | LeSymbolStrokeWidth Double
- | LeSymbolType Symbol
- | LeTitle Text
- | LeNoTitle
- | LeTitleAlign HAlign
- | LeTitleAnchor APosition
- | LeTitleBaseline VAlign
- | LeTitleColor Color
- | LeTitleFont Text
- | LeTitleFontSize Double
- | LeTitleFontStyle Text
- | LeTitleFontWeight FontWeight
- | LeTitleLimit Double
- | LeTitleOpacity Opacity
- | LeTitleOrient Side
- | LeTitlePadding Double
- 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
- | SCRangeStep (Maybe Double)
- | SCRound Bool
- | SCTextXRangeStep Double
- | SCUseUnaggregatedDomain Bool
- data RangeConfig
- data TitleConfig
- data TitleFrame
- data ViewConfig
- = ViewWidth Double
- | ViewHeight Double
- | ViewClip Bool
- | ViewCornerRadius Double
- | ViewFill (Maybe Text)
- | ViewFillOpacity Opacity
- | ViewOpacity Opacity
- | ViewStroke (Maybe Text)
- | ViewStrokeCap StrokeCap
- | ViewStrokeDash [Double]
- | ViewStrokeDashOffset Double
- | ViewStrokeJoin StrokeJoin
- | ViewStrokeMiterLimit Double
- | ViewStrokeOpacity Opacity
- | ViewStrokeWidth Double
- data APosition
- data FieldTitleProperty
- data FacetConfig
- data ConcatConfig
- data DataValue
- data DataValues
- data DateTime
- data MonthName
- data DayName
- data TimeUnit
- = Year
- | YearQuarter
- | YearQuarterMonth
- | YearMonth
- | YearMonthDate
- | YearMonthDateHours
- | YearMonthDateHoursMinutes
- | YearMonthDateHoursMinutesSeconds
- | Quarter
- | QuarterMonth
- | Month
- | MonthDate
- | Date
- | Day
- | Hours
- | HoursMinutes
- | HoursMinutesSeconds
- | Minutes
- | MinutesSeconds
- | Seconds
- | SecondsMilliseconds
- | Milliseconds
- | Utc TimeUnit
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 3 of Vega-Lite,
although there are some differences, in part because of bugs in hvega
-
in which case please report an issue - but also because of issues with the Vega-Lite spec (for instance there
are several minor issues I have reported against version 3.3.0 of the
Vega-Lite schema).
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. |
-> [PropertySpec] | The visualization. |
-> VegaLite |
A version of toVegaLite
that allows you to change the Vega-Lite
schema version of the visualization.
toVegaLiteSchema
vlSchema4
props
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.
At the time of writing the latest version 4 schema - which
is https://vega.github.io/schema/vega-lite/v4.0.0-beta.0.json
-
can be specified as
vlSchema 4 (Just 0) (Just 0) (Just "-beta.0")
whereas
vlSchema 4 Nothing Nothing Nothing
refers to the latest version.
fromVL :: VegaLite -> VLSpec Source #
Extract the specification for passing to a VegaLite 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
,width
,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 | See |
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.
type BuildLabelledSpecs = [LabelledSpec] -> [LabelledSpec] Source #
Represent those functions which can be chained together using function composition to append new specifications onto an existing list.
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%)"
Since: 0.4.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 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
combineSpecs :: [LabelledSpec] -> VLSpec Source #
Combines a list of labelled specifications into a single specification. This is useful when you wish to create a single page with multiple visulizualizations.
combineSpecs
[ ( "vis1", myFirstVis )
, ( "vis2", mySecondVis )
, ( "vis3", myOtherVis )
]
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 3, 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 :: Text -> 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 :: [(Text, 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 |
-> Text | 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 [(Text, 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.
transform :: [LabelledSpec] -> PropertySpec Source #
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 include: aggregate
, binAs
,
calculateAs
, impute
, joinAggregate
, lookup
, lookupAs
,
flattenAs
, foldAs
, 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: |
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. |
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. |
-> [Text] | The "group by" fields. |
-> BuildLabelledSpecs |
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] -> BuildLabelledSpecs 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. |
-> Text | The field to bin. |
-> Text | The name of the binned data created by this routine. |
-> BuildLabelledSpecs |
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
Month
"date" "monthly" enc =encoding
.position
X
[PName
"date",PmType
Temporal
,PTimeUnit
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 Text) | 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 Text) | 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 |
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
|
-> Text | The field to bin. |
-> Text | The label for the binned data. |
-> BuildLabelledSpecs |
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 |
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.
:: Text | The field to be stacked. |
-> [Text] | The fields to group by. |
-> Text | The output field name (start). |
-> Text | The output field name (end). |
-> [StackProperty] | Offset and sort properties. |
-> BuildLabelledSpecs |
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.
:: Text | The calculation to perform, supporting the Vega-Lite expression syntax. |
-> Text | The field to assign the new values. |
-> BuildLabelledSpecs |
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 -> BuildLabelledSpecs 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-Lite 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 Text DataValue | Filter a data stream so that only data in a given field equal to the given value are used. |
FLessThan Text 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 Text 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 Text 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 Text 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 Text | 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 Text | Filter a data stream so that only data in a given field that are within the given interactive selection are used. sel = |
FOneOf Text DataValues | Filter a data stream so that only data in a given field contained in the given list of values are used. |
FRange Text 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 Text | 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. The first argument is the inclusive minimum vale to accept and the second the inclusive maximum.
Flattening
flatten :: [Text] -> BuildLabelledSpecs Source #
Map array-valued fields to a set of individual data objects, one per array entry.
See also flattenAs
.
Since: 0.4.0.0
:: [Text] | |
-> [Text] | The names of the output fields. |
-> BuildLabelledSpecs |
Similar to flatten
but allows the new output fields to be named.
Since: 0.4.0.0
fold :: [Text] -> BuildLabelledSpecs Source #
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. This performs the same function as the
pivot_longer and
gather
operations in the R tidyverse.
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
:: [Text] | |
-> Text | The name for the |
-> Text | The name for the |
-> BuildLabelledSpecs |
A fold
where the key
and value
fields can be renamed.
Since: 0.4.0.0
Relational Joining (lookup)
See the Vega-Lite lookup documentation.
:: Text | 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 |
-> Text | The name of the field in the secondary data source to match against the primary key. |
-> [Text] | The list of fields to store when the keys match. |
-> BuildLabelledSpecs |
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).
Unlike lookupAs
, this function will only return the specific fields
named in the fourth parameter. If you wish to return the entire set of
fields in the secondary data source as a single object, use
lookupAs
.
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.
trans =transform
.lookup
"person" (dataFromUrl
"data/lookup_people.csv" []) "name" ["age", "height"]
:: Text | 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 |
-> Text | The name of the field in the secondary data source to match against the primary key. |
-> Text | The field name for the new data. |
-> BuildLabelledSpecs |
Perform an object lookup between two data sources. This allows you to
find values in one data source based on the values in another (like a
relational join). Unlike lookup
, this function returns the entire
set of field values from the secondary data source when keys
match. Those fields are stored as an object with the name provided in
the fourth parameter.
In the following example, personDetails
would reference all the
field values in lookup_people.csv
for each row where the value in
the name
column in that file matches the value of person
in the
primary data source.
transform
.lookupAs
"person" (dataFromUrl
"data/lookup_people.csv" []) "name" "personDetails"
If the data contained columns called age
and height
then they would
then be accessed as personDetails.age
and personDetails.height
- for
example:
encoding
.position
X [PName
"personDetails.age",PmType
Temporal
,PTimeUnit
Year
,PTitle
"Age"] .position
Y [PName
"personDetails.height",PmType
Quantitative
,PTitle
"Height"]
See the Vega-Lite documentation for further details.
Data Imputation
Impute missing data. See the Vega-Lite impute documentation.
:: Text | The data field to process. |
-> Text | The key field to uniquely identify data objects within a group. |
-> [ImputeProperty] | Define how the imputation works. |
-> BuildLabelledSpecs |
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" [ImputeProperty
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 [Text] | 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 -> BuildLabelledSpecs 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
Window Transformations
See the Vega-Lite window transform field and window transform documentation.
:: [([Window], Text)] | The window-transform definition and associated output name. |
-> [WindowProperty] | The window transform. |
-> BuildLabelledSpecs |
Window transform for performing calculations over sorted groups of data objects such as ranking, lead/lag analysis, running sums and averages.
The first parameter is a list of tuples each comprising a window transform field definition and an output name. The second is the window transform definition.
transform
.window
[ ( [WAggregateOp
Sum
,WField
Time ], TotalTime ) ] [WFrame
Nothing Nothing ]
Since: 0.4.0.0
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 Text | 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 [Text] | 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.
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. |
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.
The Vega-Lite specification supports setting those properties that take
[
also to a boolean value. This is currently not
supported in MarkProperty
]hvega
.
MAlign HAlign | Horizontal alignment of a text mark. |
MAngle Angle | Rotation angle of a text mark. |
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 |
MBorders [MarkProperty] | Border properties for an Since: 0.4.0.0 |
MBox [MarkProperty] | Box-symbol properties for a Since: 0.4.0.0 |
MClip Bool | Should a mark be clipped to the enclosing group's dimensions. |
MColor Color | Default color of a mark. Note that |
MCursor Cursor | Cursor to be associated with a hyperlink mark. |
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. |
MExtent MarkErrorExtent | Extent of whiskers used with Since: 0.4.0.0 |
MFill Text | Default fill color of a mark. |
MFilled Bool | Should a mark's color should be used as the fill color instead of stroke color. |
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 |
MInterpolate MarkInterpolation | Interpolation method used by line and area marks. |
MLine LineMarker | How should the vertices of an area mark be joined? Since: 0.4.0.0 |
MMedian [MarkProperty] | Median-line properties for the Since: 0.4.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. |
MOutliers [MarkProperty] | Outlier symbol properties for the Since: 0.4.0.0 |
MNoOutliers | Do not draw outliers with the Since: 0.4.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 from its origin. |
MRule [MarkProperty] | Rule (main line) properties for the Since: 0.4.0.0 |
MShape Symbol | Shape of a point mark. |
MShortTimeLabels Bool | Aremonth and weekday names are abbreviated in a text mark? |
MSize Double | Size of a mark. |
MStroke Text | Default stroke color of a mark. |
MStrokeCap StrokeCap | Cap style of a mark's stroke. Since: 0.4.0.0 |
MStrokeDash [Double] | The stroke dash style used by a mark, defined by an alternating 'on-off' sequence of line lengths, in pixels. |
MStrokeDashOffset Double | The number of pixels before the first line dash is drawn. |
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 [Text] | Names of custom styles to apply to a mark. Each should refer to a named style defined in a separate style configuration. |
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. |
MTheta Double | Polar coordinate angle (clockwise from north in radians) of a text mark from the origin (determined by its x and y properties). |
MThickness Double | Thickness of a tick mark. |
MTicks [MarkProperty] | Tick properties for the Since: 0.4.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. Since: 0.4.0.0 |
MX2 Double | X2 position of a mark. This is the secondary position for lines and area marks). 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. Since: 0.4.0.0 |
MY2 Double | Y2 position of a mark. This is the secondary position for lines and area marks). 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 |
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
,
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 mark interpolation style. See the Vega-Lite documentation for details.
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 #
This is used with MTooltip
.
Since: 0.4.0.0
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).
encoding :: [LabelledSpec] -> PropertySpec Source #
Create an encoding specification from a list of channel encodings,
such as position
, color
, size
, shape
.
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 [LabelledSpec] -> PropertySpec
,
so it can either be used to add further encoding specifications or as
enc []
to create a specification.
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 ( |
-> BuildLabelledSpecs |
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 |
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 Text | 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 |
PNumber Double | Set a position to an arbitrary value. Useful for placing items at the top of
a plot area ( Since: 0.4.0.0 |
PRepeat Arrangement | Reference in a position channel to a field name generated by For example: enc = |
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 |
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 Text 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 Text | Sort the field into ascending order. |
WDescending Text | 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.
AxBandPosition Double | An interpolation fraction indicating where, for Since: 0.4.0.0 |
AxDomain Bool | Should the axis domain (the baseline) be displayed? |
AxDomainColor Color | The axis domain color. Since: 0.4.0.0 |
AxDomainDash [Double] | The dash style of the domain (alternating stroke, space lengths in pixels). Since: 0.4.0.0 |
AxDomainDashOffset Double | The pixel offset at which to start drawing the domain dash array. 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 |
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 |
AxGrid Bool | Should an axis grid be displayed? |
AxGridColor Color | The color for the grid. Since: 0.4.0.0 |
AxGridDash [Double] | The dash style of the grid (alternating stroke, space lengths in pixels). Since: 0.4.0.0 |
AxGridDashOffset Double | The pixel offset at which to start drawing the grid dash array. 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 |
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 |
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. |
AxTicks Bool | Should tick marks be drawn on an axis? |
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. |
AxTickDash [Double] | The dash style of the ticks (alternating stroke, space lengths in pixels). Since: 0.4.0.0 |
AxTickDashOffset Double | The pixel offset at which to start drawing the tick dash array. 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. 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 |
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 |
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. |
Positioning Constants
Text 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.
Overlapping text
data OverlapStrategy Source #
Type of overlap strategy to be applied when there is not space to show all items on an axis. 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
Mark channels
:: [MarkChannel] | What data values are used to control the size parameters of the mark. |
-> BuildLabelledSpecs |
Encode a size channel.
size
[MName
"Age",MmType
Quantitative
] []
:: [MarkChannel] | The color-encoding options. |
-> BuildLabelledSpecs |
fill :: [MarkChannel] -> BuildLabelledSpecs Source #
Encode a fill channel. This acts in a similar way to encoding by color
but
only affects the interior of closed shapes. The first parameter is a list of mark
channel properties that characterise the way a data field is encoded by fill.
The second parameter is a list of any previous channels to which this fill channel
should be added.
fill
[MName
"Species",MmType
Nominal
] []
Note that if both fill
and color
encodings are specified, fill
takes precedence.
:: [MarkChannel] | What data values are used to control the stoke parameters of the mark. |
-> BuildLabelledSpecs |
:: [MarkChannel] | What data values are used to control the stoke width parameters of the mark. |
-> BuildLabelledSpecs |
Encode a stroke width channel.
Since: 0.4.0.0
opacity :: [MarkChannel] -> BuildLabelledSpecs 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
.
fillOpacity :: [MarkChannel] -> BuildLabelledSpecs Source #
:: [MarkChannel] | What data values are used to control the stoke opacity parameters of the mark. |
-> BuildLabelledSpecs |
:: [MarkChannel] | What data values are used to control the shape parameters of the mark. |
-> BuildLabelledSpecs |
Mark Channel properties
data MarkChannel Source #
Mark channel properties used for creating a mark channel encoding.
MName Text | Field used for encoding with a mark property channel. |
MRepeat Arrangement | Reference in a mark channel to a field name generated by |
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. |
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. |
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
.
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 |
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 | Since: 0.4.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 [Double] | The dash style for symbols (alternating stroke, space lengths in pixels). Since: 0.4.0.0 |
LSymbolDashOffset Double | The pixel offset at which to start drawing the symbol dash array. Since: 0.4.0.0 |
LSymbolFillColor Color | The fill color of the legend symbol. Since: 0.4.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. |
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 |
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. |
-> BuildLabelledSpecs |
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. |
-> BuildLabelledSpecs |
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. |
-> BuildLabelledSpecs |
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 Text | Name of the field used for 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. |
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 |
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 |
TmType Measurement | Level of measurement when encoding with a text channel. |
TRepeat Arrangement | Reference in a text channel to a field name generated by |
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. |
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 |
TTimeUnit TimeUnit | Time unit aggregation of field values when encoding with a text channel. |
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. |
-> BuildLabelledSpecs |
data HyperlinkChannel Source #
Types of hyperlink channel property used for linking marks or text to URLs.
HName Text | 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. |
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 |
HAggregate Operation | Compute aggregate summary statistics for a field to be encoded with a hyperlink channel. |
HTimeUnit TimeUnit | |
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 |
HString Text | Literal string value when encoding with a hyperlink channel. |
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. |
-> BuildLabelledSpecs |
data OrderChannel Source #
Properties of an ordering channel used for sorting data fields.
OName Text | |
ORepeat Arrangement | Reference in an order channel to a field name generated by |
OmType Measurement | |
OBin [BinProperty] | |
OAggregate Operation | |
OTimeUnit TimeUnit | |
OSort [SortProperty] |
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 ( |
-> BuildLabelledSpecs |
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 ( |
-> BuildLabelledSpecs |
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. |
-> BuildLabelledSpecs |
data DetailChannel Source #
Level of detail channel properties used for creating a grouped channel encoding.
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 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 ScaleDomain | Custom scaling domain. |
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. |
SRangeStep (Maybe Double) | Distance between the starts of adjacent bands in a band scaling. If
|
SRound Bool | Are numeric values in a scaling are 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:
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 0.4.0.0
release removed the ScSequential
constructor, as
ScLinear
should be used instead.
ScLinear | A linear scale. |
ScPow | A power scale. The exponent to use for scaling is specified with
|
ScSqrt | A square-root scale. |
ScLog | A log scale. Defaults to log of base 10, but can be customised with
|
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 Since: 0.4.0.0 |
ScTime | A temporal scale. |
ScUtc | A temporal scale, in UTC. |
ScOrdinal | An ordinal scale. |
ScBand | A band scale. |
ScPoint | A point scale. |
ScBinLinear | A linear band scale. |
ScBinOrdinal | An ordinal band scale. |
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 |
categoricalDomainMap :: [(Text, Text)] -> [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, Text) -> (Double, Text) -> [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.
DNumbers [Double] | Numeric values that define a scale domain. |
DStrings [Text] | String values that define a scale domain. |
DDateTimes [[DateTime]] | Date-time values that define a scale domain. |
DSelection Text | Scale domain based on a named interactive selection. |
Unaggregated | Specify an unaggregated scale domain (type of data in scale). |
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.
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. |
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.
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. |
NInterval TimeUnit Int | "Nice" temporal interval values when scaling. |
IsNice Bool | Enable or disable nice scaling. |
NTickCount Int | Desired number of tick marks in a "nice" scaling. |
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.
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.
toVegaLite
[dataFromUrl
"data/driving.json" [] , hConcat [ spec1, spec2 ] ]
vConcat :: [VLSpec] -> PropertySpec Source #
Assigns a list of specifications to be juxtaposed vertically in a visualization.
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
, and LGridAlign
.
Since: 0.4.0.0
Resolution
Control the independence between composed views.
See the Vega-Lite resolve documentation.
resolve :: [LabelledSpec] -> PropertySpec Source #
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]]
resolution :: Resolve -> BuildLabelledSpecs Source #
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.
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 |
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 |
ChStroke | Since: 0.3.0.0 |
ChStrokeOpacity | Since: 0.4.0.0 |
ChStrokeWidth | Since: 0.4.0.0 |
ChOpacity | |
ChShape | |
ChSize | |
ChText | Since: 0.4.0.0 |
ChTooltip | Since: 0.4.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 :: [Text] -> 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 #
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 Text | 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. |
FBin [BinProperty] | Describe how to bin quantitative fields, or whether the channels are already binned. |
FHeader [HeaderProperty] | The properties of a facet's header. |
FSort [SortProperty] | Sort order for the encoded field. Since: 0.4.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 |
HTitle Text | The title for the facets. |
HNoTitle | Draw no title for the facets. Since: 0.4.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. Since: 0.4.0.0 |
HLabelColor Color | The color of the labels. Since: 0.4.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 |
HLabelLimit Double | The maximum length of each label. Since: 0.4.0.0 |
HLabelOrient Side | The position of the label relative to its sub-plot. Since: 0.4.0.0 |
HLabelPadding Double | The spacing in pixels between the label and its sub-plot. 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 |
HTitleFontWeight Text | The font weight for the title. Since: 0.4.0.0 |
HTitleLimit Double | The maximum length of the title. Since: 0.4.0.0 |
HTitleOrient Side | The position of the title relative to the sub-plots. 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.
selection :: [LabelledSpec] -> PropertySpec Source #
:: Text | The name given to the selection. |
-> Selection | The type of the selection. |
-> [SelectionProperty] | What options are applied to the selection. |
-> BuildLabelledSpecs |
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 = |
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 [Text] | 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 [(Text, 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 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.
The debounce
property, available for all input types allows a delay in input event
handling to be added in order to avoid unnecessary event broadcasting. The Element
property is an optional CSS selector indicating the parent element to which the
input element should be added. This allows the option of the input element to be
outside the visualization container.
data SelectionMarkProperty Source #
Properties for customising the appearance of an interval selection mark (dragged rectangle). For details see the Vega-Lite documentation.
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 Text | Expression that should evaluate to either true or false. Can use any valid Vega expression. |
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 Text | 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 Text | 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.
toVegaLite
[height
300 ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] , enc [] ]
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.
toVegaLite
[width
500 ,dataFromUrl
"data/population.json" [] ,mark
Bar
[] , enc [] ]
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 [] ]
background :: Text -> PropertySpec Source #
Set the background color of the visualization. Should be specified with a CSS
string such as "#ffe"
or "rgb(200,20,150)"
. If not specified the background will
be transparent.
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). |
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 | |
-> [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.
Since: 0.4.0.0
VBStyle [Text] | A list of named styles to apply. A named style can be specified
via |
VBCornerRadius Double | The radius in pixels of rounded corners. |
VBFill (Maybe Text) | Fill color. |
VBFillOpacity Opacity | Fill opacity. |
VBOpacity Opacity | Overall opacity. |
VBStroke (Maybe Text) | The stroke color for a line around the background. If |
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 [Double] | The dash style of the line around the background, if drawn. |
VBStrokeDashOffset Double | The dash offset of 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
configure :: [LabelledSpec] -> PropertySpec Source #
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
(View
[ViewStroke
(Just "transparent") ]) .configuration
(SelectionStyle
[ (Single
, [On
"dblclick" ] ) ])
configuration :: ConfigurationProperty -> BuildLabelledSpecs Source #
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.
configuration
(Axis
[DomainWidth
4 ]) []
data ConfigurationProperty Source #
Type of configuration property to customise. See the Vega-Lite documentation for details.
AreaStyle [MarkProperty] | The default appearance of area marks. |
Autosize [Autosize] | The default sizing of visualizations. |
Axis [AxisConfig] | The default appearance of axes. |
AxisBand [AxisConfig] | The default appearance of axes with band scaling. |
AxisBottom [AxisConfig] | The default appearance of the bottom-side axes. |
AxisLeft [AxisConfig] | The default appearance of the left-side axes. |
AxisRight [AxisConfig] | The default appearance of the right-side axes. |
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. |
Background Text | The default background color of visualizations. |
BarStyle [MarkProperty] | The default appearance of bar marks. |
CircleStyle [MarkProperty] | The default appearance of circle marks. |
ConcatStyle [ConcatConfig] | The default appearance of concatenated layouts. Since: 0.4.0.0 |
CountTitle Text | The default title style for count fields. |
FacetStyle [FacetConfig] | The default appearance of facet layouts. Since: 0.4.0.0 |
FieldTitle FieldTitleProperty | The default title-generation style for fields. |
GeoshapeStyle [MarkProperty] | The default appearance of geoshape marks. Since: 0.4.0.0 |
HeaderStyle [HeaderProperty] | The default appearance of facet headers. Since: 0.4.0.0 |
Legend [LegendConfig] | The default appearance of legends. |
LineStyle [MarkProperty] | The default appearance of line marks. |
MarkStyle [MarkProperty] | The default mark appearance. |
NamedStyle Text [MarkProperty] | The default appearance of a single named style. |
NamedStyles [(Text, [MarkProperty])] | The default appearance of a list of named styles. Since: 0.4.0.0 |
NumberFormat Text | The default number formatting for axis and text labels. |
Padding Padding | The default padding in pixels from the edge of the of visualization to the data rectangle. |
PointStyle [MarkProperty] | The default appearance of point marks. |
Projection [ProjectionProperty] | The default style of map projections. |
Range [RangeConfig] | The default range properties used when scaling. |
RectStyle [MarkProperty] | The default appearance of rectangle marks. |
RemoveInvalid Bool | The default handling of invalid ( |
RuleStyle [MarkProperty] | The default appearance of rule marks. |
Scale [ScaleConfig] | The default properties used when scaling. |
SelectionStyle [(Selection, [SelectionProperty])] | The default appearance of selection marks. |
SquareStyle [MarkProperty] | the default appearance of square marks |
Stack StackOffset | The default stack offset style for stackable marks. Changed from |
TextStyle [MarkProperty] | The default appearance of text marks. |
TickStyle [MarkProperty] | The default appearance of tick marks. |
TimeFormat Text | The default time format for axis and legend labels. |
TitleStyle [TitleConfig] | The default appearance of visualization titles. |
TrailStyle [MarkProperty] | The default style of trail marks. Since: 0.4.0.0 |
View [ViewConfig] | The default single view style. |
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.
The TitleMaxLength
constructor was removed in release 0.4.0.0
. The
TitleLimit
constructor should be used instead.
BandPosition Double | The default axis band position. |
Domain Bool | Should the axis domain be displayed? |
DomainColor Color | The axis domain color. |
DomainDash [Double] | The dash style of the domain (alternating stroke, space lengths in pixels). Since: 0.4.0.0 |
DomainDashOffset Double | The pixel offset at which to start drawing the domain dash array. Since: 0.4.0.0 |
DomainOpacity Opacity | The axis domain opacity. Since: 0.4.0.0 |
DomainWidth Double | The width of the axis domain. |
Grid Bool | Should an axis grid be displayed? |
GridColor Color | The color for the grid. |
GridDash [Double] | The dash style of the grid (alternating stroke, space lengths in pixels). |
GridDashOffset Double | The pixel offset at which to start drawing the grid dash array. 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. |
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 |
ShortTimeLabels Bool | Should an axis use short time labels (abbreviated month and week-day names)? |
Ticks Bool | Should tick marks be drawn on an axis? |
TickColor Color | The color of the ticks. |
TickDash [Double] | The dash style of the ticks (alternating stroke, space lengths in pixels). |
TickDashOffset Double | The pixel offset at which to start drawing the tick dash array. 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. 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. |
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. |
Legend Configuration Options
data LegendConfig Source #
Legend configuration options. For more detail see the Vega-Lite documentation.
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.
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. |
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. 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. |
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 |
LeShortTimeLabels Bool | Should month and weekday names be abbreviated? |
LeStrokeColor Color | The border stoke color for the full legend. |
LeStrokeDash [Double] | The border stroke dash pattern for the full legend (alternating stroke, space lengths in pixels). |
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 [Double] | The pattern for dashed symbol strokes (alternating stroke, space lengths in pixels). Since: 0.4.0.0 |
LeSymbolDashOffset Double | The offset at which to start deawing the symbol dash pattern, in pixels. 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 |
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. |
LeTitle Text | The legend title. Since: 0.4.0.0 |
LeNoTitle | Draw no 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. |
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. |
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. For more details see the Vega-Lite documentation.
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. |
SCRangeStep (Maybe Double) | Default range step for band and point scales when the mark is not text. |
SCRound Bool | Are numeric values are rounded to integers when scaling? Useful for snapping to the pixel grid. |
SCTextXRangeStep Double | Default range step for x band and point scales of text marks. |
SCUseUnaggregatedDomain Bool | Whether or not to use the source data range before aggregation. |
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.
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. For further details see the Vega-Lite documentation.
TAnchor APosition | Default anchor position when placing titles. |
TAngle Angle | Default angle when orientating titles. |
TBaseline VAlign | Default vertical alignment when placing titles. |
TColor Color | Default color when showing titles. |
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 | Default maximum length, in pixels, of titles. |
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 [Text] | A list of named styles to apply. A named style can be specified
via Since: 0.4.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 such as its size and default fill and stroke colors. For further details see the Vega-Lite documentation.
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.
ViewWidth Double | The default width of the single plot or each plot in a trellis plot when the
visualization has a continuous (non-ordinal) scale or when the
'SRangeStep'/'ScRangeStep' is |
ViewHeight Double | The default height of the single plot or each plot in a trellis plot when the
visualization has a continuous (non-ordinal) scale or when the
'SRangeStep'/'ScRangeStep' is |
ViewClip Bool | Should the view be clipped? |
ViewCornerRadius Double | The radius, in pixels, of rounded rectangle corners. The default is Since: 0.4.0.0 |
ViewFill (Maybe Text) | The fill color. |
ViewFillOpacity Opacity | The fill opacity. |
ViewOpacity Opacity | The overall opacity. The default is Since: 0.4.0.0 |
ViewStroke (Maybe Text) | The stroke color. |
ViewStrokeCap StrokeCap | The stroke cap for line-ending style. Since: 0.4.0.0 |
ViewStrokeDash [Double] | The stroke dash style. It is defined by an alternating 'on-off' sequence of line lengths, in pixels. |
ViewStrokeDashOffset Double | Number of pixels before the first line dash is drawn. |
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. |
Indicates the anchor position for text.
data FieldTitleProperty Source #
Indicates the style in which field names are displayed.
Facet Configuration Options
data FacetConfig Source #
Configuration options for faceted views, used with FacetStyle
.
See the Vega-Lite facet config documentation.
Since: 0.4.0.0
Concatenated View Configuration Options
data ConcatConfig Source #
Configuration options for concatenated views, used with ConcatStyle
.
Since: 0.4.0.0
ConcatColumns Int | The maximum number of columns to use in a concatenated flow layout. |
ConcatSpacing Double | The spacing in pixels between sub-views in a concatenated view. |
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.
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
) ]
Year | |
YearQuarter | |
YearQuarterMonth | |
YearMonth | |
YearMonthDate | |
YearMonthDateHours | |
YearMonthDateHoursMinutes | |
YearMonthDateHoursMinutesSeconds | |
Quarter | |
QuarterMonth | |
Month | |
MonthDate | |
Date | |
Day | |
Hours | |
HoursMinutes | |
HoursMinutesSeconds | |
Minutes | |
MinutesSeconds | |
Seconds | |
SecondsMilliseconds | |
Milliseconds | |
Utc TimeUnit | Encode a time as UTC (coordinated universal time, independent of local time zones or daylight saving). |
Update notes
The following section describes how to update code that used
an older version of hvega
.
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 Format
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 Scale
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
.
Projection
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
, 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 fromScale
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
.