- 13 Feb, 2002 14 commits
-
-
simonmar authored
Don't translate out negative (boxed) literals too early.
-
simonmar authored
Catch up with Haskell 98 revisions: allow sections like (++ x ++ y) and (3 + 4 +).
-
simonpj authored
------------------------------ Fix the "occurs check" so that it handles unifying a type variable with a type scheme ------------------------------ It's illegal to unify a type variable with a type scheme: a :=: (forall b. b->b) -> Int But I wasn't detecting that properly. Now, the same code that does the occurs check also looks for foralls.
-
simonpj authored
Import wibbles
-
simonmar authored
Add {-# OPTIONS -fno-implicit-prelude #-} to the top of GHC/PrimopWrappers.hs
-
simonmar authored
- Detect presence of a POSIX-compatible regex interface in configure, and omit Text.Regex.Posix (and hence Text.Regex) if it is missing. ToDo: pull in a suitably-licensed implementation of POSIX regex to be used in the event that the system doesn't supply one. - Rename old HaveRegex to HaveGNURegex.
-
simonmar authored
Use --update-package rather than --remove-package followed by --add-package
-
simonmar authored
Fixes to SplitObjs: we now put the split object files in a subdirectory M_split/ rather than just M/, because the latter interacts badly with our hierarchical module structure.
-
simonpj authored
------------------------------- dosifyPath before opening files ------------------------------- If you call hsc2hs foo/baz you get the amazing response: 'foo' is not recognized as an internal or external command, operable program or batch file. On the other hand hsc2hs foo\baz works fine. Solution: call dosifyPath before opening or writing the file. Somehow we should make it less easy to trip up when doing file I/O on Windows. And provide a library of path-manipulation primitives.
-
sof authored
Revised implementation of multi-threaded callouts (and callins): - unified synchronisation story for threaded and SMP builds, following up on SimonM's suggestion. The following synchro variables are now used inside the Scheduler: + thread_ready_cond - condition variable that is signalled when a H. thread has become runnable (via the THREAD_RUNNABLE() macro) and there are available capabilities. Waited on: + upon schedule() entry (iff no caps. available). + when a thread inside of the Scheduler spots that there are no runnable threads to service, but one or more external call is in progress. + in resumeThread(), waiting for a capability to become available. Prior to waiting on thread_ready_cond, a counter rts_n_waiting_tasks is incremented, so that we can keep track of the number of readily available worker threads (need this in order to make an informed decision on whether or not to create a new thread when an external call is made). + returning_worker_cond - condition variable that is waited on by an OS thread that has finished executing and external call & now want to feed its result back to the H thread that made the call. Before doing so, the counter rts_n_returning_workers is incremented. Upon entry to the Scheduler, this counter is checked for & if it is non-zero, the thread gives up its capability and signals returning_worker_cond before trying to re-grab a capability. (releaseCapability() takes care of this). + sched_mutex - protect Scheduler data structures. + gc_pending_cond - SMP-only condition variable for signalling completion of GCs. - initial implementation of call-ins, i.e., multiple OS threads may concurrently call into the RTS without interfering with each other. Implementation uses cheesy locking protocol to ensure that only one OS thread at a time can construct a function application -- stop-gap measure until the RtsAPI is revised (as discussed last month) *and* a designated block is used for allocating these applications. - In the implementation of call-ins, the OS thread blocks waiting for an RTS worker thread to complete the evaluation of the function application. Since main() also uses the RtsAPI, provide a separate entry point for it (rts_mainEvalIO()), which avoids creating a separate thread to evaluate Main.main, that can be done by the thread exec'ing main() directly. [Maybe there's a tidier way of doing this, a bit ugly the way it is now..] There are a couple of dark corners that needs to be looked at, such as conditions for shutting down (and how) + consider what ought to happen when async I/O is thrown into the mix (I know what will happen, but that's maybe not what we want). Other than that, things are in a generally happy state & I hope to declare myself done before the week is up.
-
sof authored
removed taskNotAvailable(), taskAvailable() and getTaskCount() - simplified away
-
sof authored
moved defn of RTS_SUPPORTS_THREADS from Rts.h to Stg.h
-
sof authored
uh, make that the StgTSOBlockReason enum
-
sof authored
Add BlockedOnCCall to StgTSOBlockInfo enum
-
- 12 Feb, 2002 13 commits
-
-
njn authored
Added note about the mangler removing unneeded SRTs.
-
simonmar authored
Must add 'depend' before 'all' in the boot target so that we get dependencies in time.
-
simonmar authored
This isn't needed any more
-
simonmar authored
Use LIBOBJS rather than OBJS when building the GHCi library.
-
sof authored
THREAD_RUNNABLE(): make available in threaded mode
-
sof authored
Snapshot (before heading into work): - thread_ready_aux_mutex is no more; use sched_mutex instead. - gc_pending_cond only used in SMP mode. - document the condition that thread_ready_cond captures.
-
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.
-