numhask-range-0.1.1: Numbers that are range representations

Safe HaskellNone
LanguageHaskell2010

NumHask.Rect

Description

a two-dimensional plane, implemented as a composite of a Pair of Ranges.

Synopsis

Documentation

newtype Rect a Source #

a Pair of Ranges that form a rectangle in what is often thought of as the XY plane.

>>> let a = Rect (-1) 1 (-2) 4
>>> a
Rect -1 1 -2 4
>>> let (Ranges x y) = a
>>> x
Range -1 1
>>> y
Range -2 4
>>> fmap (+1) (Rect 1 2 3 4)
Rect 2 3 4 5
>>> one :: Rect Double
Rect -0.5 0.5 -0.5 0.5
>>> zero :: Rect Double
Rect Infinity -Infinity Infinity -Infinity

as a Field instance

>>> Rect 0 1 2 3 + zero
Rect 0.0 1.0 2.0 3.0
>>> Rect 0 1 (-2) (-1) + Rect 2 3 (-5) 3
Rect 0.0 3.0 -5.0 3.0
>>> Rect 1 1 1 1 - one
Rect 0.5 1.0 0.5 1.0
>>> Rect 0 1 0 1 * one
Rect 0.0 1.0 0.0 1.0
>>> Rect 0 1 0 1 / one
Rect 0.0 1.0 0.0 1.0
>>> singleton (Pair 1.0 2.0) :: Rect Double
Rect 1.0 1.0 2.0 2.0
>>> abs (Rect 1 0 1 0)
Rect 0.0 1.0 0.0 1.0
>>> sign (Rect 1 0 1 0) == negate one
True

as a Space instance

>>> project (Rect 0 1 (-1) 0) (Rect 1 4 10 0) (Pair 0.5 1)
Pair 2.5 -10.0
>>> gridSpace (Rect 0 10 0 1) (Pair 2 2)
[Rect 0.0 5.0 0.0 0.5,Rect 0.0 5.0 0.5 1.0,Rect 5.0 10.0 0.0 0.5,Rect 5.0 10.0 0.5 1.0]
>>> grid MidPos (Rect 0 10 0 1) (Pair 2 2)
[Pair 2.5 0.25,Pair 2.5 0.75,Pair 7.5 0.25,Pair 7.5 0.75]

Constructors

Rect' (Compose Pair Range a) 

Instances

Functor Rect Source # 

Methods

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

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

Applicative Rect Source # 

Methods

pure :: a -> Rect a #

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

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

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

Foldable Rect Source # 

Methods

fold :: Monoid m => Rect m -> m #

foldMap :: Monoid m => (a -> m) -> Rect a -> m #

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

foldr' :: (a -> b -> b) -> b -> Rect a -> b #

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

foldl' :: (b -> a -> b) -> b -> Rect a -> b #

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

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

toList :: Rect a -> [a] #

null :: Rect a -> Bool #

length :: Rect a -> Int #

elem :: Eq a => a -> Rect a -> Bool #

maximum :: Ord a => Rect a -> a #

minimum :: Ord a => Rect a -> a #

sum :: Num a => Rect a -> a #

product :: Num a => Rect a -> a #

Traversable Rect Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Rect a -> f (Rect b) #

sequenceA :: Applicative f => Rect (f a) -> f (Rect a) #

mapM :: Monad m => (a -> m b) -> Rect a -> m (Rect b) #

sequence :: Monad m => Rect (m a) -> m (Rect a) #

Distributive Rect Source # 

Methods

distribute :: Functor f => f (Rect a) -> Rect (f a) #

collect :: Functor f => (a -> Rect b) -> f a -> Rect (f b) #

distributeM :: Monad m => m (Rect a) -> Rect (m a) #

collectM :: Monad m => (a -> Rect b) -> m a -> Rect (m b) #

Representable Rect Source # 

Associated Types

type Rep (Rect :: * -> *) :: * #

Methods

tabulate :: (Rep Rect -> a) -> Rect a #

index :: Rect a -> Rep Rect -> a #

Traversable1 Rect Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Rect a -> f (Rect b) #

sequence1 :: Apply f => Rect (f b) -> f (Rect b) #

Apply Rect Source # 

Methods

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

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

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

Foldable1 Rect Source # 

Methods

fold1 :: Semigroup m => Rect m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Rect a -> m #

toNonEmpty :: Rect a -> NonEmpty a #

Eq a => Eq (Rect a) Source # 

Methods

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

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

Show a => Show (Rect a) Source # 

Methods

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

show :: Rect a -> String #

showList :: [Rect a] -> ShowS #

(Signed a, Ord a, BoundedField a, FromInteger a) => Monoid (Rect a) Source # 

Methods

mempty :: Rect a #

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

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

Arbitrary a => Arbitrary (Rect a) Source # 

Methods

arbitrary :: Gen (Rect a) #

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

NFData a => NFData (Rect a) Source # 

Methods

rnf :: Rect a -> () #

(AdditiveInvertible a, BoundedField a, Ord a, FromInteger a) => Signed (Rect a) Source # 

Methods

sign :: Rect a -> Rect a #

abs :: Rect a -> Rect a #

(BoundedField a, Ord a, FromInteger a, Epsilon a) => Epsilon (Rect a) Source # 

Methods

nearZero :: Rect a -> Bool #

aboutEqual :: Rect a -> Rect a -> Bool #

positive :: Rect a -> Bool #

veryPositive :: Rect a -> Bool #

veryNegative :: Rect a -> Bool #

(Ord a, BoundedField a, FromInteger a) => MultiplicativeMagma (Rect a) Source # 

Methods

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

(Ord a, BoundedField a, FromInteger a) => MultiplicativeUnital (Rect a) Source # 

Methods

one :: Rect a #

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

Methods

recip :: Rect a -> Rect a #

(Ord a, BoundedField a, FromInteger a) => Multiplicative (Rect a) Source # 

Methods

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

(Ord a, BoundedField a, FromInteger a) => MultiplicativeGroup (Rect a) Source # 

Methods

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

(Ord a, BoundedField a, FromInteger a) => AdditiveMagma (Rect a) Source # 

Methods

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

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

Methods

zero :: Rect a #

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

Methods

negate :: Rect a -> Rect a #

(Ord a, FromInteger a, BoundedField a) => AdditiveIdempotent (Rect a) Source # 
(Ord a, BoundedField a, FromInteger a) => Additive (Rect a) Source # 

Methods

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

(Ord a, BoundedField a, FromInteger a) => AdditiveGroup (Rect a) Source # 

Methods

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

(Signed a, FromInteger a, Ord a, BoundedField a) => Space (Rect a) Source # 

Associated Types

type Element (Rect a) :: * Source #

type Grid (Rect a) :: * Source #

Methods

lower :: Rect a -> Element (Rect a) Source #

upper :: Rect a -> Element (Rect a) Source #

mid :: Rect a -> Element (Rect a) Source #

width :: Rect a -> Element (Rect a) Source #

singleton :: Element (Rect a) -> Rect a Source #

singular :: Rect a -> Bool Source #

element :: Element (Rect a) -> Rect a -> Bool Source #

contains :: Rect a -> Rect a -> Bool Source #

union :: Rect a -> Rect a -> Rect a Source #

nul :: Rect a Source #

space :: Foldable f => f (Element (Rect a)) -> Rect a Source #

project :: Rect a -> Rect a -> Element (Rect a) -> Element (Rect a) Source #

grid :: Pos -> Rect a -> Grid (Rect a) -> [Element (Rect a)] Source #

gridSpace :: Rect a -> Grid (Rect a) -> [Rect a] Source #

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

Methods

size :: Rect a -> Pair a #

type Rep Rect Source # 
type Rep Rect = (Bool, Bool)
type Element (Rect a) Source # 
type Element (Rect a) = Pair a
type Grid (Rect a) Source # 
type Grid (Rect a) = Pair Int

pattern Rect :: forall a. a -> a -> a -> a -> Rect a Source #

pattern of Rect lowerx upperx lowery uppery

pattern Ranges :: forall a. Range a -> Range a -> Rect a Source #

pattern of Ranges xrange yrange

corners :: (Signed a, FromInteger a, BoundedField a, Ord a) => Rect a -> [Pair a] Source #

create a list of pairs representing the lower left and upper right cormners of a rectangle.

projectRect :: (Signed a, FromInteger a, Ord a, BoundedField a) => Rect a -> Rect a -> Rect a -> Rect a Source #

project a Rect from an old range to a new one