| Commit message (Collapse) | Author | Age | Files | Lines |
... | |
|
|
|
| |
Fix to build with 4.08.x
|
|
|
|
|
| |
Use ioError instead of throw for IOErrors, in anticipation of
a change from IOError = Exception to IOError = IOException.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------
Fix a newtype-deriving bug
------------------
The new newtype-deriving mechanism was erroneously using the
*representation type* of the newtype. The rep type looks through all
ihtermediate newtypes, so that is wrong. See Note [newtype
representation] in TcDeriv.lhs
deriving/should_run/drvrun013 now tests for this.
|
|
|
|
| |
Move looksLikeModuleName here from InterativeUI, so we can use it elsewhere.
|
|
|
|
| |
Don't need to export Exception.try or Exception.throwDyn here.
|
|
|
|
| |
make it compile again with 4.08.x
|
|
|
|
| |
Compatibility fixes for Exception.try
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------
Implement recursive do-notation
--------------------------------
This commit adds recursive do-notation, which Hugs has had for some time.
mdo { x <- foo y ;
y <- baz x ;
return (y,x) }
turns into
do { (x,y) <- mfix (\~(x,y) -> do { x <- foo y;
y <- baz x }) ;
return (y,x) }
This is all based on work by Levent Erkok and John Lanuchbury.
The really tricky bit is in the renamer (RnExpr.rnMDoStmts) where
we break things up into minimal segments. The rest is easy, including
the type checker.
Levent laid the groundwork, and Simon finished it off. Needless to say,
I couldn't resist tidying up other stuff, so there's no guaranteed I
have not broken something.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fix up exception handling when reading an interface file, and make it
compile with 4.08.x again.
GhcExceptions weren't being caught by readIface, so an error when
reading an interface could be unintentionally fatal (errors should be
soft when reading the old interface file for the current module).
Also, the Interrupted exception should not be caught by readIface,
because we want ^C to behave as normal when reading interface files
(currently it causes an interface-file read error rather than
interrupting the whole compiler).
Some exception-related compatibility functions have been moved from
Util to Panic.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------
Make Template Haskell into the HEAD
--------------------------------------
This massive commit transfers to the HEAD all the stuff that
Simon and Tim have been doing on Template Haskell. The
meta-haskell-branch is no more!
WARNING: make sure that you
* Update your links if you are using link trees.
Some modules have been added, some have gone away.
* Do 'make clean' in all library trees.
The interface file format has changed, and you can
get strange panics (sadly) if GHC tries to read old interface files:
e.g. ghc-5.05: panic! (the `impossible' happened, GHC version 5.05):
Binary.get(TyClDecl): ForeignType
* You need to recompile the rts too; Linker.c has changed
However the libraries are almost unaltered; just a tiny change in
Base, and to the exports in Prelude.
NOTE: so far as TH itself is concerned, expression splices work
fine, but declaration splices are not complete.
---------------
The main change
---------------
The main structural change: renaming and typechecking have to be
interleaved, because we can't rename stuff after a declaration splice
until after we've typechecked the stuff before (and the splice
itself).
* Combine the renamer and typecheker monads into one
(TcRnMonad, TcRnTypes)
These two replace TcMonad and RnMonad
* Give them a single 'driver' (TcRnDriver). This driver
replaces TcModule.lhs and Rename.lhs
* The haskell-src library package has a module
Language/Haskell/THSyntax
which defines the Haskell data type seen by the TH programmer.
* New modules:
hsSyn/Convert.hs converts THSyntax -> HsSyn
deSugar/DsMeta.hs converts HsSyn -> THSyntax
* New module typecheck/TcSplice type-checks Template Haskell splices.
-------------
Linking stuff
-------------
* ByteCodeLink has been split into
ByteCodeLink (which links)
ByteCodeAsm (which assembles)
* New module ghci/ObjLink is the object-code linker.
* compMan/CmLink is removed entirely (was out of place)
Ditto CmTypes (which was tiny)
* Linker.c initialises the linker when it is first used (no need to call
initLinker any more). Template Haskell makes it harder to know when
and whether to initialise the linker.
-------------------------------------
Gathering the LIE in the type checker
-------------------------------------
* Instead of explicitly gathering constraints in the LIE
tcExpr :: RenamedExpr -> TcM (TypecheckedExpr, LIE)
we now dump the constraints into a mutable varabiable carried
by the monad, so we get
tcExpr :: RenamedExpr -> TcM TypecheckedExpr
Much less clutter in the code, and more efficient too.
(Originally suggested by Mark Shields.)
-----------------
Remove "SysNames"
-----------------
Because the renamer and the type checker were entirely separate,
we had to carry some rather tiresome implicit binders (or "SysNames")
along inside some of the HsDecl data structures. They were both
tiresome and fragile.
Now that the typechecker and renamer are more intimately coupled,
we can eliminate SysNames (well, mostly... default methods still
carry something similar).
-------------
Clean up HsPat
-------------
One big clean up is this: instead of having two HsPat types (InPat and
OutPat), they are now combined into one. This is more consistent with
the way that HsExpr etc is handled; there are some 'Out' constructors
for the type checker output.
So:
HsPat.InPat --> HsPat.Pat
HsPat.OutPat --> HsPat.Pat
No 'pat' type parameter in HsExpr, HsBinds, etc
Constructor patterns are nicer now: they use
HsPat.HsConDetails
for the three cases of constructor patterns:
prefix, infix, and record-bindings
The *same* data type HsConDetails is used in the type
declaration of the data type (HsDecls.TyData)
Lots of associated clean-up operations here and there. Less code.
Everything is wonderful.
|
|
|
|
|
|
| |
Put debugging output in #ifdef DEBUG
MERGE TO STABLE
|
|
|
|
|
|
|
| |
Finally separate the compiler from hslibs.
Mainly import wibbles, and use the new POSIX library when
bootstrapping.
|
|
|
|
| |
Remove unused import of PrelPack (should fix the build again)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Housekeeping:
- The main goal is to remove dependencies on hslibs for a
bootstrapped compiler, leaving only a requirement that the
packages base, haskell98 and readline are built in stage 1 in
order to bootstrap. We're almost there: Posix is still required
for signal handling, but all other dependencies on hslibs are now
gone.
Uses of Addr and ByteArray/MutableByteArray array are all gone
from the compiler. PrimPacked defines the Ptr type for GHC 4.08
(which didn't have it), and it defines simple BA and MBA types to
replace uses of ByteArray and MutableByteArray respectively.
- Clean up import lists. HsVersions.h now defines macros for some
modules which have moved between GHC versions. eg. one now
imports 'GLAEXTS' to get at unboxed types and primops in the
compiler.
Many import lists have been sorted as per the recommendations in
the new style guidelines in the commentary.
I've built the compiler with GHC 4.08.2, 5.00.2, 5.02.3, 5.04 and
itself, and everything still works here. Doubtless I've got something
wrong, though.
|
|
|
|
| |
printDump,printErrs,printSDoc: flush stdout and stderr
|
|
|
|
|
|
|
|
| |
In hPutLitString, catch the empty string case before calling hPutBuf.
Some older versions of hPutBufFull choke on a zero-length buffer.
Fixes occasional problems with the Sparc native code generator, which
uses SLIT("") in a couple of places.
|
|
|
|
| |
Use Unique.getKey instead of Unique.u2i (they are the same function).
|
|
|
|
| |
speakNth works for 11,12,13
|
|
|
|
|
| |
Include hschooks.h via a global option to get ghc_strlen's
prototype. It's too omnipresent for per-file OPTIONS.
|
|
|
|
| |
Re-enable bootstrapping: More Ptr trouble, now that it's (almost) abstract...
|
|
|
|
|
| |
In the get method for FastString, do the dictionary lookup strictly
(speeds things up and reduces the residency by a few k).
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- When converting ModuleNames to Modules for use in the the module
initialisation code, look them up in the IfaceTable(s) instead of
calling findModule again. They are guaranteed to be in either
the HomeIfaceTable or the PackageIfaceTable after the renamer,
so this saves some trips to the filesystem. Also, move this
code earlier in the compilation cycle to avoid holding on to the
renamed syntax for too long (not sure if this makes a difference or
not, but it definitely looked space-leakish before).
- remove Util.unJust, it is a duplicate of Maybes.expectJust
|
|
|
|
|
|
|
|
|
|
|
|
| |
- Fix bootstrapped compilation,
- Add the following RULE:
text "abc" ==> ptext SLIT("abc")
so most of the time there shouldn't be any need to use SLIT().
I'll go around and apply the opposite of the above RULE once
I've convinced myself that the RULE does what it should.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
FastString cleanup, stage 1.
The FastString type is no longer a mixture of hashed strings and
literal strings, it contains hashed strings only with O(1) comparison
(except for UnicodeStr, but that will also go away in due course). To
create a literal instance of FastString, use FSLIT("..").
By far the most common use of the old literal version of FastString
was in the pattern
ptext SLIT("...")
this combination still works, although it doesn't go via FastString
any more. The next stage will be to remove the need to use this
special combination at all, using a RULE.
To convert a FastString into an SDoc, now use 'ftext' instead of
'ptext'.
I've also removed all the FAST_STRING related macros from HsVersions.h
except for SLIT and FSLIT, just use the relevant functions from
FastString instead.
|
|
|
|
|
| |
Define out-of-line versions of strlen and memcmp for PrimPacked, and
remove the -monly-2-regs flag.
|
|
|
|
| |
Replace strncmp() with memcmp() for comparing non-zero-terminated strings.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------
Mainly derived Read
-------------------
This commit is a tangle of several things that somehow got wound up
together, I'm afraid.
The main course
~~~~~~~~~~~~~~~
Replace the derived-Read machinery with Koen's cunning new parser
combinator library. The result should be
* much smaller code sizes from derived Read
* faster execution of derived Read
WARNING: I have not thoroughly tested this stuff; I'd be glad if you did!
All the hard work is done, but there may be a few nits.
The Read class gets two new methods, not exposed
in the H98 inteface of course:
class Read a where
readsPrec :: Int -> ReadS a
readList :: ReadS [a]
readPrec :: ReadPrec a -- NEW
readListPrec :: ReadPrec [a] -- NEW
There are the following new libraries:
Text.ParserCombinators.ReadP Koens combinator parser
Text.ParserCombinators.ReadPrec Ditto, but with precedences
Text.Read.Lex An emasculated lexical analyser
that provides the functionality
of H98 'lex'
TcGenDeriv is changed to generate code that uses the new libraries.
The built-in instances of Read (List, Maybe, tuples, etc) use the new
libraries.
Other stuff
~~~~~~~~~~~
1. Some fixes the the plumbing of external-core generation. Sigbjorn
did most of the work earlier, but this commit completes the renaming and
typechecking plumbing.
2. Runtime error-generation functions, such as GHC.Err.recSelErr,
GHC.Err.recUpdErr, etc, now take an Addr#, pointing to a UTF8-encoded
C string, instead of a Haskell string. This makes the *calls* to these
functions easier to generate, and smaller too, which is a good thing.
In particular, it means that MkId.mkRecordSelectorId doesn't need to
be passed "unpackCStringId", which was GRUESOME; and that in turn means
that tcTypeAndClassDecls doesn't need to be passed unf_env, which is
a very worthwhile cleanup. Win/win situation.
3. GHC now faithfully translates do-notation using ">>" for statements
with no binding, just as the report says. While I was there I tidied
up HsDo to take a list of Ids instead of 3 (but now 4) separate Ids.
Saves a bit of code here and there. Also introduced Inst.newMethodFromName
to package a common idiom.
|
|
|
|
| |
Friday afternoon pet peeve removal: define (Util.notNull :: [a] -> Bool) and use it
|
|
|
|
| |
Make this compile with 4.08.
|
|
|
|
|
|
| |
The hPutBuf bug looks to be in 5.00 as well as 4.08 - so enable the
workaround on GHC <= 5.00. Hopefully should fix bootstrapping
problems on Alpha.
|
|
|
|
| |
Fixed imports for GHC >= 5.03
|
|
|
|
| |
Split out FastMutInt separately
|
|
|
|
| |
Comments
|
|
|
|
|
| |
Misc cleanup: remove the iface pretty-printing style, and clean up
bits of StringBuffer that aren't required any more.
|
|
|
|
|
| |
Turn "return e" into "return $! e" in several places to improve
performance.
|
|
|
|
| |
GHC version wibble
|
|
|
|
|
|
|
| |
Add a magic number to the beginning of interface files (0x1face :-) to
avoid trying to read old text-style interfaces as binary (the usual
result is an attempt to allocate a ByteArray larger than the available
memory size and an obscure crash).
|
|
|
|
| |
import openFileEx and IOModeEx(..)
|
|
|
|
| |
Read and write interfaces in binary mode; important for Win32
|
|
|
|
| |
debugging-by-nightly-build-report: make it 4.08 compatible again..?
|
|
|
|
| |
Copyright acknowledgement.
|
|
|
|
| |
make it compile with 5.02
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Binary Interface Files - stage 1
--------------------------------
This commit changes the default interface file format from text to
binary, in order to improve compilation performace.
To view an interface file, use 'ghc --show-iface Foo.hi'.
utils/Binary.hs is the basic Binary I/O library, based on the nhc98
binary I/O library but much stripped-down and working in terms of
bytes rather than bits, and with some special features for GHC: it
remembers which Module is being emitted to avoid dumping too many
qualified names, and it keeps track of a "dictionary" of FastStrings
so that we don't dump the same FastString more than once into the
binary file. I'll make a generic version of this for the libraries at
some point.
main/BinIface.hs contains most of the Binary instances. Some
instances are in the same module as the data type (RdrName, Name,
OccName in particular). Most instances were generated using a
modified version of DrIFT, which I'll commit later. However, editing
them by hand isn't hard (certainly easier than modifying
ParseIface.y).
The first thing in a binary interface is the interface version, so
nice error messages will be generated if the binary format changes and
you still have old interfaces lying around. The version also now
includes the "way" as an extra sanity check.
Other changes
-------------
I don't like the way FastStrings contain both hashed strings (with
O(1) comparison) and literal C strings (with O(n) comparison). So as
a first step to separating these I made serveral "literal" type
strings into hashed strings. SLIT() still generates a literal, and
now FSLIT() generates a hashed string. With DEBUG on, you'll get a
warning if you try to compare any SLIT()s with anything, and the
compiler will fall over if you try to dump any literal C strings into
an interface file (usually indicating a use of SLIT() which should be
FSLIT()).
mkSysLocal no longer re-encodes its FastString argument each time it
is called.
I also fixed the -pgm options so that the argument can now optionally
be separted from the option.
Bugfix: PrelNames declared Names for several comparison primops, eg.
eqCharName, eqIntName etc. but these had different uniques from the
real primop names. I've moved these to PrimOps and defined them using
mkPrimOpIdName instead, and deleted some for which we don't have real
primops (Manuel: please check that things still work for you after
this change).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Switch over to the new hierarchical libraries
---------------------------------------------
This commit reorganises our libraries to use the new hierarchical
module namespace extension.
The basic story is this:
- fptools/libraries contains the new hierarchical libraries.
Everything in here is "clean", i.e. most deprecated stuff has
been removed.
- fptools/libraries/base is the new base package
(replacing "std") and contains roughly what was previously
in std, lang, and concurrent, minus deprecated stuff.
Things that are *not allowed* in libraries/base include:
Addr, ForeignObj, ByteArray, MutableByteArray,
_casm_, _ccall_, ``'', PrimIO
For ByteArrays and MutableByteArrays we use UArray and
STUArray/IOUArray respectively now.
Modules previously called PrelFoo are now under
fptools/libraries/GHC. eg. PrelBase is now GHC.Base.
- fptools/libraries/haskell98 provides the Haskell 98 std.
libraries (Char, IO, Numeric etc.) as a package. This
package is enabled by default.
- fptools/libraries/network is a rearranged version of
the existing net package (the old package net is still
available; see below).
- Other packages will migrate to fptools/libraries in
due course.
NB. you need to checkout fptools/libraries as well as
fptools/hslibs now. The nightly build scripts will need to be
tweaked.
- fptools/hslibs still contains (almost) the same stuff as before.
Where libraries have moved into the new hierarchy, the hslibs
version contains a "stub" that just re-exports the new version.
The idea is that code will gradually migrate from fptools/hslibs
into fptools/libraries as it gets cleaned up, and in a version or
two we can remove the old packages altogether.
- I've taken the opportunity to make some changes to the build
system, ripping out the old hslibs Makefile stuff from
mk/target.mk; the new package building Makefile code is in
mk/package.mk (auto-included from mk/target.mk).
The main improvement is that packages now register themselves at
make boot time using ghc-pkg, and the monolithic package.conf
in ghc/driver is gone.
I've updated the standard packages but haven't tested win32,
graphics, xlib, object-io, or OpenGL yet. The Makefiles in
these packages may need some further tweaks, and they'll need
pkg.conf.in files added.
- Unfortunately all this rearrangement meant I had to bump the
interface-file version and create a bunch of .hi-boot-6 files :-(
|
|
|
|
| |
fromInt ==> fromIntegral
|
|
|
|
|
|
|
|
| |
Generalise types of minusUFM and intersectUFM_C (this was applied long
ago to FiniteMap, IIRC).
Untested: I haven't got a build tree handy, so please shoot me if this
2-line change to two type signatures is type-incorrect. Sorry!
|
|
|
|
| |
Warn, dont crash, when isIn gets a big list
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Get rid of multiple-result MachOps (MO_NatS_AddC, MO_NatS_SubC,
MO_NatS_MulC) which implement {add,sub,mul}IntC#. Supporting gunk
in the NCG disappears as a result.
Instead:
* {add,sub}IntC# are translated out during abstract C simplification,
turning into the xor-xor-invert-and-shift sequence previously defined
in PrimOps.h.
* mulIntC# is more difficult to get rid of portably. Instead we have
a new single-result PrimOp, mulIntMayOflo, with corresponding MachOp
MO_NatS_MulMayOflo. This tells you whether a W x W -> W signed
multiply might overflow, where W is the word size. When W=32, is
implemented by computing a 2W-long result. When W=64, we use the
previous approximation.
PrelNum.lhs' implementation of timesInteger changes slightly, to use
the new PrimOp.
|
|
|
|
| |
More shifting #ifdef-ery... :-P
|
|
|
|
|
| |
Make this module compile with the recent changes to the names of the
shift primops.
|