hw-fingertree-strict-0.1.2.0: Generic strict finger-tree structure

Copyright(c) Ross Paterson Ralf Hinze 2006
LicenseBSD-style
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilitynon-portable (MPTCs and functional dependencies)
Safe HaskellSafe
LanguageHaskell2010

HaskellWorks.Data.FingerTree.Strict

Contents

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

For a directly usable sequence type, see Data.Sequence, which is a specialization of this 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.

Note: Many of these operations have the same names as similar operations on lists in the Prelude. The ambiguity may be resolved using either qualification or the hiding clause.

Synopsis

Documentation

data FingerTree v a Source #

A representation of a sequence of values of type a, allowing access to the ends in constant time, and append and split in time logarithmic in the size of the smaller piece.

The collection is also parameterized by a measure type v, which is used to specify a position in the sequence for the split operation. The types of the operations enforce the constraint Measured v a, which also implies that the type v is determined by a.

A variety of abstract data types can be implemented by using different element types and measurements.

Constructors

Empty 
Single !a 
Deep !v !(Digit a) !(FingerTree v (Node v a)) !(Digit a) 
Instances
Measured v a => Measured v (FingerTree v a) Source #

O(1). The cached measure of a tree.

Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

measure :: FingerTree v a -> v Source #

Foldable (FingerTree v) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

fold :: Monoid m => FingerTree v m -> m #

foldMap :: Monoid m => (a -> m) -> FingerTree v a -> m #

foldr :: (a -> b -> b) -> b -> FingerTree v a -> b #

foldr' :: (a -> b -> b) -> b -> FingerTree v a -> b #

foldl :: (b -> a -> b) -> b -> FingerTree v a -> b #

foldl' :: (b -> a -> b) -> b -> FingerTree v a -> b #

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

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

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

null :: FingerTree v a -> Bool #

length :: FingerTree v a -> Int #

elem :: Eq a => a -> FingerTree v a -> Bool #

maximum :: Ord a => FingerTree v a -> a #

minimum :: Ord a => FingerTree v a -> a #

sum :: Num a => FingerTree v a -> a #

product :: Num a => FingerTree v a -> a #

