[Haskell] Probably a trivial thing for people knowing Haskell

Friedrich frido at q-software-solutions.de
Mon Oct 20 01:37:09 EDT 2008


Taral <taralx at gmail.com> writes:

> On Sat, Oct 18, 2008 at 1:50 AM, Friedrich
> <frido at q-software-solutions.de> wrote:
>> 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
>
> Wow, talk about doing everything by hand. :) There are a lot of
> utility functions that make your life easier. Try this:
>
> import Control.Monad
> import Data.Char
> import Data.List
> import System.Directory
> import System.IO
> import Text.Regex
>
> main = do
>     allFiles <- getDirectoryContents "."
>     let files = filter (isDigit . head) allFiles
>     contents <- mapM readFile files
>     let (sum, count) = foldl' countDownloads (0,0) $ lines $ concat contents
>     putStr ("Download = " ++ show sum ++ " in " ++ show count ++ " days are " ++
>  show (fromIntegral sum / fromIntegral count) ++ " downloads/day\n")
>
> match = matchRegex $ mkRegex "([0-9]+) Windows ex"
>
> countDownloads (s, c) l =
>     case match l of
>         Just [n] -> (s + read n, c + 1)
>         Nothing -> (s, c)
>
> Unfortunately, it doesn't solve your space leak. (I checked this via
> core, but you can check it by testing it.) There's only one possible
> lazy point left:
>
> countDownloads (s, c) l =
Ok,  I used that  code and now I got:
./haskell_2 
haskell_2: 8500: openFile: resource exhausted (Too many open files)


Sorry, so I can not writ it down like that. So the above part with
allFiles has to be modified to not exhaust the file descriptors.

Regards
Friedrich


-- 
Q-Software Solutions GmbH; Sitz: Bruchsal; Registergericht: Mannheim 
Registriernummer: HRB232138; Geschaeftsfuehrer: Friedrich Dominicus


More information about the Haskell mailing list