Manuel M T Chakravarty [Wed, 17 Aug 2011 04:41:59 +0000 (14:41 +1000)]
Add VECTORISE [SCALAR] type pragma
- Pragma to determine how a given type is vectorised
- At this stage only the VECTORISE SCALAR variant is used by the vectoriser.
- '{-# VECTORISE SCALAR type t #-}' implies that 't' cannot contain parallel arrays and may be used in vectorised code. However, its constructors can only be used in scalar code. We use this, e.g., for 'Int'.
- May be used on imported types
See also http://hackage.haskell.org/trac/ghc/wiki/DataParallel/VectPragma
Johan Tibell [Wed, 20 Jul 2011 16:29:22 +0000 (18:29 +0200)]
Add popCnt# primop
Simon Peyton Jones [Tue, 16 Aug 2011 09:23:52 +0000 (10:23 +0100)]
Major improvement to pattern bindings
This patch makes a number of related improvements
a) Implements the Haskell Prime semantics for pattern bindings
(Trac #2357). That is, a pattern binding p = e is typed
just as if it had been written
t = e
f = case t of p -> f
g = case t of p -> g
... etc ...
where f,g are the variables bound by p. In paricular it's
ok to say
(f,g) = (\x -> x, \y -> True)
and f and g will get propertly inferred types
f :: a -> a
g :: a -> Int
b) Eliminates the MonoPatBinds flag altogether. (For the moment
it is deprecated and has no effect.) Pattern bindings are now
generalised as per (a). Fixes Trac #2187 and #4940, in the
way the users wanted!
c) Improves the OutsideIn algorithm generalisation decision.
Given a definition without a type signature (implying "infer
the type"), the published algorithm rule is this:
- generalise *top-level* functions, and
- do not generalise *nested* functions
The new rule is
- generalise a binding whose free variables have
Guaranteed Closed Types
- do not generalise other bindings
Generally, a top-level let-bound function has a Guaranteed
Closed Type, and so does a nested function whose free vaiables
are top-level functions, and so on. (However a top-level
function that is bitten by the Monomorphism Restriction does
not have a GCT.)
Example:
f x = let { foo y = y } in ...
Here 'foo' has no free variables, so it is generalised despite
being nested.
d) When inferring a type f :: ty for a definition f = e, check that
the compiler would accept f :: ty as a type signature for that
same definition. The type is rejected precisely when the type
is ambiguous.
Example:
class Wob a b where
to :: a -> b
from :: b -> a
foo x = [x, to (from x)]
GHC 7.0 would infer the ambiguous type
foo :: forall a b. Wob a b => b -> [b]
but that type would give an error whenever it is called; and
GHC 7.0 would reject that signature if given by the
programmer. The new type checker rejects it up front.
Similarly, with the advent of type families, ambiguous types are
easy to write by mistake. See Trac #1897 and linked tickets for
many examples. Eg
type family F a :: *
f ::: F a -> Int
f x = 3
This is rejected because (F a ~ F b) does not imply a~b. Previously
GHC would *infer* the above type for f, but was unable to check it.
Now even the inferred type is rejected -- correctly.
The main implemenation mechanism is to generalise the abe_wrap
field of ABExport (in HsBinds), from [TyVar] to HsWrapper. This
beautiful generalisation turned out to make everything work nicely
with minimal programming effort. All the work was fiddling around
the edges; the core change was easy!
Simon Peyton Jones [Tue, 16 Aug 2011 09:19:22 +0000 (10:19 +0100)]
Improve debug printing of Names (respect opt_SuppressModulePrefixes)
Simon Peyton Jones [Mon, 15 Aug 2011 07:41:55 +0000 (08:41 +0100)]
Fix Trac #5404: looking up signature binders in RnEnv
See Note [Looking up Exact RdrNames] in RnEnv
Simon Peyton Jones [Mon, 15 Aug 2011 07:41:02 +0000 (08:41 +0100)]
In instance declarations, the method names are *occurrences* not *binders*
A long standing bug. The patch fixes Trac #5410
Simon Peyton Jones [Mon, 15 Aug 2011 07:26:14 +0000 (08:26 +0100)]
Comments only
Simon Marlow [Sat, 13 Aug 2011 08:42:10 +0000 (09:42 +0100)]
fix some #ifdefs that were making compilation with 7.2.1 fail - the
safified array package is not in 7.2.1
Simon Marlow [Sat, 13 Aug 2011 08:40:51 +0000 (09:40 +0100)]
fix occasional failure of numsparks001 test. During shutdown we
discard all the sparks from each Capability, but we were forgetting to
account for the discarded sparks in the stats, leading to a failure of
the assertion that tests the spark invariant.
I've moved the discarding of sparks to just before the GC, to avoid
race conditions, and counted the discarded sparks as GC'd.
Simon Marlow [Sat, 13 Aug 2011 08:22:00 +0000 (09:22 +0100)]
remove unnecessary return
Simon Peyton Jones [Fri, 12 Aug 2011 20:48:19 +0000 (21:48 +0100)]
Merge branch 'master' of darcs.haskell.org/ghc
Simon Peyton Jones [Fri, 12 Aug 2011 20:47:14 +0000 (21:47 +0100)]
Correct typo (fix Trac #5411)
Simon Marlow [Fri, 12 Aug 2011 13:26:34 +0000 (14:26 +0100)]
make shutdownHaskellAndExit() shut down the RTS and exit immediately
(#5402)
Manuel M T Chakravarty [Wed, 10 Aug 2011 11:20:53 +0000 (21:20 +1000)]
Avoid call-clobbered registers
Manuel M T Chakravarty [Wed, 10 Aug 2011 10:41:32 +0000 (20:41 +1000)]
Warning police
Stephen Blackheath [Tue, 26 Jul 2011 10:35:17 +0000 (10:35 +0000)]
ARMv5 compatibility for registerized runtime changes.
When the bootstrap compiler does not include this patch, you must add this line
to mk/build.mk, otherwise the ARM architecture cannot be detected due to a
-undef option given to the C pre-processor.
SRC_HC_OPTS = -pgmP 'gcc -E -traditional'
Karel Gardas [Thu, 14 Jul 2011 20:21:09 +0000 (22:21 +0200)]
disable for now ARM specific target data layout and triple
This patch disables ARM specific target data layout and triple.
The reason for this is that LLVM asserts on some files if this
is in use. The assert looks:
Formal argument #8 has unhandled type i32UNREACHABLE executed at
/llvm-ghc-arm/lib/CodeGen/CallingConvLower.cpp:81!
Karel Gardas [Tue, 12 Jul 2011 16:29:58 +0000 (18:29 +0200)]
fix ARM/LLVM target data layout specification together with target triple
This patch fixes ARM/LLVM target data layout specification based
on what Clang is using itself. I've modified Clang's used triple
a little bit from armv4t-* to arm-* though
Karel Gardas [Sat, 9 Jul 2011 16:07:00 +0000 (18:07 +0200)]
RTS: fix pushWSDeque to invoke write barrier when element is added
This patch fixes RTS' pushWSDeque function. We need to invoke
write barrier after element is added to the queue and before moving
bottom. The reason for this is possible write reordering on modern CPUs
(e.g. ARMv7MP) where setting of element might be done later after moving
bottom. When such situation happen other thread might be waiting to steal
data from the queue and when bottom is moved it eagerly steals undefined
data from the queue since setting of element has not happened yet.
Karel Gardas [Sat, 9 Jul 2011 15:54:30 +0000 (17:54 +0200)]
RTS: fix xchg/cas fcns to invoke memory barrier on ARMv7 platform
This patch fixes RTS' xchg and cas functions. On ARMv7 it is recommended
to add memory barrier after using ldrex/strex for implementing atomic
lock or operation.
Karel Gardas [Sat, 9 Jul 2011 15:35:56 +0000 (17:35 +0200)]
implement ARMv7 specific memory barriers
This patch provides implementation of ARMv7 specific memory barriers.
It uses dmb sy isn (or shortly dmb) for store/load and load/load barriers
and dmb st isn for store/store barrier.
Karel Gardas [Sat, 9 Jul 2011 15:30:02 +0000 (17:30 +0200)]
LLVM: set target data layout for arm-unknown-linux triplet
Karel Gardas [Wed, 6 Jul 2011 19:05:13 +0000 (21:05 +0200)]
add support for STG floating-point regs using VFPv3
This patch adds mapping for STG floating point registers
using ARM VFPv3. Since I'm using just d8-d11 also processors
with just VFPv3-D16 implemented should work (e.g. NVidia Tegra2,
Marvell Dove)
Karel Gardas [Tue, 5 Jul 2011 18:12:14 +0000 (20:12 +0200)]
make StgReturn and cas functions Thumb friendly
Karel Gardas [Tue, 5 Jul 2011 18:10:18 +0000 (20:10 +0200)]
implement ARMv6/7 specific xchg function
Karel Gardas [Sun, 3 Jul 2011 21:24:14 +0000 (23:24 +0200)]
Stephen Blackheath's GHC/ARM registerised port
This is the Stephen Blackheath's GHC/ARM registerised port
which is using modified version of LLVM and which provides
basic registerised build functionality
Simon Marlow [Wed, 10 Aug 2011 09:02:55 +0000 (10:02 +0100)]
default to using @note for saving the linker opts (someone mentioned
that it wasn't working on Alpha, because we had explicitly listed the
arches rather than having a sensible fallback).
Simon Marlow [Wed, 10 Aug 2011 09:01:44 +0000 (10:01 +0100)]
Disable saving the linker options in the binary on Solaris (#5382).
Also refactor the check into one place.
Simon Marlow [Wed, 10 Aug 2011 08:10:24 +0000 (09:10 +0100)]
Fail configure if Alex 3 is found. Haddock doesn't build with Alex 3
yet, and fixing it is non-trivial (a change to Cabal is needed). So
I'm making configure fail with an error suggesting to install an older
Alex for now.
David Terei [Tue, 9 Aug 2011 17:24:15 +0000 (10:24 -0700)]
Fix conditional pragma to work with 6.12
Simon Peyton Jones [Tue, 9 Aug 2011 16:45:27 +0000 (17:45 +0100)]
Make the free variable finder in TidyPgm work properly
We were getting exponential behaviour by gathering free
variables *both* from the unfolding *and* the RHS of
a definition. While unfoldings are of limited size this
is merely inefficient. But with -fexpose-all-unfoldings
it becomes exponentially costly. Doh.
Fixes Trac #5352.
Simon Marlow [Tue, 9 Aug 2011 11:31:03 +0000 (12:31 +0100)]
Fix an x86 code generation bug (#5393). In fact, there were two bugs
in X86.CodeGen.getNonClobberedOperand: two code fragments were the
wrong way around, and we were using the wrong size on an
instruction (32 bits instead of the word size). This bit of the code
generator must have never worked!
David Terei [Tue, 2 Aug 2011 22:17:10 +0000 (15:17 -0700)]
Add Trustworthy pragma to bin-package-db
Ian Lynagh [Mon, 8 Aug 2011 18:13:07 +0000 (19:13 +0100)]
Have validate check for the "files written by multiple tests" error
We don't actually enable the test yet, but when we do validate will
check whether it fails.
Simon Marlow [Mon, 8 Aug 2011 08:24:09 +0000 (09:24 +0100)]
compatibility with Alex 3.0
Simon Marlow [Fri, 5 Aug 2011 09:14:44 +0000 (10:14 +0100)]
comment wibble
Simon Marlow [Mon, 8 Aug 2011 08:12:08 +0000 (09:12 +0100)]
fix #5381: the -debug RTS could crash with "internal error: MVAR_CLEAN
on mutable list" after a call to tryPutMVar#.
I don't think this leads to any problems without -debug.
Simon Marlow [Fri, 5 Aug 2011 08:06:41 +0000 (09:06 +0100)]
Use the correct __GLASGOW_HASKELL__ value when invoking hsc2hs on
source code to be compiled with the stage 0 compiler. (bug noticed by
David Terei - thanks!)
Simon Peyton Jones [Mon, 8 Aug 2011 11:29:40 +0000 (12:29 +0100)]
Use parenSymOcc when displaying an export list in RnNames (fixes Trac #5385)
I also called parenSymOcc in two other places that begged for it.
Ian Lynagh [Sun, 7 Aug 2011 12:57:08 +0000 (13:57 +0100)]
Add a case for kfreebsdgnu in Platforms.hs
Ian Lynagh [Sat, 6 Aug 2011 22:55:17 +0000 (23:55 +0100)]
Merge branch 'master' of mac:ghc/git/val64/.
Ian Lynagh [Sat, 6 Aug 2011 21:20:28 +0000 (22:20 +0100)]
With -v, we now print the commandlines that get run by askCc
Edward Z. Yang [Sat, 6 Aug 2011 15:18:36 +0000 (11:18 -0400)]
Also include basic time statistics in GCStats.
Signed-off-by: Edward Z. Yang <ezyang@mit.edu>
Peter Wortmann [Fri, 22 Apr 2011 09:35:35 +0000 (10:35 +0100)]
Teach GHC to compile objective-c++ files as well (trac #5150)
Simon Peyton Jones [Fri, 5 Aug 2011 16:40:29 +0000 (17:40 +0100)]
Wibble to "Fix a long-standing bug in HsUtils.hsTyClDeclBinders"
Simon Peyton Jones [Fri, 5 Aug 2011 14:30:54 +0000 (15:30 +0100)]
A little extra tracing
Simon Peyton Jones [Fri, 5 Aug 2011 14:29:44 +0000 (15:29 +0100)]
Another run at binders in Template Haskell (fixes Trac #5379)
TH quotation was using mkName rather than newName for
top-level definitions, which is plain wrong as #5379
points out.
Simon Peyton Jones [Fri, 5 Aug 2011 14:26:31 +0000 (15:26 +0100)]
Fix a long-standing bug in HsUtils.hsTyClDeclBinders
We were returning the tycon of a type family *instance*
as a binder, and it just isn't!
Consequential tidy-ups follow. I tripped over this on
the way to something else. I'm not sure it was causing
a problem, but it is Plainly Wrong.
Simon Peyton Jones [Fri, 5 Aug 2011 10:15:50 +0000 (11:15 +0100)]
Merge branch 'master' of darcs.haskell.org/ghc
Simon Peyton Jones [Fri, 5 Aug 2011 10:14:31 +0000 (11:14 +0100)]
plusParent can see a non-parent and a parent (fixes Trac #5374)
See Note [Parents] in RdrName.
Simon Marlow [Thu, 4 Aug 2011 14:54:08 +0000 (15:54 +0100)]
Update to work with Alex 3.0: basically disabling Alex's new Unicode
support because we have our own, and defining alexGetByte instead of
alexGetChar (actually we also define alexGetChar, for backwards
compatibility).
Simon Marlow [Thu, 4 Aug 2011 11:08:26 +0000 (12:08 +0100)]
comment about using "stage = 2" in build.mk
Simon Marlow [Thu, 4 Aug 2011 11:07:30 +0000 (12:07 +0100)]
typo
Simon Marlow [Thu, 4 Aug 2011 11:06:49 +0000 (12:06 +0100)]
sanitise naming of package lists
The *predicates* all start with "PKGS_THAT_...", e.g.:
PKGS_THAT_BUILD_WITH_STAGE0 (previously "PACKAGES_STAGE0")
PKGS_THAT_BUILD_WITH_STAGE2 (previously "STAGE2_PACKAGES")
PKGS_THAT_USE_TH (previously "TH_PACKAGES)
etc. (there are a few more)
the lists of packages to build are now consistently named:
PACKAGES_STAGE0
PACKAGES_STAGE1 (previously just "PACKAGES")
PACKAGES_STAGE2
Simon Marlow [Wed, 3 Aug 2011 12:41:33 +0000 (13:41 +0100)]
small optimisation for the program in #5367: if the worker thread
being woken already has its wakeup flag set, don't bother signalling
its condition variable again.
Austin Seipp [Sun, 31 Jul 2011 15:26:52 +0000 (10:26 -0500)]
Add plugin documentation for reinitializeGlobals
Ian Lynagh [Thu, 4 Aug 2011 15:24:30 +0000 (16:24 +0100)]
Don't duplicate files in bindists; trac #5356
We were putting
includes/ghcautoconf.h
includes/ghcconfig.h
includes/ghcplatform.h
into bindists twice.
Simon Peyton Jones [Thu, 4 Aug 2011 15:00:04 +0000 (16:00 +0100)]
Missing call to tcView, fixes naughty failure in tc208
Simon Peyton Jones [Thu, 4 Aug 2011 13:03:18 +0000 (14:03 +0100)]
Merge branch 'master' of darcs.haskell.org/ghc
Max Bolingbroke [Wed, 3 Aug 2011 19:33:10 +0000 (20:33 +0100)]
Tidy up handling of PredTys: remove dead code, move functions deconstructing them to TcType
Ian Lynagh [Wed, 3 Aug 2011 19:25:52 +0000 (20:25 +0100)]
Stop using -Wl,-no_pie on OS X
Now that the in-tree gmp has been upgraded, it should no longer be
necessary, according to #5293.
Simon Peyton Jones [Wed, 3 Aug 2011 16:05:56 +0000 (17:05 +0100)]
Print type contexts with fsep, not sep
This is a slightly experimental change. When pretty-printing
a type, instead of
instance (Eq a,
Eq b,
Eq c,
Eq d,
Eq e,
Eq f,
Eq g,
Eq h,
Eq i,
Eq j,
Eq k,
Eq l) =>
Eq (a, b, c, d, e, f, g, h, i, j, k, l)
you'll get
instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i,
Eq j, Eq k, Eq l) =>
Eq (a, b, c, d, e, f, g, h, i, j, k, l)
That is, if the context doesn't fit on one line, we break it only
where necessary rather that after each item.
The test suite comparison ignores white space, so the change
produces no failures; its a UI thing. It's a one-character
change in TypeRep, so easily reversed.
Simon Peyton Jones [Wed, 3 Aug 2011 15:44:00 +0000 (16:44 +0100)]
Document the (lack of) escape conventions in quasiquotes
See Trac #5348
Simon Peyton Jones [Wed, 3 Aug 2011 15:22:06 +0000 (16:22 +0100)]
Fix a grevious error in InstEnv: Trac #5095
An claimed short-cut optimisation was actually an error.
The optimisation was this: when looking up (C a b), where
'a' and 'b' are type variables, we were returning [] immediately
if the instance environment had no instances of form (C a b).
Why? Because the thing being looked up definitely won't match
(C Int Bool), say.
BUT it will *unify* with (C Int Bool) and we care very much
about things it might unify with. If we neglect them we may
silently allow incoherent instance selection, and that is
exactly what happened in #5095.
The fix is easy: remove the "optimisation".
Simon Peyton Jones [Wed, 3 Aug 2011 15:18:53 +0000 (16:18 +0100)]
Simplify TcSMonad.matchFam's interface
Simon Peyton Jones [Wed, 3 Aug 2011 15:17:41 +0000 (16:17 +0100)]
Replace use of 'asTypeOf' by type signatures
The type signatures are much clearer, but need ScopedTypeVariables.
Happily that is now available in our bootstrap compilers.
Simon Peyton Jones [Wed, 3 Aug 2011 15:16:50 +0000 (16:16 +0100)]
Remove all escape handling from quasiquotes; fixes Trac #5348
There is a long discussion in the ticket.
Simon Peyton Jones [Wed, 3 Aug 2011 15:16:09 +0000 (16:16 +0100)]
Fix Trac #5372: a panic caused by over-eager error recovery
Simon Peyton Jones [Wed, 3 Aug 2011 15:15:29 +0000 (16:15 +0100)]
isCoVarType should look at the *representation* type,
rather than using isPredTy! In Core land, a PredTy
and its representation type are synonymous.
Simon Peyton Jones [Wed, 3 Aug 2011 15:14:26 +0000 (16:14 +0100)]
Add Type.tyConAppTyCon_maybe and tyConAppArgs_maybe, and use them
These turn out to be a useful special case of splitTyConApp_maybe.
A refactoring only; no change in behaviour
Simon Peyton Jones [Wed, 3 Aug 2011 15:12:10 +0000 (16:12 +0100)]
Comments only
Simon Peyton Jones [Wed, 3 Aug 2011 15:10:24 +0000 (16:10 +0100)]
Refactor to replace hscGetModuleExports by hscGetModuleInterface
I also tidied up the interfaces for LoadIface to be a bit simpler
Simon Marlow [Wed, 3 Aug 2011 10:24:14 +0000 (11:24 +0100)]
tiny cleanup
Simon Marlow [Wed, 3 Aug 2011 08:39:48 +0000 (09:39 +0100)]
Followup to #5289 changes: fix searching for dynamic libraries and use
of the RTS addDLL() API on Windows. When searching for DLLs we should
include the .dll extension, but addDLL() takes a filename without the
extension.
Simon Marlow [Tue, 2 Aug 2011 13:17:18 +0000 (14:17 +0100)]
Fix #5289 (loading libstdc++.so in GHCi), and also fix some other
linking scenarios. We weren't searching for .a archives to satisfy
-lfoo options on the GHCi command line, for example.
I've tidied up the code in this module so that dealing with -l options
on the command line is consistent with the handling of extra-libraries
for packages.
While I was here I moved some stuff out of Linker.hs that didn't seem
to belong here: dataConInfoPtrToName (now in new module DebuggerUtils)
and lessUnsafeCoerce (now in DynamicLoading, next to its only use)
Simon Peyton Jones [Wed, 3 Aug 2011 06:47:23 +0000 (07:47 +0100)]
Merge branch 'master' of darcs.haskell.org/ghc
Simon Peyton Jones [Wed, 3 Aug 2011 06:46:50 +0000 (07:46 +0100)]
Include the instances of associated types in the "extras" of a class
This fixes Trac #5147, which was going wrong because
the class ABI fingerprint wasn't changing when we added
or removed a Show instance to the associated type.
Ian Lynagh [Tue, 2 Aug 2011 23:53:57 +0000 (00:53 +0100)]
Refactor configure.ac's: Define FIND_GCC() in aclocal.m4
Ian Lynagh [Tue, 2 Aug 2011 23:49:10 +0000 (00:49 +0100)]
Refactor configure.ac's: Put XCODE_VERSION() in aclocal.m4
Ian Lynagh [Tue, 2 Aug 2011 23:37:24 +0000 (00:37 +0100)]
Small configure.ac refactoring
Ian Lynagh [Tue, 2 Aug 2011 21:40:58 +0000 (22:40 +0100)]
Merge branch 'master' of darcs.haskell.org/ghc
Simon Peyton Jones [Tue, 2 Aug 2011 21:03:21 +0000 (22:03 +0100)]
Avoid confusing Haddock in comment
Lennart Kolmodin [Wed, 20 Jul 2011 13:14:03 +0000 (15:14 +0200)]
Fix path to Cabal library, corrects documentation.
Simon Peyton Jones [Tue, 2 Aug 2011 17:04:22 +0000 (18:04 +0100)]
Merge branch 'master' of darcs.haskell.org/ghc
Simon Peyton Jones [Tue, 2 Aug 2011 17:03:46 +0000 (18:03 +0100)]
Fix reversed test in OccurAnal (introduced in recent commit
428f8c3d)
Simon Peyton Jones [Tue, 2 Aug 2011 16:29:50 +0000 (17:29 +0100)]
Wibble to main "Refactor the imports of InteractiveContext" patch
Simon Peyton Jones [Tue, 2 Aug 2011 16:29:16 +0000 (17:29 +0100)]
Improve pretty-printing for ambiguous imports etc
Simon Peyton Jones [Tue, 2 Aug 2011 12:35:13 +0000 (13:35 +0100)]
Add ListSetOps.removeRedundant
It's needed in ghc/InteractiveUI, although not in the compiler itself
Simon Peyton Jones [Tue, 2 Aug 2011 13:27:44 +0000 (14:27 +0100)]
Comment wibble (hash at start of line confused CPP)
Simon Peyton Jones [Tue, 2 Aug 2011 13:25:21 +0000 (14:25 +0100)]
Merge branch 'master' of darcs.haskell.org/ghc
Simon Peyton Jones [Tue, 2 Aug 2011 13:06:12 +0000 (14:06 +0100)]
Don't bleat about non-External names in mkUsageInfo
See Note [Internal used_names]. Fixes Trac #5362.
Simon Peyton Jones [Tue, 2 Aug 2011 12:34:35 +0000 (13:34 +0100)]
Add a comment
Simon Peyton Jones [Tue, 2 Aug 2011 12:34:06 +0000 (13:34 +0100)]
Fix import DEPRECATE failures for castSTUArray
Simon Peyton Jones [Tue, 2 Aug 2011 09:44:31 +0000 (10:44 +0100)]
Comments only
Simon Peyton Jones [Tue, 2 Aug 2011 09:43:57 +0000 (10:43 +0100)]
Change the representation of export lists in .hi files
Currently export list in .hi files are partitioned by module
export M T(C1,C2)
N f,g
In each list we only have OccNames, all assumed to come from
the parent module M or N resp.
This patch changes the representatation so that export lists
have full Names:
export M.T(M.C1,M.C2), N.f, N.g
Numerous advatages
* AvailInfo no longer needs to be parameterised; it always
contains Names
* Fixes Trac #5306. This was the main provocation
* Less to-and-fro conversion when reading interface files
It's all generally simpler. Interface files should not get bigger,
becuase they have a nice compact representation for Names.
Simon Peyton Jones [Tue, 2 Aug 2011 07:18:40 +0000 (08:18 +0100)]
Merge branch 'master' of darcs.haskell.org/ghc
Simon Peyton Jones [Tue, 2 Aug 2011 07:18:03 +0000 (08:18 +0100)]
Refactor the imports of InteractiveContext
Instead of two fields
ic_toplev_scope :: [Module]
ic_imports :: [ImportDecl RdrName]
we now just have one
ic_imports :: [InteractiveImport]
with the auxiliary data type
data InteractiveImport
= IIDecl (ImportDecl RdrName) -- Bring the exports of a particular module
-- (filtered by an import decl) into scope
| IIModule Module -- Bring into scope the entire top-level envt of
-- of this module, including the things imported
-- into it.
This makes lots of code less confusing. No change in behaviour.
It's preparatory to fixing Trac #5147.
While I was at I also
* Cleaned up the handling of the "implicit" Prelude import
by adding a ideclImplicit field to ImportDecl. This
significantly reduces plumbing in the handling of
the implicit Prelude import
* Used record notation consistently for ImportDecl
David Terei [Mon, 1 Aug 2011 20:37:13 +0000 (13:37 -0700)]
Merge branch 'master' of ssh://darcs.haskell.org/home/darcs/ghc
David Terei [Mon, 1 Aug 2011 20:36:30 +0000 (13:36 -0700)]
SafeHaskell: Fix bug with safe import check
Simon Peyton Jones [Mon, 1 Aug 2011 14:27:39 +0000 (15:27 +0100)]
Further simplification to OccurAnal, concerning "weak loop breakers"
Fixes Trac #5359.