{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}

{-|
Module      : Graphics.Vega.VegaLite.Core
Copyright   : (c) Douglas Burke, 2018-2021
License     : BSD3

Maintainer  : dburke.gw@gmail.com
Stability   : unstable
Portability : CPP, OverloadedStrings

The main fuctionality of VegaLite is provided by
the Foundation and Core modules, but there are types
(and functions) scattered around the place. There is
some logic into what goes where, but it's not perfect.

-}

module Graphics.Vega.VegaLite.Core
       ( transform

       , aggregate
       , joinAggregate
       , opAs
       , timeUnitAs

       , binAs

       , stack

       , calculateAs

       , filter
       , Filter(..)
       , FilterRange(..)

       , flatten
       , flattenAs
       , fold
       , foldAs
       , pivot
       , PivotProperty(..)

       , lookup
       , lookupSelection
       , LookupFields(..)
       , lookupAs

       , impute

       , sample

       , density
       , DensityProperty(..)

       , loess
       , LoessProperty(..)

       , regression
       , RegressionProperty(..)
       , RegressionMethod(..)

       , quantile
       , QuantileProperty(..)

       , window

       , mark

       , encoding

       , position

       , PositionChannel(..)

       , SortProperty(..)

       , AxisProperty(..)
       , ConditionalAxisProperty(..)

       , angle
       , color
       , fill
       , fillOpacity
       , opacity
       , shape
       , size
       , stroke
       , strokeDash
       , strokeOpacity
       , strokeWidth

       , MarkChannel(..)

       , text
       , tooltip
       , tooltips
       , TextChannel(..)

       , hyperlink
       , url
       , HyperlinkChannel(..)

       , order
       , OrderChannel(..)

       , row
       , column

       , detail
       , DetailChannel(..)

       , ariaDescription
       , AriaDescriptionChannel(..)

       , ScaleProperty(..)
       , categoricalDomainMap
       , domainRangeMap

       , layer
       , vlConcat
       , columns
       , hConcat
       , vConcat
       , align
       , alignRC
       , spacing
       , spacingRC
       , center
       , centerRC
       , bounds

       , resolve
       , resolution

       , repeat
       , repeatFlow
       , facet
       , facetFlow
       , FacetMapping(..)
       , FacetChannel(..)

       , BooleanOp(..)

       , name
       , description
       , height
       , heightOfContainer
       , heightStep
       , width
       , widthOfContainer
       , widthStep
       , padding
       , autosize
       , background
       , usermetadata

       , viewBackground

       , configure

       -- not for external export
       , autosizeProperty
       , axisProperty
       , paddingSpec
       , schemeProperty

       )
    where

-- VegaLite uses these symbols.
import Prelude hiding (filter, lookup, repeat)

import qualified Data.Aeson as A

#if MIN_VERSION_aeson(2, 0, 0)
import qualified Data.Aeson.Key as Key
#endif

import qualified Data.Text as T

import Data.Aeson (object, toJSON, (.=))
import Data.Aeson.Types (Pair)
import Data.Maybe (mapMaybe)

#if !(MIN_VERSION_base(4, 12, 0))
import Data.Monoid ((<>))
#endif

-- added in base 4.8.0.0 / ghc 7.10.1
import Numeric.Natural (Natural)

import Graphics.Vega.VegaLite.Data
  ( DataValue(..)
  , DataValues(..)
  , dataValueSpec
  , dataValuesSpecs
  )
import Graphics.Vega.VegaLite.Foundation
  ( Angle
  , Color
  , DashStyle
  , DashOffset
  , FieldName
  , Opacity
  , StyleLabel
  , VegaExpr
  , ZIndex
  , FontWeight
  , Measurement
  , Arrangement
  , APosition
  , Position
  , HAlign
  , VAlign
  , BandAlign
  , Scale
  , OverlapStrategy
  , Side
  , StackProperty
  , StackOffset
  , StrokeCap
  , Channel
  , Resolve
  , Bounds
  , CompositionAlignment
  , Padding
  , Autosize
  , RepeatFields
  , CInterpolate
  , ViewBackground
  , HeaderProperty
  , Symbol
  , fromT
  , fromColor
  , fromDS
  , splitOnNewline
  , field_
  , header_
  , order_
  , fontWeightSpec
  , measurementLabel
  , arrangementLabel
  , anchorLabel
  , hAlignLabel
  , vAlignLabel
  , bandAlignLabel
  , scaleLabel
  , strokeCapLabel
  , positionLabel
  , overlapStrategyLabel
  , sideLabel
  , stackPropertySpecSort
  , stackPropertySpecOffset
  , stackOffset
  , channelLabel
  , resolveProperty
  , boundsSpec
  , compositionAlignmentSpec
  , paddingSpec
  , autosizeProperty
  , repeatFieldsProperty
  , cInterpolateSpec
  , viewBackgroundSpec
  , symbolLabel
  , (.=~), toObject, toKey
  )
import Graphics.Vega.VegaLite.Input
  ( Data
  )
import Graphics.Vega.VegaLite.Legend
  ( LegendProperty
  , legendProp_
  )
import Graphics.Vega.VegaLite.Mark
  ( Mark
  , MarkProperty
  , markLabel
  , markProperty
  )
import Graphics.Vega.VegaLite.Scale
  ( ScaleDomain(..)
  , DomainLimits(..)
  , ScaleRange(..)
  , ScaleNice
  , scaleDomainProperty
  , domainLimitsSpec
  , scaleNiceSpec
  )
import Graphics.Vega.VegaLite.Specification
  ( VLProperty(..)
  , VLSpec
  , PropertySpec
  , EncodingSpec(..)
  , BuildEncodingSpecs
  , TransformSpec(..)
  , BuildTransformSpecs
  , ConfigureSpec(..)
  , ResolveSpec(..)
  , BuildResolveSpecs
  , SelectionLabel
  )
import Graphics.Vega.VegaLite.Time
  ( DateTime
  , TimeUnit
  , dateTimeSpec
  , timeUnitSpec
  )
import Graphics.Vega.VegaLite.Transform
  ( Operation(Count)
  , Window
  , BinProperty
  , WindowProperty
  , ImputeProperty
  , aggregate_
  , op_
  , binned_
  , impute_
  , bin
  , binProperty
  , operationSpec
  , windowTS
  , joinAggregateTS
  , imputeTS
  )


--- helpers

-- This could be extended to any Ord type but specialize for now to Double
clamped ::
  Double
  -- ^ minimum value allowed
  -> Double
  -- ^ maximum value allowed (must be > the minimum value)
  -> Double
  -- ^ user value
  -> Double
clamped :: Double -> Double -> Double -> Double
clamped Double
xmin Double
xmax Double
x = forall a. Ord a => a -> a -> a
max Double
xmin (forall a. Ord a => a -> a -> a
min Double
xmax Double
x)


repeat_ :: Arrangement -> Pair
repeat_ :: Arrangement -> Pair
repeat_ Arrangement
arr = Key
"repeat" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Arrangement -> FieldName
arrangementLabel Arrangement
arr

sort_ :: [SortProperty] -> Pair
sort_ :: [SortProperty] -> Pair
sort_ [SortProperty]
ops = Key
"sort" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [SortProperty] -> VLSpec
sortPropertySpec [SortProperty]
ops

mchan_ :: T.Text -> [MarkChannel] -> EncodingSpec
mchan_ :: FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
f [MarkChannel]
ms = (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
f forall a. ToJSON a => FieldName -> a -> (FieldName, VLSpec)
.=~ [Pair] -> VLSpec
object (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap MarkChannel -> [Pair]
markChannelProperty [MarkChannel]
ms))

mtype_ :: Measurement -> Pair
mtype_ :: Measurement -> Pair
mtype_ Measurement
m = Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Measurement -> FieldName
measurementLabel Measurement
m

timeUnit_ :: TimeUnit -> Pair
timeUnit_ :: TimeUnit -> Pair
timeUnit_ TimeUnit
tu = Key
"timeUnit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TimeUnit -> VLSpec
timeUnitSpec TimeUnit
tu

-- The assumption at the moment is that it's always correct to
-- replace the empty list by null.
--
scaleProp_ :: [ScaleProperty] -> Pair
scaleProp_ :: [ScaleProperty] -> Pair
scaleProp_ [] = Key
"scale" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null
scaleProp_ [ScaleProperty]
sps = Key
"scale" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map ScaleProperty -> Pair
scaleProperty [ScaleProperty]
sps)


value_ :: T.Text -> Pair
value_ :: FieldName -> Pair
value_ FieldName
v = Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
v


selCond_ :: (a -> [Pair]) -> BooleanOp -> [a] -> [a] -> [Pair]
selCond_ :: forall a. (a -> [Pair]) -> BooleanOp -> [a] -> [a] -> [Pair]
selCond_ a -> [Pair]
getProps BooleanOp
selName [a]
ifClause [a]
elseClause =
  let h :: Pair
h = (Key
"condition", VLSpec
hkey)
      toProps :: [a] -> [Pair]
toProps = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap a -> [Pair]
getProps
      hkey :: VLSpec
hkey = [Pair] -> VLSpec
object ((FieldName, VLSpec) -> Pair
toKey (FieldName
"selection", BooleanOp -> VLSpec
booleanOpSpec BooleanOp
selName) forall a. a -> [a] -> [a]
: [a] -> [Pair]
toProps [a]
ifClause)
      hs :: [Pair]
hs = [a] -> [Pair]
toProps [a]
elseClause
  in (Pair
h forall a. a -> [a] -> [a]
: [Pair]
hs)

-- Special case the single-condition check, so that I don't get false
-- positives when comparing against the Vega-Lite specification. There
-- should be no actionable difference from this special case (i.e.
-- the output being '[object]' and 'object' have the same meaning).
--
-- There is also the simplification to replace
--      test: { selection: xxx }
-- by
--      selection: xxx
-- which happens for the Selection operator.
--
dataCond_ :: (a -> [Pair]) -> [(BooleanOp, [a])] -> [a] -> [Pair]
dataCond_ :: forall a. (a -> [Pair]) -> [(BooleanOp, [a])] -> [a] -> [Pair]
dataCond_ a -> [Pair]
getProps [(BooleanOp, [a])]
tests [a]
elseClause =
  let h :: Pair
h = (Key
"condition", VLSpec
condClause)
      condClause :: VLSpec
condClause = case [VLSpec]
conds of
                     [VLSpec
cond] -> VLSpec
cond
                     [VLSpec]
_ -> forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
conds
      conds :: [VLSpec]
conds = forall a b. (a -> b) -> [a] -> [b]
map (BooleanOp, [a]) -> VLSpec
testClause [(BooleanOp, [a])]
tests
      testClause :: (BooleanOp, [a]) -> VLSpec
testClause (Selection FieldName
sel, [a]
ifClause) =
        [Pair] -> VLSpec
object ((Key
"selection" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
sel) forall a. a -> [a] -> [a]
: [a] -> [Pair]
toProps [a]
ifClause)
      testClause (BooleanOp
predicate, [a]
ifClause) =
        [Pair] -> VLSpec
object ((FieldName, VLSpec) -> Pair
toKey (FieldName
"test", BooleanOp -> VLSpec
booleanOpSpec BooleanOp
predicate) forall a. a -> [a] -> [a]
: [a] -> [Pair]
toProps [a]
ifClause)
      toProps :: [a] -> [Pair]
toProps = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap a -> [Pair]
getProps
      hs :: [Pair]
hs = [a] -> [Pair]
toProps [a]
elseClause
  in (Pair
h forall a. a -> [a] -> [a]
: [Pair]
hs)



{-|

Create a named aggregation operation on a field that can be added to a transformation.
For further details see the
<https://vega.github.io/vega-lite/docs/aggregate.html#aggregate-op-def Vega-Lite documentation>.

@
'transform'
    . 'aggregate'
        [ 'opAs' 'Graphics.Vega.VegaLite.Min' "people" "lowerBound"
        , 'opAs' 'Graphics.Vega.VegaLite.Max' "people" "upperBound"
        ]
        [ "age" ]
@
-}
opAs ::
  Operation
  -- ^ The aggregation operation to use.
  -> FieldName
  -- ^ The name of the field which is to be aggregated (when the operation
  --   is 'Count' leave as the empty string).
  -> FieldName
  -- ^ The name given to the transformed data.
  -> VLSpec

-- The Count case is special-cased purely to make it easier to compare
-- the hvega output against the Veg-Lite examples. There should be no
-- semantic difference here.
--
opAs :: Operation -> FieldName -> FieldName -> VLSpec
opAs Operation
Count FieldName
_ FieldName
label =
  [Pair] -> VLSpec
object [ Operation -> Pair
op_ Operation
Count, Key
"as" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
label ]
opAs Operation
op FieldName
field FieldName
label =
  [Pair] -> VLSpec
object [ Operation -> Pair
op_ Operation
op, FieldName -> Pair
field_ FieldName
field, Key
"as" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
label ]


{-|

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' 'Graphics.Vega.VegaLite.Circle' []
'mark' 'Graphics.Vega.VegaLite.Line' ['Graphics.Vega.VegaLite.MInterpolate' 'Graphics.Vega.VegaLite.StepAfter']
@

@
let dvals = 'Graphics.Vega.VegaLite.dataFromUrl' \"city.json\" ['Graphics.Vega.VegaLite.TopojsonFeature' \"boroughs\"] []
    markOpts = 'mark' 'Graphics.Vega.VegaLite.Geoshape' ['Graphics.Vega.VegaLite.MFill' \"lightgrey\", 'Graphics.Vega.VegaLite.MStroke' \"white\"]
in 'Graphics.Vega.VegaLite.toVegaLite' [dvals, markOpts]
@
-}
mark :: Mark -> [MarkProperty] -> PropertySpec
mark :: Mark -> [MarkProperty] -> PropertySpec
mark Mark
mrk [MarkProperty]
props =
  let jsName :: VLSpec
jsName = forall a. ToJSON a => a -> VLSpec
toJSON (Mark -> FieldName
markLabel Mark
mrk)
      vals :: VLSpec
vals = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [MarkProperty]
props
             then VLSpec
jsName
             else [Pair] -> VLSpec
object ((Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
jsName) forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map MarkProperty -> Pair
markProperty [MarkProperty]
props)

  in (VLProperty
VLMark, VLSpec
vals)


{-|

Mark channel properties used for creating a mark channel encoding.
-}

-- https://vega.github.io/vega-lite/docs/encoding.html#mark-prop

data MarkChannel
    = MName FieldName
      -- ^ Field used for encoding with a mark property channel.
    | MRepeat Arrangement
      -- ^ Reference in a mark channel to a field name generated by 'repeatFlow'
      --   or 'repeat'. The parameter identifies whether reference is being made to
      --   fields that are to be arranged in columns, in rows, or a with a flow layout.
    | MRepeatDatum Arrangement
      -- ^ Reference in a mark channel to a datum value generated by 'repeatFlow'
      --   or 'repeat'. The parameter identifies whether reference is being made to
      --   a datum that is to be encoded in layers, or in columns or rows in a
      --   flow layout.
      --
      --   @since 0.9.0.0
    | MmType Measurement
      -- ^ Level of measurement when encoding with a mark property channel.
    | MScale [ScaleProperty]
      -- ^ Scaling applied to a field when encoding with a mark property channel.
      --   The scale will transform a field's value into a color, shape, size etc.
      --
      --   Use an empty list to remove the scale.
    | MBin [BinProperty]
      -- ^ Discretize numeric values into bins when encoding with a mark property channel.
    | MBinned
      -- ^ Indicate that data encoding with a mark are already binned.
      --
      --   @since 0.4.0.0
    | MSort [SortProperty]
      -- ^ Sort order.
      --
      --   @since 0.4.0.0
    | MTimeUnit TimeUnit
      -- ^ Time unit aggregation of field values when encoding with a mark property channel.
    | MTitle T.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.
      --
      -- @
      -- 'color'
      --   [ MSelectionCondition ('SelectionName' \"myBrush\")
      --      [ 'MName' \"myField\", 'MmType' 'Graphics.Vega.VegaLite.Ordinal' ]
      --      [ 'MString' \"grey\" ]
      --   ]
      -- @
    | 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 @True@. The second is the encoding if none of the expressions
      --   evaluate as @True@.
      --
      -- @
      -- 'color'
      --   [ MDataCondition [ ( 'Expr' \"datum.myField === null\", [ 'MString' \"grey\" ] ) ]
      --      [ MString \"black\" ]
      --   ]
      -- @
      --
      --   The arguments to this constructor have changed in @0.4.0.0@
      --   to support multiple expressions.
    | MPath T.Text
      -- ^ SVG path string used when encoding with a mark property channel. Useful
      --   for providing custom shapes.
    | MDatum DataValue
      -- ^ Name of a literal data item used for encoding with a mark property channel.
      --   Unlike 'MNumber', 'MString', and 'MBoolean', datum literals represent values in
      --   data space.
      --
      --   @since 0.9.0.0
    | MNumber Double
      -- ^ Literal numeric value when encoding with a mark property channel.
    | MString T.Text
      -- ^ Literal string value when encoding with a mark property channel.
    | MBoolean Bool
      -- ^ Boolean value when encoding with a mark property channel.
    | MNullValue
      -- ^ A null value.
      --
      --   @since 0.11.0.0
    | MSymbol Symbol
      -- ^ A symbol literal. This can be useful when making a symbol dependent on some data or
      --   selection condition (e.g. 'MDataCondition' or 'MSelectionCondition').
      --
      --   For example:
      --
      --   @
      --   'encoding'
      --     . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' "to", 'PmType' 'Graphics.Vega.VegaLite.Quantitative', 'PAxis' [] ]
      --     . 'shape' ['MDataCondition'
      --               [('Expr' "datum.to > 100", [MSymbol 'Graphics.Vega.VegaLite.SymTriangleRight'])]
      --               [MSymbol 'Graphics.Vega.VegaLite.SymTriangleLeft']
      --   @
      --
      --   @since 0.6.0.0

markChannelProperty :: MarkChannel -> [Pair]
markChannelProperty :: MarkChannel -> [Pair]
markChannelProperty (MName FieldName
s) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s]
markChannelProperty (MRepeat Arrangement
arr) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr]]
markChannelProperty (MRepeatDatum Arrangement
arr) = [Key
"datum" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr]]
markChannelProperty (MmType Measurement
t) = [Measurement -> Pair
mtype_ Measurement
t]
markChannelProperty (MScale [ScaleProperty]
sps) = [[ScaleProperty] -> Pair
scaleProp_ [ScaleProperty]
sps]
markChannelProperty (MLegend [LegendProperty]
lps) = [[LegendProperty] -> Pair
legendProp_ [LegendProperty]
lps]
markChannelProperty (MBin [BinProperty]
bps) = [[BinProperty] -> Pair
bin [BinProperty]
bps]
markChannelProperty MarkChannel
MBinned = [Pair
binned_]
markChannelProperty (MSort [SortProperty]
ops) = [[SortProperty] -> Pair
sort_ [SortProperty]
ops]
markChannelProperty (MSelectionCondition BooleanOp
selName [MarkChannel]
ifClause [MarkChannel]
elseClause) =
  forall a. (a -> [Pair]) -> BooleanOp -> [a] -> [a] -> [Pair]
selCond_ MarkChannel -> [Pair]
markChannelProperty BooleanOp
selName [MarkChannel]
ifClause [MarkChannel]
elseClause
markChannelProperty (MDataCondition [(BooleanOp, [MarkChannel])]
tests [MarkChannel]
elseClause) =
  forall a. (a -> [Pair]) -> [(BooleanOp, [a])] -> [a] -> [Pair]
dataCond_ MarkChannel -> [Pair]
markChannelProperty [(BooleanOp, [MarkChannel])]
tests [MarkChannel]
elseClause
markChannelProperty (MTimeUnit TimeUnit
tu) = [TimeUnit -> Pair
timeUnit_ TimeUnit
tu]
markChannelProperty (MAggregate Operation
op) = [Operation -> Pair
aggregate_ Operation
op]
markChannelProperty (MPath FieldName
s) = [Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s]
markChannelProperty (MDatum DataValue
d) = [Key
"datum" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DataValue -> VLSpec
dataValueSpec DataValue
d]
markChannelProperty (MNumber Double
x) = [Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x]
markChannelProperty (MString FieldName
s) = [Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s]
markChannelProperty (MBoolean Bool
b) = [Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b]
markChannelProperty (MSymbol Symbol
s) = [Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Symbol -> FieldName
symbolLabel Symbol
s]
markChannelProperty MarkChannel
MNullValue = [Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null]
markChannelProperty (MTitle FieldName
s) = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
splitOnNewline FieldName
s]
markChannelProperty MarkChannel
MNoTitle = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null]


{-|

Create an encoding specification from a list of channel encodings.

@
enc = 'encoding'
        . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"Animal\", 'PmType' 'Graphics.Vega.VegaLite.Ordinal' ]
        . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"Age\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
        . 'shape' [ 'MName' \"Species\", 'MmType' 'Graphics.Vega.VegaLite.Nominal' ]
        . 'size' [ 'MName' \"Population\", 'MmType' 'Graphics.Vega.VegaLite.Quantitative' ]
@

The type of @enc@ in this example is @[EncodingSpec] -> PropertySpec@,
so it can either be used to add further encoding specifications or as
@enc []@ to create a specification.

The supported encodings are:
'ariaDescription', 'angle', 'color', 'column', 'detail', 'fill', 'fillOpacity',
'hyperlink', 'opacity', 'order', 'position', 'row', 'shape', 'size',
'stroke', 'strokeDash', 'strokeOpacity', 'strokeWidth', 'text', 'tooltip',
'tooltips', and 'url'.

There is currently no support for encoding by
<https://vega.github.io/vega-lite/docs/encoding.html#key key>.

-}
encoding ::
  [EncodingSpec]
  -- ^ The channel encodings (the order does not matter).
  --
  --   Prior to @0.5.0.0@ this argument was @['LabelledSpec']@.
  -> PropertySpec
encoding :: [EncodingSpec] -> PropertySpec
encoding [EncodingSpec]
channels = (VLProperty
VLEncoding, [(FieldName, VLSpec)] -> VLSpec
toObject (forall a b. (a -> b) -> [a] -> [b]
map EncodingSpec -> (FieldName, VLSpec)
unES [EncodingSpec]
channels))


{-|

Encode an Aria description.

@since 0.9.0.0
-}
ariaDescription ::
  [AriaDescriptionChannel]
  -- ^ The properties for the channel.
  -> BuildEncodingSpecs
ariaDescription :: [AriaDescriptionChannel] -> BuildEncodingSpecs
ariaDescription [AriaDescriptionChannel]
ads [EncodingSpec]
ols =
  (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"description", [Pair] -> VLSpec
object (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap AriaDescriptionChannel -> [Pair]
ariaDescriptionChannelProperty [AriaDescriptionChannel]
ads)) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

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\"
        [ 'Graphics.Vega.VegaLite.StOffset' 'Graphics.Vega.VegaLite.StNormalize', 'Graphics.Vega.VegaLite.StSort' [ 'Graphics.Vega.VegaLite.WAscending' \"Origin\" ] ]
    . 'window'
        [ ( [ 'Graphics.Vega.VegaLite.WAggregateOp' 'Graphics.Vega.VegaLite.Min', 'Graphics.Vega.VegaLite.WField' \"stack_count_Origin1\" ], \"x\" )
        , ( [ 'Graphics.Vega.VegaLite.WAggregateOp' 'Graphics.Vega.VegaLite.Max', 'Graphics.Vega.VegaLite.WField' \"stack_count_Origin2\" ], \"x2\" )
        ]
        [ 'Graphics.Vega.VegaLite.WFrame' Nothing Nothing, 'Graphics.Vega.VegaLite.WGroupBy' [ \"Origin\" ] ]
    . 'stack' \"count_*\"
        [ \"Origin\" ]
        \"y\"
        \"y2\"
        [ 'Graphics.Vega.VegaLite.StOffset' 'Graphics.Vega.VegaLite.StNormalize', 'Graphics.Vega.VegaLite.StSort' [ 'Graphics.Vega.VegaLite.WAscending' \"Cylinders\" ] ]
@

@since 0.4.0.0

-}

stack ::
  FieldName
  -- ^ The field to be stacked.
  -> [FieldName]
  -- ^ The fields to group by.
  -> FieldName
  -- ^ The output field name (start).
  -> FieldName
  -- ^ The output field name (end).
  -> [StackProperty]
  -- ^ Offset and sort properties.
  -> BuildTransformSpecs
stack :: FieldName
-> [FieldName]
-> FieldName
-> FieldName
-> [StackProperty]
-> BuildTransformSpecs
stack FieldName
f [FieldName]
grp FieldName
start FieldName
end [StackProperty]
sProps [TransformSpec]
ols =
  let addField :: Key -> [v] -> [a]
addField Key
n [v
x] = [Key
n forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= v
x]
      addField Key
_ [v]
_ = []

      mOffset :: [VLSpec]
mOffset = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe StackProperty -> Maybe VLSpec
stackPropertySpecOffset [StackProperty]
sProps
      mSort :: [VLSpec]
mSort = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe StackProperty -> Maybe VLSpec
stackPropertySpecSort [StackProperty]
sProps

      fields :: [Pair]
fields = [ Key
"stack" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
f
               , Key
"groupby" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
grp
               , Key
"as" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [ FieldName
start, FieldName
end ] ]
               forall a. Semigroup a => a -> a -> a
<> forall {a} {v}. (KeyValue a, ToJSON v) => Key -> [v] -> [a]
addField Key
"offset" [VLSpec]
mOffset
               forall a. Semigroup a => a -> a -> a
<> forall {a} {v}. (KeyValue a, ToJSON v) => Key -> [v] -> [a]
addField Key
"sort" [VLSpec]
mSort

  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
fields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Individual scale property. These are used to customise an individual scale
transformation. To customise all scales use 'configure' and supply relevant
'Graphics.Vega.VegaLite.ScaleConfig' values. For more details see the
<https://vega.github.io/vega-lite/docs/scale.html Vega-Lite documentation>.

There are two utility routines for constructing a list of scale
properties: 'categoricalDomainMap' and 'domainRangeMap'.

The @SRangeStep@ constructor was removed in version @0.5.0.0@. Users
should use the 'heightStep' and 'widthStep' functions instead.

The @SReverse@ constructor was removed in version @0.4.0.0@, as it
represented a Vega, rather than Vega-Lite, property. The order of
a scale can be changed with the 'PSort' constructor.
-}

-- based on schema 3.3.0 #/definitions/Scale

data ScaleProperty
    = SType Scale
      -- ^ Type of scaling to apply.
    | SAlign Double
      -- ^ Alignment of the steps within the scale range. A value of
      --   @0@ shifts the bands to an axis, @1@ away from the axis,
      --   and @0.5@ is centered within the range.
      --
      --   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 ('Graphics.Vega.VegaLite.ScLog').
      --
      --   Default is @10@.
      --
      --   @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 'Graphics.Vega.VegaLite.ScSymLog' function at zero.
      --
      --   The default is @1@.
      --
      --   @since 0.4.0.0
    | SDomain DomainLimits
      -- ^ Custom scaling domain. See also 'SDomainOpt'.
      --
      --   In verson @0.11.0.0@ some functionality was moved to 'SDomainOpt'.
    | SDomainMid Double
      -- ^ Set the mid-point of a continuous diverging domain.
      --
      --   This is deprecated as of 0.11.0.0 and @'SDomainOpt' ('DMid' x)@ should be used
      --   instead.
      --
      --   @since 0.6.0.0
    | SDomainOpt ScaleDomain
      -- ^ Custom scaling domain. See also 'SDomain'.
      --
      --   @since 0.11.0.0
    | SExponent Double
      -- ^ The exponent to use for power scaling ('Graphics.Vega.VegaLite.ScPow').
      --
      --   @since 0.4.0.0
    | SInterpolate CInterpolate
      -- ^ Interpolation method for scaling range values.
    | SNice ScaleNice
      -- ^ \"Nice\" minimum and maximum values in a scaling (e.g. multiples of 10).
    | SPadding Double
      -- ^ Padding in pixels to apply to a scaling.
    | SPaddingInner Double
      -- ^ Inner padding to apply to a band scaling.
    | SPaddingOuter Double
      -- ^ Outer padding to apply to a band scaling.
    | SRange ScaleRange
      -- ^ Range of a scaling. The type of range depends on the encoding channel.
    | SReverse Bool
      -- ^ Should the order of the scale range be reversed?
      --
      --   @since 0.6.0.0
    | SRound Bool
      -- ^ Are numeric values in a scaling rounded to integers?
      --
      --   The default is @False@.
    | SScheme T.Text [Double]   -- TODO: review this; what is #/definitions/SchemeParams?
      -- ^  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 to use (list of one number);
      --      - the extent of the color range to use (list of two numbers between 0 and 1);
      --      - the number of colors and extent (three numbers, first is the number of colors).
      --
      --    For the full list of supported schemes, please refer to the
      --    <https://vega.github.io/vega/docs/schemes/#reference Vega Scheme>
      --    reference.
      --
      --    The number of colors was broken prior to @0.4.0.0@ and the option to
      --    define both the count and extent was added in @0.4.0.0@.
    | SZero Bool
      -- ^ Should a numeric scaling be forced to include a zero value?
      --
      --   Not all scales support @SZero@ and the default depends on the type of
      --   channel.


scaleProperty :: ScaleProperty -> Pair
scaleProperty :: ScaleProperty -> Pair
scaleProperty (SType Scale
sType) = Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Scale -> FieldName
scaleLabel Scale
sType
scaleProperty (SAlign Double
c) = Key
"align" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double -> Double -> Double -> Double
clamped Double
0 Double
1 Double
c
scaleProperty (SBase Double
x) = Key
"base" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
scaleProperty (SBins [Double]
xs) = Key
"bins" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Double]
xs
scaleProperty (SClamp Bool
b) = Key
"clamp" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
scaleProperty (SConstant Double
x) = Key
"constant" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
scaleProperty (SDomain DomainLimits
dl) = Key
"domain" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DomainLimits -> VLSpec
domainLimitsSpec DomainLimits
dl
scaleProperty (SDomainMid Double
x) = Key
"domainMid" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
scaleProperty (SDomainOpt ScaleDomain
sd) = ScaleDomain -> Pair
scaleDomainProperty ScaleDomain
sd
scaleProperty (SExponent Double
x) = Key
"exponent" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
scaleProperty (SInterpolate CInterpolate
interp) = Key
"interpolate" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CInterpolate -> VLSpec
cInterpolateSpec CInterpolate
interp
scaleProperty (SNice ScaleNice
ni) = Key
"nice" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ScaleNice -> VLSpec
scaleNiceSpec ScaleNice
ni
scaleProperty (SPadding Double
x) = Key
"padding" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
scaleProperty (SPaddingInner Double
x) = Key
"paddingInner" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
scaleProperty (SPaddingOuter Double
x) = Key
"paddingOuter" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
scaleProperty (SRange (RField FieldName
f)) = Key
"range" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
f]
scaleProperty (SRange (RMax Double
x)) = Key
"rangeMax" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
scaleProperty (SRange (RMin Double
x)) = Key
"rangeMin" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
scaleProperty (SRange (RPair Double
lo Double
hi)) = Key
"range" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Double
lo, Double
hi]
scaleProperty (SRange (RHeight Double
w)) = Key
"range" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName -> VLSpec
fromT FieldName
"height", forall a. ToJSON a => a -> VLSpec
toJSON Double
w]
scaleProperty (SRange (RWidth Double
h)) = Key
"range" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [forall a. ToJSON a => a -> VLSpec
toJSON Double
h, FieldName -> VLSpec
fromT FieldName
"width"]
scaleProperty (SRange (RNumbers [Double]
xs)) = Key
"range" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Double]
xs
scaleProperty (SRange (RNumberLists [[Double]]
xss)) = Key
"range" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [[Double]]
xss
scaleProperty (SRange (RStrings [FieldName]
ss)) = Key
"range" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
ss
scaleProperty (SRange (RName FieldName
s)) = Key
"range" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s
scaleProperty (SReverse Bool
b) = Key
"reverse" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
scaleProperty (SRound Bool
b) = Key
"round" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
scaleProperty (SScheme FieldName
nme [Double]
extent) = FieldName -> [Double] -> Pair
schemeProperty FieldName
nme [Double]
extent
scaleProperty (SZero Bool
b) = Key
"zero" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b


-- TODO: there should probably be a more-structured way to specify this
--
-- based on schema 3.3.0 #/definitions/SchemeParams

schemeProperty :: T.Text -> [Double] -> Pair
schemeProperty :: FieldName -> [Double] -> Pair
schemeProperty FieldName
nme [Double
n] = Key
"scheme" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
nme, Key
"count" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
n]
schemeProperty FieldName
nme [Double
mn, Double
mx] = Key
"scheme" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
nme, Key
"extent" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Double
mn, Double
mx]]
schemeProperty FieldName
nme [Double
n, Double
mn, Double
mx] = Key
"scheme" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
nme, Key
"count" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
n, Key
"extent" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Double
mn, Double
mx]]
schemeProperty FieldName
nme [Double]
_ = Key
"scheme" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
nme


{-|

Allow type of sorting to be customised. For details see the
<https://vega.github.io/vega-lite/docs/sort.html 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'.

-}
data SortProperty
    = Ascending
      -- ^ Sorting is from low to high.
    | Descending
      -- ^ Sorting is from high to low.
    | CustomSort DataValues
      -- ^ Custom sort order listing data values explicitly.
      --
      --   @since 0.4.0.0
    | ByRepeatOp Arrangement Operation
      -- ^ Sort by the aggregated summaries of the given fields
      --   (referenced by a repeat iterator) using an aggregation
      --   operation.
      --
      --   @since 0.4.0.0
    | ByFieldOp FieldName Operation
      -- ^ Sort by the aggregated summary of a field using an aggregation
      --   operation. The following example sorts the categorical data field
      --   @variety@ by the mean age of the data in each variety category:
      --
      -- @
      -- 'position' 'Graphics.Vega.VegaLite.Y'
      --   [ 'PName' "variety"
      --   , 'PmType' 'Graphics.Vega.VegaLite.Ordinal'
      --   , 'PSort' [ ByFieldOp "age" 'Graphics.Vega.VegaLite.Mean', 'Descending' ]
      --   ]
      -- @
      --
      --   @since 0.4.0.0
    | ByChannel Channel
      -- ^ Sort by another channel.
      --
      -- @
      -- 'position' 'Graphics.Vega.VegaLite.Y'
      --  [ 'PName' "age"
      --  , 'PmType' 'Graphics.Vega.VegaLite.Ordinal'
      --  , 'PSort' [ ByChannel 'Graphics.Vega.VegaLite.ChX' ]
      --  ]
      -- @
      --
      --   @since 0.4.0.0


sortProperty :: SortProperty -> [Pair]
sortProperty :: SortProperty -> [Pair]
sortProperty SortProperty
Ascending = [FieldName -> Pair
order_ FieldName
"ascending"]
sortProperty SortProperty
Descending = [FieldName -> Pair
order_ FieldName
"descending"]
sortProperty (ByChannel Channel
ch) = [Key
"encoding" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Channel -> FieldName
channelLabel Channel
ch]
sortProperty (ByFieldOp FieldName
field Operation
op) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field, Operation -> Pair
op_ Operation
op]
sortProperty (ByRepeatOp Arrangement
arr Operation
op) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr], Operation -> Pair
op_ Operation
op]
sortProperty (CustomSort DataValues
_) = []


sortPropertySpec :: [SortProperty] -> VLSpec
sortPropertySpec :: [SortProperty] -> VLSpec
sortPropertySpec [] = VLSpec
A.Null
sortPropertySpec [SortProperty
Ascending] = FieldName -> VLSpec
fromT FieldName
"ascending"
sortPropertySpec [SortProperty
Descending] = FieldName -> VLSpec
fromT FieldName
"descending"
sortPropertySpec [CustomSort DataValues
dvs] = forall a. ToJSON a => a -> VLSpec
toJSON (DataValues -> [VLSpec]
dataValuesSpecs DataValues
dvs)
sortPropertySpec [SortProperty]
sps = [Pair] -> VLSpec
object (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap SortProperty -> [Pair]
sortProperty [SortProperty]
sps)


-- | Position channel properties used for creating a position channel encoding.

data PositionChannel
    = PName FieldName
      -- ^ Name of the field used for encoding with a position channel.
    | PHeight
      -- ^ Set the position to the height of the enclosing data space. Useful for placing
      --   a mark relative to the bottom edge of a view.
      --
      --   @since 0.4.0.0
    | PWidth
      -- ^ Set the position to the width of the enclosing data space. Useful for justifying
      --   a mark to the right hand edge of a view. e.g. to position a mark at the right of
      --   the data rectangle:
      --
      -- @
      -- enc =
      --   'encoding'
      --      . 'position' 'Graphics.Vega.VegaLite.X' [ PWidth ]
      -- @
      --
      --   @since 0.4.0.0
    | PDatum DataValue
      -- ^ Set a position to an arbitrary data value. Useful for placing items at a
      --   specific point in the data space. To place in data screen space use
      --   'PNumber'.
      --
      --   @since 0.9.0.0
    | PNumber Double
      -- ^ Set a position to an arbitrary value. Useful for placing items at the top of
      --   a plot area (@PNumber 0@) or a fixed number of pixels from the top.
      --   See also 'PHeight' and 'PWidth'.
      --
      --   Use 'PDatum' to place an item using a data coordinate.
      --
      --   @since 0.4.0.0
    | PRepeat Arrangement
      -- ^ Reference in a position channel to a field name generated by 'repeatFlow'
      --   or 'repeat'. The parameter identifies whether reference is being made to
      --   fields that are to be arranged in columns, in rows, or a with a flow layout.
      --
      --   For example:
      --
      -- @
      -- enc =
      --   'encoding'
      --      . 'position' 'Graphics.Vega.VegaLite.X' [ PRepeat 'Graphics.Vega.VegaLite.Flow', 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
      --
      -- spec =
      --    'Graphics.Vega.VegaLite.asSpec' [ dataVals [], 'mark' 'Graphics.Vega.VegaLite.Tick' [], enc [] ]
      --
      -- 'Graphics.Vega.VegaLite.toVegaLite'
      --    [ 'repeatFlow' [ \"Horsepower\", \"Miles_per_Gallon\", \"Acceleration\"]
      --    , 'Graphics.Vega.VegaLite.specification' spec
      --    ]
      -- @
    | PRepeatDatum Arrangement
      -- ^ Reference in a position channel to a datum value generated by 'repeatFlow'
      --   or 'repeat'. The parameter identifies whether reference is being made to
      --   a datum that is to be encoded in layers, or in columns or rows in a
      --   flow layout.
      --
      --   @since 0.9.0.0
    | PmType Measurement
      -- ^ Level of measurement when encoding with a position channel.
    | PBin [BinProperty]
      -- ^ Discretize numeric values into bins when encoding with a
      --   position channel.
      --
      --   For example, to encode a frequency histogram with bins every 5 units:
      --
      --   @
      --   enc = 'encoding'
      --           . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"x\"
      --                        , 'PmType' 'Graphics.Vega.VegaLite.Ordinal'
      --                        , 'PBin' ['Graphics.Vega.VegaLite.Step' 5]
      --                        ]
      --           . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PmType' 'Graphics.Vega.VegaLite.Quantitative'
      --                        , 'PAggregate' 'Count'
      --                        ]
      --   @
    | 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 T.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 = 'encoding'
      --           . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"role\", 'PmType' 'Graphics.Vega.VegaLite.Ordinal' ]
      --           . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"salary\"
      --                        , 'PmType' 'Graphics.Vega.VegaLite.Quantitative'
      --                        , 'PAggregate' 'Graphics.Vega.VegaLite.Mean'
      --                        ]
      --   @
    | 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 = 'encoding'
      --           . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"ageGroup\"
      --                        , 'PmType' 'Graphics.Vega.VegaLite.Nominal'
      --                        , 'PScale' ['SPaddingInner' 0.5]
      --                        ]
      --   @
    | 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](https://vega.github.io/vega-lite/examples/stacked_area_stream.html):
      --
      --   @
      --   enc = 'encoding'
      --           . 'position' 'Graphics.Vega.VegaLite.X' ['PName' \"week\", 'PmType' 'Graphics.Vega.VegaLite.Ordinal']
      --           . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"takings\"
      --                        , 'PmType' 'Graphics.Vega.VegaLite.Quantitative'
      --                        , 'PStack' 'Graphics.Vega.VegaLite.StCenter'
      --                        ]
      --           . 'color' ['MName' \"shop\", 'MmType' 'Graphics.Vega.VegaLite.Nominal']
      --   @
      --
      --   Changed from @StackProperty@ in version @0.4.0.0@.
    | PImpute [ImputeProperty]
      -- ^ Set the imputation rules for a position channel. See the
      --   [Vega-Lite impute documentation](https://vega.github.io/vega-lite/docs/impute.html).
      --
      --   @since 0.4.0.0
    | PBand Double
      -- ^ Specify the mark position or size relative to the band size.
      --   The value is in the range 0 to 1, inclusive.
      --
      --   For rectangular-based marks ('Graphics.Vega.VegaLite.Rect', 'Graphics.Vega.VegaLite.Bar', and 'Graphics.Vega.VegaLite.Image'),
      --   the value is the scale factor relative to the band width
      --   (or height), or the time unit interval.
      --
      --   For non-rectangular marks, the relative position on a band of a
      --   stacked, binned, time unit, or band scale is used. A value of
      --   0 positions the band at the beginning of the band, and 1
      --   at the end.
      --
      --   @since 0.5.0.0

positionChannelProperty :: PositionChannel -> Pair
positionChannelProperty :: PositionChannel -> Pair
positionChannelProperty (PName FieldName
s) = Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s
positionChannelProperty (PmType Measurement
m) = Measurement -> Pair
mtype_ Measurement
m
positionChannelProperty (PBin [BinProperty]
b) = [BinProperty] -> Pair
bin [BinProperty]
b
positionChannelProperty PositionChannel
PBinned = Pair
binned_
positionChannelProperty (PAggregate Operation
op) = Operation -> Pair
aggregate_ Operation
op
positionChannelProperty (PTimeUnit TimeUnit
tu) = TimeUnit -> Pair
timeUnit_ TimeUnit
tu
positionChannelProperty (PTitle FieldName
s) = Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
splitOnNewline FieldName
s
positionChannelProperty PositionChannel
PNoTitle = Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null
positionChannelProperty (PSort [SortProperty]
ops) = [SortProperty] -> Pair
sort_ [SortProperty]
ops
positionChannelProperty (PScale [ScaleProperty]
sps) = [ScaleProperty] -> Pair
scaleProp_ [ScaleProperty]
sps
positionChannelProperty (PAxis [AxisProperty]
aps) =
  let js :: VLSpec
js = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [AxisProperty]
aps
           then VLSpec
A.Null
           else [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map AxisProperty -> Pair
axisProperty [AxisProperty]
aps)
  in Key
"axis" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
js
positionChannelProperty (PStack StackOffset
so) = StackOffset -> Pair
stackOffset StackOffset
so
positionChannelProperty (PRepeat Arrangement
arr) = Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr]
positionChannelProperty (PRepeatDatum Arrangement
arr) = Key
"datum" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr]
positionChannelProperty PositionChannel
PHeight = FieldName -> Pair
value_ FieldName
"height"
positionChannelProperty PositionChannel
PWidth = FieldName -> Pair
value_ FieldName
"width"
positionChannelProperty (PDatum DataValue
d) = Key
"datum" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DataValue -> VLSpec
dataValueSpec DataValue
d
positionChannelProperty (PNumber Double
x) = Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
positionChannelProperty (PImpute [ImputeProperty]
ips) = [ImputeProperty] -> Pair
impute_ [ImputeProperty]
ips
positionChannelProperty (PBand Double
x) = Key
"band" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x


{-|

Set the background color of the visualization. If not specified the background
will be white.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'background' "rgb(251,247,238)"
    , 'Graphics.Vega.VegaLite.dataFromUrl' "data/population.json" []
    , 'mark' 'Graphics.Vega.VegaLite.Bar' []
    , enc []
    ]
@
-}
background ::
  Color
  -- ^ The background color. For example, @\"rgba(0,0,0,0)\"@ is
  --   transparent.
  --
  --   This was changed to use the @Color@ type alias in version @0.5.0.0@.
  -> PropertySpec
background :: FieldName -> PropertySpec
background FieldName
colour = (VLProperty
VLBackground, FieldName -> VLSpec
fromColor FieldName
colour)


{-|

Provides an optional description to be associated with the visualization.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'description' "Population change of key regions since 1900"
    , 'Graphics.Vega.VegaLite.dataFromUrl' "data/population.json" []
    , 'mark' 'Graphics.Vega.VegaLite.Bar' []
    , enc []
    ]
@
-}
description :: T.Text -> PropertySpec
description :: FieldName -> PropertySpec
description FieldName
s = (VLProperty
VLDescription, forall a. ToJSON a => a -> VLSpec
toJSON FieldName
s)


-- | Optional metadata.
--
--   @since 0.4.0.0

usermetadata ::
  A.Object
  -- ^ The metadata is passed around but ignored by VegaLite.
  -> PropertySpec
usermetadata :: Object -> PropertySpec
usermetadata Object
o = (VLProperty
VLUserMetadata, Object -> VLSpec
A.Object Object
o)


{-|

Axis customisation properties. These are used for customising individual axes.
To configure all axes, use 'Graphics.Vega.VegaLite.AxisConfig' with a 'Graphics.Vega.VegaLite.configuration' instead. See the
<https://vega.github.io/vega-lite/docs/axis.html#axis-properties Vega-Lite documentation>
for more details.

The @AxTitleMaxLength@ constructor was removed in release @0.4.0.0@. The
'AxTitleLimit' constructor should be used instead.

-}
{-# DEPRECATED AxDates "Please change AxDates to AxValues" #-}
data AxisProperty
    = AxAria Bool
      -- ^ A boolean flag indicating if
      --   [ARIA attributes](https://developer.mozilla.org/en-US/docs/Web/Accessibility/ARIA)
      --   should be included (SVG output only).
      --
      --   If False, the \"aria-hidden\" attribute will be set on the output SVG group, removing
      --   the axis from the ARIA accessibility tree.
      --
      --   __Default value:__ True
      --
      --   @since 0.9.0.0
    | AxAriaDescription T.Text
      -- ^ A text description of this axis for
      --   [ARIA accessibility](https://developer.mozilla.org/en-US/docs/Web/Accessibility/ARIA)
      --   (SVG output only).
      --
      --   If the 'AxAria' property is True, for SVG output the
      --   [\"aria-label\" attribute](https://developer.mozilla.org/en-US/docs/Web/Accessibility/ARIA/ARIA_Techniques/Using_the_aria-label_attribute)
      --   will be set to this description.
      --
      --   If the description is unspecified it will be automatically generated.
      --
      --   @since 0.9.0.0
    | AxBandPosition Double
      -- ^ An interpolation fraction indicating where, for @band@ scales, axis ticks should
      --   be position. A value of @0@ places ticks at the left-edge of the band, @0.5@ in
      --   the middle, and @1@ at the right edge.
      --
      --   @since 0.4.0.0
    | AxDataCondition BooleanOp ConditionalAxisProperty
      -- ^ Set conditions on an axis property. The first argument is the
      --   test to apply, and the second is the pair of properties
      --   to set if the condition holds or not.
      --
      --   The test parameter has access to the axis @value@ and @label@
      --   properties: that is
      --
      --   @
      --   'PAxis' [ 'AxDataCondition'
      --             ('Expr' "datum.value <= 2")
      --             ('CAxTickColor' "red" "blue")
      --         , 'AxDataCondition'
      --             ('Expr' "datum.label == '4.0'")
      --             ('CAxTickWidth' 5 2)
      --         ]
      --   @
      --
      --   Inline aggregation can be performed (before the test)
      --   using 'FilterOpTrans', which can be particularly useful for
      --   filtering temporal data. The following example will use solid
      --   grid lines for the first day in January, and dashes for
      --   all other dates (using 'Data.Function.&'):
      --
      --   @
      --   'PAxis' [ 'AxDataCondition'
      --             ('FEqual' "value" ('Graphics.Vega.VegaLite.DateTime' ['Grahics.Vega.VegaLite.DTMonth' 'Graphics.Vega.VegaLite.Jan', 'Graphics.Vega.VegaLite.DTDate' 1])
      --             & 'FilterOpTrans' ('MTimeUnit' ('Graphics.Vega.VegaLite.TU' 'Graphics.Vega.VegaLite.MonthDate')))
      --             ('CAxGridDash' [] [2, 2])
      --         ]
      --   @
      --
      --   @since 0.5.0.0
    | AxDomain Bool
      -- ^ Should the axis domain (the baseline) be displayed?
    | AxDomainCap StrokeCap
      -- ^ The stroke cap for the domain lines' ending style.
      --
      --   @since 0.9.0.0
    | AxDomainColor Color
      -- ^ The axis domain color.
      --
      --   @since 0.4.0.0
    | AxDomainDash DashStyle
      -- ^ The dash pattern of the domain.
      --
      --   @since 0.4.0.0
    | AxDomainDashOffset DashOffset
      -- ^ The offset for the dash pattern.
      --
      --   @since 0.4.0.0
    | AxDomainOpacity Opacity
      -- ^ The axis domain opacity.
      --
      --   @since 0.4.0.0
    | AxDomainWidth Double
      -- ^ The width of the axis domain.
      --
      --   @since 0.4.0.0
    | AxFormat T.Text
      -- ^ [Formatting pattern](https://vega.github.io/vega-lite/docs/format.html) for
      --   axis values. To distinguish between formatting as numeric values
      --   and data/time values, additionally use 'AxFormatAsNum', 'AxFormatAsTemporal',
      --   or 'AxFormatAsCustom'.
      --
      --   When used with a [custom formatType](https://vega.github.io/vega-lite/docs/config.html#custom-format-type),
      --   this value will be passed as \"format\" alongside \"datum.value\" to the
      --   registered function.
    | AxFormatAsNum
      -- ^ Facet headers should be formatted as numbers. Use a
      --   [d3 numeric format string](https://github.com/d3/d3-format#locale_format)
      --   with 'AxFormat'.
      --
      --   @since 0.4.0.0
    | AxFormatAsTemporal
      -- ^ Facet headers should be formatted as dates or times. Use a
      --   [d3 date/time format string](https://github.com/d3/d3-time-format#locale_format)
      --   with 'AxFormat'.
      --
      --   @since 0.4.0.0
    | AxFormatAsCustom T.Text
      -- ^ The [custom format type](https://vega.github.io/vega-lite/docs/config.html#custom-format-type)
      --   for use with with 'AxFormat'.
      --
      --   @since 0.9.0.0
    | AxGrid Bool
      -- ^ Should an axis grid be displayed?
    | AxGridCap StrokeCap
      -- ^ The stroke cap for the grid lines' ending style.
      --
      --   @since 0.9.0.0
    | AxGridColor Color
      -- ^ The color for the grid.
      --
      --   @since 0.4.0.0
    | AxGridDash DashStyle
      -- ^ The dash pattern of the grid.
      --
      --   @since 0.4.0.0
    | AxGridDashOffset DashOffset
      -- ^ The offset for the dash pattern.
      --
      --   @since 0.4.0.0
    | AxGridOpacity Opacity
      -- ^ The opacity of the grid.
      --
      --   @since 0.4.0.0
    | AxGridWidth Double
      -- ^ The width of the grid lines.
      --
      --   @since 0.4.0.0
    | AxLabels Bool
      -- ^ Should labels be added to an axis?
    | AxLabelAlign HAlign
      -- ^ The horizontal alignment for labels.
      --
      --   @since 0.4.0.0
    | AxLabelAngle Angle
      -- ^ The angle at which to draw labels.
    | AxLabelBaseline VAlign
      -- ^ The vertical alignment for labels.
      --
      --   @since 0.4.0.0
    | AxLabelNoBound
      -- ^ No boundary overlap check is applied to labels. This is the
      --   default behavior.
      --
      --   See also 'AxLabelBound' and 'AxLabelBoundValue'.
      --
      --   @since 0.4.0.0
    | AxLabelBound
      -- ^ Labels are hidden if they exceed the axis range by more than 1
      --   pixel.
      --
      --   See also 'AxLabelNoBound' and 'AxLabelBoundValue'.
      --
      --   @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 'AxLabelNoBound' and 'AxLabelBound'.
      --
      --   @since 0.4.0.0
    | AxLabelColor Color
      -- ^ The label color.
      --
      --   @since 0.4.0.0
    | AxLabelExpr VegaExpr
      -- ^ Provide the expression used to generate axis labels.
      --
      --   The expression can use @datum.value@ and @datum.label@ to access
      --   the data value and default label text respectively.
      --
      --   The following example uses four digit years for decades and
      --   two-digit years for other years:
      --
      --   @
      --   AxLabelExpr "if(year(datum.value) % 10 == 0, utcFormat(datum.value,'%Y'), utcFormat(datum.value,'%y'))"
      --   @
      --
      --   @since 0.5.0.0
    | AxLabelNoFlush
      -- ^ The labels are not aligned flush to the scale. This is the
      --   default for non-continuous X scales.
      --
      --   See also 'AxLabelFlush' and 'AxLabelFlushValue'.
      --
      --   @since 0.4.0.0
    | AxLabelFlush
      -- ^ The first and last axis labels are aligned flush to the scale
      --   range.
      --
      --   See also 'AxLabelNoFlush' and 'AxLabelFlushValue'.
      --
      --   @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 'AxLabelNoFlush' and 'AxLabelFlush'.
      --
      --   @since 0.4.0.0
    | AxLabelFlushOffset Double
      -- ^ The number of pixels to offset flush-adjusted labels.
      --
      --   @since 0.4.0.0
    | AxLabelFont T.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 T.Text
      -- ^ The font style of the label.
      --
      --   @since 0.4.0.0
    | AxLabelFontWeight FontWeight
      -- ^ The font weight of the label.
      --
      --   @since 0.4.0.0
    | AxLabelLimit Double
      -- ^ The maximum width of a label, in pixels.
      --
      --   @since 0.4.0.0
    | AxLabelLineHeight Double
      -- ^ The line height, in pixels, for multi-line label text.
      --
      --   Added in Vega-Lite 4.6.0.
      --
      --   @since 0.7.0.0
    | AxLabelOffset Double
      -- ^ The pixel offset for labels, in addition to 'AxTickOffset'.
      --
      --   @since 0.6.0.0
    | AxLabelOpacity Opacity
      -- ^ The opacity of the label.
      --
      --   @since 0.4.0.0
    | AxLabelOverlap OverlapStrategy
      -- ^ How should overlapping labels be displayed?
    | AxLabelPadding Double
      -- ^ The padding, in pixels, between the label and the axis.
    | AxLabelSeparation Double
      -- ^ The minimum separation, in pixels, between label bounding boxes
      --   for them to be considered non-overlapping. This is ignored if
      --   the 'AxLabelOverlap' strategy is 'Graphics.Vega.VegaLite.ONone'.
      --
      --   @since 0.4.0.0
    | AxMaxExtent Double
      -- ^ The maximum extent, in pixels, that axis ticks and labels should use.
      --   This determines a maxmium offset value for axis titles.
    | AxMinExtent Double
      -- ^ The minimum extent, in pixels, that axis ticks and labels should use.
      --   This determines a minmium offset value for axis titles.
    | AxOffset Double
      -- ^ The offset, in pixels, between the axis and the edge of the
      --   enclosing group or data rectangle.
    | AxOrient Side
      -- ^ The orientation of the axis.
    | AxPosition Double
      -- ^ The anchor position of the axis in pixels.
    | AxStyle [StyleLabel]
      -- ^ The named styles - generated with 'Graphics.Vega.VegaLite.AxisNamedStyles' -
      --   to apply to the axis.
      --
      --   @since 0.6.0.0
    | AxTicks Bool
      -- ^ Should tick marks be drawn on an axis?
    | AxTickBand BandAlign
      -- ^ For band scales, indicates if ticks and grid lines should be
      --   placed at the center of a band (the default) or at the band
      --   extents to indicate intervals.
      --
      --   @since 0.5.0.0
    | AxTickCap StrokeCap
      -- ^ The stroke cap for the grid lines' ending style.
      --
      --   @since 0.9.0.0
    | AxTickColor Color
      -- ^ The color of the ticks.
      --
      --   @since 0.4.0.0
    | AxTickCount Int
      -- ^ The desired number of ticks for axes visualizing quantitative scales.
      --   This is a hint to the system, and the actual number used will be
      --   adjusted to be \"nice\" (multiples of 2, 5, or 10) and lie within the
      --   underlying scale's range.
      --
      --   The 'AxTickCountTime' option can instead be used for \"time\" or
      --   \"utc\" scales.
    | AxTickCountTime ScaleNice
      -- ^ A specialised version of 'AxTickCount' for \"time\" and \"utc\"
      --   time scales.
      --
      --   The 'Graphics.Vega.VegaLite.IsNice' and 'Graphics.Vega.VegaLte.NTickCount'
      --   options should not be used as they generate invalid VegaLite.
      --
      --   @since 0.9.0.0
    | AxTickDash DashStyle
      -- ^ The dash pattern of the ticks.
      --
      --   @since 0.4.0.0
    | AxTickDashOffset DashOffset
      -- ^ The offset for the dash pattern.
      --
      --   @since 0.4.0.0
    | AxTickExtra Bool
      -- ^ Should an extra axis tick mark be added for the initial position of
      --   the axis?
      --
      --   @since 0.4.0.0
    | AxTickMinStep Double
      -- ^ The minimum desired step between axis ticks, in terms of the scale
      --   domain values.
      --
      --   @since 0.4.0.0
    | AxTickOffset Double
      -- ^ The position offset, in pixels, to apply to ticks, labels, and grid lines.
      --
      --   See also 'AxLabelOffset'.
      --
      --   @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 T.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 T.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 T.Text
      -- ^ The font style of the axis title.
      --
      --   @since 0.4.0.0
    | AxTitleFontWeight FontWeight
      -- ^ The font weight of the axis title.
      --
      --   @since 0.4.0.0
    | AxTitleLimit Double
      -- ^ The maximum allowed width of the axis title, in pixels.
      --
      --   @since 0.4.0.0
    | AxTitleLineHeight Double
      -- ^ Line height, in pixels, for multi-line title text.
      --
      --   @since 0.5.0.0
    | AxTitleOpacity Opacity
      -- ^ The opacity of the axis title.
      --
      --   @since 0.4.0.0
    | AxTitlePadding Double
      -- ^ The padding, in pixels, between title and axis.
    | AxTitleX Double
      -- ^ The X coordinate of the axis title, relative to the axis group.
      --
      --   @since 0.4.0.0
    | AxTitleY Double
      -- ^ The Y coordinate of the axis title, relative to the axis group.
      --
      --   @since 0.4.0.0
    | AxTranslateOffset Double
      -- ^ The translation offset in pixels applied to the axis group
      --   mark x and y. If specified it overrides the default value
      --   of a 0.5 offset to pixel-align stroked lines.
      --
      --   @since 0.5.0.0
    | AxValues DataValues
      -- ^ Set the explicit tick, grid, and label values along an axis.
      --
      --   The following three examples are for an axis displaying a
      --   quantitative, categorical, and temporal field respectively.
      --
      --   @
      --   'PAxis' ['AxValues' ('Numbers' [2, 3, 5, 7, 11, 13, 17])]
      --   'PAxis' ['AxValues' ('Strings' ["cats", "dogs", "elephants"])]
      --   'PAxis' ['AxValues' ('DateTimes' [ ['Graphics.Vega.VegaLite.DTYear' 2019, 'Graphics.Vega.VegaLite.DTMonth' 'Graphics.Vega.VegaLite.Mar', 'Graphics.Vega.VegaLite.DTDate' 31]
      --                              , ['Graphics.Vega.VegaLite.DTYear' 2019, 'Graphics.Vega.VegaLite.DTMonth' 'Graphics.Vega.VegaLite.Jun', 'Graphics.Vega.VegaLite.DTDate' 30]
      --                              , ['Graphics.Vega.VegaLite.DTYear' 2019, 'Graphics.Vega.VegaLite.DTMonth' 'Graphics.Vega.VegaLite.Sep', 'Graphics.Vega.VegaLite.DTDate' 30]
      --                              ])]
      --   @
      --
      --   Changed in @0.4.0.0@ to take 'DataValues' rather than @[Double]@.
    | AxDates [[DateTime]]
      -- ^ The dates or times to appear along the axis.
      --
      --   As of version @0.4.0.0@, this is deprecated. The 'AxValues'
      --   constructor should be used instead.
    | AxZIndex ZIndex
      -- ^ The z-index of the axis, relative to the chart marks.


axisProperty :: AxisProperty -> Pair
axisProperty :: AxisProperty -> Pair
axisProperty (AxStyle [FieldName
s]) = Key
"style" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s
axisProperty (AxStyle [FieldName]
s) = Key
"style" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
s

axisProperty (AxAria Bool
b) = Key
"aria" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
axisProperty (AxAriaDescription FieldName
t) = Key
"description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
t

axisProperty (AxBandPosition Double
x) = Key
"bandPosition" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxDataCondition BooleanOp
predicate ConditionalAxisProperty
cap) =
  let (AxisProperty
ifAxProp, AxisProperty
elseAxProp) = ConditionalAxisProperty -> (AxisProperty, AxisProperty)
conditionalAxisProperty ConditionalAxisProperty
cap
      (Key
axKey, VLSpec
ifProp) = AxisProperty -> Pair
axisProperty AxisProperty
ifAxProp
      (Key
_, VLSpec
elseProp) = AxisProperty -> Pair
axisProperty AxisProperty
elseAxProp
  in Key
axKey forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [ Key
"condition" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [ Key
"test" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= BooleanOp -> VLSpec
booleanOpSpec BooleanOp
predicate
                                             , Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
ifProp
                                             ]
                     , Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
elseProp]
axisProperty (AxDomain Bool
b) = Key
"domain" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
axisProperty (AxDomainCap StrokeCap
c) = Key
"domainCap" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrokeCap -> FieldName
strokeCapLabel StrokeCap
c
axisProperty (AxDomainColor FieldName
s) = Key
"domainColor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromColor FieldName
s
axisProperty (AxDomainDash [Double]
ds) = Key
"domainDash" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Double] -> VLSpec
fromDS [Double]
ds
axisProperty (AxDomainDashOffset Double
x) = Key
"domainDashOffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxDomainOpacity Double
x) = Key
"domainOpacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxDomainWidth Double
x) = Key
"domainWidth" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxFormat FieldName
fmt) = Key
"format" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
fmt
axisProperty AxisProperty
AxFormatAsNum = Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromT FieldName
"number"
axisProperty AxisProperty
AxFormatAsTemporal = Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromT FieldName
"time"
axisProperty (AxFormatAsCustom FieldName
c) = Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
c
axisProperty (AxGrid Bool
b) = Key
"grid" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
axisProperty (AxGridCap StrokeCap
c) = Key
"gridCap" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrokeCap -> FieldName
strokeCapLabel StrokeCap
c
axisProperty (AxGridColor FieldName
s) = Key
"gridColor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromColor FieldName
s
axisProperty (AxGridDash [Double]
ds) = Key
"gridDash" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Double] -> VLSpec
fromDS [Double]
ds
axisProperty (AxGridDashOffset Double
x) = Key
"gridDashOffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxGridOpacity Double
x) = Key
"gridOpacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxGridWidth Double
x) = Key
"gridWidth" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabels Bool
b) = Key
"labels" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
axisProperty (AxLabelAlign HAlign
ha) = Key
"labelAlign" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HAlign -> FieldName
hAlignLabel HAlign
ha
axisProperty (AxLabelAngle Double
a) = Key
"labelAngle" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
a
axisProperty (AxLabelBaseline VAlign
va) = Key
"labelBaseline" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VAlign -> FieldName
vAlignLabel VAlign
va
axisProperty AxisProperty
AxLabelNoBound = Key
"labelBound" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
False
axisProperty AxisProperty
AxLabelBound = Key
"labelBound" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
True
axisProperty (AxLabelBoundValue Double
x) = Key
"labelBound" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabelColor FieldName
s) = Key
"labelColor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromColor FieldName
s
axisProperty (AxLabelExpr FieldName
e) = Key
"labelExpr" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
e
axisProperty AxisProperty
AxLabelNoFlush = Key
"labelFlush" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
False
axisProperty AxisProperty
AxLabelFlush = Key
"labelFlush" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
True
axisProperty (AxLabelFlushValue Double
x) = Key
"labelFlush" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabelFlushOffset Double
x) = Key
"labelFlushOffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabelFont FieldName
s) = Key
"labelFont" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s
axisProperty (AxLabelFontSize Double
x) = Key
"labelFontSize" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabelFontStyle FieldName
s) = Key
"labelFontStyle" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s
axisProperty (AxLabelFontWeight FontWeight
fw) = Key
"labelFontWeight" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FontWeight -> VLSpec
fontWeightSpec FontWeight
fw
axisProperty (AxLabelLimit Double
x) = Key
"labelLimit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabelLineHeight Double
x) = Key
"labelLineHeight" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabelOffset Double
x) = Key
"labelOffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabelOpacity Double
x) = Key
"labelOpacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabelOverlap OverlapStrategy
s) = Key
"labelOverlap" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= OverlapStrategy -> VLSpec
overlapStrategyLabel OverlapStrategy
s
axisProperty (AxLabelPadding Double
x) = Key
"labelPadding" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxLabelSeparation Double
x) = Key
"labelSeparation" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxMaxExtent Double
n) = Key
"maxExtent" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
n
axisProperty (AxMinExtent Double
n) = Key
"minExtent" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
n
axisProperty (AxOffset Double
n) = Key
"offset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
n
axisProperty (AxOrient Side
side) = Key
"orient" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Side -> FieldName
sideLabel Side
side
axisProperty (AxPosition Double
n) = Key
"position" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
n
axisProperty (AxTicks Bool
b) = Key
"ticks" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
axisProperty (AxTickBand BandAlign
bnd) = Key
"tickBand" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= BandAlign -> FieldName
bandAlignLabel BandAlign
bnd
axisProperty (AxTickCap StrokeCap
c) = Key
"tickCap" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrokeCap -> FieldName
strokeCapLabel StrokeCap
c
axisProperty (AxTickColor FieldName
s) = Key
"tickColor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromColor FieldName
s
axisProperty (AxTickCount Int
n) = Key
"tickCount" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
n
axisProperty (AxTickCountTime ScaleNice
sn) = Key
"tickCount" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ScaleNice -> VLSpec
scaleNiceSpec ScaleNice
sn
axisProperty (AxTickDash [Double]
ds) = Key
"tickDash" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Double] -> VLSpec
fromDS [Double]
ds
axisProperty (AxTickDashOffset Double
x) = Key
"tickDashOffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTickExtra Bool
b) = Key
"tickExtra" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
axisProperty (AxTickMinStep Double
x) = Key
"tickMinStep" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTickOffset Double
x) = Key
"tickOffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTickOpacity Double
x) = Key
"tickOpacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTickRound Bool
b) = Key
"tickRound" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
axisProperty (AxTickSize Double
x) = Key
"tickSize" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTickWidth Double
x) = Key
"tickWidth" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTitle FieldName
ttl) = Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
splitOnNewline FieldName
ttl
axisProperty AxisProperty
AxNoTitle = Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null
axisProperty (AxTitleAlign HAlign
ha) = Key
"titleAlign" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HAlign -> FieldName
hAlignLabel HAlign
ha
axisProperty (AxTitleAnchor APosition
a) = Key
"titleAnchor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= APosition -> FieldName
anchorLabel APosition
a
axisProperty (AxTitleAngle Double
x) = Key
"titleAngle" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTitleBaseline VAlign
va) = Key
"titleBaseline" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VAlign -> FieldName
vAlignLabel VAlign
va
axisProperty (AxTitleColor FieldName
s) = Key
"titleColor" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromColor FieldName
s
axisProperty (AxTitleFont FieldName
s) = Key
"titleFont" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s
axisProperty (AxTitleFontSize Double
x) = Key
"titleFontSize" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTitleFontStyle FieldName
s) = Key
"titleFontStyle" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s
axisProperty (AxTitleFontWeight FontWeight
fw) = Key
"titleFontWeight" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FontWeight -> VLSpec
fontWeightSpec FontWeight
fw
axisProperty (AxTitleLimit Double
x) = Key
"titleLimit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTitleLineHeight Double
x) = Key
"titleLineHeight" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTitleOpacity Double
x) = Key
"titleOpacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTitlePadding Double
pad) = Key
"titlePadding" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
pad
axisProperty (AxTitleX Double
x) = Key
"titleX" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTitleY Double
x) = Key
"titleY" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxTranslateOffset Double
x) = Key
"translate" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
axisProperty (AxValues DataValues
vals) = Key
"values" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DataValues -> [VLSpec]
dataValuesSpecs DataValues
vals
axisProperty (AxDates [[DateTime]]
dtss) = Key
"values" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a b. (a -> b) -> [a] -> [b]
map [DateTime] -> VLSpec
dateTimeSpec [[DateTime]]
dtss
axisProperty (AxZIndex Natural
z) = Key
"zindex" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
z


{-|

For use with 'AxDataCondition', and defines those axis properties
which can be conditioned on their position (or label).

The constuctor determines the axis property (a label, tick, or
grid element), and the two arguments are the value to set if the condition
is 'True' (first), and for when it is 'False' (second).

@since 0.5.0.0
-}

data ConditionalAxisProperty
  = CAxGridColor Color Color
    -- ^ The color for the axis grid.
  | CAxGridDash DashStyle DashStyle
    -- ^ The dash pattern for the axis grid.
  | CAxGridDashOffset DashOffset DashOffset
    -- ^ The offset for the dash pattern.
  | CAxGridOpacity Opacity Opacity
    -- ^ The opacity of the axis grid.
  | CAxGridWidth Double Double
    -- ^ The width of the axis grid.
  | CAxLabelAlign HAlign HAlign
    -- ^ Axis label horizontal alignment.
  | CAxLabelBaseline VAlign VAlign
    -- ^ Axis label vertical alignment.
  | CAxLabelColor Color Color
    -- ^ Axis label color.
  | CAxLabelFont T.Text T.Text
    -- ^ Axis label font.
  | CAxLabelFontSize Double Double
    -- ^ Axis label font.
  | CAxLabelFontStyle T.Text T.Text
    -- ^ Axis label font style.
  | CAxLabelFontWeight FontWeight FontWeight
    -- ^ Axis label font weight.
  | CAxLabelOffset Double Double
    -- ^ Axis label offset.
    --
    --  @since 0.6.0.0
  | CAxLabelOpacity Opacity Opacity
    -- ^ Axis label opacity.
  | CAxLabelPadding Double Double
    -- ^ Axis label padding.
    --
    --   @since 0.6.0.0
  | CAxTickColor T.Text T.Text
    -- ^ Tick color for the axis.
  | CAxTickDash DashStyle DashStyle
    -- ^ The dash pattern for the axis ticks.
  | CAxTickDashOffset DashOffset DashOffset
    -- ^ The offset for the dash pattern.
  | CAxTickOpacity Opacity Opacity
    -- ^ Opacity of the axis tick marks.
  | CAxTickSize Double Double
    -- ^ Size, in pixels, of the axis tick marks.
    --
    --   @since 0.6.0.0
  | CAxTickWidth Double Double
    -- ^ Width, in pixels, of the axis tick marks.


conditionalAxisProperty :: ConditionalAxisProperty -> (AxisProperty, AxisProperty)
conditionalAxisProperty :: ConditionalAxisProperty -> (AxisProperty, AxisProperty)
conditionalAxisProperty (CAxGridColor FieldName
t FieldName
f) = (FieldName -> AxisProperty
AxGridColor FieldName
t, FieldName -> AxisProperty
AxGridColor FieldName
f)
conditionalAxisProperty (CAxGridDash [Double]
t [Double]
f) = ([Double] -> AxisProperty
AxGridDash [Double]
t, [Double] -> AxisProperty
AxGridDash [Double]
f)
conditionalAxisProperty (CAxGridDashOffset Double
t Double
f) = (Double -> AxisProperty
AxGridDashOffset Double
t, Double -> AxisProperty
AxGridDashOffset Double
f)
conditionalAxisProperty (CAxGridOpacity Double
t Double
f) = (Double -> AxisProperty
AxGridOpacity Double
t, Double -> AxisProperty
AxGridOpacity Double
f)
conditionalAxisProperty (CAxGridWidth Double
t Double
f) = (Double -> AxisProperty
AxGridWidth Double
t, Double -> AxisProperty
AxGridWidth Double
f)
conditionalAxisProperty (CAxLabelAlign HAlign
t HAlign
f) = (HAlign -> AxisProperty
AxLabelAlign HAlign
t, HAlign -> AxisProperty
AxLabelAlign HAlign
f)
conditionalAxisProperty (CAxLabelBaseline VAlign
t VAlign
f) = (VAlign -> AxisProperty
AxLabelBaseline VAlign
t, VAlign -> AxisProperty
AxLabelBaseline VAlign
f)
conditionalAxisProperty (CAxLabelColor FieldName
t FieldName
f) = (FieldName -> AxisProperty
AxLabelColor FieldName
t, FieldName -> AxisProperty
AxLabelColor FieldName
f)
conditionalAxisProperty (CAxLabelFont FieldName
t FieldName
f) = (FieldName -> AxisProperty
AxLabelFont FieldName
t, FieldName -> AxisProperty
AxLabelFont FieldName
f)
conditionalAxisProperty (CAxLabelFontSize Double
t Double
f) = (Double -> AxisProperty
AxLabelFontSize Double
t, Double -> AxisProperty
AxLabelFontSize Double
f)
conditionalAxisProperty (CAxLabelFontStyle FieldName
t FieldName
f) = (FieldName -> AxisProperty
AxLabelFontStyle FieldName
t, FieldName -> AxisProperty
AxLabelFontStyle FieldName
f)
conditionalAxisProperty (CAxLabelFontWeight FontWeight
t FontWeight
f) = (FontWeight -> AxisProperty
AxLabelFontWeight FontWeight
t, FontWeight -> AxisProperty
AxLabelFontWeight FontWeight
f)
conditionalAxisProperty (CAxLabelOffset Double
t Double
f) = (Double -> AxisProperty
AxLabelOffset Double
t, Double -> AxisProperty
AxLabelOffset Double
f)
conditionalAxisProperty (CAxLabelOpacity Double
t Double
f) = (Double -> AxisProperty
AxLabelOpacity Double
t, Double -> AxisProperty
AxLabelOpacity Double
f)
conditionalAxisProperty (CAxLabelPadding Double
t Double
f) = (Double -> AxisProperty
AxLabelPadding Double
t, Double -> AxisProperty
AxLabelPadding Double
f)
conditionalAxisProperty (CAxTickColor FieldName
t FieldName
f) = (FieldName -> AxisProperty
AxTickColor FieldName
t, FieldName -> AxisProperty
AxTickColor FieldName
f)
conditionalAxisProperty (CAxTickDash [Double]
t [Double]
f) = ([Double] -> AxisProperty
AxTickDash [Double]
t, [Double] -> AxisProperty
AxTickDash [Double]
f)
conditionalAxisProperty (CAxTickDashOffset Double
t Double
f) = (Double -> AxisProperty
AxTickDashOffset Double
t, Double -> AxisProperty
AxTickDashOffset Double
f)
conditionalAxisProperty (CAxTickOpacity Double
t Double
f) = (Double -> AxisProperty
AxTickOpacity Double
t, Double -> AxisProperty
AxTickOpacity Double
f)
conditionalAxisProperty (CAxTickSize Double
t Double
f) = (Double -> AxisProperty
AxTickSize Double
t, Double -> AxisProperty
AxTickSize Double
f)
conditionalAxisProperty (CAxTickWidth Double
t Double
f) = (Double -> AxisProperty
AxTickWidth Double
t, Double -> AxisProperty
AxTickWidth Double
f)


{-|

Declare the way the view is sized. See the
<https://vega.github.io/vega-lite/docs/size.html#autosize Vega-Lite documentation>
for details.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'width' 250
    , 'height' 300
    , 'autosize' [ 'Graphics.Vega.VegaLite.AFit', 'Graphics.Vega.VegaLite.APadding', 'Graphics.Vega.VegaLite.AResize' ]
    , 'Graphics.Vega.VegaLite.dataFromUrl' "data/population.json" []
    , 'mark' 'Graphics.Vega.VegaLite.Bar' []
    , enc []
    ]
@
-}
autosize :: [Autosize] -> PropertySpec
autosize :: [Autosize] -> PropertySpec
autosize [Autosize]
aus = (VLProperty
VLAutosize, [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map Autosize -> Pair
autosizeProperty [Autosize]
aus))


-- | The background style of a single view or layer in a view composition.
--
--   @since 0.4.0.0

viewBackground :: [ViewBackground] -> PropertySpec
viewBackground :: [ViewBackground] -> PropertySpec
viewBackground [ViewBackground]
vbs = (VLProperty
VLViewBackground, [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map ViewBackground -> Pair
viewBackgroundSpec [ViewBackground]
vbs))


{-|

Used for creating logical compositions. For example

@
'color'
    [ 'MSelectionCondition' (Or ('SelectionName' "alex") (SelectionName "morgan"))
        ['MAggregate' 'Count', 'MName' "*", 'MmType' 'Graphics.Vega.VegaLite.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") )
@
-}
data BooleanOp
    = Expr VegaExpr
      -- ^ Expression that should evaluate to either true or false.
    | FilterOp Filter
      -- ^ Convert a 'Filter' into a 'BooleanOp' so that it may be used as
      --   part of a more complex expression.
      --
      --   For example (using 'Data.Function.&' to apply 'FilterOp' to a filter):
      --
      --   @
      --   trans = 'transform'
      --             . 'filter' ('FCompose'
      --                        ('And'
      --                          ('FValid' "IMDB_Rating" & 'FilterOp')
      --                          ('FValid' "Rotten_Tomatoes_Rating" & 'FilterOp')
      --                        )
      --                      )
      --   @
      --
      --   @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 'BooleanOp' with 'FCompose' (combined using
      --   'Data.Function.&').
      --
      --   @
      --   'filter' ('FRange' "date" ('NumberRange' 2010 2017)
      --           & 'FilterOpTrans' ('MTimeUnit' ('Graphics.Vega.VegaLite.TU' 'Graphics.Vega.VegaLite.Year'))
      --           & 'FCompose'
      --           )
      --   @
      --
      --   @since 0.4.0.0
    | Selection SelectionLabel  -- TODO: rename Selected since collides with Selection type
      -- ^ 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:
      --
      -- @
      -- 'transform'
      --    . 'filter' ('FCompose' ('And' ('Selection' "brush") ('Expr' "datum.weight > 30")))
      -- @
    | SelectionName SelectionLabel
    -- ^  Name a selection that is used as part of a conditional encoding.
    --
    -- @
    -- 'color'
    --    [ 'MSelectionCondition' ('SelectionName' \"myBrush\")
    --        ['MName' \"myField\", 'MmType' 'Graphics.Vega.VegaLite.Nominal']
    --        ['MString' \"grey\"]
    --    ]
    -- @
    | And BooleanOp BooleanOp
      -- ^ Apply an \'and\' Boolean operation as part of a logical composition.
      --
      -- @
      -- 'And' ('Expr' "datum.IMDB_Rating === null") ('Expr' "datum.Rotten_Tomatoes_Rating === null")
      -- @
    | Or BooleanOp BooleanOp
      -- ^ Apply an \'or\' Boolean operation as part of a logical composition.
    | Not BooleanOp
      -- ^ Negate the given expression.
      --
      -- @
      -- 'Not' ('And' ('Expr' "datum.IMDB_Rating === null") ('Expr' "datum.Rotten_Tomatoes_Rating === null"))
      -- @

booleanOpSpec :: BooleanOp -> VLSpec
booleanOpSpec :: BooleanOp -> VLSpec
booleanOpSpec (Expr FieldName
expr) = forall a. ToJSON a => a -> VLSpec
toJSON FieldName
expr
booleanOpSpec (FilterOp Filter
f) = Filter -> VLSpec
filterSpec Filter
f
booleanOpSpec (FilterOpTrans MarkChannel
tr Filter
f) = MarkChannel -> Filter -> VLSpec
trFilterSpec MarkChannel
tr Filter
f
booleanOpSpec (SelectionName FieldName
selName) = forall a. ToJSON a => a -> VLSpec
toJSON FieldName
selName
booleanOpSpec (Selection FieldName
sel) = [Pair] -> VLSpec
object [Key
"selection" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
sel]
booleanOpSpec (And BooleanOp
operand1 BooleanOp
operand2) = [Pair] -> VLSpec
object [Key
"and" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand1, BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand2]]
booleanOpSpec (Or BooleanOp
operand1 BooleanOp
operand2) = [Pair] -> VLSpec
object [Key
"or" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand1, BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand2]]
booleanOpSpec (Not BooleanOp
operand) = [Pair] -> VLSpec
object [Key
"not" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= BooleanOp -> VLSpec
booleanOpSpec BooleanOp
operand]


{-|

Type of filtering operation. See the
<https://vega.github.io/vega-lite/docs/filter.html 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@).

-}
data Filter
    = FEqual FieldName DataValue
      -- ^ Filter a data stream so that only data in a given field equal to
      --   the given value are used.
    | FLessThan FieldName DataValue
      -- ^ Filter a data stream so that only data in a given field less than the given
      --   value are used.
      --
      --   @since 0.4.0.0
    | FLessThanEq FieldName DataValue
      -- ^ Filter a data stream so that only data in a given field less than,
      --   or equal to, the given value are used.
      --
      --   @since 0.4.0.0
    | FGreaterThan FieldName DataValue
      -- ^ Filter a data stream so that only data in a given field greater than the given
      --   value are used.
      --
      --   @since 0.4.0.0
    | FGreaterThanEq FieldName DataValue
      -- ^ Filter a data stream so that only data in a given field greater than,
      --   or equal to, the given value are used.
      --
      --   @since 0.4.0.0
    | FExpr VegaExpr
      -- ^ Filter a data stream so that only data that satisfy the given predicate
      --   expression are used.
    | FCompose BooleanOp
      -- ^ Build up a filtering predicate through logical composition such
      --   as 'And' and 'Or'.
      --
      --   The following fgragment will apply a filter to identify only
      --   those items selected interactively and that represent ages
      --   over 65:
      --
      --   @
      --   trans = 'transform'
      --             . 'filter'
      --                 ('FCompose'
      --                   ('And' ('Selection' "brush") ('Expr' "datum.age > 65"))
      --                 )
      --   @
    | FSelection SelectionLabel
      -- ^ Filter a data stream so that only data in a given field that are
      --   within the given interactive selection are used.
      --
      --   @
      --   sel = 'Graphics.Vega.VegaLite.selection' . 'Graphics.Vega.VegaLite.select' \"myBrush\" 'Graphics.Vega.VegaLite.Interval' ['Graphics.Vega.VegaLite.Encodings' ['Graphics.Vega.VegaLite.ChX']]
      --   trans = 'transform' . 'filter' ('FSelection' \"myBrush\")
      --   @
    | FOneOf FieldName DataValues
      -- ^ Filter a data stream so that only data in a given field contained in the given
      --   list of values are used.
    | FRange FieldName FilterRange
      -- ^ Filter a data stream so that only data in a given field
      --   that are within the given range are used.
      --
      --   For example:
      --
      --   @
      --   'filter' ('FRange' "date" ('DateRange' ['Graphics.Vega.VegaLite.DTYear' 2006] ['Graphics.Vega.VegaLite.DTYear' 2016])
      --   @
      --
      --   See 'FilterOpTrans' for more use cases.
    | FValid FieldName
      -- ^ Filter a data stream so that only valid data (i.e. not null or NaN) in a given
      --   field are used.
      --
      --   @since 0.4.0.0


#if MIN_VERSION_aeson(2, 0, 0)
fop_ :: FieldName -> Key.Key -> DataValue -> [Pair]
#else
fop_ :: FieldName -> T.Text -> DataValue -> [Pair]
#endif
fop_ :: FieldName -> Key -> DataValue -> [Pair]
fop_ FieldName
field Key
label DataValue
val = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field,
                        Key
label forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DataValue -> VLSpec
dataValueSpec DataValue
val]

filterProperty :: Filter -> [Pair]

filterProperty :: Filter -> [Pair]
filterProperty (FEqual FieldName
field DataValue
val) = FieldName -> Key -> DataValue -> [Pair]
fop_ FieldName
field Key
"equal" DataValue
val
filterProperty (FLessThan FieldName
field DataValue
val) = FieldName -> Key -> DataValue -> [Pair]
fop_ FieldName
field Key
"lt" DataValue
val
filterProperty (FLessThanEq FieldName
field DataValue
val) = FieldName -> Key -> DataValue -> [Pair]
fop_ FieldName
field Key
"lte" DataValue
val
filterProperty (FGreaterThan FieldName
field DataValue
val) = FieldName -> Key -> DataValue -> [Pair]
fop_ FieldName
field Key
"gt" DataValue
val
filterProperty (FGreaterThanEq FieldName
field DataValue
val) = FieldName -> Key -> DataValue -> [Pair]
fop_ FieldName
field Key
"gte" DataValue
val

filterProperty (FSelection FieldName
selName) = [Key
"selection" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
selName]

filterProperty (FRange FieldName
field FilterRange
vals) =
  let ans :: [VLSpec]
ans = case FilterRange
vals of
              NumberRange Double
mn Double
mx -> forall a b. (a -> b) -> [a] -> [b]
map forall a. ToJSON a => a -> VLSpec
toJSON [Double
mn, Double
mx]
              NumberRangeLL Double
mn -> [forall a. ToJSON a => a -> VLSpec
toJSON Double
mn, VLSpec
A.Null]
              NumberRangeUL Double
mx -> [VLSpec
A.Null, forall a. ToJSON a => a -> VLSpec
toJSON Double
mx]
              DateRange [DateTime]
dMin [DateTime]
dMax -> [[DateTime] -> VLSpec
process [DateTime]
dMin, [DateTime] -> VLSpec
process [DateTime]
dMax]

      process :: [DateTime] -> VLSpec
process [] = VLSpec
A.Null
      process [DateTime]
dts = [DateTime] -> VLSpec
dateTimeSpec [DateTime]
dts

  in [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field, Key
"range" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [VLSpec]
ans]

filterProperty (FOneOf FieldName
field DataValues
vals) =
  let ans :: [VLSpec]
ans = case DataValues
vals of
              Numbers [Double]
xs -> forall a b. (a -> b) -> [a] -> [b]
map forall a. ToJSON a => a -> VLSpec
toJSON [Double]
xs
              DateTimes [[DateTime]]
dts -> forall a b. (a -> b) -> [a] -> [b]
map [DateTime] -> VLSpec
dateTimeSpec [[DateTime]]
dts
              Strings [FieldName]
ss -> forall a b. (a -> b) -> [a] -> [b]
map forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
ss
              Booleans [Bool]
bs -> forall a b. (a -> b) -> [a] -> [b]
map forall a. ToJSON a => a -> VLSpec
toJSON [Bool]
bs

  in [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field, Key
"oneOf" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [VLSpec]
ans]

filterProperty (FValid FieldName
field) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field, Key
"valid" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
True]
filterProperty Filter
_ = []  -- ignore FExpr and FCompose


filterSpec :: Filter -> VLSpec
filterSpec :: Filter -> VLSpec
filterSpec (FExpr FieldName
expr) = forall a. ToJSON a => a -> VLSpec
toJSON FieldName
expr
filterSpec (FCompose BooleanOp
boolExpr) = BooleanOp -> VLSpec
booleanOpSpec BooleanOp
boolExpr
filterSpec Filter
f = [Pair] -> VLSpec
object (Filter -> [Pair]
filterProperty Filter
f)

trFilterSpec :: MarkChannel -> Filter -> VLSpec
trFilterSpec :: MarkChannel -> Filter -> VLSpec
trFilterSpec MarkChannel
_ (FExpr FieldName
expr) = forall a. ToJSON a => a -> VLSpec
toJSON FieldName
expr
trFilterSpec MarkChannel
_ (FCompose BooleanOp
boolExpr) = BooleanOp -> VLSpec
booleanOpSpec BooleanOp
boolExpr
trFilterSpec MarkChannel
mchan Filter
fi = [Pair] -> VLSpec
object (MarkChannel -> [Pair]
markChannelProperty MarkChannel
mchan forall a. Semigroup a => a -> a -> a
<> Filter -> [Pair]
filterProperty Filter
fi)


-- | A pair of filter range data values, used with 'FRange'.

data FilterRange
    = NumberRange Double Double
      -- ^ Select between these two values (both limits are inclusive).
    | NumberRangeLL Double
      -- ^ A lower limit (inclusive).
      --
      --   @since 0.7.0.0
    | NumberRangeUL Double
      -- ^ An upper limit (inclusive).
      --
      --   @since 0.7.0.0
    | DateRange [DateTime] [DateTime]
      -- ^ Select between these two dates (both limits are inclusive).
      --
      --   If a limit is the empty list then the filter is treated as
      --   a limit only on the other value, so
      --   @DateRange [] ['Graphics.Vega.VegaLite.DTYear' 2019]@
      --   acts as an upper-limit on the date range. One of the two
      --   limits __should__ be defined, but there is no enforcement
      --   of this.


-- | Types of hyperlink channel property used for linking marks or text to URLs.
--
--   Unfortunately there is a split between @H@ and @Hy@ as the prefix.
data HyperlinkChannel
    = HName FieldName
      -- ^ Field used for encoding with a hyperlink channel.
    | HRepeat Arrangement
      -- ^ Reference in a hyperlink channel to a field name generated by 'repeatFlow'
      --   or 'repeat'. The parameter identifies whether reference is being made to
      --   fields that are to be arranged in columns, in rows, or a with a flow layout.
    | HmType Measurement
      -- ^ Level of measurement when encoding with a hyperlink channel.
    | HAggregate Operation
      -- ^ Compute aggregate summary statistics for a field to be encoded with a
      --   hyperlink channel.
    | HyBand Double
      -- ^ Specify the mark position or size relative to the band size.
      --   The value is in the range 0 to 1, inclusive.
      --
      --   @since 0.9.0.0
    | HBin [BinProperty]
      -- ^ Discretize numeric values into bins when encoding with a hyperlink channel.
    | HBinned
      -- ^ Indicate that data encoded with a hyperlink channel are already binned.
      --
      --   @since 0.4.0.0
    | HSelectionCondition BooleanOp [HyperlinkChannel] [HyperlinkChannel]
      -- ^ Make a hyperlink channel conditional on interactive selection. The first parameter
      --   provides the selection to evaluate, the second the encoding to apply if the hyperlink
      --   has been selected, the third the encoding if it is not selected.
    | HDataCondition [(BooleanOp, [HyperlinkChannel])] [HyperlinkChannel]
      -- ^ Make a hyperlink channel conditional on one or more predicate expressions. The first
      --   parameter is a list of tuples each pairing an expression to evaluate with the encoding
      --   if that expression is @True@. The second is the encoding if none of the expressions
      --   evaluate as @True@.
      --
      --   The arguments to this constructor have changed in @0.4.0.0@
      --   to support multiple expressions.
    | HyFormat T.Text
      -- ^ [Formatting pattern](https://vega.github.io/vega-lite/docs/format.html)
      --   for hyperlink properties. To distinguish between formatting as numeric values and data/time
      --   values, additionally use 'HyFormatAsNum', 'HyFormatAsTemporal', and
      --   'HyFormatAsCustom'.
      --
      --   @since 0.9.0.0
    | HyFormatAsNum
      -- ^ The marks should be formatted as numbers. Use a
      --   [d3 numeric format string](https://github.com/d3/d3-format#locale_format)
      --   with 'HyFormat'.
      --
      --   @since 0.9.0.0
    | HyFormatAsTemporal
      -- ^ The marks should be formatted as dates or times. Use a
      --   [d3 date/time format string](https://github.com/d3/d3-time-format#locale_format)
      --   with 'HyFormat'.
      --
      --   @since 0.9.0.0
    | HyFormatAsCustom T.Text
      -- ^ The [custom format type](https://vega.github.io/vega-lite/docs/config.html#custom-format-type)
      --   for use with with 'HyFormat'.
      --
      --   @since 0.9.0.0
    | HyLabelExpr VegaExpr
      -- ^ Provide the expression used to generate labels.
      --
      --   @since 0.9.0.0
    | HString T.Text
      -- ^ Literal string value when encoding with a hyperlink channel.
    | HTimeUnit TimeUnit
      -- ^ Time unit aggregation of field values when encoding with a
      --   hyperlink channel.
    | HyTitle T.Text
      -- ^ Title of a field when encoding with a hyperlink channel.
      --
      --   @since 0.9.0.0
    | HyNoTitle
      -- ^ Display no title.
      --
      --   @since 0.9.0.0

hyperlinkChannelProperty :: HyperlinkChannel -> [Pair]
hyperlinkChannelProperty :: HyperlinkChannel -> [Pair]
hyperlinkChannelProperty (HName FieldName
s) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s]
hyperlinkChannelProperty (HRepeat Arrangement
arr) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr]]
hyperlinkChannelProperty (HmType Measurement
t) = [Measurement -> Pair
mtype_ Measurement
t]
hyperlinkChannelProperty (HAggregate Operation
op) = [Operation -> Pair
aggregate_ Operation
op]
hyperlinkChannelProperty (HyBand Double
x) = [Key
"band" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x]
hyperlinkChannelProperty (HBin [BinProperty]
bps) = [[BinProperty] -> Pair
bin [BinProperty]
bps]
hyperlinkChannelProperty HyperlinkChannel
HBinned = [Pair
binned_]
hyperlinkChannelProperty (HSelectionCondition BooleanOp
selName [HyperlinkChannel]
ifClause [HyperlinkChannel]
elseClause) =
  forall a. (a -> [Pair]) -> BooleanOp -> [a] -> [a] -> [Pair]
selCond_ HyperlinkChannel -> [Pair]
hyperlinkChannelProperty BooleanOp
selName [HyperlinkChannel]
ifClause [HyperlinkChannel]
elseClause
hyperlinkChannelProperty (HDataCondition [(BooleanOp, [HyperlinkChannel])]
tests [HyperlinkChannel]
elseClause) =
  forall a. (a -> [Pair]) -> [(BooleanOp, [a])] -> [a] -> [Pair]
dataCond_ HyperlinkChannel -> [Pair]
hyperlinkChannelProperty [(BooleanOp, [HyperlinkChannel])]
tests [HyperlinkChannel]
elseClause
hyperlinkChannelProperty (HyFormat FieldName
fmt) = [Key
"format" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
fmt]
hyperlinkChannelProperty HyperlinkChannel
HyFormatAsNum = [Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromT FieldName
"number"]
hyperlinkChannelProperty HyperlinkChannel
HyFormatAsTemporal = [Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromT FieldName
"time"]
hyperlinkChannelProperty (HyFormatAsCustom FieldName
c) = [Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
c]
hyperlinkChannelProperty (HyLabelExpr FieldName
lbl) = [Key
"labelExpr" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
lbl]
hyperlinkChannelProperty (HString FieldName
s) = [FieldName -> Pair
value_ FieldName
s]
hyperlinkChannelProperty (HTimeUnit TimeUnit
tu) = [TimeUnit -> Pair
timeUnit_ TimeUnit
tu]
hyperlinkChannelProperty (HyTitle FieldName
t) = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
t]
hyperlinkChannelProperty HyperlinkChannel
HyNoTitle = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null]


-- | A text description of this mark for ARIA accessibility.
--
--   @since 0.9.0.0
data AriaDescriptionChannel
    = ADName FieldName
      -- ^ Field used for encoding with an Aria description.
    | ADRepeat Arrangement
      -- ^ Reference in an Aria description channel to a field name generated by 'repeatFlow'
      --   or 'repeat'. The parameter identifies whether reference is being made to
      --   fields that are to be arranged in columns, in rows, or a with a flow layout.
    | ADmType Measurement
      -- ^ Level of measurement.
    | ADAggregate Operation
      -- ^ Compute aggregate summary statistics for a field to be encoded.
    | ADBand Double
      -- ^ Specify the mark position or size relative to the band size.
      --   The value is in the range 0 to 1, inclusive.
    | ADBin [BinProperty]
      -- ^ Discretize numeric values into bins.
    | ADBinned
      -- ^ Indicate that data encoded are already binned.
    | ADSelectionCondition BooleanOp [AriaDescriptionChannel] [AriaDescriptionChannel]
      -- ^ Make the channel conditional on interactive selection. The first parameter
      --   provides the selection to evaluate, the second the encoding to apply if the description
      --   has been selected, the third the encoding if it is not selected.
    | ADDataCondition [(BooleanOp, [AriaDescriptionChannel])] [AriaDescriptionChannel]
      -- ^ Make the channel conditional on one or more predicate expressions. The first
      --   parameter is a list of tuples each pairing an expression to evaluate with the encoding
      --   if that expression is @True@. The second is the encoding if none of the expressions
      --   evaluate as @True@.
    | ADFormat T.Text
      -- ^ [Formatting pattern](https://vega.github.io/vega-lite/docs/format.html)
      --   for descriptions. To distinguish between formatting as numeric values and data/time
      --   values, additionally use 'ADFormatAsNum', 'ADFormatAsTemporal', and
      --   'ADFormatAsCustom'.
    | ADFormatAsNum
      -- ^ The marks should be formatted as numbers. Use a
      --   [d3 numeric format string](https://github.com/d3/d3-format#locale_format)
      --   with 'ADFormat'.
    | ADFormatAsTemporal
      -- ^ The marks should be formatted as dates or times. Use a
      --   [d3 date/time format string](https://github.com/d3/d3-time-format#locale_format)
      --   with 'ADFormat'.
    | ADFormatAsCustom T.Text
      -- ^ The [custom format type](https://vega.github.io/vega-lite/docs/config.html#custom-format-type)
      --   for use with with 'ADFormat'.
    | ADLabelExpr VegaExpr
      -- ^ Provide the expression used to generate labels.
    | ADString T.Text
      -- ^ Literal string value.
    | ADTimeUnit TimeUnit
      -- ^ Time unit aggregation of field values when encoding with an Aria
      --   description channel.
    | ADTitle T.Text
      -- ^ Title of a field when encoding with an Aria description channel.
    | ADNoTitle
      -- ^ Display no title.


ariaDescriptionChannelProperty :: AriaDescriptionChannel -> [Pair]
ariaDescriptionChannelProperty :: AriaDescriptionChannel -> [Pair]
ariaDescriptionChannelProperty (ADName FieldName
s) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s]
ariaDescriptionChannelProperty (ADRepeat Arrangement
arr) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr]]
ariaDescriptionChannelProperty (ADmType Measurement
t) = [Measurement -> Pair
mtype_ Measurement
t]
ariaDescriptionChannelProperty (ADAggregate Operation
op) = [Operation -> Pair
aggregate_ Operation
op]
ariaDescriptionChannelProperty (ADBand Double
x) = [Key
"band" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x]
ariaDescriptionChannelProperty (ADBin [BinProperty]
bps) = [[BinProperty] -> Pair
bin [BinProperty]
bps]
ariaDescriptionChannelProperty AriaDescriptionChannel
ADBinned = [Pair
binned_]
ariaDescriptionChannelProperty (ADSelectionCondition BooleanOp
selName [AriaDescriptionChannel]
ifClause [AriaDescriptionChannel]
elseClause) =
  forall a. (a -> [Pair]) -> BooleanOp -> [a] -> [a] -> [Pair]
selCond_ AriaDescriptionChannel -> [Pair]
ariaDescriptionChannelProperty BooleanOp
selName [AriaDescriptionChannel]
ifClause [AriaDescriptionChannel]
elseClause
ariaDescriptionChannelProperty (ADDataCondition [(BooleanOp, [AriaDescriptionChannel])]
tests [AriaDescriptionChannel]
elseClause) =
  forall a. (a -> [Pair]) -> [(BooleanOp, [a])] -> [a] -> [Pair]
dataCond_ AriaDescriptionChannel -> [Pair]
ariaDescriptionChannelProperty [(BooleanOp, [AriaDescriptionChannel])]
tests [AriaDescriptionChannel]
elseClause
ariaDescriptionChannelProperty (ADFormat FieldName
fmt) = [Key
"format" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
fmt]
ariaDescriptionChannelProperty AriaDescriptionChannel
ADFormatAsNum = [Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromT FieldName
"number"]
ariaDescriptionChannelProperty AriaDescriptionChannel
ADFormatAsTemporal = [Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromT FieldName
"time"]
ariaDescriptionChannelProperty (ADFormatAsCustom FieldName
c) = [Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
c]
ariaDescriptionChannelProperty (ADLabelExpr FieldName
lbl) = [Key
"labelExpr" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
lbl]
ariaDescriptionChannelProperty (ADString FieldName
s) = [FieldName -> Pair
value_ FieldName
s]
ariaDescriptionChannelProperty (ADTimeUnit TimeUnit
tu) = [TimeUnit -> Pair
timeUnit_ TimeUnit
tu]
ariaDescriptionChannelProperty (ADTitle FieldName
t) = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
t]
ariaDescriptionChannelProperty AriaDescriptionChannel
ADNoTitle = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null]


----

{-|

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' 'Graphics.Vega.VegaLite.Ordinal'
    , 'MScale' (domainRangeMap (1955, \"rgb(230,149,156)\") (2000, \"rgb(145,26,36)\"))
    ]
@
-}

domainRangeMap :: (Double, Color) -> (Double, Color) -> [ScaleProperty]
domainRangeMap :: (Double, FieldName) -> (Double, FieldName) -> [ScaleProperty]
domainRangeMap (Double, FieldName)
lowerMap (Double, FieldName)
upperMap =
  let ([Double]
domain, [FieldName]
range) = forall a b. [(a, b)] -> ([a], [b])
unzip [(Double, FieldName)
lowerMap, (Double, FieldName)
upperMap]
  in [DomainLimits -> ScaleProperty
SDomain ([Double] -> DomainLimits
DNumbers [Double]
domain), ScaleRange -> ScaleProperty
SRange ([FieldName] -> ScaleRange
RStrings [FieldName]
range)]


{-|

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" )
            ]
        )
    ]
@
-}

categoricalDomainMap :: [(T.Text, Color)] -> [ScaleProperty]
categoricalDomainMap :: [(FieldName, FieldName)] -> [ScaleProperty]
categoricalDomainMap [(FieldName, FieldName)]
scaleDomainPairs =
  let ([FieldName]
domain, [FieldName]
range) = forall a b. [(a, b)] -> ([a], [b])
unzip [(FieldName, FieldName)]
scaleDomainPairs
  in [DomainLimits -> ScaleProperty
SDomain ([FieldName] -> DomainLimits
DStrings [FieldName]
domain), ScaleRange -> ScaleProperty
SRange ([FieldName] -> ScaleRange
RStrings [FieldName]
range)]


{-|

Types of facet channel property used for creating a composed facet view of small
multiples.

-}

-- based on schema 3.3.0 #/definitions/FacetFieldDef
-- although it's a bit different now (maybe RowColumnEncodingFieldDef in 4.2.0)


data FacetChannel
    = FName FieldName
      -- ^ The name of the field from which to pull a data value.
    | FmType Measurement
      -- ^ The encoded field's type of measurement.
    | FAggregate Operation
      -- ^ Aggregation function for the field.
    | FAlign CompositionAlignment
      -- ^ The alignment to apply to the row- or column- facet's subplot.
      --
      --   @since 0.6.0.0
    | FBin [BinProperty]
      -- ^ Describe how to bin quantitative fields, or whether the
      --   channels are already binned.
    | FCenter Bool
      -- ^ Should sub-views be centered relative to their respective rows or
      --   columns.
      --
      --   @since 0.6.0.0
    | FHeader [HeaderProperty]
      -- ^ The properties of a facet's header.
    | FSort [SortProperty]
      -- ^ Sort order for the encoded field.
      --
      --   @since 0.4.0.0
    | FSpacing Double
      -- ^ The pixel spacing between sub-views.
      --
      --   If you have code from a version of @hvega@ before @0.6.0.0@ that
      --   uses @FSpacing@ (with 'Graphics.Vega.VegaLite.FacetStyle'), please
      --   use 'Graphics.Vega.VegaLite.CompSpacing' as a replacement.
      --
      --   @since 0.6.0.0
    | FTimeUnit TimeUnit
      -- ^ The time-unit for a temporal field.
    | FTitle T.Text
      -- ^ The title for the field.
      --
      --   @since 0.4.0.0
    | FNoTitle
      -- ^ Draw no title.
      --
      -- @since 0.4.0.0

facetChannelProperty :: FacetChannel -> Pair
facetChannelProperty :: FacetChannel -> Pair
facetChannelProperty (FName FieldName
s) = Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s
facetChannelProperty (FmType Measurement
measure) = Measurement -> Pair
mtype_ Measurement
measure
facetChannelProperty (FAlign CompositionAlignment
algn) = Key
"align" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
algn
facetChannelProperty (FAggregate Operation
op) = Operation -> Pair
aggregate_ Operation
op
facetChannelProperty (FBin [BinProperty]
bps) = [BinProperty] -> Pair
bin [BinProperty]
bps
facetChannelProperty (FCenter Bool
b) = Key
"center" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
facetChannelProperty (FHeader [HeaderProperty]
hps) = (FieldName, VLSpec) -> Pair
toKey (FieldName -> [HeaderProperty] -> (FieldName, VLSpec)
header_ FieldName
"" [HeaderProperty]
hps)
facetChannelProperty (FSort [SortProperty]
sps) = [SortProperty] -> Pair
sort_ [SortProperty]
sps
facetChannelProperty (FSpacing Double
x) = Key
"spacing" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
facetChannelProperty (FTitle FieldName
s) = Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s
facetChannelProperty FacetChannel
FNoTitle = Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null
facetChannelProperty (FTimeUnit TimeUnit
tu) = TimeUnit -> Pair
timeUnit_ TimeUnit
tu


-- | Types of text channel property used for displaying text as part of the visualization.

-- Basing the following partly on vega-lite-3.3.0.json / TextFieldDef
-- but that doesn't seem to be sufficient.

