
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

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.

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.lessa@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.

On 2012-06-30, at 1:51 PM, Mauricio Hernandes wrote:
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)
Just another Haskell beginner here, so beware... You've moved the readMVar out of a thread into the application. This means (I think) that you are waiting for values in both ib and ic in the application (rather than a fourth thread). In your specific program, for these to have values require that all three threads have completed so you don't need the finished MVar anymore. However, this is pretty fragile being completely dependent on the MVars being set exactly once as the threads complete (so if you modify the code you have to be careful). The found solution is also fragile as Felipe says in his post. I don't know what those libraries Felipe mentioned are but I think I'd be looking for them right about now if I were you :-) Cheers, Bob
Valeu Mauricio
On Sun, Jul 1, 2012 at 12:24 AM, Felipe Almeida Lessa
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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
---- Bob Hutchison Recursive Design Inc. http://www.recursive.ca/ weblog: http://xampl.com/so

On 2012-07-02, at 9:10 AM, Bob Hutchison wrote:
On 2012-06-30, at 1:51 PM, Mauricio Hernandes wrote:
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)
Just another Haskell beginner here, so beware...
You've moved the readMVar out of a thread into the application. This means (I think) that you are waiting for values in both ib and ic in the application (rather than a fourth thread). In your specific program, for these to have values require that all three threads have completed so you don't need the finished MVar anymore. However, this is pretty fragile being completely dependent on the MVars being set exactly once as the threads complete (so if you modify the code you have to be careful). The found solution is also fragile as
^^^^^ finished (sorry)
Felipe says in his post. I don't know what those libraries Felipe mentioned are but I think I'd be looking for them right about now if I were you :-)
Cheers, Bob
Valeu Mauricio
On Sun, Jul 1, 2012 at 12:24 AM, Felipe Almeida Lessa
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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
---- Bob Hutchison Recursive Design Inc. http://www.recursive.ca/ weblog: http://xampl.com/so
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
---- Bob Hutchison Recursive Design Inc. http://www.recursive.ca/ weblog: http://xampl.com/so

Hi Guys, thanks again for the time reading this thread.
I was busy so I couldn't modify the code, but now it looks like this:
main = do
finished <- atomically $ newTChan
chan <- atomically $ newTChan
f <- openOffline "filename"
forkIO $ writeFile chan
forkIO $ reaFile f chan finished
a <- readTChan finished
show a
So chan is the variable for communication and finished the variable used to
readFile tell the main thread that the file is over,
It seems more neat than the previous code,
but I have a hard time understanding the sentence "...you have to manually
specify the number of threads that you opened..." in Felipe's email. What
does it mean? How do I specify automatically how many threads do I want?
Thanks a lot
Mau :)
On Mon, Jul 2, 2012 at 10:18 PM, Bob Hutchison
On 2012-07-02, at 9:10 AM, Bob Hutchison wrote:
On 2012-06-30, at 1:51 PM, Mauricio Hernandes wrote:
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)
Just another Haskell beginner here, so beware...
You've moved the readMVar out of a thread into the application. This means (I think) that you are waiting for values in both ib and ic in the application (rather than a fourth thread). In your specific program, for these to have values require that all three threads have completed so you don't need the finished MVar anymore. However, this is pretty fragile being completely dependent on the MVars being set exactly once as the threads complete (so if you modify the code you have to be careful). The found solution is also fragile as
^^^^^ finished (sorry)
Felipe says in his post. I don't know what those libraries Felipe mentioned are but I think I'd be looking for them right about now if I were you :-)
Cheers, Bob
Valeu Mauricio
On Sun, Jul 1, 2012 at 12:24 AM, Felipe Almeida Lessa < felipe.lessa@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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
---- Bob Hutchison Recursive Design Inc. http://www.recursive.ca/ weblog: http://xampl.com/so
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
---- Bob Hutchison Recursive Design Inc. http://www.recursive.ca/ weblog: http://xampl.com/so

Hi again, currently I'm trying to figure out how to properly write a parser in haskell. I've been following the instructions in a book called "Programming in Haskell" by Graham Hutton. So far I've written the following:

I am sorry, I must have hit the wrong hotkey. My code looks like this: type Parser a = String -> [(a, String)] result :: a -> Parser a result v = \inp -> [(v, inp)] zero :: Parser a zero = \inp -> [] item :: Parser Char item = \inp -> case inp of [] -> [] (x:xs) -> [(x, xs)] parse :: Parser a -> String -> [(a, String)] parse p inp = p inp (>>=) :: Parser a -> (a -> Parser b) -> Parser b (>>=) p f = \inp -> concat [f v inp' | (v, inp') <- p inp] sat :: (Char -> Bool) -> Parser Char sat p = do x <- item if p x then result x else zero I beleive I understand how this code is meant to work, but when I run it in ghci I get the follwing error-message: parser.hs:21:13: No instance for (Monad ((->) String)) arising from a do statement Possible fix: add an instance declaration for (Monad ((->) String)) In a stmt of a 'do' block: x <- item In the expression: do { x <- item; if p x then result x else zero } In an equation for `sat': sat p = do { x <- item; if p x then result x else zero } parser.hs:22:18: Couldn't match expected type `Char' with actual type `[(Char, String)]' In the first argument of `p', namely `x' In the expression: p x In a stmt of a 'do' block: if p x then result x else zero Failed, modules loaded: none. Sadly I have no idea how to fix this :( Thanks again :)

