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.FMIndex.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 Full-text Minute-space index (FM-index) and the Inverse FM-index implementations, namely seqToOccCKB, seqToOccCKT, seqToCcB, seqToCcT, seqFromFMIndexB, and seqFromFMIndexT.

The FM-index 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.

Example FM-index Output

The below example is taken from this wikipedia page.

Given the following input, "abracadabra":

and

Given the following Burrows-Wheeler matrix (BWM) of the input "abracadabra":

IFL
1$abracadabra
2a$abracadabr
3abra$abracad
4abracadabra$
5acadabra$abr
6adabra$abrac
7bra$abracada
8bracadabra$a
9cadabra$abra
10dabra$abraca
11ra$abracadab
12racadabra$ab

The FM-index output of the Burrows-Wheeler transform of the input is:

C[c] of "ard$rcaaaabb"

c$abcdr
C[c]0168910

and

Occ(c,k) of "ard$rcaaaabb"

ard$rcaaaabb
123456789101112
$000111111111
a111111234555
b000000000012
c000001111111
d001111111111
r011122222222
Synopsis

Documentation

newtype FMIndexB Source #

Basic FMIndex (ByteString) data type.

Constructors

FMIndexB (CcB, OccCKB) 

Instances

Instances details
Generic FMIndexB Source # 
Instance details

Defined in Data.FMIndex.Internal

Associated Types

type Rep FMIndexB :: Type -> Type #

Methods

from :: FMIndexB -> Rep FMIndexB x #

to :: Rep FMIndexB x -> FMIndexB #

Read FMIndexB Source # 
Instance details

Defined in Data.FMIndex.Internal

Show FMIndexB Source # 
Instance details

Defined in Data.FMIndex.Internal

Eq FMIndexB Source # 
Instance details

Defined in Data.FMIndex.Internal

Ord FMIndexB Source # 
Instance details

Defined in Data.FMIndex.Internal

type Rep FMIndexB Source # 
Instance details

Defined in Data.FMIndex.Internal

