1:- module(
    2       da_server,
    3       [
    4           da_server/1
    5       ]
    6   ).

SWI-Prolog Debug Adapter Protocol Server

This module contains the core logic for handling DAP requests sent by DAP clients which are most commonly IDE extensions controlled interactivly by a progammer. The main entry point is da_server/1.

The implementation is most dominently guided by the DAP specification. */

   19:- use_module(compat).   20:- use_module(protocol).   21:- use_module(sdk).   22
   23:- dynamic dap_server_thread_id/1.   24
   25
   26:- predicate_options(da_server/1, 1, [ in(+stream),
   27                                       out(+stream),
   28                                       threads(+list(pair)),
   29                                       setup(+callable),
   30                                       on_command(+callable),
   31                                       cleanup(+callable),
   32                                       initial_state(+any),
   33                                       handle(+any)
   34                                     ]
   35                    ).
 da_server(+Options) is det
Starts the DAP server in the current thread. Options:
in(+Stream)
Stream will be used by the server to read incoming messages from the client. Defaults to user_input.
out(+Stream)
Stream will be used by the server to emit outgoing messages to the client. Defaults to user_output.
setup(:Setup)
Setup will be called just before entering the main DAP server loop. Defaults to true.
on_command(:OnCommand)
OnCommand is a closure of arity 6 which will be called during the DAP session loop to handle incoming DAP request, like so:
call(OnCommand, +Command, +Arguments, +RequestSeq, +Handle, +State0, -State)

Where:

  • Command is an atom identyfing the type of the DAP request, e.g. stepIn.
  • Arguments is either the atom null or a dict containing Command -specific parameters.
  • RequestSeq is an integer identifying the received request in the scope of the current session.
  • Handle can be used to with the predicates from module da_sdk to communicate DAP messages (including the response for the handled command) back to the client.
  • State0 and State can be used to pass arbitrary terms between invocations of OnCommand during the course of a DAP session. The session loop will initially call OnCommand with State0 bound to an initial state term determined by the initial_state option of this predicate, in the next invocation State0 will be bound to the State argument of the prior invocation, and so forth.
cleanup(:Cleanup)
Cleanup will be called after the main DAP server loop completes. Defaults to true.
initial_state(+State)
State will be used as the initial state argument passed to OnCommand. Defaults to [].
   69:- det(da_server/1).   70da_server(Options) :-
   71    option(in(In), Options, user_input),
   72    option(out(Out), Options, user_output),
   73    option(setup(Setup), Options, true),
   74    option(on_command(OnCommand), Options),
   75    option(cleanup(Cleanup), Options, true),
   76    option(initial_state(State), Options, []),
   77    get_time(Now),
   78    option(timeout(Timeout), Options, 3600),
   79    Deadline is Now + Timeout,
   80    set_stream(In, buffer(full)),
   81    set_stream(In, newline(detect)),
   82    set_stream(In, representation_errors(error)),
   83    set_stream(In, tty(false)),
   84    message_queue_create(Q0),
   85    option(handle(Q), Options, Q0),
   86    da_server_listen(In, Q),
   87    set_stream(Out, buffer(false)),
   88    set_stream(Out, tty(false)),
   89    setup_call_cleanup(Setup,
   90                       da_server_loop(Out, Q, Deadline, OnCommand, 1, State),
   91                       Cleanup).
   92
   93
   94da_server_loop(_, _, _, _, stop, _) :- !.
   95da_server_loop(O, Q, Deadline, C, Seq0, State0) :-
   96    thread_get_message(Q, M, [deadline(Deadline)]),
   97    da_server_handle(O, Q, C, M, Seq0, Seq, State0, State),
   98    da_server_loop(O, Q, Deadline, C, Seq, State).
   99
  100da_server_handle(Out, _, _, action(Action), Seq0, Seq, State, State) :-
  101    !,
  102    da_server_perform_action(Out, Action, Seq0, Seq).
  103da_server_handle(Out, Q, CB, stream(Message), Seq0, Seq, State0, State) :-
  104    _{ type : "request",
  105       seq  : RequestSeq,
  106       command : Command0
  107     } :< Message,
  108    !,
  109    atom_string(Command, Command0),
  110    (   get_dict(arguments, Message, Arguments)
  111    ->  true
  112    ;   Arguments = null
  113    ),
  114    (   debug(dap(server), "Handling ~w request", [Command]),
  115        call(CB, Command, Arguments, RequestSeq, Q, State0, State)
  116    ->  Seq = Seq0
  117    ;   State = State0,
  118        dap_error(Out, Seq0, RequestSeq, Command, "Bad request"),
  119        Seq is Seq0 + 1
  120    ).
  121da_server_handle(_Out, _Q, _CB, stream(Message), Seq, Seq, State, State) :-
  122    _{ type : "response",
  123       command : "runInTerminal"
  124     } :< Message,
  125    !.
  126
  127da_server_perform_action(Out, response(ReqSeq, Type, Body), Seq0, Seq) :-
  128    !,
  129    dap_response(Out, Seq0, ReqSeq, Type, Body),
  130    Seq is Seq0 + 1.
  131da_server_perform_action(Out, error(ReqSeq, Type, Body), Seq0, Seq) :-
  132    !,
  133    dap_error(Out, Seq0, ReqSeq, Type, Body),
  134    Seq is Seq0 + 1.
  135da_server_perform_action(Out, event(Type, Body), Seq0, Seq) :-
  136    !,
  137    dap_event(Out, Seq0, Type, Body),
  138    Seq is Seq0 + 1.
  139da_server_perform_action(Out, request(Type, Body), Seq0, Seq) :-
  140    !,
  141    dap_request(Out, Seq0, Type, Body),
  142    Seq is Seq0 + 1.
  143da_server_perform_action(_, stop, _, stop).
  144
  145da_server_listen(S, Q) :-
  146    thread_create(da_server_listen_(S, Q), _, []).
  147
  148da_server_listen_(S, T) :-
  149    dap_read(S, Message),
  150    thread_send_message(T, stream(Message)),
  151    (   get_dict(command, Message, "disconnect")
  152    ->  true
  153    ;   da_server_listen_(S, T)
  154    )