internal error: Unable to commit 1048576 bytes of memory. Deepseq
the following code is a (nearly) minimal working example that causes the aforementioned internal error.
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.
Trac metadata
Trac field | Value |
---|---|
Version | 8.4.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |