
I am trying to modify an example in RealWorldHaskell from Chapter 24. The example is the first code snippet labeled -- file: ch24/Compressor.hs I am trying to replace the use of Readline with Haskeline. In my code the forkIO thread does not run. I guessed that since the result of the worker thread was thrown away that perhaps laziness was the problem. So, I attempted to use `seq`, but that does not work either. I am able to run the RealWorldHaskell example. I am using GHC 7.8.3. I have tried runhaskell with and without the -threaded option and on both Linux and Windows 7. import Control.Concurrent (forkIO) import Control.Exception import qualified Data.ByteString.Lazy as L import System.Console.Haskeline hiding (handle) -- Provided by the 'zlib' package on http://hackage.haskell.org/ import Codec.Compression.GZip (compress) -- Read the file, compress the data, write the compressed data worker :: FilePath -> IO () worker path = L.readFile path >>= L.writeFile (path ++ ".gz") . compress -- Run the worker on a new thread runWorker :: FilePath -> IO() runWorker path = handle (print :: SomeException -> IO ()) $ do forkIO (worker path) return () loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> let f = runWorker path in f `seq` do return f loop main = runInputT defaultSettings loop

Jeff C. Britton wrote:
I am trying to modify an example in RealWorldHaskell from Chapter 24. The example is the first code snippet labeled -- file: ch24/Compressor.hs
I am trying to replace the use of Readline with Haskeline. In my code the forkIO thread does not run. I guessed that since the result of the worker thread was thrown away that perhaps laziness was the problem. So, I attempted to use `seq`, but that does not work either.
The forkIO is not run because your code never actually runs it. :) The snippet let f = runWorker (worker path) in f `seq` do return f loop binds a value (here an `IO` action) to the variable `f`, then makes sure that the variable is evaluated to weak head normal form (which is something quite different from executing the `IO` action), and then combines the IO action `return f` (which has no side effects, but returns the value of `f`) with `loop`. The key point to understand here is that IO actions are first-class values: you can bind them to variables and combine them with `>>` and `>>=`. In a sense, you never execute IO actions, you only build them. The only time when something is executed is when the Haskell compiler executes the IO action assigned to the `main` variable. What you had in mind is a program that combines the IO action `f` directly with the `loop`, like this: let f = runWorker (worker path) in do f loop Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

