- 30 Dec, 2003 2 commits
-
-
simonpj authored
---------------------------- Re-do kind inference (again) ---------------------------- [WARNING: interface file binary representation has (as usual) changed slightly; recompile your libraries!] Inspired by the lambda-cube, for some time GHC has used type Kind = Type That is, kinds were represented by the same data type as types. But GHC also supports unboxed types and unboxed tuples, and these complicate the kind system by requiring a sub-kind relationship. Notably, an unboxed tuple is acceptable as the *result* of a function but not as an *argument*. So we have the following setup: ? / \ / \ ?? (#) / \ * # where * [LiftedTypeKind] means a lifted type # [UnliftedTypeKind] means an unlifted type (#) [UbxTupleKind] means unboxed tuple ?? [ArgTypeKind] is the lub of *,# ? [OpenTypeKind] means any type at all In particular: error :: forall a:?. String -> a (->) :: ?? -> ? -> * (\(x::t) -> ...) Here t::?? (i.e. not unboxed tuple) All this has beome rather difficult to accommodate with Kind=Type, so this commit splits the two. * Kind is a distinct type, defined in types/Kind.lhs * IfaceType.IfaceKind disappears: we just re-use Kind.Kind * TcUnify.unifyKind is a distinct unifier for kinds * TyCon no longer needs KindCon and SuperKindCon variants * TcUnify.zapExpectedType takes an expected Kind now, so that in TcPat.tcMonoPatBndr we can express that the bound variable must have an argTypeKind (??). The big change is really that kind inference is much more systematic and well behaved. In particular, a kind variable can unify only with a "simple kind", which is built from * and (->). This deals neatly with awkward questions about how we can combine sub-kinding with type inference. Lots of small consequential changes, especially to the kind-checking plumbing in TcTyClsDecls. (We played a bit fast and loose before, and now we have to be more honest, in particular about how kind inference works for type synonyms. They can have kinds like (* -> #), so This cures two long-standing SourceForge bugs * 753777 (tcfail115.hs), which used erroneously to pass, but crashed in the code generator type T a = Int -> (# Int, Int #) f :: T a -> T a f t = \x -> case t x of r -> r * 753780 (tc167.hs), which used erroneously to fail f :: (->) Int# Int# Still, the result is not entirely satisfactory. In particular * The error message from tcfail115 is pretty obscure * SourceForge bug 807249 (Instance match failure on openTypeKind) is not fixed. Alas.
-
simonpj authored
Import trimming
-
- 28 Dec, 2003 2 commits
- 23 Dec, 2003 1 commit
-
-
simonmar authored
Add performMajorGC
-
- 22 Dec, 2003 1 commit
-
-
simonmar authored
Fix threaded RTS problem that is currently causing the conc007 test to loop indefinitely. Comment from the source regarding this change: /* Major bogosity: * * In the threaded RTS, we can't set the virtual timer because the * thread which has the virtual timer might be sitting waiting for a * capability, and the virtual timer only ticks in CPU time. * * So, possible solutions: * * (1) tick in realtime. Not very good, because this ticker is used for * profiling, and this will give us unreliable time profiling * results. Furthermore, this requires picking a single OS thread * to be the timekeeper, which is a bad idea because the thread in * question might just be making a temporary call into Haskell land. * * (2) save/restore the virtual timer around excursions into STG land. * Sounds great, but I tried it and the resolution of the virtual timer * isn't good enough (on Linux) - most of our excursions fall * within the timer's resolution and we never make any progress. * * (3) have a virtual timer in every OS thread. Might be reasonable, * because most of the time there is only ever one of these * threads running, so it approximates a single virtual timer. * But still quite bogus (and I got crashes when I tried this). * * For now, we're using (1), but this needs a better solution. --SDM */
-
- 19 Dec, 2003 3 commits
-
-
simonmar authored
Fix DEBUG & !RTS_SUPPORTS_THREADS build (bogus assertion failure)
-
simonpj authored
Accept unboxed tuples in type signatures
-
simonpj authored
--------------------------------------- Precise locations for duplicate imports --------------------------------------- As a displacment activity I added reporting for duplicate imports And more precise locations for the imports themselves. For example: module T where import Maybe (isJust,isJust) import Maybe (isJust) gives Foo.hs: Warning: `isJust' is imported more than once: imported from Maybe at Foo.hs:4:16-21 imported from Maybe at Foo.hs:3:23-28 imported from Maybe at Foo.hs:3:16-21
-
- 18 Dec, 2003 8 commits
-
-
panne authored
Patch from Andres Loeh: Generate the *.raw-hs files with the inplace GHC, otherwise one runs into a "fixed-point" problem where only documentation known to the bootstrapping GHC could be built.
-
panne authored
Synched with latest changes in Hugs' aclocal.m4 (wglGetProcAddress fiddling)
-
simonmar authored
Optimisation in awaitEvent(): reset the abandonRequestWait() signal if it isn't needed (compensates for not using PulseEvent() in abandonRequestWait(), see AsyncIO.c for details). Code cleanup in awaitEvent(): don't test the various exit conditions twice.
-
simonmar authored
Fix some threaded RTS bugs: - in awaitRequests(), it was possible to return immediately even though wait was set to rtsTrue. This lead to a busy wait loop, so I've disabled that case (see code for details). - using PulseEvent in abandonRequestWait() wasn't the right thing, because it exposed a race condition. Again, see the comment in the code for details.
-
simonmar authored
Add missing 'continue' after 'passCapability'
-
simonmar authored
- make --disable-foo work for each of the --enable options - tidyup: use AC_HELP_STRING everywhere
-
simonmar authored
no_glu is spelled no_GLU, and similarly for no_GLUT
-
simonmar authored
Undo part of previous merge: the HEAD doesn't export saved_termios (it is accessed by functions in RtsStartup instead).
-
- 17 Dec, 2003 6 commits
-
-
sof authored
merge rev. 1.106.2.3
-
sof authored
merge rev. 1.128.2.11
-
simonmar authored
Fix up following changes to the Capability API. (strange, I'm *sure* I tested this stuff...)
-
simonpj authored
--------------------------------- Gate in a few more instance decls --------------------------------- When we have instance T a where... we need to suck in the instance decl rather more aggressively than we were. (A case I hadn't thought of because it only happens with undecideable instances.)
-
simonpj authored
----------------------------------------------------- Fix a subtle loop in the context-reduction machinery ---------------------------------------------------- This bug was provoked by a recent change: when trying to prove a constraint C, TcSimplify.reduce now adds C to the database before trying to prove C, thus building recursive dictionaries. Two bugs a) If we add C's superclasses (which we were) we can now build a bogusly-recursive dictionary (see Note [SUPERCLASS-LOOP]). Solution: in reduce, add C only (via addIrred NoSCs) and then later use addWanted to add its definition plus SCs. b) Since we can have recursive definitions, the superclass-loop handling machinery (findAllDeps) must carry its visited-set with it (which it was not doing before) The main file is TcSimplify; but I modified a bunch of others to take advantage of new function extendVarSetList
-
panne authored
To get wglGetProcAddress on Windows, we have to link with opengl32.dll, too, even when we are using Cygwin with X11.
-
- 16 Dec, 2003 12 commits
-
-
simonpj authored
-------------------- Towards type splices -------------------- Starts the move to supporting type splices, by making HsExpr.HsSplice a separate type of its own, and adding HsSpliceTy constructor to HsType.
-
simonpj authored
Trim exports
-
simonpj authored
Typo in comment
-
simonpj authored
Fix newtype deriving for Enum
-
simonpj authored
Remove unused parameter to groupAvails
-
simonpj authored
Dont report bindings beginning with _ as unused
-
simonpj authored
Rule selection test was exactly backwards
-
simonpj authored
Clarify newtype deriving documentation
-
simonpj authored
Clarify warn-unused-bindings documention
-
simonpj authored
comments only
-
simonmar authored
Clean up Capability API ~~~~~~~~~~~~~~~~~~~~~~~ - yieldToReturningWorker() is now yieldCapability(), and performs all kinds of yielding (both to returning workers and passing to other OS threads). yieldCapabiltiy() does *not* re-acquire a capability. - waitForWorkCapabilty() is now waitForCapability(). - releaseCapbility() also releases the capability when passing to another OS thread. It is the only way to release a capability (apart from yieldCapability(), which calls releaseCapability() internally). - passCapability() and passCapabilityToWorker() now do not release the capability. They just set a flag to indicate where the capabiliy should go when it it next released. Other cleanups: - Removed all the SMP stuff from Schedule.c. It had extensive bitrot, and was just obfuscating the code. If it is ever needed again, it can be resurrected from CVS. - Removed some other dead code in Schedule.c, in an attempt to make this file more manageable.
-
simonmar authored
ANSIfy
-
- 15 Dec, 2003 5 commits
-
-
simonmar authored
Add assertion.
-
simonmar authored
Debugging output wibble
-
simonmar authored
Fix a deadlock: an OS thread returning from a C call could enter grabReturnCapability, grabbing the capability that was in the process of being passed to another thread via passCapability. This leads to a deadlock shortly afterward, because the passCapability flag is still set, so a normal worker won't pick up the capability when it is released. Fix (not sure if this is the best fix, though): don't grab the capability in grabReturnCapability() if passCapabilty is set.
-
simonmar authored
Fix locking bug in awaitEvent(): in one code path it could return with sched_lock unlocked.
-
simonmar authored
Fix bogosity in implementation of ACQUIRE_LOCK/RELEASE_LOCK on Win32. These functions were essentially doing nothing, due to a missing dereference on the argument. I've rewritten them as inlines (to catch type errors) and added some checking of the return values, which should help catch errors like this in the future.
-