[commit: ghc] master: base: Enable TypeInType in Data.Type.Equality (b099171)

git at git.haskell.org git at git.haskell.org
Sat Sep 16 13:45:01 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/b09917143afe837d717feeaf97b699bcc9e016cd/ghc

>---------------------------------------------------------------

commit b09917143afe837d717feeaf97b699bcc9e016cd
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Fri Sep 15 18:57:43 2017 -0400

    base: Enable TypeInType in Data.Type.Equality
    
    Otherwise compilation fails with,
    
        libraries/base/Data/Type/Equality.hs:145:4: error:
            • Data constructor ‘HRefl’ constrains the choice of kind parameter:
                k2 ~ k2
              Use TypeInType to allow this
            • In the definition of data constructor ‘HRefl’
              In the data type declaration for ‘:~~:’
            |
        145 |    HRefl :: a :~~: a
            |    ^


>---------------------------------------------------------------

b09917143afe837d717feeaf97b699bcc9e016cd
 libraries/base/Data/Type/Equality.hs | 1 +
 1 file changed, 1 insertion(+)

diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs
index 64bb555..5caa35a 100644
--- a/libraries/base/Data/Type/Equality.hs
+++ b/libraries/base/Data/Type/Equality.hs
@@ -12,6 +12,7 @@
 {-# LANGUAGE ExplicitNamespaces     #-}
 {-# LANGUAGE MultiParamTypeClasses  #-}
 {-# LANGUAGE FunctionalDependencies #-}
+{-# LANGUAGE TypeInType             #-}
 {-# LANGUAGE Trustworthy            #-}
 
 -----------------------------------------------------------------------------



More information about the ghc-commits mailing list