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

GHC ghc-devs at haskell.org
Wed Nov 2 02:47:17 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
           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:
-------------------------------------+-------------------------------------
 I've just found a very strange behavior. Let's consider following program:

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

 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 "tst"

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

 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 7 instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • 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" }

 exe/Main.hs:21:20: error:
     • Could not deduce (Data.String.IsString a0)
         arising from the literal ‘"tst"’
       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 a ~ Char => Data.String.IsString [a]
           -- Defined in ‘Data.String’
         ...plus one instance involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • 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"

 }}}

 Giving explicit types to String literals fixes the problem.

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


More information about the ghc-tickets mailing list