rope-0.3: Tools for manipulating fingertrees of bytestrings with optional annotations

Data.Rope.Annotated

Contents

Synopsis

Annotated Ropes

data A s a Source

Instances

Measured Offset (A s a) 
Functor (A s) 
Foldable (A s) 
Traversable (A s) 
Comonad (A s) 

type Ann a f = A a (f a)Source

class Annotation f Source

Instances

Unpacking Annotated Rope

null :: A s a -> BoolSource

head :: Unpackable t => A s a -> tSource

last :: Unpackable t => A s a -> tSource

uncons :: (Annotation f, Unpackable t) => Ann a f -> Maybe (t, Ann (Tail t a) f)Source

unsnoc :: (Annotation f, Unpackable t) => Ann a f -> Maybe (Ann (Init a t) f, t)Source

Building Annotated Rope

append :: Annotation f => Ann a f -> Ann b f -> Ann (a :<> b) fSource

unit :: (Reducer t Rope, Annotation f) => t -> Ann a fSource

snoc :: (Annotation f, Reducer t Rope) => Ann a f -> t -> (forall c. Ann (Snoc c t a) f -> r) -> rSource

cons :: (Annotation f, Reducer t Rope) => t -> Ann a f -> (forall c. Ann (Cons c t a) f -> r) -> rSource

Cutting An Annotated Rope

splitAt :: Annotation f => Int -> Ann a f -> (forall n. Ann (Take n a) f -> Ann (Drop n a) f -> r) -> rSource

drop :: Annotation f => Int -> Ann a f -> (forall n. Ann (Drop n a) f -> r) -> rSource

take :: Annotation f => Int -> Ann a f -> (forall n. Ann (Take n a) f -> r) -> rSource

break :: (Annotation f, Breakable t) => (t -> Bool) -> Ann a f -> (forall n. Ann (Take n a) f -> Ann (Drop n a) f -> r) -> rSource

span :: (Annotation f, Breakable t) => (t -> Bool) -> Ann a f -> (forall n. Ann (Take n a) f -> Ann (Drop n a) f -> r) -> rSource

takeWhile :: (Annotation f, Breakable t) => (t -> Bool) -> Ann a f -> (forall n. Ann (Take n a) f -> r) -> rSource

dropWhile :: (Annotation f, Breakable t) => (t -> Bool) -> Ann a f -> (forall n. Ann (Drop n a) f -> r) -> rSource

Type-level constructors

data Drop n a Source

data Take n a Source

data Snoc a s t Source

data Cons s t a Source

data Tail t a Source

data Init a t Source

data a :<> b Source

Annotation Product

data (f :*: g) a Source

Constructors

(f a) :*: (g a) 

Instances

(Functor f, Functor g) => Functor (:*: f g) 
(Applicative f, Applicative g) => Applicative (:*: f g) 
(Foldable f, Foldable g) => Foldable (:*: f g) 
(Traversable f, Traversable g) => Traversable (:*: f g) 
(Annotation f, Annotation g) => Annotation (:*: f g) 

fstF :: (f :*: g) :~> fSource

sndF :: (f :*: g) :~> gSource