1:- module(
    2       swipl_debug_adapter,
    3       [
    4           swipl_debug_adapter_command_callback/6
    5       ]
    6   ).    7
    8:- use_module(library(debug_adapter/compat)).    9:- use_module(library(debug_adapter/sdk)).   10:- use_module(library(debug_adapter/server)).   11:- use_module(library(swipl_debug_adapter/stack)).   12:- use_module(library(swipl_debug_adapter/source)).   13:- use_module(library(swipl_debug_adapter/frame)).   14:- use_module(library(swipl_debug_adapter/clause)).
 swipl_debug_adapter_command_callback(+Command, +Arguments, +ReqSeq, +Handle, +State0, -State) is semidet
True when the SWI-Prolog debug adapter server transitions from State0 to State while handling DAP command Command and arguments Arguments.

This predicate is passed as the on_command callback option of da_server/1.

   23swipl_debug_adapter_command_callback(disconnect, _Arguments, ReqSeq, Handle, [], disconnected) :-
   24    !,
   25    da_sdk_response(Handle, ReqSeq, disconnect),
   26    da_sdk_stop(Handle).
   27swipl_debug_adapter_command_callback(initialize, Arguments, ReqSeq, Handle, [], initialized(Arguments)) :-
   28    !,
   29    swipl_debug_adapter_capabilities(Capabilities),
   30    da_sdk_response(Handle, ReqSeq, initialize, Capabilities),
   31    da_sdk_event(Handle, initialized).
   32swipl_debug_adapter_command_callback(initialize, _Arguments, ReqSeq, Handle, configured(Threads), configured(Threads)) :-
   33    !,
   34    swipl_debug_adapter_capabilities(Capabilities),
   35    da_sdk_response(Handle, ReqSeq, initialize, Capabilities),
   36    da_sdk_event(Handle, initialized).
   37swipl_debug_adapter_command_callback(attach, _Arguments, ReqSeq, Handle, configured(Threads), configured(Threads)) :-
   38    !,
   39    da_sdk_response(Handle, ReqSeq, attach).
   40swipl_debug_adapter_command_callback(launch, Arguments, ReqSeq, Handle, initialized(_), configured([Thread])) :-
   41    !,
   42    swipl_debug_adapter_launch_thread(Arguments, Handle, Thread),
   43    da_sdk_response(Handle, ReqSeq, launch).
   44swipl_debug_adapter_command_callback(disconnect, _Arguments, ReqSeq, Handle, initialized(_), disconnected) :-
   45    !,
   46    da_sdk_response(Handle, ReqSeq, disconnect),
   47    da_sdk_event(Handle, exited, _{ exitCode : 0 }),
   48    da_sdk_stop(Handle).
   49swipl_debug_adapter_command_callback(configurationDone, _Arguments, ReqSeq, Handle, initialized(_), configured([])) :-
   50    !,
   51    da_sdk_response(Handle, ReqSeq, configurationDone).
   52swipl_debug_adapter_command_callback(launch, Arguments, ReqSeq, Handle, configured(Threads), configured([Thread|Threads])) :-
   53    !,
   54    swipl_debug_adapter_launch_thread(Arguments, Handle, Thread),
   55    da_sdk_response(Handle, ReqSeq, launch).
   56swipl_debug_adapter_command_callback(configurationDone, _Arguments, ReqSeq, Handle, configured(Threads), configured(Threads)) :-
   57    !,
   58    da_sdk_response(Handle, ReqSeq, configurationDone).
   59swipl_debug_adapter_command_callback(threads, _Arguments, ReqSeq, Handle, configured(Threads), configured(Threads)) :-
   60    !,
   61    maplist(number_string, Threads, Names),
   62    maplist([I,N,_{id:I,name:N}]>>true, Threads, Names, Ts),
   63    da_sdk_response(Handle, ReqSeq, threads, _{threads:Ts}).
   64swipl_debug_adapter_command_callback(pause, Arguments, ReqSeq, Handle, configured(Threads0), configured(Threads)) :-
   65    !,
   66    _{ threadId : ThreadId } :< Arguments,
   67    select(ThreadId, Threads0, Threads1),
   68    catch((thread_signal(ThreadId, (retractall(swipl_debug_adapter_last_action(_)),
   69                                    asserta(swipl_debug_adapter_last_action(pause)))),
   70           thread_signal(ThreadId, trace),
   71           da_sdk_response(Handle, ReqSeq, pause),
   72           Threads = Threads0),
   73          _,
   74          (da_sdk_error(Handle, ReqSeq, pause, "Cannot pause requested thread"),
   75           Threads = Threads1)).
   76swipl_debug_adapter_command_callback(source, Arguments, ReqSeq, Handle, State, State) :-
   77    !,
   78    _{ sourceReference : SourceReference } :< Arguments,
   79    (   integer(SourceReference), SourceReference > 0
   80    ->  da_source_clause_cached_reference(ClauseRef, SourceReference),
   81        da_clause_decompiled(ClauseRef, Module, DecompiledClause, VariablesOffset),
   82        da_clause_source_term(ClauseRef, Module, DecompiledClause, VariablesOffset, SourceClause, _, _),
   83        with_output_to(string(Content), portray_clause(current_output, SourceClause, [module(Module)])),
   84        da_sdk_response(Handle, ReqSeq, source, _{content:Content})
   85    ;   da_sdk_error(Handle, ReqSeq, source, "Cannot provide source code for requested predicate")
   86    ).
   87swipl_debug_adapter_command_callback(exceptionInfo, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
   88    !,
   89    _{ threadId : ThreadId } :< Arguments,
   90    select(ThreadId, Threads0, Threads1),
   91    catch((thread_send_message(ThreadId, exception_info(ReqSeq)), Threads = Threads0),
   92          _,
   93          Threads = Threads1).
   94swipl_debug_adapter_command_callback(stackTrace, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
   95    !,
   96    _{ threadId : ThreadId } :< Arguments,
   97    select(ThreadId, Threads0, Threads1),
   98    catch((thread_send_message(ThreadId, stack_trace(ReqSeq)), Threads = Threads0),
   99          _,
  100          Threads = Threads1).
  101swipl_debug_adapter_command_callback(evaluate, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
  102    !,
  103    _{ frameId : FrameId, expression : Expression } :< Arguments,
  104    include({ReqSeq, FrameId}/[T]>>catch(thread_send_message(T, evaluate(ReqSeq, FrameId, Expression)),
  105                                         _,
  106                                         fail),
  107            Threads0,
  108            Threads).
  109swipl_debug_adapter_command_callback(completions, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
  110    !,
  111    _{ frameId : FrameId, text : Text, column: Column } :< Arguments,
  112    include({ReqSeq, FrameId}/[T]>>catch(thread_send_message(T, completions(ReqSeq, FrameId, Text, Column)),
  113                                         _,
  114                                         fail),
  115            Threads0,
  116            Threads).
  117swipl_debug_adapter_command_callback(scopes, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
  118    !,
  119    _{ frameId : FrameId } :< Arguments,
  120    include({ReqSeq, FrameId}/[T]>>catch(thread_send_message(T, scopes(ReqSeq, FrameId)),
  121                                         _,
  122                                         fail),
  123            Threads0,
  124            Threads).
  125swipl_debug_adapter_command_callback(variables, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
  126    !,
  127    _{ variablesReference : VariablesRef } :< Arguments,
  128    include({ReqSeq, VariablesRef}/[T]>>catch(thread_send_message(T, variables(ReqSeq, VariablesRef)),
  129                                         _,
  130                                         fail),
  131            Threads0,
  132            Threads).
  133swipl_debug_adapter_command_callback(stepInTargets, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
  134    !,
  135    _{ frameId : FrameId } :< Arguments,
  136    include({ReqSeq, FrameId}/[T]>>catch(thread_send_message(T, step_in_targets(ReqSeq, FrameId)),
  137                                         _,
  138                                         fail),
  139            Threads0,
  140            Threads).
  141swipl_debug_adapter_command_callback(stepIn, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
  142    !,
  143    _{ threadId : ThreadId } :< Arguments,
  144    select(ThreadId, Threads0, Threads1),
  145    (   get_dict(targetId, Arguments, Target)
  146    ->  true
  147    ;   Target = 0
  148    ),
  149    catch((thread_send_message(ThreadId, step_in(ReqSeq, Target)), Threads = Threads0),
  150          _,
  151          Threads = Threads1).
  152swipl_debug_adapter_command_callback(next, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
  153    !,
  154    _{ threadId : ThreadId } :< Arguments,
  155    select(ThreadId, Threads0, Threads1),
  156    catch((thread_send_message(ThreadId, next(ReqSeq)), Threads = Threads0),
  157          _,
  158          Threads = Threads1).
  159swipl_debug_adapter_command_callback(stepOut, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
  160    !,
  161    _{ threadId : ThreadId } :< Arguments,
  162    select(ThreadId, Threads0, Threads1),
  163    catch((thread_send_message(ThreadId, step_out(ReqSeq)), Threads = Threads0),
  164          _,
  165          Threads = Threads1).
  166swipl_debug_adapter_command_callback(restartFrame, Arguments, ReqSeq, _Handle, configured(Threads0), configured(Threads)) :-
  167    !,
  168    _{ frameId : FrameId } :< Arguments,
  169    include({ReqSeq, FrameId}/[T]>>catch(thread_send_message(T, restart_frame(ReqSeq, FrameId)),
  170                                         _,
  171                                         fail),
  172            Threads0,
  173            Threads).
  174swipl_debug_adapter_command_callback(setFunctionBreakpoints, Arguments, ReqSeq, Handle, State, State) :-
  175    !,
  176    _{ breakpoints : ReqBreakpoints } :< Arguments,
  177    maplist(swipl_debug_adapter_translate_function_breakpoint, ReqBreakpoints, PIs),
  178    retractall(swipl_debug_adapter_function_breakpoint(_)),
  179    nospyall,
  180    findall(_{verified:Verified},
  181            (member(PI, PIs),
  182             (   pi_head(PI, Head),
  183                 predicate_property(Head, defined)
  184             ->  asserta(swipl_debug_adapter_function_breakpoint(PI)),
  185                 spy(PI), nodebug,
  186                 Verified = true
  187             ;   Verified = false)),
  188            ResBreakpoints),
  189    da_sdk_response(Handle, ReqSeq, setFunctionBreakpoints, _{breakpoints:ResBreakpoints}).
  190swipl_debug_adapter_command_callback(setExceptionBreakpoints, Arguments, ReqSeq, Handle, State, State) :-
  191    !,
  192    _{ filters : Filters } :< Arguments,
  193    (   Filters == []
  194    ->  retractall(swipl_debug_adapter_trapping),
  195        da_sdk_response(Handle, ReqSeq, setExceptionBreakpoints, _{breakpoints:[]})
  196    ;   Filters = ["true"|_]
  197    ->  asserta(swipl_debug_adapter_trapping),
  198        da_sdk_response(Handle, ReqSeq, setExceptionBreakpoints, _{breakpoints:[_{verified:true}]})
  199    ).
  200swipl_debug_adapter_command_callback(setBreakpoints, Arguments, ReqSeq, Handle, State, State) :-
  201    !,
  202    _{ source      : DAPSource,
  203       breakpoints : DAPReqBreakpoints
  204     } :< Arguments,
  205    dap_source_path(DAPSource, Path),
  206    maplist(swipl_debug_adapter_translate_source_breakpoint(Path), DAPReqBreakpoints, ReqBreakpoints),
  207    swipl_debug_adapter_breakpoints_set(Path, ReqBreakpoints, ResBreakpoints),
  208    maplist(swipl_debug_adapter_translate_result_breakpoint, ResBreakpoints, DAPBreakpoints),
  209    da_sdk_response(Handle, ReqSeq, setBreakpoints, _{breakpoints:DAPBreakpoints}).
  210swipl_debug_adapter_command_callback(disconnect, _Arguments, ReqSeq, Handle, configured(Threads), disconnected) :-
  211    !,
  212    maplist([T]>>catch(thread_send_message(T, disconnect), _, true), Threads),
  213    da_sdk_response(Handle, ReqSeq, disconnect),
  214    da_sdk_stop(Handle).
  215swipl_debug_adapter_command_callback(continue, Arguments, ReqSeq, Handle, configured(Threads), configured(Threads)) :-
  216    !,
  217    _{ threadId : ThreadId } :< Arguments,
  218    select(ThreadId, Threads0, Threads1),
  219    catch((thread_send_message(ThreadId, continue), Threads = Threads0),
  220          _,
  221          Threads = Threads1),
  222    da_sdk_response(Handle, ReqSeq, continue).
  223
  224
  225swipl_debug_adapter_capabilities(_{ supportsConfigurationDoneRequest  : true,
  226                                    supportsExceptionInfoRequest      : true,
  227                                    supportsRestartFrame              : true,
  228                                    supportsEvaluateForHovers         : true,
  229                                    supportsCompletionsRequest        : true,
  230                                    supportsFunctionBreakpoints       : true,
  231                                    supportsConditionalBreakpoints    : true,
  232                                    supportsHitConditionalBreakpoints : true,
  233                                    supportsLogPoints                 : true,
  234                                    supportsStepInTargetsRequest      : true,
  235                                    exceptionBreakpointFilters        : [ _{ filter : "true" , label : "Trap exceptions", default: false } ]
  236                                  }
  237                                ).
  238
  239dap_source_path(D, path(P)     ) :- _{ path            : P0 } :< D, !, absolute_file_name(P0, P).
  240dap_source_path(D, reference(R)) :- _{ sourceReference : R  } :< D.
  241
  242swipl_debug_adapter_launch_thread(Args, Handle, ThreadId) :-
  243    _{ goal: "$run_in_terminal" } :< Args,
  244    !,
  245    thread_self(ServerThreadId),
  246    tcp_socket(ServerSocket),
  247    tcp_setopt(ServerSocket, reuseaddr),
  248    tcp_bind(ServerSocket, Port),
  249    thread_create(swipl_debug_adapter_top_level(ServerSocket, ServerThreadId, Handle), PrologThreadId),
  250    number_string(Port, PortString),
  251    working_directory(WD, WD),
  252    da_sdk_request(Handle,
  253                runInTerminal,
  254                _{   kind  : "integrated",
  255                     cwd   : WD,
  256                     title : "Toplevel",
  257                     args  : ["telnet",  "127.0.0.1", PortString]
  258                 }),
  259    thread_get_message(started(PrologThreadId)),
  260    thread_property(PrologThreadId, id(ThreadId)).
  261swipl_debug_adapter_launch_thread(Args, Handle, ThreadId) :-
  262    _{ cwd: CWD, module: ModulePath, goal: GoalString } :< Args,
  263    !,
  264    cd(CWD),
  265    user:ensure_loaded(ModulePath),
  266    thread_self(ServerThreadId),
  267    thread_create(swipl_debug_adapter_debugee(ModulePath, GoalString, ServerThreadId, Handle), PrologThreadId),
  268    thread_get_message(started(PrologThreadId)),
  269    thread_property(PrologThreadId, id(ThreadId)).
  270
  271
  272swipl_debug_adapter_top_level(ServerSocket, ServerThreadId, Handle) :-
  273    thread_self(Self),
  274    thread_send_message(ServerThreadId, started(Self)),
  275    thread_property(Self, id(Id)),
  276    da_sdk_event(Handle, thread, _{ reason   : "started",
  277                                    threadId : Id }),
  278    swipl_debug_adapter_top_level_setup(ServerSocket),
  279    swipl_debug_adapter_terminal(Handle).
  280
  281
  282:- det(swipl_debug_adapter_terminal/1).  283swipl_debug_adapter_terminal(Handle) :-
  284    swipl_debug_adapter_setup(Handle, Ref),
  285    user:prolog,
  286    thread_self(Self),
  287    thread_property(Self, id(Id)),
  288    da_sdk_event(Handle, thread, _{ reason   : "exited",
  289                                    threadId : Id }),
  290    da_sdk_event(Handle, exited, _{ exitCode : 0 }),
  291    swipl_debug_adapter_cleanup(Ref).
  292
  293swipl_debug_adapter_top_level_setup(ServerSocket) :-
  294    tcp_listen(ServerSocket, 5),
  295    tcp_accept(ServerSocket, ClientSocket, ip(127,0,_,_)),
  296    tcp_open_socket(ClientSocket, InStream, OutStream),
  297    set_stream(InStream, close_on_abort(false)),
  298    set_stream(OutStream, close_on_abort(false)),
  299    set_prolog_IO(InStream, OutStream, OutStream),
  300    set_stream(InStream, tty(true)),
  301    set_prolog_flag(tty_control, false),
  302    current_prolog_flag(encoding, Enc),
  303    set_stream(user_input, encoding(Enc)),
  304    set_stream(user_output, encoding(Enc)),
  305    set_stream(user_error, encoding(Enc)),
  306    set_stream(user_input, newline(detect)),
  307    set_stream(user_output, newline(dos)),
  308    set_stream(user_error, newline(dos)),
  309    set_prolog_flag(toplevel_prompt, '?- ').
  310
  311:- det(swipl_debug_adapter_debugee/4).  312swipl_debug_adapter_debugee(ModulePath, GoalString, ServerThreadId, Handle) :-
  313    thread_self(Self),
  314    thread_send_message(ServerThreadId, started(Self)),
  315    thread_property(Self, id(Id)),
  316    da_sdk_event(Handle, thread, _{ reason   : "started",
  317                                    threadId : Id }),
  318    term_string(Goal, GoalString, [variable_names(VarNames)]),
  319    absolute_file_name(ModulePath, AbsModulePath, []),
  320    user:ensure_loaded(AbsModulePath),
  321    (   module_property(Module, file(AbsModulePath))
  322    ->  qualified(QGoal, Module, Goal)
  323    ;   QGoal = Goal
  324    ),
  325    swipl_debug_adapter_trace(QGoal, VarNames, Handle).
  326
  327
  328swipl_debug_adapter_translate_exit_code(true        , 0) :- !.
  329swipl_debug_adapter_translate_exit_code(false       , 1) :- !.
  330swipl_debug_adapter_translate_exit_code(exception(_), 2) :- !.
  331
  332swipl_debug_adapter_translate_source_breakpoint(P, D, source_breakpoint(L, C, Cond, Hit, Log)) :-
  333    (   get_dict(line, D, L)
  334    ->  true
  335    ;   L = 0
  336    ),
  337    (   get_dict(column, D, C0)
  338    ->  true
  339    ;   C0 = 5    % 5 is a "guess" of the indentation.
  340    ),
  341    da_source_file_offsets_line_column_pairs(P, [C], [L-C0]),
  342    (   get_dict(condition, D, Cond)
  343    ->  true
  344    ;   Cond = "true"
  345    ),
  346    (   get_dict(logMessage, D, Log0)
  347    ->  Log = log_message(Log0)
  348    ;   Log = null
  349    ),
  350    (   get_dict(hitCondition, D, Hit0)
  351    ->  (   number(Hit0)
  352        ->  Hit = Hit0
  353        ;   number_string(Hit, Hit0)
  354        )
  355    ;   Hit = 0
  356    ).
  357
  358
  359swipl_debug_adapter_translate_variable(variable(Name, Value, VariablesRef),
  360                                       _{ name               : Name,
  361                                          variablesReference : VariablesRef,
  362                                          value              : Value }).
  363
  364
  365swipl_debug_adapter_translate_result_breakpoint(breakpoint(Id, Verified, Message, SourceSpan),
  366                                                _{ id                 : Id,
  367                                                   verified           : Verified,
  368                                                   message            : Message,
  369                                                   source             : DAPSource,
  370                                                   line               : SL,
  371                                                   column             : SC,
  372                                                   endLine            : EL,
  373                                                   endColumn          : EC
  374                                                 }
  375                                               ) :-
  376    swipl_debug_adapter_translate_source_span(SourceSpan, DAPSource, SL, SC, EL, EC).
  377
  378
  379swipl_debug_adapter_translate_source_span(span(path(File), SL, SC, EL, EC),
  380                                          _{ name            : Name,
  381                                             path            : File,
  382                                             origin          : "Static"
  383                                           },
  384                                          SL, SC, EL, EC
  385                                         ) :-
  386    !,
  387    file_base_name(File, Name).
  388swipl_debug_adapter_translate_source_span(span(reference(SourceReference), SL, SC, EL, EC),
  389                                          _{ name            : "*dynamic*",
  390                                             sourceReference : SourceReference,
  391                                             origin          : "Dynamic"
  392                                           },
  393                                          SL, SC, EL, EC
  394                                         ).
  395
  396
  397swipl_debug_adapter_translate_function_breakpoint(D, M:P) :-
  398    get_dict(name, D, S),
  399    term_string(M:P, S),
  400    !.
  401swipl_debug_adapter_translate_function_breakpoint(D, user:P) :-
  402    get_dict(name, D, S),
  403    term_string(P, S).
  404
  405:- thread_local
  406   swipl_debug_adapter_last_action/1.  407
  408:- dynamic
  409   swipl_debug_adapter_handle/1,
  410   swipl_debug_adapter_trapping/0,
  411   swipl_debug_adapter_source_breakpoint/7,
  412   swipl_debug_adapter_function_breakpoint/1.  413
  414
  415swipl_debug_adapter_setup(Handle, Ref) :-
  416    asserta(swipl_debug_adapter_handle(Handle), Ref),
  417    asserta(swipl_debug_adapter_last_action(entry)),
  418    asserta((user:thread_message_hook(Term, Kind, Lines) :-
  419                 swipl_debug_adapter_message_hook(Term, Kind, Lines),
  420                 fail)),
  421    asserta((user:prolog_exception_hook(Ex, Out, Frame, Catcher) :-
  422                 swipl_debug_adapter_exception_hook(Ex, Out, Frame, Catcher),
  423                 fail)),
  424    prolog_listen(break, swipl_debug_adapter:swipl_debug_adapter_handle_break_event, [as(last), name(swipl_debug_adapter)]),
  425    create_prolog_flag(gui_tracer, true, [type(boolean)]),
  426    visible([+call, +exit, +fail, +redo, +unify, +cut_call, +cut_exit, +exception]),
  427    prolog_skip_level(_, very_deep).
  428
  429
  430:- det(swipl_debug_adapter_trace/3).  431swipl_debug_adapter_trace(QGoal, VarNames, Handle) :-
  432    swipl_debug_adapter_setup(Handle, Ref),
  433    swipl_debug_adapter_goal_reified_result(QGoal, VarNames, Result),
  434    thread_self(Self),
  435    thread_property(Self, id(Id)),
  436    da_sdk_event(Handle, thread, _{ reason   : "exited",
  437                                    threadId : Id }),
  438    swipl_debug_adapter_translate_exit_code(Result, ExitCode),
  439    da_sdk_event(Handle, exited, _{ exitCode : ExitCode }),
  440    swipl_debug_adapter_cleanup(Ref).
  441
  442
  443swipl_debug_adapter_cleanup(Ref) :-
  444    prolog_listen(break,
  445                  swipl_debug_adapter:swipl_debug_adapter_mock_break_event,
  446                  [as(last), name(swipl_debug_adapter)]),
  447    erase(Ref).
  448
  449
  450swipl_debug_adapter_goal_reified_result(Goal, VarNames, Result) :-
  451    catch((   trace, Goal, notrace
  452          ->  print_message(trace, swipl_debug_adapter_top_level_query(true(VarNames))),
  453              Result = true
  454          ;   notrace,
  455              print_message(trace, swipl_debug_adapter_top_level_query(false)),
  456              Result = false
  457          ),
  458          Catcher,
  459          (notrace,
  460           print_message(trace, swipl_debug_adapter_top_level_query(exception(Catcher))),
  461           Result = exception(Catcher)
  462          )
  463         ).
  464
  465
  466swipl_debug_adapter_handle_break_event(gc, ClauseRef, PC) :-
  467    swipl_debug_adapter_handle(Handle),
  468    !,
  469    (   retract(swipl_debug_adapter_source_breakpoint(BP, ClauseRef, PC, _, _, _, _))
  470    ->  da_sdk_event(Handle, breakpoint, _{ reason     : "removed",
  471                                            breakpoint : _{ id       : BP,
  472                                                            verified : false }})
  473    ;   true
  474    ).
  475
  476
  477swipl_debug_adapter_mock_break_event(_, _, _) :- fail.
  478
  479
  480:- public swipl_debug_adapter_exception_hook/4.  481swipl_debug_adapter_exception_hook(_In, _Out, _Frame, _Catcher) :-
  482    thread_self(Me),
  483    thread_property(Me, debug(true)),
  484    swipl_debug_adapter_trapping,
  485    trace.
  486
  487:- public swipl_debug_adapter_message_hook/3.  488swipl_debug_adapter_message_hook(_   , silent, _) :- !.
  489swipl_debug_adapter_message_hook(Term, _     , _) :-
  490    swipl_debug_adapter_handle(Handle),
  491    phrase(prolog:message(Term), Lines),
  492    print_message_lines(string(String), '', Lines),
  493    da_sdk_event(Handle, output, _{output:String, category:"stdout"}).
  494
  495
  496:- multifile prolog:open_source_hook/3.  497
  498prolog:open_source_hook(Path, Stream, _Options) :-
  499    (   swipl_debug_adapter_handle(Handle)
  500    ->  (   source_file(Path)
  501        ->  Reason = "new"
  502        ;   Reason = "changed"
  503        ),
  504        file_base_name(Path, BaseName),
  505        da_sdk_event(Handle, loadedSource, _{ reason : Reason,
  506                                              source : _{ name : BaseName,
  507                                                          path : Path }})
  508    ;   true
  509    ),
  510    open(Path, read, Stream).
  511
  512
  513:- multifile prolog:message//1.  514
  515prolog:message(swipl_debug_adapter_top_level_query(true([]))) -->
  516    !,
  517    [ 'true.'-[] ].
  518prolog:message(swipl_debug_adapter_top_level_query(true(VarNames))) -->
  519    !,
  520    [ '~p'-[VarNames], nl ],
  521    [ 'true.'-[] ].
  522prolog:message(swipl_debug_adapter_top_level_query(false)) -->
  523    !,
  524    [ 'false.'-[] ].
  525prolog:message(swipl_debug_adapter_top_level_query(exception(E))) -->
  526    !,
  527    [ 'unhandled exception: ~w.'-[E] ].
  528prolog:message(log_message(BP, Map, String0)) -->
  529    { interpolate_string(String0, String, Map, []) },
  530    !,
  531    [ 'Log point ~w: ~w'-[BP, String] ].
  532prolog:message(swipl_debug_adapter_client_choice(Choice)) -->
  533    !,
  534    [ 'Starting DAP client ~w'-[Choice] ].
  535prolog:message(swipl_debug_adapter_client_choices(Choices)) -->
  536    !,
  537    [ 'Available DAP clients:'-[], nl ],
  538    swipl_debug_adapter_client_choices_message(Choices, 1).
  539swipl_debug_adapter_client_choices_message([], _) -->
  540    !,
  541    [ 'Choice: '-[] ].
  542swipl_debug_adapter_client_choices_message([c(C, _, _)|T], N) -->
  543    !,
  544    [ '~w: ~w'-[N, C], nl ],
  545    { S is N + 1 },
  546    swipl_debug_adapter_client_choices_message(T, S).
  547
  548
  549
  550user:prolog_trace_interception(Port, Frame, Choice, Action) :-
  551    notrace(swipl_debug_adapter_trace_interception(Port, Frame, Choice, Action)),
  552    swipl_debug_adapter_tracer_yield(Action).
  553
  554
  555swipl_debug_adapter_trace_interception(Port, Frame, Choice, Action) :-
  556    swipl_debug_adapter_handle(Handle),
  557    !,
  558    swipl_debug_adapter_last_action(LastAction),
  559    !,
  560    swipl_debug_adapter_stopped(Port, Frame, Choice, LastAction, Handle, Action).
  561swipl_debug_adapter_trace_interception(Port, Frame, Choice, Action) :-
  562    swipl_debug_adapter_initiate_session(In, Out),
  563    !,
  564    thread_self(Self),
  565    thread_property(Self, id(Id)),
  566    message_queue_create(Handle),
  567    thread_create(da_server([initial_state(configured([Id])), in(In), out(Out), on_command(swipl_debug_adapter_command_callback), handle(Handle)]), _ServerThreadId),
  568    swipl_debug_adapter_setup(Handle, _),
  569    da_sdk_event(Handle, stopped, _{reason:"entry", threadId:Id}),
  570    swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action).
  571
  572
  573:- det(swipl_debug_adapter_stopped/6).  574swipl_debug_adapter_stopped(Port, Frame, Choice, LastAction, Handle, Action) :-
  575    swipl_debug_adapter_stopped_reason(Port, Frame, LastAction, Reason),
  576    thread_self(Self),
  577    thread_property(Self, id(Id)),
  578    put_dict(threadId, Reason, Id, Body),
  579    da_sdk_event(Handle, stopped, Body),
  580    swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action).
  581
  582swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action) :-
  583    thread_get_message(M),
  584    swipl_debug_adapter_handle_message(M, Port, Frame, Choice, Handle, Action).
  585
  586swipl_debug_adapter_handle_message(continue, _Port, _Frame, _Choice, Handle, continue) :-
  587    !,
  588    thread_self(Self),
  589    thread_property(Self, id(Id)),
  590    da_sdk_event(Handle, continued, _{threadId:Id}),
  591    retractall(swipl_debug_adapter_last_action(_)),
  592    asserta(swipl_debug_adapter_last_action(continue)).
  593swipl_debug_adapter_handle_message(stack_trace(ReqSeq), Port, Frame, Choice, Handle, Action) :-
  594    !,
  595    swipl_debug_adapter_stack_trace(Port, Frame, Choice, StackFrames),
  596    da_sdk_response(Handle, ReqSeq, stackTrace, _{stackFrames:StackFrames}),
  597    swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action).
  598swipl_debug_adapter_handle_message(disconnect, _Port, _Frame, _Choice, Handle, nodebug) :-
  599    !,
  600    thread_self(Self),
  601    thread_property(Self, id(Id)),
  602    da_sdk_event(Handle, continued, _{threadId:Id}),
  603    retractall(swipl_debug_adapter_last_action(_)),
  604    asserta(swipl_debug_adapter_last_action(continue)).
  605swipl_debug_adapter_handle_message(exception_info(ReqSeq), Port, Frame, Choice, Handle, Action) :-
  606    !,
  607    (   Port = exception(Exception)
  608    ->  term_string(Exception, String),
  609        da_sdk_response(Handle, ReqSeq, exceptionInfo, _{exceptionId:String, description:String})
  610    ;   da_sdk_error(Handle, ReqSeq, exceptionInfo, "No exceptionInfo available")
  611    ),
  612    swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action).
  613swipl_debug_adapter_handle_message(evaluate(ReqSeq, FrameId, SourceTerm), Port, Frame, Choice, Handle, Action) :-
  614    !,
  615    da_frame_evaluate(FrameId, SourceTerm, Result, Bindings),
  616    prolog:translate_bindings(Bindings, TraslatedBindings, _, _, _),
  617    phrase('$messages':bindings(TraslatedBindings, []), Lines),
  618    print_message_lines(string(Res0), '', Lines),
  619    format(string(Res), "~w~w.", [Res0, Result]),
  620    da_sdk_response(Handle, ReqSeq, evaluate, _{result:Res, variablesReference:0}),
  621    swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action).
  622swipl_debug_adapter_handle_message(step_in_targets(ReqSeq, FrameId), Port, Frame, Choice, Handle, Action) :-
  623    !,
  624    da_frame_step_in_targets(FrameId, Frame, Choice, Targets),
  625    maplist(swipl_debug_adapter_translate_step_in_target, Targets, DAPTargets),
  626    da_sdk_response(Handle, ReqSeq, stepInTargets, _{targets:DAPTargets}),
  627    swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action).
  628swipl_debug_adapter_handle_message(scopes(ReqSeq, FrameId), Port, Frame, Choice, Handle, Action) :-
  629    !,
  630    da_frame_scopes(FrameId, Frame, Port, Scopes),
  631    maplist(swipl_debug_adapter_translate_scope, Scopes, DAPScopes),
  632    da_sdk_response(Handle, ReqSeq, scopes, _{scopes:DAPScopes}),
  633    swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action).
  634swipl_debug_adapter_handle_message(variables(ReqSeq, VariablesRef), Port, Frame, Choice, Handle, Action) :-
  635    !,
  636    da_referenced_variables(VariablesRef, Variables),
  637    maplist(swipl_debug_adapter_translate_variable, Variables, DAPVariables),
  638    da_sdk_response(Handle, ReqSeq, variables, _{variables:DAPVariables}),
  639    swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action).
  640swipl_debug_adapter_handle_message(step_in(ReqSeq, 0), _Port, _Frame, _Choice, Handle, continue) :-
  641    !,
  642    da_sdk_response(Handle, ReqSeq, stepIn),
  643    retractall(swipl_debug_adapter_last_action(_)),
  644    asserta(swipl_debug_adapter_last_action(step_in)).
  645swipl_debug_adapter_handle_message(step_in(ReqSeq, 1), _Port, _Frame, _Choice, Handle, fail) :-
  646    !,
  647    da_sdk_response(Handle, ReqSeq, stepIn),
  648    retractall(swipl_debug_adapter_last_action(_)),
  649    asserta(swipl_debug_adapter_last_action(step_in)).
  650swipl_debug_adapter_handle_message(next(ReqSeq), _Port, _Frame, _Choice, Handle, skip) :-
  651    !,
  652    da_sdk_response(Handle, ReqSeq, next),
  653    retractall(swipl_debug_adapter_last_action(_)),
  654    asserta(swipl_debug_adapter_last_action(next)).
  655swipl_debug_adapter_handle_message(step_out(ReqSeq), _Port, _Frame, _Choice, Handle, up) :-
  656    !,
  657    da_sdk_response(Handle, ReqSeq, stepOut),
  658    retractall(swipl_debug_adapter_last_action(_)),
  659    asserta(swipl_debug_adapter_last_action(step_out)).
  660swipl_debug_adapter_handle_message(restart_frame(ReqSeq, FrameId), _Port, _Frame, _Choice, Handle, retry(FrameId)) :-
  661    !,
  662    da_sdk_response(Handle, ReqSeq, restartFrame),
  663    retractall(swipl_debug_adapter_last_action(_)),
  664    asserta(swipl_debug_adapter_last_action(restart_frame)).
  665swipl_debug_adapter_handle_message(completions(ReqSeq, FrameId, Text, Column), Port, Frame, Choice, Handle, Action) :-
  666    !,
  667    string_codes(Text, Codes),
  668    phrase(token_prefix_at(TokenPrefix, Column), Codes, _),
  669    swipl_debug_adapter_completion_targets(TokenPrefix, FrameId, Targets),
  670    da_sdk_response(Handle, ReqSeq, completions, _{targets:Targets}),
  671    swipl_debug_adapter_handle_messages(Port, Frame, Choice, Handle, Action).
  672
  673swipl_debug_adapter_completion_targets(atom(Prefix), _, Targets) :-
  674    findall(_{ label: Label,
  675               text : Text,
  676               type : Type },
  677            swipl_debug_adapter_atom_completion(Prefix, Label, Text, Type),
  678            Targets).
  679swipl_debug_adapter_completion_targets(var(Prefix), FrameId, Targets) :-
  680    da_frame_variables_mapping(FrameId, Mapping),
  681    findall(_{ label: Name,
  682               text : Name,
  683               type : variable },
  684            (member(Name0=_, Mapping), atom_string(Name0, Name), sub_string(Name, 0, _, _, Prefix)),
  685            Targets, Tail),
  686    findall(_{ label: Label,
  687               text : Text,
  688               type : Type },
  689            (swipl_debug_adapter_atom_completion(Prefix, Label, Text0, Type),
  690             format(string(Text), "'~w'", [Text0])),
  691            Tail).
  692swipl_debug_adapter_completion_targets(symbol(Prefix), _, Targets) :-
  693    findall(_{ label: Label,
  694               text : Text,
  695               type : Type },
  696            swipl_debug_adapter_symbol_completion(Prefix, Label, Text, Type),
  697            Targets).
  698
  699swipl_debug_adapter_atom_completion(Prefix, Label, Text, predicate) :-
  700    current_predicate(P/I),
  701    sub_atom(P, 0, _, _, Prefix),
  702    format(string(Label), "~w/~w", [P,I]),
  703    format(string(Text), "~w(", [P]).
  704swipl_debug_adapter_atom_completion(Prefix, Label, Text, predicate) :-
  705    current_predicate(M:P/I),
  706    atom_string(P, Name),
  707    sub_string(Name, 0, _, _, Prefix),
  708    format(string(Label), "~w:~w/~w", [M, P, I]),
  709    format(string(Text), "~w:~w(", [M, P]).
  710swipl_debug_adapter_atom_completion(Prefix, Label, Text, module) :-
  711    current_module(M),
  712    atom_string(M, Name),
  713    sub_string(Name, 0, _, _, Prefix),
  714    format(string(Label), "~w", [M]),
  715    format(string(Text), "~w:", [M]).
  716swipl_debug_adapter_atom_completion(Prefix, Label, Text, Type) :-
  717    current_op(_, Associativity, Op),
  718    atom_string(Op, Name),
  719    sub_string(Name, 0, _, _, Prefix),
  720    swipl_debug_adapter_operator_completion(Associativity, Op, Label, Text, Type).
  721swipl_debug_adapter_atom_completion(Prefix, Atom, Atom, atom) :-
  722    current_atom(Atom),
  723    atom_string(Atom, Name),
  724    sub_string(Name, 0, _, _, Prefix).
  725
  726
  727swipl_debug_adapter_symbol_completion(Prefix, Label, Text, Type) :-
  728    current_op(_, Associativity, Op),
  729    atom_string(Op, Name),
  730    sub_string(Name, 0, _, _, Prefix),
  731    swipl_debug_adapter_operator_completion(Associativity, Op, Label, Text, Type).
  732
  733
  734swipl_debug_adapter_operator_completion(xf , Op, Label, Op, 'suffix operator') :-
  735    format(string(Label), "X ~w", [Op]).
  736swipl_debug_adapter_operator_completion(yf , Op, Label, Op, 'suffix operator') :-
  737    format(string(Label), "Y ~w", [Op]).
  738swipl_debug_adapter_operator_completion(xfx, Op, Label, Tx, 'infix operator' ) :-
  739    format(string(Label), "X ~w X", [Op]),
  740    format(string(Tx), "~w ", [Op]).
  741swipl_debug_adapter_operator_completion(xfy, Op, Label, Tx, 'infix operator' ) :-
  742    format(string(Label), "X ~w Y", [Op]),
  743    format(string(Tx), "~w ", [Op]).
  744swipl_debug_adapter_operator_completion(yfx, Op, Label, Tx, 'infix operator' ) :-
  745    format(string(Label), "Y ~w X", [Op]),
  746    format(string(Tx), "~w ", [Op]).
  747swipl_debug_adapter_operator_completion(fy , Op, Label, Tx, 'prefix operator') :-
  748    format(string(Label), "~w Y", [Op]),
  749    format(string(Tx), "~w ", [Op]).
  750swipl_debug_adapter_operator_completion(fx , Op, Label, Tx, 'prefix operator') :-
  751    format(string(Label), "~w X", [Op]),
  752    format(string(Tx), "~w ", [Op]).
  753
  754token_prefix_at(T, N) -->
  755    [C],
  756    {   P is N - 1   },
  757    code_token_prefix_at(C, T, P).
  758
  759
  760code_token_prefix_at(C, T, N) -->
  761    {   code_type(C, prolog_atom_start)   },
  762    !,
  763    continuation_at(atom, [C], T, N).
  764code_token_prefix_at(C, T, N) -->
  765    {   code_type(C, prolog_var_start)   },
  766    !,
  767    continuation_at(var, [C], T, N).
  768code_token_prefix_at(C, T, N) -->
  769    {   code_type(C, prolog_symbol)   },
  770    !,
  771    symbol_at([C], T, N).
  772code_token_prefix_at(_, T, N) -->
  773    token_prefix_at(T, N).
  774
  775
  776continuation_at(atom, Codes0, atom(Prefix), 0) -->
  777    !,
  778    {   reverse(Codes0, Codes), string_codes(Prefix, Codes)   }.
  779continuation_at(var, Codes0, var(Prefix), 0) -->
  780    !,
  781    {   reverse(Codes0, Codes), string_codes(Prefix, Codes)   }.
  782continuation_at(Kind, Codes, T, N) -->
  783    [C],
  784    {   P is N - 1   },
  785    code_continuation_at(Kind, C, Codes, T, P).
  786
  787
  788code_continuation_at(Kind, C, Codes, T, N) -->
  789    {   code_type(C, prolog_identifier_continue)   },
  790    !,
  791    continuation_at(Kind, [C|Codes], T, N).
  792code_continuation_at(_Kind, C, _Codes, T, N) -->
  793    code_token_prefix_at(C, T, N).
  794
  795
  796symbol_at(Codes0, symbol(Prefix), 0) -->
  797    !,
  798    {   reverse(Codes0, Codes), string_codes(Prefix, Codes)   }.
  799symbol_at(Codes, T, N) -->
  800    [C],
  801    {   P is N - 1   },
  802    code_symbol_at(C, Codes, T, P).
  803
  804
  805code_symbol_at(C, Codes, T, N) -->
  806    {   code_type(C, prolog_symbol)   },
  807    !,
  808    symbol_at([C|Codes], T, N).
  809code_symbol_at(C, _Codes, T, N) -->
  810    code_token_prefix_at(C, T, N).
  811
  812
  813
  814swipl_debug_adapter_stopped_reason(exception(E), _, _            , _{reason:exception, description:D}) :- !, term_string(E, D).
  815swipl_debug_adapter_stopped_reason(call        , _, entry        , _{reason:entry}) :- !.
  816swipl_debug_adapter_stopped_reason(_           , _, step_in      , _{reason:step}) :- !.
  817swipl_debug_adapter_stopped_reason(_           , _, step_out     , _{reason:step}) :- !.
  818swipl_debug_adapter_stopped_reason(_           , _, next         , _{reason:step}) :- !.
  819swipl_debug_adapter_stopped_reason(_           , _, restart_frame, _{reason:restart}) :- !.
  820swipl_debug_adapter_stopped_reason(_           , _, pause        , _{reason:pause}) :- !.
  821swipl_debug_adapter_stopped_reason(_           , _, breakpoint(B), _{reason:breakpoint, hitBreakpointIds:[B]}) :- !.
  822swipl_debug_adapter_stopped_reason(call        , F, _            , _{reason:"function breakpoint"}) :-
  823    prolog_frame_attribute(F, predicate_indicator, PI),
  824    (   PI = _:_
  825    ->  swipl_debug_adapter_function_breakpoint(PI)
  826    ;   swipl_debug_adapter_function_breakpoint(user:PI)
  827    ),
  828    !.
  829swipl_debug_adapter_stopped_reason(_           , _, _            , _{reason:trace}).
  830
  831
  832swipl_debug_adapter_tracer_yield(skip) :-
  833    trace.
  834swipl_debug_adapter_tracer_yield(retry) :-
  835    prolog_skip_level(_, very_deep),
  836    trace.
  837swipl_debug_adapter_tracer_yield(retry(_)) :-
  838    prolog_skip_level(_, very_deep),
  839    trace.
  840swipl_debug_adapter_tracer_yield(fail) :-
  841    prolog_skip_level(_, very_deep),
  842    trace.
  843swipl_debug_adapter_tracer_yield(continue) :-
  844    swipl_debug_adapter_last_action(continue),
  845    !,
  846    notrace,
  847    prolog_skip_level(_, very_deep),
  848    debug.
  849swipl_debug_adapter_tracer_yield(continue) :-
  850    prolog_skip_level(_, very_deep),
  851    trace.
  852swipl_debug_adapter_tracer_yield(up) :-
  853    prolog_skip_level(_, very_deep),
  854    trace.
  855swipl_debug_adapter_tracer_yield(nodebug).
  856swipl_debug_adapter_tracer_yield(abort).
  857swipl_debug_adapter_tracer_yield(ignore) :-
  858    trace.
  859
  860
  861swipl_debug_adapter_stack_trace(Port, Frame, Choice, StackTrace) :-
  862    da_stack_frame_at_port(Frame, Port, Choice, ActiveFrame),
  863    da_stack_trace(Frame, StackFrames),
  864    maplist(swipl_debug_adapter_translate_stack_frame, [ActiveFrame|StackFrames], StackTrace).
  865
  866swipl_debug_adapter_translate_stack_frame(stack_frame(Id, InFrameLabel, PI, _Alternative, SourceSpan),
  867                                          _{ id                          : Id,
  868                                             name                        : Name,
  869                                             line                        : SL,
  870                                             column                      : SC,
  871                                             endLine                     : EL,
  872                                             endColumn                   : EC,
  873                                             source                      : DAPSource,
  874                                             instructionPointerReference : DAPLabel
  875                                           }) :-
  876    term_string(PI, Name),
  877    swipl_debug_adapter_translate_source_span(SourceSpan, DAPSource, SL, SC, EL, EC),
  878    swipl_debug_adapter_translate_inframe_label(InFrameLabel, DAPLabel).
  879
  880swipl_debug_adapter_translate_scope(scope(Name, VariablesRef, SourceSpan),
  881                                    _{ name               : Name,
  882                                       variablesReference : VariablesRef,
  883                                       expensive          : false,
  884                                       source             : DAPSource,
  885                                       line               : SL,
  886                                       column             : SC,
  887                                       endLine            : EL,
  888                                       endColumn          : EC
  889                                     }
  890                                   ) :-
  891    swipl_debug_adapter_translate_source_span(SourceSpan, DAPSource, SL, SC, EL, EC).
  892
  893swipl_debug_adapter_translate_inframe_label(port(Port), DAPLabel) :-
  894    !,
  895    functor(Port, PortName, _Arity),
  896    atom_string(PortName, DAPLabel).
  897swipl_debug_adapter_translate_inframe_label(pc(PC), DAPLabel) :-
  898    number_string(PC, DAPLabel).
  899
  900
  901swipl_debug_adapter_translate_step_in_target(step_in_target(Id, null), _{ id    : Id,
  902                                                                          label : "step" }) :- !.
  903swipl_debug_adapter_translate_step_in_target(step_in_target(Id, _Alt), _{ id    : Id,
  904                                                                          label : "fail" }).
  905
  906
  907prolog:break_hook(Clause, PC, FR, BFR, Expression, Action) :-
  908    swipl_debug_adapter_source_breakpoint(BP, Clause, PC, Cond, Hit0, Hit, Log),
  909    swipl_debug_adapter_break_hook(BP, Clause, PC, FR, BFR, Expression, Cond, Hit0, Hit, Log, Action).
  910
  911
  912:- det(swipl_debug_adapter_break_hook/11).  913swipl_debug_adapter_break_hook(BP, Clause, PC, FR, _BFR, _Expression, Cond, Hit, Hit, Log, Action) :-
  914    !,
  915    retractall(swipl_debug_adapter_source_breakpoint(BP, _, _, _, _, _, _)),
  916    asserta(swipl_debug_adapter_source_breakpoint(BP, Clause, PC, Cond, 0, Hit, Log)),
  917    da_frame_evaluate(FR, Cond, Result, _),
  918    swipl_debug_adapter_breakpoint_action(BP, FR, Result, Log, Action).
  919swipl_debug_adapter_break_hook(BP, Clause, PC, _FR, _BFR, _Expression, Cond, Hit0, Hit, Log, continue) :-
  920    retractall(swipl_debug_adapter_source_breakpoint(BP, _, _, _, _, _, _)),
  921    Hit1 is Hit0 + 1,
  922    asserta(swipl_debug_adapter_source_breakpoint(BP, Clause, PC, Cond, Hit1, Hit, Log)).
  923
  924
  925:- det(swipl_debug_adapter_breakpoint_action/5).  926swipl_debug_adapter_breakpoint_action( BP, _FR, true, null, trace   ) :- !,
  927    retractall(swipl_debug_adapter_last_action(_)),
  928    asserta(swipl_debug_adapter_last_action(breakpoint(BP))).
  929swipl_debug_adapter_breakpoint_action(_BP, _FR, _   , null               , continue) :- !.
  930swipl_debug_adapter_breakpoint_action( BP,  FR, true, log_message(String), continue) :- !,
  931    da_frame_variables_mapping(FR, Map),
  932    print_message(trace, log_message(BP, Map, String)).
  933swipl_debug_adapter_breakpoint_action(_BP, _FR, _   , _                  , continue).
  934
  935
  936:- det(swipl_debug_adapter_breakpoints_set/3).  937swipl_debug_adapter_breakpoints_set(path(Path), Req, Res) :-
  938    user:ensure_loaded(Path),
  939    forall(swipl_debug_adapter_breakpoint_path(BP, Path),
  940           swipl_debug_adapter_breakpoints_delete(BP)),
  941    phrase(swipl_debug_adapter_breakpoints_set(Req, path(Path)), Res).
  942
  943
  944swipl_debug_adapter_breakpoints_delete(BP) :-
  945    catch(ignore(prolog_breakpoints:delete_breakpoint(BP)), _, true),
  946    retractall(swipl_debug_adapter_source_breakpoint(BP, _, _, _, _, _, _)).
  947
  948
  949swipl_debug_adapter_breakpoint_path(BP, Path) :-
  950    prolog_breakpoints:breakpoint_property(BP, file(Path)).
  951
  952
  953swipl_debug_adapter_breakpoints_set([   ], _) --> [].
  954swipl_debug_adapter_breakpoints_set([H|T], P) --> swipl_debug_adapter_breakpoint_set(H, P), swipl_debug_adapter_breakpoints_set(T, P).
  955
  956
  957:- det(swipl_debug_adapter_breakpoint_set/4).  958swipl_debug_adapter_breakpoint_set(source_breakpoint(L0, C0, Cond, Hit, Log), path(P)) -->
  959    {   prolog_breakpoints:set_breakpoint(P, L0, C0, BP)   },
  960    !,
  961    {   prolog_breakpoints:known_breakpoint(Clause, PC, _, BP),
  962        asserta(swipl_debug_adapter_source_breakpoint(BP, Clause, PC, Cond, 0, Hit, Log)),
  963        prolog_breakpoints:breakpoint_property(BP, character_range(A, L)),
  964        Z is A + L,
  965        da_source_file_offsets_line_column_pairs(path(P), [A, Z], [SL-SC, EL-EC])
  966    },
  967    [   breakpoint(BP, true, null, span(path(P), SL, SC, EL, EC))   ].
  968swipl_debug_adapter_breakpoint_set(_, _) --> [].
  969
  970
  971swipl_debug_adapter_initiate_session(InStream, OutStream) :-
  972    tcp_socket(ServerSocket),
  973    tcp_setopt(ServerSocket, reuseaddr),
  974    tcp_bind(ServerSocket, TCPPort),
  975    tcp_listen(ServerSocket, 5),
  976    (   swipl_debug_adapter_initiate_client(TCPPort, _)
  977    ->  tcp_accept(ServerSocket, ClientSocket, Peer),
  978        (   Peer = ip(127,0,_,_)
  979        ->  tcp_open_socket(ClientSocket, InStream, OutStream)
  980        ;   tcp_close_socket(ServerSocket), tcp_close_socket(ClientSocket), !, fail
  981        )
  982    ;   tcp_close_socket(ServerSocket), !, fail
  983    ).
  984
  985
  986swipl_debug_adapter_initiate_client(TCPPort, PID) :-
  987    findall(c(Client, Exec, Args),
  988            swipl_debug_adapter_client_command(TCPPort, Client, Exec, Args),
  989            [H|T]),
  990    (   T == []
  991    ->  H =  c(C, E, A)
  992    ;   print_message(informational, swipl_debug_adapter_client_choices([H|T])),
  993        get_char(N),
  994        atom_number(N, M),
  995        nth1(M, [H|T], c(C, E, A))
  996    ),
  997    print_message(informational, swipl_debug_adapter_client_choice(C)),
  998    process_create(E, A, [detached(true), process(PID)]).
  999
 1000
 1001:- multifile swipl_debug_adapter_client_command/4. 1002:- dynamic swipl_debug_adapter_client_command/4. 1003:- public swipl_debug_adapter_client_command/4.
 swipl_debug_adapter_client_command(+TCPPort, -Client, -Exec, -Args) is multi
Multifile predicate, specifies an external command used for starting an interactive DAP client.

By default, swipl_debug_adapter currently defines a single DAP client, which unifies Client with emacs('dap-mode'), Exec with path(emacs) and Args with ['--eval', Elisp] where ELisp is a string denoting an Emacs Lisp form that Emacs executes to start the DAP session.

Users can specify different DAP clients by defining other clauses for this predicate. The solutions of this predicate are collected using findall/3, if mulitple solutions are found when the tracer is started, the user will be prompted to select a client to start.

Note: before version 0.7.0 of the debug_adapter package, a similar feature was provided that relied on a different multifle predicate, user:debugger_connection_template/1. This predicate supersedes that interface which is now obsolete.

Arguments:

 1029swipl_debug_adapter_client_command(TCPPort, emacs('dap-mode'), path(emacs), ['--eval', SExp]) :-
 1030    format(string(SExp), '(dap-debug (list :type \"swi-prolog-tcp\" :debugServer ~w))', [TCPPort])