
On Sat, Jul 21, 2012 at 2:34 AM, Brent Yorgey
You are right, actually, only ExistentialQuantification is necessary, as long as we also stop using GADT syntax. I didn't realize before that this syntax is accepted:
{-# LANGUAGE ExistentialQuantification #-}
data Delimiter a = DelimEltPred (a -> Bool) | Eq a => DelimSublist [a]
I do agree that this is a bit weird, what's going on here is not exactly existential quantification. But in any case the ExistentialQuantification extension turns on this ability to embed class constraints in data constructors -- at least in GHC.
GADTs and ExistentialQuantification are pretty similar. There's only two differences: - Syntax - GADTs enable equality constraints, ExistentialQuantification does not But if you have equality constraints from somewhere else (say, TypeFamilies) then ExistentialQuantification is equivalent to GADTs. An unrelated suggestion: you can give type signatures to the various functions which are synonyms of each other as a group and they will show up as a single item in the Haddocks. For example, instead of -- | some docs splitOn :: Eq a => [a] -> [a] -> [[a]] -- | some other docs sepBy :: Eq a => [a] -> [a] -> [[a]] -- | different docs unintercalate :: Eq a => [a] -> [a] -> [[a]] you can have -- | one and only docs splitOn, sepBy, unintercalate :: Eq a => [a] -> [a] -> [[a]] I don't know if you consider this an improvement. I think I do. -- Your ship was caught in a monadic eruption.