Skip to content
Snippets Groups Projects
  1. Mar 28, 2000
  2. Mar 27, 2000
    • Simon Peyton Jones's avatar
      [project @ 2000-03-27 16:22:09 by simonpj] · 783e505e
      Simon Peyton Jones authored
      Fix a bug in import listing in interface files that meant we lost track of
      interface files.  This fixes the problem that led Sven to add lots of
      import PprType() decls.  I've removed them all again!
      783e505e
    • Simon Peyton Jones's avatar
      [project @ 2000-03-27 13:24:12 by simonpj] · a127213c
      Simon Peyton Jones authored
      a) Move Unfolding and UnfoldingGuidance to CoreSyn
         As a result, remove several SOURCE imports
         Shrink CoreSyn.hi-boot considerably
         Delete CoreUnfold.hi-boot altogether
      
      b) Add CoreUtils.exprIsConApp_maybe
         Use in PrelRules to fix a bug in the dataToTag rule
      
      c) Fix boolean polarity error in Simplify.lhs
      a127213c
    • Simon Peyton Jones's avatar
      [project @ 2000-03-27 13:23:49 by simonpj] · 8ddfc3c1
      Simon Peyton Jones authored
      Improve the error messages given when a definition isn't polymorphic enough.
      In paticular, for this program:
      
          let v = runST (newSTRef True)
          in
          runST (readSTRef v)
      
      we get the message
      
          Inferred type is less polymorphic than expected
      	Quantified type variable `s' escapes
      	It is reachable from the type variable(s) `a'
      	  which are free in the signature
          Signature type:     forall s. ST s a
          Type to generalise: ST s (STRef s Bool)
          When checking an expression type signature
          In the first argument of `runST', namely `(newSTRef True)'
          In the right-hand side of a pattern binding: runST (newSTRef True)
      8ddfc3c1
    • Simon Peyton Jones's avatar
      [project @ 2000-03-27 08:58:37 by simonpj] · 36908417
      Simon Peyton Jones authored
      Fix sig for guard in module header
      36908417
    • Simon Marlow's avatar
      [project @ 2000-03-27 08:50:15 by simonmar] · f9e2bf38
      Simon Marlow authored
      Don't treat 'ccall' and 'stdcall' as reserved words.  This fixes
      another problem with bootstrapping.
      f9e2bf38
    • Simon Marlow's avatar
      [project @ 2000-03-27 08:46:15 by simonmar] · d807babf
      Simon Marlow authored
      rearrange tokens to be in roughly the same order as everywhere else.
      d807babf
  3. Mar 25, 2000
    • sven.panne@aedion.de's avatar
      [project @ 2000-03-25 12:38:40 by panne] · cca2c69f
      sven.panne@aedion.de authored
      Adding a bunch of `import PprType ()' to make 4.07 compile itself.
      Strangely enough, compilation with 4.06 worked without these, so
      this is probably only fighting the symptoms of something deeper,
      and somebody should have a look at it. But for now, I simply need
      a bootstrapping 4.07...
      cca2c69f
  4. Mar 24, 2000
  5. Mar 23, 2000
    • Simon Peyton Jones's avatar
      [project @ 2000-03-23 17:46:59 by simonpj] · 5e95bdca
      Simon Peyton Jones authored
      Remove the .so suffixes in the foreign imports
      5e95bdca
    • Simon Peyton Jones's avatar
      [project @ 2000-03-23 17:45:17 by simonpj] · 111cee3f
      Simon Peyton Jones authored
      This utterly gigantic commit is what I've been up to in background
      mode in the last couple of months.  Originally the main goal
      was to get rid of Con (staturated constant applications)
      in the CoreExpr type, but one thing led to another, and I kept
      postponing actually committing.   Sorry.
      
      	Simon, 23 March 2000
      
      
      I've tested it pretty thoroughly, but doubtless things will break.
      
      Here are the highlights
      
      * Con is gone; the CoreExpr type is simpler
      * NoRepLits have gone
      * Better usage info in interface files => less recompilation
      * Result type signatures work
      * CCall primop is tidied up
      * Constant folding now done by Rules
      * Lots of hackery in the simplifier
      * Improvements in CPR and strictness analysis
      
      Many bug fixes including
      
      * Sergey's DoCon compiles OK; no loop in the strictness analyser
      * Volker Wysk's programs don't crash the CPR analyser
      
      I have not done much on measuring compilation times and binary sizes;
      they could have got worse.  I think performance has got significantly
      better, though, in most cases.
      
      
      Removing the Con form of Core expressions
      ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
      The big thing is that
      
        For every constructor C there are now *two* Ids:
      
      	C is the constructor's *wrapper*. It evaluates and unboxes arguments
      	before calling $wC.  It has a perfectly ordinary top-level defn
      	in the module defining the data type.
      
      	$wC is the constructor's *worker*.  It is like a primop that simply
      	allocates and builds the constructor value.  Its arguments are the
      	actual representation arguments of the constructor.
      	Its type may be different to C, because:
      		- useless dict args are dropped
      		- strict args may be flattened
      
        For every primop P there is *one* Id, its (curried) Id
      
        Neither contructor worker Id nor the primop Id have a defminition anywhere.
        Instead they are saturated during the core-to-STG pass, and the code generator
        generates code for them directly. The STG language still has saturated
        primops and constructor applications.
      
      * The Const type disappears, along with Const.lhs.  The literal part
        of Const.lhs reappears as Literal.lhs.  Much tidying up in here,
        to bring all the range checking into this one module.
      
      * I got rid of NoRep literals entirely.  They just seem to be too much trouble.
      
      * Because Con's don't exist any more, the funny C { args } syntax
        disappears from inteface files.
      
      
      Parsing
      ~~~~~~~
      * Result type signatures now work
      	f :: Int -> Int = \x -> x
      	-- The Int->Int is the type of f
      
      	g x y :: Int = x+y
      	-- The Int is the type of the result of (g x y)
      
      
      Recompilation checking and make
      ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
      * The .hi file for a modules is not touched if it doesn't change.  (It used to
        be touched regardless, forcing a chain of recompilations.)  The penalty for this
        is that we record exported things just as if they were mentioned in the body of
        the module.  And the penalty for that is that we may recompile a module when
        the only things that have changed are the things it is passing on without using.
        But it seems like a good trade.
      
      * -recomp is on by default
      
      Foreign declarations
      ~~~~~~~~~~~~~~~~~~~~
      * If you say
      	foreign export zoo :: Int -> IO Int
        then you get a C produre called 'zoo', not 'zzoo' as before.
        I've also added a check that complains if you export (or import) a C
        procedure whose name isn't legal C.
      
      
      Code generation and labels
      ~~~~~~~~~~~~~~~~~~~~~~~~~~
      * Now that constructor workers and wrappers have distinct names, there's
        no need to have a Foo_static_closure and a Foo_closure for constructor Foo.
        I nuked the entire StaticClosure story.  This has effects in some of
        the RTS headers (i.e. s/static_closure/closure/g)
      
      
      Rules, constant folding
      ~~~~~~~~~~~~~~~~~~~~~~~
      * Constant folding becomes just another rewrite rule, attached to the Id for the
        PrimOp.   To achieve this, there's a new form of Rule, a BuiltinRule (see CoreSyn.lhs).
        The prelude rules are in prelude/PrelRules.lhs, while simplCore/ConFold.lhs has gone.
      
      * Appending of constant strings now works, using fold/build fusion, plus
        the rewrite rule
      	unpack "foo" c (unpack "baz" c n)  =  unpack "foobaz" c n
        Implemented in PrelRules.lhs
      
      * The CCall primop is tidied up quite a bit.  There is now a data type CCall,
        defined in PrimOp, that packages up the info needed for a particular CCall.
        There is a new Id for each new ccall, with an big "occurrence name"
      	{__ccall "foo" gc Int# -> Int#}
        In interface files, this is parsed as a single Id, which is what it is, really.
      
      Miscellaneous
      ~~~~~~~~~~~~~
      * There were numerous places where the host compiler's
        minInt/maxInt was being used as the target machine's minInt/maxInt.
        I nuked all of these; everything is localised to inIntRange and inWordRange,
        in Literal.lhs
      
      * Desugaring record updates was broken: it didn't generate correct matches when
        used withe records with fancy unboxing etc.  It now uses matchWrapper.
      
      * Significant tidying up in codeGen/SMRep.lhs
      
      * Add __word, __word64, __int64 terminals to signal the obvious types
        in interface files.  Add the ability to print word values in hex into
        C code.
      
      * PrimOp.lhs is no longer part of a loop.  Remove PrimOp.hi-boot*
      
      
      Types
      ~~~~~
      * isProductTyCon no longer returns False for recursive products, nor
        for unboxed products; you have to test for these separately.
        There's no reason not to do CPR for recursive product types, for example.
        Ditto splitProductType_maybe.
      
      Simplification
      ~~~~~~~~~~~~~~~
      * New -fno-case-of-case flag for the simplifier.  We use this in the first run
        of the simplifier, where it helps to stop messing up expressions that
        the (subsequent) full laziness pass would otherwise find float out.
        It's much more effective than previous half-baked hacks in inlining.
      
        Actually, it turned out that there were three places in Simplify.lhs that
        needed to know use this flag.
      
      * Make the float-in pass push duplicatable bindings into the branches of
        a case expression, in the hope that we never have to allocate them.
        (see FloatIn.sepBindsByDropPoint)
      
      * Arrange that top-level bottoming Ids get a NOINLINE pragma
        This reduced gratuitous inlining of error messages.
        But arrange that such things still get w/w'd.
      
      * Arrange that a strict argument position is regarded as an 'interesting'
        context, so that if we see
      	foldr k z (g x)
        then we'll be inclined to inline g; this can expose a build.
      
      * There was a missing case in CoreUtils.exprEtaExpandArity that meant
        we were missing some obvious cases for eta expansion
        Also improve the code when handling applications.
      
      * Make record selectors (identifiable by their IdFlavour) into "cheap" operations.
      	  [The change is a 2-liner in CoreUtils.exprIsCheap]
        This means that record selection may be inlined into function bodies, which
        greatly improves the arities of overloaded functions.
      
      * Make a cleaner job of inlining "lone variables".  There was some distributed
        cunning, but I've centralised it all now in SimplUtils.analyseCont, which
        analyses the context of a call to decide whether it is "interesting".
      
      * Don't specialise very small functions in Specialise.specDefn
        It's better to inline it.  Rather like the worker/wrapper case.
      
      * Be just a little more aggressive when floating out of let rhss.
        See comments with Simplify.wantToExpose
        A small change with an occasional big effect.
      
      * Make the inline-size computation think that
      	case x of I# x -> ...
        is *free*.
      
      
      CPR analysis
      ~~~~~~~~~~~~
      * Fix what was essentially a bug in CPR analysis.  Consider
      
      	letrec f x = let g y = let ... in f e1
      		     in
      		     if ... then (a,b) else g x
      
        g has the CPR property if f does; so when generating the final annotated
        RHS for f, we must use an envt in which f is bound to its final abstract
        value.  This wasn't happening.  Instead, f was given the CPR tag but g
        wasn't; but of course the w/w pass gives rotten results in that case!!
        (Because f's CPR-ness relied on g's.)
      
        On they way I tidied up the code in CprAnalyse.  It's quite a bit shorter.
      
        The fact that some data constructors return a constructed product shows
        up in their CPR info (MkId.mkDataConId) not in CprAnalyse.lhs
      
      
      
      Strictness analysis and worker/wrapper
      ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
      * BIG THING: pass in the demand to StrictAnal.saExpr.  This affects situations
        like
      	f (let x = e1 in (x,x))
        where f turns out to have strictness u(SS), say.  In this case we can
        mark x as demanded, and use a case expression for it.
      
        The situation before is that we didn't "know" that there is the u(SS)
        demand on the argument, so we simply computed that the body of the let
        expression is lazy in x, and marked x as lazily-demanded.  Then even after
        f was w/w'd we got
      
      	let x = e1 in case (x,x) of (a,b) -> $wf a b
      
        and hence
      
      	let x = e1 in $wf a b
      
        I found a much more complicated situation in spectral/sphere/Main.shade,
        which improved quite a bit with this change.
      
      * Moved the StrictnessInfo type from IdInfo to Demand.  It's the logical
        place for it, and helps avoid module loops
      
      * Do worker/wrapper for coerces even if the arity is zero.  Thus:
      	stdout = coerce Handle (..blurg..)
        ==>
      	wibble = (...blurg...)
      	stdout = coerce Handle wibble
        This is good because I found places where we were saying
      	case coerce t stdout of { MVar a ->
      	...
      	case coerce t stdout of { MVar b ->
      	...
        and the redundant case wasn't getting eliminated because of the coerce.
      111cee3f
    • Simon Marlow's avatar
      [project @ 2000-03-23 16:01:16 by simonmar] · 290e7896
      Simon Marlow authored
      Work around the slightly deranged way we deal with thunks and
      MIN_UPD_SIZE at the moment.
      290e7896
    • Reuben Thomas's avatar
      [project @ 2000-03-23 15:53:22 by rrt] · e752aaea
      Reuben Thomas authored
      Stopped PrelHugs being compiled into HSprel.dll, and stopped using
      -split-objs when building libraries as DLLs.
      e752aaea
    • Julian Seward's avatar
      [project @ 2000-03-23 14:54:20 by sewardj] · e3bb5d64
      Julian Seward authored
      Make Hugs compile on Win32 again after recent changes.  Also, rename
      prelude.h to hugsbasictypes.h to avoid conflicts with includes/Prelude.h.
      e3bb5d64
    • Simon Marlow's avatar
      [project @ 2000-03-23 14:30:13 by simonmar] · 0b0ee1f3
      Simon Marlow authored
      Fix GCing of SEQ_FRAMES, CATCH_FRAMES and STOP_FRAMES when the closure
      header size is more than one word (eg. with profiling on).
      
      Hans: you may need to check this w.r.t. PAR & GRAN.
      0b0ee1f3
    • Simon Marlow's avatar
      [project @ 2000-03-23 13:13:29 by simonmar] · 14e5c14e
      Simon Marlow authored
      Avoid loops in CCS graph.
      14e5c14e
    • Julian Seward's avatar
      [project @ 2000-03-23 12:22:04 by sewardj] · 1e5271f1
      Julian Seward authored
      In interface files, don't forget to mention the names of modules imported
      via hi-boot files.  This is needed so that Hugs can use the import decls
      in interface files to safely overestimate the dependency sets which it will
      encounter when linking object code.
      1e5271f1
    • Julian Seward's avatar
      [project @ 2000-03-23 12:19:22 by sewardj] · 7e3624ba
      Julian Seward authored
      Allow clients of the linker library (object.[ch]) to specify, portably,
      symbols they wish to ignore in calls to ocGetNames().  Use this modification
      to support ignoring the multiple occurrences of ghc_cc_ID.
      7e3624ba
    • Simon Marlow's avatar
      [project @ 2000-03-23 12:02:38 by simonmar] · 37d4af06
      Simon Marlow authored
      Don't wake up threads if the select() was interrupted by a signal.
      37d4af06
    • Julian Seward's avatar
      [project @ 2000-03-23 10:53:26 by sewardj] · b14d8a68
      Julian Seward authored
      storage.h needs to see a machine-dependant file-timestamp type for
      use in Module symbol table entries -- hence this file.
      b14d8a68
    • Simon Marlow's avatar
      [project @ 2000-03-23 09:33:17 by simonmar] · 11a7a240
      Simon Marlow authored
      update expected output
      11a7a240
    • Simon Marlow's avatar
      [project @ 2000-03-23 09:32:36 by simonmar] · 8056af16
      Simon Marlow authored
      Add a few more test cases.
      8056af16
    • Simon Marlow's avatar
      [project @ 2000-03-23 09:32:13 by simonmar] · e5af99b1
      Simon Marlow authored
      Disable some of the special cases in remInteger and quotInteger, which
      turned out to be wrong.
      e5af99b1
  6. Mar 22, 2000
    • Julian Seward's avatar
      [project @ 2000-03-22 18:17:12 by sewardj] · 87b42906
      Julian Seward authored
      Zap outdated ifdeffery.
      87b42906
    • Julian Seward's avatar
      [project @ 2000-03-22 18:14:22 by sewardj] · 73be9570
      Julian Seward authored
      Initial commit of major changes to module chasing and storage management:
      
      * Total reimplementation of module chasing (see achieveTargetModules
        in hugs.c).  Build, maintain and use module dependency graphs
        to decide what needs reloading when.  The old mechanism with a
        stack of scripts, etc, is gone forever.  All the rest of these points
        are in support of the module-chasing change:
      
      * The result of parsing a module is now a parse tree, rather than a
        half-baked parse tree and a bunch of side-effects.  Hooray!
      
      * Redo symbol tables for Names, Tycons, Classes, Instances and
        Modules.  They are now dynamically expandable, doubling in size
        automatically when full, and use a freelist system to keep track
        of available slots.
      
      * Allow arbitrary modules to be deleted from the system.  The
        main honcho here is nukeModule().
      
      * Not strictly necessary, but ... unify the address space for all
        compile-time entities.  See revised whatIs().  Text is part of
        the unified address space.  This is very convenient for debugging.
        print() can now print practically anything.  Generally simplify
        storage management as much as possible, and zap the years of
        elaborate hacks needed to make Hugs work well in 16-bit systems.
        Added a load of sanity-checking support to storage.[ch].
      
      * We don't support project files any more.  They were useful for a
        while, but no longer seem relevant.
      
      * Nuked a large bunch of irrelevant options in rts/options.h.
      
      As of this commit, the system can load and chase modules, both in
      standalone and combined modes.  The :l (load), :a (also), :r (refresh),
      :i (info), :t (show type) and :m (set eval module) commands appear
      to work.  There are also several temporary limitations which will
      be fixed soon:
      
      * Anything to do with external editors, etc, doesn't work.
      
      * The downward-closure-of-object-code (if M is object, all
        modules below M must be too) is not enforced nor checked for.
        It needs to be.
      
      * Module M _must_ reside in M.hs/M.o (sigh).  To be fixed.
      
      * Error handling is probably flaky, and interrupt handling
        very likely is.
      
      * Error messages don't have line numbers.  (A 5-minute fix).
      
      * Progress messages are all at sea; needs re-thinking now that
        the order in which things are done is radically different.
      
      * Compile-time GC is temporarily disabled whilst I figure out how
        to stress-test the GC.
      
      * Freed-up symbol table entries are never re-entered on the free
        lists -- a debugging measure.
      
      * :% is given a bad type in combined mode.  To be investigated.
      73be9570
Loading