Say I have code like below. If I comment the leftover in main, I got (Just
"L1\n", Just "L2\n", Just "L3\n", Just "L4\n"). But if I did not comment
the leftover, then I got (Just "L1\n", Just "L1\n", Just "", Just "L2\n").
Why is not it (Just "L1\n", Just "L1\n", Just "L2\n", Just "L3\n")?

takeLine :: (Monad m) => Consumer ByteString m (Maybe ByteString)
takeLine = do
  mBS <- await
  case mBS of
    Nothing -> return Nothing
    Just bs ->
      case DBS.elemIndex _lf bs of
        Nothing -> return $ Just bs
        Just i -> do
          let (l, ls) = DBS.splitAt (i + 1) bs
          leftover ls
          return $ Just l

main = do
  m <- runResourceT $ sourceFile "test.simple" $$ (do
    a <- takeLine
    leftover $ fromJust a
    b <- takeLine
    c <- takeLine
    d <- takeLine
    return (a, b, c, d))
  print m

-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to