data TextChannel
    = TName FieldName
      -- ^ Name of the field used for encoding with a text channel.
    | TRepeat Arrangement
      -- ^ Reference in a text channel to a field name generated by 'repeatFlow'
      --   or 'repeat'. The parameter identifies whether reference is being made to
      --   fields that are to be arranged in columns, in rows, or a with a flow layout.
    | TRepeatDatum Arrangement
      -- ^ Reference in a text channel to a datum value generated by 'repeatFlow'
      --   or 'repeat'. The parameter identifies whether reference is being made to
      --   a datum that is to be encoded in layers, or in columns or rows in a
      --   flow layout.
      --
      --   @since 0.9.0.0
    | TmType Measurement
      -- ^ Level of measurement when encoding with a text channel.
    | TAggregate Operation
      -- ^ Compute some aggregate summary statistics for a field to be encoded with a
      --   text channel. The type of aggregation is determined by the given operation
      --   parameter.
    | TBand Double
      -- ^ Specify the mark position or size relative to the band size.
      --   The value is in the range 0 to 1, inclusive.
      --
      --   @since 0.9.0.0
    | TBin [BinProperty]
      -- ^ Discretize numeric values into bins when encoding with a text channel.
    | TBinned
      -- ^ Indicate that data encoded with a text channel are already binned.
      --
      --   @since 0.4.0.0
    | TDataCondition [(BooleanOp, [TextChannel])] [TextChannel]
      -- ^ Make a text channel conditional on one or more predicate expressions. The first
      --   parameter is a list of tuples each pairing an expression to evaluate with the encoding
      --   if that expression is @True@. The second is the encoding if none of the expressions
      --   evaluate as @True@.
      --
      --   The arguments to this constructor have changed in @0.4.0.0@
      --   to support multiple expressions.
    | TSelectionCondition BooleanOp [TextChannel] [TextChannel]
      -- ^ Make a text channel conditional on interactive selection. The first parameter
      --   is a selection condition to evaluate; the second the encoding to apply if that
      --   selection is true; the third parameter is the encoding if the selection is false.
    | TDatum DataValue
      -- ^ A constant value in the data domain.
      --
      --   @since 0.9.0.0
    | TFormat T.Text
      -- ^ [Formatting pattern](https://vega.github.io/vega-lite/docs/format.html)
      --   for text marks. To distinguish between formatting as numeric values and data/time
      --   values, additionally use 'TFormatAsNum', 'TFormatAsTemporal', and
      --   'TFormatAsCustom'.
    | TFormatAsNum
      -- ^ The text marks should be formatted as numbers. Use a
      --   [d3 numeric format string](https://github.com/d3/d3-format#locale_format)
      --   with 'TFormat'.
      --
      --   @since 0.4.0.0
    | TFormatAsTemporal
      -- ^ The text marks should be formatted as dates or times. Use a
      --   [d3 date/time format string](https://github.com/d3/d3-time-format#locale_format)
      --   with 'TFormat'.
      --
      --   @since 0.4.0.0
    | TFormatAsCustom T.Text
      -- ^ The [custom format type](https://vega.github.io/vega-lite/docs/config.html#custom-format-type)
      --   for use with with 'TFormat'.
      --
      --   @since 0.9.0.0
    | TLabelExpr VegaExpr
      -- ^ Provide the expression used to generate labels.
      --
      --   @since 0.9.0.0
    | TString T.Text
      -- ^ A literal value for encoding a text property channel. See also 'TStrings'.
      --
      --   This can be useful for a text annotation, such as:
      --
      --   @
      --   'encoding'
      --      . 'position' 'Graphics.Vega.VegaLite.X' [ 'PNumber' 300 ]
      --      . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PNumber' 1234 ]
      --      . 'text' [ 'TString' \"Upper limit\" ]
      --   @
      --
      --   @since 0.5.0.0
    | TStrings [T.Text]
      -- ^ A multi-line value. See also 'TString'.
      --
      --   @since 0.7.0.0
    | TTimeUnit TimeUnit
      -- ^ Time unit aggregation of field values when encoding with a text channel.
    | TTitle T.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

textChannelProperty :: TextChannel -> [Pair]
textChannelProperty :: TextChannel -> [Pair]
textChannelProperty (TName FieldName
s) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s]
textChannelProperty (TRepeat Arrangement
arr) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr]]
textChannelProperty (TRepeatDatum Arrangement
arr) = [Key
"datum" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr]]
textChannelProperty (TmType Measurement
measure) = [Measurement -> Pair
mtype_ Measurement
measure]
textChannelProperty (TAggregate Operation
op) = [Operation -> Pair
aggregate_ Operation
op]
textChannelProperty (TBand Double
x) = [Key
"band" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x]
textChannelProperty (TBin [BinProperty]
bps) = [[BinProperty] -> Pair
bin [BinProperty]
bps]
textChannelProperty TextChannel
TBinned = [Pair
binned_]
textChannelProperty (TDataCondition [(BooleanOp, [TextChannel])]
tests [TextChannel]
elseClause) =
  forall a. (a -> [Pair]) -> [(BooleanOp, [a])] -> [a] -> [Pair]
dataCond_ TextChannel -> [Pair]
textChannelProperty [(BooleanOp, [TextChannel])]
tests [TextChannel]
elseClause
textChannelProperty (TSelectionCondition BooleanOp
selName [TextChannel]
ifClause [TextChannel]
elseClause) =
  forall a. (a -> [Pair]) -> BooleanOp -> [a] -> [a] -> [Pair]
selCond_ TextChannel -> [Pair]
textChannelProperty BooleanOp
selName [TextChannel]
ifClause [TextChannel]
elseClause
textChannelProperty (TDatum DataValue
dv) = [Key
"datum" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DataValue -> VLSpec
dataValueSpec DataValue
dv]
textChannelProperty (TFormat FieldName
fmt) = [Key
"format" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
fmt]
textChannelProperty TextChannel
TFormatAsNum = [Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromT FieldName
"number"]
textChannelProperty TextChannel
TFormatAsTemporal = [Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
fromT FieldName
"time"]
textChannelProperty (TFormatAsCustom FieldName
c) = [Key
"formatType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
c]
textChannelProperty (TLabelExpr FieldName
e) = [Key
"labelExpr" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
e]
textChannelProperty (TString FieldName
s) = [Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s]
textChannelProperty (TStrings [FieldName]
xs) = [Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
xs]
textChannelProperty (TTimeUnit TimeUnit
tu) = [TimeUnit -> Pair
timeUnit_ TimeUnit
tu]
textChannelProperty (TTitle FieldName
s) = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName -> VLSpec
splitOnNewline FieldName
s]
textChannelProperty TextChannel
TNoTitle = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null]


-- | Properties of an ordering channel used for sorting data fields.

-- maps to OrderFieldDef

data OrderChannel
    = OName FieldName
      -- ^ The name of the field used for encoding with an order channel.
    | ORepeat Arrangement
      -- ^ Reference in an order channel to a field name generated by 'repeatFlow'
      -- or 'repeat'. The parameter identifies whether reference is being made to
      -- fields that are to be arranged in columns, in rows, or a with a flow layout.
    | OAggregate Operation
      -- ^ Compute some aggregate summary statistics for a field to be encoded
      --   with an order channel.
    | OBand Double
      -- ^ For rect-based marks, define the mark size relative to the bandwidth of
      --   band scales, bins, or time units: a value of 1 uses the range and 0.5
      --   half the range. For other marks it defines the relative position in a
      --   band of a stacked, binned, time unit, or band scale: if 0 the marks
      --   will be positioned at the beginning of the band and 0.5 gives the
      --   middle of the band.
      --
      --   The argument must be in the range 0 to 1, inclusive, but there is no
      --   check on this.
      --
      --   @since 0.11.0.0
    | OBin [BinProperty]
      -- ^ Discretize numeric values into bins when encoding with an
      --   order channel.
    | OSort [SortProperty]
      -- ^ Sort order for field when encoding with an order channel.
    | OTimeUnit TimeUnit
      -- ^ Form of time unit aggregation of field values when encoding with
      --   an order channel.
    | OTitle T.Text
      -- ^ The title for the field.
      --
      --   Note that if both the field and axis, header, or legend titles are
      --   defined than the latter (axis, header, or legend) will be used.
      --
      --   @since 0.11.0.0
    | ONoTitle
      -- ^ Remove the title.
      --
      --   @since 0.11.0.0
    | OmType Measurement
      -- ^ The level of measurement when encoding with an order channel.
    | ODataCondition [(BooleanOp, [OrderChannel])] [OrderChannel]
      -- ^ Make an order channel conditional on one or more predicate expressions. The first
      --   parameter is a list of tuples each pairing an expression to evaluate with the encoding
      --   if that expression is @True@. The second is the encoding if none of the expressions
      --   evaluate as @True@.
      --
      --   @since 0.11.0.0
    | OSelectionCondition BooleanOp [OrderChannel] [OrderChannel]
      -- ^ Make an order channel conditional on interactive selection. The first parameter
      --   is a selection condition to evaluate; the second the encoding to apply if that
      --   selection is true; the third parameter is the encoding if the selection is false.
      --
      --   An example:
      --
      --   @'order' ['OSelectionCondition' ('SelectionName' "highlight")
      --           ['ONumber' 1] ['ONumber' 0]]
      --   @
      --
      --   @since 0.11.0.0
    | ONumber Double
      -- ^ Create a value with this number. For use with 'OSelectionCondition'
      --   and 'ODataCondition'.
      --
      --   @since 0.11.0.0

orderChannelProperty :: OrderChannel -> [Pair]
orderChannelProperty :: OrderChannel -> [Pair]
orderChannelProperty (OAggregate Operation
op) = [Operation -> Pair
aggregate_ Operation
op]
orderChannelProperty (OBand Double
x) = [Key
"band" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x]
orderChannelProperty (OBin [BinProperty]
bps) = [[BinProperty] -> Pair
bin [BinProperty]
bps]
orderChannelProperty (OName FieldName
s) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s]
orderChannelProperty (ORepeat Arrangement
arr) = [Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Arrangement -> Pair
repeat_ Arrangement
arr]]
orderChannelProperty (OSort [SortProperty]
ops) = [[SortProperty] -> Pair
sort_ [SortProperty]
ops]
orderChannelProperty (OTimeUnit TimeUnit
tu) = [TimeUnit -> Pair
timeUnit_ TimeUnit
tu]
orderChannelProperty (OTitle FieldName
s) = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s]
orderChannelProperty OrderChannel
ONoTitle = [Key
"title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
A.Null]
orderChannelProperty (OmType Measurement
measure) = [Measurement -> Pair
mtype_ Measurement
measure]
orderChannelProperty (ODataCondition [(BooleanOp, [OrderChannel])]
tests [OrderChannel]
elseClause) =
  forall a. (a -> [Pair]) -> [(BooleanOp, [a])] -> [a] -> [Pair]
dataCond_ OrderChannel -> [Pair]
orderChannelProperty [(BooleanOp, [OrderChannel])]
tests [OrderChannel]
elseClause
orderChannelProperty (OSelectionCondition BooleanOp
selName [OrderChannel]
ifClause [OrderChannel]
elseClause) =
  forall a. (a -> [Pair]) -> BooleanOp -> [a] -> [a] -> [Pair]
selCond_ OrderChannel -> [Pair]
orderChannelProperty BooleanOp
selName [OrderChannel]
ifClause [OrderChannel]
elseClause
orderChannelProperty (ONumber Double
n) = [Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
n]

-- | Level of detail channel properties used for creating a grouped channel
--   encoding.

data DetailChannel
    = DName FieldName
      -- ^ The name of the field.
    | DmType Measurement
      -- ^ The measurement type of the field.
    | DBin [BinProperty]
      -- ^ How to convert discrete numeric values into bins.
    | DTimeUnit TimeUnit
      -- ^ The form of time unit aggregation.
    | DAggregate Operation
      -- ^ How should the detail field be aggregated?


detailChannelProperty :: DetailChannel -> Pair
detailChannelProperty :: DetailChannel -> Pair
detailChannelProperty (DName FieldName
s) = Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
s  -- field_ s
detailChannelProperty (DmType Measurement
t) = Measurement -> Pair
mtype_ Measurement
t
detailChannelProperty (DBin [BinProperty]
bps) = [BinProperty] -> Pair
bin [BinProperty]
bps
detailChannelProperty (DTimeUnit TimeUnit
tu) = TimeUnit -> Pair
timeUnit_ TimeUnit
tu
detailChannelProperty (DAggregate Operation
op) = Operation -> Pair
aggregate_ Operation
op


{-|

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
<https://vega.github.io/vega-lite/docs/facet.html#mapping Vega-Lite documentation>.
-}
data FacetMapping
    = ColumnBy [FacetChannel]
    | RowBy [FacetChannel]


facetMappingProperty :: FacetMapping -> Pair
facetMappingProperty :: FacetMapping -> Pair
facetMappingProperty (RowBy [FacetChannel]
fFields) =
  Key
"row" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> Pair
facetChannelProperty [FacetChannel]
fFields)
facetMappingProperty (ColumnBy [FacetChannel]
fFields) =
  Key
"column" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> Pair
facetChannelProperty [FacetChannel]
fFields)


