(Newbie Question) How to get the value of an "IO String" Monad?

Hello, For the purpose of familiarizing myself with Haskell, and also because I love Haskell :), I am trying to re-make a script that I made in Python that sends a request to a server and extracts the list of email addresses from a Mailman web-page by using an XML Parser on the page's HTML that has been converted to XHTML by "HTML Tidy". However, I cannot seem to figure out a way to get the state of a Monad; Specifically I cannot get the value of an "IO String" Monad. I have read some tutorials on Monads but I guess I must have missed something. I have read that the >>= operator is the only way to extract the state of an action as a string, and pipe it to a function. So far so good. But, That does not seem to work, because as I understand the >>= operator, it expects the function on the right hand side to return an IO Monad, which completely defeats the purpose here. So, How am I supposed to get the value of an IO Monad, such as "IO String", without returning an IO Monad? If this is of any help, here is the function I am stuck on: recv_headers' :: Socket.Socket -> String -> IO [[String]] recv_headers' sock bulk | received == "" = error "Connection died unexpectedly." | received == "\n" && endswith bulk "\r\n\r" = return [["foo", "bar"]] | otherwise = recv_headers' sock (bulk ++ received) where received = (Socket.recv sock 1) --- End code --- And here is the (expected) error I get from trying to compare "IO String" to "String": MemberBackup.hs:29:18: Couldn't match `IO String' against `[Char]' Expected type: IO String Inferred type: [Char] In the second argument of `(==)', namely `""' In a pattern guard for the definition of `recv_headers'': received == "" Failed, modules loaded: none. --- End error --- Thanks for the help, Peter

You can access IO values only from within do blocks (see any tutorial, previous posts or google). It looks like this then: do= myvalue <- functionwhichreturnsIOValue dosomethingwith myvalue Due to monads you don't have to leave the IO monad this way. Oh. Have to go now. do is translated into >>= syntax, see do expansion. Hope this did help else wait for another longer answer ;-) Marc

Peter
So, How am I supposed to get the value of an IO Monad, such as "IO String", without returning an IO Monad?
Short answer: you don't. IO is a one way street. Build your application top down in the IO monad (starting with 'main'), and bottom up with pure code, and hope you can make them meet somewhere in the middle. :-) -k -- If I haven't seen further, it is by standing in the footprints of giants

On 2/17/06, Peter
Hello,
For the purpose of familiarizing myself with Haskell, and also because I love Haskell :), I am trying to re-make a script that I made in Python that sends a request to a server and extracts the list of email addresses from a Mailman web-page by using an XML Parser on the page's HTML that has been converted to XHTML by "HTML Tidy".
However, I cannot seem to figure out a way to get the state of a Monad; Specifically I cannot get the value of an "IO String" Monad.
I have read some tutorials on Monads but I guess I must have missed something.
I have read that the >>= operator is the only way to extract the state of an action as a string, and pipe it to a function. So far so good. But, That does not seem to work, because as I understand the >>= operator, it expects the function on the right hand side to return an IO Monad, which completely defeats the purpose here.
So, How am I supposed to get the value of an IO Monad, such as "IO String", without returning an IO Monad?
If this is of any help, here is the function I am stuck on: recv_headers' :: Socket.Socket -> String -> IO [[String]] recv_headers' sock bulk | received == "" = error "Connection died unexpectedly." | received == "\n" && endswith bulk "\r\n\r" = return [["foo", "bar"]] | otherwise = recv_headers' sock (bulk ++ received) where received = (Socket.recv sock 1)
Try: recv_headers' sock bulk = do received <- Socket.recv sock 1 case received of "" -> error ... "\n" | endswith bulk "\r\n\r" -> ... _ -> recv_headers' sock (bulk ++ received) -- Friendly, Lemmih

Hi, Am Freitag, 17. Februar 2006 14:42 schrieb Peter:
Hello,
For the purpose of familiarizing myself with Haskell, and also because I love Haskell :),
very good!
I am trying to re-make a script that I made in Python that sends a request to a server and extracts the list of email addresses from a Mailman web-page by using an XML Parser on the page's HTML that has been converted to XHTML by "HTML Tidy".
However, I cannot seem to figure out a way to get the state of a Monad; Specifically I cannot get the value of an "IO String" Monad.
I have read some tutorials on Monads but I guess I must have missed something.
I have read that the >>= operator is the only way to extract the state of an action as a string, and pipe it to a function. So far so good. But, That does not seem to work, because as I understand the >>= operator, it expects the function on the right hand side to return an IO Monad, which completely defeats the purpose here.
I find do-notation often more readable, then you write val <- action and val is an ordinary value, you can use afterwards (within the same do-block, of course)
So, How am I supposed to get the value of an IO Monad, such as "IO String", without returning an IO Monad?
If this is of any help, here is the function I am stuck on: recv_headers' :: Socket.Socket -> String -> IO [[String]] recv_headers' sock bulk
| received == "" = error "Connection died unexpectedly." | received == "\n"
&& endswith bulk "\r\n\r" = return [["foo", "bar"]]
| otherwise = recv_headers' sock (bulk ++ received)
where received = (Socket.recv sock 1) --- End code ---
This should do it: recv_headers' :: Socket.Socket -> String -> IO [[String]] recv_headers' sock bulk = do { received <- Socket.recv sock 1 ; case received of "" -> error "Connection died unexpectedly." "\n" | endswith bulk "\r\n\r" -> return [["foo", "bar"]] _ -> recv_headers' sock (bulk ++ received) } at least, it compiles.
And here is the (expected) error I get from trying to compare "IO String" to "String": MemberBackup.hs:29:18: Couldn't match `IO String' against `[Char]' Expected type: IO String Inferred type: [Char] In the second argument of `(==)', namely `""' In a pattern guard for the definition of `recv_headers'': received == "" Failed, modules loaded: none. --- End error ---
Thanks for the help, Peter
Cheers, Daniel -- "In My Egotistical Opinion, most people's C programs should be indented six feet downward and covered with dirt." -- Blair P. Houghton

