[GHC] #8062: Panic "Lookup local fingerprint main:Main.main{v r6xE}"
GHC
ghc-devs at haskell.org
Tue Jul 16 19:53:16 CEST 2013
#8062: Panic "Lookup local fingerprint main:Main.main{v r6xE}"
---------------------------------+------------------------------------
Reporter: tommd | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Resolution: fixed | Keywords:
Operating System: Linux | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
---------------------------------+------------------------------------
Changes (by tommd):
* status: new => closed
* resolution: => fixed
Comment:
This is fixed in head, though the error message is a bit odd. For the
curious, a working example is:
{{{
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeFamilies #-}
main = do
bench bar :: IO Int
return ()
-- Run the monad, applying the value
bench :: Pr c -> IO c
bench = undefined
-- Protocol monad
newtype Pr a = Pr a
-- Shared
newtype Cont a = Cont a
type family S (m :: * -> *) :: * -> *
type instance S Pr = Cont
bar :: Pr (S Pr a)
bar = undefined
}}}
I'll close the ticket now. Thanks to emertens for working to build the
example and test HEAD.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8062#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list