GADT pattern match in non-rigid context

Neil Mitchell ndmitchell at gmail.com
Mon Dec 17 11:23:24 EST 2007


Hi,

Upgrading from GHC 6.6 to 6.8 has caused some code to stop working:

----------------------------------------------------------------------
{-# OPTIONS_GHC -fglasgow-exts #-}

module Data2 where

data CCompany

data Paradise :: * -> * where
    CC :: Paradise CCompany

rewrapCC CC = []
----------------------------------------------------------------------

[1 of 1] Compiling Data2            ( Data2.hs, interpreted )

Data2.hs:12:9:
    GADT pattern match in non-rigid context for `CC'
      Tell GHC HQ if you'd like this to unify the context
    In the pattern: CC
    In the definition of `rewrapCC': rewrapCC CC = []

This code is from the Uniplate benchmarking code, which runs the
Paradise benchmark from SYB on Uniplate, Compos and SYB. The Compos
code uses GADT's, so the program first needs to convert from standard
data structures to GADT's before it can work, then back at the end.
It's the problem of converting from a GADT to a normal data structure
that is failing.

So is there an easy workaround? Or should I be asking GHC HQ to unify things?

Thanks

Neil


More information about the Glasgow-haskell-users mailing list