Friedrich wrote: > Taral <[EMAIL PROTECTED]> writes: > > Wow, talk about doing everything by hand. :) There are a lot of > > utility functions that make your life easier. Try this:
Given a strict pair, it should work:
> > import Control.Monad
> > import Data.Char
> > import Data.List
> > import System.Directory
> > import System.IO
> > import Text.Regex
> >
data Pair = Pair !Integer !Integer
> > main = do
> > allFiles <- getDirectoryContents "."
> > let files = filter (isDigit . head) allFiles
> > contents <- mapM readFile files
> > let (sum, count) = foldl' countDownloads (0,0) $ lines $ concat contents
let Pair sum count = foldl' countDownloads (Pair 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)
countDownloads p@(Pair s c) l =
case match l of
Just [n] -> Pair (s + read n) (c + 1)
Nothing -> p
-Udo
signature.asc
Description: Digital signature
_______________________________________________ Haskell mailing list [email protected] http://www.haskell.org/mailman/listinfo/haskell
