RE: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

If only it were that easy. Sadly, it's not. Let's look at the following example: data Test = Test { foo :: Int, bar :: Char, baz :: Bool } smallPrint t = concatMap (\f -> show $ f t) [foo, bar, baz] In this code the list [foo, bar, baz] should have the type [exists a. Show a => Test -> a]. If we explicitly specify the type, replacing the exists with a forall, then GHC complains about not being able to match Int, Char and Bool against type a. Forall is not the same as exists and GHC only implements the former. ________________________________________ From: Bulat Ziganshin [bulat.ziganshin@gmail.com] Sent: 19 April 2009 22:07 To: Niemeijer, R.A. Cc: haskell-cafe@haskell.org Subject: Re[2]: [Haskell-cafe] ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release Hello R.A., Sunday, April 19, 2009, 11:46:53 PM, you wrote:
Does anybody know if there are any plans to incorporate some of these extensions into GHC - specifically the existential typing ?
it is already here, but you should use "forall" keyword instead odf "exists" -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

|data Test = Test { foo :: Int, bar :: Char, baz :: Bool } |smallPrint t = concatMap (\f -> show $ f t) [foo, bar, baz] |In this code the list [foo, bar, baz] should have the type [exists a. Show a => Test -> a]. {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ExistentialQuantification #-} data EShow = forall a. Show a => EShow a smallPrint t = concatMap (\f-> case f t of EShow a -> show a) [EShow . foo, EShow . bar, EShow . baz] data Test = Test { foo :: Int, bar :: Char, baz :: Bool } Apart from the extra wrapping, this hardcodes the class. So perhaps you'd prefer something like data E t = forall a. E (a->t) a smallPrint' t = concatMap (\f-> case f t of E show a -> show a) [E show . foo, E show . bar, E show . baz] GHC does have existentials (Hugs has them, too, and HBC had them as well?), but is more conservative about their use than UHC seems to be. Claus PS there's also the old standby of applying the functions in the interface and letting non-strict evaluation taking care of the rest (keeping the intermediate type implicit, instead of explicitly hidden): smallPrint_ t = concatMap (\f-> f t) [show . foo, show . bar, show . baz]
participants (2)
-
Claus Reinke
-
Niemeijer, R.A.