If I modify the code to the suggested form: let f = runWorker (worker path) in do f loop then I get the following compile error Couldn't match type `IO' with `InputT IO' Expected type: InputT IO () Actual type: IO () In a stmt of a 'do' block: f In the expression: do { f; loop } I have also tried let f = runWorker (worker path) in do return f loop This compiles, but won't run forkIO. I can't figure out how to get forkIO to run and make the type system happy. I am going to past the code again, because the line breaks got messed up the first time. I have removed the `seq` call though as it simplifies the code a bit. import Control.Concurrent (forkIO) import Control.Exception import qualified Data.ByteString.Lazy as L import System.Console.Haskeline hiding (handle) -- Provided by the 'zlib' package on http://hackage.haskell.org/ import Codec.Compression.GZip (compress) worker :: FilePath -> IO () worker path = L.readFile path >>= L.writeFile (path ++ ".gz") . compress runWorker :: FilePath -> IO() runWorker path = handle (print :: SomeException -> IO ()) $ do forkIO (worker path) return () loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> do return (runWorker path) loop main = runInputT defaultSettings loop

"Jeff C. Britton"
loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> do return (runWorker path) loop
The other issue you're having is because `runWorker path` is an `IO ()` value but at the point where you use it in the code the type system wants an `InputT IO ()`. To try to satisfy the type system you used `return` to build a `InputT IO (IO ())` value, but that doesn't actually work (as you've noticed). Since `InputT` is a transformer you have an extra layer to work through and so need to *lift* your `IO ()` value into the `InputT IO` layer. Try this: -- Add this import import Control.Monad.IO.Class loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> do liftIO (runWorker path) loop You can think of `liftIO` as having this signature (in this context): liftIO :: IO () -> InputT IO () -- Peter Jones, Founder, Devalot.com Defending the honor of good code

Thanks Peter,
That suggestion works.
I will have to continue learning more about Monads.
--Jeff
-----Original Message-----
From: Beginners [mailto:beginners-bounces@haskell.org] On Behalf Of Peter Jones
Sent: Thursday, August 28, 2014 7:11 AM
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Haskeline and forkIO
"Jeff C. Britton"
loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> do return (runWorker path) loop
The other issue you're having is because `runWorker path` is an `IO ()` value but at the point where you use it in the code the type system wants an `InputT IO ()`. To try to satisfy the type system you used `return` to build a `InputT IO (IO ())` value, but that doesn't actually work (as you've noticed). Since `InputT` is a transformer you have an extra layer to work through and so need to *lift* your `IO ()` value into the `InputT IO` layer. Try this: -- Add this import import Control.Monad.IO.Class loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> do liftIO (runWorker path) loop You can think of `liftIO` as having this signature (in this context): liftIO :: IO () -> InputT IO () -- Peter Jones, Founder, Devalot.com Defending the honor of good code _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

"Jeff C. Britton"
That suggestion works. I will have to continue learning more about Monads.
I should have also mentioned that if you enable GHC warnings it should tell you that having the `return` before `loop` is discarding the value given to it.
-----Original Message----- From: Beginners [mailto:beginners-bounces@haskell.org] Sent: Thursday, August 28, 2014 7:11 AM To: beginners@haskell.org Subject: Re: [Haskell-beginners] Haskeline and forkIO
"Jeff C. Britton"
writes: loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> do return (runWorker path) loop
The other issue you're having is because `runWorker path` is an `IO ()` value but at the point where you use it in the code the type system wants an `InputT IO ()`. To try to satisfy the type system you used `return` to build a `InputT IO (IO ())` value, but that doesn't actually work (as you've noticed). Since `InputT` is a transformer you have an extra layer to work through and so need to *lift* your `IO ()` value into the `InputT IO` layer. Try this:
-- Add this import import Control.Monad.IO.Class
loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> do liftIO (runWorker path) loop
You can think of `liftIO` as having this signature (in this context):
liftIO :: IO () -> InputT IO ()
-- Peter Jones, Founder, Devalot.com Defending the honor of good code

As a Haskell beginner, I would also like to recommend HLint as a very
useful tool to catch these kinds of things.
On Sep 3, 2014 12:25 PM, "Peter Jones"
"Jeff C. Britton"
writes: That suggestion works. I will have to continue learning more about Monads.
I should have also mentioned that if you enable GHC warnings it should tell you that having the `return` before `loop` is discarding the value given to it.
-----Original Message----- From: Beginners [mailto:beginners-bounces@haskell.org] Sent: Thursday, August 28, 2014 7:11 AM To: beginners@haskell.org Subject: Re: [Haskell-beginners] Haskeline and forkIO
"Jeff C. Britton"
writes: loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> do return (runWorker path) loop
The other issue you're having is because `runWorker path` is an `IO ()` value but at the point where you use it in the code the type system wants an `InputT IO ()`. To try to satisfy the type system you used `return` to build a `InputT IO (IO ())` value, but that doesn't actually work (as you've noticed). Since `InputT` is a transformer you have an extra layer to work through and so need to *lift* your `IO ()` value into the `InputT IO` layer. Try this:
-- Add this import import Control.Monad.IO.Class
loop :: InputT IO () loop = do maybeLine <- getInputLine "Enter a file to compress> " case maybeLine of Nothing -> return () -- user entered EOF Just "" -> return () -- treat no name as "want to quit" Just path -> do liftIO (runWorker path) loop
You can think of `liftIO` as having this signature (in this context):
liftIO :: IO () -> InputT IO ()
-- Peter Jones, Founder, Devalot.com Defending the honor of good code
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (4)
-
Heinrich Apfelmus
-
Jeff C. Britton
-
Neeraj Rao
-
Peter Jones