
I am learning Haskell, so I decided to implement everyone's favorite, overused Unix command -- cat. Below is my simple implementation, comments about style, implementation, etc. are welcomed. In particular, is my untilEOF idiomatically ok? Is there a better way to accomplish this? Also, while talking about untilEOF, it is slightly annoying that hIsEOF returns IO Bool and that functions like 'not' only want Bool. Sure makes the logic tests feel like more work than they should be. cat.hs: module Main where import IO import System(getArgs) untilEOF :: Handle -> (Handle -> IO ()) -> IO () untilEOF hdl f = do eof <- hIsEOF hdl if eof then return () else do f hdl untilEOF hdl f cat :: Handle -> IO () cat hdl = do line <- hGetLine hdl putStrLn line catFile :: FilePath -> IO () catFile path = do hdl <- openFile path ReadMode untilEOF hdl cat main :: IO () main = do args <- getArgs if (length args) > 0 then mapM_ catFile args else untilEOF stdin cat

On Fri, 2005-02-18 at 01:58 -0800, Sean Perry wrote:
I am learning Haskell, so I decided to implement everyone's favorite, overused Unix command -- cat. Below is my simple implementation, comments about style, implementation, etc. are welcomed.
In particular, is my untilEOF idiomatically ok? Is there a better way to accomplish this?
Haskell allows lazy IO. One example is hGetContents (and getContents which is specialised for stdin): hGetContents :: Handle -> IO String It looks like you get the whole file contents at once, but under the hood it is read on demand. This allows you to avoid the awkward tests for EOF. Lazy IO is not without its problems, in particular it makes life hard for the people who implement the compilers. You should look around the haskell list archives for the discussions about lazy that have happened in the past. Cheers, Bernie.

Hi Sean, I'm not expert, but since you asked for idiomatic comments, here are a few... On 18 Feb 2005, at 09:58, Sean Perry wrote:
Also, while talking about untilEOF, it is slightly annoying that hIsEOF returns IO Bool and that functions like 'not' only want Bool. Sure makes the logic tests feel like more work than they should be.
`Annoying' in some sense, but it could hardly be any other way. You can always lift 'not' into the IO monad, as in (liftM not).hIsEOF
untilEOF :: Handle -> (Handle -> IO ()) -> IO () untilEOF hdl f = do eof <- hIsEOF hdl if eof then return () else do f hdl untilEOF hdl f
This idiom with if .. then return () else ... is the 'unless' idiom from Control.Monad: untilEOF hdl f = do eof <- hIsEOF hdl unless eof $ do f hdl untilEOF hdl f there is also 'when' for the opposite. Here is an example just to demonstrate how to lift 'not' should you ever want to: untilEOF' hdl f = do eof <- (liftM not)(hIsEOF hdl) when eof $ do f hdl untilEOF' hdl f
cat :: Handle -> IO () cat hdl = do line <- hGetLine hdl putStrLn line
arguably more idiomatic is: cat hdl = hGetLine hdl >>= putStrLn
main :: IO () main = do args <- getArgs if (length args) > 0 then mapM_ catFile args else untilEOF stdin cat
if (not null args) is preferred to if (length args) > 0 as a general principle (it's faster for long lists). Jules
participants (3)
-
Bernard Pope
-
Jules Bean
-
Sean Perry