Isn't this tail recursive?

Jyrinx jyrinx_list@mindspring.com
10 Mar 2002 18:36:01 -0800


For practice, I'm playing with reimplementing the solution to the word
count problem on the Great Computer Language Shootout
(www.bagley.org/~doug/shootout). My current solution looks tail
recursive to me:

--- snip ---

-- wc-luke.hs
-- Reimplimentation of the Haskell word count program for the Great
-- 	Computer Language Shootout
-- Luke Maurer
-- jyrinx@mindspring.com

module Main where

import IO

data CharKind = Normal | White | Newline

charKind :: Char -> CharKind
charKind c =
    case c of
        '\n' -> Newline
        ' '  -> White
        '\t' -> White
        _    -> Normal

countAll :: String -> (Int, Int, Int)
countAll str =
    countAll' str 0 0 0 0
        where countAll' [] _ nl nw nc = (nl, nw, nc)
              countAll' (c:cs) newWord nl nw nc =
                case charKind c of
		    -- The following should all be tail calls ... right?
                    Normal  -> countAll' cs 0 nl (nw + newWord) (nc + 1)
                    White   -> countAll' cs 1 nl nw (nc + 1)
                    Newline -> countAll' cs 1 (nl + 1) nw (nc + 1)

main = do
    -- We need a 4K buffer, as per the rules
    hSetBuffering stdin (BlockBuffering (Just 4096))

    file <- getContents
    let (l, w, c) = countAll file

    putStrLn ((show l) ++ " " ++ (show w) ++ " " ++ (show c))

--- snip ---

In the case expression at the end of countAll, each of the values looks
to me like a recursive tail call - I should think (hope?) that it would
be optimized by GHC into a goto statement (a la Scheme). Instead, my
program eats up memory (I've got 256 MB) until the RTS whines about a
stack overflow.

Am I wrong about the tail call? Is there some optimization I should be
aware of (I'm compiling with -O2)? Is this a flaw in GHC?

(BTW, as a beginner, I'd be glad to hear general commentary on my code
...)

Thanks!

Jyrinx
jyrinx_list at mindspring dot com