type Rep FMIndexB = D1 ('MetaData "FMIndexB" "Data.FMIndex.Internal" "text-compression-0.1.0.15-1U3drBT2M3HZ6U4DNXh3m" 'True) (C1 ('MetaCons "FMIndexB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CcB, OccCKB))))

newtype FMIndexT Source #

Basic FMIndex (Text) data type.

Constructors

FMIndexT (CcT, OccCKT) 

Instances

Instances details
Generic FMIndexT Source # 
Instance details

Defined in Data.FMIndex.Internal

Associated Types

type Rep FMIndexT :: Type -> Type #

Methods

from :: FMIndexT -> Rep FMIndexT x #

to :: Rep FMIndexT x -> FMIndexT #

Read FMIndexT Source # 
Instance details

Defined in Data.FMIndex.Internal

Show FMIndexT Source # 
Instance details

Defined in Data.FMIndex.Internal

Eq FMIndexT Source # 
Instance details

Defined in Data.FMIndex.Internal

Ord FMIndexT Source # 
Instance details

Defined in Data.FMIndex.Internal

type Rep FMIndexT Source # 
Instance details

Defined in Data.FMIndex.Internal

type Rep FMIndexT = D1 ('MetaData "FMIndexT" "Data.FMIndex.Internal" "text-compression-0.1.0.15-1U3drBT2M3HZ6U4DNXh3m" 'True) (C1 ('MetaCons "FMIndexT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CcT, OccCKT))))

newtype OccCKB Source #

Basic OccCKB (ByteString) data type.

Instances

Instances details
Generic OccCKB Source # 
Instance details

Defined in Data.FMIndex.Internal

Associated Types

type Rep OccCKB :: Type -> Type #

Methods

from :: OccCKB -> Rep OccCKB x #

to :: Rep OccCKB x -> OccCKB #

Read OccCKB Source # 
Instance details

Defined in Data.FMIndex.Internal

Show OccCKB Source # 
Instance details

Defined in Data.FMIndex.Internal

Eq OccCKB Source # 
Instance details

Defined in Data.FMIndex.Internal

Methods

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

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

Ord OccCKB Source # 
Instance details

Defined in Data.FMIndex.Internal

type Rep OccCKB Source # 
Instance details

Defined in Data.FMIndex.Internal

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

newtype OccCKT Source #

Basic OccCKT (Text) data type.

Constructors

OccCKT (Seq (Maybe Text, Seq (Int, Int, Maybe Text))) 

Instances

Instances details
Generic OccCKT Source # 
Instance details

Defined in Data.FMIndex.Internal

Associated Types

type Rep OccCKT :: Type -> Type #

Methods

from :: OccCKT -> Rep OccCKT x #

to :: Rep OccCKT x -> OccCKT #

Read OccCKT Source # 
Instance details

Defined in Data.FMIndex.Internal

Show OccCKT Source # 
Instance details

Defined in Data.FMIndex.Internal

Eq OccCKT Source # 
Instance details

Defined in Data.FMIndex.Internal

Methods

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

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

Ord OccCKT Source # 
Instance details

Defined in Data.FMIndex.Internal

type Rep OccCKT Source # 
Instance details

Defined in Data.FMIndex.Internal

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

newtype CcB Source #

Basic C[c] table (ByteString) data type.

Constructors

CcB (Seq (Int, Maybe ByteString)) 

Instances

Instances details
Generic CcB Source # 
Instance details

Defined in Data.FMIndex.Internal

Associated Types

type Rep CcB :: Type -> Type #

Methods

from :: CcB -> Rep CcB x #

to :: Rep CcB x -> CcB #

Read CcB Source # 
Instance details

Defined in Data.FMIndex.Internal

Show CcB Source # 
Instance details

Defined in Data.FMIndex.Internal

Methods

showsPrec :: Int -> CcB -> ShowS #

show :: CcB -> String #

showList :: [CcB] -> ShowS #

Eq CcB Source # 
Instance details

Defined in Data.FMIndex.Internal

Methods

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

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

Ord CcB Source # 
Instance details

Defined in Data.FMIndex.Internal

Methods

compare :: CcB -> CcB -> Ordering #

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

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

(>) :: CcB -> CcB -> Bool #

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

max :: CcB -> CcB -> CcB #

min :: CcB -> CcB -> CcB #

type Rep CcB Source # 
Instance details

Defined in Data.FMIndex.Internal

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

newtype CcT Source #

Basic C[c] table (Text) data type.

Constructors

CcT (Seq (Int, Maybe Text)) 

Instances

Instances details
Generic CcT Source # 
Instance details

Defined in Data.FMIndex.Internal

Associated Types

type Rep CcT :: Type -> Type #

Methods

from :: CcT -> Rep CcT x #

to :: Rep CcT x -> CcT #

Read CcT Source # 
Instance details

Defined in Data.FMIndex.Internal

Show CcT Source # 
Instance details

Defined in Data.FMIndex.Internal

Methods

showsPrec :: Int -> CcT -> ShowS #

show :: CcT -> String #

showList :: [CcT] -> ShowS #

Eq CcT Source # 
Instance details

Defined in Data.FMIndex.Internal

Methods

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

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

Ord CcT Source # 
Instance details

Defined in Data.FMIndex.Internal

Methods

compare :: CcT -> CcT -> Ordering #

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

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

(>) :: CcT -> CcT -> Bool #

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

max :: CcT -> CcT -> CcT #

min :: CcT -> CcT -> CcT #

type Rep CcT Source # 
Instance details

Defined in Data.FMIndex.Internal

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

type PBOccCKSeqB = Seq (Maybe ByteString) Source #

Abstract PBOccCKSeqB type utilizing a Seq.

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

Abstract OccCKSeqB type utilizing a Seq. (c,(indexofinputcurrentelement,Occ(c,k),inputcurrentelement))

type STOccCKSeqB s a = STRef s OccCKSeqB Source #

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

updateSTOccCKSeqAB :: STOccCKSeqB s (Seq (Maybe ByteString, Seq (Int, Int, Maybe ByteString))) -> (Int, Int, Maybe ByteString) -> ST s () Source #

State function to update OccCKSeqB with each step of the OccCK.

updateSTOccCKSeqBB :: STOccCKSeqB s (Seq (Maybe ByteString, Seq (Int, Int, Maybe ByteString))) -> Maybe ByteString -> ST s () Source #

State function to update OccCKSeqB with each step of the OccCK.

emptySTOccCKSeqB :: ST s (STOccCKSeqB s a) Source #

State function to create empty STOccCKSeqB type.

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

Abstract STOccCKILB and associated state type.

loadSTOccCKILB :: STOccCKILB s (Maybe ByteString) -> Seq (Maybe ByteString) -> ST s () Source #

State function to load list into STOccCKILB.

emptySTOccCKILB :: ST s (STOccCKILB s a) Source #

State function to create empty STOccCKILB type.

type STOccCKCounterB s a = STRef s Int Source #

Abstract STOccCKCounterB and associated state type.

updateSTOccCKCounterB :: STOccCKCounterB s Int -> Int -> ST s () Source #

State function to update STOccCKCounterB.

emptySTOccCKCounterB :: ST s (STOccCKCounterB s Int) Source #

State function to create empty STOccCKCounterB type.

seqToOccCKB :: PBOccCKSeqB -> ST s OccCKSeqB Source #

Strict state monad function.

type PTOccCKSeqT = Seq (Maybe Text) Source #

Abstract PTOccCKSeqT type utilizing a Seq.

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

Abstract OccCKSeqT type utilizing a Seq. (c,(indexofinputcurrentelement,Occ(c,k),inputcurrentelement))

type STOccCKSeqT s a = STRef s OccCKSeqT Source #

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

updateSTOccCKSeqAT :: STOccCKSeqT s (Seq (Maybe Text, Seq (Int, Int, Maybe Text))) -> (Int, Int, Maybe Text) -> ST s () Source #

State function to update OccCKSeqT with each step of the OccCK.

updateSTOccCKSeqBT :: STOccCKSeqT s (Seq (Maybe Text, Seq (Int, Int, Maybe Text))) -> Maybe Text -> ST s () Source #

State function to update OccCKSeqT with each step of the OccCK.

emptySTOccCKSeqT :: ST s (STOccCKSeqT s a) Source #

State function to create empty STOccCKSeqT type.

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

Abstract STOccCKILT and associated state type.

loadSTOccCKILT :: STOccCKILT s (Maybe Text) -> Seq (Maybe Text) -> ST s () Source #

State function to load list into STOccCKILT.

emptySTOccCKILT :: ST s (STOccCKILT s a) Source #

State function to create empty STOccCKILT type.

type STOccCKCounterT s a = STRef s Int Source #

Abstract STOccCKCounterT and associated state type.

updateSTOccCKCounterT :: STOccCKCounterT s Int -> Int -> ST s () Source #

State function to update STOccCKCounterT.

emptySTOccCKCounterT :: ST s (STOccCKCounterT s Int) Source #

State function to create empty STOccCKCounterT type.

seqToOccCKT :: PTOccCKSeqT -> ST s OccCKSeqT Source #

Strict state monad function.

type PBCcSeqB = Seq (Maybe ByteString) Source #

Abstract PBCcSeqB type utilizing a Seq.

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

Abstract CcSeqB type utilizing a Seq. (C[c],c)

type STCcSeqB s a = STRef s CcSeqB Source #

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

updateSTCcSeqB :: STCcSeqB s (Seq (Int, Maybe ByteString)) -> (Int, Maybe ByteString) -> ST s () Source #

State function to update CcSeqB with each step of the C[c].

emptySTCcSeqB :: ST s (STCcSeqB s a) Source #

State function to create empty STCcSeqT type.

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

Abstract STCcILB and associated state type.

loadSTCcILB :: STCcILB s (Maybe ByteString) -> Seq (Maybe ByteString) -> ST s () Source #

State function to load list into STCcILB.

emptySTCcILB :: ST s (STCcILB s a) Source #

State function to create empty STCcILB type.

type STCcCounterB s a = STRef s Int Source #

Abstract STCcCounterB and associated state type.

updateSTCcCounterB :: STCcCounterB s Int -> Int -> ST s () Source #

State function to update STCcCounterB.

emptySTCcCounterB :: ST s (STCcCounterB s Int) Source #

State function to create empty STCcCounterT type.

seqToCcB :: PBCcSeqB -> ST s CcSeqB Source #

Strict state monad function.

type PTCcSeqT = Seq (Maybe Text) Source #

Abstract PTCcSeqT type utilizing a Seq.

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

Abstract CcSeqT type utilizing a Seq. (C[c],c)

type STCcSeqT s a = STRef s CcSeqT Source #

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

updateSTCcSeqT :: STCcSeqT s (Seq (Int, Maybe Text)) -> (Int, Maybe Text) -> ST s () Source #

State function to update CcSeqT with each step of the C[c].

emptySTCcSeqT :: ST s (STCcSeqT s a) Source #

State function to create empty STCcSeqT type.

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

Abstract STCcILT and associated state type.

loadSTCcILT :: STCcILT s (Maybe Text) -> Seq (Maybe Text) -> ST s () Source #

State function to load list into STCcILT.

emptySTCcILT :: ST s (STCcILT s a) Source #

State function to create empty STCcILT type.

type STCcCounterT s a = STRef s Int Source #

Abstract STCcCounterT and associated state type.

updateSTCcCounterT :: STCcCounterT s Int -> Int -> ST s () Source #

State function to update STCcCounterT.

emptySTCcCounterT :: ST s (STCcCounterT s Int) Source #

State function to create empty STCcCounterT type.

seqToCcT :: PTCcSeqT -> ST s CcSeqT Source #

Strict state monad function.

type FFMIndexSeqB = Seq (Maybe ByteString) Source #

Abstract FFMIndexSeqB type utilizing a Seq.

seqFromFMIndexB :: FMIndexB -> FFMIndexSeqB Source #

Simple Inverse FMIndex function.

type FFMIndexSeqT = Seq (Maybe Text) Source #

Abstract FFMIndexSeqT type utilizing a Seq.

seqFromFMIndexT :: FMIndexT -> FFMIndexSeqT Source #

Simple Inverse FMIndex function.