numhask-range-0.0.1: see readme.md

Safe HaskellNone
LanguageHaskell2010

NumHask.Rect

Synopsis

Documentation

newtype Rect a Source #

a two-dimensional plane, bounded by ranges.

Constructors

Rect 

Fields

Instances

Functor Rect Source # 

Methods

fmap :: (a -> b) -> Rect a -> Rect b #

(<$) :: a -> Rect b -> Rect a #

Eq a => Eq (Rect a) Source # 

Methods

(==) :: Rect a -> Rect a -> Bool #

(/=) :: Rect a -> Rect a -> Bool #

Ord a => Ord (Rect a) Source # 

Methods

compare :: Rect a -> Rect a -> Ordering #

(<) :: Rect a -> Rect a -> Bool #

(<=) :: Rect a -> Rect a -> Bool #

(>) :: Rect a -> Rect a -> Bool #

(>=) :: Rect a -> Rect a -> Bool #

max :: Rect a -> Rect a -> Rect a #

min :: Rect a -> Rect a -> Rect a #

Show a => Show (Rect a) Source # 

Methods

showsPrec :: Int -> Rect a -> ShowS #

show :: Rect a -> String #

showList :: [Rect a] -> ShowS #

Ord a => Semigroup (Rect a) Source # 

Methods

(<>) :: Rect a -> Rect a -> Rect a #

sconcat :: NonEmpty (Rect a) -> Rect a #

stimes :: Integral b => b -> Rect a -> Rect a #

(AdditiveUnital (Rect a), Semigroup (Rect a)) => Monoid (Rect a) Source # 

Methods

mempty :: Rect a #

mappend :: Rect a -> Rect a -> Rect a #

mconcat :: [Rect a] -> Rect a #

Ord a => AdditiveMagma (Rect a) Source #

a convex hull approach

Methods

plus :: Rect a -> Rect a -> Rect a #

(Ord a, BoundedField a) => AdditiveUnital (Rect a) Source # 

Methods

zero :: Rect a #

Ord a => AdditiveAssociative (Rect a) Source # 
Ord a => AdditiveCommutative (Rect a) Source # 
(Ord a, BoundedField a) => Additive (Rect a) Source # 

Methods

(+) :: Rect a -> Rect a -> Rect a #

BoundedField a => MultiplicativeMagma (Rect a) Source # 

Methods

times :: Rect a -> Rect a -> Rect a #

BoundedField a => MultiplicativeUnital (Rect a) Source # 

Methods

one :: Rect a #

BoundedField a => MultiplicativeAssociative (Rect a) Source # 
(Ord a, BoundedField a) => MultiplicativeInvertible (Rect a) Source # 

Methods

recip :: Rect a -> Rect a #

(Ord a, BoundedField a) => MultiplicativeLeftCancellative (Rect a) Source # 

Methods

(~/) :: Rect a -> Rect a -> Rect a #

(Ord a, BoundedField a) => MultiplicativeRightCancellative (Rect a) Source # 

Methods

(/~) :: Rect a -> Rect a -> Rect a #

AdditiveGroup a => Normed (Rect a) (V2 a) Source # 

Methods

size :: Rect a -> V2 a #

(Ord a, AdditiveGroup a) => Metric (Rect a) (V2 a) Source # 

Methods

distance :: Rect a -> Rect a -> V2 a #

Ord a => AdditiveHomomorphic (V2 a) (Rect a) Source #

natural interpretation of an a as an `Rect a`

Methods

plushom :: V2 a -> Rect a #

rect :: Iso' (V4 a) (Rect a) Source #

an alternative specification; as a 4-dim vector `V4 x y z w` where: - (x,y) is the lower left corner of a rectangle, and - (z,w) is the upper right corner of a rectangle

positRect :: Ord a => Rect a -> Rect a Source #

corners :: Rect a -> [V2 a] Source #

elementRect :: Ord a => V2 a -> Rect a -> Bool Source #

determine whether a point is within the range

singularRect :: Eq a => Rect a -> Bool Source #

is the range a singleton V2 (has zero area)

intersectionRect :: Ord a => Rect a -> Rect a -> Rect a Source #

containsRect :: Ord a => Rect a -> Rect a -> Bool Source #

rescaleP :: Field b => Range b -> Range b -> b -> b Source #

`rescaleP rold rnew p` rescales a data point from an old range to a new range rescaleP o n (view low o) == view low n rescaleP o n (view high o) == view high n rescaleP a a == id

rangeR2s :: (BoundedField a, Traversable g, Traversable f, R2 r, Ord a) => g (f (r a)) -> Rect a Source #

range specialized to double traversables

scaleR2s :: (R2 r, BoundedField a, Traversable f, Traversable g, Ord a) => Rect a -> g (f (r a)) -> g (f (r a)) Source #

scale a double container of r2s from the current range

rangeRects :: (Ord a, BoundedField a, Traversable f) => f (Rect a) -> Rect a Source #

the range of a container of Rects

rescaleRect :: Field a => Rect a -> Rect a -> Rect a -> Rect a Source #

rescales a Rect from an old Rect range to a new one

scaleRects :: (BoundedField a, Traversable f, Ord a) => Rect a -> f (Rect a) -> f (Rect a) Source #

scale a double container of Rects from the current range

scaleRectss :: (BoundedField a, Traversable f, Traversable g, Ord a) => Rect a -> g (f (Rect a)) -> g (f (Rect a)) Source #

scale a double container of Rects from the current range

gridP :: (Field a, FromInteger a) => TickPos -> Rect a -> V2 Int -> [V2 a] Source #

grid points on a rectange, divided up by a V2 Int

grid :: (BoundedField a, FromInteger a) => Rect a -> V2 Int -> [Rect a] Source #

a rectangle divided up by a V2 Int, making a list of smaller rectangles