{-|

Create a single global configuration from a list of configuration specifications.
Configurations are applied to all relevant items in the specification. See the
<https://vega.github.io/vega-lite/docs/config.html 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'
        . 'Graphics.Vega.VegaLite.configuration' ('Graphics.Vega.VegaLite.Axis' [ 'Graphics.Vega.VegaLite.DomainWidth' 1 ])
        . 'Graphics.Vega.VegaLite.configuration' ('Graphics.Vega.VegaLite.ViewStyle' [ 'Graphics.Vega.VegaLite.ViewStroke' "transparent" ])
        . 'Graphics.Vega.VegaLite.configuration' ('Graphics.Vega.VegaLite.SelectionStyle' [ ( 'Graphics.Vega.VegaLite.Single', [ 'Graphics.Vega.VegaLite.On' \"dblclick\" ] ) ])
@
-}

configure ::
  [ConfigureSpec]
  -- ^ The configuration options, created with 'Graphics.Vega.VegaLite.configuration'.
  --
  --    Prior to version @0.5.0.0@ this was @['LabelledSpec']@.
  -> PropertySpec
configure :: [ConfigureSpec] -> PropertySpec
configure [ConfigureSpec]
configs = (VLProperty
VLConfig, [(FieldName, VLSpec)] -> VLSpec
toObject (forall a b. (a -> b) -> [a] -> [b]
map ConfigureSpec -> (FieldName, VLSpec)
unCS [ConfigureSpec]
configs))


-- | 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

align :: CompositionAlignment -> PropertySpec
align :: CompositionAlignment -> PropertySpec
align CompositionAlignment
algn = (VLProperty
VLAlign, CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
algn)


-- | Similar to 'align' but with independent alignments for rows and columns.
--
--   See also 'align'.
--
--   @since 0.4.0.0

alignRC ::
  CompositionAlignment     -- ^ Row alignment
  -> CompositionAlignment  -- ^ Column alignment
  -> PropertySpec
alignRC :: CompositionAlignment -> CompositionAlignment -> PropertySpec
alignRC CompositionAlignment
alRow CompositionAlignment
alCol =
  (VLProperty
VLSpacing, [Pair] -> VLSpec
object [ Key
"row" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
alRow
                     , Key
"col" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CompositionAlignment -> VLSpec
compositionAlignmentSpec CompositionAlignment
alCol
                     ])


-- | Spacing between sub-views in a composition operator.
--
--   See also 'spacingRC'.
--
--   @since 0.4.0.0

spacing ::
  Double   -- ^ Spacing in pixels.
  -> PropertySpec
spacing :: Double -> PropertySpec
spacing Double
sp = (VLProperty
VLSpacing, forall a. ToJSON a => a -> VLSpec
toJSON Double
sp)


-- | Set the spacing between the rows and columns.
--
--   See also 'spacing'.
--
--   @since 0.4.0.0

spacingRC ::
  Double      -- ^ Spacing between rows (in pixels).
  -> Double   -- ^ Spacing between columns (in pixels).
  -> PropertySpec
spacingRC :: Double -> Double -> PropertySpec
spacingRC Double
spRow Double
spCol = (VLProperty
VLSpacing, [Pair] -> VLSpec
object [Key
"row" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
spRow, Key
"column" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
spCol])


-- | Are sub-views in a composition operator centred relative to their respective
--   rows and columns?
--
--   See also 'centerRC'.
--
--   @since 0.4.0.0

center :: Bool -> PropertySpec
center :: Bool -> PropertySpec
center Bool
c = (VLProperty
VLCenter, forall a. ToJSON a => a -> VLSpec
toJSON Bool
c)


-- | Are sub-views in a composition operator centred relative to their respective
--   rows and columns?
--
--   See also 'center'.
--
--   @since 0.4.0.0

centerRC ::
  Bool     -- ^ Are rows to be centered?
  -> Bool  -- ^ Are columns to be centered?
  -> PropertySpec
centerRC :: Bool -> Bool -> PropertySpec
centerRC Bool
cRow Bool
cCol = (VLProperty
VLCenter, [Pair] -> VLSpec
object [Key
"row" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
cRow, Key
"col" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
cCol])


{-|

Bounds calculation method to use for determining the extent of a sub-plot in
a composed view.

@since 0.4.0.0
-}
bounds :: Bounds -> PropertySpec
bounds :: Bounds -> PropertySpec
bounds Bounds
bnds = (VLProperty
VLBounds, Bounds -> VLSpec
boundsSpec Bounds
bnds)


{-|

The list of specifications to be juxtaposed horizontally in a flow
layout of views.
See also 'hConcat' and 'vConcat'.

The number of columns in the flow layout can be set with 'columns'
and, if not specified, will default to a single row of unlimited columns.

@
let dvals = 'Graphics.Vega.VegaLite.dataSequenceAs' 0 6.28 0.1 \"x\"
    trans = 'transform'
              . 'calculateAs' \"sin(datum.x)\" \"sinX\"
              . 'calculateAs' \"cos(datum.x)\" \"cosX\"
    enc = 'encoding'
            . 'position' 'Graphics.Vega.VegaLite.X' ['PName' \"x\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']
    encCos = enc . 'position' 'Graphics.Vega.VegaLite.Y' ['PName' \"cosX\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']
    encSin = enc . 'position' 'Graphics.Vega.VegaLite.Y' ['PName' \"sinX\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']

in toVegaLite [ dvals
              , trans []
              , 'vlConcat' [ 'Graphics.Vega.VegaLite.asSpec' [encCos [], 'mark' 'Graphics.Vega.VegaLite.Line' []]
                         , 'Graphics.Vega.VegaLite.asSpec' [encSin [], 'mark' 'Graphics.Vega.VegaLite.Line' []]
                         ]
              ]
@

This is named @concat@ in Elm VegaLite but has been renamed here
to avoid conflicting with the Prelude.

@since 0.4.0.0

-}
vlConcat :: [VLSpec] -> PropertySpec
vlConcat :: [VLSpec] -> PropertySpec
vlConcat [VLSpec]
specs = (VLProperty
VLConcat, forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
specs)


{-|

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 'Graphics.Vega.VegaLite.asSpec'.

See the
<https://vega.github.io/vega-lite/docs/facet.html Vega-Lite documentation>
for further details.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ facet [ 'RowBy' [ 'FName' \"Month\", 'FmType' 'Graphics.Vega.VegaLite.Ordinal' ]
            , 'ColumnBy' [ 'FName' \"Week\", 'FmType' 'Graphics.Vega.VegaLite.Ordinal' ]
            ]
    , 'Graphics.Vega.VegaLite.specification' spec
    ]
@

See also 'facetFlow'.

-}

facet :: [FacetMapping] -> PropertySpec
facet :: [FacetMapping] -> PropertySpec
facet [FacetMapping]
fMaps = (VLProperty
VLFacet, [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map FacetMapping -> Pair
facetMappingProperty [FacetMapping]
fMaps))


{-|

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 'Graphics.Vega.VegaLite.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').

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ facetFlow [ 'FName' \"Origin\", 'FmType' 'Graphics.Vega.VegaLite.Nominal' ]
    , 'Graphics.Vega.VegaLite.specification' spec
    ]
@

See also 'facet'.

@since 0.4.0.0
-}
facetFlow :: [FacetChannel] -> PropertySpec
facetFlow :: [FacetChannel] -> PropertySpec
facetFlow [FacetChannel]
fFields = (VLProperty
VLFacet, [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> Pair
facetChannelProperty [FacetChannel]
fFields))


{-|

Overrides the default height of the visualization. If not specified the height
will be calculated based on the content of the visualization. See
'autosize' for customization of the content sizing relative to this
setting, 'heightOfContainer' for setting the height to that of
the surrounding container,
and 'heightStep' for setting the height of discrete fields.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'height' 300
    , 'Graphics.Vega.VegaLite.dataFromUrl' "data/population.json" []
    , 'mark' 'Graphics.Vega.VegaLite.Bar' []
    , enc []
    ]
@
-}
height :: Double -> PropertySpec
height :: Double -> PropertySpec
height Double
h = (VLProperty
VLHeight, forall a. ToJSON a => a -> VLSpec
toJSON Double
h)


{-|
Set the height of the view to that of the surrounding container,
to allow for responsive sizing.

Please see the [Vega Lite responsive sizing](https://vega.github.io/vega-lite/docs/size.html#specifying-responsive-width-and-height)
documentation for caveats and limitations.

@since 0.5.0.0
-}
heightOfContainer :: PropertySpec
heightOfContainer :: PropertySpec
heightOfContainer = (VLProperty
VLHeight, FieldName -> VLSpec
fromT FieldName
"container")


{-|

Set the height of the discrete y-field (e.g. individual bars in a
horizontal bar chart).
The total height is then calculated based on the number of discrete fields
(e.g. bars).

@
'Graphics.Vega.VegaLite.toVegaLite'
  [ 'heightStep' 17
  , data []
  , enc []
  , 'mark' 'Graphcs.Vega.VegaLite.Bar' []
  ]
@

This replaces the use of @SRangeStep@ from 'ScaleProperty'.

@since 0.5.0.0
-}

-- Note that unlike ELm, we do not create a separate property here
-- (ie no VLHeightStep)
--
heightStep :: Double -> PropertySpec
heightStep :: Double -> PropertySpec
heightStep Double
s = (VLProperty
VLHeight, [Pair] -> VLSpec
object [ Key
"step" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
s ])


{-|

Assigns a list of specifications to be juxtaposed horizontally in a visualization.
See also 'vConcat' and 'vlConcat'.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'Graphics.Vega.VegaLite.dataFromUrl' "data/driving.json" []
    , hConcat [ spec1, spec2 ]
    ]
@
-}
hConcat :: [VLSpec] -> PropertySpec
hConcat :: [VLSpec] -> PropertySpec
hConcat [VLSpec]
specs = (VLProperty
VLHConcat, forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
specs)


{-|

Assigns a list of specifications to superposed layers in a visualization.

@
'Graphics.Vega.VegaLite.toVegaLite' ['Graphics.Vega.VegaLite.dataFromUrl' "data/driving.json" [], layer [spec1, spec2]]
@

A complete example showing @layer@ in use:

@
let dvals = 'Graphics.Vega.VegaLite.dataFromColumns' []
              . 'Graphics.Vega.VegaLite.dataColumn' \"x\" ('Numbers' [1, 2, 3, 4, 5])
              . 'Graphics.Vega.VegaLite.dataColumn' \"a\" ('Numbers' [28, 91, 43, 55, 81])
    enc = 'encoding'
             . 'position' 'Graphics.Vega.VegaLite.X' ['PName' \"x\", 'PmType' 'Graphics.Vega.VegaLite.Ordinal']
             . 'position' 'Graphics.Vega.VegaLite.Y' ['PName' \"a\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']
             . 'text' ['TName' \"a\", 'TmType' 'Graphics.Vega.VegaLite.Nominal']

    in 'Graphics.Vega.VegaLite.toVegaLite' [ dvals []
                  , enc []
                  , 'layer' [ 'Graphics.Vega.VegaLite.asSpec' ['mark' 'Graphics.Vega.VegaLite.Bar' []]
                          , 'Graphics.Vega.VegaLite.asSpec' ['mark' 'Graphics.Vega.VegaLite.Text' ['Graphics.Vega.VegaLite.MdY' (-8)]]
                          ]
                  ]
@

-}
layer :: [VLSpec] -> PropertySpec
layer :: [VLSpec] -> PropertySpec
layer [VLSpec]
specs = (VLProperty
VLLayer, forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
specs)


{-|

Provides an optional name to be associated with the visualization.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'name' \"PopGrowth\"
    , 'Graphics.Vega.VegaLite.dataFromUrl' \"data/population.json\" []
    , 'mark' 'Graphics.Vega.VegaLite.Bar' []
    , enc []
    ]
@
-}
name :: T.Text -> PropertySpec
name :: FieldName -> PropertySpec
name FieldName
s = (VLProperty
VLName, forall a. ToJSON a => a -> VLSpec
toJSON FieldName
s)


{-|

Set the padding around the visualization in pixel units. The way padding is
interpreted will depend on the 'autosize' properties. See the
<https://vega.github.io/vega-lite/docs/spec.html#top-level-specifications Vega-Lite documentation>
for details.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'width' 500
    , 'padding' ('Graphics.Vega.VegaLite.PEdges' 20 10 5 15)
    , 'Graphics.Vega.VegaLite.dataFromUrl' "data/population.json" []
    , 'mark' 'Graphics.Vega.VegaLite.Bar' []
    , enc []
    ]
@
-}
padding :: Padding -> PropertySpec
padding :: Padding -> PropertySpec
padding Padding
pad = (VLProperty
VLPadding, Padding -> VLSpec
paddingSpec Padding
pad)


{-|

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 'Graphics.Vega.VegaLite.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
<https://vega.github.io/vega-lite/docs/repeat.html Vega-Lite documentation>
for further details.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'repeat' ['Graphics.Vega.VegaLite.ColumnFields' [\"Cat\", \"Dog\", \"Fish\"]]
    , 'Graphics.Vega.VegaLite.specification' ('Graphics.Vega.VegaLite.asSpec' spec)
    ]
@

See also 'repeatFlow'.

-}

repeat :: [RepeatFields] -> PropertySpec
repeat :: [RepeatFields] -> PropertySpec
repeat [RepeatFields]
fields = (VLProperty
VLRepeat, [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map RepeatFields -> Pair
repeatFieldsProperty [RepeatFields]
fields))


{-|

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 'Graphics.Vega.VegaLite.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').

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'repeatFlow' [ \"Cat\", \"Dog\", \"Fish\" ]
    , 'Graphics.Vega.VegaLite.specification' ('Graphics.Vega.VegaLite.asSpec' spec)
    ]
@

See also 'repeat'.

@since 0.4.0.0

-}
repeatFlow ::
  [FieldName]
  -> PropertySpec
repeatFlow :: [FieldName] -> PropertySpec
repeatFlow [FieldName]
fields = (VLProperty
VLRepeat, forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
fields)


{-|

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' ('Graphics.Vega.VegaLite.RLegend' [('Graphics.Vega.VegaLite.ChColor', 'Graphics.Vega.VegaLite.Independent')])

in 'Graphics.Vega.VegaLite.toVegaLite'
    [ 'Graphics.Vega.VegaLite.dataFromUrl' \"data/movies.json\" []
    , 'vConcat' [heatSpec, barSpec]
    , res []
    ]
@

For more information see the
<https://vega.github.io/vega-lite/docs/resolve.html Vega-Lite documentation>.

@
let dvals = 'Graphics.Vega.VegaLite.dataFromColumns' []
              . 'Graphics.Vega.VegaLite.dataColumn' "x" ('Numbers' [1, 2, 3, 4, 5])
              . 'Graphics.Vega.VegaLite.dataColumn' "a" ('Numbers' [28, 91, 43, 55, 81])
              . 'Graphics.Vega.VegaLite.dataColumn' "b" ('Numbers' [17, 22, 28, 30, 40])
    encBar = 'encoding'
               . 'position' 'Graphics.Vega.VegaLite.X' ['PName' \"x\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']
               . 'position' 'Graphics.Vega.VegaLite.Y' ['PName' \"a\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']
    specBar = 'Graphics.Vega.VegaLite.asSpec' ['mark' 'Graphics.Vega.VegaLite.Bar' [], encBar []]
    encLine = 'encoding'
                . 'position' 'Graphics.Vega.VegaLite.X' ['PName' \"x\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']
                . 'position' 'Graphics.Vega.VegaLite.Y' ['PName' \"b\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']
    specLine = 'Graphics.Vega.VegaLite.asSpec' ['mark' 'Graphics.Vega.VegaLite.Line' ['Graphics.Vega.VegaLite.MColor' \"firebrick\"], encLine []]
    res = 'resolve'
            . 'resolution' ('Graphics.Vega.VegaLite.RScale' [('Graphics.Vega.VegaLite.ChY', 'Graphics.Vega.VegaLite.Independent')])

in 'Graphics.Vega.VegaLite.toVegaLite' [dvals [], res [], 'layer' [specBar, specLine]]
@

-}
resolve ::
  [ResolveSpec]
  -- ^ The arguments created by 'Graphics.Vega.VegaLite.resolution'.
  --
  --   Prior to @0.5.0.0@ this argument was @['LabelledSpec']@.
  -> PropertySpec
resolve :: [ResolveSpec] -> PropertySpec
resolve [ResolveSpec]
res = (VLProperty
VLResolve, [(FieldName, VLSpec)] -> VLSpec
toObject (forall a b. (a -> b) -> [a] -> [b]
map ResolveSpec -> (FieldName, VLSpec)
unRS [ResolveSpec]
res))


{-|

Create a single transform from a list of transformation
specifications. Note that the order of transformations can be
important, especially if labels created with 'calculateAs',
'timeUnitAs', and 'binAs' are used in other transformations.  Using
the functional composition pipeline idiom (as example below) allows
you to provide the transformations in the order intended in a clear
manner.

@
'transform'
    . 'filter' ('FExpr' "datum.year == 2010")
    . 'calculateAs' "datum.sex == 2 ? \'Female\' : \'Male\'" "gender"
@

The supported transformations are:
'aggregate', 'binAs', 'calculateAs', 'density', 'filter', 'flatten',
'flattenAs', 'fold', 'foldAs', 'impute', 'joinAggregate', 'loess',
'lookup', 'lookupAs', 'lookupSelection', 'pivot', 'quantile',
'regression', 'sample', 'stack', 'timeUnitAs', and 'window'.

-}

transform ::
  [TransformSpec]
  -- ^ The transformations to apply. The order does matter.
  --
  --   Prior to @0.5.0.0@ this argument was @['LabelledSpec']@.
  -> PropertySpec
transform :: [TransformSpec] -> PropertySpec
transform [TransformSpec]
transforms =
  let js :: VLSpec
js = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TransformSpec]
transforms then VLSpec
A.Null else forall a. ToJSON a => a -> VLSpec
toJSON (forall a b. (a -> b) -> [a] -> [b]
map TransformSpec -> VLSpec
unTS [TransformSpec]
transforms)
  in (VLProperty
VLTransform, VLSpec
js)


{-|

Assigns a list of specifications to be juxtaposed vertically in a visualization.
See also 'hConcat' and 'vlConcat'.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'Graphics.Vega.VegaLite.dataFromUrl' "data/driving.json" []
    , 'vConcat' [ spec1, spec2 ]
    ]
@
-}
vConcat :: [VLSpec] -> PropertySpec
vConcat :: [VLSpec] -> PropertySpec
vConcat [VLSpec]
specs = (VLProperty
VLVConcat, forall a. ToJSON a => a -> VLSpec
toJSON [VLSpec]
specs)


{-|

Override the default width of the visualization. If not specified the width
will be calculated based on the content of the visualization. See
'autosize' for customization of the content sizing relative to this
setting, 'widthOfContainer' for setting the width to that of
the surrounding container,
and 'widthStep' for setting the width of discrete fields.

@
'Graphics.Vega.VegaLite.toVegaLite'
    [ 'width' 500
    , 'Graphics.Vega.VegaLite.dataFromUrl' "data/population.json" []
    , 'mark' 'Graphics.Vega.VegaLite.Bar' []
    , enc []
    ]
@
-}
width :: Double -> PropertySpec
width :: Double -> PropertySpec
width Double
w = (VLProperty
VLWidth, forall a. ToJSON a => a -> VLSpec
toJSON Double
w)


{-|
Set the width of the view to that of the surrounding container,
to allow for responsive sizing.

Please see the [Vega Lite responsive sizing](https://vega.github.io/vega-lite/docs/size.html#specifying-responsive-width-and-height)
documentation for caveats and limitations.

@since 0.5.0.0
-}
widthOfContainer :: PropertySpec
widthOfContainer :: PropertySpec
widthOfContainer = (VLProperty
VLWidth, FieldName -> VLSpec
fromT FieldName
"container")


{-|

Set the width of the discrete x-field (e.g. individual bars in a bar chart).
The total width is then calculated based on the number of discrete fields
(e.g. bars).

@
'Graphics.Vega.VegaLite.toVegaLite'
  [ 'widthStep' 17
  , data []
  , enc []
  , 'mark' 'Graphcs.Vega.VegaLite.Bar' []
  ]
@

This replaces the use of @SRangeStep@ from 'ScaleProperty'.

@since 0.5.0.0
-}

-- Note that unlike ELm, we do not create a separate property here
-- (ie no VLWidthStep)
--
widthStep :: Double -> PropertySpec
widthStep :: Double -> PropertySpec
widthStep Double
s = (VLProperty
VLWidth, [Pair] -> VLSpec
object [ Key
"step" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
s ])


{-|

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
<https://vega.github.io/vega-lite/docs/aggregate.html#aggregate-op-def Vega-Lite documentation>.

@
'transform'
    . 'aggregate'
        [ 'opAs' 'Graphics.Vega.VegaLite.Min' "people" "lowerBound"
        , 'opAs' 'Graphics.Vega.VegaLite.Max' "people" "upperBound" ]
        [ "age" ]
@

See also 'joinAggregate'.

-}
aggregate ::
  [VLSpec]
  -- ^ The named aggregation operations to apply.
  -> [FieldName]
  -- ^ The \"group by\" fields.
  -> BuildTransformSpecs
aggregate :: [VLSpec] -> [FieldName] -> BuildTransformSpecs
aggregate [VLSpec]
ops [FieldName]
groups [TransformSpec]
ols =
  let fields :: [Pair]
fields = [ Key
"aggregate" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [VLSpec]
ops
               , Key
"groupby" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
groups ]
  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
fields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

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' 'Graphics.Vega.VegaLite.Mean' "rating" "avYearRating" ]
        [ 'Graphics.Vega.VegaLite.WGroupBy' [ "year" ] ]
    . 'filter' ('FExpr' "(datum.rating - datum.avYearRating) > 3"))
@

For details, see the
<https://vega.github.io/vega-lite/docs/joinaggregate.html Vega-Lite join aggregate documentation>.

See also 'aggregate'.

@since 0.4.0.0
-}

joinAggregate ::
  [VLSpec]
  -> [WindowProperty]
  -> BuildTransformSpecs
joinAggregate :: [VLSpec] -> [WindowProperty] -> BuildTransformSpecs
joinAggregate [VLSpec]
ops [WindowProperty]
wProps [TransformSpec]
ols = [VLSpec] -> [WindowProperty] -> TransformSpec
joinAggregateTS [VLSpec]
ops [WindowProperty]
wProps forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Window transform for performing calculations over sorted groups of
data objects such as ranking, lead/lag analysis, running sums and averages.

@
'transform'
    . 'window' [ ( [ 'Graphics.Vega.VegaLite.WAggregateOp' 'Graphics.Vega.VegaLite.Sum', 'Graphics.Vega.VegaLite.WField' \"Time\" ], \"TotalTime\" ) ]
             [ 'Graphics.Vega.VegaLite.WFrame' Nothing Nothing ]
@

@since 0.4.0.0

-}
window ::
  [([Window], FieldName)]
  -- ^ The window-transform definition and associated output name.
  -> [WindowProperty]
  -- ^ The window transform.
  -> BuildTransformSpecs
window :: [([Window], FieldName)] -> [WindowProperty] -> BuildTransformSpecs
window [([Window], FieldName)]
wss [WindowProperty]
wProps [TransformSpec]
ols = [([Window], FieldName)] -> [WindowProperty] -> TransformSpec
windowTS [([Window], FieldName)]
wss [WindowProperty]
wProps forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

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 = 'Graphics.Vega.VegaLite.dataSequenceAs' 0 13 0.001 \"x\"
 trans = 'transform'
           . 'calculateAs' \"sin(datum.x)\" \"y\"
           . 'sample' 50
@

@since 0.4.0.0

-}

sample :: Int -> BuildTransformSpecs
sample :: Int -> BuildTransformSpecs
sample Int
maxSize [TransformSpec]
ols = VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [ Key
"sample" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
maxSize ]) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Configure the kernel density estimation process. Used by 'density'.

@since 0.5.0.0
-}

data DensityProperty
  = DnAs FieldName FieldName
    -- ^ Name the outputs of a density transform. The first argument is the
    --   name of the field containing the samples and the second the name
    --   for the field containing the density estimates.
    --
    --   The defaults are @\"value\"@ and @\"density\"@ respectively.
  | DnBandwidth Double
    -- ^ The bandwidth (standard deviation) of the Gaussian kernel to be
    --   used in the KDE. If not given, or set to 0, then
    --   [Scott's method](https://stats.stackexchange.com/questions/90656/kernel-bandwidth-scotts-vs-silvermans-rules)
    --   is used.
  | DnCounts Bool
    -- ^ If @'True'@ then the KDE generates counts, if @'False'@ it
    --   generates probabilities.
    --
    --   The default is probabilities.
  | DnCumulative Bool
    -- ^ Should the density estimates be cumulative?
    --
    --   The default is @'False'@.
  | DnExtent Double Double
    -- ^ The domain (minimum to maximum) from which to sample a distribution
    --   for the density estimation.
    --
    --   The default is to use the full extent of the input values.
  | DnGroupBy [FieldName]
    -- ^ The data fields to group by.
    --
    --   The default is to use a single group containing all the data objects.
  | DnMaxSteps Natural
    -- ^ The maximum number of samples to take from the extent domain.
    --
    --   The default is 200.
  | DnMinSteps Natural
    -- ^ The minimum number of samples to take from the extent domain.
    --
    --   The default is 25.
  | DnSteps Natural
    -- ^ This overrides the 'DnMinSteps' and 'DnMaxSteps' options and
    --   specified an exact number of steps to take from the extent
    --   domain.
    --
    --   It can be used with 'DnExtent' to ensure a consistent
    --   set of sample points for stacked densities.


data DensityPropertyLabel =
  DPLGroupby | DPLCumulative | DPLCounts | DPLBandwidth | DPLExtent |
  DPLMinsteps | DPLMaxsteps | DPLSteps | DPLAs


densityPropertySpec :: DensityPropertyLabel -> [DensityProperty] -> VLSpec
densityPropertySpec :: DensityPropertyLabel -> [DensityProperty] -> VLSpec
densityPropertySpec DensityPropertyLabel
DPLGroupby [DensityProperty]
ps =
  let wanted :: DensityProperty -> Maybe [FieldName]
wanted (DnGroupBy [FieldName]
xs) = forall a. a -> Maybe a
Just [FieldName]
xs
      wanted DensityProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe [FieldName]
wanted [DensityProperty]
ps of
    [[FieldName]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
x
    [[FieldName]]
_ -> VLSpec
A.Null

densityPropertySpec DensityPropertyLabel
DPLCumulative [DensityProperty]
ps =
  let wanted :: DensityProperty -> Maybe Bool
wanted (DnCumulative Bool
xs) = forall a. a -> Maybe a
Just Bool
xs
      wanted DensityProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe Bool
wanted [DensityProperty]
ps of
    [Bool
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Bool
x
    [Bool]
_ -> VLSpec
A.Null

densityPropertySpec DensityPropertyLabel
DPLCounts [DensityProperty]
ps =
  let wanted :: DensityProperty -> Maybe Bool
wanted (DnCounts Bool
xs) = forall a. a -> Maybe a
Just Bool
xs
      wanted DensityProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe Bool
wanted [DensityProperty]
ps of
    [Bool
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Bool
x
    [Bool]
_ -> VLSpec
A.Null

densityPropertySpec DensityPropertyLabel
DPLBandwidth [DensityProperty]
ps =
  let wanted :: DensityProperty -> Maybe Double
wanted (DnBandwidth Double
xs) = forall a. a -> Maybe a
Just Double
xs
      wanted DensityProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe Double
wanted [DensityProperty]
ps of
    [Double
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Double
x
    [Double]
_ -> VLSpec
A.Null

densityPropertySpec DensityPropertyLabel
DPLExtent [DensityProperty]
ps =
  let wanted :: DensityProperty -> Maybe [Double]
wanted (DnExtent Double
xs Double
ys) = forall a. a -> Maybe a
Just [Double
xs, Double
ys]
      wanted DensityProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe [Double]
wanted [DensityProperty]
ps of
    [[Double]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [Double]
x
    [[Double]]
_ -> VLSpec
A.Null

densityPropertySpec DensityPropertyLabel
DPLMinsteps [DensityProperty]
ps =
  let wanted :: DensityProperty -> Maybe Natural
wanted (DnMinSteps Natural
xs) = forall a. a -> Maybe a
Just Natural
xs
      wanted DensityProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe Natural
wanted [DensityProperty]
ps of
    [Natural
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Natural
x
    [Natural]
_ -> VLSpec
A.Null

densityPropertySpec DensityPropertyLabel
DPLMaxsteps [DensityProperty]
ps =
  let wanted :: DensityProperty -> Maybe Natural
wanted (DnMaxSteps Natural
xs) = forall a. a -> Maybe a
Just Natural
xs
      wanted DensityProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe Natural
wanted [DensityProperty]
ps of
    [Natural
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Natural
x
    [Natural]
_ -> VLSpec
A.Null

densityPropertySpec DensityPropertyLabel
DPLSteps [DensityProperty]
ps =
  let wanted :: DensityProperty -> Maybe Natural
wanted (DnSteps Natural
xs) = forall a. a -> Maybe a
Just Natural
xs
      wanted DensityProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe Natural
wanted [DensityProperty]
ps of
    [Natural
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Natural
x
    [Natural]
_ -> VLSpec
A.Null

densityPropertySpec DensityPropertyLabel
DPLAs [DensityProperty]
ps =
  let wanted :: DensityProperty -> Maybe [FieldName]
wanted (DnAs FieldName
xs FieldName
ys) = forall a. a -> Maybe a
Just [FieldName
xs, FieldName
ys]
      wanted DensityProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DensityProperty -> Maybe [FieldName]
wanted [DensityProperty]
ps of
    [[FieldName]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
x
    [[FieldName]]
_ -> VLSpec
A.Null



{-|

Apply /Kernel Density Estimation/ to a data stream to generate a new stream
of samples of the estimated density. This is useful for representing
probability distributions and generating continuous distributions from
discrete samples.

The following example creates a faceted display of the smoothed
length and width distributions from the iris dataset.

@
dvals = 'Graphics.Vega.VegaLite.dataFromUrl' \"https:\/\/vega.github.io\/vega-lite\/data\/iris.json" []

colNames = [ \"petalWidth\", \"petalLength\", \"sepalWidth\", \"sepalLength\" ]
trans = 'transform'
        . 'foldAs' colNames \"measurement\" \"value\"
        . 'density' \"value\" [ 'DnGroupBy' [ \"measurement\" ] ]

enc = 'encoding'
      . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"value\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
      . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"density\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
      . 'row' [ 'FName' \"measurement\", 'FmType' 'Graphics.Vega.VegaLite.Nominal' ]

layer = 'Graphics.Vega.VegaLite.asSpec' [ trans [], enc [], 'mark' 'Graphics.Vega.VegaLite.Area' [ 'Graphics.Vega.VegaLite.MOpacity' 0.7 ] ]
@

@since 0.5.0.0
-}

density ::
  FieldName
  -- ^ The field used for the KDE.
  -> [DensityProperty]
  -- ^ Configure the calculation.
  -> BuildTransformSpecs
density :: FieldName -> [DensityProperty] -> BuildTransformSpecs
density FieldName
field [DensityProperty]
dps [TransformSpec]
ols =
  let addField :: Key -> DensityPropertyLabel -> [a]
addField Key
n DensityPropertyLabel
p = case DensityPropertyLabel -> [DensityProperty] -> VLSpec
densityPropertySpec DensityPropertyLabel
p [DensityProperty]
dps of
                       VLSpec
A.Null -> []
                       VLSpec
x -> [ Key
n forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
x ]

      ofields :: [Pair]
ofields = [ Key
"density" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field ]
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> DensityPropertyLabel -> [a]
addField Key
"groupby" DensityPropertyLabel
DPLGroupby
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> DensityPropertyLabel -> [a]
addField Key
"cumulative" DensityPropertyLabel
DPLCumulative
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> DensityPropertyLabel -> [a]
addField Key
"counts" DensityPropertyLabel
DPLCounts
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> DensityPropertyLabel -> [a]
addField Key
"bandwidth" DensityPropertyLabel
DPLBandwidth
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> DensityPropertyLabel -> [a]
addField Key
"extent" DensityPropertyLabel
DPLExtent
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> DensityPropertyLabel -> [a]
addField Key
"minsteps" DensityPropertyLabel
DPLMinsteps
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> DensityPropertyLabel -> [a]
addField Key
"maxsteps" DensityPropertyLabel
DPLMaxsteps
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> DensityPropertyLabel -> [a]
addField Key
"steps" DensityPropertyLabel
DPLSteps
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> DensityPropertyLabel -> [a]
addField Key
"as" DensityPropertyLabel
DPLAs

  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
ofields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Configure the trend fitting used by the 'loess' encoding.

@since 0.5.0.0
-}
data LoessProperty
  = LsAs FieldName FieldName
    -- ^ Name the outputs of a loess transform. The first argument is the
    --   name of the field containing the smoothed independent variable
    --   and the second the name for the field containing the smoothed
    --   dependent variable.
    --
    --   If not specified the original field names will be used.
  | LsBandwidth Double
    -- ^ The amount of smoothing. The value should be in the range 0 to 1,
    --   inclusive.
    --
    --   The default is 0.3.
  | LsGroupBy [FieldName]
    -- ^ The data fields to group by.
    --
    --   The default is to use a single group containing all the data objects.


data LoessPropertyLabel = LLAs | LLBandwidth | LLGroupBy

loessPropertySpec :: LoessPropertyLabel -> [LoessProperty] -> VLSpec
loessPropertySpec :: LoessPropertyLabel -> [LoessProperty] -> VLSpec
loessPropertySpec LoessPropertyLabel
LLAs [LoessProperty]
ps =
  let wanted :: LoessProperty -> Maybe [FieldName]
wanted (LsAs FieldName
xs FieldName
ys) = forall a. a -> Maybe a
Just [FieldName
xs, FieldName
ys]
      wanted LoessProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe LoessProperty -> Maybe [FieldName]
wanted [LoessProperty]
ps of
    [[FieldName]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
x
    [[FieldName]]
_ -> VLSpec
A.Null

loessPropertySpec LoessPropertyLabel
LLBandwidth [LoessProperty]
ps =
  let wanted :: LoessProperty -> Maybe Double
wanted (LsBandwidth Double
xs) = forall a. a -> Maybe a
Just Double
xs
      wanted LoessProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe LoessProperty -> Maybe Double
wanted [LoessProperty]
ps of
    [Double
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Double
x
    [Double]
_ -> VLSpec
A.Null

loessPropertySpec LoessPropertyLabel
LLGroupBy [LoessProperty]
ps =
  let wanted :: LoessProperty -> Maybe [FieldName]
wanted (LsGroupBy [FieldName]
xs) = forall a. a -> Maybe a
Just [FieldName]
xs
      wanted LoessProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe LoessProperty -> Maybe [FieldName]
wanted [LoessProperty]
ps of
    [[FieldName]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
x
    [[FieldName]]
_ -> VLSpec
A.Null


{-|

Generate a /loess/ (locally-estimated scatterplot smoothing) trendline
through a pair of data fields.

See also 'regression'.

The following example overlays the trendline generated by 'loess'
(the \"xsm\", \"ysm\" points) on the raw points (assuming the data
source has fields called \"xraw\" and \"yraw\" for the independent
and dependent fields, respectively).

@
transLS = 'transform'
          . 'loess' \"yraw\" \"xraw\" [ 'LsAs' \"xsm\" \"ysm\" ]

encRaw = 'encoding'
         . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"xraw\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
         . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"yraw\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]

encLS = 'encoding'
        . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"xsm\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
        . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"ysm\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]

layers = 'layer' [ 'Graphics.Vega.VegaLite.asSpec' [ encRaw [], 'mark' 'Graphics.Vega.VegaLite.Point' [ 'Graphics.Vega.VegaLite.MOpacity' 0.5 ] ]
               , 'Graphics.Vega.VegaLite.asSpec' [ transLS [], encLS [], 'mark' 'Graphics.Vega.VegaLite.Line' [ 'Graphics.Vega.VegaLite.MColor' \"firebrick\" ] ]
               ]
@

@since 0.5.0.0
-}

loess ::
  FieldName
  -- ^ The field representing the dependent variable (often displayed on
  --   the y axis).
  -> FieldName
  -- ^ The field representing the independent variable (often the x axis).
  -> [LoessProperty]
  -- ^ Customize the trend fitting.
  -> BuildTransformSpecs
loess :: FieldName -> FieldName -> [LoessProperty] -> BuildTransformSpecs
loess FieldName
depField FieldName
indField [LoessProperty]
lsp [TransformSpec]
ols =
  let addField :: Key -> LoessPropertyLabel -> [a]
addField Key
n LoessPropertyLabel
p = case LoessPropertyLabel -> [LoessProperty] -> VLSpec
loessPropertySpec LoessPropertyLabel
p [LoessProperty]
lsp of
                       VLSpec
A.Null -> []
                       VLSpec
x -> [ Key
n forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
x ]

      ofields :: [Pair]
ofields = [ Key
"loess" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
depField
                , Key
"on" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
indField ]
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> LoessPropertyLabel -> [a]
addField Key
"groupby" LoessPropertyLabel
LLGroupBy
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> LoessPropertyLabel -> [a]
addField Key
"bandwidth" LoessPropertyLabel
LLBandwidth
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> LoessPropertyLabel -> [a]
addField Key
"as" LoessPropertyLabel
LLAs

  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
ofields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

The functional form of the regression analysis. Used by 'RgMethod'.

@since 0.5.0.0
-}
data RegressionMethod
  = RgLinear
    -- ^ Linear regression.
  | RgLog
    -- ^ Logarithmic regression.
  | RgExp
    -- ^ Exponential regression.
  | RgPow
    -- ^ Power regression.
  | RgQuad
    -- ^ Quadratic regression.
  | RgPoly
    -- ^ A polynomial. The order to use is given by the 'RgOrder'
    --   constructor, and defaults to 3.

regressionMethodSpec :: RegressionMethod -> VLSpec
regressionMethodSpec :: RegressionMethod -> VLSpec
regressionMethodSpec RegressionMethod
RgLinear = FieldName -> VLSpec
fromT FieldName
"linear"
regressionMethodSpec RegressionMethod
RgLog = FieldName -> VLSpec
fromT FieldName
"log"
regressionMethodSpec RegressionMethod
RgExp = FieldName -> VLSpec
fromT FieldName
"exp"
regressionMethodSpec RegressionMethod
RgPow = FieldName -> VLSpec
fromT FieldName
"pow"
regressionMethodSpec RegressionMethod
RgQuad = FieldName -> VLSpec
fromT FieldName
"quad"
regressionMethodSpec RegressionMethod
RgPoly = FieldName -> VLSpec
fromT FieldName
"poly"


{-|

Configure the regression process (used by 'regression').

@since 0.5.0.0
-}

data RegressionProperty
  = RgAs FieldName FieldName
    -- ^ Name the outputs of the regression analysis. The first argument is the
    --   name of the field containing the independent variable, the second
    --   the dependent variable.
    --
    --   If not specified the original field names will be used.
  | RgExtent Double Double
    -- ^ The domain (minimum to maximum) over which to estimate the dependent
    --   variable in the regression.
    --
    --   The default is to use the full extent of the input values.
  | RgGroupBy [FieldName]
    -- ^ The data fields to group by.
    --
    --   The default is to use a single group containing all the data objects.
  | RgMethod RegressionMethod
    -- ^ The type of regression model to use.
  | RgOrder Natural
    -- ^ The order of the polynomial model.
    --
    --   This is only used if @'RgMethod' 'RgPoly'@ is set.
  | RgParams Bool
    -- ^ Should the transform return the regression model parameters, one object
    --   per group, rather than the trend line points.
    --
    --   If set, the returned objects include a @\"coef\"@ array of fitted
    --   coefficient values, starting with the intercept term and then including
    --   terms of increasing order, and a @\"rSquared\"@ value, indicating
    --   the total variance explained by the model.
    --
    --   The default is @'False'@.


data RegressionPropertyLabel =
  RPLAs | RPLExtent | RPLGroupBy | RPLMethod | RPLOrder | RPLParams


regressionPropertySpec :: RegressionPropertyLabel -> [RegressionProperty] -> VLSpec
regressionPropertySpec :: RegressionPropertyLabel -> [RegressionProperty] -> VLSpec
regressionPropertySpec RegressionPropertyLabel
RPLAs [RegressionProperty]
ps =
  let wanted :: RegressionProperty -> Maybe [FieldName]
wanted (RgAs FieldName
xs FieldName
ys) = forall a. a -> Maybe a
Just [FieldName
xs, FieldName
ys]
      wanted RegressionProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe [FieldName]
wanted [RegressionProperty]
ps of
    [[FieldName]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
x
    [[FieldName]]
_ -> VLSpec
A.Null

regressionPropertySpec RegressionPropertyLabel
RPLExtent [RegressionProperty]
ps =
  let wanted :: RegressionProperty -> Maybe [Double]
wanted (RgExtent Double
xs Double
ys) = forall a. a -> Maybe a
Just [Double
xs, Double
ys]
      wanted RegressionProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe [Double]
wanted [RegressionProperty]
ps of
    [[Double]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [Double]
x
    [[Double]]
_ -> VLSpec
A.Null

regressionPropertySpec RegressionPropertyLabel
RPLGroupBy [RegressionProperty]
ps =
  let wanted :: RegressionProperty -> Maybe [FieldName]
wanted (RgGroupBy [FieldName]
xs) = forall a. a -> Maybe a
Just [FieldName]
xs
      wanted RegressionProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe [FieldName]
wanted [RegressionProperty]
ps of
    [[FieldName]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
x
    [[FieldName]]
_ -> VLSpec
A.Null

regressionPropertySpec RegressionPropertyLabel
RPLMethod [RegressionProperty]
ps =
  let wanted :: RegressionProperty -> Maybe RegressionMethod
wanted (RgMethod RegressionMethod
xs) = forall a. a -> Maybe a
Just RegressionMethod
xs
      wanted RegressionProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe RegressionMethod
wanted [RegressionProperty]
ps of
    [RegressionMethod
x] -> RegressionMethod -> VLSpec
regressionMethodSpec RegressionMethod
x
    [RegressionMethod]
_ -> VLSpec
A.Null

regressionPropertySpec RegressionPropertyLabel
RPLOrder [RegressionProperty]
ps =
  let wanted :: RegressionProperty -> Maybe Natural
wanted (RgOrder Natural
xs) = forall a. a -> Maybe a
Just Natural
xs
      wanted RegressionProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe Natural
wanted [RegressionProperty]
ps of
    [Natural
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Natural
x
    [Natural]
_ -> VLSpec
A.Null

regressionPropertySpec RegressionPropertyLabel
RPLParams [RegressionProperty]
ps =
  let wanted :: RegressionProperty -> Maybe Bool
wanted (RgParams Bool
xs) = forall a. a -> Maybe a
Just Bool
xs
      wanted RegressionProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe RegressionProperty -> Maybe Bool
wanted [RegressionProperty]
ps of
    [Bool
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Bool
x
    [Bool]
_ -> VLSpec
A.Null


{-|

Generate a 2d regression model for smoothing and predicting data.

See also 'loess'.

The following example overlays the points generated by 'regression'
(the \"xrg\", \"yrg\" points) on the raw points (assuming the data
source has fields called \"xraw\" and \"yraw\" for the independent
and dependent fields, respectively).

@
transLS = 'transform'
          . 'regression' \"yraw\" \"xraw\" [ 'RgAs' \"xrg\" \"yrg\" ]

encRaw = 'encoding'
         . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"xraw\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
         . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"yraw\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]

encLS = 'encoding'
        . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"xrg\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
        . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"yrg\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]

layers = 'layer' [ 'Graphics.Vega.VegaLite.asSpec' [ encRaw [], 'mark' 'Graphics.Vega.VegaLite.Point' [ 'Graphics.Vega.VegaLite.MOpacity' 0.5 ] ]
               , 'Graphics.Vega.VegaLite.asSpec' [ transLS [], encLS [], 'mark' 'Graphics.Vega.VegaLite.Line' [ 'Graphics.Vega.VegaLite.MColor' \"firebrick\" ] ]
               ]
@

@since 0.5.0.0
-}

regression ::
  FieldName
  -- ^ The field representing the dependent variable (often displayed on
  --   the y axis).
  -> FieldName
  -- ^ The field representing the independent variable (often the x axis).
  -> [RegressionProperty]
  -- ^ Customize the regression.
  -> BuildTransformSpecs
regression :: FieldName
-> FieldName -> [RegressionProperty] -> BuildTransformSpecs
regression FieldName
depField FieldName
indField [RegressionProperty]
rps [TransformSpec]
ols =
  let addField :: Key -> RegressionPropertyLabel -> [a]
addField Key
n RegressionPropertyLabel
p = case RegressionPropertyLabel -> [RegressionProperty] -> VLSpec
regressionPropertySpec RegressionPropertyLabel
p [RegressionProperty]
rps of
                       VLSpec
A.Null -> []
                       VLSpec
x -> [ Key
n forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
x ]

      ofields :: [Pair]
ofields = [ Key
"regression" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
depField
                , Key
"on" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
indField ]
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> RegressionPropertyLabel -> [a]
addField Key
"groupby" RegressionPropertyLabel
RPLGroupBy
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> RegressionPropertyLabel -> [a]
addField Key
"method" RegressionPropertyLabel
RPLMethod
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> RegressionPropertyLabel -> [a]
addField Key
"order" RegressionPropertyLabel
RPLOrder
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> RegressionPropertyLabel -> [a]
addField Key
"extent" RegressionPropertyLabel
RPLExtent
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> RegressionPropertyLabel -> [a]
addField Key
"params" RegressionPropertyLabel
RPLParams
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> RegressionPropertyLabel -> [a]
addField Key
"as" RegressionPropertyLabel
RPLAs

  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
ofields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|
Configure the quantile analysis performed by 'quantile'.

@since 0.5.0.0
-}
data QuantileProperty
  = QtAs FieldName FieldName
    -- ^ Name the fields used to store the calculated probability and
    --   associated quantile values.
    --
    --   The defaults are @\"prob\"@ and @\"value\"@.
  | QtGroupBy [FieldName]
    -- ^ The data fields to group by.
    --
    -- The default is to use a single group containing all the data objects.
  | QtProbs [Double]
    -- ^ The probabilites (measured in the range 0-1) for which to
    --   compute quantile values.
    --
    --   The default is to use a step size of 0.01, or the
    --   'QtStep' value if given.
  | QtStep Double
    -- ^ The interval between probabilities when performing a quantile
    --   transformation.
    --
    --   All value from half the given step size to 1 will be sampled,
    --   and is only used if 'QtProbs' is not set.


data QuantilePropertyLabel =
  QPLAs | QPLGroupBy | QPLProbs | QPLStep


quantilePropertySpec :: QuantilePropertyLabel -> [QuantileProperty] -> VLSpec
quantilePropertySpec :: QuantilePropertyLabel -> [QuantileProperty] -> VLSpec
quantilePropertySpec QuantilePropertyLabel
QPLAs [QuantileProperty]
ps =
  let wanted :: QuantileProperty -> Maybe [FieldName]
wanted (QtAs FieldName
xs FieldName
ys) = forall a. a -> Maybe a
Just [FieldName
xs, FieldName
ys]
      wanted QuantileProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe QuantileProperty -> Maybe [FieldName]
wanted [QuantileProperty]
ps of
    [[FieldName]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
x
    [[FieldName]]
_ -> VLSpec
A.Null

quantilePropertySpec QuantilePropertyLabel
QPLGroupBy [QuantileProperty]
ps =
  let wanted :: QuantileProperty -> Maybe [FieldName]
wanted (QtGroupBy [FieldName]
xs) = forall a. a -> Maybe a
Just [FieldName]
xs
      wanted QuantileProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe QuantileProperty -> Maybe [FieldName]
wanted [QuantileProperty]
ps of
    [[FieldName]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
x
    [[FieldName]]
_ -> VLSpec
A.Null

quantilePropertySpec QuantilePropertyLabel
QPLProbs [QuantileProperty]
ps =
  let wanted :: QuantileProperty -> Maybe [Double]
wanted (QtProbs [Double]
xs) = forall a. a -> Maybe a
Just [Double]
xs
      wanted QuantileProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe QuantileProperty -> Maybe [Double]
wanted [QuantileProperty]
ps of
    [[Double]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [Double]
x
    [[Double]]
_ -> VLSpec
A.Null

quantilePropertySpec QuantilePropertyLabel
QPLStep [QuantileProperty]
ps =
  let wanted :: QuantileProperty -> Maybe Double
wanted (QtStep Double
xs) = forall a. a -> Maybe a
Just Double
xs
      wanted QuantileProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe QuantileProperty -> Maybe Double
wanted [QuantileProperty]
ps of
    [Double
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Double
x
    [Double]
_ -> VLSpec
A.Null


{-|
Calculate quantile values from an input data stream. This can be useful
for examining distributional properties of a data stream, and for
creating
<https://en.wikipedia.org/wiki/Q–Q_plot Q-Q plots>.

As an example:

@
let dvals = 'Graphics.Vega.VegaLite.dataFromUrl' \"data/normal-2d.json\" []

    trans = 'transform'
            . 'quantile' \"u\" [ 'QtStep' 0.01, 'QtAs' \"p\" \"v\" ]
            . 'calculateAs' \"quantileUniform(datum.p)\" \"unif\"
            . 'calculateAs' \"quantileNormal(datum.p)\" \"norm\"

    enc x y = 'encoding'
              . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' x, 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
              . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' y, 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]

    leftSpec = 'Graphics.Vega.VegaLite.asSpec' [ 'mark' 'Graphics.Vega.VegaLite.Point' [], enc \"unif\" \"v\" [] ]
    rightSpec = 'Graphics.Vega.VegaLite.asSpec' [ 'mark' 'Graphics.Vega.VegaLite.Point' [], enc \"norm\" \"v\" [] ]

in 'Graphics.Vega.VegaLite.toVegaLite' [ dvals, trans [], 'hConcat' [ leftSpec, rightSpec ] ]
@

@since 0.5.0.0
-}
quantile ::
  FieldName
  -- ^ The field to analyse.
  -> [QuantileProperty]
  -- ^ Configure the quantile analysis
  -> BuildTransformSpecs
quantile :: FieldName -> [QuantileProperty] -> BuildTransformSpecs
quantile FieldName
field [QuantileProperty]
qps [TransformSpec]
ols =
  let addField :: Key -> QuantilePropertyLabel -> [a]
addField Key
n QuantilePropertyLabel
p = case QuantilePropertyLabel -> [QuantileProperty] -> VLSpec
quantilePropertySpec QuantilePropertyLabel
p [QuantileProperty]
qps of
                       VLSpec
A.Null -> []
                       VLSpec
x -> [ Key
n forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
x ]

      ofields :: [Pair]
ofields = [ Key
"quantile" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field ]
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> QuantilePropertyLabel -> [a]
addField Key
"groupby" QuantilePropertyLabel
QPLGroupBy
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> QuantilePropertyLabel -> [a]
addField Key
"probs" QuantilePropertyLabel
QPLProbs
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> QuantilePropertyLabel -> [a]
addField Key
"step" QuantilePropertyLabel
QPLStep
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> QuantilePropertyLabel -> [a]
addField Key
"as" QuantilePropertyLabel
QPLAs

  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
ofields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Create a named binning transformation that may be referenced in other Transformations
or encodings. See the
<https://vega.github.io/vega-lite/docs/bin.html Vega-Lite documentation> for
more details. Note that usually, direct binning within an encoding is preferred
over this form of bin transformation.

@
'transform'
    . 'binAs' [ 'Graphics.Vega.VegaLite.MaxBins' 3 ] \"IMDB_Rating\" \"ratingGroup\"
@
-}
binAs ::
  [BinProperty]
  -- ^ An empty list means that the default binning is used (that is, the
  --   @bin@ field will be set to @true@ in the Vega-Lite specification).
  -> FieldName
  -- ^ The field to bin.
  -> FieldName
  -- ^ The label for the binned data.
  -> BuildTransformSpecs
binAs :: [BinProperty] -> FieldName -> FieldName -> BuildTransformSpecs
binAs [BinProperty]
bProps FieldName
field FieldName
label [TransformSpec]
ols =
  let fields :: [Pair]
fields = [ Key
"bin" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [BinProperty]
bProps then forall a. ToJSON a => a -> VLSpec
toJSON Bool
True else VLSpec
binObj
               , Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field
               , Key
"as" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
label ]

      binObj :: VLSpec
binObj = [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map BinProperty -> Pair
binProperty [BinProperty]
bProps)

 in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
fields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Creates a new data field based on calculations from existing fields and values.

See the <https://vega.github.io/vega-lite/docs/calculate.html Vega-Lite documentation>
for further details.

@
'transform' . 'calculateAs' "datum.sex == 2 ? \'F\' : \'M\'" "gender"
@
-}
calculateAs ::
  VegaExpr
  -- ^ The calculation to perform.
  -> FieldName
  -- ^ The field to assign the new values.
  -> BuildTransformSpecs
calculateAs :: FieldName -> FieldName -> BuildTransformSpecs
calculateAs FieldName
expr FieldName
label [TransformSpec]
ols =
  let fields :: [Pair]
fields = [ Key
"calculate" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
expr, Key
"as" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
label ]
  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
fields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Encode an angle (orientation) channel, which allows for data-driven
rotation of text, point, and square marks.

@since 0.9.0.0
-}
angle ::
  [MarkChannel]
  -- ^ The color-encoding options.
  -> BuildEncodingSpecs
angle :: [MarkChannel] -> BuildEncodingSpecs
angle [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"angle" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a color channel.

@
'color' [ 'MName' \"Species\", 'MmType' 'Graphics.Vega.VegaLite.Nominal' ] []
@

Encoding a color channel will generate a legend by default. To stop the legend
appearing, just supply an empty list of legend properties to 'MLegend':

@
'color' [ 'MName' \"Species\", 'MmType' 'Graphics.Vega.VegaLite.Nominal', 'MLegend' [] ] []
@
-}
color ::
  [MarkChannel]
  -- ^ The color-encoding options.
  -> BuildEncodingSpecs
color :: [MarkChannel] -> BuildEncodingSpecs
color [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"color" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encodes a new facet to be arranged in columns. See the
<https://vega.github.io/vega-lite/docs/facet.html#facet-row-and-column-encoding-channels 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 = 'Graphics.Vega.VegaLite.dataFromUrl' \"crimeData.csv\"
    enc = 'encoding'
            . 'position' 'Graphics.Vega.VegaLite.X' ['PName' \"month\", 'PmType' 'Graphics.Vega.VegaLite.Temporal']
            . 'position' 'Graphics.Vega.VegaLite.Y' ['PName' \"reportedCrimes\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative'
                         , 'PAggregate' 'Graphics.Vega.VegaLite.Sum']
            . 'column' ['FName' \"crimeType\", 'FmType' 'Graphics.Vega.VegaLite.Nominal']

    in 'Graphics.Vega.VegaLite.toVegaLite' ['width' 100, dvals [], 'mark' 'Graphics.Vega.VegaLite.Bar' [], enc [] ]
@
-}
column ::
  [FacetChannel]
  -- ^ The list of properties that define the faceting channel. At a minimum
  --   this should include the data field ('FName') and its measurement type
  --   ('FmType').
  -> BuildEncodingSpecs
column :: [FacetChannel] -> BuildEncodingSpecs
column [FacetChannel]
fFields [EncodingSpec]
ols =
  (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"column", [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> Pair
facetChannelProperty [FacetChannel]
fFields)) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

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

-}

columns ::
  Natural
  -- ^ A value of 0 means that a single row will be used (which is also
  --   the default behavior).
  -> PropertySpec
columns :: Natural -> PropertySpec
columns Natural
cols = (VLProperty
VLColumns, forall a. ToJSON a => a -> VLSpec
toJSON Natural
cols)


{-|

Encode a \"level of detail\" channel. This provides a way of grouping by a field
but unlike, say 'color', all groups have the same visual properties.

See the
<https://vega.github.io/vega-lite/docs/encoding.html#detail Vega-Lite documentation>
for details.

@
'detail' ['DName' \"Species\", 'DmType' 'Graphics.Vega.VegaLite.Nominal'] []
@
-}
detail ::
  [DetailChannel]
  -- ^ The field to group.
  -> BuildEncodingSpecs
detail :: [DetailChannel] -> BuildEncodingSpecs
detail [DetailChannel]
detailProps [EncodingSpec]
ols =
    (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"detail", [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map DetailChannel -> Pair
detailChannelProperty [DetailChannel]
detailProps)) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-

Elm added this in version 2.0, but I think it needs more structure
than just a field name, so am leaving out for now.

Encode a key channel, to support dynamic data via the
<https://vega.github.io/vega/docs/api/view/ Vega View API>.

See the <https://vega.github.io/vega-lite/docs/encoding.html#key Vega-Lite documentation>
for more information.

@
'encoding' . 'keyChannel' \"Species\"
@

@since 0.5.0.0
keyChannel ::
  FieldName
  -- ^ The field to use as the unique key for data binding.
  -> BuildLabelledSpecs
keyChannel f ols =
    ("key" .= object ["field" .= f]) : ols
    -- ("key" .= f) : ols

-}

{-|

Encode a fill channel. This acts in a similar way to encoding by 'color' but
only affects the interior of closed shapes.

@
'fill' [ 'MName' \"Species\", 'MmType' 'Graphics.Vega.VegaLite.Nominal' ] []
@

Note that if both @fill@ and 'color' encodings are specified, @fill@ takes precedence.

-}

fill ::
  [MarkChannel]
  -- ^ Configure the fill.
  -> BuildEncodingSpecs
fill :: [MarkChannel] -> BuildEncodingSpecs
fill [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"fill" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a fill opacity channel. This acts in a similar way to encoding by 'opacity'
but only affects the interior of closed shapes. If both @fillOpacity@ and 'opacity'
encodings are specified, @fillOpacity@ takes precedence.

See also 'fill'.

@since 0.4.0.0
-}

fillOpacity :: [MarkChannel] -> BuildEncodingSpecs
fillOpacity :: [MarkChannel] -> BuildEncodingSpecs
fillOpacity [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"fillOpacity" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Adds the given filter operation a list of transformations that may be applied
to a channel or field.

@
'transform'
    . 'filter' ('FEqual' \"Animal\" ('Str' \"Cat\"))
@

Filter operations can combine selections and data predicates with 'BooleanOp'
expressions (and as of @0.4.0.0@, 'FilterOp' and 'FilterOpTrans'
can be used to lift the 'Filter' type into boolean expressions):

@
'transform'
    . 'filter' ('FCompose' ('And' ('Expr' "datum.Weight_in_lbs > 3000") ('Selection' "brush")))
@

The [Vega expression documentation](https://vega.github.io/vega/docs/expressions/)
describes the supported format (e.g. the requirement to precede column names
with @"datum."@).

-}
filter :: Filter -> BuildTransformSpecs
filter :: Filter -> BuildTransformSpecs
filter Filter
f [TransformSpec]
ols = VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [ Key
"filter" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Filter -> VLSpec
filterSpec Filter
f ]) forall a. a -> [a] -> [a]
: [TransformSpec]
ols



{-|

Map array-valued fields to a set of individual data objects, one per array entry.

See also 'flattenAs'.

@since 0.4.0.0

-}

flatten :: [FieldName] -> BuildTransformSpecs
flatten :: [FieldName] -> BuildTransformSpecs
flatten [FieldName]
fields [TransformSpec]
ols = VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [ Key
"flatten" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
fields ]) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Similar to 'flatten' but allows the new output fields to be named.

@since 0.4.0.0

-}

flattenAs ::
  [FieldName]
  -> [FieldName]
  -- ^ The names of the output fields.
  -> BuildTransformSpecs
flattenAs :: [FieldName] -> [FieldName] -> BuildTransformSpecs
flattenAs [FieldName]
fields [FieldName]
names [TransformSpec]
ols =
  let ofields :: [Pair]
ofields = [ Key
"flatten" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
fields, Key
"as" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
names ]
  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
ofields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Perform a /gather/ operation to /tidy/ a table. Collapse multiple data fields
into two new data fields: @key@ containing the original data field names and
@value@ containing the corresponding data values.

It is the inverse of 'pivot'. See also 'foldAs'.

@
dvals =
    'Graphics.Vega.VegaLite.dataFromColumns' []
        . 'Graphics.Vega.VegaLite.dataColumn' \"city\" ('Strings' [ \"Bristol\", \"Sheffield\", \"Glasgow\" ])
        . 'Graphics.Vega.VegaLite.dataColumn' \"temp2017\" ('Numbers' [ 12, 11, 7 ])
        . 'Graphics.Vega.VegaLite.dataColumn' \"temp2018\" ('Numbers' [ 14, 13, 10 ])

trans =
    'transform'
        . 'fold' [ \"temp2017\", \"temp2018\" ]

enc =
    'encoding'
        . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"key\", 'PmType' 'Graphics.Vega.VegaLite.Nominal' ]
        . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"city\", 'PmType' 'Graphics.Vega.VegaLite.Nominal' ]
        . 'size' [ 'MName' \"value\", 'MmType' 'Graphics.Vega.VegaLite.Quantitative' ]
@

@since 0.4.0.0
-}

fold ::
  [FieldName]
  -- ^ The data fields to fold.
  -> BuildTransformSpecs
fold :: [FieldName] -> BuildTransformSpecs
fold [FieldName]
fields [TransformSpec]
ols = VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [ Key
"fold" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
fields ]) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

A 'fold' where the @key@ and @value@ fields can be renamed.

@since 0.4.0.0

-}

foldAs ::
  [FieldName]
  -- ^ The data fields to fold.
  -> FieldName
  -- ^ The name for the @key@ field.
  -> FieldName
  -- ^ The name for the @value@ field.
  -> BuildTransformSpecs
foldAs :: [FieldName] -> FieldName -> FieldName -> BuildTransformSpecs
foldAs [FieldName]
fields FieldName
keyName FieldName
valName [TransformSpec]
ols =
  let ofields :: [Pair]
ofields = [ Key
"fold" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldName]
fields
                , Key
"as" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [ FieldName
keyName, FieldName
valName ]
                ]
  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
ofields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Perform a /pivot/ operation on a table. Spreads a key-value pair of fields
across multiple fields according to the data in the /key/ field.

It is the inverse of 'fold'.

@
dvals =
    'Graphics.Vega.VegaLite.dataFromColumns' []
        . 'Graphics.Vega.VegaLite.dataColumn' \"city\" ('Strings' [ \"Bristol\", \"Bristol\", \"Sheffield\", \"Sheffield\", \"Glasgow\", \"Glasgow\" ])
        . 'Graphics.Vega.VegaLite.dataColumn' \"temperature\" ('Numbers' [ 12, 14, 11, 13, 7, 10 ])
        . 'Graphics.Vega.VegaLite.dataColumn' \"year\" ('Numbers' [ 2017, 2018, 2017, 2018, 2017, 2018 ])

trans =
    'transform'
        . 'pivot' "year" "temperature" [ 'PiGroupBy' [ \"city\" ] ]

enc =
    'encoding'
        . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"2017\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
        . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"city\", 'PmType' 'Graphics.Vega.VegaLite.Nominal' ]
@

@since 0.5.0.0
-}

pivot ::
  FieldName
  -- ^ The key field.
  -> FieldName
  -- ^ The value field.
  -> [PivotProperty]
  -> BuildTransformSpecs
pivot :: FieldName -> FieldName -> [PivotProperty] -> BuildTransformSpecs
pivot FieldName
field FieldName
valField [PivotProperty]
pProps [TransformSpec]
ols =
  let addField :: Key -> PivotPropertyLabel -> [a]
addField Key
n PivotPropertyLabel
p = case PivotPropertyLabel -> [PivotProperty] -> VLSpec
pivotPropertySpec PivotPropertyLabel
p [PivotProperty]
pProps of
                       VLSpec
A.Null -> []
                       VLSpec
x -> [Key
n forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
x]

      ofields :: [Pair]
ofields = [ Key
"pivot" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field
                , Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
valField ]
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> PivotPropertyLabel -> [a]
addField Key
"groupby" PivotPropertyLabel
PPLGroupBy
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> PivotPropertyLabel -> [a]
addField Key
"limit" PivotPropertyLabel
PPLLimit
                forall a. Semigroup a => a -> a -> a
<> forall {a}. KeyValue a => Key -> PivotPropertyLabel -> [a]
addField Key
"op" PivotPropertyLabel
PPLOp

  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
ofields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|
Configure the 'pivot' operation.

@since 0.5.0.0
-}

data PivotProperty
  = PiGroupBy [FieldName]
    -- ^ The data fields to group by when pivoting. If unspecified
    --   then a single group containing all the data objects will
    --   be used.
  | PiLimit Natural
    -- ^ The maximum number of fields to generate when pivoting. If
    --   0 or unspecified all fields are pivoted. The pivot names
    --   are sorted into ascending order before the limit is
    --   applied.
  | PiOp Operation
    -- ^ The aggregation operation to apply to grouped fields.


data PivotPropertyLabel = PPLGroupBy | PPLLimit | PPLOp

-- Multiple properties will lead to no output; in some ways
-- this makes sense (aka "you are telling me multiple things,
-- so I give up") and is used elsewhere.
--
-- TODO: this should return a Maybe VLSpec
pivotPropertySpec ::
  PivotPropertyLabel
  -> [PivotProperty]
  -> VLSpec
pivotPropertySpec :: PivotPropertyLabel -> [PivotProperty] -> VLSpec
pivotPropertySpec PivotPropertyLabel
PPLGroupBy [PivotProperty]
ps =
  let wanted :: PivotProperty -> Maybe [FieldName]
wanted (PiGroupBy [FieldName]
xs) = forall a. a -> Maybe a
Just [FieldName]
xs
      wanted PivotProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe PivotProperty -> Maybe [FieldName]
wanted [PivotProperty]
ps of
    [[FieldName]
x] -> forall a. ToJSON a => a -> VLSpec
toJSON [FieldName]
x
    [[FieldName]]
_ -> VLSpec
A.Null

pivotPropertySpec PivotPropertyLabel
PPLLimit [PivotProperty]
ps =
  let wanted :: PivotProperty -> Maybe Natural
wanted (PiLimit Natural
xs) = forall a. a -> Maybe a
Just Natural
xs
      wanted PivotProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe PivotProperty -> Maybe Natural
wanted [PivotProperty]
ps of
    [Natural
x] -> forall a. ToJSON a => a -> VLSpec
toJSON Natural
x
    [Natural]
_ -> VLSpec
A.Null

pivotPropertySpec PivotPropertyLabel
PPLOp [PivotProperty]
ps =
  let wanted :: PivotProperty -> Maybe Operation
wanted (PiOp Operation
xs) = forall a. a -> Maybe a
Just Operation
xs
      wanted PivotProperty
_ = forall a. Maybe a
Nothing

  in case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe PivotProperty -> Maybe Operation
wanted [PivotProperty]
ps of
    [Operation
x] -> Operation -> VLSpec
operationSpec Operation
x
    [Operation]
_ -> VLSpec
A.Null


{-|

Encode a URL for use with the 'Graphics.Vega.VegaLite.Image' mark type.

The URL can be encoded directly:

@
let axVals = 'Numbers' [ 0.5, 1.5, 2.5 ]

    dvals = 'Graphics.Vega.VegaLite.dataFromColumns' []
            . 'Graphics.Vega.VegaLite.dataColumn' "x" axVals
            . 'Graphics.Vega.VegaLite.dataColumn' "y" axVals

    enc = 'encoding'
          . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' "x", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
          . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' "y", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
          . 'url' [ 'HString' \"wonderful-image.png\" ]

    imMark = 'mark' 'Graphics.Vega.VegaLite.Image' [ 'Graphics.Vega.VegaLite.MWidth' 50, 'Graphics.Vega.VegaLite.MHeight' 25 ]

in 'Graphics.Vega.VegaLite.toVegaLite' [ dvals [], enc [], imMark ]
@

or by referencing a data field containing the URL values:

@
... 'Graphics.Vega.VegaLite.dataColumn' "img" ('Strings' [ \"i1.png\", \"i2.png\", \"i4.png\" ])

... 'url' [ 'HName' \"img\", 'HmType' 'Graphics.Vega.VegaLite.Nominal' ]
@

@since 0.5.0.0
-}

url :: [HyperlinkChannel] -> BuildEncodingSpecs
url :: [HyperlinkChannel] -> BuildEncodingSpecs
url [HyperlinkChannel]
hPs [EncodingSpec]
ols =
  (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"url", [Pair] -> VLSpec
object (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap HyperlinkChannel -> [Pair]
hyperlinkChannelProperty [HyperlinkChannel]
hPs)) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a hyperlink channel.

@
'encoding'
  . 'hyperlink' [ 'HName' \"Species\", 'HmType' 'Graphics.Vega.VegaLite.Nominal' ]
@

@
'encoding'
  . 'hyperlink' [ 'HString' \"http://www.imdb.com\" ]
@

For further details see the
<https://vega.github.io/vega-lite/docs/encoding.html#href Vega-Lite documentation>.

-}
hyperlink ::
  [HyperlinkChannel]
  -- ^ The properties for the hyperlink channel.
  -> BuildEncodingSpecs
hyperlink :: [HyperlinkChannel] -> BuildEncodingSpecs
hyperlink [HyperlinkChannel]
hyperProps [EncodingSpec]
ols =
  (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"href", [Pair] -> VLSpec
object (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap HyperlinkChannel -> [Pair]
hyperlinkChannelProperty [HyperlinkChannel]
hyperProps)) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Perform a lookup of named fields between two data sources. This allows
you to find values in one data source based on the values in another
(like a relational join).

Use 'lookupSelection' for linking data with interactive selections.

See the <https://vega.github.io/vega-lite/docs/lookup.html Vega-Lite documentation>
for further details.

The following would return the values in the @age@ and @height@ fields from
@lookup_people.csv@ for all rows where the value in the @name@ column in that
file matches the value of @person@ in the primary data source.

@
peopleData = 'Graphics.Vega.VegaLite.dataFromUrl' \"data/lookup_people.csv\" []
lfields = 'LuFields' [\"age\", \"height\"]
trans = 'transform'
          . 'lookup' \"person\" peopleData \"name\" lfields
@

Note that the interface has changed in version @0.5.0.0@: the
output field names argument now uses the new 'LookupFields'
type. This provides greater flexibility in naming and
default behaviour. The conversion from version 0.4 is
simple: change

@
lookup key1 dataSource key2 fields
@

to

@
lookup key1 dataSource key2 (LuFields fields)
@

-}
lookup ::
  FieldName
  -- ^ The field in the primary data structure acting as the key.
  -> Data
  -- ^ The secondary data source (e.g. the return from the data-generating
  --   functions such as 'Graphics.Vega.VegaLite.dataFromUrl').
  -> FieldName
  -- ^ The name of the field in the secondary data source to match against
  --   the primary key.
  -> LookupFields
  -- ^ The list of fields to store when the keys match.
  --
  --   This was changed from @[T.Text]@ in vesion 0.5.0.0.
  -> BuildTransformSpecs
lookup :: FieldName
-> PropertySpec -> FieldName -> LookupFields -> BuildTransformSpecs
lookup FieldName
key1 (VLProperty
_, VLSpec
spec) FieldName
key2 LookupFields
lfields [TransformSpec]
ols =
  let get1 :: [(FieldName, b)] -> Maybe VLSpec
get1 = forall a. ToJSON a => a -> Maybe VLSpec
jj forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst
      get2 :: [(a, FieldName)] -> Maybe VLSpec
get2 = forall a. ToJSON a => a -> Maybe VLSpec
jj forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd

      jj :: A.ToJSON a => a -> Maybe A.Value
      jj :: forall a. ToJSON a => a -> Maybe VLSpec
jj = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> VLSpec
toJSON

      res :: (Maybe VLSpec, Maybe VLSpec, Maybe VLSpec)
res = case LookupFields
lfields of
             LuFields [FieldName]
fs -> ( forall a. ToJSON a => a -> Maybe VLSpec
jj [FieldName]
fs, forall a. Maybe a
Nothing, forall a. Maybe a
Nothing )
             LuFieldAs [(FieldName, FieldName)]
fas -> ( forall {b}. [(FieldName, b)] -> Maybe VLSpec
get1 [(FieldName, FieldName)]
fas, forall {a}. [(a, FieldName)] -> Maybe VLSpec
get2 [(FieldName, FieldName)]
fas, forall a. Maybe a
Nothing )
             LuAs FieldName
s -> ( forall a. Maybe a
Nothing, forall a. ToJSON a => a -> Maybe VLSpec
jj FieldName
s, forall a. Maybe a
Nothing )
             LuFieldsWithDefault [FieldName]
fs FieldName
def
               -> ( forall a. ToJSON a => a -> Maybe VLSpec
jj [FieldName]
fs, forall a. Maybe a
Nothing , forall a. ToJSON a => a -> Maybe VLSpec
jj FieldName
def )
             LuFieldsAsWithDefault [(FieldName, FieldName)]
fas FieldName
def
               -> ( forall {b}. [(FieldName, b)] -> Maybe VLSpec
get1 [(FieldName, FieldName)]
fas, forall {a}. [(a, FieldName)] -> Maybe VLSpec
get2 [(FieldName, FieldName)]
fas, forall a. ToJSON a => a -> Maybe VLSpec
jj FieldName
def )
             LuAsWithDefault FieldName
s FieldName
def -> ( forall a. Maybe a
Nothing, forall a. ToJSON a => a -> Maybe VLSpec
jj FieldName
s, forall a. ToJSON a => a -> Maybe VLSpec
jj FieldName
def )

      (Maybe VLSpec
mfields, Maybe VLSpec
mas, Maybe VLSpec
mdefault) = (Maybe VLSpec, Maybe VLSpec, Maybe VLSpec)
res

      addField :: a -> Maybe b -> [(a, b)]
addField a
n (Just b
x) = [ (a
n, b
x) ]
      addField a
_ Maybe b
_ = []

      fromFields :: [Pair]
fromFields = [ Key
"data" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VLSpec
spec
                   , Key
"key" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
key2
                   ]
                   forall a. Semigroup a => a -> a -> a
<> forall {a} {b}. a -> Maybe b -> [(a, b)]
addField Key
"fields" Maybe VLSpec
mfields

      ofields :: [Pair]
ofields = [ Key
"lookup" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
key1
                , Key
"from" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [Pair]
fromFields
                ]
                forall a. Semigroup a => a -> a -> a
<> forall {a} {b}. a -> Maybe b -> [(a, b)]
addField Key
"as" Maybe VLSpec
mas
                forall a. Semigroup a => a -> a -> a
<> forall {a} {b}. a -> Maybe b -> [(a, b)]
addField Key
"default" Maybe VLSpec
mdefault

  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
ofields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Attach the results of an interactive selection to a primary data source.
This is similar to 'lookup' except that the data in a selection are used
in place of the secondary data source.

See the [Vega Lite lookup selection](https://vega.github.io/vega-lite/docs/lookup.html#lookup-selection) documentation.

@
sel = 'Graphics.Vega.VegaLite.selection'
      . 'Graphics.Vega.VegaLite.select' \"mySel\" 'Graphics.Vega.VegaLite.Single' [ 'Graphics.Vega.VegaLite.On' \"mouseover\", 'Graphics.Vega.VegaLite.Encodings' [ 'Graphics.Vega.VegaLite.ChX' ] ]

trans = 'transform'
        . 'lookupSelection' \"country\" \"mySel\" \"country\"
@

@since 0.5.0.0
-}

lookupSelection ::
  FieldName
  -- ^ The field to lookup in the primary data source.
  -> SelectionLabel
  -- ^ The name of the selection (as set with 'Graphics.Vega.VegaLite.select').
  -> FieldName
  -- ^ The name of the field in the selection to link with the
  --   primary data field.
  -> BuildTransformSpecs
lookupSelection :: FieldName -> FieldName -> FieldName -> BuildTransformSpecs
lookupSelection FieldName
key1 FieldName
selName FieldName
key2 [TransformSpec]
ols =
  let ofields :: [Pair]
ofields = [ Key
"lookup" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
key1
                , Key
"from" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> VLSpec
object [ Key
"selection" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
selName
                                   , Key
"key" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
key2 ]
                ]

  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
ofields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|
Configure the field selection in 'lookup'.

@since 0.5.0.0
-}
data LookupFields
  = LuFields [FieldName]
    -- ^ The name of the fields to return from the secondary data
    --   source.
  | LuFieldAs [(FieldName, FieldName)]
    -- ^ Select fields from the secondary data source (first
    --   argument) and allow them to be referred to with a
    --   new name (second argument).
  | LuAs FieldName
    -- ^ Create a single name for all the fields in the
    --   secondary data source. The individual fields use dot
    --   notation to combine the given name with the field name.
    --
    --   @
    --   dvals = 'Graphics.Vega.VegaLite.dataFromUrl' \"data/flights.airport.csv" []
    --   trans = 'transform'
    --           . 'lookup' \"origin\" dvals "iata" ('LuAs' \"o\")
    --   enc = 'encoding'
    --         . 'position' 'Graphics.Vega.VegaLite.Longitude' [ 'PName' \"o.longitude\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
    --         . 'position' 'Graphics.Vega.VegaLite.Lattude' [ 'PName' \"o.latitude\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
    --   @
  | LuFieldsWithDefault [FieldName] T.Text
    -- ^ The name of the fields to return from the secondary
    --   data source, along with the default value to use
    --   if the lookup fails.
  | LuFieldsAsWithDefault [(FieldName, FieldName)] T.Text
    -- ^ Allow fields to be renamed and provide a default for
    --   when the lookup fails.
  | LuAsWithDefault FieldName T.Text
    -- ^ Create a single name for all the fields in the
    --   secondary data source, but the second parameter
    --   gives the default value for when the lookup fails.


{-|

This routine is deprecated (as of version @0.5.0.0@) in favor
of 'lookup', as

@
lookupAs "key1" dataSource "key2" "matchName"
@

can be written as

@
lookup "key1" dataSource "key2" (LuAs "matchName")
@

-}
{-# DEPRECATED lookupAs "Please change 'lookupAs ... alias' to 'lookup ... (LuAs alias)'" #-}
lookupAs ::
  FieldName
  -- ^ The field in the primary data structure acting as the key.
  -> Data
  -- ^ The secondary data source (e.g. the return from the data-generating
  --   functions such as 'Graphics.Vega.VegaLite.dataFromUrl').
  -> FieldName
  -- ^ The name of the field in the secondary data source to match against
  --   the primary key.
  -> FieldName
  -- ^ The field name for the new data.
  -> BuildTransformSpecs
lookupAs :: FieldName
-> PropertySpec -> FieldName -> FieldName -> BuildTransformSpecs
lookupAs FieldName
key1 PropertySpec
sData FieldName
key2 FieldName
asName =
  FieldName
-> PropertySpec -> FieldName -> LookupFields -> BuildTransformSpecs
lookup FieldName
key1 PropertySpec
sData FieldName
key2 (FieldName -> LookupFields
LuAs FieldName
asName)


{-|

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 = 'Graphics.Vega.VegaLite.dataFromColumns' []
              . 'Graphics.Vega.VegaLite.dataColumn' "a" ('Numbers' [0, 0, 10, 10, 20, 20, 30])
              . 'Graphics.Vega.VegaLite.dataColumn' "b" ('Numbers' [28, 91, 43, 55, 81, 53, 19])
              . 'Graphics.Vega.VegaLite.dataColumn' "c" ('Numbers' [0, 1, 0, 1, 0, 1, 0])

    trans = 'transform'
              . 'impute' "b" "a" ['Graphics.Vega.VegaLite.ImMethod' 'Graphics.Vega.VegaLite.ImMean', 'Graphics.Vega.VegaLite.ImGroupBy' ["c"]]

    enc = 'encoding'
            . 'position' 'Graphics.Vega.VegaLite.X' ['PName' \"a\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']
            . 'position' 'Graphics.Vega.VegaLite.Y' ['PName' \"b\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative']
            . 'color' ['MName' \"c\", 'MmType' 'Graphics.Vega.VegaLite.Nominal']

    in 'Graphics.Vega.VegaLite.toVegaLite' [dvals [], trans [], enc [], 'mark' 'Graphics.Vega.VegaLite.Line' []]
@

@since 0.4.0.0
-}

impute ::
  FieldName
  -- ^ The data field to process.
  -> FieldName
  -- ^ The key field to uniquely identify data objects within a group.
  -> [ImputeProperty]
  -- ^ Define how the imputation works.
  -> BuildTransformSpecs
impute :: FieldName -> FieldName -> [ImputeProperty] -> BuildTransformSpecs
impute FieldName
fields FieldName
keyField [ImputeProperty]
imProps [TransformSpec]
ols = FieldName -> FieldName -> [ImputeProperty] -> TransformSpec
imputeTS FieldName
fields FieldName
keyField [ImputeProperty]
imProps forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

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' 'Graphics.Vega.VegaLite.Quantitative' ] []
@

See also 'fillOpacity'.

-}

opacity :: [MarkChannel] -> BuildEncodingSpecs
opacity :: [MarkChannel] -> BuildEncodingSpecs
opacity [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"opacity" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode an order channel.

@
'encoding'
    . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' "miles", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
    . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' "gas", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
    . 'order' [ 'OName' "year", 'OmType' 'Graphics.Vega.VegaLite.Temporal', 'OSort' ['Descending'] ]
@

<https://vega.github.io/vega-lite/docs/condition.html Conditional values>
can be set with 'OSelectionCondition', such as

@
'order' [ 'OSelectionCondition' ('SelectionName "highlight")
          ['ONumber' 1] ['ONumber' 0]
@
-}

order ::
  [OrderChannel]
  -- ^ The order-encoding options.
  -> BuildEncodingSpecs
order :: [OrderChannel] -> BuildEncodingSpecs
order [OrderChannel]
oDefs [EncodingSpec]
ols =
  (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"order", [Pair] -> VLSpec
object (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap OrderChannel -> [Pair]
orderChannelProperty [OrderChannel]
oDefs)) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a position channel.

@
enc =
    'encoding'
      . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"Animal\", 'PmType' 'Graphics.Vega.VegaLite.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' 'Graphics.Vega.VegaLite.X' [ 'PName' \"Animal\", 'PmType' 'Graphics.Vega.VegaLite.Ordinal', 'PAxis' [] ]
@
-}
position ::
  Position
  -- ^ The channel to encode.
  -> [PositionChannel]
  -- ^ The options for the channel; this will usually include the name ('PName')
  --    and measurement type ('PmType'), but can be a reference to a row or
  --    column repeat field.
  -> BuildEncodingSpecs
position :: Position -> [PositionChannel] -> BuildEncodingSpecs
position Position
pos [PositionChannel]
pDefs [EncodingSpec]
ols =
  let defs :: VLSpec
defs = [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map PositionChannel -> Pair
positionChannelProperty [PositionChannel]
pDefs)
  in (FieldName, VLSpec) -> EncodingSpec
ES (Position -> FieldName
positionLabel Position
pos, VLSpec
defs) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

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 ('Graphics.Vega.VegaLite.RScale' [ ( 'Graphics.Vega.VegaLite.ChY', 'Graphics.Vega.VegaLite.Independent' ) ])
@
-}
resolution ::
  Resolve
  -> BuildResolveSpecs
  -- ^ Prior to @0.5.0.0@ this was @BuildLabelledSpecs@.
resolution :: Resolve -> BuildResolveSpecs
resolution Resolve
res [ResolveSpec]
ols = Resolve -> ResolveSpec
resolveProperty Resolve
res forall a. a -> [a] -> [a]
: [ResolveSpec]
ols


{-|

Encode a new facet to be arranged in rows.

See the
<https://vega.github.io/vega-lite/docs/facet.html#facet-row-and-column-encoding-channels 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 = 'Graphics.Vega.VegaLite.dataFromUrl' \"crimeData.csv\"
    enc = 'encoding'
            . 'position' 'Graphics.Vega.VegaLite.X' ['PName' \"month\", 'PmType' 'Graphics.Vega.VegaLite.Temporal']
            . 'position' 'Graphics.Vega.VegaLite.Y' ['PName' \"reportedCrimes\"
                         , 'PmType' 'Graphics.Vega.VegaLite.Quantitative'
                         , 'PAggregate' 'Graphics.Vega.VegaLite.Sum'
                         , 'PAxis' ['AxNoTitle']
                         ]
            . 'row' ['FName' \"crimeType\", 'FmType' 'Graphics.Vega.VegaLite.Nominal']

in 'Graphics.Vega.VegaLite.toVegaLite' ['height' 80, dvals [], 'mark' 'Graphics.Vega.VegaLite.Bar' [], enc []]
@

-}
row ::
  [FacetChannel]
  -- ^ The facet properties for the channel; this should include the name of
  --   the field ('FName') and its measurement type ('FmType').
  -> BuildEncodingSpecs
row :: [FacetChannel] -> BuildEncodingSpecs
row [FacetChannel]
fFields [EncodingSpec]
ols = (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"row", [Pair] -> VLSpec
object (forall a b. (a -> b) -> [a] -> [b]
map FacetChannel -> Pair
facetChannelProperty [FacetChannel]
fFields)) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a shape channel.

@
'shape' [ 'MName' \"Species\", 'MmType' 'Graphics.Vega.VegaLite.Nominal' ] []
@
-}
shape ::
  [MarkChannel]
  -- ^ What data values are used to control the shape parameters of the mark.
  -> BuildEncodingSpecs
shape :: [MarkChannel] -> BuildEncodingSpecs
shape [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"shape" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a size channel.

@
'size' [ 'MName' \"Age\", 'MmType' 'Graphics.Vega.VegaLite.Quantitative' ] []
@
-}
size ::
  [MarkChannel]
  -- ^ What data values are used to control the size parameters of the mark.
  -> BuildEncodingSpecs
size :: [MarkChannel] -> BuildEncodingSpecs
size [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"size" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a stroke channel. This acts in a similar way to encoding by 'color' but
only affects the exterior boundary of marks.

@
'stroke' [ 'MName' \"Species\", 'MmType' 'Graphics.Vega.VegaLite.Nominal' ] []
@

Note that if both @stroke@ and 'color' encodings are specified, @stroke@ takes
precedence.

-}
stroke ::
  [MarkChannel]
  -- ^ What data values are used to control the stoke parameters of the mark.
  -> BuildEncodingSpecs
stroke :: [MarkChannel] -> BuildEncodingSpecs
stroke [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"stroke" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a stroke-dash channel.

The following will use a different dash style for each value in the
\"symbol" field (a multi-series line chart):

@
'Graphics.Vega.VegaLite.toVegaLite' [ 'Graphics.Vega.VegaLite.dataFromUrl' \"data/stocks.csv\" []
           , 'mark' 'Graphics.Vega.VegaLite.Line' []
           , 'encoding'
             . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"date\", 'PmType' 'Graphics.Vega.VegaLite.Temporal' ]
             . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"price\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
             . strokeDash [ 'MName' \"symbol\", 'MmType' 'Graphics.Vega.VegaLite.Nominal' ]
             $ []
           ]
@

It can also be used to change the line style for connected
points (e.g. to indicate where the data changes its \"predicted\"
value, noting that there are two points at @\"a\"@ equal to @\"E\"@):

@
'Graphics.Vega.VegaLite.toVegaLite' [ 'Graphics.Vega.VegaLite.dataFromColumns' []
             . 'Graphics.Vega.VegaLite.dataColumn' \"a\" ('Strings' [ \"A\", \"B\", \"D\", \"E\", \"E\", \"G\", \"H\"])
             . 'Graphics.Vega.VegaLite.dataColumn' \"b\" ('Numbers' [ 28, 55, 91, 81, 81, 19, 87 ])
             . 'Graphics.Vega.VegaLite.dataColumn' \"predicted\" ('Booleans' [False, False, False, False, True, True, True])
             $ []
           , 'mark' 'Graphics.Vega.VegaLite.Line' []
           , 'encoding'
             . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"a\", 'PmType' 'Graphics.Vega.VegaLite.Ordinal' ]
             . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"b\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
             . strokeDash [ 'MName' \"predicted\", 'MmType' 'Graphics.Vega.VegaLite.Nominal' ]
             $ []
           ]
@

@since 0.6.0.0

-}

strokeDash ::
  [MarkChannel]
  -- ^ What data values are used to control the stoke opacity parameters of the mark.
  -> BuildEncodingSpecs
strokeDash :: [MarkChannel] -> BuildEncodingSpecs
strokeDash [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"strokeDash" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a stroke opacity channel. This acts in a similar way to encoding by
'opacity' but only affects the exterior boundary of marks. If both 'opacity' and
@strokeOpacity@ are specified, @strokeOpacity@ takes precedence for stroke encoding.

@since 0.4.0.0

-}

strokeOpacity ::
  [MarkChannel]
  -- ^ What data values are used to control the stoke opacity parameters of the mark.
  -> BuildEncodingSpecs
strokeOpacity :: [MarkChannel] -> BuildEncodingSpecs
strokeOpacity [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"strokeOpacity" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a stroke width channel.

@since 0.4.0.0

-}

strokeWidth ::
  [MarkChannel]
  -- ^ What data values are used to control the stoke width parameters of the mark.
  -> BuildEncodingSpecs
strokeWidth :: [MarkChannel] -> BuildEncodingSpecs
strokeWidth [MarkChannel]
markProps [EncodingSpec]
ols = FieldName -> [MarkChannel] -> EncodingSpec
mchan_ FieldName
"strokeWidth" [MarkChannel]
markProps forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a text channel. See the
<https://vega.github.io/vega-lite/docs/encoding.html#text Vega-Lite documentation>
for further details on the text and tooltip channels and
<https://vega.github.io/vega-lite/docs/format.html Vega-Lite formatting documentation>
for formatting the appearance of the text.

@
'encoding'
    . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' "miles", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
    . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' "gas", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
    . 'text' [ 'TName' "miles", 'TmType' 'Graphics.Vega.VegaLite.Quantitative' ]
@
-}
text ::
  [TextChannel]
  -- ^ What data values are used to control the text parameters.
  -> BuildEncodingSpecs
text :: [TextChannel] -> BuildEncodingSpecs
text [TextChannel]
tDefs [EncodingSpec]
ols =
  (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"text", [Pair] -> VLSpec
object (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TextChannel -> [Pair]
textChannelProperty [TextChannel]
tDefs)) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

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
<https://vega.github.io/vega-lite/docs/timeunit.html#transform 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' ('Graphics.Vega.VegaLite.TU' 'Graphics.Vega.VegaLite.Month') \"date\" \"monthly\"

enc = 'encoding'
        . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"date\", 'PmType' 'Graphics.Vega.VegaLite.Temporal', 'PTimeUnit' ('Graphics.Vega.VegaLite.TU' 'Graphics.Vega.VegaLite.Day') ]
        . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PAggregate' 'Graphics.Vega.VegaLite.Sum', 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
        . 'detail' [ 'DName' \"monthly\", 'DmType' 'Graphics.Vega.VegaLite.Temporal' ]
@

-}
timeUnitAs ::
  TimeUnit
  -- ^ The width of each bin.
  --
  --   Prior to @0.10.0.0@ this was sent a single time unit.
  -> FieldName
  -- ^ The field to bin.
  -> FieldName
  -- ^ The name of the binned data created by this routine.
  -> BuildTransformSpecs
timeUnitAs :: TimeUnit -> FieldName -> FieldName -> BuildTransformSpecs
timeUnitAs TimeUnit
tu FieldName
field FieldName
label [TransformSpec]
ols =
  let fields :: [Pair]
fields = [ Key
"timeUnit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TimeUnit -> VLSpec
timeUnitSpec TimeUnit
tu
               , Key
"field" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
field
               , Key
"as" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FieldName
label ]
  in VLSpec -> TransformSpec
TS ([Pair] -> VLSpec
object [Pair]
fields) forall a. a -> [a] -> [a]
: [TransformSpec]
ols


{-|

Encode a tooltip channel. See the
<https://vega.github.io/vega-lite/docs/encoding.html#text Vega-Lite documentation>
for further details on the text and tooltip channels and
<https://vega.github.io/vega-lite/docs/format.html Vega-Lite formatting documentation>
for formatting the appearance of the text.

@
enc = 'encoding'
        . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"Horsepower\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
        . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"Miles_per_Gallon\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
        . 'tooltip' [ 'TName' \"Year\", 'TmType' 'Graphics.Vega.VegaLite.Temporal', 'TFormat' "%Y" ]
@

To encode multiple tooltip values with a mark, use 'tooltips'.

-}
tooltip ::
  [TextChannel]
  -- ^ The properties for the channel.
  --
  --   If the list is empty then this turns off tooltip support for
  --   this channel. This is new to @0.5.0.0@, but is also the
  --   default behavior in Vega Lite 4.
  -> BuildEncodingSpecs
tooltip :: [TextChannel] -> BuildEncodingSpecs
tooltip [] [EncodingSpec]
ols =
  (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"tooltip", VLSpec
A.Null) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols
tooltip [TextChannel]
tDefs [EncodingSpec]
ols =
  (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"tooltip", [Pair] -> VLSpec
object (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TextChannel -> [Pair]
textChannelProperty [TextChannel]
tDefs)) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols


{-|

Encode a tooltip channel using multiple data fields.

@since 0.3.0.0

@
'encoding'
    . 'position' 'Graphics.Vega.VegaLite.X' [ 'PName' \"Horsepower\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
    . 'position' 'Graphics.Vega.VegaLite.Y' [ 'PName' \"Miles_per_Gallon\", 'PmType' 'Graphics.Vega.VegaLite.Quantitative' ]
    . 'tooltips' [ [ 'TName' \"Year\",  'TmType' 'Graphics.Vega.VegaLite.Temporal', 'TFormat' "%Y" ]
               , [ 'TName' \"Month\", 'TmType' 'Graphics.Vega.VegaLite.Temporal', 'TFormat' "%Y" ] ]
@
-}
tooltips ::
  [[TextChannel]]
  -- ^ A separate list of properties for each channel.
  -> BuildEncodingSpecs
tooltips :: [[TextChannel]] -> BuildEncodingSpecs
tooltips [[TextChannel]]
tDefs [EncodingSpec]
ols =
  (FieldName, VLSpec) -> EncodingSpec
ES (FieldName
"tooltip" forall a. ToJSON a => FieldName -> a -> (FieldName, VLSpec)
.=~ forall a b. (a -> b) -> [a] -> [b]
map ([Pair] -> VLSpec
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TextChannel -> [Pair]
textChannelProperty) [[TextChannel]]
tDefs) forall a. a -> [a] -> [a]
: [EncodingSpec]
ols