[Haskell-beginners] Evaluate behaviour

Elvio Rogelio Toccalino elviotoccalino at gmail.com
Thu Jul 8 00:17:48 EDT 2010


...Oh, I just saw this:
"""
instead have;

names <- evaluate (fmap (runGet $ readStrings numStrings) $ L.hGetContents h)
"""
My apologizes, I was tackling a different question.


I believe the magic attributed to the (<-) operator results from the following:

let FUN be "(fmap (runGet $ readStrings numStrings) $ L.hGetContents h)"
then FUN :: IO [String]

This:
       names <- FUN
       evaluate names
bounds the result of the FUN computation to 'names'. Evaluate is run
on names, therefore 'evaluate'ing the result of the FUN computation.

On the other hand, this:
	names <- evaluate FUN
bounds to 'names' the results of 'evaluate'ing FUN. The action is
executed and the argument (FUN) is evaluated to WHNF. Let's see,

evaluate :: a -> IO a
evaluate FUN :: IO (IO [String])
names <- evaluate FUN

... and 'names' is bound to a [String] which has been evaluated to
WHNF. You end up closing a handle before reading your input.

If my reasoning is wrong, please (please!) let me know, you'd be
helping me greatly.

2010/7/8, Elvio Rogelio Toccalino <elviotoccalino at gmail.com>:
> This is a common behaviour, Tom. I suggest you read about the
> "semi-closed" state of Handles in the documentation for System.IO.
>
> It's kind of Zen :D
>
> Basically, you are reading lazily from a bytestring (1 chunk at a
> time)... Although it may seem as your program read and processed the
> whole bytestring, it didn't (it's lazy!). If you close the handle
> before "using" the output (when you 'return' it from your main
> function), you're shutting down the incoming data channel before a
> single request for a chunk of the bytestring is made.
>
> Check it out for yourself... don't hClose the handle, just leave it
> be. (It's messy, I know, but experiment with it.)
>
> 2010/7/7, Tom Hobbs <tvhobbs at googlemail.com>:
>> Hi guys,
>>
>> Thanks to everyone who helped me, I hit a milestone this evening and
>> finally got the (small) bit of functionality I was working on, working!
>> A
>> huge "thank you" to everyone who has taken the time to use very small
>> words to explain things to me!  (I just need to sort out some nicer error
>> handling now...)
>>
>> Just one more question... for today.
>>
>> Here's my code;
>>
>> import Network
>> import System.IO
>> (hGetLine,hClose,hPutStrLn,hSetBuffering,BufferMode(..),Handle,stdout)
>> import Data.Bits
>> import Data.Binary
>> import Data.Binary.Put
>> import Data.Binary.Get
>> import qualified Data.ByteString.Lazy	as L
>> import qualified Data.ByteString.UTF8	as UTF
>> import Control.Monad
>> import Control.Exception (evaluate)
>>
>> ping a t = do
>> 	h <- connectTo a (PortNumber t)
>> 	hSetBuffering h NoBuffering
>> 	L.hPut h (encode (0xFAB10000 :: Word32))
>> 	numStrings <- fmap (fromIntegral . runGet getWord64be) $ L.hGet h 8
>> 	names <- (fmap (runGet $ readStrings numStrings) $ L.hGetContents h)
>> 	evaluate names
>> 	hClose h
>> 	return names
>>
>> readStrings :: Int -> Get [String]
>> readStrings n = replicateM n $ do
>> 		len <- getWord32be
>> 		name <- getByteString $ fromIntegral len
>> 		return $ UTF.toString name
>>
>> This works in GHCi exactly as I want it to.  Note the call to "evaluate"
>> in the ping function which allows me to close the handle before returning
>> the IO [String].  This behaviour prints out the list of Strings as read
>>  from the handle in GHCi, exactly what I wanted it to do.  Here's the
>> strange part;
>>
>> If I remove the evalute line, and instead have;
>>
>> names <- evaluate (fmap (runGet $ readStrings numStrings) $
>> L.hGetContents
>> h)
>>
>> GHCI claims that this is okay, but when I call ping I don't get any
>> output.  I don't get any errors either, but I would expect to see the
>> same
>> list of Strings as before.
>>
>> Can anyone explain to me why that happpens?  I'm assuming it's something
>> to do with the "<-" magic, but I don't know what.
>>
>> Thanks,
>>
>> Tom
>>
>>
>> --
>> Using Opera's revolutionary e-mail client: http://www.opera.com/mail/
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>


More information about the Beginners mailing list