34
   35:- module(html_basics,
   36          [ hidden//2,                     37            form_input//2,                 38            form_submit//1,                39            n//2,                          40            nc//2,                         41            nc//3,                         42            odd_even_row//3,               43            sort_th//3,                    44            insert_html_file//1            45          ]).   46:- use_module(library(http/html_write)).   47:- use_module(library(sgml)).   48:- use_module(library(lists)).   49:- use_module(library(option)).   50:- use_module(library(occurs)).   51:- use_module(library(http/http_dispatch)).   52:- use_module(library(http/http_wrapper)).   53
   54:- html_meta((
   55        form_input(html, html, ?, ?),
   56        odd_even_row(+, -, html, ?, ?),
   57        sort_th(+, +, html, ?, ?))).
   62                 
   70hidden(Name, Value) -->
   71    html(input([ type(hidden),
   72                 name(Name),
   73                 value(Value)
   74               ])).
   84form_input(Label, Input) -->
   85    html(tr([ th(class(label), Label),
   86              td(Input)
   87            ])).
   88
   89
   90form_submit(Label) -->
   91    html(tr(class(buttons),
   92            [ th([align(right), colspan(2)],
   93                 input([ type(submit),
   94                         value(Label)
   95                       ]))
   96            ])).
   97
   98
   99                 
  116nc(Fmt, Value) -->
  117    nc(Fmt, Value, []).
  118
  119nc(Fmt, Value, Options) -->
  120    { class(Value, Class),
  121      merge_options(Options,
  122                    [ align(right),
  123                      class(Class)
  124                    ], Opts),
  125      number_html(Fmt, Value, HTML)
  126    },
  127    html(td(Opts, HTML)).
  128
  129class(Value, Class) :-
  130    (   integer(Value)
  131    ->  Class = int
  132    ;   float(Value)
  133    ->  Class = float
  134    ;   Class = value
  135    ).
  142odd_even_row(Row, Next, Content) -->
  143    { (   Row mod 2 =:= 0
  144      ->  Class = even
  145      ;   Class = odd
  146      ),
  147      Next is Row+1
  148    },
  149    html(tr(class(Class), Content)).
  166sort_th(Name, Name, Label) -->
  167    html(th(a([class(sorted)], Label))).
  168sort_th(Name, _By, Label) -->
  169    { http_current_request(Request),
  170      http_reload_with_parameters(Request, [sort_by(Name)], HREF)
  171    },
  172    html(th(a([href(HREF), class(resort)], Label))).
  173
  174
  175                 
  185n(Fmt, Value) -->
  186    { number_html(Fmt, Value, HTML) },
  187    html(HTML).
  188
  189number_html(human, Value, HTML) :-
  190    integer(Value),
  191    !,
  192    human_count(Value, HTML).
  193number_html(Fmt, Value, HTML) :-
  194    number(Value),
  195    !,
  196    HTML = Fmt-[Value].
  197number_html(_, Value, '~p'-[Value]).
  198
  199
  200human_count(Number, HTML) :-
  201    Number < 1024,
  202    !,
  203    HTML = '~d'-[Number].
  204human_count(Number, HTML) :-
  205    Number < 1024*1024,
  206    !,
  207    KB is Number/1024,
  208    digits(KB, N),
  209    HTML = '~*fK'-[N, KB].
  210human_count(Number, HTML) :-
  211    Number < 1024*1024*1024,
  212    !,
  213    MB is Number/(1024*1024),
  214    digits(MB, N),
  215    HTML = '~*fM'-[N, MB].
  216human_count(Number, HTML) :-
  217    TB is Number/(1024*1024*1024),
  218    digits(TB, N),
  219    HTML = '~*fG'-[N, TB].
  220
  221digits(Count, N) :-
  222    (   Count < 100
  223    ->  N = 1
  224    ;   N = 0
  225    ).
  226
  227
  228                 
  237insert_html_file(Alias) -->
  238    { absolute_file_name(Alias, Page, [access(read)]),
  239      load_html_file(Page, DOM),
  240      contains_term(element(body, _, Body), DOM),
  241      Style = element(style, _, _),
  242      findall(Style, sub_term(Style, DOM), Styles),
  243      append(Styles, Body, Content)
  244    },
  245    html(Content)
 
Simple Small HTML components
*/