Convert from type `T a` to `T b` without boilerplate - haskell

So, I have an AST data type with a large number of cases, which is parameterized by an "annotation" type
data Expr a = Plus a Int Int
| ...
| Times a Int Int
I have annotation types S and T, and some function f :: S -> T. I want to take an Expr S and convert it to an Expr T using my conversion f on each S which occurs within an Expr value.
Is there a way to do this using SYB or generics and avoid having to pattern match on every case? It seems like the type of thing that this is suited for. I just am not familiar enough with SYB to know the specific way to do it.

It sounds like you want a Functor instance. This can be automatically derived by GHC using the DeriveFunctor extension.

Based on your follow-up question, it seems that a generics library is more appropriate to your situation than Functor. I'd recommend just using the function given on SYB's wiki page:
{-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables, FlexibleContexts #-}
import Data.Generics
import Unsafe.Coerce
newtype C a = C a deriving (Data,Typeable)
fmapData :: forall t a b. (Typeable a, Data (t (C a)), Data (t a)) =>
(a -> b) -> t a -> t b
fmapData f input = uc . everywhere (mkT $ \(x::C a) -> uc (f (uc x)))
$ (uc input :: t (C a))
where uc = unsafeCoerce
The reason for the extra C type is to avoid a problematic corner case where there are occurrences of fields at the same type as a (more details on the wiki). The caller of fmapData doesn't need to ever see it.
This function does have a few extra requirements compared to the real fmap: there must be instances of Typeable for a, and Data for t a. In your case t a is Expr a, which means that you'll need to add a deriving Data to the definition of Expr, as well as have a Data instance in scope for whatever a you're using.

Related

How to 'show' unshowable types?

I am using data-reify and graphviz to transform an eDSL into a nice graphical representation, for introspection purposes.
As simple, contrived example, consider:
{-# LANGUAGE GADTs #-}
data Expr a where
Constant :: a -> Expr a
Map :: (other -> a) -> Expr a -> Expr a
Apply :: Expr (other -> a) -> Expr a -> Expr a
instance Functor Expr where
fmap fun val = Map fun val
instance Applicative Expr where
fun_expr <*> data_expr = Apply fun_expr data_expr
pure val = Constant val
-- And then some functions to optimize an Expr AST, evaluate Exprs, etc.
To make introspection nicer, I would like to print the values which are stored inside certain AST nodes of the DSL datatype.
However, in general any a might be stored in Constant, even those that do not implement Show. This is not necessarily a problem since we can constrain the instance of Expr like so:
instance Show a => Show (Expr a) where
...
This is not what I want however: I would still like to be able to print Expr even if a is not Show-able, by printing some placeholder value (such as just its type and a message that it is unprintable) instead.
So we want to do one thing if we have an a implementing Show, and another if a particular a does not.
Furthermore, the DSL also has the constructors Map and Apply which are even more problematic. The constructor is existential in other, and thus we cannot assume anything about other, a or (other -> a). Adding constraints to the type of other to the Map resp. Apply constructors would break the implementation of Functor resp. Applicative which forwards to them.
But here also I'd like to print for the functions:
a unique reference. This is always possible (even though it is not pretty as it requires unsafePerformIO) using System.Mem.StableName.
Its type, if possible (one technique is to use show (typeOf fun), but it requires that fun is Typeable).
Again we reach the issue where we want to do one thing if we have an f implementing Typeable and another if f does not.
How to do this?
Extra disclaimer: The goal here is not to create 'correct' Show instances for types that do not support it. There is no aspiration to be able to Read them later, or that print a != print b implies a != b.
The goal is to print any datastructure in a 'nice for human introspection' way.
The part I am stuck at, is that I want to use one implementation if extra constraints are holding for a resp. (other -> a), but a 'default' one if these do not exist.
Maybe type classes with FlexibleInstances, or maybe type families are needed here? I have not been able to figure it out (and maybe I am on the wrong track all together).
Not all problems have solutions. Not all constraint systems have a satisfying assignment.
So... relax the constraints. Store the data you need to make a sensible introspective function in your data structure, and use functions with type signatures like show, fmap, pure, and (<*>), but not exactly equal to them. If you need IO, use IO in your type signature. In short: free yourself from the expectation that your exceptional needs fit into the standard library.
To deal with things where you may either have an instance or not, store data saying whether you have an instance or not:
data InstanceOrNot c where
Instance :: c => InstanceOrNot c
Not :: InstanceOrNot c
(Perhaps a Constraint-kinded Either-alike, rather than Maybe-alike, would be more appropriate. I suspect as you start coding this you will discover what's needed.) Demand that clients that call notFmap and friends supply these as appropriate.
In the comments, I propose parameterizing your type by the constraints you demand, and giving a Functor instance for the no-constraints version. Here's a short example showing how that might look:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
import Data.Kind
type family All cs a :: Constraint where
All '[] a = ()
All (c:cs) a = (c a, All cs a)
data Lol cs a where
Leaf :: a -> Lol cs a
Fmap :: All cs b => (a -> b) -> Lol cs a -> Lol cs b
instance Functor (Lol '[]) where
fmap f (Leaf a) = Leaf (f a)
fmap f (Fmap g garg) = Fmap (f . g) garg
Great timing! Well-typed recently released a library which allows you to recover runtime information. They specifically have an example of showing arbitrary values. It's on github at https://github.com/well-typed/recover-rtti.
It turns out that this is a problem which has been recognized by multiple people in the past, known as the 'Constrained Monad Problem'. There is an elegant solution, explained in detail in the paper The Constrained-Monad Problem by Neil Sculthorpe and Jan Bracker and George Giorgidze and Andy Gill.
A brief summary of the technique: Monads (and other typeclasses) have a 'normal form'. We can 'lift' primitives (which are constrained any way we wish) into this 'normal form' construction, itself an existential datatype, and then use any of the operations available for the typeclass we have lifted into. These operations themselves are not constrained, and thus we can use all of Haskell's normal typeclass functions.
Finally, to turn this back into the concrete type (which again has all the constraints we are interested in) we 'lower' it, which is an operation that takes for each of the typeclass' operations a function which it will apply at the appropriate time.
This way, constraints from the outside (which are part of the functions supplied to the lowering) and constraints from the inside (which are part of the primitives we lifted) are able to be matched, and finally we end up with one big happy constrained datatype for which we have been able to use any of the normal Functor/Monoid/Monad/etc. operations.
Interestingly, while the intermediate operations are not constrained, to my knowledge it is impossible to write something which 'breaks' them as this would break the categorical laws that the typeclass under consideration should adhere to.
This is available in the constrained-normal Hackage package to use in your own code.
The example I struggled with, could be implemented as follows:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UndecidableInstances #-}
module Example where
import Data.Dynamic
import Data.Kind
import Data.Typeable
import Control.Monad.ConstrainedNormal
-- | Required to have a simple constraint which we can use as argument to `Expr` / `Expr'`.
-- | This is definitely the part of the example with the roughest edges: I have yet to figure out
-- | how to make Haskell happy with constraints
class (Show a, Typeable a) => Introspectable a where {}
instance (Show a, Typeable a) => Introspectable a where {}
data Expr' (c :: * -> Constraint) a where
C :: a -> Expr' c a
-- M :: (a -> b) -> Expr' a -> Expr' b --^ NOTE: This one is actually never used as ConstrainedNormal will use the 'free' implementation based on A + C.
A :: c a => Expr' c (a -> b) -> Expr' c a -> Expr' c b
instance Introspectable a => Show (Expr' Introspectable a) where
show e = case e of
C x -> "(C " ++ show x ++ ")"
-- M f x = "(M " ++ show val ++ ")"
A fx x -> "(A " ++ show (typeOf fx) ++ " " ++ show x ++ ")"
-- | In user-facing code you'd not want to expose the guts of this construction
-- So let's introduce a 'wrapper type' which is what a user would normally interact with.
type Expr c a = NAF c (Expr' c) a
liftExpr :: c a => Expr' c a -> Expr c a
liftExpr expr = liftNAF expr
lowerExpr :: c a => Expr c a -> Expr' c a
lowerExpr lifted_expr = lowerNAF C A lifted_expr
constant :: Introspectable a => a -> Expr c a
constant val = pure val -- liftExpr (C val)
You could now for instance write
ghci> val = constant 10 :: Expr Introspectable Int
(C 10)
ghci> (+2) <$> val
(C 12)
ghci> (+) <$> constant 10 <*> constant 32 :: Expr Introspectable Int
And by using Data.Constraint.Trivial (part of the trivial-constrained library, although it is also possible to write your own 'empty constrained') one could instead write e.g.
ghci> val = constant 10 :: Expr Unconstrained Int
which will work just as before, but now val cannot be printed.
The one thing I have not yet figured out, is how to properly work with subsets of constraints (i.e. if I have a function that only requires Show, make it work with something that is Introspectable). Currently everything has to work with the 'big' set of constraints.
Another minor drawback is of course that you'll have to annotate the constraint type (e.g. if you do not want constraints, write Unconstrained manually), as GHC will otherwise complain that c0 is not known.
We've reached the goal of having a type which can be optionally be constrained to be printable, with all machinery that does not need printing to work also on all instances of the family of types including those that are not printable, and the types can be used as Monoids, Functors, Applicatives, etc just as you like.
I think it is a beautiful approach, and want to commend Neil Sculthorpe et al. for their work on the paper and the constrained-normal library that makes this possible. It's very cool!

Subset algebraic data type, or type-level set, in Haskell

Suppose you have a large number of types and a large number of functions that each return "subsets" of these types.
Let's use a small example to make the situation more explicit. Here's a simple algebraic data type:
data T = A | B | C
and there are two functions f, g that return a T
f :: T
g :: T
For the situation at hand, assume it is important that f can only return a A or B and g can only return a B or C.
I would like to encode this in the type system. Here are a few reasons/circumstances why this might be desirable:
Let the functions f and g have a more informative signature than just ::T
Enforce that implementations of f and g do not accidentally return a forbidden type that users of the implementation then accidentally use
Allow code reuse, e.g. when helper functions are involved that only operate on subsets of type T
Avoid boilerplate code (see below)
Make refactoring (much!) easier
One way to do this is to split up the algebraic datatype and wrap the individual types as needed:
data A = A
data B = B
data C = C
data Retf = RetfA A | RetfB B
data Retg = RetgB B | RetgC C
f :: Retf
g :: Retg
This works, and is easy to understand, but carries a lot of boilerplate for frequent unwrapping of the return types Retf and Retg.
I don't see polymorphism being of any help, here.
So, probably, this is a case for dependent types. It's not really a type-level list, rather a type-level set, but I've never seen a type-level set.
The goal, in the end, is to encode the domain knowledge via the types, so that compile-time checks are available, without having excessive boilerplate. (The boilerplate gets really annoying when there are lots of types and lots of functions.)
Define an auxiliary sum type (to be used as a data kind) where each branch corresponds to a version of your main type:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DataKinds #-}
import Data.Kind
import Data.Void
import GHC.TypeLits
data Version = AllEnabled | SomeDisabled
Then define a type family that maps the version and the constructor name (given as a type-level Symbol) to the type () if that branch is allowed, and to the empty type Void if it's disallowed.
type Enabled :: Version -> Symbol -> Type
type family Enabled v ctor where
Enabled SomeDisabled "C" = Void
Enabled _ _ = ()
Then define your type as follows:
type T :: Version -> Type
data T v = A !(Enabled v "A")
| B !(Enabled v "B")
| C !(Enabled v "C")
(The strictness annotations are there to help the exhaustivity checker.)
Typeclass instances can be derived, but separately for each version:
deriving instance Show (T AllEnabled)
deriving instance Eq (T AllEnabled)
deriving instance Show (T SomeDisabled)
deriving instance Eq (T SomeDisabled)
Here's an example of use:
noC :: T SomeDisabled
noC = A ()
main :: IO ()
main = print $ case noC of
A _ -> "A"
B _ -> "B"
-- this doesn't give a warning with -Wincomplete-patterns
This solution makes pattern-matching and construction more cumbersome, because those () are always there.
A variation is to have one type family per branch (as in Trees that Grow) instead of a two-parameter type family.
I tried to achieve something like this in the past, but without much success -- I was not too satisfied with my solution.
Still, one can use GADTs to encode this constraint:
data TagA = IsA | NotA
data TagC = IsC | NotC
data T (ta :: TagA) (tc :: TagC) where
A :: T 'IsA 'NotC
B :: T 'NotA 'NotC
C :: T 'NotA 'IsC
-- existential wrappers
data TnotC where TnotC :: T ta 'NotC -> TnotC
data TnotA where TnotA :: T 'NotA tc -> TnotA
f :: TnotC
g :: TnotA
This however gets boring fast, because of the wrapping/unwrapping of the exponentials. Consumer functions are more convenient since we can write
giveMeNotAnA :: T 'NotA tc -> Int
to require anything but an A. Producer functions instead need to use existentials.
In a type with many constructors, it also gets inconvenient since we have to use a GADT with many tags/parameters. Maybe this can be streamlined with some clever typeclass machinery.
Giving each individual value its own type scales extremely badly, and is quite unnecessarily fine-grained.
What you probably want is just restrict the types by some property on their values. In e.g. Coq, that would be a subset type:
Inductive T: Type :=
| A
| B
| C.
Definition Retf: Type := { x: T | x<>C }.
Definition Retg: Type := { x: T | x<>A }.
Well, Haskell has no way of expressing such value constraints, but that doesn't stop you from creating types that conceptually fulfill them. Just use newtypes:
newtype Retf = Retf { getRetf :: T }
mkRetf :: T -> Maybe Retf
mkRetf C = Nothing
mkRetf x = Retf x
newtype Retg = Retg { getRetg :: T }
mkRetg :: ...
Then in the implementation of f, you match for the final result of mkRetf and raise an error if it's Nothing. That way, an implementation mistake that makes it give a C will unfortunately not give a compilation error, but at least a runtime error from within the function that's actually at fault, rather than somewhere further down the line.
An alternative that might be ideal for you is Liquid Haskell, which does support subset types. I can't say too much about it, but it's supposedly pretty good (and will in new GHC versions have direct support).

Type Constraint in Constructor [duplicate]

This question already has answers here:
Type Constraints in Data Declaration Haskell
(3 answers)
Closed 3 years ago.
I am trying to make a normal form game solver for game theory, and I'm trying to make it as generic as possible for good practice and for my own convenience. I would like to use the same functions to solve both zero-sum and non-zero-sum games, so I am using the following data type:
data Payoffs = (Num a, Eq a, Ord a) => ZS a
| (Num a, Eq a, Ord a) => NZS (a,a)
However, this is not correct syntax. Is there any way to constrain a so that it must satisfy those type constraints?
Short answer (and probably not the one you need):
To make your code work as is, you need a forall quantifier (for which you need to enable ExistentialQuantification):
{-# LANGUAGE ExistentialQuantification #-}
data Payoffs =
forall a. (Num a, Eq a, Ord a) => ZS a
| forall a. (Num a, Eq a, Ord a) => NZS (a,a)
If you have a type variable in the data constructor (i.e. ZS a), then you have two choices: either that variable has to appear in the type constructor (i.e. data Payoffs a =), or you need to say "I don't care what type it is, as long as it supports these classes" - which is achieved via the forall quantifier.
But this looks kinda useless to me, which suggests that you may be misunderstanding what it means. If you write the above code, every value of your Payoffs type will be able to wrap a value of any type, as long as that type supports Num, Eq, and Ord. One subtle consequence of this is that, if you have two values of Payoffs lying around, they will not necessarily wrap the same type. For example:
let x = ZS (42 :: Int) -- wraps an Int
let y = NZS (2.71 :: Double, 3.14) -- wraps two Doubles
This means that, upon unpacking them, you won't be able to, for example, add them together, because, even though they both implement Num, the compiler doesn't have any proof that they're actually the same type.
What I suspect you actually need is a parametrized type, like this:
data Payoffs a = ZS a | NZS (a, a)
But then, of course, you lose the constraints: anybody can go and create ZS String or something. You can use the GADT syntax (with the GADTs extension) to bring them back:
{-# LANGUAGE GADTs #-}
data Payoffs a where
ZS :: (Num a, Ord a, Eq a) => a -> Payoffs a
NZS :: (Num a, Ord a, Eq a) => (a, a) -> Payoffs a
This notation is equivalent to ZS a | NZS (a, a), except you get to define each constructor with the same syntax as any function - including constraints. A type defined like this won't allow for creating values of type Payoffs a unless a satisfies the constraints.
At the same time, if you have a value of a type like this lying around, you know what type it wraps inside. And this allows you to tell if two Payoffs values wrap the same type or different. And then, if you know that they're the same, you can do things with them using the supported classes, for example:
addPayoffs :: Payoffs a -> Payoffs a -> Payoffs a
addPayoffs (ZS a) (ZS b) = ZS (a + b)
addPayoffs (ZS a) (NZS (x,y)) = NZS (a+x, a+y)
... etc.

Is it possible to ensure that two GADT type variables are the same without dependent types?

I'm writing a compiler where I'm using GADTs for my IR but standard data types for my everything else. I'm having trouble during the conversion from the old data type to the GADT. I've attempted to recreate the situation with a smaller/simplified language below.
To start with, I have the following data types:
data OldLVal = VarOL Int -- The nth variable. Can be used to construct a Temp later.
| LDeref OldLVal
data Exp = Var Int -- See above
| IntT Int32
| Deref Exp
data Statement = AssignStmt OldLVal Exp
| ...
I want to convert these into this intermediate form:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
-- Note: this is a Phantom type
data Temp a = Temp Int
data Type = IntT
| PtrT Type
data Command where
Assign :: NewLVal a -> Pure a -> Command
...
data NewLVal :: Type -> * where
VarNL :: Temp a -> NewLVal a
DerefNL :: NewLVal ('PtrT ('Just a)) -> NewLVal a
data Pure :: Type -> * where
ConstP :: Int32 -> Pure 'IntT
ConstPtrP :: Int32 -> Pure ('PtrT a)
VarP :: Temp a -> Pure a
At this point, I just want to write a conversion from the old data type to the new GADT. For right now, I have something that looks like this.
convert :: Statement -> Either String Command
convert (AssignStmt oldLval exp) = do
newLval <- convertLVal oldLval -- Either String (NewLVal a)
pure <- convertPure exp -- Either String (Pure b)
-- return $ Assign newLval pure -- Obvious failure. Can't ensure a ~ b.
pure' <- matchType newLval pure -- Either String (Pure a)
return $ Assign newLval pure'
-- Converts Pure b into Pure a. Should essentially be a noop, but simply
-- proves that it is possible.
matchType :: NewLVal a -> Pure b -> Either String (Pure a)
matchType = undefined
I realized that I couldn't write convert trivially, so I attempted to solve the problem using this idea of matchType which acts as a proof that these two types are indeed equal. The question is: how do I actually write matchType? This would be much easier if I had fully dependent types (or so I'm told), but can I finish this code here?
An alternative to this would be to somehow provide newLval as an argument to convertPure, but I think that essentially is just attempting to use dependent types.
Any other suggestions are welcome.
If it helps, I also have a function that can convert an Exp or OldLVal to its type:
class Typed a where
typeOf :: a -> Type
instance Typed Exp where
...
instance Typed OldLVal where
...
EDIT:
Thanks to the excellent answers below, I've been able to finish writing this module.
I ended up using the singletons package mentioned below. It was a little strange at first, but I found it pretty reasonable to use after I started understanding what I was doing. However, I did run into one pitfall: The type of convertLVal and convertPure requires an existential to express.
data WrappedPure = forall a. WrappedPure (Pure a, SType a)
data WrappedLVal = forall a. WrappedLVal (NewLVal a, SType a)
convertPure :: Exp -> Either String WrappedPure
convertLVal :: OldLVal -> Either String WrappedLVal
This means that you'll have to unwrap that existential in convert, but otherwise, the answers below show you the way. Thanks so much once again.
You want to perform a comparison at runtime on some type level data (namely the Types by which your values are indexed). But by the time you run your code, and the values start to interact, the types are long gone. They're erased by the compiler, in the name of producing efficient code. So you need to manually reconstruct the type level data that was erased, using a value which reminds you of the type you'd forgotten you were looking at. You need a singleton copy of Type.
data SType t where
SIntT :: SType IntT
SPtrT :: SType t -> SType (PtrT t)
Members of SType look like members of Type - compare the structure of a value like SPtrT (SPtrT SIntT) with that of PtrT (PtrT IntT) - but they're indexed by the (type-level) Types that they resemble. For each t :: Type there's precisely one SType t (hence the name singleton), and because SType is a GADT, pattern matching on an SType t tells the type checker about the t. Singletons span the otherwise strictly-enforced separation between types and values.
So when you're constructing your typed tree, you need to track the runtime STypes of your values and compare them when necessary. (This basically amounts to writing a partially verified type checker.) There's a class in Data.Type.Equality containing a function which compares two singletons and tells you whether their indexes match or not.
instance TestEquality SType where
-- testEquality :: SType t1 -> SType t2 -> Maybe (t1 :~: t2)
testEquality SIntT SIntT = Just Refl
testEquality (SPtrT t1) (SPtrT t2)
| Just Refl <- testEquality t1 t2 = Just Refl
testEquality _ _ = Nothing
Applying this in your convert function looks roughly like this:
convert :: Statement -> Either String Command
convert (AssignStmt oldLval exp) = do
(newLval, newLValSType) <- convertLVal oldLval
(pure, pureSType) <- convertPure exp
case testEquality newLValSType pureSType of
Just Refl -> return $ Assign newLval pure'
Nothing -> Left "type mismatch"
There actually aren't a whole lot of dependently typed programs you can't fake up with TypeInType and singletons (are there any?), but it's a real hassle to duplicate all of your datatypes in both "normal" and "singleton" form. (The duplication gets even worse if you want to pass singletons around implicitly - see Hasochism for the details.) The singletons package can generate much of the boilerplate for you, but it doesn't really alleviate the pain caused by duplicating the concepts themselves. That's why people want to add real dependent types to Haskell, but we're a good few years away from that yet.
The new Type.Reflection module contains a rewritten Typeable class. Its TypeRep is GADT-like and can act as a sort of "universal singleton". But programming with it is even more awkward than programming with singletons, in my opinion.
matchType as written is not possible to implement, but the idea you are going for is definitely possible. Do you know about Data.Typeable? Typeable is a class that provides some basic reflective operations for inspecting types. To use it, you need a Typeable a constraint in scope for any type variable a you want to know about. So for matchType you would have
matchType :: (Typeable a, Typeable b) => NewLVal a -> Pure b -> Either String (Pure a)
It needs also to infect your GADTs any time you want to hide a type variable:
data Command where
Assign :: (Typeable a) => NewLVal a -> Pure a -> Command
...
But if you have the appropriate constraints in scope, you can use eqT to make type-safe runtime type comparisons. For example
-- using ScopedTypeVariables and TypeApplications
matchType :: forall a b. (Typeable a, Typeable b) => NewLVal a -> Pure b -> Either String (Pure b)
matchType = case eqT #a #b of
Nothing -> Left "types are not equal"
Just Refl -> {- in this scope the compiler knows that
a and b are the same type -}

Is this use of GADTs fully equivalent to existential types?

Existentially quantified data constructors like
data Foo = forall a. MkFoo a (a -> Bool)
| Nil
can be easily translated to GADTs:
data Foo where
MkFoo :: a -> (a -> Bool) -> Foo
Nil :: Foo
Are there any differences between them: code which compiles with one but not another, or gives different results?
They are nearly equivalent, albeit not completely so, depending on which extensions you turn on.
First of all, note that you don't need to enable the GADTs extension to use the data .. where syntax for existential types. It suffices to enable the following lesser extensions.
{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE ExistentialQuantification #-}
With these extensions, you can compile
data U where
U :: a -> (a -> String) -> U
foo :: U -> String
foo (U x f) = f x
g x = let h y = const y x
in (h True, h 'a')
The above code also compiles if we replace the extensions and the type definition with
{-# LANGUAGE ExistentialQuantification #-}
data U = forall a . U a (a -> String)
The above code, however, does not compile with the GADTs extension turned on! This is because GADTs also turns on the MonoLocalBinds extension, which prevents the above definition of g to compile. This is because the latter extension prevents h to receive a polymorphic type.
From the documentation:
Notice that GADT-style syntax generalises existential types (Existentially quantified data constructors). For example, these two declarations are equivalent:
data Foo = forall a. MkFoo a (a -> Bool)
data Foo' where { MKFoo :: a -> (a->Bool) -> Foo' }
(emphasis on the word equivalent)
The latter isn't actually a GADT - it's an existentially quantified data type declared with GADT syntax. As such, it is identical to the former.
The reason it's not a GADT is that there is no type variable that gets refined based on the choice of constructor. That's the key new functionality added by GADTs. If you have a GADT like this:
data Foo a where
StringFoo :: String -> Foo String
IntFoo :: Int -> Foo Int
Then pattern-matching on each constructor reveals additional information that can be used inside the matching clause. For instance:
deconstructFoo :: Foo a -> a
deconstructFoo (StringFoo s) = "Hello! " ++ s ++ " is a String!"
deconstructFoo (IntFoo i) = i * 3 + 1
Notice that something very interesting is happening there, from the point of view of the type system. deconstructFoo promises it will work for any choice of a, as long as it's passed a value of type Foo a. But then the first equation returns a String, and the second equation returns an Int.
This is what you cannot do with a regular data type, and the new thing GADTs provide. In the first equation, the pattern match adds the constraint (a ~ String) to its context. In the second equation, the pattern match adds (a ~ Int).
If you haven't created a type where pattern-matching can cause type refinement, you don't have a GADT. You just have a type declared with GADT syntax. Which is fine - in a lot of ways, it's a better syntax than the basic data type syntax. It's just more verbose for the easiest cases.

Resources