
#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): Replying to [comment:37 rwbarton]: It still would not work: 1) the following script does not compile 2) I DO want to determine the output type based on the input types - I really want to introduce there fundep. I mean - I want to be able to write `tst a = property (property a)` and use it as `tst X` and get `Z` as the result. Additional - this is only one of the exampels we are using the extension. There are some other places where it works quite well. I do not know if here is the best place to discuss possible workarounds (but I'm very happy and thankfull to hear suggestions)? Anyway, I post the code I mentioned above: {{{#!haskell {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE AllowAmbiguousTypes #-} 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 :: forall a s b. (Property a s, Property s b) => a -> b tst a = property (property a :: s) main = do print (property $ property X) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8634#comment:38 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler