[m-rev.] semidet code managed in ssdb

Peter Wang novalazy at gmail.com
Mon Oct 29 11:36:54 AEDT 2007


On 2007-10-27, Olivier Annet <oan at missioncriticalit.com> wrote:
> Hi,
> 
> could someone review my code before the commit please.
> 
> ===================================================================
> 
> 
> Estimated hours taken: 50
> Branches: main
> 
> The source-to-source debugger is able to manage the semidet predicate/function 
> now.
> 
> 
> compiler/ssdebug.m:
> 	Modification to manage the semidet function.
> 	Optimization in the generation of the goal's argument at exit point.
>     
> ssdb/ssdb.m:
> 	Correction of some bugs in the prompt.
> 
> tools/lmc.in:
> 	Search in the `ssdb' directory for C header files and modules.
> 
> 
> Index: compiler/ssdebug.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/ssdebug.m,v
> retrieving revision 1.6
> diff -u -r1.6 ssdebug.m
> --- compiler/ssdebug.m	18 Oct 2007 14:59:44 -0000	1.6
> +++ compiler/ssdebug.m	26 Oct 2007 06:06:35 -0000
> @@ -149,6 +149,7 @@
>  
>  :- import_module check_hlds.mode_util.
>  :- import_module check_hlds.polymorphism.
> +:- import_module check_hlds.purity.
>  :- import_module hlds.goal_util.
>  :- import_module hlds.hlds_goal.
>  :- import_module hlds.instmap.
> @@ -177,9 +178,51 @@
>  
>  %-----------------------------------------------------------------------------%
>  
> -process_proc(PredId, _ProcId, !ProcInfo, !ModuleInfo, !IO) :-
> +     %
> +     % Switch on the determinism used. It's the compiler determinism which
> +     % is used. The determinism for the goal migth be the same.
> +     %
> +process_proc(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO) :-
> + 
> +    proc_info_get_inferred_determinism(!.ProcInfo, Determinism),
> +     
> +    ( Determinism = detism_det,
> +        process_proc_det(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO)
> +
> +    ; Determinism = detism_semi,
> +        process_proc_semi(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO)
> +     
> +    ; Determinism = detism_multi,
> +        error("determ_multi: not yet implemented in ssdb")
> + 
> +    ; Determinism = detism_non,
> +        error("determ_non: not yet implemented in ssdb")
> + 
> +    ; Determinism = detism_cc_multi,
> +        error("determ_cc_multi: not yet implemented in ssdb")
> + 
> +    ; Determinism = detism_cc_non,
> +        error("detism_cc_non: not yet implemented in ssdb")
> +  
> +    ; Determinism = detism_erroneous,
> +        error("detism_erroneous: not yet implemented in ssdb")
> +     
> +    ; Determinism = detism_failure,
> +        error("detism_failure: not yet implemented in ssdb")
> + 
> +    ).

Write switches just like disjunctions.

> +  
> +      %
> +      % Generate code for a deterministic goal
> +      %
> +:- pred process_proc_det(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_det(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO) :-
>      proc_info_get_goal(!.ProcInfo, Goal0),
> -
> +    HldsGoalInfo = get_hlds_goal_info(Goal0),
> +     

Call it GoalInfo0 to match Goal0.  Name Goal0 more clearly, e.g. BodyGoal0.

>      some [!PredInfo, !Varset, !Vartypes] (
>          proc_info_get_varset(!.ProcInfo, !:Varset),
>          proc_info_get_vartypes(!.ProcInfo, !:Vartypes),
> @@ -196,120 +239,241 @@
>          %
>          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_call_list_arg(ssdb_call, InitInstMap, HeadVars, CallArgListVar, 
> -	    CallArgListGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, 
> -	    !Vartypes),
> +        make_arg_list(0, InitInstMap, HeadVars, map.init, CallArgListVar, 
> +            CallArgListGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, 
> +            !Vartypes, map.init, BoundVarDescsAtCall),
>  
>          %
>          % Generate the call.
>          % Generate the call to handle_event(call).

Delete the first line.

> -        % Return a list of goals.
>          %
> -        make_handle_event_call(ssdb_call, ProcIdVar, CallArgListVar,
> +        make_call_handle_event(ssdb_call, ProcIdVar, CallArgListVar,

Why did you rename it?

>              HandleEventCallGoals, !ModuleInfo, !Varset, !Vartypes),
> -        
> +       
>          %
>          % Get the updated InstMap.
>          %
>          update_instmap(Goal0, InitInstMap, UpdatedInstMap),

Call that FinalInstMap.

>  
> -	%
> +        %
> +        % Rename the variable
> +        %

Full stop.

> +        proc_info_instantiated_head_vars(!.ModuleInfo, !.ProcInfo, 
> +            InstantiatedVars),
> +        goal_info_get_instmap_delta(HldsGoalInfo) = InstMapDelta,
> +        create_renaming(InstantiatedVars, InstMapDelta, !Varset, !Vartypes, 
> +            RenamingGoals, _NewVars, Renaming),
> +        rename_some_vars_in_goal(Renaming, Goal0, Goal1),
> +
> +        %
>          % 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.
>          %
> -        % XXX Optimization : Only output variables should be regenerated.
> -        %
> -	make_call_list_arg(ssdb_exit, UpdatedInstMap, HeadVars, ExitArgListVar, 
> -	    ExitArgListGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, 
> -	    !Vartypes),
> +        make_arg_list(0, UpdatedInstMap, HeadVars, Renaming, ExitArgListVar, 
> +            ExitArgListGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, 
> +            !Vartypes, BoundVarDescsAtCall, _BoundVarDescsAtExit),
>  
>          %
>          % Generate the exit.
>          % Generate the call to handle_event(exit).

Delete the first line.

> -        % Return a list of goals.
>          %
> -        make_handle_event_call(ssdb_exit, ProcIdVar, ExitArgListVar,
> +        make_call_handle_event(ssdb_exit, ProcIdVar, ExitArgListVar,
>              HandleEventExitGoals, !ModuleInfo, !Varset, !Vartypes),
>  
>  
>          %
> -        % Place the call and exit events around the initial goal.
> +        % Organize the order of the generated code.
>          %
>          ConjGoals = ProcIdGoals ++ CallArgListGoals ++ HandleEventCallGoals ++ 
> -            [Goal0 | ExitArgListGoals] ++ HandleEventExitGoals,
> +            [Goal1 | ExitArgListGoals] ++ HandleEventExitGoals ++ RenamingGoals,
>  
> +        goal_info_init(GoalInfoWP),
> +        GoalWithoutPurity = hlds_goal(conj(plain_conj, ConjGoals), GoalInfoWP),
> +
> +        %
> +        % Get the purity of the goal
> +        %

.

> +        Purity = goal_info_get_purity(HldsGoalInfo),
> +        ScopeReason = promise_purity(dont_make_implicit_promises, Purity),
>          goal_info_init(GoalInfo),
> -        Goal = hlds_goal(conj(plain_conj, ConjGoals), GoalInfo),
> +        Goal = hlds_goal(scope(ScopeReason, GoalWithoutPurity), GoalInfo),      

You don't need a promise if the goal is already impure.

>  
> -        proc_info_set_varset(!.Varset, !ProcInfo),
> -        proc_info_set_vartypes(!.Vartypes, !ProcInfo),
> +        commit_goal_changes(Goal, PredId, ProcId, !.PredInfo, !ProcInfo, 
> +            !ModuleInfo, !.Varset, !.Vartypes)    
> +    ).
>  
> -        proc_info_set_goal(Goal, !ProcInfo),
>  
> -        requantify_proc(!ProcInfo),
> -        recompute_instmap_delta_proc(yes, !ProcInfo, !ModuleInfo),
> +    %
> +    % Generate code for un semi-det goal

a semidet goal

> +    %
> +:- pred process_proc_semi(pred_id::in, proc_id::in,
> +    proc_info::in, proc_info::out, module_info::in, module_info::out,
> +    io::di, io::uo) is det.
>  
> -        module_info_set_pred_info(PredId, !.PredInfo, !ModuleInfo)
> -    ).
> +process_proc_semi(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO) :-
> +    proc_info_get_goal(!.ProcInfo, Goal0),

Same as before.

> +    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),

I think ProcIdGoals and ProcIdVar sound too similar to ProcId.

> +        
> +        %
> +        % Get list(prog_var) and there type.
> +        %

Get the list of head variables and their types.

> +        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),
>  
> -:- pred make_call_list_arg(ssdb_event_type::in, instmap::in, 
> -    list(prog_var)::in, prog_var::out, list(hlds_goal)::out, 
> -    module_info::in, module_info::out, proc_info::in, proc_info::out,
> -    pred_info::in, pred_info::out, prog_varset::in, prog_varset::out,
> -    vartypes::in, vartypes::out) is det.
> +        %
> +        % Generate the call.
> +        % Generate the call to handle_event(call).
> +        %

Delete one line.

> +        make_call_handle_event(ssdb_call, ProcIdVar, CallArgListVar,
> +            HandleEventCallGoals, !ModuleInfo, !Varset, !Vartypes),
>  
> -make_call_list_arg(Event, InstMap, HeadVars, ArgListVar, ArgListGoals, 
> -    !ModuleInfo, !ProcInfo, !PredInfo, !Varset, !Vartypes) :-
> +        %
> +        % Get the updated InstMap.
> +        %
> +        update_instmap(Goal0, InitInstMap, UpdatedInstMap),

FinalInstMap

>  
> -    (    
> -        ( Event = ssdb_call
> -        ; Event = ssdb_exit
> -        ),
> -    
>          %
> -        % Make the list of argument at call/exit point
> +        % Rename the variable
>          %

.

> -        make_arg_list(0, InstMap, HeadVars, ArgListVar, ArgListGoals,
> -            !ModuleInfo, !ProcInfo, !PredInfo, !Varset, !Vartypes)
> +        proc_info_instantiated_head_vars(!.ModuleInfo, !.ProcInfo, 
> +            InstantiatedVars),
> +        get_hlds_goal_info(Goal0) = HldsGoalInfo,

Same as before.

> +        goal_info_get_instmap_delta(HldsGoalInfo) = InstMapDelta,
> +        create_renaming(InstantiatedVars, InstMapDelta, !Varset, !Vartypes, 
> +            RenamingGoals, _NewVars, Renaming),
> +        rename_some_vars_in_goal(Renaming, Goal0, Goal1),
> +        
> +        %
> +        % 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, UpdatedInstMap, HeadVars, Renaming, ExitArgListVar, 
> +            ExitArgListGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, 
> +            !Vartypes, BoundVarDescsAtCall, _BoundVarDescsAtExit),
>  
> -    ;
> -        ( Event = ssdb_fail
> -        ; Event = ssdb_redo
> -        ),
> +        %
> +        % Generate the exit.
> +        % Generate the call to handle_event(exit).
> +        %

same

> +        make_call_handle_event(ssdb_exit, ProcIdVar, ExitArgListVar,
> +            HandleEventExitGoals, !ModuleInfo, !Varset, !Vartypes),
> +
> +
> +        %
> +        % Generate the goal's list argument.
> +        %

Generate the list of head variables at the fail port.

> +        make_arg_list(0, InitInstMap, [], Renaming, FailArgListVar, 
> +            FailArgListGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, 
> +            !Vartypes, BoundVarDescsAtCall, _BoundVarDescsAtFail),
>  
>          %
> -        % Make the list of argument at fail/redo point
> -        % Need only to generate the empty list.
> +        % Generate the fail.
> +        % Generate the call to handle_event(fail).
> +        %

same

> +        make_call_handle_event(ssdb_fail, ProcIdVar, FailArgListVar,
> +            HandleEventFailGoals, !ModuleInfo, !Varset, !Vartypes),
> +
> +        make_fail(FailGoal, !.ModuleInfo),

make_fail_call

> +
> +
>          %
> -        make_arg_list(0, InstMap, HeadVars, ArgListVar, ArgListGoals,
> -            !ModuleInfo, !ProcInfo, !PredInfo, !Varset, !Vartypes)
> +        % Organize the order of the generated code.
> +        %       
> +        CallVarGoal = ProcIdGoals ++ CallArgListGoals ++ HandleEventCallGoals,
> +        GoalsIf     = [Goal1],

"Cond" would be better than "If".

> +        GoalsThen   = ExitArgListGoals ++ HandleEventExitGoals ++ RenamingGoals,
> +        GoalsElse   = FailArgListGoals ++ HandleEventFailGoals ++ [FailGoal],
> +
> +        goal_info_init(GoalInfo0),
> +        goal_list_determinism(GoalsIf, Detism),
> +        goal_info_set_determinism(Detism, GoalInfo0, GoalInfo),

GoalInfoIf

> +
> +        goal_info_set_determinism(detism_det, GoalInfo0, GoalInfoThen),
> +        goal_info_set_determinism(detism_semi, GoalInfo0, GoalInfoElse),
> +
> +        IteExistVars = [],
> +        IfGoal   = hlds_goal(conj(plain_conj, GoalsIf), GoalInfo),
> +        ThenGoal = hlds_goal(conj(plain_conj, GoalsThen), GoalInfoThen),
> +        ElseGoal = hlds_goal(conj(plain_conj, GoalsElse), GoalInfoElse),
> +
> +        % XXX not sure about determinism
> +        GoalITE = hlds_goal(if_then_else(IteExistVars, IfGoal, ThenGoal, 
> +            ElseGoal), GoalInfo),
> +
> +        ConjGoal = CallVarGoal ++ [GoalITE],

Move the "CallVarGoal =" line closer to here.

> +        GoalWithoutPurity = hlds_goal(conj(plain_conj, ConjGoal), GoalInfo),
> +
> +        %
> +        % Get the purity of the initial goal.
> +        %
> +        Purity = goal_info_get_purity(HldsGoalInfo),
> +        ScopeReason = promise_purity(dont_make_implicit_promises, Purity),
> +        Goal = hlds_goal(scope(ScopeReason, GoalWithoutPurity), GoalInfo), 
> +
> +        commit_goal_changes(Goal, PredId, ProcId, !.PredInfo, !ProcInfo,
> +            !ModuleInfo, !.Varset, !.Vartypes)    
>      ).
>  
>  
>  
> +:- pred commit_goal_changes(hlds_goal::in, pred_id::in, proc_id::in,
> +    pred_info::in, proc_info::in, proc_info::out, 
> +    module_info::in, module_info::out, prog_varset::in, vartypes::in) is det.
> +
> +commit_changes(Goal, PredId, ProcId, !.PredInfo, !ProcInfo, !ModuleInfo, 
> +    Varset, Vartypes) :-

Should be commit_goal_changes.

> +        proc_info_set_varset(Varset, !ProcInfo),
> +        proc_info_set_vartypes(Vartypes, !ProcInfo),
> +
> +        proc_info_set_goal(Goal, !ProcInfo),
> +
> +        requantify_proc(!ProcInfo),
> +        recompute_instmap_delta_proc(yes, !ProcInfo, !ModuleInfo),
> +        pred_info_set_proc_info(ProcId, !.ProcInfo, !PredInfo),
> +        repuritycheck_proc(!.ModuleInfo, proc(PredId, ProcId), !PredInfo),
> +        module_info_set_pred_info(PredId, !.PredInfo, !ModuleInfo).

Fix the indentation.

>  
> -:- pred make_handle_event_call(ssdb_event_type::in, prog_var::in, 
> +
> +%-----------------------------------------------------------------------------%
> +
> +
> +    %
> +    % Build the following goal : handle_event(ProcId, Event, ListOfArgument).

Arguments

> +    %
> +:- pred make_call_handle_event(ssdb_event_type::in, prog_var::in, 
>      prog_var::in, list(hlds_goal)::out, module_info::in, module_info::out, 
>      prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
>  
> -make_handle_event_call(Event, ProcIdVar, ArgListVar, Goals, !ModuleInfo, 
> +make_call_handle_event(Event, ProcIdVar, ArgListVar, Goals, !ModuleInfo, 
>      !Varset, !Vartypes) :-
>  
>      make_ssdb_event_type_construction(Event, EventConstructor, EventVar, 
>          !Varset, !Vartypes),
>  
> -    %
> -    % Build the following goal
> -    %   handle_event(ProcId, Event, VarList).
> -    %
>      SSDBModule = mercury_ssdb_builtin_module,
>      Features = [],
>      InstMapSrc = [],
> @@ -321,7 +485,6 @@
>          
>      Goals = [EventConstructor, HandleEventGoal].
>  
> -%-----------------------------------------------------------------------------%
>  
>      %
>      % make_proc_id_construction(PredInfo, ProcInfo,
> @@ -332,8 +495,7 @@
>      % ssdb_proc_id.
>      %
>  :- pred make_proc_id_construction(pred_info::in, proc_info::in,
> -    hlds_goals::out, prog_var::out,
> -    prog_varset::in, prog_varset::out,
> +    hlds_goals::out, prog_var::out, prog_varset::in, prog_varset::out,
>      vartypes::in, vartypes::out) is det.
>  
>  make_proc_id_construction(PredInfo,
> @@ -360,6 +522,22 @@
>  
>      Goals = [ConstructModuleName, ConstructPredName, ConstructProcIdGoal].
>  
> +
> +    %
> +    % make_fail(FailGoal, ModuleInfo)
> +    %
> +    % Contruct the fail goal.
> +    %
> +:- pred make_fail(hlds_goal::out, module_info::in) is det.
> +
> +make_fail(FailGoal, ModuleInfo) :-
> +    Features = [],
> +    InstMapSrc = [],
> +    Context = term.context_init,
> +    goal_util.generate_simple_call(mercury_public_builtin_module, 
> +    "false", pf_predicate, only_mode, detism_failure, purity_pure, 
> +    [], Features, InstMapSrc, ModuleInfo, Context, FailGoal).

Indentation.

> +
>  %-----------------------------------------------------------------------------%
>  
>  
> @@ -374,27 +552,37 @@
>      % to display.
>      %
>  :- pred make_arg_list(int::in, instmap::in, list(prog_var)::in, 
> -    prog_var::out, list(hlds_goal)::out, module_info::in, module_info::out, 
> -    proc_info::in, proc_info::out, pred_info::in, pred_info::out,
> -    prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +    map(prog_var, prog_var)::in, prog_var::out, list(hlds_goal)::out, 
> +    module_info::in, module_info::out, proc_info::in, proc_info::out, 
> +    pred_info::in, pred_info::out, prog_varset::in, prog_varset::out, 
> +    vartypes::in, vartypes::out, 
> +    map(prog_var, prog_var)::in, map(prog_var, prog_var)::out) is det.
>  
> -make_arg_list(_, _, [], Var, [Goal], !ModuleInfo, !ProcInfo, !PredInfo, 
> -    !Varset, !Vartypes) :-
> +make_arg_list(_, _, [], _, Var, [Goal], !ModuleInfo, !ProcInfo, !PredInfo, 
> +        !Varset, !Vartypes, !BoundVarDescs) :-

Please name the anonymous variables.

>      
>      svvarset.new_named_var("EmptyVarList", Var, !Varset), 
>      svmap.det_insert(Var, list_var_value_type, !Vartypes),
>      ConsId = cons(qualified(unqualified("list"), "[]" ), 0),
>      construct_functor(Var, ConsId, [], Goal).
>  
> -make_arg_list(Pos0, InstMap, [VarToInspect | ListCallVar], Var, Goals, 
> -    !ModuleInfo, !ProcInfo, !PredInfo, !Varset, !Vartypes) :-
> +make_arg_list(Pos0, InstMap, [VarToInspect | ListCallVar], Renaming, Var, 
> +        Goals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, !Vartypes, 
> +        !BoundVarDescs) :-

Please rename ListCallVar, Var and Goals.

>  
>      Pos = Pos0 + 1,
>  
> -    make_arg_list(Pos, InstMap, ListCallVar, Var0, Goals0, 
> -        !ModuleInfo, !ProcInfo, !PredInfo, !Varset, !Vartypes),
> -    make_var_value(InstMap, VarToInspect, VarDesc, Pos0, ValueGoals, 
> -        !ModuleInfo, !ProcInfo, !PredInfo, !Varset, !Vartypes),
> +    make_arg_list(Pos, InstMap, ListCallVar, Renaming, Var0, Goals0, 
> +        !ModuleInfo, !ProcInfo, !PredInfo, !Varset, !Vartypes, !BoundVarDescs),

Put a comment to explain the next part:

> +
> +    ( map.search(!.BoundVarDescs, VarToInspect, ExistingVarDesc) ->
> +        ValueGoals = [],
> +        VarDesc = ExistingVarDesc
> +    ;
> +        make_var_value(InstMap, VarToInspect, Renaming, VarDesc, Pos0, 
> +            ValueGoals, !ModuleInfo, !ProcInfo, !PredInfo, !Varset, !Vartypes,
> +            !BoundVarDescs)
> +    ),
>     
>      svvarset.new_named_var("FullListVar", Var, !Varset), 
>      svmap.det_insert(Var, list_var_value_type, !Vartypes),
> @@ -426,22 +614,23 @@
>      % -> unbound_head_var(Name, Pos) if it is an unbound argument
>      % -> bound_head_var(type_of_T, Name, Position, T) if it is a bound argument
>      %
> -:- pred make_var_value(instmap::in, prog_var::in, prog_var::out, 
> -    int::in, list(hlds_goal)::out, module_info::in, module_info::out, 
> -    proc_info::in, proc_info::out, pred_info::in, pred_info::out, 
> -    prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +:- pred make_var_value(instmap::in, prog_var::in, map(prog_var, prog_var)::in, 
> +    prog_var::out, int::in, list(hlds_goal)::out, 
> +    module_info::in, module_info::out, proc_info::in, proc_info::out, 
> +    pred_info::in, pred_info::out, prog_varset::in, prog_varset::out, 
> +    vartypes::in, vartypes::out, map(prog_var, prog_var)::in, 
> +    map(prog_var, prog_var)::out) is det.
>  
>  
> -make_var_value(InstMap, VarToInspect, VarDesc, VarPos, Goals, 
> -    !ModuleInfo, !ProcInfo, !PredInfo, !VarSet, !VarTypes) :-
> +make_var_value(InstMap, VarToInspect, Renaming, VarDesc, VarPos, Goals, 
> +        !ModuleInfo, !ProcInfo, !PredInfo, !VarSet, !VarTypes, !BoundVarDescs) :-
>  
>  
>      SSDBModule = mercury_ssdb_builtin_module,
>      TypeCtor = type_ctor(qualified(SSDBModule, "var_value"), 0),
>  
> -    % Find the name of the prog_var.
>      varset.lookup_name(!.VarSet, VarToInspect, VarName),
> -    
> +
>      make_string_const_construction_alloc(VarName, yes("VarName"),
>          ConstructVarName, VarNameVar, !VarSet, !VarTypes),
>  
> @@ -450,15 +639,16 @@
>  
>      ( var_is_ground_in_instmap(!.ModuleInfo, InstMap, VarToInspect) ->
>                      
> -	%
> -	% Update proc_varset and proc_vartypes, without this, the
> -	% polymorphism_make_type_info_var uses a prog_var which is 
> -	% already bound.
> -	%
> -	proc_info_set_varset(!.VarSet, !ProcInfo),
> -	proc_info_set_vartypes(!.VarTypes, !ProcInfo),
>  
> -	%
> +        %
> +        % Update proc_varset and proc_vartypes, without this, the
> +        % polymorphism_make_type_info_var uses a prog_var which is 
> +        % already bound.
> +        %
> +        proc_info_set_varset(!.VarSet, !ProcInfo),
> +        proc_info_set_vartypes(!.VarTypes, !ProcInfo),
> +
> +        %
>          % Create dynamic constructor for the value of the argument.
>          %
>          % Call polymorphism.m to create the type_infos, add an hidden field
> @@ -467,31 +657,44 @@
>          % some[T] bound_head_var(string, int, T) ---->
>          %   some[T] bound_head_var(type_of_T, string, int, T)
>          %
> -	create_poly_info(!.ModuleInfo, !.PredInfo, !.ProcInfo, 
> -	    PolyInfo0),
> -	term.context_init(Context),
> -	map.lookup(!.VarTypes, VarToInspect, MerType),
> -	polymorphism_make_type_info_var(MerType, Context, TypeInfoVar, 
> -	    TypeInfoGoal, PolyInfo0, PolyInfo),
> -	poly_info_extract(PolyInfo, !PredInfo, !ProcInfo, 
> -	    !:ModuleInfo),
> -	
> -	%
> -	% Give a new prog_var to the polymorphic structure.
> -	%
> -	svvarset.new_named_var("VarType", VarTypo, !VarSet),
> -	svmap.det_insert(VarTypo, MerType, !VarTypes),
> +        create_poly_info(!.ModuleInfo, !.PredInfo, !.ProcInfo, 
> +            PolyInfo0),
> +        term.context_init(Context),
> +        map.lookup(!.VarTypes, VarToInspect, MerType),
> +        polymorphism_make_type_info_var(MerType, Context, TypeInfoVar, 
> +            TypeInfoGoal, PolyInfo0, PolyInfo),
> +        poly_info_extract(PolyInfo, !PredInfo, !ProcInfo, 
> +            !:ModuleInfo),
> +
> +        proc_info_get_varset(!.ProcInfo, !:VarSet),
> +        proc_info_get_vartypes(!.ProcInfo, !:VarTypes),
> +        
> +        %
> +        % Give a new prog_var to the polymorphic structure.
> +        %

That comment doesn't describe what it does.

> +        svvarset.new_named_var("VarType", VarTypo, !VarSet),
> +        svmap.det_insert(VarTypo, MerType, !VarTypes),

VarType

>  
>          % Constructor of the variable's description.
>          svvarset.new_named_var("VarDesc", VarDesc, !VarSet), 
>          ConsId = cons(qualified(SSDBModule, "bound_head_var"), 3),
>          construct_type(TypeCtor, [], VarType), 
>          svmap.det_insert(VarDesc, VarType, !VarTypes),
> -        construct_functor(VarDesc, ConsId, [TypeInfoVar, VarNameVar, 
> -            VarPosVar, VarToInspect], ConstructVarGoal),
> +         
> +        ( map.is_empty(Renaming) ->
> +            construct_functor(VarDesc, ConsId, [TypeInfoVar, VarNameVar, 
> +                VarPosVar, VarToInspect], ConstructVarGoal)

Explain that.

> +        ;
> +            map.lookup(Renaming, VarToInspect, RenamedVar), 
> +            construct_functor(VarDesc, ConsId, [TypeInfoVar, VarNameVar, 
> +                VarPosVar, RenamedVar], ConstructVarGoal)
> +        ),
>  
>          Goals = [ConstructVarName, ConstructVarPos | TypeInfoGoal] ++
> -            [ConstructVarGoal]
> +            [ConstructVarGoal],
> +
> +        svmap.det_insert(VarToInspect, VarDesc, !BoundVarDescs)
> +
>      ;
>          svvarset.new_named_var("VarDesc", VarDesc, !VarSet), 
>          ConsId = cons(qualified(SSDBModule, "unbound_head_var"), 2),
> Index: ssdb/ssdb.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/ssdb/ssdb.m,v
> retrieving revision 1.6
> diff -u -r1.6 ssdb.m
> --- ssdb/ssdb.m	18 Oct 2007 08:27:08 -0000	1.6
> +++ ssdb/ssdb.m	26 Oct 2007 06:06:35 -0000
> @@ -173,6 +173,7 @@
>      % XXX Not yet implemented : redo, fail.
>      %
>  handle_event(ProcId, Event, ListVarValue) :-
> +    
>      impure get_event_num_inc(EventNum),
>      impure update_depth(Event, PrintDepth),
>  
> @@ -180,6 +181,7 @@
>          Event = ssdb_call,
>          % 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),
>  
> @@ -197,12 +199,14 @@
>          impure set_list_var_value_in_stack(ListVarValue),
>          semipure get_debugger_state(InitialState),
>          stack.top_det(InitialState ^ ssdb_stack, StackFrame)
> +
>      ;
>          Event = ssdb_redo,
>          error("ssdb_redo: not yet implemented")
>      ;
>          Event = ssdb_fail,
> -        error("ssdb_fail: not yet implemented")
> +        semipure get_debugger_state(InitialState),
> +        stack.top_det(InitialState ^ ssdb_stack, StackFrame)
>      ),
>   
>      semipure get_debugger_state(State0),
> @@ -228,7 +232,9 @@
>      ;
>          NextStop0 = ns_final_port(StopCSN),
>          (
> -            Event = ssdb_exit,
> +            ( Event = ssdb_exit
> +	    ; Event = ssdb_fail
> +	    ),

There are tab characters here.

>              is_same_event(StopCSN, CSN, Stop)
>          ;
>              Event = ssdb_call,
> @@ -256,7 +262,7 @@
>              io.nl(!IO),
>          
>              semipure get_shadow_stack(ShadowStack),
> -            impure prompt(ShadowStack, 0, WhatNext, !IO),
> +            impure prompt(Event, ShadowStack, 0, WhatNext, !IO),
>  
>              impure consume_io(!.IO),
>          
> @@ -291,12 +297,16 @@
>          StateEv1 = PopState ^ ssdb_stack := FinalStack1,
>          impure set_debugger_state(StateEv1)
>  
> +    ; Event = ssdb_fail,

indent


Peter

--------------------------------------------------------------------------
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