Add an AbsoluteOrRemotePath type
--------------------------------
> Eric Kow <[EMAIL PROTECTED]>**20081024170048
>  Ignore-this: 8b2ec1303eea170b88f2c8081efd1315
> ] hunk ./src/Darcs/RepoPath.hs 25
>                          SubPath, makeSubPathOf, simpleSubPath,
>                          AbsolutePathOrStd,
>                          makeAbsoluteOrStd, ioAbsoluteOrStd, useAbsoluteOrStd,
> +                        AbsoluteOrRemotePath, ioAbsoluteOrRemote, isRemote,
>                          makeRelative, sp2fn,
>                          FilePathOrURL(..), FilePathLike(toFilePath),
>                          getCurrentDirectory, setCurrentDirectory
> hunk ./src/Darcs/RepoPath.hs 31
>                        ) where
>  
> -import Data.List ( isPrefixOf )
> +import Data.List ( isPrefixOf, isSuffixOf )
>  import Control.Exception ( bracket )
>  
> hunk ./src/Darcs/RepoPath.hs 34
> -import Darcs.URL ( is_absolute, is_relative )
> +import Darcs.URL ( is_absolute, is_relative, is_ssh_nopath )
>  import Autoconf ( path_separator )
>  import qualified Workaround ( getCurrentDirectory )
>  import qualified System.Directory ( setCurrentDirectory )
Imports, export the new type (AbsoluteOrRemotePath) and two new functions
(ioAbsoluteOrRemote, isRemote).

> hunk ./src/Darcs/RepoPath.hs 55
>  newtype SubPath      = SubPath FilePath deriving (Eq, Ord)
>  newtype AbsolutePath = AbsolutePath FilePath deriving (Eq, Ord)
>  data AbsolutePathOrStd = AP AbsolutePath | APStd deriving (Eq, Ord)
> +data AbsoluteOrRemotePath = AbsP AbsolutePath | RmtP String deriving (Eq, 
> Ord)
>  
>  instance FilePathOrURL AbsolutePath where
>   toPath (AbsolutePath x) = x
> hunk ./src/Darcs/RepoPath.hs 64
>  instance CharLike c => FilePathOrURL [c] where
>   toPath = toFilePath
>  
> +instance FilePathOrURL AbsoluteOrRemotePath where
> + toPath (AbsP a) = toPath a
> + toPath (RmtP r) = r
> +
This toPath thing looks a little dangerous overall, but it's been there
before...

>  instance FilePathOrURL PatchFileName.FileName where
>      toPath = PatchFileName.fn2fp
>  instance FilePathLike PatchFileName.FileName where
> hunk ./src/Darcs/RepoPath.hs 162
>  useAbsoluteOrStd _ f APStd = f
>  useAbsoluteOrStd f _ (AP x) = f x
>  
> +ioAbsoluteOrRemote :: String -> IO AbsoluteOrRemotePath
> +ioAbsoluteOrRemote p = do
> +  isdir <- doesDirectoryExist p
> +  if not isdir
> +     then return $ RmtP $
> +          case () of _ | is_ssh_nopath p    -> p++"."
> +                       | "/" `isSuffixOf` p -> init p
> +                       | otherwise          -> p
> +     else AbsP `fmap` ioAbsolute p
> +
> +isRemote :: AbsoluteOrRemotePath -> Bool
> +isRemote (RmtP _) = True
> +isRemote _ = False
> +
>  takeDirectory :: AbsolutePath -> AbsolutePath
>  takeDirectory (AbsolutePath x) =
>      case reverse $ drop 1 $ dropWhile (/='/') $ reverse x of
> hunk ./src/Darcs/RepoPath.hs 189
>  instance Show AbsolutePathOrStd where
>      show (AP a) = show a
>      show APStd = "standard input/output"
> +instance Show AbsoluteOrRemotePath where
> +    show (AbsP a) = show a
> +    show (RmtP r) = show r
>  
>  cleanup :: Char -> Char
>  cleanup '\\' | path_separator == '\\' = '/'


Switch from absolute_dir to ioAbsoluteOrRemote in commands
----------------------------------------------------------
> Eric Kow <[EMAIL PROTECTED]>**20081027142933
>  Ignore-this: 79e892ea2f0732367b8d293b550946e9
>  Note that this is only a superficial change, but it brings
>  us one step closer to getting rid of FilePathUtils.
> ] hunk ./src/Darcs/Commands/Convert.lhs 50
>                            createPristineDirectoryTree,
>                            revertRepositoryChanges, 
> finalizeRepositoryChanges, sync_repo )
>  import Darcs.Global ( darcsdir )
> -import Darcs.FilePathUtils ( absolute_dir )
>  import Darcs.Patch ( RealPatch, Patch, Named, showPatch, patch2patchinfo, 
> fromPrims, infopatch,
>                       modernize_patch,
>                       adddeps, getdeps, effect, flattenFL, is_merger, 
> patchcontents )
> hunk ./src/Darcs/Commands/Convert.lhs 59
>  import Darcs.Patch.Info ( pi_rename, pi_tag )
>  import Darcs.Patch.Commute ( public_unravel )
>  import Darcs.Patch.Real ( mergeUnravelled )
> +import Darcs.RepoPath ( ioAbsoluteOrRemote, toPath )
>  import Darcs.Repository.Motd ( show_motd )
>  import Darcs.Utils ( clarify_errors, askUser )
>  import Darcs.Progress ( progressFL )
> hunk ./src/Darcs/Commands/Convert.lhs 126
>    vow' <- askUser ("by typing `" ++ vow ++ "': ")
>    when (vow' /= vow) $ fail "User didn't understand the consequences."
>    let opts = UseFormat2:orig_opts
> -  repodir <- absolute_dir inrepodir
> +  typed_repodir <- ioAbsoluteOrRemote inrepodir
> +  let repodir = toPath typed_repodir
>    show_motd opts repodir
>    mysimplename <- make_repo_name opts repodir
>    createDirectory mysimplename
> hunk ./src/Darcs/Commands/Get.lhs 64
>  import Darcs.Match ( have_patchset_match, get_one_patchset )
>  import Darcs.Utils ( catchall, formatPath, withCurrentDirectory )
>  import Darcs.Progress ( debugMessage )
> -import Darcs.FilePathUtils ( absolute_dir )
>  import Printer ( text, vcat, errorDoc, ($$), Doc, putDocLn, )
>  import Darcs.Lock ( writeBinFile )
> hunk ./src/Darcs/Commands/Get.lhs 66
> -import Darcs.RepoPath ( toFilePath )
> +import Darcs.RepoPath ( toFilePath, toPath, ioAbsoluteOrRemote)
>  import Darcs.Sealed ( Sealed(..), unsafeUnflippedseal )
>  import Darcs.Global ( darcsdir )
>  #include "impossible.h"
> hunk ./src/Darcs/Commands/Get.lhs 125
>  get_cmd opts [inrepodir, outname] = get_cmd (WorkDir outname:opts) 
> [inrepodir]
>  get_cmd opts [inrepodir] = do
>    debugMessage "Starting work on get..."
> -  repodir <- absolute_dir inrepodir
> +  typed_repodir <- ioAbsoluteOrRemote inrepodir
> +  let repodir = toPath typed_repodir
>    show_motd opts repodir
>    when (Partial `elem` opts) $ debugMessage "Reading checkpoint..."
>    mysimplename <- make_repo_name opts repodir
> hunk ./src/Darcs/Commands/Put.lhs 28
>  import Darcs.URL ( is_url, is_file )
>  import Darcs.Utils ( withCurrentDirectory )
>  import Darcs.Progress ( debugMessage )
> -import Darcs.FilePathUtils ( absolute_dir )
> +import Darcs.RepoPath ( ioAbsoluteOrRemote, toPath )
>  import Darcs.SlurpDirectory ( empty_slurpy )
>  import Darcs.External ( execSSH )
>  import Darcs.RemoteApply ( remote_apply )
> hunk ./src/Darcs/Commands/Put.lhs 77
>   do
>   repodir <- fixUrl opts unfixedrepodir
>   -- Test to make sure we aren't trying to push to the current repo
> - cur_absolute_repo_dir <- absolute_dir "."
> - req_absolute_repo_dir <- absolute_dir repodir
> + t_cur_absolute_repo_dir <- ioAbsoluteOrRemote "."
> + t_req_absolute_repo_dir <- ioAbsoluteOrRemote repodir
> + let cur_absolute_repo_dir = toPath t_cur_absolute_repo_dir
> +     req_absolute_repo_dir = toPath t_req_absolute_repo_dir
>   when (cur_absolute_repo_dir == req_absolute_repo_dir) $
>         fail "Can't put to current repository!"
>   when (is_url req_absolute_repo_dir) $ error "Can't put to a URL!"

This replaces occurances of absolute_dir with ioAbsoluteOrRemote, immediately
untyping it to preserve the rest of the code unchanged.

Replace absolute_dir with ioAbsoluteOrRemote in Darcs.Repository
----------------------------------------------------------------
> Eric Kow <[EMAIL PROTECTED]>**20081027155955
>  Ignore-this: 8f745c354308ca9406dbb2e54f66b600
>  only very superficially though
> ] hunk ./src/Darcs/Repository/Checkpoint.lhs 66
>  import Darcs.Patch.Depends ( get_patches_beyond_tag, get_patches_in_tag )
>  import Darcs.Repository.Prefs ( filetype_function )
>  import Darcs.Utils ( catchall )
> -import Darcs.FilePathUtils ( absolute_dir )
> +import Darcs.RepoPath ( ioAbsoluteOrRemote, toPath )
>  import Darcs.Global ( darcsdir )
>  import Printer ( Doc, ($$), empty )
>  #include "impossible.h"
> hunk ./src/Darcs/Repository/Checkpoint.lhs 85
>  \begin{code}
>  read_checkpoints :: String -> IO [(PatchInfo, Maybe Slurpy)]
>  read_checkpoints d = do
> -  realdir <- absolute_dir d
> +  realdir <- toPath `fmap` ioAbsoluteOrRemote d
>    pistr <- fetchFilePS (realdir++"/"++darcsdir++"/checkpoints/inventory") 
> Uncachable
>             `catchall` return B.empty
>    pis <- return $ reverse $ read_patch_ids pistr
> hunk ./src/Darcs/Repository/DarcsRepo.lhs 67
>  import Workaround ( renameFile )
>  import Darcs.Utils ( clarify_errors )
>  import Darcs.Progress ( debugMessage, beginTedious, endTedious, 
> finishedOneIO )
> -import Darcs.FilePathUtils ( absolute_dir )
> +import Darcs.RepoPath ( ioAbsoluteOrRemote, toPath )
>  import System.IO ( hPutStrLn, stderr )
>  import System.IO.Unsafe ( unsafeInterleaveIO )
>  import Control.Monad ( liftM, when, unless )
> hunk ./src/Darcs/Repository/DarcsRepo.lhs 184
>                              <> showPatchInfo (patch2patchinfo p)
>         when (is_tag $ patch2patchinfo p) $
>              do debugMessage "Optimizing the tentative inventory, since we're 
> adding a tag."
> -               realdir <- absolute_dir "."
> +               realdir <- toPath `fmap` ioAbsoluteOrRemote "."
>                 let k = "Reading tentative inventory"
>                 beginTedious k
>                 Sealed ps <- read_repo_private k opts realdir 
> "tentative_inventory"
> hunk ./src/Darcs/Repository/DarcsRepo.lhs 242
>  \begin{code}
>  copy_patches :: [DarcsFlag] -> FilePath -> FilePath -> [PatchInfo] -> IO ()
>  copy_patches opts dir out patches = do
> -  realdir <- absolute_dir dir
> +  realdir <- toPath `fmap` ioAbsoluteOrRemote dir
>    copyFilesOrUrls opts (realdir++"/"++darcsdir++"/patches") (map 
> make_filename patches)
>                         (out++"/"++darcsdir++"/patches") Cachable
>  
> hunk ./src/Darcs/Repository/DarcsRepo.lhs 248
>  read_repo :: RepoPatch p => [DarcsFlag] -> String -> IO (SealedPatchSet p)
>  read_repo opts d = do
> -  realdir <- absolute_dir d
> +  realdir <- toPath `fmap` ioAbsoluteOrRemote d
>    let k = "Reading inventory of repository "++d
>    beginTedious k
>    read_repo_private k opts realdir "inventory" `catch`
> hunk ./src/Darcs/Repository/DarcsRepo.lhs 257
>  
>  read_tentative_repo :: RepoPatch p => [DarcsFlag] -> String -> IO 
> (SealedPatchSet p)
>  read_tentative_repo opts d = do
> -  realdir <- absolute_dir d
> +  realdir <- toPath `fmap` ioAbsoluteOrRemote d
>    let k = "Reading tentative inventory of repository "++d
>    beginTedious k
>    read_repo_private k opts realdir "tentative_inventory" `catch`
> hunk ./src/Darcs/Repository/DarcsRepo.lhs 315
>  \begin{code}
>  read_checkpoints :: String -> IO [(PatchInfo, Maybe Slurpy)]
>  read_checkpoints d = do
> -  realdir <- absolute_dir d
> +  realdir <- toPath `fmap` ioAbsoluteOrRemote d
>    pistr <- fetchFilePS (realdir++"/"++darcsdir++"/checkpoints/inventory") 
> Uncachable
>             `catchall` return B.empty
>    pis <- return $ reverse $ read_patch_ids pistr
> hunk ./src/Darcs/Repository/HashedRepo.lhs 49
>  import Workaround ( renameFile )
>  import Darcs.Flags ( DarcsFlag, Compression )
>  import Darcs.Patch.Set ( PatchSet, SealedPatchSet )
> -import Darcs.FilePathUtils ( absolute_dir )
> -import Darcs.RepoPath ( FilePathLike )
> +import Darcs.RepoPath ( FilePathLike, ioAbsoluteOrRemote, toPath )
>  import Darcs.Repository.Cache ( Cache, fetchFileUsingCache, 
> speculateFileUsingCache,
>                                  writeFileUsingCache,
>                                  unionCaches, repo2cache, okayHash, takeHash,
> hunk ./src/Darcs/Repository/HashedRepo.lhs 160
>  
>  read_repo :: RepoPatch p => Repository p C(r u t) -> String -> IO (PatchSet 
> p C(r))
>  read_repo repo d = do
> -  realdir <- absolute_dir d
> +  realdir <- toPath `fmap` ioAbsoluteOrRemote d
>    Sealed ps <- read_repo_private repo realdir "hashed_inventory" `catch`
>                   (\e -> do hPutStrLn stderr ("Invalid repository:  " ++ 
> realdir)
>                             ioError e)
> hunk ./src/Darcs/Repository/HashedRepo.lhs 168
>  
>  read_tentative_repo :: RepoPatch p => Repository p C(r u t) -> String -> IO 
> (PatchSet p C(t))
>  read_tentative_repo repo d = do
> -  realdir <- absolute_dir d
> +  realdir <- toPath `fmap` ioAbsoluteOrRemote d
>    Sealed ps <- read_repo_private repo realdir "tentative_hashed_inventory" 
> `catch`
>                   (\e -> do hPutStrLn stderr ("Invalid repository:  " ++ 
> realdir)
>                             ioError e)
> hunk ./src/Darcs/Repository/Internal.hs 137
>  import Darcs.Patch.Apply ( markup_file, LineMark(None) )
>  import Darcs.Patch.Depends ( get_common_and_uncommon, deep_optimize_patchset 
> )
>  import Darcs.Diff ( unsafeDiffAtPaths, unsafeDiff )
> -import Darcs.RepoPath ( FilePathLike, AbsolutePath, toFilePath )
> +import Darcs.RepoPath ( FilePathLike, AbsolutePath, toFilePath,
> +                        ioAbsoluteOrRemote, toPath )
>  import Darcs.Utils ( promptYorn, catchall, withCurrentDirectory, withUMask, 
> nubsort )
>  import Darcs.Progress ( progressFL, debugMessage )
> hunk ./src/Darcs/Repository/Internal.hs 141
> -import Darcs.FilePathUtils ( absolute_dir )
>  import Darcs.URL ( is_file )
>  import Darcs.Repository.Prefs ( darcsdir_filter, boring_file_filter, 
> filetype_function,
>                                  getCaches )
> hunk ./src/Darcs/Repository/Internal.hs 202
>  maybeIdentifyRepository opts "." =
>      do darcs <- doesDirectoryExist darcsdir
>         rf_or_e <- identifyRepoFormat "."
> -       here <- absolute_dir "."
> +       here <- toPath `fmap` ioAbsoluteOrRemote "."
>         case rf_or_e of
>           Left err -> return $ Left err
>           Right rf ->
> hunk ./src/Darcs/Repository/Internal.hs 213
>                                           return $ Right $ Repo here opts rf 
> (DarcsRepository pris cs)
>                                   else return (Left "Not a repository")
>  maybeIdentifyRepository opts url' =
> - do url <- absolute_dir url'
> + do url <- toPath `fmap` ioAbsoluteOrRemote url'
>      rf_or_e <- identifyRepoFormat url
>      case rf_or_e of
>        Left e -> return $ Left e
> hunk ./src/Darcs/Repository/Internal.hs 947
>          do createDirectoryIfMissing True reldir
>             withCurrentDirectory reldir $ HashedRepo.copy_pristine c 
> (compression opts) r (darcsdir++"/hashed_inventory")
>      | otherwise =
> -        do dir <- absolute_dir reldir
> +        do dir <- toPath `fmap` ioAbsoluteOrRemote reldir
>             done <- withCurrentDirectory r $ easyCreatePristineDirectoryTree 
> pris dir
>             unless done $ do Sealed patches <- (seal . reverseRL . concatRL) 
> `liftM` read_repo repo
>                              createDirectoryIfMissing True dir
> hunk ./src/Darcs/Repository/Internal.hs 981
>  
>  checkPristineAgainstCwd :: RepoPatch p => Repository p C(r u t) -> IO Bool
>  checkPristineAgainstCwd (Repo dir _ rf (DarcsRepository p _))
> -    | not $ format_has HashedInventory rf = do here <- absolute_dir "."
> +    | not $ format_has HashedInventory rf = do here <- toPath `fmap` 
> ioAbsoluteOrRemote "."
>                                                 withCurrentDirectory dir $ 
> checkPristine here p
>  checkPristineAgainstCwd r =
>      do s <- mmap_slurp "."

Same thing again, absolute_dir ~ toPath `fmap` ioAbsoluteOrRemote (toPath is a
sort of unsafe type coercion thing for paths).


Replace (++ "/" ++) with filepath's (</>) in Darcs.External.cloneTree
---------------------------------------------------------------------
> Eric Kow <[EMAIL PROTECTED]>**20081027165044
>  Ignore-this: 2c820b01f52de3544dd05f87e88dbc50
> ] hunk ./src/Darcs/External.hs 50
>  #endif
>  import System.Posix.Files ( createLink )
>  import System.Directory ( createDirectoryIfMissing )
> +import System.FilePath ( (</>) )
>  
>  import Darcs.Flags ( DarcsFlag( SignAs, Sign, SignSSL, NoLinks,
>                                  Verify, VerifySSL ) )
> hunk ./src/Darcs/External.hs 141
>  
>  clonePath :: FilePath -> FilePath -> FilePath -> IO ()
>  clonePath source dest path
> - = do let source' = source ++ "/" ++ path
> -          dest' = dest ++ "/" ++ path
> + = do let source' = source </> path
> +          dest' = dest </> path
>        fs <- getSymbolicLinkStatus source'
>        if isDirectory fs then do
>            createDirectoryIfMissing True dest'
> hunk ./src/Darcs/External.hs 147
>         else if isRegularFile fs then do
> -          createDirectoryIfMissing True (dest ++ "/" ++ basename path)
> +          createDirectoryIfMissing True (dest </> basename path)
>            cloneFile source' dest'
>         else fail ("clonePath: Bad file " ++ source')
> hunk ./src/Darcs/External.hs 150
> -   `catch` fail ("clonePath: Bad file " ++ source ++ "/" ++ path)
> +   `catch` fail ("clonePath: Bad file " ++ source </> path)
>   where basename = reverse . dropWhile ('/' /=) . dropWhile ('/' ==) . reverse
>  
>  clonePartialsTree :: FilePath -> FilePath -> [FilePath] -> IO ()
> hunk ./src/Darcs/External.hs 159
>  clonePartialTree :: FilePath -> FilePath -> FilePath -> IO ()
>  clonePartialTree source dest "" = cloneTree source dest
>  clonePartialTree source dest pref
> - = do createDirectoryIfMissing True (dest ++ "/" ++ basename pref)
> -      cloneSubTree (source ++ "/" ++ pref) (dest ++ "/" ++ pref)
> + = do createDirectoryIfMissing True (dest </> basename pref)
> +      cloneSubTree (source </> pref) (dest </> pref)
>   where basename = reverse . dropWhile ('/' /=) . dropWhile ('/' ==) . reverse
>  
>  cloneTree :: FilePath -> FilePath -> IO ()
> hunk ./src/Darcs/External.hs 172
>      if isDirectory fs then do
>          fps <- getDirectoryContents source
>          let fps' = filter (`notElem` (".":"..":except)) fps
> -            mk_source fp = source ++ "/" ++ fp
> -            mk_dest   fp = dest   ++ "/" ++ fp
> +            mk_source fp = source </> fp
> +            mk_dest   fp = dest   </> fp
>          zipWithM_ cloneSubTree (map mk_source fps') (map mk_dest fps')
>       else fail ("cloneTreeExcept: Bad source " ++ source)
>     `catch` fail ("cloneTreeExcept: Bad source " ++ source)
> hunk ./src/Darcs/External.hs 185
>          createDirectory dest
>          fps <- getDirectoryContents source
>          let fps' = filter (`notElem` [".", ".."]) fps
> -            mk_source fp = source ++ "/" ++ fp
> -            mk_dest   fp = dest   ++ "/" ++ fp
> +            mk_source fp = source </> fp
> +            mk_dest   fp = dest   </> fp
>          zipWithM_ cloneSubTree (map mk_source fps') (map mk_dest fps')
>       else if isRegularFile fs then do
>          cloneFile source dest

Does just what the name says. I'm wondering if this gives us backslashes on
Windows though, which *might* pose an issue? Maybe keeping to FilePath.Posix
might be better for now, changing over everything at once when we know it is
safe to do so?


Replace basename with filepath's takeDirectory in Darcs.External.
-----------------------------------------------------------------
> Eric Kow <[EMAIL PROTECTED]>**20081027165405
>  Ignore-this: 2a3eec675e9f63cc0549317564bfee54
>  Note that basename was a misnomer in the original code.
> ] hunk ./src/Darcs/External.hs 50
>  #endif
>  import System.Posix.Files ( createLink )
>  import System.Directory ( createDirectoryIfMissing )
> -import System.FilePath ( (</>) )
> +import System.FilePath ( (</>), takeDirectory )
>  
>  import Darcs.Flags ( DarcsFlag( SignAs, Sign, SignSSL, NoLinks,
>                                  Verify, VerifySSL ) )
> hunk ./src/Darcs/External.hs 147
>        if isDirectory fs then do
>            createDirectoryIfMissing True dest'
>         else if isRegularFile fs then do
> -          createDirectoryIfMissing True (dest </> basename path)
> +          createDirectoryIfMissing True (dest </> takeDirectory path)
>            cloneFile source' dest'
>         else fail ("clonePath: Bad file " ++ source')
>     `catch` fail ("clonePath: Bad file " ++ source </> path)
> hunk ./src/Darcs/External.hs 151
> - where basename = reverse . dropWhile ('/' /=) . dropWhile ('/' ==) . reverse
>  
>  clonePartialsTree :: FilePath -> FilePath -> [FilePath] -> IO ()
>  clonePartialsTree source dest = mapM_ (clonePartialTree source dest)
> hunk ./src/Darcs/External.hs 158
>  clonePartialTree :: FilePath -> FilePath -> FilePath -> IO ()
>  clonePartialTree source dest "" = cloneTree source dest
>  clonePartialTree source dest pref
> - = do createDirectoryIfMissing True (dest </> basename pref)
> + = do createDirectoryIfMissing True (dest </> takeDirectory pref)
>        cloneSubTree (source </> pref) (dest </> pref)
> hunk ./src/Darcs/External.hs 160
> - where basename = reverse . dropWhile ('/' /=) . dropWhile ('/' ==) . reverse
>  
>  cloneTree :: FilePath -> FilePath -> IO ()
>  cloneTree = cloneTreeExcept []

This seems to do the right thing, however, basename and takeDirectory are not
equivalent:

Prelude System.FilePath> reverse . dropWhile ('/' /=) . dropWhile ('/' ==) . 
reverse $ "a/b/"
"a/"

Prelude System.FilePath> takeDirectory "a/b/"
"a/b"

Moreover, takeDirectory always removes any trailing slashes that would have
appeared in the result, whereas basename always keeps all trailing slashes
intact. (Ie. basename "a/b" -> "a/", takeDirectory "a/b" -> "a").

It doesn't matter here, since all we do is pass this to
createDirectoryIfMissing, but it might be worth keeping in mind in future
conversions of similar functions.

Replace UglyFileName normalisation in Darcs.External
----------------------------------------------------
> Eric Kow <[EMAIL PROTECTED]>**20081027170454
>  Ignore-this: 53c57c63eead2574dcf3e211b376fd7f
>  with System.FilePath equivalent
> ] hunk ./src/Darcs/External.hs 50
>  #endif
>  import System.Posix.Files ( createLink )
>  import System.Directory ( createDirectoryIfMissing )
> -import System.FilePath ( (</>), takeDirectory )
> +import System.FilePath ( (</>), takeDirectory, normalise )
>  
>  import Darcs.Flags ( DarcsFlag( SignAs, Sign, SignSSL, NoLinks,
>                                  Verify, VerifySSL ) )
> hunk ./src/Darcs/External.hs 72
>  import Ssh ( getSSH, copySSH, copySSHs, SSHCmd(..) )
>  import URL ( Cachable(..) )
>  import Exec ( exec, Redirect(..), withoutNonBlock )
> -import UglyFileName ( fn2fp, fp2fn, norm_path )
>  import Darcs.URL ( is_file, is_url, is_ssh )
>  import Darcs.Utils ( catchall )
>  import Printer ( Doc, Printers, putDocLnWith, hPutDoc, hPutDocLn, 
> hPutDocWith, ($$), (<+>), renderPS,
> hunk ./src/Darcs/External.hs 91
>    copy x y = do
>      isD <- doesDirectoryExist x
>      if isD then do createDirectory y
> -                   cloneTree (do_norm x) (do_norm y)
> +                   cloneTree (normalise x) (normalise y)
>             else copyFile x y
> hunk ./src/Darcs/External.hs 93
> -  do_norm f = fn2fp $ norm_path $ fp2fn f
>  
>  backupBy :: (FilePath -> FilePath -> IO ()) -> FilePath -> IO ()
>  backupBy backup f =

Ahw, norm_path is pretty complex. Again, it doesn't seem to matter here, but
let's be a little paranoid:

Prelude UglyFileName Test.QuickCheck System.FilePath> quickCheck (\ p -> 
normalise p == (fn2fp $ norm_path $ fp2fn p))
*** Failed! Falsifiable (after 98 tests and 5 shrinks):    
"/"

Prelude UglyFileName Test.QuickCheck System.FilePath> quickCheck (\ p -> (p /= 
"/") ==> normalise p == (fn2fp $ norm_path $ fp2fn p))
*** Failed! Falsifiable (after 43 tests and 2 shrinks):    
"a/"

Prelude UglyFileName Test.QuickCheck System.FilePath> sequence [ quickCheck (\ 
p -> (if not $ null p then last p /= '/' else True) ==> normalise p == (fn2fp $ 
norm_path $ fp2fn p)) | _ <- [1..] ]

>From here, this passes everything I threw at it. So again, the only difference
seems to be the trailing slash. Good.

Specify that we want System.FilePath.Posix in Darcs.External
------------------------------------------------------------
> Eric Kow <[EMAIL PROTECTED]>**20081027172514
>  Ignore-this: 8548e7e86f2c5dff1ddf0806e48bda15
>  to prevent the accidental creation of patches with backslashes
>  in their paths.
> ] hunk ./src/Darcs/External.hs 50
>  #endif
>  import System.Posix.Files ( createLink )
>  import System.Directory ( createDirectoryIfMissing )
> -import System.FilePath ( (</>), takeDirectory, normalise )
> +import System.FilePath.Posix ( (</>), takeDirectory, normalise )
>  
>  import Darcs.Flags ( DarcsFlag( SignAs, Sign, SignSSL, NoLinks,
>                                  Verify, VerifySSL ) )

