1:- module(lsp_parser, [lsp_request//1]).
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).
The HTTP headers are parsed into an assoc tree which maps
strings to strings. The body of the request is parsed into a dict according
to json_read_dict/3. The headers list must include a Content-Length
header.
?- phrase(lsp_request(Req), `Content-Length: 7\r\n\r\n{"x":1}`).
Req = _{body:_{x:1}, headers:t("Content-Length", "7", -, t, t)}.
40lsp_request(_{headers: Headers, body: Body}) -->
41 headers(HeadersList),
42 { list_to_assoc(HeadersList, Headers),
43 get_assoc("Content-Length", Headers, LengthS),
44 number_string(Length, LengthS),
45 length(JsonCodes, Length) },
46 ,
47 { ground(JsonCodes),
48 open_codes_stream(JsonCodes, JsonStream),
49 json_read_dict(JsonStream, Body, []) }
LSP Parser
Module for parsing the body & headers from an LSP client.