[GHC] #13264: GHC panic with (->) generalization branch while compiling lens
GHC
ghc-devs at haskell.org
Fri Feb 10 19:59:16 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: |
-------------------------------------+-------------------------------------
Comment (by bgamari):
Here is a standalone reproducer,
{{{#!hs
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Control.Lens.Traversal where
import Control.Category
import Prelude hiding ((.),id)
type Over p f s t a b = p a (f b) -> s -> f t
newtype Bazaar p a b t = Bazaar { runBazaar :: forall f. Applicative f =>
p a (f b) -> f t }
newtype Pretext p a b t = Pretext { runPretext :: forall f. Functor f => p
a (f b) -> f t }
newtype Tagged s b = Tagged { unTagged :: b }
class Conjoined p where
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
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13264#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list