Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Concurrent vs GHC (Mauricio Hernandes)
   2. Re:  Concurrent vs GHC (Felipe Almeida Lessa)
   3. Re:  Concurrent vs GHC (Mauricio Hernandes)


----------------------------------------------------------------------

Message: 1
Date: Sun, 1 Jul 2012 00:03:34 +0900
From: Mauricio Hernandes <maukeshig...@gmail.com>
Subject: [Haskell-beginners] Concurrent vs GHC
To: beginners@haskell.org
Message-ID:
        <caoons7zurxzpyejxp-wxlutfbx+jdstrhfnvaq2+5w8f9_r...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hello, I'm having a problem with GHC.

When I compile the code bellow it does nothing, but If I try to use ghci it
works normally.

it seems a simple problem, but I can't understand.

Thanks for the help

Mauricio


import System.IO
import Control.Concurrent
import Data.List

main = do
     input <- newMVar  [1..30000]
     ia <- newEmptyMVar
     ib <- newEmptyMVar
     ic <- newEmptyMVar

     forkIO $ do x <- readMVar input
                 putMVar ia x

     forkIO $ do a <- readMVar ia
                 putMVar ib ( sum a )

     forkIO $ do a <- readMVar ia
                 putMVar ic ( reverse a )

     forkIO $ do b <- readMVar ib
                 c <- readMVar ic
                 print b
                 print c
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120701/712d04f7/attachment-0001.htm>

------------------------------

Message: 2
Date: Sat, 30 Jun 2012 12:24:02 -0300
From: Felipe Almeida Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] Concurrent vs GHC
To: maukeshig...@gmail.com
Cc: beginners@haskell.org
Message-ID:
        <CANd=ogeerxzpn116cqlpoddvassuebynwrbrg2tp4j3q9ob...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Your application is exiting before your forkIOs get a chance to
execute.  Instead of

  forkIO $ do
    ...
  forkIO $ do
    ...
  forkIO $ do
    ...

use something like

  finished <- newEmptyMVar

  forkIO $ do
    ...
    putMVar finished ()

  forkIO $ do
    ...
    putMVar finished ()

  forkIO $ do
    ...
    putMVar finished ()

  replicateM_ 3 (takeMVar finished)

Doing so will avoid your program to exit until all threads have finished.

Note that the code above is extremely fragile: doesn't handle
exceptions, you have to manually specify the number of threads that
you opened, etc.  These are abstracted by some libraries on Hackage
that you may use later for Real World Code (TM).

Cheers, =)

-- 
Felipe.



------------------------------

Message: 3
Date: Sun, 1 Jul 2012 02:51:27 +0900
From: Mauricio Hernandes <maukeshig...@gmail.com>
Subject: Re: [Haskell-beginners] Concurrent vs GHC
To: Felipe Almeida Lessa <felipe.le...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAOons7a6j9Mws-CTHJvRr5zHFQXmVX7-tpzq=xt0hpnjoej...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Eternal Gratitude for the help, it's working perfectly, I will consider the
exceptions and other stuff now.

the code looks like this now


import System.IO
import Control.Concurrent
import Data.List
import Control.Monad

main = do
          finished <- newEmptyMVar
          input <- newMVar  [1..30000]
          ia <- newEmptyMVar
          ib <- newEmptyMVar
          ic <- newEmptyMVar

          forkIO $ do x <- readMVar input
                      putMVar ia x
                      putMVar finished ()

          forkIO $ do a <- readMVar ia
                      putMVar ib ( sum a )
                      putMVar finished ()

          forkIO $ do a <- readMVar ia
                      putMVar ic ( reverse a )
                      putMVar finished ()

          b <- readMVar ib
          c <- readMVar ic
          writeFile "somaEprod.txt" (show b ++ "\n")
          appendFile "somaEprod.txt" (show c)
          replicateM_ 3 (takeMVar finished)




Valeu
Mauricio

On Sun, Jul 1, 2012 at 12:24 AM, Felipe Almeida Lessa <
felipe.le...@gmail.com> wrote:

> Your application is exiting before your forkIOs get a chance to
> execute.  Instead of
>
>  forkIO $ do
>    ...
>  forkIO $ do
>    ...
>  forkIO $ do
>    ...
>
> use something like
>
>  finished <- newEmptyMVar
>
>  forkIO $ do
>    ...
>    putMVar finished ()
>
>  forkIO $ do
>    ...
>    putMVar finished ()
>
>  forkIO $ do
>    ...
>    putMVar finished ()
>
>  replicateM_ 3 (takeMVar finished)
>
> Doing so will avoid your program to exit until all threads have finished.
>
> Note that the code above is extremely fragile: doesn't handle
> exceptions, you have to manually specify the number of threads that
> you opened, etc.  These are abstracted by some libraries on Hackage
> that you may use later for Real World Code (TM).
>
> Cheers, =)
>
> --
> Felipe.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120701/8e97db80/attachment-0001.htm>

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 49, Issue 1
****************************************

Reply via email to