Hi Eric.
On Wed, Nov 12, 2008 at 6:51 PM, Eric Kow <[EMAIL PROTECTED]> wrote:
> Hi Dmitry,
>
> Can I ask you to review this one? Thanks!
>
All looks good. The only thing I would change is using takeFilename
instead of takeBaseName in Darcs.Commands.Dist. See below for more
(mostly useless) comments.
Replace our breakup with filepath's splitDirectories in Darcs.Lock
------------------------------------------------------------------
Eric Kow <[EMAIL PROTECTED]>**20081112150313
> hunk ./src/Darcs/Lock.hs 49
> getDirectoryContents, createDirectory,
> getTemporaryDirectory,
> )
> +import System.FilePath.Posix ( splitDirectories )
> import Workaround ( renameFile )
> import Darcs.Utils ( withCurrentDirectory, maybeGetEnv, firstJustIO )
> import Control.Monad ( unless, when )
> hunk ./src/Darcs/Lock.hs 65
>
> import Darcs.SignalHandler ( withSignalsBlocked )
> import Printer ( Doc, hPutDoc, packedString, empty, renderPSs )
> -import UglyFileName ( breakup )
> import Darcs.Global ( atexit, darcsdir )
> import Darcs.Compat ( mk_stdout_temp, canonFilename, maybeRelink,
> atomic_create, sloppy_atomic_create )
Changed imports.
> hunk ./src/Darcs/Lock.hs 176
> getCurrentDirectorySansDarcs = do
> c <- getCurrentDirectory
> return $ listToMaybe $ drop 5 $ reverse $ takeWhile no_darcs $ inits $
> toFilePath c
> - where no_darcs x = not $ darcsdir `elem` breakup x
> + where no_darcs x = not $ darcsdir `elem` splitDirectories x
>
> data WithDirKind = Perm | Temp | Delayed
>
Replace breakup with splitDirectories. Just what patch description says.
I have looked in docs and looks like this is equivalent here. But in
general splitDirectories is not the same as breakup for absolute
paths:
breakup "/a/b/c" = ["a","b","c"]
splitDirectories "/a/b/c" = ["/","a","b","c"]
Replace UglyFileName with filepath equivalents in Darcs.CommandsAux
-------------------------------------------------------------------
Eric Kow <[EMAIL PROTECTED]>**20081112150646
> hunk ./src/Darcs/CommandsAux.hs 26
> module Darcs.CommandsAux ( check_paths, malicious_patches,
> has_malicious_path,
> ) where
> import Darcs.Flags ( DarcsFlag( RestrictPaths, DontRestrictPaths ) )
> -import UglyFileName ( breakup, is_explicitly_relative )
> import Darcs.Patch ( Patchy, list_touched_files )
> import Darcs.Ordered ( FL, mapFL )
> import Darcs.Sealed ( Sealed2(..), unseal2 )
> hunk ./src/Darcs/CommandsAux.hs 31
> import Darcs.Global ( darcsdir )
> import Data.List ( intersect )
> +import System.FilePath ( splitDirectories )
>
> -- * File paths
> {-
Imports.
> hunk ./src/Darcs/CommandsAux.hs 98
> is_malicious_path :: String -> Bool
> is_malicious_path fp =
> not (is_explicitly_relative fp) ||
> - breakup fp `contains_any` [ "..", darcsdir ]
> + splitDirectories fp `contains_any` [ "..", darcsdir ]
> where
> contains_any a b = not . null $ intersect a b
Breakup replaced similar to the previous patch. Should be safe.
> hunk ./src/Darcs/CommandsAux.hs 101
> +
> +is_explicitly_relative :: String -> Bool
> +is_explicitly_relative ('.':'/':_) = True -- begins with "./"
> +is_explicitly_relative _ = False
Copied from UglyFileName to avoid import.
Copy UglyFileName.patch_filename into Darcs.Commands.Send
---------------------------------------------------------
Eric Kow <[EMAIL PROTECTED]>**20081112150818
> hunk ./src/Darcs/Commands/Send.lhs 24
> {-# LANGUAGE CPP #-}
>
> module Darcs.Commands.Send ( send ) where
> +import Data.Char ( isAlpha, isDigit, isSpace, toLower )
> import System.Exit ( exitWith, ExitCode( ExitSuccess ) )
> import System.IO.Error ( ioeGetErrorString )
> import System.IO ( hClose )
> hunk ./src/Darcs/Commands/Send.lhs 69
> import Darcs.Progress ( debugMessage )
> import Darcs.Email ( make_email )
> import Printer ( Doc, vsep, vcat, text, ($$), putDocLn, putDoc )
> -import UglyFileName ( patch_filename )
> import Darcs.RepoPath ( toFilePath, AbsolutePath, AbsolutePathOrStd,
> getCurrentDirectory, makeAbsoluteOrStd,
> useAbsoluteOrStd )
> import HTTP ( postUrl )
Imports.
> hunk ./src/Darcs/Commands/Send.lhs 259
> lt (t:ts) = t++" , "++lt ts
> lt [] = ""
>
> +safeFileChar :: Char -> Char
> +safeFileChar c | isAlpha c = toLower c
> + | isDigit c = c
> + | isSpace c = '-'
> +safeFileChar _ = '_'
> +
> +patch_filename :: String -> String
> +patch_filename the_summary = name ++ ".dpatch"
> + where name = map safeFileChar the_summary
> \end{code}
>
> \begin{options}
safeFileChar and patch_filename are copied from UglyFileName to avoid
import.
Replace homegrown code with filepath functions in Darcs.Commands.Dist
---------------------------------------------------------------------
Eric Kow <[EMAIL PROTECTED]>**20081112152219
> hunk ./src/Darcs/Commands/Dist.lhs 25
> import Workaround ( getCurrentDirectory )
> import System.Exit ( ExitCode(..) )
> import System.Cmd ( system )
> +import System.FilePath.Posix ( takeBaseName, (</>) )
> import Data.Char ( isAlphaNum )
> import Control.Monad ( when )
>
> hunk ./src/Darcs/Commands/Dist.lhs 38
> import Darcs.Lock ( withTemp, withTempDir, readBinFile )
> import Darcs.RepoPath ( toFilePath )
> import Darcs.Utils ( withCurrentDirectory )
> -import UglyFileName ( own_name, fn2fp, fp2fn )
> import Exec ( exec, Redirect(..) )
>
> \end{code}
Imports.
> hunk ./src/Darcs/Commands/Dist.lhs 103
> path_list <- if null args
> then return [""]
> else map toFilePath `fmap` fixSubPaths opts args
> - resultfile <- return (formerdir++"/"++distname++".tar.gz")
> + resultfile <- return (formerdir</>distname++".tar.gz")
> withTemp $ \tarfile ->
> withTempDir "darcsdist" $ \tempdir -> do
> setCurrentDirectory (formerdir)
> hunk ./src/Darcs/Commands/Dist.lhs 107
> - withTempDir (toFilePath tempdir++"/"++(basename distname)) $ \ddir ->
> do
> + withTempDir (toFilePath tempdir </> takeBaseName distname) $ \ddir ->
> do
> if have_nonrange_match opts
> then withCurrentDirectory ddir $ get_nonrange_match repository opts
> else createPartialsPristineDirectoryTree repository path_list
> (toFilePath ddir)
> hunk ./src/Darcs/Commands/Dist.lhs 114
> case predist of Nothing -> return ExitSuccess
> Just pd -> system pd
> setCurrentDirectory (toFilePath tempdir)
> - exec "tar" ["-cf", "-", safename $ basename $ toFilePath ddir]
> + exec "tar" ["-cf", "-", safename $ takeBaseName $ toFilePath ddir]
> (Null, File tarfile, AsIs)
> when verb $ withTemp $ \tar_listing -> do
> exec "tar" ["-tf", "-"]
> hunk ./src/Darcs/Commands/Dist.lhs 125
> (File tarfile, File resultfile, AsIs)
> putStrLn $ "Created dist as "++resultfile
> where
> - basename = fn2fp . own_name . fp2fn
> safename n@(c:_) | isAlphaNum c = n
> safename n = "./" ++ n
Use </> instead of direct "/" concat, use takeBaseName instead of
own_name.
Why do you use takeBaseName here and not takeFileName? They have the
same effect here since we apply them to directories. But I think
takeFileName would make it a little easier to read.
Replace FilePathUtils.(///) with filepath equivalent in Darcs.Diff
------------------------------------------------------------------
Eric Kow <[EMAIL PROTECTED]>**20081112153114
> hunk ./src/Darcs/Diff.hs 64
> #endif
> )
> #ifndef GADT_WITNESSES
> -import Darcs.FilePathUtils ( (///) )
> +import System.FilePath.Posix ( (///) )
> #endif
> import Darcs.Patch ( Prim
> #ifndef GADT_WITNESSES
Imports.
> replace ./src/Darcs/Diff.hs [</>] /// </>
Replace (///) with </>. Looks good. But it took me a second to
understand why you import (///) from System.FilePath.Posix and not </>
:)
Specifically import System.FilePath.Posix in darcs commands
-----------------------------------------------------------
Eric Kow <[EMAIL PROTECTED]>**20081112153509
> We want to document the fact that we are only using forward
> slashes.
> ] hunk ./src/Darcs/Commands/Diff.lhs 25
>
> module Darcs.Commands.Diff ( diff_command ) where
>
> -import System.FilePath ( takeFileName )
> +import System.FilePath.Posix ( takeFileName )
> import System.Directory ( setCurrentDirectory )
> import Workaround ( getCurrentDirectory )
> import Darcs.Utils ( askUser, withCurrentDirectory )
> hunk ./src/Darcs/Commands/ShowContents.lhs 24
>
> import Control.Monad ( filterM )
> import System.IO ( stdout )
> -import System.FilePath ( takeFileName )
> +import System.FilePath.Posix ( takeFileName )
>
> import qualified Data.ByteString as B
> import Workaround ( getCurrentDirectory )
Just what the patch description says.
Replace homegrown code with filepath equivalents in Darcs.Commands.Add
----------------------------------------------------------------------
Eric Kow <[EMAIL PROTECTED]>**20081112153944
> hunk ./src/Darcs/Commands/Add.lhs 44
> doesFileReallyExist, slurp_hasdir,
> )
> import Darcs.Patch.FileName ( fp2fn )
> -import Darcs.FilePathUtils ( (///) )
> import Darcs.RepoPath ( toFilePath )
> import Control.Monad ( when )
> import Darcs.Repository.Prefs ( darcsdir_filter, boring_file_filter )
> hunk ./src/Darcs/Commands/Add.lhs 48
> import Data.Maybe ( maybeToList )
> +import System.FilePath.Posix ( takeDirectory, (</>) )
> import System.IO ( hPutStrLn, stderr )
> import qualified System.FilePath.Windows as WindowsFilePath
> \end{code}
> hunk ./src/Darcs/Commands/Add.lhs 206
> return (cur, Nothing, Nothing)
> Just s' -> do putVerbose $ msg_adding msgs++" '"++f++"'"
> return (s', Just p, Nothing)
> - parentdir = get_parentdir f
> + parentdir = takeDirectory f
> have_parentdir = slurp_hasdir (fp2fn parentdir) cur
> parent_error = if have_parentdir
> then ""
Replace get_parentdir with takeDirectory.
> hunk ./src/Darcs/Commands/Add.lhs 271
> isdir <- doesDirectoryReallyExist f
> if not isdir then return [f]
> else do fs <- withCurrentDirectory f list_files
> - return $ f: map ((///) f) fs
> + return $ f: map (f </>) fs
>
> get_parents :: Slurpy -> [FilePath] -> IO [FilePath]
> get_parents cur fs =
Replace (///) with </>.
> hunk ./src/Darcs/Commands/Add.lhs 282
> then return []
> else do grandparents <- get_parent cur parentdir
> return (grandparents ++ [parentdir])
> - where parentdir = get_parentdir f
> -
> -get_parentdir :: FilePath -> FilePath
> -get_parentdir f = reverse $ drop 1 $ dropWhile (/='/') $ reverse f
> -
> + where parentdir = takeDirectory f
> \end{code}
>
Replace get_parentdir with takeDirectory and remove get_parentdir.
Remove homegrown code with filepath equivalents in Darcs.Commands.Mv
--------------------------------------------------------------------
Eric Kow <[EMAIL PROTECTED]>**20081112154541
> hunk ./src/Darcs/Commands/Mv.lhs 33
> fixSubPaths, working_repo_dir,
> list_files, allow_problematic_filenames,
> umask_option,
> )
> -import Darcs.FilePathUtils ( (///) )
> import Darcs.RepoPath ( toFilePath, sp2fn )
> hunk ./src/Darcs/Commands/Mv.lhs 34
> +import System.FilePath.Posix ( (</>), takeFileName )
> import System.Directory ( renameDirectory )
> import Workaround ( renameFile )
> import Darcs.Repository ( Repository, withRepoLock, ($-), amInRepository,
> hunk ./src/Darcs/Commands/Mv.lhs 130
>
> move_to_dir :: RepoPatch p => Repository p -> [DarcsFlag] -> [FilePath] ->
> FilePath -> IO ()
> move_to_dir repository opts moved finaldir =
> - let movefns = map (reverse.takeWhile (/='/').reverse) moved
> - movetargets = map (finaldir///) movefns
> + let movefns = map takeFileName moved
> + movetargets = map (finaldir </>) movefns
> movepatches = zipWith Darcs.Patch.move moved movetargets
> in do
> cur <- slurp_pending repository
Use takeFileName and </>. Looks good.
Remove deprecated (and now unused) homegrown filepath modules
-------------------------------------------------------------
Eric Kow <[EMAIL PROTECTED]>**20081112154607
> hunk ./src/Darcs/FilePathUtils.hs 1
> -{-# OPTIONS_GHC -cpp #-}
> -{-# LANGUAGE CPP #-}
> -
> --- Copyright (C) 2005 David Roundy
> ---
> --- This program is free software; you can redistribute it and/or modify
> --- it under the terms of the GNU General Public License as published by
> --- the Free Software Foundation; either version 2, or (at your option)
> --- any later version.
> ---
> --- This program is distributed in the hope that it will be useful,
> --- but WITHOUT ANY WARRANTY; without even the implied warranty of
> --- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
> --- GNU General Public License for more details.
> ---
> --- You should have received a copy of the GNU General Public License
> --- along with this program; see the file COPYING. If not, write to
> --- the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
> --- Boston, MA 02110-1301, USA.
> -
> -module Darcs.FilePathUtils ( absolute_dir, (///) ) where
> -
> -import System.Directory ( doesDirectoryExist )
> -import Darcs.Utils ( withCurrentDirectory )
> -import Workaround ( getCurrentDirectory )
> -import Darcs.URL ( is_ssh_nopath )
> -import UglyFileName ( fn2fp, fp2fn, norm_path )
> -
> --- WARNING, WARNING, WARNING!!!!
> -
> --- This file is deprecated in favor of the newer Darcs.RepoPath. It's
> --- still got a few functions, which are gradually being moved
> --- elsewhere. Please do not add new functions here, and if possible,
> --- avoid using these functions in new places.
> -
> -absolute_dir :: FilePath -> IO FilePath
> -absolute_dir dir = do
> - isdir <- doesDirectoryExist dir
> - if not isdir
> - then if is_ssh_nopath dir
> - then return $ dir++"."
> - else return $ if (take 1 $ reverse dir) == "/"
> - then init dir
> - else dir
> - -- hope it's an URL
> - else do
> - realdir <- withCurrentDirectory dir getCurrentDirectory
> - -- This one is absolute!
> - return realdir
> -
> -(///) :: FilePath -> FilePath -> FilePath
> -""///a = do_norm a
> -a///b = do_norm $ a ++ "/" ++ b
> -
> -do_norm :: FilePath -> FilePath
> -do_norm f = fn2fp $ norm_path $ fp2fn f
> rmfile ./src/Darcs/FilePathUtils.hs
> hunk ./src/UglyFileName.hs 1
> --- Copyright (C) 2002-2003,2008 David Roundy
> ---
> --- This program is free software; you can redistribute it and/or modify
> --- it under the terms of the GNU General Public License as published by
> --- the Free Software Foundation; either version 2, or (at your option)
> --- any later version.
> ---
> --- This program is distributed in the hope that it will be useful,
> --- but WITHOUT ANY WARRANTY; without even the implied warranty of
> --- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
> --- GNU General Public License for more details.
> ---
> --- You should have received a copy of the GNU General Public License
> --- along with this program; see the file COPYING. If not, write to
> --- the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
> --- Boston, MA 02110-1301, USA.
> -
> -
> --- THIS MODULE IS DEPRECATED. DON'T USE IT FOR ANYTHING NEW, AND REMOVE
> --- CODE FROM IT WHEN POSSIBLE!
> -
> -module UglyFileName ( fp2fn, fn2fp,
> - norm_path, own_name, super_name,
> - patch_filename,
> - breakup, is_explicitly_relative,
> - ) where
> -
> --- THIS MODULE IS DEPRECATED. DON'T USE IT FOR ANYTHING NEW, AND
> --- REMOVE CODE FROM IT WHEN POSSIBLE! WE'D LIKE TO REMOVE IT SOON...
> -
> -import System.IO
> -import Data.Char ( isAlpha, isSpace, isDigit, toLower )
> -
> -newtype FileName = FN FilePath deriving ( Eq, Ord )
> -
> -instance Show FileName where
> - showsPrec d (FN fp) = showParen (d > app_prec) $ showString "fp2fn " .
> showsPrec (app_prec + 1) fp
> - where app_prec = 10
> -
> -{-# INLINE fp2fn #-}
> -fp2fn :: FilePath -> FileName
> -fp2fn fp = FN fp
> -
> -{-# INLINE fn2fp #-}
> -fn2fp :: FileName -> FilePath
> -fn2fp (FN fp) = fp
> -
> -own_name :: FileName -> FileName
> -own_name (FN f) = case breakLast '/' f of Nothing -> FN f
> - Just (_,f') -> FN f'
> -super_name :: FileName -> FileName
> -super_name fn = case norm_path fn of
> - FN f -> case breakLast '/' f of
> - Nothing -> FN "."
> - Just ("",_) -> FN "/"
> - Just (d ,_) -> FN d
> -
> -norm_path :: FileName -> FileName -- remove "./"
> -norm_path (FN p) = FN $ repath $ drop_dotdot $ breakup p
> -
> -repath :: [String] -> String
> -repath [] = ""
> -repath [f] = f
> -repath (d:p) = d ++ "/" ++ repath p
> -
> -drop_dotdot :: [String] -> [String]
> -drop_dotdot [] = []
> -drop_dotdot f@(a:b)
> - | null a = "" : (drop_dotdot' b) -- first empty element is important
> - -- for absolute paths
> - | otherwise = drop_dotdot' f
> - where drop_dotdot' ("":p) = drop_dotdot' p
> - drop_dotdot' (".":p) = drop_dotdot' p
> - drop_dotdot' ("..":p) = ".." : (drop_dotdot' p)
> - drop_dotdot' (_:"..":p) = drop_dotdot' p
> - drop_dotdot' (d:p) = case drop_dotdot' p of
> - ("..":p') -> p'
> - p' -> d : p'
> - drop_dotdot' [] = []
> -
> -breakup :: String -> [String]
> -breakup p = case break (=='/') p of
> - (d,"") -> [d]
> - (d,p') -> d : breakup (tail p')
> -
> -breakFirst :: Char -> String -> Maybe (String,String)
> -breakFirst c l = bf [] l
> - where bf a (r:rs) | r == c = Just (reverse a,rs)
> - | otherwise = bf (r:a) rs
> - bf _ [] = Nothing
> -breakLast :: Char -> String -> Maybe (String,String)
> -breakLast c l = case breakFirst c (reverse l) of
> - Nothing -> Nothing
> - Just (a,b) -> Just (reverse b, reverse a)
> -
> -safeFileChar :: Char -> Char
> -safeFileChar c | isAlpha c = toLower c
> - | isDigit c = c
> - | isSpace c = '-'
> -safeFileChar _ = '_'
> -
> -patch_filename :: String -> String
> -patch_filename summary = name ++ ".dpatch"
> - where name = map safeFileChar summary
> -
> -
> -is_explicitly_relative :: String -> Bool
> -is_explicitly_relative ('.':'/':_) = True -- begins with "./"
> -is_explicitly_relative _ = False
> rmfile ./src/UglyFileName.hs
The best part :) UglyFileName removed.
Regards,
Dmitry
_______________________________________________
darcs-users mailing list
[email protected]
http://lists.osuosl.org/mailman/listinfo/darcs-users