I'm trying to learn how to use pipes together with attoparsec by following the tutorial https://hackage.haskell.org/package/pipes-attoparsec-0.1.0.1/docs/Control-Proxy-Attoparsec-Tutorial.html . But I was not able to import Control.Proxy.Trans.Either . In which lib is this module located?
You hit on an old version of pipes-attoparsec
corresponding to an old version of pipes
. With recent versions, something like the first example would be written without a pipe. We would use the parsed
function, which just applies a parser repeatedly until it fails, streaming good parses as they come.
{-# LANGUAGE OverloadedStrings #-}
import Pipes
import qualified Pipes.Prelude as P
import Pipes.Attoparsec
import Data.Attoparsec.Text
import Data.Text (Text)
data Name = Name Text deriving (Show)
hello :: Parser Name
hello = fmap Name $ "Hello " *> takeWhile1 (/='.') <* "."
helloparses :: Monad m => Producer Text m r -> Producer Name m (Either (ParsingError, Producer Text m r) r)
helloparses = parsed hello
process txt = do
e <- runEffect $ helloparses txt >-> P.print
case e of
Left (err,rest) -> print err >> runEffect (rest >-> P.print)
Right () -> return ()
input1, input2 :: Monad m => Producer Text m ()
input1 = each
[ "Hello Kate."
, "Hello Mary.Hello Jef"
, "f."
, "Hel"
, "lo Tom."
]
input2 = input1 >> yield "garbage"
Then we see
-- >>> process input1
-- Name "Kate"
-- Name "Mary"
-- Name "Jeff"
-- Name "Tom"
-- >>> process input2
-- Name "Kate"
-- Name "Mary"
-- Name "Jeff"
-- Name "Tom"
-- ParsingError {peContexts = [], peMessage = "string"}
-- "garbage"
The other principle function pipes-attoparsec
defined is just parse
. This converts an attoparsec parser into a pipes StateT
parser to parse an initial segment of a producer that matches the parser. You can read about them here http://www.haskellforall.com/2014/02/pipes-parse-30-lens-based-parsing.html