
#14863: QuantifiedConstraints: Can't deduce `c' from `(a, b)' and `a |- b |- c' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Once again, I think this `:-` thing is a red herring. Here's what I believe to be the essence of the bug: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ImpredicativeTypes #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE UndecidableInstances #-} module Bug where data Dict c where Dict :: c => Dict c class (a => b) => Implies a b instance (a => b) => Implies a b uncurryCImpredic1 :: forall a b c. Implies a (b => c) => Dict (Implies (a, b) c) uncurryCImpredic1 = Dict uncurryCImpredic2 :: forall a b c. a => Implies b c => Dict (Implies (a, b) c) uncurryCImpredic2 = Dict uncurryC1 :: forall a b c. (a => b => c) => Dict (Implies (a, b) c) uncurryC1 = Dict uncurryC2 :: forall a b c. Implies a (Implies b c) => Dict (Implies (a, b) c) uncurryC2 = Dict }}} {{{ $ ghc-cq/inplace/bin/ghc-stage2 --interactive Bug.hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:27:13: error: • Could not deduce: c arising from a use of ‘Dict’ from the context: Implies a (Implies b c) bound by the type signature for: uncurryC2 :: forall (a :: Constraint) (b :: Constraint) (c :: Constraint). Implies a (Implies b c) => Dict (Implies (a, b) c) at Bug.hs:26:1-77 or from: (a, b) bound by a quantified context at Bug.hs:1:1 • In the expression: Dict In an equation for ‘uncurryC2’: uncurryC2 = Dict • Relevant bindings include uncurryC2 :: Dict (Implies (a, b) c) (bound at Bug.hs:27:1) | 27 | uncurryC2 = Dict | ^^^^ }}} All of these `uncurryC`-functions typecheck except for `uncurryC2`. (Note that the first two require `ImpredicativeTypes`, so I'm not sure if this is intended to be supported or not.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14863#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler