[GHC] #12202: GHC 7.10.3 throws away callstack frames for outer

GHC ghc-devs at haskell.org
Fri Jun 17 09:03:35 UTC 2016


#12202: GHC 7.10.3 throws away callstack frames for outer
-------------------------------------+-------------------------------------
           Reporter:  bgamari        |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  7.10.3
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Incorrect result
  Unknown/Multiple                   |  at runtime
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 It was noticed that GHC 7.10.3 sometimes drops outer callers from IP
 callstacks. For instance,

 {{{#!hs
 {-# LANGUAGE ImplicitParams #-}

 import GHC.Stack
 import Control.Monad.Catch

 newtype MyError = MyError CallStack
 instance Exception MyError

 instance Show MyError where
     show (MyError e) = show e

 fromEvents :: (MonadThrow m, ?loc :: CallStack) => m (Maybe Int)
 fromEvents = do
     Just <$> require 42
   where
     -- require :: (MonadThrow m, ?loc :: CallStack) => Int -> m Int
     require n                               -- line 17
       | even n = throwM $ MyError ?loc
       | otherwise = return n


 main = do
     putStrLn "Hello world"
     fromEvents                              -- line 24
 }}}


 GHC 8.0.1 produces the correct output,
 {{{
 $ ./Hi
 Hello world
 Hi: [("fromEvents",SrcLoc {srcLocPackage = "main", srcLocModule = "Main",
 srcLocFile = "Hi.hs", srcLocStartLine = 24, srcLocStartCol = 5,
 srcLocEndLine = 24, srcLocEndCol = 15})]
 }}}

 GHC 7.10.3 produces only one
 {{{#!hs
 $ ./Hi
 Hello world
 Hi: CallStack {getCallStack = [("?loc",SrcLoc {srcLocPackage = "main",
 srcLocModule = "Main", srcLocFile = "Hi.hs", srcLocStartLine = 17,
 srcLocStartCol = 35, srcLocEndLine = 17, srcLocEndCol = 39})]}
 }}}

 Uncommenting the type signature for `require` however results in more-or-
 less the expected callstack with 7.10.3,
 {{{#!hs
 $ ./Hi
 Hello world
 Hi: CallStack {getCallStack = [("?loc",SrcLoc {srcLocPackage = "main",
 srcLocModule = "Main", srcLocFile = "Hi.hs", srcLocStartLine = 18,
 srcLocStartCol = 35, srcLocEndLine = 18, srcLocEndCol =
 39}),("require",SrcLoc {srcLocPackage = "main", srcLocModule = "Main",
 srcLocFile = "Hi.hs", srcLocStartLine = 14, srcLocStartCol = 14,
 srcLocEndLine = 14, srcLocEndCol = 21}),("fromEvents",SrcLoc
 {srcLocPackage = "main", srcLocModule = "Main", srcLocFile = "Hi.hs",
 srcLocStartLine = 24, srcLocStartCol = 5, srcLocEndLine = 24, srcLocEndCol
 = 15})]}
 }}}

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


More information about the ghc-tickets mailing list