gelatin-0.1.0.1: A graphics description language.

Safe HaskellNone
LanguageHaskell2010

Gelatin.Picture

Contents

Description

A picture in gelatin's context is a collection of vertices, organized into geometries of triangles, beziers, triangle strips, triangle fans and polylines. The vertices of these pictures can be anything, but the currently available backends already support these vertices:

  • (V2 Float, V4 Float), ie. colored points in 2d space
  • (V2 Float, V2 Float), ie. textured points in 2d space

Synopsis

Defining Vertex Data

newtype VerticesT a m b Source #

A monad transformer for defining geometry.

Constructors

Vertices 

Fields

Instances

MonadTrans (VerticesT a) Source # 

Methods

lift :: Monad m => m a -> VerticesT a m a #

Monad m => Monad (VerticesT a m) Source # 

Methods

(>>=) :: VerticesT a m a -> (a -> VerticesT a m b) -> VerticesT a m b #

(>>) :: VerticesT a m a -> VerticesT a m b -> VerticesT a m b #

return :: a -> VerticesT a m a #

fail :: String -> VerticesT a m a #

Functor m => Functor (VerticesT a m) Source # 

Methods

fmap :: (a -> b) -> VerticesT a m a -> VerticesT a m b #

(<$) :: a -> VerticesT a m b -> VerticesT a m a #

Monad m => Applicative (VerticesT a m) Source # 

Methods

pure :: a -> VerticesT a m a #

(<*>) :: VerticesT a m (a -> b) -> VerticesT a m a -> VerticesT a m b #

(*>) :: VerticesT a m a -> VerticesT a m b -> VerticesT a m b #

(<*) :: VerticesT a m a -> VerticesT a m b -> VerticesT a m a #

MonadIO m => MonadIO (VerticesT a m) Source # 

Methods

liftIO :: IO a -> VerticesT a m a #

runVerticesT :: (Monad m, Unbox a) => VerticesT a m b -> m (Vector a) Source #

Extract the raw Vector of vertices monadically.

type Vertices a = VerticesT a Identity () Source #

A pure context for defining geometry. This is VerticesT parameterized over Identity.

runVertices :: Unbox a => Vertices a -> Vector a Source #

Extract the raw Vector of vertices.

tri :: (Monad m, Unbox a) => a -> a -> a -> VerticesT a m () Source #

Add a triangle of vertices.

bez :: (Monad m, Unbox a) => a -> a -> a -> VerticesT a m () Source #

Add a bezier of vertices. This is an alias of tri but looks better in the context of drawing beziers.

to :: (Monad m, Unbox a) => a -> VerticesT a m () Source #

Add one vertex.

addVertexList :: (Monad m, Unbox a) => [a] -> VerticesT a m () Source #

Add vertices from a list.

segment :: (Monad m, Unbox a) => a -> a -> VerticesT a m () Source #

Add two vertices.

mapVertices :: (Monad m, Unbox a, Unbox c) => (a -> c) -> VerticesT a m b -> VerticesT c m () Source #

Map all the vertices in the computation.

Defining Geometry (Vertex Data + Drawing Operation)

data RawGeometry a Source #

Mixed drawing types roughly corresponding to OpenGL's draw modes.

Constructors

RawTriangles (Vector a)

A collection of points known to be triangles.

RawBeziers (Vector a)

A collection of points known to be beziers.

RawTriangleStrip (Vector a)

A collection of points known to be a triangle strip.

RawTriangleFan (Vector a)

A collection of points known to be a triangle fan.

RawLine (Vector a)

A collection of points known to be a polyline. *Note* that in the future polylines will be expressed in terms of the other constructors.

mapRawGeometry :: (Unbox a, Unbox b) => (a -> b) -> RawGeometry a -> RawGeometry b Source #

Map all the vertices within a RawGeometry.

newtype GeometryT a m b Source #

A monad transformer for defining collections of geometries, specifically mixed collections of triangles, beziers, strips, fans and polylines.

Constructors

Geometry 

Fields

Instances

MonadTrans (GeometryT a) Source # 

Methods

lift :: Monad m => m a -> GeometryT a m a #

Monad m => Monad (GeometryT a m) Source # 

Methods

(>>=) :: GeometryT a m a -> (a -> GeometryT a m b) -> GeometryT a m b #

(>>) :: GeometryT a m a -> GeometryT a m b -> GeometryT a m b #

return :: a -> GeometryT a m a #

fail :: String -> GeometryT a m a #

Functor m => Functor (GeometryT a m) Source # 

Methods

fmap :: (a -> b) -> GeometryT a m a -> GeometryT a m b #

(<$) :: a -> GeometryT a m b -> GeometryT a m a #

Monad m => Applicative (GeometryT a m) Source # 

Methods

pure :: a -> GeometryT a m a #

(<*>) :: GeometryT a m (a -> b) -> GeometryT a m a -> GeometryT a m b #

(*>) :: GeometryT a m a -> GeometryT a m b -> GeometryT a m b #

(<*) :: GeometryT a m a -> GeometryT a m b -> GeometryT a m a #

MonadIO m => MonadIO (GeometryT a m) Source # 

Methods

liftIO :: IO a -> GeometryT a m a #

runGeometryT :: Monad m => GeometryT a m b -> m (Vector (RawGeometry a)) Source #

