[Haskell-cafe] Why does replicateM (10^6) $ return 0 produce output in the IO monad, but overflow the maybe monad?

Thomas Hartman tphyahoo at gmail.com
Wed Oct 14 16:21:46 EDT 2009


-- Why does replicateM (10^6) $ return 0 produce output in the IO
monad, but overflow the maybe monad?

iterateNTimes i f x = foldr (.) id (replicate i f) $ x
tntIO :: IO Int
-- same as replicateM (10^6) $ return 0, same as sequence . replicate
(10^6) $ return 0
tntIO = return . head =<< (iterateNTimes (10^6) (mcons . return $ 0)
(return [])) -- produces output
tntMb :: Maybe Int -- overflows
tntMb = return . head =<< (iterateNTimes (10^6) (mcons . return $ 0)
(return [])) -- stack overflow

-- equivalently: mcons m ms = (:) <$> m <*> ms
mcons m ms = ap (liftM (:) m) $ ms

I guess the maybe version builds up a huge chain of unevaluated thunks
somewhere, that's usually the reason. But specifically where and why,
and why doesn't IO do the same thing?

Equivalent, with 3 element list:

(mcons $ return $ 0 ) $ (mcons $ return $ 0) $ (mcons $ return $ 0) $
(return [])
(ap . liftM (:) . return $ 0 ) $ (ap . liftM (:) . return $ 0) $ (ap .
liftM (:) . return $ 0) $ (return [])
(ap $ liftM (:) $ return $ 0 ) $ (ap $ liftM (:) $ return $ 0) $ (ap $
liftM (:) $ return $ 0) $ (return [])

t.


More information about the Haskell-Cafe mailing list