
Ah now I see. The relevant comment, TcExpr line 465, says -- Doing record updates on -- GADTs and/or existentials is more than my tiny brain can cope with today Should be fixable, even with a tiny brain. Simon | -----Original Message----- | From: Sittampalam, Ganesh [mailto:ganesh.sittampalam@credit-suisse.com] | Sent: 10 September 2008 17:43 | To: Simon Peyton-Jones; Wolfgang Jeltsch; glasgow-haskell-users@haskell.org | Cc: Dimitrios Vytiniotis | Subject: RE: Is FPH implemented in GHC? | | > | A possibly related question is whether you would expect to make | record | > | selectors and updaters work for all record types at the same time? | > | That would definitely be very useful. | | > I'm not sure what you mean by this. Would you care to elaborate? | | The most important thing for me is supporting record update for | existentially | quantified data records, as in the error below. | | In general I also find working with code that involves existential type | variables quite hard work - for example I can't use foo as a record | selector | either, even if I immediately do something that seals the existential | type back | up again. | | I don't understand this stuff well enough to be sure whether it's an | impredicativity issue or not, though. | | Cheers, | | Ganesh | | Foo.hs:11:8: | Record update for the non-Haskell-98 data type `Foo' is not (yet) | supported | Use pattern-matching instead | In the expression: rec {foo = id} | In the definition of `f': f rec = rec {foo = id} | | {-# LANGUAGE Rank2Types #-} | | module Foo where | | data Foo = forall a . Foo { foo :: a -> a, bar :: Int } | | x :: Foo | x = Foo { foo = id, bar = 3 } | | f :: Foo -> Foo | f rec = rec { foo = id } | | g :: Foo -> Foo | g rec = rec { bar = 3 } | | ============================================================================= | = | Please access the attached hyperlink for an important electronic | communications disclaimer: | | http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html | ============================================================================= | = |