module Graphics.Rendering.Plot.Render (
render
, newFigureState
, updateFigureState
, renderFigureState
, OutputType(..)
, writeFigure
, writeFigureState
) where
import qualified Graphics.Rendering.Cairo as C
import qualified Graphics.Rendering.Pango as P
import Graphics.Rendering.Plot.Types
import Graphics.Rendering.Plot.Defaults
import Graphics.Rendering.Plot.Render.Types
import Graphics.Rendering.Plot.Render.Text
import Graphics.Rendering.Plot.Render.Plot
render :: Figure ()
-> (Int,Int)
-> C.Render ()
render g = (\(w,h) -> do
pc <- pango $ P.cairoCreateContext Nothing
to <- pango $ getDefaultTextOptions pc
let options' = Options defaultLineOptions
defaultPointOptions defaultBarOptions to
let (FigureState options _ figure) =
execFigure g (FigureState options' defaultSupply emptyFigure)
evalRender (renderFigure figure) (RenderEnv pc options)
(BoundingBox 0 0 (fromIntegral w) (fromIntegral h)))
newFigureState :: Figure () -> IO FigureState
newFigureState f = do
pc <- P.cairoCreateContext Nothing
to <- getDefaultTextOptions pc
let options' = Options defaultLineOptions
defaultPointOptions defaultBarOptions to
return $ execFigure f (FigureState options' defaultSupply emptyFigure)
updateFigureState :: FigureState -> Figure () -> FigureState
updateFigureState s f = execFigure f s
renderFigureState :: FigureState
-> (Int,Int)
-> C.Render ()
renderFigureState (FigureState options _ figure) = (\(w,h) -> do
pc <- pango $ P.cairoCreateContext Nothing
evalRender (renderFigure figure) (RenderEnv pc options)
(BoundingBox 0 0 (fromIntegral w) (fromIntegral h)))
writeFigure :: OutputType
-> FilePath
-> (Int,Int)
-> Figure ()
-> IO ()
writeFigure PNG fn wh f = withImageSurface wh (writeSurfaceToPNG fn (render f wh))
writeFigure PS fn wh f = writeSurface C.withPSSurface fn wh f
writeFigure PDF fn wh f = writeSurface C.withPDFSurface fn wh f
writeFigure SVG fn wh f = writeSurface C.withSVGSurface fn wh f
withImageSurface :: (Int,Int) -> (C.Surface -> IO ()) -> IO ()
withImageSurface (w,h) = C.withImageSurface C.FormatARGB32 w h
writeSurfaceToPNG :: FilePath -> C.Render () -> C.Surface -> IO ()
writeSurfaceToPNG fn r s = do
C.renderWith s r
C.surfaceWriteToPNG s fn
writeSurface :: (FilePath -> Double -> Double -> (C.Surface -> IO ()) -> IO ())
-> FilePath -> (Int,Int) -> Figure () -> IO ()
writeSurface rw fn (w,h) f = rw fn (fromIntegral w) (fromIntegral h)
(flip C.renderWith (render f (w,h)))
writeFigureState :: OutputType
-> FilePath
-> (Int,Int)
-> FigureState
-> IO ()
writeFigureState PNG fn wh f = withImageSurface wh
(writeSurfaceToPNG fn (renderFigureState f wh))
writeFigureState PS fn wh f = writeSurfaceFS C.withPSSurface fn wh f
writeFigureState PDF fn wh f = writeSurfaceFS C.withPDFSurface fn wh f
writeFigureState SVG fn wh f = writeSurfaceFS C.withSVGSurface fn wh f
writeSurfaceFS :: (FilePath -> Double -> Double -> (C.Surface -> IO ()) -> IO ())
-> FilePath -> (Int,Int) -> FigureState -> IO ()
writeSurfaceFS rw fn (w,h) f = rw fn (fromIntegral w) (fromIntegral h)
(flip C.renderWith (renderFigureState f (w,h)))
renderFigure :: FigureData -> Render ()
renderFigure (Figure b p t s d) = do
cairo $ do
C.save
setColour b
C.paint
C.restore
applyPads p
tx <- bbCentreWidth
ty <- bbTopHeight
(_,th) <- renderText t Centre TTop tx ty
bbLowerTop (th+textPad)
sx <- bbCentreWidth
sy <- bbTopHeight
(_,sh) <- renderText s Centre TTop sx sy
bbLowerTop (sh+textPad)
renderPlots d