Created on 2010-06-18.18:55:13 by kowey, last changed 2011-05-10.22:05:37 by darcswatch. Tracked on DarcsWatch.
See mailing list archives
for discussion on individual patches.
msg11479 (view) |
Author: kowey |
Date: 2010-06-18.18:55:13 |
|
As requested by Reinier. Notes:
* I guess issue1227 probably should not have been marked as ProbablyEasy
since I had to muck around in Darcs.Repository. It wasn't so hard for
me since I've been here a while, but if you don't know the code :-/
(I was expecting something easier, hence the 'probably')
* The second patch fixes the immediate problem.
* I'm a bit doubtful about my third patch. It seems better than matching
on our error strings, but not sure if this sort of organic growth in the
types is the way to go. Is there a more principled approach?
Could I get a reviewer?
3 patches for repository http://darcs.net:
Fri Jun 18 19:54:14 BST 2010 Eric Kow <kowey@darcs.net>
* Accept issue1227: darcs repository format errors not reported in add.
Fri Jun 18 19:54:23 BST 2010 Eric Kow <kowey@darcs.net>
* Resolve issue1227: percolate repository format errors correctly.
The problem is that we do not distinguish between bad repos and
non-repositories so we keep seeking upwards.
Fri Jun 18 19:54:28 BST 2010 Eric Kow <kowey@darcs.net>
* Generalise mechanism for distinguishing between bad and non repos.
Attachments
|
msg11480 (view) |
Author: kowey |
Date: 2010-06-18.19:05:09 |
|
Manualy rebased because I got my issue1227 and issue1277 confused.
3 patches for repository http://darcs.net:
Fri Jun 18 20:01:06 BST 2010 Eric Kow <kowey@darcs.net>
* Accept issue1227: darcs repository format errors not reported in add.
Fri Jun 18 19:54:23 BST 2010 Eric Kow <kowey@darcs.net>
* Resolve issue1277: percolate repository format errors correctly.
The problem is that we do not distinguish between bad repos and
non-repositories so we keep seeking upwards.
Fri Jun 18 19:54:28 BST 2010 Eric Kow <kowey@darcs.net>
* Generalise mechanism for distinguishing between bad and non repos.
Attachments
|
msg11482 (view) |
Author: kowey |
Date: 2010-06-18.19:06:42 |
|
Shoot, I did it wrong *again*
|
msg11483 (view) |
Author: kowey |
Date: 2010-06-18.19:11:04 |
|
Sorry for the noise!
3 patches for repository http://darcs.net:
Fri Jun 18 20:01:06 BST 2010 Eric Kow <kowey@darcs.net>
* Accept issue1277: darcs repository format errors not reported in add.
Fri Jun 18 19:54:23 BST 2010 Eric Kow <kowey@darcs.net>
* Resolve issue1277: percolate repository format errors correctly.
The problem is that we do not distinguish between bad repos and
non-repositories so we keep seeking upwards.
Fri Jun 18 19:54:28 BST 2010 Eric Kow <kowey@darcs.net>
* Generalise mechanism for distinguishing between bad and non repos.
Attachments
|
msg11500 (view) |
Author: tux_rocker |
Date: 2010-06-20.18:25:27 |
|
Hi Eric,
Before pushing this, I'd like to know:
* if the change of protocol of seekRepo is harmless
* if we should also change amInRepository
> New patches:
>
> [Accept issue1277: darcs repository format errors not reported in add.
> Eric Kow <kowey@darcs.net>**20100618190106
>
> Ignore-this: d0961642c7526643b98a5ed066434288
>
> ] addfile ./tests/failing-issue1277-repo-format.sh
> hunk ./tests/failing-issue1277-repo-format.sh 1
> +. lib # Load some portability helpers.
> +rm -rf R # Another script may have left a mess.
> +darcs init --repo R # Create our test repos.
> +cd R
> + darcs init --repo R2 # Protect the darcs darcs repo with R
> + cd R2
> + echo impossible >> _darcs/format
> + echo 'Example content.' > f
> + not darcs add f > log
> + grep "Can't understand repository format" log
> + cd ..
> +cd ..
Here, we check that if the _darcs/format file of R2 is corrupted, we don't
accidentally fall back to the repository in its enclosing directory R.
> [Resolve issue1277: percolate repository format errors correctly.
> Eric Kow <kowey@darcs.net>**20100618185423
>
> Ignore-this: b541efa39c3b55b67479b209f55ffd1d
> The problem is that we do not distinguish between bad repos and
> non-repositories so we keep seeking upwards.
>
> ] move ./tests/failing-issue1277-repo-format.sh ./tests/issue1277-repo-format.sh
> hunk ./src/Darcs/Repository/Internal.hs 137
>
> import Darcs.Witnesses.Sealed ( Sealed(Sealed), seal,
> FlippedSeal(FlippedSeal), flipSeal ) import
> Darcs.Repository.InternalTypes( Repository(..), RepoType(..) ) import
> Darcs.Global ( darcsdir )
>
> +
> +import Data.List ( isPrefixOf )
In this patch we're going to distinguish nonexistent from unreadable repos
by checking the start of the error message. Hence import "isPrefixOf".
> hunk ./src/Darcs/Repository/Internal.hs 259
>
> -> IO (Either String ())
>
> seekRepo onFail = getCurrentDirectory >>= helper where
>
> helper startpwd = do
>
> - air <- currentDirIsRepository
> - if air
> - then return (Right ())
> - else do cd <- toFilePath `fmap` getCurrentDirectory
> + status <- maybeIdentifyRepository [] "."
> + case status of
> + Right _ -> return (Right ())
> + Left e | "Can't understand repository format" `isPrefixOf` e -> return (Left e)
> + Left _ ->
> + do cd <- toFilePath `fmap` getCurrentDirectory
>
> setCurrentDirectory ".."
> cd' <- toFilePath `fmap` getCurrentDirectory
> if cd' /= cd
>
So here we distinguish a new case, the one where our error is one about the
repository format. This is the fix for the issue.
But doesn't calling code expect to get either Right () or the given onFail
from this function? At least that was the behavior of the old function. In
findRepository, I see a call "seekRepo (Right ())". Doesn't that expect
never to get a Left? But it looks like findRepository is usually used as a
commandPrereq, in which case a Left will be handled.
The patch below removes he match on the error string and introduces a more
principled approach ung a type with three constructors (instead of
piggybacking on the two-constructor Either type).
> [Generalise mechanism for distinguishing between bad and non repos.
> Eric Kow <kowey@darcs.net>**20100618185428
>
> Ignore-this: f637d68510645249ce221ad91df076ae
>
> ] hunk ./src/Darcs/Repository.hs 56
> - maybeIdentifyRepository, identifyRepositoryFor,
> + maybeIdentifyRepository, identifyRepositoryFor, IdentifyRepo(..),
So here we have that three-constructor IdentifyRepo type.
> hunk ./src/Darcs/Repository.hs 259
>
> maybeRepo <- maybeIdentifyRepository opts "."
> let repo@(Repo _ _ rf2 (DarcsRepository _ c)) =
>
> case maybeRepo of
>
> - Right r -> r
> - Left e -> bug ("Current directory not repository in writePatchSet: " ++ e)
> + GoodRepository r -> r
> + BadRepository e -> bug ("Current directory is a 'bad' repository in writePatchSet: " ++ e)
> + NonRepository e -> bug ("Current directory not a repository in writePatchSet: " ++ e)
> debugMessage "Writing inventory"
> if formatHas HashedInventory rf2
>
> then do HashedRepo.writeTentativeInventory c (compression opts)
> patchset
So this is in the writePatchSet function, which writes a PatchSet to a
repository, discarding what's already in the repo. Could I ask you to remove
the quotes around "bad"? ;-)
> hunk ./src/Darcs/Repository.hs 354
>
> withCurrentDirectory dir $ readWorking >>= replacePristine repo
>
> pristineFromWorking (Repo dir _ _ (DarcsRepository p _)) =
>
> withCurrentDirectory dir $ createPristineFromWorking p
>
> +
Spurious newline added? Looking at it with hexedit, the file does not
currently have a newline at the end. I'm willing to let this pass.
> hunk ./src/Darcs/Repository/Internal.hs 26
>
> module Darcs.Repository.Internal ( Repository(..), RepoType(..),
> RIO(unsafeUnRIO), ($-),
>
> maybeIdentifyRepository, identifyDarcs1Repository,
> identifyRepositoryFor,
>
> + IdentifyRepo(..),
>
> findRepository, amInRepository, amNotInRepository,
> revertRepositoryChanges,
> announceMergeConflicts, setTentativePending,
>
Add the 3-constructor IdentifyRepo to the export list of
Darcs.Repository.Internal
> hunk ./src/Darcs/Repository/Internal.hs 139
>
> import Darcs.Repository.InternalTypes( Repository(..), RepoType(..) )
> import Darcs.Global ( darcsdir )
>
> -import Data.List ( isPrefixOf )
>
> import System.Mem( performGC )
>
> import qualified Storage.Hashed.Tree as Tree
>
We don't use isPrefixOf anymore now that the error message matching is gone.
> hunk ./src/Darcs/Repository/Internal.hs 193
>
> getRepository :: RIO p C(r u t t) (Repository p C(r u t))
> getRepository = RIO return
>
> -maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (Either String (Repository p C(r u t)))
> +-- | The status of a given directory: is it a darcs repository?
> +data IdentifyRepo p C(r u t) = BadRepository String -- ^ looks like a repository with some error
> + | NonRepository String -- ^ safest guess
> + | GoodRepository (Repository p C(r u t))
> +
> +maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (IdentifyRepo p C(r u t))
> maybeIdentifyRepository opts "." =
>
> do darcs <- doesDirectoryExist darcsdir
>
> rf_or_e <- identifyRepoFormat "."
>
This adds the 3-constructor IdentifyRepo type and changes
maybeIdentifyRepository to use it.
> hunk ./src/Darcs/Repository/Internal.hs 204
>
> here <- toPath `fmap` ioAbsoluteOrRemote "."
> case rf_or_e of
>
> - Left err -> return $ Left err
> + Left err -> return $ NonRepository err
>
> Right rf ->
>
> case readProblem rf of
>
Now we're inside the maybeIdentifyRepository function, in a pattern match
alternative that special-cases it for trying to identify the current
directory ("."). This hunk handles the case that identifyRepoFormat returns
Left, in which case there is no _darcs/format or _darcs/inventory file in
the directory. It's safe to guess it's not a repo then.
> hunk ./src/Darcs/Repository/Internal.hs 207
> - Just err -> return $ Left err
> + Just err -> return $ BadRepository err
>
> Nothing -> if darcs then do pris <- identifyPristine
>
> cs <- getCaches opts here
>
This handles the case that readProblem returns an error. readProblem
examines the repository format, so at least we got a format when we get
here. So we return BadRepository, not NonRepository.
> hunk ./src/Darcs/Repository/Internal.hs 210
> - return $ Right $ Repo here opts rf (DarcsRepository pris cs)
> - else return (Left "Not a repository")
> + return $ GoodRepository $ Repo here opts rf (DarcsRepository pris cs)
> + else return (NonRepository "Not a repository")
And finally we handle the case that the _darcs directory does not exist: in
that case it's not a repo. But what sense does it make to check if _darcs
exist if we already found an inventory or a format file, which is what
identifyRepoFormat seems to check for?
> hunk ./src/Darcs/Repository/Internal.hs 216
>
> case rf_or_e of
>
> - Left e -> return $ Left e
> + Left e -> return $ NonRepository e
>
> Right rf -> case readProblem rf of
>
> hunk ./src/Darcs/Repository/Internal.hs 218
> - Just err -> return $ Left err
> + Just err -> return $ BadRepository err
> Nothing -> do cs <- getCaches opts url
>
> hunk ./src/Darcs/Repository/Internal.hs 220
> - return $ Right $ Repo url opts rf (DarcsRepository nopristine cs)
> + return $ GoodRepository $ Repo url opts rf (DarcsRepository nopristine cs)
>
> identifyDarcs1Repository :: [DarcsFlag] -> String -> IO (Repository Patch C(r u t)) identifyDarcs1Repository opts url =
>
Here we do the same thing for the other pattern match alternative, which
does identification of repositories at all URLs that are not ".".
Interestingly, the check if _darcs exist is not present here.
> hunk ./src/Darcs/Repository/Internal.hs 226
>
> do er <- maybeIdentifyRepository opts url
>
> case er of
>
> - Left s -> fail s
> - Right r -> return r
> + BadRepository s -> fail s
> + NonRepository s -> fail s
> + GoodRepository r -> return r
>
> identifyRepositoryFor :: forall p C(r u t). RepoPatch p => Repository p
> C(r u t) -> String -> IO (Repository p C(r u t)) identifyRepositoryFor
> (Repo _ opts rf _) url =
>
Change some code to use the new interface of maybeIdentifyRepository.
> hunk ./src/Darcs/Repository/Internal.hs 238
>
> Just e -> fail $ "Incompatibility with repository " ++ url ++
> ":\n" ++ e Nothing -> return $ Repo absurl opts rf_ t'
>
> -isRight :: Either a b -> Bool
> -isRight (Right _) = True
> -isRight _ = False
> -
>
> currentDirIsRepository :: IO Bool
>
Remove an isRight function that is apparently no longer used.
> hunk ./src/Darcs/Repository/Internal.hs 239
> -currentDirIsRepository = isRight `liftM` maybeIdentifyRepository [] "."
> +currentDirIsRepository = isGoodRepository `fmap` maybeIdentifyRepository
> [] "." + where
> + isGoodRepository (GoodRepository _) = True
> + isGoodRepository _ = False
>
> amInRepository :: [DarcsFlag] -> IO (Either String ())
> amInRepository (WorkRepoDir d:_) =
>
Switch currentDirIsRepository to the new interface for
maybeIdentifyRepository.
> hunk ./src/Darcs/Repository/Internal.hs 266
>
> helper startpwd = do
>
> status <- maybeIdentifyRepository [] "."
> case status of
>
> - Right _ -> return (Right ())
> - Left e | "Can't understand repository format" `isPrefixOf` e ->
> return (Left e) - Left _ ->
> + GoodRepository _ -> return (Right ())
> + BadRepository e -> return (Left e)
> + NonRepository _ ->
>
> do cd <- toFilePath `fmap` getCurrentDirectory
>
> setCurrentDirectory ".."
> cd' <- toFilePath `fmap` getCurrentDirectory
And finally, change seekRepo to use this new interface.
Shouldn't we also change the amInRepository function above seekRepo? It will
still say "You need to be a repository directory to run this command." even
when it should already know that it *is* in a repo but just doesn't
understand the format. At least if it gets an argument of the "WorkRepoDir"
constructor. But I don't even know what that is, so I'll shut up.
--
Reinier
|
msg11501 (view) |
Author: tux_rocker |
Date: 2010-06-20.18:35:00 |
|
Oh, and I now that I finally run the test: you have to change the line
not darcs add f > log
to
not darcs add f > log 2>&1
otherwise the test will fail even with your patch.
|
msg11502 (view) |
Author: kowey |
Date: 2010-06-20.20:03:24 |
|
Hi,
Thanks for the review and for catching oversights! I'll be sending
my amendments, hopefully after tonight's meeting with Adolfo
On Sun, Jun 20, 2010 at 18:25:27 +0000, Reinier Lamers wrote:
> > hunk ./tests/failing-issue1277-repo-format.sh 1
> > +. lib # Load some portability helpers.
> > +rm -rf R # Another script may have left a mess.
> > +darcs init --repo R # Create our test repos.
> > +cd R
> > + darcs init --repo R2 # Protect the darcs darcs repo with R
> > + cd R2
> > + echo impossible >> _darcs/format
> > + echo 'Example content.' > f
> > + not darcs add f > log
> > + grep "Can't understand repository format" log
> > + cd ..
> > +cd ..
Acknowledged on the redirection in your previous mail. I wonder why I
missed it this, though when running the test The
> > - air <- currentDirIsRepository
> > - if air
> > - then return (Right ())
> > - else do cd <- toFilePath `fmap` getCurrentDirectory
> > + status <- maybeIdentifyRepository [] "."
> > + case status of
> > + Right _ -> return (Right ())
> > + Left e | "Can't understand repository format" `isPrefixOf` e -> return (Left e)
> > + Left _ ->
> > + do cd <- toFilePath `fmap` getCurrentDirectory
> >
> > setCurrentDirectory ".."
> > cd' <- toFilePath `fmap` getCurrentDirectory
> > if cd' /= cd
> >
>
> So here we distinguish a new case, the one where our error is one about the
> repository format. This is the fix for the issue.
> But doesn't calling code expect to get either Right () or the given onFail
> from this function? At least that was the behavior of the old function. In
> findRepository, I see a call "seekRepo (Right ())". Doesn't that expect
> never to get a Left? But it looks like findRepository is usually used as a
> commandPrereq, in which case a Left will be handled.
Yow, this was indeed an oversight. Unfortunately, I went chasing after
the code before I read your paragraph correctly only to come to the same
conclusions.
I guess the only reason why we have both amInRepository and
findRepository is that the latter handles the --repo flag (which unlike
its cousin --repodir, handles remote repositories). I think we should
think about making findRepository make some sort of remark, something
similar to amInRepository but not identical (because you don't need to
be *in* a repository to run darcs changes --repo foo). Also perhaps the
amInRepository error for the --repodir flag should say something like
"'d' needs to be in a repository"
> So this is in the writePatchSet function, which writes a PatchSet to a
> repository, discarding what's already in the repo. Could I ask you to remove
> the quotes around "bad"? ;-)
Yep! On my way.
> Spurious newline added? Looking at it with hexedit, the file does not
> currently have a newline at the end. I'm willing to let this pass.
Sorry about that. I'll see if I remember to fix this too (this be
addressed in a separate whitespace patch, to keep patches as easy to
review as possible)
> Now we're inside the maybeIdentifyRepository function, in a pattern match
> alternative that special-cases it for trying to identify the current
> directory ("."). This hunk handles the case that identifyRepoFormat returns
> Left, in which case there is no _darcs/format or _darcs/inventory file in
> the directory. It's safe to guess it's not a repo then.
Note that I think of the "not a repo" guess as being the conservative
one in the sense that this will make Darcs keep trying (by seeking
upwards), but I think that's just perspective.
>
> > hunk ./src/Darcs/Repository/Internal.hs 210
> > - return $ Right $ Repo here opts rf (DarcsRepository pris cs)
> > - else return (Left "Not a repository")
> > + return $ GoodRepository $ Repo here opts rf (DarcsRepository pris cs)
> > + else return (NonRepository "Not a repository")
>
> And finally we handle the case that the _darcs directory does not exist: in
> that case it's not a repo. But what sense does it make to check if _darcs
> exist if we already found an inventory or a format file, which is what
> identifyRepoFormat seems to check for?
Nice not taking preexisting code for granted. One reason I'm a fan of
(conspicuous) review is that it forces is to revisit and sometimes
question the surrounding code.
I think the reason we do this is because old fashioned darcs-1 repos
will have no 'format' file (I suspect the mechanism was only introduced
after darcs release, but not sure).
> Shouldn't we also change the amInRepository function above seekRepo? It will
> still say "You need to be a repository directory to run this command." even
> when it should already know that it *is* in a repo but just doesn't
> understand the format. At least if it gets an argument of the "WorkRepoDir"
> constructor. But I don't even know what that is, so I'll shut up.
That sounds like a good idea. I bet we could extend the test case to
show that darcs whatsnew --repodir X does the wrong thing when it does
not understand the format in X
--
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
PGP Key ID: 08AC04F9
|
msg11518 (view) |
Author: kowey |
Date: 2010-06-21.18:23:24 |
|
Hi Reinier,
Some modified patches if you wouldn't mind reviewing them.
Also: one thing I should make clear (in case my patch is misleading) is that
the patch is intended as future-proofing for further formats, not so much to
deal with corrupt format files. Hope the code isn't framing things the wrong
way with 'BadRepository'
> Fri Jun 18 20:01:06 BST 2010 Eric Kow <kowey@darcs.net>
> * Accept issue1277: darcs repository format errors not reported in add.
log file redirect fix (how did I miss this, I thought I ran it?!)
> Fri Jun 18 19:54:23 BST 2010 Eric Kow <kowey@darcs.net>
> * Resolve issue1277: percolate repository format errors correctly.
> The problem is that we do not distinguish between bad repos and
> non-repositories so we keep seeking upwards.
(I think this is the same, although not technically the same patch
due to manual rebase, so be careful to unpull the old patch!)
> Mon Jun 21 19:18:53 BST 2010 Eric Kow <kowey@darcs.net>
> * Generalise mechanism for distinguishing between bad and non repos.
> We remove the potentially misleading currentDirectoryIsRepository
> along the way.
Minor issues fixed.
Also, good catch on the amInRepository. Fixing this made me realise that I
also needed to have a better story for amNotInRepository, which then made me
realise that currentDirectoryIsRepository is inherently problematic, so I
nuked it.
> Mon Jun 21 19:20:16 BST 2010 Eric Kow <kowey@darcs.net>
> * Extend issue1277 test for more prerequisites.
New.
Attachments
|
msg11519 (view) |
Author: kowey |
Date: 2010-06-21.18:26:31 |
|
Mon Jun 21 19:28:34 BST 2010 Eric Kow <kowey@darcs.net>
* Generalise mechanism for distinguishing between bad and non repos.
We remove the potentially misleading currentDirIsRepository along
the way.
Oops, resent with amended long patch name.
Attachments
|
msg11600 (view) |
Author: tux_rocker |
Date: 2010-06-27.13:46:32 |
|
Applied, thanks!
I was already halfway reviewing this patch, and then I tried to suspend my
laptop for the first time on Ubuntu Lucid and things froze and it was lost.
Hence the delay.
> New patches:
>
> [Accept issue1277: darcs repository format errors not reported in add.
> Eric Kow <kowey@darcs.net>**20100618190106
>
> Ignore-this: d0961642c7526643b98a5ed066434288
>
> ] addfile ./tests/failing-issue1277-repo-format.sh
> hunk ./tests/failing-issue1277-repo-format.sh 1
> +#!/usr/bin/env bash
> +## Test for issue1277 - repository format errors should be reported
> +## correctly (ie. not as some totally unrelated error)
> +##
> +## Copyright (C) 2010 Eric Kow
> +##
> +## Permission is hereby granted, free of charge, to any person
> +## obtaining a copy of this software and associated documentation
> +## files (the "Software"), to deal in the Software without
> +## restriction, including without limitation the rights to use, copy,
> +## modify, merge, publish, distribute, sublicense, and/or sell copies
> +## of the Software, and to permit persons to whom the Software is
> +## furnished to do so, subject to the following conditions:
> +##
> +## The above copyright notice and this permission notice shall be
> +## included in all copies or substantial portions of the Software.
> +##
> +## THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
> +## EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
> +## MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
> +## NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS
> +## BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN
> +## ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN
> +## CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
> +## SOFTWARE.
> +
> +. lib # Load some portability helpers.
> +rm -rf R # Another script may have left a mess.
> +darcs init --repo R # Create our test repos.
> +cd R
> + darcs init --repo R2 # Protect the darcs darcs repo with R
> + cd R2
> + echo impossible >> _darcs/format
> + echo 'Example content.' > f
> + not darcs add f > log 2>&1
> + grep "Can't understand repository format" log
> + cd ..
> +cd ..
This just adds the redirection, okay.
> [Resolve issue1277: percolate repository format errors correctly.
> Eric Kow <kowey@darcs.net>**20100618185423
>
> Ignore-this: b541efa39c3b55b67479b209f55ffd1d
> The problem is that we do not distinguish between bad repos and
> non-repositories so we keep seeking upwards.
>
> ] move ./tests/failing-issue1277-repo-format.sh
> ./tests/issue1277-repo-format.sh hunk ./src/Darcs/Repository/Internal.hs
> 137
>
> import Darcs.Witnesses.Sealed ( Sealed(Sealed), seal,
> FlippedSeal(FlippedSeal), flipSeal ) import
> Darcs.Repository.InternalTypes( Repository(..), RepoType(..) ) import
> Darcs.Global ( darcsdir )
>
> +
> +import Data.List ( isPrefixOf )
>
> import System.Mem( performGC )
>
> import qualified Storage.Hashed.Tree as Tree
>
> hunk ./src/Darcs/Repository/Internal.hs 259
>
> -> IO (Either String ())
>
> seekRepo onFail = getCurrentDirectory >>= helper where
>
> helper startpwd = do
>
> - air <- currentDirIsRepository
> - if air
> - then return (Right ())
> - else do cd <- toFilePath `fmap` getCurrentDirectory
> + status <- maybeIdentifyRepository [] "."
> + case status of
> + Right _ -> return (Right ())
> + Left e | "Can't understand repository format" `isPrefixOf` e ->
> return (Left e) + Left _ ->
> + do cd <- toFilePath `fmap` getCurrentDirectory
>
> setCurrentDirectory ".."
> cd' <- toFilePath `fmap` getCurrentDirectory
> if cd' /= cd
This hasn't changed since last review, OK.
> [Extend issue1277 test for more prerequisites.
> Eric Kow <kowey@darcs.net>**20100621182016
>
> Ignore-this: 49548f2470cd22133cecca1c5458b1d9
>
> ] hunk ./tests/issue1277-repo-format.sh 37
>
> echo 'Example content.' > f
> not darcs add f > log 2>&1
> grep "Can't understand repository format" log
>
> + not darcs whatsnew > log 2>&1
> + grep "Can't understand repository format" log
> + not darcs init > log 2>&1
> + grep "You may not run this command in a repository" log
This is the last line printed before it fails, without applying the next
test. Apparently the 'whatsnew' case already works without the following
patch.
> [Generalise mechanism for distinguishing between bad and non repos.
> Eric Kow <kowey@darcs.net>**20100621182834
>
> Ignore-this: 85bb5cfee6f8955eedea4cd438603e2d
> We remove the potentially misleading currentDirIsRepository along
> the way.
>
> ] hunk ./src/Darcs/Repository.hs 56
>
> import Darcs.Repository.Internal
>
> (Repository(..), RepoType(..), ($-),
>
> - maybeIdentifyRepository, identifyRepositoryFor,
> + maybeIdentifyRepository, identifyRepositoryFor, IdentifyRepo(..),
>
> findRepository, amInRepository, amNotInRepository,
> makePatchLazy,
> withRecorded,
>
> hunk ./src/Darcs/Repository.hs 259
>
> maybeRepo <- maybeIdentifyRepository opts "."
> let repo@(Repo _ _ rf2 (DarcsRepository _ c)) =
>
> case maybeRepo of
>
> - Right r -> r
> - Left e -> bug ("Current directory not repository in writePatchSet: " ++ e)
> + GoodRepository r -> r
> + BadRepository e -> bug ("Current directory is a bad repository in writePatchSet: " ++ e)
> + NonRepository e -> bug ("Current directory not a repository in writePatchSet: " ++ e)
>
> debugMessage "Writing inventory"
> if formatHas HashedInventory rf2
>
> then do HashedRepo.writeTentativeInventory c (compression opts)
> patchset
>
Thanks for removing the quotes =)
> hunk ./src/Darcs/Repository/Internal.hs 26
>
> module Darcs.Repository.Internal ( Repository(..), RepoType(..),
> RIO(unsafeUnRIO), ($-),
>
> maybeIdentifyRepository, identifyDarcs1Repository,
> identifyRepositoryFor,
>
> + IdentifyRepo(..),
>
> findRepository, amInRepository, amNotInRepository,
> revertRepositoryChanges,
> announceMergeConflicts, setTentativePending,
>
> hunk ./src/Darcs/Repository/Internal.hs 139
>
> import Darcs.Repository.InternalTypes( Repository(..), RepoType(..) )
> import Darcs.Global ( darcsdir )
>
> -import Data.List ( isPrefixOf )
>
> import System.Mem( performGC )
>
> import qualified Storage.Hashed.Tree as Tree
>
> hunk ./src/Darcs/Repository/Internal.hs 193
>
> getRepository :: RIO p C(r u t t) (Repository p C(r u t))
> getRepository = RIO return
>
> -maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (Either String (Repository p C(r u t)))
> +-- | The status of a given directory: is it a darcs repository?
> +data IdentifyRepo p C(r u t) = BadRepository String -- ^ looks like a repository with some error
> + | NonRepository String -- ^ safest guess
> + | GoodRepository (Repository p C(r u t))
> +
> +maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (IdentifyRepo p C(r u t))
>
> maybeIdentifyRepository opts "." =
>
> do darcs <- doesDirectoryExist darcsdir
>
> rf_or_e <- identifyRepoFormat "."
>
> hunk ./src/Darcs/Repository/Internal.hs 204
>
> here <- toPath `fmap` ioAbsoluteOrRemote "."
> case rf_or_e of
>
> - Left err -> return $ Left err
> + Left err -> return $ NonRepository err
>
> Right rf ->
>
> case readProblem rf of
>
> hunk ./src/Darcs/Repository/Internal.hs 207
> - Just err -> return $ Left err
> + Just err -> return $ BadRepository err
>
> Nothing -> if darcs then do pris <- identifyPristine
>
> cs <- getCaches opts here
>
> hunk ./src/Darcs/Repository/Internal.hs 210
> - return $ Right $ Repo here opts rf (DarcsRepository pris cs)
> - else return (Left "Not a repository")
> + return $ GoodRepository $ Repo here opts rf (DarcsRepository pris cs)
> + else return (NonRepository "Not a repository")
>
> maybeIdentifyRepository opts url' =
>
> do url <- toPath `fmap` ioAbsoluteOrRemote url'
>
> rf_or_e <- identifyRepoFormat url
>
> hunk ./src/Darcs/Repository/Internal.hs 216
>
> case rf_or_e of
>
> - Left e -> return $ Left e
> + Left e -> return $ NonRepository e
>
> Right rf -> case readProblem rf of
>
> hunk ./src/Darcs/Repository/Internal.hs 218
> - Just err -> return $ Left err
> + Just err -> return $ BadRepository err
>
> Nothing -> do cs <- getCaches opts url
>
> hunk ./src/Darcs/Repository/Internal.hs 220
> - return $ Right $ Repo url opts rf (DarcsRepository nopristine cs)
> + return $ GoodRepository $ Repo url opts rf (DarcsRepository nopristine cs)
>
> identifyDarcs1Repository :: [DarcsFlag] -> String -> IO (Repository Patch
> C(r u t)) identifyDarcs1Repository opts url =
>
This is all old news from the previous review. The check of the "_darcs"
directory remains for "." and stays absent for the general case. But we're
not here to fix that now, if necessary.
> hunk ./src/Darcs/Repository/Internal.hs 226
>
> do er <- maybeIdentifyRepository opts url
>
> case er of
>
> - Left s -> fail s
> - Right r -> return r
> + BadRepository s -> fail s
> + NonRepository s -> fail s
> + GoodRepository r -> return r
>
> identifyRepositoryFor :: forall p C(r u t). RepoPatch p => Repository p
> C(r u t) -> String -> IO (Repository p C(r u t)) identifyRepositoryFor
> (Repo _ opts rf _) url =
>
> hunk ./src/Darcs/Repository/Internal.hs 238
>
> Just e -> fail $ "Incompatibility with repository " ++ url ++
> ":\n" ++ e Nothing -> return $ Repo absurl opts rf_ t'
>
> -isRight :: Either a b -> Bool
> -isRight (Right _) = True
> -isRight _ = False
> -
> -currentDirIsRepository :: IO Bool
> -currentDirIsRepository = isRight `liftM` maybeIdentifyRepository [] "."
> -
>
> amInRepository :: [DarcsFlag] -> IO (Either String ())
> amInRepository (WorkRepoDir d:_) =
>
> do setCurrentDirectory d `catchall` (fail $ "can't set directory to
> "++d)
>
Old news up to the point where we delete "currentDirIsRepository". I suppose
it has to go because it returns a Boolean, while we want some tri-state
(good repo, bad repo, non repo) return type now.
> hunk ./src/Darcs/Repository/Internal.hs 241
> - air <- currentDirIsRepository
> - if air
> - then return (Right ())
> - else return (Left "You need to be in a repository directory to run this command.")
> + status <- maybeIdentifyRepository [] "."
> + case status of
> + GoodRepository _ -> return (Right ())
> + BadRepository e -> return (Left $ "While " ++ d ++ " looks like a repository directory, we have a problem with it:\n" ++ e)
> + NonRepository _ -> return (Left "You need to be in a repository directory to run this command.")
>
> amInRepository (_:fs) = amInRepository fs
> amInRepository [] =
>
> seekRepo (Left "You need to be in a repository directory to run this
> command.")
>
This is the new amInRepository that checks whether we're in a usable
repository, and supplies an error message if not.
"But" might be a better conjunction to use than "while". Like 'd ++ "looks
like a repository directory, but we have a problem with it:\n" ++ e'. But
note that I misspelt "than" as "then" initially, so don't trust me too hard
:).
> hunk ./src/Darcs/Repository/Internal.hs 261
>
> helper startpwd = do
>
> status <- maybeIdentifyRepository [] "."
> case status of
>
> - Right _ -> return (Right ())
> - Left e | "Can't understand repository format" `isPrefixOf` e -> return (Left e)
> - Left _ ->
> + GoodRepository _ -> return (Right ())
> + BadRepository e -> return (Left e)
> + NonRepository _ ->
>
> do cd <- toFilePath `fmap` getCurrentDirectory
>
> setCurrentDirectory ".."
> cd' <- toFilePath `fmap` getCurrentDirectory
>
This changes seekRepo, this is old news, okay.
> hunk ./src/Darcs/Repository/Internal.hs 283
>
> amNotInRepository []
>
> amNotInRepository (_:f) = amNotInRepository f
> amNotInRepository [] =
>
> - do air <- currentDirIsRepository
> - if air then return (Left $ "You may not run this command in a repository.")
> - else return $ Right ()
> + do status <- maybeIdentifyRepository [] "."
> + case status of
> + GoodRepository _ -> return (Left $ "You may not run this command in a repository.")
> + BadRepository e -> return (Left $ "You may not run this command in a repository.\nBy the way, we have a problem with it:\n" ++ e)
> + NonRepository _ -> return (Right ())
>
> findRepository :: [DarcsFlag] -> IO (Either String ())
> findRepository (WorkRepoUrl d:_) | isFile d =
>
And here we adapt amNotInRepository to the removal of currentDirIsRepository. amNotInRepository is what's used in init. So this makes the test
succeed again.
Regards,
Reinier
|
msg11602 (view) |
Author: darcswatch |
Date: 2010-06-27.14:02:15 |
|
This patch bundle (with 4 patches) was just applied to the repository http://darcs.net/.
This message was brought to you by DarcsWatch
http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-fbf98e0d16e6f53ce205d54f635609bad8a839c5
|
msg14218 (view) |
Author: darcswatch |
Date: 2011-05-10.19:37:50 |
|
This patch bundle (with 4 patches) was just applied to the repository http://darcs.net/reviewed.
This message was brought to you by DarcsWatch
http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-fbf98e0d16e6f53ce205d54f635609bad8a839c5
|
|
Date |
User |
Action |
Args |
2010-06-18 18:55:13 | kowey | create | |
2010-06-18 19:05:10 | kowey | set | files:
+ accept-issue1227_-darcs-repository-format-errors-not-reported-in-add_-.dpatch, unnamed messages:
+ msg11480 |
2010-06-18 19:06:42 | kowey | set | messages:
+ msg11482 issues:
+ darcs add, remove, etc should report repository format errors as such |
2010-06-18 19:09:51 | kowey | set | files:
- accept-issue1227_-darcs-repository-format-errors-not-reported-in-add_-.dpatch |
2010-06-18 19:09:53 | kowey | set | files:
- accept-issue1227_-darcs-repository-format-errors-not-reported-in-add_-.dpatch |
2010-06-18 19:09:56 | kowey | set | files:
- unnamed |
2010-06-18 19:09:59 | kowey | set | files:
- unnamed |
2010-06-18 19:11:04 | kowey | set | files:
+ accept-issue1277_-darcs-repository-format-errors-not-reported-in-add_-.dpatch, unnamed messages:
+ msg11483 |
2010-06-18 20:12:03 | tux_rocker | set | status: needs-review -> review-in-progress assignedto: tux_rocker nosy:
+ tux_rocker |
2010-06-19 15:12:42 | kowey | set | title: Accept issue1227: darcs repository forma... (and 2 more) -> Accept issue1277: darcs repository forma... (and 2 more) |
2010-06-20 18:25:27 | tux_rocker | set | messages:
+ msg11500 title: Accept issue1277: darcs repository forma... (and 2 more) -> Accept issue1227: darcs repository forma... (and 2 more) |
2010-06-20 18:35:00 | tux_rocker | set | messages:
+ msg11501 |
2010-06-20 20:03:25 | kowey | set | messages:
+ msg11502 |
2010-06-21 18:06:00 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-80ab199b43bfb3ebcce59577a0230fcfcfb9f036 |
2010-06-21 18:06:06 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-80ab199b43bfb3ebcce59577a0230fcfcfb9f036 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-6a2f0607ae558349c537ae412e3ad33da66b600c |
2010-06-21 18:06:25 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-6a2f0607ae558349c537ae412e3ad33da66b600c -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-06544296b81149290bf71cc847c4d5917e16fa58 |
2010-06-21 18:23:24 | kowey | set | files:
+ accept-issue1277_-darcs-repository-format-errors-not-reported-in-add_-.dpatch, unnamed messages:
+ msg11518 |
2010-06-21 18:23:59 | kowey | set | status: review-in-progress -> needs-review |
2010-06-21 18:25:19 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-06544296b81149290bf71cc847c4d5917e16fa58 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-3238fcb7291af01adee6e0c3ec831db60fe3cc6a |
2010-06-21 18:26:28 | kowey | set | files:
- accept-issue1277_-darcs-repository-format-errors-not-reported-in-add_-.dpatch |
2010-06-21 18:26:31 | kowey | set | files:
+ accept-issue1277_-darcs-repository-format-errors-not-reported-in-add_-.dpatch, unnamed messages:
+ msg11519 |
2010-06-21 18:26:32 | kowey | set | files:
- accept-issue1277_-darcs-repository-format-errors-not-reported-in-add_-.dpatch |
2010-06-21 18:28:11 | kowey | set | title: Accept issue1227: darcs repository forma... (and 2 more) -> Accept issue1277: darcs repository forma... (and 2 more) |
2010-06-21 18:29:05 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-3238fcb7291af01adee6e0c3ec831db60fe3cc6a -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-fbf98e0d16e6f53ce205d54f635609bad8a839c5 |
2010-06-27 13:46:33 | tux_rocker | set | messages:
+ msg11600 title: Accept issue1277: darcs repository forma... (and 2 more) -> Accept issue1227: darcs repository forma... (and 2 more) |
2010-06-27 14:02:15 | darcswatch | set | status: needs-review -> accepted messages:
+ msg11602 |
2011-05-10 19:35:32 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-fbf98e0d16e6f53ce205d54f635609bad8a839c5 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-6a2f0607ae558349c537ae412e3ad33da66b600c |
2011-05-10 19:36:53 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-6a2f0607ae558349c537ae412e3ad33da66b600c -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-3238fcb7291af01adee6e0c3ec831db60fe3cc6a |
2011-05-10 19:37:50 | darcswatch | set | messages:
+ msg14218 |
2011-05-10 20:36:02 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-3238fcb7291af01adee6e0c3ec831db60fe3cc6a -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-06544296b81149290bf71cc847c4d5917e16fa58 |
2011-05-10 22:05:37 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-06544296b81149290bf71cc847c4d5917e16fa58 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-80ab199b43bfb3ebcce59577a0230fcfcfb9f036 |
|