Magnus Therning:
> Still no cigar :(

Yes, this is a little more subtle than I first thought. Look at liftM
and filterM:

liftM f m1 = do { x1 <- m1; return (f x1) }

filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
filterM _ [] =  return []
filterM p (x:xs) = do
   flg <- p x
   ys <- filterM p xs
   return (if flg then x:ys else ys)

In liftM, the result of (f x1) is not forced, and in filterM, flg is not
tested until after xs is traversed. The result is that when filterM runs
the (p x) action, a file is opened, but hasEmpty (and thus readFile) is
not forced until all other files have likewise been opened.

It should suffice to use a more strict version of liftM:

liftM' f m1 = do { x1 <- m1; return $! f x1 }

That should also fix the problem with Jules' solution, or alternatively:

readFile' f = do s <- readFile f
                 return $! (length s `seq` s)


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

Reply via email to