[Haskell] Reading a directory tree

Isaac Jones ijones at syntaxpolice.org
Mon Jun 28 11:08:38 EDT 2004


[Followups to libraries at haskell.org]

This thread makes me want to mention that I'm starting to put together
a little library of useful path-based functions (I started it based on
OS.Path in Python).  Not sure how to organize it, exactly, since some
things that might make sense here are already in System.Directory (and
some things in there don't make sense in there) and some things may
require Posix, and so should be split off into a separate module.

My basic requirement is that they should be functions useful for
system administration.

We've sucked in some functions in from GHC and from Cabal[1]. It would
be nice if we could just have a dumping ground for related functions
that people have written.

For now, if you have darcs[2], you can say:
darcs get http://www.syntaxpolice.org/darcs_repos/OS.Path/

(And if you don't have darcs, you can browse around inside there with
a web browser to get an idea of how it's shaping up.)

That'll download the tree.  You can make changes and additions, then
use "darcs send" to email the changes to me.  I think we should just
dump together a bunch of these functions and worry about organizing it
later (wiki-style).

Here's a function[3] I wrote that's similar to what's mentioned here.
It builds a tree out of a file directory.  I'd like a function like
"walk"[4] that walks this tree and executes an IO action (like
printing out all the .txt files or something).  It doesn't have to be
based on Tree.

peace,

  isaac


------------------------------------------------------------
[1] http://www.haskell.org/cabal

[2] http://abridgegame.org/darcs/

[3]
-- |Create a tree out of the given starting point.  If the starting
-- point is a directory, we recurse down and give the entire
-- sub-structure, otherwise, we return a single node.
-- I think it only requires Posix to test whether this is a directory,
-- maybe we can do this with System.Directory?

makeDirectoryTree :: FilePath -- ^Starting point (file or directory)
                  -> IO (Tree (FilePath, Bool))
makeDirectoryTree path'
    = makeDirTree' Nothing path'
      where
      makeDirTree' :: Maybe FilePath -- ^Parent Dir
                   -> FilePath -- ^Starting point
                   -> IO (Tree (FilePath, Bool))
      makeDirTree' parentIn pathIn
          = do let fullPath = case parentIn of
                               Just pi' -> (dropLast pi' pathSeparator) ++ [pathSeparator] ++ pathIn
                               Nothing -> pathIn
               isDir <- pathIsDirectory fullPath
               contents <- if isDir
                            then getDirectoryContents fullPath
                            else return []
               subForest <- mapM (makeDirTree' (Just fullPath)) [c | c <- contents,
                                                               c /= ".",
                                                               c /= ['.', pathSeparator] ,
                                                               c /= ['.', '.', pathSeparator],
                                                               c /= ".."]
               return $ Node (pathIn, isDir) subForest

      -- FIX: probably better not to use "error" here, but rather let exception occur.
      pathIsDirectory :: FilePath -> IO Bool
      pathIsDirectory p = do existsP <- doesFileExist p
                             existsP2 <- doesDirectoryExist p
                             when (not (existsP || existsP2))
                                      (error $ "File does not exist: " ++ show p)
                             status <- getFileStatus p
                             return $ isDirectory status

      dropLast [] _ = []
      dropLast (h:[]) toDrop | h == toDrop = []
                             | otherwise = [h]
      dropLast (h:t) toDrop = h:(dropLast t toDrop)

[4]
-- |Apply the given function in each directory starting at the
-- root. use 'makeDirectoryTree'? FIX: how do we handle symlinks?
walk :: FilePath -- ^root
     -> (FilePath      -- current directory
         -> [FilePath] -- list of files in the directory
         -> IO a) -- ^visit function (current dir, list of files)
     -> IO (Tree a)



More information about the Libraries mailing list