[Haskell-cafe] new Haskell hacker seeking peer review

Sean Perry shaleh at speakeasy.net
Fri Feb 18 04:48:43 EST 2005


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


More information about the Haskell-Cafe mailing list