data-r-tree-0.6.0: R-Tree is a spatial data structure similar to Quadtrees or B-Trees.

CopyrightCopyright (c) 2015 Birte Wagner Sebastian Philipp
LicenseMIT
MaintainerBirte Wagner, Sebastian Philipp (sebastian@spawnhost.de)
Stabilityexperimental
Portabilitynot portable
Safe HaskellNone
LanguageHaskell2010

Data.RTree.Strict

Contents

Description

This is the Strict version of RTree

the following property should be true (by using isNF ) :

>>> propNF :: RTree a -> IO Bool
>>> propNF e = isNF $! e
Synopsis

MBB

data MBB Source #

Minimal bounding box

Instances
Eq MBB Source # 
Instance details

Defined in Data.RTree.MBB

Methods

(==) :: MBB -> MBB -> Bool #

(/=) :: MBB -> MBB -> Bool #

Ord MBB Source # 
Instance details

Defined in Data.RTree.MBB

Methods

compare :: MBB -> MBB -> Ordering #

(<) :: MBB -> MBB -> Bool #

(<=) :: MBB -> MBB -> Bool #

(>) :: MBB -> MBB -> Bool #

(>=) :: MBB -> MBB -> Bool #

max :: MBB -> MBB -> MBB #

min :: MBB -> MBB -> MBB #

Show MBB Source # 
Instance details

Defined in Data.RTree.MBB

Methods

showsPrec :: Int -> MBB -> ShowS #

show :: MBB -> String #

showList :: [MBB] -> ShowS #

Generic MBB Source # 
Instance details

Defined in Data.RTree.MBB

Associated Types

type Rep MBB :: Type -> Type #

Methods

from :: MBB -> Rep MBB x #

to :: Rep MBB x -> MBB #

Binary MBB Source # 
Instance details

Defined in Data.RTree.MBB

Methods

put :: MBB -> Put #

get :: Get MBB #

putList :: [MBB] -> Put #

type Rep MBB Source # 
Instance details

Defined in Data.RTree.MBB

type Rep MBB = D1 (MetaData "MBB" "Data.RTree.MBB" "data-r-tree-0.6.0-HxW7KWxwR847heBr9qHG8D" False) (C1 (MetaCons "MBB" PrefixI True) ((S1 (MetaSel (Just "getUlx") SourceUnpack SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "getUly") SourceUnpack SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Just "getBrx") SourceUnpack SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "getBry") SourceUnpack SourceStrict DecidedStrict) (Rec0 Double))))

mbb Source #

Arguments

:: Double

x - coordinate of first point

-> Double

y - coordinate of first point

-> Double

x - coordinate of second point

-> Double

x - coordinate of second point

-> MBB 

created a minimal bounding box (or a rectangle) The first point must be smaller, than the second one. This is unchecked.

Data Type

data RTree a Source #

Instances
Functor RTree Source #

RTree is not really a Functor. Because this law doesn't hold:

fmap id = id
Instance details

Defined in Data.RTree.Strict

Methods

fmap :: (a -> b) -> RTree a -> RTree b #

(<$) :: a -> RTree b -> RTree a #

Eq a => Eq (RTree a) Source # 
Instance details

Defined in Data.RTree.Strict

Methods

(==) :: RTree a -> RTree a -> Bool #

(/=) :: RTree a -> RTree a -> Bool #

Show a => Show (RTree a) Source # 
Instance details

Defined in Data.RTree.Strict

Methods

showsPrec :: Int -> RTree a -> ShowS #

show :: RTree a -> String #

showList :: [RTree a] -> ShowS #

Generic (RTree a) Source # 
Instance details

Defined in Data.RTree.Strict

Associated Types

type Rep (RTree a) :: Type -> Type #

Methods

from :: RTree a -> Rep (RTree a) x #

to :: Rep (RTree a) x -> RTree a #

Semigroup a => Semigroup (RTree a) Source # 
Instance details

Defined in Data.RTree.Strict

Methods

(<>) :: RTree a -> RTree a -> RTree a #

sconcat :: NonEmpty (RTree a) -> RTree a #

stimes :: Integral b => b -> RTree a -> RTree a #

Monoid a => Monoid (RTree a) Source # 
Instance details

Defined in Data.RTree.Strict

Methods

mempty :: RTree a #

mappend :: RTree a -> RTree a -> RTree a #

mconcat :: [RTree a] -> RTree a #

Binary a => Binary (RTree a) Source # 
Instance details

Defined in Data.RTree.Strict

Methods

put :: RTree a -> Put #

get :: Get (RTree a) #

putList :: [RTree a] -> Put #

NFData a => NFData (RTree a) Source # 
Instance details

Defined in Data.RTree.Strict

Methods

rnf :: RTree a -> () #

type Rep (RTree a) Source # 
Instance details

Defined in Data.RTree.Strict

type Rep (RTree a) = D1 (MetaData "RTree" "Data.RTree.Strict" "data-r-tree-0.6.0-HxW7KWxwR847heBr9qHG8D" True) (C1 (MetaCons "RTree" PrefixI True) (S1 (MetaSel (Just "toLazy'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RTree a))))

toLazy :: RTree a -> RTree a Source #

converts a strict RTree into a lazy RTree O(1)

toStrict :: RTree a -> RTree a Source #

converts a lazy RTree into a strict RTree O(n)

Constructors

empty :: RTree a Source #

creates an empty tree

singleton :: MBB -> a -> RTree a Source #

creates a single element tree

Modification

insert :: MBB -> a -> RTree a -> RTree a Source #

Inserts an element whith the given MBB and a value in a tree. An existing value will be overwritten with the given one.

insert = insertWith const

insertWith :: (a -> a -> a) -> MBB -> a -> RTree a -> RTree a Source #

Inserts an element whith the given MBB and a value in a tree. The combining function will be used if the value already exists.

delete :: MBB -> RTree a -> RTree a Source #

Delete a key and its value from the RTree. When the key is not a member of the tree, the original tree is returned.

mapMaybe :: (a -> Maybe b) -> RTree a -> RTree b Source #

map, which also filters Nothing values

Merging

union :: RTree a -> RTree a -> RTree a Source #

Unifies the first and the second tree into one. If an MBB is a key in both trees, the value from the left tree is chosen.

union = unionWith const

unionWith :: (a -> a -> a) -> RTree a -> RTree a -> RTree a Source #

Unifies the first and the second tree into one. The combining function is used for elemets which exists in both trees.

Searching and Properties

lookup :: MBB -> RTree a -> Maybe a Source #

returns the value if it exists in the tree

intersectWithKey :: MBB -> RTree a -> [(MBB, a)] Source #

returns all keys and values, which intersect with the given bounding box.

intersect :: MBB -> RTree a -> [a] Source #

returns all values, which intersect with the given bounding box

lookupRange :: MBB -> RTree a -> [a] Source #

returns all values, which are located in the given bounding box.

lookupRangeWithKey :: MBB -> RTree a -> [(MBB, a)] Source #

returns all keys and values, which are located in the given bounding box.

lookupContainsRange :: MBB -> RTree a -> [a] Source #

returns all values containing the given bounding box

lookupContainsRangeWithKey :: MBB -> RTree a -> [(MBB, a)] Source #

returns all keys and values containing the given bounding box

length :: RTree a -> Int Source #

returns the number of elements in a tree

null :: RTree a -> Bool Source #

returns True, if empty

null empty = True

keys :: RTree a -> [MBB] Source #

returns all keys in this tree

toList t = zip (keys t) (values t)

values :: RTree a -> [a] Source #

returns all values in this tree

toList t = zip (keys t) (values t)

Lists

fromList :: [(MBB, a)] -> RTree a Source #

creates a tree out of pairs

toList :: RTree a -> [(MBB, a)] Source #

creates a list of pairs out of a tree

toList t = zip (keys t) (values t)