Default Rules stop working when providing some constraints
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.
Edited by danilo2