[Haskell-cafe] Re: Need for speed: the Burrows-Wheeler Transform
Chris Kuklewicz
haskell at list.mightyreason.com
Sat Jun 23 22:24:28 EDT 2007
I enjoy code like this that requires laziness. My modified version of your code
is below...
Bertram Felgenhauer wrote:
>>>> Code: >>>
>
> "bwt" implements a variation of the Burrows-Wheeler transform, using
> \0 as a sentinel character for simplicity. The sentinel has to be smaller
> than all other characters in the string.
>
>> bwt xs = let
>> suffixes = [(a,as) | a:as <- tails ('\0':xs)]
>> in
>> map fst . sortBy (\(_,a) (_,b) -> a `compare` b) $ suffixes
>
> "rbwt" implements the corresponding inverse BWT. It's a fun knot tying
> exercise.
>
>> rbwt xs = let
>> res = sortBy (\(a:as) (b:bs) -> a `compare` b) (zipWith' (:) xs res)
>> in
>> tail . map snd . zip xs $ head res
>
> "zipWith'" is a variant of zipWith that asserts that the third argument
> has the same shape as the second one.
>
>> zipWith' f [] _ = []
>> zipWith' f (x:xs) ~(y:ys) = f x y : zipWith' f xs ys
>
> <<< End Code <<
I did not like the look of (map snd . zip xs) since it looks like a no-op (that
constructs a useless (,) which may or may not be elided by a sufficiently smart
compiler). But it is using the fact that xs is finite and (head res) is not to
do "take (length xs) $ head res" without the extra traversal and math. But one
can abuse (zipWith' (flip const)) for a 'rbwt' appeals to me more:
> import Data.List
>
> f `on` g = \x y -> (g x) `f` (g y)
>
> zipWith' f [] _ = []
> zipWith' f (x:xs) ~(y:ys) = f x y : zipWith' f xs ys
>
> bwt = map head . sortBy (compare `on` tail) . init . tails . ('\0':)
>
> rbwt xs = tail $ zipWith' (flip const) xs $ head res
> where res = sortBy (compare `on` head) (zipWith' (:) xs res)
While I was removing (,) from the 'rbwt' I went ahead and removed it from 'bwt'
as well. This was, of course, pointless...
Thanks for the fun example,
Chris
More information about the Haskell-Cafe
mailing list