monad nomad gonad gomad

ok so taking MAN's suggestion: "I think It's time for you to get serious with the monads" that's just what i'm going to do! i found the following references: You Could Have Invented Monads! http://blog.sigfpe.com/2006/08/you-could-have-invented-monads-and.html an interesting way to become familiar with the idea Monads for the Working Haskell Programmer http://www.engr.mun.ca/~theo/Misc/haskell_and_monads.htm seems to have several practical ideas there (though i don't understand them yet) A tour of the Haskell Monad functions http://members.chello.nl/hjgtuyl/tourdemonad.html a nice reference with brief explanations Explaining Haskell IO without Monads http://neilmitchell.blogspot.com/2010/01/haskell-io-without-monads.html possibly a good conceptual aid for background All About Monads http://www.haskell.org/all_about_monads/html/index.html this seems to have everything though it'll take some work to dig in in any case, monads seem to be a rather important concept to getting anything done in haskell. for instance, i have a program which is generating the output it is supposed to (i can print it), but i can't seem to get it into another function and keep getting the error i've seen so many times: Couldn't match expected type `[String]' against inferred type `IO [String]' so it's time to understand them. besides, the stuff looks rather intriguing and certainly appears to take one into computer language design theory. any sources others have found useful would be appreciated as well as suggestions on how to proceed through the above. in friendship, prad -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

On Fri, 13 Aug 2010 21:39:33 -0700
prad
"I think It's time for you to get serious with the monads" that's just what i'm going to do!
i'm asking the question in this thread because i think it has something to do with monads though i'm not sure. in fact, the problem seems completely bizarre to me. i have a function: mkTxt :: (IConnection conn) => conn -> String -> [String] mkTxt conn tS = do --zzzz <- readFile "zzpubs.htm" let wL = words (rpNls tS) ((f,vL):zz) = gtInx wL ["```"] rvL = reverse vL doIns wL rvL where doIns wL [] = wL doIns wL (v:vs) = do let (f,a:b:ss) = splitAt v wL (doIns f vs) ++ ["aoeeuu"] ++ ss the program compiles and runs fine. however, if i remove the comment dashes to allow zzzz <- readFile "zzpubs.htm" the compiler produces what is to me an incomprehensible rationale for an error: ==== gadit.hs:103:4: Couldn't match expected type `IO String' against inferred type `[String]' In a stmt of a 'do' expression: zzzz <- readFile "zzpubs.htm" In the expression: do { zzzz <- readFile "zzpubs.htm"; let wL = words (rpNls tS) ((f, vL) : zz) = gtInx wL ... ....; doIns wL rvL } In the definition of `mkTxt': mkTxt conn tS = do { zzzz <- readFile "zzpubs.htm"; let wL = ... ....; doIns wL rvL } where doIns wL [] = wL doIns wL (v : vs) = do { let ...; .... } ==== i don't do anything with zzzz!! it merely is the name i'm giving to the monadic computation to read in a file. in fact, it has nothing to do with the rest of the function because i don't use it at all. why is the compiler complaining? -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

For your string-manipulation problem, I don't think you meant to use do-notation. The compiler accepted it because sees it as the list monad, and as a coincidence of the way you wrote it, it did what you expected. Try this, using (let ... in ) syntax.
mkTxt :: (IConnection conn) => conn -> String -> [String] mkTxt conn tS = let wL = words (rpNls tS) ((f,vL):zz) = gtInx wL ["```"] rvL = reverse vL in doIns wL rvL where doIns wL [] = wL doIns wL (v:vs) = let (f,a:b:ss) = splitAt v wL in (doIns f vs) ++ ["aoeeuu"] ++ ss
(Untested.) Next readFile has the signature readFile :: FilePath -> IO String So the way I think of it is that any function using it has to return a result of "IO <something>" You would have to call your pure function mkTxt from inside a monadic computation: run :: IO () run = do zzzz <- readFile "zzpubs.txt" ... -- assuming mkTxt is modified to accept a third arg let result = mkTxt conn ts zzzz print result Finally, yes Haskell complains about type-related faults in identifiers you don't use... because it is trying to help you find your mistakes. How does it know it wasn't a mistake on your part? This is an advantage over script languages. Mike prad wrote:
On Fri, 13 Aug 2010 21:39:33 -0700 prad
wrote: "I think It's time for you to get serious with the monads" that's just what i'm going to do!
i'm asking the question in this thread because i think it has something to do with monads though i'm not sure. in fact, the problem seems completely bizarre to me.
i have a function:
mkTxt :: (IConnection conn) => conn -> String -> [String] mkTxt conn tS = do --zzzz <- readFile "zzpubs.htm" let wL = words (rpNls tS) ((f,vL):zz) = gtInx wL ["```"] rvL = reverse vL doIns wL rvL where doIns wL [] = wL doIns wL (v:vs) = do let (f,a:b:ss) = splitAt v wL (doIns f vs) ++ ["aoeeuu"] ++ ss
the program compiles and runs fine. however, if i remove the comment dashes to allow zzzz <- readFile "zzpubs.htm"
the compiler produces what is to me an incomprehensible rationale for an error:
==== gadit.hs:103:4: Couldn't match expected type `IO String' against inferred type `[String]' In a stmt of a 'do' expression: zzzz <- readFile "zzpubs.htm" In the expression: do { zzzz <- readFile "zzpubs.htm"; let wL = words (rpNls tS) ((f, vL) : zz) = gtInx wL ... ....; doIns wL rvL } In the definition of `mkTxt': mkTxt conn tS = do { zzzz <- readFile "zzpubs.htm"; let wL = ... ....; doIns wL rvL } where doIns wL [] = wL doIns wL (v : vs) = do { let ...; .... } ====
i don't do anything with zzzz!! it merely is the name i'm giving to the monadic computation to read in a file. in fact, it has nothing to do with the rest of the function because i don't use it at all.
why is the compiler complaining?

On Sat, 14 Aug 2010 18:28:03 -0700
Michael Mossey
Finally, yes Haskell complains about type-related faults in identifiers you don't use... because it is trying to help you find your mistakes. How does it know it wasn't a mistake on your part?
This is an advantage over script languages.
wow! this is amazing! i guess when you understand the compiler's intentions, you acquire a powerful ally! experimenting in another file, i did something similar: =========== gtKys conn = do z <- readFile "monads.txt" r <- quickQuery conn "select key from main" [] --return $ concat $ map (map fromSql) r manip z manip f = do let wL = words f putStrLn $ show wL ========== this works fine, even though the r quickQuery line is never used. so i guess one has to try to figure out how to work with the compiler. part of the feeling i'm getting is that a function should only do one thing and i likely try to squeeze too much into it. i'm used to using a lot of print statements to figure out errors, but may be the idea here is not to make errors because you're functions are written correctly and are precise. i'll rethink what i'm writing and how. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

prad wrote:
part of the feeling i'm getting is that a function should only do one thing and i likely try to squeeze too much into it.
I don't think that's universally true, but you may need to stay simple while learning.
i'm used to using a lot of print statements to figure out errors, but may be the idea here is not to make errors because you're functions are written correctly and are precise.
Look at the Debug.Trace module. You can emit debugging messages in a non-safe but usually helpful manner. Be aware that the messages may come in an unexpected order due to laziness. Mike

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 8/14/10 19:51 , prad wrote:
mkTxt :: (IConnection conn) => conn -> String -> [String] (...) the compiler produces what is to me an incomprehensible rationale for an error:
==== gadit.hs:103:4: Couldn't match expected type `IO String' against inferred type `[String]'
You didn't specify that mkTxt is in IO; your result type is [String], which (given your use of the monad machinery) means you return a String in the List monad. So, "(zzzz :: String) <- (readFile "zzPubs.htm" :: IO String)", but because of the List monad in the result type this means that it's expecting a [String], not an IO String. - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkxnS+sACgkQIn7hlCsL25XmGQCgrhMM6vCzRNMH4deG41od7eD3 l9cAn0a+WbwvkAWC7ikG9mFB6ybIjTKa =Voo5 -----END PGP SIGNATURE-----

prad
in any case, monads seem to be a rather important concept to getting anything done in haskell. for instance, i have a program which is generating the output it is supposed to (i can print it), but i can't seem to get it into another function and keep getting the error i've seen so many times:
Couldn't match expected type `[String]' against inferred type `IO [String]'
so it's time to understand them.
In an earlier thread titled "= vs <-" you asked for the difference between equations (=) and monadic binding (<-). Since you didn't respond, I'm not sure whether you are reading our posts, but we have explained in detail the difference. Once understood, you won't get errors like that anymore. As a well meant suggestion, you have to actually read the answers to your posts, even if they are long. Posting essentially the same questions over and over gets you nowhere.
besides, the stuff looks rather intriguing and certainly appears to take one into computer language design theory.
Not really. A monad is just a way to combine computations. You're still thinking way too complicated.
any sources others have found useful would be appreciated as well as suggestions on how to proceed through the above.
Well, I have the impression that writing monad tutorials is very hateful in the Haskell community, independent of the tutorial's actual quality. That's why I don't like to mention my own one, even though so far I have only received very positive feedback (thanks to all, who have bothered to write me). I think that new tutorials aren't even reviewed by experienced Haskell users anymore, especially since Brent Yorgey wrote his famous blog entry [1]. I agree with Brent, but his post had a negative side effect, too. New tutorials seem to be marked as spam by reflex now by most people. Personally I find this very unfortunate, and I'm not sure whether that was Brent's intention. [1] http://byorgey.wordpress.com/2009/01/12/abstraction-intuition-and-the-monad-... Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Sun, 15 Aug 2010 16:43:09 +0200
Ertugrul Soeylemez
I'm not sure whether you are reading our posts, but we have explained in detail the difference. Once understood, you won't get errors like that anymore.
As a well meant suggestion, you have to actually read the answers to your posts, even if they are long.
ertugrul, believe me i read the posts (more than a few times) - especially yours in fact and am very appreciative. however, it takes me a while to understand what's going on - even to connect similar ideas together. i certainly don't mind long posts either, but i am still having difficulties putting the ideas together. i tend to be a bit slow anyway and keep thinking in python terms. i intend to respond once i understand the ideas better. for instance, what you wrote here made sense to me: ======== let readBlahTxt = readFile "blah.txt" content <- readBlahTxt This should show the difference more clearly. ======== however, i still can't quite connect it to the idea of what it has to do with getting monad data out of a monad and into the pure realm. late last night, though, i was able to do so, but it took while.
Posting essentially the same questions over and over gets you nowhere.
agreed and i apologize. my problem is that i don't even see that it is the same question. as you have pointed out once before, "You're still thinking way too complicated." i think what happens is i keep trying different things over and over again. that affects my thinking no doubt. i should likely think more and try less.
A monad is just a way to combine computations.
this wasn't clear to me till now even though i had read your continuing exchange with kyle and the example both of you were discussing regarding >>= (and i had read up on the operator and even tried it).
I don't like to mention my own one
i would very much like to see yours.
I agree with Brent
i think brent's delightful blog post describes my present dilemmas ... except i haven't quite gotten to the point of being able to say "monads are burritos" ... so i think there is likely still hope for me. ;) -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

prad
On Sun, 15 Aug 2010 16:43:09 +0200 Ertugrul Soeylemez
wrote: I'm not sure whether you are reading our posts, but we have explained in detail the difference. Once understood, you won't get errors like that anymore.
As a well meant suggestion, you have to actually read the answers to your posts, even if they are long.
believe me i read the posts (more than a few times) - especially yours in fact and am very appreciative. however, it takes me a while to understand what's going on - even to connect similar ideas together. i certainly don't mind long posts either, but i am still having difficulties putting the ideas together. i tend to be a bit slow anyway and keep thinking in python terms.
i intend to respond once i understand the ideas better. for instance, what you wrote here made sense to me:
======== let readBlahTxt = readFile "blah.txt" content <- readBlahTxt
This should show the difference more clearly. ========
however, i still can't quite connect it to the idea of what it has to do with getting monad data out of a monad and into the pure realm. late last night, though, i was able to do so, but it took while.
I'd say don't bother. "Getting out of" is just a metaphor. Monads are no boxes. You have a monadic computation, which has a result, and you want to refer to this result, and that's all. let a = getLine b <- getLine In this example, 'a' is the same as 'getLine'. It's a computation, which reads a line from stdin. It's not the result of the computation (String), but the computation itself (IO String), because you defined 'a' and 'getLine' to be the same thing. On the other hand, 'b' is the result. You could just as well write: b <- a Just remember this: You have an IO computation? You want to refer to its result? Fine, just use '<-'. That's it. Now what is meant by the "getting out of" metaphor? You can use the '<-' notation only inside of a monadic computation. In other words, even though you can refer to the result of getLine, ultimately you are making a new IO computation, which uses the result: readAndSquare :: IO Integer readAndSquare = do line <- getLine let n = read line return (n^2) readAndSquare is an IO computation itself and there is nothing you could do about it. As long as you refer to results of IO computations, if you go down the call tree, you will always end up in an IO computation. This is what people refer to as not being able to "get out of" IO. This is not true for the list monad: getFirstWord :: String -> String getFirstWord = head . words The list concept is also a monad, or in Haskell terms: [] is a monad. You are using the result of a monadic computation, namely 'words': words :: String -> [String] -- brackets style words :: String -> [] String -- prefix style But the getFirstWord function is itself not monadic (let's disregard the fact that strings are lists). Using the 'head' function head :: [a] -> a -- brackets style head :: [] a -> a -- prefix style you have broken out of the [] monad. There is no such function for the IO monad: breakOut :: IO a -> a Well, that's not entirely true. There is unsafePerformIO, which has exactly that type signature, but seriously, never use it. Especially as a beginner coming from the imperative world one is often tempted to use it, but don't. Using it is almost always the wrong approach, and as its name suggests a very unsafe one, too.
Posting essentially the same questions over and over gets you nowhere.
agreed and i apologize. my problem is that i don't even see that it is the same question. as you have pointed out once before, "You're still thinking way too complicated."
i think what happens is i keep trying different things over and over again. that affects my thinking no doubt. i should likely think more and try less.
In fact, I recommend not to think more, but to think less. Forget the word 'monad' and just concentrate on specific monads like IO or Maybe. At some point it will make click and suddenly everything gets clear. Everybody has this experience with monads (unless they give up).
I don't like to mention my own one
i would very much like to see yours.
It's linked on the tutorials wiki page as "Understanding Haskell Monads".
I agree with Brent
i think brent's delightful blog post describes my present dilemmas ... except i haven't quite gotten to the point of being able to say "monads are burritos" ... so i think there is likely still hope for me. ;)
Try this [1]. ;) [1] http://blog.plover.com/prog/burritos.html Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Sun, 15 Aug 2010 21:11:52 +0200
Ertugrul Soeylemez
Just remember this: You have an IO computation? You want to refer to its result? Fine, just use '<-'. That's it.
that's what i've been doing the past two days and it works ... except in one case. for example, i have: ======== flData <- readFile key let (sec:tle:kwd:dsc:url:typ:dat:txt) = lines flData ======== so flData is the computation which reads the contents of a file and i can take that and do a lines on it. no problem. however, i also have: ======== subs (l:ls) | ls==[] = l : [] | otherwise = case l of "```" -> do let (code:z) = ls str = gt code -- works --str <- readFile "B" -- doesn't work subs (str:z) _ -> l : subs ls gt s = case s of "B" -> "BBBB" "C" -> "CCCC" ======== now str = gt code is fine because it's not monadic. however, if i try to get the data from a file or a db, it gives the error Couldn't match expected type `[[Char]]' against inferred type `IO b' because i'm trying to get an IO monad into a [String] from what i understand. so i'm trying different things here, but haven't found a way yet.
In fact, I recommend not to think more, but to think less.
ok! i'll see what i can do! as you rightly keep telling me, i'm being way too complicated. :D i'm enjoying your extensive tutorial: http://ertes.de/articles/monads.html though it's going slowly, but things are coming together little by little. i was also pointed to this: http://codingcactus.wordpress.com/2010/08/16/writemonad1/ and i just saw mike vanier's post here: very detailed monad tutorials (a series of articles) http://mvanier.livejournal.com/3917.html so with all this help i'm sure to 'get it' eventually!
At some point it will make click and suddenly everything gets clear. Everybody has this experience with monads (unless they give up).
no worries about that! i do see the light in the long tunnel - now it's just a matter of getting to it. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

prad wrote:
On Sun, 15 Aug 2010 21:11:52 +0200 however, i also have:
======== subs (l:ls) | ls==[] = l : [] | otherwise = case l of "```" -> do let (code:z) = ls str = gt code -- works --str <- readFile "B" -- doesn't work subs (str:z) _ -> l : subs ls
gt s = case s of "B" -> "BBBB" "C" -> "CCCC" ========
Can I make a general suggestion? It looks to me like you need to work through a book like "Real World Haskell" sequentially from the beginning. It looks like you are trying to do complex things before you've mastered simple things. Mike

On Tue, 17 Aug 2010 13:34:01 -0700
Michael Mossey
It looks to me like you need to work through a book like "Real World Haskell" sequentially from the beginning.
well i'm doing that too, michael. (i remember you made this suggestion to me several weeks ago and i have worked my way through a few chapters in rw and most of the haskell wiki tutorial). i've joined the reading group on the agora forum for rwhaskell. i'm also going through the video lectures here: http://www.cs.nott.ac.uk/~gmh/book.html what i find interesting is that you say what i'm trying to do here is complicated, because it seemed to me it was one of the simpler things that i actually understood. now i think i'm in trouble, because evidently i haven't understood it too well. :D it seemed to me that in one situation i was trying to get data from a function gt which just returns a string: gt :: String -> String in the other situation, i wanted to get the same data from a file, but can't seem to because the file is returning an IO instead of a String (in fact it is expecting [String]). however, i know you are right. i really need to get a better understanding of the basics, so i'll focus on that for the next few days and see if i can understand these problems i'm having better than i presently do. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

On Tue, Aug 17, 2010 at 01:59:44PM -0700, prad wrote:
On Tue, 17 Aug 2010 13:34:01 -0700 Michael Mossey
wrote: It looks to me like you need to work through a book like "Real World Haskell" sequentially from the beginning.
well i'm doing that too, michael. (i remember you made this suggestion to me several weeks ago and i have worked my way through a few chapters in rw and most of the haskell wiki tutorial).
Well, I may not help you, Prad, but the enormous amount of questions you've send to this mailing-list have helped me to re-discover many basic concepts of Haskell ,-) I am also trying to learn it since last January. So I can add this piece of advice for you : do not rush things. It seems you are reading too many different contents on monads lately. That's strange for someone as lazy as me who cannot digest this much amount of data in such a short time. I usually evaluate my time spend on a specific subject as the number of nights spend between each of my readings and I can say this: monads have taken me a good month of sleep to figure them out :)
what i find interesting is that you say what i'm trying to do here is complicated, because it seemed to me it was one of the simpler things that i actually understood. now i think i'm in trouble, because evidently i haven't understood it too well. :D
No it's not simple. I am not able to read Haskell code which play with database and files, so your code is already behind my understanding.
it seemed to me that in one situation i was trying to get data from a function gt which just returns a string: gt :: String -> String
in the other situation, i wanted to get the same data from a file, but can't seem to because the file is returning an IO instead of a String (in fact it is expecting [String]).
From what I remember, RWH's authors always advocate to separate monadic code from basic code. You should pause for a moment and refactor your code so you do not get caught in this situation again (situation = trying to read a file as you read a String).
If I were you, I would break my problem in even smaller chunks and try to analyze patiently how Haskell could process each individually. regards, /John P.S.: ah ! and keep posting questions on precise problems you encounter. I may be interested in them :p

prad wrote:
On Tue, 17 Aug 2010 13:34:01 -0700 Michael Mossey
wrote: It looks to me like you need to work through a book like "Real World Haskell" sequentially from the beginning.
what i find interesting is that you say what i'm trying to do here is complicated, because it seemed to me it was one of the simpler things that i actually understood. now i think i'm in trouble, because evidently i haven't understood it too well. :D
It may be simple to do once you understand, but your past several questions relate to - purity - do-notation as syntactic sugar for monadic computations - the IO monad If you understood these things you would not be running into this trouble, or you would quickly see the problem yourself. Because most books and tutorials introduce these things gradually, giving you lots of practice problems /at the level they are introduced/, I think your learning process would go more smoothly if you - pick a single book. don't try to digest all these different tutorials and books at once - read it sequentially - work the problems. if you want to branch into your own problem, stay close to the examples you've seen so far Best wishes, Mike

