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 HaskellSafe
LanguageHaskell2010

Data.RTree.Base

Contents

Description

Internal implementations. Use RTree instead or use at you own risc.

Synopsis

Data Type

data RTree a Source #

Constructors

Node4 

Fields

Node3 

Fields

Node2 

Fields

Node 

Fields

Leaf 

Fields

Empty 
Instances
Functor RTree Source # 
Instance details

Defined in Data.RTree.Base

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.Base

Methods

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

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

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

Defined in Data.RTree.Base

Methods

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

show :: RTree a -> String #

showList :: [RTree a] -> ShowS #

Generic (RTree a) Source # 
Instance details

Defined in Data.RTree.Base

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.Base

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.Base

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.Base

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.Base

Methods

rnf :: RTree a -> () #

type Rep (RTree a) Source # 
Instance details

Defined in Data.RTree.Base

type Rep (RTree a) = D1 (MetaData "RTree" "Data.RTree.Base" "data-r-tree-0.6.0-HxW7KWxwR847heBr9qHG8D" False) ((C1 (MetaCons "Node4" PrefixI True) ((S1 (MetaSel (Just "getMBB") SourceUnpack SourceStrict DecidedStrict) (Rec0 MBB) :*: S1 (MetaSel (Just "getC1") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RTree a))) :*: (S1 (MetaSel (Just "getC2") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RTree a)) :*: (S1 (MetaSel (Just "getC3") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RTree a)) :*: S1 (MetaSel (Just "getC4") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RTree a))))) :+: (C1 (MetaCons "Node3" PrefixI True) ((S1 (MetaSel (Just "getMBB") SourceUnpack SourceStrict DecidedStrict) (Rec0 MBB) :*: S1 (MetaSel (Just "getC1") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RTree a))) :*: (S1 (MetaSel (Just "getC2") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RTree a)) :*: S1 (MetaSel (Just "getC3") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RTree a)))) :+: C1 (MetaCons "Node2" PrefixI True) (S1 (MetaSel (Just "getMBB") SourceUnpack SourceStrict DecidedStrict) (Rec0 MBB) :*: (S1 (MetaSel (Just "getC1") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RTree a)) :*: S1 (MetaSel (Just "getC2") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (RTree a)))))) :+: (C1 (MetaCons "Node" PrefixI True) (S1 (MetaSel (Just "getMBB") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MBB) :*: S1 (MetaSel (Just "getChildren'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RTree a])) :+: (C1 (MetaCons "Leaf" PrefixI True) (S1 (MetaSel (Just "getMBB") SourceUnpack SourceStrict DecidedStrict) (Rec0 MBB) :*: S1 (MetaSel (Just "getElem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Empty" PrefixI False) (U1 :: Type -> Type))))

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 intersects with the given bounding box.

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

returns all values, which intersects 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.

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

returns all keys and values containing the given bounding box

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

returns all 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)

Internal and Testing

foldWithMBB :: (MBB -> a -> b) -> (MBB -> [b] -> b) -> b -> RTree a -> b Source #

pp :: Show a => RTree a -> IO () Source #

isValid :: Show b => b -> RTree a -> Bool Source #

unionDistinct :: RTree a -> RTree a -> RTree a Source #

Únifies left and right RTree. Will create invalid trees, if the tree is not a leaf and contains MBBs which also exists in the left tree. Much faster than union, though.

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

Unifies left and right RTree. Will create invalid trees, if the tree is not a leaf and contains MBBs which also exists in the left tree. Much faster than union, though.

fromList' :: [RTree a] -> RTree a Source #

merges all singletons into a single tree.

unionDistinctSplit :: (a -> a -> a) -> RTree a -> RTree a -> [RTree a] Source #

partition :: (a -> Bool) -> [a] -> ([a], [a]) #

The partition function takes a predicate a list and returns the pair of lists of elements which do and do not satisfy the predicate, respectively; i.e.,

partition p xs == (filter p xs, filter (not . p) xs)
>>> partition (`elem` "aeiou") "Hello World!"
("eoo","Hll Wrld!")

n :: Int Source #

It is possible, to change these constants, but the tree won't be space optimal anymore.

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

O(n²) solution

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