| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Geometry.Slab
Synopsis
- data Orthogonal
- newtype Slab (o :: Orthogonal) a r = Slab {}
- unSlab :: forall o a r o a r. Iso (Slab o a r) (Slab o a r) (Interval a r) (Interval a r)
- horizontalSlab :: (r :+ a) -> (r :+ a) -> Slab Horizontal a r
- verticalSlab :: (r :+ a) -> (r :+ a) -> Slab Vertical a r
- class HasBoundingLines (o :: Orthogonal) where
Documentation
data Orthogonal Source #
Constructors
| Horizontal | |
| Vertical |
Instances
| Eq Orthogonal Source # | |
Defined in Data.Geometry.Slab | |
| Read Orthogonal Source # | |
Defined in Data.Geometry.Slab Methods readsPrec :: Int -> ReadS Orthogonal # readList :: ReadS [Orthogonal] # readPrec :: ReadPrec Orthogonal # readListPrec :: ReadPrec [Orthogonal] # | |
| Show Orthogonal Source # | |
Defined in Data.Geometry.Slab Methods showsPrec :: Int -> Orthogonal -> ShowS # show :: Orthogonal -> String # showList :: [Orthogonal] -> ShowS # | |
newtype Slab (o :: Orthogonal) a r Source #
Instances
| Bifunctor (Slab o) Source # | |
| Functor (Slab o a) Source # | |
| Foldable (Slab o a) Source # | |
Defined in Data.Geometry.Slab Methods fold :: Monoid m => Slab o a m -> 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] # 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 # | |
| Traversable (Slab o a) Source # | |
Defined in Data.Geometry.Slab | |
| (Fractional r, Ord r, HasBoundingLines o) => IsIntersectableWith (Line 2 r) (Slab o a r) Source # | |
| (Eq r, Eq a) => Eq (Slab o a r) Source # | |
| (Show a, Show r) => Show (Slab o a r) Source # | |
| (Fractional r, Ord r, HasBoundingLines o) => IsIntersectableWith (LineSegment 2 a r) (Slab o a r) Source # | |
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 # | |
| IsIntersectableWith (Slab Horizontal a r) (Slab Vertical a r) Source # | |
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 # | |
Defined in Data.Geometry.Slab | |
| type IntersectionOf (Line 2 r) (Slab o a r) Source # | |
Defined in Data.Geometry.Slab type IntersectionOf (Line 2 r) (Slab o a r) = NoIntersection ': (Line 2 r ': (LineSegment 2 a r ': ([] :: [Type]))) | |
| type IntersectionOf (LineSegment 2 p r) (Slab o a r) Source # | |
Defined in Data.Geometry.Slab type IntersectionOf (LineSegment 2 p r) (Slab o a r) = NoIntersection ': (LineSegment 2 () r ': ([] :: [Type])) | |
| type IntersectionOf (Slab o a r) (Slab o a r) Source # | |
Defined in Data.Geometry.Slab | |
| type IntersectionOf (Slab Horizontal a r) (Slab Vertical a r) Source # | |
Defined in Data.Geometry.Slab | |
| type IntersectionOf (SubLine 2 p s r) (Slab o a r) Source # | |
Defined in Data.Geometry.Slab | |
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:
Instances
| HasBoundingLines Horizontal Source # | |
Defined in Data.Geometry.Slab | |
| HasBoundingLines Vertical Source # | |