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

GHC ghc-devs at haskell.org
Mon Jul 21 20:24:01 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 emertens):

 Instead of using "dysfunctional" dependencies, the above programs can be
 written in GHC today as shown below. This pattern actually happens in the
 wild regularly and takes advantage of the way GHC resolves instances.

 {{{
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FlexibleInstances #-}

 {-# LANGUAGE UndecidableInstances #-}

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

 data X = X
 data Y = Y deriving Show

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

 instance (Monad m, m Int ~ y) => Property Y y where
     property _ = return 5

 main = do
     print =<< property Y
     print (property Y :: [Int])
     print (property X)
 }}}

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


More information about the ghc-tickets mailing list