Extract the raw Vector of geometries monadically.

type Geometry a = GeometryT a Identity () Source #

A pure context for defining collections of geometry.

runGeometry :: Geometry a -> Vector (RawGeometry a) Source #

Extract the raw Vector of geometries.

triangles :: (Unbox a, Monad m) => VerticesT a m () -> GeometryT a m () Source #

Define and add some triangles.

beziers :: (Monad m, Unbox a) => VerticesT a m () -> GeometryT a m () Source #

Define and add some beziers.

strip :: (Monad m, Unbox a) => VerticesT a m () -> GeometryT a m () Source #

Define and add a triangle strip.

fan :: (Monad m, Unbox a) => VerticesT a m () -> GeometryT a m () Source #

Define and add a triangle fan.

line :: (Monad m, Unbox a) => VerticesT a m () -> GeometryT a m () Source #

Define and add a polyline.

mapGeometry :: (Monad m, Unbox a, Unbox c) => (a -> c) -> GeometryT a m b -> GeometryT c m () Source #

Map all the vertices within all geometries in the computation.

The Picture API

type PictureT tex vert = StateT (PictureData tex vert) Source #

A monad transformer computation that defines a picture.

runPictureT :: PictureT t v m a -> m (a, PictureData t v) Source #

Extract the result and PictureData from a PictureT computation.

type Picture t v = PictureT t v Identity Source #

PictureT parameterized over Identity.

runPicture :: Picture t v a -> (a, PictureData t v) Source #

Extract the result and PictureData of a pure Picture computation.

setRawGeometry :: Monad m => Vector (RawGeometry v) -> PictureT t v m () Source #

Set the geometries of the PictureT with a Vector explicitly.

getRawGeometry :: Monad m => PictureT t v m (Vector (RawGeometry v)) Source #

Extract the current geometries of the PictureT as a Vector.

setGeometry :: Monad m => GeometryT v m () -> PictureT t v m () Source #

Define and set the geometries of the PictureT.

setStroke :: Monad m => [StrokeAttr] -> PictureT t v m () Source #

Set the stroke attributes of the PictureT.

getStroke :: Monad m => PictureT t v m [StrokeAttr] Source #

Get the current stroke attributes of the PictureT.

setTextures :: Monad m => [t] -> PictureT t v m () Source #

Set the textures contained within the PictureT. These textures [t] are backend dependent.

getTextures :: Monad m => PictureT t v m [t] Source #

Get the current textures within the PictureT.

setRenderingOptions :: Monad m => [RenderingOption] -> PictureT t v m () Source #

Set any special rendering options. Nothing to see here.

getRenderingOptions :: Monad m => PictureT t v m [RenderingOption] Source #

Get any special rendering options. Nothing to see here.

An example of creating a Picture

Here is an example of drawing two colored beziers into a 2d picture using colors from the Color module:

bezierPicture :: Picture tex (V2 Float, V4 Float) ()
bezierPicture = setGeometry $ beziers $ do
  bez (V2 0   0,   white) (V2 200 0, blue) (V2 200 200, green)
  bez (V2 400 200, white) (V2 400 0, blue) (V2 200 0,   green)

Here is the rendering of that picture after being compiled by a backend:

As you can see the two beziers have different fill directions, the first is fill inner while the second is fill outer. This is determined by the bezier's winding.

Measuring Pictures (2d)

mapPictureVertices :: (Monad m, Unbox v, Unbox s) => (v -> s) -> PictureT t v m (Vector s) Source #

Evaluates the current geometry in the PictureT, mapping each vertex.

pictureBounds2 :: (Monad m, Unbox v) => (v -> V2 Float) -> PictureT t v m (V2 Float, V2 Float) Source #

Determines the bounds of a PictureT defined in 2d space.

pictureSize2 :: (Monad m, Unbox v) => (v -> V2 Float) -> PictureT t v m (V2 Float) Source #

Determines the size of a PictureT defined in 2d space.

pictureOrigin2 :: (Monad m, Unbox v) => (v -> V2 Float) -> PictureT t v m (V2 Float) Source #

Determines the origin of a PictureT defined in 2d space.

pictureCenter2 :: (Monad m, Unbox v) => (v -> V2 Float) -> PictureT t v m (V2 Float) Source #

Determines the center point of a PictureT defined in 2d space.

Measuring Pictures (3d)

pictureBounds3 :: (Monad m, Unbox v) => (v -> V3 Float) -> PictureT t v m BCube Source #

Determines the bounds of a PictureT defined in 3d space.

pictureSize3 :: (Monad m, Unbox v) => (v -> V3 Float) -> PictureT t v m (V3 Float) Source #

Determines the size of a PictureT defined in 3d space.

pictureOrigin3 :: (Monad m, Unbox v) => (v -> V3 Float) -> PictureT t v m (V3 Float) Source #

Determines the origin of a PictureT defined in 3d space.

pictureCenter3 :: (Monad m, Unbox v) => (v -> V3 Float) -> PictureT t v m (V3 Float) Source #

Determines the center point of a PictureT defined in 3d space.

Underlying PictureData Exported for renderers

data RenderingOption Source #

Some special rendering options. Not much to see here.

Constructors

StencilMaskOption 

data PictureData texture vertex Source #

Underlying picture data used to accumulate a visible picture.

Constructors

PictureData 

Fields