Here's a two-line, mildly obfuscated version of the same

main = applyM putStr $ map unlines $ applyM 
       (mapM (\ x -> map (head.lines) $ readFile x)) $ (map lines $ readFile 
"filenames.txt")

sorry, couldn't resist :)

--Sigbjorn

Sven Panne writes:
> Roland Senn wrote:
> > [...] I now want to write a simple program, that prints out the first
> > line of every file mentioned in 'filenames.txt'.
> > [...]
> > Everybody immediately sees, that the last function 'processSingleFile'
> > is wrong! But how, has this example to be changed, to compile and
> > run successfully ??
> 
> This can be done using mapM:
> 
> ---------------------------------------------------------------------
> import IO
> 
> main ::   IO ()
> main = do fromHandle <- openFile "filenames.txt" ReadMode
>           contents <- hGetContents fromHandle
>           firstLines <- mapM processSingleFile (lines contents)
>           putStr (unlines firstLines)
> 
> processSingleFile :: String -> IO String
> processSingleFile s = do inh <- openFile s ReadMode
>                          cont <- hGetContents inh
>                          return (head (lines cont))
> ---------------------------------------------------------------------
> 
> mapM is in the standard Prelude and has the following signature:
> 
>    mapM :: Monad m => (a -> m b) -> [a] -> m [b]
> 
> Specialized to the IO monad this means:
> 
>    Given an IO action expecting an "a" and returning a "b"
>    and a list of "a"s,
>    yield an IO action returning a list of "b"s.
> 
> Here, both "a" and "b" are String.
> 
> 
> P.S.: Closing the files with hClose would be a good idea...
> 
> -- 
> Sven Panne                                        Tel.: +49/89/2178-2235
> LMU, Institut fuer Informatik                     FAX : +49/89/2178-2211
> LFE Programmier- und Modellierungssprachen              Oettingenstr. 67
> mailto:[EMAIL PROTECTED]            D-80538 Muenchen
> http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne


Reply via email to