- 13 Apr, 2002 8 commits
-
-
sof authored
Calling-in section: clarify truth vs. fiction
-
sof authored
added design/impl doc describing ConcHask MT extension
-
sof authored
- clarified/fixed sched_mutex locking problems when calling raiseAsync() from withing the bowels of the Scheduler. - we now yieldToReturningWorker() as part of the main Scheduler loop. - simplified grabCapability() and waitForWorkCapability() usage.
-
sof authored
entry points that scheduled/created an external thread weren't correctly blocking on the TSO condition variable; now fixed.
-
sof authored
yieldToReturningWorker(): once yielded to a returning worker, thread now directly waits for capability to become available again (via waitForWorkCapability()) -- simplifies Cap. grabbing 'logic' in the Scheduler. grabReturnCapability(): assume pMutex is held upon entry.
-
sof authored
fixed config of PACKAGE_CPP_OPTS in DEBUG mode
-
sof authored
debug versions of ACQUIRE_LOCK() and RELEASE_LOCK() macros
-
sof authored
GarbageCollect(): thread resurrection now assumes sched_mutex is held
-
- 12 Apr, 2002 2 commits
- 11 Apr, 2002 4 commits
-
-
simonpj authored
------------------- 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.
-
simonpj authored
Add stuff about non-blocking I/O for Win32
-
simonmar authored
add missing file to source dist
-
simonmar authored
Fix some wibbles with the :m command
-
- 10 Apr, 2002 5 commits
-
-
simonpj authored
Make the earlier context-simplification loop-detection fix work properly
-
simonmar authored
(from Simon P.J) Make generics work with zero-constructor datatypes.
-
stolz authored
Two new scheduler-API primops: 1) GHC.Conc.forkProcess/forkProcess# :: IO Int This is a low-level call to fork() to replace Posix.forkProcess(). In a Concurrent Haskell setting, only the thread invoking forkProcess() is alive in the child process. Other threads will be GC'ed! This brings the RTS closer to pthreads, where a call to fork() doesn't clone any pthreads, either. The result is 0 for the child and the child's pid for the parent. The primop will barf() when used on mingw32, sorry. 2) GHC.Conc.labelThread/forkProcess# :: String -> IO () Useful for scheduler debugging: If the RTS is compiled with DEBUGging support, this primitive assigns a name to the current thread which will be used in debugging output (+RTS -D1). For larger applications, simply numbering threads is not sufficient. Notice: The Haskell side of this call is always available, but if you are not compiling with debugging support, the actual primop will turn into a no-op.
-
simonmar authored
Don't claim that i386-unknown-cygwin32 is supported, replace it with i386-unknown-mingw32. (the build docs for Win32 are probably also out of date, but I didn't touch those)
-
simonmar authored
Currently configure falls over if $srcdir/ghc exists and Happy >= 1.9 can't be found. For a source distribution this is too paranoid, because we ship the Happy-generated .hs files with the sources. Now we ignore a missing Happy if ghc/compiler/parser/Parser.hs exists, which should be a reasonable heuristic.
-
- 09 Apr, 2002 3 commits
-
-
simonmar authored
If we free a StablePtr which has no StableName attached, then just add its entry to the free list immediately, rather than waiting for the garbage collector to free it.
-
simonmar authored
- Revert rev. 1.7, i.e. go back to using malloc/free and a free list to manage hash list cells, because the arena method doesn't recycle used cells, resulting in memory leaks. - Add a freeHashList() call which was missing in removeHashTable().
-
njn authored
Removed the unnecessary arg from TICK_ENT_{STATIC,DYN}_THK macros in the "#ifdef TICKY_TICKY" case. This meant the libraries would not compile with way=t for SimonPJ even though they did for me...
-
- 08 Apr, 2002 2 commits
- 05 Apr, 2002 6 commits
-
-
sof authored
Friday afternoon pet peeve removal: define (Util.notNull :: [a] -> Bool) and use it
-
sof authored
Catch the use of non-existent output directories & report this back to the user. By not doing this, we relied on external tools (such as the linker or assembler) to give good feedback about this error condition -- this wasn't the case (cf. GAS on mingw/cygwin.) To insert more sanity checks of the effective options (to the batch compiler), use Main.checkOptions
-
sof authored
Cleaned up the way the External Core front-end was integrated with the rest of the compiler; guided by detailed and helpful feedback from Simon PJ. Input files ending in ".hcr" are now assumed to contain external core -- still working on getting the renamer to slurp in interface files (implicitly) referred to in the Core source.
-
simonpj authored
More wibbles
-
simonpj authored
More head-healing
-
simonpj authored
Heal the head
-
- 04 Apr, 2002 3 commits
-
-
simonmar authored
This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations.
-
simonpj authored
--------------------------------------- A glorious improvement to CPR analysis --------------------------------------- Working on the CPR paper, I finally figured out how to do a decent job of taking account of strictness analyis when doing CPR analysis. There are two places we do that: 1. Usually, on a letrec for a *thunk* we discard any CPR info from the RHS. We can't worker/wrapper a thunk. BUT, if the let is non-recursive non-top-level used strictly we don't need to discard the CPR info, because the thunk-splitting transform (WorkWrap.splitThunk) works. This idea isn't new in this commit. 2. Arguments to strict functions. Consider fac n m = if n==0 then m else fac (n-1) (m*n) Does it have the CPR property? Apparently not, because it returns the accumulating parameter, m. But the strictness analyser will discover that fac is strict in m, so it will be passed unboxed to the worker for fac. More concretely, here is the worker/wrapper split that will result from strictness analysis alone: fac n m = case n of MkInt n' -> case m of MkInt m' -> facw n' m' facw n' m' = if n' ==# 0# then I# m' else facw (n' -# 1#) (m' *# n') Now facw clearly does have the CPR property! We can take advantage of this by giving a demanded lambda the CPR property. To make this work nicely, I've made NewDemandInfo into Maybe Demand rather than simply Demand, so that we can tell when we are on the first iteration. Lots of comments about this in Note [CPR-AND-STRICTNESS]. I don't know how much all this buys us, but it is simple and elegant.
-
simonmar authored
An I/O error while opening/writing the output file is *not* a panic.
-
- 03 Apr, 2002 2 commits
-
-
simonpj authored
Make -fgenerics the default
-
simonpj authored
----------------------------- Put existential tyvars second [fixes ParsecPerm lint error] ----------------------------- In an existential data constr: data Eq a => T a = forall b. Ord b => MkT a [b] the type of MkT is MkT :: forall a b . Ord b => a -> [b] -> MkT a Note that the existential tyvars (b in this case) come *after* the "ordinary" tyvars. I had switched this around earlier in the week, but I'm putting it back (and fixing a bug) because I found it really works better second. Reason: in a case expression we may find: case (e :: T t) of { MkT b (d:Ord b) (x:t) (xs:[b]) -> ... } It's convenient to apply the rep-type of MkT to 't', to get forall b. Ord b => ... and use that to check the pattern. Mind you, this is really only use in CoreLint.
-
- 02 Apr, 2002 5 commits
-
-
simonmar authored
Allow the use of 'let' for implcit bindings. Support for 'with' is left in place for the time being, but on seeing a 'with' we emit a non-suppressible warning about 'with' being deprecated in favour of 'let'.
-
simonpj authored
----------------------------------------------------- Fix two nasty, subtle loops in context simplification ----------------------------------------------------- The context simplifier in TcSimplify was building a recursive dictionary, which meant the program looped when run. The reason was pretty devious; in fact there are two independent causes. Cause 1 ~~~~~~~ Consider class Eq b => Foo a b instance Eq a => Foo [a] a If we are reducing d:Foo [t] t we'll first deduce that it holds (via the instance decl), thus: d:Foo [t] t = $fFooList deq deq:Eq t = ...some rhs depending on t... Now we add d's superclasses. We must not then overwrite the Eq t constraint with a superclass selection!! The only decent way to solve this is to track what dependencies a binding has; that is what the is_loop parameter to TcSimplify.addSCs now does. Cause 2 ~~~~~~~ This shows up when simplifying the superclass context of an instance declaration. Consider class S a class S a => C a where { opc :: a -> a } class S b => D b where { opd :: b -> b } instance C Int where opc = opd instance D Int where opd = opc From (instance C Int) we get the constraint set {ds1:S Int, dd:D Int} Simplifying, we may well get: $dfCInt = :C ds1 (opd dd) dd = $dfDInt ds1 = $p1 dd Notice that we spot that we can extract ds1 from dd. Alas! Alack! We can do the same for (instance D Int): $dfDInt = :D ds2 (opc dc) dc = $dfCInt ds2 = $p1 dc And now we've defined the superclass in terms of itself. Solution: treat the superclass context separately, and simplify it all the way down to nothing on its own. Don't toss any 'free' parts out to be simplified together with other bits of context. This is done in TcInstDcls.tcSuperClasses, which is well commented. All this from a bug report from Peter White!
-
simonmar authored
Make this compile with 4.08.
-
simonpj authored
Error message tidy up
-
simonmar authored
oops, accidentally committed some untested (and non-working) cleanups in the last commit. This commit fixes it up again. (fixes the ByteCodeGen panic in GHCi on the HEAD)
-