text-compression-0.1.0.16: 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 Seq provided by the containers.

The internal BWTMatrix data type relies upon the Seq as well.

Synopsis

Base BWT types

data Suffix a Source #

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

Constructors

Suffix 

Instances

Instances details
Generic (Suffix a) Source # 
Instance details

Defined in Data.BWT.Internal

Associated Types

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

Methods

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

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

Read a => Read (Suffix a) Source # 
Instance details

Defined in Data.BWT.Internal

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

Defined in Data.BWT.Internal

Methods

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

show :: Suffix a -> String #

showList :: [Suffix a] -> ShowS #

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

Defined in Data.BWT.Internal

Methods

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

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

Ord a => Ord (Suffix a) Source # 
Instance details

Defined in Data.BWT.Internal

Methods

compare :: Suffix a -> Suffix a -> Ordering #

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

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

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

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

max :: Suffix a -> Suffix a -> Suffix a #

min :: Suffix a -> Suffix a -> Suffix a #

type Rep (Suffix a) Source # 
Instance details

Defined in Data.BWT.Internal

type Rep (Suffix a) = D1 ('MetaData "Suffix" "Data.BWT.Internal" "text-compression-0.1.0.16-EGmAxK0JgwH3t6C21JNSfQ" '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 (Maybe (Seq a))))))

type SuffixArray a = Seq (Suffix a) Source #

The SuffixArray data type. Uses Seq internally.

newtype BWT a Source #

The BWT data type. Uses Seq internally.

Constructors

BWT (Seq (Maybe a)) 

Instances

Instances details
Generic (BWT a) Source # 
Instance details

Defined in Data.BWT.Internal

Associated Types

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

Methods

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

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

Read a => Read (BWT a) Source # 
Instance details

Defined in Data.BWT.Internal

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

Defined in Data.BWT.Internal

Methods

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

show :: BWT a -> String #

showList :: [BWT a] -> ShowS #

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

Defined in Data.BWT.Internal

Methods

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

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

Ord a => Ord (BWT a) Source # 
Instance details

Defined in Data.BWT.Internal

Methods

compare :: BWT a -> BWT a -> Ordering #

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

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

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

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

max :: BWT a -> BWT a -> BWT a #

min :: BWT a -> BWT a -> BWT a #

type Rep (BWT a) Source # 
Instance details

Defined in Data.BWT.Internal

type Rep (BWT a) = D1 ('MetaData "BWT" "Data.BWT.Internal" "text-compression-0.1.0.16-EGmAxK0JgwH3t6C21JNSfQ" 'True) (C1 ('MetaCons "BWT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq (Maybe a)))))

newtype BWTMatrix a Source #

The BWTMatrix data type. Uses a Array internally.

Constructors

BWTMatrix (Seq (Seq (Maybe a))) 

Instances

Instances details
Generic (BWTMatrix a) Source # 
Instance details

Defined in Data.BWT.Internal

Associated Types

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

Methods

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

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

Read a => Read (BWTMatrix a) Source # 
Instance details

Defined in Data.BWT.Internal

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

Defined in Data.BWT.Internal

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

Defined in Data.BWT.Internal

Methods

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

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

Ord a => Ord (BWTMatrix a) Source # 
Instance details

Defined in Data.BWT.Internal

type Rep (BWTMatrix a) Source # 
Instance details

Defined in Data.BWT.Internal

type Rep (BWTMatrix a) = D1 ('MetaData "BWTMatrix" "Data.BWT.Internal" "text-compression-0.1.0.16-EGmAxK0JgwH3t6C21JNSfQ" 'True) (C1 ('MetaCons "BWTMatrix" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq (Seq (Maybe a))))))

To BWT functions

saToBWT :: SuffixArray a -> Seq a -> Seq (Maybe a) Source #

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

createSuffixArray :: Ord a => Seq a -> SuffixArray a Source #

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

From BWT functions

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 a Source #

Abstract BWTSeq type utilizing a Seq.

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

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

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

State function to push BWTString data into stack.

emptySTBWTSeq :: ST s (STBWTSeq s a) 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 (Maybe a, Int) -> ST s (BWTSeq a) Source #

Magic Inverse BWT function.

Create BWT Matrix function

createBWTMatrix :: Ord a => [a] -> BWTMatrix a Source #

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