text-compression-0.1.0.14: 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 seqToFMIndexB, seqToFMIndexT, 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.

FM-index output of the Burrows-Wheeler transform of the input "abracadabra" -> "ard$rcaaaabb"

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.

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.14-9ORM6NM9jqVJfQeS6LjkQQ" 'True) (C1 ('MetaCons "FMIndexB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq (Maybe ByteString, Seq (Int, Int, Maybe ByteString))))))

newtype FMIndexT Source #

Basic FMIndex (Text) data type.

Constructors

FMIndexT (Seq (Maybe Text, Seq (Int, Int, Maybe Text))) 

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.14-9ORM6NM9jqVJfQeS6LjkQQ" 'True) (C1 ('MetaCons "FMIndexT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq (Maybe Text, Seq (Int, Int, Maybe Text))))))

type PBFMIndexSeqB = Seq (Maybe ByteString) Source #

Abstract PBFMIndexSeqB type utilizing a Seq.

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

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

type STFMIndexSeqB s a = STRef s FMIndexSeqB Source #

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

updateSTFMIndexSeqAB :: STFMIndexSeqB s (Seq (Maybe ByteString, Seq (Int, Int, Maybe ByteString))) -> (Int, Int, Maybe ByteString) -> ST s () Source #

State function to update FMIndexSeqB with each step of the FMIndex.

updateSTFMIndexSeqBB :: STFMIndexSeqB s (Seq (Maybe ByteString, Seq (Int, Int, Maybe ByteString))) -> Maybe ByteString -> ST s () Source #

State function to update FMIndexSeqB with each step of the FMIndex.

emptySTFMIndexSeqB :: ST s (STFMIndexSeqB s a) Source #

State function to create empty STFMIndexSeqB type.

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

Abstract STFMIndexILB and associated state type.

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

State function to load list into STFMIndexILB.

emptySTFMIndexILB :: ST s (STFMIndexILB s a) Source #

State function to create empty STFMIndexILB type.

type STFMIndexCounterB s a = STRef s Int Source #

Abstract STFMIndexCounterB and associated state type.

updateSTFMIndexCounterB :: STFMIndexCounterB s Int -> Int -> ST s () Source #

State function to update STFMIndexCounterB.

emptySTFMIndexCounterB :: ST s (STFMIndexCounterB s Int) Source #

State function to create empty STFMIndexCounterB type.

seqToFMIndexB :: PBFMIndexSeqB -> ST s FMIndexSeqB Source #

Strict state monad function.

type PTFMIndexSeqT = Seq (Maybe Text) Source #

Abstract PTFMIndexSeqT type utilizing a Seq.

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

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

type STFMIndexSeqT s a = STRef s FMIndexSeqT Source #

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

updateSTFMIndexSeqAT :: STFMIndexSeqT s (Seq (Maybe Text, Seq (Int, Int, Maybe Text))) -> (Int, Int, Maybe Text) -> ST s () Source #

State function to update FMIndexSeqT with each step of the FMIndex.

updateSTFMIndexSeqBT :: STFMIndexSeqT s (Seq (Maybe Text, Seq (Int, Int, Maybe Text))) -> Maybe Text -> ST s () Source #

State function to update FMIndexSeqT with each step of the FMIndex.

emptySTFMIndexSeqT :: ST s (STFMIndexSeqT s a) Source #

State function to create empty STFMIndexSeqT type.

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

Abstract STFMIndexILT and associated state type.

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

State function to load list into STFMIndexILT.

emptySTFMIndexILT :: ST s (STFMIndexILT s a) Source #

State function to create empty STFMIndexILT type.

type STFMIndexCounterT s a = STRef s Int Source #

Abstract STFMIndexCounterT and associated state type.

updateSTFMIndexCounterT :: STFMIndexCounterT s Int -> Int -> ST s () Source #

State function to update STFMIndexCounterT.

emptySTFMIndexCounterT :: ST s (STFMIndexCounterT s Int) Source #

State function to create empty STFMIndexCounterT type.

seqToFMIndexT :: PTFMIndexSeqT -> ST s FMIndexSeqT 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.