| Portability | needs GADTs and rank n types |
|---|---|
| Stability | experimental |
| Maintainer | Luke Palmer <lrpalmer@gmail.com> |
Graphics.DrawingCombinators
Description
Drawing combinators as a functional interface to OpenGL (for 2D drawings only... for now).
This module is intended to be imported qualified, as in:
import Graphics.DrawingCombinators as Draw
It is recommended that you use this module in combination
with SDL; it has not been tested in any other environments.
For some reason the GL picking stuff (sample) crashes GHCi,
but it works okay compiled.
- module Graphics.DrawingCombinators.Affine
- data Image a
- render :: Image a -> IO ()
- clearRender :: Image a -> IO ()
- sample :: R2 -> Image a -> IO a
- init :: IO ()
- point :: R2 -> Image Any
- line :: R2 -> R2 -> Image Any
- regularPoly :: Int -> Image Any
- circle :: Image Any
- convexPoly :: [R2] -> Image Any
- (%%) :: Affine -> Image a -> Image a
- data Color = Color R R R R
- modulate :: Color -> Color -> Color
- tint :: Color -> Image a -> Image a
- data Sprite
- data SpriteScaling
- = ScaleMax
- | ScaleWidth
- | ScaleHeight
- surfaceToSprite :: SpriteScaling -> Surface -> IO Sprite
- imageToSprite :: SpriteScaling -> FilePath -> IO Sprite
- sprite :: Sprite -> Image Any
- data Font
- openFont :: String -> Int -> IO Font
- text :: Font -> String -> Image Any
Documentation
Basic types
The type of images.
[[Image a]] = R2 -> (Color, a)
render :: Image a -> IO ()Source
Draw an Image on the screen in the current OpenGL coordinate system (which, in absense of information, is (-1,-1) in the lower left and (1,1) in the upper right).
clearRender :: Image a -> IO ()Source
Like render, but clears the screen first. This is so
you can use this module and pretend that OpenGL doesn't
exist at all.
Selection
sample :: R2 -> Image a -> IO aSource
Sample the value of the image at a point.
[[sample p i]] = snd ([[i]] [[p]])
Initialization
Geometry
The geomertic combinators all return an Image Any. Any
is a wrapper around Bool with (False, (||)) as its Monoid.
This is so you can use the Monoid instance on Image to
automatically get the union of primitives. So:
circle `mappend` (translate (1,0) %% circle)
Will have the value Any True when either of the circles is
sampled. To extract the Bool, use getAny, or pattern match
on Any True and Any False instead of True and False.
point :: R2 -> Image AnySource
A single pixel at the specified point.
[[point p]] r | [[r]] == [[p]] = (one, Any True)
| otherwise = (zero, Any False)
regularPoly :: Int -> Image AnySource
A regular polygon centered at the origin with n sides.
An (imperfect) unit circle centered at the origin. Implemented as:
circle = regularPoly 24
convexPoly :: [R2] -> Image AnySource
A convex polygon given by the list of points.
(%%) :: Affine -> Image a -> Image aSource
Transform an image by an Affine transformation.
[[tr % im]] = [[im]] . inverse [[tr]]
Colors
Color is defined in the usual computer graphics sense, of a 4 vector containing red, green, blue, and alpha.
The Monoid instance is given by alpha transparency blending, so:
mempty = Color 1 1 1 1 mappend c@(Color _ _ _ a) c'@(Color _ _ _ a') = a*c + (1-a)*c'
Where multiplication is componentwise. In the semantcs the
values zero and one are used, which are defined as:
zero = Color 0 0 0 0 one = Color 1 1 1 1
modulate :: Color -> Color -> ColorSource
Modulate two colors by each other.
modulate (Color r g b a) (Color r' g' b' a')
= Color (r*r') (g*g') (b*b') (a*a')
tint :: Color -> Image a -> Image aSource
Tint an image by a color; i.e. modulate the colors of an image by a color.
[[tint c im]] = first (modulate c) . [[im]]
where first f (x,y) = (f x, y)
Sprites (images from files)
data SpriteScaling Source
Indicate how a non-square image is to be mapped to a sprite.
Constructors
| ScaleMax | ScaleMax will set the maximum of the height and width of the image to 1. |
| ScaleWidth | ScaleWidth will set the width of the image to 1, and scale the height appropriately. |
| ScaleHeight | ScaleHeight will set the height of the image to 1, and scale the width appropriately. |
surfaceToSprite :: SpriteScaling -> Surface -> IO SpriteSource
Convert an SDL.Surface to a Sprite.
imageToSprite :: SpriteScaling -> FilePath -> IO SpriteSource
Load an image from a file and create a sprite out of it.
sprite :: Sprite -> Image AnySource
The image of a sprite at the origin.
[[sprite s]] p | p `elem` [-1,1]^2 = ([[s]] p, Any True)
| otherwise = (zero, Any False)