- 12 Feb, 2002 7 commits
-
-
sof authored
- give rts_n_free_capabilities an interpretation in threaded mode (possible values: 0,1) - noFreeCapabilities() -? noCapabilities()
-
simonmar authored
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 :-(
-
simonmar authored
Fix bug in previous commit
-
simonmar authored
fromInt ==> fromIntegral
-
sof authored
bring stuff in parallel/ into scope when running 'mkdependC'
-
sof authored
comment wibble
-
chak authored
This fixes a problem with the recent clean up in the parsing of type declarations. The cleaned up version was correct by H98 (I think), but unfortunately won't compile the Prelude anymore. I made the definition a little bit more liberal as follows: - In `tycl_hdr' allow `gtycon' instead of just `tycon' for the defined type constructor. This allows beyond H98 special syntax like "[]" etc as well as tycon ops in parenthesis. Moreover, it allows qualified names, but the renamer flags the latter as errors. - Allow `gtycon' instead of only `qtycon' for the class name in definitions of the form `Eq a => T a' to avoid a whole list of s/r conflicts. (I have *not* checked that the renamer flags misuse, but I would expect that it does.) ToDo: I think, the renamer should raise an error for all these additional forms *unless* -fglasgow-exts is given. In PrelBase, I needed to replace the infix notation by prefix notation in the definition of `:+:' and `:*:'.
-
- 11 Feb, 2002 13 commits
-
-
simonmar authored
- Addr ==> Ptr - Don't directly import PrelIOBase & PrelBase
-
simonmar authored
fromInt ==> fromIntegral
-
simonpj authored
Wibble
-
simonmar authored
Fix lexer bug: we didn't look far enough ahead when parsing 1.0e+x (i.e. the e+x shouldn't be treated as an exponent).
-
simonpj authored
Documentation for kinded declarations
-
simonpj authored
---------------------------------- Implement kinded type declarations ---------------------------------- This commit allows the programmer to supply kinds in * data decls * type decls * class decls * 'forall's in types e.g. data T (x :: *->*) = MkT type Composer c = forall (x :: * -> *) (y :: * -> *) (z :: * -> *). (c y z) -> (c x y) -> (c x z); This is occasionally useful. It turned out to be convenient to add the form (type :: kind) to the syntax of types too, so you can put kind signatures in types as well.
-
simonmar authored
fromInt ==> fromIntegral
-
chak authored
Documentation for the parallel array extension merged earlier. (This documents Milestone 1 as well as some of the basics of flattening.)
-
simonmar authored
Add a missing dependency (submitted by Volker Stolz; thanks)
-
simonpj authored
------------------------------ Towards kinded data type decls ------------------------------ Move towards being able to have 'kinded' data type decls. The burden of this commit, though, is to tidy up the parsing of data type decls. Previously we had data ctype '=' constrs where the 'ctype' is a completetely general polymorphic type. forall a. (Eq a) => T a Then a separate function checked that it was of a suitably restricted form. The reason for this is the usual thing --- it's hard to tell when looking at data Eq a => T a = ... whether you are reading the data type or the context when you have only got as far as 'Eq a'. However, the 'ctype' trick doesn't work if we want to allow data T (a :: * -> *) = ... So we have to parse the data type decl in a more serious way. That's what this commit does, and it makes the grammar look much nicer. The main new producion is tycl_hdr.
-
simonpj authored
Remove unused rules
-
chak authored
Updated to the use of [~N] in rules implementing foldr/build.
-
chak authored
******************************* * Merging from ghc-ndp-branch * ******************************* This commit merges the current state of the "parallel array extension" and includes the following: * (Almost) completed Milestone 1: - The option `-fparr' activates the H98 extension for parallel arrays. - These changes have a high likelihood of conflicting (in the CVS sense) with other changes to GHC and are the reason for merging now. - ToDo: There are still some (less often used) functions not implemented in `PrelPArr' and a mechanism is needed to automatically import `PrelPArr' iff `-fparr' is given. Documentation that should go into the Commentary is currently in `ghc/compiler/ndpFlatten/TODO'. * Partial Milestone 2: - The option `-fflatten' activates the flattening transformation and `-ndp' selects the "ndp" way (where all libraries have to be compiled with flattening). The way option `-ndp' automagically turns on `-fparr' and `-fflatten'. - Almost all changes are in the new directory `ndpFlatten' and shouldn't affect the rest of the compiler. The only exception are the options and the points in `HscMain' where the flattening phase is called when `-fflatten' is given. - This isn't usable yet, but already implements function lifting, vectorisation, and a new analysis that determines which parts of a module have to undergo the flattening transformation. Missing are data structure and function specialisation, the unboxed array library (including fusion rules), and lots of testing. I have just run the regression tests on the thing without any problems. So, it seems, as if we haven't broken anything crucial.
-
- 08 Feb, 2002 7 commits
-
-
simonmar authored
Remove dependency on package text.
-
simonmar authored
Avoid using findPS/packString where simple string matching will do.
-
simonmar authored
Don't use RegexString to parse OPTIONS pragmas, instead do the matching by hand, thereby removing a dependency on RegexString (and hence Regex).
-
sewardj authored
Back out rev 1.28. In retrospect saving the pre-messed-with %esp in a global location is thread/reentrancy unsafe and a brain-dead thing to do, and we can't think of a clean way to fix this. So am backing it out.
-
simonpj authored
Improve wording slightly
-
sof authored
naive script for preparing a binary-dist tree for the installer
-
sof authored
declare MainCapability + simplify releaseCapability()
-
- 07 Feb, 2002 10 commits
-
-
sewardj authored
Describe ultrakludge^Hclever engineering which makes IO types work in the interpreter.
-
sewardj authored
Add many details about bytecode generation, the interpreter, and compiled/interpreted code interop.
-
simonpj authored
Remove duplication of CVS info, and improve Win32 notes
-
simonpj authored
------------------------------------------- Improve the "stragely-kinded tyvar" problem ------------------------------------------- When the type checker finds a type variable with no binding, which means it can be instantiated with an arbitrary type, it usually instantiates it to Void. Eg. length [] ===> length Void (Nil Void) But in really obscure programs, the type variable might have a kind other than *, so we need to invent a suitably-kinded type. This commit uses Void for kind * List for kind *->* Tuple for kind *->...*->* which deals with most cases. (Previously, it only dealt with kind *.) In the other cases, it just makes up a TyCon with a suitable kind. If this gets into an interface file, anyone reading that file won't understand it. This is fixable (by making the client of the interface file make up a TyCon too) but it is tiresome and never happens, so I am leaving it. Most of the added lines are comments.
-
simonpj authored
-------------------------------------------------- Slurp in a few more instance decls with ghc --make -------------------------------------------------- ghc --make wasn't slurping in quite enough instance decls. The relevant comment is in RnIfaces; the new part is marked. George Russel's Uniform showed this up. We slurp in an instance decl from the gated instance pool iff all its gates are either in the gates of the module, or are a previously-loaded tycon or class. The latter constraint is because there might have been an instance decl slurped in during an earlier compilation, like this: instance Foo a => Baz (Maybe a) where ... In the module being compiled we might need (Baz (Maybe T)), where T is defined in this module, and hence we need (Foo T). So @Foo@ becomes a gate. But there's no way to 'see' that. NEW: More generally, types might be involved as well: NEW: instance Foo2 T a => Baz2 a where ... NEW: NEW: Now we must treat T as a gate too, as well as Foo. So the solution NEW: we adopt is: NEW: NEW: we simply treat all previously-loaded NEW: tycons and classes as gates. NEW: NEW: This gloss only affects ghc --make and ghc --interactive.
-
simonpj authored
---------------------------------------------------- Make TcType.match and TcUnify.uUnboundVar kind-aware ---------------------------------------------------- George Russel had apparently-overlapping (ha) instance decls like instance .. => C (a b) where instance .. => C (x y) where But the a,b and x,y were different kinds! Turned out that TcType.unify was kind-aware (so we didn't report a duplicate instance decl, but TcType.match was not (so we simply selected the wrong one, and got a mis-kinded constraint popping up from the ".." part. Very exciting to track down. I also make the ordinary unification kind-aware in the same way. It's quite legitimate to attempt to unify, say, (a b) with (c d) but the unification should fail if a's kind differs from c's. (There was a kind of debug warning before, but it's actually not an error in the compiler... so it should just make unification fail gracefully.)
-
simonpj authored
Better pretty printing
-
simonmar authored
clean $(HC_OBJS) too
-
simonmar authored
- update some comments - split up DERIVED_SRCS into separate variables so we can refer to them separately in the specification of the various CLEAN_FILES variables. - only clean happy-generated files in maintainer-clean mode
-
sof authored
Little bit more doc on suspended_ccalling_threads
-
- 06 Feb, 2002 3 commits
-
-
sof authored
unbreak stdcall handling (caused by recent change to Outputable instance for CCallConv)
-
simonpj authored
Eliminate all vestiages of UsageTy, in preparation for Keith's new version. Hurrah! Keith: LBVarInfo and usOnce,usMany are still there, because I know you have eliminated LBVarInfo, and I didn't want to cause unnecessary conflicts.
-
sewardj authored
x86 only: make %esp be 8-aligned before entering HC-world code. This avoids misalignment penalties for C doubles stored on the C stack. A quick test using nofib/imaginary/rfib shows that getting this wrong increases run time by about 10% on our 1 GHz PIII.
-