:- use_module(library(sockets)). :- use_module(library(lists)). :- use_module(library(format)). :- use_module(library(charsio)). :- use_module(library(dcgs)). :- use_module(library(iso_ext)). :- use_module(library(dif)). :- use_module(library(pio)). :- use_module(library(reif)). server(Port) :- server('127.0.0.1', Port). server(IP, Port) :- socket_server_open(IP:Port, Socket), accept_loop(Socket). accept_loop(Socket) :- format("waiting for connections...~n", []), setup_call_cleanup(socket_server_accept(Socket, Client, Stream, [type(binary)]), ( format("handling client ~q...~n", [Client]), request_response(Stream) ), close(Stream)), accept_loop(Socket). request_response(Stream) :- read_line_to_chars(Stream, Chars, []), format("request is ~s", [Chars]), chars_base64(Chars, Response, []), catch(format(Stream, "~s", [Response]), Err, portray_clause(caught(Err))). /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ?- server(6011). - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */