graphics-drawingcombinators-1.1.1: A functional interface to 2D drawing in OpenGL

Portabilityneeds GADTs and rank n types
Stabilityexperimental
MaintainerLuke Palmer <lrpalmer@gmail.com>

Graphics.DrawingCombinators

Contents

Description

Drawing combinators as a functional interface to 2D graphics using OpenGL.

This module is intended to be imported qualified, as in:

 import qualified Graphics.DrawingCombinators as Draw

Whenever possible, a denotational semantics for operations in this library is given. Read [[x]] as "the meaning of x".

Intuitively, an Image a is an infinite plane of pairs of colors and a's. The colors are what are drawn on the screen when you render, and the a's are what you can recover from coordinates using sample. The latter allows you to tell, for example, what a user clicked on.

The following discussion is about the associated data. If you are only interested in drawing, rather than mapping from coordinates to values, you can ignore the following and just use mappend and mconcat (Data.Monoid) to overlay images.

Wrangling the a's -- the associated data with each "pixel" -- is done using the Functor, Applicative, and Monoid instances.

The primitive Images such as circle and text all return Image Any objects. Any is just a wrapper around Bool, with (||) as its monoid operator. So e.g. the points inside the circle will have the value Any True, and those outside will have the value Any False. Returning Any instead of plain Bool allows you to use Images as a monoid, e.g. mappend to overlay two images. But if you are doing anything with sampling, you probably want to map this to something. Here is a drawing with two circles that reports which one was hit:

 twoCircles :: Image String
 twoCircles = liftA2 test (translate (-1,0) %% circle) (translate (1,0) %% circle)
   where 
   test (Any False) (Any False) = "Miss!"
   test (Any False) (Any True)  = "Hit Right!"
   test (Any True)  (Any False) = "Hit Left!"
   test (Any True)  (Any True)  = "Hit Both??!"

The last case would only be possible if the circles were overlapping.

Synopsis

Documentation

Basic types

data Image a Source

The type of images.

 [[Image a]] = R2 -> (Color, a)

The semantics of the instances are all consistent with type class morphism. I.e. Functor, Applicative, and Monoid act point-wise, using the Color monoid described below.

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 :: Image a -> R2 -> IO aSource

Sample the value of the image at a point.

 [[sample i p]] = snd ([[i]] p)

Even though this ought to be a pure function, it is not safe to unsafePerformIO it, because it uses OpenGL state.

Geometry

point :: R2 -> Image AnySource

A single "pixel" at the specified point.

 [[point p]] r | [[r]] == [[p]] = (one, Any True) 
               | otherwise      = (zero, Any False)

line :: R2 -> R2 -> Image AnySource

A line connecting the two given points.

regularPoly :: Integral a => a -> Image AnySource

A regular polygon centered at the origin with n sides.

circle :: Image AnySource

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]]

bezierCurve :: [R2] -> Image AnySource

A Bezier curve given a list of control points. It is a curve that begins at the first point in the list, ends at the last one, and smoothly interpolates between the rest. It is the empty image (mempty) if zero or one points are given.

Colors

data Color Source

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' = 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

Constructors

Color R R R R 

Instances

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 Sprite Source

A Sprite represents a finite bitmap image.

 [[Sprite]] = [-1,1]^2 -> Color

openSprite :: 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)

Text

openFont :: String -> IO FontSource

Load a TTF font from a file.

text :: Font -> String -> Image AnySource

The image representing some text rendered with a font. The baseline is at y=0, the text starts at x=0, and the height of a lowercase x is 1 unit.

textWidth :: Font -> String -> RSource

textWidth font str is the width of the text in text font str.