Wed Oct 11 22:43:01 CEST 2006  [EMAIL PROTECTED]
  * Fixed spelling error in compiler/ghci/InteractiveUI.hs and 
docs/users_guide/ghci.xml
New patches:

[Fixed spelling error in compiler/ghci/InteractiveUI.hs and docs/users_guide/ghci.xml
[EMAIL PROTECTED] {
hunk ./compiler/ghci/InteractiveUI.hs 186
- "   :etags [<file>]             create tags file for Emacs (defauilt: \"TAGS\")\n" ++
+ "   :etags [<file>]             create tags file for Emacs (default: \"TAGS\")\n" ++
hunk ./docs/users_guide/ghci.xml 71
-   :etags [&lt;file&gt;]             create tags file for Emacs (defauilt: "TAGS")
+   :etags [&lt;file&gt;]             create tags file for Emacs (default: "TAGS")
}

Context:

[Use relative URLs when referring to libraries; push to 6.6 branch
[EMAIL PROTECTED] 
[Improve documentation of concurrent and parallel Haskell; push to branch
[EMAIL PROTECTED] 
[Correct id to linkend
[EMAIL PROTECTED] 
[Fix trac #921: generate *q instructions for int-float conversions
Ian Lynagh <[EMAIL PROTECTED]>**20061011140007
 We need to generate, e.g., cvtsi2sdq rather than cvtsi2sd on amd64 in
 order to have int-float conversions work correctly for values not
 correctly representable in 32 bits.
] 
[Module header tidyup #2
Simon Marlow <[EMAIL PROTECTED]>**20061011143523
 Push this further along, and fix build problems in the first patch.
] 
[remove BitSet, it isn't used
Simon Marlow <[EMAIL PROTECTED]>**20061011131614] 
[Module header tidyup, phase 1
Simon Marlow <[EMAIL PROTECTED]>**20061011120517
 This patch is a start on removing import lists and generally tidying
 up the top of each module.  In addition to removing import lists:
 
    - Change DATA.IOREF -> Data.IORef etc.
    - Change List -> Data.List etc.
    - Remove $Id$
    - Update copyrights
    - Re-order imports to put non-GHC imports last
    - Remove some unused and duplicate imports
] 
[Interface file optimisation and removal of nameParent
Simon Marlow <[EMAIL PROTECTED]>**20061011120518
 
 This large commit combines several interrelated changes:
 
   - IfaceSyn now contains actual Names rather than the special
     IfaceExtName type.  The binary interface file contains
     a symbol table of Names, where each entry is a (package,
     ModuleName, OccName) triple.  Names in the IfaceSyn point
     to entries in the symbol table.
 
     This reduces the size of interface files, which should
     hopefully improve performance (not measured yet).
 
     The toIfaceXXX functions now do not need to pass around
     a function from Name -> IfaceExtName, which makes that
     code simpler.
 
   - Names now do not point directly to their parents, and the
     nameParent operation has gone away.  It turned out to be hard to
     keep this information consistent in practice, and the parent info
     was only valid in some Names.  Instead we made the following
     changes:
 
     * ImportAvails contains a new field 
           imp_parent :: NameEnv AvailInfo
       which gives the family info for any Name in scope, and
       is used by the renamer when renaming export lists, amongst
       other things.  This info is thrown away after renaming.
 
     * The mi_ver_fn field of ModIface now maps to
       (OccName,Version) instead of just Version, where the
       OccName is the parent name.  This mapping is used when
       constructing the usage info for dependent modules.
       There may be entries in mi_ver_fn for things that are not in
       scope, whereas imp_parent only deals with in-scope things.
 
     * The md_exports field of ModDetails now contains
       [AvailInfo] rather than NameSet.  This gives us
       family info for the exported names of a module.
 
 Also:
 
    - ifaceDeclSubBinders moved to IfaceSyn (seems like the
      right place for it).
 
    - heavily refactored renaming of import/export lists.
 
    - Unfortunately external core is now broken, as it relied on
      IfaceSyn.  It requires some attention.
] 
[add extendNameEnvList_C
Simon Marlow <[EMAIL PROTECTED]>**20061010153137] 
[getMainDeclBinder should return Nothing for a binding with no variables
Simon Marlow <[EMAIL PROTECTED]>**20061010153023
 See test rn003
 
] 
[Use ":Co", not "Co" to prefix coercion TyCon names
Simon Marlow <[EMAIL PROTECTED]>**20061010134449
 Avoid possibility of name clash
] 
[Fix another hi-boot file
Ian Lynagh <[EMAIL PROTECTED]>**20061010235157] 
[Removed unused unwrapFamInstBody from MkId
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061010205843] 
[Rejig the auto-scc wrapping stuff
[EMAIL PROTECTED] 
[Do not filter the type envt after each GHCi stmt
[EMAIL PROTECTED]
 
 Fixes Trac #925
 
 A new comment in TcRnDriver in tcRnStmt reads thus: 
 
 At one stage I removed any shadowed bindings from the type_env;
 they are inaccessible but might, I suppose, cause a space leak if we leave them there.
 However, with Template Haskell they aren't necessarily inaccessible.  Consider this
 GHCi session
 	 Prelude> let f n = n * 2 :: Int
 	 Prelude> fName <- runQ [| f |]
 	 Prelude> $(return $ AppE fName (LitE (IntegerL 7)))
 	 14
 	 Prelude> let f n = n * 3 :: Int
 	 Prelude> $(return $ AppE fName (LitE (IntegerL 7)))
 In the last line we use 'fName', which resolves to the *first* 'f'
 in scope. If we delete it from the type env, GHCi crashes because
 it doesn't expect that.
 
 
] 
[Fail more informatively when a global isn't in the type environment
[EMAIL PROTECTED] 
[Rough matches for family instances
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20061010044656
 - Class and type family instances just got a lot more similar.
 - FamInst, like Instance, now has a rough match signature.  The idea is the
   same: if the rough match doesn't match, there is no need to pull in the while
   tycon describing the instance (from a lazily read iface).
 - IfaceFamInst changes in a similar way and the list of all IFaceFamInsts is
   now written into the binary iface (as for class instances), as deriving it
   from the tycon (as before) would render the whole rough matching useless.
 - As a result of this, the plumbing of class instances and type instances 
   through the various environments, ModIface, ModGuts, and ModDetails is now
   almost the same.  (The remaining difference are mostly because the dfun of a
   class instance is an Id, but type instance refer to a TyCon, not an Id.)
 
 *** WARNING: The interface file format changed! ***
 ***	     Rebuild from scratch.		***
] 
[Tweaks and missing case in disassembler
Ian Lynagh <[EMAIL PROTECTED]>**20061009230539] 
[Update hi-boot files to fix building with old GHCs
Ian Lynagh <[EMAIL PROTECTED]>**20061009193218] 
[STM invariants
[EMAIL PROTECTED] 
[Fix unregisterised alpha builds
Ian Lynagh <[EMAIL PROTECTED]>**20061004125857] 
[Comments and an import-trim
[EMAIL PROTECTED] 
[Mention that the module sub-directory structure for .o and .hi files is created automatically by GHC
[EMAIL PROTECTED] 
[Bale out before renamer errors are duplicated
[EMAIL PROTECTED]
 
 With the new Haddock patch, renamer errors can be duplicated;
 so we want to bale out before doing the Haddock stuff if errors
 are found.
 
 (E.g test mod67 shows this up.)
 
] 
[Avoid repeatedly loading GHC.Prim
[EMAIL PROTECTED]
 
 This patch changes HscTypes.lookupIfaceByModule.  The problem was that
 when compiling the 'base' package, we'd repeatedly reload GHC.Prim.
 This is easily fixed by looking in the PIT too. A comment with
 lookupIfaceByModule explains
 
] 
[Print the 'skipping' messages at verbosity level 1
[EMAIL PROTECTED] 
[Fix up the typechecking of interface files during --make
[EMAIL PROTECTED]
 
 This patch fixes Trac #909.  The problem was that when compiling 
 the base package, the handling of wired-in things wasn't right;
 in TcIface.tcWiredInTyCon it repeatedly loaded GHC.Base.hi into the
 PIT, even though that was the very module it was compiling.
 
 The main fix is by introducing TcIface.ifCheckWiredInThing.
 
 But I did some minor refactoring as well.
 
] 
[Import trimming
[EMAIL PROTECTED] 
[Figure out where the rest of the repositories are, based on defaultrepo
Simon Marlow <[EMAIL PROTECTED]>**20061006100049
 This is a slight improvement over the patch sent by [EMAIL PROTECTED],
 we now do it properly if the source repo was a GHC tree on the local
 filesystem too.
 
 Merge post 6.6.
] 
[Yet another fix to mkAtomicArgs (for floating of casts)
[EMAIL PROTECTED]
 
 Comment Note [Take care] explains.
 
 mkAtomicArgs is a mess.  A substantial rewrite of Simplify is needed.
 
] 
[Improve comments and error tracing
[EMAIL PROTECTED] 
[Improve error message
[EMAIL PROTECTED] 
[Undo an accidentally-committed  patch by Audrey
[EMAIL PROTECTED] 
[Merge Haddock comment support from ghc.haddock -- big patch
[EMAIL PROTECTED] 
[Remove casts from lvalues to allow compilation under GCC 4.0
[EMAIL PROTECTED] 
[Correct the float-coercions-out-of-let patch
[EMAIL PROTECTED] 
[Merge changes
Ian Lynagh <[EMAIL PROTECTED]>**20061005150630] 
[Improve the correlation betweens documented and existent options
Ian Lynagh <[EMAIL PROTECTED]>**20061003220354] 
[Document -dfaststring-stats
Ian Lynagh <[EMAIL PROTECTED]>**20061003154147] 
[Rearrange docs to have all the -ddump-* options together
Ian Lynagh <[EMAIL PROTECTED]>**20061003153422] 
[Remove unused option -femit-extern-decls
Ian Lynagh <[EMAIL PROTECTED]>**20061003145854] 
[Documentation updates
Ian Lynagh <[EMAIL PROTECTED]>**20061003142658] 
[Fix typo
Ian Lynagh <[EMAIL PROTECTED]>**20061003121926] 
[More bootstrapping updates
Ian Lynagh <[EMAIL PROTECTED]>**20061005145629] 
[TAG 2006-10-05
Lemmih <[EMAIL PROTECTED]>**20061005150234] 
Patch bundle hash:
fa53e459e7e593c251d23491513f28d70bcc3643
_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to