Prev Next Up Home Keys Figs Search New

Using a Socket Library

Appeared in Volume 10/2, May 1997

Keywords: networking.


harvey@tr.unisys.com
Harvey Abramson
14th February 1997

Does anyone have a simple example of how to use the sockets library in Sicstus?


mary@amzi.com
Mary Kroening (Amzi! inc.)
14th February 1997

There are two simple examples (coded in Amzi! Prolog) at our Web site http://www.amzi.com/support.htm. You will also need to download the Sockets LSX (logic server extension).


inaf@inaf.com
Nathan Finstein
16th February 1997

Here is some code taken out of a larger application of mine. I've made a few changes to make the code sensible out of the context of the larger program.

This code is for the server only, and it assumes that the client follows certain rules. Also, it only handles one connection at a time.

:- use_module(library(sockets),
     [ socket/2,
       current_host/1,
       hostname_address/2,
       socket_bind/2,
       socket_listen/2,
       socket_accept/2,
       socket_select/5
     ]       ).

%% Execute inaftcp_init once at start of run to set up server.
inaftcp_init:-
    %% setup listener, listens for client connections
    socket('AF_INET',Listner),
    current_host(CurHost),
    socket_bind(Listner, 'AF_INET'(CurHost, Port)),
    socket_listen(Listner, 10),
    assert(inaf_socket(Listner)),
    %% write port and host name to file of well known name
    %% so that client will know with what port-host to connect
    ... some code here to instantiate PortHostFile with file name
    open(PortHostFile,write,PhStream),
    write(PhStream,Port), nl(PhStream),
    hostname_address(CurHost,CurAddr),
    write(PhStream,CurAddr), nl(PhStream),
    close(PhStream).


%% Server calls this goal first time it is to get info from a client.
%% We assume server gets info from client before writing to it
get_info(SomeInfo) :-<
    %% listener socket, see assert(inaf_socket(_)) above
    inaf_socket(Socket),   %% pick up listener socket
    socket_accept(Socket,SockStream),   %% accept client connection
    assert(inaf_stream(SockStream)),    %% remember this stream
    tcp_get_atom(SockStream, SomeInfo).

%% Assume get_info was already called for this connection.
%% socket_accept already done, get more info
get_more_info(SomeInfo) :-
    inaf_stream(SockStream),    %% see assert above
    tcp_get_atom(SockStream, SomeInfo).


tcp_get_atom(IStream, Atom) :-
    tcp_get_atom0(IStream, [], Atom).

%% Client and server agree that each chunk of data will be preceded by
%%  three bytes binary length code.
tcp_get_atom0(IStream, [HH,HL,LL], Atom) :-  %% have first 3 bytes
    !,
    Len is (((HH * 256) +HL) * 256) +LL,       %% convert to length
    tcp_get_atom1(Len, IStream, [], Atom).     %% get length bytes
tcp_get_atom0(IStream, Acc, Atom) :-
    socket_select([],_,off,[IStream],_),       %% wait for data to be ready
    get0(IStream,B),		%% get a length code byte
    append(Acc,[B],Acc0),
    tcp_get_atom0(IStream, Acc0, Atom).

tcp_get_atom1(0, _, Acc, Atom) :-	%% entire length of chunk read
    !,
    reverse(Acc,Chars),
    atom_chars(Atom,Chars).
tcp_get_atom1(Len, IStream, Acc, Atom) :-
    socket_select([],_,off,[IStream],_),    %% wait for data to be ready
    get0(IStream,C),                        %% get byte of data
    Len0 is Len -1,
    tcp_get_atom1(Len0, IStream, [C|Acc], Atom).


%% ---------------------------------------------

%% Server calls tcp_length to send data (in the form of
%%  a list of atoms) to the client.
%% Assume get_info called before this.
%% If server sends data before receiving, this program
%% would need some modification.
tcp_length([]) :- !.   %% nothing to send really, do nothing
tcp_length([H|T]) :-
   inaf_stream(SockStream),    %% see assert in get_info
   !,
   tcp_len_calc([H|T],0,[HH,HL,LL]),   %% length of data to send
   put(OStream,HH),		%% as 3 byt binary length code
   put(OStream,HL),
   put(OStream,LL),
   tcp_write_list([H|T], OStream),     %% now write the data to client
   flush_output(OStream).
tcp_length(NotList) :- tcp_length([NotList]).


tcp_write_list([], _).
tcp_write_list([H|T], OStream) :-
    write(OStream,H),
    tcp_write_list(T, OStream).

tcp_len_calc([],L,[HH,HL,LL]) :-
    HH is (L // 256) // 256,
    HL is (L // 256) mod 256,
    LL is L mod 256.
tcp_len_calc([H|T],N,ALen) :-
    atom_chars(H,HC),
    length(HC,LHC),
    N0 is N +LHC,
    tcp_len_calc(T,N0,ALen).


%% Call this to close the socket connection with a client.
%% Assume get_info was called before for this connection.
close_connection :-
    inaf_stream(SockStream),    %% see assert in get_info
    close(SockStream).

Prev Next Up Home Keys Figs Search New