
Hi, I’m trying to build up a list of all folders (including subfolders) from a given root folder. So I have folders :: FilePath -> IO [FilePath] folders fp = do all <- getDirectoryContents fp filterM doesDirectoryExist $ map (fp >) all and this just gets the immediate folders within the given folder. I’m stuck on how to recursively call folders and build up the IO [FilePath] folders :: FilePath -> IO [FilePath] folders fp = do all <- getDirectoryContents fp -- z :: IO [FilePath] let z = filterM doesDirectoryExist $ map (fp >) all — z’ :: [FilePath] z' <- z — ?? what should happen here? z : (map folders z’) Couldn't match expected type ‘[FilePath]’ with actual type ‘IO [FilePath]’ In the first argument of ‘(:)’, namely ‘z’ In a stmt of a 'do' block: z : (map folders z') etc... Thanks Mike

Hello Mike, below code find all files recursively from a starting point. It works. You'd need to tweak it to find folders instead. import System.Directory import Data.List findAllFiles::FilePath -> IO [FilePath] findAllFiles base0 = gd1 base0 >>= \list1 -> concatMap' recurse3 list1 where gd1 d1 = filter f2 <$> (getDirectoryContents d1) f2 "." = False f2 ".." = False f2 _ = True recurse3 md3 = doesDirectoryExist md3full >>= \isDir3 -> if isDir3 then findAllFiles md3full else pure [md3full] where md3full = base0 ++ "/" ++ md3 concatMap':: (a -> IO [b]) -> [a] -> IO [b] concatMap' m0 list0 = sequence (m0 <$> list0) >>= \list2 -> pure $ concat list2

Thanks. I sweated it bit more and got isOk FilePath -> Bool isOk = not . isPrefixOf "." folders :: FilePath -> IO [FilePath] folders fp = do all <- getDirectoryContents fp z' <- filterM doesDirectoryExist $ map (fp >) (filter isOk all) x' <- mapM (\x -> folders x) z' return $ z' ++ (concat x') :: which seems to work.
On 25 Feb 2016, at 19:07, Imants Cekusins
wrote: Hello Mike,
below code find all files recursively from a starting point. It works.
You'd need to tweak it to find folders instead.
import System.Directory import Data.List
findAllFiles::FilePath -> IO [FilePath] findAllFiles base0 = gd1 base0
= \list1 -> concatMap' recurse3 list1 where gd1 d1 = filter f2 <$> (getDirectoryContents d1) f2 "." = False f2 ".." = False f2 _ = True recurse3 md3 = doesDirectoryExist md3full = \isDir3 -> if isDir3 then findAllFiles md3full else pure [md3full] where md3full = base0 ++ "/" ++ md3
concatMap':: (a -> IO [b]) -> [a] -> IO [b] concatMap' m0 list0 = sequence (m0 <$> list0)
= \list2 -> pure $ concat list2
Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Your "isOk" function will filter out hidden directories on Unix (which may
be what you want?).
Otherwise: isOk = (`notElem` [".",".."])
Also "\x -> folders x" = "folders"
2016-02-26 11:42 GMT+01:00 Mike Houghton
Thanks.
I sweated it bit more and got
isOk FilePath -> Bool isOk = not . isPrefixOf "."
folders :: FilePath -> IO [FilePath] folders fp = do all <- getDirectoryContents fp z' <- filterM doesDirectoryExist $ map (fp >) (filter isOk all) x' <- mapM (\x -> folders x) z' return $ z' ++ (concat x') ::
which seems to work.
On 25 Feb 2016, at 19:07, Imants Cekusins
wrote: Hello Mike,
below code find all files recursively from a starting point. It works.
You'd need to tweak it to find folders instead.
import System.Directory import Data.List
findAllFiles::FilePath -> IO [FilePath] findAllFiles base0 = gd1 base0
= \list1 -> concatMap' recurse3 list1 where gd1 d1 = filter f2 <$> (getDirectoryContents d1) f2 "." = False f2 ".." = False f2 _ = True recurse3 md3 = doesDirectoryExist md3full = \isDir3 -> if isDir3 then findAllFiles md3full else pure [md3full] where md3full = base0 ++ "/" ++ md3
concatMap':: (a -> IO [b]) -> [a] -> IO [b] concatMap' m0 list0 = sequence (m0 <$> list0)
= \list2 -> pure $ concat list2
Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Cool, thanks.
On 26 Feb 2016, at 13:01, Sylvain Henry
wrote: Your "isOk" function will filter out hidden directories on Unix (which may be what you want?).
Otherwise: isOk = (`notElem` [".",".."])
Also "\x -> folders x" = "folders"
2016-02-26 11:42 GMT+01:00 Mike Houghton
mailto:mike_k_houghton@yahoo.co.uk>: Thanks. I sweated it bit more and got
isOk FilePath -> Bool isOk = not . isPrefixOf "."
folders :: FilePath -> IO [FilePath] folders fp = do all <- getDirectoryContents fp z' <- filterM doesDirectoryExist $ map (fp >) (filter isOk all) x' <- mapM (\x -> folders x) z' return $ z' ++ (concat x') ::
which seems to work.
On 25 Feb 2016, at 19:07, Imants Cekusins
mailto:imantc@gmail.com> wrote: Hello Mike,
below code find all files recursively from a starting point. It works.
You'd need to tweak it to find folders instead.
import System.Directory import Data.List
findAllFiles::FilePath -> IO [FilePath] findAllFiles base0 = gd1 base0
= \list1 -> concatMap' recurse3 list1 where gd1 d1 = filter f2 <$> (getDirectoryContents d1) f2 "." = False f2 ".." = False f2 _ = True recurse3 md3 = doesDirectoryExist md3full = \isDir3 -> if isDir3 then findAllFiles md3full else pure [md3full] where md3full = base0 ++ "/" ++ md3
concatMap':: (a -> IO [b]) -> [a] -> IO [b] concatMap' m0 list0 = sequence (m0 <$> list0)
= \list2 -> pure $ concat list2
Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (3)
-
Imants Cekusins
-
Mike Houghton
-
Sylvain Henry