[ANN] Symparsec 2.0: Type level string parsing

I have released a major update on Hackage to my type level string parser combinator library Symparsec. The previous version was limited: it seemed impossible to define mutually recursive or certain failable parsers. That’s now a thing of the past. Symparsec 2.0 lets you do whatever:

> import Symparsec
> import Symparsec.Example.Expr
> :k! Run PExpr "1+2*3"
...
= Right '(EBOp Add (ELit 1) (EBOp Mul (ELit 2) (ELit 3)), "")

Error messages are tweaked to approximate megaparsec:

> import Data.Proxy -- workaround for GHCi to print type errors
> Proxy @(RunTest PExpr "1++")
<interactive>:18:1: error: [GHC-47403]
    • Symparsec parse error:
      1:3
        |
      1 | 1++
        |   ^
      badly formed expression
    • When checking the inferred type
        it :: Proxy (TypeError ...)

I think one should be able to define most Parsec-style parsers now. Parsers often utilize instances on the parser type, like Applicative and Alternative. But this isn’t an issue: I provide monomorphized versions using the same operators, so you can write e.g.

type Optional p = Con1 Just <$> p <|> Pure Nothing

which effectively matches the term-level definition in Control.Applicative:

optional v = Just <$> v <|> pure Nothing

This time around, I don’t feel like the library is very complete. In particular, I want to re-add parser singling (complex and tedious), and write lots more “how to use” materials. I would be very receptive to any interest in working on or using Symparsec, and would gladly help!

15 Likes