| Commit message (Collapse) | Author | Age | Files | Lines |
... | |
|
|
|
| |
export ModLocation(..)
|
|
|
|
| |
Wibble to printing FunTyCon in GHCi that makes :b GHC.Base work
|
|
|
|
| |
Dont try to output code for "naughty" record selectors
|
|
|
|
| |
-ddump-minimal-imports shouldn't turn off recompilation checking
|
|
|
|
|
| |
report the correct version number in the "compiled by GHC version.."
message in a bootstrapped compiler.
|
|
|
|
|
|
| |
make --mk-dll work with --make
Submitted by: Esa Ilari Vuokko <eivuokko@gmail.com>, thanks!
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
oops, it's i386_TARGET_ARCH, not x86_TARGET_ARCH
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
gcc's -fstrict-aliasing is biting us when we use the stack to store
different types of objects. For example:
*((StgDouble*)((W_)Sp-8)) = *((StgDouble*)((W_)Sp+8));
Sp[1] = (W_)&s1Cx_info;
gcc feels free to reorder these two lines, because they refer to
differently typed objects, even though the assignment to Sp[1] clearly
aliases the read from the same location.
Trying to fix this by accessing locations using union types might be
possible, but I took the sledgehammer approach of
-fno-strict-aliasing. This is justified to a certain extent because
our generated C code is derived from a very weakly-typed internal
language (C--).
|
|
|
|
|
|
|
| |
unless I'm mistaken, only x86 needs -ffloat-store. x86_64 certainly
doesn't need it, because it uses SSE2 with the correct-sized floating
point registers and doesn't store temporary results with more
precision than results in memory.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- Add support for the GHC_PACKAGE_PATH environment variable, which
specifies a :-separated (;-separated on Windows) list of package
database files. If the list ends in : (; on Windows), then the
normal user and global databases are added.
GHC_PACKAGE_PATH is searched left-to-right for packages, like
$PATH, but unlike -package-conf flags, which are searched
right-to-left. This isn't ideal, but it seemed the least worst to me
(command line flags always override right-to-left (except -i),
whereas the PATH environment variable overrides left-to-right, I chose
to follow the environment variable convention). I can always change
it if there's an outcry.
- Rationalise the interpretation of --user, --global, and -f on the
ghc-pkg command line. The story is now this: --user and --global
say which package database to *act upon*, they do not change the
shape of the database stack. -f pushes a database on the stack, and
also requests that the specified database be the one to act upon, for
commands that modify the database. If a database is already on the stack,
then -f just selects it as the one to act upon.
This means you can have a bunch of databases in GHC_PACKAGE_PATH, and
use -f to select the one to modify.
|
|
|
|
| |
x86_64: pass -fno-unit-at-a-time to gcc. See comment for details.
|
|
|
|
|
|
| |
Change the way in which the .exe suffix to the output file is added. The reason
is that "-o main" will generate main.exe on Windows while the doesFileExists "main"
in DriverPipeline.link will return False.
|
|
|
|
|
|
|
| |
The guessed output file should have ".exe" extension on Windows. ld tends to
add .exe automatically if the output file doesn't have extension but if
we don't add the extension explicitly then the doesFileExists check in
DriverPipeline.link will fail.
|
|
|
|
|
| |
Fixed the last commit, which broke the nightly builds. I'm not sure if
this is really a fix or a workaround only, though...
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add -stubdir option to control location of generated stub files. Also
do some clean up while I'm here - remove hscStubCOut/hscStubHOut from
DynFlags, and add
mkStubPaths :: DynFlags -> Module -> ModLocation -> (FilePath,FilePath)
to Finder. (this seemed better than caching the stub paths in every
ModLocation, because they are rarely needed and only present in home
modules, and are easily calculated from other available information).
-stubdir behaves in exactly the same way as -odir and -hidir.
|
|
|
|
|
|
|
|
|
|
|
|
| |
Change the default executable name to match the basename of the source
file containing the Main module (or the module specified by -main-is),
if there is one. On Windows, the .exe extension is added.
As requested on the ghc-users list, and as implemented by Tomasz
Zielonka <tomasz.zielonka at gmail.com>, with modifications by me.
I changed the type of the mainModIs field of DynFlags from Maybe
String to Module, which removed some duplicate code.
|
|
|
|
|
| |
Fix double "Linking ..." message, and mention the name of the
executable in the message.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
[mingw/msys only]
Undo long-standing workaround for buggy GNU ld's on mingw/msys; i.e.,
the linker wasn't correctly generating relocatable object files when
the number of relocs exceeded 2^16. Worked around the issue by
hackily splitting up the GHCi object file for the larger packages
('base', 'ObjectIO' and 'win32') into a handful of object files,
each with a manageable number of relocs. Tiresome and error-prone
(but the hack has served us well!)
This commit imposes a restriction on the 'ld' you use to compile
up GHC with; it now has to be ld-2.15.x or later (something GHC
binary dists have shipped with since 6.2.2)
|
|
|
|
| |
add missing boot files
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Two changes from Krasimir Angelov, which were required for Visual
Haskell:
- messaging cleanup throughout the compiler. DynFlags has a new
field:
log_action :: Severity -> SrcSpan -> PprStyle -> Message -> IO ()
this action is invoked for every message generated by the
compiler. This means a client of the GHC API can direct messages to
any destination, or collect them up in an IORef for later
perusal.
This replaces previous hacks to redirect messages in the GHC API
(hence some changes to function types in GHC.hs).
- The JustTypecheck mode of GHC now does what it says. It doesn't
run any of the compiler passes beyond the typechecker for each module,
but does generate the ModIface in order that further modules can be
typechecked.
And one change from me:
- implement the LANGUAGE pragma, finally
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Some more informative diagnostics for ghc -v about what the package
system is doing. This should help when diagnosing strange-looking
errors from GHC:
Using package config file: /home/simonmar/fp/lib/i386-unknown-linux/ghc-6.4.1/package.conf
package posix-1.0 will be ignored due to missing dependencies:
lang-1.0
package util-1.0 will be ignored due to missing dependencies:
lang-1.0
package data-1.0 will be ignored due to missing dependencies:
lang-1.0
package text-1.0 will be ignored due to missing dependencies:
lang-1.0
package Cabal-1.1.4 will be ignored due to missing dependencies:
util-1.0
*** Deleting temp files
Deleting:
ghc-6.4.1: unknown package: Cabal-1.1.4
|
|
|
|
| |
Fix a couple of problems with the "unknown package" error message
|
|
|
|
|
| |
Fix a bug I just found: hiding a package if later versions are exposed
wasn't actually checking the exposed flag.
|
|
|
|
| |
in --make mode, don't re-link when the executable is up to date.
|
|
|
|
|
| |
Fix last commit: it's opt_Static in the HEAD branch, not a local variable
"static".
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
A hack to make -dynamic work again:
when a library listed in extraLibraries ends with "_cbits", append "_dyn"
when -dynamic is passed, i.e. extraLibraries = ["foo", "HSbase_cbits"]
loads -lfoo and -lHSbase_cbits in the static case, but -lfoo and
-lHSbase_cbits_dyn in the -dynamic case.
It's an ugly hack, but it affects only the case when -dynamic is passed,
which would not work otherwise right now, so let's
MERGE TO STABLE
|
|
|
|
| |
Make -fno-code work again
|
|
|
|
|
|
| |
add pprInstanceHdr function. It is analogous to pprTyThingHdr and prints the
instance but without the "-- Defined at ...." comment. The function is used in
VStudio to populate the ClassView tree.
|
|
|
|
| |
fix bogus #ifdef in defaultHscTarget
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fix the location of _stub.o files when compiling with -odir. The
comment from the source:
-- The _stub.c file is derived from the haskell source file (but stored
-- in hscStubCOutName in the dflags for some reason, probably historical).
-- Consequently, we derive the _stub.o filename from the haskell object
-- filename.
--
-- This isn't necessarily the same as the object filename we
-- would get if we just compiled the _stub.c file using the pipeline.
-- For example:
--
-- ghc src/A.hs -odir obj
--
-- results in obj/A.o, and src/A_stub.c. If we compile src/A_stub.c with
-- -odir obj, we would get obj/src/A_stub.o, which is wrong; we want
-- obj/A_stub.o.
|
|
|
|
| |
Fix an SCC
|
|
|
|
|
|
|
| |
Make ghc -M work when you give multiple files with the same
module name. We want to do this to the STABLE branch too,
but this commit will not merge; it'll need to be done
afresh.
|
|
|
|
|
|
|
| |
When trimming type constructors for export, no need to trim enumerations,
because they don't give rise to any further exported things.
(Minor improvement: no need to merge)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
MERGE TO STABLE
Fix a long-standing bug in dependency tracking.
If you have
import M( x )
then you must recompile if M's export list changes, because it might
no longer export x. Until now we have only done that if the import was
import M
I can't think why this bug has lasted so long. Thanks to Ian Lynagh
for pointing it out.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
WARNING: this is a big commit. You might want
to wait a few days before updating, in case I've
broken something.
However, if any of the changes are what you wanted,
please check it out and test!
This commit does three main things:
1. A re-organisation of the way that GHC handles bindings in HsSyn.
This has been a bit of a mess for quite a while. The key new
types are
-- Bindings for a let or where clause
data HsLocalBinds id
= HsValBinds (HsValBinds id)
| HsIPBinds (HsIPBinds id)
| EmptyLocalBinds
-- Value bindings (not implicit parameters)
data HsValBinds id
= ValBindsIn -- Before typechecking
(LHsBinds id) [LSig id] -- Not dependency analysed
-- Recursive by default
| ValBindsOut -- After typechecking
[(RecFlag, LHsBinds id)]-- Dependency analysed
2. Implement Mark Jones's idea of increasing polymoprhism
by using type signatures to cut the strongly-connected components
of a recursive group. As a consequence, GHC no longer insists
on the contexts of the type signatures of a recursive group
being identical.
This drove a significant change: the renamer no longer does dependency
analysis. Instead, it attaches a free-variable set to each binding,
so that the type checker can do the dep anal. Reason: the typechecker
needs to do *two* analyses:
one to find the true mutually-recursive groups
(which we need so we can build the right CoreSyn)
one to find the groups in which to typecheck, taking
account of type signatures
3. Implement non-ground SPECIALISE pragmas, as promised, and as
requested by Remi and Ross. Certainly, this should fix the
current problem with GHC, namely that if you have
g :: Eq a => a -> b -> b
then you can now specialise thus
SPECIALISE g :: Int -> b -> b
(This didn't use to work.)
However, it goes further than that. For example:
f :: (Eq a, Ix b) => a -> b -> b
then you can make a partial specialisation
SPECIALISE f :: (Eq a) => a -> Int -> Int
In principle, you can specialise f to *any* type that is
"less polymorphic" (in the sense of subsumption) than f's
actual type. Such as
SPECIALISE f :: Eq a => [a] -> Int -> Int
But I haven't tested that.
I implemented this by doing the specialisation in the typechecker
and desugarer, rather than leaving around the strange SpecPragmaIds,
for the specialiser to find. Indeed, SpecPragmaIds have vanished
altogether (hooray).
Pragmas in general are handled more tidily. There's a new
data type HsBinds.Prag, which lives in an AbsBinds, and carries
pragma info from the typechecker to the desugarer.
Smaller things
- The loop in the renamer goes via RnExpr, instead of RnSource.
(That makes it more like the type checker.)
- I fixed the thing that was causing 'check_tc' warnings to be
emitted.
|
|
|
|
|
|
|
|
| |
- -package P picks the latest version of P, instead of complaining
if P is ambiguous.
- -hide-package P hides all versions of P, instead of complaining
if P is ambiguous.
|
|
|
|
|
|
|
|
|
| |
- -package P hides all other versions of P (this was advertised
in the documentation, but wasn't actually implemented in 6.4)
- if multiple packages with the same name are still exposed after
the flags have been processed, then all except the latest version
are hidden.
|
|
|
|
| |
handle PrimTyCons in pprTyConHdr (fixes :i GHC.Base.Int# in GHCi)
|
|
|
|
| |
export some more bits
|
|
|
|
|
|
| |
x86_64: Pass -fno-asynchronous-unwind-tables to gcc, which eliminates
some unnecessary junk from the via-C generated code and allows
-split-objs to work.
|
|
|
|
|
| |
genOutputFilenameFunc: fix output filename generated for non-Haskell
compilations with -odir.
|
|
|
|
|
|
| |
pkgIdMap should include adjustments made by -package flags (it used
to; I broke this yesterday). Also add origPkgIdMap for keeping the
original package database - this might be needed in the future.
|
|
|
|
| |
Check the result of GHC.depanal for errors.
|
|
|
|
| |
fix Windows build
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Relax the restrictions on conflicting packages. This should address
many of the traps that people have been falling into with the current
package story.
Now, a local module can shadow a module in an exposed package, as long
as the package is not otherwise required by the program. GHC checks
for conflicts when it knows the dependencies of the module being
compiled.
Also, we now check for module conflicts in exposed packages only when
importing a module: if an import can be satisfied from multiple
packages, that's an error. It's not possible to prevent GHC from
starting by installing packages now (unless you install another base
package).
It seems to be possible to confuse GHCi by having a local module
shadowing a package module that goes away and comes back again. I
think it's nearly right, but strange happenings have been observed.
I'll try to merge this into the STABLE branch.
|
|
|
|
| |
Add pprTyThingHdr function.
|
|
|
|
| |
Fix -optdep--exclude-module (looks like this has been broken for a while)
|
|
|
|
| |
Fix stage1 compilation
|