hgeometry-0.12.0.2: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Slab

Description

 
Synopsis

Documentation

data Orthogonal Source #

Constructors

Horizontal 
Vertical 

Instances

Instances details
Eq Orthogonal Source # 
Instance details

Defined in Data.Geometry.Slab

Read Orthogonal Source # 
Instance details

Defined in Data.Geometry.Slab

Show Orthogonal Source # 
Instance details

Defined in Data.Geometry.Slab

newtype Slab (o :: Orthogonal) a r Source #

Constructors

Slab 

Fields

Instances

Instances details
Bifunctor (Slab o) Source # 
Instance details

Defined in Data.Geometry.Slab

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

Defined in Data.Geometry.Slab

Methods

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

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

Foldable (Slab o a) Source # 
Instance details

Defined in Data.Geometry.Slab

Methods

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

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

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

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

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

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

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

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

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

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

null :: Slab o a a0 -> Bool #

length :: Slab o a a0 -> Int #

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

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

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

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

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

Traversable (Slab o a) Source # 
Instance details

Defined in Data.Geometry.Slab

Methods

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

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

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

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

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

Defined in Data.Geometry.Slab

Methods

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

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

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

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

Defined in Data.Geometry.Slab

Methods

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

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

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

Defined in Data.Geometry.Slab

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 (LineSegment 2 a r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

Methods

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

intersects :: LineSegment 2 a r -> Slab o a r -> Bool #

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

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

Defined in Data.Geometry.Slab

Methods

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

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

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

IsIntersectableWith (Slab 'Horizontal a r) (Slab 'Vertical a r) Source # 
Instance details

Defined in Data.Geometry.Slab

Methods

intersect :: Slab 'Horizontal a r -> Slab 'Vertical a r -> Intersection (Slab 'Horizontal a r) (Slab 'Vertical a r) #

intersects :: Slab 'Horizontal a r -> Slab 'Vertical a r -> Bool #

nonEmptyIntersection :: proxy (Slab 'Horizontal a r) -> proxy (Slab 'Vertical a r) -> Intersection (Slab 'Horizontal a r) (Slab 'Vertical a r) -> Bool #

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

Defined in Data.Geometry.Slab

Methods

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

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

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

type IntersectionOf (Line 2 r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

type IntersectionOf (Line 2 r) (Slab o a r) = '[NoIntersection, Line 2 r, LineSegment 2 a r]
type IntersectionOf (LineSegment 2 p r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

type IntersectionOf (LineSegment 2 p r) (Slab o a r) = '[NoIntersection, LineSegment 2 () r]
type IntersectionOf (Slab o a r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

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

Defined in Data.Geometry.Slab

type IntersectionOf (Slab 'Horizontal a r) (Slab 'Vertical a r) = '[Rectangle (a, a) r]
type IntersectionOf (SubLine 2 p s r) (Slab o a r) Source # 
Instance details

Defined in Data.Geometry.Slab

type IntersectionOf (SubLine 2 p s r) (Slab o a r) = '[NoIntersection, SubLine 2 () s 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 :: Orthogonal) where Source #

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

Instances details
HasBoundingLines 'Horizontal Source # 
Instance details

Defined in Data.Geometry.Slab

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

Defined in Data.Geometry.Slab

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 #