Chart-fltkhs-0.1.0.5: A backend for the Chart library for FLTKHS

Copyright(c) Michael Oswald 2019
LicenseBSD-3
Maintainermichael.oswald@onikudaki.net
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Chart.Backend.FLTKHS

Description

To render a Chart to a widget, it is best to create a custom widget and override it's draw method.

An example:

widget' <- widgetCustom
    (FL.Rectangle (Position (X 0) (Y 0)) (Size (Width width) (Height height)))
    Nothing
    drawChart
    defaultCustomWidgetFuncs

Here, drawChart is the provided draw method for the widget. A possible implementation could be this:

-- The char itself, to be used here with Graphics.Rendering.Chart.Easy
signal :: [Double] -> [(Double,Double)]
signal xs = [ (x,(sin (x*3.1415945) + 1)  2 * sin (x*3.14159/5)) | x <- xs ]

-- the overloaded drawing function
drawChart :: Ref Widget -> IO ()
drawChart widget = do
    -- determine a clipping area for the whole widget first
    rectangle' <- getRectangle widget

    -- with this clipping area, we draw the graph. This graph is taken from Example 1 https://github.com/timbod7/haskell-chart/wiki/example-1
    -- from the Chart library
    withFlClip rectangle' $
        renderToWidgetEC widget $ do
            layout_title .= "Amplitude Modulation"
            setColors [opaque blue, opaque red]
            plot (line "am" [signal [0,(0.5)..400]])
            plot (points "am points" (signal [0,7..400]))
Synopsis

Documentation

renderToWidget :: Ref Widget -> Renderable a -> IO (PickFn a) Source #

Render a Renderable to a widget. It renders to the full widget (it gets the rectangle of the widgets area) and uses that as the sizes for rendering.

renderToWidgetOffscreen :: Ref Widget -> FlOffscreen -> Renderable a -> IO (PickFn a) Source #

Render a Renderable to a widget, using an FlOffscreen buffer for double buffering. It renders to the full widget (it gets the rectangle of the widgets area) and uses that as the sizes for rendering. The offscreen buffer needs to be allocated beforehand and needs to have the necessary size (see FLTKs documentation for using the offscreen rendering)

renderToWidgetEC :: (Default r, ToRenderable r) => Ref Widget -> EC r () -> IO () Source #

Render a Chart created with the statefull Graphics.Rendering.Chart.Easy API. Calls renderToWidget internally

renderToWidgetOffscreenEC :: (Default r, ToRenderable r) => Ref Widget -> FlOffscreen -> EC r () -> IO () Source #

Render a Chart created with the statefull Graphics.Rendering.Chart.Easy API. Calls renderToWidgetOffscreen internally, so it also needs a FlOffscreen buffer as argument

runBackend :: FLTKHSEnv -> BackendProgram a -> IO a Source #

Run this backends renderer

data FLTKHSEnv Source #

The environment internally used for drawing

defaultEnv :: AlignmentFns -> FLTKHSEnv Source #

Provide a default environment. The AlignmentFns used should be bitmapAlignmentFns from the Chart library

withFlClip :: Rectangle -> IO a -> IO a Source #

Performs a drawing action in a widget within a defined clipping rectangle. This is a convenience function, as FLTKHS is quite statefull and a flcPushClip must be closed by a flcPopClip. So this function exactly provides this, while executing the given drawing action in between push and pop