| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Most of the other users of the fptools build system have migrated to
Cabal, and with the move to darcs we can now flatten the source tree
without losing history, so here goes.
The main change is that the ghc/ subdir is gone, and most of what it
contained is now at the top level. The build system now makes no
pretense at being multi-project, it is just the GHC build system.
No doubt this will break many things, and there will be a period of
instability while we fix the dependencies. A straightforward build
should work, but I haven't yet fixed binary/source distributions.
Changes to the Building Guide will follow, too.
|
| |
|
|
|
|
|
|
| |
I've changed the name to 'getGhcMode'. If someone changes
it back, please write an explanation above it.
|
| |
|
| |
|
| |
|
|
|
|
|
|
| |
This restructoring makes the renamed export and import lists
available in IDE mode.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add support for UTF-8 source files
GHC finally has support for full Unicode in source files. Source
files are now assumed to be UTF-8 encoded, and the full range of
Unicode characters can be used, with classifications recognised using
the implementation from Data.Char. This incedentally means that only
the stage2 compiler will recognise Unicode in source files, because I
was too lazy to port the unicode classifier code into libcompat.
Additionally, the following synonyms for keywords are now recognised:
forall symbol (U+2200) forall
right arrow (U+2192) ->
left arrow (U+2190) <-
horizontal ellipsis (U+22EF) ..
there are probably more things we could add here.
This will break some source files if Latin-1 characters are being used.
In most cases this should result in a UTF-8 decoding error. Later on
if we want to support more encodings (perhaps with a pragma to specify
the encoding), I plan to do it by recoding into UTF-8 before parsing.
Internally, there were some pretty big changes:
- FastStrings are now stored in UTF-8
- Z-encoding has been moved right to the back end. Previously we
used to Z-encode every identifier on the way in for simplicity,
and only decode when we needed to show something to the user.
Instead, we now keep every string in its UTF-8 encoding, and
Z-encode right before printing it out. To avoid Z-encoding the
same string multiple times, the Z-encoding is cached inside the
FastString the first time it is requested.
This speeds up the compiler - I've measured some definite
improvement in parsing at least, and I expect compilations overall
to be faster too. It also cleans up a lot of cruft from the
OccName interface. Z-encoding is nicely hidden inside the
Outputable instance for Names & OccNames now.
- StringBuffers are UTF-8 too, and are now represented as
ForeignPtrs.
- I've put together some test cases, not by any means exhaustive,
but there are some interesting UTF-8 decoding error cases that
aren't obvious. Also, take a look at unicode001.hs for a demo.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add a new pragma: SPECIALISE INLINE
This amounts to adding an INLINE pragma to the specialised version
of the function. You can add phase stuff too (SPECIALISE INLINE [2]),
and NOINLINE instead of INLINE.
The reason for doing this is to support inlining of type-directed
recursive functions. The main example is this:
-- non-uniform array type
data Arr e where
ArrInt :: !Int -> ByteArray# -> Arr Int
ArrPair :: !Int -> Arr e1 -> Arr e2 -> Arr (e1, e2)
(!:) :: Arr e -> Int -> e
{-# SPECIALISE INLINE (!:) :: Arr Int -> Int -> Int #-}
{-# SPECIALISE INLINE (!:) :: Arr (a, b) -> Int -> (a, b) #-}
ArrInt _ ba !: (I# i) = I# (indexIntArray# ba i)
ArrPair _ a1 a2 !: i = (a1 !: i, a2 !: i)
If we use (!:) at a particular array type, we want to inline (:!),
which is recursive, until all the type specialisation is done.
On the way I did a bit of renaming and tidying of the way that
pragmas are carried, so quite a lot of files are touched in a
fairly trivial way.
|
|
|
|
| |
Simplify Provenance (the LocalDef constructor) a little
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
MERGE TO STABLE
Fix a long-standing bug in dependency tracking.
If you have
import M( x )
then you must recompile if M's export list changes, because it might
no longer export x. Until now we have only done that if the import was
import M
I can't think why this bug has lasted so long. Thanks to Ian Lynagh
for pointing it out.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
WARNING: this is a big commit. You might want
to wait a few days before updating, in case I've
broken something.
However, if any of the changes are what you wanted,
please check it out and test!
This commit does three main things:
1. A re-organisation of the way that GHC handles bindings in HsSyn.
This has been a bit of a mess for quite a while. The key new
types are
-- Bindings for a let or where clause
data HsLocalBinds id
= HsValBinds (HsValBinds id)
| HsIPBinds (HsIPBinds id)
| EmptyLocalBinds
-- Value bindings (not implicit parameters)
data HsValBinds id
= ValBindsIn -- Before typechecking
(LHsBinds id) [LSig id] -- Not dependency analysed
-- Recursive by default
| ValBindsOut -- After typechecking
[(RecFlag, LHsBinds id)]-- Dependency analysed
2. Implement Mark Jones's idea of increasing polymoprhism
by using type signatures to cut the strongly-connected components
of a recursive group. As a consequence, GHC no longer insists
on the contexts of the type signatures of a recursive group
being identical.
This drove a significant change: the renamer no longer does dependency
analysis. Instead, it attaches a free-variable set to each binding,
so that the type checker can do the dep anal. Reason: the typechecker
needs to do *two* analyses:
one to find the true mutually-recursive groups
(which we need so we can build the right CoreSyn)
one to find the groups in which to typecheck, taking
account of type signatures
3. Implement non-ground SPECIALISE pragmas, as promised, and as
requested by Remi and Ross. Certainly, this should fix the
current problem with GHC, namely that if you have
g :: Eq a => a -> b -> b
then you can now specialise thus
SPECIALISE g :: Int -> b -> b
(This didn't use to work.)
However, it goes further than that. For example:
f :: (Eq a, Ix b) => a -> b -> b
then you can make a partial specialisation
SPECIALISE f :: (Eq a) => a -> Int -> Int
In principle, you can specialise f to *any* type that is
"less polymorphic" (in the sense of subsumption) than f's
actual type. Such as
SPECIALISE f :: Eq a => [a] -> Int -> Int
But I haven't tested that.
I implemented this by doing the specialisation in the typechecker
and desugarer, rather than leaving around the strange SpecPragmaIds,
for the specialiser to find. Indeed, SpecPragmaIds have vanished
altogether (hooray).
Pragmas in general are handled more tidily. There's a new
data type HsBinds.Prag, which lives in an AbsBinds, and carries
pragma info from the typechecker to the desugarer.
Smaller things
- The loop in the renamer goes via RnExpr, instead of RnSource.
(That makes it more like the type checker.)
- I fixed the thing that was causing 'check_tc' warnings to be
emitted.
|
|
|
|
| |
Comments
|
|
|
|
| |
rename exportsFromAvail
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Tune up the reporting of unused imports
Merge to STABLE
(I think the earlier change made it across)
(PS: the commit also does some trimming of
redundant imports. If they don't merge, just
discard them.)
My earlier fixes to the reporting of unused imports still missed
some obscure cases, some of which are now fixed by this commit.
I had to make the import-provenance data type yet richer, but in
fact it has more sharing now, so it may be cheaper on space.
There's still one infelicity. Consider
import M( x )
imoprt N( x )
where the same underlying 'x' is involved in both cases. Currently we
don't report a redundant import, because dropping either import would
change the qualified names in scope (M.x, N.x). But if the qualified
names aren't used, the import is indeed redundant. Sadly we don't know
that, because we only know what Names are used. Left for the future!
There's a comment in RnNames.warnDuplicateImports
This commit also trims quite a few redundant imports disovered
by the new setup.
|
|
|
|
|
|
|
|
|
| |
Two small things
a) report duplicate declarations in canonical order
b) report deprecations for all uses (a longstanding bug)
both MERGE TO STABLE
|
|
|
|
| |
Further wibbles to unused-import reporting; merge to stable
|
|
|
|
| |
Second stab at the duplicate-import warnings
|
|
|
|
|
|
|
|
|
| |
Improve generation of 'duplicate import' warnings.
This involved changing (actually simplifying) the
definition of RdrName.ImportSpec.
I'm not sure whether this one merits merging or not.
Perhaps worth a try.
|
|
|
|
|
|
|
|
|
| |
Fix the test for duplicate local bindings, so that it works with
Template Haskell. Pre-TH, all the local bindings came into scope
at once, but with TH they come into scope in groups, and we must
check for conflict with existing local bindings.
MERGE TO STABLE
|
|
|
|
|
|
|
|
|
| |
Re-plumb the connections between TidyPgm and the various
code generators. There's a new type, CgGuts, to mediate this,
which has the happy effect that ModGuts can die earlier.
The non-O route still isn't quite right, because default methods
are being lost. I'm working on it.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This big commit does several things at once (aeroplane hacking)
which change the format of interface files.
So you'll need to recompile your libraries!
1. The "stupid theta" of a newtype declaration
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Retain the "stupid theta" in a newtype declaration.
For some reason this was being discarded, and putting it
back in meant changing TyCon and IfaceSyn slightly.
2. Overlap flags travel with the instance
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Arrange that the ability to support overlap and incoherence
is a property of the *instance declaration* rather than the
module that imports the instance decl. This allows a library
writer to define overlapping instance decls without the
library client having to know.
The implementation is that in an Instance we store the
overlap flag, and preseve that across interface files
3. Nuke the "instnce pool" and "rule pool"
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
A major tidy-up and simplification of the way that instances
and rules are sucked in from interface files. Up till now
an instance decl has been held in a "pool" until its "gates"
(a set of Names) are in play, when the instance is typechecked
and added to the InstEnv in the ExternalPackageState.
This is complicated and error-prone; it's easy to suck in
too few (and miss an instance) or too many (and thereby be
forced to suck in its type constructors, etc).
Now, as we load an instance from an interface files, we
put it straight in the InstEnv... but the Instance we put in
the InstEnv has some Names (the "rough-match" names) that
can be used on lookup to say "this Instance can't match".
The detailed dfun is only read lazily, and the rough-match
thing meansn it is'nt poked on until it has a chance of
being needed.
This simply continues the successful idea for Ids, whereby
they are loaded straightaway into the TypeEnv, but their
TyThing is a lazy thunk, not poked on until the thing is looked
up.
Just the same idea applies to Rules.
On the way, I made CoreRule and Instance into full-blown records
with lots of info, with the same kind of key status as TyCon or
DataCon or Class. And got rid of IdCoreRule altogether.
It's all much more solid and uniform, but it meant touching
a *lot* of modules.
4. Allow instance decls in hs-boot files
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Allowing instance decls in hs-boot files is jolly useful, becuase
in a big mutually-recursive bunch of data types, you want to give
the instances with the data type declarations. To achieve this
* The hs-boot file makes a provisional name for the dict-fun, something
like $fx9.
* When checking the "mother module", we check that the instance
declarations line up (by type) and generate bindings for the
boot dfuns, such as
$fx9 = $f2
where $f2 is the dfun generated by the mother module
* In doing this I decided that it's cleaner to have DFunIds get their
final External Name at birth. To do that they need a stable OccName,
so I have an integer-valued dfun-name-supply in the TcM monad.
That keeps it simple.
This feature is hardly tested yet.
5. Tidy up tidying, and Iface file generation
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
main/TidyPgm now has two entry points:
simpleTidyPgm is for hi-boot files, when typechecking only
(not yet implemented), and potentially when compiling without -O.
It ignores the bindings, and generates a nice small TypeEnv.
optTidyPgm is the normal case: compiling with -O. It generates a
TypeEnv rich in IdInfo
MkIface.mkIface now only generates a ModIface. A separate
procedure, MkIface.writeIfaceFile, writes the file out to disk.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Significant clean-up of the handling of hi-boot files.
Previously, when compling A.hs, we loaded A.hi-boot, and
it went into the External Package Table. It was strange
but it worked. This tidy up stops it going anywhere;
it's just read in, and typechecked into a ModDetails.
All this was on the way to improving the handling of
instances in hs-boot files, something Chris Ryder wanted.
I think they work quite sensibly now.
If I've got all this right (have not had a chance to
fully test it) we can merge it into STABLE.
|
|
|
|
|
|
|
| |
Tweaks to get the GHC sources through Haddock. Doesn't quite work
yet, because Haddock complains about the recursive modules. Haddock
needs to understand SOURCE imports (it can probably just ignore them
as a first attempt).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Flags cleanup.
Basically the purpose of this commit is to move more of the compiler's
global state into DynFlags, which is moving in the direction we need
to go for the GHC API which can have multiple active sessions
supported by a single GHC instance.
Before:
$ grep 'global_var' */*hs | wc -l
78
After:
$ grep 'global_var' */*hs | wc -l
27
Well, it's an improvement. Most of what's left won't really affect
our ability to host multiple sessions.
Lots of static flags have become dynamic flags (yay!). Notably lots
of flags that we used to think of as "driver" flags, like -I and -L,
are now dynamic. The most notable static flags left behind are the
"way" flags, eg. -prof. It would be nice to fix this, but it isn't
urgent.
On the way, lots of cleanup has happened. Everything related to
static and dynamic flags lives in StaticFlags and DynFlags
respectively, and they share a common command-line parser library in
CmdLineParser. The flags related to modes (--makde, --interactive
etc.) are now private to the front end: in fact private to Main
itself, for now.
|
|
|
|
| |
Fix what looks like a typo in the previous commit
|
|
|
|
| |
Avoid losing location info for ghci; please merge
|
|
|
|
| |
Comments
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------
Improve unused-import warnings
------------------------------
Merge to STABLE
This commit improves the warning messages for unused imports, in the
case where the 'module A' form is used in an export list.
In doing this, I've realised that the unused-import checking is deficient
in several ways. At least
a) it doesn't recognise that there might be several import statements
for the same module (TcRnTypes.imp_mods has only one entry per
module
b) it doesn't understand about qualified modules at all
c) even more fundamentally, it starts from the used Names,
but if the module mentions (say) aliases M.f and N.f for
the same Name, then two imports might be necessary for it
I'm not going to fix these problems now; this message just records them.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------------
Replace hi-boot files with hs-boot files
--------------------------------------------
This major commit completely re-organises the way that recursive modules
are dealt with.
* It should have NO EFFECT if you do not use recursive modules
* It is a BREAKING CHANGE if you do
====== Warning: .hi-file format has changed, so if you are
====== updating into an existing HEAD build, you'll
====== need to make clean and re-make
The details: [documentation still to be done]
* Recursive loops are now broken with Foo.hs-boot (or Foo.lhs-boot),
not Foo.hi-boot
* An hs-boot files is a proper source file. It is compiled just like
a regular Haskell source file:
ghc Foo.hs generates Foo.hi, Foo.o
ghc Foo.hs-boot generates Foo.hi-boot, Foo.o-boot
* hs-boot files are precisely a subset of Haskell. In particular:
- they have the same import, export, and scoping rules
- errors (such as kind errors) in hs-boot files are checked
You do *not* need to mention the "original" name of something in
an hs-boot file, any more than you do in any other Haskell module.
* The Foo.hi-boot file generated by compiling Foo.hs-boot is a machine-
generated interface file, in precisely the same format as Foo.hi
* When compiling Foo.hs, its exports are checked for compatibility with
Foo.hi-boot (previously generated by compiling Foo.hs-boot)
* The dependency analyser (ghc -M) knows about Foo.hs-boot files, and
generates appropriate dependencies. For regular source files it
generates
Foo.o : Foo.hs
Foo.o : Baz.hi -- Foo.hs imports Baz
Foo.o : Bog.hi-boot -- Foo.hs source-imports Bog
For a hs-boot file it generates similar dependencies
Bog.o-boot : Bog.hs-boot
Bog.o-boot : Nib.hi -- Bog.hs-boto imports Nib
* ghc -M is also enhanced to use the compilation manager dependency
chasing, so that
ghc -M Main
will usually do the job. No need to enumerate all the source files.
* The -c flag is no longer a "compiler mode". It simply means "omit the
link step", and synonymous with -no-link.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------
Reorganisation of hi-boot files
------------------------
The main point of this commit is to arrange that in the Compilation
Manager's dependendency graph, hi-boot files are proper nodes. This
is important to make sure that we compile everything in the right
order. It's a step towards hs-boot files.
* The fundamental change is that CompManager.ModSummary has a new
field, ms_boot :: IsBootInterface
I also tided up CompManager a bit. No change to the Basic Plan.
ModSummary is now exported abstractly from CompManager (was concrete)
* Hi-boot files now have import declarations. The idea is they are
compulsory, so that the dependency analyser can find them
* I changed an invariant: the Compilation Manager used to ensure that
hscMain was given a HomePackageTable only for the modules 'below' the
one being compiled. This was really only important for instances and
rules, and it was a bit inconvenient. So I moved the filter to the
compiler itself: see HscTypes.hptInstances and hptRules.
* Module Packages.hs now defines
data PackageIdH
= HomePackage -- The "home" package is the package
-- curently being compiled
| ExtPackage PackageId -- An "external" package is any other package
It was just a Maybe type before, so this makes it a bit clearer.
* I tried to add a bit better location info to the IfM monad, so that
errors in interfaces come with a slightly more helpful error message.
See the if_loc field in TcRnTypes --- and follow-on consequences
* Changed Either to Maybes.MaybeErr in a couple of places (more perspicuous)
|
|
|
|
|
|
|
|
|
|
|
|
| |
Sorry for the fact that there are overlapping three commits in here...
1. Make -fno-monomorphism-restriction
and -fno-implicit-prelude reversible, like other flags
2. Fix a wibble in the new ImportAvails story, in RnNames.mkExportAvails
3. Fix a Template Haskell bug that meant that top-level names created
with newName were not made properly unique.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
---------------------
Simplify ImportAvails
---------------------
Every Name has, for some while, contained its "parent";
the type or class inside which it is defined. But the rest
of the renamer wasn't using this information as much as it
could do. In particular, the ImportAvails type was more elaborate
than necessary.
This commit combines these two fields of ImportAvails:
imp_env :: AvailEnv
imp_qual :: ModuleEnv AvailEnv
into one
imp_env :: ModuleEnv NameSet
This is quite a bit simpler. Less redundancy and, I think, less
code.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Further integration with the new package story. GHC now supports
pretty much everything in the package proposal.
- GHC now works in terms of PackageIds (<pkg>-<version>) rather than
just package names. You can still specify package names without
versions on the command line, as long as the name is unambiguous.
- GHC understands hidden/exposed modules in a package, and will refuse
to import a hidden module. Also, the hidden/eposed status of packages
is taken into account.
- I had to remove the old package syntax from ghc-pkg, backwards
compatibility isn't really practical.
- All the package.conf.in files have been rewritten in the new syntax,
and contain a complete list of modules in the package. I've set all
the versions to 1.0 for now - please check your package(s) and fix the
version number & other info appropriately.
- New options:
-hide-package P sets the expose flag on package P to False
-ignore-package P unregisters P for this compilation
For comparison, -package P sets the expose flag on package P
to True, and also causes P to be linked in eagerly.
-package-name is no longer officially supported. Unofficially, it's
a synonym for -ignore-package, which has more or less the same effect
as -package-name used to.
Note that a package may be hidden and yet still be linked into
the program, by virtue of being a dependency of some other package.
To completely remove a package from the compiler's internal database,
use -ignore-package.
The compiler will complain if any two packages in the
transitive closure of exposed packages contain the same
module.
You *must* use -ignore-package P when compiling modules for
package P, if package P (or an older version of P) is already
registered. The compiler will helpfully complain if you don't.
The fptools build system does this.
- Note: the Cabal library won't work yet. It still thinks GHC uses
the old package config syntax.
Internal changes/cleanups:
- The ModuleName type has gone away. Modules are now just (a
newtype of) FastStrings, and don't contain any package information.
All the package-related knowledge is in DynFlags, which is passed
down to where it is needed.
- DynFlags manipulation has been cleaned up somewhat: there are no
global variables holding DynFlags any more, instead the DynFlags
are passed around properly.
- There are a few less global variables in GHC. Lots more are
scheduled for removal.
- -i is now a dynamic flag, as are all the package-related flags (but
using them in {-# OPTIONS #-} is Officially Not Recommended).
- make -j now appears to work under fptools/libraries/. Probably
wouldn't take much to get it working for a whole build.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
---------------------------------
Fix a bug in usage recording
---------------------------------
As a result of the new stuff on hi-boot-file consistency checking, I
accidentally caused Foo.hi to record a usage line for module Foo, and
this in turn caused rather nasty bad things to happen. In particular,
there were occasional crashes of form
ghc-6.3: panic! (the `impossible' happened, GHC version 6.3.20041017):
forkM Constructor Var.TcTyVar{d r1B9}
At least I think that's why the crash happened.
Anyway, it was certainly a bug, and this commit fixes it. The main
payload of this fix is in Desugar.lhs; the rest is comments and
tidying.
|
|
|
|
| |
Better reporting of duplicate top-level defns
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------
Simplify the treatment of newtypes
Complete hi-boot file consistency checking
------------------------------------
In the representation of types, newtypes used to have a special constructor
all to themselves, very like TyConApp, called NewTcApp. The trouble is
that means we have to *know* when a newtype is a newtype, and in an hi-boot
context we may not -- the data type might be declared as
data T
in the hi-boot file, but as
newtype T = ...
in the source file. In GHCi, which accumulates stuff from multiple compiles,
this makes a difference.
So I've nuked NewTcApp. Newtypes are represented using TyConApps again. This
turned out to reduce the total amount of code, and simplify the Type data type,
which is all to the good.
This commit also fixes a few things in the hi-boot consistency checking
stuff.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-----------------------------------
Do simple checking on hi-boot files
-----------------------------------
This commit arranges that, when compiling A.hs, we compare
the types we infer with those in A.hi-boot, if the latter
exists. (Or, more accurately, if anything A.hs imports in
turn imports A.hi-boot, directly or indirectly.)
This has been on the to-do list forever.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------
Add Generalised Algebraic Data Types
------------------------------------
This rather big commit adds support for GADTs. For example,
data Term a where
Lit :: Int -> Term Int
App :: Term (a->b) -> Term a -> Term b
If :: Term Bool -> Term a -> Term a
..etc..
eval :: Term a -> a
eval (Lit i) = i
eval (App a b) = eval a (eval b)
eval (If p q r) | eval p = eval q
| otherwise = eval r
Lots and lots of of related changes throughout the compiler to make
this fit nicely.
One important change, only loosely related to GADTs, is that skolem
constants in the typechecker are genuinely immutable and constant, so
we often get better error messages from the type checker. See
TcType.TcTyVarDetails.
There's a new module types/Unify.lhs, which has purely-functional
unification and matching for Type. This is used both in the typechecker
(for type refinement of GADTs) and in Core Lint (also for type refinement).
|
|
|
|
| |
Make error messages consistent
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------
Print built-in sytax right
-------------------------------
Built-in syntax, like (:) and [], is not "in scope" via the GlobalRdrEnv
in the usual way. When we print it out, we should also print it in unqualified
form, even though it's not in the environment.
I've finally bitten the (not very big) bullet, and added to Name the information
about whether or not a name is one of these built-in ones. That entailed changing
the calls to mkWiredInName, but those are exactly the places where you have to
decide whether it's built-in or not, which is fine.
Built-in syntax => It's a syntactic form, not "in scope" (e.g. [])
Wired-in thing => The thing (Id, TyCon) is fully known to the compiler,
not read from an interface file.
E.g. Bool, True, Int, Float, and many others
All built-in syntax is for wired-in things.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------
Use merge-sort not quicksort
Nuke quicksort altogether
-------------------------------
Quicksort has O(n**2) behaviour worst case, and this occasionally bites.
In particular, when compiling large files consisting only of static data,
we get loads of top-level delarations -- and that led to more than half the
total compile time being spent in the strongly connected component analysis
for the occurrence analyser. Switching to merge sort completely solved the
problem.
I've nuked quicksort altogether to make sure this does not happen again.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------
Add instance information to :i
Get rid of the DeclPool
-------------------------------
1. Add instance information to :info command. GHCi now prints out
which instances a type or class belongs to, when you use :i
2. Tidy up printing of unqualified names in user output.
Previously Outputable.PrintUnqualified was
type PrintUnqualified = Name -> Bool
but it's now
type PrintUnqualified = ModuleName -> OccName -> Bool
This turns out to be tidier even for Names, and it's now also usable
when printing IfaceSyn stuff in GHCi, eliminating a grevious hack.
3. On the way to doing this, Simon M had the great idea that we could
get rid of the DeclPool holding pen, which held declarations read from
interface files but not yet type-checked. We do this by eagerly
populating the TypeEnv with thunks what, when poked, do the type
checking. This is just a logical continuation of lazy import
mechanism we've now had for some while.
The InstPool and RulePool still exist, but I plan to get rid of them in
the same way. The new scheme does mean that more rules get sucked in than
before, because previously the TypeEnv was used to mean "this thing was needed"
and hence to control which rules were sucked in. But now the TypeEnv is
populated more eagerly => more rules get sucked in. However this problem
will go away when I get rid of the Inst and Rule pools.
I should have kept these changes separate, but I didn't. Change (1)
affects mainly
TcRnDriver, HscMain, CompMan, InteractiveUI
whereas change (3) is more wide ranging.
|
|
|
|
|
|
|
|
| |
-----------------------------------------------
Improve reporting of TH reify out-of-scope errors
-----------------------------------------------
No change to functionality, just better error reports.
|
|
|
|
| |
Renamed Opt_WarnMisc to Opt_WarnDodgyImports
|
|
|
|
|
|
|
|
|
| |
-----------------------------------------------
Improve location info on unused-import warnings
-----------------------------------------------
Improving the location involves plumbing the location of the import a bit
more assiduously -- hence change to imp_mods in TcRnTypes
|
|
|
|
|
|
| |
In multiple declaration errors, give the location of one of the
declarations as the location of the error message, instead of the
top-level of the file.
|
|
|
|
| |
White space
|
|
|
|
| |
Back out hiding change -- hiding should hide the qualified name too
|
|
|
|
|
|
|
| |
Fix a long-standing bug, whereby 'hiding' hid the qualified name as
well as the unqualified one.
This bug is not as easy to fix in the 6.2 branch, unfortunately; don't merge.
|