Porting PiLLoW to Quintus Prolog: Difference between revisions

From This Prolog Life
Jump to navigation Jump to search
(Remove broken syntax highlighting)
Line 22: Line 22:




<syntaxhighlight lang="prolog">
<pre class="prolog">
:- use_module(library(tcp)).
:- use_module(library(tcp)).
:- use_module(library(socketio)).
:- use_module(library(socketio)).
Line 68: Line 68:


:- use_module( library(environ), [environ/2] ).
:- use_module( library(environ), [environ/2] ).
</syntaxhighlight>
</pre>
The ISO Prolog predicates used in PiLLoW can be mapped to equivalent Quintus built-in predicates.
The ISO Prolog predicates used in PiLLoW can be mapped to equivalent Quintus built-in predicates.


<syntaxhighlight lang="prolog">flush_output :-
<pre class="prolog">flush_output :-
     ttyflush.
     ttyflush.


Line 93: Line 93:


put_code( Code ) :-
put_code( Code ) :-
     put( Code ).</syntaxhighlight>
     put( Code ).</pre>
Similarly, some library predicates are not defined/defined differently in Quintus:
Similarly, some library predicates are not defined/defined differently in Quintus:


<syntaxhighlight lang="prolog">atom_concat( A, B, AB ) :-
<pre class="prolog">atom_concat( A, B, AB ) :-
     name( A, AS ),
     name( A, AS ),
     name( B, BS ),
     name( B, BS ),
Line 105: Line 105:
     environ( Var, QueryString ).
     environ( Var, QueryString ).


:- use_module( library(environ), [environ/2] ).</syntaxhighlight>
:- use_module( library(environ), [environ/2] ).</pre>


==Pillow 1.0==
==Pillow 1.0==

Revision as of 18:57, 5 January 2017

Porting PiLLoW to Quintus Prolog 3.X

The PiLLoW library provides predicates for developing HTTP client and server applications.

For client applications, it provides mechanisms to retrieve HTML files and to parse HTML into useful Prolog terms.

For server applications, it provides a predicate to access CGI query parameters, so that a Prolog application can be used to handle form input directly i.e. without additional scripting. Additionally, HTML parsing supports the reverse translation of terms into HTML, so that forms can be generated.

PiLLoW 1.1

If you want to port PiLLoW 1.1 to Quintus Prolog, the following notes may be of use.

http_transaction/5

must be rewritten to use the Quintus tcp and socketio libraries.

http_transaction(+Host, +Port, +Request, +Timeout, -Response)

Sends an HTTP Request to an HTTP server Host:Port and returns the resulting message in Response.

Timeout defines the maximum number of seconds to wait for a response.


:- use_module(library(tcp)).
:- use_module(library(socketio)).
:- use_module(library(date), [now/1]).

http_transaction( Host, Port, Request, Timeout, Response ) :-
    tcp:connect( Host, Port, Socket ),
    Socket >= 0,  % Fail if connect error
    socket_io_open_output( Socket, Ocode ),
    stream_code( OStream, Ocode ),
    write_string( OStream, Request ),
    close( OStream ),
    socket_io_open_input( Socket, Icode ),
    stream_code( IStream, Icode ),
    now( Now ),
    http_transaction1( Now, Socket, IStream, Timeout, Response ),
    close( IStream ),
    tcp:tcp_shutdown( Socket, _Status ),
    Response \== timeout.

http_transaction1( Now, Socket, IStream, Timeout, Response ) :-
    tcp:tcp_select( 0, Timeout, FD, Status ),
    http_transaction2( Status, Now, Socket, FD, IStream, Timeout, Response ).

http_transaction2( 1, Then, Socket, FD, IStream, Timeout, Response ) :-
    ( Socket == FD ->
        stream_to_string( IStream, Response )
    ; otherwise ->
        now( Now ),
        Elapsed is Now - Then,
        ( Elapsed < Timeout ->
            Timeout1 is Timeout - Elapsed,
            http_transaction1( Now, Socket, IStream, Timeout1, Response )
        ; otherwise ->
            Response = timeout
        )
    ).
http_transaction2( 0, _Then, _Socket, _FD, _IStream, _Timeout, timeout ).
http_transaction2( -1, _Then, Socket, _FD, IStream, Timeout, _Response ) :-
    raise_exception( socket_error(Socket, IStream, Timeout) ).

getenvstr( Var, Chars ) :-
    environ( Var, Atom ),
    atom_chars( Atom, Chars ).

:- use_module( library(environ), [environ/2] ).

The ISO Prolog predicates used in PiLLoW can be mapped to equivalent Quintus built-in predicates.

flush_output :-
    ttyflush.

atom_codes( Atom, Codes ) :-
    atom_chars( Atom, Codes ).

catch( Goal, Error, Action ) :-
    on_exception( Error, Goal, Action ).

get_code( Code ) :-
    get0( Code ).

get_code( Stream, Code ) :-
    get0( Stream, Code ).

include( File ) :-
    ensure_loaded( File ).

number_codes( Number, Codes ) :-
    number_chars( Number, Codes ).

put_code( Code ) :-
    put( Code ).

Similarly, some library predicates are not defined/defined differently in Quintus:

atom_concat( A, B, AB ) :-
    name( A, AS ),
    name( B, BS ),
    append( AS, BS, ABS ),
    atom_chars( AB, ABS ).

getenv( Var, QueryString ) :-
    environ( Var, QueryString ).

:- use_module( library(environ), [environ/2] ).

Pillow 1.0

I have ported PiLLoW 1.0 to use the Quintus Prolog 3.X libraries, and made it available as a 260Kb Zip file. It is offered here as free, unsupported source code, for which the author accepts no liability whatsoever.

Note: The parsing of "multipart" form data on win32 can produce errors, when binary files are submitted, e.g. sending image files as part of the form input. This is because the default for "stdin" on win32 is "text".