composition-tree-0.2.0.0: Composition trees for arbitrary monoids.

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Compositions.Internal

Description

See Data.Compositions for normal day-to-day use. This module contains the implementation of that module.

Synopsis

Documentation

>>> :set -XScopedTypeVariables
>>> import Control.Applicative
>>> import Test.QuickCheck
>>> import qualified Data.List as List
>>> type Element = [Int]
>>> newtype C = Compositions (Compositions Element) deriving (Show, Eq)
>>> instance (Monoid a, Arbitrary a) => Arbitrary (Compositions a) where arbitrary = fromList <$> arbitrary
>>> instance Arbitrary C where arbitrary = Compositions <$> arbitrary

wellformed :: (Monoid a, Eq a) => Compositions a -> Bool Source

Returns true if the given tree is appropriately right-biased. Used for the following internal debugging tests:

\(Compositions l) -> wellformed l
wellformed (mempty :: Compositions Element)
\(Compositions a) (Compositions b) -> wellformed (a <> b)
\(Compositions t) n -> wellformed (take n t)
\(Compositions t) n -> wellformed (drop n t)

newtype Compositions a Source

A compositions list or composition tree is a list data type where the elements are monoids, and the mconcat of any contiguous sublist can be computed in logarithmic time. A common use case of this type is in a wiki, version control system, or collaborative editor, where each change or delta would be stored in a list, and it is sometimes necessary to compute the composed delta between any two versions.

This version of a composition list is strictly biased to right-associativity, in that we only support efficient consing to the front of the list. This also means that the take operation can be inefficient. The append operation a <> b performs O(a log (a + b)) element compositions, so you want the left-hand list a to be as small as possible.

For a version of the composition list with the opposite bias, and therefore opposite performance characteristics, see Data.Compositions.Snoc.

Monoid laws:

\(Compositions l) -> mempty <> l == l
\(Compositions l) -> l <> mempty == l
\(Compositions t) (Compositions u) (Compositions v) -> t <> (u <> v) == (t <> u) <> v

toList is monoid morphism:

toList (mempty :: Compositions Element) == []
\(Compositions a) (Compositions b) -> toList (a <> b) == toList a ++ toList b

Constructors

Tree 

Fields

unwrap :: [Node a]
 

data Node a Source

Constructors

Node 

Fields

nodeSize :: Int
 
nodeChildren :: Maybe (Node a, Node a)
 
nodeValue :: !a
 

Instances

unsafeMap :: (a -> b) -> Compositions a -> Compositions b Source

Only valid if the function given is a monoid morphism

Otherwise, use fromList . map f . toList (which is much slower).

drop :: Monoid a => Int -> Compositions a -> Compositions a Source

Return the compositions list with the first k elements removed, in O(log k) time.

\(Compositions l) (Positive n) (Positive m) -> drop n (drop m l) == drop m (drop n l)
\(Compositions l) (Positive n) (Positive m) -> drop n (drop m l) == drop (m + n) l
\(Compositions l) (Positive n) -> length (drop n l) == max (length l - n) 0
\(Compositions t) (Compositions u) -> drop (length t) (t <> u) == u
\(Compositions l) -> drop 0 l == l
\n -> drop n (mempty :: Compositions Element) == mempty

Refinement of drop:

\(l :: [Element]) n -> drop n (fromList l) == fromList (List.drop n l)
\(Compositions l) n -> toList (drop n l) == List.drop n (toList l)

take :: Monoid a => Int -> Compositions a -> Compositions a Source

Return the compositions list containing only the first k elements of the input. In the worst case, performs O(k log k) element compositions, in order to maintain the right-associative bias. If you wish to run composed on the result of take, use takeComposed for better performance. Rewrite RULES are provided for compilers which support them.

\(Compositions l) (Positive n) (Positive m) -> take n (take m l) == take m (take n l)
\(Compositions l) (Positive n) (Positive m) -> take m (take n l) == take (m `min` n) l
\(Compositions l) (Positive n) -> length (take n l) == min (length l) n
\(Compositions l) -> take (length l) l == l
\(Compositions l) (Positive n) -> take (length l + n) l == l
\(Positive n) -> take n (mempty :: Compositions Element) == mempty

Refinement of take:

\(l :: [Element]) n -> take n (fromList l) == fromList (List.take n l)
\(Compositions l) n -> toList (take n l) == List.take n (toList l)
\(Compositions l) (Positive n) -> take n l <> drop n l == l

takeComposed :: Monoid a => Int -> Compositions a -> a Source

Returns the composition of the first k elements of the compositions list, doing only O(log k) compositions. Faster than simply using take and then composed separately.

\(Compositions l) n -> takeComposed n l == composed (take n l)
\(Compositions l) -> takeComposed (length l) l == composed l

splitAt :: Monoid a => Int -> Compositions a -> (Compositions a, Compositions a) Source

A convenience alias for take and drop

\(Compositions l) i -> splitAt i l == (take i l, drop i l)

composed :: Monoid a => Compositions a -> a Source

Compose every element in the compositions list. Performs only O(log n) compositions.

Refinement of mconcat:

\(l :: [Element]) -> composed (fromList l) == mconcat l
\(Compositions l) -> composed l == mconcat (toList l)

Is a monoid morphism:

\(Compositions a) (Compositions b) -> composed (a <> b) == composed a <> composed b
composed mempty == (mempty :: Element)

singleton :: Monoid a => a -> Compositions a Source

Construct a compositions list containing just one element.

\(x :: Element) -> singleton x == cons x mempty
\(x :: Element) -> composed (singleton x) == x
\(x :: Element) -> length (singleton x) == 1

Refinement of singleton lists:

\(x :: Element) -> toList (singleton x) == [x]
\(x :: Element) -> singleton x == fromList [x]

length :: Compositions a -> Int Source

Get the number of elements in the compositions list, in O(log n) time.

Is a monoid morphism:

length (mempty :: Compositions Element) == 0
\(Compositions a) (Compositions b) -> length (a <> b) == length a + length b

Refinement of length:

\(x :: [Element]) -> length (fromList x) == List.length x
\(Compositions x) -> length x == List.length (toList x)

fromList :: Monoid a => [a] -> Compositions a Source

Convert a compositions list into a list of elements. The other direction is provided in the Foldable instance. This will perform O(n log n) element compositions.

Isomorphism to lists:

\(Compositions x) -> fromList (toList x) == x
\(x :: [Element]) -> toList (fromList x) == x

Is monoid morphism:

fromList ([] :: [Element]) == mempty
\(a :: [Element]) b -> fromList (a ++ b) == fromList a <> fromList b

cons :: Monoid a => a -> Compositions a -> Compositions a Source

Add a new element to the front of a compositions list. Performs O(log n) element compositions.

\(x :: Element) (Compositions xs) -> cons x xs == singleton x <> xs
\(x :: Element) (Compositions xs) -> length (cons x xs) == length xs + 1

Refinement of List (:):

\(x :: Element) (xs :: [Element]) -> cons x (fromList xs) == fromList (x : xs)
\(x :: Element) (Compositions xs) -> toList (cons x xs) == x : toList xs