
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