- Jul 15, 1999
-
-
sven.panne@aedion.de authored
Patched my previous patch ($ vs $$, && vs if/then/fi). Installing a Happy binary-dist still only creates a happy and no happy-1.6 executable, but this has very probably nothing to do with my changes.
-
sven.panne@aedion.de authored
Two checks for empty file lists added.
-
sven.panne@aedion.de authored
We have to be very careful with numeric literals in the C part, in this case 0xff (of type int = 4 bytes on Alpha) was shifted left 56 times => always zero :-{ Using an L or UL suffix is not always practical, because the needed size depends on conditional typedefs somewhere else. Solution: Cast! :-P ghc/includes contains some more suspicious literals, but I did not have a look at them yet.
-
Keith Wansbrough authored
This commit makes a start at implementing polymorphic usage annotations. * The module Type has now been split into TypeRep, containing the representation Type(..) and other information for `friends' only, and Type, providing the public interface to Type. Due to a bug in the interface-file slurping prior to ghc-4.04, {-# SOURCE #-} dependencies must unfortunately still refer to TypeRep even though they are not friends. * Unfoldings in interface files now print as __U instead of __u. UpdateInfo now prints as __UA instead of __U. * A new sort of variables, UVar, in their own namespace, uvName, has been introduced for usage variables. * Usage binders __fuall uv have been introduced. Usage annotations are now __u - ty (used once), __u ! ty (used possibly many times), __u uv ty (used uv times), where uv is a UVar. __o and __m have gone. All this still lives only in a TyNote, *for now* (but not for much longer). * Variance calculation for TyCons has moved from typecheck/TcTyClsDecls to types/Variance. * Usage annotation and inference are now done together in a single pass. Provision has been made for inferring polymorphic usage annotations (with __fuall) but this has not yet been implemented. Watch this space!
-
Simon Marlow authored
No more RAWCPP, thank you.
-
Simon Marlow authored
Use +RTS -S<file> rather than +RTS -s<file>, since the latter only gives summary statistics now.
-
Simon Marlow authored
A prime example of how an inconsistent .hi-boot file can really ruin your day: the definition of CoreRules in CoreSyn.hi-boot was out of sync with the real one, which meant that the compiler generated the wrong code for a `seq` on something of type CoreRules.
-
Simon Marlow authored
oops, forgot to commit this yesterday. RAWCPP is now '$(CPP) -undef -traditional'.
-
- Jul 14, 1999
-
-
Simon Peyton Jones authored
[Simon: this should fix that -funfolding-use-threshold0 lint bug] [Kevin: have a look at WwLib.mkWwBodies. Isn't it a thing of beauty? Could you think about whether the CPR stuff could be cleaned up a bit? The strictness stuff is much shorter.] This commit tidies up WwLib.mkWwBodies, fixing a couple of bugs. * One bug showed up when CPR made a worker return an unboxed tuple, but the worker didn't have any other arguments. The "add a void arg" hack needed to be generalised a bit. * The other bug showed up when booting the compiler. There's a long comment near splitProductType in WwLib.lhs that explains the problem.
-
sven.panne@aedion.de authored
Enlarged heap for 2.10-compiled Happy on Alphas
-
Simon Marlow authored
pre-4.03 didn't have __HASKELL98__, use something else.
-
Simon Peyton Jones authored
Main things: * Add splitProductType_maybe to DataCon.lhs, with type splitProductType_maybe :: Type -- A product type, perhaps -> Maybe (TyCon, -- The type constructor [Type], -- Type args of the tycon DataCon, -- The data constructor [Type]) -- Its *representation* arg types Then use it in many places (e.g. worker-wrapper places) instead of a pile of junk * Clean up various uses of dataConArgTys, which were plain wrong because they weren't passed the existential type arguments. Most of these calls are eliminated by using splitProductType_maybe above. I hope I correctly squashed the others. This fixes a bug that Meurig's programs showed up. module FailGHC (killSustainer) where import Weak import IOExts data Sustainer = forall a . Sustainer (IORef (Maybe a)) (IO ()) killSustainer :: Sustainer -> IO () killSustainer (Sustainer _ act) = act The above program used to kill the compiler. * A fairly concerted attack on the Dreaded Space Leak. - Add Type.seqType, CoreSyn.seqExpr, CoreSyn.seqRules - Add some seq'ing when building Ids and IdInfos These reduce the space usage a lot - Add CoreSyn.coreBindsSize, which is pretty strict in the program, and call it when we have -dshow-passes. - Do not put the inlining in an Id that is being plugged into the result-expression of the simplifier. This cures a the 'wedge' in the space profile for reasons I don't understand fully Together, these things reduce the max space usage when compiling PrelNum from 17M to about 7Mbytes. I think there are now *too many* seqs, and they waste work, but I don't have time to find which ones. Furthermore, we aren't done. For some reason, some of the stuff allocated by the simplifier makes it through all during code generation and I don't see why. There's a should-be-unnecessary call to coreBindsSize in Main.main which zaps some, but not all of this space. -dshow-passes reduces space usage a bit, but I don't think it should really. All the measurements were made on a compiler compiled with profiling by GHC 3.03. I hope they carry over to other builds! * One trivial thing: changed all variables 'label' to 'lbl', becuase the former is a keyword with -fglagow-exts in GHC 3.03 (which I was compiling with). Something similar in StringBuffer.
-
Simon Marlow authored
- Add findPtr() - searches through the heap for an occurrence of a given value. Useful when debugging.
-
Simon Marlow authored
Workaround bug in Linux's glibc 2.1: don't fflush(stdout) before writing to stderr.
-
Simon Marlow authored
use shutdownHaskellAndExit().
-
Simon Marlow authored
- add USE_REPORT_PRELUDE - Directory and Time don't need -monly-3-regs any more - remove a -fno-prune-tydecls
-
Julian Seward authored
Changed vars of the form _unused to zz_unused, since 3.02 doesn't understand this convention.
-
Simon Marlow authored
Don't attempt to discover the exact location of cpp, instead use 'gcc -E'. With the right combination of flags, it seems we can get the same behaviour as calling cpp directly.
-
Simon Marlow authored
Update to match CgUsages.hi-boot-5
-
Simon Marlow authored
Recover the -funbox-strict-fields test.
-
Simon Marlow authored
4.04
-
Simon Marlow authored
4.04 changes.
-
Simon Marlow authored
- add 4.04 release notes - several other docfixes and markup fixes.
-
Simon Marlow authored
link in NonTermination_static_closure.
-
Simon Marlow authored
add NonTermination_closure.
-
Simon Marlow authored
Fix my email address.
-
Simon Marlow authored
Small typos from Wolfram Kahl.
-
Simon Marlow authored
USE_REPORT_PRELUDE patches from Wolfram Kahl.
-
Simon Marlow authored
Add NonTermination to the exception type. Prints as "<<loop>>" (better suggestions welcome).
-
- Jul 12, 1999
-
-
Simon Marlow authored
Keep the original name for non-exported record selectors and class methods.
-
sof authored
Cygwin B19 compatibility fixes
-
- Jul 08, 1999
-
-
sof authored
foreign export regression test
-
sof authored
A 'foreign export' (static) declaration doesn't bind a name but simply adds an occurrence of a name.
-
Simon Peyton Jones authored
Fix shadowing bug in rule matcher (showed up in spectral/rewrite)
-
Simon Marlow authored
Back out rev 1.30 - it broke a lot of things.
-
- Jul 07, 1999
-
-
Simon Marlow authored
Reduce ScrutConDiscount from 3 to 2.
-
Simon Marlow authored
- charge 1 for a case expression - give a discount of opt_UF_ScrutConDiscount each time a constructor is scrutinised (previously a case expression was not charged for at all, and the discount for a scrutinised constructor was (opt_UF_ScrutConDiscount * tyconFamilySize). In 4.02, a case expression was also charged tyconFamilySize to balance the discount, but this had the disadvantage of charging for alternatives which may not be present in the actual case expression).
-
Simon Marlow authored
Back out yesterday's change - needs more thought.
-
- Jul 06, 1999
-
-
Simon Peyton Jones authored
All Simon's recent tuning changes. Rough summary follows: * Fix Kevin Atkinson's cant-find-instance bug. Turns out that Rename.slurpSourceRefs needs to repeatedly call getImportedInstDecls, and then go back to slurping source-refs. Comments with Rename.slurpSourceRefs. * Add a case to Simplify.mkDupableAlt for the quite-common case where there's a very simple alternative, in which case there's no point in creating a join-point binding. * Fix CoreUtils.exprOkForSpeculation so that it returns True of (==# a# b#). This lack meant that case ==# a# b# of { True -> x; False -> x } was not simplifying * Make float-out dump bindings at the top of a function argument, as at the top of a let(rec) rhs. See notes with FloatOut.floatRhs * Make the ArgOf case of mkDupableAlt generate a OneShot lambda. This gave a noticeable boost to spectral/boyer2 * Reduce the number of coerces, using worker/wrapper stuff. The main idea is in WwLib.mkWWcoerce. The gloss is that we must do the w/w split even for small non-recursive things. See notes with WorkWrap.tryWw. * This further complicated getWorkerId, so I finally bit the bullet and make the workerInfo field of the IdInfo work properly, including under substitutions. Death to getWorkerId. Kevin Glynn will be happy. * Make all lambdas over realWorldStatePrimTy into one-shot lambdas. This is a GROSS HACK. * Also make the occurrence analyser aware of one-shot lambdas. * Make various Prelude things into INLINE, so that foldr doesn't get inlined in their body, so that the caller gets the benefit of fusion. Notably in PrelArr.lhs.
-
Julian Seward authored
Assembler/Disassembler: handle and print calls to compiled code Evaluator: return to scheduler when entering unknown closure StgCRun: debugging trace in miniinterpreter (temporary) Updates: fix normal and vectored returns to Hugs
-