Very useful to get a gadt back to monotype without an existential, which would mean to use classes for future uses of it with its load of object oriented thinking.
 
Thanks for sharing.

paolino

2012/6/4 Ryan Ingram <ryani.spam@gmail.com>
Another option is to reify the type so that you can get it back somehow.  Here's a few diffs to your file (I've attached the full code):

A new type:
data Typed f where
   TDouble :: f Double -> Typed f
   TBool :: f Bool -> Typed f

runT :: (f Double -> a) -> (f Bool -> a) -> Typed f -> a
runT k _ (TDouble x) = k x
runT _ k (TBool x)   = k x

New version of pExpr that can parse both expression types, by tagging with the type

-- pExpr     = pArit <|> pBool <|> pEqual
pExpr     = (TDouble <$> pArit) <|> (TBool <$> pBool) <|> (TDouble <$> pEqual)

and now main:
main = do line <- getLine
          case parse pExpr "" line of
            Left msg -> putStrLn (show msg)
            Right e -> putStrLn (runT (show . eval) (show . eval) e)

What I'm doing here is reifying the possible types of top level expressions and then providing a handler in main which works on all possible types.  There are other ways to do this (embed any expression in an existential, for example), but this makes it really clear what is going on, and shows the way forward for parsing a larger typed language.

  -- ryan

On Wed, May 2, 2012 at 6:08 AM, <j.romildo@gmail.com> wrote:
On Wed, May 02, 2012 at 03:02:46PM +0300, Roman Cheplyaka wrote:
> * j.romildo@gmail.com <j.romildo@gmail.com> [2012-05-02 08:03:45-0300]
[...]
> The alternatives given to <|> must be of the same type. In your case,
> one is Expr Double and one is Expr Bool.
>
> Inclusion of pBool in pFactor is probably a mistake — unless you're
> going to multiply booleans.

You are right in the sense that I cannot mix Expr Bool and Expr Double
in a (O op l r) expression.

But the parser should be able to parse any form of expressions. So I
rewrite my program to take this into account.

The new versions still does not compile:

Expr.hs:27:23:
   Couldn't match expected type `Double' with actual type `Bool'
   Expected type: ParsecT
                    String () Data.Functor.Identity.Identity (Expr Double)
     Actual type: ParsecT
                    String () Data.Functor.Identity.Identity (Expr Bool)
   In the first argument of `(<|>)', namely `pBool'
   In the second argument of `(<|>)', namely `pBool <|> pEqual'

Romildo

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe