[Haskell-beginners] lazy mapM
David McBride
toad3k at gmail.com
Mon Apr 1 04:51:27 CEST 2013
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 <toad3k at gmail.com> 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 <ovidiudeac at gmail.com> 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 <toad3k at gmail.com> 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 <ovidiudeac at gmail.com> 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 at haskell.org
>>>> http://www.haskell.org/mailman/listinfo/beginners
>>>>
>>>>
>>>
>>> _______________________________________________
>>> Beginners mailing list
>>> Beginners at haskell.org
>>> http://www.haskell.org/mailman/listinfo/beginners
>>>
>>>
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130331/edb61b49/attachment.htm>
More information about the Beginners
mailing list