#4953: panic: urk! lookup local fingerprint main:B.throwErr{v rR3}
---------------------------------+------------------------------------------
Reporter: igloo | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 7.0.2
Component: Compiler | Version: 7.0.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by igloo):
I've cut it down a bit more, and added some debugging info to the
compiler. `B.hs` and some debugging output from `addFingerprints` (related
to the `edges` calculation) is below.
Note that `joinI` mentions `throwErr`, but only in the nested unfolding of
the let binding. It looks like GHC thus doesn't realise that `joinI`
depends on `throwErr`, I'd guess due to `freeNamesIfLetBndr`; is this
comment right?:
{{{
freeNamesIfLetBndr :: IfaceLetBndr -> NameSet
-- Remember IfaceLetBndr is used only for *nested* bindings
-- The cut-down IdInfo never contains any Names, but the type may!
freeNamesIfLetBndr (IfLetBndr _name ty _info) = freeNamesIfType ty
}}}
{{{
module B (throwErr, joinI) where
import A
import Control.Exception
import Data.Maybe
excDivergent :: SomeException
excDivergent = undefined
throwErr :: (Monad m) => SomeException -> Iteratee s m a
throwErr e = icont (const (throwErr e)) (Just e)
joinI ::
(Monad m, Nullable s) =>
Iteratee s m (Iteratee s' m a)
-> Iteratee s m a
joinI = (>>=
\inner -> Iteratee $ \od oc ->
let on_cont k Nothing = runIter (k EOF) undefined f
on_cont _ (Just e) = runIter (throwErr e) od oc
f _ e = runIter (throwErr (fromMaybe excDivergent e)) od oc
in runIter inner undefined on_cont)
}}}
{{{
((main:B,
throwErr :: forall (m::* -> *) s a.
GHC.Base.Monad m =>
GHC.Exception.SomeException -> A.Iteratee s m a
{- Arity: 2, HasNoCafRefs, Strictness: AL, Inline: INLINE[0],
Unfolding: Worker(ext0: B.$wthrowErr (arity 2) -},
infixl 9),
throwErr,
[(28, GHC.Base.Monad), (rd, GHC.Exception.SomeException),
(rE, A.Iteratee), (rrE, B.$wthrowErr)],
([(28, GHC.Base.Monad), (rd, GHC.Exception.SomeException),
(rE, A.Iteratee)],
[(rrE, B.$wthrowErr)],
[],
[]),
[$wthrowErr])
((main:B,
joinI :: forall (m::* -> *) s s' a.
(GHC.Base.Monad m, A.Nullable s) =>
A.Iteratee s m (A.Iteratee s' m a) -> A.Iteratee s m a
{- Arity: 3, Strictness: LLL,
Unfolding: (\ @ (m::* -> *)
@ s
@ s'
@ a
$dMonad :: GHC.Base.Monad m
$dNullable :: A.Nullable s
eta :: A.Iteratee s m (A.Iteratee s' m a) ->
A.$fMonadIteratee_$c>>=
@ m
@ s
$dMonad
$dNullable
@ (A.Iteratee s' m a)
@ a
eta
(\ inner :: A.Iteratee s' m a
@ r
od :: a -> A.Stream s -> m r
oc :: (A.Stream s -> A.Iteratee s m a)
-> Data.Maybe.Maybe
GHC.Exception.SomeException
-> m r ->
inner `cast` (A.NTCo:Iteratee s' m a)
@ r
(GHC.Err.undefined @ (a -> A.Stream s' -> m r))
(let {
f :: forall t.
t -> Data.Maybe.Maybe
GHC.Exception.SomeException -> m r
{- Arity: 2, Strictness: AL,
Unfolding: InlineRule (2, True, False)
(\ @ t
ds :: t
e :: Data.Maybe.Maybe
GHC.Exception.SomeException ->
(B.throwErr
@ m
@ s
@ a
$dMonad
(case @
GHC.Exception.SomeException e of wild {
Data.Maybe.Nothing
-> GHC.Err.undefined @
GHC.Exception.SomeException
Data.Maybe.Just v -> v
}))
`cast`
(A.NTCo:Iteratee s m a)
@ r
od
oc) -}
= \ @ t
ds :: t
e :: Data.Maybe.Maybe
GHC.Exception.SomeException ->
B.$wthrowErr
@ m
@ s
@ a
(case @ GHC.Exception.SomeException e of
wild {
Data.Maybe.Nothing
-> GHC.Err.undefined @
GHC.Exception.SomeException
Data.Maybe.Just v -> v })
@ r
od
oc
} in
\ k :: A.Stream s' -> A.Iteratee s' m a
ds :: Data.Maybe.Maybe
GHC.Exception.SomeException ->
case @ (m r) ds of wild {
Data.Maybe.Nothing
-> (k (A.EOF @ s')) `cast` (A.NTCo:Iteratee s'
m a)
@ r
(GHC.Err.undefined @ (a -> A.Stream s' ->
m r))
(f @ (A.Stream s' -> A.Iteratee s' m a))
Data.Maybe.Just e -> B.$wthrowErr @ m @ s @ a e
@ r od oc }))
`cast`
(A.Iteratee s' m a -> sym (A.NTCo:Iteratee s m a)))
-},
infixl 9),
joinI,
[(28, GHC.Base.Monad), (34v, sym), (r8, A.NTCo:Iteratee),
(rd, GHC.Exception.SomeException), (re, Data.Maybe.Maybe),
(rx, A.Stream), (ry, GHC.Err.undefined),
(rD, A.$fMonadIteratee_$c>>=), (rE, A.Iteratee), (rF, A.Nullable),
(rH, Data.Maybe.Nothing), (rdR, A.EOF), (rrE, B.$wthrowErr)],
([(28, GHC.Base.Monad), (rE, A.Iteratee), (rF, A.Nullable)],
[(28, GHC.Base.Monad), (34v, sym), (r8, A.NTCo:Iteratee),
(rd, GHC.Exception.SomeException), (re, Data.Maybe.Maybe),
(rx, A.Stream), (ry, GHC.Err.undefined),
(rD, A.$fMonadIteratee_$c>>=), (rE, A.Iteratee), (rF, A.Nullable),
(rH, Data.Maybe.Nothing), (rdR, A.EOF), (rrE, B.$wthrowErr)],
[],
[]),
[$wthrowErr])
((main:B,
$wthrowErr :: forall (m::* -> *) s a.
GHC.Exception.SomeException
-> forall r.
(a -> A.Stream s -> m r)
-> ((A.Stream s -> A.Iteratee s m a)
-> Data.Maybe.Maybe GHC.Exception.SomeException
-> m r)
-> m r
{- Arity: 1, HasNoCafRefs, Strictness: L -},
infixl 9),
$wthrowErr,
[(rd, GHC.Exception.SomeException), (re, Data.Maybe.Maybe),
(rx, A.Stream), (rE, A.Iteratee)],
([(rd, GHC.Exception.SomeException), (re, Data.Maybe.Maybe),
(rx, A.Stream), (rE, A.Iteratee)],
[],
[],
[]),
[])
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4953#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs