[GHC] #1158: Problem with GADTs and explicit type signatures

GHC ghc-devs at haskell.org
Sun Jan 24 13:06:55 UTC 2016


#1158: Problem with GADTs and explicit type signatures
-------------------------------------+-------------------------------------
        Reporter:  guest             |                Owner:  simonpj
            Type:  bug               |               Status:  new
        Priority:  lowest            |            Milestone:  ⊥
       Component:  Compiler (Type    |              Version:  6.6
  checker)                           |             Keywords:
      Resolution:                    |  MultiParamTypeClasses,
                                     |  AllowAmbiguousTypes
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by thomie):

 * keywords:   => MultiParamTypeClasses, AllowAmbiguousTypes
 * component:  Compiler => Compiler (Type checker)


@@ -1,3 +1,5 @@
- {{{
-
- {-# OPTIONS_GHC -fglasgow-exts #-}
+ {{{#!hs
+ {-# LANGUAGE GADTs #-}
+ {-# LANGUAGE MultiParamTypeClasses #-}
+ {-# LANGUAGE FlexibleInstances #-}
+ {-# LANGUAGE AllowAmbiguousTypes #-}
@@ -25,1 +27,0 @@
-
@@ -29,11 +30,15 @@
- test.hs:45:14:
-     Overlapping instances for LiftToExp a a11
-       arising from use of `liftToExp' at test.hs:45:14-24
-     Matching instances:
-       instance (Floating a) => LiftToExp a b -- Defined at test.hs:19:0
-       instance LiftToExp (Exp a) a -- Defined at test.hs:16:0
-     (The choice depends on the instantiation of `a, a11'
-      Use -fallow-incoherent-instances to use the first choice above)
-     In the first argument of `App', namely `(liftToExp x)'
-     In the expression: App (liftToExp x)
-     In the definition of `test': test x = App (liftToExp x)
+ Test.hs:48:15: error:
+     • Overlapping instances for LiftToExp a a0
+         arising from a use of ‘liftToExp’
+       Matching givens (or their superclasses):
+         LiftToExp a a1
+           bound by the type signature for:
+                      test :: LiftToExp a a1 => a -> Exp b
+           at Test.hs:47:1-38
+       Matching instances:
+         instance LiftToExp a b -- Defined at Test.hs:22:10
+         instance LiftToExp (Exp a) a -- Defined at Test.hs:19:10
+       (The choice depends on the instantiation of ‘a, a0’)
+     • In the first argument of ‘App’, namely ‘(liftToExp x)’
+       In the expression: App (liftToExp x)
+       In an equation for ‘test’: test x = App (liftToExp x)
@@ -42,4 +47,0 @@
-
- Tested with GHC 6.6 (compiler and interpreter) under OS X 10.4.8 on an
- iMac G5.
-

New description:

 {{{#!hs
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE AllowAmbiguousTypes #-}

 module Main where

 data Exp a where
     Val :: a -> Exp b
     App :: Exp a -> Exp b

 instance Show (Exp a) where
     show (Val _) = "Val"
     show (App _) = "App"

 class LiftToExp a b where
     liftToExp :: a -> Exp b

 instance LiftToExp (Exp a) a where
     liftToExp = id

 instance Floating a => LiftToExp a b where
     liftToExp v = Val v :: Exp b

 {-
 Uncommenting the type signature below causes GHCi to fail to load the
 file:

 Test.hs:48:15: error:
     • Overlapping instances for LiftToExp a a0
         arising from a use of ‘liftToExp’
       Matching givens (or their superclasses):
         LiftToExp a a1
           bound by the type signature for:
                      test :: LiftToExp a a1 => a -> Exp b
           at Test.hs:47:1-38
       Matching instances:
         instance LiftToExp a b -- Defined at Test.hs:22:10
         instance LiftToExp (Exp a) a -- Defined at Test.hs:19:10
       (The choice depends on the instantiation of ‘a, a0’)
     • In the first argument of ‘App’, namely ‘(liftToExp x)’
       In the expression: App (liftToExp x)
       In an equation for ‘test’: test x = App (liftToExp x)

 However typing :t test at the GHCi prompt gives this exact signature.
 -}

 --test :: (LiftToExp a a1) => a -> Exp b
 test x = App (liftToExp x)

 main = putStrLn $ show (test (3.0::Float)::Exp Int)

 }}}

--

Comment:

 This example now requires `AllowAmbiguousTypes` (ghc-8.0.1).

 Is this still considered to be a bug, or are people who enable
 `AllowAmbiguousTypes` "asking for it"?

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/1158#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list