[Haskell-cafe] Help wanted getting old GADT code to compile
Norman Ramsey
nr at cs.tufts.edu
Fri Jul 5 13:34:37 UTC 2019
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
More information about the Haskell-Cafe
mailing list