hcg-minus-0.15: haskell cg (minus)

Safe HaskellSafe-Inferred
LanguageHaskell98

Data.CG.Minus

Contents

Description

CG library (minus).

Synopsis

Types

data Pt a Source

Two-dimensional point.

Pt are Num, pointwise, ie:

Pt 1 2 + Pt 3 4 == Pt 4 6
Pt 1 2 * Pt 3 4 == Pt 3 8
negate (Pt 0 1) == Pt 0 (-1)
abs (Pt (-1) 1) == Pt 1 1
signum (Pt (-1/2) (1/2)) == Pt (-1) 1

Constructors

Pt 

Fields

pt_x :: a
 
pt_y :: a
 

Instances

Eq a => Eq (Pt a) 
Num a => Num (Pt a) 
Ord a => Ord (Pt a) 
Show a => Show (Pt a) 

data Vc a Source

Two-dimensional vector. Vector are Num in the same manner as Pt.

Constructors

Vc 

Fields

vc_x :: a
 
vc_y :: a
 

Instances

Eq a => Eq (Vc a) 
Num a => Num (Vc a) 
Ord a => Ord (Vc a) 
Show a => Show (Vc a) 

data Ln a Source

Two-dimensional line.

Constructors

Ln 

Fields

ln_start :: Pt a
 
ln_end :: Pt a
 

Instances

Eq a => Eq (Ln a) 
Ord a => Ord (Ln a) 
Show a => Show (Ln a) 

type Ls a = [Pt a] Source

Line segments.

data Wn a Source

Window, given by a lower left Pt and an extent Vc.

Constructors

Wn 

Fields

wn_ll :: Pt a
 
wn_ex :: Vc a
 

Instances

Eq a => Eq (Wn a) 
Show a => Show (Wn a) 

type R = Double Source

Real number, synonym for Double.

R(eal) functions

epsilon :: Floating n => n Source

Epsilon.

(~=) :: (Floating a, Ord a) => a -> a -> Bool Source

Is absolute difference less than epsilon.

r_to_radians :: R -> R Source

Degrees to radians.

map r_to_radians [-180,-90,0,90,180] == [-pi,-pi/2,0,pi/2,pi]

r_from_radians :: R -> R Source

Radians to degrees, inverse of r_to_radians.

map r_from_radians [-pi,-pi/2,0,pi/2,pi] == [-180,-90,0,90,180]

r_constrain :: (R, R) -> R -> R Source

R modulo within range.

map (r_constrain (3,5)) [2.75,5.25] == [4.75,3.25]

mag_sq :: Num a => a -> a -> a Source

Sum of squares.

mag :: Floating c => c -> c -> c Source

Pt functions

pt' :: (a, a) -> Pt a Source

Tuple constructor.

pt_xy :: Pt t -> (t, t) Source

Tuple accessor.

pt_origin :: Num a => Pt a Source

Pt of (0,0).

pt_origin == Pt 0 0

pt_uop :: (a -> b) -> Pt a -> Pt b Source

Unary operator at Pt, ie. basis for Num instances.

pt_binop :: (a -> b -> c) -> Pt a -> Pt b -> Pt c Source

Binary operator at Pt, ie. basis for Num instances.

pt_from_scalar :: Num a => a -> Pt a Source

Pt at (n,n).

pt_from_scalar 1 == Pt 1 1

pt_clipu :: (Ord a, Num a) => a -> Pt a -> Pt a Source

Clip x and y to lie in (0,n).

pt_clipu 1 (Pt 0.5 1.5) == Pt 0.5 1

pt_swap :: Pt a -> Pt a Source

Swap x and y coordinates at Pt.

pt_swap (Pt 1 2) == Pt 2 1

pt_negate_y :: Num a => Pt a -> Pt a Source

Negate y element of Pt.

pt_negate_y (Pt 1 1) == Pt 1 (-1)

pt_to_radians :: Pt R -> Pt R Source

Pt variant of r_to_radians.

pt_to_radians (Pt 90 270) == Pt (pi/2) (pi*(3/2))

pt_to_polar :: Pt R -> Pt R Source

Cartesian to polar.

pt_to_polar (Pt 0 pi) == Pt pi (pi/2)

pt_from_polar :: Pt R -> Pt R Source

Polar to cartesian, inverse of pt_to_polar.

pt_from_polar (Pt pi (pi/2)) ~= Pt 0 pi

pt_offset :: Num a => a -> Pt a -> Pt a Source

Scalar Pt +.

pt_offset 1 pt_origin == Pt 1 1

pt_scale :: Num a => a -> Pt a -> Pt a Source

Scalar Pt *.

pt_scale 2 (Pt 1 2) == Pt 2 4

pt_min :: Ord a => Pt a -> Pt a -> Pt a Source

Pointwise min.

pt_max :: Ord a => Pt a -> Pt a -> Pt a Source

Pointwise max.

pt_ternary_f :: (a -> a -> b -> b -> c -> c -> d) -> Pt a -> Pt b -> Pt c -> d Source

Apply function to x and y fields of three Pt.

pt_minmax :: Ord a => (Pt a, Pt a) -> Pt a -> (Pt a, Pt a) Source

Given a (minima,maxima) pair, expand so as to include p.

pt_minmax (Pt 0 0,Pt 1 1) (Pt (-1) 2) == (Pt (-1) 0,Pt 1 2)

pt_constrain :: (Pt R, Pt R) -> Pt R -> Pt R Source

Pt variant of constrain.

pt_angle_o :: Pt R -> R Source

Angle to origin.

pt_angle_o (Pt 0 1) == pi / 2

pt_angle :: Pt R -> Pt R -> R Source

Angle from p to q.

pt_angle (Pt 0 (-1)) (Pt 0 1) == pi/2
pt_angle (Pt 1 0) (Pt 0 1) == pi * 3/4
pt_angle (Pt 0 1) (Pt 0 1) == 0

pt_translate :: (Num a, Eq a) => Pt a -> Vc a -> Pt a Source

Pointwise +.

pt_translate (Pt 0 0) (vc 1 1) == pt 1 1

pt_mag_sq :: Num a => Pt a -> a Source

mag_sq of x y of Pt.

pt_mag :: Floating a => Pt a -> a Source

mag of x y of Pt.

pt_distance :: (Floating a, Eq a) => Pt a -> Pt a -> a Source

Distance from Pt p to Pt q.

pt_distance (Pt 0 0) (Pt 0 1) == 1
pt_distance (Pt 0 0) (Pt 1 1) == sqrt 2

pt_is_normal :: (Ord a, Num a) => Pt a -> Bool Source

Are x and y of Pt p in range (0,1).

map pt_is_normal [Pt 0 0,Pt 1 1,Pt 2 2] == [True,True,False]

pt_rotate :: Floating a => a -> Pt a -> Pt a Source

Rotate Pt n radians.

pt_rotate pi (Pt 1 0) ~= Pt (-1) 0

pt_rotate_about :: Floating a => a -> Pt a -> Pt a -> Pt a Source

Vc functions

vc_uop :: (a -> b) -> Vc a -> Vc b Source

Unary operator at Vc, ie. basis for Num instances.

vc_binop :: (a -> b -> c) -> Vc a -> Vc b -> Vc c Source

Binary operator at Vc, ie. basis for Num instances.

vc_mag_sq :: Floating c => Vc c -> c Source

vc_mag :: Floating c => Vc c -> c Source

mag of Vc.

vc_scale :: Num a => a -> Vc a -> Vc a Source

Multiply Vc pointwise by scalar.

vc_scale 2 (Vc 3 4) == Vc 6 8

vc_dot :: Num a => Vc a -> Vc a -> a Source

Vc dot product.

vc_dot (Vc 1 2) (Vc 3 4) == 11

vc_unit :: (Ord a, Floating a) => Vc a -> Vc a Source

Scale Vc to have unit magnitude (to within tolerance).

vc_unit (Vc 1 1) ~= let x = (sqrt 2) / 2 in Vc x x

vc_angle :: Vc R -> Vc R -> R Source

The angle between two vectors on a plane. The angle is from v1 to v2, positive anticlockwise. The result is in (-pi,pi)

Line functions

ln' :: (Num a, Eq a) => (a, a) -> (a, a) -> Ln a Source

Variant on Ln which takes Pt co-ordinates as duples.

