module Granite.String (
Plot (..),
defPlot,
series,
module RE,
bins,
LabelFormatter,
scatter,
lineGraph,
bars,
stackedBars,
histogram,
pie,
heatmap,
boxPlot,
) where
import Data.Text (Text)
import Data.Bifunctor
import Data.Text qualified as Text
import Granite qualified as G
import Granite as RE (AxisEnv (..), Bins, Color (..), LegendPos (..))
data Plot = Plot
{ Plot -> Int
widthChars :: Int
, Plot -> Int
heightChars :: Int
, Plot -> Int
leftMargin :: Int
, Plot -> Int
bottomMargin :: Int
, Plot -> Int
titleMargin :: Int
, Plot -> (Maybe Double, Maybe Double)
xBounds :: (Maybe Double, Maybe Double)
, Plot -> (Maybe Double, Maybe Double)
yBounds :: (Maybe Double, Maybe Double)
, Plot -> String
plotTitle :: String
, Plot -> LegendPos
legendPos :: G.LegendPos
, Plot -> [Color]
colorPalette :: [G.Color]
, Plot -> LabelFormatter
xFormatter :: LabelFormatter
, Plot -> LabelFormatter
yFormatter :: LabelFormatter
, Plot -> Int
xNumTicks :: Int
, Plot -> Int
yNumTicks :: Int
}
type LabelFormatter =
G.AxisEnv ->
Int ->
Double ->
String
defPlot :: Plot
defPlot :: Plot
defPlot = Plot -> Plot
fromGranitePlot Plot
G.defPlot
bins ::
Int ->
Double ->
Double ->
G.Bins
bins :: Int -> Double -> Double -> Bins
bins = Int -> Double -> Double -> Bins
G.bins
series ::
String ->
[(Double, Double)] ->
(String, [(Double, Double)])
series :: String -> [(Double, Double)] -> (String, [(Double, Double)])
series String
name [(Double, Double)]
points = (String
name, [(Double, Double)]
points)
scatter ::
[(String, [(Double, Double)])] ->
Plot ->
String
scatter :: [(String, [(Double, Double)])] -> Plot -> String
scatter [(String, [(Double, Double)])]
seriesList Plot
plot =
Text -> String
Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$
[(Text, [(Double, Double)])] -> Plot -> Text
G.scatter (((String, [(Double, Double)]) -> (Text, [(Double, Double)]))
-> [(String, [(Double, Double)])] -> [(Text, [(Double, Double)])]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Text)
-> (String, [(Double, Double)]) -> (Text, [(Double, Double)])
forall a b c. (a -> b) -> (a, c) -> (b, c)
mapFirst String -> Text
Text.pack) [(String, [(Double, Double)])]
seriesList) (Plot -> Plot
toGranitePlot Plot
plot)
lineGraph ::
[(String, [(Double, Double)])] ->
Plot ->
String
lineGraph :: [(String, [(Double, Double)])] -> Plot -> String
lineGraph [(String, [(Double, Double)])]
seriesList Plot
plot =
Text -> String
Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$
[(Text, [(Double, Double)])] -> Plot -> Text
G.lineGraph (((String, [(Double, Double)]) -> (Text, [(Double, Double)]))
-> [(String, [(Double, Double)])] -> [(Text, [(Double, Double)])]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Text)
-> (String, [(Double, Double)]) -> (Text, [(Double, Double)])
forall a b c. (a -> b) -> (a, c) -> (b, c)
mapFirst String -> Text
Text.pack) [(String, [(Double, Double)])]
seriesList) (Plot -> Plot
toGranitePlot Plot
plot)
bars ::
[(String, Double)] ->
Plot ->
String
bars :: [(String, Double)] -> Plot -> String
bars [(String, Double)]
categories Plot
plot =
Text -> String
Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ [(Text, Double)] -> Plot -> Text
G.bars (((String, Double) -> (Text, Double))
-> [(String, Double)] -> [(Text, Double)]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Text) -> (String, Double) -> (Text, Double)
forall a b c. (a -> b) -> (a, c) -> (b, c)
mapFirst String -> Text
Text.pack) [(String, Double)]
categories) (Plot -> Plot
toGranitePlot Plot
plot)
stackedBars ::
[(String, [(String, Double)])] ->
Plot ->
String
stackedBars :: [(String, [(String, Double)])] -> Plot -> String
stackedBars [(String, [(String, Double)])]
categories Plot
plot =
Text -> String
Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$
[(Text, [(Text, Double)])] -> Plot -> Text
G.stackedBars
(((String, [(String, Double)]) -> (Text, [(Text, Double)]))
-> [(String, [(String, Double)])] -> [(Text, [(Text, Double)])]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Text)
-> ([(String, Double)] -> [(Text, Double)])
-> (String, [(String, Double)])
-> (Text, [(Text, Double)])
forall a b c d. (a -> b) -> (c -> d) -> (a, c) -> (b, d)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
Data.Bifunctor.bimap String -> Text
Text.pack (((String, Double) -> (Text, Double))
-> [(String, Double)] -> [(Text, Double)]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Text) -> (String, Double) -> (Text, Double)
forall a b c. (a -> b) -> (a, c) -> (b, c)
mapFirst String -> Text
Text.pack))) [(String, [(String, Double)])]
categories)
(Plot -> Plot
toGranitePlot Plot
plot)
histogram ::
G.Bins ->
[Double] ->
Plot ->
String
histogram :: Bins -> [Double] -> Plot -> String
histogram Bins
binConfig [Double]
values Plot
plot =
Text -> String
Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Bins -> [Double] -> Plot -> Text
G.histogram Bins
binConfig [Double]
values (Plot -> Plot
toGranitePlot Plot
plot)
pie ::
[(String, Double)] ->
Plot ->
String
pie :: [(String, Double)] -> Plot -> String
pie [(String, Double)]
slices Plot
plot =
Text -> String
Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ [(Text, Double)] -> Plot -> Text
G.pie (((String, Double) -> (Text, Double))
-> [(String, Double)] -> [(Text, Double)]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Text) -> (String, Double) -> (Text, Double)
forall a b c. (a -> b) -> (a, c) -> (b, c)
mapFirst String -> Text
Text.pack) [(String, Double)]
slices) (Plot -> Plot
toGranitePlot Plot
plot)
heatmap ::
[[Double]] ->
Plot ->
String
heatmap :: [[Double]] -> Plot -> String
heatmap [[Double]]
matrix Plot
plot =
Text -> String
Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ [[Double]] -> Plot -> Text
G.heatmap [[Double]]
matrix (Plot -> Plot
toGranitePlot Plot
plot)
boxPlot ::
[(String, [Double])] ->
Plot ->
String
boxPlot :: [(String, [Double])] -> Plot -> String
boxPlot [(String, [Double])]
datasets Plot
plot =
Text -> String
Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ [(Text, [Double])] -> Plot -> Text
G.boxPlot (((String, [Double]) -> (Text, [Double]))
-> [(String, [Double])] -> [(Text, [Double])]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Text) -> (String, [Double]) -> (Text, [Double])
forall a b c. (a -> b) -> (a, c) -> (b, c)
mapFirst String -> Text
Text.pack) [(String, [Double])]
datasets) (Plot -> Plot
toGranitePlot Plot
plot)
toGranitePlot :: Plot -> G.Plot
toGranitePlot :: Plot -> Plot
toGranitePlot Plot
p =
G.Plot
{ widthChars :: Int
G.widthChars = Plot -> Int
widthChars Plot
p
, heightChars :: Int
G.heightChars = Plot -> Int
heightChars Plot
p
, leftMargin :: Int
G.leftMargin = Plot -> Int
leftMargin Plot
p
, bottomMargin :: Int
G.bottomMargin = Plot -> Int
bottomMargin Plot
p
, titleMargin :: Int
G.titleMargin = Plot -> Int
titleMargin Plot
p
, xBounds :: (Maybe Double, Maybe Double)
G.xBounds = Plot -> (Maybe Double, Maybe Double)
xBounds Plot
p
, yBounds :: (Maybe Double, Maybe Double)
G.yBounds = Plot -> (Maybe Double, Maybe Double)
yBounds Plot
p
, plotTitle :: Text
G.plotTitle = String -> Text
Text.pack (Plot -> String
plotTitle Plot
p)
, legendPos :: LegendPos
G.legendPos = Plot -> LegendPos
legendPos Plot
p
, colorPalette :: [Color]
G.colorPalette = Plot -> [Color]
colorPalette Plot
p
, xFormatter :: LabelFormatter
G.xFormatter = LabelFormatter -> LabelFormatter
formatWithText (Plot -> LabelFormatter
xFormatter Plot
p)
, yFormatter :: LabelFormatter
G.yFormatter = LabelFormatter -> LabelFormatter
formatWithText (Plot -> LabelFormatter
yFormatter Plot
p)
, xNumTicks :: Int
G.xNumTicks = Plot -> Int
xNumTicks Plot
p
, yNumTicks :: Int
G.yNumTicks = Plot -> Int
yNumTicks Plot
p
}
fromGranitePlot :: G.Plot -> Plot
fromGranitePlot :: Plot -> Plot
fromGranitePlot Plot
p =
Plot
{ widthChars :: Int
widthChars = Plot -> Int
G.widthChars Plot
p
, heightChars :: Int
heightChars = Plot -> Int
G.heightChars Plot
p
, leftMargin :: Int
leftMargin = Plot -> Int
G.leftMargin Plot
p
, bottomMargin :: Int
bottomMargin = Plot -> Int
G.bottomMargin Plot
p
, titleMargin :: Int
titleMargin = Plot -> Int
G.titleMargin Plot
p
, xBounds :: (Maybe Double, Maybe Double)
xBounds = Plot -> (Maybe Double, Maybe Double)
G.xBounds Plot
p
, yBounds :: (Maybe Double, Maybe Double)
yBounds = Plot -> (Maybe Double, Maybe Double)
G.yBounds Plot
p
, plotTitle :: String
plotTitle = Text -> String
Text.unpack (Plot -> Text
G.plotTitle Plot
p)
, legendPos :: LegendPos
legendPos = Plot -> LegendPos
G.legendPos Plot
p
, colorPalette :: [Color]
colorPalette = Plot -> [Color]
G.colorPalette Plot
p
, xFormatter :: LabelFormatter
xFormatter = LabelFormatter -> LabelFormatter
formatWithString (Plot -> LabelFormatter
G.xFormatter Plot
p)
, yFormatter :: LabelFormatter
yFormatter = LabelFormatter -> LabelFormatter
formatWithString (Plot -> LabelFormatter
G.yFormatter Plot
p)
, xNumTicks :: Int
xNumTicks = Plot -> Int
G.xNumTicks Plot
p
, yNumTicks :: Int
yNumTicks = Plot -> Int
G.yNumTicks Plot
p
}
mapFirst :: (a -> b) -> (a, c) -> (b, c)
mapFirst :: forall a b c. (a -> b) -> (a, c) -> (b, c)
mapFirst a -> b
f (a
a, c
c) = (a -> b
f a
a, c
c)
formatWithText ::
(G.AxisEnv -> Int -> Double -> String) -> G.AxisEnv -> Int -> Double -> Text
formatWithText :: LabelFormatter -> LabelFormatter
formatWithText LabelFormatter
f AxisEnv
env Int
i Double
d = String -> Text
Text.pack (LabelFormatter
f AxisEnv
env Int
i Double
d)
formatWithString ::
(G.AxisEnv -> Int -> Double -> Text) -> G.AxisEnv -> Int -> Double -> String
formatWithString :: LabelFormatter -> LabelFormatter
formatWithString LabelFormatter
f AxisEnv
env Int
i Double
d = Text -> String
Text.unpack (LabelFormatter
f AxisEnv
env Int
i Double
d)