wumpus-basic-0.24.0: Basic objects and system code built on Wumpus-Core.

PortabilityGHC
Stabilityhighly unstable
Maintainerstephen.tetley@gmail.com
Safe HaskellSafe-Infered

Wumpus.Basic.Kernel.Objects.Trail

Contents

Description

Trails - prototype paths. Less resource heavy than the Path object in Wumpus-Drawing.

CatTrail supports concatenation. AnaTrail supports initial displacement - this can account for drawing rectangles from their center, for example.

Synopsis

Trail types

data TrailSegment u Source

Trail segment - trails are prototype paths, so the are built from the usual straight lines and Bezier curves.

Constructors

TLine (Vec2 u) 
TCurve (Vec2 u) (Vec2 u) (Vec2 u) 

Instances

data CatTrail u Source

Trail supporting concatenation.

Instances

data AnaTrail u Source

Trail with an initial (undrawn) displacement - an anacrusis.

This allows trails to represent centered objects.

Instances

(Ord u, Tolerance u) => Eq (AnaTrail u) 
(Ord u, Tolerance u) => Ord (AnaTrail u) 
Show u => Show (AnaTrail u) 

Trail operations

renderAnaTrail :: InterpretUnit u => PathMode -> AnaTrail u -> LocGraphic uSource

Render an AnaTrail to make a drawable LocGraphic.

renderCatTrail :: InterpretUnit u => PathMode -> CatTrail u -> LocGraphic uSource

Render a CatTrail to make a drawable LocGraphic.

destrAnaTrail :: AnaTrail u -> (Vec2 u, [TrailSegment u])Source

Destructor for the opaque AnaTrail type.

destrCatTrail :: CatTrail u -> [TrailSegment u]Source

Destructor for the opaque CatTrail type.

modifyAna :: (Vec2 u -> Vec2 u) -> AnaTrail u -> AnaTrail uSource

trailIterateLocus :: Num u => [Vec2 u] -> AnaTrail uSource

Create a AnaTrail from the vector list - each vector in the input list iterates to the start point rather then the cumulative tip.

When the AnaTrail is run, the supplied point is the locus of the path and it does not form part of the path proper.

Like trailStartIsLocus, this constructor is typically used to make shape paths. Some shapes are easier to express as iterated displacements of the center rather than turtle drawing.

catcurve :: Vec2 u -> Vec2 u -> Vec2 u -> CatTrail uSource

orthoCatTrail :: Floating u => u -> u -> Radian -> CatTrail uSource

Alternative to catline, specifying the vector components rather the vector itself.

(cf. orthoVec from Wumpus-Core)

diffCurve :: Num u => Point2 u -> Point2 u -> Point2 u -> Point2 u -> CatTrail uSource

Form a Bezier CatTrail from the vectors between four control points.

diffLines :: Num u => [Point2 u] -> CatTrail uSource

Form a CatTrail from the linear segment joining the list of points.

Some configurations of vectors seem easier to specify using located points then making them coordinate free by taking the joining vectors.

Shape trails

rectangleTrail :: Fractional u => u -> u -> AnaTrail uSource

rectangleTrail : width * height -> AnaTrail

diamondTrail :: Num u => u -> u -> AnaTrail uSource

diamondTrail : half_width * half_height -> AnaTrail

polygonTrail :: Floating u => Int -> u -> AnaTrail uSource

polygonTrail : num_points * radius -> AnaTrail

wedgeTrail :: (Real u, Floating u) => u -> Radian -> Radian -> AnaTrail uSource

wedgeTrail : radius * apex_angle

Wedge is drawn at the apex.

Named Trail constructors

trail_up :: Num u => u -> CatTrail uSource

trail_theta_adj_grazing :: Floating u => u -> Radian -> Radian -> CatTrail uSource

Return the line a-o when supplied length of b-o and the grazing angle boa:

    a
    .\
    . \
  ..b..o

This is useful for building arrowhead vectors.

trail_theta_bkwd_adj_grazing :: Floating u => u -> Radian -> Radian -> CatTrail uSource

Return the line o-c when supplied length of b-o and the grazing angle boc:

  ..b..o
    . /
    ./
    c

This is useful for building arrowhead vectors.

semicircleTrail :: (Real u, Floating u) => ClockDirection -> Vec2 u -> CatTrail uSource

semicircleCW : base_vector -> CatTrail

Make an open semicircle from two Bezier curves.

Although this function produces an approximation of a semicircle, the approximation seems fine in practice.

semiellipseTrail :: (Real u, Floating u) => ClockDirection -> u -> Vec2 u -> CatTrail uSource

semicircleTrail : clock_direction * ry * base_vector -> CatTrail

Make an open semiellipse from two Bezier curves.

Although this function produces an approximation of a semiellipse, the approximation seems fine in practice.

minorCircleSweep :: (Real u, Floating u) => ClockDirection -> Radian -> u -> Radian -> CatTrail uSource

minorCircleSweep : clock_direction * angle * radius * inclination -> CatTrail

 ang should be in the range 0 < ang <= 90deg.

circleSweep :: (Real u, Floating u) => ClockDirection -> Radian -> u -> Radian -> CatTrail uSource

circleSweep : clock_direction * apex_angle * radius * inclination -> CatTrail

 ang should be in the range 0 < ang < 360deg.
 if   0 < ang <=  90 returns 1 segment
 if  90 < ang <= 180 returns 2 segments
 if 180 < ang <= 270 returns 3 segments
 if 270 < ang <  360 returns 4 segmenets

sineWave :: (Real u, Floating u) => Int -> u -> Radian -> CatTrail uSource

sineWave1 :: (Real u, Floating u) => u -> u -> Radian -> CatTrail uSource

One-phase sine wave. Height is parametric.

squiggleWave :: (Real u, Floating u) => Int -> u -> Radian -> CatTrail uSource

Proper semicircles do not make a good squiggle (it needs a bit of pinch).

triCurve :: Floating u => ClockDirection -> u -> u -> Radian -> CatTrail uSource

triCurve : clock_direction * base_width * height * base_inclination -> CatTrail

Curve in a triangle - base_width and height are expected to be positive.

rectCurve :: Floating u => ClockDirection -> u -> u -> Radian -> CatTrail uSource

rectCurve : clock_direction * base_width * height * base_inclination -> CatTrail

Curve in a rectangle.

trapCurve :: Floating u => ClockDirection -> u -> u -> Radian -> Radian -> CatTrail uSource

Curve in a trapezium.

bowCurve :: Floating u => ClockDirection -> u -> u -> Radian -> CatTrail uSource

Curve in half a bowtie.

wedgeCurve :: Floating u => ClockDirection -> u -> u -> Radian -> CatTrail uSource

Wedge curve formed inside a bowtie rotated by 90deg.

loopCurve :: Floating u => ClockDirection -> u -> u -> Radian -> CatTrail uSource

Variation of wedge curve that draws a loop.