[Haskell-cafe] a little parsec enhancement
Petr Pudlák
petr.mvd at gmail.com
Thu Sep 5 11:18:25 CEST 2013
Hi,
when thinking about this SO question
<http://stackoverflow.com/q/18583416/1333025>, I couldn't find a
combinator that allows a parser to /optionally/ fail without consuming
input, or consume input and return its value. So I'm suggesting such a
function:
|-- | @emptyIf p@ parses @p@ and if its return value is @Nothing@, pretends
-- that an error has occured with no input consumed.
--
-- If @p@ fails and consumes some input, so does @emptyIf p at . Combine with
-- 'try' if this is undesirable.
emptyIf :: (Stream s m t) =>ParsecT s u m (Maybe a) ->ParsecT s u m a
emptyIf p =ParsecT $ \s cok cerr eok eerr ->
let cok' (Just x) s e = cok x s e
cok'Nothing _ e = eerr e
eok' (Just x) s e = eok x s e
eok'Nothing _ e = eerr e
in unParser p s cok' cerr eok' eerr|
With this function, the answer to the SO question becomes really easy:
|rcomb :: (Stream s m t) =>ParsecT s u m a ->ParsecT s u m b ->ParsecT s u m b
rcomb p q = emptyIf $ runMaybeT (opt p *> opt q)
where
opt =MaybeT . optional-- optional from Control.Applicative!|
Whenever |p| or |q| fails without consuming input, then |rcomb p q|
fails without consuming input.
Unfortunately |ParsecT| constructor isn't exported so I'm not able to
implement it outside /parsec/. (Perhaps it would make sense to export
|ParsecT| in some module such as |Text.Parsec.Internal|?) Therefore I'm
suggesting to add such a function to /parsec/ (darcs patch included).
Perhaps change the name, I couldn't think of anything better.
Best regards,
Petr
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130905/f08d8944/attachment.htm>
-------------- next part --------------
1 patch for repository http://code.haskell.org/parsec3:
Thu Sep 5 11:12:47 CEST 2013 Petr Pudlak <petr at pudlak.name>
* Add 'emptyIf' which allows a parser to optinally fail without consuming any input.
New patches:
[Add 'emptyIf' which allows a parser to optinally fail without consuming any input.
Petr Pudlak <petr at pudlak.name>**20130905091247
Ignore-this: 59b93c660fe860acd9a5fff887f7678f
] {
hunk ./Text/Parsec/Prim.hs 38
, parserPlus
, (<?>)
, (<|>)
+ , emptyIf
, label
, labels
, lookAhead
hunk ./Text/Parsec/Prim.hs 455
p' = ParsecT $ \s cok cerr eok eerr ->
unParser p s eok cerr eok eerr
+-- | @emptyIf p@ parses @p@ and if its return value is @Nothing@, pretends
+-- that an error has occured with no input consumed.
+--
+-- If @p@ fails and consumes some input, so does @emptyIf p at . Combine with
+-- 'try' if this is undesirable.
+
+emptyIf :: (Stream s m t) => ParsecT s u m (Maybe a) -> ParsecT s u m a
+emptyIf p = ParsecT $ \s cok cerr eok eerr ->
+ let cok' (Just x) s e = cok x s e
+ cok' Nothing _ e = eerr e
+ eok' (Just x) s e = eok x s e
+ eok' Nothing _ e = eerr e
+ in unParser p s cok' cerr eok' eerr
+
+
-- | The parser @token showTok posFromTok testTok@ accepts a token @t@
-- with result @x@ when the function @testTok t@ returns @'Just' x at . The
-- source position of the @t@ should be returned by @posFromTok t@ and
}
Context:
[Fix haddock module links.
Bjorn Buckwalter <bjorn at buckwalter.se>**20130821095713
Ignore-this: 304217ec8b73f59edcd96dd13aca67af
]
[TAG 3.1.3
Antoine Latter <aslatter at gmail.com>**20120612020909
Ignore-this: 7100375a3e4853c09f1ea993ae32eed7
]
Patch bundle hash:
173111b8bbc5a6eb69d41926053184c35ae9b3cc
More information about the Haskell-Cafe
mailing list