graphics-drawingcombinators-0.4: A functional interface to 2D drawing in OpenGLSource codeContentsIndex
Graphics.DrawingCombinators
Portabilityneeds GADTs and rank n types
Stabilityexperimental
MaintainerLuke Palmer <lrpalmer@gmail.com>
Contents
Basic types
Selection
Combinators
Initialization
Geometric Primitives
Transformations
Colors
Sprites (images from files)
Text
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 selection stuff (selectRegion, click) crashes GHCi, but it works okay compiled.

Synopsis
data Draw a
runDrawing :: Draw a -> IO ()
draw :: Draw a -> IO ()
type Vec2 = (Double, Double)
selectRegion :: Vec2 -> Vec2 -> Draw a -> IO (Maybe a)
click :: Vec2 -> Draw a -> IO (Maybe a)
over :: Draw a -> Draw a -> Draw a
overlay :: (a -> a -> a) -> Draw a -> Draw a -> Draw a
empty :: Draw a
init :: IO ()
point :: Vec2 -> Draw ()
line :: Vec2 -> Vec2 -> Draw ()
regularPoly :: Int -> Draw ()
circle :: Draw ()
convexPoly :: [Vec2] -> Draw ()
translate :: Vec2 -> Draw a -> Draw a
rotate :: Double -> Draw a -> Draw a
scale :: Double -> Double -> Draw a -> Draw a
type Color = (Double, Double, Double, Double)
color :: Color -> Draw a -> Draw a
colorFunc :: (Color -> Color) -> Draw a -> Draw a
data Sprite
data SpriteScaling
= ScaleMax
| ScaleWidth
| ScaleHeight
surfaceToSprite :: SpriteScaling -> Surface -> IO Sprite
imageToSprite :: SpriteScaling -> FilePath -> IO Sprite
sprite :: Sprite -> Draw ()
data Font
openFont :: String -> Int -> IO Font
text :: Font -> String -> Draw ()
Basic types
data Draw a Source
Draw a represents a drawing which returns a value of type a when selected.
show/hide Instances
runDrawing :: Draw a -> IO ()Source
Draw a Drawing 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).
draw :: Draw a -> IO ()Source
Like runDrawing, but clears the screen first, and sets up a little necessary OpenGL state. This is so you can use this module and pretend that OpenGL doesn't exist at all.
type Vec2 = (Double, Double)Source
Selection
selectRegion :: Vec2 -> Vec2 -> Draw a -> IO (Maybe a)Source
Given a bounding box, lower left and upper right in the default coordinate system (-1,-1) to (1,1), return the topmost drawing's value (with respect to over) intersecting that bounding box.
click :: Vec2 -> Draw a -> IO (Maybe a)Source
Combinators
over :: Draw a -> Draw a -> Draw aSource
overlay :: (a -> a -> a) -> Draw a -> Draw a -> Draw aSource
empty :: Draw aSource
Initialization
init :: IO ()Source
Perform initialization of the library. This can fail.
Geometric Primitives
point :: Vec2 -> Draw ()Source
Draw a single pixel at the specified point.
line :: Vec2 -> Vec2 -> Draw ()Source
Draw a line connecting the two given points.
regularPoly :: Int -> Draw ()Source
Draw a regular polygon centered at the origin with n sides.
circle :: Draw ()Source
Draw a unit circle centered at the origin. This is equivalent to regularPoly 24.
convexPoly :: [Vec2] -> Draw ()Source
Draw a convex polygon given by the list of points.
Transformations
translate :: Vec2 -> Draw a -> Draw aSource
Translate the given drawing by the given amount.
rotate :: Double -> Draw a -> Draw aSource
Rotate the given drawing counterclockwise by the given number of radians.
scale :: Double -> Double -> Draw a -> Draw aSource
scale x y d scales d by a factor of x in the horizontal direction and y in the vertical direction.
Colors
type Color = (Double, Double, Double, Double)Source
color :: Color -> Draw a -> Draw aSource
color c d sets the color of the drawing to exactly c.
colorFunc :: (Color -> Color) -> Draw a -> Draw aSource

colorFunc f d modifies all colors appearing in d with the function f. For example:

 colorFunc (\(r,g,b,a) -> (r,g,b,a/2)) d

Will draw d at greater transparency, regardless of the calls to color within.

Sprites (images from files)
data Sprite Source
A sprite represents a bitmap image.
data SpriteScaling Source
Indicate how a nonrectangular image is to be mapped to a sprite.
Constructors
ScaleMaxScaleMax will set the maximum of the height and width of the image to 1.
ScaleWidthScaleWidth will set the width of the image to 1, and scale the height appropriately.
ScaleHeightScaleHeight 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 -> Draw ()Source
Draw a sprite at the origin.
Text
data Font Source
openFont :: String -> Int -> IO FontSource
Load a TTF font from a file.
text :: Font -> String -> Draw ()Source
Draw a string using a font. The resulting string will have height 1.
Produced by Haddock version 2.6.0