Petr RoÄkai <[email protected]> added the comment: Hi again,
just amended out a minor fluke with sanitisation of email addresses... (I was generating double opening <)... Yours, Petr. 2 patches for repository http://darcs.net/: Sat Aug 7 15:08:44 CEST 2010 Petr Rockai <[email protected]> * Add --import and --export to available flags. Sat Aug 7 15:25:32 CEST 2010 Petr Rockai <[email protected]> * Implement convert --export to generate a git fast-import stream. __________________________________ Darcs bug tracker <[email protected]> <http://bugs.darcs.net/patch332> __________________________________
New patches: [Add --import and --export to available flags. Petr Rockai <[email protected]>**20100807130844 Ignore-this: 5f3f00ad6da4483c62052b6e5a3031c7 ] hunk ./src/Darcs/Arguments.lhs 89 networkOptions, noCache, allowUnrelatedRepos, checkOrRepair, justThisRepo, optimizePristine, - optimizeHTTP, getOutput, makeScriptsExecutable + optimizeHTTP, getOutput, makeScriptsExecutable, + optImport, optExport ) where import System.Console.GetOpt import System.Directory ( doesDirectoryExist ) hunk ./src/Darcs/Arguments.lhs 321 getContent JustThisRepo = NoContent getContent OptimizePristine = NoContent getContent OptimizeHTTP = NoContent +getContent Import = NoContent +getContent Export = NoContent getContentString :: DarcsFlag -> Maybe String getContentString f = hunk ./src/Darcs/Arguments.lhs 1814 makeScriptsExecutable :: Patchy p => [DarcsFlag] -> p C(x y) -> IO () makeScriptsExecutable opts p = when (SetScriptsExecutable `elem` opts) $ setScriptsExecutablePatches p + +optImport = DarcsSingleOption $ + DarcsNoArgOption [] ["import"] Import + "Import from a fast-export format" +optExport = DarcsSingleOption $ + DarcsNoArgOption [] ["export"] Export + "Export a repository to the fast-export format" \end{code} hunk ./src/Darcs/Flags.hs 107 | NoCache | AllowUnrelatedRepos | Check | Repair | JustThisRepo + | Export | Import | NullFlag deriving ( Eq, Show ) [Implement convert --export to generate a git fast-import stream. Petr Rockai <[email protected]>**20100807132532 Ignore-this: 9885ec737e33c940184f42e1cb641a0a ] hunk ./src/Darcs/Commands/Convert.lhs 28 module Darcs.Commands.Convert ( convert ) where +import Prelude hiding ( readFile ) import System.Directory ( setCurrentDirectory, doesDirectoryExist, doesFileExist, createDirectory ) import Workaround ( getCurrentDirectory ) hunk ./src/Darcs/Commands/Convert.lhs 32 -import Control.Monad ( when ) +import Control.Monad ( when, forM_ ) +import Control.Monad.Trans ( liftIO ) +import Control.Monad.State.Strict( gets ) +import Control.Exception( finally ) import GHC.Base ( unsafeCoerce# ) hunk ./src/Darcs/Commands/Convert.lhs 37 -import Data.Maybe ( catMaybes ) +import Data.Maybe ( catMaybes, fromJust ) import qualified Data.ByteString as B hunk ./src/Darcs/Commands/Convert.lhs 39 +import qualified Data.ByteString.Lazy.Char8 as BL import Darcs.Hopefully ( PatchInfoAnd, n2pia, info, hopefully ) import Darcs.Commands ( DarcsCommand(..), nodefaults, putInfo, putVerbose ) hunk ./src/Darcs/Commands/Convert.lhs 46 import Darcs.Arguments ( DarcsFlag ( AllowConflicts, NewRepo, SetScriptsExecutable, UseFormat2 - , NoUpdateWorking + , NoUpdateWorking, WorkRepoDir, Import, Export ) , reponame , setScriptsExecutableOption hunk ./src/Darcs/Commands/Convert.lhs 50 - , networkOptions + , networkOptions, optExport ) import Darcs.Repository ( Repository, withRepoLock, ($-), withRepositoryDirectory, readRepo, createRepository, invalidateIndex, hunk ./src/Darcs/Commands/Convert.lhs 58 tentativelyMergePatches, patchSetToPatches, createPristineDirectoryTree, revertRepositoryChanges, finalizeRepositoryChanges, - applyToWorking, setScriptsExecutable ) + applyToWorking, setScriptsExecutable, withRepository ) +import Darcs.Repository.Cache ( HashedDir( HashedPristineDir ) ) +import Darcs.Repository.HashedRepo ( readHashedPristineRoot ) +import Darcs.Repository.HashedIO ( cleanHashdir ) +import Darcs.Repository.InternalTypes ( extractCache ) import Darcs.Global ( darcsdir ) import Darcs.Patch ( RealPatch, Patch, Named, showPatch, patch2patchinfo, fromPrims, infopatch, modernizePatch, hunk ./src/Darcs/Commands/Convert.lhs 66 - adddeps, getdeps, effect, flattenFL, isMerger, patchcontents ) + adddeps, getdeps, effect, flattenFL, isMerger, patchcontents, + listTouchedFiles, apply, RepoPatch ) import Darcs.Witnesses.Ordered ( FL(..), RL(..), EqCheck(..), (=/\=), bunchFL, mapFL, mapFL_FL, hunk ./src/Darcs/Commands/Convert.lhs 69 - concatFL, mapRL ) -import Darcs.Patch.Info ( piRename, piTag, isTag, PatchInfo ) + concatFL, mapRL, lengthFL ) +import Darcs.Patch.Info ( piRename, piTag, isTag, PatchInfo, piAuthor, piName, piLog ) import Darcs.Patch.Commute ( publicUnravel ) import Darcs.Patch.Real ( mergeUnravelled ) hunk ./src/Darcs/Commands/Convert.lhs 73 -import Darcs.Patch.Set ( PatchSet(..), Tagged(..), newset2RL ) +import Darcs.Patch.Set ( PatchSet(..), Tagged(..), newset2RL, newset2FL ) import Darcs.RepoPath ( ioAbsoluteOrRemote, toPath ) import Darcs.Repository.Format(identifyRepoFormat, formatHas, RepoProperty(Darcs2)) import Darcs.Repository.Motd ( showMotd ) hunk ./src/Darcs/Commands/Convert.lhs 77 -import Darcs.Utils ( clarifyErrors, askUser, catchall ) +import Darcs.Utils ( clarifyErrors, askUser, catchall, withCurrentDirectory ) import Darcs.ProgressPatches ( progressFL ) import Darcs.Witnesses.Sealed ( FlippedSeal(..), Sealed(..) ) import Printer ( text, ($$) ) hunk ./src/Darcs/Commands/Convert.lhs 86 import Darcs.External import System.FilePath.Posix +import Storage.Hashed.Monad hiding ( createDirectory, exists ) +import Storage.Hashed.Darcs +import Storage.Hashed.Tree( emptyTree, listImmediate, findTree ) +import Storage.Hashed.AnchoredPath( floatPath, AnchoredPath, anchorPath, appendPath ) + #include "gadts.h" convertDescription :: String hunk ./src/Darcs/Commands/Convert.lhs 145 commandGetArgPossibilities = return [], commandArgdefaults = nodefaults, commandAdvancedOptions = networkOptions, - commandBasicOptions = [reponame,setScriptsExecutableOption]} + commandBasicOptions = [reponame,setScriptsExecutableOption,optExport]} convertCmd :: [DarcsFlag] -> [String] -> IO () hunk ./src/Darcs/Commands/Convert.lhs 148 -convertCmd opts [inrepodir, outname] = convertCmd (NewRepo outname:opts) [inrepodir] -convertCmd orig_opts [inrepodir] = do +convertCmd opts repos = case opts of + _ | Export `elem` opts -> fastExport opts repos + | Import `elem` opts -> fastImport opts repos + | otherwise -> toDarcs2 opts repos + +fastImport :: [DarcsFlag] -> [String] -> IO () +fastImport _ _ = fail "Not supported yet." + +fastExport :: [DarcsFlag] -> [String] -> IO () +fastExport opts [repodir] = fastExport (WorkRepoDir repodir:opts) [] +fastExport _ (_:_) = fail "Only one repository can be exported at a time." +fastExport opts [] = withCurrentDirectory repodir $ withRepository opts $- \repo -> do + putStrLn "progress (reading repository)" + patches <- newset2FL `fmap` readRepo repo + let total = show (lengthFL patches) + dumpfiles :: [AnchoredPath] -> TreeIO () + dumpfiles files = forM_ files $ \file -> do + isfile <- fileExists file + isdir <- directoryExists file + when isfile $ do bits <- readFile file + liftIO $ putStrLn $ "M 100644 inline " ++ anchorPath "" file + liftIO $ putStrLn $ "data " ++ show (BL.length bits) + liftIO $ putStrLn (BL.unpack bits) + when isdir $ do tt <- gets tree -- ick + let subs = [ file `appendPath` n | (n, _) <- + listImmediate $ fromJust $ findTree tt file ] + dumpfiles subs + when (not isfile && not isdir) $ liftIO $ putStrLn $ "D " ++ anchorPath "" file + wibbleAuthor a = case span (/='<') a of + (name, "") -> name ++ " <unknown>" + (name, rest) -> case span (/='>') $ tail rest of + (email, _) -> name ++ "<" ++ email ++ ">" + dump :: (RepoPatch p) => Int -> FL (PatchInfoAnd p) C(x y) -> TreeIO () + dump _ NilFL = liftIO $ putStrLn "progress (patches converted)" + dump n (p:>:ps) = do + apply p + let author = wibbleAuthor $ piAuthor $ info p + message = (piName $ info p) ++ case (unlines . piLog $ info p) of + "" -> "" + plog -> "\n" ++ plog + files = map floatPath $ listTouchedFiles p + liftIO $ putStr $ unlines + [ "progress " ++ show n ++ " / " ++ total ++ ": " ++ piName (info p) + , "commit refs/heads/master" -- ? + , "author " ++ author ++ " 12345 +0000" + , "committer " ++ author ++ " 12345 +0000" + , "data " ++ show (length message) + , message ] + dumpfiles files + dump (n + 1) ps + putStrLn "reset refs/heads/master" + hashedTreeIO (dump 0 patches) emptyTree "_darcs/pristine.hashed" + return () + `finally` do + putStrLn "progress (cleaning up)" + current <- readHashedPristineRoot repo + cleanHashdir (extractCache repo) HashedPristineDir $ catMaybes [current] + putStrLn "progress done" + return () + where repodir = head $ [ dir | WorkRepoDir dir <- opts ] ++ ["."] + +toDarcs2 :: [DarcsFlag] -> [String] -> IO () +toDarcs2 opts [inrepodir, outname] = toDarcs2 (NewRepo outname:opts) [inrepodir] +toDarcs2 orig_opts [inrepodir] = do typed_repodir <- ioAbsoluteOrRemote inrepodir let repodir = toPath typed_repodir hunk ./src/Darcs/Commands/Convert.lhs 309 "but recoverable state. You should be able to make the new", "repository consistent again by running darcs revert -a."] -convertCmd _ _ = fail "You must provide 'convert' with either one or two arguments." +toDarcs2 _ _ = fail "You must provide 'convert' with either one or two arguments." makeRepoName :: [DarcsFlag] -> FilePath -> IO String makeRepoName (NewRepo n:_) _ = Context: [switch homepage to two-column format ala xmonad.org Guillaume Hoffmann <[email protected]>**20100805134439 Ignore-this: 21fa11e338fd9064b526f96c2f5be12 ] [resolve issue1896: enable witnesses for library Ganesh Sittampalam <[email protected]>**20100721053731 Ignore-this: 5209e15b5d2c446eea5df2fe1fe700b5 ] [Undo an edit to the issue1829 test, since the original was clearer. Petr Rockai <[email protected]>**20100806131253 Ignore-this: 925c73124e2b3d17239ccb7c47578f19 ] [Add a test for issue1829 by Ganesh & Ian. Petr Rockai <[email protected]>**20100806125230 Ignore-this: 7e11a7b4b54f189e1864952ff048f0fb ] [Cut functions Darcs.Utils.putStrLnError and putDocLnError. Eric Kow <[email protected]>**20100718102621 Ignore-this: 92c29385add92fb7b875342842432b5a ] [Tidy Darcs.Utils exports. Eric Kow <[email protected]>**20100718101900 Ignore-this: 78740886b92947d941f0e3baa86ba3f2 ] [Remove a couple of redundant type variables from foralls. Petr Rockai <[email protected]>**20100806085630 Ignore-this: 552924bfd0cf15cd9c5922a88ae282f9 ] [Accept issue1290: darcs diff --index support. Eric Kow <[email protected]>**20100805124559 Ignore-this: 560bf7125a441de79f0939e5851b95ed ] [Resolve issue1892: Improve safety of makeBundle* and fix a couple of related bugs. Petr Rockai <[email protected]>**20100715093842 Ignore-this: 9eaa26edfdda09ac444f124130b9e74b ] [Export usageHelper Joachim Breitner <[email protected]>**20100803173150 Ignore-this: 763398f4ab6b99a59de7666940103daa usage is darcs-specific, while usageHelper is not. ipatch could use usageHelper. ] [Add pronoun to english module [email protected]**20100803131432 Ignore-this: 707096c1b8c9d0328524cb85ea76193e ] [Make Darcs.RunCommand independent of Darcs.Commands.Help Joachim Breitner <[email protected]>**20100803165917 Ignore-this: 744025a59cdd9ad52595b65d989a638a by passing commandControlList via main.hs. This allows re-use of Darcs.RunCommand by other binaries with a different set of commands. ] [Handle English nouns that end in y. [email protected]**20100724172717 Ignore-this: 49eed82e5949fc0d8e7d2775e9fd50c0 ] [Remove unused imports in Darcs.Commands.Changes Reinier Lamers <[email protected]>**20100802181249 Ignore-this: 87d2c72fc74e4442f146d896296fb0db ] [Fix missing type signature in Darcs.Arguments. Eric Kow <[email protected]>**20100726134237 Ignore-this: 8f69ae4defc489d4a4ec9c5734fa2376 ] [Fix warnings in Darcs.Repository.State. Eric Kow <[email protected]>**20100723134611 Ignore-this: 5a7c4a33c95ba3285721d0ade56adf1b ] [Fix warnings in Darcs.Repository.InternalTypes. Eric Kow <[email protected]>**20100723134556 Ignore-this: 66a361e0ff4b1a0c616fb11dafc6467c ] [Fix warnings in Darcs.Repository.HashedIO. Eric Kow <[email protected]>**20100723134533 Ignore-this: af2a60a5bf64d53240dc4498696c7a42 ] [Fix warnings in Darcs.Repository.DarcsRepo. Eric Kow <[email protected]>**20100723134515 Ignore-this: 66f45d925ab9a7bce4c6e69ded8803fe ] [Fix warnings in Darcs.Patch.Prim. Eric Kow <[email protected]>**20100723134501 Ignore-this: dfd3b36b4b07e6de3b558073ac6bbe27 ] [Fix redundant import warning in Darcs.Patch.Patchy. Eric Kow <[email protected]>**20100723134447 Ignore-this: 3fa7ffaf1b8098c4c0793c3ccc5ecb36 ] [Fix redundant imports in Darcs.Patch.Commute. Eric Kow <[email protected]>**20100723133540 Ignore-this: 1c6919da737a8fd265a5dde9e94bbf35 ] [Fix shadow warning in Darcs.Patch.Choices. Eric Kow <[email protected]>**20100723133357 Ignore-this: 88183e55fcac7c9fa2372f35decf643f ] [Fix redundant imports in Darcs.Patch.Apply. Eric Kow <[email protected]>**20100723133239 Ignore-this: dbf30f383e7a0684ca2b9cf9dcd50fb7 Likely due to setScriptsExecutable refactor. ] [Fix RemoteDarcs related imports warning in Darcs.Flags and Darcs.RemoteApply. Eric Kow <[email protected]>**20100723132408 Ignore-this: f944bbc547fa4f8e1a70c8c3539ce6bc ] [Fix deprecation warning on GHC.Handle in Exec module. Eric Kow <[email protected]>**20100723131847 Ignore-this: 12a57c2a78af7d2c6428ec544cd09f98 It looks like it was deprecated in GHC 6.12 along with the Unicode-oriented rewrite. ] [Re-enable packs and optimize --http. Petr Rockai <[email protected]>**20100804185357 Ignore-this: f86b0ea0c1008dbd173c7b8145be6803 ] [Minimize the number of packed inventories Alexey Levan <[email protected]>**20100802035445 Ignore-this: 1f3d28bece5b29d599ea97be9bba5424 ] [Use cache while getting a packed repository Alexey Levan <[email protected]>**20100802024914 Ignore-this: 33e44bdfce82d89fd243e7d628ce2c34 ] [Hardlink files while getting a packed repository Alexey Levan <[email protected]>**20100801050349 Ignore-this: 8e6aa73b3a0cc84812d44beaaea701dd ] [Haddock promptYorn. Eric Kow <[email protected]>**20100718092334 Ignore-this: 35ea778f5a5e44b8fb08a1b340b6b8a0 ] [Add header to issue1790 test and make it follow convention more. Eric Kow <[email protected]>**20100728142928 Ignore-this: 29e6d64c5f3089ff6b7e081da5f853a4 ] [Accept issue1790: darcs send --context foo Eric Kow <[email protected]>**20100728142602 Ignore-this: cd5d7f148d32ddbcea8d8cbb2282c2ea Submitted by Loup Vaillant. ] [Modernise System.Cmd import in Distribution.ShellHarness. Eric Kow <[email protected]>**20100725220631 Ignore-this: a785da33c6089635da687a9bfe957c2b ] [Disable optimize --http for Darcs 2.5 release. Eric Kow <[email protected]>**20100726111249 Ignore-this: 92b75e71ac3041eee76762bf8042b02c ] [Disable packs for darcs 2.5. Eric Kow <[email protected]>**20100724155438 Ignore-this: 3b9a6e7b3bede56651a5f6f1b728cfb5 The packs feature is not sufficiently stable for release. ] [Restore looking for version number in exact-version context dump. Eric Kow <[email protected]>**20100726114810 Ignore-this: e18459c582c12c2e77b630f096f66190 rolling back: Sun Jul 11 13:08:54 BST 2010 Reinier Lamers <[email protected]> * Don't look for version number in exact-version context dump Petr says it masks a bug in the release tarballs. ] [resolve issue1716: allow mail header lines of all whitespace in test Reinier Lamers <[email protected]>**20100722191846 Ignore-this: 24a12e1cf2631b5363636cf32cf5e8da Reading RFC822, it seems all-whitespace lines are allowed in the header section when you've got trailing space that doesn't fit on the line before. ] [rename readPatchIds to better describe what it does Jason Dagit <[email protected]>**20100723064832 Ignore-this: aa207726cbe8894aab41c17bd01ee6ca ] [move readPatchIds to Darcs.Patch.Info Jason Dagit <[email protected]>**20100723064511 Ignore-this: 53f620c0f5ffda0ffd82693c27a70235 ] [remove duplicate code, readPatchIds Jason Dagit <[email protected]>**20100723063526 Ignore-this: a1950afa8385b04aa9c03435e4c152cb ] [resolve issue1893: move fields of conditional builds within scope of condition Ganesh Sittampalam <[email protected]>**20100716192642 Ignore-this: 5eb1c376138534dd55190e06be701588 This helps to work around a bug/misfeature in Cabal where it collects up things like build-depends without looking at whether the thing they apply to is actually buildable ] [Restore set-scripts-executable in trackdown --bisect. Eric Kow <[email protected]>**20100717124222 Ignore-this: efa2e2bba8227542b5a63933f0748c9d Note: Petr Rockai originally submitted this work as an amendment to 'Remove [DarcsFlag] parameters from apply.', but I must have accidentally pushed the first version before he sent it. This patch has the same effect as his amendment. ] [Remove [DarcsFlag] parameters from apply. Petr Rockai <[email protected]>**20100715002249 Ignore-this: 707f8193561ce890dc6ed91d1001253b ] [Resolve issue1888: fix changes --context. Petr Rockai <[email protected]>**20100729185143 Ignore-this: eed1a926b468492198547c438a85e2c9 ] [Make the "error applying hunk" error a lot more readable (and useful). Petr Rockai <[email protected]>**20100727215711 Ignore-this: d748d2632528d8e95453cb8cab76cd67 ] [Slightly fix context generation in Setup. Petr Rockai <[email protected]>**20100722111410 Ignore-this: eb3b6637f24d62332c9452a3c4143f39 ] [Fix "head: empty list" bug in Darcs.Flags.RemoteDarcs. Petr Rockai <[email protected]>**20100715123140 Ignore-this: fa172627824eb3937cad63223026db9e ] [Fix up tests to refer to --name instead of --patch-name. Petr Rockai <[email protected]>**20100715102618 Ignore-this: 630cc96d79db0ee7af9c93fa3dbf5f15 ] [Resolve issue1883: rename --patch-name option to --name. Eric Kow <[email protected]>**20100715101608 Ignore-this: 85ab2f1e23f8b561b323a9dfb94baa55 This is usually used in darcs record in shorthand (-m) form. This rename is aimed at eliminating the confusion with the --patch matcher, which bites amend-record and rollback users. ] [Update link to Darcs repository browser. Eric Kow <[email protected]>**20100713174550 Ignore-this: 3546359aec588d1262d6335b033331d0 ] [Remove [DarcsFlag] usage from Darcs.Patch.Bundle. Petr Rockai <[email protected]>**20100715081908 Ignore-this: 62297671dea56fdc0a1cac42f79d6d29 ] [Use Compression more widely, suppressing further [DarcsFlag] uses. Petr Rockai <[email protected]>**20100715003449 Ignore-this: d582d3bc381e73a964127aa3b87d0ffb ] [Replace some [DarcsFlag] uses with newly introduced RemoteDarcs. Petr Rockai <[email protected]>**20100715003320 Ignore-this: d018b8c9b328228b9d283b7ad824eb15 ] [Remove --nolinks, since its scope and usefulness is very limited. Petr Rockai <[email protected]>**20100715000822 Ignore-this: 71427fcd09e59d5e4f443bcc4e5ca649 ] [Remove [DarcsFlag] argument from unrecordedChanges. Petr Rockai <[email protected]>**20100714155059 Ignore-this: 4ba064584b4846b0ca26f6e3199a955a ] [Fix haddock error. Eric Kow <[email protected]>**20100712145740 Ignore-this: 2e41b55e17020543744a06ef57cdc599 The main problem is that bug is a cpp macro, which gets expanded out. We just work around this for now. ] [Avoid a haddock parse error. Eric Kow <[email protected]>**20100712142926 Ignore-this: 97dc0a40b82f9360d374917e243e0490 ] [Fix conflict in Distribution.ShellHarness. Eric Kow <[email protected]>**20100712132814 Ignore-this: bfde365cf2d74b05d29ed457b5382f46 Was between extended test defaults and Control.OldException removal. ] [Make --no-cache an advanced option in all commands. Eric Kow <[email protected]>**20100701161428 Ignore-this: 99ea6f8e2235bfdab407a1af9fcfb5cc ] [get rid of join_patches Ganesh Sittampalam <[email protected]>**20100712165037 Ignore-this: f9a5ca3dcc690e3c1ed9f6778b07f542 ] [stop using join_patches in Darcs.Test.Unit Ganesh Sittampalam <[email protected]>**20100712165031 Ignore-this: 563bbbd15f9f51cdfc8063b9dd7f8b0b ] [move main unit testing code into module with proper name (not Main) Ganesh Sittampalam <[email protected]>**20100707180600 Ignore-this: 9c44b4ab083ba44afc9ecaf0752cd130 This is enable other things than the unit executable to import it ] [Fix test issue1865-get-context.sh Thorkil Naur <[email protected]>**20100711121938 Ignore-this: c68995d55efb6095ada7c24ce0909716 ] [remove redundant and accidentally checked in definition Ganesh Sittampalam <[email protected]>**20100709214141 Ignore-this: d8ad150be87b467f92721c8079158541 ] [Resolve issue1887: add a missing newline to --list-options output. Petr Rockai <[email protected]>**20100711193535 Ignore-this: 912b18e8f89be19d186332f5f98a8083 ] [remove dead code Ganesh Sittampalam <[email protected]>**20100708055640 Ignore-this: 86104cf3f14952869be820f66f156fbb ] [fix warning Ganesh Sittampalam <[email protected]>**20100707061818 Ignore-this: 4b9e468819689cfc768befa8eabe4a4f ] [standardize GHC options Ganesh Sittampalam <[email protected]>**20100707180210 Ignore-this: b088f0ece12b86980225d81b37d89251 ] [fix unused variable warning Ganesh Sittampalam <[email protected]>**20100707065338 Ignore-this: b2a8e05c985912a78dc71748361271b1 ] [fix name shadowing warning Ganesh Sittampalam <[email protected]>**20100707065303 Ignore-this: 79ab8367f22333f79f66e82d5f631dac ] [rename field names to avoid shadowing warnings Ganesh Sittampalam <[email protected]>**20100707062714 Ignore-this: 6be53f3ee1ef4915bdd722153b0675e0 ] [fix unused code warning Ganesh Sittampalam <[email protected]>**20100707062701 Ignore-this: 3475bca718b26e5056c3ad7448a346dc ] [fix shadowing warnings Ganesh Sittampalam <[email protected]>**20100707062324 Ignore-this: 45d7d142735754357e7b9c53eb2c25df ] [fix warning Ganesh Sittampalam <[email protected]>**20100707062320 Ignore-this: 33b1a5f0d5895f04257e4eb133addfc5 ] [fix warning Ganesh Sittampalam <[email protected]>**20100707062315 Ignore-this: ad3da11afad97816fcd832baf25c311f ] [remove dead code Ganesh Sittampalam <[email protected]>**20100707062309 Ignore-this: a3462879709597df56cf28d239b71eef ] [add comment about why we're using a deprecated option Ganesh Sittampalam <[email protected]>**20100707061805 Ignore-this: eb1ec29ce345f96689d39f8f9638987c ] [stop using Control.OldException in Setup.lhs + deps Ganesh Sittampalam <[email protected]>**20100707060932 Ignore-this: ab49b67e05941402304aed3a8b55f52f ] [Fix tests in light of recent default flag changes. Petr Rockai <[email protected]>**20100708195100 Ignore-this: b8764f2105ed6e7870f4853041b90f9e ] [Avoid adding noCache twice to parameter lists. Petr Rockai <[email protected]>**20100708195014 Ignore-this: 59cf4dc50edb4c08367cbc29f321e431 ] [Correctly handle conflicts arising from DarcsMutuallyExclusive options. Petr Rockai <[email protected]>**20100708194904 Ignore-this: b6607175899ad6f63044adae7442fd6d ] [Do not set default repo by default in push, pull, send, fetch. Eric Kow <[email protected]>**20100701160352 Ignore-this: 611fe6db2e2fe4d6ad70758d4dfb63de As discussed during the 2010-03 sprint and documented in http://wiki.darcs.net/DefaultSwitches ] [Express --{no-,}set-default as a mutually exclusive option. Eric Kow <[email protected]>**20100701160138 Ignore-this: 189522de144a9b9b81239f4a5ff545f0 ] [Make --edit-description the default. Eric Kow <[email protected]>**20100701155253 Ignore-this: ed99469237da51949d915a8dda13706e ] [Express --{no-,}edit-description as a mutually exclusive option. Eric Kow <[email protected]>**20100701155045 Ignore-this: 419cc3945f89953e33400172d51453e9 ] [Add a notion of mutually exclusive options with a default. Eric Kow <[email protected]>**20100701155041 Ignore-this: e3a29afebe21c9ec6ce355040260e8b ] [Fix missing type signature. Eric Kow <[email protected]>**20100701153511 Ignore-this: a0669588aca19f0c45326c1244e1c766 ] [General purpose function for setting defaults. Eric Kow <[email protected]>**20100701151816 Ignore-this: d76a09aa70eba9694d3649300ef7720d ] [Fix use of atomicOptions in Darcs.ArgumentDefaults. Eric Kow <[email protected]>**20100701144916 Ignore-this: 4fc1df15e34b5c63c47e4c12c4f5963 ] [Update optimizeHTTP for new two-layer DarcsOption. Eric Kow <[email protected]>**20100701142543 Ignore-this: d892c6787ba0aa93a0b36c1e7a79b756 ] [Refactor traversal of atomic options in DarcsOption. Eric Kow <[email protected]>**20100621003601 Ignore-this: 9425a65b80f075e684fd7edaf9b5b868 ] [Better use of Data.Maybe helpers in Darcs.Arguments. Eric Kow <[email protected]>**20100621002200 Ignore-this: 46feb16524e1d61495a7ead46cce1e55 ] [Flatten DarcsOption type. Eric Kow <[email protected]>**20100621001926 Ignore-this: 34a3e0c2a9e989f0f35774d742607c93 Distinguish between DarcsAtomicOptions and DarcsOption. ] [Rename optionFromDarcsoption to optionFromDarcsOption. Eric Kow <[email protected]>**20100621000207 Ignore-this: d1c5a5cb84264a404b9b07c9094f96aa ] [TAG 2.4.98.1 Reinier Lamers <[email protected]>**20100711120953 Ignore-this: 6955d46fb3e48bc5bb0f622e495eae1f ] Patch bundle hash: 5c5724f7a89d7b1584b6857ffb90fb6bd17fecb4
unnamed
Description: Binary data
_______________________________________________ darcs-users mailing list [email protected] http://lists.osuosl.org/mailman/listinfo/darcs-users
