{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}

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

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

Basic types that are used throughout VegaLite.
Would it make sense to break this up into
smaller modules?

-}

module Graphics.Vega.VegaLite.Foundation
       ( Angle
       , Color
       , DashStyle
       , DashOffset
       , FieldName
       , Opacity
       , StyleLabel
       , VegaExpr
       , ZIndex

       , FontWeight(..)
       , Measurement(..)
       , Arrangement(..)
       , APosition(..)
       , Orientation(..)
       , Position(..)

       , HAlign(..)
       , VAlign(..)
       , BandAlign(..)

       , StrokeCap(..)
       , StrokeJoin(..)

       , Scale(..)

       , SortField(..)

       , Cursor(..)

       , OverlapStrategy(..)
       , Side(..)

       , Symbol(..)

       , StackProperty(..)
       , StackOffset(..)

       , TooltipContent(..)

       , Channel(..)
       , Resolve(..)
       , Resolution(..)

       , Bounds(..)
       , CompositionAlignment(..)
       , Padding(..)
       , Autosize(..)
       , RepeatFields(..)
       , CInterpolate(..)

       , ViewBackground(..)

       , HeaderProperty(..)

       -- not for external export
       , fontWeightSpec
       , measurementLabel
       , arrangementLabel
       , anchorLabel
       , orientationSpec
       , hAlignLabel
       , vAlignLabel
       , bandAlignLabel
       , strokeCapLabel
       , strokeJoinLabel
       , scaleLabel
       , positionLabel
       , sortFieldSpec
       , cursorLabel
       , overlapStrategyLabel
       , sideLabel
       , symbolLabel
       , stackPropertySpecSort
       , stackPropertySpecOffset
       , stackOffset
       , ttContentLabel
       , channelLabel
       , resolveProperty
       , boundsSpec
       , compositionAlignmentSpec
       , paddingSpec
       , autosizeProperty
       , repeatFieldsProperty
       , cInterpolateSpec
       , viewBackgroundSpec

       , fromT
       , fromColor
       , fromDS
       , splitOnNewline
       , field_
       , header_
       , order_
       , allowNull

       -- aeson 2.0 support
       , (.=~)
       , toKey
       , toKeys
       , toObject
       )
    where

import qualified Data.Aeson as A

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

import qualified Data.Text as T

#if MIN_VERSION_aeson(2, 0, 0)
import Control.Arrow (first)
#endif

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

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

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


import Graphics.Vega.VegaLite.Specification
  ( VLSpec
  , LabelledSpec
  , ResolveSpec(..)
  )


{-
Similar to the Aeson .= version, but retains the Text,Value pairing as
this matches LabelledSpec. Ideally we'd change LabelledSpec to match
Pair (aka Key,Value) but then we'd have different types depending on
the version of aeson in use, which is less-than-ideal. The current
thinking is that we can bump the minimum aeson value to 2.0 at some
point and make the change then.

It does leave a number of "internal" routines in place that return
LabelledSpec rather than Pair, since they have been made available for
use, which means a confusing set of "this function can use .= and this
one has to use .=~".
-}

(.=~) :: ToJSON a => T.Text -> a -> (T.Text, A.Value)
Text
a .=~ :: Text -> a -> (Text, Value)
.=~ a
b = (Text
a, a -> Value
forall a. ToJSON a => a -> Value
toJSON a
b)

toKey :: LabelledSpec -> Pair
#if MIN_VERSION_aeson(2, 0, 0)
toKey :: (Text, Value) -> Pair
toKey = (Text -> Key) -> (Text, Value) -> Pair
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Text -> Key
Key.fromText
#else
toKey = id
#endif

toKeys :: [LabelledSpec] -> [Pair]
toKeys :: [(Text, Value)] -> [Pair]
toKeys = ((Text, Value) -> Pair) -> [(Text, Value)] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Value) -> Pair
toKey

toObject :: [LabelledSpec] -> VLSpec
toObject :: [(Text, Value)] -> Value
toObject = [Pair] -> Value
object ([Pair] -> Value)
-> ([(Text, Value)] -> [Pair]) -> [(Text, Value)] -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Text, Value)] -> [Pair]
toKeys


field_ :: FieldName -> Pair
field_ :: Text -> Pair
field_ Text
f = Key
"field" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
f

header_ :: T.Text -> [HeaderProperty] -> LabelledSpec
header_ :: Text -> [HeaderProperty] -> (Text, Value)
header_ Text
extra [HeaderProperty]
hps = (Text
"header" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
extra, [Pair] -> Value
object ((HeaderProperty -> Pair) -> [HeaderProperty] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map HeaderProperty -> Pair
headerProperty [HeaderProperty]
hps))

-- could restrict to ascending/descending
order_ :: T.Text -> Pair
order_ :: Text -> Pair
order_ Text
o = Key
"order" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
o


-- allowNull :: A.ToJSON a => Maybe a -> VLSpec
allowNull :: Maybe Int -> VLSpec
allowNull :: Maybe Int -> Value
allowNull (Just Int
a) = Int -> Value
forall a. ToJSON a => a -> Value
toJSON Int
a
allowNull Maybe Int
Nothing = Value
A.Null


{-|

The field name. This can include \"dotted\" notation, such as
@\"o.latitude\"@.

There is __no attempt__ to validate this value (e.g. check it
is not empty, contains only valid characters, or
remove excess whitespace).

@since 0.5.0.0
-}
type FieldName = T.Text


{-|

Convenience type-annotation label to indicate a color value.
There is __no attempt__ to validate that the user-supplied input
is a valid color.

Any supported HTML color specification can be used, such as:

@
\"#eee\"
\"#734FD8\"
\"crimson\"
\"rgb(255,204,210)\"
\"hsl(180, 50%, 50%)\"
@

A blank string is converted to the JSON null value (new in @0.5.0.0@).

@since 0.4.0.0
-}

type Color = T.Text


-- strip out trailing white space just to be sure
fromColor :: Color -> VLSpec
fromColor :: Text -> Value
fromColor = Text -> Value
cleanT


-- strips leading and trailing white space and, if the result
-- is empty, returns Null, otherwise the trimmed text.
--
cleanT :: T.Text -> VLSpec
cleanT :: Text -> Value
cleanT Text
t =
  let tout :: Text
tout = Text -> Text
T.strip Text
t
  in if Text -> Bool
T.null Text
tout
     then Value
A.Null
     else Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
tout



{-|
The dash style for a line. This is defined as a series of on and then
off lengths, in pixels. So @[10, 4, 5, 2]@ means a long line, followed
by a space, then a line half as long as the first segment, and then
a short space. This pattern is then repeated.

This is a convenience type annotation and there is __no validation__
of the input.

@since 0.5.0.0
-}
type DashStyle = [Double]


fromDS :: DashStyle -> VLSpec
-- fromDS [] = A.Null  -- what is the correct handling of this?
fromDS :: DashStyle -> Value
fromDS = DashStyle -> Value
forall a. ToJSON a => a -> Value
toJSON


{-|
The offset at which to start drawing the line dash (given by a
'DashStyle' argument), in pixels.

This is a convenience type annotation and there is __no validation__
of the input.

@since 0.5.0.0
-}
type DashOffset = Double


{-|

Convenience type-annotation label to indicate an opacity value, which
lies in the range 0 to 1 inclusive. There is __no attempt__ to validate
that the user-supplied value falls in this range.

A value of 0 indicates fully transparent (see through), and 1 is
fully opaque (does not show anything it is on top of).

@since 0.4.0.0
-}

type Opacity = Double


{-|

Convenience type-annotation to indicate a name, or label, that represents
a set of mark or axis styles. The styles are generated with
'Graphics.Vega.VegaLite.AxisNamedStyles' and
'Graphics.Vega.VegaLite.MarkNamedStyles',
and used with constructs such as
'Graphics.Vega.VegaLite.AStyle',
'Graphics.Vega.VegaLite.AxStyle',
'Graphics.Vega.VegaLite.MStyle', and
'Graphics.Vega.VegaLite.TStyle'.

@since 0.6.0.0
-}

type StyleLabel = T.Text

{-|

Convenience type-annotation label to indicate an angle, which is measured
in degrees from the horizontal (so anti-clockwise).

The value should be in the range 0 to 360, inclusive, but __no attempt__ is
made to enforce this.

@since 0.4.0.0
-}

type Angle = Double


