hgeometry-0.6.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Slab

Synopsis

Documentation

newtype Slab o a r Source #

Constructors

Slab 

Fields

Instances

Bifunctor (Slab o) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Slab o a c -> Slab o b d #

first :: (a -> b) -> Slab o a c -> Slab o b c #

second :: (b -> c) -> Slab o a b -> Slab o a c #

Functor (Slab o a) Source # 

Methods

fmap :: (a -> b) -> Slab o a a -> Slab o a b #

(<$) :: a -> Slab o a b -> Slab o a a #

Foldable (Slab o a) Source # 

Methods

fold :: Monoid m => Slab o a m -> m #

foldMap :: Monoid m => (a -> m) -> Slab o a a -> m #

foldr :: (a -> b -> b) -> b -> Slab o a a -> b #

foldr' :: (a -> b -> b) -> b -> Slab o a a -> b #

foldl :: (b -> a -> b) -> b -> Slab o a a -> b #

foldl' :: (b -> a -> b) -> b -> Slab o a a -> b #

foldr1 :: (a -> a -> a) -> Slab o a a -> a #

foldl1 :: (a -> a -> a) -> Slab o a a -> a #

toList :: Slab o a a -> [a] #

null :: Slab o a a -> Bool #

length :: Slab o a a -> Int #

elem :: Eq a => a -> Slab o a a -> Bool #

maximum :: Ord a => Slab o a a -> a #

minimum :: Ord a => Slab o a a -> a #

sum :: Num a => Slab o a a -> a #

product :: Num a => Slab o a a -> a #

Traversable (Slab o a) Source # 

Methods

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

sequenceA :: Applicative f => Slab o a (f a) -> f (Slab o a a) #

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

sequence :: Monad m => Slab o a (m a) -> m (Slab o a a) #

(Fractional r, Ord r, HasBoundingLines o) => IsIntersectableWith (Line 2 r) (Slab o a r) Source # 

Methods

intersect :: Line 2 r -> Slab o a r -> Intersection (Line 2 r) (Slab o a r) Source #

intersects :: Line 2 r -> Slab o a r -> Bool Source #

nonEmptyIntersection :: proxy (Line 2 r) -> proxy (Slab o a r) -> Intersection (Line 2 r) (Slab o a r) -> Bool Source #

(Eq a, Eq r) => Eq (Slab o a r) Source # 

Methods

(==) :: Slab o a r -> Slab o a r -> Bool #

(/=) :: Slab o a r -> Slab o a r -> Bool #

(Show r, Show a) => Show (Slab o a r) Source # 

Methods

showsPrec :: Int -> Slab o a r -> ShowS #

show :: Slab o a r -> String #

showList :: [Slab o a r] -> ShowS #

(Fractional r, Ord r, HasBoundingLines o) => IsIntersectableWith (SubLine 2 a r) (Slab o a r) Source # 

Methods

intersect :: SubLine 2 a r -> Slab o a r -> Intersection (SubLine 2 a r) (Slab o a r) Source #

intersects :: SubLine 2 a r -> Slab o a r -> Bool Source #

nonEmptyIntersection :: proxy (SubLine 2 a r) -> proxy (Slab o a r) -> Intersection (SubLine 2 a r) (Slab o a r) -> Bool Source #

Ord r => IsIntersectableWith (Slab o a r) (Slab o a r) Source # 

Methods

intersect :: Slab o a r -> Slab o a r -> Intersection (Slab o a r) (Slab o a r) Source #

intersects :: Slab o a r -> Slab o a r -> Bool Source #

nonEmptyIntersection :: proxy (Slab o a r) -> proxy (Slab o a r) -> Intersection (Slab o a r) (Slab o a r) -> Bool Source #

IsIntersectableWith (Slab Horizontal a r) (Slab Vertical a r) Source # 
type IntersectionOf (Line 2 r) (Slab o a r) Source # 
type IntersectionOf (Line 2 r) (Slab o a r) = (:) * NoIntersection ((:) * (Line 2 r) ((:) * (LineSegment 2 a r) ([] *)))
type IntersectionOf (SubLine 2 p r) (Slab o a r) Source # 
type IntersectionOf (SubLine 2 p r) (Slab o a r) = (:) * NoIntersection ((:) * (SubLine 2 () r) ([] *))
type IntersectionOf (Slab o a r) (Slab o a r) Source # 
type IntersectionOf (Slab o a r) (Slab o a r) = (:) * NoIntersection ((:) * (Slab o a r) ([] *))
type IntersectionOf (Slab Horizontal a r) (Slab Vertical a r) Source # 
type IntersectionOf (Slab Horizontal a r) (Slab Vertical a r) = (:) * (Rectangle (a, a) r) ([] *)

unSlab :: forall o a r o a r. Iso (Slab o a r) (Slab o a r) (Interval a r) (Interval a r) Source #

horizontalSlab :: (r :+ a) -> (r :+ a) -> Slab Horizontal a r Source #

Smart consturctor for creating a horizontal slab

verticalSlab :: (r :+ a) -> (r :+ a) -> Slab Vertical a r Source #

Smart consturctor for creating a vertical slab

class HasBoundingLines o where Source #

Minimal complete definition

boundingLines, inSlab

Methods

boundingLines :: Num r => Slab o a r -> (Line 2 r :+ a, Line 2 r :+ a) Source #

The two bounding lines of the slab, first the lower one, then the higher one:

inSlab :: Ord r => Point 2 r -> Slab o a r -> Bool Source #

Instances

HasBoundingLines Horizontal Source # 

Methods

boundingLines :: Num r => Slab Horizontal a r -> (Line 2 r :+ a, Line 2 r :+ a) Source #

inSlab :: Ord r => Point 2 r -> Slab Horizontal a r -> Bool Source #

HasBoundingLines Vertical Source # 

Methods

boundingLines :: Num r => Slab Vertical a r -> (Line 2 r :+ a, Line 2 r :+ a) Source #

inSlab :: Ord r => Point 2 r -> Slab Vertical a r -> Bool Source #