Skip to content
Snippets Groups Projects
  1. May 26, 1999
  2. May 24, 1999
  3. May 21, 1999
  4. May 20, 1999
  5. May 18, 1999
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 16:38:23 by simonpj] · 45dff0ad
      Simon Peyton Jones authored
      More small changes to make Simon's big commit work
      45dff0ad
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 16:10:59 by simonpj] · 111e58bd
      Simon Peyton Jones authored
      Small changes to make Simon's big commit work
      111e58bd
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 15:41:31 by simonpj] · ade3217b
      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!
      ade3217b
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 15:20:51 by simonpj] · 8e16c2d2
      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.
      8e16c2d2
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 15:19:15 by simonpj] · 927b3cbb
      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.
      927b3cbb
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 15:17:58 by simonpj] · 3f694c56
      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
      3f694c56
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 15:16:33 by simonpj] · c5b15182
      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 ...
      c5b15182
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 15:03:54 by simonpj] · 69e14f75
      Simon Peyton Jones authored
      RULES-NOTES
      69e14f75
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 15:03:53 by simonpj] · c9dfd084
      Simon Peyton Jones authored
      Driver updates for Simons main commit; rewrite rules and flaggery
      c9dfd084
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 15:03:33 by simonpj] · 506fa77d
      Simon Peyton Jones authored
      RULES-NOTES
      506fa77d
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 14:59:04 by simonpj] · c415cd35
      Simon Peyton Jones authored
      ../compiler/msg_prel
      c415cd35
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 14:56:06 by simonpj] · 0d8269cc
      Simon Peyton Jones authored
      msg_rn
      0d8269cc
    • Simon Peyton Jones's avatar
      [project @ 1999-05-18 14:55:47 by simonpj] · ab8279d6
      Simon Peyton Jones authored
      msg_tc
      ab8279d6
    • Simon Marlow's avatar
      [project @ 1999-05-18 09:19:23 by simonm] · 7e17f862
      Simon Marlow authored
      Another sparc/egcs fix.
      7e17f862
  6. May 17, 1999
  7. May 14, 1999
  8. May 13, 1999
  9. May 12, 1999
  10. May 11, 1999
    • Keith Wansbrough's avatar
      [project @ 1999-05-11 17:05:43 by keithw] · 192b2bc9
      Keith Wansbrough authored
      Remove some comments left in by mistake.
      192b2bc9
    • Keith Wansbrough's avatar
      [project @ 1999-05-11 16:49:44 by keithw] · 59555db8
      Keith Wansbrough authored
      Whoops, forgot to mention the following change:
      
        Various ticky counters have changed:
          - TICK_ALLOC_THK is now TICK_ALLOC_{UP,SE}_THK (updatable versus
            single-entry).
          - TICK_UPD_{NEW,OLD}_IND is now TICK_UPD_{NEW,OLD}_{,PERM_}IND.
          - UPD_{CAF_,}BH_{UPDATABLE,SINGLE_ENTRY}_ctr added, counting the
            creation of various flavours of black holes.
          - ENT_PERM_IND, UPD_{NEW,OLD}_PERM_IND are only dumped if update
            squeezing is off; see comment in Ticky.c
      
        Some documentation for ticky-ticky has been added to the user guide.
      59555db8
    • Keith Wansbrough's avatar
      [project @ 1999-05-11 16:47:39 by keithw] · eb407ca1
      Keith Wansbrough authored
      (this is number 9 of 9 commits to be applied together)
      
        Usage verification changes / ticky-ticky changes:
      
        We want to verify that SingleEntry thunks are indeed entered at most
        once.  In order to do this, -ticky / -DTICKY_TICKY turns on eager
        blackholing.  We blackhole with new blackholes: SE_BLACKHOLE and
        SE_CAF_BLACKHOLE.  We will enter one of these if we attempt to enter
        a SingleEntry thunk twice.  Note that CAFs are dealt with in by
        codeGen, and ordinary thunks by the RTS.
      
        We also want to see how many times we enter each Updatable thunk.
        To this end, we have modified -ticky.  When -ticky is on, we update
        with a permanent indirection, and arrange that when we enter a
        permanent indirection we count the entry and then convert the
        indirection to a normal indirection.  This gives us a means of
        counting the number of thunks entered again after the first entry.
        Obviously this screws up profiling, and so you can't build a ticky
        and profiling compiler any more.
      
        Also a few other changes that didn't make it into the previous 8
        commits, but form a part of this set.
      eb407ca1
    • Keith Wansbrough's avatar
      [project @ 1999-05-11 16:46:20 by keithw] · 29b65248
      Keith Wansbrough authored
      (this is number 8 of 9 commits to be applied together)
      
        The CPP flag LAZY_BLACKHOLING has been moved up from options.h into
        Stg.h, so GHC can see it as well as the interpreter, and
        EAGER_BLACKHOLING has been added.  The default is still
        LAZY_BLACKHOLING && !EAGER_BLACKHOLING.
      29b65248
Loading