What about something as simple as this?<div><br></div><div><br></div><div><div>import           Control.Monad (forM)</div><div>import           System.Directory (doesDirectoryExist, getDirectoryContents)</div><div>import           System.FilePath ((&lt;/&gt;))</div>
<div>import qualified Data.ByteString as B</div><div>import           Data.Digest.OpenSSL.MD5 (md5sum)</div><div>import qualified Data.Map as M</div><div><br></div><div>getRecursiveContents :: FilePath -&gt; IO [FilePath]</div>
<div>getRecursiveContents topdir = do</div><div>        names &lt;- getDirectoryContents topdir</div><div>        let properNames = filter (`notElem` [&quot;.&quot;, &quot;..&quot;]) names</div><div>        paths &lt;- forM properNames $ \name -&gt; do</div>
<div>                let path = topdir &lt;/&gt; name</div><div>                isDirectory &lt;- doesDirectoryExist path</div><div>                if isDirectory</div><div>                        then getRecursiveContents path</div>
<div>                        else return [path]</div><div>        return (concat paths)</div><div><br></div><div>getMD5 :: FilePath -&gt; IO String</div><div>getMD5 file = md5sum `fmap` B.readFile file</div><div><br></div>
<div>main :: IO ()</div><div>main = do</div><div>        files &lt;- getRecursiveContents &quot;.&quot;</div><div>        md5s &lt;- sequence $ map getMD5 files</div><div>        let m = M.fromListWith (++) $ zip md5s [[f] | f &lt;- files]</div>
<div>        putStrLn $ M.showTree m</div></div><div><br></div><div><br></div><div>The biggest part is the &quot;getRecursiveContent&quot;, shamelessly stolen from RWH.</div><div><br></div><div>L.</div><div><br></div><div>
<br></div><div><br><br><div class="gmail_quote">On Sun, Mar 18, 2012 at 5:43 PM, Yawar Amin <span dir="ltr">&lt;<a href="mailto:yawar.amin@gmail.com">yawar.amin@gmail.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
Hi Michael,<br>
<br>
Michael Schober &lt;Micha-Schober &lt;at&gt; <a href="http://web.de" target="_blank">web.de</a>&gt; writes:<br>
<br>
&gt; [...]<br>
<div class="im">&gt; I took the liberty to modify the output a little bit to my needs - maybe<br>
&gt; a future reader will find it helpful, too. It&#39;s attached below.<br>
<br>
</div>I kind of played around with your example a little bit and wondered if it<br>
could be implemented in terms of just the basic Haskell Platform<br>
modules and functions. So as an exercise I rolled my own directory<br>
traversal and duplicate finder functions. This is what I came up with:<br>
<br>
- walkDirWith: walks a given directory with a given function that takes a<br>
Handle to any (unknown type) value, and returns association lists of<br>
paths and the unknown type values.<br>
<br>
- filePathMap: I think roughly analogous to your duplicates function.<br>
<br>
- main: In the third line of the main function, I use hFileSize as an<br>
example of a function that takes a Handle to an IO value, in this case IO<br>
Integer. A hash function could easily be put in here. The last line<br>
pretty-prints the Map in a tree-like format.<br>
<br>
import System.IO<br>
import System.Environment (getArgs)<br>
import System.Directory ( doesDirectoryExist<br>
                        , getDirectoryContents)<br>
import Control.Monad (mapM)<br>
import Control.Applicative ((&lt;$&gt;))<br>
import System.FilePath ((&lt;/&gt;))<br>
<div class="im">import qualified Data.Map as M<br>
<br>
</div>walkDirWith :: FilePath -&gt; (Handle -&gt; IO r) -&gt; IO [(r, FilePath)] -&gt;<br>
               IO [(r, FilePath)]<br>
walkDirWith path f walkList = do<br>
  isDir &lt;- doesDirectoryExist path<br>
  if isDir<br>
    then do<br>
      paths &lt;- getDirectoryContents path<br>
      concat &lt;$&gt; mapM (\p -&gt; walkDirWith (path &lt;/&gt; p) f walkList)<br>
                      [p | p &lt;- paths, p /= &quot;.&quot;, p /= &quot;..&quot;]<br>
    else do<br>
      rValue &lt;- withFile path ReadMode f<br>
      ((:) (rValue, path)) &lt;$&gt; walkList<br>
<br>
filePathMap :: Ord r =&gt; [(r, FilePath)] -&gt; M.Map r [FilePath]<br>
filePathMap pathPairs =<br>
  foldl (\theMap (r, path) -&gt; M.insertWith&#39; (++) r [path] theMap)<br>
        M.empty<br>
        pathPairs<br>
<br>
main :: IO ()<br>
<div class="im">main = do<br>
  [dir] &lt;- getArgs<br>
</div>  fileSizes &lt;- walkDirWith dir hFileSize $ return []<br>
  putStr . M.showTree $ filePathMap fileSizes<br>
<br>
Obviously there&#39;s no right or wrong way to do it, but I&#39;m wondering<br>
what you think.<br>
<br>
Regards,<br>
<br>
Yawar<br>
<div class="HOEnZb"><div class="h5"><br>
<br>
<br>
_______________________________________________<br>
Beginners mailing list<br>
<a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/beginners" target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a><br>
</div></div></blockquote></div><br></div>