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)
- breakByte :: Word8 -> Rope -> (Rope, Rope)
- breaks :: Word8 -> Rope -> [Rope]
- lines :: Rope -> [Rope]
- index :: Rope -> Int -> Char
- elemIndex :: Word8 -> Rope -> Maybe Int
- elemIndex' :: Word8 -> Rope -> Maybe Int
- elemIndices :: Word8 -> Rope -> [Int]
- readFile :: FilePath -> IO Rope
- hGet :: Handle -> Int -> IO Rope
- hGetLine :: Handle -> IO Rope
- hGetContents :: Handle -> 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 Rope
s
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 Rope
s
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 Rope
s
and concatenates the result.
Concatenations
Reducing Rope
s
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 Rope
s
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 Rope
s
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.
Input and Output
hGetLine :: Handle -> IO RopeSource
Returns the next line in the input Handle
. If you need to iterate hGetLine
,
it may be more efficient to first mmap
the file using readFile
, or even load
it with then iterate
: breakByte
0x0ahGetLine
allocates a buffer to read the file
and may waste most of this space if the lines are shorter than the standard buffer
size of this module.
hGetContents :: Handle -> IO RopeSource
Reads the contents of a file handle strictly, then closes it.