{-|

At what "depth" (z index) is the item to be drawn (a relative depth
for items in the visualization). The standard values are @0@ for
back and @1@ for front, but other values can be used if you want
to ensure a certain layering of items.

The following example is taken from a discussion with
<https://github.com/gicentre/elm-vegalite/issues/15#issuecomment-524527125 Jo Wood>:

@
let dcols = 'Graphics.Vega.VegaLite.dataFromColumns' []
              . 'Graphics.Vega.VegaLite.dataColumn' "x" ('Graphics.Vega.VegaLite.Numbers' [ 20, 10 ])
              . 'Graphics.Vega.VegaLite.dataColumn' "y" ('Graphics.Vega.VegaLite.Numbers' [ 10, 20 ])
              . 'Graphics.Vega.VegaLite.dataColumn' "cat" ('Graphics.Vega.VegaLite.Strings' [ "a", "b" ])

    axis lbl z = [ 'Graphics.Vega.VegaLite.PName' lbl, 'Graphics.Vega.VegaLite.PmType' 'Graphics.Vega.VegaLite.Quantitative', 'Graphics.Vega.VegaLite.PAxis' [ 'Graphics.Vega.VegaLite.AxZIndex' z ] ]
    enc = 'Graphics.Vega.VegaLite.encoding'
            . 'Graphics.Vega.VegaLite.position' 'X' (axis "x" 2)
            . 'Graphics.Vega.VegaLite.position' 'Y' (axis "y" 1)
            . 'Graphics.Vega.VegaLite.color' [ 'Graphics.Vega.VegaLite.MName' "cat", 'Graphics.Vega.VegaLite.MmType' 'Graphics.Vega.VegaLite.Nominal', 'Graphics.Vega.VegaLite.MLegend' [] ]

    cfg = 'Graphics.Vega.VegaLite.configure'
            . 'Graphics.Vega.VegaLite.configuration' ('Graphics.Vega.VegaLite.Axis' [ 'Graphics.Vega.VegaLite.GridWidth' 8 ])
            . 'Graphics.Vega.VegaLite.configuration' ('Graphics.Vega.VegaLite.AxisX' [ 'Graphics.Vega.VegaLite.GridColor' "red" ])
            . 'Graphics.Vega.VegaLite.configuration' ('Graphics.Vega.VegaLite.AxisY' [ 'Graphics.Vega.VegaLite.GridColor' "blue" ])

in 'Graphics.Vega.VegaLite.toVegaLite' [ cfg []
              , dcols []
              , enc []
              , 'Graphics.Vega.VegaLite.mark' 'Graphics.Vega.VegaLite.Circle' [ 'Graphics.Vega.VegaLite.MSize' 5000, 'Graphics.Vega.VegaLite.MOpacity' 1 ]
              ]
@

<<images/zindex.png>>

<https://vega.github.io/editor/#/url/vega-lite/N4KABBYEQMYPYDsBmBLA5lAXGUk-QEMAPFAZwE0sdx9ao0AnFAEwGE4AbOBqqAIw4BXAKZQatAL4AacfijEyADSq5acxi3Zce2KA2HMxasNNl55JUirNr6TZgHUWAFwAWVABw2IE2afMAtgQMANbWxlCkKABeotgArAAMyTIRcAAOBDAozgCeVACMqbZ56XHQ2QwwHKJ+xRBQzATOBOG2AG4EQsJW2ADa3viqxnQwzbyt9SPmRFQATIlT0w352AWJg3j+y8PLDWPOvHxQS8tQs2uLm7arYAvXPoMAunWyUAAkpDCuwkG8rs5nOlSJgAPSg9rCNAEAB0aByrkEfBhKDgoK+PyCEKhBAAtBwcsIIQBmGEAK1IiBOb2ECHgzBQCAw2F25ng2ja0ygqGEHEMugO1L2UFK5SgCDgAUZXSFZxqaFp-LACEEHA4g22dAu1GFPL5vFmpzoot4AEdBAQEM4cs0UJDZVyFL0dXtIFBoozmMJtXMHiYNUboLdWbY9UqoPlA+YTbpzZbrS1rfao26nZzXe7Pd7Cn7fMY85BfL4gA View the visualization in the Vega Editor>

@since 0.4.0.0
-}

type ZIndex = Natural


{-|

Convenience type-annotation label to indicate a
<https://vega.github.io/vega/docs/expressions/ Vega Expression>.
There is __no attempt__ to validate the expression.

Examples include:

@
"datum.IMDB_Rating != null"
"datum.height / 1000"
"if(datum.index % 2 == 1, datum.label, '')"
"sampleLogNormal(2.3, 0.3)"
@

@since 0.5.0.0
-}
type VegaExpr = T.Text


-- | Indicates the weight options for a font.

data FontWeight
    = Bold
    | Bolder
    | Lighter
    | Normal
    | W100
    | W200
    | W300
    | W400
    | W500
    | W600
    | W700
    | W800
    | W900


fromF :: Double -> VLSpec
fromF :: Double -> Value
fromF = Double -> Value
forall a. ToJSON a => a -> Value
toJSON

fromT :: T.Text -> VLSpec
fromT :: Text -> Value
fromT = Text -> Value
forall a. ToJSON a => a -> Value
toJSON

