Data.Rope
Contents
Description
Implementation of the ideas in http://www.cs.ubc.ca/local/reading/proceedings/spe91-95/spe/vol25/issue12/spe986.pdf. Inspired also by Data.Map and the OCaml version of ropes.
- data Rope
- empty :: Rope
- singleton :: Word8 -> Rope
- pack :: [Word8] -> Rope
- unpack :: Rope -> [Word8]
- fromByteString :: ByteString -> Rope
- toByteString :: Rope -> ByteString
- cons :: Word8 -> Rope -> Rope
- snoc :: Rope -> Word8 -> Rope
- append :: Rope -> Rope -> Rope
- head :: Rope -> Word8
- uncons :: Rope -> Maybe (Word8, Rope)
- last :: Rope -> Word8
- tail :: Rope -> Rope
- init :: Rope -> Rope
- null :: Rope -> Bool
- length :: Rope -> Int
- map :: (Word8 -> Word8) -> Rope -> Rope
- reverse :: Rope -> Rope
- intercalate :: Rope -> [Rope] -> Rope
- insert :: Rope -> Int -> Rope -> Rope
- foldl :: (a -> Word8 -> a) -> a -> Rope -> a
- foldl' :: (a -> Word8 -> a) -> a -> Rope -> a
- foldr :: (Word8 -> a -> a) -> a -> Rope -> a
- take :: Int -> Rope -> Rope
- drop :: Int -> Rope -> Rope
- splitAt# :: Int -> Rope -> (#Rope, Rope#)
- splitAt :: Int -> Rope -> (Rope, Rope)
- index :: Rope -> Int -> Char
- elemIndex :: Word8 -> Rope -> Maybe Int
- elemIndices :: Word8 -> Rope -> [Int]
- readFile :: FilePath -> IO Rope
- hGet :: Handle -> Int -> IO Rope
- hPut :: Handle -> Rope -> IO ()
- hPutStrLn :: Handle -> Rope -> IO ()
- hPutStr :: Handle -> Rope -> IO ()
- putStrLn :: Rope -> IO ()
- putStr :: Rope -> IO ()
The Rope type
Introducing and eliminating Ropes
fromByteString :: ByteString -> RopeSource
O(n) Conversion from a strict ByteString
toByteString :: Rope -> ByteStringSource
O(n) Conversion to a strict ByteString
Basic interface
cons :: Word8 -> Rope -> RopeSource
O(log n). Appends the specified byte at the beginning of the Rope.
O(log n) First element of the Rope. Raises an error if the argument is empty.
O(log n) The elements after the head. An error is raised if the Rope is empty.
Transforming Ropes
map :: (Word8 -> Word8) -> Rope -> RopeSource
O(n). applies map f rf on each element of r and returns the
concatenation of the result.
intercalate :: Rope -> [Rope] -> RopeSource
O(n) intercalate an element between each element of the list of Ropes
and concatenates the result.
Concatenations
Reducing Ropes
foldl :: (a -> Word8 -> a) -> a -> Rope -> aSource
O(n). fold over a Rope.
This implementation is not tail-recursive but never pushes more than
O(log n) calls on the stack.
foldr :: (Word8 -> a -> a) -> a -> Rope -> aSource
O(n). Right fold. Again not tail-recursive but never uses more than O(log n) on the stack.
Breaking Ropes
splitAt :: Int -> Rope -> (Rope, Rope)Source
O(log n). is equivalent to (take n xs, drop n xs), but a little faster.
splitAt n xs
Indexing Ropes
elemIndex :: Word8 -> Rope -> Maybe IntSource
O(n) returns the index of the first element equal to the query element. This implementation
uses memchr at leaves, and explores the rope in parallel (with par).
elemIndices :: Word8 -> Rope -> [Int]Source
O(n) returns the list of all positions where the queried elements occurs in the Rope.
This implementation uses memchr.