{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DuplicateRecordFields #-}
module Graphics.Plotly.Default ( PlotConfig (..), defaultConfig, fromConfig
) where
import Graphics.Plotly.Internal
fromConfig :: PlotConfig -> Layout
fromConfig :: PlotConfig -> Layout
fromConfig PlotConfig{Bool
Int
String
XBins
BarMode
ColorScale
Mode
Marker
AxisType
Margin
$sel:bins:PlotConfig :: PlotConfig -> XBins
$sel:marker:PlotConfig :: PlotConfig -> Marker
$sel:margin:PlotConfig :: PlotConfig -> Margin
$sel:width:PlotConfig :: PlotConfig -> Int
$sel:height:PlotConfig :: PlotConfig -> Int
$sel:legend:PlotConfig :: PlotConfig -> Bool
$sel:reverseScale:PlotConfig :: PlotConfig -> Bool
$sel:showScale:PlotConfig :: PlotConfig -> Bool
$sel:colorScale:PlotConfig :: PlotConfig -> ColorScale
$sel:lineMode:PlotConfig :: PlotConfig -> Mode
$sel:barMode:PlotConfig :: PlotConfig -> BarMode
$sel:ymode:PlotConfig :: PlotConfig -> AxisType
$sel:xmode:PlotConfig :: PlotConfig -> AxisType
$sel:ylabel:PlotConfig :: PlotConfig -> String
$sel:xlabel:PlotConfig :: PlotConfig -> String
$sel:title':PlotConfig :: PlotConfig -> String
bins :: XBins
marker :: Marker
margin :: Margin
width :: Int
height :: Int
legend :: Bool
reverseScale :: Bool
showScale :: Bool
colorScale :: ColorScale
lineMode :: Mode
barMode :: BarMode
ymode :: AxisType
xmode :: AxisType
ylabel :: String
xlabel :: String
title' :: String
..} = Layout
layout
where
xaxis :: Maybe Axis
xaxis = Axis -> Maybe Axis
forall a. a -> Maybe a
Just (Axis -> Maybe Axis) -> Axis -> Maybe Axis
forall a b. (a -> b) -> a -> b
$ String -> Bool -> Bool -> AxisType -> Axis
Axis String
xlabel Bool
True Bool
True AxisType
xmode
yaxis :: Maybe Axis
yaxis = Axis -> Maybe Axis
forall a. a -> Maybe a
Just (Axis -> Maybe Axis) -> Axis -> Maybe Axis
forall a b. (a -> b) -> a -> b
$ String -> Bool -> Bool -> AxisType -> Axis
Axis String
ylabel Bool
True Bool
True AxisType
ymode
barm :: Maybe BarMode
barm = BarMode -> Maybe BarMode
forall a. a -> Maybe a
Just BarMode
barMode
layout :: Layout
layout = String
-> Maybe Axis
-> Maybe Axis
-> Maybe BarMode
-> Int
-> Int
-> Maybe Bool
-> Maybe Margin
-> Layout
Layout String
title' Maybe Axis
xaxis Maybe Axis
yaxis Maybe BarMode
barm Int
height Int
width
(Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
legend) (Margin -> Maybe Margin
forall a. a -> Maybe a
Just Margin
margin)
data PlotConfig = PlotConfig { PlotConfig -> String
title' :: !String
, PlotConfig -> String
xlabel :: !String
, PlotConfig -> String
ylabel :: !String
, PlotConfig -> AxisType
xmode :: !AxisType
, PlotConfig -> AxisType
ymode :: !AxisType
, PlotConfig -> BarMode
barMode :: !BarMode
, PlotConfig -> Mode
lineMode :: !Mode
, PlotConfig -> ColorScale
colorScale :: !ColorScale
, PlotConfig -> Bool
showScale :: !Bool
, PlotConfig -> Bool
reverseScale :: !Bool
, PlotConfig -> Bool
legend :: !Bool
, PlotConfig -> Int
height :: !Int
, PlotConfig -> Int
width :: !Int
, PlotConfig -> Margin
margin :: !Margin
, PlotConfig -> Marker
marker :: !Marker
, PlotConfig -> XBins
bins :: !XBins
} deriving (Int -> PlotConfig -> ShowS
[PlotConfig] -> ShowS
PlotConfig -> String
(Int -> PlotConfig -> ShowS)
-> (PlotConfig -> String)
-> ([PlotConfig] -> ShowS)
-> Show PlotConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlotConfig] -> ShowS
$cshowList :: [PlotConfig] -> ShowS
show :: PlotConfig -> String
$cshow :: PlotConfig -> String
showsPrec :: Int -> PlotConfig -> ShowS
$cshowsPrec :: Int -> PlotConfig -> ShowS
Show)
defaultConfig :: PlotConfig
defaultConfig :: PlotConfig
defaultConfig = PlotConfig :: String
-> String
-> String
-> AxisType
-> AxisType
-> BarMode
-> Mode
-> ColorScale
-> Bool
-> Bool
-> Bool
-> Int
-> Int
-> Margin
-> Marker
-> XBins
-> PlotConfig
PlotConfig { $sel:title':PlotConfig :: String
title' = String
""
, $sel:xlabel:PlotConfig :: String
xlabel = String
""
, $sel:ylabel:PlotConfig :: String
ylabel = String
""
, $sel:xmode:PlotConfig :: AxisType
xmode = AxisType
Linear
, $sel:ymode:PlotConfig :: AxisType
ymode = AxisType
Linear
, $sel:barMode:PlotConfig :: BarMode
barMode = BarMode
Overlay
, $sel:lineMode:PlotConfig :: Mode
lineMode = Mode
Lines
, $sel:colorScale:PlotConfig :: ColorScale
colorScale = ColorScale
Viridis
, $sel:showScale:PlotConfig :: Bool
showScale = Bool
True
, $sel:reverseScale:PlotConfig :: Bool
reverseScale = Bool
False
, $sel:legend:PlotConfig :: Bool
legend = Bool
True
, $sel:height:PlotConfig :: Int
height = Int
800
, $sel:width:PlotConfig :: Int
width = Int
800
, $sel:margin:PlotConfig :: Margin
margin = Int -> Int -> Int -> Int -> Margin
Margin Int
66 Int
66 Int
66 Int
66
, $sel:marker:PlotConfig :: Marker
marker = Double -> Symbol -> Double -> Marker
Marker Double
0.1 Symbol
Circle Double
1.0
, $sel:bins:PlotConfig :: XBins
bins = Double -> Maybe Double -> Maybe Double -> XBins
XBins Double
0.05 Maybe Double
forall a. Maybe a
Nothing Maybe Double
forall a. Maybe a
Nothing
}