
Hi All. I'm very new using Concurrency and STM in Haskell. I'm trying some basic example using STM like this one: module Main where import IO import Control.Concurrent import Control.Concurrent.STM main :: IO () main = do forkIO (hPutStr stdout "Hello") hPutStr stdout " world\n" Loading this module in GHCi and running main, the result is: wHoerllldo On MacOs X 10.5.8 and on WindowsXp Compiling this module with: ghc --make Main.hs -o Main and launcing ./Main the result is just: Terminal> world Am I doing something wrong? My expected result was Hello world (or world Hello) Thanks in advance for any answer. Luca.

Hi Luca,
Just in case you weren't aware of it, your example didn't actually
contain any STM (beyond the import), just regular Haskell IO-based
concurrency.
But the answer to your question is that there's no synchronization on
writing to a file descriptor, so both threads are "simultaneously"
writing to stdout (hPutStr stdout "...\n" === putStrLn "..." by the
way) and result in the interleaved results you see. One solution is to
have a thread that effectively owns stdout, and instead of writing to
stdout, you write to a Chan (Control.Concurrent.Chan) to talk to the
stdout owner, who will then write out your messages. This approach
will give you the "Hello world" or "world Hello" output that you were
after.
Hope this helps,
Dan
On Fri, Oct 2, 2009 at 12:16 PM, Luca Ciciriello
Hi All. I'm very new using Concurrency and STM in Haskell. I'm trying some basic example using STM like this one:
module Main where
import IO import Control.Concurrent import Control.Concurrent.STM
main :: IO () main = do forkIO (hPutStr stdout "Hello") hPutStr stdout " world\n"
Loading this module in GHCi and running main, the result is:
wHoerllldo
On MacOs X 10.5.8 and on WindowsXp
Compiling this module with:
ghc --make Main.hs -o Main
and launcing ./Main the result is just:
Terminal> world
Am I doing something wrong? My expected result was Hello world (or world Hello)
Thanks in advance for any answer.
Luca. _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Thanks Dan. I understand, your explanation is clear. I just need to study more Haskell. Im' just a beginner but very enthusiastic learning this "think-different" language (I'm a 12-year experienced C++ programmer). Thanks again. Luca. On Oct 2, 2009, at 6:28 PM, Daniel Peebles wrote:
Hi Luca,
Just in case you weren't aware of it, your example didn't actually contain any STM (beyond the import), just regular Haskell IO-based concurrency.
But the answer to your question is that there's no synchronization on writing to a file descriptor, so both threads are "simultaneously" writing to stdout (hPutStr stdout "...\n" === putStrLn "..." by the way) and result in the interleaved results you see. One solution is to have a thread that effectively owns stdout, and instead of writing to stdout, you write to a Chan (Control.Concurrent.Chan) to talk to the stdout owner, who will then write out your messages. This approach will give you the "Hello world" or "world Hello" output that you were after.
Hope this helps, Dan
On Fri, Oct 2, 2009 at 12:16 PM, Luca Ciciriello
wrote: Hi All. I'm very new using Concurrency and STM in Haskell. I'm trying some basic example using STM like this one:
module Main where
import IO import Control.Concurrent import Control.Concurrent.STM
main :: IO () main = do forkIO (hPutStr stdout "Hello") hPutStr stdout " world\n"
Loading this module in GHCi and running main, the result is:
wHoerllldo
On MacOs X 10.5.8 and on WindowsXp
Compiling this module with:
ghc --make Main.hs -o Main
and launcing ./Main the result is just:
Terminal> world
Am I doing something wrong? My expected result was Hello world (or world Hello)
Thanks in advance for any answer.
Luca. _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Fri, Oct 02, 2009 at 06:16:49PM +0200, Luca Ciciriello wrote:
Compiling this module with:
ghc --make Main.hs -o Main
and launcing ./Main the result is just:
Terminal> world
Also, the reason you only get "world" here is likely because the main thread prints "world" and exits before the forked thread even gets a chance to run. If you want the main thread to wait for the forked thread you must explicitly synchronize them; the most common way to do this is to set up an MVar (or a TVar in STM code) which the main thread reads from, and the forked thread writes to when it is finished in order to signal the main thread. -Brent

Brent Yorgey schrieb:
On Fri, Oct 02, 2009 at 06:16:49PM +0200, Luca Ciciriello wrote:
Compiling this module with:
ghc --make Main.hs -o Main
and launcing ./Main the result is just:
Terminal> world
Also, the reason you only get "world" here is likely because the main thread prints "world" and exits before the forked thread even gets a chance to run. If you want the main thread to wait for the forked thread you must explicitly synchronize them; the most common way to do this is to set up an MVar (or a TVar in STM code) which the main thread reads from, and the forked thread writes to when it is finished in order to signal the main thread.
For example, using a utility function I wrote some time ago: module Main(main) where import IO import Control.Concurrent parallel :: [IO a] -> IO [a] parallel = foldr (\a c -> do v <- newEmptyMVar forkIO (a >>= putMVar v) xs <- c x <- takeMVar v return (x:xs)) (return []) main = parallel [hPutStr stdout "Hello", hPutStr stdout " world\n"] There might be better ways to do this, but I hope that this will also be interesting because of the functional abstractions that are used. Note that this will execute two forkIOs, not one as the original code. If that is not desirable, foldr1 could have been used. Best Carsten

Thanks Carsten, I've compiled your example and all works as expected. Just a note. If I load the module in GHCi (intead of compiling it) and launch main function the result is quite strange. I obtain: He lwloorld [(),()] Luca.
To: glasgow-haskell-users@haskell.org From: carsten@codimi.de Date: Mon, 12 Oct 2009 13:34:36 +0200 Subject: Re: STM experiment
Brent Yorgey schrieb:
On Fri, Oct 02, 2009 at 06:16:49PM +0200, Luca Ciciriello wrote:
Compiling this module with:
ghc --make Main.hs -o Main
and launcing ./Main the result is just:
Terminal>
Also, the reason you only get "world" here is likely because the main thread prints "world" and exits before the forked thread even gets a chance to run. If you want the main thread to wait for the forked thread you must explicitly synchronize them; the most common way to do this is to set up an MVar (or a TVar in STM code) which the main thread reads from, and the forked thread writes to when it is finished in order to signal the main thread.
For example, using a utility function I wrote some time ago:
module Main(main) where
import IO import Control.Concurrent
parallel :: [IO a] -> IO [a] parallel = foldr (\a c -> do v <- newEmptyMVar forkIO (a >>= putMVar v) xs <- c x <- takeMVar v return (x:xs)) (return [])
main = parallel [hPutStr stdout "Hello", hPutStr stdout " world\n"]
There might be better ways to do this, but I hope that this will also be interesting because of the functional abstractions that are used. Note that this will execute two forkIOs, not one as the original code. If that is not desirable, foldr1 could have been used.
Best
Carsten
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_________________________________________________________________ Learn how to add other email accounts to Hotmail in 3 easy steps. http://clk.atdmt.com/UKM/go/167688463/direct/01/

Luca Ciciriello schrieb:
Thanks Carsten, I've compiled your example and all works as expected.
Just a note. If I load the module in GHCi (intead of compiling it) and launch main function the result is quite strange. I obtain:
He lwloorld
So we actually observe the concurrency here, nice.
[(),()]
The result of the computation: Both instances of hPutStr return (), and parallel assembles these into [(),()]. The intersesting thing is that ghci suppresses an IO result if it is of type (), but not otherwise. Prelude> return () :: IO () Prelude> return [(),()] :: IO [()] [(),()] Prelude> I did not know this. Carsten
module Main(main) where
import IO import Control.Concurrent
parallel :: [IO a] -> IO [a] parallel = foldr (\a c -> do v <- newEmptyMVar forkIO (a >>= putMVar v) xs <- c x <- takeMVar v return (x:xs)) (return [])
main = parallel [hPutStr stdout "Hello", hPutStr stdout " world\n"]

Is there a way to use VisualHaskel with GHC 6.10.4? Luca

Just a Haskell beginner question. If I load in GHCi the code below all works fine, I load a file and its content is shown on screen. But if I use the second version of my "load_by_key" (the commented one) no error is reported loading and executing this code, but nothing is shown on screen. Where is my mistake? I'm using GHC 6.10.4 on MacOS X 10.5.8 Thanks in advance. Luca. module BackEnd where import IO load_by_key :: String -> String -> IO () load_by_key table key = do inh <- openFile table ReadMode contents <- hGetContents inh get_record (get_string contents) key hClose inh {- load_by_key table key = do contents <- getTableContent table get_record (get_string contents) key -} get_string :: String -> String get_string = (\x -> x) get_record :: String -> String -> IO () get_record contents key = putStr( contents ) getTableContent :: String -> IO String getTableContent table = bracket (openFile table ReadMode) hClose (\h -> (hGetContents h)) _________________________________________________________________ Did you know you can get Messenger on your mobile? http://clk.atdmt.com/UKM/go/174426567/direct/01/

