[GHC] #10844: CallStack should not be inlined

GHC ghc-devs at haskell.org
Mon Sep 7 08:53:08 UTC 2015


#10844: CallStack should not be inlined
-------------------------------------+-------------------------------------
        Reporter:  nomeata           |                   Owner:  gridaphobe
            Type:  task              |                  Status:  new
        Priority:  normal            |               Milestone:
       Component:  Compiler          |                 Version:  7.10.2
      Resolution:                    |                Keywords:
Operating System:  Unknown/Multiple  |            Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |               Test Case:
      Blocked By:                    |                Blocking:
 Related Tickets:                    |  Differential Revisions:
-------------------------------------+-------------------------------------

Comment (by nomeata):

 The source causing the above inlining of a CallStack looks like this:

 {{{#!hs
 instance Prim a => G.MVector MVector a where
   {-# INLINE basicUnsafeNew #-}
   basicUnsafeNew n
     | n < 0 = error $ "Primitive.basicUnsafeNew: negative length: " ++
 show n
     | n > mx = error $ "Primitive.basicUnsafeNew: length to large: " ++
 show n
     | otherwise = MVector 0 n `liftM` newByteArray (n * size)
     where
       size = sizeOf (undefined :: a)
       mx = maxBound `div` size :: Int
 }}}
 It is not surprising to me that an `error` in an INLINE function causes
 the CallStack to be inlined (although still rather pointless).

 You can reproduce this, if you have vector installed, by compiling the
 example program given in #10788.

 I tried to reproduce this with two smaller modules, i.e.
 {{{#!hs
 ==> T10844a.hs <==
 module T10844a where

 foo :: Int -> Int
 foo 0 = error "foo"
 foo n = n
 {-# INLINE foo #-}


 ==> T10844.hs <==
 module T10844 where

 import T10844a

 n :: Int
 n = 0
 {-# NOINLINE n #-}

 main = print (foo n)
 }}}
 but it did *not* show this behavior. But when I change the first module to

 {{{#!hs
 module T10844a where

 class Foo a where foo :: a -> a

 instance Foo Int where
     foo 0 = error "foo"
     foo n = n
     {-# INLINE foo #-}
 }}}
 then `T10844` will contain a `CallStack` referencing a source location in
 `T10844a`

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


More information about the ghc-tickets mailing list