compressed-3.11: Compressed containers and reducers

Copyright(c) Edward Kmett 2009-2011
LicenseBSD-style
Maintainerekmett@gmail.com
Stabilityexperimental
Portabilitynon-portable (type families)
Safe HaskellSafe
LanguageHaskell98

Data.Compressed.LZ78

Contents

Description

Compression algorithms are all about exploiting redundancy. When applying an expensive Reducer to a redundant source, it may be better to extract the structural redundancy that is present. LZ78 is a compression algorithm that does so, without requiring the dictionary to be populated with all of the possible values of a data type unlike its later refinement LZW, and which has fewer comparison reqirements during encoding than its earlier counterpart LZ77.

Synopsis

Lempel-Ziv 78

data LZ78 a Source #

An LZ78 compressed Generator.

Instances

Monad LZ78 Source # 

Methods

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

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

return :: a -> LZ78 a #

fail :: String -> LZ78 a #

Functor LZ78 Source # 

Methods

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

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

Applicative LZ78 Source # 

Methods

pure :: a -> LZ78 a #

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

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

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

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

Foldable LZ78 Source # 

Methods

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

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

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

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

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

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

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

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

toList :: LZ78 a -> [a] #

null :: LZ78 a -> Bool #

length :: LZ78 a -> Int #

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

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

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

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

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

MonadZip LZ78 Source # 

Methods

mzip :: LZ78 a -> LZ78 b -> LZ78 (a, b) #

mzipWith :: (a -> b -> c) -> LZ78 a -> LZ78 b -> LZ78 c #

munzip :: LZ78 (a, b) -> (LZ78 a, LZ78 b) #

Zip LZ78 Source # 

Methods

zipWith :: (a -> b -> c) -> LZ78 a -> LZ78 b -> LZ78 c #

zip :: LZ78 a -> LZ78 b -> LZ78 (a, b) #

zap :: LZ78 (a -> b) -> LZ78 a -> LZ78 b #

Indexable LZ78 Source # 

Methods

index :: LZ78 a -> Key LZ78 -> a #

Lookup LZ78 Source # 

Methods

lookup :: Key LZ78 -> LZ78 a -> Maybe a #

Adjustable LZ78 Source # 

Methods

adjust :: (a -> a) -> Key LZ78 -> LZ78 a -> LZ78 a #

replace :: Key LZ78 -> a -> LZ78 a -> LZ78 a #

FoldableWithKey LZ78 Source # 

Methods

toKeyedList :: LZ78 a -> [(Key LZ78, a)] #

foldMapWithKey :: Monoid m => (Key LZ78 -> a -> m) -> LZ78 a -> m #

foldrWithKey :: (Key LZ78 -> a -> b -> b) -> b -> LZ78 a -> b #

foldlWithKey :: (b -> Key LZ78 -> a -> b) -> b -> LZ78 a -> b #

Pointed LZ78 Source # 

Methods

point :: a -> LZ78 a #

Eq a => Eq (LZ78 a) Source # 

Methods

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

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

Ord a => Ord (LZ78 a) Source # 

Methods

compare :: LZ78 a -> LZ78 a -> Ordering #

(<) :: LZ78 a -> LZ78 a -> Bool #

(<=) :: LZ78 a -> LZ78 a -> Bool #

(>) :: LZ78 a -> LZ78 a -> Bool #

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

max :: LZ78 a -> LZ78 a -> LZ78 a #

min :: LZ78 a -> LZ78 a -> LZ78 a #

(Read a, Hashable a, Eq a) => Read (LZ78 a) Source # 
Show a => Show (LZ78 a) Source # 

Methods

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

show :: LZ78 a -> String #

showList :: [LZ78 a] -> ShowS #

Generator (LZ78 a) Source # 

Associated Types

type Elem (LZ78 a) :: * #

Methods

mapReduce :: (Reducer e m, Monoid m) => (Elem (LZ78 a) -> e) -> LZ78 a -> m #

mapTo :: (Reducer e m, Monoid m) => (Elem (LZ78 a) -> e) -> m -> LZ78 a -> m #

mapFrom :: (Reducer e m, Monoid m) => (Elem (LZ78 a) -> e) -> LZ78 a -> m -> m #

type Key LZ78 Source # 
type Key LZ78 = Int
type Elem (LZ78 a) Source # 
type Elem (LZ78 a) = a

Encoding

encode :: (Hashable a, Eq a) => [a] -> LZ78 a Source #

O(n) Construct an LZ78-compressed Generator using a HashMap internally.

encodeOrd :: Ord a => [a] -> LZ78 a Source #

O(n log n) Contruct an LZ78-compressed Generator using a Map internally.

encodeEq :: Eq a => [a] -> LZ78 a Source #

O(n^2) Contruct an LZ78-compressed Generator using a list internally, requires an instance of Eq, less efficient than encode.

Decoding (reduce)

decode :: LZ78 a -> [a] Source #

A type-constrained reduce operation

Recoding

recode :: (Eq a, Hashable a) => LZ78 a -> LZ78 a Source #

O(n). Recompress with Hashable

recodeOrd :: Ord a => LZ78 a -> LZ78 a Source #

O(n log n). Recompress with Ord

recodeEq :: Eq a => LZ78 a -> LZ78 a Source #

O(n^2). Recompress with Eq