
Hi all, I'm trying to implement the following simple Perl program in Haskell: my $nb_tests = 0 ; sub ok { my $bool = shift ; $nb_tests++ ; print STDOUT ($bool ? "ok" : "nok") . " $nb_tests\n" ; } ok(0) ; ok(1) ; The output is: nok 1 ok 2 I'm pretty much a Haskell newbie, but I know a bit about monads (and have been reading "Real World Haskell"), and I think I need to put the ok function must live inside some kind of state monad. My problem is that I also would like the ok function to perform some IO (as shown above, print). How is a case like this handled? Can my function live in 2 monads? Thanks a lot, Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Am Samstag, 21. Februar 2009 01:30 schrieb Patrick LeBoutillier:
Hi all,
I'm trying to implement the following simple Perl program in Haskell:
my $nb_tests = 0 ;
sub ok { my $bool = shift ; $nb_tests++ ; print STDOUT ($bool ? "ok" : "nok") . " $nb_tests\n" ; }
ok(0) ; ok(1) ;
The output is:
nok 1 ok 2
I'm pretty much a Haskell newbie, but I know a bit about monads (and have been reading "Real World Haskell"), and I think I need to put the ok function must live inside some kind of state monad. My problem is that I also would like the ok function to perform some IO (as shown above, print).
How is a case like this handled? Can my function live in 2 monads?
Yes, it can: -------------------- module OK where import Control.Monad.State ok :: Bool -> StateT Int IO () ok b = do increment nr <- get lift $ putStrLn $ (if b then "ok " else "nok ") ++ show nr increment :: StateT Int IO () increment = modify succ main :: IO () main = evalStateT (ok False >> ok True) 0 -------------------- Loading package base ... linking ... done. [1 of 1] Compiling OK ( OK.hs, interpreted ) Ok, modules loaded: OK. *OK> main Loading package mtl-1.1.0.1 ... linking ... done. nok 1 ok 2 What you need for this kind of stuff is a monad-transformer, there are transformers for most(? many, anyway) monads, recognizable by ending in T. They wrap one monad (here IO) inside another (State), combining their respective abilities. I'm sure there's lots of useful stuff on monad-transformers in the wikibook, too - they should also be treated in RWH, because in real-world apps you tend to need them:)
Thanks a lot,
Patrick
Cheers, Daniel

On 21 Feb 2009, at 01:30, Patrick LeBoutillier wrote:
Hi all,
I'm trying to implement the following simple Perl program in Haskell:
my $nb_tests = 0 ;
sub ok { my $bool = shift ; $nb_tests++ ; print STDOUT ($bool ? "ok" : "nok") . " $nb_tests\n" ; }
ok(0) ; ok(1) ;
The output is:
nok 1 ok 2
I'm pretty much a Haskell newbie, but I know a bit about monads (and have been reading "Real World Haskell"), and I think I need to put the ok function must live inside some kind of state monad. My problem is that I also would like the ok function to perform some IO (as shown above, print).
How is a case like this handled? Can my function live in 2 monads?
I personally wouldn't use two monads at all for this – in fact, I'd only use IO in one function: main = putStr . unlines . results inputs . snd . tests $ inputs inputs = [1,2] tests = foldr (\_ (x,l) -> (not x, x:l)) (True,[]) results = zipWith result result testN True = "ok " ++ show testN result testN False = "nok " ++ show testN Bob

Yes, this is much more idiomatic haskell.
On Sat, Feb 21, 2009 at 4:59 AM, Thomas Davie
On 21 Feb 2009, at 01:30, Patrick LeBoutillier wrote:
Hi all,
I'm trying to implement the following simple Perl program in Haskell:
my $nb_tests = 0 ;
sub ok { my $bool = shift ; $nb_tests++ ; print STDOUT ($bool ? "ok" : "nok") . " $nb_tests\n" ; }
ok(0) ; ok(1) ;
The output is:
nok 1 ok 2
I'm pretty much a Haskell newbie, but I know a bit about monads (and have been reading "Real World Haskell"), and I think I need to put the ok function must live inside some kind of state monad. My problem is that I also would like the ok function to perform some IO (as shown above, print).
How is a case like this handled? Can my function live in 2 monads?
I personally wouldn't use two monads at all for this – in fact, I'd only use IO in one function:
main = putStr . unlines . results inputs . snd . tests $ inputs
inputs = [1,2]
tests = foldr (\_ (x,l) -> (not x, x:l)) (True,[])
results = zipWith result result testN True = "ok " ++ show testN result testN False = "nok " ++ show testN
Bob
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (4)
-
Andrew Wagner
-
Daniel Fischer
-
Patrick LeBoutillier
-
Thomas Davie