new Haskell hacker seeking peer review

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

Here's an alternative: module Main where import System.IO import System(getArgs) catFile :: FilePath -> IO () catFile fp = do contents <- readFile fp putStr contents main :: IO () main = do hSetBuffering stdin (BlockBuffering Nothing) args <- getArgs if not (null args) then mapM_ catFile args else do contents <- getContents putStr contents This avoids the whole EOF problem by using lazy I/O. readFile and getContents both return a String, but it's a lazy list; the contents of the string are only generated on demand. So this does not actually read the entire file into memory as you might think at first glance. Also, I added a hSetBuffering line. Setting it to BlockBuffering can improve performance. LineBuffering could also be useful if people are used to a certain type of interactive performance with cat. -- John

John Goerzen
Here's an alternative:
module Main where
(snip john's version) And what list would be complete without a points-free version. It doesn't operate on stdin, though like John's does: pointsFreeCat :: IO () pointsFreeCat = getArgs >>= mapM readFile >>= putStrLn . concat -- And a regular version for reference cat2 :: IO () cat2 = do a <- getArgs lines <- mapM readFile a putStrLn $ concat lines peace, isaac

At 5:27 PM -0800 2/18/05, Isaac Jones wrote:
John Goerzen
writes: Here's an alternative:
module Main where
(snip john's version)
And what list would be complete without a points-free version. It doesn't operate on stdin, though like John's does:
pointsFreeCat :: IO () pointsFreeCat = getArgs >>= mapM readFile >>= putStrLn . concat
-- And a regular version for reference
cat2 :: IO () cat2 = do a <- getArgs lines <- mapM readFile a putStrLn $ concat lines
peace,
isaac
You probably want `putStr` instead of `putStrLn`, as the latter introduces a gratuitous newline at the end of the concatenated contents. Dean

Isaac Jones wrote:
John Goerzen
writes: Here's an alternative:
module Main where
(snip john's version)
And what list would be complete without a points-free version. It doesn't operate on stdin, though like John's does:
pointsFreeCat :: IO () pointsFreeCat = getArgs >>= mapM readFile >>= putStrLn . concat
Or why not the two characters shorter, but much less readable: pointsFreeCat' = getArgs >>= mapM_ ((>>= putStr) . readFile) or maybe: pointsFreeCat'' = getArgs >>= mapM_ (putStr >>. readFile) (>>.) :: (b -> IO c) -> (a -> IO b) -> a -> IO c (>>.) = (.) . flip (>>=) Is (>>.) in the standard libs? If not, should it be? I'm sure there is a shorter definition of (>>.) that I haven't thought of. /Bjorn

Bjorn Bringert said:
Or why not the two characters shorter, but much less readable:
pointsFreeCat' = getArgs >>= mapM_ ((>>= putStr) . readFile)
or maybe:
pointsFreeCat'' = getArgs >>= mapM_ (putStr >>. readFile)
(>>.) :: (b -> IO c) -> (a -> IO b) -> a -> IO c (>>.) = (.) . flip (>>=)
Is (>>.) in the standard libs? If not, should it be? I'm sure there is a shorter definition of (>>.) that I haven't thought of.
/Bjorn
Or even: k :: Monad m => (a -> m b) -> Kleisli m a b k = Kleisli runKleisli :: Monad m => Kleisli m a b -> (a -> m b) runKleisli (Kleisli f) = f cat :: IO () cat = getArgs >>= (runKleisli $ (k $ mapM readFile) >>> (k $ mapM_ putStr)) after noticing that (>>.) is pretty similar to (<<<) when we lift (a -> IO b) to (Kleisli IO a b). It is pretty disappointing that runKleisli isn't defined so that I can be cool and completely point free too ;) /Andreas -- some cannot be created more equal than others
participants (6)
-
Andreas Farre
-
Bjorn Bringert
-
Dean Herington
-
Isaac Jones
-
John Goerzen
-
Sean Perry