
IMHO although this is a great explanation of what a monad is (as far as I understand it), for newbies I think it helps a lot to first look at the specific cases where monads are used and why they are invented, as explained in http://sigfpe.blogspot.com/2006/08/you-could-have-invented-monads-and.html and then looking at http://haskell.org/haskellwiki/IO_inside for the IO thingy. However, one thing which I find annoying is that a "classic pure" function cannot evaluate an IO function unless you use unsafePerformIO; one must "promote" (?demote) the pure function into the IO monad. For example, as an exercise I tried to convert the Monte Carlo experiment as demonstrated in http://mitpress.mit.edu/sicp/full-text/sicp/book/node53.html into Haskell (warning: newbie code ahead, should be much nicer when I once become a real Haskeller in a million years ;-) In the code below I had to change the monteCarlo1 into a completely different monteCarlo2 in order to use the IO random facility. Okay, this is "expected behavior", but for an imperative programmer, this is quite a shock! Any ways of "promoting" such a pure function into the monadic one automatically? I tried playing with "liftM", without succes. import Data.Ratio import Data.List import System.Random import Control.Monad -- Monte Carlo using "pure" functions monteCarlo1 :: Integral n => n -> (a -> (a,Bool)) -> a -> Ratio n monteCarlo1 trials experiment startValue = trialsPassed % trials where trialsPassed = genericLength $ filter id outcomes outcomes = snd $ unzip $ genericTake trials $ iterate (experiment . fst) (experiment startValue) cesaroTest1 :: StdGen -> (StdGen, Bool) cesaroTest1 gen0 = (gen2, (gcd rand1 rand2) == 1) where (rand1, gen1) = random gen0 (rand2, gen2) = random gen1 estimatePi1 trials = sqrt $ 6 / (fromRational $ monteCarlo1 trials cesaroTest1 (mkStdGen 0)) -- Monte Carlo using monadic IO -- no genericReplicateM, so must use Int monteCarlo2 :: Int -> IO Bool -> IO (Ratio Integer) monteCarlo2 trials experiment = do outcomes <- replicateM trials experiment return $ fromIntegral (genericLength $ filter id outcomes) % fromIntegral trials cesaroTest2 = do rand1 <- getStdRandom random rand2 <- getStdRandom random return $ (gcd rand1 rand2) == 1 estimatePi2 trials = do mc <- monteCarlo2 trials cesaroTest2 return $ sqrt $ 6 / (fromRational mc) main = let pi1 = estimatePi1 50000 in do pi2 <- estimatePi2 50000 putStrLn (show pi1) >> putStrLn (show pi2) -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Claus Reinke Sent: Thursday, August 02, 2007 12:18 AM To: haskell-cafe@haskell.org Subject: Re: FW: RE [Haskell-cafe] Monad Description For Imperative Programmer a Monad is a type constructor with two operations, implementing a standard interface and following a few simple rules. the Monad type class tells you the interface (what operations you've got, and their types), the Monad laws tell you what all types implementing that interface should have in common. the monadic interface gives you two operations, one to throw things into a monad thing (return), and one to chain two monad things together (>>=). the chaining explicitly caters for information flowing from the first to the second parameter of (>>=). the monad laws tell you two useful facts about monad things thrown together in that way: whatever it is the monad does, anything just thrown into it will take no part in that action, and whichever way you use that chaining operation, the structure of chaining is irrelevant, only the ordering of chained monad things matters. there are usually other ways to create 'primitive' monadic things, which can be combined into complex monadic structures using the operations from the Monad interface. there is usually a way to interpret monadic structures built in this way (a 'run' operation of some kind). that's it, i think?-) claus examples include: - i/o: primitive monadic things are basic i/o operations, the 'run' operation is outside the language, applied to 'Main.main', and interprets (abstract) IO monad structures sequentially, starting with the leftmost innermost i/o operation in the structure and applying the second argument of (>>=) to the result of executing the first. - []: primitive monadic things are lists, the 'run' operation is the identity, ie, the lists are directly exposed as data structures, return creates a singleton list, (>>=) applies its second argument to each element of its first argument and concatenates the results (concatMap). - State: primitive monadic things are operations on a state type, returning a result and a state; return returns its parameter, passing its input state unchanged, (>>=) applies its first parameter to the input state, applies its second parameter to the result value and result state of the first. 'run' is runState and applies a (possibly) complex monadic thing to an input state, returning a result and a (modified) state. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe