EdisonCore-1.3.2: A library of efficient, purely-functional data structures (Core Implementations)

Copyright(c) Ross Paterson Ralf Hinze 2006
LicenseBSD-style
Maintainerrobdockins AT fastmail DOT fm
Stabilityinternal (non-stable)
Portabilitynon-portable (MPTCs and functional dependencies)
Safe HaskellNone
LanguageHaskell2010

Data.Edison.Concrete.FingerTree

Description

A general sequence representation with arbitrary annotations, for use as a base for implementations of various collection types, as described in section 4 of

This data structure forms the basis of the Data.Edison.Seq.FingerSeq sequence data structure.

An amortized running time is given for each operation, with n referring to the length of the sequence. These bounds hold even in a persistent (shared) setting.

Synopsis

Documentation

data FingerTree v a Source #

Finger trees with element type a, annotated with measures of type v. The operations enforce the constraint Measured v a.

Instances

Measured v a => Measured v (FingerTree v a) Source # 

Methods

measure :: FingerTree v a -> v #

(Measured v a, Eq a) => Eq (FingerTree v a) Source # 

Methods

(==) :: FingerTree v a -> FingerTree v a -> Bool #

(/=) :: FingerTree v a -> FingerTree v a -> Bool #

(Measured v a, Ord a) => Ord (FingerTree v a) Source # 

Methods

compare :: FingerTree v a -> FingerTree v a -> Ordering #

(<) :: FingerTree v a -> FingerTree v a -> Bool #

(<=) :: FingerTree v a -> FingerTree v a -> Bool #

(>) :: FingerTree v a -> FingerTree v a -> Bool #

(>=) :: FingerTree v a -> FingerTree v a -> Bool #

max :: FingerTree v a -> FingerTree v a -> FingerTree v a #

min :: FingerTree v a -> FingerTree v a -> FingerTree v a #

(Measured v a, Show a) => Show (FingerTree v a) Source # 

Methods

showsPrec :: Int -> FingerTree v a -> ShowS #

show :: FingerTree v a -> String #

showList :: [FingerTree v a] -> ShowS #

(Measured v a, Arbitrary a) => Arbitrary (FingerTree v a) Source # 

Methods

arbitrary :: Gen (FingerTree v a) #

shrink :: FingerTree v a -> [FingerTree v a] #

(Measured v a, CoArbitrary a) => CoArbitrary (FingerTree v a) Source # 

Methods

coarbitrary :: FingerTree v a -> Gen b -> Gen b #

data Split t a Source #

Constructors

Split t a t 

empty :: Measured v a => FingerTree v a Source #

O(1). The empty sequence.

singleton :: Measured v a => a -> FingerTree v a Source #

O(1). A singleton sequence.

lcons :: Measured v a => a -> FingerTree v a -> FingerTree v a infixr 5 Source #

O(1). Add an element to the left end of a sequence.

rcons :: Measured v a => a -> FingerTree v a -> FingerTree v a Source #

O(1). Add an element to the right end of a sequence.

append :: Measured v a => FingerTree v a -> FingerTree v a -> FingerTree v a Source #

O(log(min(n1,n2))). Concatenate two sequences.

fromList :: Measured v a => [a] -> FingerTree v a Source #

O(n). Create a sequence from a finite list of elements.

toList :: FingerTree v a -> [a] Source #

null :: Measured v a => FingerTree v a -> Bool Source #

O(1). Is this the empty sequence?

lview :: (Measured v a, Monad m) => FingerTree v a -> m (a, FingerTree v a) Source #

O(1). Analyse the left end of a sequence.

rview :: (Measured v a, Monad m) => FingerTree v a -> m (a, FingerTree v a) Source #

O(1). Analyse the right end of a sequence.

split :: Measured v a => (v -> Bool) -> FingerTree v a -> (FingerTree v a, FingerTree v a) Source #

O(log(min(i,n-i))). Split a sequence at a point where the predicate on the accumulated measure changes from False to True.

takeUntil :: Measured v a => (v -> Bool) -> FingerTree v a -> FingerTree v a Source #

dropUntil :: Measured v a => (v -> Bool) -> FingerTree v a -> FingerTree v a Source #

splitTree :: Measured v a => (v -> Bool) -> v -> FingerTree v a -> Split (FingerTree v a) a Source #

reverse :: Measured v a => FingerTree v a -> FingerTree v a Source #

O(n). The reverse of a sequence.

mapTree :: Measured v2 a2 => (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2 Source #

foldFT :: b -> (b -> b -> b) -> (a -> b) -> FingerTree v a -> b Source #

reduce1 :: (a -> a -> a) -> FingerTree v a -> a Source #

reduce1' :: (a -> a -> a) -> FingerTree v a -> a Source #

strictWith :: (a -> b) -> FingerTree v a -> FingerTree v a Source #