-- If there is a new-line in the text then convert to a list.
splitOnNewline :: T.Text -> VLSpec
splitOnNewline :: Text -> Value
splitOnNewline Text
ts =
  case (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n') Text
ts of
    [] -> Text -> Value
fromT Text
""
    [Text
s] -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
s
    [Text]
s -> [Text] -> Value
forall a. ToJSON a => a -> Value
toJSON [Text]
s


fontWeightSpec :: FontWeight -> VLSpec
fontWeightSpec :: FontWeight -> Value
fontWeightSpec FontWeight
Bold = Text -> Value
fromT Text
"bold"
fontWeightSpec FontWeight
Bolder = Text -> Value
fromT Text
"bolder"
fontWeightSpec FontWeight
Lighter = Text -> Value
fromT Text
"lighter"
fontWeightSpec FontWeight
Normal = Text -> Value
fromT Text
"normal"
fontWeightSpec FontWeight
W100 = Double -> Value
fromF Double
100
fontWeightSpec FontWeight
W200 = Double -> Value
fromF Double
200
fontWeightSpec FontWeight
W300 = Double -> Value
fromF Double
300
fontWeightSpec FontWeight
W400 = Double -> Value
fromF Double
400
fontWeightSpec FontWeight
W500 = Double -> Value
fromF Double
500
fontWeightSpec FontWeight
W600 = Double -> Value
fromF Double
600
fontWeightSpec FontWeight
W700 = Double -> Value
fromF Double
700
fontWeightSpec FontWeight
W800 = Double -> Value
fromF Double
800
fontWeightSpec FontWeight
W900 = Double -> Value
fromF Double
900


{-|

Type of measurement to be associated with some channel.

-}

data Measurement
    = Nominal
      -- ^ Data are categories identified by name alone and which have no intrinsic order.
    | Ordinal
      -- ^ Data are also categories, but ones which have some natural order.
    | Quantitative
      -- ^ Data are numeric measurements typically on a continuous scale.
    | Temporal
      -- ^ Data represents time in some manner.
    | GeoFeature
      -- ^ Geospatial position encoding ('Longitude' and 'Latitude') should specify the 'Graphics.Vega.VegaLite.PmType'
      -- as @Quantitative@. Geographically referenced features encoded as 'Graphics.Vega.VegaLite.shape' marks
      -- should specify 'Graphics.Vega.VegaLite.MmType' as @GeoFeature@ (Vega-Lite currently refers to this type
      -- as @<https://vega.github.io/vega-lite/docs/encoding.html geojson>@.


measurementLabel :: Measurement -> T.Text
measurementLabel :: Measurement -> Text
measurementLabel Measurement
Nominal = Text
"nominal"
measurementLabel Measurement
Ordinal = Text
"ordinal"
measurementLabel Measurement
Quantitative = Text
"quantitative"
measurementLabel Measurement
Temporal = Text
"temporal"
measurementLabel Measurement
GeoFeature = Text
"geojson"


-- | Identifies how repeated or faceted views are arranged.
--
--   This is used with a number of constructors: 'Graphics.Vega.VegaLite.ByRepeatOp',
--   'Graphics.Vega.VegaLite.HRepeat', 'Graphics.Vega.VegaLite.MRepeat', 'Graphics.Vega.VegaLite.ORepeat', 'Graphics.Vega.VegaLite.PRepeat', and 'Graphics.Vega.VegaLite.TRepeat'.

-- based on schema 3.3.0 #/definitions/RepeatRef

data Arrangement
    = Column
      -- ^ Column arrangement.
    | Row
      -- ^ Row arrangement.
    | Flow
      -- ^ Flow arrangement (aka \"repeat\").
      --
      --   @since 0.4.0.0
    | Layer
      -- ^ Layer arrangement in a repeat view.
      --
      --   @since 0.9.0.0


arrangementLabel :: Arrangement -> T.Text
arrangementLabel :: Arrangement -> Text
arrangementLabel Arrangement
Column = Text
"column"
arrangementLabel Arrangement
Row = Text
"row"
arrangementLabel Arrangement
Flow = Text
"repeat"  -- NOTE: not "flow"!
arrangementLabel Arrangement
Layer = Text
"layer"


-- | Indicates the anchor position for text.

data APosition
    = AStart
      -- ^ The start of the text.
    | AMiddle
      -- ^ The middle of the text.
    | AEnd
      -- ^ The end of the text.


anchorLabel :: APosition -> T.Text
anchorLabel :: APosition -> Text
anchorLabel APosition
AStart = Text
"start"
anchorLabel APosition
AMiddle = Text
"middle"
anchorLabel APosition
AEnd = Text
"end"


{-|

The orientation of an item. This is used with:
'Graphics.Vega.VegaLite.BLeLDirection', 'Graphics.Vega.VegaLite.LDirection',
'Graphics.Vega.VegaLite.LeDirection', 'Graphics.Vega.VegaLite.LeGradientDirection',
'Graphics.Vega.VegaLite.LeLDirection', 'Graphics.Vega.VegaLite.LeSymbolDirection',
and 'Graphics.Vega.VegaLite.MOrient'.

In @0.4.0.0@ this was renamed from @MarkOrientation@ to 'Orientation'.

-}

-- based on schema 3.3.0 #/definitions/Orientation

data Orientation
    = Horizontal
      -- ^ Display horizontally.
    | Vertical
      -- ^ Display vertically.


orientationSpec :: Orientation -> VLSpec
orientationSpec :: Orientation -> Value
orientationSpec Orientation
Horizontal = Value
"horizontal"
orientationSpec Orientation
Vertical = Value
"vertical"


-- TODO:
--
--  encoding of X2/... shouldn't include the PmType in the output, apparently
--  so we could try and filter that out, or just rely on the user to not
--  add the PmType fields in this case.

{-|

Type of position channel, @X@ and @Y@ represent horizontal and vertical axis
dimensions on a plane and @X2@ and @Y2@ represent secondary axis dimensions where
two scales are overlaid in the same space. Geographic positions represented by
longitude and latiutude values are identified with @Longitude@, @Latitude@ and
their respective secondary equivalents. Such geographic position channels are
subject to a map projection (set using 'Graphics.Vega.VegaLite.projection') before being placed graphically.

-}
data Position
    = X
    | Y
    | X2
    -- ^ The secondary coordinate for ranged 'Graphics.Vega.VegaLite.Area', 'Graphics.Vega.VegaLite.Bar', 'Graphics.Vega.VegaLite.Rect', and 'Graphics.Vega.VegaLite.Rule'
    --    marks.
    | Y2
    -- ^ The secondary coordinate for ranged 'Graphics.Vega.VegaLite.Area', 'Graphics.Vega.VegaLite.Bar', 'Graphics.Vega.VegaLite.Rect', and 'Graphics.Vega.VegaLite.Rule'
    --    marks.
    | Theta
      -- ^ The start angle of an arc.
      --
      --   @since 0.9.0.0
    | Theta2
      -- ^ The end angle of an arc.
      --
      --   @since 0.9.0.0
    | R
      -- ^ The outer radius of an arc.
      --
      --   @since 0.9.0.0
    | R2
      -- ^ The inner radius of an arc.
      --
      --   @since 0.9.0.0
    | XError
      -- ^ Indicates that the 'X' channel represents the mid-point and
      --   the 'XError' channel gives the offset. If 'XError2' is not
      --   defined then this channel value is applied symmetrically.
      --
      --   @since 0.4.0.0
    | XError2
      -- ^ Used to support asymmetric error ranges defined as 'XError'
      --   and 'XError2'. One of 'XError' or 'XError2' channels must
      --   contain positive values and the other negative values.
      --
      --   @since 0.4.0.0
    | YError
      -- ^ Indicates that the 'Y' channel represents the mid-point and
      --   the 'YError' channel gives the offset. If 'YError2' is not
      --   defined then this channel value is applied symmetrically.
      --
      --   @since 0.4.0.0
    | YError2
      -- ^ Used to support asymmetric error ranges defined as 'YError'
      --   and 'YError2'. One of 'YError' or 'YError2' channels must
      --   contain positive values and the other negative values.
      --
      --   @since 0.4.0.0
    | Longitude
      -- ^ The longitude value for projections.
    | Latitude
      -- ^ The latitude value for projections.
    | Longitude2
      -- ^ A second longitude coordinate.
    | Latitude2
      -- ^ A second longitude coordinate.


positionLabel :: Position -> T.Text
positionLabel :: Position -> Text
positionLabel Position
X = Text
"x"
positionLabel Position
Y = Text
"y"
positionLabel Position
X2 = Text
"x2"
positionLabel Position
Y2 = Text
"y2"
positionLabel Position
Theta = Text
"theta"
positionLabel Position
Theta2 = Text
"theta2"
positionLabel Position
R = Text
"radius"
positionLabel Position
R2 = Text
"radius2"
positionLabel Position
XError     = Text
"xError"
positionLabel Position
YError     = Text
"yError"
positionLabel Position
XError2    = Text
"xError2"
positionLabel Position
YError2    = Text
"yError2"
positionLabel Position
Longitude = Text
"longitude"
positionLabel Position
Latitude = Text
"latitude"
positionLabel Position
Longitude2 = Text
"longitude2"
positionLabel Position
Latitude2 = Text
"latitude2"



-- | Indicates the horizontal alignment of text such as on an axis or legend.

data HAlign
    = AlignCenter
    | AlignLeft
    | AlignRight


-- | Indicates the vertical alignment of text that may be attached to a mark.

data VAlign
    = AlignTop
      -- ^ The position refers to the top of the text, calculated relative to
      --   the font size. Also see 'AlignLineTop'.
    | AlignMiddle
      -- ^ The middle of the text.
    | AlignBottom
      -- ^ The position refers to the bottom of the text, including
      --   descenders, like g. This is calculated relative to the
      --   font size. Also see 'AlignLineBottom'.
    | AlignBaseline
      -- ^ The position refers to the baseline of the text (so it does
      --   not include descenders). This maps to the Vega-Lite
      --   @\"alphabetic\"@ value.
      --
      --   @since 0.6.0.0
    | AlignLineTop
      -- ^ Similar to 'AlignTop', but relative to the line height, not font size.
      --
      --   This was added in Vega-Lite 4.6.0.
      --
      --   @since 0.7.0.0
    | AlignLineBottom
      -- ^ Similar to 'AlignBottom', but relative to the line height, not font size.
      --
      --   This was added in Vega-Lite 4.6.0.
      --
      --   @since 0.7.0.0

hAlignLabel :: HAlign -> T.Text
hAlignLabel :: HAlign -> Text
hAlignLabel HAlign
AlignLeft = Text
"left"
hAlignLabel HAlign
AlignCenter = Text
"center"
hAlignLabel HAlign
AlignRight = Text
"right"

vAlignLabel :: VAlign -> T.Text
vAlignLabel :: VAlign -> Text
vAlignLabel VAlign
AlignTop = Text
"top"
vAlignLabel VAlign
AlignMiddle = Text
"middle"
vAlignLabel VAlign
AlignBottom = Text
"bottom"
vAlignLabel VAlign
AlignBaseline = Text
"alphabetic"
vAlignLabel VAlign
AlignLineTop = Text
"line-top"
vAlignLabel VAlign
AlignLineBottom = Text
"line-bottom"

{-|

Where should tick marks and grid lines be placed. This is used with
'Graphics.Vega.VegaLite.AxTickBand' and 'Graphics.Vega.VegaLite.TickBand'.

@since 0.5.0.0
-}

data BandAlign
  = BCenter
    -- ^ Use the center of the band.
  | BExtent
    -- ^ Use the band extents.


bandAlignLabel :: BandAlign -> T.Text
bandAlignLabel :: BandAlign -> Text
bandAlignLabel BandAlign
BCenter = Text
"center"
bandAlignLabel BandAlign
BExtent = Text
"extent"


-- | How are strokes capped? This is used with 'Graphics.Vega.VegaLite.MStrokeCap', 'Graphics.Vega.VegaLite.VBStrokeCap',
--   and 'Graphics.Vega.VegaLite.ViewStrokeCap'.
--
--   @since 0.4.0.0

data StrokeCap
    = CButt
      -- ^ Butt stroke cap.
    | CRound
      -- ^ Rounded stroke cap.
    | CSquare
      -- ^ Square stroke cap.


strokeCapLabel :: StrokeCap -> T.Text
strokeCapLabel :: StrokeCap -> Text
strokeCapLabel StrokeCap
CButt = Text
"butt"
strokeCapLabel StrokeCap
CRound = Text
"round"
strokeCapLabel StrokeCap
CSquare = Text
"square"


-- | How are strokes joined? This is used with 'Graphics.Vega.VegaLite.MStrokeJoin', 'Graphics.Vega.VegaLite.VBStrokeJoin',
--   and 'Graphics.Vega.VegaLite.ViewStrokeJoin'.
--
--
--   @since 0.4.0.0

data StrokeJoin
    = JMiter
      -- ^ Mitred stroke join.
    | JRound
      -- ^ Rounded stroke join.
    | JBevel
      -- ^ Bevelled stroke join.


strokeJoinLabel :: StrokeJoin -> T.Text
strokeJoinLabel :: StrokeJoin -> Text
strokeJoinLabel StrokeJoin
JMiter = Text
"miter"
strokeJoinLabel StrokeJoin
JRound = Text
"round"
strokeJoinLabel StrokeJoin
JBevel = Text
"bevel"


{-|
Used to indicate the type of scale transformation to apply.
The <https://vega.github.io/vega-lite/docs/scale.html#type Vega-Lite scale documentation>
defines which of these are for  continuous or discrete distributions,
and what the defaults are for the combination of data type and
encoding channel.

The 'Scale' type is used with the 'Graphics.Vega.VegaLite.SType'
constructor to set up the scaling properties of an encoding.
Examples:

@
'Graphics.Vega.VegaLite.PScale' [ 'Graphics.Vega.VegaLite.SType' ScTime ]
'Graphics.Vega.VegaLite.color' [ 'Graphics.Vega.VegaLite.MName' \"Acceleration\"
      , 'Graphics.Vega.VegaLite.MmType' 'Quantitative'
      , 'Graphics.Vega.VegaLite.MScale' [ 'Graphics.Vega.VegaLite.SType' ScLog, 'Graphics.Vega.VegaLite.SRange' ('Graphics.Vega.VegaLite.RStrings' [\"yellow\", \"red\"]) ]
      ]
@

The @ScBinLinear@ constructor was removed in @0.8.0.0@ because
it was not used by Vega-Lite.

The @0.4.0.0@ release removed the @ScSequential@ constructor, as
'ScLinear' should be used instead.

-}

-- #/definitions/ScaleType

data Scale
    = ScLinear
      -- ^ A linear scale.
    | ScLog
      -- ^ A log scale. Defaults to log of base 10, but can be customised with
      --   'Graphics.Vega.VegaLite.SBase'.
    | ScPow
      -- ^ A power scale. The exponent to use for scaling is specified with
      --   'Graphics.Vega.VegaLite.SExponent'.
    | ScSqrt
      -- ^ A square-root scale.
    | ScSymLog
      -- ^ A [symmetrical log (PDF link)](https://www.researchgate.net/profile/John_Webber4/publication/233967063_A_bi-symmetric_log_transformation_for_wide-range_data/links/0fcfd50d791c85082e000000.pdf)
      --   scale. Similar to a log scale but supports zero and negative values. The slope
      --   of the function at zero can be set with 'Graphics.Vega.VegaLite.SConstant'.
      --
      --   @since 0.4.0.0
    -- | ScIdentity  added in Vega-Lite 4.4, no documentation
    -- | ScSequential  added in Vega-Lite 4.4, no documentation, not clear if any different from linear
    | ScTime
      -- ^ A temporal scale.
    | ScUtc
      -- ^ A temporal scale, in UTC.
    | ScQuantile
      -- ^ A quantile scale.
      --
      --   @since 0.4.0.0
    | ScQuantize
      -- ^ A quantizing scale.
      --
      --   @since 0.4.0.0
    | ScThreshold
      -- ^ A threshold scale.
      --
      --   @since 0.4.0.0
    | ScBinOrdinal
      -- ^ An ordinal band scale.
    | ScOrdinal
      -- ^ An ordinal scale.
    | ScPoint
      -- ^ A point scale.
    | ScBand
      -- ^ A band scale.


scaleLabel :: Scale -> T.Text
scaleLabel :: Scale -> Text
scaleLabel Scale
ScLinear = Text
"linear"
scaleLabel Scale
ScLog = Text
"log"
scaleLabel Scale
ScPow = Text
"pow"
scaleLabel Scale
ScSqrt = Text
"sqrt"
scaleLabel Scale
ScSymLog = Text
"symlog"
scaleLabel Scale
ScTime = Text
"time"
scaleLabel Scale
ScUtc = Text
"utc"
scaleLabel Scale
ScQuantile = Text
"quantile"
scaleLabel Scale
ScQuantize = Text
"quantize"
scaleLabel Scale
ScThreshold = Text
"threshold"
scaleLabel Scale
ScBinOrdinal = Text
"bin-ordinal"
scaleLabel Scale
ScOrdinal = Text
"ordinal"
scaleLabel Scale
ScPoint = Text
"point"
scaleLabel Scale
ScBand = Text
"band"


-- | How should the field be sorted when performing a window transform.
--
--   @since 0.4.00

data SortField
    = WAscending FieldName
    -- ^ Sort the field into ascending order.
    | WDescending FieldName
    -- ^ Sort the field into descending order.


sortFieldSpec :: SortField -> VLSpec
sortFieldSpec :: SortField -> Value
sortFieldSpec (WAscending Text
f) = [Pair] -> Value
object [Text -> Pair
field_ Text
f, Text -> Pair
order_ Text
"ascending"]
sortFieldSpec (WDescending Text
f) = [Pair] -> Value
object [Text -> Pair
field_ Text
f, Text -> Pair
order_ Text
"descending"]


{-|

Represents the type of cursor to display. For an explanation of each type,
see the
<https://developer.mozilla.org/en-US/docs/Web/CSS/cursor#Keyword%20values CSS documentation>.

-}
data Cursor
    = CAuto
    | CDefault
    | CNone
    | CContextMenu
    | CHelp
    | CPointer
    | CProgress
    | CWait
    | CCell
    | CCrosshair
    | CText
    | CVerticalText
    | CAlias
    | CCopy
    | CMove
    | CNoDrop
    | CNotAllowed
    | CAllScroll
    | CColResize
    | CRowResize
    | CNResize
    | CEResize
    | CSResize
    | CWResize
    | CNEResize
    | CNWResize
    | CSEResize
    | CSWResize
    | CEWResize
    | CNSResize
    | CNESWResize
    | CNWSEResize
    | CZoomIn
    | CZoomOut
    | CGrab
    | CGrabbing


cursorLabel :: Cursor -> T.Text
cursorLabel :: Cursor -> Text
cursorLabel Cursor
CAuto = Text
"auto"
cursorLabel Cursor
CDefault = Text
"default"
cursorLabel Cursor
CNone = Text
"none"
cursorLabel Cursor
CContextMenu = Text
"context-menu"
cursorLabel Cursor
CHelp = Text
"help"
cursorLabel Cursor
CPointer = Text
"pointer"
cursorLabel Cursor
CProgress = Text
"progress"
cursorLabel Cursor
CWait = Text
"wait"
cursorLabel Cursor
CCell = Text
"cell"
cursorLabel Cursor
CCrosshair = Text
"crosshair"
cursorLabel Cursor
CText = Text
"text"
cursorLabel Cursor
CVerticalText = Text
"vertical-text"
cursorLabel Cursor
CAlias = Text
"alias"
cursorLabel Cursor
CCopy = Text
"copy"
cursorLabel Cursor
CMove = Text
"move"
cursorLabel Cursor
CNoDrop = Text
"no-drop"
cursorLabel Cursor
CNotAllowed = Text
"not-allowed"
cursorLabel Cursor
CAllScroll = Text
"all-scroll"
cursorLabel Cursor
CColResize = Text
"col-resize"
cursorLabel Cursor
CRowResize = Text
"row-resize"
cursorLabel Cursor
CNResize = Text
"n-resize"
cursorLabel Cursor
CEResize = Text
"e-resize"
cursorLabel Cursor
CSResize = Text
"s-resize"
cursorLabel Cursor
CWResize = Text
"w-resize"
cursorLabel Cursor
CNEResize = Text
"ne-resize"
cursorLabel Cursor
CNWResize = Text
"nw-resize"
cursorLabel Cursor
CSEResize = Text
"se-resize"
cursorLabel Cursor
CSWResize = Text
"sw-resize"
cursorLabel Cursor
CEWResize = Text
"ew-resize"
cursorLabel Cursor
CNSResize = Text
"ns-resize"
cursorLabel Cursor
CNESWResize = Text
"nesw-resize"
cursorLabel Cursor
CNWSEResize = Text
"nwse-resize"
cursorLabel Cursor
CZoomIn = Text
"zoom-in"
cursorLabel Cursor
CZoomOut = Text
"zoom-out"
cursorLabel Cursor
CGrab = Text
"grab"
cursorLabel Cursor
CGrabbing = Text
"grabbing"


{-|

Type of overlap strategy to be applied when there is not space to show all items
on an axis, and is used by
'Graphics.Vega.VegaLite.AxLabelOverlap',
'Graphics.Vega.VegaLite.LabelOverlap',
'Graphics.Vega.VegaLite.LLabelOverlap',
and 'Graphics.Vega.VegaLite.LeLabelOverlap'.
See the
<https://vega.github.io/vega-lite/docs/axis.html#labels Vega-Lite documentation>
for more details.
-}

data OverlapStrategy
    = ONone
      -- ^ No overlap strategy to be applied when there is not space to show all items
      --   on an axis.
    | OParity
      -- ^ Give all items equal weight in overlap strategy to be applied when there is
      --   not space to show them all on an axis.
    | OGreedy
      -- ^ Greedy overlap strategy to be applied when there is not space to show all
      --   items on an axis.

overlapStrategyLabel :: OverlapStrategy -> VLSpec
overlapStrategyLabel :: OverlapStrategy -> Value
overlapStrategyLabel OverlapStrategy
ONone = Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
False
overlapStrategyLabel OverlapStrategy
OParity = Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
True  -- fromT "parity"
overlapStrategyLabel OverlapStrategy
OGreedy = Text -> Value
fromT Text
"greedy"


{-|

Represents one side of a rectangular space.

Used by
'Graphics.Vega.VegaLite.AxOrient',
'Graphics.Vega.VegaLite.HLabelOrient',
'Graphics.Vega.VegaLite.HTitleOrient',
'Graphics.Vega.VegaLite.LTitleOrient',
'Graphics.Vega.VegaLite.LeTitleOrient',
'Graphics.Vega.VegaLite.Orient',
and
'Graphics.Vega.VegaLite.TOrient'.

-}

data Side
    = STop
    | SBottom
    | SLeft
    | SRight


sideLabel :: Side -> T.Text
sideLabel :: Side -> Text
sideLabel Side
STop = Text
"top"
sideLabel Side
SBottom = Text
"bottom"
sideLabel Side
SLeft = Text
"left"
sideLabel Side
SRight = Text
"right"


-- | Identifies the type of symbol used with the 'Graphics.Vega.VegaLite.Point' mark type.
--   It is used with 'Graphics.Vega.VegaLite.MShape', 'Graphics.Vega.VegaLite.LeSymbolType', and 'Graphics.Vega.VegaLite.LSymbolType'.
--
--   In version @0.4.0.0@ all constructors were changed to start
--   with @Sym@.
--
data Symbol
    = SymCircle
      -- ^ Specify a circular symbol for a shape mark.
    | SymSquare
      -- ^ Specify a square symbol for a shape mark.
    | SymCross
      -- ^ Specify a cross symbol for a shape mark.
    | SymDiamond
      -- ^ Specify a diamond symbol for a shape mark.
    | SymTriangleUp
      -- ^ Specify an upward-triangular symbol for a shape mark.
    | SymTriangleDown
      -- ^ Specify a downward-triangular symbol for a shape mark.
    | SymTriangleRight
      -- ^ Specify an right-facing triangular symbol for a shape mark.
      --
      --   @since 0.4.0.0
    | SymTriangleLeft
      -- ^ Specify an left-facing triangular symbol for a shape mark.
      --
      --   @since 0.4.0.0
    | SymStroke
      -- ^ The line symbol.
      --
      --  @since 0.4.0.0
    | SymArrow
      -- ^ Centered directional shape.
      --
      --  @since 0.4.0.0
    | SymTriangle
      -- ^ Centered directional shape. It is not clear what difference
      --   this is to 'SymTriangleUp'.
      --
      --  @since 0.4.0.0
    | SymWedge
      -- ^ Centered directional shape.
      --
      --  @since 0.4.0.0
    | SymPath T.Text
      -- ^ A custom symbol shape as an
      --   [SVG path description](https://developer.mozilla.org/en-US/docs/Web/SVG/Tutorial/Paths).
      --
      --   For correct sizing, the path should be defined within a square
      --   bounding box, defined on an axis of -1 to 1 for both dimensions.


symbolLabel :: Symbol -> T.Text
symbolLabel :: Symbol -> Text
symbolLabel Symbol
SymCircle = Text
"circle"
symbolLabel Symbol
SymSquare = Text
"square"
symbolLabel Symbol
SymCross = Text
"cross"
symbolLabel Symbol
SymDiamond = Text
"diamond"
symbolLabel Symbol
SymTriangleUp = Text
"triangle-up"
symbolLabel Symbol
SymTriangleDown = Text
"triangle-down"
symbolLabel Symbol
SymTriangleRight = Text
"triangle-right"
symbolLabel Symbol
SymTriangleLeft = Text
"triangle-left"
symbolLabel Symbol
SymStroke = Text
"stroke"
symbolLabel Symbol
SymArrow = Text
"arrow"
symbolLabel Symbol
SymTriangle = Text
"triangle"
symbolLabel Symbol
SymWedge = Text
"wedge"
symbolLabel (SymPath Text
svgPath) = Text
svgPath


-- | How are stacks applied within a transform?
--
--   Prior to version @0.4.0.0@ the @StackProperty@ type was
--   what is now @StackOffset@.

data StackProperty
    = StOffset StackOffset
      -- ^ Stack offset.
      --
      --   @since 0.4.0.0
    | StSort [SortField]
      -- ^ Ordering within a stack.
      --
      --   @since 0.4.0.0


-- | Describes the type of stacking to apply to a bar chart.
--
--   In @0.4.0.0@ this was renamed from @StackProperty@ to @StackOffset@,
--   but the constructor names have not changed.
--
data StackOffset
    = StZero
      -- ^ Offset a stacked layout using a baseline at the foot of
      --   the stack.
    | StNormalize
      -- ^ Rescale a stacked layout to use a common height while
      --   preserving the relative size of stacked quantities.
    | StCenter
      -- ^ Offset a stacked layout using a central stack baseline.
    | NoStack
      -- ^ Do not stack marks, but create a layered plot.

stackOffsetSpec :: StackOffset -> VLSpec
stackOffsetSpec :: StackOffset -> Value
stackOffsetSpec StackOffset
StZero = Value
"zero"
stackOffsetSpec StackOffset
StNormalize = Value
"normalize"
stackOffsetSpec StackOffset
StCenter = Value
"center"
stackOffsetSpec StackOffset
NoStack = Value
A.Null

stackOffset :: StackOffset -> Pair
stackOffset :: StackOffset -> Pair
stackOffset StackOffset
so = Key
"stack" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StackOffset -> Value
stackOffsetSpec StackOffset
so

stackPropertySpecOffset , stackPropertySpecSort:: StackProperty -> Maybe VLSpec
stackPropertySpecOffset :: StackProperty -> Maybe Value
stackPropertySpecOffset (StOffset StackOffset
op) = Value -> Maybe Value
forall a. a -> Maybe a
Just (StackOffset -> Value
stackOffsetSpec StackOffset
op)
stackPropertySpecOffset StackProperty
_ = Maybe Value
forall a. Maybe a
Nothing

stackPropertySpecSort :: StackProperty -> Maybe Value
stackPropertySpecSort (StSort [SortField]
sfs) = Value -> Maybe Value
forall a. a -> Maybe a
Just ([Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ((SortField -> Value) -> [SortField] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map SortField -> Value
sortFieldSpec [SortField]
sfs))
stackPropertySpecSort StackProperty
_ = Maybe Value
forall a. Maybe a
Nothing


-- | This is used with 'Graphics.Vega.VegaLite.MTooltip' and
--   can be used with 'Graphics.Vega.VegaLite.mark' or
--   'Graphics.Vega.VegaLite.MarkStyle'.
--
--   @since 0.4.0.0

data TooltipContent
  = TTEncoding
    -- ^ When enabled, tooltips are generated by the encoding
    --   (this is the default).
    --
    --   For example:
    --
    --   @'Graphics.Vega.VegaLite.mark' 'Graphics.Vega.VegaLite.Circle' ['Graphics.Vega.VegaLite.MTooltip' 'TTEncoding']@
  | TTData
    -- ^ Tooltips are generated by all fields in the underlying data.
    --
    --   For example:
    --
    --   @'Graphics.Vega.VegaLite.mark' 'Graphics.Vega.VegaLite.Circle' ['Graphics.Vega.VegaLite.MTooltip' 'TTData']@
  | TTNone
    -- ^ Disable tooltips. This is the default behavior in Vega-Lite 4,
    --   and can also be achieved by adding an encoding of
    --   @'Graphics.Vega.VegaLite.tooltip' []@.
    --
    --   For example:
    --
    --   @'Graphics.Vega.VegaLite.mark' 'Graphics.Vega.VegaLite.Circle' ['Graphics.Vega.VegaLite.MTooltip' 'TTNone']@


-- Note that TTNone is special cased by markProperty
ttContentLabel :: TooltipContent -> T.Text
ttContentLabel :: TooltipContent -> Text
ttContentLabel TooltipContent
TTEncoding = Text
"encoding"
ttContentLabel TooltipContent
TTData = Text
"data"
ttContentLabel TooltipContent
TTNone = Text
"null"


-- | Indicates a channel type to be used in a resolution specification.
--
--   Used with the 'Resolve' type and the
--   'Graphics.Vega.VegaLite.BLChannel', 'Graphics.Vega.VegaLite.BLChannelEvent',
--   'Graphics.Vega.VegaLite.ByChannel', and 'Graphics.Vega.VegaLite.Encodings'
--   constructors.
--
--   Changed in @0.7.0.0@: the @ChTooltip@ channel was removed as it was
--   dropped in Vega-Lite 4.0.

-- assuming this is based on schema 3.3.0 #/definitions/SingleDefUnitChannel

data Channel
    = ChX
    | ChY
    | ChX2
    | ChY2
    | ChLongitude
      -- ^ @since 0.4.0.0
    | ChLongitude2
      -- ^ @since 0.4.0.0
    | ChLatitude
      -- ^ @since 0.4.0.0
    | ChLatitude2
      -- ^ @since 0.4.0.0
    | ChAngle
      -- ^ @since 0.9.0.0
    | ChTheta
      -- ^ @since 0.9.0.0
    | ChTheta2
      -- ^ @since 0.9.0.0
    | ChRadius
      -- ^ @since 0.9.0.0
    | ChRadius2
      -- ^ @since 0.9.0.0
    | ChColor
    | ChFill
      -- ^ @since 0.3.0.0
    | ChFillOpacity
      -- ^ @since 0.4.0.0
    | ChHref
      -- ^ @since 0.4.0.0
    | ChKey
      -- ^ @since 0.4.0.0
    | ChOpacity
    | ChShape
    | ChSize
    | ChStroke
      -- ^ @since 0.3.0.0
    | ChStrokeDash
      -- ^ @since 0.6.0.0
    | ChStrokeOpacity
      -- ^ @since 0.4.0.0
    | ChStrokeWidth
      -- ^ @since 0.4.0.0
    | ChText
      -- ^ @since 0.4.0.0
    | ChDescription
      -- ^ @since 0.9.0.0
    | ChURL
      -- ^ @since 0.9.0.0

channelLabel :: Channel -> T.Text
channelLabel :: Channel -> Text
channelLabel Channel
ChX = Text
"x"
channelLabel Channel
ChY = Text
"y"
channelLabel Channel
ChX2 = Text
"x2"
channelLabel Channel
ChY2 = Text
"y2"
channelLabel Channel
ChLongitude = Text
"longitude"
channelLabel Channel
ChLongitude2 = Text
"longitude2"
channelLabel Channel
ChLatitude = Text
"latitude"
channelLabel Channel
ChLatitude2 = Text
"latitude2"
channelLabel Channel
ChAngle = Text
"angle"
channelLabel Channel
ChTheta = Text
"theta"
channelLabel Channel
ChTheta2 = Text
"theta2"
channelLabel Channel
ChRadius = Text
"radius"
channelLabel Channel
ChRadius2 = Text
"radius2"
channelLabel Channel
ChColor = Text
"color"
channelLabel Channel
ChFill = Text
"fill"
channelLabel Channel
ChFillOpacity = Text
"fillOpacity"
channelLabel Channel
ChHref = Text
"href"
channelLabel Channel
ChKey = Text
"key"
channelLabel Channel
ChOpacity = Text
"opacity"
channelLabel Channel
ChShape = Text
"shape"
channelLabel Channel
ChSize = Text
"size"
channelLabel Channel
ChStroke = Text
"stroke"
channelLabel Channel
ChStrokeDash = Text
"strokeDash"
channelLabel Channel
ChStrokeOpacity = Text
"strokeOpacity"
channelLabel Channel
ChStrokeWidth = Text
"strokeWidth"
channelLabel Channel
ChText = Text
"text"
channelLabel Channel
ChDescription = Text
"description"
channelLabel Channel
ChURL = Text
"url"

{-|

Indicates whether or not a scale domain should be independent of others in a
composite visualization. See the
<https://vega.github.io/vega-lite/docs/resolve.html Vega-Lite documentation> for
details.

For use with 'Resolve'.

-}
data Resolution
    = Shared
    | Independent


resolutionLabel :: Resolution -> T.Text
resolutionLabel :: Resolution -> Text
resolutionLabel Resolution
Shared = Text
"shared"
resolutionLabel Resolution
Independent = Text
"independent"


{-|

Used to determine how a channel's axis, scale or legend domains should be resolved
if defined in more than one view in a composite visualization. See the
<https://vega.github.io/vega-lite/docs/resolve.html Vega-Lite documentation>
for details.
-}
data Resolve
    = RAxis [(Channel, Resolution)]
    | RLegend [(Channel, Resolution)]
    | RScale [(Channel, Resolution)]


resolveProperty :: Resolve -> ResolveSpec
resolveProperty :: Resolve -> ResolveSpec
resolveProperty Resolve
res =
  let (Text
nme, [(Channel, Resolution)]
rls) = case Resolve
res of
        RAxis [(Channel, Resolution)]
chRules -> (Text
"axis", [(Channel, Resolution)]
chRules)
        RLegend [(Channel, Resolution)]
chRules -> (Text
"legend", [(Channel, Resolution)]
chRules)
        RScale [(Channel, Resolution)]
chRules -> (Text
"scale", [(Channel, Resolution)]
chRules)

      ans :: [(Text, Value)]
ans = ((Channel, Resolution) -> (Text, Value))
-> [(Channel, Resolution)] -> [(Text, Value)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Channel
ch, Resolution
rule) -> Channel -> Text
channelLabel Channel
ch Text -> Text -> (Text, Value)
forall a. ToJSON a => Text -> a -> (Text, Value)
.=~ Resolution -> Text
resolutionLabel Resolution
rule) [(Channel, Resolution)]
rls
  in (Text, Value) -> ResolveSpec
RS (Text
nme, [(Text, Value)] -> Value
toObject [(Text, Value)]
ans)


-- | This is used with 'Graphics.Vega.VegaLite.bounds' to define the extent of a sub plot.
--
--   @since 0.4.0.0

data Bounds
  = Full
    -- ^ Bounds calculation should use the entire plot area (including axes, title,
    --   and legend).
  | Flush
    -- ^ Bounds calculation should take only the specified width and height values for
    --   a sub-view. Useful when attempting to place sub-plots without axes or legends into
    --   a uniform grid structure.


boundsSpec :: Bounds -> VLSpec
boundsSpec :: Bounds -> Value
boundsSpec Bounds
Full = Value
"full"
boundsSpec Bounds
Flush = Value
"flush"


-- | Specifies the alignment of compositions. It is used with:
--   'Graphics.Vega.VegaLite.align', 'Graphics.Vega.VegaLite.alignRC',
--   'Graphics.Vega.VegaLite.LeGridAlign', 'Graphics.Vega.VegaLite.LGridAlign',
--   and 'Graphics.Vega.VegaLite.FAlign'.
--
--   @since 0.4.0.0

data CompositionAlignment
    = CANone
    -- ^ Flow layout is used, where adjacent subviews are placed one after
    --   another.
    | CAEach
    -- ^ Each row and column may be of a variable size.
    | CAAll
    -- ^ All the rows and columns are of the same size (this is based on the
    --   maximum subview size).


compositionAlignmentSpec :: CompositionAlignment -> VLSpec
compositionAlignmentSpec :: CompositionAlignment -> Value
compositionAlignmentSpec CompositionAlignment
CANone = Value
"none"
compositionAlignmentSpec CompositionAlignment
CAEach = Value
"each"
compositionAlignmentSpec CompositionAlignment
CAAll = Value
"all"


-- | Specify the padding dimensions in pixel units.

data Padding
    = PSize Double
      -- ^ Use the same padding on all four edges of the container.
    | PEdges Double Double Double Double
      -- ^ Specify the padding for the left, top, right, and bottom edges.


paddingSpec :: Padding -> VLSpec
paddingSpec :: Padding -> Value
paddingSpec (PSize Double
p) = Double -> Value
forall a. ToJSON a => a -> Value
toJSON Double
p
paddingSpec (PEdges Double
l Double
t Double
r Double
b) =
  [Pair] -> Value
object [ Key
"left" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
l
         , Key
"top" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
t
         , Key
"right" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
r
         , Key
"bottom" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
b
         ]


{-|

Indicates the auto-sizing characteristics of the visualization such as amount
of padding, whether it should fill the parent container etc. For more details see the
<https://vega.github.io/vega-lite/docs/size.html#autosize Vega-Lite documentation>.

-}

data Autosize
    = AContent
      -- ^ Interpret visualization dimensions to be for the data rectangle (external
      --   padding added to this size).
    | AFit
      -- ^ Interpret visualization dimensions to be for the entire visualization (data
      --   rectangle is shrunk to accommodate external decorations padding).
    | AFitX
      -- ^ Interpret visualization width to be for the entire visualization width (data
      --   rectangle width is shrunk to accommodate external decorations padding).
      --
      --   @since 0.5.0.0
    | AFitY
      -- ^ Interpret visualization height to be for the entire visualization height (data
      --   rectangle height is shrunk to accommodate external decorations padding).
      --
      --   @since 0.5.0.0
    | ANone
      -- ^ No autosizing is applied.
    | APad
      -- ^ Automatically expand size of visualization from the given dimensions in order
      --   to fit in all supplementary decorations (legends etc.).
    | APadding
      -- ^ Interpret visualization width to be for the entire visualization (data
      -- rectangle is shrunk to accommodate external padding).
    | AResize
      -- ^ Recalculate autosizing on every view update.


autosizeProperty :: Autosize -> Pair
autosizeProperty :: Autosize -> Pair
autosizeProperty Autosize
APad = Key
"type" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromT Text
"pad"
autosizeProperty Autosize
AFit = Key
"type" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromT Text
"fit"
autosizeProperty Autosize
AFitX = Key
"type" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromT Text
"fit-x"
autosizeProperty Autosize
AFitY = Key
"type" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromT Text
"fit-y"
autosizeProperty Autosize
ANone = Key
"type" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromT Text
"none"
autosizeProperty Autosize
AResize = Key
"resize" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
True
autosizeProperty Autosize
AContent = Key
"contains" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromT Text
"content"
autosizeProperty Autosize
APadding = Key
"contains" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromT Text
"padding"


{-|

Create a list of fields to use in set of repeated small multiples. The list of
fields named here can be referenced in an encoding with @'Graphics.Vega.VegaLite.PRepeat' 'Graphics.Vega.VegaLite.Column'@
or @'Graphics.Vega.VegaLite.PRepeat' 'Graphics.Vega.VegaLite.Row'@.

-}
data RepeatFields
    = RowFields [FieldName]
    | ColumnFields [FieldName]
    | LayerFields [FieldName]
      -- ^ @since 0.9.0.0

repeatFieldsProperty :: RepeatFields -> Pair
repeatFieldsProperty :: RepeatFields -> Pair
repeatFieldsProperty (RowFields [Text]
fs) = Key
"row" Key -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
fs
repeatFieldsProperty (ColumnFields [Text]
fs) = Key
"column" Key -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
fs
repeatFieldsProperty (LayerFields [Text]
fs) = Key
"layer" Key -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
fs

{-|

Indicates the type of color interpolation to apply, when mapping a data field
onto a color scale.

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

-}
data CInterpolate
    = CubeHelix Double
      -- ^ Cube helix color interpolation for continuous color scales using the given
      --   gamma value (anchored at 1).
    | CubeHelixLong Double
      -- ^ Long-path cube helix color interpolation for continuous color scales using
      --   the given gamma value (anchored at 1).
    | Hcl
      -- ^ HCL color interpolation for continuous color scales.
    | HclLong
      -- ^ HCL color interpolation in polar coordinate space for continuous color scales.
    | Hsl
      -- ^ HSL color interpolation for continuous color scales.
    | HslLong
      -- ^ HSL color interpolation in polar coordinate space for continuous color scales.
    | Lab
      -- ^ Lab color interpolation for continuous color scales.
    | Rgb Double
      -- ^ RGB color interpolation for continuous color scales using the given gamma
      --   value (anchored at 1).


-- Need to tie down some types as things are too polymorphic,
-- particularly in the presence of OverloadedStrings.
--
#if MIN_VERSION_aeson(2, 0, 0)
pairT :: Key.Key -> T.Text -> Pair
pairT :: Key -> Text -> Pair
pairT Key
a Text
b = Key
a Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
b
#else
pairT :: T.Text -> T.Text -> Pair
pairT a b = a .= b
#endif


cInterpolateSpec :: CInterpolate -> VLSpec
cInterpolateSpec :: CInterpolate -> Value
cInterpolateSpec (Rgb Double
gamma) = [Pair] -> Value
object [Key -> Text -> Pair
pairT Key
"type" Text
"rgb", Key
"gamma" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
gamma]
cInterpolateSpec CInterpolate
Hsl = [Pair] -> Value
object [Key -> Text -> Pair
pairT Key
"type" Text
"hsl"]
cInterpolateSpec CInterpolate
HslLong = [Pair] -> Value
object [Key -> Text -> Pair
pairT Key
"type" Text
"hsl-long"]
cInterpolateSpec CInterpolate
Lab = [Pair] -> Value
object [Key -> Text -> Pair
pairT Key
"type" Text
"lab"]
cInterpolateSpec CInterpolate
Hcl = [Pair] -> Value
object [Key -> Text -> Pair
pairT Key
"type" Text
"hcl"]
cInterpolateSpec CInterpolate
HclLong = [Pair] -> Value
object [Key -> Text -> Pair
pairT Key
"type" Text
"hcl-long"]
cInterpolateSpec (CubeHelix Double
gamma) = [Pair] -> Value
object [Key -> Text -> Pair
pairT Key
"type" Text
"cubehelix", Key
"gamma" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
gamma]
cInterpolateSpec (CubeHelixLong Double
gamma) = [Pair] -> Value
object [Key -> Text -> Pair
pairT Key
"type" Text
"cubehelix-long", Key
"gamma" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
gamma]


{-| The properties for a single view or layer background.

Used with 'Graphics.Vega.VegaLite.viewBackground' and
'Graphics.Vega.VegaLite.ViewBackgroundStyle'.

In version @0.6.0.0@ the constructors that used to take an optional color,
namely 'VBFill' and 'VBStroke', were split out, so that they
now take a 'Color' argument and new constructors - 'VBNoFill' and
'VBNoStroke' - were added to replace the @Nothing@ versions.

@since 0.4.0.0

-}

data ViewBackground
    = VBStyle [StyleLabel]
    -- ^ A list of named styles to apply. A named style can be specified
    --   via 'Graphics.Vega.VegaLite.MarkNamedStyles'. Later styles in the list will
    --   override earlier ones if there is a conflict in any of the mark
    --   properties.
    | VBCornerRadius Double
    -- ^ The radius in pixels of rounded corners.
    | VBFill Color
    -- ^ Fill color. See also 'VBNoFill'.
    --
    --   This was changed to use the @Color@ type alias in version @0.5.0.0@
    --   and removed the @Maybe@ type in version @0.6.0.0@.
    | VBNoFill
    -- ^ Do not use a fill. See also 'VBFill'.
    --
    --   @since 0.6.0.0
    | VBFillOpacity Opacity
    -- ^ Fill opacity.
    | VBOpacity Opacity
    -- ^ Overall opacity.
    | VBStroke Color
    -- ^ The stroke color for a line around the background. See also 'VBNoStroke'.
    --
    --   This was changed to use the @Color@ type alias in version @0.5.0.0@
    --   and removed the @Maybe@ type in version @0.6.0.0@.
    | VBNoStroke
    -- ^ Do not use a stroke. See also 'VBStroke'.
    --
    --   @since 0.6.0.0
    | VBStrokeOpacity Opacity
    -- ^ The opacity of the line around the background, if drawn.
    | VBStrokeWidth Double
    -- ^ The width of the line around the background, if drawn.
    | VBStrokeCap StrokeCap
    -- ^ The cap line-ending for the line around the background, if drawn.
    | VBStrokeDash DashStyle
    -- ^ The dash pattern of the line around the background, if drawn.
    | VBStrokeDashOffset DashOffset
    -- ^ The offset of the dash pattern for the line around the background, if drawn.
    | VBStrokeJoin StrokeJoin
    -- ^ The line-joining style of the line around the background, if drawn.
    | VBStrokeMiterLimit Double
    -- ^ The mitre limit at which to bevel the line around the background, if drawn.


viewBackgroundSpec :: ViewBackground -> Pair
viewBackgroundSpec :: ViewBackground -> Pair
viewBackgroundSpec (VBStyle [Text
style]) = Key
"style" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
style  -- special case singleton
viewBackgroundSpec (VBStyle [Text]
styles) = Key
"style" Key -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
styles
viewBackgroundSpec (VBCornerRadius Double
r) = Key
"cornerRadius" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
r
viewBackgroundSpec (VBFill Text
s) = Key
"fill" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
viewBackgroundSpec ViewBackground
VBNoFill = Key
"fill" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Value
A.Null
viewBackgroundSpec (VBFillOpacity Double
x) = Key
"fillOpacity" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBOpacity Double
x) = Key
"opacity" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBStroke Text
s) = Key
"stroke" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
viewBackgroundSpec ViewBackground
VBNoStroke = Key
"stroke" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Value
A.Null
viewBackgroundSpec (VBStrokeOpacity Double
x) = Key
"strokeOpacity" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBStrokeCap StrokeCap
cap) = Key
"strokeCap" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrokeCap -> Text
strokeCapLabel StrokeCap
cap
viewBackgroundSpec (VBStrokeJoin StrokeJoin
jn) = Key
"strokeJoin" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrokeJoin -> Text
strokeJoinLabel StrokeJoin
jn
viewBackgroundSpec (VBStrokeWidth Double
x) = Key
"strokeWidth" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBStrokeDash DashStyle
xs) = Key
"strokeDash" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DashStyle -> Value
fromDS DashStyle
xs
viewBackgroundSpec (VBStrokeDashOffset Double
x) = Key
"strokeDashOffset" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
viewBackgroundSpec (VBStrokeMiterLimit Double
x) = Key
"strokeMiterLimit" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x


{-|

Represents a facet header property. For details, see the
<https://vega.github.io/vega-lite/docs/facet.html#header Vega-Lite documentation>.

Labels refer to the title of each sub-plot in a faceted view and
title is the overall title of the collection.

-}

{-
In 4.2.0 this represents both

  HeaderConfig
  Header

which have the same keys.

-}

data HeaderProperty
    = HFormat T.Text
      -- ^ [Formatting pattern](https://vega.github.io/vega-lite/docs/format.html) for
      --   facet header (title) values. To distinguish between formatting as numeric values
      --   and data/time values, additionally use 'HFormatAsNum', 'HFormatAsTemporal',
      --   and 'HFormatAsCustom'.
    | HFormatAsNum
      -- ^ Facet headers should be formatted as numbers. Use a
      --   [d3 numeric format string](https://github.com/d3/d3-format#locale_format)
      --   with 'HFormat'.
      --
      --   @since 0.4.0.0
    | HFormatAsTemporal
      -- ^ 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 'HFormat'.
      --
      --   @since 0.4.0.0
    | HFormatAsCustom T.Text
      -- ^ The [custom format type](https://vega.github.io/vega-lite/docs/config.html#custom-format-type)
      --   for use with with 'HFormat'.
      --
      --   @since 0.9.0.0
    | HLabel Bool
      -- ^ Should labels be included as part of the header. The default is @True@.
      --
      --   @since 0.6.0.0
    | HLabelAlign HAlign
      -- ^ The horizontal alignment of the labels.
      --
      -- @since 0.4.0.0
    | HLabelAnchor APosition
      -- ^ The anchor position for the labels.
      --
      -- @since 0.4.0.0
    | HLabelAngle Angle
      -- ^ The angle to draw the labels. The default is 0 for column headers
      --   and -90 for row headers.
      --
      --   @since 0.4.0.0
    | HLabelBaseline VAlign
      -- ^ The vertical text baseline for header labels. The default is
      --   'AlignBaseline'.
      --
      --   Added in Vega-Lite 4.8.0.
      --
      --   @since 0.8.0.0
    | HLabelColor Color
      -- ^ The color of the labels.
      --
      -- @since 0.4.0.0
    | HLabelExpr VegaExpr
      -- ^ The expression used to generate header labels.
      --
      --   The expression can use @datum.value@ and @datum.label@ to access
      --   the data value and default label text respectively.
      --
      --   @since 0.6.0.0
    | HLabelFont T.Text
      -- ^ The font for the labels.
      --
      -- @since 0.4.0.0
    | HLabelFontSize Double
      -- ^ The font size for the labels.
      --
      -- @since 0.4.0.0
    | HLabelFontStyle T.Text
      -- ^ The font style for the labels.
      --
      --   @since 0.6.0.0
    | HLabelFontWeight FontWeight
      -- ^ The font weight for the header label.
      --
      --   Added in Vega-Lite 4.8.0.
      --
      --   @since 0.8.0.0
    | HLabelLimit Double
      -- ^ The maximum length of each label.
      --
      -- @since 0.4.0.0
    | HLabelLineHeight Double
      -- ^ The line height, in pixels, for multi-line header labels, or
      --   title text with baselines of 'AlignLineTop' or 'AlignLineBottom'.
      --
      --   Added in Vega-Lite 4.8.0.
      --
      --   @since 0.8.0.0
    | HLabelOrient Side
      -- ^ The position of the label relative to its sub-plot. See also
      --   'HOrient'.
      --
      -- @since 0.4.0.0
    | HLabelPadding Double
      -- ^ The spacing in pixels between the label and its sub-plot.
      --
      -- @since 0.4.0.0
    | HOrient Side
      -- ^ A shortcut for setting both 'HLabelOrient' and 'HTitleOrient'.
      --
      --   Since Vega-Lite 4.8.
      --
      --   @since 0.8.0.0
    | HTitle T.Text
      -- ^ The title for the facets.
    | HNoTitle
      -- ^ Draw no title for the facets.
      --
      -- @since 0.4.0.0
    | HTitleAlign HAlign
      -- ^ The horizontal alignment of the title.
      --
      -- @since 0.4.0.0
    | HTitleAnchor APosition
      -- ^ The anchor position for the title.
      --
      -- @since 0.4.0.0
    | HTitleAngle Angle
      -- ^ The angle to draw the title.
      --
      -- @since 0.4.0.0
    | HTitleBaseline VAlign
      -- ^ The vertical alignment of the title.
      --
      -- @since 0.4.0.0
    | HTitleColor Color
      -- ^ The color of the title.
      --
      -- @since 0.4.0.0
    | HTitleFont T.Text
      -- ^ The font for the title.
      --
      -- @since 0.4.0.0
    | HTitleFontSize Double
      -- ^ The font size for the title.
      --
      -- @since 0.4.0.0
    | HTitleFontStyle T.Text
      -- ^ The font style for the title.
      --
      --   @since 0.6.0.0
    | HTitleFontWeight FontWeight
      -- ^ The font weight for the title.
      --
      --   The argument changed from 'T.Text' in @0.8.0.0@.
      --
      --   @since 0.4.0.0
    | HTitleLimit Double
      -- ^ The maximum length of the title.
      --
      -- @since 0.4.0.0
    | HTitleLineHeight Double
      -- ^ The line height, in pixels, for multi-line header title text, or
      --   title text with baselines of 'AlignLineTop' or 'AlignLineBottom'.
      --
      --   @since 0.6.0.0
    | HTitleOrient Side
      -- ^ The position of the title relative to the sub-plots. See also 'HOrient'.
      --
      -- @since 0.4.0.0
    | HTitlePadding Double
      -- ^ The spacing in pixels between the title and the labels.
      --
      -- @since 0.4.0.0


headerProperty :: HeaderProperty -> Pair
headerProperty :: HeaderProperty -> Pair
headerProperty (HFormat Text
fmt) = Key
"format" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
fmt
headerProperty HeaderProperty
HFormatAsNum = Key
"formatType" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromT Text
"number"
headerProperty HeaderProperty
HFormatAsTemporal = Key
"formatType" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromT Text
"time"
headerProperty (HFormatAsCustom Text
c) = Key
"formatType" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
c
headerProperty (HTitle Text
ttl) = Key
"title" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
splitOnNewline Text
ttl
headerProperty HeaderProperty
HNoTitle = Key
"title" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Value
A.Null
headerProperty (HLabel Bool
b) = Key
"labels" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
b
headerProperty (HLabelAlign HAlign
ha) = Key
"labelAlign" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HAlign -> Text
hAlignLabel HAlign
ha
headerProperty (HLabelAnchor APosition
a) = Key
"labelAnchor" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= APosition -> Text
anchorLabel APosition
a
headerProperty (HLabelAngle Double
x) = Key
"labelAngle" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HLabelBaseline VAlign
va) = Key
"labelBaseline" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VAlign -> Text
vAlignLabel VAlign
va
headerProperty (HLabelColor Text
s) = Key
"labelColor" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromColor Text
s
headerProperty (HLabelExpr Text
s) = Key
"labelExpr" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HLabelFont Text
s) = Key
"labelFont" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HLabelFontSize Double
x) = Key
"labelFontSize" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HLabelFontStyle Text
s) = Key
"labelFontStyle" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HLabelFontWeight FontWeight
w) = Key
"labelFontWeight" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FontWeight -> Value
fontWeightSpec FontWeight
w
headerProperty (HLabelLimit Double
x) = Key
"labelLimit" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HLabelLineHeight Double
x) = Key
"labelLineHeight" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HLabelOrient Side
orient) = Key
"labelOrient" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Side -> Text
sideLabel Side
orient
headerProperty (HLabelPadding Double
x) = Key
"labelPadding" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HOrient Side
orient) = Key
"orient" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Side -> Text
sideLabel Side
orient
headerProperty (HTitleAlign HAlign
ha) = Key
"titleAlign" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HAlign -> Text
hAlignLabel HAlign
ha
headerProperty (HTitleAnchor APosition
a) = Key
"titleAnchor" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= APosition -> Text
anchorLabel APosition
a
headerProperty (HTitleAngle Double
x) = Key
"titleAngle" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HTitleBaseline VAlign
va) = Key
"titleBaseline" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VAlign -> Text
vAlignLabel VAlign
va
headerProperty (HTitleColor Text
s) = Key
"titleColor" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
fromColor Text
s
headerProperty (HTitleFont Text
s) = Key
"titleFont" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HTitleFontWeight FontWeight
fw) = Key
"titleFontWeight" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FontWeight -> Value
fontWeightSpec FontWeight
fw
headerProperty (HTitleFontSize Double
x) = Key
"titleFontSize" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HTitleFontStyle Text
s) = Key
"titleFontStyle" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
s
headerProperty (HTitleLimit Double
x) = Key
"titleLimit" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HTitleLineHeight Double
x) = Key
"titleLineHeight" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x
headerProperty (HTitleOrient Side
orient) = Key
"titleOrient" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Side -> Text
sideLabel Side
orient
headerProperty (HTitlePadding Double
x) = Key
"titlePadding" Key -> Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Double
x