Hi,

So I wanted to give implementing :next ghci debugger command a shot. It looked easy and I could use it. Moreover it would give me an easy way to implement dynamic stack in ghci (using similar approach as used for trace) ... well if I would feel like that since I was a bit discouraged about it. The problem is I failed miserably. I still think it is easy to do. I just do not know how to create correct arguments for rts_breakpoint_io_action and I have given up finding up myself for now.


The proposed meaning for :next

Lets mark dynamic stack size at a breakpoint (at which we issue :next) as breakStackSize and its selected expression as breakSpan. Then :next would single step till any of these is true:
1) current dynamic stack size is smaller than breakStackSize
2) current dynamic stack size is equal to breakStackSize and the current selected expression is not a subset of breakSpan

I hope the above would make good sense but I do not really know since maybe rts does some funny things with stack sometimes. If you think the proposed behavior is garbage let me know why so that I do not waste more time with this :)


Ok, lets get back to why I failed. I think anybody who knows rts well could probably tell me what's wrong in few minutes. The patch representing my attempt is attached. It is done against the latest ghc (head branch). I want to add stack size as the last argument of rts_breakpoint_io_action so its signature would change from:
Bool -> BreakInfo -> HValue -> IO ()
to:
Bool -> BreakInfo -> HValue -> Int -> IO ()

Since dynamic stack is continuous I can find out stack size easily. I did not implemented this yet, as well I did not implement this at all for exceptions. The only thing I cared for now is passing one more integer to rts_breakpoint_io_action. The argument contains only zero now but that should be enough to see if I can add one more argument.
I tested it by loading this source code to ghci:
f :: Int -> Int
f x = x + 1
a = f 1

... then I used ":break f" and ":force a" in ghci to see whether I can pass the new argument correctly. This test works since I added printing of the last argument (the wanna be stack size) in
noBreakAction :: Bool -> BreakInfo -> HValue -> Int -> IO ()
noBreakAction False _ _ x = putStrLn $ "*** Ignoring breakpoint " ++ show x
noBreakAction True  _ _ _ = return () -- exception: just continue

The noBreakAction implementation is just a test for now. Unfortunately when I force the last argument it crashes. I think it is because I do not create the closure for it correctly in the code for bci_BRK_FUN in rts/Interpreter.c. Can somebody tell me what is wrong there or where to find more information about how to fill in the stack with rts_breakpoint_io_action arguments correctly?


Also, any information somewhere about where to use allocate and where to use allocateLocal? I was surprised a bit that interpretBCO uses allocate much but no allocateLocal which is supposed to be quicker for a single thread.


I skimmed all of ghc commentary and read the pages which looked related carefully but either it is not there or I missed it :-(


Thanks,
Peter.
hunk ./compiler/main/InteractiveEval.hs 348
 
 -- this points to the IO action that is executed when a breakpoint is hit
 foreign import ccall "&rts_breakpoint_io_action" [_$_]
-   breakPointIOAction :: Ptr (StablePtr (Bool -> BreakInfo -> HValue -> IO ())) [_$_]
+   breakPointIOAction :: Ptr (StablePtr (Bool -> BreakInfo -> HValue -> Int -> IO ()))
 
 -- When running a computation, we redirect ^C exceptions to the running
 -- thread.  ToDo: we might want a way to continue even if the target
hunk ./compiler/main/InteractiveEval.hs 416
         -- might be a bit surprising.  The exception flag is turned off
         -- as soon as it is hit, or in resetBreakAction below.
 
-   onBreak is_exception info apStack = do
+   onBreak is_exception info apStack _ = do
      tid <- myThreadId
      putMVar statusMVar (Break is_exception apStack info tid)
      takeMVar breakMVar
hunk ./compiler/main/InteractiveEval.hs 427
      resetStepFlag
      freeStablePtr stablePtr
 
-noBreakStablePtr :: StablePtr (Bool -> BreakInfo -> HValue -> IO ())
+noBreakStablePtr :: StablePtr (Bool -> BreakInfo -> HValue -> Int -> IO ())
 noBreakStablePtr = unsafePerformIO $ newStablePtr noBreakAction
 
hunk ./compiler/main/InteractiveEval.hs 430
-noBreakAction :: Bool -> BreakInfo -> HValue -> IO ()
-noBreakAction False _ _ = putStrLn "*** Ignoring breakpoint"
-noBreakAction True  _ _ = return () -- exception: just continue
+noBreakAction :: Bool -> BreakInfo -> HValue -> Int -> IO ()
+noBreakAction False _ _ x = putStrLn $ "*** Ignoring breakpoint " ++ show x
+noBreakAction True  _ _ _ = return () -- exception: just continue
 
 resume :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> m RunResult
 resume canLogSpan step
hunk ./includes/StgMiscClosures.h 380
 RTS_RET_INFO(stg_ap_ppp_info);
 RTS_RET_INFO(stg_ap_pppv_info);
 RTS_RET_INFO(stg_ap_pppp_info);
+RTS_RET_INFO(stg_ap_ppppv_info);
 RTS_RET_INFO(stg_ap_ppppp_info);
 RTS_RET_INFO(stg_ap_pppppp_info);
 
hunk ./rts/Exception.cmm 405
             // be per-thread.
             W_[rts_stop_on_exception] = 0;
             ("ptr" ioAction) = foreign "C" deRefStablePtr (W_[rts_breakpoint_io_action] "ptr") [];
-            Sp = Sp - WDS(7);
-            Sp(6) = exception;
-            Sp(5) = stg_raise_ret_info;
-            Sp(4) = stg_noforceIO_info;    // required for unregisterised
+            Sp = Sp - WDS(8);
+            Sp(7) = exception;
+            Sp(6) = stg_raise_ret_info;
+            Sp(5) = stg_noforceIO_info;    // required for unregisterised
+            Sp(4) = 0;
             Sp(3) = exception;             // the AP_STACK
             Sp(2) = ghczmprim_GHCziBool_True_closure; // dummy breakpoint info
             Sp(1) = ghczmprim_GHCziBool_True_closure; // True <=> a breakpoint
hunk ./rts/Exception.cmm 414
             R1 = ioAction;
-            jump RET_LBL(stg_ap_pppv);
+            jump RET_LBL(stg_ap_ppppv);
         }
     }
 
hunk ./rts/Interpreter.c 818
         case bci_BRK_FUN: [_$_]
         {
             int arg1_brk_array, arg2_array_index, arg3_freeVars;
-            StgArrWords *breakPoints;
             int returning_from_break;     // are we resuming execution from a breakpoint?
                                           //  if yes, then don't break this time around
hunk ./rts/Interpreter.c 820
-            StgClosure *ioAction;         // the io action to run at a breakpoint
-
-            StgAP_STACK *new_aps;         // a closure to save the top stack frame on the heap
-            int i;
-            int size_words;
 
             arg1_brk_array      = BCO_NEXT;  // 1st arg of break instruction
             arg2_array_index    = BCO_NEXT;  // 2nd arg of break instruction
hunk ./rts/Interpreter.c 833
             // and continue executing
             if (!returning_from_break)
             {
+               StgArrWords *breakPoints;
                breakPoints = (StgArrWords *) BCO_PTR(arg1_brk_array);
 
                // stop the current thread if either the
hunk ./rts/Interpreter.c 843
                if (rts_stop_next_breakpoint == rtsTrue || [_$_]
                    breakPoints->payload[arg2_array_index] == rtsTrue)
                {
+                  StgClosure *ioAction;         // the io action to run at a breakpoint
+                  StgAP_STACK *new_aps;         // a closure to save the top stack frame on the heap
+                  StgClosure *stackSize;
+                  int size_words;
+                  int i;
+
                   // make sure we don't automatically stop at the
                   // next breakpoint
                   rts_stop_next_breakpoint = rtsFalse;
hunk ./rts/Interpreter.c 873
                      new_aps->payload[i] = (StgClosure *)Sp[i-2];
                   }
 
+                  stackSize = (StgClosure*) allocate(CONSTR_sizeW(0,1));
+                  SET_HDR(stackSize, Izh_con_info, CCS_SYSTEM);
+                  stackSize->payload[0]  = (StgClosure *)(StgInt) 0;
+
                   // prepare the stack so that we can call the
                   // rts_breakpoint_io_action and ensure that the stack is
                   // in a reasonable state for the GC and so that
hunk ./rts/Interpreter.c 882
                   // execution of this BCO can continue when we resume
                   ioAction = (StgClosure *) deRefStablePtr (rts_breakpoint_io_action);
-                  Sp -= 9;
-                  Sp[8] = (W_)obj;   [_$_]
-                  Sp[7] = (W_)&stg_apply_interp_info;
-                  Sp[6] = (W_)&stg_noforceIO_info;     // see [unreg] below
+                  Sp -= 10;
+                  Sp[9] = (W_)obj;
+                  Sp[8] = (W_)&stg_apply_interp_info;
+                  Sp[7] = (W_)&stg_noforceIO_info;     // see [unreg] below
+                  Sp[6] = (W_)stackSize;               // stack size just before the breakpoint hit
                   Sp[5] = (W_)new_aps;                 // the AP_STACK
                   Sp[4] = (W_)BCO_PTR(arg3_freeVars);  // the info about local vars of the breakpoint
                   Sp[3] = (W_)False_closure;            // True <=> a breakpoint
hunk ./rts/Interpreter.c 890
-                  Sp[2] = (W_)&stg_ap_pppv_info;
+                  Sp[2] = (W_)&stg_ap_ppppv_info;
                   Sp[1] = (W_)ioAction;                // apply the IO action to its two arguments above
                   Sp[0] = (W_)&stg_enter_info;         // get ready to run the IO action
                   // Note [unreg]: in unregisterised mode, the return
hunk ./utils/genapply/GenApply.hs 795
 	[P,P,P],
 	[P,P,P,V],
 	[P,P,P,P],
+	[P,P,P,P,V],
 	[P,P,P,P,P],
 	[P,P,P,P,P,P]
    ]
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to