[Haskell] Reading a directory tree

Gregory Wright gwright at comcast.net
Tue Jun 22 10:03:27 EDT 2004


Hi Tom,

Attached is a haskell file I wrote when I was learning how to use the
directory functions. It builds a tree structure corresponding to the 
directory
tree and finds the files that end in ".txt". It then sorted the files 
in order
of modification time. As you can guess from the program, it was for 
managing
weblog entries in Blosxom.

It's beginner-ish code, but you can probably adapt it to your needs.
Note that the top level directory name "dir" is hardcoded into the 
program.


Best Wishes,
Greg


On Jun 22, 2004, at 5:20 AM, Tom Hofte wrote:

> Hi,
>  
> 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.
> For example, I want to find a file, corresponding to a given 
> filename, in a directory and its subdirectories.
>  
> Is there a way to implement this in Haskell?
>  
> Kind regards,
>  
> Tom Hofte
>  
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>

dirtree.hs:

--
-- walk a directory tree and find all of the files ending in .txt
--

module Main (main) where

import Monad
import Directory
import Text.Regex
import List

--
-- dirTree returns a tree with nodes containing file
-- information or directory information and a subdirectory.
--

data DTree = FileNode String | DirNode String [DTree]


addPrefix d str = do return (d ++ str)
addSuffix d str = do return (str ++ d)

scanDir d = do
         dentries <- getDirectoryContents d

         files  <- mapM (addPrefix d) dentries
         ffiles <- filterM doesFileExist files

         -- directory names require extra processing: we must delete the 
"." and ".." entries
         -- and add a trailing "/"

         dirs    <- filterM (\x -> do return (x /= "." && x /= "..")) 
dentries
         ddirs   <- mapM (addPrefix d) dirs
         dddirs  <- mapM (addSuffix "/") ddirs
         subdirs <- filterM doesDirectoryExist dddirs

         subDTrees <- mapM scanDir subdirs

         return (DirNode d ((map (\f -> FileNode f) ffiles) ++ 
subDTrees))


-- walk a directory tree, printing the contents

showDTree (FileNode fname) = do print fname
showDTree (DirNode  dname ds) = do
         print dname
         mapM showDTree ds
         return ()

-- given a directory tree, find the files that end in ".txt"

findTxt (DirNode dname ds) = concat (map findTxt ds)
findTxt (FileNode fname)   = if (isTextFile fname) then [fname] else []

-- given a file name, see if it ends in ".txt"

isTextFile f = (matchRegex regexp f) /= Nothing where regexp = mkRegex 
".*txt"
printIfMatched f = if (isTextFile f) then do print f else do return ()


dir = "/Users/gwright/Desktop/Blosxom/docs/"

timeSortedFiles d = do
        directoryTree <- scanDir d
        showDTree directoryTree
        textFiles     <- do return (findTxt directoryTree)
        modTimes      <- mapM getModificationTime textFiles

        fs  <- do return (sortBy (\(f1,t1) (f2,t2) -> compare t1 t2) 
(zip textFiles modTimes))
        return (map fst fs)


main = do
        fs  <- timeSortedFiles dir
        fs' <- do return (take 1 fs)
        mapM (\f -> do c <- readFile f; putStr c) fs'
        return ()

-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: text/enriched
Size: 3746 bytes
Desc: not available
Url : http://www.haskell.org//pipermail/haskell/attachments/20040622/27a3f90e/attachment.bin


More information about the Haskell mailing list