Search code examples
haskellhaskell-pipes

How to replace double tabs with single tabs using pipes?


I need to replace all consecutive tabs in a bytestring with single tabs, like so:

"___\t___\t\t___\t\t\t___"

becomes

"___\t___\t___\t___"

I have no idea how to do it.

After half an hour of figuring stuff out I managed to replace the first occurrence of double tabs, like so (and even this is actually wrong – it adds a tab to an empty string):

import qualified Pipes.ByteString as PB
import qualified Data.ByteString as B

removeConsecutiveTabs =
  PB.break (== tab) . mapped %~ \p -> do
    yield (B.singleton tab)
    PB.dropWhile (== tab) p

However, I still don't know how to replace all occurrences of consecutive tabs.


Solution

  • Try this:

    {-# LANGUAGE OverloadedStrings #-}
    
    import Pipes
    import qualified Pipes.Prelude as P
    import qualified Pipes.ByteString as PB
    import           Data.ByteString (ByteString)
    import Control.Lens hiding (each)
    
    cleanTabs p = do
      p1 <- view (PB.span (/= 9)) p
      x <- lift $ next p1
      case x of
        Left r -> return r
        Right (a, p2) -> do
          yield "\t"
          let p3 = PB.dropWhile (== 9) (yield a >> p2)
          cleanTabs p3
    
    source :: Monad m => Producer ByteString m ()
    source = each [ "this", "is\t an", "\t\texample\t", "\t.", "\t\tmiddle\t", "\there"]
    
    example = do
      putStrLn $ "input: " ++ (show $ P.toList source)
      putStrLn $ "output:" ++ (show $ P.toList (cleanTabs source))