Okey, just what I was concerned above. We ensure </> gives us forward slashes
here even on Windows.


Replace FilePathUtils.(///) with filepath equivalent in preproc
---------------------------------------------------------------
> Eric Kow <[EMAIL PROTECTED]>**20081027173947
>  Ignore-this: 99a21202f798d6423d047afe4b417403
> ] hunk ./src/preproc.hs 1
> +import System.FilePath ( (///) )
>  import System.Environment ( getArgs )
>  import System.Exit ( exitWith, ExitCode(..) )
>  import Text.Regex ( matchRegex, mkRegex )
> hunk ./src/preproc.hs 9
>  import Darcs.Commands
>  import Darcs.Arguments
>  import Darcs.Commands.Help ( command_control_list )
> -import Darcs.FilePathUtils ( (///) )
>  import Autoconf ( darcs_version )
>  
>  the_commands :: [DarcsCommand]
> replace ./src/preproc.hs [</>] /// </>

Indeed, we just use </> instead of ///. Again, same thing as above, same remark
about FilePath.Posix. (Oh, but this is just preproc.hs, so a non-issue I
presume.)

Replace UglyFileName with filepath equivalents in Darcs.RepoPath
----------------------------------------------------------------
> Eric Kow <[EMAIL PROTECTED]>**20081028141522
>  Ignore-this: c685595782a0eb01e7b7c37da991e7b9
> ] hunk ./src/Darcs/RepoPath.hs 39
>  import qualified Workaround ( getCurrentDirectory )
>  import qualified System.Directory ( setCurrentDirectory )
>  import System.Directory ( doesDirectoryExist )
> -import UglyFileName ( fn2fp, super_name, fp2fn, own_name, norm_path )
> +import qualified System.FilePath.Posix as FilePath
>  import qualified Darcs.Patch.FileName as PatchFileName ( FileName, fp2fn, 
> fn2fp )
>  
>  class FilePathOrURL a where
> hunk ./src/Darcs/RepoPath.hs 97
>      else Nothing
>  
>  simpleSubPath :: FilePath -> Maybe SubPath
> -simpleSubPath x | is_relative x = Just $ SubPath $ fn2fp $ norm_path $ fp2fn 
> $ map cleanup x
> +simpleSubPath x | is_relative x = Just $ SubPath $ FilePath.normalise $ map 
> cleanup x
>                  | otherwise = Nothing
>  
>  makeRelative :: AbsolutePath -> AbsolutePath -> FilePath
> hunk ./src/Darcs/RepoPath.hs 119
>           then bracket (setCurrentDirectory dir)
>                        (const $ setCurrentDirectory $ toFilePath here)
>                        (const getCurrentDirectory)
> -         else let super_dir = (fn2fp . super_name . fp2fn) dir
> -                  file = (fn2fp . own_name . fp2fn) dir
> +         else let super_dir = case FilePath.takeDirectory dir of
> +                                "" ->  "."
> +                                d  -> d
> +                  file = FilePath.takeFileName dir
>                in do abs_dir <- ioAbsolute super_dir
>                      return $ makeAbsolute abs_dir file
>  
> hunk ./src/Darcs/RepoPath.hs 129
>  makeAbsolute :: AbsolutePath -> FilePath -> AbsolutePath
>  makeAbsolute a dir = if is_absolute dir
>                       then AbsolutePath $
> -                          slashes ++ (fn2fp $ norm_path $ fp2fn cleandir)
> -                     else ma a $ fn2fp $ norm_path $ fp2fn cleandir
> +                          slashes ++ FilePath.normalise cleandir
> +                     else ma a $ FilePath.normalise cleandir
>    where
>      cleandir  = map cleanup dir
>      slashes = norm_slashes $ takeWhile (== '/') cleandir
>

>From a distance, this looks safe (with the above remarks about normalise). A
good catch about the "." case, too.

Sorry to have taken this long, but it's a busy day today and other issues keep
interrupting me. : - \ Hopefully, you find the review helpful.

Yours,
   Petr.

-- 
Peter Rockai | me()mornfall!net | prockai()redhat!com
 http://blog.mornfall.net | http://web.mornfall.net

"In My Egotistical Opinion, most people's C programs should be
 indented six feet downward and covered with dirt."
     -- Blair P. Houghton on the subject of C program indentation
_______________________________________________
darcs-users mailing list
[email protected]
http://lists.osuosl.org/mailman/listinfo/darcs-users

Reply via email to