Tail-call optimization

I always wandered, does ghc do tail-call optimization? Would it optimize the two variants of the function below or just the first one? --- Proper? writeLoop :: (Event a -> IO ()) -> Handle -> (SSL, BIO, BIO) -> IO () writeLoop post h ssl = do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd writeLoop post h ssl --- Bad? writeLoop :: (Event a -> IO ()) -> Handle -> (SSL, BIO, BIO) -> IO () writeLoop post h ssl = do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd writeLoop post h ssl Thanks, Joel -- http://wagerlabs.com/

Hello Joel, Saturday, December 10, 2005, 11:41:52 PM, you wrote: JR> I always wandered, does ghc do tail-call optimization? ghc does this. but only first of your examples is tail-called. second recursively creates exception hadnlers around your code. just try to textually replace call to writeLoop with its contents: writeLoop :: (Event a -> IO ()) -> Handle -> (SSL, BIO, BIO) -> IO () writeLoop post h ssl = do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd writeLoop post h ssl = do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd writeLoop post h ssl = do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd and so on... :) JR> Would it optimize the two variants of the function below or just the JR> first one? what you want to do after exception is handled? exit writeLoop or go to next loop? depending on it use one of following: writeLoop post h ssl = do handle (\e -> post $ NetworkError e) $ repeat_foreverM $ do cmd <- read h ssl post $! Cmd $! cmd writeLoop post h ssl = repeat_foreverM $ do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd repeat_foreverM action = do action repeat_foreverM action btw, i also has the follwing control structures: concatMapM :: Monad io => (a -> io [b]) -> [a] -> io [b] concatMapM f x = mapM f x >>== concat whenM cond action = do allow <- cond when allow action whenJustM x action = x >>= maybe (return Nothing) action repeat_whileM inp cond out = do x <- inp if (cond x) then do out x repeat_whileM inp cond out else return x repeat_untilM action = do done <- action when (not done) $ do repeat_untilM action doChunks size chunk action = case size of 0 -> return () _ -> do let n = minI size chunk action (fromIntegral n) doChunks (size-n) chunk action recursiveM action x = action x >>= mapM_ (recursiveM action) mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] mapMaybeM f = go [] where go accum [] = return$ reverse accum go accum (x:xs) = f x >>= maybe ( go accum xs) (\r -> go (r:accum) xs) -- Best regards, Bulat mailto:bulatz@HotPOP.com

G'day.
Quoting Joel Reymont
writeLoop :: (Event a -> IO ()) -> Handle -> (SSL, BIO, BIO) -> IO () writeLoop post h ssl = do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd writeLoop post h ssl
Good, but even better is this: writeLoop :: (Event a -> IO ()) -> Handle -> (SSL, BIO, BIO) -> IO () writeLoop post h ssl = loop where loop = do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd loop Avoiding parameter passing can make your code a lot easier to read. Cheers, Andrew Bromage

Thank you Andrew! Does it have any effect on performance? Is there a speed up of any sort from not passing parameters? On Dec 11, 2005, at 11:50 PM, ajb@spamcop.net wrote:
Good, but even better is this:
writeLoop :: (Event a -> IO ()) -> Handle -> (SSL, BIO, BIO) -> IO () writeLoop post h ssl = loop where loop = do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd loop
Avoiding parameter passing can make your code a lot easier to read.

On Sunday 11 December 2005 06:54 pm, Joel Reymont wrote:
Thank you Andrew! Does it have any effect on performance? Is there a speed up of any sort from not passing parameters?
Shooting from the hip here, but I doubt it -- AFAIK it all gets lambda-lifted in the compiler anyway.
On Dec 11, 2005, at 11:50 PM, ajb@spamcop.net wrote:
Good, but even better is this:
writeLoop :: (Event a -> IO ()) -> Handle -> (SSL, BIO, BIO) -> IO () writeLoop post h ssl = loop where loop = do handle (\e -> post $ NetworkError e) $ do cmd <- read h ssl post $! Cmd $! cmd loop
Avoiding parameter passing can make your code a lot easier to read.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

G'day all.
Quoting Joel Reymont
Thank you Andrew! Does it have any effect on performance?
Yes, however I believe that GHC can perform this transformation automatically at high optimisation levels. Even so, for portability, it's wise not to rely on your implementation performing specific high-level transformations for you.
Is there a speed up of any sort from not passing parameters?
It depends on the implementation. There is no difference for an implementation which relies on lambda lifting (e.g. Gofer). For the STG machine, which both Hugs and GHC use, it theoretically makes a difference for the better, though it might not be measurable in practice. You can be almost certain that the second version is no worse in performance, and it's usually more readable. Cheers, Andrew Bromage
participants (4)
-
ajb@spamcop.net
-
Bulat Ziganshin
-
Joel Reymont
-
Robert Dockins