module Graphics.Rendering.Plot.Figure.Plot (
Plot
, Border
, setBorder
, setPlotBackgroundColour
, setPlotPadding
, withHeading
, D.Abscissa(), D.Ordinate(), D.Dataset()
, SeriesLabel
, D.FormattedSeries()
, D.line, D.point, D.linepoint
, D.impulse, D.step
, D.area
, D.bar
, D.hist
, D.candle, D.whisker
, setDataset
, Location, Head, Fill
, AN.arrow
, AN.oval
, AN.rect
, AN.glyph
, AN.text
, AN.cairo
, withAnnotations
, setSeriesType
, setAllSeriesTypes
, D.PlotFormats(..)
, withSeriesFormat
, withAllSeriesFormats
, Scale(..)
, setRange
, setRangeFromData
, AX.Axis
, AxisType(..),AxisSide(..),AxisPosn(..)
, clearAxes
, clearAxis
, addAxis
, withAxis
, barSetting
, sampleData
, L.Legend
, LegendBorder
, L.LegendLocation(..), L.LegendOrientation(..)
, clearLegend
, setLegend
, withLegendFormat
, Tick(..), TickValues(..), GridLines
, TickFormat(..)
, AX.setTicks
, AX.setGridlines
, AX.setTickLabelFormat
, AX.setTickLabels
, AX.withTickLabelsFormat
, AX.withAxisLabel
, AX.withAxisLine
, AX.withGridLine
) where
import Numeric.LinearAlgebra.Data hiding(Range)
import qualified Data.Array.IArray as A
import Control.Monad.State
import Control.Monad.Reader
import Prelude hiding(min,max)
import qualified Prelude as Prelude
import Graphics.Rendering.Plot.Types
import Graphics.Rendering.Plot.Defaults
import qualified Graphics.Rendering.Plot.Figure.Text as T
import qualified Graphics.Rendering.Plot.Figure.Plot.Data as D
import qualified Graphics.Rendering.Plot.Figure.Plot.Axis as AX
import qualified Graphics.Rendering.Plot.Figure.Plot.Legend as L
import qualified Graphics.Rendering.Plot.Figure.Plot.Annotation as AN
setBorder :: Border -> Plot ()
setBorder b = modify $ \s -> s { _border = b }
setPlotBackgroundColour :: Color -> Plot ()
setPlotBackgroundColour c = modify $ \s -> s { _back_colr = c }
setPlotPadding :: Double -> Double -> Double -> Double -> Plot ()
setPlotPadding l r b t = modify $ \s -> s { _plot_pads = Padding l r b t }
withHeading :: Text () -> Plot ()
withHeading m = do
o <- asks _textoptions
modify $ \s -> s { _heading = execText m o (_heading s) }
setRange :: AxisType -> AxisSide -> Scale -> Double -> Double -> Plot ()
setRange XAxis sd sc min max = modify $ \s -> s { _ranges = setXRanges' (_ranges s) }
where setXRanges' r
| sc == Log && min <= 0 = error "non-positive logarithmic range"
| otherwise = setXRanges sd r
setXRanges Lower (Ranges (Left _) yr) = Ranges (Left (Range sc min max)) yr
setXRanges Lower (Ranges (Right (_,xr)) yr) = Ranges (Right ((Range sc min max,xr))) yr
setXRanges Upper (Ranges (Left xr) yr) = Ranges (Right (xr,Range sc min max)) yr
setXRanges Upper (Ranges (Right (_,xr)) yr) = Ranges (Right (Range sc min max,xr)) yr
setRange YAxis sd sc min max = modify $ \s -> s { _ranges = setYRanges' (_ranges s) }
where setYRanges' r
| sc == Log && min <= 0 = error "non-positive logarithmic range"
| otherwise = setYRanges sd r
setYRanges Lower (Ranges xr (Left _)) = Ranges xr (Left (Range sc min max))
setYRanges Lower (Ranges xr (Right (_,yr))) = Ranges xr (Right ((Range sc min max,yr)))
setYRanges Upper (Ranges xr (Left yr)) = Ranges xr (Right (yr,Range sc min max))
setYRanges Upper (Ranges xr (Right (_,yr))) = Ranges xr (Right ((Range sc min max,yr)))
setRangeFromData :: AxisType -> AxisSide -> Scale -> Plot ()
setRangeFromData ax sd sc = do
ds <- gets _data
let ((xmin,xmax),(ymin,ymax)) = calculateRanges ds
case ax of
XAxis -> setRange ax sd sc (if sc == Log then if xmin == 0 then 1 else xmin else xmin) xmax
YAxis -> setRange ax sd sc (if sc == Log then if ymin == 0 then 1 else ymin else ymin) ymax
withAnnotations :: Annote () -> Plot ()
withAnnotations = annoteInPlot
clearAxes :: Plot ()
clearAxes = modify $ \s -> s { _axes = [] }
clearAxis :: AxisType -> AxisPosn -> Plot ()
clearAxis at axp = do
ax <- gets _axes
modify $ \s -> s { _axes =
filter (\(Axis at' axp' _ _ _ _ _ _) -> not (at == at' && axp == axp')) ax }
addAxis :: AxisType -> AxisPosn -> AX.Axis () -> Plot ()
addAxis at axp m = do
ax' <- gets _axes
o <- ask
let ax = execAxis m o (defaultAxis at axp)
modify $ \s -> s { _axes = ax : ax' }
withAxis :: AxisType -> AxisPosn -> AX.Axis () -> Plot ()
withAxis at axp m = do
axes' <- gets _axes
o <- ask
modify $ \s -> s { _axes =
map (\a@(Axis at' ap' _ _ _ _ _ _) -> if at == at' && axp == ap'
then execAxis m o a
else a) axes' }
barSetting :: BarSetting -> Plot ()
barSetting bc = modify $ \s -> s { _barconfig = bc }
sampleData :: SampleData -> Plot ()
sampleData sd = modify $ \s -> s { _sampledata = sd }
clearLegend :: Plot ()
clearLegend = withLegend $ L.clearLegend
setLegend :: L.LegendBorder -> L.LegendLocation -> L.LegendOrientation -> Plot ()
setLegend b l o = withLegend $ L.setLegend b l o
withLegendFormat :: T.Text () -> Plot ()
withLegendFormat f = withLegend $ L.withLegendFormat f
withLegend :: L.Legend () -> Plot ()
withLegend = legendInPlot
withData :: D.Data () -> Plot ()
withData = dataInPlot
setDataset :: D.Dataset a => a -> Plot ()
setDataset d = withData $ D.setDataSeries d
setSeriesType :: Int -> SeriesType -> Plot ()
setSeriesType i t = withData $ D.setSeriesType t i
setAllSeriesTypes :: SeriesType -> Plot ()
setAllSeriesTypes t = withData $ D.setAllSeriesTypes t
withSeriesFormat :: D.PlotFormats m => Int -> m () -> Plot ()
withSeriesFormat i f = withData $ D.withSeriesFormat i f
withAllSeriesFormats :: D.PlotFormats m => (Int -> m ()) -> Plot ()
withAllSeriesFormats f = withData $ D.withAllSeriesFormats f
findMinMax :: Abscissae -> Ordinates -> (Double,Double)
findMinMax (AbsFunction _) (OrdFunction _ f _) =
let v = f (linspace 100 (1,1))
in (minElement v,maxElement v)
findMinMax (AbsPoints _ x) (OrdFunction _ f _) =
let v = f x
in (minElement v,maxElement v)
findMinMax _ (OrdPoints _ (Plain o) _) = (minElement o,maxElement o)
findMinMax _ (OrdPoints _ (Error o _) _) = (minElement o,maxElement o)
findMinMax _ (OrdPoints _ (MinMax (o,p) _) _) =
(Prelude.min (minElement o) (minElement p)
,Prelude.max (maxElement o) (maxElement p))
abscMinMax :: Abscissae -> (Double,Double)
abscMinMax (AbsFunction _) = defaultXAxisSideLowerRange
abscMinMax (AbsPoints _ x) = (minElement x,maxElement x)
ordDim :: Ordinates -> Int
ordDim (OrdFunction _ _ _) = 1
ordDim (OrdPoints _ o _) = size $ getOrdData o
calculateRanges :: DataSeries -> ((Double,Double),(Double,Double))
calculateRanges (DS_Y ys) =
let xmax = maximum $ map (\(DecSeries o _) ->
fromIntegral $ ordDim o) $ A.elems ys
ym = unzip $ map (\(DecSeries o _) ->
findMinMax (AbsFunction id) o) $ A.elems ys
ymm = (minimum $ fst ym,maximum $ snd ym)
in ((0,xmax),ymm)
calculateRanges (DS_1toN x ys) =
let ym = unzip $ map (\(DecSeries o _) -> findMinMax x o) $ A.elems ys
ymm = (minimum $ fst ym,maximum $ snd ym)
xmm = abscMinMax x
in (xmm,ymm)
calculateRanges (DS_1to1 ys) =
let (xm',ym') = unzip $ A.elems ys
ym = unzip $ map (\(x,(DecSeries o _)) -> findMinMax x o) (zip xm' ym')
ymm = (minimum $ fst ym,maximum $ snd ym)
xm = unzip $ map abscMinMax xm'
xmm = (minimum $ fst xm,maximum $ snd xm)
in (xmm,ymm)
calculateRanges (DS_Surf m) =
((0,fromIntegral $ cols m),(fromIntegral $ rows m,0))