[Haskell-cafe] printing a list of directories which don't exist
Daniel Fischer
daniel.is.fischer at web.de
Wed May 14 12:04:56 EDT 2008
Am Mittwoch, 14. Mai 2008 17:47 schrieb Mike Jarmy:
> Newbie question: Given a list of type '[FilePath]', how do I create a list
> of all those directories which do not actually exist, and then print the
> list? I've figured out how to extract the ones which *do* exist, like so:
>
> module Main where
>
> import Control.Monad (filterM)
> import System.Directory (doesDirectoryExist)
> import System.Environment (getArgs)
>
> main :: IO ()
> main = do
> dirs <- getArgs
> let existing = filterM doesDirectoryExist dirs
> ......
>
> which gives me a list of type 'IO [FilePath]'. However, because of the
> 'IO' tag, I cannot figure out how to do any of the following 3 things
> (noted in comments):
What you want is 'fmap' (from the Functor class) or 'liftM' (from the Monad
class).
bogusDirs <- filterM (fmap not . doesDirectoryExist) dirs
should work, same with liftM in place of fmap.
>
> -- filter via composition
> let bogusDirs = filterM (not . doesDirectoryExist) dirs
>
> -- test for emptiness
> if bogusDirs /= []
> -- print the list
> then putStrLn $ "bogus: " ++ show bogusDirs
> else putStrLn "OK"
>
> Can anyone set me straight? How do I make the IO tag go away, or am I
> going about this all wrong? E.g. the 'filterM (not . doesDirectoryExist)
> dirs' expression gives the following compilation error:
>
> ~/code/haskell$ ghc -o newbie newbie.hs
>
> newbie.hs:16:35:
> Couldn't match expected type `Bool' against inferred type `IO Bool'
> Expected type: FilePath -> Bool
> Inferred type: FilePath -> IO Bool
> In the second argument of `(.)', namely `doesDirectoryExist'
> In the first argument of `filterM', namely
> `(not . doesDirectoryExist)'
More information about the Haskell-Cafe
mailing list