Mon Oct  2 14:37:19 PDT 2006  Echo Nolan <[EMAIL PROTECTED]>
  * Document -ddump-cmm and remove dead -ddump-absC documentation
New patches:

[Document -ddump-cmm and remove dead -ddump-absC documentation
Echo Nolan <[EMAIL PROTECTED]>**20061002213719] {
hunk ./docs/users_guide/flags.xml 1583
-	      <entry><option>-ddump-absC</option></entry>
-	      <entry>Dump abstract C</entry>
+	      <entry><option>-ddump-cmm</option></entry>
+	      <entry>Dump (quasi) C--</entry>
}

Context:

[Add a C++ phase. Fixes bug #800
Lemmih <[EMAIL PROTECTED]>**20060727080023] 
[Latin-1-to-UTF8 pre-processor example for docs from Christian Maeder
Ian Lynagh <[EMAIL PROTECTED]>**20061001010700] 
[add :edit to the release notes, and improve the docs a bit
Simon Marlow <[EMAIL PROTECTED]>**20060929112108] 
[Simplify the way in which the coKindFun in CoercionTyCon is handled
[EMAIL PROTECTED]
 
 Before the coKindFun could be applied to too many arguments;
 now it expects exactly the right number of arguments.  That
 makes it easier to write the coKindFuns, and localises the work.
 
] 
[Match let before lambda in rule-matching (see comment with Lam case of Rules.match)
[EMAIL PROTECTED] 
[Fix bug in SCRIPT_SHELL patch (| should be ||)
[EMAIL PROTECTED] 
[Add missing case for EqPred
[EMAIL PROTECTED] 
[Amplify scoped tyvar changes
[EMAIL PROTECTED] 
[Update release notes
[EMAIL PROTECTED] 
[Remove Linear Implicit Parameters, and all their works
[EMAIL PROTECTED]
 
 Linear implicit parameters have been in GHC quite a while,
 but we decided they were a mis-feature and scheduled them for
 removal.  This patch does the job.
 
] 
[Global renamings in HsSyn
[EMAIL PROTECTED] 
[Improve pretty-printing of Core
[EMAIL PROTECTED] 
[Another correction to the (subtle) exprIsConApp_maybe
[EMAIL PROTECTED] 
[Spelling correction
[EMAIL PROTECTED] 
[Improve pretty printing of IfaceSyn
[EMAIL PROTECTED] 
[Improve unification error messages (again) (push to 6.6 branch)
[EMAIL PROTECTED] 
[:edit runs notepad by default on Windows
Simon Marlow <[EMAIL PROTECTED]>**20060929102739] 
[unbreak :edit patch on Windows
Simon Marlow <[EMAIL PROTECTED]>**20060928155951] 
[Fix #906, and do #914 while I'm in here (it wasn't too hard)
Simon Marlow <[EMAIL PROTECTED]>**20060928151705] 
[Add basic :edit support
Simon Marlow <[EMAIL PROTECTED]>**20060928135156
 Without jumping to line numbers or %-expansion, we could add that later.
] 
[tiny fix in porting docs I just spotted
Simon Marlow <[EMAIL PROTECTED]>**20060928105611] 
[only make stdin/stdout unbuffered in GHCi, not runghc or ghc -e.
Simon Marlow <[EMAIL PROTECTED]>**20060928105403] 
[testsuite *is* boring
Simon Marlow <[EMAIL PROTECTED]>**20060928105342] 
[fix typo in comment
Andres Loeh <[EMAIL PROTECTED]>**20060914235648] 
[remove non-boring directories
Norman Ramsey <[EMAIL PROTECTED]>**20060915234902] 
[Modify toArgs to parse quotes/escapes like /bin/sh
[EMAIL PROTECTED]
 Addresses ticket #197, which asks for escape sequences to be supported directly (i.e.
 not only in dquoted strings) on :load commands in GHCI.  Fix modifies the toArgs
 function to parse its input like /bin/sh does, i.e. recognizing escapes anywhere
 and treating quoted strings as atomic chunks.  Thus:
   :load a\ b c\"d e" "f
 would parse with three arguments, namely 'a b', 'c"d', and 'e f'.
 
 toArgs is used to parse arguments for both :load and :main, but doesn't appear to
 be used elsewhere.  I see no harm in modifying both to be consistent -- in fact,
 the functionality is probably more useful for :main than for :load.
] 
[Fix mulIntMayOflo on 64-bit arches; fixes trac #867
Ian Lynagh <[EMAIL PROTECTED]>**20060928004806
 We were assuming we could multiply 2 32-bit numbers without overflowing
 a 64-bit number, but we can't as the top bit is the sign bit.
] 
[Handle clock_gettime failing
Ian Lynagh <[EMAIL PROTECTED]>**20060927234630] 
[Change default repo root for the 6.6 branch
Ian Lynagh <[EMAIL PROTECTED]>*-20060902174936] 
[Tell the 6.6 branch where to find extralibs
Ian Lynagh <[EMAIL PROTECTED]>*-20060906124640] 
[Rename -no-recomp to -fforce-recomp, and document it
Simon Marlow <[EMAIL PROTECTED]>**20060927132707] 
[Make printing of binding results optional in GHCi, and document it
Simon Marlow <[EMAIL PROTECTED]>**20060927132550
 You can say :set -fno-print-bind-result in GHCi to disable this behaviour.
 Addresses #887
] 
[Tell the 6.6 branch where to find extralibs
Ian Lynagh <[EMAIL PROTECTED]>**20060906124640] 
[Change default repo root for the 6.6 branch
Ian Lynagh <[EMAIL PROTECTED]>**20060902174936] 
[Fix exprIsConApp_maybe (wasn't dealing properly with the EqSpec of the DataCon)
[EMAIL PROTECTED] 
[unbreak mingw-on-cygwin (/=MSYS) builds
[EMAIL PROTECTED] 
[Add source code links to Haddock docs
Simon Marlow <[EMAIL PROTECTED]>**20060908112725
 
 Right now we can only manage to add a source code link for the module,
 but that's better than nothing.
 
 I had to put the list of core packages in a Makefile variable,
 $(CorePackages), so we'll have to be careful to keep this up to date.
 (I could have slurped it out of libraries/core-packages with $(shell),
 but that's ugly and really slow on Windows).
 
 There are a couple of new tweakables: CorePackageSourceURL and
 ExtraPackageSourceURL in config.mk.in, set these to the appropriate
 patterns for generating source links.
 
 (when we merge this patch onto the HEAD we'll have to tweak these
 settings).
 
 Unfortunately it still doesn't work for all the modules, because
 modules compiled without -cpp don't get any #line directives.  More
 hackery required...
] 
[Fix derived instances (again); prevents infinite superclass loop
[EMAIL PROTECTED] 
[Various documentation improvements suggested by Bulat Ziganshin
Ian Lynagh <[EMAIL PROTECTED]>**20060925231855] 
[Fix comment/code inconsistency spotted by Bulat Ziganshin
Ian Lynagh <[EMAIL PROTECTED]>**20060925195925
 I'm not sure if this is the example that was intended, but it's at least
 now consistent.
] 
[rejig library include/ files
[EMAIL PROTECTED] 
[Fix newtype deriving properly (un-doing Audreys patch)
[EMAIL PROTECTED]
 
 The newtype-deriving mechanism generates a HsSyn case expression looking
 like this
 	case (d `cast` co) of { ... }
 That is, the case expression scrutinises a dictionary.  This is 
 otherwise never seen in HsSyn, and it made the desugarer
 (Check.get_unused_cons) crash in tcTyConAppTyCon.
 
 It would really be better to generate Core in TcInstDecls (the newtype
 deriving part) but I'm not going to do that today.  Instead, I made
 Check.get_unused_cons a bit more robust.
 
 Audrey tried to fix this over the weekend, but her fix was, alas, utterly
 bogus, which caused mysterious failures later.  I completely undid this
 change.
 
 Anyway it should work now!
 
] 
[Document -F in the flag reference
Ian Lynagh <[EMAIL PROTECTED]>**20060925134816] 
[Added Darwinports path to DocBook XSL stylesheets to configure.
[EMAIL PROTECTED] 
[Comment-only: Fix a typo, and note that the PredTy case on SplitTyConApp_maybe was added as a kluge.
[EMAIL PROTECTED] 
[In tcSplittyConApp_maybe, add the PredTy case
[EMAIL PROTECTED]
 such that this can compile again:
 
     newtype Moose = MkMoose () deriving (Eq, Ord)
 
] 
[Fixed DocBook XML once again, "make validate" is your friend!
[EMAIL PROTECTED] 
[Trim more imports 
[EMAIL PROTECTED] 
[Fix origin for addDataConStupidTheta
[EMAIL PROTECTED] 
[Remove ASSERT from mkDataCon, and add comments to explain why
[EMAIL PROTECTED] 
[The unboxed tuple kind is (#), not (##)
[EMAIL PROTECTED] 
[Complete definition of cmPredX to take account of EqPred
[EMAIL PROTECTED] 
[Correct crucial typo in isSubKind (kc1 -> kc2)!
[EMAIL PROTECTED] 
[Re-work the newtype-deriving support
[EMAIL PROTECTED]
 
 The newtype deriving mechanism is much trickier to support than it
 seems at first.  Kevin didn't get it quite right when moving to FC,
 and I ended up re-writing quite a bit of it.  
 
 I think it's right now, but I have not yet tested it thoroughly.
 
] 
[Add TcRnMonad.newSysLocalIds, and use it
[EMAIL PROTECTED] 
[Remove dead code concerning coercions from TypeRep
[EMAIL PROTECTED] 
[Move snocView in the file, nearer the other spliting functions
[EMAIL PROTECTED] 
[Improve documentation of newtype-deriving (todo: check formatting still works)
[EMAIL PROTECTED] 
[Add VarSet.disjointVarSet, and use it
[EMAIL PROTECTED] 
[Trim imports, and remove some dead code
[EMAIL PROTECTED] 
[Improve specialisation in SpecConstr
[EMAIL PROTECTED]
 
 This patch enables argToPat to look through let expressions
 
 e.g.	f (let v = rhs in \y -> ...v...)
 
 Here we can specialise for f (\y -> ...) because the rule-matcher will
 look through the let.
 
] 
[Remove duplicate call to getDOpts
[EMAIL PROTECTED] 
[Remove use of isVanillaDataCon, which was wrong under the new FC dispensation
[EMAIL PROTECTED] 
[Trim imports, reformatting
[EMAIL PROTECTED] 
[Add a crucial missing prime in tcConPat
[EMAIL PROTECTED]
 
 This fixes a typo -- a missing prime in tcConPat.  
 
 The test is gadt18.
 
 While modifying TcPat I also trimmed imports, fixed non-exhaustive
 patterns, and improved tracing.
 
 
] 
[64bit fixes for the symbol lookup table
[EMAIL PROTECTED] 
[In ByteCodeGen, correctly passthru AnnCast in all relevant places, so the previous band-aid fix is no longer needed.
[EMAIL PROTECTED] 
[Add explicit eta-reduction to GHCI's schemeE such that deriving Typeable won't panick.
[EMAIL PROTECTED] 
[Repair "ghci" under FC+AT by handling AnnCast in bytecode generator.
[EMAIL PROTECTED] 
[Fix Linker import when BREAKPOINT is off
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20060921210029] 
[Extend IfaceSyn.eqIfTc to cover type kind variants from FC
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20060921161400] 
[Use --export-dynamic to ensure ghci works on newer openbsds
Don Stewart <[EMAIL PROTECTED]>**20060921010155
 
 Changes to the RTLD_DEFAULT semantics broke the trick we used to ensure
 libc symbols were available to the ghci linker, in OpenBSD 4.0. We can
 fix this by linking the ghc binary itself with --export-dynamic on this
 system, removing the need for any magic Linker.c games.
 
 GHCi now works on OpenBSD 4.0
 
 Contributed by Eric Mertens <emertens at gmail.com>
 
] 
[* TypeRep.lhs and TypeRep.lhs-boot didn't agree on their signatures (SuperKind vs Kind)
[EMAIL PROTECTED] 
[* Fix stray comma in HsTypes.lhs's import line.
[EMAIL PROTECTED] 
[TAG After FC branch merge
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20060920211146] 
Patch bundle hash:
10fe388b788c5fbbf0b549ffad4b299c1c6399d1
_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to