module Graphics.Rendering.Plot.Figure.Plot.Axis (
Axis
, AxisType(..),AxisSide(..),AxisPosn(..)
, Tick(..), TickValues(..), GridLines
, TickFormat(..)
, setTicks
, setGridlines
, setTickLabelFormat
, setTickLabels
, withTickLabelsFormat
, withAxisLabel
, withAxisLine
, withGridLine
) where
import Control.Monad.State
import Control.Monad.Reader
import Graphics.Rendering.Plot.Types
import Graphics.Rendering.Plot.Defaults
changeLineType :: LineType -> AxisData -> AxisData
changeLineType lt ax = ax { _line_type = lt }
changeMinorTicks :: (Maybe Ticks -> Maybe Ticks) -> AxisData -> AxisData
changeMinorTicks t ax = ax { _minor_ticks = t (_minor_ticks ax) }
changeMajorTicks :: (Maybe Ticks -> Maybe Ticks) -> AxisData -> AxisData
changeMajorTicks t ax = ax { _major_ticks = t (_major_ticks ax) }
changeTickFormat :: TickFormat -> AxisData -> AxisData
changeTickFormat tf ax = ax { _tick_format = tf }
changeLabel :: (TextEntry -> TextEntry) -> AxisData -> AxisData
changeLabel f ax = ax { _label = f (_label ax) }
changeTickLabels :: ([TextEntry] -> [TextEntry]) -> AxisData -> AxisData
changeTickLabels f ax = ax { _tick_labels = f (_tick_labels ax) }
withAxisLine :: Line () -> Axis ()
withAxisLine m = do
l <- gets _line_type
lo <- asks _lineoptions
let lt = execLine m lo l
modify $ \s -> s { _line_type = lt }
withGridLine :: Tick -> Line () -> Axis ()
withGridLine t m = do
lo <- asks _lineoptions
(lt',v) <- case t of
Minor -> do
(Just (Ticks lt'' v')) <- gets _minor_ticks
return (lt'',v')
Major -> do
(Just (Ticks lt'' v')) <- gets _major_ticks
return (lt'',v')
let lt = execLine m lo lt'
case t of
Minor -> modify $ \s -> s { _minor_ticks = (Just (Ticks lt v)) }
Major -> modify $ \s -> s { _major_ticks = (Just (Ticks lt v)) }
setTicks :: Tick -> TickValues -> Axis ()
setTicks Minor (TickNumber 0) = modify $ \s ->
changeMinorTicks (const Nothing) s
setTicks Minor ts = modify $ \s ->
changeMinorTicks (setTickValues ts) s
setTicks Major (TickNumber 0) = modify $ \s ->
changeMajorTicks (const Nothing) s
setTicks Major ts = modify $ \s ->
changeMajorTicks (setTickValues ts) s
setGridlines :: Tick -> GridLines -> Axis ()
setGridlines Minor gl = modify $ \s ->
changeMinorTicks (setTickGridlines (if gl then defaultGridLine else NoLine)) s
setGridlines Major gl = modify $ \s ->
changeMajorTicks (setTickGridlines (if gl then defaultGridLine else NoLine)) s
setTickLabelFormat :: TickFormat -> Axis ()
setTickLabelFormat tf = modify $ \s -> changeTickFormat tf s
setTickLabels :: [String] -> Axis ()
setTickLabels dl = modify $ \s ->
changeTickLabels (const (map BareText dl)) s
withTickLabelsFormat :: Text () -> Axis ()
withTickLabelsFormat m = do
ax <- get
to <- asks _textoptions
put $ ax { _tick_labels = map (execText m to) (_tick_labels ax) }
withAxisLabel :: Text () -> Axis ()
withAxisLabel m = do
ax <- get
to <- asks _textoptions
put $ ax { _label = execText m to (_label ax) }
withTickLabelFormat :: Text () -> Axis ()
withTickLabelFormat m = do
ax <- get
to <- asks _textoptions
put $ ax { _tick_labels = map (execText m to) (_tick_labels ax) }