text-compression-0.1.0.23: A text compression library.
Copyright(c) Matthew Mosior 2022
LicenseBSD-style
Maintainermattm.github@gmail.com
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.MTF.Internal

Description

WARNING

This module is considered internal.

The Package Versioning Policy does not apply.

The contents of this module may change in any way whatsoever and without any warning between minor versions of this package.

Authors importing this library are expected to track development closely.

All credit goes to the author(s)/maintainer(s) of the containers library for the above warning text.

Description

Various data structures and custom data types to describe the Move-to-front transform (MTF) and the Inverse MTF implementations, namely seqToMTFB, seqToMTFT, seqFromMTFB, and seqFromMTFT.

The MTF implementations rely heavily upon Seq provided by the containers, STRef and associated functions in the stref library, and runST in the Control.Monad.ST library.

Synopsis

Base MTF types

newtype MTFB Source #

Basic MTF (ByteString) data type.

Constructors

MTFB (Seq Int, Seq (Maybe ByteString)) 

Instances

Instances details
Generic MTFB Source # 
Instance details

Defined in Data.MTF.Internal

Associated Types

type Rep MTFB :: Type -> Type #

Methods

from :: MTFB -> Rep MTFB x #

to :: Rep MTFB x -> MTFB #

Read MTFB Source # 
Instance details

Defined in Data.MTF.Internal

Show MTFB Source # 
Instance details

Defined in Data.MTF.Internal

Methods

showsPrec :: Int -> MTFB -> ShowS #

show :: MTFB -> String #

showList :: [MTFB] -> ShowS #

Eq MTFB Source # 
Instance details

Defined in Data.MTF.Internal

Methods

(==) :: MTFB -> MTFB -> Bool #

(/=) :: MTFB -> MTFB -> Bool #

Ord MTFB Source # 
Instance details

Defined in Data.MTF.Internal

Methods

compare :: MTFB -> MTFB -> Ordering #

(<) :: MTFB -> MTFB -> Bool #

(<=) :: MTFB -> MTFB -> Bool #

(>) :: MTFB -> MTFB -> Bool #

(>=) :: MTFB -> MTFB -> Bool #

max :: MTFB -> MTFB -> MTFB #

min :: MTFB -> MTFB -> MTFB #

type Rep MTFB Source # 
Instance details

Defined in Data.MTF.Internal

