| 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.
|
|
|
|
|
| |
-fignore-breakpoints can be used to ignore breakpoints.
|
| |
|
|
|
|
|
|
| |
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.
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
| |
This commit adds bang-patterns,
enabled by -fglasgow-exts or -fbang-patterns
diabled by -fno-bang-patterns
The idea is described here
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/BangPatterns
|
|
|
|
|
|
|
| |
We must record the type of a TuplePat after typechecking, just like a ConPatOut,
so that desugaring works correctly for GADTs. See comments with the declaration
of HsPat.TuplePat, and test gadt15
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
Improve warning a little (suggested by Benjamin Pierce)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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 two small Template Haskell bugs.
(1) A bug in the renaming of [d| brackets |]. The problem was
that when we renamed the bracket we messed up the name cache, because
the module was still that of the parent module. Now we set a fake
module before renaming it.
TH_spliceDecl4 is the test.
(2) An expression splice can in principle mention *any* variable,
so the renamer really has to assume that it does when doing depdendency
analysis. For example
f = ...
h = ...$(thing "f")...
The renamer had better not put 'h' before 'f', else the type checker
won't find a defn for 'f' in the type envt.
TH_spliceE5 is the test
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add record syntax for GADTs
~~~~~~~~~~~~~~~~~~~~~~~~~~~
Atrijus Tang wanted to add record syntax for GADTs and existential
types, so he and I worked on it a bit at ICFP. This commit is the
result. Now you can say
data T a where
T1 { x :: a } :: T [a]
T2 { x :: a, y :: Int } :: T [a]
forall b. Show b =>
T3 { naughty :: b, ok :: Int } :: T Int
T4 :: Eq a => a -> b -> T (a,b)
Here the constructors are declared using record syntax.
Still to come after this commit:
- User manual documentation
- More regression tests
- Some missing cases in the parser (e.g. T3 won't parse)
Autrijus is going to do these.
Here's a quick summary of the rules. (Atrijus is going to write
proper documentation shortly.)
Defnition: a 'vanilla' constructor has a type of the form
forall a1..an. t1 -> ... -> tm -> T a1 ... an
No existentials, no context, nothing. A constructor declared with
Haskell-98 syntax is vanilla by construction. A constructor declared
with GADT-style syntax is vanilla iff its type looks like the above.
(In the latter case, the order of the type variables does not matter.)
* You can mix record syntax and non-record syntax in a single decl
* All constructors that share a common field 'x' must have the
same result type (T [a] in the example).
* You can use field names without restriction in record construction
and record pattern matching.
* Record *update* only works for data types that only have 'vanilla'
constructors.
* Consider the field 'naughty', which uses a type variable that does
not appear in the result type ('b' in the example). You can use the
field 'naughty' in pattern matching and construction, but NO
SELECTOR function is generated for 'naughty'. [An attempt to use
'naughty' as a selector function will elicit a helpful error
message.]
* Data types declared in GADT syntax cannot have a context. So this
is illegal:
data (Monad m) => T a where
....
* Constructors in GADT syntax can have a context (t.g. T3, T4 above)
and that context is stored in the constructor and made available
when the constructor is pattern-matched on. WARNING: not competely
implemented yet, but that's the plan.
Implementation notes
~~~~~~~~~~~~~~~~~~~~
- Data constructors (even vanilla ones) no longer share the type
variables of their parent type constructor.
- HsDecls.ConDecl has changed quite a bit
- TyCons don't record the field labels and type any more (doesn't
make sense for existential fields)
- GlobalIdDetails records which selectors are 'naughty', and hence
don't have real code.
|
|
|
|
| |
Grr: another wibble to duplicate signature detection
|
|
|
|
| |
Ack! Ack!
|
|
|
|
| |
Ack! missed one!
|
|
|
|
| |
Fix bogon in reporting of duplicate sigs; make mod68 work again
|
|
|
|
|
|
|
|
|
|
|
|
| |
It turned out that doing all binding dependency analysis in the typechecker
meant that the renamer's unused-binding error messages got worse. So now
I've put the first dep anal back into the renamer, while the second (which
is specific to type checking) remains in the type checker.
I've also made the pretty printer sort the decls back into source order
before printing them (except with -dppr-debug).
Fixes rn041.
|
|
|
|
| |
Wibble to loadHomeInterface for TH quoting; MERGE to STABLE
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
MERGE to STABLE
Fix a TH name-reification bug. The problem is that when you say
'name
in TH, you'd better load the home interface for "name", so that
deprecations are reported properly.
Fixes SourceForge
[ghc-Bugs-1246483 ] Template Haskell panic with class names
TH_reifyType2 is a test for it.
|
|
|
|
| |
Wibble to dup-sig reporting
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
Import trimming
|
|
|
|
| |
remove RnSource.lhs-boot and add RnExpr.lhs-boot
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fix a bug in the renamer for parallel list comprehensions
MERGE TO STABLE
It's surprinsingly tricky to combine
a) The parallel scopes for par-list-comps
with
b) The general form of the renamer types, whereby
scoped constructs work like
rnPat :: Pat -> RnM (thing,FreeVars)
-> RnM ((Pat,thing), FreeVars)
This general shape neatly allows rnPat to
extend the envt, report unused variables from
the 'thing' inside, and return the correct set
of free variables
But combining (a) and (b) is tricky, and was plain wrong before.
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Make it so that you can deprecate a data constructor.
Previously {-# DEPRECATED T "no" #-} referred only to the type
or class T. Now it refers to the data constructor T as well,
just like in fixity declarations.
There's no way to deprecate the data constructor T without also
deprecating the type T, alas. Same problem in fixity decls.
Main problem is coming up with a suitable concrete syntax to do
so.
We could consider merging this to the STABLE branch.
NB: Sven, the manual fixes are not XML-valideated! I'm at home.
|
|
|
|
|
|
|
|
|
| |
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
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Another go at the handling of -< in arrow notation, continuing and
fixing the changes in
http://www.haskell.org/pipermail/cvs-all/2005-April/040391.html
Now do the same thing in the renamer as we do in the type checker,
i.e. return to the environment of the proc when considering the left
argument of -<.
This is much simpler than the old proc_level stuff, and matches the
type rules more clearly. But there is a change in error messages.
For the input
f :: Int -> Int
f = proc x -> (+x) -< 1
GHC 6.4 says
test.hs:6:
Command-bound variable `x' is not in scope here
Reason: it is used in the left argument of (-<)
In the second argument of `(+)', namely `x'
In the command: (+ x) -< 1
In the definition of `f': f = proc x -> (+ x) -< 1
but now we just get the blunt
test.hs:6:16: Not in scope: `x'
The beauty is all on the inside.
Similarly leakage of existential type variables (arrow1) is detected,
but the error message isn't very helpful.
|
|
|
|
| |
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.
|