Eric Kow <ko...@darcs.net> added the comment:

12 patches for repository http://darcs.net:

This is just the same bundle with the potentially problematic ptaches
cherry-picked out.

I actually have quite a few more of these cleanups in my working director, but
appear to be dithering on grouping them into patches.

Fri Jul 23 14:18:47 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix deprecation warning on GHC.Handle in Exec module.
  It looks like it was deprecated in GHC 6.12 along with the
  Unicode-oriented rewrite.

Fri Jul 23 14:24:08 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix RemoteDarcs related imports warning in Darcs.Flags and 
Darcs.RemoteApply.

Fri Jul 23 14:32:39 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix redundant imports in Darcs.Patch.Apply.
  Likely due to setScriptsExecutable refactor.

Fri Jul 23 14:33:57 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix shadow warning in Darcs.Patch.Choices.

Fri Jul 23 14:35:40 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix redundant imports in Darcs.Patch.Commute.

Fri Jul 23 14:44:47 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix redundant import warning in Darcs.Patch.Patchy.

Fri Jul 23 14:45:01 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix warnings in Darcs.Patch.Prim.

Fri Jul 23 14:45:15 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix warnings in Darcs.Repository.DarcsRepo.

Fri Jul 23 14:45:33 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix warnings in Darcs.Repository.HashedIO.

Fri Jul 23 14:45:56 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix warnings in Darcs.Repository.InternalTypes.

Fri Jul 23 14:46:11 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix warnings in Darcs.Repository.State.

Mon Jul 26 14:42:37 BST 2010  Eric Kow <ko...@darcs.net>
  * Fix missing type signature in Darcs.Arguments.


___________________________________________________________
This email has been scanned by MessageLabs' Email Security
System on behalf of the University of Brighton.
For more information see http://www.brighton.ac.uk/is/spam/
___________________________________________________________

__________________________________
Darcs bug tracker <b...@darcs.net>
<http://bugs.darcs.net/patch315>
__________________________________
New patches:

[Fix deprecation warning on GHC.Handle in Exec module.
Eric Kow <ko...@darcs.net>**20100723131847
 Ignore-this: 12a57c2a78af7d2c6428ec544cd09f98
 It looks like it was deprecated in GHC 6.12 along with the
 Unicode-oriented rewrite.
] hunk ./src/Exec.hs 45
 import System.Cmd ( system )
 import System.IO ( IOMode(..), openBinaryFile, stdout )
 import System.Process   ( runProcess, terminateProcess, waitForProcess )
+#if __GLASGOW_HASKELL__ >= 612
+import GHC.IO.Handle ( hDuplicate )
+#else
 import GHC.Handle ( hDuplicate )
hunk ./src/Exec.hs 49
-        -- urgh.  hDuplicate isn't available from a standard place.
+#endif
 import Control.Exception.Extensible ( bracketOnError, Exception(..), SomeException(..) )
 
 import Darcs.Global ( whenDebugMode )
[Fix RemoteDarcs related imports warning in Darcs.Flags and Darcs.RemoteApply.
Eric Kow <ko...@darcs.net>**20100723132408
 Ignore-this: f944bbc547fa4f8e1a70c8c3539ce6bc
] hunk ./src/Darcs/External.hs 53
 import System.FilePath.Posix ( (</>), takeDirectory, normalise )
 
 import Darcs.Flags ( DarcsFlag( SignAs, Sign, SignSSL,
-                                Verify, VerifySSL, RemoteDarcsOpt ), RemoteDarcs(..) )
+                                Verify, VerifySSL )
+                   , RemoteDarcs(..) )
 import Darcs.RepoPath ( AbsolutePath, toFilePath )
 import Darcs.Utils ( withCurrentDirectory, breakCommand, getViewer, ortryrunning, )
 import Progress ( withoutProgress, progressList, debugMessage )
hunk ./src/Darcs/RemoteApply.hs 8
 
 import System.Exit ( ExitCode )
 
-import Darcs.Flags ( DarcsFlag( ApplyAs, Debug ), RemoteDarcs(..), remoteDarcs )
+import Darcs.Flags ( DarcsFlag( ApplyAs, Debug ), remoteDarcs )
 import Darcs.Utils ( breakCommand )
 import Darcs.URL ( isUrl, isSsh )
 import Darcs.External
[Fix redundant imports in Darcs.Patch.Apply.
Eric Kow <ko...@darcs.net>**20100723133239
 Ignore-this: dbf30f383e7a0684ca2b9cf9dcd50fb7
 Likely due to setScriptsExecutable refactor.
] hunk ./src/Darcs/Patch/Apply.lhs 38
 
 import qualified Data.ByteString.Char8 as BC (split, break, pack, singleton)
 
-import qualified Data.ByteString       as B (ByteString, null, empty, concat, isPrefixOf)
+import qualified Data.ByteString       as B (ByteString, null, empty, concat)
 import ByteStringUtils ( linesPS, unlinesPS, breakAfterNthNewline, breakBeforeNthNewline, )
 
 import Darcs.Patch.FileName ( fn2ps, fn2fp, fp2fn,
[Fix shadow warning in Darcs.Patch.Choices.
Eric Kow <ko...@darcs.net>**20100723133357
 Ignore-this: 88183e55fcac7c9fa2372f35decf643f
] hunk ./src/Darcs/Patch/Choices.hs 264
                       ( FORALL(x y) TaggedPatch p C(x y) -> Bool)
                       -> PatchChoices p C(a b)
                       -> PatchChoices p C(a b)
-forceMatchingFirst pred (PCs f l) =
-  fmfLasts f NilRL l
+forceMatchingFirst pred (PCs fn l) =
+  fmfLasts fn NilRL l
     where
       fmfLasts :: FL (TaggedPatch p) C(a m)
                  -> RL (PatchChoice p) C(m n)
hunk ./src/Darcs/Patch/Choices.hs 359
   Patchy p => PatchChoices p C(x y) -> PatchChoices p C(x y)
 makeEverythingSooner (PCs f l) =
   case mes NilRL NilRL l
-       of (m :> l) ->
-            PCs (f +>+ m) l
+       of (m :> l') ->
+            PCs (f +>+ m) l'
     where
       mes :: FORALL(m1 m2 m3)
             RL (TaggedPatch p) C(m1 m2) ->
[Fix redundant imports in Darcs.Patch.Commute.
Eric Kow <ko...@darcs.net>**20100723133540
 Ignore-this: 1c6919da737a8fd265a5dde9e94bbf35
] hunk ./src/Darcs/Patch/Commute.lhs 64
 import Darcs.Witnesses.Sealed ( unsafeUnseal, unsafeUnsealFlipped )
 import Darcs.Utils ( nubsort )
 #include "impossible.h"
-import Darcs.Witnesses.Sealed ( Sealed(..), mapSeal, unseal, FlippedSeal(..), mapFlipped, unsealFlipped )
+import Darcs.Witnesses.Sealed ( Sealed(..), mapSeal, unseal, FlippedSeal(..), mapFlipped )
 import Darcs.Witnesses.Ordered ( mapFL, mapFL_FL, unsafeCoerceP,
                              unsafeCoercePStart, unsafeCoercePEnd,
                              FL(..), RL(..),
[Fix redundant import warning in Darcs.Patch.Patchy.
Eric Kow <ko...@darcs.net>**20100723134447
 Ignore-this: 3fa7ffaf1b8098c4c0793c3ccc5ecb36
] hunk ./src/Darcs/Patch/Patchy.hs 46
 import Printer ( Doc, (<>), text )
 import Darcs.Lock ( writeDocBinFile, gzWriteDocFile )
 import Darcs.IO ( WriteableDirectory )
-import Darcs.Flags ( DarcsFlag )
 import English ( plural, Noun(Noun) )
 
 import ByteStringUtils ( ifHeadThenTail, dropSpace )
[Fix warnings in Darcs.Patch.Prim.
Eric Kow <ko...@darcs.net>**20100723134501
 Ignore-this: dfd3b36b4b07e6de3b558073ac6bbe27
] hunk ./src/Darcs/Patch/Prim.lhs 52
 import Data.Map ( elems, fromListWith, mapWithKey )
 
 import ByteStringUtils ( substrPS, fromPS2Hex)
-import qualified Data.ByteString as B (ByteString, length, null, head, take, concat, drop)
+import qualified Data.ByteString as B (ByteString, length, null, take, concat, drop)
 import qualified Data.ByteString.Char8 as BC (break, pack, head)
 
 import Darcs.Patch.FileName ( FileName, fn2ps, fn2fp, fp2fn, normPath,
hunk ./src/Darcs/Patch/Prim.lhs 438
   where
         unsealList :: [Sealed2 p] -> FL p C(a b)
         unsealList [] = unsafeCoerceP NilFL
-        unsealList (x:xs) = unsafeUnseal2 x :>: unsealList xs
+        unsealList (y:ys) = unsafeUnseal2 y :>: unsealList ys
 
         toSimpleSealed :: Sealed2 Prim -> Maybe (FileName, Sealed2 Simple)
         toSimpleSealed (Sealed2 p) = fmap (\(fn, s) -> (fn, Sealed2 s)) (toSimple p)
[Fix warnings in Darcs.Repository.DarcsRepo.
Eric Kow <ko...@darcs.net>**20100723134515
 Ignore-this: 66f45d925ab9a7bce4c6e69ded8803fe
] hunk ./src/Darcs/Repository/DarcsRepo.lhs 77
 import Darcs.SignalHandler ( withSignalsBlocked )
 
 import ByteStringUtils ( gzReadFilePS )
-import qualified Data.ByteString as B (ByteString, null, readFile, empty)
+import qualified Data.ByteString as B (readFile, empty)
 import qualified Data.ByteString.Char8 as BC (break, pack)
 
 import Darcs.Patch ( RepoPatch, Effect, Prim, Named, invert,
hunk ./src/Darcs/Repository/DarcsRepo.lhs 90
 import Darcs.Witnesses.Ordered ( FL(..), RL(..), (:>>)(..), (+<+),
                              reverseFL, mapFL, unsafeCoerceP,
                              reverseRL, mapRL )
-import Darcs.Patch.Info ( PatchInfo, makeFilename, readPatchInfo,
+import Darcs.Patch.Info ( PatchInfo, makeFilename,
                           showPatchInfo, isTag, readPatchInfos
                  )
 import Darcs.Patch.Set ( PatchSet(..), Tagged(..), SealedPatchSet, newset2RL )
[Fix warnings in Darcs.Repository.HashedIO.
Eric Kow <ko...@darcs.net>**20100723134533
 Ignore-this: af2a60a5bf64d53240dc4498696c7a42
] hunk ./src/Darcs/Repository/HashedIO.hs 24
 
 module Darcs.Repository.HashedIO ( HashedIO,
                                    copyHashed, copyPartialsHashed,
-                                   cleanHashdir ) where
+                                   cleanHashdir,
+                                   RW(RW) -- only exported to make warning go away
+                                 ) where
 
 import Darcs.Global ( darcsdir )
 import qualified Data.Set as Set
hunk ./src/Darcs/Repository/HashedIO.hs 36
 import Control.Applicative ( (<$>) )
 import Data.Maybe ( isJust )
 import System.IO.Unsafe ( unsafeInterleaveIO )
-import System.IO ( hPutStrLn, stderr )
 
 import Darcs.Repository.Cache ( Cache(..), fetchFileUsingCache, writeFileUsingCache,
                                 peekInCache, speculateFileUsingCache,
hunk ./src/Darcs/Repository/HashedIO.hs 40
                                 okayHash, cleanCachesWithHint, HashedDir(..), hashedDir )
-import Darcs.Patch ( Patchy, apply )
 import Darcs.RepoPath ( FilePathLike, toFilePath )
 import Darcs.IO ( ReadableDirectory(..), WriteableDirectory(..) )
hunk ./src/Darcs/Repository/HashedIO.hs 42
-import Darcs.Flags ( DarcsFlag, Compression( .. ) )
+import Darcs.Flags ( Compression( .. ) )
 import Darcs.Lock ( writeAtomicFilePS, removeFileMayNotExist )
 import Darcs.Utils ( withCurrentDirectory )
 import Progress ( debugMessage, tediousSize, finishedOneIO )
hunk ./src/Darcs/Repository/HashedIO.hs 53
 import qualified Data.ByteString       as B  (ByteString, length, empty)
 import qualified Data.ByteString.Char8 as BC (unpack, pack)
 
-import Storage.Hashed.Darcs( hashedTreeIO, readDarcsHashedNosize, readDarcsHashed,
-                             writeDarcsHashed, readDarcsHashedDir, darcsLocation,
+import Storage.Hashed.Darcs( readDarcsHashedDir, darcsLocation,
                              decodeDarcsHash, decodeDarcsSize )
hunk ./src/Darcs/Repository/HashedIO.hs 55
-import Storage.Hashed.Tree( treeHash, ItemType(..) )
-import Storage.Hashed.Hash( encodeBase16, Hash(..) )
+import Storage.Hashed.Tree( ItemType(..) )
 
 -- | @readHashFile c subdir hash@ reads the file with hash @hash@ in dir subdir,
 -- fetching it from 'Cache' @c@ if needed.
hunk ./src/Darcs/Repository/HashedIO.hs 288
           listone h = do let size = decodeDarcsSize $ BC.pack h
                              hash = decodeDarcsHash $ BC.pack h
                          x <- readDarcsHashedDir hashdir (size, hash)
-                         let subs = [ fst $ darcsLocation "" (s, h) | (TreeType, _, s, h) <- x ]
-                             hashes = h : [ fst $ darcsLocation "" (s, h) | (_, _, s, h) <- x ]
+                         let subs = [ fst $ darcsLocation "" (s, h') | (TreeType, _, s, h') <- x ]
+                             hashes = h : [ fst $ darcsLocation "" (s, h') | (_, _, s, h') <- x ]
                          (hashes++) . concat <$> mapM listone subs
       hs <- set . concat <$> mapM listone hashroots
       fs <- set . filter okayHash <$> getDirectoryContents hashdir
[Fix warnings in Darcs.Repository.InternalTypes.
Eric Kow <ko...@darcs.net>**20100723134556
 Ignore-this: 66a361e0ff4b1a0c616fb11dafc6467c
] hunk ./src/Darcs/Repository/InternalTypes.hs 54
 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 dr
   where dr            = DarcsRepository pristine . cmap ( sortBy compareByLocality . nub ) $ f cache
-        cmap f (Ca c) = Ca (f c)
+        cmap g (Ca c) = Ca (g c)
[Fix warnings in Darcs.Repository.State.
Eric Kow <ko...@darcs.net>**20100723134611
 Ignore-this: 5a7c4a33c95ba3285721d0ade56adf1b
] hunk ./src/Darcs/Repository/State.hs 47
 import qualified Data.ByteString as BS
 import qualified Data.ByteString.Char8 as BSC
 
-import Darcs.Patch ( RepoPatch, Prim, invert, applyToTree, applyToFilepaths
+import Darcs.Patch ( RepoPatch, Prim, applyToTree, applyToFilepaths
                    , sortCoalesceFL )
hunk ./src/Darcs/Repository/State.hs 49
-import Darcs.Patch.TouchesFiles ( chooseTouching )
 import Darcs.Witnesses.Ordered ( FL(..), (+>+) )
 import Darcs.Witnesses.Ordered ( unsafeCoerceP, EqCheck(IsEq) )
 import Darcs.Witnesses.Sealed ( Sealed(Sealed), seal, unFreeLeft )
[Fix missing type signature in Darcs.Arguments.
Eric Kow <ko...@darcs.net>**20100726134237
 Ignore-this: 8f69ae4defc489d4a4ec9c5734fa2376
] hunk ./src/Darcs/Arguments.lhs 418
   option (x,y,z) = x y z
   third f (x,y,z) = (x,y,f z)
 
+nubOptions :: [DarcsOption] -> [DarcsFlag] -> [DarcsFlag]
 nubOptions [] opts = opts
 nubOptions (DarcsMutuallyExclusive ch _:options) opts = nubOptions options $ collapse opts
   where collapse (x:xs) | x `elem` flags ch = x : clear xs

Context:

[Disable optimize --http for Darcs 2.5 release.
Eric Kow <e.y....@brighton.ac.uk>**20100726111249
 Ignore-this: 92b75e71ac3041eee76762bf8042b02c
] 
[Disable packs for darcs 2.5.
Eric Kow <e.y....@brighton.ac.uk>**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 <ko...@darcs.net>**20100726114810
 Ignore-this: e18459c582c12c2e77b630f096f66190
 
 rolling back:
 
 Sun Jul 11 13:08:54 BST 2010  Reinier Lamers <tux_roc...@reinier.de>
   * 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 <tux_roc...@reinier.de>**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 <da...@codersbase.com>**20100723064832
 Ignore-this: aa207726cbe8894aab41c17bd01ee6ca
] 
[move readPatchIds to Darcs.Patch.Info
Jason Dagit <da...@codersbase.com>**20100723064511
 Ignore-this: 53f620c0f5ffda0ffd82693c27a70235
] 
[remove duplicate code, readPatchIds
Jason Dagit <da...@codersbase.com>**20100723063526
 Ignore-this: a1950afa8385b04aa9c03435e4c152cb
] 
[Slightly fix context generation in Setup.
Petr Rockai <m...@mornfall.net>**20100722111410
 Ignore-this: eb3b6637f24d62332c9452a3c4143f39
] 
[Fix "head: empty list" bug in Darcs.Flags.RemoteDarcs.
Petr Rockai <m...@mornfall.net>**20100715123140
 Ignore-this: fa172627824eb3937cad63223026db9e
] 
[Remove [DarcsFlag] usage from Darcs.Patch.Bundle.
Petr Rockai <m...@mornfall.net>**20100715081908
 Ignore-this: 62297671dea56fdc0a1cac42f79d6d29
] 
[Use Compression more widely, suppressing further [DarcsFlag] uses.
Petr Rockai <m...@mornfall.net>**20100715003449
 Ignore-this: d582d3bc381e73a964127aa3b87d0ffb
] 
[Replace some [DarcsFlag] uses with newly introduced RemoteDarcs.
Petr Rockai <m...@mornfall.net>**20100715003320
 Ignore-this: d018b8c9b328228b9d283b7ad824eb15
] 
[Remove --nolinks, since its scope and usefulness is very limited.
Petr Rockai <m...@mornfall.net>**20100715000822
 Ignore-this: 71427fcd09e59d5e4f443bcc4e5ca649
] 
[resolve issue1893: move fields of conditional builds within scope of condition
Ganesh Sittampalam <gan...@earth.li>**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 <ko...@darcs.net>**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 <m...@mornfall.net>**20100715002249
 Ignore-this: 707f8193561ce890dc6ed91d1001253b
] 
[Fix up tests to refer to --name instead of --patch-name.
Petr Rockai <m...@mornfall.net>**20100715102618
 Ignore-this: 630cc96d79db0ee7af9c93fa3dbf5f15
] 
[Resolve issue1883: rename --patch-name option to --name.
Eric Kow <ko...@darcs.net>**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.
] 
[Remove [DarcsFlag] argument from unrecordedChanges.
Petr Rockai <m...@mornfall.net>**20100714155059
 Ignore-this: 4ba064584b4846b0ca26f6e3199a955a
] 
[Update link to Darcs repository browser.
Eric Kow <ko...@darcs.net>**20100713174550
 Ignore-this: 3546359aec588d1262d6335b033331d0
] 
[get rid of join_patches
Ganesh Sittampalam <gan...@earth.li>**20100712165037
 Ignore-this: f9a5ca3dcc690e3c1ed9f6778b07f542
] 
[stop using join_patches in Darcs.Test.Unit
Ganesh Sittampalam <gan...@earth.li>**20100712165031
 Ignore-this: 563bbbd15f9f51cdfc8063b9dd7f8b0b
] 
[move main unit testing code into module with proper name (not Main)
Ganesh Sittampalam <gan...@earth.li>**20100707180600
 Ignore-this: 9c44b4ab083ba44afc9ecaf0752cd130
 This is enable other things than the unit executable to import it
 
] 
[Fix haddock error.
Eric Kow <ko...@darcs.net>**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 <ko...@darcs.net>**20100712142926
 Ignore-this: 97dc0a40b82f9360d374917e243e0490
] 
[Resolve issue1887: add a missing newline to --list-options output.
Petr Rockai <m...@mornfall.net>**20100711193535
 Ignore-this: 912b18e8f89be19d186332f5f98a8083
] 
[Fix conflict in Distribution.ShellHarness.
Eric Kow <ko...@darcs.net>**20100712132814
 Ignore-this: bfde365cf2d74b05d29ed457b5382f46
 Was between extended test defaults and Control.OldException removal.
] 
[Fix tests in light of recent default flag changes.
Petr Rockai <m...@mornfall.net>**20100708195100
 Ignore-this: b8764f2105ed6e7870f4853041b90f9e
] 
[Correctly handle conflicts arising from DarcsMutuallyExclusive options.
Petr Rockai <m...@mornfall.net>**20100708194904
 Ignore-this: b6607175899ad6f63044adae7442fd6d
] 
[Avoid adding noCache twice to parameter lists.
Petr Rockai <m...@mornfall.net>**20100708195014
 Ignore-this: 59cf4dc50edb4c08367cbc29f321e431
] 
[Make --no-cache an advanced option in all commands.
Eric Kow <ko...@darcs.net>**20100701161428
 Ignore-this: 99ea6f8e2235bfdab407a1af9fcfb5cc
] 
[Do not set default repo by default in push, pull, send, fetch.
Eric Kow <ko...@darcs.net>**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 <ko...@darcs.net>**20100701160138
 Ignore-this: 189522de144a9b9b81239f4a5ff545f0
] 
[Make --edit-description the default.
Eric Kow <ko...@darcs.net>**20100701155253
 Ignore-this: ed99469237da51949d915a8dda13706e
] 
[Express --{no-,}edit-description as a mutually exclusive option.
Eric Kow <ko...@darcs.net>**20100701155045
 Ignore-this: 419cc3945f89953e33400172d51453e9
] 
[Add a notion of mutually exclusive options with a default.
Eric Kow <ko...@darcs.net>**20100701155041
 Ignore-this: e3a29afebe21c9ec6ce355040260e8b
] 
[General purpose function for setting defaults.
Eric Kow <ko...@darcs.net>**20100701151816
 Ignore-this: d76a09aa70eba9694d3649300ef7720d
] 
[Fix use of atomicOptions in Darcs.ArgumentDefaults.
Eric Kow <ko...@darcs.net>**20100701144916
 Ignore-this: 4fc1df15e34b5c63c47e4c12c4f5963
] 
[Update optimizeHTTP for new two-layer DarcsOption.
Eric Kow <ko...@darcs.net>**20100701142543
 Ignore-this: d892c6787ba0aa93a0b36c1e7a79b756
] 
[Refactor traversal of atomic options in DarcsOption.
Eric Kow <ko...@darcs.net>**20100621003601
 Ignore-this: 9425a65b80f075e684fd7edaf9b5b868
] 
[Better use of Data.Maybe helpers in Darcs.Arguments.
Eric Kow <ko...@darcs.net>**20100621002200
 Ignore-this: 46feb16524e1d61495a7ead46cce1e55
] 
[Flatten DarcsOption type.
Eric Kow <ko...@darcs.net>**20100621001926
 Ignore-this: 34a3e0c2a9e989f0f35774d742607c93
 Distinguish between DarcsAtomicOptions and DarcsOption.
] 
[Fix test issue1865-get-context.sh
Thorkil Naur <n...@post11.tele.dk>**20100711121938
 Ignore-this: c68995d55efb6095ada7c24ce0909716
] 
[remove redundant and accidentally checked in definition
Ganesh Sittampalam <gan...@earth.li>**20100709214141
 Ignore-this: d8ad150be87b467f92721c8079158541
] 
[remove dead code
Ganesh Sittampalam <gan...@earth.li>**20100708055640
 Ignore-this: 86104cf3f14952869be820f66f156fbb
] 
[fix warning
Ganesh Sittampalam <gan...@earth.li>**20100707061818
 Ignore-this: 4b9e468819689cfc768befa8eabe4a4f
] 
[standardize GHC options
Ganesh Sittampalam <gan...@earth.li>**20100707180210
 Ignore-this: b088f0ece12b86980225d81b37d89251
] 
[fix unused variable warning
Ganesh Sittampalam <gan...@earth.li>**20100707065338
 Ignore-this: b2a8e05c985912a78dc71748361271b1
] 
[fix name shadowing warning
Ganesh Sittampalam <gan...@earth.li>**20100707065303
 Ignore-this: 79ab8367f22333f79f66e82d5f631dac
] 
[rename field names to avoid shadowing warnings
Ganesh Sittampalam <gan...@earth.li>**20100707062714
 Ignore-this: 6be53f3ee1ef4915bdd722153b0675e0
] 
[fix unused code warning
Ganesh Sittampalam <gan...@earth.li>**20100707062701
 Ignore-this: 3475bca718b26e5056c3ad7448a346dc
] 
[fix shadowing warnings
Ganesh Sittampalam <gan...@earth.li>**20100707062324
 Ignore-this: 45d7d142735754357e7b9c53eb2c25df
] 
[fix warning
Ganesh Sittampalam <gan...@earth.li>**20100707062320
 Ignore-this: 33b1a5f0d5895f04257e4eb133addfc5
] 
[fix warning
Ganesh Sittampalam <gan...@earth.li>**20100707062315
 Ignore-this: ad3da11afad97816fcd832baf25c311f
] 
[remove dead code
Ganesh Sittampalam <gan...@earth.li>**20100707062309
 Ignore-this: a3462879709597df56cf28d239b71eef
] 
[add comment about why we're using a deprecated option
Ganesh Sittampalam <gan...@earth.li>**20100707061805
 Ignore-this: eb1ec29ce345f96689d39f8f9638987c
] 
[stop using Control.OldException in Setup.lhs + deps
Ganesh Sittampalam <gan...@earth.li>**20100707060932
 Ignore-this: ab49b67e05941402304aed3a8b55f52f
] 
[Fix missing type signature.
Eric Kow <ko...@darcs.net>**20100701153511
 Ignore-this: a0669588aca19f0c45326c1244e1c766
] 
[Rename optionFromDarcsoption to optionFromDarcsOption.
Eric Kow <ko...@darcs.net>**20100621000207
 Ignore-this: d1c5a5cb84264a404b9b07c9094f96aa
] 
[TAG 2.4.98.1
Reinier Lamers <tux_roc...@reinier.de>**20100711120953
 Ignore-this: 6955d46fb3e48bc5bb0f622e495eae1f
] 
Patch bundle hash:
74946b7f981e3ed21b8780bff47fb6ce4119a3fe

Attachment: unnamed
Description: Binary data

_______________________________________________
darcs-users mailing list
darcs-users@darcs.net
http://lists.osuosl.org/mailman/listinfo/darcs-users

Reply via email to