Eq a => Eq (FingerTree v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

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

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

Ord a => Ord (FingerTree v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

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 #

(Show a, Show v) => Show (FingerTree v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

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

show :: FingerTree v a -> String #

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

Generic (FingerTree v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Associated Types

type Rep (FingerTree v a) :: Type -> Type #

Methods

from :: FingerTree v a -> Rep (FingerTree v a) x #

to :: Rep (FingerTree v a) x -> FingerTree v a #

Measured v a => Semigroup (FingerTree v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

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

sconcat :: NonEmpty (FingerTree v a) -> FingerTree v a #

stimes :: Integral b => b -> FingerTree v a -> FingerTree v a #

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

empty and ><.

Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

mempty :: FingerTree v a #

mappend :: FingerTree v a -> FingerTree v a -> FingerTree v a #

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

(NFData a, NFData v) => NFData (FingerTree v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

rnf :: FingerTree v a -> () #

type Rep (FingerTree v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

data Digit a Source #

Constructors

One !a 
Two !a !a 
Three !a !a !a 
Four !a !a !a !a 
Instances
Foldable Digit Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

fold :: Monoid m => Digit m -> m #

foldMap :: Monoid m => (a -> m) -> Digit a -> m #

foldr :: (a -> b -> b) -> b -> Digit a -> b #

foldr' :: (a -> b -> b) -> b -> Digit a -> b #

foldl :: (b -> a -> b) -> b -> Digit a -> b #

foldl' :: (b -> a -> b) -> b -> Digit a -> b #

foldr1 :: (a -> a -> a) -> Digit a -> a #

foldl1 :: (a -> a -> a) -> Digit a -> a #

toList :: Digit a -> [a] #

null :: Digit a -> Bool #

length :: Digit a -> Int #

elem :: Eq a => a -> Digit a -> Bool #

maximum :: Ord a => Digit a -> a #

minimum :: Ord a => Digit a -> a #

sum :: Num a => Digit a -> a #

product :: Num a => Digit a -> a #

Measured v a => Measured v (Digit a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

measure :: Digit a -> v Source #

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

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

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

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

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

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

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

show :: Digit a -> String #

showList :: [Digit a] -> ShowS #

Generic (Digit a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Associated Types

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

Methods

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

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

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

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

rnf :: Digit a -> () #

type Rep (Digit a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

data Node v a Source #

Constructors

Node2 !v !a !a 
Node3 !v !a !a !a 
Instances
Monoid v => Measured v (Node v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

measure :: Node v a -> v Source #

Foldable (Node v) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

fold :: Monoid m => Node v m -> m #

foldMap :: Monoid m => (a -> m) -> Node v a -> m #

foldr :: (a -> b -> b) -> b -> Node v a -> b #

foldr' :: (a -> b -> b) -> b -> Node v a -> b #

foldl :: (b -> a -> b) -> b -> Node v a -> b #

foldl' :: (b -> a -> b) -> b -> Node v a -> b #

foldr1 :: (a -> a -> a) -> Node v a -> a #

foldl1 :: (a -> a -> a) -> Node v a -> a #

toList :: Node v a -> [a] #

null :: Node v a -> Bool #

length :: Node v a -> Int #

elem :: Eq a => a -> Node v a -> Bool #

maximum :: Ord a => Node v a -> a #

minimum :: Ord a => Node v a -> a #

sum :: Num a => Node v a -> a #

product :: Num a => Node v a -> a #

(Show v, Show a) => Show (Node v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

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

show :: Node v a -> String #

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

Generic (Node v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Associated Types

type Rep (Node v a) :: Type -> Type #

Methods

from :: Node v a -> Rep (Node v a) x #

to :: Rep (Node v a) x -> Node v a #

(NFData v, NFData a) => NFData (Node v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

rnf :: Node v a -> () #

type Rep (Node v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

deep :: Measured v a => Digit a -> FingerTree v (Node v a) -> Digit a -> FingerTree v a Source #

node2 :: Measured v a => a -> a -> Node v a Source #

node3 :: Measured v a => a -> a -> a -> Node v a Source #

class Monoid v => Measured v a | a -> v where Source #

Things that can be measured.

Methods

measure :: a -> v Source #

Instances
Measured v a => Measured v (Digit a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

measure :: Digit a -> v Source #

Monoid k => Measured k (Segment k) Source # 
Instance details

Defined in HaskellWorks.Data.Segment.Strict

Methods

measure :: Segment k -> k Source #

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

O(1). The cached measure of a tree.

Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

measure :: FingerTree v a -> v Source #

Monoid v => Measured v (Node v a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

measure :: Node v a -> v Source #

Monoid k => Measured k (Item k a) Source # 
Instance details

Defined in HaskellWorks.Data.Item.Strict

Methods

measure :: Item k a -> k Source #

Construction

empty :: FingerTree v a Source #

O(1). The empty sequence.

singleton :: a -> FingerTree v a Source #

O(1). A singleton sequence.

(<|) :: 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. Mnemonic: a triangle with the single element at the pointy end.

(|>) :: Measured v a => FingerTree v a -> a -> FingerTree v a infixl 5 Source #

O(1). Add an element to the right end of a sequence. Mnemonic: a triangle with the single element at the pointy end.

(><) :: Measured v a => FingerTree v a -> FingerTree v a -> FingerTree v a infixr 5 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.

Deconstruction

null :: FingerTree v a -> Bool Source #

O(1). Is this the empty sequence?

data ViewL s a Source #

View of the left end of a sequence.

Constructors

EmptyL

empty sequence

!a :< !(s a) infixr 5

leftmost element and the rest of the sequence

Instances
Functor s => Functor (ViewL s) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

fmap :: (a -> b) -> ViewL s a -> ViewL s b #

(<$) :: a -> ViewL s b -> ViewL s a #

(Eq a, Eq (s a)) => Eq (ViewL s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

(==) :: ViewL s a -> ViewL s a -> Bool #

(/=) :: ViewL s a -> ViewL s a -> Bool #

(Ord a, Ord (s a)) => Ord (ViewL s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

compare :: ViewL s a -> ViewL s a -> Ordering #

(<) :: ViewL s a -> ViewL s a -> Bool #

(<=) :: ViewL s a -> ViewL s a -> Bool #

(>) :: ViewL s a -> ViewL s a -> Bool #

(>=) :: ViewL s a -> ViewL s a -> Bool #

max :: ViewL s a -> ViewL s a -> ViewL s a #

min :: ViewL s a -> ViewL s a -> ViewL s a #

(Read a, Read (s a)) => Read (ViewL s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

(Show a, Show (s a)) => Show (ViewL s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

showsPrec :: Int -> ViewL s a -> ShowS #

show :: ViewL s a -> String #

showList :: [ViewL s a] -> ShowS #

Generic (ViewL s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Associated Types

type Rep (ViewL s a) :: Type -> Type #

Methods

from :: ViewL s a -> Rep (ViewL s a) x #

to :: Rep (ViewL s a) x -> ViewL s a #

(NFData a, NFData (s a)) => NFData (ViewL s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

rnf :: ViewL s a -> () #

type Rep (ViewL s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

type Rep (ViewL s a) = D1 (MetaData "ViewL" "HaskellWorks.Data.FingerTree.Strict" "hw-fingertree-strict-0.1.2.0-9KMqjjq0jDuC8F7Rb6fXpc" False) (C1 (MetaCons "EmptyL" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons ":<" (InfixI RightAssociative 5) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (s a))))

data ViewR s a Source #

View of the right end of a sequence.

Constructors

EmptyR

empty sequence

!(s a) :> !a infixl 5

the sequence minus the rightmost element, and the rightmost element

Instances
Functor s => Functor (ViewR s) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

fmap :: (a -> b) -> ViewR s a -> ViewR s b #

(<$) :: a -> ViewR s b -> ViewR s a #

(Eq a, Eq (s a)) => Eq (ViewR s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

(==) :: ViewR s a -> ViewR s a -> Bool #

(/=) :: ViewR s a -> ViewR s a -> Bool #

(Ord a, Ord (s a)) => Ord (ViewR s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

compare :: ViewR s a -> ViewR s a -> Ordering #

(<) :: ViewR s a -> ViewR s a -> Bool #

(<=) :: ViewR s a -> ViewR s a -> Bool #

(>) :: ViewR s a -> ViewR s a -> Bool #

(>=) :: ViewR s a -> ViewR s a -> Bool #

max :: ViewR s a -> ViewR s a -> ViewR s a #

min :: ViewR s a -> ViewR s a -> ViewR s a #

(Read a, Read (s a)) => Read (ViewR s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

(Show a, Show (s a)) => Show (ViewR s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

showsPrec :: Int -> ViewR s a -> ShowS #

show :: ViewR s a -> String #

showList :: [ViewR s a] -> ShowS #

Generic (ViewR s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Associated Types

type Rep (ViewR s a) :: Type -> Type #

Methods

from :: ViewR s a -> Rep (ViewR s a) x #

to :: Rep (ViewR s a) x -> ViewR s a #

(NFData a, NFData (s a)) => NFData (ViewR s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

Methods

rnf :: ViewR s a -> () #

type Rep (ViewR s a) Source # 
Instance details

Defined in HaskellWorks.Data.FingerTree.Strict

type Rep (ViewR s a) = D1 (MetaData "ViewR" "HaskellWorks.Data.FingerTree.Strict" "hw-fingertree-strict-0.1.2.0-9KMqjjq0jDuC8F7Rb6fXpc" False) (C1 (MetaCons "EmptyR" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons ":>" (InfixI LeftAssociative 5) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (s a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)))

viewl :: Measured v a => FingerTree v a -> ViewL (FingerTree v) a Source #

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

viewr :: Measured v a => FingerTree v a -> ViewR (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.

For predictable results, one should ensure that there is only one such point, i.e. that the predicate is monotonic.

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

O(log(min(i,n-i))). Given a monotonic predicate p, takeUntil p t is the largest prefix of t whose measure does not satisfy p.

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

O(log(min(i,n-i))). Given a monotonic predicate p, dropUntil p t is the rest of t after removing the largest prefix whose measure does not satisfy p.

Transformation

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

O(n). The reverse of a sequence.

fmap' :: (Measured v1 a1, Measured v2 a2) => (a1 -> a2) -> FingerTree v1 a1 -> FingerTree v2 a2 Source #

Like fmap, but with a more constrained type.

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

Map all elements of the tree with a function that also takes the measure of the prefix of the tree to the left of the element.

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

Like fmap, but safe only if the function preserves the measure.

traverse' :: (Measured v1 a1, Measured v2 a2, Applicative f) => (a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2) Source #

Like traverse, but with a more constrained type.

traverseWithPos :: (Measured v1 a1, Measured v2 a2, Applicative f) => (v1 -> a1 -> f a2) -> FingerTree v1 a1 -> f (FingerTree v2 a2) Source #

Traverse the tree with a function that also takes the measure of the prefix of the tree to the left of the element.

unsafeTraverse :: Applicative f => (a -> f b) -> FingerTree v a -> f (FingerTree v b) Source #

Like traverse, but safe only if the function preserves the measure.

Example

Particular abstract data types may be implemented by defining element types with suitable Measured instances.

(from section 4.5 of the paper) Simple sequences can be implemented using a Sum monoid as a measure:

newtype Elem a = Elem { getElem :: a }

instance Measured (Sum Int) (Elem a) where
    measure (Elem _) = Sum 1

newtype Seq a = Seq (FingerTree (Sum Int) (Elem a))

Then the measure of a subsequence is simply its length. This representation supports log-time extraction of subsequences:

take :: Int -> Seq a -> Seq a
take k (Seq xs) = Seq (takeUntil (> Sum k) xs)

drop :: Int -> Seq a -> Seq a
drop k (Seq xs) = Seq (dropUntil (> Sum k) xs)

The module Data.Sequence is an optimized instantiation of this type.

For further examples, see Data.IntervalMap.FingerTree and Data.PriorityQueue.FingerTree.