How to write elegant Haskell programms? (long posting)

Hello list, I'm new to Haskell and I'm trying to learn how to write elegant code using Haskell. I decided to convert the following small tool, written in ruby: =========================================================== #! /usr/bin/env ruby require 'pathname' BASENAMES = %w{ mail.log thttpd.log } ARCHIVEDIR = Pathname.new '/var/log/archive' LOGDIR = Pathname.new '/var/log' class Pathname def glob glob_pattern Pathname.glob self.join(glob_pattern) end def timestamp stat.mtime.strftime '%Y%m%d' end end for basename in BASENAMES for oldname in LOGDIR.glob "#{basename}.*.gz" newname = ARCHIVEDIR.join "#{basename}.#{oldname.timestamp}.gz" puts "mv #{oldname} #{newname}" File.rename oldname, newname end end =========================================================== My solution in Haskell is: =========================================================== import System.Directory (getDirectoryContents, getModificationTime, renameFile) import System.Locale (defaultTimeLocale) import System.Time (ClockTime, toUTCTime, formatCalendarTime) import Text.Regex (mkRegex, matchRegex) import Maybe import Control.Monad logdir, archivedir :: String logfiles :: [String] logfiles = [ "mail.log", "thttpd.log" ] logdir = "/var/log" archivedir = "/var/log/archive" basename :: String -> String basename filename = head . fromMaybe [""] $ matchRegex rx filename where rx = mkRegex "^(.+)(\\.[0-9]+\\.gz)$" isLogfile :: String -> Bool isLogfile filename = basename filename `elem` logfiles timestamp :: ClockTime -> String timestamp time = formatCalendarTime defaultTimeLocale "%Y%m%d" (toUTCTime time) makeOldname :: String -> String makeOldname fn = logdir ++ '/' : fn makeNewname :: String -> String -> String makeNewname bn ts = archivedir ++ '/' : bn ++ '.' : ts ++ ".gz" move :: String -> String -> IO () move oldname newname = do putStrLn $ "mv " ++ oldname ++ ' ' : newname renameFile oldname newname main :: IO () main = do files <- liftM (filter isLogfile) (getDirectoryContents logdir) let oldnames = map makeOldname files times <- mapM getModificationTime oldnames let newnames = zipWith makeNewname (map basename files) (map timestamp times) zipWithM_ move oldnames newnames =========================================================== Ok, the tool written in Haskell works. But, to me, the source doesn't look very nice and even it is larger than the ruby solution, and more imporant, the programm flow feels (at least to me) not very clear. Are there any libraries available to make writing such tools easier? How can I made the haskell source looking more beautiful? Michael Roth

On Mon, Jan 29, 2007 at 08:14:55PM +0100, Michael Roth wrote:
Hello list,
Hi! Just to simplify one function...
logdir = "/var/log" ... makeOldname :: String -> String makeOldname fn = logdir ++ '/' : fn ... main :: IO () main = do files <- liftM (filter isLogfile) (getDirectoryContents logdir) let oldnames = map makeOldname files times <- mapM getModificationTime oldnames
main = do files <- liftM (filter isLogfile) (getDirectoryContents logdir) times <- mapM (getModificationTime . ("/var/log/"++)) files (also consider) main = do files <- filter isLogfile `fmap` getDirectoryContents logdir times <- (getModificationTime . ("/var/log/"++)) `mapM` files If you count reindenting of the first line of the do statement and removal of type signatures, I've eliminated six out of eight lines, and the resulting function doesn't need to be read like spaghetti, looking back and forth to find out what makeOldname and logdir are. Of course, if you expect to change logdir or use it elsewhere in the code, you still might want to give it a name. But my versions I'd say are more readable and much more compact. On large projects it's worthwhile using type declarations for top-level functions, and it's worth adding them while debugging (to get better error messages), or for tricky functions where the types aren't obvious. But for code like this, they just make it harder to read. -- David Roundy Department of Physics Oregon State University

-- Here's my contribution to the "Haskell" way to do it import Directory (renameFile) import System.FilePath import System.Path.Glob (glob) import System.Time basenames = [ "mail.log", "thttpd.log" ] logdir = "/var/log" archivedir = "/var/log/archive" main = forM_ bases $ \base -> do olds <- glob $ logdir > base <.> "*.gz" forM_ olds $ \old -> do now <- timestamp old let new = archivedir > basename <.> now <.> "gz" printf "mv %s %s" old new renameFile old new timestamp f = do t <- getModificationTime return $ formatCalendarTime defaultTimeLocale "%Y%m%d" (toUTCTime t)

