wumpus-basic-0.5.0: Common drawing utilities built on wumpus-core.Source codeContentsIndex
Wumpus.Basic.Graphic
PortabilityGHC
Stabilityhighly unstable
Maintainerstephen.tetley@gmail.com
Contents
Type aliases
General combinators
Operations
Graphic primitives
Displacement
Grid
Description

Graphic type and opertations

** WARNING ** - this module is highly experimental, and may change significantly or even be dropped from future revisions.

Synopsis
type Graphic u = H (Primitive u)
type DGraphic = Graphic Double
type GraphicF u = Point2 u -> Graphic u
type DGraphicF = GraphicF Double
cc :: (r1 -> a -> ans) -> (r1 -> r2 -> a) -> r1 -> r2 -> ans
supply :: u -> (u -> a) -> a
drawGraphic :: (Real u, Floating u, FromPtSize u) => Graphic u -> Maybe (Picture u)
drawGraphicU :: (Real u, Floating u, FromPtSize u) => Graphic u -> Picture u
wrapG :: Primitive u -> Graphic u
emptyG :: Graphic u
textline :: (TextLabel t, Num u) => t -> String -> GraphicF u
straightLine :: (Stroke t, Fractional u) => t -> Vec2 u -> GraphicF u
strokedRectangle :: (Stroke t, Fractional u) => t -> u -> u -> GraphicF u
filledRectangle :: (Fill t, Fractional u) => t -> u -> u -> GraphicF u
rectanglePath :: Num u => u -> u -> Point2 u -> PrimPath u
strokedCircle :: (Stroke t, Floating u) => t -> Int -> u -> GraphicF u
filledCircle :: (Fill t, Floating u) => t -> Int -> u -> GraphicF u
disk :: (Ellipse t, Fractional u) => t -> u -> GraphicF u
type Point2T u = Point2 u -> Point2 u
type DPoint2T = Point2T Double
positionWith :: Point2T u -> (Point2 u -> a) -> Point2 u -> a
disp :: Num u => u -> u -> Point2T u
vdisp :: Num u => u -> Point2T u
hdisp :: Num u => u -> Point2T u
data Rectangle u = Rectangle {
rect_width :: !u
rect_height :: !u
}
type DRectangle = Rectangle Double
grid :: (Stroke t, RealFrac u) => t -> u -> u -> Rectangle u -> GraphicF u
border :: (Stroke t, Num u) => t -> Rectangle u -> GraphicF u
type RectangleLoc u = (Rectangle u, Point2 u)
type DRectangleLoc = RectangleLoc Double
withinRectangleLoc :: (Num u, Ord u) => Point2 u -> RectangleLoc u -> Bool
Type aliases
type Graphic u = H (Primitive u)Source
Note - this representation allows for zero, one or more Primitives to be collected together.
type DGraphic = Graphic DoubleSource
type GraphicF u = Point2 u -> Graphic uSource
type DGraphicF = GraphicF DoubleSource
General combinators
cc :: (r1 -> a -> ans) -> (r1 -> r2 -> a) -> r1 -> r2 -> ansSource

Composition operator...

 cc f g = \x y -> f x (g x y)
supply :: u -> (u -> a) -> aSource
Reverse application.
Operations
drawGraphic :: (Real u, Floating u, FromPtSize u) => Graphic u -> Maybe (Picture u)Source
Note - a Picture cannot be empty whereas a Graphic can. Hence this function returns via Maybe.
drawGraphicU :: (Real u, Floating u, FromPtSize u) => Graphic u -> Picture uSource
Unsafe version of drawGraphic - this function throws an error when the graphic is empty.
wrapG :: Primitive u -> Graphic uSource
Lift a Primitive to a Graphic
emptyG :: Graphic uSource
The empty graphic.
Graphic primitives
textline :: (TextLabel t, Num u) => t -> String -> GraphicF uSource

Text should not contain newlines.

Note the supplied point is the 'left-baseline'.

straightLine :: (Stroke t, Fractional u) => t -> Vec2 u -> GraphicF uSource
Vector is applied to the point.
strokedRectangle :: (Stroke t, Fractional u) => t -> u -> u -> GraphicF uSource
Supplied point is center.
filledRectangle :: (Fill t, Fractional u) => t -> u -> u -> GraphicF uSource
Supplied point is center.
rectanglePath :: Num u => u -> u -> Point2 u -> PrimPath uSource
Supplied point is bottom-left.
strokedCircle :: (Stroke t, Floating u) => t -> Int -> u -> GraphicF uSource

strokedCircle : stroked_props * num_subs * radius -> GraphicF

Draw a stroked circle made from Bezier curves. num_subs is the number of subdivisions per quadrant.

The result is a HOF (GraphicF :: Point -> Graphic) where the point is the center.

filledCircle :: (Fill t, Floating u) => t -> Int -> u -> GraphicF uSource

filledCircle : fill_props * num_subs * radius -> GraphicF

Draw a filled circle made from Bezier curves. num_subs is the number of subdivisions per quadrant.

The result is a HOF (GraphicF :: Point -> Graphic) where the point is the center.

disk :: (Ellipse t, Fractional u) => t -> u -> GraphicF uSource

disk is drawn with Wumpus-Core's ellipse primitive.

This is a efficient representation of circles using PostScript's arc or SVG's circle in the generated output. However, stroked-circles do not draw well after non-uniform scaling - the line width is scaled as well as the shape.

For stroked circles that can be scaled, consider making the circle from Bezier curves.

Displacement
type Point2T u = Point2 u -> Point2 uSource
type DPoint2T = Point2T DoubleSource
positionWith :: Point2T u -> (Point2 u -> a) -> Point2 u -> aSource
disp :: Num u => u -> u -> Point2T uSource
vdisp :: Num u => u -> Point2T uSource
hdisp :: Num u => u -> Point2T uSource
Grid
data Rectangle u Source
Constructors
Rectangle
rect_width :: !u
rect_height :: !u
show/hide Instances
Eq u => Eq (Rectangle u)
Ord u => Ord (Rectangle u)
Show u => Show (Rectangle u)
type DRectangle = Rectangle DoubleSource
grid :: (Stroke t, RealFrac u) => t -> u -> u -> Rectangle u -> GraphicF uSource

grid : stroke_props * xstep * ystep * boundary_rect -> GraphicF

The result is a HOF (GraphicF :: Point -> Graphic) where the point is bottom-left.

border :: (Stroke t, Num u) => t -> Rectangle u -> GraphicF uSource

border : stroke_props * boundary_rect -> GraphicF

The result is a HOF (GraphicF :: Point -> Graphic) where the point is bottom-left.

type RectangleLoc u = (Rectangle u, Point2 u)Source
type DRectangleLoc = RectangleLoc DoubleSource
withinRectangleLoc :: (Num u, Ord u) => Point2 u -> RectangleLoc u -> BoolSource
Produced by Haddock version 2.6.1