type Rep MTFB = D1 ('MetaData "MTFB" "Data.MTF.Internal" "text-compression-0.1.0.23-AoUvaMr8O098DefxAwCCxG" 'True) (C1 ('MetaCons "MTFB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Int, Seq (Maybe ByteString)))))

newtype MTFT Source #

Basic MTF (Text) data type.

Constructors

MTFT (Seq Int, Seq (Maybe Text)) 

Instances

Instances details
Generic MTFT Source # 
Instance details

Defined in Data.MTF.Internal

Associated Types

type Rep MTFT :: Type -> Type #

Methods

from :: MTFT -> Rep MTFT x #

to :: Rep MTFT x -> MTFT #

Read MTFT Source # 
Instance details

Defined in Data.MTF.Internal

Show MTFT Source # 
Instance details

Defined in Data.MTF.Internal

Methods

showsPrec :: Int -> MTFT -> ShowS #

show :: MTFT -> String #

showList :: [MTFT] -> ShowS #

Eq MTFT Source # 
Instance details

Defined in Data.MTF.Internal

Methods

(==) :: MTFT -> MTFT -> Bool #

(/=) :: MTFT -> MTFT -> Bool #

Ord MTFT Source # 
Instance details

Defined in Data.MTF.Internal

Methods

compare :: MTFT -> MTFT -> Ordering #

(<) :: MTFT -> MTFT -> Bool #

(<=) :: MTFT -> MTFT -> Bool #

(>) :: MTFT -> MTFT -> Bool #

(>=) :: MTFT -> MTFT -> Bool #

max :: MTFT -> MTFT -> MTFT #

min :: MTFT -> MTFT -> MTFT #

type Rep MTFT Source # 
Instance details

Defined in Data.MTF.Internal

type Rep MTFT = D1 ('MetaData "MTFT" "Data.MTF.Internal" "text-compression-0.1.0.23-AoUvaMr8O098DefxAwCCxG" 'True) (C1 ('MetaCons "MTFT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Int, Seq (Maybe Text)))))

Auxiliary functions

nubSeq' :: Ord a => Seq (Maybe a) -> Seq (Maybe a) Source #

Useful to acquire the unique elements that make up a Seq. Credit to @DavidFletcher. See this stackoverflow post.

To MTF (ByteString) functions

type PBMTFSeqB = Seq (Maybe ByteString) Source #

Abstract PBMTFSeqB type utilizing a Seq

type MTFLSSeqB = (Seq Int, Seq (Maybe ByteString)) Source #

Abstract MTFLSSeqB type utilizing a Seq.

type STMTFLSSeqB s a = STRef s MTFLSSeqB Source #

Abstract data type representing a MTFLSSeqB in the (strict) ST monad.

initializeSTMTFLSSeqB :: STMTFLSSeqB s (Seq Int, Seq (Maybe ByteString)) -> Seq (Maybe ByteString) -> ST s () Source #

Abstract data type to initialize a STMTFLSSeqB using the initial list.

updateSTMTFLSSeqB :: STMTFLSSeqB s (Seq Int, Seq (Maybe ByteString)) -> Int -> ST s () Source #

State function to update MTFLSSeqB with each step of the MTF.

emptySTMTFLSSeqB :: ST s (STMTFLSSeqB s a) Source #

State function to create empty STMTFLSSeqB type.

type STMTFILB s a = STRef s (Seq (Maybe ByteString)) Source #

Abstract STMTFILB and associated state type.

loadSTMTFILB :: STMTFILB s (Maybe ByteString) -> Seq (Maybe ByteString) -> ST s () Source #

State function to load list into STMTFILB.

emptySTMTFILB :: ST s (STMTFILB s a) Source #

State function to create empty STMTFILB type.

type STMTFCounterB s a = STRef s Int Source #

Abstract STMTFCounterB and associated state type.

updateSTMTFCounterB :: STMTFCounterB s Int -> Int -> ST s () Source #

State function to update STMTFCounterB.

emptySTMTFCounterB :: ST s (STMTFCounterB s Int) Source #

State function to create empty STMTFCounterB type.

seqToMTFB :: PBMTFSeqB -> ST s MTFLSSeqB Source #

Strict state monad function.

To MTF (Text) functions

type PTMTFSeqT = Seq (Maybe Text) Source #

Abstract PTMTFSeqT type utilizing a Seq

type MTFLSSeqT = (Seq Int, Seq (Maybe Text)) Source #

Abstract MTFLSSeqT type utilizing a Seq.

type STMTFLSSeqT s a = STRef s MTFLSSeqT Source #

Abstract data type representing a MTFLSSeqT in the (strict) ST monad.

initializeSTMTFLSSeqT :: STMTFLSSeqT s (Seq Int, Seq (Maybe Text)) -> Seq (Maybe Text) -> ST s () Source #

Abstract data type to initialize a STMTFLSSeqT using the initial list.

updateSTMTFLSSeqT :: STMTFLSSeqT s (Seq Int, Seq (Maybe Text)) -> Int -> ST s () Source #

State function to update STMTFLSSeqT with each step of the MTF.

emptySTMTFLSSeqT :: ST s (STMTFLSSeqT s a) Source #

State function to create empty STMTFLSSeqT type.

type STMTFILT s a = STRef s (Seq (Maybe Text)) Source #

Abstract STMTFILT and associated state type.

loadSTMTFILT :: STMTFILT s (Maybe Text) -> Seq (Maybe Text) -> ST s () Source #

State function to load list into STMTFILT.

emptySTMTFILT :: ST s (STMTFILT s a) Source #

State function to create empty STMTFILT type.

type STMTFCounterT s a = STRef s Int Source #

Abstract STMTFCounterT and associated state type.

updateSTMTFCounterT :: STMTFCounterT s Int -> Int -> ST s () Source #

State function to update STMTFCounterT.

emptySTMTFCounterT :: ST s (STMTFCounterT s Int) Source #

State function to create empty STMTFCounterT type.

seqToMTFT :: PTMTFSeqT -> ST s MTFLSSeqT Source #

Strict state monad function.

From MTF (ByteString) functions

type FMTFSeqB = Seq (Maybe ByteString) Source #

Abstract FMTFSeqB type utilizing a Seq.

type FSTMTFSeqB s a = STRef s FMTFSeqB Source #

Abstract data type representing a FMTFSeqB in the (strict) ST monad.

updateFSTMTFSeqB :: FSTMTFSeqB s (Maybe ByteString) -> Maybe ByteString -> ST s () Source #

State function to update FSTMTFSeqB with each step of the inverse MTF.

emptyFSTMTFSeqB :: ST s (FSTMTFSeqB s a) Source #

State function to create empty FSTMTFSeqB type.

type FSTMTFILB s a = STRef s (Seq (Maybe ByteString)) Source #

Abstract FSTMTFILB and associated state type.

loadFSTMTFILB :: FSTMTFILB s (Maybe ByteString) -> Seq (Maybe ByteString) -> ST s () Source #

State function to load list into FSTMTFILB.

updateFSTMTFILB :: FSTMTFILB s (Maybe ByteString) -> Int -> ST s () Source #

State function to update FSTMTFILB.

emptyFSTMTFILB :: ST s (FSTMTFILB s a) Source #

State function to create empty FSTMTFILB type.

seqFromMTFB :: MTFB -> ST s FMTFSeqB Source #

Strict state monad function.

From MTF (Text) functions

type FMTFSeqT = Seq (Maybe Text) Source #

Abstract FMTFSeqT type utilizing a Seq.

type FSTMTFSeqT s a = STRef s FMTFSeqT Source #

Abstract data type representing a FMTFSeqT in the (strict) ST monad.

updateFSTMTFSeqT :: FSTMTFSeqT s (Maybe Text) -> Maybe Text -> ST s () Source #

State function to update FSTMTFSeqT with each step of the inverse MTF.

emptyFSTMTFSeqT :: ST s (FSTMTFSeqT s a) Source #

State function to create empty FSTMTFSeqT type.

type FSTMTFILT s a = STRef s (Seq (Maybe Text)) Source #

Abstract FSTMTFILT and associated state type.

loadFSTMTFILT :: FSTMTFILT s (Maybe Text) -> Seq (Maybe Text) -> ST s () Source #

State function to load list into FSTMTFILT.

updateFSTMTFILT :: FSTMTFILT s (Maybe Text) -> Int -> ST s () Source #

State function to update FSTMTFILT.

emptyFSTMTFILT :: ST s (FSTMTFILT s a) Source #

State function to create empty FSTMTFILT type.

seqFromMTFT :: MTFT -> ST s FMTFSeqT Source #

Strict state monad function.