rle-0.1.0.1: A data type of run-length-encoded lists
Safe HaskellNone
LanguageHaskell2010

Data.RLE

Description

A data type of run-length-encoded lists.

This module is meant to be imported qualified with the exception of the type RLE itself. It exports names that clash with things in Prelude and many other data structure modules.

Synopsis

Run-Length Encoded Lists

data RLE a Source #

A run-length encoded representation of a [a].

This doesn't have a Functor or Traversable instance because it would need an Eq constraint on the element type to uphold invariants, but there are map and traverse functions exported.

Instances

Instances details
Foldable RLE Source # 
Instance details

Defined in Data.RLE

Methods

fold :: Monoid m => RLE m -> m #

foldMap :: Monoid m => (a -> m) -> RLE a -> m #

foldMap' :: Monoid m => (a -> m) -> RLE a -> m #

foldr :: (a -> b -> b) -> b -> RLE a -> b #

foldr' :: (a -> b -> b) -> b -> RLE a -> b #

foldl :: (b -> a -> b) -> b -> RLE a -> b #

foldl' :: (b -> a -> b) -> b -> RLE a -> b #

foldr1 :: (a -> a -> a) -> RLE a -> a #

foldl1 :: (a -> a -> a) -> RLE a -> a #

toList :: RLE a -> [a] #

null :: RLE a -> Bool #

length :: RLE a -> Int #

elem :: Eq a => a -> RLE a -> Bool #

maximum :: Ord a => RLE a -> a #

minimum :: Ord a => RLE a -> a #

sum :: Num a => RLE a -> a #

product :: Num a => RLE a -> a #

Eq a => IsList (RLE a) Source # 
Instance details

Defined in Data.RLE

Associated Types

type Item (RLE a) #

Methods

fromList :: [Item (RLE a)] -> RLE a #

fromListN :: Int -> [Item (RLE a)] -> RLE a #

toList :: RLE a -> [Item (RLE a)] #

Eq a => Eq (RLE a) Source # 
Instance details

Defined in Data.RLE

Methods

(==) :: RLE a -> RLE a -> Bool #

(/=) :: RLE a -> RLE a -> Bool #

Show a => Show (RLE a) Source # 
Instance details

Defined in Data.RLE

Methods

showsPrec :: Int -> RLE a -> ShowS #

show :: RLE a -> String #

showList :: [RLE a] -> ShowS #

a ~ Char => IsString (RLE a) Source # 
Instance details

Defined in Data.RLE

Methods

fromString :: String -> RLE a #

Generic (RLE a) Source # 
Instance details

Defined in Data.RLE

Associated Types

type Rep (RLE a) :: Type -> Type #

Methods

from :: RLE a -> Rep (RLE a) x #

to :: Rep (RLE a) x -> RLE a #

Eq a => Semigroup (RLE a) Source # 
Instance details

Defined in Data.RLE

Methods

(<>) :: RLE a -> RLE a -> RLE a #

sconcat :: NonEmpty (RLE a) -> RLE a #

stimes :: Integral b => b -> RLE a -> RLE a #

Eq a => Monoid (RLE a) Source # 
Instance details

Defined in Data.RLE

Methods

mempty :: RLE a #

mappend :: RLE a -> RLE a -> RLE a #

mconcat :: [RLE a] -> RLE a #

Serialize a => Serialize (RLE a) Source # 
Instance details

Defined in Data.RLE

Methods

put :: Putter (RLE a) #

get :: Get (RLE a) #

NFData a => NFData (RLE a) Source # 
Instance details

Defined in Data.RLE

Methods

rnf :: RLE a -> () #

Portray a => Portray (RLE a) Source # 
Instance details

Defined in Data.RLE

Methods

portray :: RLE a -> Portrayal #

portrayList :: [RLE a] -> Portrayal #

(Portray a, Diff a) => Diff (RLE a) Source # 
Instance details

Defined in Data.RLE

Methods

diff :: RLE a -> RLE a -> Maybe Portrayal #

type Rep (RLE a) Source # 
Instance details

Defined in Data.RLE

type Rep (RLE a) = D1 ('MetaData "RLE" "Data.RLE" "rle-0.1.0.1-IoLX9sRwIfiLS57snIrklB" 'True) (C1 ('MetaCons "RLE" 'PrefixI 'True) (S1 ('MetaSel ('Just "toRuns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Run a])))
type Item (RLE a) Source # 
Instance details

Defined in Data.RLE

type Item (RLE a) = a

toList :: RLE a -> [a] Source #

toList specialized to RLE.

fromList :: Eq a => [a] -> RLE a Source #

Run-length-encode a list by testing adjacent elements for equality.

singleton :: a -> RLE a Source #

Creates an RLE with a single element.

empty :: RLE a Source #

An empty RLE.

cons :: Eq a => a -> RLE a -> RLE a Source #

Add an element onto the beginning of the sequence.

uncons :: Eq a => RLE a -> Maybe (a, RLE a) Source #

Split the first element from the rest of the sequence.

reverse :: RLE a -> RLE a Source #

Reverse the order of the elements in the sequence.

splitAt :: (HasCallStack, Eq a) => Int -> RLE a -> (RLE a, RLE a) Source #

Returns a tuple where the first element contains the first n elements of the sequence, and the second element is the remainder of the sequence.

take :: Int -> RLE a -> RLE a Source #

Return an RLE containing the first n elements of the input.

init :: HasCallStack => RLE a -> RLE a Source #

Return an RLE containing all but the last element of the input.

null :: RLE a -> Bool Source #

Returns True iff the argument contains no elements.

length :: RLE a -> Int Source #

length specialized to RLE.

(++) :: Eq a => RLE a -> RLE a -> RLE a Source #

Append two sequences.

map :: Eq b => (a -> b) -> RLE a -> RLE b Source #

Map the given function over each element of the sequence.

mapInvertible :: (a -> b) -> RLE a -> RLE b Source #

Map the given invertible function over each element of the sequence. This is only safe when the function is invertible.

This is slightly faster than map and does not require an Eq constraint on the result type.

traverse :: (Eq b, Applicative f) => (a -> f b) -> RLE a -> f (RLE b) Source #

Visit each element of the sequence in an Applicative.

traverse :: Eq b => Traversal (RLE a) (RLE b) a b

zipWith :: Eq c => (a -> b -> c) -> RLE a -> RLE b -> RLE c Source #

Zip two sequences together.

Runs

data Run a Source #

n :>< x denotes a sequence of n copies of x, as part of an RLE.

Constructors

Int :>< a infixr 5 

Instances

Instances details
Monad Run Source # 
Instance details

Defined in Data.RLE

Methods

(>>=) :: Run a -> (a -> Run b) -> Run b #

(>>) :: Run a -> Run b -> Run b #

return :: a -> Run a #

Functor Run Source # 
Instance details

Defined in Data.RLE

Methods

fmap :: (a -> b) -> Run a -> Run b #

(<$) :: a -> Run b -> Run a #

Applicative Run Source #

After all, why not?

This is basically Writer (Product Int).

Instance details

Defined in Data.RLE

Methods

pure :: a -> Run a #

(<*>) :: Run (a -> b) -> Run a -> Run b #

liftA2 :: (a -> b -> c) -> Run a -> Run b -> Run c #

(*>) :: Run a -> Run b -> Run b #

(<*) :: Run a -> Run b -> Run a #

Foldable Run Source # 
Instance details

Defined in Data.RLE

Methods

fold :: Monoid m => Run m -> m #

foldMap :: Monoid m => (a -> m) -> Run a -> m #

foldMap' :: Monoid m => (a -> m) -> Run a -> m #

foldr :: (a -> b -> b) -> b -> Run a -> b #

foldr' :: (a -> b -> b) -> b -> Run a -> b #

foldl :: (b -> a -> b) -> b -> Run a -> b #

foldl' :: (b -> a -> b) -> b -> Run a -> b #

foldr1 :: (a -> a -> a) -> Run a -> a #

foldl1 :: (a -> a -> a) -> Run a -> a #

toList :: Run a -> [a] #

null :: Run a -> Bool #

length :: Run a -> Int #

elem :: Eq a => a -> Run a -> Bool #

maximum :: Ord a => Run a -> a #

minimum :: Ord a => Run a -> a #

sum :: Num a => Run a -> a #

product :: Num a => Run a -> a #

Eq a => Eq (Run a) Source # 
Instance details

Defined in Data.RLE

Methods

(==) :: Run a -> Run a -> Bool #

(/=) :: Run a -> Run a -> Bool #

Show a => Show (Run a) Source # 
Instance details

Defined in Data.RLE

Methods

showsPrec :: Int -> Run a -> ShowS #

show :: Run a -> String #

showList :: [Run a] -> ShowS #

Generic (Run a) Source # 
Instance details

Defined in Data.RLE

Associated Types

type Rep (Run a) :: Type -> Type #

Methods

from :: Run a -> Rep (Run a) x #

to :: Rep (Run a) x -> Run a #

Serialize a => Serialize (Run a) Source # 
Instance details

Defined in Data.RLE

Methods

put :: Putter (Run a) #

get :: Get (Run a) #

NFData a => NFData (Run a) Source # 
Instance details

Defined in Data.RLE

Methods

rnf :: Run a -> () #

Portray a => Portray (Run a) Source # 
Instance details

Defined in Data.RLE

Methods

portray :: Run a -> Portrayal #

portrayList :: [Run a] -> Portrayal #

Diff a => Diff (Run a) Source # 
Instance details

Defined in Data.RLE

Methods

diff :: Run a -> Run a -> Maybe Portrayal #

type Rep (Run a) Source # 
Instance details

Defined in Data.RLE

toRuns :: RLE a -> [Run a] Source #

Extract the contents of an RLE as a list of runs.

This is not a retraction of fromRuns: toRuns . fromRuns merges adjacent runs of equal values and eliminates empty runs.

fromRuns :: Eq a => [Run a] -> RLE a Source #

Construct an RLE from a list of runs.

This is a retraction of toRuns.

consRun :: forall a. Eq a => Run a -> RLE a -> RLE a Source #

Add a run of equal elements onto the beginning of the sequence.

unconsRun :: RLE a -> Maybe (Run a, RLE a) Source #

Split the first run of equal elements from the rest of the sequence.

runs :: (Contravariant f, Applicative f) => (Run a -> f (Run a)) -> RLE a -> f (RLE a) Source #

Fold over the contained runs in order.

This is as strong a type as this can have without breaking any laws, due to the invariants that no empty or mergeable runs exist: if we make it a Traversal, it can end up changing the number of targets, and if we make it an Iso to [(Int, a)], the reverse direction is not an isomorphism.

If you want to use a law-breaking Iso or Traversal for this anyway, use iso fromRuns toRuns to inline the problematic Iso.

runs :: Fold (RLE a) (Int, a)