-- here was my original before I allowed someone (no names) to mangle mine for me ;) import Control.Monad (liftM, forM_) import Directory (getModificationTime, renameFile) import Text.Printf (printf) import System.FilePath ((>),(<.>)) import System.Locale (defaultTimeLocale) import System.Path.Glob (glob) import System.Time (toUTCTime, formatCalendarTime, getClockTime, ClockTime) basenames = ["mail.log", "thttpd.log" ] logdir = "/var/log" main = forM_ basenames $ \ basename -> do oldnames <- glob (logdir > basename <.> "*.gz") forM_ oldnames $ \ oldname -> do now <- timestamp oldname let newname = logdir > "archive" > basename <.> now <.> "gz" printf "mv %s %s" oldname newname renameFile oldname newname timestamp path = do t <- getModificationTime path return $ formatCalendarTime defaultTimeLocale "%Y%m%d" $ toUTCTime t

On Mon, Jan 29, 2007 at 05:30:41PM -0600, Eric Mertens wrote:
import Control.Monad (liftM, forM_) import Directory (getModificationTime, renameFile) import Text.Printf (printf) import System.FilePath ((>),(<.>)) import System.Locale (defaultTimeLocale) import System.Path.Glob (glob) import System.Time (toUTCTime, formatCalendarTime, getClockTime, ClockTime)
basenames = ["mail.log", "thttpd.log" ] logdir = "/var/log"
main = forM_ basenames $ \ basename -> do
Interesting, I've never used forM_! It's just flip mapM_, but that's pretty convenient...
oldnames <- glob (logdir > basename <.> "*.gz") forM_ oldnames $ \ oldname -> do now <- timestamp oldname let newname = logdir > "archive" > basename <.> now <.> "gz" printf "mv %s %s" oldname newname
Surely it'd be more idiomatic to just use putStrLn $ unwords ["mv", oldname, newname] or putStrLn $ "mv " ++ oldname ++ " " ++ newname (which also prints a newline, but I imagine that's what's actually wanted)
renameFile oldname newname
timestamp path = do t <- getModificationTime path return $ formatCalendarTime defaultTimeLocale "%Y%m%d" $ toUTCTime t
Surely this would be nicer as: timestamp path = (formatCalendarTime defaultTimeLocale "%Y%m%d" . toUTCTime) `liftM` getModificationTime path (although I prefer using fmap instead of liftM) -- David Roundy Department of Physics Oregon State University

On Mon, 2007-29-01 at 20:14 +0100, Michael Roth wrote:
Ok, the tool written in Haskell works. But, to me, the source doesn't look very nice and even it is larger than the ruby solution, and more imporant, the programm flow feels (at least to me) not very clear.
I am by no means a Haskell (or even FP) expert so I'll let the experts
talk about your code and will instead focus on philosophy.
I think that whole "program flow" thing is something you get used to.
In true, pure functional programming (i.e. Haskell) "program flow" is a
meaningless term, basically. Haskell is a declarative language, not an
imperative one. You have to learn to give up that control and trust the
runtime to Do The Right Thing. (In this regard it's similar to logic
programming languages.)
My canonical example is the three-line quicksort:
quicksort :: Ord a => [a] -> [a]
quicksort [] = []
quicksort (x:xs) = quicksort [y|y<-xs,y

Hello, I think that whole "program flow" thing is something you get used to. In
true, pure functional programming (i.e. Haskell) "program flow" is a meaningless term, basically. Haskell is a declarative language, not an imperative one. You have to learn to give up that control and trust the runtime to Do The Right Thing. (In this regard it's similar to logic programming languages.)
I think it's important/useful to point out that "program flow" in a pure functional language is really a matter of data dependency. The compiler is only free to arbitrarily order computations if there are no data dependencies. Furthermore, monads are not special in any way (they are after all just a useful set of combinators; e.g. http://sigfpe.blogspot.com/2006/08/you-could-have-invented-monads-and.html); they only wind up sequencing computations because they set up a data dependency between the two arguments of the bind operator. -Jeff
participants (5)
-
David Roundy
-
Eric Mertens
-
jeff p
-
Michael Roth
-
Michael T. Richter