
#12885: "too many iterations" causes constraint solving issue. -------------------------------------+------------------------------------- Reporter: judahj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2-rc1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following file compiled fine with ghc-7.10, but fails in ghc-8.0.2-rc1 (as well as ghc-8.0.1). This is a simplified version of a compilation issue with ghc-8 and https://github.com/tensorflow/haskell. It seems similar to #12175, but even though that was fixed in ghc-8.0.2-rc1, the below code still doesn't compile. {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module ConstraintTest where import Data.Int import Data.Word import GHC.Exts (Constraint) import Lens.Family2 ((.~), (&), Lens') import Lens.Family2.Unchecked (lens) class MyType a where instance MyType Int8 instance MyType Int16 instance MyType Int32 instance MyType Int64 instance MyType Word8 instance MyType Word16 instance MyType Word32 -- Require every element in the list to be an instance of 'MyType'. type family MyTypes (as :: [*]) :: Constraint where MyTypes '[] = () MyTypes (a ': as) = (MyType a, MyTypes as) data Foo = Foo { fooInt :: Int } class Attr a where attr :: Lens' Foo a instance Attr Int where attr = lens fooInt (\f n -> f { fooInt = n }) test :: MyTypes '[Int8,Int16,Int32,Int64,Word8,Word16,Word32] => Foo test = attr .~ (3 :: Int) $ Foo 0 }}} Compilation error: {{{ tensorflow/tests/ConstraintTest.hs:1:1: error: solveWanteds: too many iterations (limit = 4) Unsolved: WC {wc_simple = [W] hole{a282} :: b_a25A ~ Int (CNonCanonical)} New superclasses found Set limit with -fconstraint-solver-iterations=n; n=0 for no limit }}} Some ways to change the test to make the compilation succeed: - Pass "-fconstraint-solver-iterations=0" to ghc. - Shorten the type-level list in the constraint of `test`. - Replace `Lens.Family2` with `Lens.Micro` from the `microlens` package. I think this is because `Lens.Family2`'s version of (.~) is higher-order than `Lens.Micro`: https://hackage.haskell.org/package/lens-family-1.2.1/docs/Lens- Family2.html#v:.-126- https://hackage.haskell.org/package/microlens-0.4.7.0/docs/Lens- Micro.html#v:.-126- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12885 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler