| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------
GHC heart/lung transplant
-------------------------
This major commit changes the way that GHC deals with importing
types and functions defined in other modules, during renaming and
typechecking. On the way I've changed or cleaned up numerous other
things, including many that I probably fail to mention here.
Major benefit: GHC should suck in many fewer interface files when
compiling (esp with -O). (You can see this with -ddump-rn-stats.)
It's also some 1500 lines of code shorter than before.
** So expect bugs! I can do a 3-stage bootstrap, and run
** the test suite, but you may be doing stuff I havn't tested.
** Don't update if you are relying on a working HEAD.
In particular, (a) External Core and (b) GHCi are very little tested.
But please, please DO test this version!
------------------------
Big things
------------------------
Interface files, version control, and importing declarations
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* There is a totally new data type for stuff that lives in interface files:
Original names IfaceType.IfaceExtName
Types IfaceType.IfaceType
Declarations (type,class,id) IfaceSyn.IfaceDecl
Unfoldings IfaceSyn.IfaceExpr
(Previously we used HsSyn for type/class decls, and UfExpr for unfoldings.)
The new data types are in iface/IfaceType and iface/IfaceSyn. They are
all instances of Binary, so they can be written into interface files.
Previous engronkulation concering the binary instance of RdrName has
gone away -- RdrName is not an instance of Binary any more. Nor does
Binary.lhs need to know about the ``current module'' which it used to,
which made it specialised to GHC.
A good feature of this is that the type checker for source code doesn't
need to worry about the possibility that we might be typechecking interface
file stuff. Nor does it need to do renaming; we can typecheck direct from
IfaceSyn, saving a whole pass (module TcIface)
* Stuff from interface files is sucked in *lazily*, rather than being eagerly
sucked in by the renamer. Instead, we use unsafeInterleaveIO to capture
a thunk for the unfolding of an imported function (say). If that unfolding
is every pulled on, TcIface will scramble over the unfolding, which may
in turn pull in the interface files of things mentioned in the unfolding.
The External Package State is held in a mutable variable so that it
can be side-effected by this lazy-sucking-in process (which may happen
way later, e.g. when the simplifier runs). In effect, the EPS is a kind
of lazy memo table, filled in as we suck things in. Or you could think
of it as a global symbol table, populated on demand.
* This lazy sucking is very cool, but it can lead to truly awful bugs. The
intent is that updates to the symbol table happen atomically, but very bad
things happen if you read the variable for the table, and then force a
thunk which updates the table. Updates can get lost that way. I regret
this subtlety.
One example of the way it showed up is that the top level of TidyPgm
(which updates the global name cache) to be much more disciplined about
those updates, since TidyPgm may itself force thunks which allocate new
names.
* Version numbering in interface files has changed completely, fixing
one major bug with ghc --make. Previously, the version of A.f changed
only if A.f's type and unfolding was textually different. That missed
changes to things that A.f's unfolding mentions; which was fixed by
eagerly sucking in all of those things, and listing them in the module's
usage list. But that didn't work with --make, because they might have
been already sucked in.
Now, A.f's version changes if anything reachable from A.f (via interface
files) changes. A module with unchanged source code needs recompiling
only if the versions of any of its free variables changes. [This isn't
quite right for dictionary functions and rules, which aren't mentioned
explicitly in the source. There are extensive comments in module MkIface,
where all version-handling stuff is done.]
* We don't need equality on HsDecls any more (because they aren't used in
interface files). Instead we have a specialised equality for IfaceSyn
(eqIfDecl etc), which uses IfaceEq instead of Bool as its result type.
See notes in IfaceSyn.
* The horrid bit of the renamer that tried to predict what instance decls
would be needed has gone entirely. Instead, the type checker simply
sucks in whatever instance decls it needs, when it needs them. Easy!
Similarly, no need for 'implicitModuleFVs' and 'implicitTemplateHaskellFVs'
etc. Hooray!
Types and type checking
~~~~~~~~~~~~~~~~~~~~~~~
* Kind-checking of types is far far tidier (new module TcHsTypes replaces
the badly-named TcMonoType). Strangely, this was one of my
original goals, because the kind check for types is the Right Place to
do type splicing, but it just didn't fit there before.
* There's a new representation for newtypes in TypeRep.lhs. Previously
they were represented using "SourceTypes" which was a funny compromise.
Now they have their own constructor in the Type datatype. SourceType
has turned back into PredType, which is what it used to be.
* Instance decl overlap checking done lazily. Consider
instance C Int b
instance C a Int
These were rejected before as overlapping, because when seeking
(C Int Int) one couldn't tell which to use. But there's no problem when
seeking (C Bool Int); it can only be the second.
So instead of checking for overlap when adding a new instance declaration,
we check for overlap when looking up an Inst. If we find more than one
matching instance, we see if any of the candidates dominates the others
(in the sense of being a substitution instance of all the others);
and only if not do we report an error.
------------------------
Medium things
------------------------
* The TcRn monad is generalised a bit further. It's now based on utils/IOEnv.lhs,
the IO monad with an environment. The desugarer uses the monad too,
so that anything it needs can get faulted in nicely.
* Reduce the number of wired-in things; in particular Word and Integer
are no longer wired in. The latter required HsLit.HsInteger to get a
Type argument. The 'derivable type classes' data types (:+:, :*: etc)
are not wired in any more either (see stuff about derivable type classes
below).
* The PersistentComilerState is now held in a mutable variable
in the HscEnv. Previously (a) it was passed to and then returned by
many top-level functions, which was painful; (b) it was invariably
accompanied by the HscEnv. This change tidies up top-level plumbing
without changing anything important.
* Derivable type classes are treated much more like 'deriving' clauses.
Previously, the Ids for the to/from functions lived inside the TyCon,
but now the TyCon simply records their existence (with a simple boolean).
Anyone who wants to use them must look them up in the environment.
This in turn makes it easy to generate the to/from functions (done
in types/Generics) using HsSyn (like TcGenDeriv for ordinary derivings)
instead of CoreSyn, which in turn means that (a) we don't have to figure
out all the type arguments etc; and (b) it'll be type-checked for us.
Generally, the task of generating the code has become easier, which is
good for Manuel, who wants to make it more sophisticated.
* A Name now says what its "parent" is. For example, the parent of a data
constructor is its type constructor; the parent of a class op is its
class. This relationship corresponds exactly to the Avail data type;
there may be other places we can exploit it. (I made the change so that
version comparison in interface files would be a bit easier; but in
fact it tided up other things here and there (see calls to
Name.nameParent). For example, the declaration pool, of declararations
read from interface files, but not yet used, is now keyed only by the 'main'
name of the declaration, not the subordinate names.
* New types OccEnv and OccSet, with the usual operations.
OccNames can be efficiently compared, because they have uniques, thanks
to the hashing implementation of FastStrings.
* The GlobalRdrEnv is now keyed by OccName rather than RdrName. Not only
does this halve the size of the env (because we don't need both qualified
and unqualified versions in the env), but it's also more efficient because
we can use a UniqFM instead of a FiniteMap.
Consequential changes to Provenance, which has moved to RdrName.
* External Core remains a bit of a hack, as it was before, done with a mixture
of HsDecls (so that recursiveness and argument variance is still inferred),
and IfaceExprs (for value declarations). It's not thoroughly tested.
------------------------
Minor things
------------------------
* DataCon fields dcWorkId, dcWrapId combined into a single field
dcIds, that is explicit about whether the data con is a newtype or not.
MkId.mkDataConWorkId and mkDataConWrapId are similarly combined into
MkId.mkDataConIds
* Choosing the boxing strategy is done for *source* type decls only, and
hence is now in TcTyDecls, not DataCon.
* WiredIn names are distinguished by their n_sort field, not by their location,
which was rather strange
* Define Maybes.mapCatMaybes :: (a -> Maybe b) -> [a] -> [b]
and use it here and there
* Much better pretty-printing of interface files (--show-iface)
Many, many other small things.
------------------------
File changes
------------------------
* New iface/ subdirectory
* Much of RnEnv has moved to iface/IfaceEnv
* MkIface and BinIface have moved from main/ to iface/
* types/Variance has been absorbed into typecheck/TcTyDecls
* RnHiFiles and RnIfaces have vanished entirely. Their
work is done by iface/LoadIface
* hsSyn/HsCore has gone, replaced by iface/IfaceSyn
* typecheck/TcIfaceSig has gone, replaced by iface/TcIface
* typecheck/TcMonoType has been renamed to typecheck/TcHsType
* basicTypes/Var.hi-boot and basicTypes/Generics.hi-boot have gone altogether
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- Convert many of the optimisation options into dynamic options (that is,
they can be mentioned in {-# OPTIONS #-} pragmas).
- Add a new way to specify constructor-field unboxing on a selective
basis. To tell the compiler to unbox a constructor field, do this:
data T = T !!Int
and GHC will store that field unboxed if possible. If it isn't possible
(say, because the field has a sum type) then the annotation is ignored.
The -funbox-strict-fields flag is now a dynamic flag, and has the same
effect as replacing all the '!' annotations with '!!'.
|
|
|
|
| |
Comment only
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------------
Improve the "unused binding" warnings
-------------------------------------
We've had a succession of hacks for reporting warnings for
unused bindings. Consider
module M( f ) where
f x = x
g x = g x + h x
h x = x
Here, g mentions itself and h, but is not itself mentioned. So
really both g and h are dead code. We've been getting this wrong
for ages, and every hack so far has failed on some simple programs.
This commit does a much better job. The renamer applied to a bunch
of bindings returns a NameSet.DefUses, which is a dependency-ordered
lists of def/use pairs. It's documented in NameSet.
Given this, we can work out precisely what is not used, in a nice
tidy way.
It's less convenient in the case of type and class declarations, because
the strongly-connected-component analysis can span module boundaries.
So things are pretty much as they were for these.
As usual, there was a lot of chuffing around tidying things up.
I havn't tested it at all thoroughly yet.
Various unrelated import-decl-pruning has been done too.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------------
Two minor wibbles
-------------------------------------
1. Make the generic toT/fromT Ids for "generic derived classes" into
proper ImplicitIds, with their own GlobalIdDetails. This makes it
easier to identify them. (The lack of this showed up as a bug
when I made an apparently-innocuous other change.)
2. Distinguish ClassOpIds from RecordSelIds in their GlobalIdDetails.
They are treated differently here and there, so I made this change
as part of (1)
3. Ensure that a declaration quotation [d| ... |] does not have a
permanent effect on the instance environment. (A TH fix.)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------------
Big upheaval to the way that constructors are named
-------------------------------------
This commit enshrines the new story for constructor names. We could never
really get External Core to work nicely before, but now it does.
The story is laid out in detail in the Commentary
ghc/docs/comm/the-beast/data-types.html
so I will not repeat it here.
[Manuel: the commentary isn't being updated, apparently.]
However, the net effect is that in Core and in External Core, contructors look
like constructors, and the way things are printed is all consistent.
It is a fairly pervasive change (which is why it has been so long postponed),
but I hope the question is now finally closed.
All the libraries compile etc, and I've run many tests, but doubtless there will
be some dark corners.
|
|
|
|
| |
Use nameIsLocalOrFrom instead of open code
|
|
|
|
| |
Import trimming
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------
More dependency fiddling
------------------------
WARNING: Interface file format has changed (again)
You need to 'make clean' in all library code
* Orphan modules are now kept separately
Home-package dependencies now contain only home-package dependencies!
See HscTypes.Dependencies
* Linker now uses the dependencies to do dynamic linking
Result: Template Haskell should work even without --make (not yet tested)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------------
1. New try and module and package dependencies
2. OrigNameCache always contains final info
------------------------------------------
These things nearly complete sorting out the incremental
linking problem that started us off!
1. This commit separates two kinds of information:
(a) HscTypes.Dependencies:
What (i) home-package modules, and
(ii) other packages
this module depends on, transitively.
That is, to link the module, it should be enough
to link the dependent modules and packages (plus
any C stubs etc).
Along with this info we record whether the dependent module
is (a) a boot interface or (b) an orphan module. So in
fact (i) can contain non-home-package modules, namely the
orphan ones in other packages (sigh).
(b) HscTypes.Usage:
What version of imported things were used to
actually compile the module. This info is used for
recompilation control only.
2. The Finder now returns a correct Module (incl package indicator)
first time, so we can install the absolutely final Name in the
OrigNameCache when we first come across an occurrence of that name,
even if it's only an occurrence in an unfolding in some other interface
file. This is much tidier.
As a result Module.lhs is much cleaner
No DunnoYet
No mkVanillaModule
ALl very joyful stuff.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-----------------------------------
Lots more Template Haskell stuff
-----------------------------------
At last! Top-level declaration splices work!
Syntax is
$(f x)
not "splice (f x)" as in the paper.
Lots jiggling around, particularly with the top-level plumbining.
Note the new data type HsDecls.HsGroup.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------
Make Template Haskell into the HEAD
--------------------------------------
This massive commit transfers to the HEAD all the stuff that
Simon and Tim have been doing on Template Haskell. The
meta-haskell-branch is no more!
WARNING: make sure that you
* Update your links if you are using link trees.
Some modules have been added, some have gone away.
* Do 'make clean' in all library trees.
The interface file format has changed, and you can
get strange panics (sadly) if GHC tries to read old interface files:
e.g. ghc-5.05: panic! (the `impossible' happened, GHC version 5.05):
Binary.get(TyClDecl): ForeignType
* You need to recompile the rts too; Linker.c has changed
However the libraries are almost unaltered; just a tiny change in
Base, and to the exports in Prelude.
NOTE: so far as TH itself is concerned, expression splices work
fine, but declaration splices are not complete.
---------------
The main change
---------------
The main structural change: renaming and typechecking have to be
interleaved, because we can't rename stuff after a declaration splice
until after we've typechecked the stuff before (and the splice
itself).
* Combine the renamer and typecheker monads into one
(TcRnMonad, TcRnTypes)
These two replace TcMonad and RnMonad
* Give them a single 'driver' (TcRnDriver). This driver
replaces TcModule.lhs and Rename.lhs
* The haskell-src library package has a module
Language/Haskell/THSyntax
which defines the Haskell data type seen by the TH programmer.
* New modules:
hsSyn/Convert.hs converts THSyntax -> HsSyn
deSugar/DsMeta.hs converts HsSyn -> THSyntax
* New module typecheck/TcSplice type-checks Template Haskell splices.
-------------
Linking stuff
-------------
* ByteCodeLink has been split into
ByteCodeLink (which links)
ByteCodeAsm (which assembles)
* New module ghci/ObjLink is the object-code linker.
* compMan/CmLink is removed entirely (was out of place)
Ditto CmTypes (which was tiny)
* Linker.c initialises the linker when it is first used (no need to call
initLinker any more). Template Haskell makes it harder to know when
and whether to initialise the linker.
-------------------------------------
Gathering the LIE in the type checker
-------------------------------------
* Instead of explicitly gathering constraints in the LIE
tcExpr :: RenamedExpr -> TcM (TypecheckedExpr, LIE)
we now dump the constraints into a mutable varabiable carried
by the monad, so we get
tcExpr :: RenamedExpr -> TcM TypecheckedExpr
Much less clutter in the code, and more efficient too.
(Originally suggested by Mark Shields.)
-----------------
Remove "SysNames"
-----------------
Because the renamer and the type checker were entirely separate,
we had to carry some rather tiresome implicit binders (or "SysNames")
along inside some of the HsDecl data structures. They were both
tiresome and fragile.
Now that the typechecker and renamer are more intimately coupled,
we can eliminate SysNames (well, mostly... default methods still
carry something similar).
-------------
Clean up HsPat
-------------
One big clean up is this: instead of having two HsPat types (InPat and
OutPat), they are now combined into one. This is more consistent with
the way that HsExpr etc is handled; there are some 'Out' constructors
for the type checker output.
So:
HsPat.InPat --> HsPat.Pat
HsPat.OutPat --> HsPat.Pat
No 'pat' type parameter in HsExpr, HsBinds, etc
Constructor patterns are nicer now: they use
HsPat.HsConDetails
for the three cases of constructor patterns:
prefix, infix, and record-bindings
The *same* data type HsConDetails is used in the type
declaration of the data type (HsDecls.TyData)
Lots of associated clean-up operations here and there. Less code.
Everything is wonderful.
|
|
|
|
|
|
| |
seqList the result of mkImportInfo: this fixes a space leak whereby
the entire collection of Ifaces read by the renamer were being held on
to during the core-to-core phases.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------
Mainly derived Read
-------------------
This commit is a tangle of several things that somehow got wound up
together, I'm afraid.
The main course
~~~~~~~~~~~~~~~
Replace the derived-Read machinery with Koen's cunning new parser
combinator library. The result should be
* much smaller code sizes from derived Read
* faster execution of derived Read
WARNING: I have not thoroughly tested this stuff; I'd be glad if you did!
All the hard work is done, but there may be a few nits.
The Read class gets two new methods, not exposed
in the H98 inteface of course:
class Read a where
readsPrec :: Int -> ReadS a
readList :: ReadS [a]
readPrec :: ReadPrec a -- NEW
readListPrec :: ReadPrec [a] -- NEW
There are the following new libraries:
Text.ParserCombinators.ReadP Koens combinator parser
Text.ParserCombinators.ReadPrec Ditto, but with precedences
Text.Read.Lex An emasculated lexical analyser
that provides the functionality
of H98 'lex'
TcGenDeriv is changed to generate code that uses the new libraries.
The built-in instances of Read (List, Maybe, tuples, etc) use the new
libraries.
Other stuff
~~~~~~~~~~~
1. Some fixes the the plumbing of external-core generation. Sigbjorn
did most of the work earlier, but this commit completes the renaming and
typechecking plumbing.
2. Runtime error-generation functions, such as GHC.Err.recSelErr,
GHC.Err.recUpdErr, etc, now take an Addr#, pointing to a UTF8-encoded
C string, instead of a Haskell string. This makes the *calls* to these
functions easier to generate, and smaller too, which is a good thing.
In particular, it means that MkId.mkRecordSelectorId doesn't need to
be passed "unpackCStringId", which was GRUESOME; and that in turn means
that tcTypeAndClassDecls doesn't need to be passed unf_env, which is
a very worthwhile cleanup. Win/win situation.
3. GHC now faithfully translates do-notation using ">>" for statements
with no binding, just as the report says. While I was there I tidied
up HsDo to take a list of Ids instead of 3 (but now 4) separate Ids.
Saves a bit of code here and there. Also introduced Inst.newMethodFromName
to package a common idiom.
|
|
|
|
|
|
|
|
|
| |
Front end for External Core.
Initial go at implementing a Core front end
(enabled via -fcore); work in progress (renamer
is currently not willing to slurp in & resolve
imports.)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------
Change
GlobalName --> ExternalName
LocalName -> InternalName
------------------------
For a long time there's been terminological confusion between
GlobalName vs LocalName (property of a Name)
GlobalId vs LocalId (property of an Id)
I've now changed the terminology for Name to be
ExternalName vs InternalName
I've also added quite a bit of documentation in the Commentary.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
----------------------------------
Do the Right Thing for TyCons where we
can't see all their constructors.
----------------------------------
Inside a TyCon, three things can happen
1. GHC knows all the constructors, and has them to hand.
(Nowadays, there may be zero constructors.)
2. GHC knows all the constructors, but has declined to slurp
them all in, to avoid sucking in more declarations than
necessary. All we remember is the number of constructors,
so we can get the return convention right.
3. GHC doesn't know anything. This happens *only* for decls
coming from .hi-boot files, where the programmer declines to
supply a representation.
Until now, these three cases have been conflated together. Matters
are worse now that a TyCon really can have zero constructors. In
fact, by confusing (3) with (1) we can actually generate bogus code.
With this commit, the dataCons field of a TyCon is of type:
data DataConDetails datacon
= DataCons [datacon] -- Its data constructors, with fully polymorphic types
-- A type can have zero constructors
| Unknown -- We're importing this data type from an hi-boot file
-- and we don't know what its constructors are
| HasCons Int -- In a quest for compilation speed we have imported
-- only the number of constructors (to get return
-- conventions right) but not the constructors themselves
This says exactly what is going on. There are lots of consequential small
changes.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------------------
Slurp in a few more instance decls with ghc --make
--------------------------------------------------
ghc --make wasn't slurping in quite enough instance decls.
The relevant comment is in RnIfaces; the new part is marked.
George Russel's Uniform showed this up.
We slurp in an instance decl from the gated instance pool iff
all its gates are either in the gates of the module,
or are a previously-loaded tycon or class.
The latter constraint is because there might have been an instance
decl slurped in during an earlier compilation, like this:
instance Foo a => Baz (Maybe a) where ...
In the module being compiled we might need (Baz (Maybe T)), where T
is defined in this module, and hence we need (Foo T). So @Foo@ becomes
a gate. But there's no way to 'see' that.
NEW: More generally, types might be involved as well:
NEW: instance Foo2 T a => Baz2 a where ...
NEW:
NEW: Now we must treat T as a gate too, as well as Foo. So the solution
NEW: we adopt is:
NEW:
NEW: we simply treat all previously-loaded
NEW: tycons and classes as gates.
NEW:
NEW: This gloss only affects ghc --make and ghc --interactive.
|
|
|
|
| |
cosmetic only: reformat to 80 cols
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------------------
Be a bit more liberal when slurping instance decls
--------------------------------------------------
Functional dependencies have (as usual) made things more complicated
Suppose an interface file contains
interface A where
class C a b | a->b where op :: a->b
instance C Foo Baz where ...
Now we are compiling
module B where
import A
t = op (v::Foo)
Should we slurp the instance decl, even though Baz is nowhere mentioned
in module B? YES! Because of the fundep, the (C Foo ?) part is enough to
select this instance decl, and the Baz part follows.
Rather than take fundeps into account "properly", we just slurp
if C is visible and *any one* of the Names in the types
This is a slightly brutal approximation, but most instance decls
are regular H98 ones and it's perfect for them.
Changes:
HscTypes:
generalise the types of GatedDecl a bit
RnHiFiles.loadInstDecl, RnHiFiles.loadRule, RnIfaces.selectGated:
the meat of the solution
RdrName, OccName etc:
some consequential wibbles
|
|
|
|
| |
Output a slightly better message for -ddump-hi-diffs
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
----------------
Squash newtypes
----------------
This commit squashes newtypes and their coerces, from the typechecker
onwards. The original idea was that the coerces would not get in the
way of optimising transformations, but despite much effort they continue
to do so. There's no very good reason to retain newtype information
beyond the typechecker, so now we don't.
Main points:
* The post-typechecker suite of Type-manipulating functions is in
types/Type.lhs, as before. But now there's a new suite in types/TcType.lhs.
The difference is that in the former, newtype are transparent, while in
the latter they are opaque. The typechecker should only import TcType,
not Type.
* The operations in TcType are all non-monadic, and most of them start with
"tc" (e.g. tcSplitTyConApp). All the monadic operations (used exclusively
by the typechecker) are in a new module, typecheck/TcMType.lhs
* I've grouped newtypes with predicate types, thus:
data Type = TyVarTy Tyvar | ....
| SourceTy SourceType
data SourceType = NType TyCon [Type]
| ClassP Class [Type]
| IParam Type
[SourceType was called PredType.] This is a little wierd in some ways,
because NTypes can't occur in qualified types. However, the idea is that
a SourceType is a type that is opaque to the type checker, but transparent
to the rest of the compiler, and newtypes fit that as do implicit parameters
and dictionaries.
* Recursive newtypes still retain their coreces, exactly as before. If
they were transparent we'd get a recursive type, and that would make
various bits of the compiler diverge (e.g. things which do type comparison).
* I've removed types/Unify.lhs (non-monadic type unifier and matcher),
merging it into TcType.
Ditto typecheck/TcUnify.lhs (monadic unifier), merging it into TcMType.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------------------------
More stuff towards generalising 'foreign' declarations
------------------------------------------------------
This is the second step towards generalising 'foreign' declarations to
handle langauges other than C. Now I can handle
foreign import dotnet type T
foreign import dotnet "void Foo.Baz.f( T )" f :: T -> IO ()
** WARNING **
I believe that all the foreign stuff for C should
work exactly as before, but I have not tested it
thoroughly. Sven, Manuel, Marcin: please give it a
whirl and compare old with new output.
Lots of fiddling around with data types. The main changes are
* HsDecls.lhs
The ForeignDecl type and its friends
Note also the ForeignType constructor to TyClDecl
* ForeignCall.lhs
Here's where the stuff that survives right through
compilation lives
* TcForeign.lhs DsForeign.lhs
Substantial changes driven by the new data types
* Parser.y ParseIface.y RnSource
Just what you'd expect
|
|
|
|
| |
Import Double when necessary to make defaulting work
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------
Fix the dreaded export list bug
-------------------------------
With unfailing regularity I manage to get the following wrong:
module A(f) where
f = ...
module B(f) where
import A(f)
We must ensure that if A.f changes its type (etc) then B.hi
gets changed, so that people who import B will get recompiled.
There's a large comment with RnIfaces.mkImportInfo, and some
reorganisation in Rename, with a few mainly cosmetic consequences
in RnEnv.
[Simon: I think this will fix the 'OccurAnal not recompiled' problem.]
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------------
Import more rules, and fix usage info
-------------------------------------
1. A rule wasn't being slurped in that should have been.
Reason: wordToWord32# was in the 'TypeEnv', because it's a primop,
so the renamer thought it was already slurped in, which is true.
But it forgot to use the TypeEnv as a source of gates when deciding
which rules to pull in. Result: a useful rule for the primop wasn't
making it in. Thanks to Marcin for isolating this one.
2. RnIfaces.recordTypeEnvSlurp (was recordVSlurp) was blindly adding
the name to the iVSlurp set, but the iVSlurp set is supposed to contain
only "big" names (tycons, classes, and Ids that aren't data cons,
class ops etc). We need to get the big name from the thing.
Mildly tiresomely, this means we have to keep the Class inside
the TyCon derived from that class. Hence updates to TyCon and Class.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------
A major hygiene pass
--------------------
1. The main change here is to
Move what was the "IdFlavour" out of IdInfo,
and into the varDetails field of a Var
It was a mess before, because the flavour was a permanent attribute
of an Id, whereas the rest of the IdInfo was ephemeral. It's
all much tidier now.
Main places to look:
Var.lhs Defn of VarDetails
IdInfo.lhs Defn of GlobalIdDetails
The main remaining infelicity is that SpecPragmaIds are right down
in Var.lhs, which seems unduly built-in for such an ephemeral thing.
But that is no worse than before.
2. Tidy up the HscMain story a little. Move mkModDetails from MkIface
into CoreTidy (where it belongs more nicely)
This was partly forced by (1) above, because I didn't want to make
DictFun Ids into a separate kind of Id (which is how it was before).
Not having them separate means we have to keep a list of them right
through, rather than pull them out of the bindings at the end.
3. Add NameEnv as a separate module (to join NameSet).
4. Remove unnecessary {-# SOURCE #-} imports from FieldLabel.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
GHCi fixes:
- expressions are now compiled in a pseudo-module "$Interactive",
which avoids some problems with storage of demand-loaded declarations.
- compilation manager now detects when it needs to read the interace
for a module, even if it is already compiled. GHCi never demand-loads
interfaces now.
- (from Simon PJ) fix a problem with the recompilation checker, which
meant that modules were sometimes not recompiled when they should
have been.
- ByteCodeGen/Link: move linker related stuff into ByteCodeLink.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Implement do-style bindings on the GHCi command line.
The syntax for a command-line is exactly that of a do statement, with
the following meanings:
- `pat <- expr'
performs expr, and binds each of the variables in pat.
- `let pat = expr; ...'
binds each of the variables in pat, doesn't do any evaluation
- `expr'
behaves as `it <- expr' if expr is IO-typed, or `let it = expr'
followed by `print it' otherwise.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
fromInt
Remove fromInt from class Num, though it is retained
as an overloaded operation (with unchanged type) in PrelNum.
There are quite a few consequential changes in the Prelude.
I hope I got them all correct!
Also fix a bug that meant Integer (and its instances)
wasn't getting slurped in by the renamer, even though it
was needed for defaulting.
|
|
|
|
|
|
|
|
|
|
|
|
| |
Deprecations [HscTypes, MkIface, Rename, RnEnv, RnIfaces]
~~~~~~~~~~~~
* Arrange that a change in deprecations is treated as a
hi-file difference.
* Warn about deprecations at the usage site. This entailed
changing HscTypes.GlobalRdrEnv to include deprecations.
While I was at it, I changed the range of GlobalRdrEnv
to a data type, GlobalRdrElt, instead a of a pair.
|
|
|
|
| |
slight reorganisation of the -ddump-hi-diffs output
|
|
|
|
| |
Remove extra tracing
|
|
|
|
| |
Mainly rename rnDecl to rnSourceDecl; and add more tracing to renamer
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
1. Make the new version machinery work.
I think it does now!
2. Consequence of (1): Move the generation of
default method names to one place (namely
in RdrHsSyn.mkClassOpSigDM
3. Major clean up on HsDecls.TyClDecl
These big constructors should have been records
ages ago, and they are now. At last.
|
|
|
|
| |
Unused imports and suchlike
|
|
|
|
| |
Fix renamer bugs
|
|
|
|
|
|
|
|
|
| |
Split HscResult into HscFail | HscNoRecomp | HscRecomp, and clean up
producers and consumers of such. In particular, if no recompilation
happens, the resulting iface is put into the HIT instead of being
thrown away.
Also (trivial) unify functions *ModuleInThisPackage with *HomeModule.
|
|
|
|
| |
Remember local decls when no recompilation is required
|
|
|
|
| |
Make data constructors visible in unfoldings
|
|
|
|
|
|
| |
This commit completes the merge of compiler part
of the HEAD with the before-ghci-branch to
before-ghci-branch-merged.
|
|
|
|
| |
More small changes
|
|
|
|
| |
Dealing with instance-decl imports; and removing unnecessary imports
|
|
|
|
| |
More renamer... not in a working state I fear
|
|
|
|
|
|
|
|
|
|
|
| |
More renamer commits
Versioning now works properly I think.
The main irritation is that interface files now have fuly-qualified names for
*everything*, even things defined in that module. This is a deficiency in
the pretty printing for interface files. Probable solution: add something
to the SDoc styles. But not today.
|
|
|
|
| |
Improve MkIface; get ready for NameEnv.lhs
|
|
|
|
| |
More tidying up; esp of isLocallyDefined
|
|
|
|
|
| |
Move readIface from RnM to IO, and commensurate changes. Also, add a
field to ModuleLocation to hold preprocessed source locations.
|
|
|
|
| |
Renamer tidying up
|
|
|
|
|
| |
Only pass a ModuleLocation into hscMain, not a ModSummary, so as to
facilitate Main.main not necessarily being in Main.hs.
|