numhask-space-0.2.0: numerical spaces

Safe HaskellNone
LanguageHaskell2010

NumHask.Rect

Description

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

Synopsis

Documentation

newtype Rect a Source #

a Point 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 (Point 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) (Point 0.5 1)
Point 2.5 -10.0
>>> gridSpace (Rect 0 10 0 1) (Point 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) (Point 2 2)
[Point 2.5 0.25,Point 2.5 0.75,Point 7.5 0.25,Point 7.5 0.75]

Constructors

Rect' (Compose Point Range a) 
Instances
Functor Rect Source # 
Instance details

Defined in NumHask.Rect

Methods

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

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

Applicative Rect Source # 
Instance details

Defined in NumHask.Rect

Methods

pure :: a -> Rect a #

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

liftA2 :: (a -> b -> c) -> Rect a -> Rect b -> Rect c #

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

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

Foldable Rect Source # 
Instance details

Defined in NumHask.Rect

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 # 
Instance details

Defined in NumHask.Rect

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 # 
Instance details

Defined in NumHask.Rect

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 # 
Instance details

Defined in NumHask.Rect

Associated Types

type Rep Rect :: Type #

Methods

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

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

Eq a => Eq (Rect a) Source # 
Instance details

Defined in NumHask.Rect

Methods

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

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

Show a => Show (Rect a) Source # 
Instance details

Defined in NumHask.Rect

Methods

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

show :: Rect a -> String #

showList :: [Rect a] -> ShowS #

Generic (Rect a) Source # 
Instance details

Defined in NumHask.Rect

Associated Types

type Rep (Rect a) :: Type -> Type #

Methods

from :: Rect a -> Rep (Rect a) x #

to :: Rep (Rect a) x -> Rect a #

Ord a => Semigroup (Rect a) Source # 
Instance details

Defined in NumHask.Rect

Methods

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

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

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

(Ord a, Fractional a, Num a) => FieldSpace (Rect a) Source # 
Instance details

Defined in NumHask.Rect

Associated Types

type Grid (Rect a) :: Type Source #

Methods

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

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

Ord a => Space (Rect a) Source # 
Instance details

Defined in NumHask.Rect

Associated Types

type Element (Rect a) :: Type Source #

Methods

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

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

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

intersection :: Rect a -> Rect a -> Rect a Source #

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

norm :: Rect a -> Rect a Source #

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

(>.<) :: Element (Rect a) -> Element (Rect a) -> Rect a Source #

(|.|) :: Element (Rect a) -> Rect a -> Bool Source #

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

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

type Rep Rect Source # 
Instance details

Defined in NumHask.Rect

type Rep Rect = (Bool, Bool)
type Rep (Rect a) Source # 
Instance details

Defined in NumHask.Rect

type Rep (Rect a) = D1 (MetaData "Rect" "NumHask.Rect" "numhask-space-0.2.0-Lufpc8Rnj2uGfgI0GjZHwy" True) (C1 (MetaCons "Rect'" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Compose Point Range a))))
type Grid (Rect a) Source # 
Instance details

Defined in NumHask.Rect

type Grid (Rect a) = Point Int
type Element (Rect a) Source # 
Instance details

Defined in NumHask.Rect

type Element (Rect a) = Point a

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

pattern of Rect lowerx upperx lowery uppery

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

pattern of Ranges xrange yrange

corners :: Ord a => Rect a -> [Point a] Source #

create a list of points representing the lower left and upper right corners of a rectangle.

corners4 :: Rect a -> NonEmpty (Point a) Source #

the 4 corners

projectRect :: (Ord a, Fractional a) => Rect a -> Rect a -> Rect a -> Rect a Source #

project a Rect from an old range to a new 1

addRect :: Num a => Rect a -> Rect a -> Rect a Source #

Rect projection maths: some sort of affine projection lurking under the hood? > width one = one > mid zero = zero

multRect :: (Ord a, Fractional a) => Rect a -> Rect a -> Rect a Source #

foldRect :: Ord a => [Rect a] -> Maybe (Rect a) Source #

addPoint :: Num a => Point a -> Rect a -> Rect a Source #

rotateRect :: (Floating a, Ord a) => a -> Rect a -> Rect a Source #

rotate the corners of a Rect by x degrees relative to the origin, and fold to a new Rcet

gridR :: (Ord a, Fractional a) => (a -> a) -> Range a -> Int -> [Rect a] Source #

Create Rects for a formulae y = f(x) across an x range

gridF :: (Ord a, Fractional a) => (Point a -> b) -> Rect a -> Grid (Rect a) -> [(Rect a, b)] Source #

Create values c for Rects data for a formulae c = f(x,y)

aspect :: Fractional a => a -> Rect a Source #

convert a ratio of x-plane : y-plane to a ViewBox with a height of one.

ratio :: Fractional a => Rect a -> a Source #

convert a Rect to a ratio