Dear Luca, The problem in your alternative code is that hGetContents lazily reads the contents of the handle it is passed. You've run into a cognitive bootstrap problem; the documentation for System.IO [1] does explain it, but I can see that you need to understand it to be able to read it ;) These are the important bits for your example: - hGetContents h puts handle h into a "semi-closed" state, but doesn't actually read anything (yet). - Any other function that gets a semi-closed handle (except hClose) will see it as a closed handle. - When a semi-closed handle becomes closes, the contents of the associated list becomes fixed. In other words; the actual reading from the handle doesn't happen until you evaluate the resulting list (and then still only the part that you evaluate). In your bracket, you open a handle, then you "convert" the handle into a lazy list that would evaluate to the contents of the file, but then you close the handle, fixing the list you got to an empty list. If you want to do this, you would want something like this: withTableContents :: String -> (String -> IO a) -> IO a withTableContents table cont = bracket (openFile table ReadMode) hClose (\h -> hGetContents h >>= cont) Hope this helps. By the way, this type of question should probably go to haskell-cafe@haskell.org which will usually give you a lot of explanation quite quickly. Regards, Philip [1] http://haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html#v:hGet... On Wed, 2009-10-14 at 07:26 +0100, Luca Ciciriello wrote:
Just a Haskell beginner question. If I load in GHCi the code below all works fine, I load a file and its content is shown on screen. But if I use the second version of my "load_by_key" (the commented one) no error is reported loading and executing this code, but nothing is shown on screen. Where is my mistake? I'm using GHC 6.10.4 on MacOS X 10.5.8
Thanks in advance.
Luca.
module BackEnd where
import IO
load_by_key :: String -> String -> IO ()
load_by_key table key = do inh <- openFile table ReadMode contents <- hGetContents inh get_record (get_string contents) key hClose inh
{- load_by_key table key = do contents <- getTableContent table get_record (get_string contents) key -}
get_string :: String -> String get_string = (\x -> x)
get_record :: String -> String -> IO () get_record contents key = putStr( contents )
getTableContent :: String -> IO String getTableContent table = bracket (openFile table ReadMode) hClose (\h -> (hGetContents h))
______________________________________________________________________ Did you know you can get Messenger on your mobile? Learn more. _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Am Mittwoch 14 Oktober 2009 08:26:10 schrieb Luca Ciciriello:
Just a Haskell beginner question.
This sort of generic question has a higher probability of receiving a quick answer on haskell-cafe@haskell.org or beginners@haskell.org, where more people are reading.
If I load in GHCi the code below all works fine, I load a file and its content is shown on screen. But if I use the second version of my "load_by_key" (the commented one) no error is reported loading and executing this code, but nothing is shown on screen. Where is my mistake?
You're bitten by laziness. It's a very common problem you're having. In the working version, you explicitly open the file, lazily get its contents, then print it out and after that is done, close the file.
load_by_key table key = do inh <- openFile table ReadMode contents <- hGetContents inh get_record (get_string contents) key hClose inh
Here you use bracket, which doesn't interact well with hGetContents. hGetContents is lazy and returns immediately, without reading any of the file's contents yet. Once hGetContents returns, bracket performs its exit action, here it closes the file - before you've read anything from it. Then you try to print the file contents and hGetContents tries to read the file. That is now closed, hence hGetContents can't read anything and returns "", which then is output. Don't mix bracket and hGetContents. Consider using readFile instead.
{- load_by_key table key = do contents <- getTableContent table get_record (get_string contents) key -}
get_string :: String -> String get_string = (\x -> x)
get_record :: String -> String -> IO () get_record contents key = putStr( contents )
getTableContent :: String -> IO String getTableContent table = bracket (openFile table ReadMode) hClose (\h -> (hGetContents h))

Thanks Philip and Daniel for your help. Your explanation is clear. Thanks also for direct me on the right news letters :-) Luca. _________________________________________________________________ Chat to your friends for free on selected mobiles http://clk.atdmt.com/UKM/go/174426567/direct/01/
participants (7)
-
Brent Yorgey
-
Carsten Schultz
-
Daniel Fischer
-
Daniel Peebles
-
Luca Ciciriello
-
Philip K.F. Hölzenspies
-
Simon Marlow