Hi,
this bundle hopefully improves the Repository.Repair module somewhat. I agree
that the middle patch makes applyAndFix there even uglier than it already was,
but I have started working on making Slurpies "syncable" in a way that would
make this less ugly and more (hopefully much more) efficient.
It passed the suite and I don't see any obvious mistakes, other than that
output of darcs check is currently suboptimal. I'll eventually fix that, too.
Yours,
(should have been in bed for 2 hours now) Petr.
Wed Nov 5 23:41:32 CET 2008 Petr Rockai <[EMAIL PROTECTED]>
* Change "Repairing patch" to "Replaying patch" as progress report in
replayRepository.
Thu Nov 6 00:46:38 CET 2008 Petr Rockai <[EMAIL PROTECTED]>
* Refactor Repository.Repair.replayRepository to get rid of CanRepair.
We now instead return the new (repaired) patchset that needs to be written out
to the caller, and let them handle it.
Thu Nov 6 01:00:49 CET 2008 Petr Rockai <[EMAIL PROTECTED]>
* Avoid exporting cleanupRepositoryReplay.
We instead let replayRepository take the post-replay action as a parameter and
clean up automatically when it's done. Looks like a safer API to me.
New patches:
[Change "Repairing patch" to "Replaying patch" as progress report in replayRepository.
Petr Rockai <[EMAIL PROTECTED]>**20081105224132] hunk ./src/Darcs/Repository/Repair.hs 63
ps <- aaf 0 s_ psin
endTedious k
return ps
- where k = "Repairing patch" -- FIXME
+ where k = "Replaying patch"
aaf _ s NilFL = return (NilFL, s)
aaf i s (p:>:ps) = do
(s', mp') <- run_slurpy s $ applyAndTryToFix p
[Refactor Repository.Repair.replayRepository to get rid of CanRepair.
Petr Rockai <[EMAIL PROTECTED]>**20081105234638
We now instead return the new (repaired) patchset that needs to be written out
to the caller, and let them handle it.
] hunk ./src/Darcs/Commands/Check.lhs 30
leave_test_dir, working_repo_dir,
)
import Darcs.Repository.Repair( replayRepository, cleanupRepositoryReplay,
- RepositoryConsistency(..), CanRepair(..) )
+ RepositoryConsistency(..) )
import Darcs.Repository ( Repository, amInRepository, withRepository, ($-), slurp_recorded,
testTentative )
import Darcs.Patch ( RepoPatch, showPatch )
hunk ./src/Darcs/Commands/Check.lhs 92
check' :: (RepoPatch p) => Repository p -> [DarcsFlag] -> IO ()
check' repository opts = do
- let putInfo s = when (not $ Quiet `elem` opts) $ putDocLn s
- state <- replayRepository CannotRepair repository opts
+ state <- replayRepository repository opts
case state of
RepositoryConsistent -> do
putInfo $ text "The repository is consistent!"
hunk ./src/Darcs/Commands/Check.lhs 98
unless (NoTest `elem` opts) $ testTentative repository
done ExitSuccess
- RepositoryInconsistent newpris -> do
+ BrokenPristine newpris -> do
+ brokenPristine newpris
+ done $ ExitFailure 1
+ BrokenPatches newpris _ -> do
+ brokenPristine newpris
+ putInfo $ text "Found broken patches."
+ done $ ExitFailure 1
+ where done r = do cleanupRepositoryReplay repository
+ exitWith r
+ brokenPristine newpris = do
putInfo $ text "Looks like we have a difference..."
mc <- slurp_recorded repository
ftf <- filetype_function
hunk ./src/Darcs/Commands/Check.lhs 116
patch -> text "Difference: " <+> showPatch patch
putInfo $ text ""
$$ text "Inconsistent repository!"
- done $ ExitFailure 1
- where done r = do cleanupRepositoryReplay repository
- exitWith r
+ putInfo s = when (not $ Quiet `elem` opts) $ putDocLn s
\end{code}
\input{Darcs/Test.lhs}
hunk ./src/Darcs/Commands/Repair.lhs 29
working_repo_dir, umask_option,
)
import Darcs.Repository ( withRepoLock, ($-), amInRepository,
- replacePristineFromSlurpy )
+ replacePristineFromSlurpy, writePatchSet )
import Darcs.Repository.Repair( replayRepository, cleanupRepositoryReplay,
hunk ./src/Darcs/Commands/Repair.lhs 31
- RepositoryConsistency(..), CanRepair(..) )
+ RepositoryConsistency(..) )
\end{code}
\options{repair}
hunk ./src/Darcs/Commands/Repair.lhs 71
repair_cmd :: [DarcsFlag] -> [String] -> IO ()
repair_cmd opts _ = withRepoLock opts $- \repository -> do
- state <- replayRepository CanRepair repository opts
+ state <- replayRepository repository opts
case state of
RepositoryConsistent ->
putStrLn "The repository is already consistent, no changes made."
hunk ./src/Darcs/Commands/Repair.lhs 75
- RepositoryInconsistent s -> do
+ BrokenPristine s -> do
putStrLn "Fixing pristine tree..."
replacePristineFromSlurpy repository s
hunk ./src/Darcs/Commands/Repair.lhs 78
+ BrokenPatches s newps -> do
+ putStrLn "Writing out repaired patches..."
+ writePatchSet newps opts
+ putStrLn "Fixing pristine tree..."
+ replacePristineFromSlurpy repository s
+ return ()
cleanupRepositoryReplay repository
exitWith ExitSuccess
hunk ./src/Darcs/Repository/Repair.hs 2
module Darcs.Repository.Repair ( replayRepository, cleanupRepositoryReplay,
- RepositoryConsistency(..), CanRepair(..) )
+ RepositoryConsistency(..) )
where
import Control.Monad ( when, unless )
hunk ./src/Darcs/Repository/Repair.hs 19
import Darcs.Patch.Depends ( get_patches_beyond_tag )
import Darcs.Patch.Patchy ( applyAndTryToFix )
import Darcs.Patch.Info ( human_friendly )
+import Darcs.Patch.Set ( PatchSet )
import Darcs.Patch ( RepoPatch, patch2patchinfo )
import Darcs.Repository.Format ( identifyRepoFormat,
hunk ./src/Darcs/Repository/Repair.hs 32
import Darcs.Repository.InternalTypes ( extractCache )
import Darcs.Repository ( Repository, read_repo,
checkPristineAgainstSlurpy,
- writePatchSet, makePatchLazy )
+ makePatchLazy )
import Darcs.Sealed ( Sealed(..), unsafeUnflippedseal )
import Darcs.Progress ( debugMessage, beginTedious, endTedious, tediousSize, finishedOneIO )
hunk ./src/Darcs/Repository/Repair.hs 56
clean_hashdir c HashedPristineDir $ catMaybes [Just h, current]
return s'
-applyAndFix :: RepoPatch p => Cache -> [DarcsFlag] -> Slurpy -> Repository p -> FL (PatchInfoAnd p) -> IO (FL (PatchInfoAnd p), Slurpy)
-applyAndFix _ _ s _ NilFL = return (NilFL, s)
+applyAndFix :: RepoPatch p => Cache -> [DarcsFlag] -> Slurpy -> Repository p -> FL (PatchInfoAnd p) -> IO ((FL (PatchInfoAnd p)), Slurpy, Bool)
+applyAndFix _ _ s _ NilFL = return (NilFL, s, True)
applyAndFix c opts s_ r psin =
do beginTedious k
tediousSize k $ lengthFL psin
hunk ./src/Darcs/Repository/Repair.hs 65
endTedious k
return ps
where k = "Replaying patch"
- aaf _ s NilFL = return (NilFL, s)
+ aaf _ s NilFL = return (NilFL, s, True)
aaf i s (p:>:ps) = do
(s', mp') <- run_slurpy s $ applyAndTryToFix p
finishedOneIO k $ show $ human_friendly $ info p
hunk ./src/Darcs/Repository/Repair.hs 69
- p' <- case mp' of
- Nothing -> return p
+ (p', ourok) <- case mp' of
+ Nothing -> return (p, True)
Just (e,pp) -> do putStrLn e
hunk ./src/Darcs/Repository/Repair.hs 72
- return pp
+ return (pp, False)
p'' <- makePatchLazy r p'
let j = if ((i::Int) + 1 < 100) then i + 1 else 0
hunk ./src/Darcs/Repository/Repair.hs 75
- (ps', s'') <- aaf j s' ps
+ (ps', s'', restok) <- aaf j s' ps
s''' <- if j == 0 then update_slurpy r c opts s''
else return s''
hunk ./src/Darcs/Repository/Repair.hs 78
- return ((p'':>:ps'), s''')
+ return ((p'':>:ps'), s''', restok && ourok)
hunk ./src/Darcs/Repository/Repair.hs 80
-data RepositoryConsistency = RepositoryConsistent | RepositoryInconsistent Slurpy
-data CanRepair = CanRepair | CannotRepair deriving Eq
+data RepositoryConsistency p =
+ RepositoryConsistent
+ | BrokenPristine Slurpy
+ | BrokenPatches Slurpy (PatchSet p)
check_uniqueness :: RepoPatch p => (Doc -> IO ()) -> (Doc -> IO ()) -> Repository p -> IO ()
check_uniqueness putVerbose putInfo repository =
hunk ./src/Darcs/Repository/Repair.hs 101
hd [] = Nothing
hd (x1:x2:xs) | x1 == x2 = Just x1
| otherwise = hd (x2:xs)
-replayRepository :: (RepoPatch p) => CanRepair -> Repository p -> [DarcsFlag] -> IO RepositoryConsistency
-replayRepository canrepair repo opts = do
+replayRepository :: (RepoPatch p) => Repository p -> [DarcsFlag] -> IO (RepositoryConsistency p)
+replayRepository repo opts = do
let putVerbose s = when (Verbose `elem` opts) $ putDocLn s
putInfo s = when (not $ Quiet `elem` opts) $ putDocLn s
check_uniqueness putVerbose putInfo repo
hunk ./src/Darcs/Repository/Repair.hs 112
rooth <- writeHashedPristine c (compression opts) empty_slurpy
s <- slurpHashedPristine c (compression opts) rooth
putVerbose $ text "Applying patches..."
- s' <- case maybe_chk of
+ patches <- read_repo repo
+ (s', newpatches, patches_ok) <- case maybe_chk of
Just (Sealed chk) ->
do let chtg = patch2patchinfo chk
putVerbose $ text "I am repairing from a checkpoint."
hunk ./src/Darcs/Repository/Repair.hs 117
- patches <- read_repo repo
(s'', _) <- run_slurpy s $ applyAndTryToFix chk
hunk ./src/Darcs/Repository/Repair.hs 118
- (_, s_) <- applyAndFix c opts s'' repo
+ (_, s_, ok) <- applyAndFix c opts s'' repo
(reverseRL $ concatRL $ unsafeUnflippedseal $ get_patches_beyond_tag chtg patches)
hunk ./src/Darcs/Repository/Repair.hs 120
- return s_
+ return (s_, patches, ok)
Nothing -> do debugMessage "Fixing any broken patches..."
hunk ./src/Darcs/Repository/Repair.hs 122
- rawpatches <- read_repo repo
- let psin = reverseRL $ concatRL rawpatches
- (ps, s_) <- applyAndFix c opts s repo psin
- when (canrepair == CanRepair) $ do
- writePatchSet (reverseFL ps :<: NilRL) opts
- return ()
+ let psin = reverseRL $ concatRL patches
+ (ps, s_, ok) <- applyAndFix c opts s repo psin
debugMessage "Done fixing broken patches..."
hunk ./src/Darcs/Repository/Repair.hs 125
- return s_
+ return (s_, (reverseFL ps :<: NilRL), ok)
debugMessage "Checking pristine agains slurpy"
is_same <- checkPristineAgainstSlurpy repo s' `catchall` return False
hunk ./src/Darcs/Repository/Repair.hs 128
- if is_same
- then return RepositoryConsistent
- else return $ RepositoryInconsistent s'
+ -- TODO is the latter condition needed? Does a broken patch imply pristine
+ -- difference? Why, or why not?
+ return (if is_same && patches_ok
+ then RepositoryConsistent
+ else if patches_ok
+ then BrokenPristine s'
+ else BrokenPatches s' newpatches)
cleanupRepositoryReplay :: Repository p -> IO ()
cleanupRepositoryReplay r = do
[Avoid exporting cleanupRepositoryReplay.
Petr Rockai <[EMAIL PROTECTED]>**20081106000049
We instead let replayRepository take the post-replay action as a parameter and
clean up automatically when it's done. Looks like a safer API to me.
] hunk ./src/Darcs/Commands/Check.lhs 29
partial_check, notest,
leave_test_dir, working_repo_dir,
)
-import Darcs.Repository.Repair( replayRepository, cleanupRepositoryReplay,
+import Darcs.Repository.Repair( replayRepository,
RepositoryConsistency(..) )
import Darcs.Repository ( Repository, amInRepository, withRepository, ($-), slurp_recorded,
testTentative )
hunk ./src/Darcs/Commands/Check.lhs 92
check' :: (RepoPatch p) => Repository p -> [DarcsFlag] -> IO ()
check' repository opts = do
- state <- replayRepository repository opts
- case state of
- RepositoryConsistent -> do
- putInfo $ text "The repository is consistent!"
- unless (NoTest `elem` opts) $ testTentative repository
- done ExitSuccess
- BrokenPristine newpris -> do
- brokenPristine newpris
- done $ ExitFailure 1
- BrokenPatches newpris _ -> do
- brokenPristine newpris
- putInfo $ text "Found broken patches."
- done $ ExitFailure 1
- where done r = do cleanupRepositoryReplay repository
- exitWith r
- brokenPristine newpris = do
- putInfo $ text "Looks like we have a difference..."
- mc <- slurp_recorded repository
- ftf <- filetype_function
- putInfo $ case unsafeDiff opts ftf newpris mc of
+ res <- replayRepository repository opts $ \ state -> do
+ case state of
+ RepositoryConsistent -> do
+ putInfo $ text "The repository is consistent!"
+ unless (NoTest `elem` opts) $ testTentative repository
+ return ExitSuccess
+ BrokenPristine newpris -> do
+ brokenPristine newpris
+ return $ ExitFailure 1
+ BrokenPatches newpris _ -> do
+ brokenPristine newpris
+ putInfo $ text "Found broken patches."
+ return $ ExitFailure 1
+ exitWith res
+ where
+ brokenPristine newpris = do
+ putInfo $ text "Looks like we have a difference..."
+ mc <- slurp_recorded repository
+ ftf <- filetype_function
+ putInfo $ case unsafeDiff opts ftf newpris mc of
NilFL -> text "Nothing"
patch -> text "Difference: " <+> showPatch patch
hunk ./src/Darcs/Commands/Check.lhs 114
- putInfo $ text ""
+ putInfo $ text ""
$$ text "Inconsistent repository!"
hunk ./src/Darcs/Commands/Check.lhs 116
- putInfo s = when (not $ Quiet `elem` opts) $ putDocLn s
+ putInfo s = when (not $ Quiet `elem` opts) $ putDocLn s
\end{code}
\input{Darcs/Test.lhs}
hunk ./src/Darcs/Commands/Repair.lhs 30
)
import Darcs.Repository ( withRepoLock, ($-), amInRepository,
replacePristineFromSlurpy, writePatchSet )
-import Darcs.Repository.Repair( replayRepository, cleanupRepositoryReplay,
+import Darcs.Repository.Repair( replayRepository,
RepositoryConsistency(..) )
\end{code}
hunk ./src/Darcs/Commands/Repair.lhs 71
repair_cmd :: [DarcsFlag] -> [String] -> IO ()
repair_cmd opts _ = withRepoLock opts $- \repository -> do
- state <- replayRepository repository opts
- case state of
+ replayRepository repository opts $ \state ->
+ case state of
RepositoryConsistent ->
putStrLn "The repository is already consistent, no changes made."
BrokenPristine s -> do
hunk ./src/Darcs/Commands/Repair.lhs 84
putStrLn "Fixing pristine tree..."
replacePristineFromSlurpy repository s
return ()
- cleanupRepositoryReplay repository
exitWith ExitSuccess
\end{code}
hunk ./src/Darcs/Repository/Repair.hs 1
-module Darcs.Repository.Repair ( replayRepository, cleanupRepositoryReplay,
+module Darcs.Repository.Repair ( replayRepository,
RepositoryConsistency(..) )
where
hunk ./src/Darcs/Repository/Repair.hs 101
hd [] = Nothing
hd (x1:x2:xs) | x1 == x2 = Just x1
| otherwise = hd (x2:xs)
-replayRepository :: (RepoPatch p) => Repository p -> [DarcsFlag] -> IO (RepositoryConsistency p)
-replayRepository repo opts = do
+replayRepository' :: (RepoPatch p) => Repository p -> [DarcsFlag] -> IO (RepositoryConsistency p)
+replayRepository' repo opts = do
let putVerbose s = when (Verbose `elem` opts) $ putDocLn s
putInfo s = when (not $ Quiet `elem` opts) $ putDocLn s
check_uniqueness putVerbose putInfo repo
hunk ./src/Darcs/Repository/Repair.hs 147
when (format_has HashedInventory rf) $ do
current <- readHashedPristineRoot r
clean_hashdir c HashedPristineDir $ catMaybes [current]
+
+replayRepository :: (RepoPatch p) => Repository p -> [DarcsFlag] -> (RepositoryConsistency p -> IO a) -> IO a
+replayRepository r opt f = do
+ st <- replayRepository' r opt
+ ret <- f st
+ cleanupRepositoryReplay r
+ return ret
Context:
[Restore 'pass/fail' output in shell_harness.
Eric Kow <[EMAIL PROTECTED]>**20081105093446
Ignore-this: 93d9a4fba1f83b79a5b7b63c87e0e955
rolling back accidentally applied patch:
Fri Oct 24 06:57:55 BST 2008 Trent W. Buck <[EMAIL PROTECTED]>
* Colour test output in Emacs' M-x compile.
]
[Refactor away boilerplate in naughty ./configure-circumventing profile targets.
Trent W. Buck <[EMAIL PROTECTED]>**20081105052235]
[Resolve conflicts.
Trent W. Buck <[EMAIL PROTECTED]>**20081105014527
Mostly conflicts were between Trent's make refactoring and Kowey's
copy-and-paste job to add support for building profiled object files
and executables in parallel to the non-profiled build.
]
[Typo: make distclean and maintainer-clean rules cumulative.
Trent W. Buck <[EMAIL PROTECTED]>**20081104235641]
[Refactor TAGS targets.
Trent W. Buck <[EMAIL PROTECTED]>**20081104132834
Renamed targets to match default output files, obviating PHONY.
Removed the ugly manual sorting, as exuberant ctags sorts by default.
Moved cleanup into distclean.
Added C inputs to dependency list.
Avoid abusing $ETAGS and $CTAGS for hasktags.
]
[autoconf.mk doesn't depend on darcs.cgi.in.
Trent W. Buck <[EMAIL PROTECTED]>**20081104130338
The old version was saying things "autoconf.mk depends on
darcs.cgi.in", which isn't quite right. The replacement is shorter
and more correct.
]
[Delete unused "register" target.
Trent W. Buck <[EMAIL PROTECTED]>**20081104124530]
[Move cleanup rules to appropriate target (clean/distclean).
Trent W. Buck <[EMAIL PROTECTED]>**20081104124116]
[Resolve conflicts.
Trent W. Buck <[EMAIL PROTECTED]>**20081104123359]
[Merge autoconf.mk and .depend inclusion.
Trent W. Buck <[EMAIL PROTECTED]>**20081102045359
In a declarative expert system like Make, it shouldn't matter where
.depend is included. Actual experiments suggest that it does, and
putting it at the top will help avoid illogical behaviour.
It also reduces the makefile's length by several lines.
]
[Make .hs.in of trivial .lhs.in files.
Trent W. Buck <[EMAIL PROTECTED]>**20081029025407]
[Make .hs of trivial .lhs files.
Trent W. Buck <[EMAIL PROTECTED]>**20081029025326]
[Split darcs.lhs into darcs.tex and darcs.hs.
Trent W. Buck <[EMAIL PROTECTED]>**20081026063231
After all, the Main module and main function don't really have
anything to do with the introductory chapters of the user manual.
I used these commands and then some touch-ups:
$ sed '/\\begin{code}/,/\\end{code}/d' src/darcs.lhs >src/darcs.tex
$ darcs mv src/darcs.lhs src/darcs.hs
$ sed --in-place '/\\end{code}/,/\\begin{code}/d' src/darcs.hs
]
[Only .lhs (not .hs) files could possibly be TeX sources.
Trent W. Buck <[EMAIL PROTECTED]>**20081025141537]
[Typo: remove silly circular dependency.
Trent W. Buck <[EMAIL PROTECTED]>**20081025121957]
[Don't warn unless ALL alternatives are missing.
Trent W. Buck <[EMAIL PROTECTED]>**20081025120102]
[If installed, use rubber(1) to quieten TeX.
Trent W. Buck <[EMAIL PROTECTED]>**20081025113643]
[Typo.
Trent W. Buck <[EMAIL PROTECTED]>**20081025113607]
[Turn procedural assignments (:=) into declarations (=).
Trent W. Buck <[EMAIL PROTECTED]>**20081025100744]
[Refactor .hi rule.
Trent W. Buck <[EMAIL PROTECTED]>**20081025100732]
[Refactor install rules.
Trent W. Buck <[EMAIL PROTECTED]>**20081025100527
Importantly, this means that if you just do "make" it will either
build PDF or PS, but not both (with a preference for PDF).
The "installbin" target has been renamed to "install", since 1) that's
the convention, and 2) it was already installing non-binary stuff,
namely the bash completion and manpage.
Leverages concatenative rules (::) to reduce repetition.
]
[Refactor targets that prevent "include autoconf.mk" (and .depend).
Trent W. Buck <[EMAIL PROTECTED]>**20081025012208
As well as being clearer, this is now a good deal more liberal. For
example, it won't rebuild .depend during "make maintainer-clean".
]
[Generate TEXSOURCES programmatically.
Trent W. Buck <[EMAIL PROTECTED]>**20081025011935]
[Generate DARCS_FILES by blacklist, not whitelist.
Trent W. Buck <[EMAIL PROTECTED]>**20081025010803
This attempt is far from perfect, but at least it works.
]
[Use $@ and $* to shrink test_harness.
Trent W. Buck <[EMAIL PROTECTED]>**20081024085740
Note that I have also removed the use of @ to hide what make is doing.
It is better to use "make --silent" to hide such noise, because then I
can debug problems in the makefile by running *without* --silent,
rather than having to temporarily remove the @'s.
]
[Refactor test rules.
Trent W. Buck <[EMAIL PROTECTED]>**20081024034429
Now the target names correspond to the darcs switches, e.g. "make
test-darcs-2" instead of "make test-format2". There are some legacy
pointers so the old targets still work, but they probably put the
results in a different directory.
]
[Don't call GHC on autoconf.mk in .depend rule.
Trent W. Buck <[EMAIL PROTECTED]>**20081024031700
I don't know why, but $^ included autoconf.mk. I used $(filter) to
remove it, and put all the deps on one line while I was at it.
]
[Miscellaneous refactoring.
Trent W. Buck <[EMAIL PROTECTED]>**20081023050926]
[Replace procedural := with declarative =.
Trent W. Buck <[EMAIL PROTECTED]>**20081023034044
When you do "x = a b" in make, it doesn't get evaluated until you
actually attempt to refer to $x in a rule, because make is an expert
system. The reason := exists is because if you do
f = $(shell really-slow-command)
and then try to build a bunch of object files, $f will cause
really-slow-command to be run separately for each one. Since we're
just doing internal stuff like $(patsubst), we don't need := and using
it makes it harder to reason about the system, because it's no longer
declarative.
]
[Obviate SRC_DIRS altogether.
Trent W. Buck <[EMAIL PROTECTED]>**20081023030139
Note that find -delete would be better, but it is not standard:
http://www.opengroup.org/onlinepubs/009695399/utilities/find.html
]
[Ameliorative ChangeLog mode hint for Emacs.
Trent W. Buck <[EMAIL PROTECTED]>**20081104125751
This patch makes Emacs use outline (hierarchical) mode, and to
recognize "darcs (N)" as a first-level heading and " * foo" as a
third-level heading. Treating the latter correctly, as second-level
headings, is beyond my capabilities.
I'd prefer that this file be moved to "NEWS" and formatted as outline-
mode expects: each Nth-level heading starts with N stars and a space.
]
[quickCheck tests for QuickCheck 2.1
Florent Becker <[EMAIL PROTECTED]>**20081006135708]
[add yet another braindead file path to file path canonicalization test
Reinier Lamers <[EMAIL PROTECTED]>**20081103222552
Ignore-this: a2b2f6f8c47a14943dd99a6a1d0a5c7d
]
[Add bug script for issue1196
Reinier Lamers <[EMAIL PROTECTED]>**20081103222106
Ignore-this: a91333382a944602881b388da4606eca
]
[Fix "make bugs" target in makefile
Reinier Lamers <[EMAIL PROTECTED]>**20081103221941
Ignore-this: 541567455acb0308bbbcf8eb4fe4c83b
]
[Try a bit harder to hack darcs pathname canonicalization in tests
Reinier Lamers <[EMAIL PROTECTED]>**20081103211112
Ignore-this: 3b419ed6b5c3b4d8529ca045d8c63548
]
[Typo: install-pdf was trying to install *.ps.
Trent W. Buck <[EMAIL PROTECTED]>**20081025122922]
[Typo.
Trent W. Buck <[EMAIL PROTECTED]>**20081025083214]
[Add conventional install-ps/pdf/html targets.
Trent W. Buck <[EMAIL PROTECTED]>**20081024085052
See info page (make)Standard Targets.
]
[Use new "ps", "pdf" and "html" targets.
Trent W. Buck <[EMAIL PROTECTED]>**20081024084215]
[Clean hspwd.
Trent W. Buck <[EMAIL PROTECTED]>**20081024081050]
[Colour test output in Emacs' M-x compile.
Trent W. Buck <[EMAIL PROTECTED]>**20081024055755
This change means doing M-x compile RET make test RET in an ordinary
Emacs will highlight failed tests in red, and working tests in green.
This makes it easier to spot problems.
The down side is that yes/no is less clear than passed/failed.
]
[Reduce loquacity of haddock targets.
Trent W. Buck <[EMAIL PROTECTED]>**20081023072048
I think that if someone runs "make api-doc", it's not useful to
immediately print
echo "Generating html"
Generating html
Therefore I'm removing these lines.
]
[Fix some predicates I accidentally reversed.
Trent W. Buck <[EMAIL PROTECTED]>**20081023072013]
[release/debian is long gone.
Trent W. Buck <[EMAIL PROTECTED]>**20081023071427]
[Make it obvious why deps are being filtered.
Trent W. Buck <[EMAIL PROTECTED]>**20081023070847]
[Leverage gmake's order-only dependencies.
Trent W. Buck <[EMAIL PROTECTED]>**20081023051023]
[-fregs-graph seems to be a problem on both ghc 6.6 and 6.10
Jason Dagit <[EMAIL PROTECTED]>**20081028032741
This flag doesn't seem to cause a problem on 6.8, but having
does seem to cause a problem for 6.6 and 6.10.
]
[Resolve conflict between make darcs_p and make continuous
Eric Kow <[EMAIL PROTECTED]>**20081102122954
Ignore-this: 385fc4a7bd4b617f1c073f97c860c6ad
]
[restore -auto-all to profiling options
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081026144023]
[avoid .depend doubling in size on every make
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081026141924
Ignore-this: e106a7ba53738279ebb8293eeea16679
]
[Also clean intermediate profiling files.
Eric Kow <[EMAIL PROTECTED]>**20081026145926]
[Do not use -threaded when building darcs_p
Eric Kow <[EMAIL PROTECTED]>**20081026145415]
[Clean up how darcs_p is built
Eric Kow <[EMAIL PROTECTED]>**20081026145406
Treat GHCFLAGS_P as an alternative to GHCFLAGS, not an addition.
]
[Rename DARCS_OBJS_P and GHCFLAGS_P
Eric Kow <[EMAIL PROTECTED]>**20081026145619
from DARCS_P_OBJS and GHC_PROF_FLAGS
]
[Allow the profiling and non-profiling versions of darcs to co-exist
Eric Kow <[EMAIL PROTECTED]>**20081026135910
by teaching the Makefile about the suffixes .p_hi and .p_o.
]
[Add -fregs-graph to build instructions for SHA1.o
Eric Kow <[EMAIL PROTECTED]>**20081026133031
This helps us avoid a GHC error when building the profiling version of darcs,
namely: RegAllocLinear.getStackSlotFor: out of stack slots, try -fregs-graph
]
[replace a hoogle workaround with a comment, we now index names beginning with _
Simon Michael <[EMAIL PROTECTED]>**20081103165516
Ignore-this: 537874d6183556322091ff063ba1015b
]
[Make haddock aware of CommandLine module comment.
Trent W. Buck <[EMAIL PROTECTED]>**20081102011801]
[Refactor QuickCheck 2 test.
Trent W. Buck <[EMAIL PROTECTED]>**20081103101155
This makes the output resemble autoconf, so Emacs colours it by default.
It also means the user gets information before the test starts.
Lastly, it redirects the stderr of grep, as GNU grep's manpage recommends.
]
[Use cute short form of $(dir) and $(notdir).
Trent W. Buck <[EMAIL PROTECTED]>**20081025113759]
[Refactor dependency declaration for helper utils.
Trent W. Buck <[EMAIL PROTECTED]>**20081025011633
The .hs/.lhs deps that "disappear" are still in autoconf.mk.in.
]
[Turn descriptive commands into comments.
Trent W. Buck <[EMAIL PROTECTED]>**20081024032405
I don't think there's any point in printing "I'm deleting information
you can't recover" immediately before doing so, without offering an
abort step. Therefore, that message can just be an ordinary comment
in the makefile.
]
[Quieten removal of "Main" intermediaries.
Trent W. Buck <[EMAIL PROTECTED]>**20081023093107
This matches the quietness in the "darcs" target in GNUmakefile.
]
[Add conventional "pdf", "ps" and "html" targets.
Trent W. Buck <[EMAIL PROTECTED]>**20081023070550
See info page (make)Standard Targets.
]
[Don't override MAKEFLAGS's -j.
Trent W. Buck <[EMAIL PROTECTED]>**20081023065134
Make does hairy things within $MAKEFLAGS (which is included in $MAKE)
to ensure that -j does the right thing in the presence of nested
makes. Overriding this with $(MAKE) -j4 is almost certainly naughty.
Instead, you should do "make -j4 disttest" or implicitly, with
"MAKEFLAGS=j4 darcs record --test".
]
[Use ANNOUNCE_GHC convention for darcs.
Trent W. Buck <[EMAIL PROTECTED]>**20081024085359]
[Conventionalize make rule for hspwd.
Trent W. Buck <[EMAIL PROTECTED]>**20081024033900]
[Reduce disttest noise for teetotalers.
Trent W. Buck <[EMAIL PROTECTED]>**20081103094530
Without wine installed, "make disttest" was printing nine copies of:
/bin/sh: wine: not found
test: 1: =: argument expected
This DOES NOT fix the case where wine is installed, but GHC is not
available from wine:
wine runghc Setup.hs configure
wine: could not load L"C:\\windows\\system32\\runghc.exe": Module not found
make: *** [disttest] Error 126
]
[resolve conflict in makefile.
David Roundy <[EMAIL PROTECTED]>**20081103002009
Ignore-this: 3677a2bad189f858b1ac06e56b9e4c2f
]
[fixup SRC_DIRS
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081029190715]
[a slight simplification
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081028185358]
[clarify SlurpDirectory interface
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081028072911]
[cleanup some patterns
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081028065424]
[simplify slurp_has_anycase
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081026200442]
[another obvious use of the SlurpyMap
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081026192715]
[bug fix
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081026185518]
[make use of the SlurpyDir Map in the obvious places
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081026153749]
[dumb changeover of SlurpDir contents from [] to Map
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081026135906]
[refactor Slurpy to common up name component between File/Dir
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081026123722]
[Remove unpleasant sequencing operators (;) from haddock targets.
Trent W. Buck <[EMAIL PROTECTED]>**20081023061830
Make is will abort a run when any command fails. Using ;\\\n to join
separate lines means make can't detect if the first line fails. Also,
continuation lines are ugly.
When disabling failure propagation is intentional and desired, you can
achieve this explicitly by starting the command with a hyphen (-).
]
[Remove obsolete "deb" target.
Trent W. Buck <[EMAIL PROTECTED]>**20081023060745
I maintain the Debian darcs package, and I don't use this target.
I doubt anyone else has a use for it.
]
[Explain ghcflags_fancy.
Trent W. Buck <[EMAIL PROTECTED]>**20081023053956]
[Tweak C_OBJS declaration.
Trent W. Buck <[EMAIL PROTECTED]>**20081023033409]
[DARCS_FILES_DEPS is never bound, so don't evaluate it.
Trent W. Buck <[EMAIL PROTECTED]>**20081023030902]
[Generate SRC_DIRS programmatically.
Trent W. Buck <[EMAIL PROTECTED]>**20081023024212
The -name sys -prune -o ... -print part is a hack to skip the
src/win32/sys, which is probably safe to include in the list, but I
didn't want to take any chances.
]
[Typo: inadequate quotation in configure.ac.
Trent W. Buck <[EMAIL PROTECTED]>**20081101072848]
[ByteStringUtils: simply re-export BS functions for GHC > 6.6
Spencer Janssen <[EMAIL PROTECTED]>**20081028042219]
[cleaner implementation of linesPS test
Don Stewart <[EMAIL PROTECTED]>**20081026232500
Ignore-this: 6e3af59e5a5a3bdc4a6a62502056955a
]
[remove dead code
Don Stewart <[EMAIL PROTECTED]>**20081026231432
Ignore-this: 5a4a4b4cdcf0309214a93a88f4543421
]
[pack the small string, rather than unpack the bytestring
Don Stewart <[EMAIL PROTECTED]>**20081026194321
Ignore-this: eff62569f383215d2be31a7810ed187c
]
[remove quadratic blowups from mapPrimFL
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081029190730]
[resolve another replace conflict.
David Roundy <[EMAIL PROTECTED]>**20081102122813
Ignore-this: ee690c9cde6a07b1c15441fe90c03eeb
]
[use fmap in unit.lhs
Jason Dagit <[EMAIL PROTECTED]>**20081028064753
Ignore-this: af4cbe231e58d9b9e4ad332b30542a68
]
[use fmap in Patch.Apply
Jason Dagit <[EMAIL PROTECTED]>**20081028064147
Ignore-this: b58bdab550fcc5acc75e2ef3a53ed490
]
[use fmap in Match
Jason Dagit <[EMAIL PROTECTED]>**20081028060342
Ignore-this: 6b81e2f9cf92d8dad5186709b11d5750
]
[use fmap in Lock
Jason Dagit <[EMAIL PROTECTED]>**20081028060232
Ignore-this: faa5607b5a1d1b741ddebec3c0836907
]
[use fmap in External
Jason Dagit <[EMAIL PROTECTED]>**20081028060146
Ignore-this: f22668532d19292d4b45a7dc62f33134
]
[use fmap in Diff
Jason Dagit <[EMAIL PROTECTED]>**20081028060047
Ignore-this: f99385acad67e2b39d3d6b0c78faae1a
]
[use fmap in Commands.Send
Jason Dagit <[EMAIL PROTECTED]>**20081028055751
Ignore-this: bbf45d660eeed9f295d58f151464ce8a
]
[use fmap in Commands.Annotate
Jason Dagit <[EMAIL PROTECTED]>**20081028055323
Ignore-this: 8493690ea502127655a4cde85296acef
]
[use fmap in ByteStringUtils
Jason Dagit <[EMAIL PROTECTED]>**20081028054836
Ignore-this: 900d79b15507324b793c694c063a2e19
]
[add test of lazy get of lazy get.
David Roundy <[EMAIL PROTECTED]>**20081102121358
Ignore-this: e10b727babff3ef33ddbc7bd9816b3f9
]
[simplify Setup.hs a bit.
David Roundy <[EMAIL PROTECTED]>**20081102121344
Ignore-this: abd70cfa96a253f61ef9de57ba5b39e4
]
[compensate for bugfix in franchise in defineAs.
David Roundy <[EMAIL PROTECTED]>**20081102022049
Ignore-this: fc5be27e41e8b1cc4d21eec2a47884d2
]
[rewrite partitionFL and partitionRL to reduce the number of commutes they do
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081028222841
Ignore-this: e1861f289d56911b595653ae2f3891bf
This patch avoids a quadratic blowup when most/all patches fail the predicate
- previously they would all be commuted past each other. Now we accumulate them
until a patch that passes the predicate comes along, and then only commute as
necessary.
]
[don't link into the manual, since this is fragile.
David Roundy <[EMAIL PROTECTED]>**20081101135932
Ignore-this: 4d1f7f6ddaa3b9f215e254faf76b59ae
The trouble is that these sections can change pretty easily, and I'd rather
not have to update the index.html.in when this happens.
]
[improve front page of http://darcs.net
Eric P. Mangold <[EMAIL PROTECTED]>**20081030014049
I was a little confused by the wording on the darcs.net front-page.
Where it says "Originally developed by David Roundy" that made me
think that Mr. Roundy might not be involved in development anymore.
The kind folks on IRC set me straight, however :)
So I improved the wording in a couple places and added a section that
says a few things about the current state of the development
community.
]
[revert hashing change that ignores all but last 20 bytes of each line.
David Roundy <[EMAIL PROTECTED]>**20081031170230
Ignore-this: f97249571125d049bed9f3ae1d0a10a0
]
[resolve conflicts
David Roundy <[EMAIL PROTECTED]>**20081030182815
Ignore-this: f874ea6f34ddc5a745504b4ba988840d
]
[Unused import police
Eric Kow <[EMAIL PROTECTED]>**20081026080744]
[fixup ByteString compatibility for sake of ghc6.6
Jason Dagit <[EMAIL PROTECTED]>**20081028033305]
[clean up module imports after ByteString changes
Jason Dagit <[EMAIL PROTECTED]>**20081027001651]
[small merges
Don Stewart <[EMAIL PROTECTED]>**20081027000055
Ignore-this: 4c5dc100a17c5cbad4b4d24b71877cc1
]
[Remove all references to FastPackedString the module. Gone
Don Stewart <[EMAIL PROTECTED]>**20081026235917
Ignore-this: 2dd5679d9b33bed79c180a75fcd8c7a0
]
[remove last references to the PackedString type
Don Stewart <[EMAIL PROTECTED]>**20081026235151
Ignore-this: fe2c138c24305f85888d62a65b0c7c8
]
[clean up module imports after ByteString changes
Jason Dagit <[EMAIL PROTECTED]>**20081026234541]
[remove dead code
Don Stewart <[EMAIL PROTECTED]>**20081026232258
Ignore-this: 56cc675677fad6a10a77dc53b2f4f44f
]
[remove all references to unsafeWithCStringLenPS
Don Stewart <[EMAIL PROTECTED]>**20081026232045
Ignore-this: 1819ebbbcbf1d248c7e1715b5125ba97
]
[remove all references to mallocForeignPtr
Don Stewart <[EMAIL PROTECTED]>**20081026231851
Ignore-this: 59fa33be88801523d5e47c5eef85e973
]
[remove all references to createPS
Don Stewart <[EMAIL PROTECTED]>**20081026231230
Ignore-this: 619c8813cded454c829647ee89e37e4e
]
[and in tests
Don Stewart <[EMAIL PROTECTED]>**20081026231013
Ignore-this: 67fd51ccf6a8f0d3517788a115d87428
]
[remove all traces of packString
Don Stewart <[EMAIL PROTECTED]>**20081026230403
Ignore-this: 7ee645d5f5bddbd0265411e7868ca0f5
]
[remove all references to breakOnPS
Don Stewart <[EMAIL PROTECTED]>**20081026223727
Ignore-this: 60f6808d17ab581316bbe2bf9a0f8de2
]
[remove all references to spanEndPS
Don Stewart <[EMAIL PROTECTED]>**20081026223054
Ignore-this: 9cea6233b902f5a4652dae9e9759895b
]
[remove all references to indexPSW (only ever used as 'head')
Don Stewart <[EMAIL PROTECTED]>**20081026222913
Ignore-this: 7a25b911d1b320eb7ec3396eb1fff75d
]
[remove all references to generatePS
Don Stewart <[EMAIL PROTECTED]>**20081026222613
Ignore-this: 3673c57fa1eff4e1cf798c59fc967229
]
[clean up imports in other modules after ByteString refactorings
Jason Dagit <[EMAIL PROTECTED]>**20081026201508]
[Remove all references to dropWhilePS, clean up silly_lex while I'm here
Don Stewart <[EMAIL PROTECTED]>**20081026195652
Ignore-this: 29abf7de4539ae4957b70283df4dcf23
]
[pure haskell implementation of breakSpace, from Data.ByteString
Don Stewart <[EMAIL PROTECTED]>**20081026193729
Ignore-this: cbedb39a15ad4626f2561aa22f73a370
]
[remove fpstring.c:first_nonwhite, in favor of pure haskell implementation
Don Stewart <[EMAIL PROTECTED]>**20081026192211
Ignore-this: 7780e5f310a5785ffa3df332ec68972a
fpstring.c defined first_nonwhite, also provided via
Data.ByteString.Char8, however darcs uses a restricted definition of
ISSPACE, so we just port that over.
]
[remove all references to dropPS
Don Stewart <[EMAIL PROTECTED]>**20081026183226
Ignore-this: c75ac479bf0a9c2b37e5e5d511950940
]
[remove all references to concatPS
Don Stewart <[EMAIL PROTECTED]>**20081026182717
Ignore-this: 4b40da286f924625c4a2f6d71df1d3f6
]
[remove all references to findLastPS
Don Stewart <[EMAIL PROTECTED]>**20081026182232
Ignore-this: 7ff10d123f12bd12c76d5eff857367f0
]
[remove all references to breakPS
Don Stewart <[EMAIL PROTECTED]>**20081026182122
Ignore-this: 7e878cd0c3066b2a51a7f7df11f2c498
]
[remove all references to findPS
Don Stewart <[EMAIL PROTECTED]>**20081026181842
Ignore-this: 6ac31cb52cc1d63f4339177b21b853bc
]
[remove all references to packWords
Don Stewart <[EMAIL PROTECTED]>**20081026181624
Ignore-this: 91cff1fa32b422143d3dac87e5560329
]
[remove all references to takePS
Don Stewart <[EMAIL PROTECTED]>**20081026181041
Ignore-this: 122b854846d68e8659c8b6ab3b3ce3e2
]
[Remove appendPS, dead code
Don Stewart <[EMAIL PROTECTED]>**20081026180523
Ignore-this: 174c217104948ac658bac1e14b72b803
]
[remove all references to initPS
Don Stewart <[EMAIL PROTECTED]>**20081026180435
Ignore-this: 465e6980cd79e5d920f418ac471256b6
]
[remove all references to tailPS
Don Stewart <[EMAIL PROTECTED]>**20081026175536
Ignore-this: 845990c011fb3236826d62a45e0d96bc
]
[remove all references to nilPS
Don Stewart <[EMAIL PROTECTED]>**20081026174711
Ignore-this: 9a9261c1cef9028614734f4f363e33f5
]
[remove writeFilePS usage from HTTP.hs
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081026102421]
[Remove all references to unpackPS
Don Stewart <[EMAIL PROTECTED]>**20081026025309
Ignore-this: 839f30a7611668a1f158305f84f84751
]
[optimise use of unpack in Format.lhs
Don Stewart <[EMAIL PROTECTED]>**20081026022702
Ignore-this: ac72de83c3d453bab443089e85d2cf9a
]
[Optimize inefficiency when unpacking string for tok replace
Don Stewart <[EMAIL PROTECTED]>**20081026022129
Ignore-this: 26ede7c95f78e5b6c6b19c5e1c01127b
]
[Optimize hunk handling not to needlessly unpack bytestrings
Don Stewart <[EMAIL PROTECTED]>**20081026021727
Ignore-this: 93866b5b7a2d0b0dc7b98a1fbfd2b58f
]
[Don't unpack the same bytestring twice in two lines
Don Stewart <[EMAIL PROTECTED]>**20081026021141
Ignore-this: 7e673b449491eb467a21446048c17f50
]
[Optimize ignore_junk to not unpack the bytestring
Don Stewart <[EMAIL PROTECTED]>**20081026020635
Ignore-this: 3ab0d287de52b89434650f4a53bc0719
]
[remove nullPS from Darcs.Patch.Test
Jason Dagit <[EMAIL PROTECTED]>**20081026020430]
[Remove all references to nullPS
Don Stewart <[EMAIL PROTECTED]>**20081026015325
Ignore-this: 4ecc1ab4ca8f16a15090faaeb2cc063b
]
[remove all references to headPS
Don Stewart <[EMAIL PROTECTED]>**20081026013626
Ignore-this: d0e026a45ea9a16ff4f7301755caa9f4
]
[make BC.last depend on GADT_WITNESSES in Diff.lhs
Jason Dagit <[EMAIL PROTECTED]>**20081026013303]
[remove all references to splitAtPS
Don Stewart <[EMAIL PROTECTED]>**20081026012749
Ignore-this: f86b7f5fab8da6af5f6539510f068627
]
[More explict import lists
Don Stewart <[EMAIL PROTECTED]>**20081026012036
Ignore-this: a47ccb6c58a2a1d9c80974cfa832b05f
]
[explicit import lists
Don Stewart <[EMAIL PROTECTED]>**20081026011834
Ignore-this: de2b0cb8b1c3a7f102cb39a3c2822f2c
]
[remove all referenes to lengthPS
Don Stewart <[EMAIL PROTECTED]>**20081026011551
Ignore-this: 8c027d1510415cc3e6840162bce88d85
]
[replace reimplementation of c2w with bytestring's c2w
Don Stewart <[EMAIL PROTECTED]>**20081026005846
Ignore-this: 7be4c2d3e34b5ad1a4d1f89eedd79c73
]
[remove references to indexPS
Don Stewart <[EMAIL PROTECTED]>**20081026005455
Ignore-this: 868c3fa12869acf0ea3b7ddcd4504e16
]
[remove references to lastPS
Don Stewart <[EMAIL PROTECTED]>**20081026004952
Ignore-this: d374d4f54aedc9d9dcd8928793658c11
]
[remove references anyPS
Don Stewart <[EMAIL PROTECTED]>**20081026004428
Ignore-this: 41ae735dfca929b453d589d2e0494791
]
[remove references to hGetPS
Don Stewart <[EMAIL PROTECTED]>**20081026004032
Ignore-this: beab20131ee0453a7b8b44e3bf7391a3
]
[remove references to hPutPS
Don Stewart <[EMAIL PROTECTED]>**20081026003558
Ignore-this: 4c56823bf1cce0da3ce0f9b27bc2058
]
[Remove all references to hGetContentsPS
Don Stewart <[EMAIL PROTECTED]>**20081026002401
Ignore-this: d97a8ad95f0bf3de561b7ad081c42a10
]
[remove references to readFilePS
Don Stewart <[EMAIL PROTECTED]>**20081026001942
Ignore-this: c45ef1b82c5ba8243269b07e3b59ec49
]
[Remove references to writeFilePS
Don Stewart <[EMAIL PROTECTED]>**20081026000739
Ignore-this: de68ac72bd06f21d0f8634490c95cd71
]
[Remove splitPS in favor of its definition
Don Stewart <[EMAIL PROTECTED]>**20081025235851
Ignore-this: def77f09fee27b7224d9935ab9dcb6d0
]
[Remove OldFastPackedString entirely
Don Stewart <[EMAIL PROTECTED]>**20081025234228
Ignore-this: aa5fdf008176143575de7a966fb43874
]
[just hash the last 20 characters in LCS
Ganesh Sittampalam <[EMAIL PROTECTED]>**20081025122331]
[TAG unstable before bytestring patches.
David Roundy <[EMAIL PROTECTED]>**20081030175727
Ignore-this: 8af46543d274b193a6904883c9608559
]
Patch bundle hash:
65da81925084814facfe5b90cf90cc78cdf839bd
_______________________________________________
darcs-users mailing list
[email protected]
http://lists.osuosl.org/mailman/listinfo/darcs-users