dstring-0.3.0.1: 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) append 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 make use of some functions from the string-combinators package: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/string-combinators)

 {-# LANGUAGE OverloadedStrings #-}

 import Data.DString
 import Data.String.Combinators ((<+>), fromShow, paren)

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

 instance Show a => Show (Tree a) where
     show = toString . go
         where
           go (Leaf x)     = "Leaf" <+> fromShow x
           go (Branch l r) = "Branch" <+> paren (go l) <+> paren (go r)

Conversion

fromDList :: DList Char -> DStringSource

Convert a difference list of Chars to a difference string

toDList :: DString -> DList CharSource

Convert a difference string to a difference list

fromShowS :: ShowS -> DStringSource

Convert a ShowS to a difference string

toShowS :: DString -> ShowSSource

Convert a difference string to a ShowS

Basic functions

singleton :: Char -> DStringSource

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 :: b -> (Char -> DString -> b) -> DString -> bSource

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 :: (b -> Maybe (Char, b)) -> b -> DStringSource

Unfoldr for difference strings

foldr :: (Char -> b -> b) -> b -> DString -> bSource

Foldr over difference strings