[GHC] #11379: New superclass solver fails to compile

#11379: New superclass solver fails to compile -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This example (derived from `xmonad-contrib`) failed to compile with `master`, {{{#!hs {-# LANGUAGE ExistentialQuantification, RankNTypes, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, FlexibleContexts #-} module XMonad.Layout.MultiToggle where import Data.Typeable -- This appears to be the culprit expand :: (HList ts a) => MultiToggleS ts l a -> MultiToggle ts l a expand (MultiToggleS b ts) = resolve ts id (\x mt -> let g = transform' x in mt{ currLayout = g $ currLayout mt }) (MultiToggle (EL b id) ts) class (Typeable t) => Transformer t a | t -> a where transform :: t -> l a -> (forall l'. l' a -> (l' a -> l a) -> b) -> b data EL l a = forall l'. EL (l' a) (l' a -> l a) transform' :: (Transformer t a) => t -> EL l a -> EL l a transform' t (EL l det) = undefined data MultiToggleS ts l a = MultiToggleS (l a) ts deriving (Read, Show) data MultiToggle ts l a = MultiToggle{ currLayout :: EL l a, transformers :: ts } class HList c a where resolve :: c -> b -> (forall t. (Transformer t a) => t -> b) -> b }}} failing during constraint solving with,, {{{ XMonad/Layout/MultiToggle.hs:1:1: error: solveWanteds: too many iterations (limit = 4) Unsolved: WC {wc_simple = [D] _ :: Transformer t a (CDictCan) [D] _ :: a_aIoy ~ a (CNonCanonical) [D] _ :: Typeable t (CDictCan) wc_impl = Implic { TcLevel = 7 Skolems = (l :: * -> *) No-eqs = True Status = Unsolved Given = Wanted = WC {wc_simple = [W] $dTransformer_aIoM :: Transformer t a (CDictCan)} Binds = Just EvBindsVar<aIoN> the inferred type of g :: EL l_aIoL a_aIoK -> EL l_aIoL a_aIoK }} New superclasses found Set limit with -fconstraint-solver-iterations=n; n=0 for no limit }}} Lifting the solver iteration limit just results in a loop. I suspect the issue may be in the `Typeable` solving logic, as removing the `Typable` constraint from `Transformer`'s head allows compilation to proceed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11379 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11379: Solver hits iteration limit in code without recursive constraints -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11379#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11379: Solver hits iteration limit in code without recursive constraints -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: Old description:
This example (derived from `xmonad-contrib`) failed to compile with `master`,
{{{#!hs {-# LANGUAGE ExistentialQuantification, RankNTypes, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, FlexibleContexts #-}
module XMonad.Layout.MultiToggle where
import Data.Typeable
-- This appears to be the culprit expand :: (HList ts a) => MultiToggleS ts l a -> MultiToggle ts l a expand (MultiToggleS b ts) = resolve ts id (\x mt -> let g = transform' x in mt{ currLayout = g $ currLayout mt }) (MultiToggle (EL b id) ts)
class (Typeable t) => Transformer t a | t -> a where transform :: t -> l a -> (forall l'. l' a -> (l' a -> l a) -> b) -> b
data EL l a = forall l'. EL (l' a) (l' a -> l a)
transform' :: (Transformer t a) => t -> EL l a -> EL l a transform' t (EL l det) = undefined
data MultiToggleS ts l a = MultiToggleS (l a) ts deriving (Read, Show)
data MultiToggle ts l a = MultiToggle{ currLayout :: EL l a, transformers :: ts }
class HList c a where resolve :: c -> b -> (forall t. (Transformer t a) => t -> b) -> b }}}
failing during constraint solving with,,
{{{ XMonad/Layout/MultiToggle.hs:1:1: error: solveWanteds: too many iterations (limit = 4) Unsolved: WC {wc_simple = [D] _ :: Transformer t a (CDictCan) [D] _ :: a_aIoy ~ a (CNonCanonical) [D] _ :: Typeable t (CDictCan) wc_impl = Implic { TcLevel = 7 Skolems = (l :: * -> *) No-eqs = True Status = Unsolved Given = Wanted = WC {wc_simple = [W] $dTransformer_aIoM :: Transformer t a (CDictCan)} Binds = Just EvBindsVar<aIoN> the inferred type of g :: EL l_aIoL a_aIoK -> EL l_aIoL a_aIoK }} New superclasses found Set limit with -fconstraint-solver-iterations=n; n=0 for no limit }}}
Lifting the solver iteration limit just results in a loop.
I suspect the issue may be in the `Typeable` solving logic, as removing the `Typable` constraint from `Transformer`'s head allows compilation to proceed.
New description: This example (derived from `xmonad-contrib`) failed to compile with `master`, {{{#!hs {-# LANGUAGE ExistentialQuantification, RankNTypes, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, FlexibleContexts #-} module XMonad.Layout.MultiToggle where import Data.Typeable -- This appears to be the culprit expand :: (HList ts a) => MultiToggleS ts l a -> MultiToggle ts l a expand (MultiToggleS b ts) = resolve ts id (\x mt -> let g = transform' x in mt{ currLayout = g $ currLayout mt }) (MultiToggle (EL b id) ts) -- Removing the Typeable constraint here allows compilation to finish class (Typeable t) => Transformer t a | t -> a where transform :: t -> l a -> (forall l'. l' a -> (l' a -> l a) -> b) -> b data EL l a = forall l'. EL (l' a) (l' a -> l a) transform' :: (Transformer t a) => t -> EL l a -> EL l a transform' t (EL l det) = undefined data MultiToggleS ts l a = MultiToggleS (l a) ts deriving (Read, Show) data MultiToggle ts l a = MultiToggle{ currLayout :: EL l a, transformers :: ts } class HList c a where resolve :: c -> b -> (forall t. (Transformer t a) => t -> b) -> b }}} failing during constraint solving with,, {{{ XMonad/Layout/MultiToggle.hs:1:1: error: solveWanteds: too many iterations (limit = 4) Unsolved: WC {wc_simple = [D] _ :: Transformer t a (CDictCan) [D] _ :: a_aIoy ~ a (CNonCanonical) [D] _ :: Typeable t (CDictCan) wc_impl = Implic { TcLevel = 7 Skolems = (l :: * -> *) No-eqs = True Status = Unsolved Given = Wanted = WC {wc_simple = [W] $dTransformer_aIoM :: Transformer t a (CDictCan)} Binds = Just EvBindsVar<aIoN> the inferred type of g :: EL l_aIoL a_aIoK -> EL l_aIoL a_aIoK }} New superclasses found Set limit with -fconstraint-solver-iterations=n; n=0 for no limit }}} Lifting the solver iteration limit just results in a loop. I suspect the issue may be in the `Typeable` solving logic, as removing the `Typable` constraint from `Transformer`'s head allows compilation to proceed. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11379#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11379: Solver hits iteration limit in code without recursive constraints -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hvr): * cc: hvr, simonpj (added) * component: Compiler => Compiler (Type checker) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11379#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11379: Solver hits iteration limit in code without recursive constraints -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonpj Comment: I'm on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11379#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11379: Solver hits iteration limit in code without recursive constraints -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by slyfox): * cc: slyfox (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11379#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11379: Solver hits iteration limit in code without recursive constraints
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner: simonpj
Type: bug | Status: merge
Priority: highest | Milestone: 8.0.1
Component: Compiler (Type | Version: 8.0.1-rc1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by simonpj):
* status: new => merge
Comment:
Actually this ticket #11is fixed by the following commit. I forgot to
mention it in the list of fixes in the commit message. The important bit
of the patch for #11379 is the new function `TcSMonad.mkShadowCt`,
explained by `Note [Keep CDictCan shadows as CDictCan]`.
Let's merge this.
{{{
commit 9308c736d43b92bf8634babf565048e66e071bd8
Author: Simon Peyton Jones

#11379: Solver hits iteration limit in code without recursive constraints
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner: simonpj
Type: bug | Status: merge
Priority: highest | Milestone: 8.0.1
Component: Compiler (Type | Version: 8.0.1-rc1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#11379: Solver hits iteration limit in code without recursive constraints -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: This was merged to `ghc-8.0` as 9f466c8841c7ddda84951c9e3470540d25d0bfdb. The test will be merged shortly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11379#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11379: Solver hits iteration limit in code without recursive constraints -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by NeilMitchell): * cc: ndmitchell (added) Comment: For info, I found a similar bug while trying Shake with GHC 8.0-rc1 provided by hvr (8.0.0.20160111+git.0.497454f). Chopping out the relevant bit leaves: {{{#!hs -- optIntArg :: (Ord a0, Read a0, Show a0) => a0 -> [Char] -> t0 -> (Maybe a0 -> t2) -> Maybe String -> Either [Char] ([t1], t2) optIntArg mn flag a f = maybe (Right ([], f Nothing)) $ \x -> case reads x of [(i,"")] | i >= mn -> Right ([],f $ Just i) _ -> Left $ "the `--" ++ flag ++ "' option requires a number, " ++ show mn ++ " or above" }}} Uncommenting the type signature makes it work. Without, it fails with: {{{ solveWanteds: too many iterations (limit = 4) Unsolved: WC {wc_simple = [D] _ :: Eq a (CDictCan) [D] _ :: Ord a (CDictCan) [D] _ :: Read a (CDictCan) [D] _ :: Show a (CDictCan) [W] hole{a5xW} :: a ~ a (CNonCanonical) [D] _ :: Eq a (CDictCan)} New superclasses found Set limit with -fconstraint-solver-iterations=n; n=0 for no limit] }}} Given the size of the code fragment that triggers it, and the fact a number of bugs were found, this might be another useful test case. Tweaking to give: {{{#!hs optIntArg mn flag a f = maybe (Right ([], f Nothing)) $ \x -> case reads x of [(i,"")] | i == mn -> Right ([],f $ Just i) _ -> Left $ "the `--" ++ flag ++ "' option requires a number, or above" }}} I end up with a very different error: {{{ src\Demo.hs:5:41: error: * Couldn't match type `a' with `a1' because type variable `a1' would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: Maybe a1 at src\Demo.hs:5:37-46 Expected type: Maybe a1 Actual type: Maybe a }}} This code compiles fine with GHC 7.10, so seems like a different bug, or different manifestation of the same bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11379#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11379: Solver hits iteration limit in code without recursive constraints -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Neil, thank you. You have found a much more serious and quite unrelated bug, which I've created as #11458. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11379#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC