
Hi again, Given the following code: g :: IO String -> IO String f :: [IO String] -> IO [ String ] f = mapM g The implementation of f is wrong because I would like to: 1. Make f behave lazy Its input list is made of lines read from stdin and I want it to process lines one by one as they are entered by the user. 2. Implement f such that it stops consuming items from the input list when the input item meets some condition. For example: isExit item = ("exit" == item) I tried to implement my own custom iteration by recursion but I got stuck in the combination of IO and list monads. Any help is appreciated. Thanks!

On Sun, Mar 31, 2013 at 4:26 PM, Ovidiu D
I tried to implement my own custom iteration by recursion but I got stuck in the combination of IO and list monads.
I think this is a good way to start. If you post the code you had, I'm sure you'll be able to get some help understanding what went wrong. -Karl

On Mon, Apr 1, 2013 at 6:26 AM, Ovidiu D
1. Make f behave lazy Its input list is made of lines read from stdin and I want it to process lines one by one as they are entered by the user.
Eschewing laziness (which adds only complexity in this case), here's something that'll work, if a little ugly: import System.Exit f :: String -> IO () f "exit" = exitSuccess f a = putStrLn $ "you entered: " ++ a main = do s <- getLine f s main Going down this path would involve IORef's, among others from the "sin bin". Something more pure and haskell-y would typically involve an analysis of the DSL abstract syntax and state space and implementation using a combination of State and Free monads. -- Kim-Ee

Thanks. Since this is an exercise I would be really curious what is the
idiomatic Haskell approach.
On Mon, Apr 1, 2013 at 3:29 AM, Kim-Ee Yeoh
On Mon, Apr 1, 2013 at 6:26 AM, Ovidiu D
wrote: 1. Make f behave lazy Its input list is made of lines read from stdin and I want it to process lines one by one as they are entered by the user.
Eschewing laziness (which adds only complexity in this case), here's something that'll work, if a little ugly:
import System.Exit
f :: String -> IO () f "exit" = exitSuccess f a = putStrLn $ "you entered: " ++ a
main = do s <- getLine f s main
Going down this path would involve IORef's, among others from the "sin bin".
Something more pure and haskell-y would typically involve an analysis of the DSL abstract syntax and state space and implementation using a combination of State and Free monads.
-- Kim-Ee
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I know you have the best intentions in writing this, but there are
pitfalls. Unexpected things happen when you interleave IO in this manner,
but nonetheless, here's how you would do it.
myGetLine = do
x <- getLine
if (x == "exit")
then return []
else do
xs <- unsafeInterleaveIO myGetLine
return (x:xs)
main = do
x <- myGetLine
print x
Just know that at some point you should learn to use conduits or pipes for
a much better approach to modeling things like this.
On Sun, Mar 31, 2013 at 7:26 PM, Ovidiu D
Hi again,
Given the following code:
g :: IO String -> IO String
f :: [IO String] -> IO [ String ] f = mapM g
The implementation of f is wrong because I would like to: 1. Make f behave lazy Its input list is made of lines read from stdin and I want it to process lines one by one as they are entered by the user.
2. Implement f such that it stops consuming items from the input list when the input item meets some condition. For example: isExit item = ("exit" == item)
I tried to implement my own custom iteration by recursion but I got stuck in the combination of IO and list monads.
Any help is appreciated.
Thanks!
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I'm not sure I understand what you mean by "I know you have the best
intentions in writing this, but there are pitfalls.". Anyway, here's the
code which doesn't work apparently because mapM is waiting for the whole
list before it goes further.
prompt = ">> "
commands :: [IO String]
commands = readCommand : commands
where readCommand = putStr prompt >> getLine
display :: Show a => [ a ] -> IO ()
display = mapM_ $ putStr . show
executeCommand :: String -> String
executeCommand = printf "Command not implemented: '%s'"
processCommands :: [IO String] -> IO [ String ]
processCommands = mapM processOneCommand
where processOneCommand cmd = cmd >>= (return . executeCommand )
main =
hSetBuffering stdout NoBuffering
>> processCommands commands
>>= display
This is just for learning purposes and I'm looking for the "haskell way to
do it". My intention is to write the function processCommands such that it
takes the decision to either fetch the next command from the command list
(i.e. console) or to exit the application.
Regarding your comment "Just know that at some point you should learn to
use conduits or pipes for a much better approach to modeling things like
this.". Can you point me to some documentation?
Thanks!
On Mon, Apr 1, 2013 at 3:53 AM, David McBride
I know you have the best intentions in writing this, but there are pitfalls. Unexpected things happen when you interleave IO in this manner, but nonetheless, here's how you would do it.
myGetLine = do x <- getLine if (x == "exit") then return [] else do xs <- unsafeInterleaveIO myGetLine return (x:xs)
main = do x <- myGetLine print x
Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.
On Sun, Mar 31, 2013 at 7:26 PM, Ovidiu D
wrote: Hi again,
Given the following code:
g :: IO String -> IO String
f :: [IO String] -> IO [ String ] f = mapM g
The implementation of f is wrong because I would like to: 1. Make f behave lazy Its input list is made of lines read from stdin and I want it to process lines one by one as they are entered by the user.
2. Implement f such that it stops consuming items from the input list when the input item meets some condition. For example: isExit item = ("exit" == item)
I tried to implement my own custom iteration by recursion but I got stuck in the combination of IO and list monads.
Any help is appreciated.
Thanks!
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Doing it the way you are trying to do it breaks the IO abstraction. In
order to do it you'd have to use unsafe functions. Unsafe functions are
bad. I'm not going to explain why but they tend to bite you as your
program gets more complex and weirdness starts to occur, like threads
ceasing operation while awaiting input is something that bit me when I went
down that route. So let me explain how I would do it using both pipes and
conduits as examples:
import Data.Conduit as C hiding ((>+>), runPipe)
import System.IO
import Control.Monad.Trans
import Text.Printf.Mauke
import Control.Pipe as P
import Control.Monad (forever)
-- Source runs in the IO monad and produces Strings
commandSource :: Source IO String
commandSource = do
command <- liftIO getLine
if command == "exit"
then return ()
else do
C.yield command
commandSource -- loop to fetching new values to send down the pipe
-- Sink runs in the IO monad and takes any printfable argument and returns
() when pipe completes.
displaySink :: PrintfArg a => Sink a IO ()
displaySink = do
m <- C.await
case m of
Nothing -> return () -- if nothing comes in, just exit
Just x -> do
liftIO $ printf "Command not implemented (conduit): '%s'\n" x
displaySink
main = do
hSetBuffering stdout NoBuffering
commandSource $$ displaySink
runPipe $ commandProducer >+> displayConsumer
commandProducer :: PrintfArg a => Producer a String IO ()
commandProducer = do
x <- lift getLine
if x == "exit"
then return ()
else P.yield x >> commandProducer
displayConsumer :: Consumer String IO ()
displayConsumer = forever $ P.await >>= lift . printf "Command not
implemented (pipes): '%s'\n"
There are some utility function to shorten some of these definitions a bit
in conduit. These two examples are equivalent. But basically you are
creating a pipeline, the first of which gets commands until it gets an exit
and then sends them down the pipeline (as a string). The second piece of
the pipe accepts anything that is printfable and prints it. It will stop
when the upstream stops sending it strings to print. The point here is
that you have little functions that you can compose together with other
functions and create something bigger where none of the pieces interfere
with each other or break the IO abstraction.
As to which of these libraries you should try? Conduits is a bit more
straight forward and has a lot more documentation and supporting
libraries. Pipes is a lot more flexible in that you could send things both
directions along the pipe in the future when you become proficient with the
library.
On Sun, Mar 31, 2013 at 9:38 PM, Ovidiu D
I'm not sure I understand what you mean by "I know you have the best intentions in writing this, but there are pitfalls.". Anyway, here's the code which doesn't work apparently because mapM is waiting for the whole list before it goes further.
prompt = ">> "
commands :: [IO String] commands = readCommand : commands where readCommand = putStr prompt >> getLine
display :: Show a => [ a ] -> IO () display = mapM_ $ putStr . show
executeCommand :: String -> String executeCommand = printf "Command not implemented: '%s'"
processCommands :: [IO String] -> IO [ String ] processCommands = mapM processOneCommand where processOneCommand cmd = cmd >>= (return . executeCommand )
main = hSetBuffering stdout NoBuffering >> processCommands commands >>= display
This is just for learning purposes and I'm looking for the "haskell way to do it". My intention is to write the function processCommands such that it takes the decision to either fetch the next command from the command list (i.e. console) or to exit the application.
Regarding your comment "Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.". Can you point me to some documentation?
Thanks!
On Mon, Apr 1, 2013 at 3:53 AM, David McBride
wrote: I know you have the best intentions in writing this, but there are pitfalls. Unexpected things happen when you interleave IO in this manner, but nonetheless, here's how you would do it.
myGetLine = do x <- getLine if (x == "exit") then return [] else do xs <- unsafeInterleaveIO myGetLine return (x:xs)
main = do x <- myGetLine print x
Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.
On Sun, Mar 31, 2013 at 7:26 PM, Ovidiu D
wrote: Hi again,
Given the following code:
g :: IO String -> IO String
f :: [IO String] -> IO [ String ] f = mapM g
The implementation of f is wrong because I would like to: 1. Make f behave lazy Its input list is made of lines read from stdin and I want it to process lines one by one as they are entered by the user.
2. Implement f such that it stops consuming items from the input list when the input item meets some condition. For example: isExit item = ("exit" == item)
I tried to implement my own custom iteration by recursion but I got stuck in the combination of IO and list monads.
Any help is appreciated.
Thanks!
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I'm sorry I jacked up the code editing my email inline, the pipes section
below main should look like this:
commandProducer :: Producer String IO ()
commandProducer = do
x <- lift getLine
if x == "exit"
then return ()
else P.yield x >> commandProducer
displayConsumer :: PrintfArg a => Consumer a IO ()
displayConsumer = forever $ P.await >>= lift . printf "Command not
implemented (pipes): '%s'\n"
On Sun, Mar 31, 2013 at 10:49 PM, David McBride
Doing it the way you are trying to do it breaks the IO abstraction. In order to do it you'd have to use unsafe functions. Unsafe functions are bad. I'm not going to explain why but they tend to bite you as your program gets more complex and weirdness starts to occur, like threads ceasing operation while awaiting input is something that bit me when I went down that route. So let me explain how I would do it using both pipes and conduits as examples:
import Data.Conduit as C hiding ((>+>), runPipe) import System.IO import Control.Monad.Trans import Text.Printf.Mauke
import Control.Pipe as P import Control.Monad (forever)
-- Source runs in the IO monad and produces Strings commandSource :: Source IO String commandSource = do command <- liftIO getLine if command == "exit" then return () else do C.yield command commandSource -- loop to fetching new values to send down the pipe
-- Sink runs in the IO monad and takes any printfable argument and returns () when pipe completes. displaySink :: PrintfArg a => Sink a IO () displaySink = do m <- C.await case m of Nothing -> return () -- if nothing comes in, just exit Just x -> do liftIO $ printf "Command not implemented (conduit): '%s'\n" x displaySink
main = do hSetBuffering stdout NoBuffering commandSource $$ displaySink runPipe $ commandProducer >+> displayConsumer
commandProducer :: PrintfArg a => Producer a String IO () commandProducer = do x <- lift getLine if x == "exit" then return () else P.yield x >> commandProducer
displayConsumer :: Consumer String IO () displayConsumer = forever $ P.await >>= lift . printf "Command not implemented (pipes): '%s'\n"
There are some utility function to shorten some of these definitions a bit in conduit. These two examples are equivalent. But basically you are creating a pipeline, the first of which gets commands until it gets an exit and then sends them down the pipeline (as a string). The second piece of the pipe accepts anything that is printfable and prints it. It will stop when the upstream stops sending it strings to print. The point here is that you have little functions that you can compose together with other functions and create something bigger where none of the pieces interfere with each other or break the IO abstraction.
As to which of these libraries you should try? Conduits is a bit more straight forward and has a lot more documentation and supporting libraries. Pipes is a lot more flexible in that you could send things both directions along the pipe in the future when you become proficient with the library.
On Sun, Mar 31, 2013 at 9:38 PM, Ovidiu D
wrote: I'm not sure I understand what you mean by "I know you have the best intentions in writing this, but there are pitfalls.". Anyway, here's the code which doesn't work apparently because mapM is waiting for the whole list before it goes further.
prompt = ">> "
commands :: [IO String] commands = readCommand : commands where readCommand = putStr prompt >> getLine
display :: Show a => [ a ] -> IO () display = mapM_ $ putStr . show
executeCommand :: String -> String executeCommand = printf "Command not implemented: '%s'"
processCommands :: [IO String] -> IO [ String ] processCommands = mapM processOneCommand where processOneCommand cmd = cmd >>= (return . executeCommand )
main = hSetBuffering stdout NoBuffering >> processCommands commands >>= display
This is just for learning purposes and I'm looking for the "haskell way to do it". My intention is to write the function processCommands such that it takes the decision to either fetch the next command from the command list (i.e. console) or to exit the application.
Regarding your comment "Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.". Can you point me to some documentation?
Thanks!
On Mon, Apr 1, 2013 at 3:53 AM, David McBride
wrote: I know you have the best intentions in writing this, but there are pitfalls. Unexpected things happen when you interleave IO in this manner, but nonetheless, here's how you would do it.
myGetLine = do x <- getLine if (x == "exit") then return [] else do xs <- unsafeInterleaveIO myGetLine return (x:xs)
main = do x <- myGetLine print x
Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.
On Sun, Mar 31, 2013 at 7:26 PM, Ovidiu D
wrote: Hi again,
Given the following code:
g :: IO String -> IO String
f :: [IO String] -> IO [ String ] f = mapM g
The implementation of f is wrong because I would like to: 1. Make f behave lazy Its input list is made of lines read from stdin and I want it to process lines one by one as they are entered by the user.
2. Implement f such that it stops consuming items from the input list when the input item meets some condition. For example: isExit item = ("exit" == item)
I tried to implement my own custom iteration by recursion but I got stuck in the combination of IO and list monads.
Any help is appreciated.
Thanks!
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I managed to compile and it works but I don't full understand all the type
details. I'll have to dig into Pipes and Conduits.
Thanks a lot for the code!
On Mon, Apr 1, 2013 at 5:51 AM, David McBride
I'm sorry I jacked up the code editing my email inline, the pipes section below main should look like this:
commandProducer :: Producer String IO ()
commandProducer = do x <- lift getLine if x == "exit" then return () else P.yield x >> commandProducer
displayConsumer :: PrintfArg a => Consumer a IO ()
displayConsumer = forever $ P.await >>= lift . printf "Command not implemented (pipes): '%s'\n"
On Sun, Mar 31, 2013 at 10:49 PM, David McBride
wrote: Doing it the way you are trying to do it breaks the IO abstraction. In order to do it you'd have to use unsafe functions. Unsafe functions are bad. I'm not going to explain why but they tend to bite you as your program gets more complex and weirdness starts to occur, like threads ceasing operation while awaiting input is something that bit me when I went down that route. So let me explain how I would do it using both pipes and conduits as examples:
import Data.Conduit as C hiding ((>+>), runPipe) import System.IO import Control.Monad.Trans import Text.Printf.Mauke
import Control.Pipe as P import Control.Monad (forever)
-- Source runs in the IO monad and produces Strings commandSource :: Source IO String commandSource = do command <- liftIO getLine if command == "exit" then return () else do C.yield command commandSource -- loop to fetching new values to send down the pipe
-- Sink runs in the IO monad and takes any printfable argument and returns () when pipe completes. displaySink :: PrintfArg a => Sink a IO () displaySink = do m <- C.await case m of Nothing -> return () -- if nothing comes in, just exit Just x -> do liftIO $ printf "Command not implemented (conduit): '%s'\n" x displaySink
main = do hSetBuffering stdout NoBuffering commandSource $$ displaySink runPipe $ commandProducer >+> displayConsumer
commandProducer :: PrintfArg a => Producer a String IO () commandProducer = do x <- lift getLine if x == "exit" then return () else P.yield x >> commandProducer
displayConsumer :: Consumer String IO () displayConsumer = forever $ P.await >>= lift . printf "Command not implemented (pipes): '%s'\n"
There are some utility function to shorten some of these definitions a bit in conduit. These two examples are equivalent. But basically you are creating a pipeline, the first of which gets commands until it gets an exit and then sends them down the pipeline (as a string). The second piece of the pipe accepts anything that is printfable and prints it. It will stop when the upstream stops sending it strings to print. The point here is that you have little functions that you can compose together with other functions and create something bigger where none of the pieces interfere with each other or break the IO abstraction.
As to which of these libraries you should try? Conduits is a bit more straight forward and has a lot more documentation and supporting libraries. Pipes is a lot more flexible in that you could send things both directions along the pipe in the future when you become proficient with the library.
On Sun, Mar 31, 2013 at 9:38 PM, Ovidiu D
wrote: I'm not sure I understand what you mean by "I know you have the best intentions in writing this, but there are pitfalls.". Anyway, here's the code which doesn't work apparently because mapM is waiting for the whole list before it goes further.
prompt = ">> "
commands :: [IO String] commands = readCommand : commands where readCommand = putStr prompt >> getLine
display :: Show a => [ a ] -> IO () display = mapM_ $ putStr . show
executeCommand :: String -> String executeCommand = printf "Command not implemented: '%s'"
processCommands :: [IO String] -> IO [ String ] processCommands = mapM processOneCommand where processOneCommand cmd = cmd >>= (return . executeCommand )
main = hSetBuffering stdout NoBuffering >> processCommands commands >>= display
This is just for learning purposes and I'm looking for the "haskell way to do it". My intention is to write the function processCommands such that it takes the decision to either fetch the next command from the command list (i.e. console) or to exit the application.
Regarding your comment "Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.". Can you point me to some documentation?
Thanks!
On Mon, Apr 1, 2013 at 3:53 AM, David McBride
wrote: I know you have the best intentions in writing this, but there are pitfalls. Unexpected things happen when you interleave IO in this manner, but nonetheless, here's how you would do it.
myGetLine = do x <- getLine if (x == "exit") then return [] else do xs <- unsafeInterleaveIO myGetLine return (x:xs)
main = do x <- myGetLine print x
Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.
On Sun, Mar 31, 2013 at 7:26 PM, Ovidiu D
wrote: Hi again,
Given the following code:
g :: IO String -> IO String
f :: [IO String] -> IO [ String ] f = mapM g
The implementation of f is wrong because I would like to: 1. Make f behave lazy Its input list is made of lines read from stdin and I want it to process lines one by one as they are entered by the user.
2. Implement f such that it stops consuming items from the input list when the input item meets some condition. For example: isExit item = ("exit" == item)
I tried to implement my own custom iteration by recursion but I got stuck in the combination of IO and list monads.
Any help is appreciated.
Thanks!
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Trying to understand the conduits and looking for "the clean way to do it"
I got to the code below (based on David's conduit example).
I'm quite happy with the result. My problem is that I had to write
functions like conduitTakeWhile and conduitSource (see them at the bottom
of the code). Are there any functions like this in the conduit library
which I'm missing somehow? Is there a way to emulate this behaviour with
the existing functions from conduit package?
import Data.Conduit
import Data.Conduit.List as L
import System.IO
import Control.Monad.Trans
main = do
hSetBuffering stdout NoBuffering
runProcessPipe
runProcessPipe =
conduitSource readCommand
$= conduitTakeWhile ( "exit" /=)
=$= L.map processCommand
$$ L.mapM_ $ putStr.unlines
readCommand :: IO (Maybe String)
readCommand = do
putStr ">> "
isEof <- hIsEOF stdin
if isEof
then return Nothing
else getLine >>= return . Just
processCommand cmd = ["reversed string:",reverse cmd]
-- Utilities
conduitSource :: Monad m => (m (Maybe a)) -> Source m a
conduitSource f = do
v <- lift f
case v of
Nothing -> return ()
Just x -> yield x >> conduitSource f
conduitTakeWhile :: Monad m => ( a -> Bool ) -> Conduit a m a
conduitTakeWhile p = do
cmd <- await
case cmd of
Nothing -> return ()
Just v -> do
if p v
then yield v >> conduitTakeWhile p
else return ()
On Wed, Apr 3, 2013 at 12:05 AM, Ovidiu D
I managed to compile and it works but I don't full understand all the type details. I'll have to dig into Pipes and Conduits.
Thanks a lot for the code!
On Mon, Apr 1, 2013 at 5:51 AM, David McBride
wrote: I'm sorry I jacked up the code editing my email inline, the pipes section below main should look like this:
commandProducer :: Producer String IO ()
commandProducer = do x <- lift getLine if x == "exit" then return () else P.yield x >> commandProducer
displayConsumer :: PrintfArg a => Consumer a IO ()
displayConsumer = forever $ P.await >>= lift . printf "Command not implemented (pipes): '%s'\n"
On Sun, Mar 31, 2013 at 10:49 PM, David McBride
wrote: Doing it the way you are trying to do it breaks the IO abstraction. In order to do it you'd have to use unsafe functions. Unsafe functions are bad. I'm not going to explain why but they tend to bite you as your program gets more complex and weirdness starts to occur, like threads ceasing operation while awaiting input is something that bit me when I went down that route. So let me explain how I would do it using both pipes and conduits as examples:
import Data.Conduit as C hiding ((>+>), runPipe) import System.IO import Control.Monad.Trans import Text.Printf.Mauke
import Control.Pipe as P import Control.Monad (forever)
-- Source runs in the IO monad and produces Strings commandSource :: Source IO String commandSource = do command <- liftIO getLine if command == "exit" then return () else do C.yield command commandSource -- loop to fetching new values to send down the pipe
-- Sink runs in the IO monad and takes any printfable argument and returns () when pipe completes. displaySink :: PrintfArg a => Sink a IO () displaySink = do m <- C.await case m of Nothing -> return () -- if nothing comes in, just exit Just x -> do liftIO $ printf "Command not implemented (conduit): '%s'\n" x displaySink
main = do hSetBuffering stdout NoBuffering commandSource $$ displaySink runPipe $ commandProducer >+> displayConsumer
commandProducer :: PrintfArg a => Producer a String IO () commandProducer = do x <- lift getLine if x == "exit" then return () else P.yield x >> commandProducer
displayConsumer :: Consumer String IO () displayConsumer = forever $ P.await >>= lift . printf "Command not implemented (pipes): '%s'\n"
There are some utility function to shorten some of these definitions a bit in conduit. These two examples are equivalent. But basically you are creating a pipeline, the first of which gets commands until it gets an exit and then sends them down the pipeline (as a string). The second piece of the pipe accepts anything that is printfable and prints it. It will stop when the upstream stops sending it strings to print. The point here is that you have little functions that you can compose together with other functions and create something bigger where none of the pieces interfere with each other or break the IO abstraction.
As to which of these libraries you should try? Conduits is a bit more straight forward and has a lot more documentation and supporting libraries. Pipes is a lot more flexible in that you could send things both directions along the pipe in the future when you become proficient with the library.
On Sun, Mar 31, 2013 at 9:38 PM, Ovidiu D
wrote: I'm not sure I understand what you mean by "I know you have the best intentions in writing this, but there are pitfalls.". Anyway, here's the code which doesn't work apparently because mapM is waiting for the whole list before it goes further.
prompt = ">> "
commands :: [IO String] commands = readCommand : commands where readCommand = putStr prompt >> getLine
display :: Show a => [ a ] -> IO () display = mapM_ $ putStr . show
executeCommand :: String -> String executeCommand = printf "Command not implemented: '%s'"
processCommands :: [IO String] -> IO [ String ] processCommands = mapM processOneCommand where processOneCommand cmd = cmd >>= (return . executeCommand )
main = hSetBuffering stdout NoBuffering >> processCommands commands >>= display
This is just for learning purposes and I'm looking for the "haskell way to do it". My intention is to write the function processCommands such that it takes the decision to either fetch the next command from the command list (i.e. console) or to exit the application.
Regarding your comment "Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.". Can you point me to some documentation?
Thanks!
On Mon, Apr 1, 2013 at 3:53 AM, David McBride
wrote: I know you have the best intentions in writing this, but there are pitfalls. Unexpected things happen when you interleave IO in this manner, but nonetheless, here's how you would do it.
myGetLine = do x <- getLine if (x == "exit") then return [] else do xs <- unsafeInterleaveIO myGetLine return (x:xs)
main = do x <- myGetLine print x
Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.
On Sun, Mar 31, 2013 at 7:26 PM, Ovidiu D
wrote: Hi again,
Given the following code:
g :: IO String -> IO String
f :: [IO String] -> IO [ String ] f = mapM g
The implementation of f is wrong because I would like to: 1. Make f behave lazy Its input list is made of lines read from stdin and I want it to process lines one by one as they are entered by the user.
2. Implement f such that it stops consuming items from the input list when the input item meets some condition. For example: isExit item = ("exit" == item)
I tried to implement my own custom iteration by recursion but I got stuck in the combination of IO and list monads.
Any help is appreciated.
Thanks!
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Actually, I'm not sure there is. I can make a few minor improvements, but
that's about it. When chaining conduits together, they are kind of weird,
but a general way that I string them together would be like this:
runProcessPipe =
conduitSource readCommand
$= conduitTakeWhile ( "exit" /=)
$= CL.map processCommand
$$ CL.mapM_ (putStr . unlines)
Where each source combines with a conduit to make a new source, which
combines with next conduit, etc and then the last sink uses a $$ to finish
it off. But other than that I think you have a handle on it.
On Tue, Apr 2, 2013 at 8:39 PM, Ovidiu D
Trying to understand the conduits and looking for "the clean way to do it" I got to the code below (based on David's conduit example).
I'm quite happy with the result. My problem is that I had to write functions like conduitTakeWhile and conduitSource (see them at the bottom of the code). Are there any functions like this in the conduit library which I'm missing somehow? Is there a way to emulate this behaviour with the existing functions from conduit package?
import Data.Conduit import Data.Conduit.List as L import System.IO import Control.Monad.Trans
main = do hSetBuffering stdout NoBuffering runProcessPipe
runProcessPipe = conduitSource readCommand $= conduitTakeWhile ( "exit" /=) =$= L.map processCommand $$ L.mapM_ $ putStr.unlines
readCommand :: IO (Maybe String) readCommand = do putStr ">> " isEof <- hIsEOF stdin if isEof then return Nothing else getLine >>= return . Just
processCommand cmd = ["reversed string:",reverse cmd]
-- Utilities
conduitSource :: Monad m => (m (Maybe a)) -> Source m a conduitSource f = do v <- lift f
case v of Nothing -> return () Just x -> yield x >> conduitSource f
conduitTakeWhile :: Monad m => ( a -> Bool ) -> Conduit a m a conduitTakeWhile p = do cmd <- await case cmd of Nothing -> return () Just v -> do if p v then yield v >> conduitTakeWhile p else return ()
On Wed, Apr 3, 2013 at 12:05 AM, Ovidiu D
wrote: I managed to compile and it works but I don't full understand all the type details. I'll have to dig into Pipes and Conduits.
Thanks a lot for the code!
On Mon, Apr 1, 2013 at 5:51 AM, David McBride
wrote: I'm sorry I jacked up the code editing my email inline, the pipes section below main should look like this:
commandProducer :: Producer String IO ()
commandProducer = do x <- lift getLine if x == "exit" then return () else P.yield x >> commandProducer
displayConsumer :: PrintfArg a => Consumer a IO ()
displayConsumer = forever $ P.await >>= lift . printf "Command not implemented (pipes): '%s'\n"
On Sun, Mar 31, 2013 at 10:49 PM, David McBride
wrote: Doing it the way you are trying to do it breaks the IO abstraction. In order to do it you'd have to use unsafe functions. Unsafe functions are bad. I'm not going to explain why but they tend to bite you as your program gets more complex and weirdness starts to occur, like threads ceasing operation while awaiting input is something that bit me when I went down that route. So let me explain how I would do it using both pipes and conduits as examples:
import Data.Conduit as C hiding ((>+>), runPipe) import System.IO import Control.Monad.Trans import Text.Printf.Mauke
import Control.Pipe as P import Control.Monad (forever)
-- Source runs in the IO monad and produces Strings commandSource :: Source IO String commandSource = do command <- liftIO getLine if command == "exit" then return () else do C.yield command commandSource -- loop to fetching new values to send down the pipe
-- Sink runs in the IO monad and takes any printfable argument and returns () when pipe completes. displaySink :: PrintfArg a => Sink a IO () displaySink = do m <- C.await case m of Nothing -> return () -- if nothing comes in, just exit Just x -> do liftIO $ printf "Command not implemented (conduit): '%s'\n" x displaySink
main = do hSetBuffering stdout NoBuffering commandSource $$ displaySink runPipe $ commandProducer >+> displayConsumer
commandProducer :: PrintfArg a => Producer a String IO () commandProducer = do x <- lift getLine if x == "exit" then return () else P.yield x >> commandProducer
displayConsumer :: Consumer String IO () displayConsumer = forever $ P.await >>= lift . printf "Command not implemented (pipes): '%s'\n"
There are some utility function to shorten some of these definitions a bit in conduit. These two examples are equivalent. But basically you are creating a pipeline, the first of which gets commands until it gets an exit and then sends them down the pipeline (as a string). The second piece of the pipe accepts anything that is printfable and prints it. It will stop when the upstream stops sending it strings to print. The point here is that you have little functions that you can compose together with other functions and create something bigger where none of the pieces interfere with each other or break the IO abstraction.
As to which of these libraries you should try? Conduits is a bit more straight forward and has a lot more documentation and supporting libraries. Pipes is a lot more flexible in that you could send things both directions along the pipe in the future when you become proficient with the library.
On Sun, Mar 31, 2013 at 9:38 PM, Ovidiu D
wrote: I'm not sure I understand what you mean by "I know you have the best intentions in writing this, but there are pitfalls.". Anyway, here's the code which doesn't work apparently because mapM is waiting for the whole list before it goes further.
prompt = ">> "
commands :: [IO String] commands = readCommand : commands where readCommand = putStr prompt >> getLine
display :: Show a => [ a ] -> IO () display = mapM_ $ putStr . show
executeCommand :: String -> String executeCommand = printf "Command not implemented: '%s'"
processCommands :: [IO String] -> IO [ String ] processCommands = mapM processOneCommand where processOneCommand cmd = cmd >>= (return . executeCommand )
main = hSetBuffering stdout NoBuffering >> processCommands commands >>= display
This is just for learning purposes and I'm looking for the "haskell way to do it". My intention is to write the function processCommands such that it takes the decision to either fetch the next command from the command list (i.e. console) or to exit the application.
Regarding your comment "Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.". Can you point me to some documentation?
Thanks!
On Mon, Apr 1, 2013 at 3:53 AM, David McBride
wrote: I know you have the best intentions in writing this, but there are pitfalls. Unexpected things happen when you interleave IO in this manner, but nonetheless, here's how you would do it.
myGetLine = do x <- getLine if (x == "exit") then return [] else do xs <- unsafeInterleaveIO myGetLine return (x:xs)
main = do x <- myGetLine print x
Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.
On Sun, Mar 31, 2013 at 7:26 PM, Ovidiu D
wrote: > Hi again, > > Given the following code: > > g :: IO String -> IO String > > f :: [IO String] -> IO [ String ] > f = mapM g > > The implementation of f is wrong because I would like to: > 1. Make f behave lazy > Its input list is made of lines read from stdin and I want it to > process lines one by one as they are entered by the user. > > 2. Implement f such that it stops consuming items from the input > list when the input item meets some condition. For example: > isExit item = ("exit" == item) > > I tried to implement my own custom iteration by recursion but I got > stuck in the combination of IO and list monads. > > Any help is appreciated. > > Thanks! > > > _______________________________________________ > Beginners mailing list > Beginners@haskell.org > http://www.haskell.org/mailman/listinfo/beginners > >
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

OK. Thanks for the help and see you around!
On Wed, Apr 3, 2013 at 4:50 AM, David McBride
Actually, I'm not sure there is. I can make a few minor improvements, but that's about it. When chaining conduits together, they are kind of weird, but a general way that I string them together would be like this:
runProcessPipe = conduitSource readCommand $= conduitTakeWhile ( "exit" /=) $= CL.map processCommand $$ CL.mapM_ (putStr . unlines)
Where each source combines with a conduit to make a new source, which combines with next conduit, etc and then the last sink uses a $$ to finish it off. But other than that I think you have a handle on it.
On Tue, Apr 2, 2013 at 8:39 PM, Ovidiu D
wrote: Trying to understand the conduits and looking for "the clean way to do it" I got to the code below (based on David's conduit example).
I'm quite happy with the result. My problem is that I had to write functions like conduitTakeWhile and conduitSource (see them at the bottom of the code). Are there any functions like this in the conduit library which I'm missing somehow? Is there a way to emulate this behaviour with the existing functions from conduit package?
import Data.Conduit import Data.Conduit.List as L import System.IO import Control.Monad.Trans
main = do hSetBuffering stdout NoBuffering runProcessPipe
runProcessPipe = conduitSource readCommand $= conduitTakeWhile ( "exit" /=) =$= L.map processCommand $$ L.mapM_ $ putStr.unlines
readCommand :: IO (Maybe String) readCommand = do putStr ">> " isEof <- hIsEOF stdin if isEof then return Nothing else getLine >>= return . Just
processCommand cmd = ["reversed string:",reverse cmd]
-- Utilities
conduitSource :: Monad m => (m (Maybe a)) -> Source m a conduitSource f = do v <- lift f
case v of Nothing -> return () Just x -> yield x >> conduitSource f
conduitTakeWhile :: Monad m => ( a -> Bool ) -> Conduit a m a conduitTakeWhile p = do cmd <- await case cmd of Nothing -> return () Just v -> do if p v then yield v >> conduitTakeWhile p else return ()
On Wed, Apr 3, 2013 at 12:05 AM, Ovidiu D
wrote: I managed to compile and it works but I don't full understand all the type details. I'll have to dig into Pipes and Conduits.
Thanks a lot for the code!
On Mon, Apr 1, 2013 at 5:51 AM, David McBride
wrote: I'm sorry I jacked up the code editing my email inline, the pipes section below main should look like this:
commandProducer :: Producer String IO ()
commandProducer = do x <- lift getLine if x == "exit" then return () else P.yield x >> commandProducer
displayConsumer :: PrintfArg a => Consumer a IO ()
displayConsumer = forever $ P.await >>= lift . printf "Command not implemented (pipes): '%s'\n"
On Sun, Mar 31, 2013 at 10:49 PM, David McBride
wrote: Doing it the way you are trying to do it breaks the IO abstraction. In order to do it you'd have to use unsafe functions. Unsafe functions are bad. I'm not going to explain why but they tend to bite you as your program gets more complex and weirdness starts to occur, like threads ceasing operation while awaiting input is something that bit me when I went down that route. So let me explain how I would do it using both pipes and conduits as examples:
import Data.Conduit as C hiding ((>+>), runPipe) import System.IO import Control.Monad.Trans import Text.Printf.Mauke
import Control.Pipe as P import Control.Monad (forever)
-- Source runs in the IO monad and produces Strings commandSource :: Source IO String commandSource = do command <- liftIO getLine if command == "exit" then return () else do C.yield command commandSource -- loop to fetching new values to send down the pipe
-- Sink runs in the IO monad and takes any printfable argument and returns () when pipe completes. displaySink :: PrintfArg a => Sink a IO () displaySink = do m <- C.await case m of Nothing -> return () -- if nothing comes in, just exit Just x -> do liftIO $ printf "Command not implemented (conduit): '%s'\n" x displaySink
main = do hSetBuffering stdout NoBuffering commandSource $$ displaySink runPipe $ commandProducer >+> displayConsumer
commandProducer :: PrintfArg a => Producer a String IO () commandProducer = do x <- lift getLine if x == "exit" then return () else P.yield x >> commandProducer
displayConsumer :: Consumer String IO () displayConsumer = forever $ P.await >>= lift . printf "Command not implemented (pipes): '%s'\n"
There are some utility function to shorten some of these definitions a bit in conduit. These two examples are equivalent. But basically you are creating a pipeline, the first of which gets commands until it gets an exit and then sends them down the pipeline (as a string). The second piece of the pipe accepts anything that is printfable and prints it. It will stop when the upstream stops sending it strings to print. The point here is that you have little functions that you can compose together with other functions and create something bigger where none of the pieces interfere with each other or break the IO abstraction.
As to which of these libraries you should try? Conduits is a bit more straight forward and has a lot more documentation and supporting libraries. Pipes is a lot more flexible in that you could send things both directions along the pipe in the future when you become proficient with the library.
On Sun, Mar 31, 2013 at 9:38 PM, Ovidiu D
wrote: I'm not sure I understand what you mean by "I know you have the best intentions in writing this, but there are pitfalls.". Anyway, here's the code which doesn't work apparently because mapM is waiting for the whole list before it goes further.
prompt = ">> "
commands :: [IO String] commands = readCommand : commands where readCommand = putStr prompt >> getLine
display :: Show a => [ a ] -> IO () display = mapM_ $ putStr . show
executeCommand :: String -> String executeCommand = printf "Command not implemented: '%s'"
processCommands :: [IO String] -> IO [ String ] processCommands = mapM processOneCommand where processOneCommand cmd = cmd >>= (return . executeCommand )
main = hSetBuffering stdout NoBuffering >> processCommands commands >>= display
This is just for learning purposes and I'm looking for the "haskell way to do it". My intention is to write the function processCommands such that it takes the decision to either fetch the next command from the command list (i.e. console) or to exit the application.
Regarding your comment "Just know that at some point you should learn to use conduits or pipes for a much better approach to modeling things like this.". Can you point me to some documentation?
Thanks!
On Mon, Apr 1, 2013 at 3:53 AM, David McBride
wrote: > I know you have the best intentions in writing this, but there are > pitfalls. Unexpected things happen when you interleave IO in this manner, > but nonetheless, here's how you would do it. > > myGetLine = do > x <- getLine > if (x == "exit") > then return [] > else do > xs <- unsafeInterleaveIO myGetLine > return (x:xs) > > main = do > x <- myGetLine > print x > > Just know that at some point you should learn to use conduits or > pipes for a much better approach to modeling things like this. > > > > On Sun, Mar 31, 2013 at 7:26 PM, Ovidiu D
wrote: > >> Hi again, >> >> Given the following code: >> >> g :: IO String -> IO String >> >> f :: [IO String] -> IO [ String ] >> f = mapM g >> >> The implementation of f is wrong because I would like to: >> 1. Make f behave lazy >> Its input list is made of lines read from stdin and I want it to >> process lines one by one as they are entered by the user. >> >> 2. Implement f such that it stops consuming items from the input >> list when the input item meets some condition. For example: >> isExit item = ("exit" == item) >> >> I tried to implement my own custom iteration by recursion but I got >> stuck in the combination of IO and list monads. >> >> Any help is appreciated. >> >> Thanks! >> >> >> _______________________________________________ >> Beginners mailing list >> Beginners@haskell.org >> http://www.haskell.org/mailman/listinfo/beginners >> >> > > _______________________________________________ > Beginners mailing list > Beginners@haskell.org > http://www.haskell.org/mailman/listinfo/beginners > > _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (4)
-
David McBride
-
Karl Voelker
-
Kim-Ee Yeoh
-
Ovidiu D