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

Data.BWT.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 Burrows-Wheeler Transform (BWT) and the Inverse BWT.

The implementation of the BWT relies upon sequence provided by the containers.

The internal BWTMatrix data type relies upon the massiv package.

Synopsis

Documentation

data Suffix Source #

Basic suffix data type. Used to describe the core data inside of the SuffixArray data type.

Constructors

Suffix 

Instances

Instances details
Generic Suffix Source # 
Instance details

Defined in Data.BWT.Internal

Associated Types

type Rep Suffix :: Type -> Type #

Methods

from :: Suffix -> Rep Suffix x #

to :: Rep Suffix x -> Suffix #

Read Suffix Source # 
Instance details

Defined in Data.BWT.Internal

Show Suffix Source # 
Instance details

Defined in Data.BWT.Internal

Eq Suffix Source # 
Instance details

Defined in Data.BWT.Internal

Methods

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

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

Ord Suffix Source # 
Instance details

Defined in Data.BWT.Internal

type Rep Suffix Source # 
Instance details

Defined in Data.BWT.Internal

type Rep Suffix = D1 ('MetaData "Suffix" "Data.BWT.Internal" "text-compression-0.1.0.3-3MpNIRMRQ1O4EHOgYUmLSc" 'False) (C1 ('MetaCons "Suffix" 'PrefixI 'True) (S1 ('MetaSel ('Just "suffixindex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "suffixstartpos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "suffix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq Char)))))

type SuffixArray = Seq Suffix Source #

The SuffixArray data type. Uses sequence internally.

type BWT = Seq Char Source #

The BWT data type. Uses sequence internally.

type BWTMatrix = Array BN Ix1 String Source #

The BWTMatrix data type. Uses a massiv array internally.

saToBWT :: SuffixArray -> Seq Char -> BWT Source #

Computes the Burrows-Wheeler Transform (BWT) using the suffix array and the original string (represented as a sequence for performance).

createSuffixArray :: Seq Char -> SuffixArray Source #

Computes the corresponding SuffixArray of a given string. Please see suffix array for more information.

sortTB :: (Ord a1, Ord a2) => (a1, a2) -> (a1, a2) -> Ordering Source #

Hierarchical sorting scheme that compares fst first then snd. Necessary for the setting up the BWT in order to correctly invert it using the Magic algorithm.

type BWTSeq a = Seq Char Source #

Abstract BWTSeq type utilizing a sequence.

type STBWTSeq s a = STRef s (BWTSeq Char) Source #

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

pushSTBWTSeq :: STBWTSeq s Char -> Char -> ST s () Source #

State function to push BWTString data into stack.

emptySTBWTSeq :: ST s (STBWTSeq s Char) Source #

State function to create empty STBWTString type.

type STBWTCounter s a = STRef s Int Source #

Abstract BWTCounter and associated state type.

updateSTBWTCounter :: STBWTCounter s Int -> Int -> ST s () Source #

State function to update BWTCounter.

emptySTBWTCounter :: ST s (STBWTCounter s Int) Source #

State function to create empty STBWTCounter type.

magicInverseBWT :: Seq (Char, Int) -> ST s (BWTSeq Char) Source #

Magic Inverse BWT function.

grabHeadChunks :: Seq (Seq Char) -> (Seq Char, Seq Char) Source #

Easy way to grab the first two elements of a sequence.

createBWTMatrix :: String -> BWTMatrix Source #

Simple yet efficient implementation of converting a given string into a BWT Matrix (the BWTMatrix type is a massiv array).