[GHC] #13249: Default signature check can be quite onerous
GHC
ghc-devs at haskell.org
Thu Feb 9 06:05:06 UTC 2017
#13249: Default signature check can be quite onerous
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner:
Type: feature | Status: new
request |
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.1
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets: #12918
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The `bytes` library currently doesn't compile with GHC `master` due to the
new check of default signatures (7363d5380e600e2ef868a069d5df6857d9e5c17e,
#12918). Consider this example,
{{{#!hs
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DefaultSignatures #-}
module Hi where
import Control.Monad.Trans.Class
class MonadGet m where
type Remaining m :: *
remaining :: m (Remaining m)
default remaining :: (MonadTrans t, MonadGet n, m ~ t n) => m (Remaining
(t m))
remaining = lift remaining
}}}
Patching this up requires a fair amount of hand-holding,
{{{#!hs
default remaining :: (MonadTrans t, MonadGet n, m ~ t n, Remaining m ~
Remaining n, Monad n) => m (Remaining m)
}}}
Yuck.
I suppose this is just how the world works, but I thought I'd leave this
here in case anyone had a clever idea for improvement.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13249>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list