You're welcome!
On 10/26/15 1:18 PM, Michael Whitehead wrote:
Nevermind. If I change the wrap function then I get what I want.
|
wrap :: Parser a -> Parser a
wrap p = p
<|> ("escape" *> p)
<|> anyChar *> wrap p
|
Thanks for the help!
On Monday, October 26, 2015 at 8:54:06 AM UTC-6, Michael Whitehead wrote:
> The solution I came up with was to push as much logic into the
parser as possible:
Thanks for your solution. That is pretty much what I was looking for
Just one last thing that I am trying to figure out is that the
command that immediately follows an "escape" gets swallowed somehow.
So in this example
example :: Producer B.ByteString IO ()
example = do
yield "foobarbaz"
yield "foo"
yield "escape" -- exit early from parse based on specific
value
yield "foobarbaz"
It should give
Just (Command Foo Bar Baz)
Nothing
Just (Command Foo Bar Baz)
But it only gives this
Just (Command Foo Bar Baz)
Nothing
I know that there is probably something really simple that I am
missing.
On Sunday, October 25, 2015 at 3:45:47 PM UTC-6, Gabriel Gonzalez
wrote:
The solution I came up with was to push as much logic into the
parser as possible:
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Applicative
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
wrap :: Parser a -> Parser (Maybe a)
wrap p
= fmap Just p
<|> ("escape" *> pure Nothing)
<|> anyChar *> wrap p
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 (Maybe Command)
commandParser =
liftA3 (liftA3 Command)
(wrap fooParser)
(wrap barParser)
(wrap 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 ()
This gives the following output:
Just (Command Foo Bar Baz)
Just (Command Foo Bar Baz)
Nothing
Then you can tell the downstream stages to stop looping when
you get a `Nothing` since that indicates that it parsed the
`escape` token.
On 10/23/2015 10:30 PM, Michael Whitehead wrote:
|
{-# 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 ()
|
--
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
<mailto:haskell-pipes+unsubscr...@googlegroups.com>.
To post to this group, send email to haskell-pipes@googlegroups.com
<mailto:haskell-pipes@googlegroups.com>.
--
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.