1:- module(pwp,
2 [ pwp_files/2, 3 pwp_stream/3, 4 pwp_xml/3 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]).
320:- meta_predicate
321 pwp_files(:, +),
322 pwp_stream(:, +, +),
323 pwp_xml(:, -, +).
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)).
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
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 ; 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).
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).
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', -).
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).
507pwp_unite([], _).
508pwp_unite([Binding|Bindings], Context) :-
509 memberchk(Binding, Context),
510 !,
511 pwp_unite(Bindings, Context).
512pwp_unite([_=Value|_], _) :-
513 functor(Value, _, _).
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).
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)
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:
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.
write(Datum)
writeq(Datum)
write_canonical(Datum)
print(Datum)
print(Datum)
format(Format)
format(Format, Arguments)
The default value for pwp:how is text.
Examples:
where
msg.pl
containsThis 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.
staff.pl
definingstaff(NickName, FullName, Office, Phone, E_Mail_Address)
.status(NickName, full_time | part_time)
. We want to make a phone list of full time staff.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).