ln' (0,0) (1,1) == Ln (Pt 0 0) (Pt 1 1)
ln_start (Ln (Pt 0 0) (Pt 1 1)) == Pt 0 0
ln_end (Ln (Pt 0 0) (Pt 1 1)) == Pt 1 1

ln_vc :: (Num a, Eq a) => Ln a -> Vc a Source

Vc that pt_translates start Pt to end Pt of Ln.

let l = Ln (Pt 0 0) (Pt 1 1)
in ln_start l `pt_translate` ln_vc l == Pt 1 1

ln_uop :: (Pt a -> Pt b) -> Ln a -> Ln b Source

Pt UOp at Ln.

ln_scale :: Num b => b -> Ln b -> Ln b Source

ln_angle :: Ln R -> R Source

The angle, in radians, anti-clockwise from the x-axis.

ln_angle (ln' (0,0) (0,0)) == 0
ln_angle (ln' (0,0) (1,1)) == pi/4
ln_angle (ln' (0,0) (0,1)) == pi/2
ln_angle (ln' (0,0) (-1,1)) == pi * 3/4

ln_pt :: (Num a, Eq a) => Ln a -> (Pt a, Pt a) Source

Start and end points of Ln.

ln_pt (Ln (Pt 1 0) (Pt 0 0)) == (Pt 1 0,Pt 0 0)

ln_pt' :: (Num a, Eq a) => Ln a -> ((a, a), (a, a)) Source

Variant of ln_pt giving co-ordinates as duples.

ln_pt' (Ln (Pt 1 0) (Pt 0 0)) == ((1,0),(0,0))

ln_midpoint :: (Fractional a, Eq a) => Ln a -> Pt a Source

Midpoint of a Ln.

ln_midpoint (Ln (Pt 0 0) (Pt 2 1)) == Pt 1 (1/2)

cc_midpoint :: (Maybe (Pt R), Maybe (Pt R)) -> Pt R Source

Variant on ln_midpoint.

cc_midpoint (Just (Pt 0 0),Nothing) == Pt 0 0
cc_midpoint (Nothing,Just (Pt 2 1)) == Pt 2 1
cc_midpoint (Just (Pt 0 0),Just (Pt 2 1)) == Pt 1 (1/2)

ln_magnitude :: Ln R -> R Source

Magnitude of Ln, ie. length of line.

ln_magnitude (Ln (Pt 0 0) (Pt 1 1)) == sqrt 2
pt_x (pt_to_polar (Pt 1 1)) == sqrt 2

ln_sort :: (Num a, Ord a) => Ln a -> Ln a Source

Order Pt at Ln so that p is to the left of q. If x fields are equal, sort on y.

ln_sort (Ln (Pt 1 0) (Pt 0 0)) == Ln (Pt 0 0) (Pt 1 0)
ln_sort (Ln (Pt 0 1) (Pt 0 0)) == Ln (Pt 0 0) (Pt 0 1)

ln_adjust :: (Floating a, Ord a) => a -> Ln a -> Ln a Source

Adjust Ln to have equal starting Pt but magnitude R.

ln_adjust (sqrt 2) (Ln (Pt 0 0) (Pt 2 2)) == Ln (Pt 0 0) (Pt 1 1)

ln_extend :: R -> Ln R -> Ln R Source

Extend Ln by R, ie. ln_adjust with n added to ln_magnitude.

ln_extend (sqrt 2) (Ln (Pt 0 0) (Pt 1 1)) ~= Ln (Pt 0 0) (Pt 2 2)

ln_extend_ :: R -> Ln R -> Ln R Source

Variant definition of ln_extend.

ln_extend_ (sqrt 2) (Ln (Pt 0 0) (Pt 1 1)) == Ln (Pt 0 0) (Pt 2 2)

pt_linear_extension :: R -> Ln R -> Pt R Source

Calculate the point that extends a line by length n.

pt_linear_extension (sqrt 2) (Ln (Pt 1 1) (Pt 2 2)) ~= Pt 3 3
pt_linear_extension 1 (Ln (Pt 1 1) (Pt 1 2)) ~= Pt 1 3

pt_on_line :: Ln R -> Pt R -> Bool Source

Does Pt p lie on Ln (inclusive).

let {f = pt_on_line (Ln (Pt 0 0) (Pt 1 1))
    ;r = [True,False,False,True]}
in map f [Pt 0.5 0.5,Pt 2 2,Pt (-1) (-1),Pt 0 0] == r

Intersection

ln_intersect :: (Eq t, Fractional t) => Ln t -> Ln t -> Maybe (t, t) Source

ln_pt_along :: (Eq a, Num a) => a -> Ln a -> Pt a Source

ln_intersection :: (Ord a, Fractional a) => Ln a -> Ln a -> Maybe (Pt a) Source

Do two Lns intersect, and if so at which Pt.

ln_intersection (ln' (0,0) (5,5)) (ln' (5,0) (0,5)) == Just (Pt 2.5 2.5)
ln_intersection (ln' (1,3) (9,3)) (ln' (0,1) (2,1)) == Nothing
ln_intersection (ln' (1,5) (6,8)) (ln' (0.5,3) (6,4)) == Nothing
ln_intersection (ln' (1,2) (3,6)) (ln' (2,4) (4,8)) == Nothing
ln_intersection (ln' (2,3) (7,9)) (ln' (1,2) (5,7)) == Nothing
ln_intersection (ln' (0,0) (1,1)) (ln' (0,0) (1,0)) == Just (Pt 0 0)

ln_intersection_ :: (Ord a, Fractional a) => Ln a -> Ln a -> Maybe (Pt a) Source

Variant definition of ln_intersection, using algorithm at http://paulbourke.net/geometry/lineline2d/.

ln_intersection_ (ln' (1,2) (3,6)) (ln' (2,4) (4,8)) == Nothing
ln_intersection_ (ln' (0,0) (1,1)) (ln' (0,0) (1,0)) == Just (Pt 0 0)

ln_intersect_p :: (Ord a, Fractional a) => Ln a -> Ln a -> Bool Source

Predicate variant of ln_intersection.

ln_intersect_p (ln' (1,1) (3,8)) (ln' (0.5,2) (4,7)) == True
ln_intersect_p (ln' (3.5,9) (3.5,0.5)) (ln' (3,1) (9,1)) == True

Line slope

ln_slope :: (Fractional a, Eq a) => Ln a -> Maybe a Source

Slope of Ln or Nothing if vertical.

let l = zipWith ln' (repeat (0,0)) [(1,0),(2,1),(1,1),(0,1),(-1,1)]
in map ln_slope l == [Just 0,Just (1/2),Just 1,Nothing,Just (-1)]

ln_parallel :: (Ord a, Fractional a) => Ln a -> Ln a -> Bool Source

Are Lns parallel, ie. have equal ln_slope. Note that the direction of the Ln is not relevant, ie. this is not equal to ln_same_direction.

ln_parallel (ln' (0,0) (1,1)) (ln' (2,2) (1,1)) == True
ln_parallel (ln' (0,0) (1,1)) (ln' (2,0) (1,1)) == False
ln_parallel (ln' (1,2) (3,6)) (ln' (2,4) (4,8)) == True
map ln_slope [ln' (2,2) (1,1),ln' (2,0) (1,1)] == [Just 1,Just (-1)]

ln_parallel_ :: Ln R -> Ln R -> Bool Source

Are Lns parallel, ie. have equal ln_angle.

ln_parallel_ (ln' (0,0) (1,1)) (ln' (2,2) (1,1)) == True

vc_same_direction :: (Ord a, Floating a) => Vc a -> Vc a -> Bool Source

Are two vectors are in the same direction (to within a small tolerance).

ln_same_direction :: (Ord a, Floating a) => Ln a -> Ln a -> Bool Source

Do Lns have same direction (within tolerance).

ln_same_direction (ln' (0,0) (1,1)) (ln' (0,0) (2,2)) == True
ln_same_direction (ln' (0,0) (1,1)) (ln' (2,2) (0,0)) == False

ln_parallel__ :: Ln R -> Ln R -> Bool Source

Are Lns parallel, ie. does ln_vc of each equal ln_same_direction.

ln_parallel__ (ln' (0,0) (1,1)) (ln' (2,2) (1,1)) == True

ln_horizontal :: (Fractional a, Eq a) => Ln a -> Bool Source

Is Ln horizontal, ie. is ln_slope zero.

ln_horizontal (ln' (0,0) (1,0)) == True
ln_horizontal (ln' (1,0) (0,0)) == True

ln_vertical :: (Fractional a, Eq a) => Ln a -> Bool Source

Is Ln vertical, ie. is ln_slope Nothing.

ln_vertical (ln' (0,0) (0,1)) == True

Ln sets

lns_minmax :: Ord n => [Ln n] -> (Pt n, Pt n) Source

pt_minmax for set of Ln.

lns_normalise :: (Fractional n, Ord n) => n -> [Ln n] -> [Ln n] Source

Normalise to (0,m).

L(ine) s(egment) functions

ls :: [Pt a] -> Ls a Source

Ls constructor.

ls' :: [(a, a)] -> Ls a Source

Variant Ls constructor from Pt co-ordinates as duples.

ls_negate_y :: Num a => Ls a -> Ls a Source

Negate y elements.

ls_minmax :: Ord a => Ls a -> (Pt a, Pt a) Source

Generate minima and maxima Points from Ls.

ls_separate :: (Ord a, Num a) => Vc a -> Ls a -> [Ls a] Source

Separate Ls at points where the Vc from one element to the next exceeds the indicated distance.

map length (ls_separate (Vc 2 2) (map (uncurry Pt) [(0,0),(1,1),(3,3)])) == [2,1]

ls_tolerate :: (Ord a, Num a) => Vc a -> Ls a -> Ls a Source

Delete Pt from Ls so that no two Pt are within a tolerance given by Vc.

ls_tolerate' :: (Ord a, Num a) => Maybe (Vc a) -> Ls a -> Ls a Source

Variant of ls_tolerate where Vc is optional, and Nothing gives id.

ls_pt_inside :: Ls R -> Pt R -> Bool Source

Test if point Pt lies inside polygon Ls.

ls_pt_inside (ls' [(0,0),(1,0),(1,1),(0,1)]) (Pt 0.5 0.5) == True

ls_pt_inside' :: Ls R -> Pt R -> Bool Source

Variant that counts points at vertices as inside.

ls_pt_inside' (ls' [(0,0),(1,0),(1,1),(0,1)]) (Pt 0 1) == True

ls_check_normalised :: (Ord a, Num a) => Ls a -> Bool Source

Check all Pt at Ls are pt_is_normal.

ls_xy :: Ls a -> [a] Source

Line co-ordinates as x,y list.

ls_xy [Pt 0 0,Pt 1 1] == [0,0,1,1]

ls_centroid :: Fractional t => Ls t -> Pt t Source

Ls average.

Window

wn' :: Num a => (a, a) -> (a, a) -> Wn a Source

Variant Wn constructor.

wn_extract :: Wn a -> ((a, a), (a, a)) Source

Extract (x,y) and (dx,dy) pairs.

wn_extract (Wn (Pt 0 0) (Vc 1 1)) == ((0,0),(1,1))

wn_show :: Int -> Wn R -> String Source

Show function for window with fixed precision of n.

wn_show 1 (Wn (Pt 0 0) (Vc 1 1)) == "((0.0,0.0),(1.0,1.0))"

wn_unit :: Num n => Wn n Source

Unit window at origin.

pt_in_window :: (Ord a, Num a) => Wn a -> Pt a -> Bool Source

Is Pt within Wn exclusive of edge.

map (pt_in_window (wn' (0,0) (1,1))) [Pt 0.5 0.5,Pt 1 1] == [True,False]

wn_from_extent :: (Num a, Ord a) => (Pt a, Pt a) -> Wn a Source

Wn from (lower-left,upper-right) extent.

ls_window :: (Num a, Ord a) => Ls a -> Wn a Source

Wn containing Ls.

ls_window (ls' [(0,0),(1,1),(2,0)]) == wn' (0,0) (2,1)

wn_join :: (Num a, Ord a) => Wn a -> Wn a -> Wn a Source

A Wn that encompasses both input Wns.

wn_intersect :: (Num a, Ord a) => Wn a -> Wn a -> Bool Source

Predictate to determine if two Wns intersect.

ls_in_window :: Wn R -> Ls R -> Bool Source

Are all points at Ls within the Wn.

ls_enters_window :: Wn R -> Ls R -> Bool Source

Are any points at Ls within the window Wn.

ls_not_in_window :: Wn R -> Ls R -> Bool Source

Are all points at Ls outside the Wn.

ls_segment_window :: Wn R -> Ls R -> [Ls R] Source

Break Ls into segments that are entirely within the Wn.

wn_normalise_f :: (Ord n, Fractional n) => Wn n -> Pt n -> Pt n Source

Normalisation function for Wn, ie. map Pt to lie within (0,1).

ls_normalise_w :: (Ord n, Fractional n) => Wn n -> Ls n -> Ls n Source

Given Wn normalise the Ls.

ln_normalise_w :: (Ord n, Fractional n) => Wn n -> Ln n -> Ln n Source

Given Wn normalise Ln.

ls_normalise :: (Ord n, Fractional n) => Ls n -> Ls n Source

Variant of ls_normalise_w, the window is determined by the extent of the Ls.

ls_normalise_set :: (Ord n, Fractional n) => [Ls n] -> [Ls n] Source

Normalise a set of line segments using composite window.

pt_shift_w :: Num a => Pt a -> Wn a -> Wn a Source

Shift lower left Pt of Wn by indicated Pt.

wn_negate_y :: Num a => Wn a -> Wn a Source

Negate y field of lower left Pt of Wn.

Matrix

data Matrix n Source

Transformation matrix data type.

Constructors

Matrix n n n n n n 

Instances

Eq n => Eq (Matrix n) 
Num n => Num (Matrix n) 
Show n => Show (Matrix n) 

data Matrix_Index Source

Enumeration of Matrix indices.

Constructors

I0 
I1 
I2 

mx_row :: Num n => Matrix n -> Matrix_Index -> (n, n, n) Source

mx_col :: Num n => Matrix n -> Matrix_Index -> (n, n, n) Source

mx_uop :: (n -> n) -> Matrix n -> Matrix n Source

Pointwise unary operator.

mx_binop :: (n -> n -> n) -> Matrix n -> Matrix n -> Matrix n Source

Pointwise binary operator.

mx_translation :: Num n => n -> n -> Matrix n Source

A translation matrix with independent x and y offsets.

mx_scaling :: Num n => n -> n -> Matrix n Source

A scaling matrix with independent x and y scalars.

mx_rotation :: Floating n => n -> Matrix n Source

A rotation matrix through the indicated angle (in radians).

mx_identity :: Num n => Matrix n Source

The identity matrix.

mx_translate :: Num n => n -> n -> Matrix n -> Matrix n Source

mx_scale :: Num n => n -> n -> Matrix n -> Matrix n Source

mx_rotate :: Floating n => n -> Matrix n -> Matrix n Source

mx_list :: Matrix n -> [n] Source

pt_transform :: Num n => Matrix n -> Pt n -> Pt n Source

Apply a transformation matrix to a point.

Bezier functions.

bezier3 :: Num n => Pt n -> Pt n -> Pt n -> n -> Pt n Source

bezier4 :: Num n => Pt n -> Pt n -> Pt n -> Pt n -> n -> Pt n Source

Four-point bezier curve interpolation. The index mu is in the range zero to one.

Ord

in_range :: Ord a => a -> a -> a -> Bool Source

Given left and right, is x in range (inclusive).

map (in_range 0 1) [-1,0,1,2] == [False,True,True,False]

List

split_f :: (a -> a -> Bool) -> [a] -> ([a], [a]) Source

Split list at element where predicate f over adjacent elements first holds.

split_f (\p q -> q - p < 3) [1,2,4,7,11] == ([1,2,4],[7,11])

segment_f :: (a -> a -> Bool) -> [a] -> [[a]] Source

Variant on split_f that segments input.

segment_f (\p q -> abs (q - p) < 3) [1,3,7,9,15] == [[1,3],[7,9],[15]]

delete_f :: (a -> a -> Bool) -> [a] -> [a] Source

Delete elements of a list using a predicate over the previous and current elements.

pairs :: [x] -> [(x, x)] Source

All adjacent pairs of a list.

pairs [1..5] == [(1,2),(2,3),(3,4),(4,5)]