[GHC] #8634: Relax functional dependency coherence check ("liberal coverage condition")

GHC ghc-devs at haskell.org
Mon Jul 21 22:13:48 UTC 2014


#8634: Relax functional dependency coherence check ("liberal coverage condition")
-------------------------------------+-------------------------------------
              Reporter:  danilo2     |             Owner:
                  Type:  feature     |            Status:  new
  request                            |         Milestone:  7.10.1
              Priority:  high        |           Version:  7.7
             Component:  Compiler    |          Keywords:
            Resolution:              |  Operating System:  Unknown/Multiple
Differential Revisions:  Phab:D69    |   Type of failure:  None/Unknown
          Architecture:              |         Test Case:
  Unknown/Multiple                   |          Blocking:
            Difficulty:  Unknown     |
            Blocked By:              |
       Related Tickets:  #1241,      |
  #2247, #8356, #9103, #9227         |
-------------------------------------+-------------------------------------

Comment (by danilo2):

 @emertens: I know it really well, it would not work - look at this
 example:

 {{{#!haskell
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}

 class Property a b where
    property :: a -> b

 data X = X
 data Y = Y deriving Show
 data Z = Z deriving Show

 instance (y ~ Y) => Property X y where
     property _ = Y

 instance (z ~ Z) => Property Y z where
     property _ = Z

 tst a = property $ property a

 main = do
     print (property $ property X)
 }}}

 Error:
 {{{#!haskell
     Could not deduce (Property s0 b)
       arising from the ambiguity check for ‘tst’
     from the context (Property a s, Property s b)
       bound by the inferred type for ‘tst’:
                  (Property a s, Property s b) => a -> b
       at Tmp.hs:21:1-29
     The type variable ‘s0’ is ambiguous
     When checking that ‘tst’ has the inferred type
       tst :: forall b s a. (Property a s, Property s b) => a -> b
     Probable cause: the inferred type is ambiguous
 }}}

 It will work for simple examples but will fail for functions like `tst` -
 it's caused by open world assumption - you never knows if there will be
 another instance defined, which will be more precise than already defined
 (with `-XOverlappingInstances` enabled). The only way around is to use
 fundeps here :)

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


More information about the ghc-tickets mailing list