dstring-0.4: Difference strings

Stabilityexperimental
MaintainerBas van Dijk <v.dijk.bas@gmail.com>

Data.DString

Contents

Description

Difference strings: a data structure for O(1) append on strings. Note that a DString is just a newtype wrapper around a DList Char. The reason we need a new type instead of just a type synonym is that we can have an instance IsString DString without using language extensions (TypeSynonymInstances or FlexibleInstances) so we can write overloaded string literals of type DString.

Synopsis

Documentation

data DString Source

A difference string is a function that given a string, returns the original contents of the difference string prepended at the given string.

This structure supports O(1) mappend en snoc operations on strings making it very usefull for append-heavy uses such as logging and pretty printing.

You can use it to efficiently show a tree for example: (Note that we use some handy functions from the string-combinators package)

 {-# LANGUAGE OverloadedStrings #-}

 import Data.DString (toShowS, fromShowS)
 import Data.String.Combinators ((<+>), parens, thenParens)

 data Tree a = Leaf a | Branch (Tree a) (Tree a)

 instance Show a => Show (Tree a) where
     showsPrec prec t = toShowS $ (prec >= funAppPrec) `thenParens` go t
         where
           go (Leaf x)     = "Leaf" <+> fromShowS (showsPrec funAppPrec x)
           go (Branch l r) = "Branch" <+> parens (go l) <+> parens (go r)

           funAppPrec = 10

Conversion

toString :: DString -> StringSource

O(n) Convert a difference string to a normal string.

fromDList :: DList Char -> DStringSource

O(1) Convert a difference list of Chars to a difference string.

toDList :: DString -> DList CharSource

O(1) Convert a difference string to a difference list.

fromShowS :: ShowS -> DStringSource

O(1) Convert a ShowS to a difference string.

toShowS :: DString -> ShowSSource

O(1) Convert a difference string to a ShowS.

Basic functions

singleton :: Char -> DStringSource

O(1) Build a difference string from a single Char.

cons :: Char -> DString -> DStringSource

O(1), Prepend a Char to a difference string.

snoc :: DString -> Char -> DStringSource

O(1), Append a Char to a difference string.

concat :: [DString] -> DStringSource

O(spine), Concatenate difference strings.

list :: α -> (Char -> DString -> α) -> DString -> αSource

O(length ds), difference list elimination, head, tail.

head :: DString -> CharSource

Return the head of the difference string.

tail :: DString -> DStringSource

Return the tail of the difference string.

unfoldr :: (α -> Maybe (Char, α)) -> α -> DStringSource

Unfoldr for difference strings.

foldr :: (Char -> α -> α) -> α -> DString -> αSource

Foldr over difference strings.