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

Data.RLE.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 Run-length encoding (RLE) and the Inverse RLE implementations, namely seqToRLEB, seqToRLET, seqFromRLEB, and seqFromRLET.

The RLE 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

Documentation

newtype RLEB Source #

Basic RLE (ByteString) data type.

Constructors

RLEB (Seq (Maybe ByteString)) 

Instances

Instances details
Generic RLEB Source # 
Instance details

Defined in Data.RLE.Internal

Associated Types

type Rep RLEB :: Type -> Type #

Methods

from :: RLEB -> Rep RLEB x #

to :: Rep RLEB x -> RLEB #

Read RLEB Source # 
Instance details

Defined in Data.RLE.Internal

Show RLEB Source # 
Instance details

Defined in Data.RLE.Internal

Methods

showsPrec :: Int -> RLEB -> ShowS #

show :: RLEB -> String #

showList :: [RLEB] -> ShowS #

Eq RLEB Source # 
Instance details

Defined in Data.RLE.Internal

Methods

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

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

Ord RLEB Source # 
Instance details

Defined in Data.RLE.Internal

Methods

compare :: RLEB -> RLEB -> Ordering #

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

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

(>) :: RLEB -> RLEB -> Bool #

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

max :: RLEB -> RLEB -> RLEB #

min :: RLEB -> RLEB -> RLEB #

type Rep RLEB Source # 
Instance details

Defined in Data.RLE.Internal

type Rep RLEB = D1 ('MetaData "RLEB" "Data.RLE.Internal" "text-compression-0.1.0.15-1U3drBT2M3HZ6U4DNXh3m" 'True) (C1 ('MetaCons "RLEB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq (Maybe ByteString)))))

newtype RLET Source #

Basic RLE (Text) data type.

Constructors

RLET (Seq (Maybe Text)) 

Instances

Instances details
Generic RLET Source # 
Instance details

Defined in Data.RLE.Internal

Associated Types

type Rep RLET :: Type -> Type #

Methods

from :: RLET -> Rep RLET x #

to :: Rep RLET x -> RLET #

Read RLET Source # 
Instance details

Defined in Data.RLE.Internal

Show RLET Source # 
Instance details

Defined in Data.RLE.Internal

Methods

showsPrec :: Int -> RLET -> ShowS #

show :: RLET -> String #

showList :: [RLET] -> ShowS #

Eq RLET Source # 
Instance details

Defined in Data.RLE.Internal

Methods

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

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

Ord RLET Source # 
Instance details

Defined in Data.RLE.Internal

Methods

compare :: RLET -> RLET -> Ordering #

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

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

(>) :: RLET -> RLET -> Bool #

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

max :: RLET -> RLET -> RLET #

min :: RLET -> RLET -> RLET #

type Rep RLET Source # 
Instance details

Defined in Data.RLE.Internal

type Rep RLET = D1 ('MetaData "RLET" "Data.RLE.Internal" "text-compression-0.1.0.15-1U3drBT2M3HZ6U4DNXh3m" 'True) (C1 ('MetaCons "RLET" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq (Maybe Text)))))

type RLESeqB = Seq (Maybe ByteString) Source #

Abstract RLESeqB type utilizing a Seq.

type STRLESeqB s a = STRef s RLESeqB Source #

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

pushSTRLESeqB :: STRLESeqB s (Maybe ByteString) -> Maybe ByteString -> ST s () Source #

State function to push RLESeqB data into stack.

emptySTRLESeqB :: ST s (STRLESeqB s a) Source #

State function to create empty STRLESeqB type.

type STRLETempB s a = STRef s (Maybe ByteString) Source #

Abstract STRLETempB and associated state type.

updateSTRLETempB :: STRLETempB s (Maybe ByteString) -> Maybe ByteString -> ST s () Source #

State function to update STRLETempB.

emptySTRLETempB :: ST s (STRLETempB s a) Source #

State function to create empty STRLETempB type.

type STRLECounterB s a = STRef s Int Source #

Abstract STRLECounterB state type.

updateSTRLECounterB :: STRLECounterB s Int -> Int -> ST s () Source #

State function to update STRLECounterB.

emptySTRLECounterB :: ST s (STRLECounterB s Int) Source #

State function to create empty STRLECounterB type.

seqToRLEB :: RLESeqB -> ST s RLESeqB Source #

Strict state monad function.

type RLESeqT = Seq (Maybe Text) Source #

Abstract RLESeqT type utilizing a Seq.

type STRLESeqT s a = STRef s RLESeqT Source #

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

pushSTRLESeqT :: STRLESeqT s (Maybe Text) -> Maybe Text -> ST s () Source #

State function to push RLESeqT data into stack.

emptySTRLESeqT :: ST s (STRLESeqT s a) Source #

State function to create empty STRLESeqT type.

type STRLETempT s a = STRef s (Maybe Text) Source #

Abstract STRLETempT state type.

updateSTRLETempT :: STRLETempT s (Maybe Text) -> Maybe Text -> ST s () Source #

State function to update STRLETempT.

emptySTRLETempT :: ST s (STRLETempT s a) Source #

State function to create empty STRLETempT type.

type STRLECounterT s a = STRef s Int Source #

Abstract STRLECounterT and associated state type.

updateSTRLECounterT :: STRLECounterT s Int -> Int -> ST s () Source #

State function to update STRLECounterT.

emptySTRLECounterT :: ST s (STRLECounterT s Int) Source #

State function to create empty STRLECounterT type.

seqToRLET :: RLESeqT -> ST s RLESeqT Source #

Strict state monad function.

type FRLESeqB = Seq (Maybe ByteString) Source #

Abstract FRLESeqB type utilizing a Seq.

type FSTRLESeqB s a = STRef s FRLESeqB Source #

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

pushFSTRLESeqB :: FSTRLESeqB s (Maybe ByteString) -> Maybe ByteString -> ST s () Source #

State function to push FRLESeqB data into stack.

emptyFSTRLESeqB :: ST s (FSTRLESeqB s a) Source #

State function to create empty FSTRLESeqB type.

seqFromRLEB :: RLEB -> ST s FRLESeqB Source #

Strict state monad function.

type FRLESeqT = Seq (Maybe Text) Source #

Abstract FRLESeqT type utilizing a Seq.

type FSTRLESeqT s a = STRef s FRLESeqT Source #

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

pushFSTRLESeqT :: FSTRLESeqT s (Maybe Text) -> Maybe Text -> ST s () Source #

State function to push FSTRLESeqT data into stack.

emptyFSTRLESeqT :: ST s (FSTRLESeqT s a) Source #

State function to create empty FSTRLESeqT type.

seqFromRLET :: RLET -> ST s FRLESeqT Source #

Strict state monad function.