Question

Background

I'm trying to create a Parsec parser for numeric values. Those values can be either Integer or Double. They can also be signed or unsigned. I created a sign parser that returns polymorphic function id for + and negate for -. I also have a function that constructs proper version of my expression node, when given polymorphic sign function and Either Integer Double. I'm trying to put it all together as shown on simplified version of my code below.

{-# LANGUAGE RankNTypes #-}

-- (...)

data Expr = IntExpr Integer | DoubleExpr Double
pSign :: Num a => MyParser (a -> a) -- returns id for + or negate for -
pReal :: (forall a. Num a => a -> a) -> Either Integer Double -> MyParser Expr

pNum :: MyParser Expr
pNum = do
    sign <- pSign
    numVal <- ParsecToken.naturalOrFloat lexer
    pReal sign numVal

I get a compilation error "Could not deduce (a ~ Integer) ..." when I use my code like above.

When I change my code by defining sign function inside a let statement in my monad, everything compiles fine:

pNum :: MyParser Expr
pNum = do
    sign <- pSign
    numVal <- ParsecToken.naturalOrFloat lexer
    let t = sign 1
        sign' :: Num a => a -> a
        sign' = if t == 1 then id else negate
    pReal sign numVal

My guess is that in the first case, polymophic type of sign is somehow lost and converted to Integer -> Integer.

Question

  • What mechanism makes original sign :: Num a => a -> a monad variable not work as first argument of pReal :: (forall a. Num a => a -> a) -> ..., while its redefined version of the same type (sign') works?
  • How can I achieve passing polymorphic variable sign created in my monad to pReal function without re-defining (sign') it inside my monad?

Notes

I already tried approaches like explicitly defining type of sign with

pNum = pSign >>= \(sign :: Num a => a -> a) -> do ...

or the same with normal function definition etc.

Please note that I know that I can make the code easier by simply returning a boolean variable from sign instead of a polymorphic function. The point of this question is to understand how types work here.

Was it helpful?

Solution

You write

pSign :: Num a => MyParser (a -> a)

which means that pSign is a polymorphic value that, for any given instantiation of a, produces a parser containing a monomorphic function. Instead, you want a monomorphic parser containing a polymorphic function, so:

pSign :: MyParser (forall a. Num a => a -> a)

You will need to make a few other changes as well to get GHC to understand how to keep things polymorphic until the last second. Here is a complete, compilable example.

{-# LANGUAGE ImpredicativeTypes, LiberalTypeSynonyms, RankNTypes, ScopedTypeVariables #-}

import Text.ParserCombinators.Parsec

type MyParser = Parser

data Expr = IntExpr Integer | DoubleExpr Double
pSign :: MyParser (forall a. Num a => a -> a) -- returns id for + or negate for -
pReal :: (forall a. Num a => a -> a) -> Either Integer Double -> MyParser Expr
foo :: MyParser (Either Integer Double)
pSign = undefined
pReal = undefined
foo = undefined

pNum :: MyParser Expr
pNum =
    pSign >>= \(sign :: forall a. Num a => a -> a) ->
    foo >>= \numVal ->
    pReal sign numVal
Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top