1:- module(da_script,
    2          [
    3              run_script/2   % run_script(+Path, +Options)
    4          ]
    5         ).    6
    7:- use_module(compat).    8:- use_module(session).    9
   10:- predicate_options(run_script/2, 2, [ server_executable(+any),
   11                                        server_cli_args(+list(atom)),
   12                                        bindings(+list(any))]).
 run_script(Path, Options) is det
Main entry point for executing dapscripts. Reads the script from the file located at Path.

Supported Options are:

server_executable(+Exec)
Exec specifies the path of the DAP server executable to run the script against. Defaults to the swipl executable.
server_cli_args(+Args)
Args is a list of command line arguments that will be passed to the DAP server executable. Defaults to instructing swipl to load and run the SWI-Prolog debug adapter server from library(debug_adapter/main).
bindings(+Bindings)
Bindings is a list of variable bindings given as Name = Value pairs that will be made available in the context of the executed dapscript. Defaults to [].
   30run_script(Path, Options) :-
   31    swipl_executable(Swipl),
   32    option(server_executable(Exec), Options, Swipl),
   33    option(server_cli_args(Args), Options, ['-g', '[library(debug_adapter/main)]', '-t', 'halt', '--', '-T', '16']),
   34    option(bindings(Vars), Options, []),
   35    setup_call_cleanup(open(Path, read, In),
   36                       setup_call_cleanup(session_start([Exec|Args], Session),
   37                                          run_script_from_stream(In, Vars, Session),
   38                                          session_stop(Session)),
   39                       close(In)).
   40
   41run_script_from_stream(In, Vars0, Session) :-
   42    read_term(In, Term, [variable_names(Vars1)]),
   43    unify_vars(Vars1, Vars0, Vars),
   44    execute_term(Term, In, Vars, Session).
   45
   46:- det(unify_vars/3).   47unify_vars([], Vars, Vars) :- !.
   48unify_vars([H|T], Vars0, Vars) :-
   49    memberchk(H, Vars0), !,
   50    unify_vars(T, Vars0, Vars).
   51unify_vars([H|T], Vars0, [H|Vars]) :-
   52    unify_vars(T, Vars0, Vars).
   53
   54execute_term(end_of_file, _, _, _).
   55execute_term(?- Goal, In, Vars, Session) :-
   56    Goal,
   57    run_script_from_stream(In, Vars, Session).
   58execute_term(Kind :- Body, In, Vars, Session0) :-
   59    semicolon_list(Body, Parts),
   60    foldl(execute_part_(Kind), Parts, Session0, Session),
   61    run_script_from_stream(In, Vars, Session).
   62
   63execute_part_(Kind, Part, Session0, Session) :-
   64    debug(dap(script), "Executing ~p :- ~p", [Kind, Part]),
   65    execute_part(Kind, Part, Session0, Session).
   66execute_part(request, (Type:Req -> Res), Session0, Session) :-
   67    debug(dap(test), "here", []),
   68    !, session_request_response(Type, Req, Res, Session0, Session).
   69execute_part(request, (Type -> Res), Session0, Session) :-
   70    debug(dap(test), "there", []),
   71    !, session_request_response(Type, null, Res, Session0, Session),
   72    debug(dap(test), "there ~w", [Res]).
   73execute_part(request, (Type:Req *-> Success:Res0), Session0, Session) :-
   74    !, session_request_response(Type, Req, Success:Res, Session0, Session), Res0 >:< Res.
   75execute_part(request, (Type *-> Success:Res0), Session0, Session) :-
   76    !, session_request_response(Type, null, Success:Res, Session0, Session), Res0 >:< Res.
   77execute_part(request, (Type:Req), Session0, Session) :-
   78    !, session_request_response(Type, Req, _, Session0, Session).
   79execute_part(request, Type, Session0, Session) :-
   80    !, session_request_response(Type, null, _, Session0, Session).
   81execute_part(event, Type:Body, Session0, Session) :-
   82    !, session_event(Type, Body, Session0, Session), !.
   83execute_part(event, Type:<Body0, Session0, Session) :-
   84    !, session_event(Type, Body, Session0, Session), Body0 >:< Body, !.
   85execute_part(event, Type, Session0, Session) :-
   86    !, session_event(Type, _, Session0, Session), !.
   87execute_part(reverse, Type:Body, Session0, Session) :-
   88    !, session_reverse_request(Type, Body, Session0, Session), !.
   89execute_part(reverse, Type, Session0, Session) :-
   90    !, session_reverse_request(Type, _, Session0, Session), !.
   91
   92
   93swipl_executable('C:\\Program Files\\swipl\\bin\\swipl.exe') :-
   94    current_prolog_flag(windows, true),
   95    !.
   96swipl_executable(path(swipl))