Search code examples
haskellparsec

Parsec parsing in Haskell


I have 2 parsers:

nexpr::Parser (Expr Double)
sexpr::Parser (Expr String)

How do I build a parser that tries one and then the other if it doesn't work? I can't figure out what to return. There must be a clever way to do this.

Thanks.

EDIT:

Adding a bit more info...

I'm learning Haskel, so I started with :

data Expr a where
    N::Double -> Expr Double
    S::String -> Expr String
    Add::Expr Double -> Expr Double -> Expr Double
    Cat::Expr String -> Expr String -> Expr String

then I read about F-algebra (here) and so I changed it to:

data ExprF :: (* -> *) -> * -> * where
    N::Double -> ExprF r Double
    S::String -> ExprF r String
    Add::r Double -> r Double -> ExprF r Double
    Cat::r String -> r String -> ExprF r String

with

type Expr = HFix ExprF

so my parse to:

Parser (Expr Double)

is actually:

Parser (ExprF HFix Double)

Maybe I'm biting off more than I can chew...


Solution

  • As noted in the comments, you can have a parser like this

    nOrSexpr :: Parser (Either (Expr Double) (Expr String))
    nOrSexpr = (Left <$> nexpr) <|> (Right <$> sexpr)
    

    However, I think the reason that you are having this difficulty is because you are not representing your parse tree as a single type, which is the more usual thing to do. Something like this:

    data Expr = 
          ExprDouble Double 
        | ExprInt Int 
        | ExprString String
    

    That way you can have parsers for each kind of expression that are all of type Parser Expr. This is the same as using Either but more flexible and maintainable. So you might have

    doubleParser :: Parser Expr
    doubleParser = ...
    
    intParser :: Parser Expr
    intParser = ...
    
    stringParser :: Parser Expr
    stringParser = ...
    
    exprParser :: Parser Expr
    exprParser = intParser <|> doubleParser <|> stringParser
    

    Note that the order of the parsers does matter and use can use Parsec's try function if backtracking is needed.

    So, for example, if you want to have a sum expression now, you can add to the data type

    data Expr = 
          ExprDouble Double 
        | ExprInt Int 
        | ExprString String
        | ExprSum Expr Expr
    

    and make the parser

    sumParser :: Parser Expr
    sumParser = do
        a <- exprParser
        string " + "
        b <- exprParser
        return $ ExprSum a b
    

    UPDATE

    Well, I take my hat off to you diving straight into GADTs if you are just starting with Haskell. I have been reading through the paper you linked and noticed this immediately in the first paragraph:

    The jury is still out on whether the additional type-safety provided by GADTs is worth the added inconvenience of working with them.

    There are three points worth taking away here I think. The first is simply that I would have a go with the simpler way of doing things first, to get an idea of how it works and why you might want to add more type safety, before trying to more complicated type theoretical stuff. That comment may not help so feel free to ignore it!

    Secondly, and more importantly, your representation...

    data ExprF :: (* -> *) -> * -> * where
        N :: Double -> ExprF r Double
        S :: String -> ExprF r String
        Add :: r Double -> r Double -> ExprF r Double
        Cat :: r String -> r String -> ExprF r String
    

    ...is specifically designed to not allow ill formed type expressions. Contrasted with mine which can, eg ExprSum (ExprDouble 5.0) (ExprString "test"). So the question you really want to ask is what should actually happen when the parser attempts to parse something like "5.0 + \"test\""? Do you want it to just not parse, or do you want it to return a nice message saying that this expression is the wrong type? Compilers are usually designed in multiple stages for this reason. The first pass turns the input into an abstract syntax tree (AST), and further passes annotate this tree with type judgements. This annotated AST can then be transformed into the semantic representation that you really want it in.

    So in your case I would recommend two stages. first, parse into a dumb representation like mine, that will give you the correct tree shape but allow ill-typed expressions. Like

    data ExprAST = 
          ExprASTDouble Double 
        | ExprASTInt Int 
        | ExprASTString String
        | ExprASTAdd Expr Expr
    

    Then have another function that will typecheck the ExprAST. Something like

     typecheck :: ExprAST -> Maybe (ExprF HFix a)
    

    (You could also use Either and return either the typechecked GADT or an error string saying what the problem is.) The further problem here is that you don't know what a is statically. The other answer solves this by using type tags and an existential wrapper, which you might find to be the best way to go. I feel like it might be simpler to have a top level expression in your GADT that all expressions must live in, so an entire parse will always have the same type. In the end there is usually only one program type.

    My third, and last, point is related to this

    The jury is still out on whether the additional type-safety provided by GADTs is worth the added inconvenience of working with them.

    The more type safety, generally the more work you have to do to get it. You mention you are new to Haskell, yet this adventure has taken us right to the edge of what it is capable of doing. The type of the parsed expression cannot depend only on the input string in a Haskell function, because it does not allow for dependant types. If you want to go down this path, I might suggest you have a look at a language called Idris. A great introduction to what it is capable of can be found in this video, in which he constructs a typesafe printf.