
On Sat, Dec 27, 2008 at 3:09 PM, Andrew Wagner
Hmm, I actually simplified my problem too much. What I actually want is: data Foo a = forall a. Bar a => Foo a Bool
...except I want the 'a' on the left to match the 'a' on the right, so that you can only construct values out of values of the parameterized type, which also must be of the Bar class.
Something like this?
{-# LANGUAGE ExistentialQuantification #-}
class Bar a where
bar :: a -> a
data Foo a = (Bar a) => Foo a Bool
baz :: Foo a -> a
baz (Foo a _) = bar a
This works fine for me with GHC 6.8, but I'd expect Hugs and earlier
versions of GHC to reject it.
See section 8.4.5 of the GHC manual.
http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions...
--
Dave Menendez