diagrams-0.1: An EDSL for creating simple diagrams

Portabilityportable
Stabilityexperimental
Maintainerbyorgey@gmail.com
Safe HaskellNone

Graphics.Rendering.Diagrams.Types

Contents

Description

Type definitions and convenience functions for Graphics.Rendering.Diagrams, an embedded domain-specific language (EDSL) for creating simple diagrams.

Synopsis

Primitive types

data Diagram Source

Diagram is the core data type which describes a diagram. Diagrams may be constructed, transformed, combined, and ultimately rendered as an image.

Constructors

Empty

The empty diagram

Prim Shape

A primitive shape

Ann Attr Diagram

An annotated diagram

Compound Layout

A compound diagram

Union [Diagram]

A fully processed compound diagram, ready for rendering

Sized Point Diagram

An explicitly sized diagram whose bounding box takes up a particular amount of space.

data Color Source

The Color type represents colors in red-green-blue-alpha format, with each channel in the range 0-1. For a large list of predefined colors, see Graphics.Rendering.Diagrams.Colors.

Instances

rgbSource

Arguments

:: Double

red channel

-> Double

green channel

-> Double

blue channel

-> Color 

Construct an opaque (alpha = 1) color from RGB values specified as Doubles in the range 0-1.

rgbaSource

Arguments

:: Double

red channel

-> Double

green channel

-> Double

blue channel

-> Double

alpha (transparency) channel

-> Color 

Construct a color from RGBA values, specified as Doubles in the range 0-1.

type Point = (Double, Double)Source

Basic 2D points/vectors.

(.+) :: Point -> Point -> PointSource

Elementwise addition and multiplication for Points.

(.*) :: Point -> Point -> PointSource

Elementwise addition and multiplication for Points.

Shapes, attributes, and layouts

class ShapeClass s whereSource

The primitive shapes which can be used to build up a diagram. Every primitive shape must be an instance of ShapeClass.

Given a shape s, if shapeSize s evaluates to (w,h), then the drawing rendered by renderShape s should fit within a w by h rectangle centered at the origin.

You can create your own shape primitives by creating a new data type and making it an instance of ShapeClass. If you do so, you must be sure that your ShapeClass instance satisfies the law described above, on which the rendering engine relies in order to compute the proper positions for objects in a diagram. Otherwise, instances of your object in a diagram may extend outside the boundaries of the rendered image, or inadvertently overlap or be overlapped by other diagram elements. Of course, you are free to ignore this "law" as well; it will cause unexpected output at worst, and at best you may find some clever way to bend the system to your will. =)

Methods

shapeSize :: s -> PointSource

Calculate the size (the dimensions of a bounding box centered at the origin) of a shape.

renderShape :: s -> DiaRenderM ()Source

Calculate a cairo Render action to render a shape.

data Shape Source

Existential wrapper type for shapes.

Constructors

forall s . ShapeClass s => Shape s 

class AttrClass a whereSource

Attributes which can be applied as annotations to a Diagram, and change the way the Diagram is interpreted or rendered. Every attribute must be an instance of AttrClass.

Methods

attrSize :: a -> Point -> PointSource

Given an attribute and the size of the diagram to which it is an annotation, return a new size for the diagram. The default implementation is to simply return the size unchanged.

renderAttr :: a -> DiaRenderM (DiaRenderEnv -> DiaRenderEnv)Source

In order to implement this attribute, renderAttr may perform an action in the DiaRenderM monad, and return a function which produces a local modification to the render environment. The change produced by this function will only remain in effect for any sub-diagrams, and the environment will return to its former state afterwards.

data Attr Source

Existential wrapper type for attributes.

Constructors

forall a . AttrClass a => Attr a 

class Functor f => LayoutClass l f whereSource

All layouts must be instances of LayoutClass, along with an appropriate container type which must be an instance of Functor.

Methods

layoutSizeAndPos :: l -> f (Point, Diagram) -> (Point, [Diagram])Source

Given a layout and a container of (size, diagram) pairs (which have already had all subdiagrams appropriately positioned), compute the overall bounding box size for this layout, as well as a list of positioned subdiagrams.

data Layout Source

An existential wrapper type for layouts. A layout consists of a (possibly parameterized) layout type, along with a container of Diagrams.

Constructors

forall l f . LayoutClass l f => Layout l (f Diagram) 

Rendering

data DiaRenderEnv Source

An environment containing additional parameters to be made available while rendering, which for one reason or another are not or cannot be provided by the cairo Render monad itself. For example, cairo only tracks one current color, so we must track a fill color and stroke color separately.

defaultDiaRenderEnv :: DiaRenderEnvSource

The default rendering environment: transparent fill with 1-pixel black strokes.

newtype DiaRenderM a Source

The custom rendering monad: ReaderT DiaRenderEnv on top of cairo's Render monad.

Constructors

DRM (ReaderT DiaRenderEnv Render a) 

runDiaRenderM :: DiaRenderM a -> DiaRenderEnv -> Render aSource

Run a DiaRenderM action, given an initial rendering environment, to produce a cairo Render action.

c :: Render a -> DiaRenderM aSource

Lift a cairo Render action into a DiaRenderM action.