{-# LANGUAGE OverloadedStrings #-}
module Eventlog.VegaTemplate
(
AreaChartType(..)
, ChartConfig(..)
, ChartType(..)
, vegaResult
, vegaJson
, vegaJsonText
) where
import Prelude hiding (filter, lookup)
import Graphics.Vega.VegaLite as VL
import Data.Aeson.Types hiding (Number)
import Data.Text (Text)
import Data.Aeson.Text (encodeToLazyText)
import Data.Text.Lazy (toStrict)
data AreaChartType
= Stacked
| Normalized
| StreamGraph
data ChartType
= AreaChart AreaChartType
| LineChart
| HeapChart
data ChartConfig =
ChartConfig { ChartConfig -> Double
cwidth :: Double
, ChartConfig -> Double
cheight :: Double
, ChartConfig -> Bool
traces :: Bool
, ChartConfig -> Text
colourScheme :: Text
, ChartConfig -> Text
lineColourScheme :: Text
, ChartConfig -> ChartType
chartType :: ChartType
, ChartConfig -> Maybe Double
fixedYAxisExtent :: Maybe Double
}
colourProperty :: ChartConfig -> ScaleProperty
colourProperty :: ChartConfig -> ScaleProperty
colourProperty ChartConfig
c = Text -> [Double] -> ScaleProperty
SScheme (ChartConfig -> Text
colourScheme ChartConfig
c) []
lineColourProperty :: ChartConfig -> ScaleProperty
lineColourProperty :: ChartConfig -> ScaleProperty
lineColourProperty ChartConfig
c = Text -> [Double] -> ScaleProperty
SScheme (ChartConfig -> Text
lineColourScheme ChartConfig
c) []
vegaJson :: ChartConfig -> Value
vegaJson :: ChartConfig -> Value
vegaJson ChartConfig
conf = VegaLite -> Value
fromVL (ChartConfig -> VegaLite
vegaResult ChartConfig
conf)
vegaJsonText :: ChartConfig -> Text
vegaJsonText :: ChartConfig -> Text
vegaJsonText ChartConfig
conf = Text -> Text
toStrict (Value -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText (ChartConfig -> Value
vegaJson ChartConfig
conf))
vegaResult :: ChartConfig -> VegaLite
vegaResult :: ChartConfig -> VegaLite
vegaResult ChartConfig
conf = [PropertySpec] -> VegaLite
toVegaLite ([PropertySpec] -> VegaLite) -> [PropertySpec] -> VegaLite
forall a b. (a -> b) -> a -> b
$
let c' :: ChartConfig
c' = ChartConfig
conf { cwidth :: Double
cwidth = ChartConfig -> Double
cwidth ChartConfig
conf Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
130 }
in
[
Double -> PropertySpec
VL.width (ChartConfig -> Double
cwidth ChartConfig
conf),
Double -> PropertySpec
VL.height (ChartConfig -> Double
cheight ChartConfig
conf),
[ConfigureSpec] -> PropertySpec
config [],
Text -> PropertySpec
description Text
"Heap Profile",
case ChartConfig -> ChartType
chartType ChartConfig
conf of
ChartType
LineChart -> ChartConfig -> PropertySpec
lineChartFull ChartConfig
c'
ChartType
HeapChart -> ChartConfig -> PropertySpec
heapChartFull ChartConfig
c'
AreaChart AreaChartType
ct -> AreaChartType -> ChartConfig -> PropertySpec
areaChartFull AreaChartType
ct ChartConfig
c'
]
areaChartFull :: AreaChartType -> ChartConfig -> (VLProperty, VLSpec)
areaChartFull :: AreaChartType -> ChartConfig -> PropertySpec
areaChartFull AreaChartType
ct ChartConfig
c = [Value] -> PropertySpec
vConcat [AreaChartType -> ChartConfig -> Value
areaChart AreaChartType
ct ChartConfig
c, ChartConfig -> Value
selectionChart ChartConfig
c]
lineChartFull :: ChartConfig -> (VLProperty, VLSpec)
lineChartFull :: ChartConfig -> PropertySpec
lineChartFull ChartConfig
c = [Value] -> PropertySpec
vConcat [ChartConfig -> Value
lineChart ChartConfig
c, ChartConfig -> Value
selectionChart ChartConfig
c]
heapChartFull :: ChartConfig -> (VLProperty, VLSpec)
heapChartFull :: ChartConfig -> PropertySpec
heapChartFull ChartConfig
c = [Value] -> PropertySpec
vConcat [ChartConfig -> Value
heapChart ChartConfig
c, ChartConfig -> Value
selectionHeapChart ChartConfig
c]
config :: [ConfigureSpec] -> (VLProperty, VLSpec)
config :: [ConfigureSpec] -> PropertySpec
config =
[ConfigureSpec] -> PropertySpec
configure
([ConfigureSpec] -> PropertySpec)
-> ([ConfigureSpec] -> [ConfigureSpec])
-> [ConfigureSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfigurationProperty -> [ConfigureSpec] -> [ConfigureSpec]
configuration ([MarkProperty] -> ConfigurationProperty
TextStyle [(HAlign -> MarkProperty
MAlign HAlign
AlignRight), (Double -> MarkProperty
MdX (-Double
5)), (Double -> MarkProperty
MdY Double
5)])
lineChart :: ChartConfig -> VLSpec
lineChart :: ChartConfig -> Value
lineChart ChartConfig
c = [PropertySpec] -> Value
asSpec [[Value] -> PropertySpec
layer ([ChartConfig -> Value
linesLayer ChartConfig
c] [Value] -> [Value] -> [Value]
forall a. [a] -> [a] -> [a]
++ [Value
tracesLayer | ChartConfig -> Bool
traces ChartConfig
c])]
linesLayer :: ChartConfig -> VLSpec
linesLayer :: ChartConfig -> Value
linesLayer ChartConfig
c = [PropertySpec] -> Value
asSpec
[
Double -> PropertySpec
VL.width (Double
0.9 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cwidth ChartConfig
c),
Double -> PropertySpec
VL.height (Double
0.7 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cheight ChartConfig
c),
Text -> [Format] -> PropertySpec
dataFromSource Text
"data_json_samples" [],
Mark -> [MarkProperty] -> PropertySpec
VL.mark Mark
Line [PointMarker -> MarkProperty
MPoint ([MarkProperty] -> PointMarker
PMMarker [])],
ChartConfig -> [EncodingSpec] -> PropertySpec
encodingLineLayer ChartConfig
c [],
[TransformSpec] -> PropertySpec
transformLineLayer [],
[SelectSpec] -> PropertySpec
selectionRight []
]
encodingLineLayer :: ChartConfig -> [EncodingSpec] -> (VLProperty, VLSpec)
encodingLineLayer :: ChartConfig -> [EncodingSpec] -> PropertySpec
encodingLineLayer ChartConfig
c
= [EncodingSpec] -> PropertySpec
encoding
([EncodingSpec] -> PropertySpec)
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [MarkChannel] -> [EncodingSpec] -> [EncodingSpec]
color [Text -> MarkChannel
MName Text
"c", Measurement -> MarkChannel
MmType Measurement
Nominal, [ScaleProperty] -> MarkChannel
MScale [ChartConfig -> ScaleProperty
colourProperty ChartConfig
c]
, [SortProperty] -> MarkChannel
MSort [Text -> Operation -> SortProperty
ByFieldOp Text
"k" Operation
Max, SortProperty
Descending]
, [LegendProperty] -> MarkChannel
MLegend [LegendProperty
LNoTitle]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
X [Text -> PositionChannel
PName Text
"x", Measurement -> PositionChannel
PmType Measurement
Quantitative, [AxisProperty] -> PositionChannel
PAxis [Text -> AxisProperty
AxTitle Text
""]
,[ScaleProperty] -> PositionChannel
PScale [ScaleDomain -> ScaleProperty
SDomainOpt (Text -> ScaleDomain
DSelection Text
"brush")]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
Y [Text -> PositionChannel
PName Text
"norm_y", Measurement -> PositionChannel
PmType Measurement
Quantitative, [AxisProperty] -> PositionChannel
PAxis [Text -> AxisProperty
AxTitle Text
"Allocation", Text -> AxisProperty
AxFormat Text
".1f"]]
transformLineLayer :: [TransformSpec] -> (VLProperty, VLSpec)
transformLineLayer :: [TransformSpec] -> PropertySpec
transformLineLayer =
[TransformSpec] -> PropertySpec
transform
([TransformSpec] -> PropertySpec)
-> ([TransformSpec] -> [TransformSpec])
-> [TransformSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [([Window], Text)]
-> [WindowProperty] -> [TransformSpec] -> [TransformSpec]
window [([Text -> Window
WField Text
"y", Operation -> Window
WAggregateOp Operation
Max], Text
"max_y")] [Maybe Int -> Maybe Int -> WindowProperty
WFrame Maybe Int
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing, [Text] -> WindowProperty
WGroupBy [Text
"k"]]
([TransformSpec] -> [TransformSpec])
-> ([TransformSpec] -> [TransformSpec])
-> [TransformSpec]
-> [TransformSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [TransformSpec] -> [TransformSpec]
calculateAs Text
"datum.y / datum.max_y" Text
"norm_y"
([TransformSpec] -> [TransformSpec])
-> ([TransformSpec] -> [TransformSpec])
-> [TransformSpec]
-> [TransformSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Filter -> [TransformSpec] -> [TransformSpec]
filter (Text -> Filter
FSelection Text
"legend")
heapChart :: ChartConfig -> VLSpec
heapChart :: ChartConfig -> Value
heapChart ChartConfig
c = [PropertySpec] -> Value
asSpec [[Value] -> PropertySpec
layer ([ChartConfig -> Value
heapLayer ChartConfig
c] [Value] -> [Value] -> [Value]
forall a. [a] -> [a] -> [a]
++ [Value
tracesLayer | ChartConfig -> Bool
traces ChartConfig
c])]
heapLayer :: ChartConfig -> VLSpec
heapLayer :: ChartConfig -> Value
heapLayer ChartConfig
c = [PropertySpec] -> Value
asSpec
[
Double -> PropertySpec
VL.width (Double
0.9 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cwidth ChartConfig
c),
Double -> PropertySpec
VL.height (Double
0.7 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cheight ChartConfig
c),
Text -> [Format] -> PropertySpec
dataFromSource Text
"data_json_heap" [],
Mark -> [MarkProperty] -> PropertySpec
VL.mark Mark
Line [PointMarker -> MarkProperty
MPoint ([MarkProperty] -> PointMarker
PMMarker [])],
ChartConfig -> [EncodingSpec] -> PropertySpec
encodingHeapLayer ChartConfig
c [],
[TransformSpec] -> PropertySpec
transformHeapLayer [],
[SelectSpec] -> PropertySpec
selectionRight []
]
transformHeapLayer :: [TransformSpec] -> (VLProperty, VLSpec)
transformHeapLayer :: [TransformSpec] -> PropertySpec
transformHeapLayer =
[TransformSpec] -> PropertySpec
transform
([TransformSpec] -> PropertySpec)
-> ([TransformSpec] -> [TransformSpec])
-> [TransformSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Filter -> [TransformSpec] -> [TransformSpec]
filter (Text -> Filter
FSelection Text
"legend")
encodingHeapLayer :: ChartConfig -> [EncodingSpec] -> (VLProperty, VLSpec)
encodingHeapLayer :: ChartConfig -> [EncodingSpec] -> PropertySpec
encodingHeapLayer ChartConfig
c
= [EncodingSpec] -> PropertySpec
encoding
([EncodingSpec] -> PropertySpec)
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [MarkChannel] -> [EncodingSpec] -> [EncodingSpec]
color [Text -> MarkChannel
MName Text
"c", Measurement -> MarkChannel
MmType Measurement
Nominal, [ScaleProperty] -> MarkChannel
MScale [ChartConfig -> ScaleProperty
lineColourProperty ChartConfig
c]
, [LegendProperty] -> MarkChannel
MLegend [LegendProperty
LNoTitle]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
X [Text -> PositionChannel
PName Text
"x", Measurement -> PositionChannel
PmType Measurement
Quantitative, [AxisProperty] -> PositionChannel
PAxis [Text -> AxisProperty
AxTitle Text
""]
,[ScaleProperty] -> PositionChannel
PScale [ScaleDomain -> ScaleProperty
SDomainOpt (Text -> ScaleDomain
DSelection Text
"brush")]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
Y [Text -> PositionChannel
PName Text
"y", Measurement -> PositionChannel
PmType Measurement
Quantitative
, [AxisProperty] -> PositionChannel
PAxis [Text -> AxisProperty
AxTitle Text
"Allocation", Text -> AxisProperty
AxFormat Text
"s"]
, [SortProperty] -> PositionChannel
PSort [Text -> Operation -> SortProperty
ByFieldOp Text
"k" Operation
Max]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TextChannel] -> [EncodingSpec] -> [EncodingSpec]
tooltip [Text -> TextChannel
TName Text
"y", Measurement -> TextChannel
TmType Measurement
Quantitative, Text -> TextChannel
TFormat Text
"s" ]
encodingSelection :: ChartConfig -> [EncodingSpec] -> (VLProperty, VLSpec)
encodingSelection :: ChartConfig -> [EncodingSpec] -> PropertySpec
encodingSelection ChartConfig
c =
[EncodingSpec] -> PropertySpec
encoding
([EncodingSpec] -> PropertySpec)
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [OrderChannel] -> [EncodingSpec] -> [EncodingSpec]
order [Text -> OrderChannel
OName Text
"k", Measurement -> OrderChannel
OmType Measurement
Quantitative]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TextChannel] -> [EncodingSpec] -> [EncodingSpec]
tooltip []
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [MarkChannel] -> [EncodingSpec] -> [EncodingSpec]
color [Text -> MarkChannel
MName Text
"c", Measurement -> MarkChannel
MmType Measurement
Nominal, [ScaleProperty] -> MarkChannel
MScale [ChartConfig -> ScaleProperty
colourProperty ChartConfig
c], [LegendProperty] -> MarkChannel
MLegend []
, [SortProperty] -> MarkChannel
MSort [Text -> Operation -> SortProperty
ByFieldOp Text
"k" Operation
Max, SortProperty
Descending]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
X [Text -> PositionChannel
PName Text
"x", Measurement -> PositionChannel
PmType Measurement
Quantitative, [AxisProperty] -> PositionChannel
PAxis [Text -> AxisProperty
AxTitle Text
"Time (s)"]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
Y [Text -> PositionChannel
PName Text
"y", Measurement -> PositionChannel
PmType Measurement
Quantitative, [AxisProperty] -> PositionChannel
PAxis [], Operation -> PositionChannel
PAggregate Operation
Sum, StackOffset -> PositionChannel
PStack StackOffset
StZero]
brush :: [SelectSpec] -> PropertySpec
brush :: [SelectSpec] -> PropertySpec
brush = [SelectSpec] -> PropertySpec
selection ([SelectSpec] -> PropertySpec)
-> ([SelectSpec] -> [SelectSpec]) -> [SelectSpec] -> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text
-> Selection -> [SelectionProperty] -> [SelectSpec] -> [SelectSpec]
select Text
"brush" Selection
Interval [Maybe (DataValue, DataValue)
-> Maybe (DataValue, DataValue) -> SelectionProperty
SInitInterval ((DataValue, DataValue) -> Maybe (DataValue, DataValue)
forall a. a -> Maybe a
Just (DataValue
NullValue, DataValue
NullValue)) Maybe (DataValue, DataValue)
forall a. Maybe a
Nothing]
selectionChart :: ChartConfig -> VLSpec
selectionChart :: ChartConfig -> Value
selectionChart ChartConfig
c = [PropertySpec] -> Value
asSpec [
Double -> PropertySpec
VL.width (Double
0.9 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cwidth ChartConfig
c),
Double -> PropertySpec
VL.height (Double
0.1 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cheight ChartConfig
c),
Text -> [Format] -> PropertySpec
dataFromSource Text
"data_json_samples" [],
Mark -> [MarkProperty] -> PropertySpec
VL.mark Mark
Area [],
ChartConfig -> [EncodingSpec] -> PropertySpec
encodingSelection ChartConfig
c [],
[SelectSpec] -> PropertySpec
brush []
]
encodingHeapSelection :: ChartConfig -> [EncodingSpec] -> (VLProperty, VLSpec)
encodingHeapSelection :: ChartConfig -> [EncodingSpec] -> PropertySpec
encodingHeapSelection ChartConfig
c =
[EncodingSpec] -> PropertySpec
encoding
([EncodingSpec] -> PropertySpec)
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TextChannel] -> [EncodingSpec] -> [EncodingSpec]
tooltip []
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [MarkChannel] -> [EncodingSpec] -> [EncodingSpec]
color [Text -> MarkChannel
MName Text
"c", Measurement -> MarkChannel
MmType Measurement
Nominal, [ScaleProperty] -> MarkChannel
MScale [ChartConfig -> ScaleProperty
lineColourProperty ChartConfig
c], [LegendProperty] -> MarkChannel
MLegend [LegendValues -> LegendProperty
LValues ([Text] -> LegendValues
LStrings [Text
"Heap Size", Text
"Blocks Size", Text
"Live Bytes"])]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
X [Text -> PositionChannel
PName Text
"x", Measurement -> PositionChannel
PmType Measurement
Quantitative, [AxisProperty] -> PositionChannel
PAxis [Text -> AxisProperty
AxTitle Text
"Time (s)"]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
Y [Text -> PositionChannel
PName Text
"y", Measurement -> PositionChannel
PmType Measurement
Quantitative, [AxisProperty] -> PositionChannel
PAxis [], [SortProperty] -> PositionChannel
PSort [Text -> Operation -> SortProperty
ByFieldOp Text
"k" Operation
Max]]
selectionHeapChart :: ChartConfig -> VLSpec
selectionHeapChart :: ChartConfig -> Value
selectionHeapChart ChartConfig
c = [PropertySpec] -> Value
asSpec [
Double -> PropertySpec
VL.width (Double
0.9 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cwidth ChartConfig
c),
Double -> PropertySpec
VL.height (Double
0.1 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cheight ChartConfig
c),
Text -> [Format] -> PropertySpec
dataFromSource Text
"data_json_heap" [],
Mark -> [MarkProperty] -> PropertySpec
VL.mark Mark
Line [PointMarker -> MarkProperty
MPoint ([MarkProperty] -> PointMarker
PMMarker [])],
ChartConfig -> [EncodingSpec] -> PropertySpec
encodingHeapSelection ChartConfig
c [],
[SelectSpec] -> PropertySpec
brush []
]
areaChart :: AreaChartType -> ChartConfig -> VLSpec
areaChart :: AreaChartType -> ChartConfig -> Value
areaChart AreaChartType
ct ChartConfig
c = [PropertySpec] -> Value
asSpec [[Value] -> PropertySpec
layer ([AreaChartType -> ChartConfig -> Value
bandsLayer AreaChartType
ct ChartConfig
c] [Value] -> [Value] -> [Value]
forall a. [a] -> [a] -> [a]
++ [Value
tracesLayer | ChartConfig -> Bool
traces ChartConfig
c])]
bandsLayer :: AreaChartType -> ChartConfig -> VLSpec
bandsLayer :: AreaChartType -> ChartConfig -> Value
bandsLayer AreaChartType
ct ChartConfig
c = [PropertySpec] -> Value
asSpec
[
Double -> PropertySpec
VL.width (Double
0.9 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cwidth ChartConfig
c),
Double -> PropertySpec
VL.height (Double
0.7 Double -> Double -> Double
forall a. Num a => a -> a -> a
* ChartConfig -> Double
cheight ChartConfig
c),
Text -> [Format] -> PropertySpec
dataFromSource Text
"data_json_samples" [],
Mark -> [MarkProperty] -> PropertySpec
VL.mark Mark
Area [],
AreaChartType -> ChartConfig -> [EncodingSpec] -> PropertySpec
encodingBandsLayer AreaChartType
ct ChartConfig
c [],
[TransformSpec] -> PropertySpec
transformBandsLayer [],
[SelectSpec] -> PropertySpec
selectionRight []
]
encodingBandsLayer :: AreaChartType
-> ChartConfig
-> [EncodingSpec]
-> (VLProperty, VLSpec)
encodingBandsLayer :: AreaChartType -> ChartConfig -> [EncodingSpec] -> PropertySpec
encodingBandsLayer AreaChartType
ct ChartConfig
c =
[EncodingSpec] -> PropertySpec
encoding
([EncodingSpec] -> PropertySpec)
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [OrderChannel] -> [EncodingSpec] -> [EncodingSpec]
order [Text -> OrderChannel
OName Text
"k", Measurement -> OrderChannel
OmType Measurement
Quantitative]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [MarkChannel] -> [EncodingSpec] -> [EncodingSpec]
color [Text -> MarkChannel
MName Text
"c", Measurement -> MarkChannel
MmType Measurement
Nominal, [ScaleProperty] -> MarkChannel
MScale [ChartConfig -> ScaleProperty
colourProperty ChartConfig
c]
, [SortProperty] -> MarkChannel
MSort [Text -> Operation -> SortProperty
ByFieldOp Text
"k" Operation
Max, SortProperty
Descending]
, [LegendProperty] -> MarkChannel
MLegend [LegendProperty
LNoTitle]
]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[TextChannel]] -> [EncodingSpec] -> [EncodingSpec]
tooltips
[ [Text -> TextChannel
TName Text
"y", Measurement -> TextChannel
TmType Measurement
Quantitative, Text -> TextChannel
TFormat Text
"s", Text -> TextChannel
TTitle Text
"Allocation"]
, [Text -> TextChannel
TName Text
"c", Measurement -> TextChannel
TmType Measurement
Nominal, Text -> TextChannel
TTitle Text
"Type"]
]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
X [Text -> PositionChannel
PName Text
"x", Measurement -> PositionChannel
PmType Measurement
Quantitative, [AxisProperty] -> PositionChannel
PAxis [Text -> AxisProperty
AxTitle Text
""]
, [ScaleProperty] -> PositionChannel
PScale [ScaleDomain -> ScaleProperty
SDomainOpt (Text -> ScaleDomain
DSelection Text
"brush")]]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
Y ([Text -> PositionChannel
PName Text
"y"
, Measurement -> PositionChannel
PmType Measurement
Quantitative
, [AxisProperty] -> PositionChannel
PAxis ([AxisProperty] -> PositionChannel)
-> [AxisProperty] -> PositionChannel
forall a b. (a -> b) -> a -> b
$ case AreaChartType
ct of
AreaChartType
Stacked -> [Text -> AxisProperty
AxTitle Text
"Allocation"
, Text -> AxisProperty
AxFormat Text
"s"
, Double -> AxisProperty
AxTitlePadding Double
15.0
, Double -> AxisProperty
AxMaxExtent Double
15.0]
AreaChartType
Normalized -> [Text -> AxisProperty
AxTitle Text
"Allocation (Normalized)", Text -> AxisProperty
AxFormat Text
"p"]
AreaChartType
StreamGraph -> [Text -> AxisProperty
AxTitle Text
"Allocation (Streamgraph)", Bool -> AxisProperty
AxLabels Bool
False, Bool -> AxisProperty
AxTicks Bool
False, Double -> AxisProperty
AxTitlePadding Double
10.0]
, Operation -> PositionChannel
PAggregate Operation
Sum
, StackOffset -> PositionChannel
PStack (case AreaChartType
ct of
AreaChartType
Stacked -> StackOffset
StZero
AreaChartType
Normalized -> StackOffset
StNormalize
AreaChartType
StreamGraph -> StackOffset
StCenter)]
[PositionChannel] -> [PositionChannel] -> [PositionChannel]
forall a. [a] -> [a] -> [a]
++
[[ScaleProperty] -> PositionChannel
PScale [DomainLimits -> ScaleProperty
SDomain ([Double] -> DomainLimits
DNumbers [Double
0, Double
extent])] | Just Double
extent <- [ChartConfig -> Maybe Double
fixedYAxisExtent ChartConfig
c]] )
transformBandsLayer :: [TransformSpec] -> (VLProperty, VLSpec)
transformBandsLayer :: [TransformSpec] -> PropertySpec
transformBandsLayer =
[TransformSpec] -> PropertySpec
transform
([TransformSpec] -> PropertySpec)
-> ([TransformSpec] -> [TransformSpec])
-> [TransformSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Filter -> [TransformSpec] -> [TransformSpec]
filter (Text -> Filter
FSelection Text
"legend")
tracesLayer :: VLSpec
tracesLayer :: Value
tracesLayer = [PropertySpec] -> Value
asSpec
[
Text -> [Format] -> PropertySpec
dataFromSource Text
"data_json_traces" [],
Mark -> [MarkProperty] -> PropertySpec
VL.mark Mark
Rule [],
[EncodingSpec] -> PropertySpec
encodingTracesLayer []
]
encodingTracesLayer :: [EncodingSpec] -> (VLProperty, VLSpec)
encodingTracesLayer :: [EncodingSpec] -> PropertySpec
encodingTracesLayer =
[EncodingSpec] -> PropertySpec
encoding
([EncodingSpec] -> PropertySpec)
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [MarkChannel] -> [EncodingSpec] -> [EncodingSpec]
color [Text -> MarkChannel
MString Text
"grey"]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> [PositionChannel] -> [EncodingSpec] -> [EncodingSpec]
position Position
X [Measurement -> PositionChannel
PmType Measurement
Quantitative, [AxisProperty] -> PositionChannel
PAxis [], Text -> PositionChannel
PName Text
"tx"
, [ScaleProperty] -> PositionChannel
PScale [ScaleDomain -> ScaleProperty
SDomainOpt (Text -> ScaleDomain
DSelection Text
"brush")] ]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [MarkChannel] -> [EncodingSpec] -> [EncodingSpec]
VL.size [Double -> MarkChannel
MNumber Double
2]
([EncodingSpec] -> [EncodingSpec])
-> ([EncodingSpec] -> [EncodingSpec])
-> [EncodingSpec]
-> [EncodingSpec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TextChannel] -> [EncodingSpec] -> [EncodingSpec]
tooltip [Text -> TextChannel
TName Text
"desc", Measurement -> TextChannel
TmType Measurement
Nominal]
selectionRight :: [SelectSpec] -> (VLProperty, VLSpec)
selectionRight :: [SelectSpec] -> PropertySpec
selectionRight =
[SelectSpec] -> PropertySpec
selection
([SelectSpec] -> PropertySpec)
-> ([SelectSpec] -> [SelectSpec]) -> [SelectSpec] -> PropertySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text
-> Selection -> [SelectionProperty] -> [SelectSpec] -> [SelectSpec]
select Text
"legend" Selection
Multi [BindLegendProperty -> SelectionProperty
BindLegend (Text -> BindLegendProperty
BLField Text
"c")]