Hi, the promised review reaction...
Eric Kow <ko...@darcs.net> writes: > Nice work. But you moved too fast (I would have waited until the > adventure branch discussion made progress before actually creating > the branch, but no harm done). Anyway Let's hold off on pushing patches > to this adventure branch until we've made more progress on the > discussion. Consensus building is slow, patient and sometimes > frustrating work, but it's worth it in the end. I hope you are right. :) > That said, just because consensus building is slow doesn't mean we can't > get some work done while we're trying to build consensus. I don't see > any reason folks can't review review patches for efficiency while > the adventure branch thread converges... trying my hand at a little bit > of high-level review (sorry, this really is a token effort): > >> Wed Aug 11 17:39:29 CEST 2010 Petr Rockai <m...@mornfall.net> >> * First stab at a hashed-storage 0.6 port. > > I mostly skipped as it was a big one, and also because I didn't really > know how to review a replace-this-bit-hs-use-with-this-other-bit > patch. Unless you spotted something really hideous, I guess you could take my word on it. (I have hopefully fixed all the actual hideous bits in later patches.) >> Wed Jul 14 19:52:08 CEST 2010 Petr Rockai <m...@mornfall.net> >> * Wibble path building in Repository.Prefs. >> >> Thu Jul 15 10:59:38 CEST 2010 Petr Rockai <m...@mornfall.net> >> * Use more meaningful names for seal_up_patches' parameters. >> >> Sat Jul 17 10:40:48 CEST 2010 Petr Rockai <m...@mornfall.net> >> * Update haddock. I think you could maybe cherry-pick those for mainline, so they would disappear from the radar and shrink future resends of this bundle. >> Wed Aug 11 21:25:55 CEST 2010 Petr Rockai <m...@mornfall.net> >> * Move the preferences system into IO where it belongs. More about this below. >> Wed Aug 11 21:45:04 CEST 2010 Petr Rockai <m...@mornfall.net> >> * Make FileName an alias to Relative (from Hashed.Storage.Path). >> >> Wed Aug 11 22:12:49 CEST 2010 Petr Rockai <m...@mornfall.net> >> * Fix annotate that got broken due to path format change. >> >> Thu Aug 12 00:02:43 CEST 2010 Petr Rockai <m...@mornfall.net> >> * Replace FilePath with FileName in SelectChanges and ChooseTouching. >> >> Thu Aug 12 00:09:46 CEST 2010 Petr Rockai <m...@mornfall.net> >> * Make SubPath just another alias for Relative. > > I only got up to here... and hmm, it took me a couple of hours > of review, so I don't know if I'm doing something wrong or just > being slow. > > Update haddock. > --------------- > Slightly more precise patch names please Next time. :) > First stab at a hashed-storage 0.6 port. > ---------------------------------------- > Seems to replace anchorPath (old stuff) > >> - return $ map (anchorPath "" . fst) $ list recorded >> + return $ map (pathToString . fst) $ list recorded > > I'm going to just have to guess anchorPath "" and pathToString > both from hashed-storage are equivalent Yes, anchorPath "" is same as anchorPath "." which is same as pathToString. >> filesDirs :: Bool -> Bool -> Tree m -> [FilePath] >> filesDirs False False _ = [] >> -filesDirs False True t = "." : [ anchorPath "." p | (p, SubTree _) <- list >> t ] >> +filesDirs False True t = "." : [ pathToString p | (p, SubTree _) <- list t >> ] >> -filesDirs True False t = [ anchorPath "." p | (p, File _) <- list t ] >> +filesDirs True False t = [ pathToString p | (p, File _) <- list t ] >> -filesDirs True True t = "." : (map (anchorPath "." . fst) $ list t) >> +filesDirs True True t = "." : (map (pathToString . fst) $ list t) > > What was the difference between anchorPath "." and anchorPath ""? > Seems to be none according to this block of code. Indeed. See above. >> -import Storage.Hashed( floatPath ) >> +import Storage.Hashed.Path( unsafePathFromString ) > > And I guess I have to assume these do the same thing They don't and that was a bug that I fixed up somewhere later. The more reasonable counterpart to floatPath is parsePath. It is not equivalent either, but parsePath is supposed to handle all kinds of mess (like foo/../bar, foo/./bar etc.). >> conflictor [ >> hunk ./src/Darcs/Diff.hs 56 >> - where diff :: Gap w >> - => AnchoredPath -> Maybe (TreeItem IO) -> Maybe (TreeItem IO) >> - -> IO (w (FL Prim)) >> + where diff :: AnchoredPath -> Maybe (TreeItem m) -> Maybe (TreeItem m) >> + -> m (w (FL Prim)) >> hunk ./src/Darcs/Diff.hs 56 >> - where diff :: AnchoredPath -> Maybe (TreeItem m) -> Maybe (TreeItem m) >> - -> m (w (FL Prim)) >> - diff _ (Just (SubTree _)) (Just (SubTree _)) = return (emptyGap >> NilFL) >> - diff p (Just (SubTree _)) Nothing = >> + where >> + -- sort into removes, changes, adds, with removes in reverse-path >> order >> + -- and everything else in forward order >> + organise :: (AnchoredPath, Diff m) -> (AnchoredPath, Diff m) -> >> Ordering >> + >> + organise (p1, Changed _ _ ) (p2, Changed _ _) = compare p1 p2 >> + organise (p1, Added _) (p2, Added _) = compare p1 p2 >> + organise (p1, Removed _) (p2, Removed _) = compare p2 p1 >> + >> + organise (p1, Removed _) _ = LT >> + organise _ (p1, Removed _) = GT >> + >> + organise (p1, Changed _ _) _ = LT >> + organise _ (p1, Changed _ _) = GT >> + >> + diff :: AnchoredPath -> Diff m -> m (w (FL Prim)) >> + diff _ (Changed (SubTree _) (SubTree _)) = return (emptyGap NilFL) >> + diff p (Removed (SubTree _)) = >> hunk ./src/Darcs/Diff.hs 65 >> - organise (p1, Removed _) _ = LT >> - organise _ (p1, Removed _) = GT >> + organise (_, Removed _) _ = LT >> + organise _ (_, Removed _) = GT >> hunk ./src/Darcs/Diff.hs 68 >> - organise (p1, Changed _ _) _ = LT >> - organise _ (p1, Changed _ _) = GT >> + organise (_, Changed _ _) _ = LT >> + organise _ (_, Changed _ _) = GT >> ] >> : >> hunk ./src/Darcs/Diff.hs 57 >> - => AnchoredPath -> Maybe (TreeItem IO) -> Maybe (TreeItem IO) >> + => Relative -> Maybe (TreeItem IO) -> Maybe (TreeItem IO) > > Hmm, not sure how to react to a conflictor like this. Me neither. The actual change on my end was to just replace AnchoredPath with Relative on the piece of code. In retrospect, darcs replace could have worked better. (We could really use some smarter diff that would notice these kinds of thing... or something.) >> +pathFromFileName :: FileName -> Relative >> +pathFromFileName x = y -- trace ("pathFromFileName: " ++ show x ++ " -> " >> ++ show y) y >> + where y = unsafePathFromString $ fix $ fn2fp x >> + fix p | "./" `isPrefixOf` p = drop 2 p >> + | otherwise = p > > I'm not going to worry about this because it's going away in a future > patch Indeed. > Move the preferences system into IO where it belongs. > ----------------------------------------------------- >> +import System.IO.Unsafe( unsafePerformIO ) > > What was wrong with using ReadableDirectory and WriteableDirectory? It was a rampant API abuse. The problem is that the changepref patch does not apply to things in the repository. The FooDirectory abstraction is broken >> hunk ./src/Darcs/Patch/Apply.lhs 145 >> apply (Move f f') = mRename f f' >> apply (ChangePref p f t) = >> do b <- mDoesDirectoryExist (fp2fn $ darcsdir++"/prefs") >> - when b $ changePrefval p f t >> + when b $ return $! unsafePerformIO (changePrefval p f t) -- fuck >> you. > > No fucking profanity, please. I'm not so much worried about protecting > people's delicate eyes, as about keeping things > simple/minimal/professional. Sorry. I'll fix that. I was a bit frustrated with the whole changepref mess. > Surely you have a more meaningful comment to make. Well, not really. The changepref patch implementation does not make any sense. We really need to gut it and go about it differently. The idea is to just make apply (ChangePref ...) a noop and handle this like we handle setScriptsExecutable nowadays, externally. It's going to slow things down slightly, but it will also further un-mess the patch application code. > Make FileName an alias to Relative (from Hashed.Storage.Path). > -------------------------------------------------------------- >> hunk ./src/Darcs/Patch/FileName.hs 41 >> -newtype FileName = FN FilePath deriving ( Eq, Ord ) >> +type FileName = Relative > > How do we know that FileName and Relative behave the same ways where it > counts? We want to be very very careful here. I realise the whole point > of this work is that we replace our braindead path representation with > something far saner, but we have to be super careful about backwards > compatibility. No surprises. > Also how do we know that Storage.Hashed.Path has sane behaviour in the > first place? It seems like Storage.Hashed.Path is a module that lends > itself fairly well to testing, some examples being: > > - path/unpath roundtrips > - properties on isPrefix is reflexivity, antisymmetry, transitivity > - crazy things with .. > - maybe just ideas taken from the System.FilePath test suite > > Does Storage.Hashed.Path.Absolute behave sanely on Windows (consider > paths starting with \\). Yeah OK all this stuff is a pain in the ass > but we're going to have deal with it someday Not yet -- the path code as it is now is a prototype and there is no win32 trapping. I will add that a bit later, as well as a testsuite. I have also seriously considered splitting the path code away into a separate library. Hopefully it won't be interpreted as me picking on Neil... > So I'm picking on the path stuff for two reasons: first that we count > on it so much, and second that it seems to be fairly self-contained, so > it could be easy as a way to help us learn to test. I think I can work > on this if I have some time, but I hope we can agree on the principle > that it's not safe to merge adventure until we at least how the path > stuff really behaves. That would be great. The Path module in h-s is closed enough that you can pick it out and write tests as you have time. I'll get to that at some point too, so hopefully in the end we are fairly well-covered. >> -encodeWhite :: FilePath -> String >> -encodeWhite (c:cs) | isSpace c || c == '\\' = >> - '\\' : (show $ ord c) ++ "\\" ++ encodeWhite cs >> -encodeWhite (c:cs) = c : encodeWhite cs >> -encodeWhite [] = [] >> +encodeWhite :: B.ByteString -> B.ByteString >> +encodeWhite = BC.concatMap encode >> + where encode c >> + | isSpace c || c == '\\' = B.concat [ "\\", BC.pack $ show $ ord >> c, "\\" ] >> + | otherwise = BC.singleton c > > Looks like the FilePath -> String representation should have been > written this way. This and decodeWhite are the sort of function where > we have haddocks that show examples of what this does for clarity. Said > haddocks should also be tests, IMHO. >> -ownName :: FileName -> FileName >> -ownName (FN f) = case breakLast '/' f of Nothing -> FN f >> - Just (_,f') -> FN f' >> -superName :: FileName -> FileName >> -superName fn = case normPath fn of >> - FN f -> case breakLast '/' f of >> - Nothing -> FN "." >> - Just (d,_) -> FN d >> -breakOnDir :: FileName -> Maybe (FileName,FileName) >> -breakOnDir (FN p) = case breakFirst '/' p of >> - Nothing -> Nothing >> - Just (d,f) | d == "." -> breakOnDir $ FN f >> - | otherwise -> Just (FN d, FN f) > >> -dropDotdot :: [String] -> [String] >> -dropDotdot ("":p) = dropDotdot p >> -dropDotdot (".":p) = dropDotdot p >> -dropDotdot ("..":p) = ".." : (dropDotdot p) >> -dropDotdot (_:"..":p) = dropDotdot p >> -dropDotdot (d:p) = case dropDotdot p of >> - ("..":p') -> p' >> - p' -> d : p' >> -dropDotdot [] = [] > > This is the kind of thing which I expect is easy for us get wrong. How > does the hashed-storage version compare? (</>) :: forall p. (Show p, Path p) => p -> Name -> p (unpath -> p) </> n | n == BS.pack "." = path p | n == BS.pack ".." = parent (path p :: p) (...) (We disallow non-leading .. and all . components as an invariant on the Path types.) >> hunk ./src/Darcs/Patch/FileName.hs 102 >> -movedirfilename :: FileName -> FileName -> FileName -> FileName >> -movedirfilename old new name = >> - if name' == old' then new >> - else if length name' > length old' && >> - take (length old'+1) name' == old'++"/" >> - then fp2fn ("./"++new'++drop (length old') name') >> - else name >> - where old' = fn2fp $ normPath old >> - new' = fn2fp $ normPath new >> - name' = fn2fp $ normPath name > >> +movedirfilename :: FileName -> FileName -> FileName -> FileName >> +movedirfilename old new name >> + | old == name = new >> + | old `isPrefix` name = new +/+ (suffix old name) >> + | otherwise = name > > I can believe the new one is cleaner/safer but it really could stand to > be checked. Well, it took a while to figure. If it comforts you any, a buggy version made the shell tests explode quite colourfully. > Fix annotate that got broken due to path format change. > ------------------------------------------------------- > I didn't really understand what broke here, so I didn't really > look at this much. Obsoleted by new annotate anyway. I just wanted to keep a working midpoint here. > > Replace FilePath with FileName in SelectChanges and ChooseTouching. > ------------------------------------------------------------------- > Making a point of high-level only reviewing this was useful. I imagine > that the idea is that SelectChanges and ChooseTouching are really > repo-local operations. When working on the adventure branch, I might > suggest targeting certain local changes like this for mainline. > > The rest of this was just a cursory look. > >> -isMaliciousPath :: String -> Bool >> -isMaliciousPath fp = >> - splitDirectories fp `contains_any` [ "..", darcsdir ] >> - where >> - contains_any a b = not . null $ intersect a b >> +isMaliciousPath :: FileName -> Bool >> +isMaliciousPath fp = not $ nodarcs fp >> + where nodarcs (directory -> dir :/: rest) = dir /= "_darcs" && nodarcs rest >> + nodarcs _ = True > > Again the sort of thing we should really be careful with. > (I dimly recall seeing another patch that fixes this later) > > Also, why is this "not . nodarcs" when it could be just "hasDarcs"? Redone in a later patch. > >> hunk ./src/Darcs/External.hs 108 >> -backupByCopying :: FilePath -> IO () >> +backupByCopying :: FileName -> IO () > > This also looks like a good idea, but perhaps it's a separate patch. > >> -applyToFilepaths :: Apply p => p C(x y) -> [FilePath] -> [FilePath] >> +applyToFilepaths :: Apply p => p C(x y) -> [FileName] -> [FileName] >> applyToFilepaths pa fs = withFilePaths fs (apply pa) > >> -fix :: FilePath -> FilePath >> -fix f | "/" `isSuffixOf` f = fix $ init f >> -fix "" = "." >> -fix "." = "." >> -fix f = "./" ++ f > > Hooray? This seems to be just tidying up trailing dots and slashes > and I'm glad to see it go Again, invariants on the new Path types prevent such things from existing. > Make SubPath just another alias for Relative. > --------------------------------------------- > Yes, I like the idea that FileName and SubPath get consolidated. > > I don't mean to bang on the testing drum again, but the fact that > we're sweeping it all into one central pile means it should be > even easier to have some tests. Yours, Petr. _______________________________________________ darcs-users mailing list darcs-users@darcs.net http://lists.osuosl.org/mailman/listinfo/darcs-users