Rasterific-0.7.4.2: A pure haskell drawing engine.

Safe HaskellNone
LanguageHaskell2010

Graphics.Rasterific.Immediate

Description

This module implements drawing primitives to draw directly into the output texture, without generating an intermediate scene representation.

If you need to draw complex scenes or plot an important set of data, this is the module you should use. The downside is that you must specify everything you need at each draw call, there is no API to help you propagate constants.

The "stroking" must be done using the functions of the Outline module.

Synopsis

Documentation

type DrawContext m px = StateT (MutableImage (PrimState m) px) m Source #

Monad used to describe the drawing context.

data DrawOrder px Source #

Reify a filling function call, to be able to manipulate them in a simpler fashion.

Constructors

DrawOrder 

Fields

Instances
Transformable (DrawOrder px) Source # 
Instance details

Defined in Graphics.Rasterific.Immediate

Methods

transform :: (Point -> Point) -> DrawOrder px -> DrawOrder px Source #

transformM :: Monad m => (Point -> m Point) -> DrawOrder px -> m (DrawOrder px) Source #

PlaneBoundable (DrawOrder px) Source # 
Instance details

Defined in Graphics.Rasterific.Immediate

orderToDrawing :: DrawOrder px -> Drawing px () Source #

Transform back a low level drawing order to a more high level Drawing

runDrawContext Source #

Arguments

:: (PrimMonad m, RenderablePixel px) 
=> Int

Rendering width

-> Int

Rendering height

-> px

Background color

-> DrawContext m px ()

Actual drawing computation

-> m (Image px) 

Start an image rendering. See fillWithTexture for an usage example. This function can work with either IO or ST.

fillWithTextureAndMask Source #

Arguments

:: (PrimMonad m, RenderablePixel px) 
=> FillMethod 
-> Texture px

Color/Texture used for the filling of the geometry

-> Texture (PixelBaseComponent px)

Texture used for the mask.

-> [Primitive]

Primitives to fill

-> DrawContext m px () 

Fill some geometry using a composition mask for visibility.

immediateDrawMaskExample :: Image PixelRGBA8
immediateDrawMaskExample = runST $
  runDrawContext 200 200 (PixelRGBA8 0 0 0 255) $
    forM_ [1 .. 10] $ \ix ->
       fillWithTextureAndMask FillWinding texture mask $
           rectangle (V2 10 (ix * 18 - 5)) 180 13
  where
    texture = uniformTexture $ PixelRGBA8 0 0x86 0xc1 255
    mask = sampledImageTexture
         $ runST
         $ runDrawContext 200 200 0
         $ fillWithTexture FillWinding (uniformTexture 255) maskGeometry

    maskGeometry = strokize 15 JoinRound (CapRound, CapRound)
                 $ circle (V2 100 100) 80

fillWithTexture Source #

Arguments

:: (PrimMonad m, RenderablePixel px) 
=> FillMethod 
-> Texture px

Color/Texture used for the filling

-> [Primitive]

Primitives to fill

-> DrawContext m px () 

Fill some geometry.

immediateDrawExample :: Image PixelRGBA8
immediateDrawExample = runST $
  runDrawContext 200 200 (PixelRGBA8 0 0 0 0) $
    fillWithTexture FillWinding texture geometry
  where
    circlePrimitives = circle (V2 100 100) 50
    geometry = strokize 4 JoinRound (CapRound, CapRound) circlePrimitives
    texture = uniformTexture (PixelRGBA8 255 255 255 255)

fillWithTextureNoAA Source #

Arguments

:: (PrimMonad m, RenderablePixel px) 
=> FillMethod 
-> Texture px

Color/Texture used for the filling

-> [Primitive]

Primitives to fill

-> DrawContext m px () 

Function identical to fillWithTexture but with anti-aliasing (and transparency) disabled.

fillOrder :: (PrimMonad m, RenderablePixel px) => DrawOrder px -> DrawContext m px () Source #

Render the drawing orders on the canvas.

textToDrawOrders Source #

Arguments

:: Dpi

Current output device resolution

-> Texture px

Texture to use if no texture is defined in the range

-> Point

Baseline position

-> [TextRange px]

Text description.

-> [DrawOrder px] 

Helper function transforming text range to draw order.