[m-rev.] nondet & multi code managed by ssdb

Olivier Annet oan at missioncriticalit.com
Thu Nov 1 14:02:56 AEDT 2007


Hi,

could someone can review my code before commit.

Thank you.


===================================================================


Estimated hours taken: 15
Branches: main

The source-to-source debugger is able to managed multi, nondet, cc_multi and 
cc_nondet code now.

compiler/mercury_compile.m:
	Run the automatic determinism analysis because I have a problem with my
	manual determinism. I'm going to optimize it later.

compiler/ssdebug.m:
	Addition of code to managed the nondet and multi procedures.

ssdb/ssdb.m:
	Modification of the code due to the introduction of the redo port.

Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.452
diff -u -r1.452 mercury_compile.m
--- compiler/mercury_compile.m	4 Oct 2007 09:04:42 -0000	1.452
+++ compiler/mercury_compile.m	1 Nov 2007 02:31:42 -0000
@@ -3191,7 +3191,10 @@
         process_all_nonimported_procs(
             update_module_io(ssdebug.process_proc), !HLDS, !IO),
         maybe_write_string(Verbose, "% done.\n", !IO),
-        maybe_report_stats(Stats, !IO)
+        maybe_report_stats(Stats, !IO),
+
+        determinism_pass(!HLDS, _Specs),
+	true
     ;
         SSDB = no
     ).
Index: compiler/ssdebug.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ssdebug.m,v
retrieving revision 1.8
diff -u -r1.8 ssdebug.m
--- compiler/ssdebug.m	30 Oct 2007 00:51:23 -0000	1.8
+++ compiler/ssdebug.m	1 Nov 2007 02:31:43 -0000
@@ -193,16 +193,16 @@
         process_proc_semi(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO)
     ;
         Determinism = detism_multi,
-        error("determ_multi: not yet implemented in ssdb")
+        process_proc_nondet(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO)
     ; 
         Determinism = detism_non,
-        error("determ_non: not yet implemented in ssdb")
+        process_proc_nondet(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO)
     ; 
         Determinism = detism_cc_multi,
-        error("determ_cc_multi: not yet implemented in ssdb")
+        process_proc_det(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO)
     ; 
         Determinism = detism_cc_non,
-        error("detism_cc_non: not yet implemented in ssdb")
+        process_proc_semi(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO)
     ; 
         Determinism = detism_erroneous,
         error("detism_erroneous: not yet implemented in ssdb")
@@ -286,26 +286,22 @@
 
         %
         % Organize the order of the generated code.
-        %
+        % XXX Need optimization in list append.
+        goal_to_conj_list(BodyGoal1, BodyGoalList),
         ConjGoals = ProcIdGoals ++ CallArgListGoals ++ 
-            [HandleEventCallGoal, BodyGoal1 | ExitArgListGoals] ++ 
+            [HandleEventCallGoal] ++ BodyGoalList ++ ExitArgListGoals ++ 
             [HandleEventExitGoal | RenamingGoals],
 
-        goal_info_init(GoalInfoWP),
-        GoalWithoutPurity = hlds_goal(conj(plain_conj, ConjGoals), GoalInfoWP),
+        % Set the determinism.
+        Determinism = detism_det,
+        goal_info_init(GoalInfo0),
+        goal_info_set_determinism(Determinism, GoalInfo0, GoalInfo),
+        
+        conj_list_to_goal(ConjGoals, GoalInfo, GoalWithoutPurity),
 
-        %
-        % Get the purity of the goal.
-        %
+        % Goal => promise_purity(Goal).
         Purity = goal_info_get_purity(BodyGoalInfo0),
-        
-        ( Purity = purity_impure ->
-            Goal = GoalWithoutPurity
-        ;
-            ScopeReason = promise_purity(dont_make_implicit_promises, Purity),
-            goal_info_init(GoalInfo),
-            Goal = hlds_goal(scope(ScopeReason, GoalWithoutPurity), GoalInfo)
-        ),
+	set_goal_purity(Purity, GoalInfo, GoalWithoutPurity, Goal),
 
         commit_goal_changes(Goal, PredId, ProcId, !.PredInfo, !ProcInfo, 
             !ModuleInfo, !.Varset, !.Vartypes)    
