Not sure if I should try to solve my problem with attoparsec itself or with 
pipes. Either way I don't really know where to start so I would appreciate 
it if someone could help me a little.

{-# LANGUAGE OverloadedStrings #-}

module Main where

import qualified Data.ByteString as B
import Pipes
import qualified Pipes.Prelude as P
import qualified Pipes.Attoparsec as P
import Data.Attoparsec.ByteString.Char8 as A


data Foo = Foo deriving Show
data Bar = Bar deriving Show
data Baz = Baz deriving Show
data Command = Command Foo Bar Baz deriving Show
data Escape = Escape deriving Show

fooParser :: Parser Foo
fooParser = string "foo" >> return Foo

barParser :: Parser Bar
barParser = string "bar" >> return Bar

bazParser :: Parser Baz
bazParser = string "baz" >> return Baz

exitParser :: Parser Escape
exitParser = string "escape" >> return Escape

commandParser :: Parser Command
commandParser =
    Command <$> fooParser
            <*> barParser
            <*> bazParser


example :: Producer B.ByteString IO ()
example = do
  yield "foobarbaz"
  yield "foo"
  yield "bar"
  yield "invalid" -- skip over invalid input
  yield "baz"
  yield "foo"
  yield "escape" -- exit early from parse based on specific value
  yield "foobarbaz"

main :: IO ()
main = do
  runEffect $ P.parsed commandParser example >-> P.print
  return ()


Basically I want to make it so that when there is an invalid input it will 
just skip it and continue where it left off. Also I would like to be able 
to handle special values that will allow an exit from the parsing so I can 
start fresh.

-- 
You received this message because you are subscribed to the Google Groups 
"Haskell Pipes" group.
To unsubscribe from this group and stop receiving emails from it, send an email 
to haskell-pipes+unsubscr...@googlegroups.com.
To post to this group, send email to haskell-pipes@googlegroups.com.

Reply via email to