[Haskell-cafe] Suggested additions to System.FilePath.Posix/Windows

Marcus D. Gabriel marcus at gabriel.name
Thu Sep 17 05:58:32 EDT 2009


Hello Neil

I used System.FilePath.Posix quite extensively recently, and I thank
you for the package filepath.  There were however two words that I
needed which I could not construct from those in
System.FilePath.Posix.  They are maybe of interest to you and others.

I submit these two words to you for consideration for inclusion in
System.FilePath.Posix.  Please change the names as you see fit.

I do not know if they make sense for System.FilePath.Windows.  If
the do not make sense, then please feel free to drop them so as to
preserve the interface.

As requested, I Cc'ed the haskell-cafe, but I am not at the moment
following these threads, so if anyone else responds, please Cc me
if you wish.

Thanks again and cheers,
- Marcus

P.S. Here they are.  Although I use ksh(1) as an example, this is a
feature of POSIX shells.

> -- | 'reduceFilePath' returns a pathname that is reduced to canonical
> -- form equivalent to that of ksh(1), that is, symbolic link names are
> -- treated literally when finding the directory name.  See @cd -L@ of
> -- ksh(1).  Specifically, extraneous separators @(\"/\")@, dot
> -- @(\".\")@, and double-dot @(\"..\")@ directories are removed.
>
> reduceFilePath :: FilePath -> FilePath
> reduceFilePath = joinPath . filePathComponents

This is in turn built on filePathComponents that does all the work.

> filePathComponents :: FilePath -> [FilePath]
> filePathComponents ""     = []
> filePathComponents (c:cs) =
>     reverse $ snd $ foldl accumulate
>                           (if c == pathSeparator then ([],["/"]) else
> ([c],[]))
>                           (cs++[pathSeparator])
>     where
>     accumulate :: (String,[String]) -> Char -> (String,[String])
>     accumulate (cs, css) c =
>         if c == pathSeparator
>         then ([],(if null cs then id else cons cs) css)
>         else (cs++[c],css)
>     cons :: String -> [String] -> [String]
>     cons cs css
>         | cs == "." = css
>         | cs /= ".." || null css = cs : css
>         | otherwise =
>           let hd = head css
>               tl = tail css
>           in if hd == [pathSeparator]
>              then css
>              else if hd == ".."
>                   then cs : css
>                   else if null tl
>                        then ["."]
>                        else tl

//

-- 
  Marcus D. Gabriel, Ph.D.                         Saint Louis, FRANCE
  http://www.marcus.gabriel.name            mailto:marcus at gabriel.name
  Tel: +33.3.89.69.05.06                   Portable: +33.6.34.56.07.75




More information about the Haskell-Cafe mailing list