[Haskell-beginners] Too much mapM, fmap and concat

Vlatko Basic vlatko.basic at gmail.com
Wed Aug 13 18:39:00 UTC 2014


Hi Martin,

While fmap you might consider noise, mapM you can't. If you have a list, you 
have to map(M) over it. What you can do is use map(M) once, and combine 
functions that you're mapping over. That way there is only one pass over the list.

There is an operator (<$>) that is a synonym for fmap, so you can use that for 
noise reduction.

If you wanted to shorten the code, here is my try.


main = do
   fs <- concat . fst <$> globDir [compile filePattern] fileDirectory
   result <- mapM (fmap (concat . processFile) . nameAndContent) fs
   mapM_ putStrLn result
--  This one combines the two above
--  mapM_ (join . fmap (print . concat . processFile) . nameAndContent) fs
   where
     nameAndContent :: String -> IO (FilePath, [String])
     nameAndContent fn = do
       content <- lines <$> readFile fn
       return $ (fn, content)


vlatko

-------- Original Message  --------
Subject: [Haskell-beginners] Too much mapM, fmap and concat
From: martin <martin.drautzburg at web.de>
To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level 
topics related to Haskell <beginners at haskell.org>
Date: 13.08.2014 18:21

> Hello all,
>
> I never did much IO in haskell, but now I have to process some files. I catch myself adding a mapM here and an fmap
> there. While it is clear to me what these functions do, I wonder if there is a way to avoid the noise. Also I could not
> find a simple way to pair the lines of a file with its filename. I ended up writing a function "nameAndContent". Finally
> I am amazed by the many "concat"s I need.
>
> Maybe these things just lie in the nature of the problem ("process a number of files"). Otherwise any style suggestions
> would be much appreciated.
>
> import System.FilePath.Glob
> import Data.List
>
> filePattern="*.hs"
> fileDirectory = "."
>
> processFile :: (FilePath, [String]) -> [String]
> processFile (path, flines) = ["done"]
>
> main = do
>      matchingFiles <- fmap (concat . fst) $ globDir [compile filePattern] fileDirectory
>      flines <- mapM nameAndContent matchingFiles
>      result <- mapM (return . processFile) flines
>      mapM putStrLn $ concat  result
>              where
>                  nameAndContent :: FilePath -> IO (FilePath, [String])
>                  nameAndContent fn = do
>                      content <- fmap lines $ readFile fn
>                      return (fn, content)
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


More information about the Beginners mailing list