| 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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This very large commit adds impredicativity to GHC, plus
numerous other small things.
*** WARNING: I have compiled all the libraries, and
*** a stage-2 compiler, and everything seems
*** fine. But don't grab this patch if you
*** can't tolerate a hiccup if something is
*** broken.
The big picture is this:
a) GHC handles impredicative polymorphism, as described in the
"Boxy types: type inference for higher-rank types and
impredicativity" paper
b) GHC handles GADTs in the new simplified (and very sligtly less
epxrssive) way described in the
"Simple unification-based type inference for GADTs" paper
But there are lots of smaller changes, and since it was pre-Darcs
they are not individually recorded.
Some things to watch out for:
c) The story on lexically-scoped type variables has changed, as per
my email. I append the story below for completeness, but I
am still not happy with it, and it may change again. In particular,
the new story does not allow a pattern-bound scoped type variable
to be wobbly, so (\(x::[a]) -> ...) is usually rejected. This is
more restrictive than before, and we might loosen up again.
d) A consequence of adding impredicativity is that GHC is a bit less
gung ho about converting automatically between
(ty1 -> forall a. ty2) and (forall a. ty1 -> ty2)
In particular, you may need to eta-expand some functions to make
typechecking work again.
Furthermore, functions are now invariant in their argument types,
rather than being contravariant. Again, the main consequence is
that you may occasionally need to eta-expand function arguments when
using higher-rank polymorphism.
Please test, and let me know of any hiccups
Scoped type variables in GHC
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
January 2006
0) Terminology.
A *pattern binding* is of the form
pat = rhs
A *function binding* is of the form
f pat1 .. patn = rhs
A binding of the formm
var = rhs
is treated as a (degenerate) *function binding*.
A *declaration type signature* is a separate type signature for a
let-bound or where-bound variable:
f :: Int -> Int
A *pattern type signature* is a signature in a pattern:
\(x::a) -> x
f (x::a) = x
A *result type signature* is a signature on the result of a
function definition:
f :: forall a. [a] -> a
head (x:xs) :: a = x
The form
x :: a = rhs
is treated as a (degnerate) function binding with a result
type signature, not as a pattern binding.
1) The main invariants:
A) A lexically-scoped type variable always names a (rigid)
type variable (not an arbitrary type). THIS IS A CHANGE.
Previously, a scoped type variable named an arbitrary *type*.
B) A type signature always describes a rigid type (since
its free (scoped) type variables name rigid type variables).
This is also a change, a consequence of (A).
C) Distinct lexically-scoped type variables name distinct
rigid type variables. This choice is open;
2) Scoping
2(a) If a declaration type signature has an explicit forall, those type
variables are brought into scope in the right hand side of the
corresponding binding (plus, for function bindings, the patterns on
the LHS).
f :: forall a. a -> [a]
f (x::a) = [x :: a, x]
Both occurences of 'a' in the second line are bound by
the 'forall a' in the first line
A declaration type signature *without* an explicit top-level forall
is implicitly quantified over all the type variables that are
mentioned in the type but not already in scope. GHC's current
rule is that this implicit quantification does *not* bring into scope
any new scoped type variables.
f :: a -> a
f x = ...('a' is not in scope here)...
This gives compatibility with Haskell 98
2(b) A pattern type signature implicitly brings into scope any type
variables mentioned in the type that are not already into scope.
These are called *pattern-bound type variables*.
g :: a -> a -> [a]
g (x::a) (y::a) = [y :: a, x]
The pattern type signature (x::a) brings 'a' into scope.
The 'a' in the pattern (y::a) is bound, as is the occurrence on
the RHS.
A pattern type siganture is the only way you can bring existentials
into scope.
data T where
MkT :: forall a. a -> (a->Int) -> T
f x = case x of
MkT (x::a) f -> f (x::a)
2a) QUESTION
class C a where
op :: forall b. b->a->a
instance C (T p q) where
op = <rhs>
Clearly p,q are in scope in <rhs>, but is 'b'? Not at the moment.
Nor can you add a type signature for op in the instance decl.
You'd have to say this:
instance C (T p q) where
op = let op' :: forall b. ...
op' = <rhs>
in op'
3) A pattern-bound type variable is allowed only if the pattern's
expected type is rigid. Otherwise we don't know exactly *which*
skolem the scoped type variable should be bound to, and that means
we can't do GADT refinement. This is invariant (A), and it is a
big change from the current situation.
f (x::a) = x -- NO; pattern type is wobbly
g1 :: b -> b
g1 (x::b) = x -- YES, because the pattern type is rigid
g2 :: b -> b
g2 (x::c) = x -- YES, same reason
h :: forall b. b -> b
h (x::b) = x -- YES, but the inner b is bound
k :: forall b. b -> b
k (x::c) = x -- NO, it can't be both b and c
3a) You cannot give different names for the same type variable in the same scope
(Invariant (C)):
f1 :: p -> p -> p -- NO; because 'a' and 'b' would be
f1 (x::a) (y::b) = (x::a) -- bound to the same type variable
f2 :: p -> p -> p -- OK; 'a' is bound to the type variable
f2 (x::a) (y::a) = (x::a) -- over which f2 is quantified
-- NB: 'p' is not lexically scoped
f3 :: forall p. p -> p -> p -- NO: 'p' is now scoped, and is bound to
f3 (x::a) (y::a) = (x::a) -- to the same type varialble as 'a'
f4 :: forall p. p -> p -> p -- OK: 'p' is now scoped, and its occurences
f4 (x::p) (y::p) = (x::p) -- in the patterns are bound by the forall
3b) You can give a different name to the same type variable in different
disjoint scopes, just as you can (if you want) give diferent names to
the same value parameter
g :: a -> Bool -> Maybe a
g (x::p) True = Just x :: Maybe p
g (y::q) False = Nothing :: Maybe q
3c) Scoped type variables respect alpha renaming. For example,
function f2 from (3a) above could also be written:
f2' :: p -> p -> p
f2' (x::b) (y::b) = x::b
where the scoped type variable is called 'b' instead of 'a'.
4) Result type signatures obey the same rules as pattern types signatures.
In particular, they can bind a type variable only if the result type is rigid
f x :: a = x -- NO
g :: b -> b
g x :: b = x -- YES; binds b in rhs
5) A *pattern type signature* in a *pattern binding* cannot bind a
scoped type variable
(x::a, y) = ... -- Legal only if 'a' is already in scope
Reason: in type checking, the "expected type" of the LHS pattern is
always wobbly, so we can't bind a rigid type variable. (The exception
would be for an existential type variable, but existentials are not
allowed in pattern bindings either.)
Even this is illegal
f :: forall a. a -> a
f x = let ((y::b)::a, z) = ...
in
Here it looks as if 'b' might get a rigid binding; but you can't bind
it to the same skolem as a.
6) Explicitly-forall'd type variables in the *declaration type signature(s)*
for a *pattern binding* do not scope AT ALL.
x :: forall a. a->a -- NO; the forall a does
Just (x::a->a) = Just id -- not scope at all
y :: forall a. a->a
Just y = Just (id :: a->a) -- NO; same reason
THIS IS A CHANGE, but one I bet that very few people will notice.
Here's why:
strange :: forall b. (b->b,b->b)
strange = (id,id)
x1 :: forall a. a->a
y1 :: forall b. b->b
(x1,y1) = strange
This is legal Haskell 98 (modulo the forall). If both 'a' and 'b'
both scoped over the RHS, they'd get unified and so cannot stand
for distinct type variables. One could *imagine* allowing this:
x2 :: forall a. a->a
y2 :: forall a. a->a
(x2,y2) = strange
using the very same type variable 'a' in both signatures, so that
a single 'a' scopes over the RHS. That seems defensible, but odd,
because though there are two type signatures, they introduce just
*one* scoped type variable, a.
7) Possible extension. We might consider allowing
\(x :: [ _ ]) -> <expr>
where "_" is a wild card, to mean "x has type list of something", without
naming the something.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Two significant changes to the representation of types
1. Change the representation of type synonyms
Up to now, type synonym applications have been held in
*both* expanded *and* un-expanded form. Unfortunately, this
has exponential (!) behaviour when type synonyms are deeply
nested. E.g.
type P a b = (a,b)
f :: P a (P b (P c (P d e)))
This showed up in a program of Joel Reymont, now immortalised
as typecheck/should_compile/syn-perf.hs
So now synonyms are held as ordinary TyConApps, and expanded
only on demand.
SynNote has disappeared altogether, so the only remaining TyNote
is a FTVNote. I'm not sure if it's even useful.
2. Eta-reduce newtypes
See the Note [Newtype eta] in TyCon.lhs
If we have
newtype T a b = MkT (S a b)
then, in Core land, we would like S = T, even though the application
of T is then not saturated. This commit eta-reduces T's RHS, and
keeps that inside the TyCon (in nt_etad_rhs). Result is that
coreEqType can be simpler, and has less need of expanding newtypes.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
---------------------------------------------
Type signatures are no longer instantiated with skolem constants
---------------------------------------------
Merge to STABLE
Consider
p :: a
q :: b
(p,q,r) = (r,r,p)
Here, 'a' and 'b' end up being the same, because they are both bound
to the type for 'r', which is just a meta type variable. So 'a' and 'b'
can't be skolems.
Sigh. This commit goes back to an earlier way of doing things, by
arranging that type signatures get instantiated with *meta* type
variables; then at the end we must check that they have not been
unified with types, nor with each other.
This is a real bore. I had to do quite a bit of related fiddling around
to make error messages come out right. Improved one or two.
Also a small unrelated fix to make
:i (:+)
print with parens in ghci. Sorry this got mixed up in the same commit.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Arrange that when seeking instance decls in GHCi, in response
to a :info command, we only print ones whose types are in scope
unqualified. This eliminates an alarmingly long list when
simply typing ':info Show', say.
On the way, I reorganised a bit. GHCi printing happens by
converting a TyThing to an IfaceDecl, and printing that.
I now arrange to generate unqualifed IfaceExtNames directly
during this conversion, based on what is in scope. Previously
it was done during the pretty-printing part via the UserStyle.
But this is nicer.
|
|
|
|
| |
comment
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------------
Keep-alive set and Template Haskell quotes
------------------------------------------
a) Template Haskell quotes should be able to mention top-leve
things without resorting to lifting. Example
module Foo( foo ) where
f x = x
foo = [| f 4 |]
Here the reference to 'f' is ok; no need to 'lift' it.
The relevant changes are in TcExpr.tcId
b) However, we must take care not to discard the binding for f,
so we add it to the 'keep-alive' set for the module. I've
now made this into (another) mutable bucket, tcg_keep,
in the TcGblEnv
c) That in turn led me to look at the handling of orphan rules;
as a result I made IdCoreRule into its own data type, which
has simle but non-local ramifications
|
|
|
|
| |
Fix missing case for algTyConRhs; fixes test ghci011
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------
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).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------
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.
|
|
|
|
| |
Fix GHCi buglet when browsing module
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------
Sort out the :i command for GHCi
-------------------------------
The :info command has been broken in the HEAD for some time, since the new IfaceSyn
story. This commit sorts it out, and makes it nicer than before. For example, when
you :i a record selector, you get a cut-down data type declaration, so you can see
the context.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-----------------------------------------------
Record whether data constructors are declared infix
-----------------------------------------------
This allows us to generate the InfixC form in Template Hasekll.
And for 'deriving' Read and Show, we now read and parse the infix
form iff the constructor was declared infix, rather than just if
it does not have the default fixity (as before).
IfaceSyn changes slightly, so that IfaceConDecl can record their
fixity, so there are trivial changes scattered about, and
you'll need to recompile everything.
In TysWiredIn I took the opportunity to simplify pcDataCon slightly,
by eliminating the unused Theta argument.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Elaborate IfaceSyn.HsWorker to give the full IfaceExtName of the worker,
rather than just the internal OccName. Very occasionally, the worker for
a function in module A turns out to be (by simplification) a function
defined in module B. So we must remember the module. This shows up in
package ObjectIO,
Graphics.UI.ObjectIO.OS.Window.osValidateWindowRect
which has a worker
Graphics.UI.ObjectIO.OS.WindowCCall_12.$wwinValidateRect
*** Unfortunately this changes the binary format of hi files slightly, so
*** you'll have to recompile all your libraries from scratch.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Get rid of DiscardedInfo, and fix a Ghci bug at the same time.
The new story is this:
- We always read the whole interface file, as it exists on disk,
not dropping pragmas or anything.
- We compare that from-the-disk copy with the new version before
writing the new interface file.
- We drop the pragmas
a) Before loading the interface payload into the declaration pools
b) In the no-need-to-recompile case, before typechecking the
interface decls. Omitting this was the previous bug.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------
More newtype clearing up
------------------------
* Change the representation of TyCons so that it accurately reflects
* data (0 or more constrs)
* newtype (1 constr)
* abstract (unknown)
Replaces DataConDetails and AlgTyConFlavour with AlgTyConRhs
* Add IfaceSyn.IfaceConDecls, a kind of stripped-down analogue
of AlgTyConRhs
* Move NewOrData from BasicTypes to HsDecl (it's now an HsSyn thing)
* Arrange that Type.newTypeRep and splitRecNewType_maybe unwrap just
one layer of new-type-ness, leaving the caller to recurse.
This still leaves typeRep and repType in Type.lhs; these functions
are still vaguely disturbing and probably should get some attention.
Lots of knock-on changes. Fixes bug in ds054.
|
|
|
|
| |
Wibbles to exporting types abstractly
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
---------------------------------------
Don't expose constructors as vigorously
---------------------------------------
GHC used to expose the constructors of a data type in the interface file,
even if (a) we were not optimising, and (b) the constructors are not exported.
In practice this isn't really necessary, and it's bad because it forces too
much recompilation. I've been meaning to fix this for some while.
Now the data cons are hidden, even in the interface file, if both (a) and (b)
are true. That means less interface file wobbling.
Mind you, the interface file still changes, because the to/from functions for
generic type classes change their types. But provided you don't use them, you'll
get "compilation not required".
We could play the same game for classes (by hiding their class ops) but that'd
mean we'd have to change the data type for IfaceClassDecl, and I can't be
bothered to do that today. It's unusual to have a class which exports none
of its methods anyway.
On the way, I changed the representation of tcg_exports and mg_exports (from
Avails to NameSet), but that should be externally invisible.
|
|
|
|
| |
Show generic-ness when printing a data decl
|
|
Oops; forgot to add this entire directory!
|