Am 03.07.2012 15:16, schrieb Robert Heumüller:
I am sorry, I must have hit the wrong hotkey. My code looks like this:
type Parser a = String -> [(a, String)]
This type synonym is unsuitable for a Monad instance. Better would be: newtype Parser a = Parser (String -> [(a, String)]) but that would require to change your code below.
result :: a -> Parser a result v = \inp -> [(v, inp)]
zero :: Parser a zero = \inp -> []
item :: Parser Char item = \inp -> case inp of [] -> [] (x:xs) -> [(x, xs)]
parse :: Parser a -> String -> [(a, String)] parse p inp = p inp
(>>=) :: Parser a -> (a -> Parser b) -> Parser b (>>=) p f = \inp -> concat [f v inp' | (v, inp') <- p inp]
Such a definition (without signature and adapted to the newtype) should be used within a Monad instance. "instance Monad Parser where ..."
sat :: (Char -> Bool) -> Parser Char sat p = do x <- item if p x then result x else zero
Without proper Monad instance you should not use "do". Instead you could expand it yourself manually to: sat p = item Main.>>= \x -> if p x then result x else zero Note the clash between your ">>=" function (Main.>>=) and the one from the Prelude! HTH Christian P.S. there is a "instance Monad ((->) r))" in Control.Monad.Instances but that does not fit your parser type, too.
I beleive I understand how this code is meant to work, but when I run it in ghci I get the follwing error-message:
parser.hs:21:13: No instance for (Monad ((->) String)) arising from a do statement Possible fix: add an instance declaration for (Monad ((->) String)) In a stmt of a 'do' block: x <- item In the expression: do { x <- item; if p x then result x else zero } In an equation for `sat': sat p = do { x <- item; if p x then result x else zero }
parser.hs:22:18: Couldn't match expected type `Char' with actual type `[(Char, String)]' In the first argument of `p', namely `x' In the expression: p x In a stmt of a 'do' block: if p x then result x else zero Failed, modules loaded: none.
Sadly I have no idea how to fix this :(
Thanks again :)

On 3 July 2012 15:13, Christian Maeder
This type synonym is unsuitable for a Monad instance. Better would be: newtype Parser a = Parser (String -> [(a, String)]) but that would require to change your code below.
This is alluded to in the closing chapter remarks (section 8.9) of Graham Hutton's book and there is code available on the website that accompanies the book that "solves" the problem. Unfortunately, this chapter does seem to trip people up who use the book for self study.

Thank you very much.
I'll check out the code on the website tomorrow and hopefully this will
solve the problem.
Whenever monads apper things seem to get tricky - sadly there won't be
a lecture on functional programming in the next semester at the
university I study at :(
Am Tue, 3 Jul 2012 18:01:32 +0100
schrieb Stephen Tetley
On 3 July 2012 15:13, Christian Maeder
wrote: This type synonym is unsuitable for a Monad instance. Better would be: newtype Parser a = Parser (String -> [(a, String)]) but that would require to change your code below.
This is alluded to in the closing chapter remarks (section 8.9) of Graham Hutton's book and there is code available on the website that accompanies the book that "solves" the problem. Unfortunately, this chapter does seem to trip people up who use the book for self study.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Tue, Jul 3, 2012 at 5:02 PM, Robert Heumüller
Whenever monads apper things seem to get tricky - sadly there won't be a lecture on functional programming in the next semester at the university I study at :(
The only trick here is that the text wants to introduce you to monads by doing something that won't work in a normal Haskell; you need to put the compiler in a mode which allows you to in effect rebuild them from scratch. (You can't simply provide your own definitions because "do" notation is hardwired to use the standard ones anyway, unless you use the RebindableSyntax extension to tell it to use yours. You'd also have to make sure you don't get the standard definitions, which means NoImplicitPrelude and manually importing Prelude minus the standard machinery. I don't think RebindableSyntax let you rebind "do" notation properly when that textbook was written, btw, so when it was written *no* Haskell compiler supported the direct use of its examples.) This was a rather unfortunate choice on Hutton's part, as it means his examples *only* work on paper. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms
participants (7)
-
Bob Hutchison
-
Brandon Allbery
-
Christian Maeder
-
Felipe Almeida Lessa
-
Mauricio Hernandes
-
Robert Heumüller
-
Stephen Tetley