I am writing a parser for a custom jupter kernel using megaparsec. I was able to re-use the parser to provide completions too: the custom error message generated from the megaparsec library are transformed to the list of expected symbols. It that way, whenever I change the parser, completion automatically adjust itself. Which is great.
The only thing I am struggling is how to get info from the optional parsers. The minimal example illustrating what I want to achieve is following:
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Applicative
import Text.Megaparsec
import Text.Megaparsec.Char
import qualified Text.Megaparsec.Char.Lexer as L
import Data.Monoid
import Data.Text (Text)
import Data.Set (singleton)
type Parser = Parsec MyError Text
data MyError = ExpectKeyword Text deriving (Eq, Ord, Show)
lexeme = L.lexeme sc
sc = L.space (skipSome (oneOf [' ', '\t'])) empty empty
-- | Reserved words
rword :: Text -> Parser Text
rword w = region (fancyExpect (ExpectKeyword w)) $
lexeme (string w *> return w)
fancyExpect f e = FancyError (errorPos e) (singleton . ErrorCustom $ f)
p1 = rword "foo" <|> rword "bar"
p2 = (<>) <$> option "def" (rword "opt") <*> p1
main = do
putStrLn . show $ parse p1 "" ("xyz" :: Text) -- shows "foo" and "bar" in errors
putStrLn . show $ parse p2 "" ("xyz" :: Text) -- like above, no optional "opt"
In the first case, parser fails and I get the list of all errors from all alternatives. Ideally, in the second case I would like to see the error of the failed optional parser too.
This example can be simply solved by removing option
and making two branches with <|>
: one with option and the other without. However in real case the optional part is a permutation parser consisting of several optional parts, so such trick is not feasible.
option x p = p <|> pure x
be definition, so I can't see why making two branches as you say would help, since it would be equivalent top <|> p <|> pure x
. – Pazp3 = ((<>) <$> rword "opt" <*> p1) <|> p1
. That parser in custom error reports that it expects "foo", "bar" or "opt". Whilep2
informs only on "foo" and "bar", despite the fact that "opt" would be fine too. – Revocationoption
does produce custom error:pure
is parser that always succeeds, so the wholeoption
parser does not need any input to succeed. The question is still valid: how elegantly get what is expected by optional parser. – Revocationlabel
/<?>
of any help for your issue? It is not the same, but... – Paz