Tomasz

I'm happy to say that this is fixed. Try the HEAD.
I've immortalised your example as tests gadt21 and gadt22

Simon

| -----Original Message-----
| From: Tomasz Zielonka [mailto:[EMAIL PROTECTED]
| Sent: 14 November 2006 07:31
| To: Simon Peyton-Jones
| Subject: Re: Major type-class overhaul
|
| On Mon, Nov 13, 2006 at 03:33:25PM +0000, Simon Peyton-Jones wrote:
| > | If you want, I can create a small example.
| >
| > yes please.  I can't help at all without !
|
| It seems that it was my error, at least to some degree. Example
| code giving this strange error:
|
|     {-# OPTIONS -fglasgow-exts -Wall #-}
|
|     module Expr where
|
|     import Data.Set (Set)
|
|     data Type a where
|         TypeInt     :: Type Int
|         TypeSet     :: {- Ord a => -} Type a -> Type (Set a)
|         TypeFun     :: Type a -> Type b -> Type (a -> b)
|
|     data Expr :: * -> * where
|         Const :: Type a -> a -> Expr a
|
|     data DynExpr = forall a. DynExpr (Expr a)
|
|     withOrdDynExpr :: DynExpr -> (forall a. Ord a => Expr a -> b) ->
| Maybe b
|     withOrdDynExpr (DynExpr e@(Const (TypeSet _) _)) f = Just (f e)
|     withOrdDynExpr (DynExpr e@(Const TypeInt _)) f = Just (f e)
|     withOrdDynExpr _ _ = Nothing
|
| It compiles when you uncomment the (Ord a) context.
| When there is no context, I get the "Overlapping instances"
| error.
|
| Best regards
| Tomasz

_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to