Rasterific-0.2: A pure haskell drawing engine.

Safe HaskellNone

Graphics.Rasterific.Texture

Contents

Description

Module describing the various filling method of the geometric primitives.

All points coordinate given in this module are expressed final image pixel coordinates.

Synopsis

Documentation

type Texture px = SamplerRepeat -> Float -> Float -> pxSource

A texture is just a function which given pixel coordinate give back a pixel. The float coordinate type allow for transformations to happen in the pixel space.

type Gradient px = [(Float, px)]Source

A gradient definition is just a list of stop and pixel values. For instance for a simple gradient of black to white, the finition would be :

 [(0, PixelRGBA8 0 0 0 255), (1, PixelRGBA8 255 255 255 255)]

the first stop value must be zero and the last, one.

withSampler :: SamplerRepeat -> Texture px -> Texture pxSource

Set the repeat pattern of the texture (if any). With padding:

 withTexture (sampledImageTexture textureImage) $
   fill $ rectangle (V2 0 0) 200 200

With repeat:

 withTexture (withSampler SamplerRepeat $
                 sampledImageTexture textureImage) $
     fill $ rectangle (V2 0 0) 200 200

With reflect:

 withTexture (withSampler SamplerReflect $
                 sampledImageTexture textureImage) $
     fill $ rectangle (V2 0 0) 200 200

uniformTextureSource

Arguments

:: px

The color used for all the texture.

-> Texture px 

The uniform texture is the simplest texture of all: an uniform color.

Texture kind

linearGradientTextureSource

Arguments

:: (Pixel px, Modulable (PixelBaseComponent px)) 
=> Gradient px

Gradient description.

-> Point

Linear gradient start point.

-> Point

Linear gradient end point.

-> Texture px 

Linear gradient texture.

 let gradDef = [(0, PixelRGBA8 0 0x86 0xc1 255)
               ,(0.5, PixelRGBA8 0xff 0xf4 0xc1 255)
               ,(1, PixelRGBA8 0xFF 0x53 0x73 255)] in
 withTexture (linearGradientTexture SamplerPad gradDef
                        (V2 40 40) (V2 130 130)) $
    fill $ circle (V2 100 100) 100

radialGradientTextureSource

Arguments

:: (Pixel px, Modulable (PixelBaseComponent px)) 
=> Gradient px

Gradient description

-> Point

Radial gradient center

-> Float

Radial gradient radius

-> Texture px 

Radial gradient texture

 let gradDef = [(0, PixelRGBA8 0 0x86 0xc1 255)
               ,(0.5, PixelRGBA8 0xff 0xf4 0xc1 255)
               ,(1, PixelRGBA8 0xFF 0x53 0x73 255)] in
 withTexture (radialGradientTexture SamplerPad gradDef
                    (V2 100 100) 75) $
    fill $ circle (V2 100 100) 100

radialGradientWithFocusTextureSource

Arguments

:: (Pixel px, Modulable (PixelBaseComponent px)) 
=> Gradient px

Gradient description

-> Point

Radial gradient center

-> Float

Radial gradient radius

-> Point

Radial gradient focus point

-> Texture px 

Radial gradient texture with a focus point.

 let gradDef = [(0, PixelRGBA8 0 0x86 0xc1 255)
               ,(0.5, PixelRGBA8 0xff 0xf4 0xc1 255)
               ,(1, PixelRGBA8 0xFF 0x53 0x73 255)] in
 withTexture (radialGradientWithFocusTexture SamplerPad gradDef
                    (V2 100 100) 75 (V2 70 70) ) $
    fill $ circle (V2 100 100) 100

imageTexture :: forall px. Pixel px => Image px -> Texture pxSource

Use another image as a texture for the filling. This texture use the nearest filtering, AKA no filtering at all.

sampledImageTexture :: forall px. (Pixel px, Modulable (PixelBaseComponent px)) => Image px -> Texture pxSource

Use another image as a texture for the filling. Contrary to imageTexture, this function perform a bilinear filtering on the texture.

Texture manipulation

modulateTextureSource

Arguments

:: (Pixel px, Modulable (PixelBaseComponent px)) 
=> Texture px

The full blown texture.

-> Texture (PixelBaseComponent px)

A greyscale modulation texture.

-> Texture px

The resulting texture.

Perform a multiplication operation between a full color texture and a greyscale one, used for clip-path implementation.

transformTexture :: Transformation -> Texture px -> Texture pxSource

Transform the coordinates used for texture before applying it, allow interesting transformations.

 withTexture (withSampler SamplerRepeat $
             transformTexture (rotateCenter 1 (V2 0 0) <> 
                               scale 0.5 0.25)
             $ sampledImageTexture textureImage) $
     fill $ rectangle (V2 0 0) 200 200