On 05/31/2011 04:48 PM, Artyom Kazak wrote:
> 
> Oh, sorry. I was unclear. I have meant "assuming IO is lazy", as Yves
> wrote.

Ah, ok. That makes more sense.

> 
> And saying "some hacks" I meant unsafeInterleaveIO, which lies beneath
> the laziness of, for example, getContents.

Which explains why assuming getContents is strict has never worked for me.

I'm trying to implement unfoldM1 without using unsafeIO, if possible. Since

  unfoldM1 f l = do
    next <- f l
    rest <- unfoldM1 f (next : l)
    return (next : rest)

obviously won't work, I've been trying to use fmap

  unfoldM1 :: (Functor m, Monad m) => ([a] -> m a) -> [a] -> m [a]
  unfoldM1 f l = do
    next <- f l
    fmap (next :) $ unfoldM1 f (next : l)

Evaluation here also doesn't terminate (or, (head $ unfoldM (return .
head)) doesn't), although I can't figure out why. fmap shouldn't need to
fully evaluate a list to prepend an element, right?

Attachment: signature.asc
Description: OpenPGP digital signature

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to