[Haskell-cafe] Re: Haskell Speed

Branimir Maksimovic bmaxa at hotmail.com
Mon Dec 26 15:32:17 EST 2005




>From: Branimir Maksimovic <bmaxa at hotmail.com>

>
>module Main where
>import IO
>import Char
>
>main = do s <- hGetContents stdin
>           putStrLn $ show $ wc s
>
>wc :: String -> (Int , Int , Int)
>wc strs = wc' strs (0,0,0)
>         where wc' [] res = res
>               wc' (s:str) (lns, wrds, lngth )
>                   | s == '\n' =  wc' str (lns+1,wrds, lngth+1)
>                   | isAlpha s = wc'' str (lns, wrds+1,lngth+1)
>                   | otherwise = wc' str (lns,wrds, lngth+1)
>               wc'' [] res = res
>               wc'' (s:str) (lns,wrds,lngth)
>                    = if isAlphaNum s
>                         then wc'' str (lns,wrds,lngth+1)
>                         else wc' str (lns,wrds, lngth+1)
>
>
err, I've tested windows file on unix :)

              wc'' strs@(s:str) (lns,wrds,lngth)
                   = if isAlphaNum s
                        then wc'' str (lns,wrds,lngth+1)
                        else wc' strs (lns,wrds, lngth)


>Greetings, Bane.
>

_________________________________________________________________
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/



More information about the Haskell-Cafe mailing list