Created on 2010-06-01.16:28:54 by builes.adolfo, last changed 2011-05-10.22:05:34 by darcswatch. Tracked on DarcsWatch.
File name |
Status |
Uploaded |
Type |
Edit |
Remove |
resolve-issue-1503.dpatch
|
|
builes.adolfo,
2010-06-01.16:28:54
|
text/x-darcs-patch |
|
|
resolve-issue-1503_-try-local-repos-before-remote-ones_.dpatch
|
|
builes.adolfo,
2010-06-02.04:19:20
|
text/x-darcs-patch |
|
|
resolve-issue-1503_-when-pulling_-prefer-local-repos-to-remote-ones.dpatch
|
|
builes.adolfo,
2010-06-01.22:46:03
|
text/x-darcs-patch |
|
|
resolve-issue1503_-prefer-local-caches-to-remote-ones.dpatch
|
|
builes.adolfo,
2010-06-03.06:27:26
|
text/x-darcs-patch |
|
|
testRepos.tar
|
|
builes.adolfo,
2010-06-03.07:02:49
|
application/x-tar |
|
|
unnamed
|
|
builes.adolfo,
2010-06-01.16:28:54
|
|
|
|
unnamed
|
|
builes.adolfo,
2010-06-01.22:18:58
|
text/html |
|
|
unnamed
|
|
builes.adolfo,
2010-06-01.22:46:03
|
|
|
|
unnamed
|
|
builes.adolfo,
2010-06-02.04:10:50
|
text/html |
|
|
unnamed
|
|
builes.adolfo,
2010-06-02.04:19:20
|
|
|
|
unnamed
|
|
builes.adolfo,
2010-06-03.06:26:27
|
text/html |
|
|
unnamed
|
|
builes.adolfo,
2010-06-03.06:27:26
|
|
|
|
unnamed
|
|
builes.adolfo,
2010-06-03.07:02:49
|
text/html |
|
|
See mailing list archives
for discussion on individual patches.
msg11175 (view) |
Author: abuiles |
Date: 2010-06-01.16:28:54 |
|
1 patch for repository http://darcs.net:
Mon May 31 20:15:34 COT 2010 builes.adolfo@googlemail.com
* Resolve issue 1503
Attachments
|
msg11176 (view) |
Author: kowey |
Date: 2010-06-01.17:39:11 |
|
On Tue, Jun 01, 2010 at 16:28:54 +0000, Adolfo Builes wrote:
> Mon May 31 20:15:34 COT 2010 builes.adolfo@googlemail.com
> * Resolve issue 1503
Hooray, first GSoC patch!
OK, some minor things to fix at least:
* the patch name
* separate out unrelated patches from content patch
Things to think about and discuss if needed:
* design/functionality questions
* stylistic changes
* testing
As for testing: Is there any reasonable way you can think of to test
this patch automatically? See the network directory for some examples.
We could set up some test repositories on darcs.net if you need.
Resolve issue 1503
------------------
This should have a slightly more descriptive title. For example,
Resolve issue1503: treat pull repos as source entries
You're not always going to be able to fit everything into the patch
name, but just get the important points down so that people know what
it is at a glance. You could always say more in the patch log if you
feel the need.
http://wiki.darcs.net/Development/GettingStarted
> -import Darcs.Repository.Merge
Cleanup changes like this (and your trailing whitespace cleanup) should
be done in a separate patch so that it's clearer what the actual meat of
your work is.
> +import qualified Darcs.Repository.InternalTypes as DRI
Importing these internal modules is a often bad sign (sometimes it's a
necessary evil, because the Darcs.Repository.* layer is not very clean).
Do we really need it? Can we import from Darcs.Repository instead?
> pullCmd :: [DarcsFlag] -> [String] -> IO ()
> pullCmd opts repos =
> - withRepoLock opts $- \repository ->
> - fetchPatches opts' repos "pull" repository >>= applyPatches opts' repository
> + withRepoLock opts $- \repository -> do
> + repository' <- addLocalReposToCache repository repos
> + out <- fetchPatches opts' repos "pull" repository'
> + applyPatches opts' repository' out
Note that in situations like this, it's easy (for me) to accidentally
use the wrong identifier (eg. repository when I mean repository').
I wonder if there's a way you can get rid of one of these points
somehow. Maybe some sort of partial application thing like
withRepoLock opts $- addLocalReposToCache repos >>= $ \repository ->
> hunk ./src/Darcs/Commands/Pull.lhs 186
> +-- | If we are pulling from local repositories, they are appended to
> +-- the list of the caches loaded from sources, the idea behind is to
> +-- avoid going to remote repositories, as darcs always try first the
> +-- ones read from sources, before trying the one given as arguments
> +-- with the command pull.
Thanks for the haddock.
This is interesting because your code makes this only half-true now, in
the sense that Darcs will only do this if the repos we are pulling from
are remote ones. So maybe a clearer way here is not to talk about how
Darcs behaves in general and just focus on the specific case. For
example, "this is to ensure that local repositories will be tried first,
even if there are already remote repositories in the sources."
> +addLocalReposToCache :: forall p C(r u). RepoPatch p => Repository p C(r u r) ->
> + [String] -> IO (Repository p C(r u r))
> +addLocalReposToCache (DRI.Repo dir opts rf(DRI.DarcsRepository pristine (DRC.Ca ccache))) repos =
> + do
> + pullingFrom <- (mapM (fixUrl opts) repos)
> + let cache = DRC.Ca (appendRepos ccache pullingFrom)
> + return (DRI.Repo dir opts rf (DRI.DarcsRepository pristine cache))
I wonder if it would be better to have a function on the
Darcs.Repository layer like
modifyCache :: forall p C(r u t). RepoPatch p => (Cache -> Cache)
-> Repository p C(r u t)
-> Repository p C(r u t)
> + where
> + appendRepos cache [] = cache
> + appendRepos cache (x:xs) = if isFile x
> + then
> + (DRC.Cache DRC.Repo DRC.NotWritable x) : appendRepos cache xs
> + else
> + appendRepos cache xs
Hmm, this seems like a step in the right direction because it would
ensure that when pulling from local repositories, we will not
accidentally prioritise any remote repositories in the sources list.
It sounds like this would solve this particular bug. But how about a
more general solution which divides cache entries by locality?
For example you could say something like
compareByLocality x y
| isLocal x && isRemote y = LT
| isRemote x && isLocal y = GT
| otherwise = compare x y
Your approach is a bit more conservative, but I think the approach I
suggest is a bit more general as it will cause Darcs to systematically
prefer all local cache entries to remote ones.
Stylistic issues [hlint could be helpful here]:
* I think you mean prepend instead of append (I think appending xs to ys
means ys ++ xs).
* It seems like appendRepos would be a simpler with filter/map instead
of explicit recursion.
* Superfluous parentheses (mapM...)
--
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
PGP Key ID: 08AC04F9
|
msg11177 (view) |
Author: abuiles |
Date: 2010-06-01.22:18:58 |
|
>
> As for testing: Is there any reasonable way you can think of to test
> this patch automatically? See the network directory for some examples.
> We could set up some test repositories on darcs.net if you need.
I used http://physics.oregonstate.edu/~roundyd/code/franchise for testing,
but I think It would be good if we have our own repos in darcs.net, let me
now when we have some and I will write the test.
Attachments
|
msg11178 (view) |
Author: abuiles |
Date: 2010-06-01.22:46:03 |
|
1 patch for repository http://darcs.net:
Tue Jun 1 17:33:13 COT 2010 builes.adolfo@googlemail.com
* Resolve issue 1503: when pulling, prefer local repos to remote ones
Attachments
|
msg11180 (view) |
Author: abuiles |
Date: 2010-06-02.04:10:50 |
|
While I was looking at issue 1210, I noticed I was missing something, I was
only sorting in the function "copyFileUsingCache", but it is also necessary
in "fetchFileUsingCachePrivate", I'm resending the patch fixing that, and
changing again the patch name, that remembers me Phil Karlton quote:
*“*There are only two hard problems in Computer Science: cache invalidation
> and naming things.”
**
On Tue, Jun 1, 2010 at 5:47 PM, <builes.adolfo@googlemail.com> wrote:
> 1 patch for repository http://darcs.net:
>
> Tue Jun 1 17:33:13 COT 2010 builes.adolfo@googlemail.com
> * Resolve issue 1503: when pulling, prefer local repos to remote ones
>
Attachments
|
msg11181 (view) |
Author: abuiles |
Date: 2010-06-02.04:19:20 |
|
1 patch for repository http://darcs.net:
Tue Jun 1 23:01:49 COT 2010 builes.adolfo@googlemail.com
* Resolve issue 1503: try local repos before remote ones.
Attachments
|
msg11185 (view) |
Author: kowey |
Date: 2010-06-02.10:29:00 |
|
OK, I think I'm almost ready to apply this (no obvious bugs or things to
complain about).
But I have some design questions to ask you, so I'd like to wait for you
to tell me what is the right thing to do. (This really is largely about
me not knowing how to manage certain tradeoffs, so what I'm trying to do
is make sure that you've at least thought about them and are not
counting on me to have the right answers).
An example of the kind of trade-off to manage is "How close to the core
should X bit of code be? Do I want it in the surface-level code? Or
does it belong deeper down?" One could spend hours arguing about it,
which may not be productive. Alternatively, we could at least make sure
we've made a sort of "best effort" at thinking about it and then just
make a decision and see how things go. So please let me know what the
right thing to do is :-)
Resolve issue 1503: try local repos before remote ones.
-------------------------------------------------------
> + pullingFrom <- mapM (fixUrl opts) repos
> + withRepoLock opts $- \initialRepository ->
> + modifyCache initialRepository pullingFrom >>= \repository ->
> + fetchPatches opts' repos "pull" repository >>= applyPatches opts' repository
OK, we still have the two repositories here but at least it's clearer
which one you should be using at all times.
You could get rid of the extra argument by reversing the definition of
modifyCache so it lends itself more to partial application.
> +-- | Add locals repositories to cache, ensuring that locals are tried before any remote one.
> +modifyCache :: forall p C(r u). RepoPatch p => Repository p C(r u r) ->
> + [String] -> IO (Repository p C(r u r))
> +modifyCache (Repo dir opts rf(DarcsRepository pristine (Ca ccache))) repos =
I think modifyCache would be more useful as a higher order function
(otherwise, I would be not so inclined to have it in the
Darcs.Repository hierarchy).
Rather than being specifically about adding the local repositories to
the cache, it could just be about applying some (Cache -> Cache) on the
repository's cache.
> + do
> + let cache = Ca (addLocals ccache repos)
> + return (Repo dir opts rf (DarcsRepository pristine cache))
> + where
> + addLocals = foldr (\a b -> if isFile a
> + then Cache DarcsCache.Repo NotWritable a : b
> + else b)
OK, you've gotten rid of the explicit recursion, but perhaps something
like this formulation would be clearer?
addLocals xs ys = locals xs ++ ys
locals = map (Cache DarcsCache.Repo NotWritable) . filter isFile
Or maybe
addLocals xs ys = [ Cache DarcsCache.Repo NotWritable x | x <- xs, isFile x ] ++ ys
> +compareByLocality (Cache _ _ x) (Cache _ _ y)
> + | isFile x && (isUrl y || isSsh y) = LT
> + | (isUrl x || isSsh x) && isFile y = GT
> + | otherwise = EQ
Every top level function should have a type signature.
You can refactor this slightly with something like
where
isRemote z = isUrl z || isSSh z
Or maybe it'd make sense in the interest of clarity to define both
where
isLocal z = isFile z
isRemote z = isUrl z || isSSh z
Or maybe we want to make it clear that the two cases are mutually
exclusive (in which case you need to reason first if that's what
you really want to say)
where
isLocal = isFile
isRemote = not . isLocal
> copyFileUsingCache :: OrOnlySpeculate -> Cache -> HashedDir -> String -> IO ()
> -copyFileUsingCache oos (Ca cache) subdir f =
> - do debugMessage $ "I'm doing copyFileUsingCache on "++(hashedDir subdir)++"/"++f
> +copyFileUsingCache oos (Ca unsortedCache) subdir f =
> + do let (Ca cache) = Ca (sortBy compareByLocality unsortedCache)
> + debugMessage $ "I'm doing copyFileUsingCache on "++(hashedDir subdir)++"/"++f
Interesting. One question: does this sorting belong here? What if in
the future we want to sort by proximity to the repository directory?
How would we manage that? What's the right attitude to adopt here? One
possible answer, for example, is YAGNI. Is that the right one?
> fetchFileUsingCachePrivate :: FromWhere -> Cache -> HashedDir -> String -> IO (String, B.ByteString)
> -fetchFileUsingCachePrivate fromWhere (Ca cache) subdir f =
> +fetchFileUsingCachePrivate fromWhere (Ca unsortedCache) subdir f =
> do when (fromWhere == Anywhere) $ copyFileUsingCache ActuallyCopy (Ca cache) subdir f
> ffuc cache
> `catchall` debugFail ("Couldn't fetch `"++f++"'\nin subdir "++(hashedDir subdir)++
> hunk ./src/Darcs/Repository/Cache.hs 265
>
> ffuc [] = debugFail $ "No sources from which to fetch file `"++f++"'\n"++ show (Ca cache)
>
> + Ca cache = Ca (sortBy compareByLocality unsortedCache)
What's the difference between these two functions?
--
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
PGP Key ID: 08AC04F9
|
msg11186 (view) |
Author: kowey |
Date: 2010-06-02.11:00:28 |
|
On Tue, Jun 01, 2010 at 17:20:05 -0500, Adolfo Builes wrote:
> I used http://physics.oregonstate.edu/~roundyd/code/franchise for testing,
> but I think It would be good if we have our own repos in darcs.net, let me
> now when we have some and I will write the test.
Could you please create some minimal repositories and send them to me?
I think it makes more sense that you do this because you have a better
idea what to be testing for. :-)
Thanks,
--
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
PGP Key ID: 08AC04F9
|
msg11191 (view) |
Author: mornfall |
Date: 2010-06-02.15:54:36 |
|
Hi,
Eric Kow <kowey@darcs.net> writes:
> OK, I think I'm almost ready to apply this (no obvious bugs or things to
> complain about).
>> copyFileUsingCache :: OrOnlySpeculate -> Cache -> HashedDir -> String -> IO ()
>> -copyFileUsingCache oos (Ca cache) subdir f =
>> - do debugMessage $ "I'm doing copyFileUsingCache on "++(hashedDir subdir)++"/"++f
>> +copyFileUsingCache oos (Ca unsortedCache) subdir f =
>> + do let (Ca cache) = Ca (sortBy compareByLocality unsortedCache)
>> + debugMessage $ "I'm doing copyFileUsingCache on "++(hashedDir subdir)++"/"++f
>
> Interesting. One question: does this sorting belong here? What if in
> the future we want to sort by proximity to the repository directory?
> How would we manage that? What's the right attitude to adopt here? One
> possible answer, for example, is YAGNI. Is that the right one?
I wouldn't say that future-proofing is the problem with this bit of
code. What I find sorely inadequate is that the caches are re-sorted for
every single file that needs to be fetched. Note that with populated
cache and hardlinking, this is a *very* fast operation and the constant
sorting could actually contribute non-negligible amount of time to it.
I think a more global solution that sorts the cache as it is populated
would be more appropriate.
>> fetchFileUsingCachePrivate :: FromWhere -> Cache -> HashedDir -> String -> IO (String, B.ByteString)
>> -fetchFileUsingCachePrivate fromWhere (Ca cache) subdir f =
>> +fetchFileUsingCachePrivate fromWhere (Ca unsortedCache) subdir f =
>> do when (fromWhere == Anywhere) $ copyFileUsingCache ActuallyCopy (Ca cache) subdir f
>> ffuc cache
>> `catchall` debugFail ("Couldn't fetch `"++f++"'\nin subdir "++(hashedDir subdir)++
>> hunk ./src/Darcs/Repository/Cache.hs 265
>>
>> ffuc [] = debugFail $ "No sources from which to fetch file `"++f++"'\n"++ show (Ca cache)
>>
>> + Ca cache = Ca (sortBy compareByLocality unsortedCache)
>
> What's the difference between these two functions?
(This obviously points out the other problem with the "late" sorting:
you need to do it in every function that non-trivially uses the
cache... so it's not just performance, but also maintainability)
Yours,
Petr.
|
msg11207 (view) |
Author: abuiles |
Date: 2010-06-03.06:26:27 |
|
I have fixed some things now, and it looks better
------------------------------
>
> -------------------------
> > + pullingFrom <- mapM (fixUrl opts) repos
> > + withRepoLock opts $- \initialRepository ->
> > + modifyCache initialRepository pullingFrom >>= \repository ->
> > + fetchPatches opts' repos "pull" repository >>= applyPatches opts'
> repository
>
> OK, we still have the two repositories here but at least it's clearer
> which one you should be using at all times.
>
> You could get rid of the extra argument by reversing the definition of
> modifyCache so it lends itself more to partial application.
>
I tried before with partial application, but I was getting each time
"Inferred type is less polymorphic than expected Quantified type variable
`p' escapes", I read a workaround for it in a Oleg's paper, but that will
mean creating a newtype and ... , I think is not work for this case, I used
the lambda instead, I came back to use the do notation, I tried to do it
with binding but the compiler was complaining about a type which was
infering incorrectly, using do notation did the trick.
> +-- | Add locals repositories to cache, ensuring that locals are tried
> before any remote one.
> > +modifyCache :: forall p C(r u). RepoPatch p => Repository p C(r u r) ->
> > + [String] -> IO (Repository p C(r u r))
> > +modifyCache (Repo dir opts rf(DarcsRepository pristine (Ca ccache)))
> repos =
>
> I think modifyCache would be more useful as a higher order function
> (otherwise, I would be not so inclined to have it in the
> Darcs.Repository hierarchy).
>
> Rather than being specifically about adding the local repositories to
> the cache, it could just be about applying some (Cache -> Cache) on the
> repository's cache.
>
>
I modify "modifyCache" now it is located in Repository.InternalTypes, there
is a similar function there which acts over ther cache, so that's why I
decided to put there, also, mornfal noticed :
*18:23 mornfall: InternalTypes is a misnomer already -- but yes, it will do
> for now.*
>
So, I will write these down for a future refactor.
> + do
> > + let cache = Ca (addLocals ccache repos)
> > + return (Repo dir opts rf (DarcsRepository pristine cache))
> > + where
> > + addLocals = foldr (\a b -> if isFile a
> > + then Cache DarcsCache.Repo NotWritable
> a : b
> > + else b)
>
Now the addLocal method looks is clearer, also I moved back to Pull.hs, and
makes use of the function "modifyCache", it looks like :
addLocal repo repos = modifyCache repo $ \ (Ca cache) ->
Ca $ [Cache
DarcsCache.Repo NotWritable r | r <- repos, isFile r ] ++ cache
> +compareByLocality (Cache _ _ x) (Cache _ _ y)
> > + | isFile x && (isUrl y || isSsh y) = LT
> > + | (isUrl x || isSsh x) && isFile y = GT
> > + | otherwise = EQ
>
> Every top level function should have a type signature.
>
>
Sorry, I didn't added it :).. now it has its signature
> copyFileUsingCache :: OrOnlySpeculate -> Cache -> HashedDir -> String ->
> IO ()
> > -copyFileUsingCache oos (Ca cache) subdir f =
> > - do debugMessage $ "I'm doing copyFileUsingCache on "++(hashedDir
> subdir)++"/"++f
> > +copyFileUsingCache oos (Ca unsortedCache) subdir f =
> > + do let (Ca cache) = Ca (sortBy compareByLocality unsortedCache)
> > + debugMessage $ "I'm doing copyFileUsingCache on "++(hashedDir
> subdir)++"/"++f
>
> Interesting. One question: does this sorting belong here? What if in
> the future we want to sort by proximity to the repository directory?
> How would we manage that? What's the right attitude to adopt here? One
> possible answer, for example, is YAGNI. Is that the right one?
>
> I have lifted all that sorting from there, now it is done when it is as it
is populated ( thanks Petr :))
> fetchFileUsingCachePrivate :: FromWhere -> Cache -> HashedDir -> String
> -> IO (String, B.ByteString)
> > -fetchFileUsingCachePrivate fromWhere (Ca cache) subdir f =
> > +fetchFileUsingCachePrivate fromWhere (Ca unsortedCache) subdir f =
> > do when (fromWhere == Anywhere) $ copyFileUsingCache ActuallyCopy
> (Ca cache) subdir f
> > ffuc cache
> > `catchall` debugFail ("Couldn't fetch `"++f++"'\nin subdir
> "++(hashedDir subdir)++
> > hunk ./src/Darcs/Repository/Cache.
>>
>> hs 265
>> >
>> > ffuc [] = debugFail $ "No sources from which to fetch file
>> `"++f++"'\n"++ show (Ca cache)
>> >
>> > + Ca cache = Ca (sortBy compareByLocality unsortedCache)
>>
>> What's the difference between these two functions?
>
>
I don't have a clear answer for that question, I was writing something but
then I realize it was a supposition I was doing, I hope to have a proper
answer by the weekend :).
--
Adolfo
Attachments
|
msg11208 (view) |
Author: abuiles |
Date: 2010-06-03.06:27:26 |
|
1 patch for repository http://darcs.net:
Thu Jun 3 00:36:59 COT 2010 builes.adolfo@googlemail.com
* Resolve issue1503: prefer local caches to remote ones
Attachments
|
msg11209 (view) |
Author: abuiles |
Date: 2010-06-03.07:02:49 |
|
>
> Could you please create some minimal repositories and send them to me?
>
> I think it makes more sense that you do this because you have a better
> idea what to be testing for. :-)
>
>
Okay :). I created two basic repositories which I think will be enough to
write the test, it would be similar to the test you write in the issue,
although, trying with local repos is not a problem, it is when the initial
repo is remote.
Attachments
|
msg11213 (view) |
Author: kowey |
Date: 2010-06-03.14:49:34 |
|
Looks like we're ready for push! I'll be pushing this in and adding a
very minor whitespace cleanup.
Resolve issue1503: prefer local caches to remote ones
-----------------------------------------------------
> pullCmd :: [DarcsFlag] -> [String] -> IO ()
> pullCmd opts repos =
> - withRepoLock opts $- \repository ->
> - fetchPatches opts' repos "pull" repository >>= applyPatches opts' repository
> + do
> + pullingFrom <- mapM (fixUrl opts) repos
> + withRepoLock opts $- \ initRepo -> do
> + let repository = addLocal initRepo pullingFrom
> + r <- fetchPatches opts' repos "pull" repository
> + applyPatches opts' repository r
> where
> opts' = mergeOpts opts
> hunk ./src/Darcs/Commands/Pull.lhs 186
> + addLocal repo repos = modifyCache repo $ \ (Ca cache) -> Ca $ [Cache DarcsCache.Repo NotWritable r | r <- repos, isFile r ] ++ cache
Yeah, I think this version has the right scope for the bits and pieces
of helper code.
> hunk ./src/Darcs/Repository/Cache.hs 15
> +-- | Compares two caches, a remote cache is greater than a local one.
> +compareByLocality :: CacheLoc -> CacheLoc -> Ordering
> +compareByLocality (Cache _ _ x) (Cache _ _ y)
> + | isLocal x && isRemote y = LT
> + | isRemote x && isLocal y = GT
> + | otherwise = EQ
> + where
> + isRemote r= isUrl r || isSsh r
> + isLocal = isFile
At first, I was going to say something about the sortBy function
assuming a total ordering, but I guess this *is* one:
- antisymmetry - check
- transitivity - check (well, you'll never have a < b < c)
- totality - check
Hmm, dunno what I was worried about. Maybe I was confused by the
definition of EQ. Moment of superstition?
> +-- | Modifies the cache of a given repository with the function f
> +modifyCache :: FORALL(p r u t) (RepoPatch p) => Repository p C(r u t) -> (Cache -> Cache) -> Repository p C(r u t)
> +modifyCache (Repo dir opts rf (DarcsRepository pristine cache)) f =
> + Repo dir opts rf (DarcsRepository pristine (f cache))
There's some trailing whitespace which I'll fix in a separate patch
> hunk ./src/Darcs/Repository/Prefs.lhs 520
> - return $ Ca $ nub $ thisrepo ++ globalcache ++ globalsources ++
> + let tempCache = nub $ thisrepo ++ globalcache ++ globalsources ++
> here ++ [Cache Repo NotWritable repodir] ++ there
> + return $ Ca $ sortBy compareByLocality tempCache
This just introduces locality-based sorting into getCaches, so no matter
how your repo has the caches sorted, it'll try the local ones first.
--
Eric Kow <http://www.nltg.brighton.ac.uk/home/Eric.Kow>
PGP Key ID: 08AC04F9
|
msg11218 (view) |
Author: darcswatch |
Date: 2010-06-03.17:20:53 |
|
This patch bundle (with 1 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-335f961f3ce6a5b14c5d82bf68e9b60639330174
|
msg14334 (view) |
Author: darcswatch |
Date: 2011-05-10.21:35:44 |
|
This patch bundle (with 1 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-335f961f3ce6a5b14c5d82bf68e9b60639330174
|
|
Date |
User |
Action |
Args |
2010-06-01 16:28:54 | builes.adolfo | create | |
2010-06-01 16:31:08 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-bc8d0735587b411eda2c101b659fcaef4885bbe7 |
2010-06-01 17:39:12 | kowey | set | nosy:
+ kowey messages:
+ msg11176 |
2010-06-01 22:18:58 | builes.adolfo | set | files:
+ unnamed messages:
+ msg11177 |
2010-06-01 22:46:03 | builes.adolfo | set | files:
+ resolve-issue-1503_-when-pulling_-prefer-local-repos-to-remote-ones.dpatch, unnamed messages:
+ msg11178 |
2010-06-01 22:47:15 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-bc8d0735587b411eda2c101b659fcaef4885bbe7 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-84c605bc4517a02a8a2806409d48501d990039f8 |
2010-06-02 04:10:51 | builes.adolfo | set | files:
+ unnamed messages:
+ msg11180 |
2010-06-02 04:19:20 | builes.adolfo | set | files:
+ resolve-issue-1503_-try-local-repos-before-remote-ones_.dpatch, unnamed messages:
+ msg11181 |
2010-06-02 04:20:23 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-84c605bc4517a02a8a2806409d48501d990039f8 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-c4ea038c82184bd28979c7b0026f1ebfd7406b03 |
2010-06-02 10:29:00 | kowey | set | messages:
+ msg11185 |
2010-06-02 11:00:28 | kowey | set | nosy:
+ abuiles messages:
+ msg11186 |
2010-06-02 15:54:36 | mornfall | set | nosy:
+ mornfall messages:
+ msg11191 |
2010-06-03 06:26:27 | builes.adolfo | set | files:
+ unnamed messages:
+ msg11207 |
2010-06-03 06:27:26 | builes.adolfo | set | files:
+ resolve-issue1503_-prefer-local-caches-to-remote-ones.dpatch, unnamed messages:
+ msg11208 |
2010-06-03 06:28:25 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-c4ea038c82184bd28979c7b0026f1ebfd7406b03 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-335f961f3ce6a5b14c5d82bf68e9b60639330174 |
2010-06-03 07:02:49 | builes.adolfo | set | files:
+ unnamed, testRepos.tar messages:
+ msg11209 |
2010-06-03 14:49:34 | kowey | set | messages:
+ msg11213 |
2010-06-03 17:20:53 | darcswatch | set | status: needs-review -> accepted messages:
+ msg11218 |
2011-05-10 19:06:26 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_.html#bundle-335f961f3ce6a5b14c5d82bf68e9b60639330174 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-bc8d0735587b411eda2c101b659fcaef4885bbe7 |
2011-05-10 19:36:51 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-bc8d0735587b411eda2c101b659fcaef4885bbe7 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-84c605bc4517a02a8a2806409d48501d990039f8 |
2011-05-10 21:35:44 | darcswatch | set | messages:
+ msg14334 |
2011-05-10 22:05:34 | darcswatch | set | darcswatchurl: http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-84c605bc4517a02a8a2806409d48501d990039f8 -> http://darcswatch.nomeata.de/repo_http:__darcs.net_reviewed.html#bundle-c4ea038c82184bd28979c7b0026f1ebfd7406b03 |
|