Tom Hofte writes:

 > I'm looking for a way to iteratively read all the files
 > in a directory and its subdirectories, given the filepath
 > of the top-level dir.

Hope this helps:

\begin{code}
module ReadDirHier
    ( Entry(..)
    , name
    , readDirHier
    ) where

import System.Directory (getDirectoryContents, doesDirectoryExist)
import Data.List (isPrefixOf, sort)

data Entry              = Dir  FilePath [Entry]
                        | File FilePath

name                    :: Entry -> FilePath
name (Dir p _)          = p
name (File p)           = p

-- |Read the complete directory hierarchy starting at 'FilePath' and
-- return a tree representing it. The top-most 'Entry' will -
-- obviously - be a 'Dir'. Directories contain their sub-entries in
-- alphabetic order. The returned tree starts with the 'name' \"@[EMAIL PROTECTED]"
-- - /not/ with the given 'FilePath'. All file names are relative to
-- their current directory.
--
-- The function may throw exceptions when I/O fails.

readDirHier             :: FilePath -> IO Entry
readDirHier path        = readDirHier' path "."

readDirHier'            :: FilePath -> FilePath -> IO Entry
readDirHier' pre p      = do files   <- getDirectoryContents $ pre ++ "/" ++ p
                             entries <- mapM toEntry $ sort $ clean files
                             return (Dir p entries)
    where
    toEntry x   = do isDir <- doesDirectoryExist $ path ++ "/" ++ x
                     if isDir then readDirHier' path x
                              else return (File x)
                  where path = pre ++ "/" ++ p

    clean xs    = [ x | x <- xs, x /= "."     -- TODO: This should really be a
                               , x /= ".."    -- function provided by the caller.
                               , x /= "CVS"
                               , not (".#" `isPrefixOf` x)
                  ]
\end{code}

_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to