prad
On Sun, 15 Aug 2010 21:11:52 +0200 Ertugrul Soeylemez
wrote: Just remember this: You have an IO computation? You want to refer to its result? Fine, just use '<-'. That's it.
that's what i've been doing the past two days and it works ... except in one case.
for example, i have:
======== flData <- readFile key let (sec:tle:kwd:dsc:url:typ:dat:txt) = lines flData ========
so flData is the computation which reads the contents of a file and i can take that and do a lines on it. no problem.
I have the impression that you have understood the problem, but you have yet to realize that you have. Your 'subs' function needs the contents of a file, so either you pass those contents explicitly or it needs to become an IO computation, so it can read them itself. Anyway, honestly I don't understand what your 'subs' function is about. It seems to interpret stuff after "```", but you can write this a whole lot simpler and probably more correct, although still very fragile: subs :: [String] -> [String] subs [] = [] subs ("```" : code : ts) = gt code : subs ts subs (t:ts) = t : subs ts Why is this fragile? Well, try the following: subs ["```"] Also do yourself and others a favor and write type annotations at least for all top level definitions. Yes, Haskell has type inference, but for important parts of your code you should really write explicit type annotations. Reason: First of all, the types of your functions are the specification of your program. To write a function, the very first thing you should do is to write its type signature. Never start with the function definition. Sometimes you write a valid function, which doesn't match your intended specification. Also given the type signature you can reason much better about whether your code really does what it should do, without even compiling it. Secondly type annotations make your program far more readable. For some really simple one-liner functions they aren't strictly necessary for readability, but personally I write them even for the simplest functions/values. Now what's the type of your function, when it should read a file? Think about it for a while. One very easy way is to give it the contents of the file as a parameter: subs :: String -> [String] -> [String] Another reasonable way is to let the function read the file itself: subs :: FilePath -> [String] -> IO [String] But beware: The way you were going to do it is very bad. It would read the file once for each occurence of "```". Better read the file at the beginning only, at which point you can just as well split this into two functions: subs :: String -> [String] -> [String] subsUsingFile :: FilePath -> [String] -> IO [String] This particular way to make a nonmonadic functions monadic is called lifting, and because it is such a common thing to do, there are loads of combinators to do it, most notably liftM, fmap and (<$>), which are all the same (though liftM can be used in monads only): liftM :: Monad m => (a -> b) -> (m a -> m b) fmap :: Functor f => (a -> b) -> (f a -> f b) (<$>) :: Functor f => (a -> b) -> (f a -> f b) The subsUsingFile function can be implemented in one of the following ways: -- Raw: subsUsingFile fn ts = do content <- readFile fn return (subs content ts) -- Using lifting: subsUsingFile fn ts = liftM (`subs` ts) $ readFile fn subsUsingFile fn ts = fmap (`subs` ts) $ readFile fn subsUsingFile fn ts = (`subs` ts) <$> readFile fn Further note that you are overusing do-notation, even for nonmonadic code. Read section 6 of my tutorial [1] or a HaskellWiki article about this [2]. Whenever you see this pattern: do x <- c return (f x) you should consider using lifting: f <$> c and don't use do-notation if all you want to do is to make an equation: let x = y in ... especially when your code is not monadic. Your use of the do-notation in your 'subs' function works only incidentally, because it is indeed a monadic function, but not in the IO monad, but in the list monad. [1] http://ertes.de/articles/monads.html#section-9 [2] http://www.haskell.org/haskellwiki/Do_notation_considered_harmful Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

Hi prad! Reading the recent threads about Monads I decided to put my learning experience online. It might be of use to someone (maybe you?). http://codingcactus.wordpress.com/2010/08/16/writemonad1/ Regards, Thomas On 15.08.2010 19:52, prad wrote:
On Sun, 15 Aug 2010 16:43:09 +0200 Ertugrul Soeylemez
wrote: I'm not sure whether you are reading our posts, but we have explained in detail the difference. Once understood, you won't get errors like that anymore.
As a well meant suggestion, you have to actually read the answers to your posts, even if they are long.
ertugrul,
believe me i read the posts (more than a few times) - especially yours in fact and am very appreciative. however, it takes me a while to understand what's going on - even to connect similar ideas together. i certainly don't mind long posts either, but i am still having difficulties putting the ideas together. i tend to be a bit slow anyway and keep thinking in python terms.
i intend to respond once i understand the ideas better. for instance, what you wrote here made sense to me:
======== let readBlahTxt = readFile "blah.txt" content<- readBlahTxt
This should show the difference more clearly. ========
however, i still can't quite connect it to the idea of what it has to do with getting monad data out of a monad and into the pure realm. late last night, though, i was able to do so, but it took while.
Posting essentially the same questions over and over gets you nowhere.
agreed and i apologize. my problem is that i don't even see that it is the same question. as you have pointed out once before, "You're still thinking way too complicated."
i think what happens is i keep trying different things over and over again. that affects my thinking no doubt. i should likely think more and try less.
A monad is just a way to combine computations.
this wasn't clear to me till now even though i had read your continuing exchange with kyle and the example both of you were discussing regarding>>= (and i had read up on the operator and even tried it).
I don't like to mention my own one
i would very much like to see yours.
I agree with Brent
i think brent's delightful blog post describes my present dilemmas ... except i haven't quite gotten to the point of being able to say "monads are burritos" ... so i think there is likely still hope for me. ;)
participants (6)
-
Brandon S Allbery KF8NH
-
Ertugrul Soeylemez
-
John Obbele
-
Michael Mossey
-
prad
-
Thomas