- Jun 03, 1999
-
-
Simon Marlow authored
Fix bug in compat version of bracket.
-
sof authored
suppress needless warning
-
sof authored
Added rts_evalLazyIO
-
sof authored
DLL install support
-
- Jun 02, 1999
-
-
Simon Marlow authored
Small grammar correction: 'x @ Rec{..}' should parse as 'x @ (Rec{..})'.
-
Simon Marlow authored
- parse _scc_ expressions - give a proper error on illegal characters in the lexer.
-
Simon Marlow authored
^M should be a space character.
-
Simon Marlow authored
Fix tyvars field of RuleDecls.
-
Simon Marlow authored
Don't pass strange hsp-type arguments anymore.
-
- Jun 01, 1999
-
-
Simon Marlow authored
This commit replaces the old yacc parser with a Happy-generated one. Notes: - The generated .hs file is *big*. Best to use a recent version of Happy, and even better to add the -c flag to use unsafeCoerce# with ghc (versions 4.02+ please). - The lexer has grown all sorts of unsightly growths and should be put down as soon as possible. - Parse errors may result in strange diagnostics. I'm looking into this. - HsSyn now contains a few extra constructors due to the way patterns are parsed as expressions in the parser. - The layout rule is implemented according to the Haskell report. I found a couple of places in the libraries where we previously weren't adhering to this - in particular the rule about "nested contexts must be more indented than outer contexts". The rule is necessary to disambiguate in the presence of empty declaration lists.
-
Simon Marlow authored
Remove illegal use of layout.
-
Simon Marlow authored
"oops"
-
- May 28, 1999
-
-
Simon Peyton Jones authored
Enable rules for simplification of SeqOp Fix a related bug in WwLib that made it look as if the binder in a case expression was being demanded, when it wasn't.
-
Simon Peyton Jones authored
Make the default instance for Ord such that it suffices to define <=, as claimed
-
Simon Peyton Jones authored
Yet more fixes to the dreaded Enum instances
-
Simon Peyton Jones authored
Make Ix instances more inlinable
-
Simon Peyton Jones authored
Make the Enum Integer instance deforestable
-
Simon Peyton Jones authored
Fix a killer bug in the RULES for 'all' and 'any' that simply made them wrong, with various obscure consequences.
-
Simon Marlow authored
Fixes for case-of-case and let-no-escape.
-
sof authored
semi-automatic support for indexing
-
Simon Peyton Jones authored
Minor wibble to do with module names that contain a Z
-
Simon Peyton Jones authored
Make the renamer so that the class ops on the LEFT HAND SIDE of the bindings of an instance decl count as free variables of that declaration. E.g. instance Foo [a] where op x = ... bop y = ... Here, 'op' and 'bop' are now counted as free variables of the decl. This is vital, because the class decl for Foo might be imported, and look like this: class Foo a where op :: a -> S bop :: T -> a and these might happen to be the only mentions of S and T in the program. Then we need to treat S and T as instance gates for the purpose of hauling in further instance decls, and the Right Way to do that is to announce that 'op' and 'bop' have been mentioned. I also removed the (now obselete) rn_omit field in the monad.
-
- May 26, 1999
-
-
Simon Peyton Jones authored
Minor improvements in error messages
-
Simon Marlow authored
Several bugfixes (from SLPJ's tree).
-
- May 24, 1999
-
-
Simon Marlow authored
Remove dangling 'where'.
-
Simon Marlow authored
stg_gc_noregs should leave the return address on the stack (it's a case alternative).
-
- May 21, 1999
-
-
sof authored
documented -no-hs-main option
-
sof authored
Made rts_evalIO() stricter, i.e., rts_evalIO( action ); will now essentially cause `action' to be applied to the following (imaginary) defn of `evalIO': evalIO :: IO a -> IO a evalIO action = action >>= \ x -> x `seq` return x instead of just evalIO :: IO a -> IO a evalIO action = action >>= \ x -> return x The old, lazier behaviour is now available via rts_evalLazyIO().
-
sof authored
Improved precision of LOOKS_LIKE_PTR()
-
sof authored
Don't perform repeated shutdowns
-
Simon Marlow authored
Misc patches from SLPJ.
-
Simon Marlow authored
A bunch of patches from SLPJ to fix various things.
-
- May 20, 1999
-
-
Simon Marlow authored
+RTS -s<file> now gives "summary" statistics only (i.e. without the per-gc stat lines).
-
- May 18, 1999
-
-
Simon Peyton Jones authored
More small changes to make Simon's big commit work
-
Simon Peyton Jones authored
Small changes to make Simon's big commit work
-
Simon Peyton Jones authored
Documentation for rewrite rules. Some stuff in (a) glasgow exts (b) debugging Doubtless incomplete, and since I can't build the docs on (my) NT box, I don't even know if my changes are syntactically correct!
-
Simon Peyton Jones authored
Simon's Prelude changes ~~~~~~~~~~~~~~~~~~~~~~~ [The real commit preceded this, but had the stupid message "msg_prel" because I used "cvs commit -m" instead of "cvs commit -F"] Prelude is split into more modules new are: PrelEnum, PrelShow, PrelNum removed: PrelBounded (all in PrelEnum now) PrelEither (all in PrelMaybe now) There are also a lot of RULES, of course.
-
Simon Peyton Jones authored
Renamer changes ~~~~~~~~~~~~~~~ [The real commit preceded this, but had the stupid message "msg_rn" because I used "cvs commit -m" instead of "cvs commit -F"] Fairly substantial changes to the renamer: * opt_PruneTyDecls is gone, gone, gone. Hurrah. Ditto the 'deferred data decls' which was a bug farm. Instead, the compiler slurps in the transitive closure of all type declarations. It is nevertheless still parsimonious about slurping in instance decls and rewrite rules. * The renamer now uses the usage information stored in each interface file to figure out whether to look for A.hi or A.hi-boot when looking for a declaration for A.f (say). * Because of the above, there are no "A!f" symbols in interface files any more. However, the header of the interface file does contain a "!" to indicate that the mdoule contains "orphan" instance decls or rewrite rules. __interface Foo 3 ! 403 where Likewise, the usage info contains a "!" to indicate that the module mentioned has orphans: import Foo 3 ! :: a 1 b 7 ; * The renamer now only reads an interface looking for fixities if it finds an occurrence of an operator from that module. (Previously it pessimistically read the home modlese of all in-scope variables.) * Some flags have changed to more consistent names: -ddump-rn-stats (was -dshow-rn-stats) -ddump-rn-trace (was -dshow-rn-trace) * Exports now come before imports in interface files. (This was an un-forced change.) * The usage info is now explicit when a module imports the whole of another: import M 3 ; -- Imports the whole of M import M 3 :: a 2 b 7 ; -- Imports M.a, M.b import M 3 :: ; -- Imports nothing from M The last one is still vital to record that this module depends indirectly on M, even though it didn't use anything from M directly. * The renamer warns if you import {- SOURCE -} unnecessarily.
-
Simon Peyton Jones authored
SMALL TYPECHECKER FIXES [The real commit preceded this, but had the stupid message "RULES-NOTES" because I used "cvs commit -m" instead of "cvs commit -F"] 1. Allow type synonyms with kind other than '*' 2. Check that the default methods declared in a class decl are from that class decl
-
Simon Peyton Jones authored
SIMON's MASSIVE COMMIT [The real commit preceded this, but had the stupid message "RULES-NOTES" because I used "cvs commit -m" instead of "cvs commit -F"] Module reorganisation ~~~~~~~~~~~~~~~~~~~~~~~~~~~ coreSyn/CoreFVs replaces coreSyn/FreeVars coreSyn/CoreTidy is new (was code in simplCore/SimplCore) coreSyn/Subst is new (implements substitution incl dealing with name clashes main/CodeOutput is new (was gruesome code in main/Main) parser/rulevar.ugn Ugen file for rules prelude/ThinAir.lhs is new (defns for "thin air" ids; was in prelude/PrelVals) specialise/Rules is new (implements rewrite rule matching) typecheck/TcRules is new (typechecks rewrite rules) types/InstEnv is new (implements the instance env in Class; replaces SpecEnv) specialise/SpecEnv has gone simplCore/MagicUFs has gone (hurrah) Rewrite rules ~~~~~~~~~~~~~ This major commit adds the ability to specify transformation rules. E.g. {-# RULES forall f,g,xs. map f (map g xs) = map (f . g) xs #-} The rules are typechecked, and survive across separate compilation. * specialise/SpecEnv.lhs has gone, replaced by specialise/Rules.lhs. Rules.lhs implements transformation-rule matching. * Info about class instances is no longer held in a SpecEnv in the class; instead classes have their own thing, typecheck/InstEnv.lhs * Specialisations are held in list of rules, held inside an Id. So although specialisations arise from SPECIALISE pragmas and uses of overloaded functions, they are still expressed as transformation rules. However these rules are held inside the relevant Id, as before. The RULES ones are held globally. Cloning ~~~~~~~ I've removed -fplease-clone as a simplifier flag. It complicates the plumbing quite a bit. The simplifier now simply ensures that there's no shadowing in its output. It's up to other passes to solve their own cloning problems. It turned out to be easy: - SetLevels clones where necessary, so that floating out doesn't cause a problem. - CoreToStg clones so that the code generator can use uniques for labels Instead, the simplifier clones by using VarSet.uniqAway to find a unique that doesn't conflict with any that are in scope. If you say -dppr-debug you get a trace of how many times uniqAway had to loop before finding a suitable unique. It's too much at present; something to improve. Flags ~~~~~ * I have stopped -fcase-of-case and friends being 'per-simplfication' flags, and instead made them global 'opt_' things. This is simpler and more efficient, and the extra expressiveness was never used anyway. * -dsimplifier-stats has been renamed to -ddump-simpl-stats and prints much more coherent info than before. If you add -dppr-debug you get much more detailed information. * -ddump-inlinings is more or less as before, but a bit improved. Inlining and inline phase ~~~~~~~~~~~~~~~~~~~~~~~~~ I've moved the crucial inline-control function (now called callSiteInline) to CoreUnfold from Simplify, so that all the key inlining decisions are made in CoreUnfold. I've removed IWantToBeINLINEd as an InlinePragInfo on an Id. Instead, I've added a new Note on expressions, InlineMe. This is much more robust to program transformations than the old way. Essentially, an expression wrapped in an InlineMe note looks small to the inliner. In order to prevent variables on the LHS of transformation rules being inlined prematurely, the simplifier maintains a "black list" of variables that should not be inlined. Before each run of the simplifier, it constructs its black list based on the "inline phase number", controlled by the per-simplification flag -finline-phase1, -finline-phase2 etc. Details of what happens in the different phases are defined by the function CoreUnfold.blackListed. Function and primop arguments ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ I've improved the way that the simplifier deals with strict arguments of functions and primops. These are now both dealt with by Simplify.prepareArgs. As as result strict arguments are no longer case-ifyd in Core. That happens in the core-to-stg transformation. This is important so that transformation rules work easily. We want to see foldr k z (build g) and not case build g of { x -> foldr k z x } CoreToStg now takes accouunt of the strictness of functions and primops, to ensure that strict arguments are done with case. Cheap primops ~~~~~~~~~~~~~ Primops that are cheap and can't fail (i.e not divide!) reply True to primOpOkForSpeculation. Applications of such primops are now allowed to appear in lets (rather than cases), so that they are easier to float. They are honorary lets, in the sense that they can float out or in without damage. Again core-to-stg turns them into cases. Class op selectors ~~~~~~~~~~~~~~~~~~ Generate bindings for class-op selectors. The immediate reason for doing this is so we can write transformation rules involving them; black-listing won't work if they have to be inlined! The longer-term reason is because Hugs will need these bindings. Also there's no point in inling them if the dictionary is lambda bound. Simplifier ~~~~~~~~~~ I've made a number of detailed changes to the innards of the simplifier. Result is (a bit) less code, and fewer iterations. Only the biggest modules provoke the "more than 4 iterations" complaint. ... And tons of other minor stuff ...
-