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

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Compositions.Snoc.Internal

Description

See Data.Compositions.Snoc 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

newtype Flip a Source #

Constructors

Flip 

Fields

Instances

Functor Flip Source # 

Methods

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

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

Eq a => Eq (Flip a) Source # 

Methods

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

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

Monoid a => Monoid (Flip a) Source # 

Methods

mempty :: Flip a #

mappend :: Flip a -> Flip a -> Flip a #

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

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 left-associativity, in that we only support efficient snoccing to the end of the list. This also means that the drop operation can be inefficient. The append operation a <> b performs O(b log (a + b)) element compositions, so you want the right-hand list b to be as small as possible.

For a version biased to consing, see Data.Compositions. This gives the opposite performance characteristics, where take is slow and drop is fast.

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

C 

Fields

Instances

Foldable Compositions Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Compositions a -> [a] #

null :: Compositions a -> Bool #

length :: Compositions a -> Int #

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

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

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

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

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

Eq a => Eq (Compositions a) Source # 
(Monoid a, Read a) => Read (Compositions a) Source # 
Show a => Show (Compositions a) Source # 
Monoid a => Monoid (Compositions a) Source # 

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

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

Construct a compositions list containing just one element.

\(x :: Element) -> singleton x == snoc mempty x
\(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]

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 the worst case, performs O(k log k) element compositions, in order to maintain the left-associative bias. If you wish to run composed on the result of drop, use dropComposed for better performance. Rewrite RULES are provided for compilers which support them.

\(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 O(log k) time.

\(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

dropComposed :: Monoid a => Int -> Compositions a -> a Source #

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

\(Compositions l) n -> dropComposed n l == composed (drop n l)
\(Compositions l) -> dropComposed 0 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)

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)

snoc :: Monoid a => Compositions a -> a -> Compositions a Source #

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

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

Refinement of List snoc:

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