[Haskell] Probably a trivial thing for people knowing Haskell

Friedrich frido at q-software-solutions.de
Sat Oct 18 04:50:55 EDT 2008


I've written just a few programs in Haskell one in a comparison for a
task I had "nearly daily".

The code analyzes Apache logs and picks some certain stuff from it and
after that calculates a bit around with it.

Here's the code
module Main where
import System
import System.IO
import System.Directory
import System.IO.Error
import Text.Regex
import Control.Monad

regexp = mkRegex ("([0-9]+) Windows ex")

main = do
       files <- show_dir "[0-9].*"
       (sum,count) <- run_on_all_files (0,0) files
       let dd = (fromIntegral (sum::Integer))/ (fromIntegral (count::Int))
           in
            putStr("Download = " ++ show sum ++ " in " ++ show count ++ " days are " ++ show dd ++ " downloads/day\n") 




run_on_all_files (a,b) [] = return (a,b)
run_on_all_files (a,b) (x:xs) = do (s,c) <- run_on(a,b) x
                                   run_on_all_files (s,c) xs


run_on (a,b) file_name = do
    handle <- openFile file_name ReadMode
    (sum,count) <- for_each_line (a,b) handle
    hClose handle
    return ((sum,count))
                              
for_each_line (sum,count) handle = do
                       l <- try (hGetLine handle)
                       case l of
                              Left err 
                                  | isEOFError err -> return(sum,count)
                                  | otherwise -> ioError err
                              Right line  -> do 
                                             let (nsum, ncount) = check_line line sum count
                                             for_each_line (nsum,ncount) handle 
                                                                                
                       
          
check_line line sum count =  
    let match = matchRegex regexp line
        in case match of
               Just strs -> (sum + read (head strs) :: Integer, count + 1)
               Nothing -> (sum, count)
    
                    
                            
    
show_dir regmatch = do   
                    files <- getDirectoryContents "."
                    let reg = mkRegex regmatch in
                              return(filter (\file_name -> let fm = matchRegex reg file_name
                                      in case fm of
                                      Just strs -> True
                                      Nothing -> False) files)


The point is this code works if there are just say a few files
files to check. But  it trashes my machine with around 1751 files.

It sucks memory as wild and so it does not run as I  think it should.

I think I've overseen something which is bad written. Would you mind
to  tell me where I did "extraordinarily" bad.

With best regards
Friedrich





More information about the Haskell mailing list