Skip to content
Snippets Groups Projects
  1. Jul 15, 1999
  2. Jul 14, 1999
    • Simon Peyton Jones's avatar
      [project @ 1999-07-14 22:10:40 by simonpj] · 72af48cb
      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.
      72af48cb
    • sven.panne@aedion.de's avatar
      [project @ 1999-07-14 20:29:34 by panne] · c458067f
      sven.panne@aedion.de authored
      Enlarged heap for 2.10-compiled Happy on Alphas
      c458067f
    • Simon Marlow's avatar
      [project @ 1999-07-14 15:28:08 by simonmar] · f1d1a25d
      Simon Marlow authored
      pre-4.03 didn't have __HASKELL98__, use something else.
      f1d1a25d
    • Simon Peyton Jones's avatar
      [project @ 1999-07-14 14:40:20 by simonpj] · 4e7d56fd
      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.
      4e7d56fd
    • Simon Marlow's avatar
      [project @ 1999-07-14 13:44:19 by simonmar] · 0b127ebe
      Simon Marlow authored
      - Add findPtr() - searches through the heap for an occurrence of a
        given value.  Useful when debugging.
      0b127ebe
    • Simon Marlow's avatar
      [project @ 1999-07-14 13:39:46 by simonmar] · 5706d07c
      Simon Marlow authored
      Workaround bug in Linux's glibc 2.1:  don't fflush(stdout) before
      writing to stderr.
      5706d07c
    • Simon Marlow's avatar
      [project @ 1999-07-14 13:38:27 by simonmar] · cae7e8ce
      Simon Marlow authored
      use shutdownHaskellAndExit().
      cae7e8ce
    • Simon Marlow's avatar
      [project @ 1999-07-14 13:37:44 by simonmar] · 47a2e454
      Simon Marlow authored
      - add USE_REPORT_PRELUDE
      - Directory and Time don't need -monly-3-regs any more
      - remove a -fno-prune-tydecls
      47a2e454
    • Julian Seward's avatar
      [project @ 1999-07-14 13:35:49 by sewardj] · c0ecf485
      Julian Seward authored
      Changed vars of the form _unused to zz_unused, since 3.02 doesn't understand
      this convention.
      c0ecf485
    • Simon Marlow's avatar
      [project @ 1999-07-14 13:26:48 by simonmar] · a9778107
      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.
      a9778107
    • Simon Marlow's avatar
      [project @ 1999-07-14 13:23:51 by simonmar] · d4c4c40f
      Simon Marlow authored
      Update to match CgUsages.hi-boot-5
      d4c4c40f
    • Simon Marlow's avatar
      [project @ 1999-07-14 12:31:14 by simonmar] · fc23a3d9
      Simon Marlow authored
      Recover the -funbox-strict-fields test.
      fc23a3d9
    • Simon Marlow's avatar
      [project @ 1999-07-14 11:47:12 by simonmar] · 1824ff0e
      Simon Marlow authored
      4.04
      1824ff0e
    • Simon Marlow's avatar
      [project @ 1999-07-14 11:46:36 by simonmar] · 4ad45759
      Simon Marlow authored
      4.04 changes.
      4ad45759
    • Simon Marlow's avatar
      [project @ 1999-07-14 11:33:10 by simonmar] · 98c314db
      Simon Marlow authored
      - add 4.04 release notes
      - several other docfixes and markup fixes.
      98c314db
    • Simon Marlow's avatar
      [project @ 1999-07-14 11:16:43 by simonmar] · 94edb050
      Simon Marlow authored
      link in NonTermination_static_closure.
      94edb050
    • Simon Marlow's avatar
      [project @ 1999-07-14 11:15:09 by simonmar] · 24ca991c
      Simon Marlow authored
      add NonTermination_closure.
      24ca991c
    • Simon Marlow's avatar
      [project @ 1999-07-14 10:01:43 by simonmar] · 0eea4fc8
      Simon Marlow authored
      Fix my email address.
      0eea4fc8
    • Simon Marlow's avatar
      [project @ 1999-07-14 08:41:21 by simonmar] · 526875cb
      Simon Marlow authored
      Small typos from Wolfram Kahl.
      526875cb
    • Simon Marlow's avatar
      [project @ 1999-07-14 08:37:57 by simonmar] · cc4d138d
      Simon Marlow authored
      USE_REPORT_PRELUDE patches from Wolfram Kahl.
      cc4d138d
    • Simon Marlow's avatar
      [project @ 1999-07-14 08:33:38 by simonmar] · d1ab5c38
      Simon Marlow authored
      Add NonTermination to the exception type.  Prints as "<<loop>>"
      (better suggestions welcome).
      d1ab5c38
  3. Jul 12, 1999
  4. Jul 08, 1999
  5. Jul 07, 1999
    • Simon Marlow's avatar
      [project @ 1999-07-07 15:28:19 by simonmar] · d8e3e531
      Simon Marlow authored
      Reduce ScrutConDiscount from 3 to 2.
      d8e3e531
    • Simon Marlow's avatar
      [project @ 1999-07-07 15:27:27 by simonmar] · 65284c96
      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).
      65284c96
    • Simon Marlow's avatar
      [project @ 1999-07-07 11:22:13 by simonmar] · 69a603fb
      Simon Marlow authored
      Back out yesterday's change - needs more thought.
      69a603fb
  6. Jul 06, 1999
    • Simon Peyton Jones's avatar
      [project @ 1999-07-06 16:45:31 by simonpj] · 9d38678e
      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.
      9d38678e
    • Julian Seward's avatar
      [project @ 1999-07-06 16:40:22 by sewardj] · 47a40c89
      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
      47a40c89
    • Julian Seward's avatar
      [project @ 1999-07-06 16:17:39 by sewardj] · 7635e89a
      Julian Seward authored
      Make vectored returns to Hugs work, and make IS_CODE_PTR etc work
      for dynamically loaded objects.
      7635e89a
    • Simon Marlow's avatar
      [project @ 1999-07-06 15:33:23 by simonmar] · 99032744
      Simon Marlow authored
      Should really call OnExitHook() in shutdownHaskellAndExit().
      99032744
    • Julian Seward's avatar
      [project @ 1999-07-06 15:24:36 by sewardj] · ca6e1e45
      Julian Seward authored
      Mods to enable interworking with simple compiled code.  Supports fns and
      data decls.  Classes, instances, primops, don't work yet.
      Unregisterised, mininterpreted x86-ELF is the supported object format.
      GC appears to work correctly.
      ca6e1e45
    • Simon Marlow's avatar
      [project @ 1999-07-06 15:24:35 by simonmar] · 17622819
      Simon Marlow authored
      we're on to 4.04 now.
      17622819
    • Julian Seward's avatar
      [project @ 1999-07-06 15:24:35 by sewardj] · 4c633843
      Julian Seward authored
      Mods to enable interworking with simple compiled code.  Supports fns and
      data decls.  Classes, instances, primops, don't work yet.
      Unregisterised, mininterpreted x86-ELF is the supported object format.
      GC appears to work correctly.
      4c633843
Loading