[GHC] #15500: internal error: Unable to commit 1048576 bytes of memory. Deepseq

GHC ghc-devs at haskell.org
Thu Aug 9 23:07:55 UTC 2018


#15500: internal error: Unable to commit 1048576 bytes of memory. Deepseq
--------------------------------------+----------------------------------
           Reporter:  alxdb           |             Owner:  (none)
               Type:  bug             |            Status:  new
           Priority:  normal          |         Milestone:  8.6.1
          Component:  Compiler        |           Version:  8.4.3
           Keywords:  memory deepseq  |  Operating System:  Linux
       Architecture:  x86_64 (amd64)  |   Type of failure:  Runtime crash
          Test Case:                  |        Blocked By:
           Blocking:                  |   Related Tickets:
Differential Rev(s):                  |         Wiki Page:
--------------------------------------+----------------------------------
 the following code is a (nearly) minimal working example that causes the
 aforementioned internal error.

 {{{#!hs
 module Main where

 import           Control.DeepSeq

 myfunc :: Int -> Int
 myfunc x = sum . take x $ [0..]

 logiter :: (NFData a) => Int -> (a -> a) -> a -> IO a
 logiter iter f x
   | iter >= 0 = do
         let y = f x
         deepseq y print $ "iter " ++ show iter
         if iter == 0 then return y else logiter (iter - 1) f y
   | otherwise = error "no negative iter!"

 main :: IO ()
 main = do
     print "start"
     print . show $ myfunc 2000000
     print "done"
     print "start"
     res <- logiter 5 myfunc 2000000
     print "done"
     print . show $ res

 }}}

 Perhaps this is an issue with deepseq, however it the message does say to
 come and report the bug, so that's what I'm doing.

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


More information about the ghc-tickets mailing list