1:- module(lsp_parser, [lsp_request//1]).

LSP Parser

Module for parsing the body & headers from an LSP client.

author
- James Cash */
    9:- use_module(library(assoc), [list_to_assoc/2, get_assoc/3]).   10:- use_module(library(codesio), [open_codes_stream/2]).   11:- use_module(library(dcg/basics), [string_without//2]).   12:- use_module(library(http/json), [json_read_dict/3]).   13
   14header(Key-Value) -->
   15    string_without(":", KeyC), ": ", string_without("\r", ValueC),
   16    { string_codes(Key, KeyC), string_codes(Value, ValueC) }.
   17
   18headers([Header]) -->
   19    header(Header), "\r\n\r\n", !.
   20headers([Header|Headers]) -->
   21    header(Header), "\r\n",
   22    headers(Headers).
   23
   24json_chars(0, []) --> [].
   25json_chars(N, [C|Cs]) --> [C], { succ(Nn, N) }, json_chars(Nn, Cs).
   26
   27lsp_request(_{headers: Headers, body: Body}) -->
   28    headers(HeadersList),
   29    { list_to_assoc(HeadersList, Headers),
   30      get_assoc("Content-Length", Headers, LengthS),
   31      number_string(Length, LengthS) },
   32    json_chars(Length, JsonCodes),
   33    { ground(JsonCodes),
   34      open_codes_stream(JsonCodes, JsonStream),
   35      json_read_dict(JsonStream, Body, []) }