View source with raw comments or as raw
    1:- module(pwp,
    2          [ pwp_files/2,                % +FileIn, +FileOut
    3            pwp_stream/3,               % +StreamIn, +StreamOut, +Context
    4            pwp_xml/3                   % +DomIn, -DOMOut, +Context
    5          ]).    6:- autoload(library(lists),[append/3]).    7:- autoload(library(readutil),[read_file_to_codes/3]).    8:- autoload(library(sgml),[load_xml_file/2]).    9:- autoload(library(sgml_write),[xml_write/3]).

Prolog Well-formed Pages

PWP is an approach to server-side scripting using Prolog which is based on a simple key principle:

Especially when generating XML rather than HTML, this is such an obvious thing to do. We have many kinds of XML checking tools.

Having decided that the input should be well formed, that means NO NEW SYNTAX

None of the weird and horrible <% ... %> or whatever not-quite-XML stuff you see in other template systems, making checking so very hard (and therefore, making errors so distressingly common).

That in turns means that PWP "markup" must be based on special elements or special attributes. The fact that an XML parser must allow undeclared attributes on any element even when validating, but must not allow undeclared elements, suggests doing this through attributes. In particular, one should be able to take an existing DTD, such as an XHTML DTD, and just use that without modification. So the design reduces to

This description uses the following name space:

xmlns:pwp='http://www.cs.otago.ac.nz/staffpriv/ok/pwp.pl'

The attributes are

Here's what they mean. Each element is expanded in the context of a set of variable bindings. After expansion, if the tag is not mapped to '-', all attributes in the pwp: namespace are removed and the children elements are recursively expanded.

Examples:

  1. A "Hello World" like example
    <html
      xmlns:pwp="http://www.cs.otago.ac.nz/staffpriv/ok/pwp.pl"
      pwp:ask = "ensure_loaded(msg), once(msg(Greeting))">
      <head>
        <title pwp:use="Greeting"/>
      </head>
      <body>
        <p><span pwp:use="Greeting" pwp:tag='-'/></p>
      </body>
    </html>

    where msg.pl contains

    msg('Hello, World!').

    This example illustrates an important point. Prolog Well-Formed Pages provide NO way to physically incorporate Prolog clauses into a page template. Prolog clauses must be put in separate files which can be checked by a Prolog syntax checker, compiler, cross-referencer, &c WITHOUT the Prolog tool in question needing to know anything whatsoever about PWP. You load the files using pwp:ask on the root element.

  2. Binding some variables and using them
    <html
      xmlns:pwp="http://www.cs.otago.ac.nz/staffpriv/ok/pwp.pl">
      <head><title>Example 2</title></head>
      <body pwp:ask="Hello = 'Hello world', A = 20, B = 22">
        <h1 pwp:use="Hello"/>
        <p>The answer is <span pwp:use="C" pwp:ask="C is A+B"/>.</p>
      </body>
    </html>
  3. Making a table We are given a Prolog database staff.pl defining staff(NickName, FullName, Office, Phone, E_Mail_Address). status(NickName, full_time | part_time). We want to make a phone list of full time staff.
    <html
      xmlns:pwp="http://www.cs.otago.ac.nz/staffpriv/ok/pwp.pl"
      pwp:ask='ensure_loaded(staff)'>
      <head>
        <title>Phone list for Full-Time staff.</title>
      </head>
      <body>
        <h1>Phone list for Full-Time staff.</h1>
        <table
          pwp:ask = "setof(FullName-Phone,
                           N^O^E^(
                             status(N, full_time),
                             staff(N, FullName, O, Phone, E)
                           ),
                           Staff_List)">
          <tr><th>Name</th><th>Phone</th></tr>
          <tr pwp:ask="member(FullName-Phone, Staff_List)">
            <td pwp:use="FullName"/>
            <td pwp:use="Phone"/>
          </tr>
        </table>
      </body>
    </html>
  4. Substituting into an attribute Same data base as before, but now we want to make a mailing list page.
    <html
      xmlns:pwp="http://www.cs.otago.ac.nz/staffpriv/ok/pwp.pl"
      pwp:ask='ensure_loaded(staff)'>
      <head>
        <title>Phone list for Full-Time staff.</title>
      </head>
      <body>
        <h1>Phone list for Full-Time staff.</h1>
        <table
          pwp:ask = "setof(FullName-E_Mail,
                           N^O^P^staff(N, FullName, O, P, E_Mail),
                           Staff_List)">
          <tr><th>Name</th><th>Address</th></tr>
          <tr pwp:ask="member(FullName-E_Mail, Staff_List)">
            <td pwp:use="FullName"/>
            <td><a pwp:use="E_Mail"
                   pwp:att='$' href="mailto:$(E_Mail)$"/></td>
          </tr>
        </table>
      </body>
    </html>
  5. If-then-else effect A page that displays the value of the 'SHELL' environment variable if it has one, otherwise displays 'There is no default shell.'
    <html
      xmlns:pwp="http://www.cs.otago.ac.nz/staffpriv/ok/pwp.pl">
      <head><title>$SHELL</title></head>
      <body>
        <p pwp:ask="getenv('SHELL', Shell)"
        >The default shell is <span pwp:tag="-" pwp:use="Shell"/>.</p>
        <p pwp:ask="\+getenv('SHELL',_)">There is no default shell.</p>
      </body>
    </html>

    There is one other criterion for a good server-side template language:

    It should be possible to compile templates so as to eliminate most if not all interpretation overhead.

    This particular notation satisfies that criterion with the limitation that the conversion of a term to character data requires run-time traversal of terms (because the terms are not known until run time).

author
- Richard O'Keefe
To be done
- Support compilation of PWP input files */
  320:- meta_predicate
  321    pwp_files(:, +),
  322    pwp_stream(:, +, +),
  323    pwp_xml(:, -, +).
 pwp_files(:In:atom, +Out:atom) is det
loads an Xml document from the file named In, transforms it using the PWP attributes, and writes the transformed version to the new file named Out.
  332pwp_files(M:In, Out) :-
  333    load_xml_file(In, Contents),
  334    pwp_xml(M:Contents, Transformed, []),
  335    !,
  336    setup_call_cleanup(open(Out, write, Output),
  337                       xml_write(Output, Transformed, []),
  338                       close(Output)).
 pwp_stream(:Input:input_stream, +Output:output_stream, +Context:list) is det
Loads an Xml document from the given Input stream, transforms it using the PWP attributes, and writes the transformed version to the given Output stream. Context provides initial contextual variables and is a list of Name=Value.
  349pwp_stream(M:Input, Output, Context) :-
  350    load_xml_file(stream(Input), Contents),
  351    pwp_xml(M:Contents, Transformed, Context),
  352    !,
  353    xml_write(Output, Transformed, []).
  354
  355
  356/*  Recall that an XML term is one of
  357
  358        <atom>                  Character Data
  359        sdata(...)              SDATA (SGML only)
  360        ndata(...)              NDATA
  361        pi(...)                 Processing instruction
  362
  363        element(Name, [Att...], [Child...])
  364
  365            where Att is Attribute=Value and Child is an XML term.
  366
  367    We are only concerned with elements; all other XML terms are
  368    left alone.  I have given some thought to recognising
  369
  370        <?pwp ...Command...?>
  371
  372    processing instructions, executing the Command, and removing
  373    the processing instructions, as a debugging tool.  But this
  374    is a proof-of-concept implementation; debugging features can
  375    wait for The Real Thing.
  376*/
 pwp_xml(:In:list(xml), -Out:list(xml), +Context)
maps down a list of XML items, acting specially on elements and copying everything else unchanged, including white space. The Context is a list of 'VariableName'=CurrentValue bindings.
  386pwp_xml(M:In, Out, Context) :-
  387    pwp_list(In, Out, M, Context).
  388
  389pwp_list([], [], _, _).
  390pwp_list([element(Tag0,Atts0,Kids0)|Xs], Ys0, M, Context) :-
  391    !,
  392    pwp_attributes(Atts0, Ask, Use, How, Att, Tag1, Atts1),
  393    (   nonvar(Tag1), Tag1 \== '' -> Tag2 = Tag1
  394    ;   Tag2 = Tag0
  395    ),
  396    (   nonvar(Ask), Ask \== '', Ask \== 'true'
  397    ->  atom_to_term(Ask, Query, Bindings),
  398        pwp_unite(Bindings, Context, Context1),
  399        findall(Xml,
  400                ( M:Query,
  401                  pwp_element(Tag2, Atts1, Kids0, Use, How, Att,
  402                              M, Context1, Xml)),
  403                NewContent)
  404    ;   /* Ask is missing, empty, or true */
  405            pwp_element(Tag2, Atts1, Kids0, Use, How, Att,
  406                    M, Context, NewContent)
  407    ),
  408    pwp_attach(NewContent, Ys0, Ys1),
  409    pwp_list(Xs, Ys1, M, Context).
  410pwp_list([X|Xs], [X|Ys], M, Context) :-
  411    pwp_list(Xs, Ys, M, Context).
 pwp_attributes(+Atts0:list(atom=atom), -Ask:atom, -Use:atom, -How:atom, -Att:atom, -Tag:atom, -Atts1:list(atom=atom))
Walks down a list of AttributeName=ItsValue pairs, stripping out those whose AttributeName begins with the 'pwp:' prefix, and copying the rest to Atts1. Along the way, Ask/Use/How/Att/Tag are bound to the values of the pwp:ask/pwp:use/pwp:how/pwp:att/pwp:tag attributes, if any. At the end, any of these variables that are still unbound REMAIN unbound; they are not bound to default values.
  426pwp_attributes([], _, _, _, _, _, []).
  427pwp_attributes([AV|AVs], Ask, Use, How, Att, Tag, New_Atts1) :-
  428    AV = (Name=Value),
  429    (   pwp_attr(Name, PWPName)
  430    ->  (   pwp_attr(PWPName, Value, Ask, Use, How, Att, Tag)
  431        ->  New_Atts1 = New_Atts2
  432        ;   New_Atts1 = New_Atts2
  433        )
  434    ;   New_Atts1 = [AV|New_Atts2]
  435    ),
  436    pwp_attributes(AVs, Ask, Use, How, Att, Tag, New_Atts2).
  437
  438
  439pwp_attr(ask, Value, Value, _Use, _How, _Att, _Tag).
  440pwp_attr(use, Value, _Ask, Value, _How, _Att, _Tag).
  441pwp_attr(how, Value, _Ask, _Use, Value, _Att, _Tag).
  442pwp_attr(att, Value, _Ask, _Use, _How, Value, _Tag).
  443pwp_attr(tag, Value, _Ask, _Use, _How, _Att, Value).
 pwp_attr(+XMLAttr, -PWPLocal) is semidet
True if PWPLocal is the local name of a pwp:Local expression in XML. This predicate deals with the three different XML representations: the form is returned of XML namespace processing is not enabled. The second if it is enabled and the namespace is properly defined and the last if the namespace is not defined.
  454pwp_attr(Atom, PWP) :-
  455    atom(Atom),
  456    atom_concat('pwp:', PWP, Atom),
  457    !.
  458pwp_attr('http://www.cs.otago.ac.nz/staffpriv/ok/pwp.pl':PWP, PWP) :- !.
  459pwp_attr('pwp':PWP, PWP) :- !.
  460pwp_attr('xmlns:pwp', -).
 pwp_unite(+Bindings, +Context0, -Context:list(atom=any))
merges the new Bindings with the bindings in the outer Context0, constructing a new list of VariableName=CurrentValue bindings in Context1. This is only used when the CurrentValue parts of the new Bindings are known to be distinct new variables, so the Bindings cannot possibly conflict with any existing binding in Context0. This is O(|Bindings|.|Context0|), which is not that efficient, but since we do not expect there to be very many variables it doesn't matter much.
  473pwp_unite(Bindings, Context0, Context) :-
  474    pwp_unite(Bindings, Context0, Context0, Context).
  475
  476
  477pwp_unite([], _, Context, Context).
  478pwp_unite([Binding|Bindings], Context0, Context1, Context) :-
  479    memberchk(Binding, Context0),
  480    !,
  481    pwp_unite(Bindings, Context0, Context1, Context).
  482pwp_unite(['CONTEXT'=Context0|Bindings], Context0, Context1, Context) :-
  483    !,
  484    pwp_unite(Bindings, Context0, Context1, Context).
  485pwp_unite([Binding|Bindings], Context0, Context1, Context) :-
  486    pwp_unite(Bindings, Context0, [Binding|Context1], Context).
 pwp_unite(+Bindings, +Context0:list(atom=any))
looks up the bindings in Bindings in the outer Context0. This is only used for 'pwp:use' terms (and the related terms in $(...)$ attribute value substitutions), so that we have no interest in forming a new context. (If we did, we'd use pwp_unite/3 instead.) This is only used when the CurrentValue parts of the new Bindings are known to be distinct new variables, so the Bindings cannot possibly conflict with any existing binding in Context0. However, there could be new variables in Bindings, and that would cause problems. An XML term may not contain variables, and a term we want to convert to a list of character codes had better not contain variables either. One approach would be to just bind such variables to something, another is to throw some kind of exception. For the moment we call functor/3 so as to get an instantiation error.
  507pwp_unite([], _).
  508pwp_unite([Binding|Bindings], Context) :-
  509    memberchk(Binding, Context),
  510    !,
  511    pwp_unite(Bindings, Context).
  512pwp_unite([_=Value|_], _) :-
  513    functor(Value, _, _).
 pwp_attach(+Tree, ?Ys0:list(xml), ?Ys:list(xml))
is a combination of "flatten" and "append". It unifies Ys0\Ys with the result of flattening Tree.
  520pwp_attach([], Ys, Ys) :- !.
  521pwp_attach([X|Xs], Ys0, Ys) :-
  522    !,
  523    pwp_attach(X, Ys0, Ys1),
  524    pwp_attach(Xs, Ys1, Ys).
  525pwp_attach(X, [X|Ys], Ys).
  526
  527
  528
  529pwp_element('-', _, Kids, Use, How, _, M, Context, Xml) :-
  530    !,
  531    pwp_use(Use, How, Kids, M, Context, Xml).
  532pwp_element(Tag, Atts, [Value], Use, How, Magic, M, Context,
  533            element(Tag,Atts1,Kids1)) :-
  534    verbatim_element(Tag), nonvar(Magic), atomic(Value),
  535    !,
  537        
  538        pwp_substitute([cdata=Value|Atts], Magic, Context,
  539                   [cdata=Value1|Atts1]),
  540    pwp_use(Use, How, [Value1], M, Context, Kids1)
  540.
  541pwp_element(Tag, Atts, Kids, Use, How, Magic, M, Context,
  542            element(Tag,Atts1,Kids1)) :-
  543    (   nonvar(Magic)
  544    ->  pwp_substitute(Atts, Magic, Context, Atts1)
  545    ;   Atts1 = Atts
  546    ),
  547    pwp_use(Use, How, Kids, M, Context, Kids1).
  548
  549pwp_use('', _, Kids, M, Context, Kids1) :-
  550    !,
  551    pwp_list(Kids, Kids1, M, Context).
  552pwp_use(Use, How, _, M, Context, Kids1) :-
  553    atom_to_term(Use, Term, Bindings),
  554    pwp_unite(Bindings, Context),
  555    pwp_how(How, Term, M, Context, Kids1).
  556
  557pwp_how('text', Term, _,_, [CData]) :-
  558    !,
  559    pwp_use_codes(Term, Codes, []),
  560    atom_codes(CData, Codes).
  561pwp_how('xml', Term, _,_, Kids1) :-
  562    (   Term == []   -> Kids1 = Term
  563    ;   Term = [_|_] -> Kids1 = Term
  564    ;                   Kids1 = [Term]
  565    ).
  566pwp_how('text-file', Term, _,_, [CData]) :-
  567    pwp_use_codes(Term, Codes, []),
  568    atom_codes(FileName, Codes),
  569    read_file_to_codes(FileName, FileCodes, []),
  570    atom_codes(CData, FileCodes).
  571pwp_how('xml-file', Term, _,_, Kids1) :-
  572    pwp_use_codes(Term, Codes, []),
  573    atom_codes(FileName, Codes),
  574    load_xml_file(FileName, Kids1).
  575pwp_how('pwp-file', Term, M,Context, Kids1) :-
  576    pwp_use_codes(Term, Codes, []),
  577    atom_codes(FileName, Codes),
  578    ( memberchk('SCRIPT_DIRECTORY'=ScriptDir,Context) -> true
  579    ; ScriptDir='.'
  580    ),
  581    absolute_file_name(FileName, PathName, [relative_to(ScriptDir)]),
  582    load_xml_file(PathName, Kids0),
  583    pwp_xml(M:Kids0, Kids1, Context),
  584    !.
  585
  586
  587pwp_substitute([], _, _, []).
  588pwp_substitute([AV|AVs], Magic, Context, NewAvs) :-
  589    AV = (Name = Value),
  590    (   sub_atom(Value, _, _, _, Magic)
  591    ->  char_code(Magic, C),
  592        atom_codes(Value, Codes),
  593        pwp_split(Codes, C, B0, T0, A0, Type),
  594        !,
  595        (   pwp_substitute(B0, T0, A0, C, Context, V, Type)
  596        ->  NewAvs = [AV1|Atts1],
  597            atom_codes(New_Value, V),
  598            AV1 = (Name = New_Value)
  599        ;   Type == existence->
  600            NewAvs = Atts1
  601        ),
  602        pwp_substitute(AVs, Magic, Context, Atts1)
  603    ).
  604pwp_substitute([AV|AVs], Magic, Context, [AV|Atts1]) :-
  605    pwp_substitute(AVs, Magic, Context, Atts1).
  606
  607
  608pwp_substitute(B0, T0, A0, C, Context, V0, Type) :-
  609    append(B0, V1, V0),
  610    atom_codes(Atom, T0),
  611    atom_to_term(Atom, Term, Bindings),
  612    pwp_unite(Bindings, Context, _),
  613    (   Type == value
  614    ->  pwp_use_codes(Term, V1, V2)
  615    ;   catch(Term, _, fail),
  616        V2 = V1
  617    ),
  618    (   pwp_split(A0, C, B1, T1, A1, T2)
  619    ->  pwp_substitute(B1, T1, A1, C, Context, V2, T2)
  620    ;   V2 = A0
  621    ).
  622
  623
  624pwp_split(Codes, C, Before, Text, After, Type) :-
  625    append(Before, [C,C1|Rest], Codes),
  626    (   C1 == 0'(
  627    ->  Type = value,
  628        C2 = 0')
  629    ;   C1 == 0'[,
  630        Type = existence,
  631        C2 = 0']
  632    ),
  633    append(Text,   [C2,C|After], Rest),
  634    !.
  635
  636pwp_use_codes(format(Format), S0, S) :-
  637    !,
  638    pwp_format(Format, [], S0, S).
  639pwp_use_codes(format(Format,Args), S0, S) :-
  640    !,
  641    pwp_format(Format, Args, S0, S).
  642pwp_use_codes(write_canonical(Datum), S0, S) :-
  643    !,
  644    pwp_format('~k', [Datum], S0, S).
  645pwp_use_codes(print(Datum), S0, S) :-
  646    !,
  647    pwp_format('~p', [Datum], S0, S).
  648pwp_use_codes(writeq(Datum), S0, S) :-
  649    !,
  650    pwp_format('~q', [Datum], S0, S).
  651pwp_use_codes(write(Datum), S0, S) :-
  652    !,
  653    pwp_format('~w', [Datum], S0, S).
  654pwp_use_codes(Atomic, S0, S) :-
  655    atomic(Atomic),
  656    !,
  657    (   number(Atomic) -> number_codes(Atomic, Codes)
  658    ;   atom(Atomic)   -> atom_codes(Atomic, Codes)
  659    ;   string(Atomic) -> string_codes(Atomic, Codes)
  660    ;   pwp_format('~w', [Atomic], S0, S)
  661    ),
  662    append(Codes, S, S0).
  663pwp_use_codes([X|Xs], S0, S) :-
  664    pwp_is_codes([X|Xs]),
  665    !,
  666    append([X|Xs], S, S0).
  667pwp_use_codes([X|Xs], S0, S) :-
  668    !,
  669    pwp_use_codes(Xs, X, S0, S).
  670pwp_use_codes(Compound, S0, S) :-
  671    Compound =.. [_,X|Xs],
  672    pwp_use_codes(Xs, X, S0, S).
  673
  674
  675
  676pwp_use_codes([], X, S0, S) :-
  677    !,
  678    pwp_use_codes(X, S0, S).
  679pwp_use_codes([Y|Ys], X, S0, S) :-
  680    pwp_use_codes(X, S0, S1),
  681    pwp_use_codes(Ys, Y, S1, S).
 pwp_is_codes(+String:any)
is true when String is a list of integers and each of those integers is a possible Unicode value (in the range U+0000..U+10FFFF). Back in the days of ISO Latin 1 we would have checked for 0..255, and way back in the days of ASCII for 0..127. Yes, there are more than a million possible characters in Unicode; currently about 100 000 of them are in use.
  694pwp_is_codes([]).
  695pwp_is_codes([C|Cs]) :-
  696    integer(C), C >= 0, C =< 0x10FFFF,
  697    pwp_is_codes(Cs).
  698
  699pwp_format(Format, Arguments, S0, S) :-
  700    format(codes(S0, S), Format, Arguments).
  701
  702
  703verbatim_element(script).
  704verbatim_element(style)