Peter wrote:
So, How am I supposed to get the value of an IO Monad, such as "IO String", without returning an IO Monad?
You read correctly, this is impossible. You already got some valid answers, and here's another variant that preserves most of the nice guarded expressions: recv_headers' :: Socket.Socket -> String -> IO [[String]] recv_headers' sock bulk = Socket.recv sock 1 >>= dispatch where dispatch "" = error "Connection died unexpectedly." dispatch "\n" | endswith bulk "\r\n\r" = return [["foo", "bar"]] dispatch _ = recv_headers' sock (bulk ++ received) Udo. -- "Gadgets are not necessarily an improvement, vide the succession: Blackboard -> Overhead Projector -> PowerPoint" -- E. W. Dijkstra

Hi,
Apart from the other posts, you might also want to read
http://www.haskell.org/hawiki/IntroductionToIO which is a quick intro
to the way IO is handled in Haskell and
http://www.haskell.org/hawiki/UsingIo which covers similar ground, but
which also goes into a number of other common questions.
- Cale
On 17/02/06, Peter
Hello,
For the purpose of familiarizing myself with Haskell, and also because I love Haskell :), I am trying to re-make a script that I made in Python that sends a request to a server and extracts the list of email addresses from a Mailman web-page by using an XML Parser on the page's HTML that has been converted to XHTML by "HTML Tidy".
However, I cannot seem to figure out a way to get the state of a Monad; Specifically I cannot get the value of an "IO String" Monad.
I have read some tutorials on Monads but I guess I must have missed something.
I have read that the >>= operator is the only way to extract the state of an action as a string, and pipe it to a function. So far so good. But, That does not seem to work, because as I understand the >>= operator, it expects the function on the right hand side to return an IO Monad, which completely defeats the purpose here.
So, How am I supposed to get the value of an IO Monad, such as "IO String", without returning an IO Monad?
If this is of any help, here is the function I am stuck on: recv_headers' :: Socket.Socket -> String -> IO [[String]] recv_headers' sock bulk | received == "" = error "Connection died unexpectedly." | received == "\n" && endswith bulk "\r\n\r" = return [["foo", "bar"]] | otherwise = recv_headers' sock (bulk ++ received) where received = (Socket.recv sock 1) --- End code ---
And here is the (expected) error I get from trying to compare "IO String" to "String": MemberBackup.hs:29:18: Couldn't match `IO String' against `[Char]' Expected type: IO String Inferred type: [Char] In the second argument of `(==)', namely `""' In a pattern guard for the definition of `recv_headers'': received == "" Failed, modules loaded: none. --- End error ---
Thanks for the help, Peter
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (7)
-
Cale Gibbard
-
Daniel Fischer
-
Ketil Malde
-
Lemmih
-
Marc Weber
-
Peter
-
Udo Stenzel