3.21 The library(http/html_write) library
All Application Manual Name SummaryHelp

  • Documentation
    • Reference manual
    • Packages
      • SWI-Prolog HTTP support
        • The HTTP server libraries
          • The library(http/html_write) library
            • html//1
            • page//2
            • page//1
            • html_begin//1
            • html_end//1
            • Emitting HTML documents
            • Repositioning HTML for CSS and javascript links
            • Adding rules for html//1
            • Generating layout
            • Examples for using the HTML write library
            • Remarks on the library(http/html_write) library

3.21.5 Examples for using the HTML write library

In the following example we will generate a table of Prolog predicates we find from the SWI-Prolog help system based on a keyword. The primary database is defined by the predicate predicate/5 We will make hyperlinks for the predicates pointing to their documentation.

:- use_module(library(http/html_write)).
:- use_module(library(pldoc/man_index)).
:- use_module(library(uri)).

html_apropos(Kwd) :-
    findall(Pred, apropos_predicate(Kwd, Pred), Matches),
    phrase(apropos_page(Kwd, Matches), Tokens),
    print_html(Tokens).

%       emit page with title, header and table of matches

apropos_page(Kwd, Matches) -->
    page([ title(['Predicates for ', Kwd])
         ],
         [ h2(align(center),
              ['Predicates for ', Kwd]),
           table([ align(center),
                   border(1),
                   width('80%')
                 ],
                 [ tr([ th('Predicate'),
                        th('Summary')
                      ])
                 | \apropos_rows(Matches)
                 ])
         ]).

%       emit the rows for the body of the table.

apropos_rows([]) -->
    [].
apropos_rows([pred(Name, Arity, Summary)|T]) -->
    html([ tr([ td(\predref(Name/Arity)),
                td(em(Summary))
              ])
         ]),
    apropos_rows(T).

%!  predref(Name/Arity)//
%
%   Emit Name/Arity as a hyperlink to
%
%           /cgi-bin/plman?name=Name&arity=Arity

predref(Name/Arity) -->
    { uri_edit([search([name=Name,arity=Arity])],
               '/cgi-bin/plman', Href)
    },
    html(a(href(Href), [Name, /, Arity])).

%       Find predicates from a keyword.

apropos_predicate(Pattern, pred(Name, Arity, Summary)) :-
    man_object_property(Name/Arity, summary(Summary)),
    (   sub_atom_icasechk(Name, _, Pattern)
    ->  true
    ;   sub_atom_icasechk(Summary, _, Pattern)
    ).