
Hi Norman, This is a bug in GHC 8.0.1, fixed in later versions. Dropping the parentheses around your forall-type will fix the problem:
TLit :: forall a . (a -> (TExp a)
GHC uses something of a dumb algorithm for detecting the result of a constructor, and that algorithm got stymied by parentheses. Even today, it gets stymied by, e.g., type families, but at least it knows about parentheses. I hope this helps! Richard
On Jul 5, 2019, at 9:34 AM, Norman Ramsey
wrote: Here is a legacy file that does not compile with GHC 8.0.1:
{-# LANGUAGE RankNTypes, GADTs, KindSignatures #-}
module Bookgadt where
data TExp :: * -> * where TLit :: (forall a . (a -> (TExp a))) TLit' :: (a -> (TExp a))
The compiler rejects value constructor TLit with this error message:
• Data constructor ‘TLit’ returns type ‘forall a. a -> TExp a’ instead of an instance of its parent type ‘TExp a’
I really want to keep the explicit "forall," as I'm trying to make a point for readers not familiar with Haskell. Does anyone know if there is some option or other incantation that would enable this code to compile?
Norman _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.