Hi all,

I have a function from Text -> Text which I want to apply to each line using pipes-text and pipes-group.


I'm pretty sure my pipe is not doing what I expect. I'm going back over the pipes tutorial now, but I think I could use some help figuring it out.

I have the following (buildable github project: https://github.com/codygman/fixedWidthToDelimited) code:

import Data.Monoid
import Pipes
import qualified Pipes.Text as Text
import qualified Pipes.Text.IO as Text
import System.IO
import Lens.Family
import qualified Pipes.Group as Group
import qualified Data.Text as T



appendAt :: Int -> T.Text -> T.Text -> (T.Text,T.Text)
appendAt i appendBS bs = let (first, rest) = T.splitAt i bs in (first <> appendBS <> rest,rest)

-- TODO figure out how to test a pipe (I'm sure pipes-text or any other libraries test their pipes)
toDelimPipe :: Monad m => [Int] -> Pipe T.Text T.Text m r
toDelimPipe offsets = do
    chunk <- await
    let text = (fixedWidthLine offsets) chunk
    if T.null text
      then (toDelimPipe offsets)
      else do yield text
              cat

fixedWidthLine :: [Int] -> T.Text -> T.Text
fixedWidthLine offsets bs = fst $ go offsets ("" :: T.Text,bs)
  where go :: [Int] -> (T.Text,T.Text) -> (T.Text,T.Text)
        go [] x = x
        go (x:xs) (acc,rest) = let (newAcc,newRest) = T.splitAt x rest in go xs (acc <> (fst $ appendAt x "|" newAcc),newRest)

{-
got:
runEffect $ over Text.lines (Group.maps (>-> toDelimPipe [2,2,2] )) (Text.fromLazy (LT.replicate 2 "x" <> LT.replicate 2 "y" <> LT.replicate 2 "z")) >-> Text.stdout
xx|||yyzz

Expected:

xx|yy|zz|

When I use fixedWidthLine alone with the same offsets I get:

λ> fixedWidthLine [2,2,2] (T.replicate 2 "x" <> T.replicate 2 "y" <> T.replicate 2 "z")
"xx|yy|zz|"

I think my pipe is wrong

-}