I expected that the following code would run and exit immediately because p
is never actually used, but instead, it runs for over 7 minutes and then is seemingly killed by the os.
{-# LANGUAGE DeriveFunctor #-}
import Control.Monad (liftM2)
main = print $ ((product' 1 >>= \p -> Nothing) :: Maybe Integer)
data Term f = In { out :: f (Term f) }
type Algebra f a = (f a -> a)
cata :: (Functor f) => Algebra f a -> Term f -> a
cata g t = g $ fmap (cata g) $ out t
type CoAlgebra f a = (a -> f a)
ana :: (Functor f) => CoAlgebra f a -> a -> Term f
ana g a = In $ fmap (ana g) $ g a
data A a = A (Maybe Integer) [a] | B deriving (Functor)
product' :: Integer -> Maybe Integer
product' i = cata h $ ana g $ fmap Just [i..1000]
where g (x:xs) = A x $ replicate 10 xs
g [] = B
h (A k l) = foldr (liftM2 (*)) k l
h B = Just 1
I thought this had to do with the bind operator, but the following code takes 9 seconds to run:
import Control.Monad (liftM2)
import Data.Foldable (foldr1)
main = print $ ((p >>= \p' -> Just p') :: Maybe Integer)
p :: Maybe Integer
p = foldr1 (liftM2 (*)) $ fmap Just [1..100000]
And this code exits immediately:
import Control.Monad (liftM2)
import Data.Foldable (foldr1)
main = print $ ((p >>= \p' -> Nothing) :: Maybe Integer)
p :: Maybe Integer
p = foldr1 (liftM2 (*)) $ fmap Just [1..100000]
Note that >>=
is strict in the first argument for Maybe
, so even if k >>= \x -> Nothing
is always going to be Nothing
, k
still gets evaluated to weak head normal form (which means in this case it has the form Just _
or Nothing
, where _
can be an unevaluated thunk).
In your case, k
is product' 1
. You'll notice that just trying to evaluate that to weak normal head form hangs. In fact, you can see that product' x
will probably take a really long time since it gets slower and slower as you have 1000 - x
larger and larger. On my laptop even product' 995
takes a really long time (and that is with -O2
).
Your benchmarks are not actually showing what you think they are. >>=
really is strict in the first argument, but only to WNHF (not all the way down). To make a case to prove my point, notice that the following exits immediately.
import Control.Monad (liftM2)
import Data.Foldable (foldr1)
main = print $ ((p >>= \_ -> Just 1) :: Maybe Integer)
p :: Maybe Integer
p = foldr1 (liftM2 (*)) $ fmap Just [1..100000]
The reason your second code snippet hangs is that it gets stuck trying to do the multiplication (which is pretty big) in order to print the result. If you ignore the result (as I do above), that doesn't happen - the result stays unevaluated. Another clue: your second code snippet hangs after having begun printing Just
.