Data.Rope
Contents
- data Rope a
- length :: Rope m -> Int
- null :: Rope m -> Bool
- class Monoid m => Reducer c m where
- class Reducer ByteString a => Annotation a where
- elide :: Annotation a => Int -> Int -> Rope a -> Rope a
- splitAt :: Annotation a => Int -> Rope a -> (Rope a, Rope a)
- take :: Annotation a => Int -> Rope a -> Rope a
- drop :: Annotation a => Int -> Rope a -> Rope a
- class Unpackable a where
- class Packable a where
- pack :: Annotation m => a -> Rope m
- packl :: Annotation m => a -> Rope m -> Rope m
- packr :: Annotation m => Rope m -> a -> Rope m
- empty :: Monoid m => Rope m
- fromByteString :: Reducer ByteString m => ByteString -> Rope m
- fromChunks :: Reducer ByteString m => [ByteString] -> Rope m
- fromLazyByteString :: Reducer ByteString m => ByteString -> Rope m
- fromWords :: Reducer ByteString m => [Word8] -> Rope m
- fromChar :: Reducer ByteString m => Char -> Rope m
- fromWord8 :: Reducer ByteString m => Word8 -> Rope m
- fromString :: Reducer ByteString m => String -> Rope m
- toChunks :: Rope m -> [ByteString]
- toLazyByteString :: Rope m -> ByteString
- toString :: Rope m -> String
Size
Instances
| Monad Rope | |
| Functor Rope | |
| Typeable1 Rope | |
| Applicative Rope | |
| Foldable Rope | |
| Traversable Rope | |
| Comonad Rope | |
| Measured Count (Rope a) | |
| (Packable a, Annotation m) => Reducer a (Rope m) | |
| Eq a => Eq (Rope a) | |
| (Annotation a, Data a) => Data (Rope a) | |
| Show a => Show (Rope a) | |
| Monoid a => Monoid (Rope a) | |
| Annotation n => Packable (Rope n) | |
| Annotation a => Annotation (Rope a) | |
| MonadWriter (Rope ()) Rope |
Splicing
class Monoid m => Reducer c m whereSource
This type may be best read infix. A c is a Reducer mMonoid m that maps
values of type c through unit to values of type m. A c-Reducer may also
supply operations which tack-on another c to an existing Monoid m on the left
or right. These specialized reductions may be more efficient in some scenarios
and are used when appropriate by a Generator. The names cons and snoc work
by analogy to the synonymous operations in the list monoid.
This class deliberately avoids functional-dependencies, so that () can be a c-Reducer
for all c, and so many common reducers can work over multiple types, for instance,
First and Last may reduce both a and Maybe a. Since a Generator has a fixed element
type, the input to the reducer is generally known and extracting from the monoid usually
is sufficient to fix the result type. Combinators are available for most scenarios where
this is not the case, and the few remaining cases can be handled by using an explicit
type annotation.
Methods
Convert a value into a Monoid
Append a value to a Monoid for use in left-to-right reduction
Prepend a value onto a Monoid for use during right-to-left reduction
Instances
| Reducer Bool All | |
| Reducer Bool Any | |
| Reducer c () | |
| Reducer ByteString ByteString | |
| Reducer ByteString ByteString | |
| Reducer ByteString Body | |
| Reducer a (Last a) | |
| Reducer a (First a) | |
| Num a => Reducer a (Product a) | |
| Num a => Reducer a (Sum a) | |
| Monoid a => Reducer a (Dual a) | |
| Reducer c [c] | |
| (Packable a, Annotation m) => Reducer a (Rope m) | |
| Measured v a => Reducer a (FingerTree v a) | |
| (Reducer c m, Reducer c n) => Reducer c (m, n) | |
| (Reducer c a, Reducer c b) => Reducer c (:*: a b) | |
| (Reducer c m, Reducer c n, Reducer c o) => Reducer c (m, n, o) | |
| (Reducer c m, Reducer c n, Reducer c o, Reducer c p) => Reducer c (m, n, o, p) | |
| Reducer (Maybe a) (Last a) | |
| Reducer (Maybe a) (First a) | |
| Reducer (a -> a) (Endo a) |
Slicing
class Reducer ByteString a => Annotation a whereSource
Methods
elide' :: Int -> Int -> Rope a -> aSource
splitAt' :: Int -> Rope a -> (a, a)Source
Instances
| Annotation () | |
| Annotation ByteString | |
| Annotation ByteString | |
| Annotation Body | |
| Annotation a => Annotation (Rope a) | |
| (Annotation a, Annotation b) => Annotation (a, b) | |
| (Annotation a, Annotation b) => Annotation (:*: a b) |
Walking
class Unpackable a whereSource
Instances
Packing Rope
Polymorphic construction
Methods
pack :: Annotation m => a -> Rope mSource
packl :: Annotation m => a -> Rope m -> Rope mSource
packr :: Annotation m => Rope m -> a -> Rope mSource
Explicit construction
fromByteString :: Reducer ByteString m => ByteString -> Rope mSource
fromChunks :: Reducer ByteString m => [ByteString] -> Rope mSource
fromLazyByteString :: Reducer ByteString m => ByteString -> Rope mSource
fromString :: Reducer ByteString m => String -> Rope mSource
Deconstructing Ropes
toChunks :: Rope m -> [ByteString]Source
toLazyByteString :: Rope m -> ByteStringSource