1:- module(
    2       da_protocol,
    3       [
    4           dap_read/2,
    5           dap_error/5,
    6           dap_response/4,
    7           dap_response/5,
    8           dap_response/7,
    9           dap_request/3,
   10           dap_request/4,
   11           dap_event/3,
   12           dap_event/4,
   13           dap_message/4
   14       ]
   15   ).   16
   17:- use_module(library(http/json)).   18:- use_module(library(settings)).   19
   20
   21dap_read(In, Message) :-
   22    read_line_to_string(In, Line),
   23    sub_string(Line, 16, _, 0, ContentLengthString), % string_length("Content-Length: ", 16).
   24    number_string(ContentLength, ContentLengthString),
   25    read_line_to_string(In, ""),
   26    read_string(In, ContentLength, Serialized),
   27    atom_json_dict(Serialized, Message, []).
   28
   29dap_error(Out, Seq, RequestSeq, Command, Message) :-
   30    dap_response(Out, Seq, RequestSeq, Command, false, Message, null).
   31
   32dap_response(Out, Seq, RequestSeq, Command) :-
   33    dap_response(Out, Seq, RequestSeq, Command, null).
   34
   35dap_response(Out, Seq, RequestSeq, Command, Body) :-
   36    dap_response(Out, Seq, RequestSeq, Command, true, null, Body).
   37
   38dap_response(Out, Seq, RequestSeq, Command, Success, Message, Body) :-
   39    dap_message(Out, Seq, "response", _{ request_seq: RequestSeq,
   40                                         success    : Success,
   41                                         command    : Command,
   42                                         message    : Message,
   43                                         body       : Body
   44                                       }
   45               ).
   46
   47dap_event(Out, Seq, Event) :-
   48    dap_event(Out, Seq, Event, null).
   49
   50dap_event(Out, Seq, Event, Body) :-
   51    dap_message(Out, Seq, "event", _{ event: Event,
   52                                      body : Body
   53                                    }
   54               ).
   55
   56dap_request(Out, Seq, Command) :-
   57    dap_request(Out, Seq, Command, null).
   58
   59dap_request(Out, Seq, Command, Arguments) :-
   60    dap_message(Out, Seq, "request", _{ command : Command,
   61                                        arguments : Arguments
   62                                      }
   63               ).
   64
   65dap_message(Out, Seq, Type, Rest) :-
   66    put_dict(_{ seq : Seq,
   67                type: Type
   68              },
   69             Rest,
   70             Message
   71            ),
   72    atom_json_dict(Serialized, Message, []),
   73    dap_serialized_content(Out, Serialized).
   74
   75dap_serialized_content(Out, Content) :-
   76    string_length(Content, ContentLength),
   77    format(Out, "Content-Length: ~w\r\n\r\n", [ContentLength]),
   78    format(Out, "~w", Content)