{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module Plots.Axis
(
Axis
, axes
, axisPlots
, currentPlots
, finalPlots
, plotModifier
, axisSize
, colourBarRange
, r2Axis
, r3Axis
, polarAxis
, BaseSpace
, addPlot
, addPlotable
, addPlotable'
, SingleAxis
, xAxis
, xLabel
, xMin
, xMax
, yAxis
, yLabel
, yMin
, yMax
, rAxis
, rLabel
, rMax
, thetaAxis
, thetaLabel
, zAxis
, zLabel
, zMin
, zMax
) where
import Control.Monad.State
import Data.Complex
import Data.Default
import Data.Typeable
import Diagrams.Coordinates.Polar
import Diagrams.Prelude
import Diagrams.TwoD.Text
import Plots.Axis.ColourBar
import Plots.Axis.Grid
import Plots.Axis.Labels
import Plots.Axis.Line
import Plots.Axis.Scale
import Plots.Axis.Title
import Plots.Axis.Ticks
import Plots.Legend
import Plots.Style
import Plots.Types
import Linear
data SingleAxis v = SingleAxis
{ saLabel :: AxisLabel v
, saLine :: AxisLine v
, saTickLabel :: TickLabels v
, saScaling :: AxisScaling
, saGridLines :: GridLines v
, saTicks :: Ticks v
, saVisible :: Bool
}
type instance V (SingleAxis v) = v
type instance N (SingleAxis v) = Double
instance Default (SingleAxis V2) where
def = SingleAxis
{ saLabel = def
, saLine = def
, saTickLabel = def
, saGridLines = def
, saTicks = def
, saScaling = def
, saVisible = True
}
instance Default (SingleAxis V3) where
def = SingleAxis
{ saLabel = def
, saLine = def
, saTickLabel = def
, saGridLines = def
, saTicks = def
, saScaling = def
, saVisible = True
}
instance Functor f => HasTicks f (SingleAxis v) where
bothTicks = lens saTicks (\sa ticks -> sa {saTicks = ticks})
instance Functor f => HasMajorTicks f (SingleAxis v) where
majorTicks = bothTicks . majorTicks
instance Functor f => HasMinorTicks f (SingleAxis v) where
minorTicks = bothTicks . minorTicks
instance Functor f => HasAxisLabel f (SingleAxis v) where
axisLabel = lens saLabel (\sa l -> sa {saLabel = l})
instance Functor f => HasTickLabels f (SingleAxis v) where
tickLabel = lens saTickLabel (\sa tl -> sa {saTickLabel = tl})
instance Functor f => HasAxisLine f (SingleAxis v) where
axisLine = lens saLine (\sa l -> sa {saLine = l})
instance Functor f => HasGridLines f (SingleAxis v) where
gridLines = lens saGridLines (\sa l -> sa {saGridLines = l})
instance Functor f => HasMajorGridLines f (SingleAxis v) where
majorGridLines = gridLines . majorGridLines
instance Functor f => HasMinorGridLines f (SingleAxis v) where
minorGridLines = gridLines . minorGridLines
instance Functor f => HasAxisScaling f (SingleAxis v) where
axisScaling = lens saScaling (\sa s -> sa {saScaling = s})
instance HasVisibility (SingleAxis v) where
visible = lens saVisible (\sa b -> sa {saVisible = b})
type family BaseSpace (c :: * -> *) :: * -> *
type instance BaseSpace V2 = V2
type instance BaseSpace Complex = V2
type instance BaseSpace Polar = V2
type instance BaseSpace V3 = V3
data Axis c = Axis
{ _axisStyle :: AxisStyle (BaseSpace c)
, _colourBar :: ColourBar
, _colourBarR :: (Double,Double)
, _legend :: Legend
, _axisTitle :: Title (BaseSpace c)
, _axisPlots :: [DynamicPlot (BaseSpace c)]
, _plotModifier :: Endo (StyledPlot (BaseSpace c))
, _axes :: c (SingleAxis (BaseSpace c))
} deriving Typeable
axes :: (v ~ BaseSpace c, v ~ BaseSpace c')
=> Lens (Axis c)
(Axis c')
(c (SingleAxis v))
(c' (SingleAxis v))
axes = lens _axes (\(Axis a1 a2 a3 a4 a5 a6 a7 _) a8 -> Axis a1 a2 a3 a4 a5 a6 a7 a8)
axisPlots :: BaseSpace c ~ v => Lens' (Axis c) [DynamicPlot v]
axisPlots = lens _axisPlots (\a ps -> a {_axisPlots = ps})
currentPlots :: BaseSpace c ~ v => Traversal' (Axis c) (DynamicPlot v)
currentPlots = axisPlots . traversed
finalPlots :: BaseSpace c ~ v => Setter' (Axis c) (StyledPlot v)
finalPlots = sets $ \f a -> a {_plotModifier = _plotModifier a <> Endo f}
plotModifier :: BaseSpace c ~ v => Lens' (Axis c) (Endo (StyledPlot v))
plotModifier = lens _plotModifier (\a f -> a {_plotModifier = f})
type instance V (Axis c) = BaseSpace c
type instance N (Axis c) = Double
instance (Applicative f, Traversable c) => HasTicks f (Axis c) where
bothTicks = axes . traverse . bothTicks
instance (Applicative f, Traversable c) => HasMajorTicks f (Axis c) where
majorTicks = axes . traverse . majorTicks
instance (Applicative f, Traversable c) => HasMinorTicks f (Axis c) where
minorTicks = axes . traverse . minorTicks
instance (Applicative f, Traversable c) => HasGridLines f (Axis c) where
gridLines = axes . traverse . gridLines
instance (Applicative f, Traversable c) => HasMajorGridLines f (Axis c) where
majorGridLines = axes . traverse . majorGridLines
instance (Applicative f, Traversable c) => HasMinorGridLines f (Axis c) where
minorGridLines = axes . traverse . minorGridLines
instance (Applicative f, Traversable c) => HasAxisLine f (Axis c) where
axisLine = axes . traverse . axisLine
instance (Applicative f, Traversable c) => HasAxisLabel f (Axis c) where
axisLabel = axes . traverse . axisLabel
instance (Applicative f, Traversable c) => HasTickLabels f (Axis c) where
tickLabel = axes . traverse . tickLabel
instance (Applicative f, Traversable c) => HasAxisScaling f (Axis c) where
axisScaling = axes . traverse . axisScaling
instance Settable f => HasPlotOptions f (Axis c) where
plotOptions = finalPlots . plotOptions
instance Settable f => HasPlotStyle f (Axis c) where
plotStyle = finalPlots . plotStyle
instance HasLegend (Axis c) where
legend = lens _legend (\a l -> a {_legend = l})
instance HasTitle (Axis c) where
title = lens _axisTitle (\a t -> a {_axisTitle = t})
axisSize :: HasLinearMap c => Lens' (Axis c) (SizeSpec c Double)
axisSize = axes . column renderSize . iso mkSizeSpec getSpec
colourBarRange :: Lens' (Axis v) (Double,Double)
colourBarRange = lens _colourBarR (\a r -> a {_colourBarR = r})
instance HasAxisStyle (Axis v) where
axisStyle = lens _axisStyle (\a sty -> a {_axisStyle = sty})
instance HasColourBar (Axis v) where
colourBar = lens _colourBar (\a cb -> a {_colourBar = cb})
addPlot
:: (InSpace (BaseSpace c) Double p, MonadState (Axis c) m, Plotable p)
=> Plot p
-> m ()
addPlot p = axisPlots <>= [DynamicPlot p]
addPlotable
:: (InSpace (BaseSpace c) Double p, MonadState (Axis c) m, Plotable p, HasLinearMap (BaseSpace c))
=> p
-> State (Plot p) ()
-> m ()
addPlotable p s = addPlot $ execState s (mkPlot p)
addPlotable'
:: (InSpace (BaseSpace c) Double p, MonadState (Axis c) m, Plotable p, HasLinearMap (BaseSpace c))
=> p
-> m ()
addPlotable' p = addPlotable p (return ())
r2Axis :: Axis V2
r2Axis = Axis
{ _axisStyle = fadedColours
, _colourBar = defColourBar
, _colourBarR = (0,1)
, _axisTitle = def
, _legend = def
, _axisPlots = []
, _plotModifier = mempty
, _axes = pure def
}
r3Axis :: Axis V3
r3Axis = Axis
{ _axisStyle = fadedColours3D
, _colourBar = defColourBar
, _colourBarR = (0,1)
, _axisTitle = def
, _legend = def
, _axisPlots = []
, _plotModifier = mempty
, _axes = pure def
}
xAxis :: R1 c => Lens' (Axis c) (SingleAxis (BaseSpace c))
xAxis = axes . _x
xLabel :: R1 c => Lens' (Axis c) String
xLabel = xAxis . axisLabelText
xMin :: R1 c => Lens' (Axis c) (Maybe Double)
xMin = xAxis . boundMin
xMax :: R1 c => Lens' (Axis c) (Maybe Double)
xMax = xAxis . boundMax
yAxis :: R2 c => Lens' (Axis c) (SingleAxis (BaseSpace c))
yAxis = axes . _y
yLabel :: R2 c => Lens' (Axis c) String
yLabel = yAxis . axisLabelText
yMin :: R2 c => Lens' (Axis c) (Maybe Double)
yMin = yAxis . boundMin
yMax :: R2 c => Lens' (Axis c) (Maybe Double)
yMax = yAxis . boundMax
zAxis :: R3 c => Lens' (Axis c) (SingleAxis (BaseSpace c))
zAxis = axes . _z
zLabel :: R3 c => Lens' (Axis c) String
zLabel = zAxis . axisLabelText
zMin :: R3 c => Lens' (Axis c) (Maybe Double)
zMin = zAxis . boundMin
zMax :: R3 c => Lens' (Axis c) (Maybe Double)
zMax = zAxis . boundMax
rAxis :: Radial c => Lens' (Axis c) (SingleAxis (BaseSpace c))
rAxis = axes . _radial
rLabel :: Radial c => Lens' (Axis c) String
rLabel = rAxis . axisLabelText
rMax :: Radial c => Lens' (Axis c) (Maybe Double)
rMax = rAxis . boundMax
thetaAxis :: Circle c => Lens' (Axis c) (SingleAxis (BaseSpace c))
thetaAxis = axes . el etheta
thetaLabel :: Circle c => Lens' (Axis c) String
thetaLabel = thetaAxis . axisLabelText
polarAxis :: Axis Polar
polarAxis = Axis
{ _axisStyle = fadedColours
, _colourBar = defColourBar
, _colourBarR = (0,1)
, _axisTitle = def
, _legend = def
, _axisPlots = []
, _plotModifier = mempty
, _axes = pure def
}