{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Charts.Internal.Chart where
import qualified Data.Text as T
import Data.Aeson as A
data Column =
NumberColumn T.Text
| StringColumn T.Text
| BoolColumn T.Text
| DateColumn T.Text
| DateTimeColumn T.Text
| TimeOfDayColumn T.Text
| AnnotationColumn
| AnnotationTextColumn
| CertaintyColumn
| EmphasisColumn
| IntervalColumn
| ScopeColumn
| StyleColumn
| TooltipColumn
| DomainColumn
| DataColumn
deriving (Int -> Column -> ShowS
[Column] -> ShowS
Column -> String
(Int -> Column -> ShowS)
-> (Column -> String) -> ([Column] -> ShowS) -> Show Column
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Column] -> ShowS
$cshowList :: [Column] -> ShowS
show :: Column -> String
$cshow :: Column -> String
showsPrec :: Int -> Column -> ShowS
$cshowsPrec :: Int -> Column -> ShowS
Show, Column -> Column -> Bool
(Column -> Column -> Bool)
-> (Column -> Column -> Bool) -> Eq Column
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Column -> Column -> Bool
$c/= :: Column -> Column -> Bool
== :: Column -> Column -> Bool
$c== :: Column -> Column -> Bool
Eq)
instance ToJSON Column where
toJSON :: Column -> Value
toJSON Column
col =
case Column
col of
StringColumn Text
a -> [Pair] -> Value
object [ Text
"label" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
a, Text
"type" Text -> Text -> Pair
~= Text
"string"]
NumberColumn Text
a -> [Pair] -> Value
object [ Text
"label" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
a, Text
"type" Text -> Text -> Pair
~= Text
"number"]
BoolColumn Text
a -> [Pair] -> Value
object [ Text
"label" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
a, Text
"type" Text -> Text -> Pair
~= Text
"boolean"]
DateColumn Text
a -> [Pair] -> Value
object [ Text
"label" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
a, Text
"type" Text -> Text -> Pair
~= Text
"date"]
DateTimeColumn Text
a -> [Pair] -> Value
object [ Text
"label" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
a, Text
"type" Text -> Text -> Pair
~= Text
"datetime"]
TimeOfDayColumn Text
a -> [Pair] -> Value
object [ Text
"label" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
a, Text
"type" Text -> Text -> Pair
~= Text
"timeofday"]
Column
AnnotationColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"annotation"]
Column
AnnotationTextColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"annotationText"]
Column
CertaintyColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"certainty"]
Column
EmphasisColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"emphasis"]
Column
IntervalColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"interval"]
Column
ScopeColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"scope"]
Column
StyleColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"style"]
Column
TooltipColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"tooltip"]
Column
DomainColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"domain"]
Column
DataColumn -> [Pair] -> Value
object [Text
"role" Text -> Text -> Pair
~= Text
"data"]
where
(~=):: T.Text -> T.Text -> (T.Text, Value)
~= :: Text -> Text -> Pair
(~=) = Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
(.=)
data ChartStyle = LineChart
| Histogram
| BarChart
| ColumnChart
| ScatterChart
| AreaChart
| PieChart
| BubbleChart
| SteppedAreaChart
| CandlestickChart
deriving (Int -> ChartStyle -> ShowS
[ChartStyle] -> ShowS
ChartStyle -> String
(Int -> ChartStyle -> ShowS)
-> (ChartStyle -> String)
-> ([ChartStyle] -> ShowS)
-> Show ChartStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChartStyle] -> ShowS
$cshowList :: [ChartStyle] -> ShowS
show :: ChartStyle -> String
$cshow :: ChartStyle -> String
showsPrec :: Int -> ChartStyle -> ShowS
$cshowsPrec :: Int -> ChartStyle -> ShowS
Show, ChartStyle -> ChartStyle -> Bool
(ChartStyle -> ChartStyle -> Bool)
-> (ChartStyle -> ChartStyle -> Bool) -> Eq ChartStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChartStyle -> ChartStyle -> Bool
$c/= :: ChartStyle -> ChartStyle -> Bool
== :: ChartStyle -> ChartStyle -> Bool
$c== :: ChartStyle -> ChartStyle -> Bool
Eq, Eq ChartStyle
Eq ChartStyle
-> (ChartStyle -> ChartStyle -> Ordering)
-> (ChartStyle -> ChartStyle -> Bool)
-> (ChartStyle -> ChartStyle -> Bool)
-> (ChartStyle -> ChartStyle -> Bool)
-> (ChartStyle -> ChartStyle -> Bool)
-> (ChartStyle -> ChartStyle -> ChartStyle)
-> (ChartStyle -> ChartStyle -> ChartStyle)
-> Ord ChartStyle
ChartStyle -> ChartStyle -> Bool
ChartStyle -> ChartStyle -> Ordering
ChartStyle -> ChartStyle -> ChartStyle
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ChartStyle -> ChartStyle -> ChartStyle
$cmin :: ChartStyle -> ChartStyle -> ChartStyle
max :: ChartStyle -> ChartStyle -> ChartStyle
$cmax :: ChartStyle -> ChartStyle -> ChartStyle
>= :: ChartStyle -> ChartStyle -> Bool
$c>= :: ChartStyle -> ChartStyle -> Bool
> :: ChartStyle -> ChartStyle -> Bool
$c> :: ChartStyle -> ChartStyle -> Bool
<= :: ChartStyle -> ChartStyle -> Bool
$c<= :: ChartStyle -> ChartStyle -> Bool
< :: ChartStyle -> ChartStyle -> Bool
$c< :: ChartStyle -> ChartStyle -> Bool
compare :: ChartStyle -> ChartStyle -> Ordering
$ccompare :: ChartStyle -> ChartStyle -> Ordering
$cp1Ord :: Eq ChartStyle
Ord)
instance ToJSON ChartStyle where
toJSON :: ChartStyle -> Value
toJSON = \case
ChartStyle
LineChart -> Value
"line"
ChartStyle
Histogram -> Value
"histogram"
ChartStyle
BarChart -> Value
"bar"
ChartStyle
ColumnChart -> Value
"column"
ChartStyle
ScatterChart -> Value
"scatter"
ChartStyle
AreaChart -> Value
"area"
ChartStyle
PieChart -> Value
"pie"
ChartStyle
BubbleChart -> Value
"bubble"
ChartStyle
SteppedAreaChart -> Value
"steppedarea"
ChartStyle
CandlestickChart -> Value
"candlestick"
data ChartOptions = ChartOptions Value
instance ToJSON ChartOptions where
toJSON :: ChartOptions -> Value
toJSON (ChartOptions Value
v) = Value
v
defaultChartOptions :: ChartOptions
defaultChartOptions :: ChartOptions
defaultChartOptions = Value -> ChartOptions
ChartOptions ([Pair] -> Value
object [])
data Chart =
Chart { Chart -> ChartOptions
options :: ChartOptions
, Chart -> ChartStyle
style :: ChartStyle
, Chart -> [Column]
columns :: [Column]
, Chart -> [[Value]]
dataTable :: [[Value]]
, Chart -> Bool
dynamic :: Bool
}
instance ToJSON Chart where
toJSON :: Chart -> Value
toJSON (Chart{Bool
[[Value]]
[Column]
ChartOptions
ChartStyle
dynamic :: Bool
dataTable :: [[Value]]
columns :: [Column]
style :: ChartStyle
options :: ChartOptions
dynamic :: Chart -> Bool
dataTable :: Chart -> [[Value]]
columns :: Chart -> [Column]
style :: Chart -> ChartStyle
options :: Chart -> ChartOptions
..}) =
[Pair] -> Value
object [ Text
"rows" Text -> [[Value]] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [[Value]]
dataTable
, Text
"options" Text -> ChartOptions -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ChartOptions
options
, Text
"columns" Text -> [Column] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Column]
columns
, Text
"style" Text -> ChartStyle -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ChartStyle
style
, Text
"dynamic" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
dynamic
]
buildChart :: ChartOptions -> ChartStyle -> [Column] -> [[Value]] -> Chart
buildChart :: ChartOptions -> ChartStyle -> [Column] -> [[Value]] -> Chart
buildChart ChartOptions
opts ChartStyle
style [Column]
columns [[Value]]
vals = ChartOptions
-> ChartStyle -> [Column] -> [[Value]] -> Bool -> Chart
Chart ChartOptions
opts ChartStyle
style [Column]
columns [[Value]]
vals Bool
True