Thu Aug 28 17:03:31 CEST 2008 [EMAIL PROTECTED]
* Fix linkage on OpenBSD.
New patches:
[Fix linkage on OpenBSD.
[EMAIL PROTECTED] hunk ./compiler/Makefile 153
-COMMON_CONFIGURE_FLAGS += --ld-options="-Xlinker -E"
+COMMON_CONFIGURE_FLAGS += --ld-options=-E
Context:
[Improve documentation of stolen syntax
[EMAIL PROTECTED]
This patch adds a section that summarises what syntax is stolen by
which flags. The section is at the end of the "syntactic extensions"
section of the manual.
]
[Fix Trac #2529: derived read for prefix constructor operators
[EMAIL PROTECTED]
[Fix Trac #745: improve error recoevery for type signatures
[EMAIL PROTECTED]
It turns out that fixing Trac #745 is easy using mapAndRecoverM,
and tidies up the code nicely in several places. Hurrah.
]
[Fix Trac #2538: better error messages when validating types
[EMAIL PROTECTED]
This fix solely concerns error messages, and uses a bit of contextual
information to suggest plausible flags.
It was rather more fiddly to implement than I expected. Oh well.
]
[Fix Trac #2520: duplicate symbols
[EMAIL PROTECTED]
The problem here was that were were quantifying over an *External* Name,
which causes no end of confusion. See Note [Const rule dicts] in DsBinds.
The fix is very easy, I'm happy to say.
]
[Only specialise on dictionaries that have some interesting structure
[EMAIL PROTECTED]
I discovered by accident that we were generating utterly useless
specialisations. See Note [Interesting dictionary arguments] in Specialise.
This patch used SimplUtils.interestingArg to restrict specialisation to
cases where the dictionary acutally has some information to give us.
]
[Better documentation for -XLiberalTypeSynonyms, and steal forall keyword
[EMAIL PROTECTED]
In my travels through the front end I discoverd that -XLiberalTypeSynonyms is
rather thinly described. Furthermore, it alleges that you can write a
forall on the RHS of a type synonym decl, so that means it should enable
the forall keyword.
]
[re-fix of #1205, fix #2542
Simon Marlow <[EMAIL PROTECTED]>**20080827102414
New form of :load in GHCi:
> :load *A
forces A to be loaded as byte-code. See the manual for details. The
previous behaviour for specifying filenames vs. module names on the
command line and in :load has been restored.
The Target datatype has a new Bool field, which is True if the target
is allowed to be loaded from compiled code, or False otherwise, so
this functionality is available via the GHC API. guessTarget
understands the *-prefix form for specifying targets.
]
[Improve documentation of MagicHash and primitive types generally (Trac #2547)
[EMAIL PROTECTED]
[Give locations of flag warnings/errors
Ian Lynagh <[EMAIL PROTECTED]>**20080826185641]
[Remove a now-redundant comment
Ian Lynagh <[EMAIL PROTECTED]>**20080826182629]
[Separate the static flag parser from the static global variables
Ian Lynagh <[EMAIL PROTECTED]>**20080826155612
This allows us to avoid a module import loop:
CmdLineParser -> SrcLoc -> Outputable -> StaticFlags -> CmdLineParser
]
[Move pprFastFilePath from SrcLoc to Outputable
Ian Lynagh <[EMAIL PROTECTED]>**20080826144452]
[Fix flaggery for RULES (cf Trac #2497)
[EMAIL PROTECTED]
This patch executes the plan described in the discussion in Trac #2497.
Specficially:
* Inside a RULE, switch on the forall-as-keyword in the lexer,
unconditionally. (Actually this is done by an earlier patch.)
* Merge the -XScopedTypeVariables and -XPatternSignatures flags,
and deprecate the latter. Distinguishing them isn't senseless,
but it's jolly confusing.
* Inside a RULE, switch on -XScopedTypeVariables unconditionally.
* Change -frewrite-rules to -fenable-rewrite-rules; deprecate the former.
Internally the DynFlag is now Opt_EnableRewriteRules.
There's a test in typecheck/should_compile/T2497.hs
]
[always treat 'forall' and '.' as reserved keywords inside RULES pragmas
Simon Marlow <[EMAIL PROTECTED]>**20080820132911]
[Fix a nasty float-in bug
[EMAIL PROTECTED]
This is a long-standing bug in FloatIn, which I somehow managed to
tickle (it's actually surprisingly hard to provoke which is why
it has not shown up before).
The problem was that we had a specialisation like this:
let
f_spec = ...
in let
{-# RULE f Int = f_spec #-}
f = ...
in
<body>
The 'f_spec' binding was being floated inside the binding for 'f',
which makes the RULE invalid becuase 'f_spec' isn't in scope.
We just need to add the free variables of the RULE in the right
places...
]
[Make rule printing wobble less
[EMAIL PROTECTED]
a) When generating specialisations, include the types in the name
of the rule, to avoid having rules with duplicate names.
(The rule name is used to put rules in canonical order for
fingerprinting.)
b) In Specialise and SpecConstr use a new function Rules.pprRulesForUser
to print rules in canonical order. This reduces unnecessary wobbling
in test output, notably in T2486
]
[syb is now in its own package
Ian Lynagh <[EMAIL PROTECTED]>**20080825214124]
[Fix "runghc foo" where the program is foo.hs or foo.lhs
Ian Lynagh <[EMAIL PROTECTED]>**20080825194352]
[When making bindists, check that we know where we are
Ian Lynagh <[EMAIL PROTECTED]>**20080825190912]
[Fix the ghci script; fixes trac #2485
Ian Lynagh <[EMAIL PROTECTED]>**20080825183247]
[Update .darcs-boring for the new libraries, plus some other odds and ends
Ian Lynagh <[EMAIL PROTECTED]>**20080825154249]
[Read the packages file in strictly in darcs-all and push-all
Ian Lynagh <[EMAIL PROTECTED]>**20080825145908
This fixes a problem where darcs tries to update it while perl has it
open. On Windows this fails. Spotted by Claus Reinke.
]
[Remove the InstallShield directory; it is no longer used
Ian Lynagh <[EMAIL PROTECTED]>**20080825143356]
[Remove the now-unused WindowsInstaller directory
Ian Lynagh <[EMAIL PROTECTED]>**20080825143214]
[Set datadir=libdir; fixes trac #2541
Ian Lynagh <[EMAIL PROTECTED]>**20080825141653
GHC needs package.conf and things like unlit to be in the same place
]
[Get everything building with base 4 in the HEAD
Ian Lynagh <[EMAIL PROTECTED]>**20080825120907
Some things were using the base3 compat library.
]
[Change references to the old BIN_DIST_TARBALL to the new BIN_DIST_TAR_BZ2
Ian Lynagh <[EMAIL PROTECTED]>**20080824233821]
[Fix the "have we got all the bootlibs" check
Ian Lynagh <[EMAIL PROTECTED]>**20080824175106
The packages file has an extra component (for "darcs" or "git") so we need
to take that into account when grepping.
]
[concurrent, unique, timeout have now been split off from base
Ian Lynagh <[EMAIL PROTECTED]>**20080824135052]
[Actually tar up Windows bindists
Ian Lynagh <[EMAIL PROTECTED]>**20080824135032]
[getopt is now split off from base
Ian Lynagh <[EMAIL PROTECTED]>**20080824020156]
[st is now split off from base
Ian Lynagh <[EMAIL PROTECTED]>**20080823222941]
[Ignore install-docs in compiler/Makefile and ghc/Makefile
Ian Lynagh <[EMAIL PROTECTED]>**20080821231349]
[Fix making bindists
Ian Lynagh <[EMAIL PROTECTED]>**20080821223537
We were looking for executable things, but not requiring that they were
files. So we were adding lots of directories (and thus their contents)
to the bindists, massively inflating their size.
]
[mk/cabal.mk now turns on -Wall
Ian Lynagh <[EMAIL PROTECTED]>**20080821173102]
[Fix warnings in runghc
Ian Lynagh <[EMAIL PROTECTED]>**20080821173051]
[Make some utils -Wall clean
Ian Lynagh <[EMAIL PROTECTED]>**20080821153914]
[unix is now warning-free
Ian Lynagh <[EMAIL PROTECTED]>**20080821120128]
[Fix references to exceptions from the RTS
Ian Lynagh <[EMAIL PROTECTED]>**20080821110620
We now need to make sure that they have been toException'd.
Also, the RTS doesn't know about the Deadlock exception any more.
]
[It doesn't look like HSprel.def is used any more
Ian Lynagh <[EMAIL PROTECTED]>**20080821105914]
[base (and base3-compat) is no warning-free
Ian Lynagh <[EMAIL PROTECTED]>**20080821001608]
[Don't put symlinks in bindists, but the files they point at instead
Ian Lynagh <[EMAIL PROTECTED]>**20080820134141]
[Fix making it possible to build without the NCG
Ian Lynagh <[EMAIL PROTECTED]>**20080818202845
If
GhcWithNativeCodeGen = NO
then we don't build the NCG modules, and we define OMIT_NATIVE_CODEGEN
]
[Comment fix
Ian Lynagh <[EMAIL PROTECTED]>**20080817210851]
[Remove GHC_TOP; we don't actually use it
Ian Lynagh <[EMAIL PROTECTED]>**20080817210226]
[We need to give make some more clues
Ian Lynagh <[EMAIL PROTECTED]>**20080817140005
Otherwise it can't work out how to make in ghc/ any more.
]
[Change how we know whether or not we are validating
Ian Lynagh <[EMAIL PROTECTED]>**20080817123311
We now set Validating=YES in mk/are-validating.mk rather than on the
commandline. This means that if you build a tree with validate then
just running make in it will use the validate flags.
"make distclean" removes mk/are-validating.mk, putting us back in
standard build mode.
]
[Don't clean the multi-stage stuff unless CLEAN_ALL_STAGES is YES
Ian Lynagh <[EMAIL PROTECTED]>**20080817121000]
[When making in compiler/, automatically make in ghc/ when we are done
Ian Lynagh <[EMAIL PROTECTED]>**20080817114202]
[Don't do the stage1 re-linking hack if we have GHC >= 6.9
Ian Lynagh <[EMAIL PROTECTED]>**20080817114132]
[Avoid scary "Package contains no library to register" message in installPackage
Ian Lynagh <[EMAIL PROTECTED]>**20080817113128
We only call register if we actually have a library to be registered
]
[Don't use the cc-options from packages when compiling .hc files
Simon Marlow <[EMAIL PROTECTED]>**20080821155549
Now that we don't include any header files in .hc apart from our own,
the cc-options from packages are at best superfluous, so don't pass
them.
We still pass them to .c compilations, although I've just made changes
to Cabal so that cc-options from a .cabal file are not copied into the
InstalledPackageInfo. Most uses of cc-options in Cabal are clearly
intended to be local to the package, but they were being propagated
everywhere, almost certainly unintentionally.
The way is left open for Cabal to allow packages to specify cc-options
that get propagated in the future, if we find a use case for this.
]
[Improve error message when 'forall' is not a keyword
[EMAIL PROTECTED]
[move directory after Win32/unix
Simon Marlow <[EMAIL PROTECTED]>**20080821100436]
[Fix Haddock comments in TcGenDeriv
[EMAIL PROTECTED]
[Fix compacting GC on 64-bit machines
Simon Marlow <[EMAIL PROTECTED]>**20080820125446
Some old experimental change leaked in with the parallel GC patches,
it seems
]
[Fix Trac #2456: eliminate duplicate bindings when deriving
[EMAIL PROTECTED]
Condsider deriving two overlapping Data declarations for the same type
deriving instance Data (T A)
deriving instance Data (T B)
We were getting duplicate bindings for the data-con and tycon auxiliary
bindings for T. This patch fixes the problem by doing these two decls
the same way as we do con2tag etc.
(Why might you want such instances; see Trac #2456.)
]
[Elaborate for-all message slightly
[EMAIL PROTECTED]
[set $(BOOTSTRAPPING_PACKAGE_CONF_HC_OPTS) automatically based on $(HC)
Simon Marlow <[EMAIL PROTECTED]>**20080819101437
This fixes nofib
]
[Fix Trac #2518: add hs-boot files as an infelicty
[EMAIL PROTECTED]
[use System.FilePath's isSearchPathSeparator instead of our own
Simon Marlow <[EMAIL PROTECTED]>**20080818113555]
[FIX #2521: trailing colon in GHC_PACKAGE_PATH
Simon Marlow <[EMAIL PROTECTED]>**20080818113345
This was broken in the System.FilePath switchover, since filepath's
splitSearchPath doesn't do what we want (it ignores empty
components on Windows, and treats them as "." on Unix). So we use our
own hand-rolled version, just like GHC.
]
[Test for and reject duplicate dependencies (#2330)
Simon Marlow <[EMAIL PROTECTED]>**20080818112434]
[When doing :l, abandon all breakpoints before we unload everything
Ian Lynagh <[EMAIL PROTECTED]>**20080816152135
I'm not 100% sure if this is the right fix, but it seems sensible and
stops break008 segfaulting for me on amd64/Linux.
]
[Comment fixes; trac #2468
Ian Lynagh <[EMAIL PROTECTED]>**20080816130910]
[Stop dph/dph-{par,seq} reconfiguring themselves all the time
Ian Lynagh <[EMAIL PROTECTED]>**20080814173013]
[Follow changes in Cabal
Ian Lynagh <[EMAIL PROTECTED]>**20080813215844]
[When distcleaning in utils/, distclean (rather then merely clean) the utils
Ian Lynagh <[EMAIL PROTECTED]>**20080815114939]
[Only clean utils/pwd/pwd when distcleaning, not when cleaning
Ian Lynagh <[EMAIL PROTECTED]>**20080812232544
Otherwise "make clean" in utils leaves us without a pwd, and lots of bad
things happen.
]
[In cabal.mk, clean is no longer identical to distclean
Ian Lynagh <[EMAIL PROTECTED]>**20080812232446
distclean will now also remove files listed in EXTRA_DISTCLEAN
]
[Improve -fwarn-orphans documentation (thanks to Tim)
[EMAIL PROTECTED]
[Fix #2441 (unregister/expose/hide packages in non-first package databases)
Simon Marlow <[EMAIL PROTECTED]>**20080814125348]
[add --no-user-package-conf
Simon Marlow <[EMAIL PROTECTED]>**20080814125312]
[move INPLACE_DATA_DIR into mk/config.mk and share it
Simon Marlow <[EMAIL PROTECTED]>**20080813144707]
[FIX #1963: use Cabal's writeFileAtomic to write the new package.conf
Simon Marlow <[EMAIL PROTECTED]>**20080813143738
This depends on #2298 also being fixed, which I'll do shortly
]
[FIX #2492: ghc-pkg insists on having HOME environment variable set
Simon Marlow <[EMAIL PROTECTED]>**20080813143436]
[FIX #2491 (ghc-pkg unregister should complain about breaking dependent packages)
Simon Marlow <[EMAIL PROTECTED]>**20080813142555]
[put back -fwarn-depcrecations
Simon Marlow <[EMAIL PROTECTED]>**20080812141606
It was replaced by -fwarn-warnings-deprecations, but I think we want
to keep it for backwards compatibility. I'm not sure we want to
deprecate it either...
]
[add special globbing file for Windows to ghc-pkg.cabal
[EMAIL PROTECTED]
[Improve error message for deprecated flags (Trac #2513)
[EMAIL PROTECTED]
[Improve docs for orphan decls (thanks Yitzchak Gale)
[EMAIL PROTECTED]
[fix cut-and-pasto
Simon Marlow <[EMAIL PROTECTED]>**20080811144158]
[build base3-compat
Simon Marlow <[EMAIL PROTECTED]>**20080811143831]
[Don't warn if 'import Prelude' doesn't import anything
Simon Marlow <[EMAIL PROTECTED]>**20080805133702
... even if Prelude doesn't come from the base package (it might come from
a old backwards-compatible version of base, for example).
]
[Add -XPackageImports, new syntax for package-qualified imports
Simon Marlow <[EMAIL PROTECTED]>**20080805133544
Now you can say
import "network" Network.Socket
and get Network.Socket from package "network", even if there are
multiple Network.Socket modules in scope from different packages
and/or the current package.
This is not really intended for general use, it's mainly so that we
can build backwards-compatible versions of packages, where we need to
be able to do
module GHC.Base (module New.GHC.Base) where
import "base" GHC.Base as New.GHC.Base
]
[Suppress uniques when (and only when) we have -dsuppress-uniques
[EMAIL PROTECTED]
[get exception names from Control.Exception.Base instead of Control.Exception
Ross Paterson <[EMAIL PROTECTED]>**20080812122048]
[Fix Trac #2490: sections should be parenthesised
[EMAIL PROTECTED]
When I added bang patterns I had to slightly generalise where the
parser would recognise sections. See Note [Parsing sections] in
parser.y.pp.
I forgot to check that ordinary H98 sections obey the original
rules. This patch adds the check.
]
[Refactoring: define TcRnMonad.failWith and use it in the renamer
[EMAIL PROTECTED]
[Layout only
[EMAIL PROTECTED]
[Use dph-{seq|par} instead of dph_{seq|par}
Roman Leshchinskiy <[EMAIL PROTECTED]>**20080812021939]
[Simplify how we build dph
Ian Lynagh <[EMAIL PROTECTED]>**20080809203803]
[Generalise libraries/Makefile.local
Ian Lynagh <[EMAIL PROTECTED]>**20080809161838
It's now possible to build libraries in, e.g.,
libraries/foo/bar
rather than just
libraries/foo
]
[The dph packages still contain warnings
Ian Lynagh <[EMAIL PROTECTED]>**20080809161815]
[Print tidy rules in user style, to avoid gratuitous uniques
[EMAIL PROTECTED]
The uniques that come out in dumpStyle make it harder to compare
output in the testsuite. And the rules are tidied, so uniques
are not necessary. If you want the uniques, use -dppr-debug.
]
[Export Depth (needed for mkUserStyle); collapse identical PrintUnqualified, QueryQualifies
[EMAIL PROTECTED]
[When suppressing uniques, don't print the separating underscore
[EMAIL PROTECTED]
[Make -dsuppress-uniques apply regardless of -ppr-debug
[EMAIL PROTECTED]
[Fix Trac #2367: selectors for GADTs
[EMAIL PROTECTED]
The generation of record selectors for GADTs and the like was
pretty screwed up. This patch fixes it.
Note that Unify.refineType is now used only in the generation of
record seletctors -- but it really does seem to be needed there.
Thanks to Max for finding this bug.
]
[Mostly fix Trac #2431: make empty case acceptable to (most of) GHC
[EMAIL PROTECTED]
See the comments with Trac #2431. This patch makes an empty HsCase
acceptable to the renamer onwards. If you want to accept empty case
in Haskell source there's a little more to do: the ticket lists the
remaining tasks.
]
[Fix Trac #2412: type synonyms and hs-boot recursion
[EMAIL PROTECTED]
Max Bolingbroke found this awkward bug, which relates to the way in
which hs-boot files are handled.
--> HEADS UP: interface file format change: recompile everything!
When we import a type synonym, we want to *refrain* from looking at its
RHS until we've "tied the knot" in the module being compiled. (Reason:
the type synonym might ultimately loop back to the module being compiled.)
To achieve this goal we need to know the *kind* of the synonym without
looking at its RHS. And to do that we need its kind recorded in the interface
file.
I slightly refactored the way that the IfaceSyn data constructor
fields work, eliminating the previous tricky re-use of the same field
as either a type or a kind.
See Note [Synonym kind loop] in TcIface
]
[Fix Trac #2506: infix assert
[EMAIL PROTECTED]
[Use do-notation
[EMAIL PROTECTED]
[Fix Trac #2494: tcSimplifyRuleLhs
[EMAIL PROTECTED]
tcSimplifyRuleLhs is a cut-down constraint simplifier, intended for
use in RULE left-hand-sides. But it was written before implication
constraints, and the exmaple of this bug report shows that when higher
rank types are involved we need to be a bit cleverer.
The whole business of simplifying constraints on rule LHSs is a bit
of a hack; but for a good reason. See the comments with tcSimplifyRuleLhs.
This patch at least cures the crash.
]
[Make comparison on equalities work right (ie look at the types)
[EMAIL PROTECTED]
This patch makes
(s1~t1) == (s2~t2) iff s1==s2, t1==t2
The comparison and equality instances for Insts are really only
used in making the AvailEnv in TcSimplify, which equalities are
never put into, which is why we've gotten away with this for so long.
But I'm now using 'nub' in the error messages for equalities,
and in any case it makes sense to have the right equality!
]
[Minor refactoring; no functionality change
[EMAIL PROTECTED]
[Fix Trac #2486: restore the specialiser to a working state
[EMAIL PROTECTED]
In improving the specialiser's data reprsentaion, thus
Mon Apr 28 16:57:11 GMT Daylight Time 2008 [EMAIL PROTECTED]
* Fix Trac #1969: perfomance bug in the specialiser
I got the sense of a pair of filter functions back to front.
As a result, almost all specialisation opportunities were being
filtered out, and no specialisations were being generated.
Fortunately, dolio notice and reported Trac #2486. The fix is
simple: put the filters the right way roud.
]
[Remove a pointless use of $(HERE_ABS)/
Ian Lynagh <[EMAIL PROTECTED]>**20080810173237]
[Don't give the -d flag to rm; it goes wrong on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20080810173053]
[Add mk/bindist.mk
Ian Lynagh <[EMAIL PROTECTED]>**20080810150737]
[Remove references to the files that the RTS no longer knows about
Ian Lynagh <[EMAIL PROTECTED]>**20080810144740
Spotted by Simon
]
[We don't need to generate driver/package.conf any more; spotted by Simon
Ian Lynagh <[EMAIL PROTECTED]>**20080810144259]
[Remove inplace-datadir when cleaning
Ian Lynagh <[EMAIL PROTECTED]>**20080810144118]
[Remove driver/ghc; The Cabal package in ghc/ now makes a wrapper itself
Ian Lynagh <[EMAIL PROTECTED]>**20080810143655]
[Make "make clean" in ghc/ only clean the stage we want to clean
Ian Lynagh <[EMAIL PROTECTED]>**20080810142409]
[Make "make clean" in compiler/ only clean the stage we want to clean
Ian Lynagh <[EMAIL PROTECTED]>**20080810142026
If you "make clean" in the root then we still clean all stages
]
[Also clean pwd.hi and pwd.o
Ian Lynagh <[EMAIL PROTECTED]>**20080810140731]
[bindist fixes
Ian Lynagh <[EMAIL PROTECTED]>**20080810133925]
[bindists are now some way towards working
Ian Lynagh <[EMAIL PROTECTED]>**20080810005016]
[Use Cabal to build pwd
Ian Lynagh <[EMAIL PROTECTED]>**20080810002807]
[Move allM to MonadUtils
Max Bolingbroke <[EMAIL PROTECTED]>**20080807224853]
[Remove redundant fromIntegral calls
Max Bolingbroke <[EMAIL PROTECTED]>**20080807224333]
[Remove CoreSyn SOURCE imports
Max Bolingbroke <[EMAIL PROTECTED]>**20080807223718]
[Fixed performance bug in ext-core preprocessor
Tim Chevalier <[EMAIL PROTECTED]>**20080809002051
The Core preprocessor was rebuilding the type and data constructor environments every time it called the typechecker, which was horribly inefficient. Fixed.
]
[Fix darcs-all get
Ian Lynagh <[EMAIL PROTECTED]>**20080807203258]
[Fix errors with haddock 0.8
Ian Lynagh <[EMAIL PROTECTED]>**20080807131506]
[Document Name and expand it's API
Max Bolingbroke <[EMAIL PROTECTED]>**20080807122901]
[Follow OccName changes in Convert
Max Bolingbroke <[EMAIL PROTECTED]>**20080731120741]
[Use DynFlags.getMainFun in TcRnDriver
Max Bolingbroke <[EMAIL PROTECTED]>**20080731055210]
[Fix Vectorise after introduction of MonadThings
Max Bolingbroke <[EMAIL PROTECTED]>**20080731054813]
[Follow introduction of MkCore in VectUtils
Max Bolingbroke <[EMAIL PROTECTED]>**20080731054722]
[Fix VectMonad after introduction of MonadThings
Max Bolingbroke <[EMAIL PROTECTED]>**20080731054623]
[Minor refactorings in TcEnv
Max Bolingbroke <[EMAIL PROTECTED]>**20080731054437]
[Handle introduction of MkCore in DsMonad and expand API
Max Bolingbroke <[EMAIL PROTECTED]>**20080731054239]
[Add MkCore, holding general Core construction facilities
Max Bolingbroke <[EMAIL PROTECTED]>**20080731054128]
[Document HscTypes, refactor it somewhat, remove unused type and add MonadThings
Max Bolingbroke <[EMAIL PROTECTED]>**20080731054042]
[Use new RdrName export in RdrHsSyn
Max Bolingbroke <[EMAIL PROTECTED]>**20080731053731]
[Document CoreUtils
Max Bolingbroke <[EMAIL PROTECTED]>**20080731053542]
[Document Packages and a minor refactoring
Max Bolingbroke <[EMAIL PROTECTED]>**20080731053054]
[Document CoreSyn and expand its API
Max Bolingbroke <[EMAIL PROTECTED]>**20080731052941]
[Document IdInfo
Max Bolingbroke <[EMAIL PROTECTED]>**20080731052819]
[Document DynFlags and expand API
Max Bolingbroke <[EMAIL PROTECTED]>**20080731052653]
[Document OccName and expand it's API
Max Bolingbroke <[EMAIL PROTECTED]>**20080731052238]
[Follow Digraph changes in VectType
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012356]
[Follow OccName changes in VectBuiltIn
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012355]
[Document Util
Max Bolingbroke <[EMAIL PROTECTED]>**20080807115505]
[Document UniqSet
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012355]
[Document UniqFM and add listToUFM_C
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012355]
[Follow FastString changes in Pretty
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012354]
[Document Outputable
Max Bolingbroke <[EMAIL PROTECTED]>**20080807114806]
[Document FiniteMap
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012353]
[Document FastString and rename strLength to lengthLS
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012353]
[Add more functionality to Digraph and refactor it's interface somewhat, including adding a Graph ADT
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012353]
[Document TypeRep and follow OccName change
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012352]
[Document Type
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012352]
[Document TyCon
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012352]
[Document Coercion
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012351]
[Follow Digraph changes in TcTyDecls
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012351]
[Make IOEnv a MonadUnique
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012351]
[Follow TcEnv API addition in TcForeign
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012350]
[Follow Digraph changes in TcBinds
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012350]
[Follow OccName and MkCore changes in Inst
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012349]
[Document Rules
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012349]
[Follow Literal change in Simplify
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012349]
[Follow Digraph changes in OccurAnal
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012348]
[Follow Digraph changes in RnBinds and small refactoring
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012348]
[Document TysWiredIn and follow OccName changes
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012347]
[Follow OccName changes in TysPrim
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012347]
[Follow OccName changes in ParserCore
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012347]
[Follow Digraph changes in RegLiveness
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012346]
[Follow Digraph changes in RegAllocLinear.hs
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012346]
[Follow Digraph changes in AsmCodeGen
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012346]
[Document InteractiveEval and follow OccName change
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012345]
[Follow Digraph changes in GHC; patch from Max Bolingbroke
Ian Lynagh <[EMAIL PROTECTED]>**20080807112510]
[Expand ErrUtils api with another plain variant
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012344]
[Follow OccName changes and minor refactorings in TcIface
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012343]
[Follow Digraph changes in MkIface
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012343]
[Minor refactoring in RtClosureInspect
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012342]
[Handle optSrcSpanFileName in InteractiveUI
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012342]
[Handle introduction of MkCore in MatchLit
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012342]
[Handle introduction of MkCore in MatchCon
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012342]
[Handle introduction of MkCore in Match
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012341]
[Handle introduction of MkCore in DsUtils
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012341]
[Handle introduction of MkCore in DsMeta
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012340]
[Handle introduction of MkCore in DsListComp
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012340]
[Handle introduction of MkCore in DsForeign
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012340]
[Handle introduction of MkCore in DsExpr
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012340]
[Handle introduction of MkCore in DsBinds
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012339]
[Handle introduction of MkCore in DsArrows
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012339]
[Handle optSrcSpanFileName rename in Coverage
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012339]
[Document CgUtils, follow Digraph changes
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012337]
[Document UniqSupply
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012334]
[Document SrcLoc
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012334]
[Document RdrName and expand its API
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012334]
[Make Module Uniquable
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012332]
[Tweak comments in MkId and follow mkStringLit renaming
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012332]
[Document Literal, expand it's API and rename mkStringLit to mkMachString
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012331]
[Document Id
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012331]
[Split the Id related functions out from Var into Id, document Var and some of Id
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012330]
[Eq and Ord have moved into GHC.Classes
Ian Lynagh <[EMAIL PROTECTED]>**20080806161815]
[Move Int, Float and Double into ghc-prim:GHC.Types
Ian Lynagh <[EMAIL PROTECTED]>**20080806224359]
[Move Int, Float and Double into ghc-prim:GHC.Types
Ian Lynagh <[EMAIL PROTECTED]>**20080806191458]
[Prepare GHC for building with Git
Max Bolingbroke <[EMAIL PROTECTED]>**20080806210207
* New packages format lets you select source control system in use
* Packages file now includes root repo explicitly
* Scripts darcs-all and push-all updated for the new packages format only
* New sync-all script, intended for use after Git changeover and for buildbots right now
* Had to remove libraries/bootstrapping from tree since Git cannot track empty directories without a hack
* Determine checkout date with Git using Darcs fallback in aclocal.m4
]
[Add -fno-implicit-import-qualified (#2452)
Simon Marlow <[EMAIL PROTECTED]>**20080805151730
The flag is off by default, but GHCi turns it on (in Main.hs). For
GHCi it can be overriden on the command-line or using :set.
]
[in stage1, always rebuild Main.hs
Simon Marlow <[EMAIL PROTECTED]>**20080805133823
GHC 6.9+ can properly handle cross-package recompilation checking, but
older versions of GHC couldn't, so in stage1 we always rebuild
Main.hs. In other words, 'make' in ghc/ should do the right thing now.
]
[Ooops; lack of mk/confi.mk doesn't mean validate shouldn't run configure!
Ian Lynagh <[EMAIL PROTECTED]>**20080806113102]
[C# has moved to ghc-prim:GHC.Types
Ian Lynagh <[EMAIL PROTECTED]>**20080805220155]
[Move the Char datatype into ghc-prim
Ian Lynagh <[EMAIL PROTECTED]>**20080805195643]
[Move the [] definion from base to ghc-prim
Ian Lynagh <[EMAIL PROTECTED]>**20080805180624]
[Don't boot/configure if we are validating --no-clean
Ian Lynagh <[EMAIL PROTECTED]>**20080804214657]
[Remove the cgi package from extralibs
Ian Lynagh <[EMAIL PROTECTED]>**20080805125551
It has some sort of Error Monad using the old Exception type.
I'm not familiar with it enough to know what the right thing to do
for it with extensible exceptions is.
]
[Follow the tuple datatype movements
Ian Lynagh <[EMAIL PROTECTED]>**20080804155402]
[Don't make a "windows" flag in the Cabal file - os(windows) already exists!
Ian Lynagh <[EMAIL PROTECTED]>**20080804153430
Pointed out by Duncan Coutts
]
[Fix Trac #2449
[EMAIL PROTECTED]
Deriving isn't allowed in hs-boot files (says the user manual)
This patch checks properly instead of crashing!
]
[2nd try: remove lochash, it isn't needed (now)
Simon Marlow <[EMAIL PROTECTED]>**20080804125944]
[FIX BUILD on Windows
Simon Marlow <[EMAIL PROTECTED]>**20080804105740]
[Fix Trac #2467: decent warnings for orphan instances
[EMAIL PROTECTED]
This patch makes
* Orphan instances and rules obey -Werror
* They look nicer when printed
]
[Fix the bug part of Trac #1930
[EMAIL PROTECTED]
[Fix Trac #2433 (deriving Typeable)
[EMAIL PROTECTED]
[Fix Trac #2478
[EMAIL PROTECTED]
A minor glitch that shows up only when a data constructor has *both* a
"stupid theta" in the data type decl, *and* an existential type variable.
]
[Improve docs for GADTs
[EMAIL PROTECTED]
[Document -dsuppress-uniques
[EMAIL PROTECTED]
[UNDO: FIX #2375: remove oc->lochash completely, it apparently isn't used
Simon Marlow <[EMAIL PROTECTED]>**20080804111801]
[haddock fixes
Ian Lynagh <[EMAIL PROTECTED]>**20080803180330]
[Follow the move of assertError from Control.Exception to GHC.IOBase
Ian Lynagh <[EMAIL PROTECTED]>**20080803141146]
[Document PackageConfig
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012345]
[Document CoreSubst
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012338]
[Document CoreFVs
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012337]
[Document CmmZipUtil
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012335]
[Document VarSet
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012335]
[Document VarEnv
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012335]
[Document Unique
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012334]
[Document LazyUniqFM
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012354]
[Document FastTypes
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012353]
[Add some type signatures to RnNames
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012348]
[Comment only in IfaceENv
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012343]
[Document ZipCfg
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012336]
[Document MachOp
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012336]
[Document Dataflow
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012336]
[Document DFMonad
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012336]
[Document NameSet
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012333]
[Document NameEnv
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012333]
[Document Module
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012332]
[Document DataCon
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012316]
[Document BasicTypes
Max Bolingbroke <[EMAIL PROTECTED]>**20080731012306]
[Rename maybeTyConSingleCon to tyConSingleDataCon_maybe
Max Bolingbroke <[EMAIL PROTECTED]>**20080731010537]
[Ignore git files
Max Bolingbroke <[EMAIL PROTECTED]>**20080731010509]
[Fix ifBuildable
Ian Lynagh <[EMAIL PROTECTED]>**20080801141731]
[Update assertErrorName; assertError has moved to Control.Exception
Ian Lynagh <[EMAIL PROTECTED]>**20080801011028]
[Fix the catching of "IOEnv failure" with extensible extensions
Ian Lynagh <[EMAIL PROTECTED]>**20080731194252]
[Follow changes in the base library
Ian Lynagh <[EMAIL PROTECTED]>**20080731173354
TopHandler now uses the new extensible exceptions module, so we
need to interact with it using the new types.
]
[Add the Exception module to ghc.cabal
Ian Lynagh <[EMAIL PROTECTED]>**20080730213419]
[Fix building with extensible exceptions
Ian Lynagh <[EMAIL PROTECTED]>**20080730194508]
[Mark the ghc package as not exposed
Ian Lynagh <[EMAIL PROTECTED]>**20080730172124]
[Follow extensible exception changes
Ian Lynagh <[EMAIL PROTECTED]>**20080730120134]
[When raising NonTermination with the RTS, build the right value
Ian Lynagh <[EMAIL PROTECTED]>**20080621144528
We now use a nonTermination value in the base library to take take of
constructing the SomeException value, with the dictionaries etc, for us.
We'll probably need to do the same for some other exceptions too
]
[Fix the way we pass GMP_INCLUDE_DIRS to hsc2hs; spotted by Andres Loh
Ian Lynagh <[EMAIL PROTECTED]>**20080730114713
We were still building the flags in Haskell list syntax, but we now pass
the arguments directly rather than constructing a Haskell program with
them.
]
[workaround #2277: turn off the RTS timer when calling into editline
Simon Marlow <[EMAIL PROTECTED]>**20080730135918]
[FIX #2388: check that the operand fits before using the 'test' opcode
Simon Marlow <[EMAIL PROTECTED]>**20080730105231]
[oops, fix a small pessimisation made in previous refactoring
Simon Marlow <[EMAIL PROTECTED]>**20080730105203]
[FIX #2375: remove oc->lochash completely, it apparently isn't used
Simon Marlow <[EMAIL PROTECTED]>**20080730101252]
[Fix a typo in powerpc/Linux-only code; spotted by Jeroen Pulles
Ian Lynagh <[EMAIL PROTECTED]>**20080729214007]
[Add the runghc wrapper script
Ian Lynagh <[EMAIL PROTECTED]>**20080729211852]
[Make cabal-bin not do any building, even of Setup.hs, when it is asked to clean
Ian Lynagh <[EMAIL PROTECTED]>**20080729202410]
[Update the test in Makefile that we have all the boot libs
Ian Lynagh <[EMAIL PROTECTED]>**20080729201640]
[Update boot's test that we have all of the bootlibs
Ian Lynagh <[EMAIL PROTECTED]>**20080729201032]
[Make the push-all script complain about bad lines
Ian Lynagh <[EMAIL PROTECTED]>**20080729200613]
[Add some comments to packages/darcs-all
Ian Lynagh <[EMAIL PROTECTED]>**20080729151934]
[Remove ndp from libraries/Makefile. We now use dph instead.
Ian Lynagh <[EMAIL PROTECTED]>**20080729141917]
[Add dph to ./packages and darcs-all
Ian Lynagh <[EMAIL PROTECTED]>**20080729141850]
[Remove cabal-install from ./packages; we've decided not to build it
Ian Lynagh <[EMAIL PROTECTED]>**20080729141824]
[FIX #2327: a fault in the thunk-selector machinery (again)
Simon Marlow <[EMAIL PROTECTED]>**20080729150518
This program contains an expression of the form
let x = snd (_, snd (_, snd (_, x)))
(probably not explicitly, but that's what appears in the heap at
runtime). Obviously the program should deadlock if it ever enters
this thing, but apparently the test program in #2327 never does.
The GC tries to evaluate the snd closures, and gets confused due to
the loop. In particular the earlier fix for #1038 was to blame.
]
[FIX #2332: avoid overflow on 64-bit machines in the memory allocator
Simon Marlow <[EMAIL PROTECTED]>**20080729150459]
[Change the calling conventions for unboxed tuples slightly
Simon Marlow <[EMAIL PROTECTED]>**20080728155621
When returning an unboxed tuple with a single non-void component, we
now use the same calling convention as for returning a value of the
same type as that component. This means that the return convention
for IO now doesn't vary depending on the platform, which make some
parts of the RTS simpler, and fixes a problem I was having with making
the FFI work in unregisterised GHCi (the byte-code compiler makes
some assumptions about calling conventions to keep things simple).
]
[don't strip the inplace GHC executables (for debugging)
Simon Marlow <[EMAIL PROTECTED]>**20080728134647]
[Complete the changes for #1205
Simon Marlow <[EMAIL PROTECTED]>**20080728105141
Now ":load M" always searches for a module called "M", rather than
using a file called "M.hs" if that exists. To get the file semantics
(i.e. not loading "M.o"), use ":load M.hs".
]
[update the comments about how we find $topdir
Simon Marlow <[EMAIL PROTECTED]>**20080725151406]
[understand absolute pathnames on Windows too
Simon Marlow <[EMAIL PROTECTED]>**20080728102243]
[change where we put gcc-lib/ld.exe to keep Cabal happy
Simon Marlow <[EMAIL PROTECTED]>**20080728100852]
[move an inline function to keep older versions of gcc happy
Simon Marlow <[EMAIL PROTECTED]>**20080725144708
no idea why this only just showed up...
]
[try to fix the way we find $topdir
Simon Marlow <[EMAIL PROTECTED]>**20080725142828]
[for the installed versions, don't use dynamic-linking wrappers
Simon Marlow <[EMAIL PROTECTED]>**20080725134551]
[don't steal %ebx for the GC on x86: it's also used by PIC
Simon Marlow <[EMAIL PROTECTED]>**20080725122921]
[SRT labels don't need to be globally visible
Simon Marlow <[EMAIL PROTECTED]>**20080725080901
Saves space in the symbol table and speeds up linking
]
[Don't prematurely link shared libraries against the RTS package
Simon Marlow <[EMAIL PROTECTED]>**20080724155001
We want to be able to pick the RTS flavour (e.g. -threaded) when we
link the final program.
]
[add --enable-shared to configure, and $(BuildSharedLibs) to the build system
Simon Marlow <[EMAIL PROTECTED]>**20080724154925]
[use RTLD_LAZY instead of RTLD_NOW
Simon Marlow <[EMAIL PROTECTED]>**20080724152727
RTLD_NOW apparently causes some problems, according to previous
mailing-list discussion
http://www.haskell.org/pipermail/cvs-ghc/2007-September/038570.html
]
[debug output tweak
Simon Marlow <[EMAIL PROTECTED]>**20080724152636]
[small cleanup
Simon Marlow <[EMAIL PROTECTED]>**20080724151614]
[Fix building runghc on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20080724182831]
[Follow darcs-all changes in push-all
Ian Lynagh <[EMAIL PROTECTED]>**20080724164153]
[Rejig how darcs-all works
Ian Lynagh <[EMAIL PROTECTED]>**20080724164142
It's now easier to add new repos anywhere in the source tree
]
[Remove the OpenGL family of libraries from extralibs
Ian Lynagh <[EMAIL PROTECTED]>**20080724102736]
[compiler/package.conf.in is no longer used, so remove it
Ian Lynagh <[EMAIL PROTECTED]>**20080724101610]
[allow EXTRA_HC_OPTS to be used from the command-line
Simon Marlow <[EMAIL PROTECTED]>**20080724081728]
[put the inplace GHC in stageN-inplace/ghc instead of stageN-inplace/bin/ghc
Simon Marlow <[EMAIL PROTECTED]>**20080724080951
just saves a bit of typing
]
[add a "rebuild" target for convenience
Simon Marlow <[EMAIL PROTECTED]>**20080723143201]
[set PAPI_LIB_DIR="" when we don't have PAPI (clean up package.conf)
Simon Marlow <[EMAIL PROTECTED]>**20080722141327]
[remove -fvia-C that I apparrently accidentally added recently
Simon Marlow <[EMAIL PROTECTED]>**20080722141255]
[Fix a build error on powerpc/Linux; spotted by Jeroen Pulles
Ian Lynagh <[EMAIL PROTECTED]>**20080723191948]
[If the extension is not .lhs, runghc now treats it as .hs; fixes trac #1232
Ian Lynagh <[EMAIL PROTECTED]>**20080723182156]
[runghc now uses the compiler that it comes with; fixes trac #1281
Ian Lynagh <[EMAIL PROTECTED]>**20080723181115
rather than the first one that it finds on the PATH
]
[Use the upstream hsc2hs repo
Ian Lynagh <[EMAIL PROTECTED]>**20080723155021]
[Remove some redundancy in darcs-all
Ian Lynagh <[EMAIL PROTECTED]>**20080723143804]
[Tell Cabal where gcc is
Ian Lynagh <[EMAIL PROTECTED]>**20080723001202]
[Undo fix for #2185: sparks really should be treated as roots
Simon Marlow <[EMAIL PROTECTED]>**20080723125205
Unless sparks are roots, strategies don't work at all: all the sparks
get GC'd. We need to think about this some more.
]
[fix bug in sparkPoolSize (affects debug output only)
Simon Marlow <[EMAIL PROTECTED]>**20080723104322]
[debug message tweaks
Simon Marlow <[EMAIL PROTECTED]>**20080723090050]
[refactoring/tidyup: (not.is64BitInteger) -> is32BitInteger
Simon Marlow <[EMAIL PROTECTED]>**20080722092113]
[non-threaded RTS: don't assume deadlock if there are signal handlers to run
Simon Marlow <[EMAIL PROTECTED]>**20080715130316]
[update the text about header files and -#include
Simon Marlow <[EMAIL PROTECTED]>**20080715101119]
[add NetBSD to some of the #ifdefs (patch partly from 6.8 branch)
Simon Marlow <[EMAIL PROTECTED]>**20080714145040]
[Warn about unrecognised pragmas; these often mean we've typoed
Ian Lynagh <[EMAIL PROTECTED]>**20080722235550]
[Sync hsc2hs's Main.hs with the Cabal repo
Ian Lynagh <[EMAIL PROTECTED]>**20080722203646]
[We need to clean the utils on "distclean", as well as "clean"
Ian Lynagh <[EMAIL PROTECTED]>**20080722170754]
[Clean stage 3
Ian Lynagh <[EMAIL PROTECTED]>**20080722170542]
[Add replacements for the -optdep flags, and deprecate the old ones
Ian Lynagh <[EMAIL PROTECTED]>**20080722163308]
[Fix the stage3 build
Ian Lynagh <[EMAIL PROTECTED]>**20080722125743]
[Fixes for haddock 0.8
Ian Lynagh <[EMAIL PROTECTED]>**20080721095256]
[haddock the stage2 compiler if HADDOCK_DOCS is YES
Ian Lynagh <[EMAIL PROTECTED]>**20080720220622]
[First step for getting rid of the old -optdep flags
Ian Lynagh <[EMAIL PROTECTED]>**20080720203239
They are now handled by the main flag parser, rather than having their
own praser that runs later.
As an added bonus, 5 global variables are also gone.
]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720173151]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720173117]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720173105]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720173017]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720172614]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720172401]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720172242]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720172222]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720172139]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720172114]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720172054]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720172010]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720171723]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720171554]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720171529]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720171424]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720171113]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720170708]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720170601]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720170421]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720165845]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720165637]
[Fix Haddock errors.
Thomas Schilling <[EMAIL PROTECTED]>**20080720164133]
[Properly comment out unused pragmas
Ian Lynagh <[EMAIL PROTECTED]>**20080720135604
We now say
-- {-# SPECIALIZE ...
rather than
{-# -- SPECIALIZE ...
]
[Add a WARNING pragma
Ian Lynagh <[EMAIL PROTECTED]>**20080720120918]
[Put a #! line in ghc-pkg's shell wrapper
Ian Lynagh <[EMAIL PROTECTED]>**20080719112544]
[Fix ghc-pkg inplace on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20080719002613]
[Some "install" and "clean" fixes
Ian Lynagh <[EMAIL PROTECTED]>**20080718223656]
[Change how inplace detection works, so that it also works on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20080718210836]
[More dependency wibbling
Ian Lynagh <[EMAIL PROTECTED]>**20080718193454]
[Build system tweaks
Ian Lynagh <[EMAIL PROTECTED]>**20080718184706]
[We need to make Parser.y and Config.hs earlier
Ian Lynagh <[EMAIL PROTECTED]>**20080718180441]
[Explicitly list HpcParser as a module in hpc-bin
Ian Lynagh <[EMAIL PROTECTED]>**20080718174657
Cabal doesn't preprocess the .y file otherwise.
]
[Disable building pwd and lndir for now
Ian Lynagh <[EMAIL PROTECTED]>**20080718170329]
[Build hpc with Cabal
Ian Lynagh <[EMAIL PROTECTED]>**20080718170047]
[Build runghc with Cabal
Ian Lynagh <[EMAIL PROTECTED]>**20080718165317]
[Add a comment
Ian Lynagh <[EMAIL PROTECTED]>**20080718154238]
[Tweak the build system for installPackage
Ian Lynagh <[EMAIL PROTECTED]>**20080718153956]
[More build system changes; hasktags is now built with Cabal
Ian Lynagh <[EMAIL PROTECTED]>**20080718153459]
[Remove a comment
Ian Lynagh <[EMAIL PROTECTED]>**20080718115044]
[More build system changes; ghc-pkg is now built with Cabal
Ian Lynagh <[EMAIL PROTECTED]>**20080718114753]
[Fix some argument names
Ian Lynagh <[EMAIL PROTECTED]>**20080717223543]
[Tweak the hsc2hs wrapper script
Ian Lynagh <[EMAIL PROTECTED]>**20080717194916]
[Fix the order in which things get built
Ian Lynagh <[EMAIL PROTECTED]>**20080717192402]
[Split building the ghc package and binary into "boot" and "all" steps
Ian Lynagh <[EMAIL PROTECTED]>**20080717150746
In "boot" we configure, and in "all" we do the actual building.
]
[Install the compiler during make install
Ian Lynagh <[EMAIL PROTECTED]>**20080717150453
For now we always install stage 2
]
[Do the building and installing of hsc2hs with the stage1 compiler
Ian Lynagh <[EMAIL PROTECTED]>**20080717150420]
[Remove some duplication
Ian Lynagh <[EMAIL PROTECTED]>**20080717144906]
[Windows fixes
Ian Lynagh <[EMAIL PROTECTED]>**20080716222719]
[Fix GHC finding extra-gcc-opts on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20080716222457]
[Fix the inplace compiler finding package.conf on Windows
Ian Lynagh <[EMAIL PROTECTED]>**20080716215000]
[Fix the build with GHC 6.4.2
Ian Lynagh <[EMAIL PROTECTED]>**20080716192836]
[Get building GHC itself with Cabal more-or-less working
Ian Lynagh <[EMAIL PROTECTED]>**20080716150441
Installing and bindist creation don't work, but they were already broken.
Only tested validating with one setup.
]
[TAG Before cabalised-GHC
Ian Lynagh <[EMAIL PROTECTED]>**20080719132217]
Patch bundle hash:
167c47325a9553f3ab0fa66dbb1a8435f948d868
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc