4221 on new codegen

Simon Marlow marlowsd at gmail.com
Thu Feb 3 10:05:04 CET 2011


I wonder if the fuel is also being used by "essential" transformations, 
like the CPS pass?

Cheers,	
	Simon

On 03/02/2011 09:01, Simon Peyton-Jones wrote:
> Correct.  The Cmm optimiser is supposed to make correctness preserving transformations.  The idea of the "fuel" is that you can binary chop your way to a situation where
>
> Fuel = 0-143    Program works
> Fuel = 144      Program crashes
>
> Then look at the single transformation that introduces the crash.
>
> Well that's the intent anyway!
>
> Simon
>
> | -----Original Message-----
> | From: ezyang [mailto:ezyang at MIT.EDU]
> | Sent: 02 February 2011 23:12
> | To: Simon Marlow; Simon Peyton-Jones
> | Cc: glasgow-haskell-users
> | Subject: Re: 4221 on new codegen
> |
> | Simon Peyton Jones, I have a question about optimization fuel and GHC panics.
> | When I vary the fuel using -dopt-fuel, I get the following varying behavior:
> |
> |     ...
> | -dopt-fuel=144 = normal segfault (late in the program)
> | -dopt-fuel=143 = segfaults ~immediately
> | -dopt-fuel=142 = normal segfault
> | -dopt-fuel=141 = fails an assert in file compiler/cmm/CmmBuildInfoTables.hs,
> | line 128
> | -dopt-fuel=140 = ditto
> | -dopt-fuel=139 = resulting executable prints 'start' and then doesn't do
> | anything
> |     ...
> |
> | My impression was that these optimizations should not affect program
> | behavior,
> | in which case the first thing I should figure out is why -dopt-fuel results
> | in
> | the programming terminating after it prints 'start'. However, I'm not sure if
> | this is a red herring. Am I on the right track?
> |
> | Cheers,
> | Edward
> |
> | Quoting Simon Marlow<marlowsd at gmail.com>:
> |
> |>  On 02/02/2011 00:29, Edward Z. Yang wrote:
> |>>  More Hoopling later, I see this segment in the rewrite function:
> |>>
> |>>         middle m@(CmmUnsafeForeignCall _ fs _) live = return $
> |>>           case map spill  (filter (flip elemRegSet (on_stack live)) fs) ++
> |>>                map reload (uniqSetToList (kill fs (in_regs live))) of
> |>>             []      ->   Nothing
> |>>             reloads ->   Just $ mkMiddles (m : reloads)
> |>>
> |>>  So, if I understand this code correctly, it unilaterally reloads
> |>>  /anything/ in the registers according to the analysis at that point.
> |>>
> |>>  Well, I could see that resulting in the behavior below.
> |>>
> |>>  It's not so clear to me what the correct rewrite is; according to
> |>>  Marlow's comment on IRC, we ought not to be spilling/reloading foreign
> |>>  calls yet, so maybe the whole bit should get excised? Otherwise, it seems
> |>>  to me that transfer function needs to accomodate unsafe foreign
> |>>  functions.
> |>
> |>  Right, there's no need to spill/reload anything around an *unsafe*
> |>  foreign call in the Cmm code generator.  The NCG's register allocator
> |>  will do any necessary spilling/reloading around foreign calls.
> |>
> |>  Cheers,
> |>  	Simon
> |>
> |>
> |>
> |>>  Cheers,
> |>>  Edward
> |>>
> |>>  Excerpts from Simon Marlow's message of Tue Feb 01 03:44:41 -0500 2011:
> |>>>  On 01/02/2011 00:01, Edward Z. Yang wrote:
> |>>>>  Current theory:
> |>>>>
> |>>>>      c1jj:
> |>>>>          _s1ep::I32 = I32[(slot<_s1ep::I32>    + 4)];   // CmmAssign
> |>>>>          _s1fP::I32 = I32[(slot<_s1fP::I32>    + 4)];   // CmmAssign
> |>>>>          // outOfLine should follow:
> |>>>>          _s1eq::F64 = F64[_s1fP::I32 + 3];   // CmmAssign
> |>>>>          I32[(young<c1jh>    + 4)] = c1jh;   // CmmStore
> |>>>>          foreign call "ccall" arg hints:  [PtrHint,]  result hints:
> |>>>>   [] call_fn_blob(...) returns to c1jh args: ([_s1ep::I32,
> |>>>>
> |>>>>                                                _s1eq::F64]) ress:
> |>>>>  ([_s1ev::F64]) with update frame 4;   // CmmForeignCall
> |>>>>      c1jh:
> |>>>>          _s1ev::F64 = F64[(slot<_s1ev::F64>    + 8)];   // CmmAssign
> |>>>>          // emitReturn: Sequel: Assign
> |>>>>          _s1ev::F64 = _s1ev::F64;   // CmmAssign
> |>>>>          F64[(slot<_s1ev::F64>    + 8)] = _s1ev::F64;   // CmmStore
> |>>>>          goto u1Ak;   // CmmBranch
> |>>>>
> |>>>>  Note the line immediately after c1jh, where we reload the ostensibly
> |>>>>  spilled _s1ev back into a register. Except that it was never spilled
> |>>>>  there in the first place, and we just clobbered the real value. Oops.
> |>>>>
> |>>>>  Is this interpretation correct?
> |>>>
> |>>>  It sounds plausible, but I really have no idea.  The code generator does
> |>>>  not have to generate spill/reloads around foreign calls, the register
> |>>>  allocator will do that.
> |>>>
> |>>>  Cheers,
> |>>>       Simon
> |>
> |>
> |
> |
>




More information about the Glasgow-haskell-users mailing list