Paul Moore wrote:
On 25 Dec 2005 12:24:38 +0100, Peter Simons <[EMAIL PROTECTED]> wrote:
Paul Moore writes:
> It would be interesting to see standalone code for wcIOB
> (where you're allowed to assume that any helpers you
> need, like your block IO library, are available from the
> standard library). This would help in comparing the
> "obviousness" of the two approaches.
A simple version of the program -- which doesn't need any
3rd party modules to compile -- is attached below. My guess
is that this approach to I/O is quite obvious, too, if you
have experience with system programming in C.
Hmm, I can't honestly believe that you feel that your code is as
"obvious" as the original. I'm not unfamiliar with monads and state,
and I know C well, but it took me a significant amount of time to
decipher your code (even knowing what it was intended to do), whereas
I knew what the original was doing instantly.
IMHO, the main point of the example in the article is that
wc :: String -> (Int, Int, Int)
wc file = ( length (lines file)
, length (words file)
, length file
)
is a crapy word-counting algorithm.
Dunno. It's certainly not a bad (executable!) definition of the
problem. My point is that Haskell allows me to write *very* clear
"executable pseudocode", but that code is not a good starting point
for writing production-quality code.
this program counts two times length of lists of strings formed by
lines, and words and third time counts again length of file.
This is not just word counting program, it creates two additional lists,
which are not used anywhere but to count :)
While it is certainly expressive, in terms of programing is pointless.
No one would write such a code for word counting.
Here is what I would write in Haskell, same logic as in C++
(i don;t know standard lib ):
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)
Greetings, Bane.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe