[GHC] #12797: Default Rules stop working when providing some constraints

GHC ghc-devs at haskell.org
Wed Nov 2 02:49:02 UTC 2016


#12797: Default Rules stop working when providing some constraints
-------------------------------------+-------------------------------------
        Reporter:  danilo2           |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  GHC rejects       |  Unknown/Multiple
  valid program                      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by danilo2:

@@ -7,1 +7,0 @@
- {-# LANGUAGE OverloadedStrings         #-}
@@ -21,1 +20,1 @@
-     liftIO $ print "tst"
+     liftIO $ print 6
@@ -25,1 +24,1 @@
-     liftIO $ print "tst"
+     liftIO $ print 6
@@ -34,0 +33,1 @@
+
@@ -46,1 +46,1 @@
-         ...plus 7 instances involving out-of-scope types
+         ...plus six instances involving out-of-scope types
@@ -48,3 +48,3 @@
-     • In the second argument of ‘($)’, namely ‘print "tst"’
-       In a stmt of a 'do' block: liftIO $ print "tst"
-       In the expression: do { liftIO $ print "tst" }
+     • In the second argument of ‘($)’, namely ‘print 6’
+       In a stmt of a 'do' block: liftIO $ print 6
+       In the expression: do { liftIO $ print 6 }
@@ -53,2 +53,1 @@
-     • Could not deduce (Data.String.IsString a0)
-         arising from the literal ‘"tst"’
+     • Could not deduce (Num a0) arising from the literal ‘6’
@@ -61,3 +60,4 @@
-         instance a ~ Char => Data.String.IsString [a]
-           -- Defined in ‘Data.String’
-         ...plus one instance involving out-of-scope types
+         instance Num Integer -- Defined in ‘GHC.Num’
+         instance Num Double -- Defined in ‘GHC.Float’
+         instance Num Float -- Defined in ‘GHC.Float’
+         ...plus two others
@@ -65,3 +65,3 @@
-     • In the first argument of ‘print’, namely ‘"tst"’
-       In the second argument of ‘($)’, namely ‘print "tst"’
-       In a stmt of a 'do' block: liftIO $ print "tst"
+     • In the first argument of ‘print’, namely ‘6’
+       In the second argument of ‘($)’, namely ‘print 6’
+       In a stmt of a 'do' block: liftIO $ print 6
@@ -71,1 +71,1 @@
- Giving explicit types to String literals fixes the problem.
+ Giving explicit types to literals fixes the problem.

New description:

 I've just found a very strange behavior. Let's consider following program:

 {{{
 {-# LANGUAGE NoMonomorphismRestriction #-}
 {-# LANGUAGE TypeFamilies              #-}
 {-# LANGUAGE ExtendedDefaultRules      #-}

 module Main where

 import Prelude
 import Control.Monad.IO.Class


 type family FuncArg m where
     FuncArg ((->) t) = 'Just t
     FuncArg m        = 'Nothing

 test1 :: (MonadIO m) => m ()
 test1 = do
     liftIO $ print 6

 test2 :: (MonadIO m, FuncArg m ~ 'Nothing) => m ()
 test2 = do
     liftIO $ print 6

 main :: IO ()
 main = return ()
 }}}

 The function `tst1` compiles fine, while `tst2` fails:

 {{{

 exe/Main.hs:21:14: error:
     • Could not deduce (Show a0) arising from a use of ‘print’
       from the context: (MonadIO m, FuncArg m ~ 'Nothing)
         bound by the type signature for:
                    tst2 :: (MonadIO m, FuncArg m ~ 'Nothing) => m ()
         at exe/Main.hs:19:1-49
       The type variable ‘a0’ is ambiguous
       These potential instances exist:
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show Integer -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
         ...plus 22 others
         ...plus six instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the second argument of ‘($)’, namely ‘print 6’
       In a stmt of a 'do' block: liftIO $ print 6
       In the expression: do { liftIO $ print 6 }

 exe/Main.hs:21:20: error:
     • Could not deduce (Num a0) arising from the literal ‘6’
       from the context: (MonadIO m, FuncArg m ~ 'Nothing)
         bound by the type signature for:
                    tst2 :: (MonadIO m, FuncArg m ~ 'Nothing) => m ()
         at exe/Main.hs:19:1-49
       The type variable ‘a0’ is ambiguous
       These potential instances exist:
         instance Num Integer -- Defined in ‘GHC.Num’
         instance Num Double -- Defined in ‘GHC.Float’
         instance Num Float -- Defined in ‘GHC.Float’
         ...plus two others
         (use -fprint-potential-instances to see them all)
     • In the first argument of ‘print’, namely ‘6’
       In the second argument of ‘($)’, namely ‘print 6’
       In a stmt of a 'do' block: liftIO $ print 6

 }}}

 Giving explicit types to literals fixes the problem.

--

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


More information about the ghc-tickets mailing list