numhask-range-0.1.0: Numbers that are range representations

Safe HaskellNone
LanguageHaskell2010

NumHask.Rect

Synopsis

Documentation

newtype Rect a Source #

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

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 #

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 #

(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 #

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

Methods

sign :: Rect a -> Rect a #

abs :: Rect a -> Rect a #

(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 #

(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 Ranges :: forall a. Range a -> Range a -> Rect a Source #

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

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

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