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

GHC ghc-devs at haskell.org
Mon Jul 21 16:04:49 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 diatchki):

 This program has the exact same problem as the one in the ticket above: it
 violates the functional dependency.  Having a "functional dependency"
 simply means that you are telling GHC that you want to work with a
 "functional relation (in the specified parameters)", and it should give
 you an error if you made a mistake.  Here is how you can rewrite your
 program without `Dysfunctional Dependencies`:

 {{{
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}

 data X = X

 class C a b where
   ctest :: a -> b

 class D a f b | a -> b where
   dtest :: a -> f b

 instance Monad m => D X m Int where
   dtest _ = return 5

 instance (Monad m) => C X (m Int) where
   ctest = dtest

 main = print (ctest X :: [Int]) -- [5]
 }}}



 Replying to [comment:19 danilo2]:
 > @diatchki please do not base your opinion on the examples above - they
 are a little old and of course, they do not obey some basic principles.
 > The idea with `-XDysfunctionalDependencies` is just to lift both the
 Paterson Conditions and the Coverage Condition - something
 `-XUndecidableInstances` claims  to do (according to documentation), but
 does not (as simonpj noticed above). When using this extension you can
 just give some interesting hints to typechecker and compile programs like
 the one I've posted on https://phabricator.haskell.org/D69 :
 >
 > {{{#!haskell
 > {-# LANGUAGE MultiParamTypeClasses #-}
 > {-# LANGUAGE FunctionalDependencies #-}
 > {-# LANGUAGE FlexibleInstances #-}
 > {-# LANGUAGE DysfunctionalDependencies #-}
 >
 > class CTest a b | a -> b where
 >    ctest :: a -> b
 >
 > data X = X
 >
 > instance Monad m => CTest X (m Int) where
 >
 > ctest _ = return 5
 >
 > main = print (ctest X :: [Int]) -- [5]
 > }}}

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


More information about the ghc-tickets mailing list