@@ -393,18 +389,20 @@
         % Organize the order of the generated code.
-        %       
-        GoalsCond   = [BodyGoal1],
+        % XXX Need optimization in list append.
+
+	% Get a flattened goal to avoid nested conjuction.
+        goal_to_conj_list(BodyGoal1, BodyGoalList),
+        GoalsCond   = BodyGoalList,
         GoalsThen   = ExitArgListGoals ++ [HandleEventExitGoal| RenamingGoals],
         GoalsElse   = FailArgListGoals ++ [HandleEventFailGoal, FailGoal],
 
@@ -416,7 +414,7 @@
         goal_info_set_determinism(detism_semi, GoalInfo0, GoalInfoElse),
 
         IteExistVars = [],
-        CondGoal = hlds_goal(conj(plain_conj, GoalsCond), GoalInfoCond),
+        conj_list_to_goal(GoalsCond, GoalInfoCond, CondGoal),
         ThenGoal = hlds_goal(conj(plain_conj, GoalsThen), GoalInfoThen),
         ElseGoal = hlds_goal(conj(plain_conj, GoalsElse), GoalInfoElse),
 
@@ -427,26 +425,170 @@
 
         ConjGoal = CallVarGoal ++ [GoalITE],
         GoalWithoutPurity = hlds_goal(conj(plain_conj, ConjGoal), 
-            GoalInfoCond),
+	    GoalInfoCond),
+        
+        Determinism = detism_det,
+        goal_info_init(GoalInfo1),
+        goal_info_set_determinism(Determinism, GoalInfo1, GoalInfo),
 
-        ( Purity = purity_impure ->
-            Goal = GoalWithoutPurity
-        ;
-            ScopeReason = promise_purity(dont_make_implicit_promises, Purity),
-            goal_info_init(GoalInfo),
-            Goal = hlds_goal(scope(ScopeReason, GoalWithoutPurity), GoalInfo)
-        ),
+	set_goal_purity(Purity, GoalInfo, GoalWithoutPurity, Goal),
 
         commit_goal_changes(Goal, PredId, ProcId, !.PredInfo, !ProcInfo,
             !ModuleInfo, !.Varset, !.Vartypes)    
     ).
 
 
+    %
+    % Source-to-source transformation for a nondet goal.
+    %
+:- pred process_proc_nondet(pred_id::in, proc_id::in,
+    proc_info::in, proc_info::out, module_info::in, module_info::out,
+    io::di, io::uo) is det.
+
+process_proc_nondet(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO) :-
+    proc_info_get_goal(!.ProcInfo, BodyGoal0),
+    get_hlds_goal_info(BodyGoal0) = BodyGoalInfo0,
+
+    some [!PredInfo, !Varset, !Vartypes] (
+        proc_info_get_varset(!.ProcInfo, !:Varset),
+        proc_info_get_vartypes(!.ProcInfo, !:Vartypes),
+
+        %
+        % Make the ssdb_proc_id.
+        %
+        module_info_pred_info(!.ModuleInfo, PredId, !:PredInfo),
+        make_proc_id_construction(!.PredInfo, !.ProcInfo, ProcIdGoals, 
+            ProcIdVar, !Varset, !Vartypes),
+        
+        %
+        % Get the list of head var iables and their type.
+        %
+        proc_info_get_headvars(!.ProcInfo, HeadVars),
+        proc_info_get_initial_instmap(!.ProcInfo, !.ModuleInfo, InitInstMap),
+
+        %
+        % Make a list which records the value for each of the head variables at
+        % the call port.
+        %
+        make_arg_list(0, InitInstMap, HeadVars, map.init, CallArgListVar, 
+            CallArgListGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, 
+            !Vartypes, map.init, BoundVarDescsAtCall),
+
+        %
+        % Generate the call to handle_event_call(ProcId, VarList).
+        %
+        make_handle_event_call(ProcIdVar, CallArgListVar, HandleEventCallGoal, 
+            !ModuleInfo, !Varset, !Vartypes),
+
+        %
+        % Get the updated InstMap.
+        %
+        update_instmap(BodyGoal0, InitInstMap, FinalInstMap),
+
+        %
+        % Rename the output variables.
+        %
+        proc_info_instantiated_head_vars(!.ModuleInfo, !.ProcInfo, 
+            InstantiatedVars),
+        goal_info_get_instmap_delta(BodyGoalInfo0) = InstMapDelta,
+        create_renaming(InstantiatedVars, InstMapDelta, !Varset, !Vartypes, 
+            RenamingGoals, _NewVars, Renaming),
+        rename_some_vars_in_goal(Renaming, BodyGoal0, BodyGoal1),
+        
+        %
+        % Make the variable list at the exit port. It's currently a completely 
+        % new list instead of adding on to the list generated for the call 
+        % port.
+        %
+        make_arg_list(0, FinalInstMap, HeadVars, Renaming, ExitArgListVar, 
+            ExitArgListGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, 
+            !Vartypes, BoundVarDescsAtCall, _BoundVarDescsAtExit),
+
+        %
+        % Generate the call to handle_event_exit(ProcId, VarList).
+        %
+        make_handle_event_exit(ProcIdVar, ExitArgListVar, HandleEventExitGoal, 
+            !ModuleInfo, !Varset, !Vartypes),
+        
+        %
+        % Generate the call to handle_event_redo(ProcId, VarList).
+        %
+        make_handle_event_redo(ProcIdVar, ExitArgListVar, HandleEventRedoGoal,
+            !ModuleInfo, !Varset, !Vartypes),
+
+        %
+        % Generate the list of argument at the fail port.
+        %
+        make_arg_list(0, InitInstMap, [], Renaming, FailArgListVar, 
+            FailArgListGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, 
+            !Vartypes, BoundVarDescsAtCall, _BoundVarDescsAtFail),
+
+        %
+        % Generate the call to handle_event_fail(ProcId, VarList).
+        %
+        make_handle_event_fail(ProcIdVar, FailArgListVar, HandleEventFailGoal,
+            !ModuleInfo, !Varset, !Vartypes),
+
+        make_fail_call(FailGoal, !.ModuleInfo),
+
+        %
+        % Organize the order of the generated code.
+        % XXX Need optimization in list append.
+
+	% Get a flattened goal to avoid nested conjuction.
+        goal_to_conj_list(BodyGoal1, BodyGoalList1),
+        CallVarGoal0 = CallArgListGoals ++ 
+	    [HandleEventCallGoal | BodyGoalList1] ++ ExitArgListGoals,
+        goal_info_init(GoalInfo),
+        conj_list_to_goal(CallVarGoal0, GoalInfo, CallVarGoal1),
+	goal_to_conj_list(CallVarGoal1, CallVarGoal),
+        
+        ConjGoal11 = hlds_goal(conj(plain_conj, 
+            [HandleEventExitGoal| RenamingGoals]), GoalInfo),
+        ConjGoal120 = hlds_goal(conj(plain_conj, 
+            [HandleEventRedoGoal, FailGoal]), GoalInfo),
+        goal_add_feature(feature_preserve_backtrack_into, ConjGoal120, 
+            ConjGoal12),
+        DisjGoal1 = hlds_goal(disj([ConjGoal11, ConjGoal12]), GoalInfo),
+
+        ConjGoal21 = hlds_goal(conj(plain_conj, 
+            CallVarGoal ++ [DisjGoal1]), GoalInfo),
+        ConjGoal220 = hlds_goal(conj(plain_conj, 
+            FailArgListGoals ++ [HandleEventFailGoal, FailGoal]), GoalInfo), 
+        goal_add_feature(feature_preserve_backtrack_into, ConjGoal220, 
+            ConjGoal22),
+        DisjGoal2 = hlds_goal(disj([ConjGoal21, ConjGoal22]), 
+            GoalInfo),
+
+	GoalWithoutPurity = hlds_goal(conj(plain_conj, 
+	    ProcIdGoals ++ [DisjGoal2]), GoalInfo),
+
+        % Goal => promise_purity(Goal).
+        Purity = goal_info_get_purity(BodyGoalInfo0),
+
+	set_goal_purity(Purity, GoalInfo, GoalWithoutPurity, Goal),        
+
+        commit_goal_changes(Goal, PredId, ProcId, !.PredInfo, !ProcInfo,
+            !ModuleInfo, !.Varset, !.Vartypes)
+    ).
+	
+
+:- pred set_goal_purity(purity::in, hlds_goal_info::in, hlds_goal::in, 
+    hlds_goal::out) is det.
+
+set_goal_purity(Purity, GoalInfo, GoalWithoutPurity, Goal) :-
+    ( 
+	Purity = purity_impure 
+    ->
+	Goal = GoalWithoutPurity
+    ;
+	ScopeReason = promise_purity(dont_make_implicit_promises, Purity),
+	Goal = hlds_goal(scope(ScopeReason, GoalWithoutPurity), GoalInfo)
+    ).
+
 
 :- pred commit_goal_changes(hlds_goal::in, pred_id::in, proc_id::in,
     pred_info::in, proc_info::in, proc_info::out, 
@@ -477,10 +619,7 @@
 make_handle_event_call(ProcIdVar, ArgListVar, HandleEventGoal, !ModuleInfo, 
     !Varset, !Vartypes) :-
 
-    SSDBModule = mercury_ssdb_builtin_module,
-    Features = [],
-    InstMapSrc = [],
-    Context = term.context_init,
+    init_simple_call_handle_event(SSDBModule, Features, InstMapSrc, Context),
     goal_util.generate_simple_call(SSDBModule, "handle_event_call", 
         pf_predicate, only_mode, detism_det, purity_impure, 
         [ProcIdVar, ArgListVar], Features, InstMapSrc, !.ModuleInfo, Context, 
@@ -497,10 +636,7 @@
 make_handle_event_exit(ProcIdVar, ArgListVar, HandleEventGoal, !ModuleInfo, 
     !Varset, !Vartypes) :-
 
-    SSDBModule = mercury_ssdb_builtin_module,
-    Features = [],
-    InstMapSrc = [],
-    Context = term.context_init,
+    init_simple_call_handle_event(SSDBModule, Features, InstMapSrc, Context),
     goal_util.generate_simple_call(SSDBModule, "handle_event_exit", 
         pf_predicate, only_mode, detism_det, purity_impure, 
         [ProcIdVar, ArgListVar], Features, InstMapSrc, !.ModuleInfo, Context, 
@@ -517,10 +653,7 @@
 make_handle_event_fail(ProcIdVar, ArgListVar, HandleEventGoal, !ModuleInfo, 
     !Varset, !Vartypes) :-
 
-    SSDBModule = mercury_ssdb_builtin_module,
-    Features = [],
-    InstMapSrc = [],
-    Context = term.context_init,
+    init_simple_call_handle_event(SSDBModule, Features, InstMapSrc, Context),
     goal_util.generate_simple_call(SSDBModule, "handle_event_fail", 
         pf_predicate, only_mode, detism_det, purity_impure, 
         [ProcIdVar, ArgListVar], Features, InstMapSrc, !.ModuleInfo, Context, 
@@ -537,16 +670,23 @@
 make_handle_event_redo(ProcIdVar, ArgListVar, HandleEventGoal, !ModuleInfo, 
     !Varset, !Vartypes) :-
 
-    SSDBModule = mercury_ssdb_builtin_module,
-    Features = [],
-    InstMapSrc = [],
-    Context = term.context_init,
+    init_simple_call_handle_event(SSDBModule, Features, InstMapSrc, Context),
     goal_util.generate_simple_call(SSDBModule, "handle_event_redo", 
         pf_predicate, only_mode, detism_det, purity_impure, 
         [ProcIdVar, ArgListVar], Features, InstMapSrc, !.ModuleInfo, Context, 
         HandleEventGoal).
 
 
+:- pred init_simple_call_handle_event(module_name::out, list(goal_feature)::out,
+    assos_list(prog_var, mer_inst)::out, term.context::out) is det.
+
+init_simple_call_handle_event(SSDBModule, Features, InstMapSrc, Context) :-
+    SSDBModule = mercury_ssdb_builtin_module,
+    Features = [],
+    InstMapSrc = [],
+    Context = term.context_init.
+
+
     %
     % make_proc_id_construction(PredInfo, ProcInfo,
     %   Goals, Var, !Varset, !Vartypes)
Index: ssdb/ssdb.m
===================================================================
RCS file: /home/mercury1/repository/mercury/ssdb/ssdb.m,v
retrieving revision 1.8
diff -u -r1.8 ssdb.m
--- ssdb/ssdb.m	30 Oct 2007 00:51:23 -0000	1.8
+++ ssdb/ssdb.m	1 Nov 2007 02:31:45 -0000
@@ -331,13 +331,52 @@
     % Write the event out and call the prompt.
     % XXX Need to be completed
     %
-handle_event_redo(_ProcId, _ListVarValue) :-
+handle_event_redo(ProcId, ListVarValue) :-
     Event = ssdb_redo,
-    impure get_event_num_inc(_EventNum),
-    impure update_depth(Event, _PrintDepth),
+    impure get_event_num_inc(EventNum),
+    impure update_depth(Event, PrintDepth),
+    
+    % Set the new CSN
+    impure get_csn_inc(_),
+
+    % Set the list_var_value of the debugger state  with the list received.
+    impure set_list_var_value(ListVarValue),
+
+    semipure get_debugger_state(InitialState),
+    StackFrame = elem(ProcId, InitialState),
+    stack.push(InitialState ^ ssdb_stack, StackFrame, FinalStack),
+    StateEv = InitialState ^ ssdb_stack := FinalStack,
+    impure set_debugger_state(StateEv),
+ 
+    semipure get_debugger_state(State0),
+
+    CSN = StackFrame ^ se_initial_state ^ ssdb_csn,
+
+    set_stop(Event, CSN, State0, ProcId, Stop),
+    (
+        Stop = yes,
+        some [!IO] 
+        (
+            impure invent_io(!:IO),
+            
+            print_event_info(Event, EventNum, ProcId, PrintDepth, CSN, !IO),  
+         
+            semipure get_shadow_stack(ShadowStack),
+            impure prompt(Event, ShadowStack, 0, WhatNext, !IO),
 
-    semipure get_debugger_state(_State0),
-    true.
+            impure consume_io(!.IO),
+
+            set_next_stop(CSN, WhatNext, NextStop),
+
+            % We need to get a new state because breakpoint could have been 
+            % added in the prompt.
+            semipure get_debugger_state(State1),
+            State = State1 ^ ssdb_next_stop := NextStop,
+            impure set_debugger_state(State)
+        )
+    ;
+        Stop = no
+    ).
 
     %
     % IsSame is 'yes' iff the two call sequence numbers are equal, 
@@ -495,15 +534,15 @@
     io.write_string("       ", !IO),
     io.write_int(EventNum, !IO),
     io.write_string("\t", !IO),
+    io.write_int(CSN, !IO),
+    io.write_string("\t", !IO),
+    io.write_int(PrintDepth, !IO),
+    io.write_string("\t", !IO),
     io.write_string(ProcId ^ module_name, !IO),
     io.write_string(".", !IO),
     io.write_string(ProcId ^ proc_name, !IO),
     io.write_string(".", !IO),
     io.write(Event, !IO),
-    io.write_string("\t\t| DEPTH = ", !IO),
-    io.write_int(PrintDepth, !IO),
-    io.write_string("\t| CSN = ", !IO),
-    io.write_int(CSN, !IO),
     io.nl(!IO).
 
 
@@ -591,7 +630,10 @@
             impure prompt(Event, ShadowStack, Depth, WhatNext, !IO)
 
         ; Words = ["n"] ->
-            ( Event = ssdb_call ->
+            ( 
+		( Event = ssdb_call 
+		; Event = ssdb_redo
+		) ->
                 WhatNext = wn_next
             ;
                 io.write_string("Impossible at exit or fail port\n", !IO),
@@ -621,7 +663,10 @@
             impure prompt(Event, ShadowStack, Depth, WhatNext, !IO)
 
         ; Words = ["f"] ->
-            ( Event = ssdb_call ->
+            ( 
+		( Event = ssdb_call
+		; Event = ssdb_redo
+		) ->
                 stack.top_det(ShadowStack, FrameStack),
                 CSN = FrameStack ^  se_initial_state ^ ssdb_csn,
                 WhatNext = wn_finish(CSN)

--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list