[GHC] #13264: GHC panic with (->) generalization branch while compiling lens

GHC ghc-devs at haskell.org
Fri Feb 10 20:27:41 UTC 2017


#13264: GHC panic with (->) generalization branch while compiling lens
-------------------------------------+-------------------------------------
        Reporter:  bgamari           |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.2.1
       Component:  Compiler          |              Version:  8.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by bgamari:

@@ -40,49 +40,0 @@
-
- While I haven't yet fully reduced the reproducer to a standalone module,
- replacing `Control.Lens.Traversal` in a `lens` working tree is sufficient,
- {{{#!hs
- {-# LANGUAGE Rank2Types #-}
- {-# LANGUAGE FlexibleContexts #-}
- {-# LANGUAGE FlexibleInstances #-}
- {-# LANGUAGE ScopedTypeVariables #-}
-
- module Control.Lens.Traversal where
-
- import Control.Category
- import Control.Lens.Internal.Bazaar
- import Control.Lens.Internal.Context
- import Control.Lens.Internal.Indexed
- import Data.Tagged
- import Prelude hiding ((.),id)
-
- type Over p f s t a b = p a (f b) -> s -> f t
-
- holesOf :: forall p s t a. Conjoined p => Over p (Bazaar p a a) s t a a ->
- s -> [Pretext p a a t]
- holesOf l s = unTagged
-   ( conjoined
-      (Tagged $ let
-         f [] _ = []
-         f (x:xs) g = Pretext (\xfy -> g . (:xs) <$> xfy x) : f xs (g .
- (x:))
-       in f (ins b) (unsafeOuts b))
-      (Tagged $ let
-         f [] _ = []
-         f (wx:xs) g = Pretext (\wxfy -> g . (:Prelude.map extract xs) <$>
- cosieve wxfy wx) : f xs (g . (extract wx:))
-       in f (pins b) (unsafeOuts b))
-     :: Tagged (p a b) [Pretext p a a t]
-   ) where b = l sell s
- }}}
-
- More specifically,
- {{{
- $ git clone git://github.com/bgamari/hashable
- $ git clone git://github.com/ekmett/comonad
- $ git clone git://github.com/ekmett/semigroupoids
- $ git clone git://github.com/ekmett/lens
- $ cabal install ./comonad ./lens ./semigroupoids ./hashable --with-
- ghc=`pwd`/inplace/bin/ghc-stage2 --allow-newer=base,template-
- haskell,primitive,ghc-prim --disable-library-profiling -j1 --ghc-
- options='-v -ddump-to-file -ddump-tc-trace'
- }}}

New description:

 While testing characterizing the performance impact of the Typeable
 branch (`wip/ttypeable`) against Hackage packages I have found that `lens`
 manages to break the `(->)` kind-generalization patch. Specifically,
 `TcCanonical.can_eq_nc` induces a panic by `tcRepSplitTyApp_maybe` during
 compilation of `Control.Lens.Traversal.holesOf`,
 {{{
     ghc-stage2: panic! (the 'impossible' happened)
       (GHC version 8.1.20170207 for x86_64-unknown-linux):
       tcRepSplitTyConApp_maybe
       ([] |> <*>_N ->_N Sym {alzj}) a_alzd[tau:5]
       c_alzb[tau:5]
       Call stack:
           CallStack (from HasCallStack):
             prettyCurrentCallStack, called at
 compiler/utils/Outputable.hs:1188:58 in ghc:Outputable
             callStackDoc, called at compiler/utils/Outputable.hs:1192:37
 in ghc:Outputable
             pprPanic, called at compiler/typecheck/TcType.hs:1456:5 in
 ghc:TcType
             tcRepSplitTyConApp_maybe, called at
 compiler/typecheck/TcCanonical.hs:617:25 in ghc:TcCanonical
 }}}

 The last thing emitted by tc-trace is,
 {{{

     can_eq_nc
       False
       [WD] hole{alyP} {0}:: (p_alyn[tau:5] :: TYPE p_alym[tau:5])
                             GHC.Prim.~#
                             (cat_alyK[tau:6] b_alyM[tau:6] c_alyN[tau:6]
 :: *)
       nominal equality
       ([] |> <*>_N ->_N Sym {alzj}) a_alzd[tau:5] -> c_alzb[tau:5]
       p_alyn[tau:5]
       cat_alyK[tau:6] b_alyM[tau:6] c_alyN[tau:6]
       cat_alyK[tau:6] b_alyM[tau:6] c_alyN[tau:6]

 }}}

--

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


More information about the ghc-tickets mailing list