Copyright | © 2018-2019 Satsuma labs |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Morton reperesentation of integer pairs (interleaved bits) used for creating spatial indexes.
Bit interleaving code is originally from the documentation of Data.Sparse by Edward Kmett at https://www.schoolofhaskell.com/user/edwardk/revisiting-matrix-multiplication/part-1
Synopsis
- newtype Morton where
- data Interval a = Interval a a
- intersectInterval :: Ord a => Interval a -> Interval a -> Maybe (Interval a)
- intervalElem :: Ord a => a -> Interval a -> Bool
- intervalSize :: Integral a => Interval a -> Integer
- intervalSizeMorton :: Interval Morton -> Integer
- data MortonRect where
- MortonRect !Morton !Morton
- pattern MortonRectSides :: Interval Word32 -> Interval Word32 -> MortonRect
- mortonRectBounds :: MortonRect -> (Interval Word32, Interval Word32)
- intersectMortonRect :: MortonRect -> MortonRect -> Maybe MortonRect
- mortonRectSize :: MortonRect -> Integer
- data MortonTile = MortonTile !Morton !Int
- mortonTileBounds :: MortonTile -> Interval Morton
- mortonTileRect :: MortonTile -> MortonRect
- enclosingMortonTile :: MortonRect -> MortonTile
- splitMortonTile :: MortonTile -> [MortonTile]
- trimMortonTile :: MortonRect -> MortonTile -> Maybe MortonTile
- mortonTileCoverSized :: Int -> Maybe Int -> MortonRect -> [MortonTile]
- mortonTileCover :: MortonRect -> [MortonTile]
- mortonTileCoverTorus :: Morton -> Morton -> [MortonTile]
Documentation
Type implementing a Morton Z-Order Curve.
Stores two Word32
values with bits interleaved.
This allows for spatial indexing by rectangular tiles which form contiguous intervals.
pattern MortonPair :: Word32 -> Word32 -> Morton | Construct a Morton value from its two coordinates. |
Intervals
Type for closed intervals. The second field should be greater than the first.
Interval a a |
intersectInterval :: Ord a => Interval a -> Interval a -> Maybe (Interval a) Source #
Returns intersection of two intervals, or Nothing if they do not overlap.
intervalElem :: Ord a => a -> Interval a -> Bool Source #
Tests whether an element is contained within a given Interval.
intervalSize :: Integral a => Interval a -> Integer Source #
Returns the size of an integer interval.
Rectangles
data MortonRect Source #
Type for retangles in Morton space reperesented by upper-left and lower-right corners
pattern MortonRectSides :: Interval Word32 -> Interval Word32 -> MortonRect | Construct/match rectangles by their sides. |
Instances
Eq MortonRect Source # | |
Defined in Data.Morton (==) :: MortonRect -> MortonRect -> Bool # (/=) :: MortonRect -> MortonRect -> Bool # | |
Read MortonRect Source # | |
Defined in Data.Morton readsPrec :: Int -> ReadS MortonRect # readList :: ReadS [MortonRect] # readPrec :: ReadPrec MortonRect # readListPrec :: ReadPrec [MortonRect] # | |
Show MortonRect Source # | |
Defined in Data.Morton showsPrec :: Int -> MortonRect -> ShowS # show :: MortonRect -> String # showList :: [MortonRect] -> ShowS # |
mortonRectBounds :: MortonRect -> (Interval Word32, Interval Word32) Source #
Returns x,y bounds of a rectangle
intersectMortonRect :: MortonRect -> MortonRect -> Maybe MortonRect Source #
Rerurns intersection of two rectangles.
mortonRectSize :: MortonRect -> Integer Source #
Returns the area of a rectangle
Tiles
data MortonTile Source #
Type for a tile in Morton space, a special type of rectangle which is the set of all points sharing a common binary prefex. Reperesented as a point and mask length simillarly to a CIDR subnet.
Instances
Eq MortonTile Source # | Values which reperesent the same tile compare equal even if the reperesentative points differ. |
Defined in Data.Morton (==) :: MortonTile -> MortonTile -> Bool # (/=) :: MortonTile -> MortonTile -> Bool # | |
Ord MortonTile Source # | A tile sorts immediately before its subtiles, i.e. x sorts before 0 and 1. |
Defined in Data.Morton compare :: MortonTile -> MortonTile -> Ordering # (<) :: MortonTile -> MortonTile -> Bool # (<=) :: MortonTile -> MortonTile -> Bool # (>) :: MortonTile -> MortonTile -> Bool # (>=) :: MortonTile -> MortonTile -> Bool # max :: MortonTile -> MortonTile -> MortonTile # min :: MortonTile -> MortonTile -> MortonTile # | |
Read MortonTile Source # | |
Defined in Data.Morton readsPrec :: Int -> ReadS MortonTile # readList :: ReadS [MortonTile] # readPrec :: ReadPrec MortonTile # readListPrec :: ReadPrec [MortonTile] # | |
Show MortonTile Source # | |
Defined in Data.Morton showsPrec :: Int -> MortonTile -> ShowS # show :: MortonTile -> String # showList :: [MortonTile] -> ShowS # |
mortonTileBounds :: MortonTile -> Interval Morton Source #
Returns a tile as an Interval
.
mortonTileRect :: MortonTile -> MortonRect Source #
Returns a tile as a MortonRect
.
enclosingMortonTile :: MortonRect -> MortonTile Source #
Finds the smallest tile completely enclosing a rectangle. This can be arbitrarily large if the rectangle crosses a seam.
splitMortonTile :: MortonTile -> [MortonTile] Source #
Splits a MortonTile
in half. Does not split tiles containing a single value.
trimMortonTile :: MortonRect -> MortonTile -> Maybe MortonTile Source #
Trims a MortonTile
to its subtile overlapping a given rectangle.
Returns Nothing
if the rectabgle and tile do not intersect.
mortonTileCoverSized :: Int -> Maybe Int -> MortonRect -> [MortonTile] Source #
Covers a rectangle using tiles within a range of sizes (specified by their mask values).
mortonTileCover :: MortonRect -> [MortonTile] Source #
Covers a rectangle with tiles no larger then the area to be covered (no lower size limit). The total area coverd by these tiles bas a trivial upper bound of 8 tiles the rectangle's area plus the area of its enclosing square and the actual performance is usually significantly better (possibly always, although I have not proven so).
mortonTileCoverTorus :: Morton -> Morton -> [MortonTile] Source #
Version of mortonTileCover
which allows the rectangle to wrap around the maximum x/y coordinates (as if the space were a torus).