{-# LANGUAGE MultiWayIf   #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE Strict       #-}


-- |
-- Module      :  Data.BWT
-- Copyright   :  (c) Matthew Mosior 2022
-- License     :  BSD-style
-- Maintainer  :  mattm.github@gmail.com
-- Portability :  portable
--
-- = Burrows-Wheeler Transform (BWT)
-- 
-- The two functions that most users will utilize are 'toBWT' and 'fromBWT'.
-- There are auxilary function(s) inside of @"Data.BWT.Internal"@.
--
-- @"Data.BWT.Internal"@ also has the function 'createBWTMatrix', which can be useful as well, although not used by either 'toBWT' or 'fromBWT'.


module Data.BWT where

import Data.BWT.Internal

import Control.Monad()
import Control.Monad.ST as CMST
import Control.Monad.State.Strict()
import Data.Foldable as DFold (toList)
import Data.Sequence as DS
import Data.STRef()


{-toBWT function(s).-}

-- | Takes a String and returns the Burrows-Wheeler Transform (BWT).
-- Implemented via a 'SuffixArray'.
toBWT :: Ord a =>
         [a]   ->
         BWT a
toBWT :: forall a. Ord a => [a] -> BWT a
toBWT [] = forall a. Seq a
DS.Empty
toBWT [a]
xs = do
  let saxs :: SuffixArray a
saxs = forall a. Ord a => Seq a -> SuffixArray a
createSuffixArray Seq a
xss
  forall a. SuffixArray a -> Seq a -> BWT a
saToBWT SuffixArray a
saxs
          Seq a
xss
    where
      xss :: Seq a
xss = forall a. [a] -> Seq a
DS.fromList [a]
xs

{--------------------}


{-fromBWT function(s).-}

-- | Takes a BWT data type (please see @"Data.BWT.Internal"@) and inverts it back to the original string.
-- 
-- This function utilizes the state monad (strict) in order
-- to implement the [Magic](https://www.youtube.com/watch?v=QwSsppKrCj4) Inverse BWT algorithm by backtracking
-- indices starting with the (__Nothing__,_) entry.
fromBWT :: Ord a =>
           BWT a ->
           [a]
fromBWT :: forall a. Ord a => BWT a -> [a]
fromBWT BWT a
bwt = do
  let originall :: BWTSeq a
originall = forall a. (forall s. ST s a) -> a
CMST.runST forall a b. (a -> b) -> a -> b
$ forall a s. Seq (Maybe a, Int) -> ST s (BWTSeq a)
magicInverseBWT Seq (Maybe a, Int)
magicsz
  forall (t :: * -> *) a. Foldable t => t a -> [a]
DFold.toList BWTSeq a
originall
    where
      magicsz :: Seq (Maybe a, Int)
magicsz = forall a. (a -> a -> Ordering) -> Seq a -> Seq a
DS.sortBy (\(Maybe a
a,Int
b) (Maybe a
c,Int
d) -> forall a1 a2. (Ord a1, Ord a2) => (a1, a2) -> (a1, a2) -> Ordering
sortTB (Maybe a
a,Int
b) (Maybe a
c,Int
d))
                Seq (Maybe a, Int)
zipped
      zipped :: Seq (Maybe a, Int)
zipped  = forall a b. Seq a -> Seq b -> Seq (a, b)
DS.zip BWT a
bwt
                       (forall a. Int -> (a -> a) -> a -> Seq a
DS.iterateN (forall a. Seq a -> Int
DS.length BWT a
bwt) (forall a. Num a => a -> a -> a
+Int
1) Int
0)

{----------------------}