34
   35:- module(format_style,
   36          [ element_css/3,                37            css_block_options/5,          38            css_inline_options/3,         39            attrs_classes/2,              40            style_css_attrs/2             41          ]).   42:- autoload(library(apply),[maplist/3,convlist/3]).   43:- autoload(library(lists),[append/2,list_to_set/2]).   44:- autoload(library(option),[option/3]).   45
   46:- multifile
   47    html_text:style/3.
   51element_css(El, Attrs, CSS) :-
   52    findall(CSSs, applicable_style(El, Attrs, CSSs), CssList),
   53    CssList \== [],
   54    append(CssList, CSS0),
   55    list_to_set(CSS0, CSS).
   56
   57applicable_style(_, Attrs, CSS) :-
   58    memberchk(style=Style, Attrs),
   59    style_css_attrs(Style, CSS0),
   60    include(text_style, CSS0, CSS).
   61applicable_style(El, Attrs, CSS) :-
   62    html_text:style(El, Cond, CSS),
   63    (   eval(Cond, Attrs)
   64    ->  true
   65    ).
   66
   67eval(true, _).
   68eval(class(Class), Attrs) :-
   69    attrs_classes(Attrs, Classes),
   70    memberchk(Class, Classes).
   71
   72attrs_classes(Attrs, Classes) :-
   73    memberchk(class=Spec, Attrs),
   74    split_string(Spec, " \t\r\n", " \t\r\n", ClassStrings),
   75    maplist(atom_string, Classes, ClassStrings).
   83style_css_attrs(Style, CSS) :-
   84    split_string(Style, ";", " \t\r\n", Parts),
   85    convlist(style_css_attr, Parts, CSS).
   86
   87style_css_attr(Style, CSS) :-
   88    split_string(Style, ":", " \t\r\n", [NameS,ValueS]),
   89    atom_string(Name, NameS),
   90    atom_string(Value, ValueS),
   91    CSS =.. [Name,Value].
   92
   93text_style(float(right)).
   99css_block_options(CSS, Top0-Bottom0, Top-Bottom, ParOptions, Style) :-
  100    option(margin_top(Top), CSS, Top0),
  101    option(margin_bottom(Bottom), CSS, Bottom0),
  102    convlist(par_option, CSS, ParOptions),
  103    convlist(font_style, CSS, Style).
  104
  105par_option(text_align(Align),   text_align(Align)).
  106par_option(margin_left(Align),  margin_left(Align)).
  107par_option(margin_right(Align), margin_right(Align)).
  108
  109font_style(font_weight(bold),     bold).
  110font_style(font_weight(normal),   normal).
  111font_style(color(BC),             hfg(C)) :- atom_concat(bright_, C, BC).
  112font_style(color(C),              fg(C)).
  113font_style(background(BC),        hbg(C)) :- atom_concat(bright_, C, BC).
  114font_style(background(C),         bg(C)).
  115font_style(text_decoration(none), underline(false)).
  121css_inline_options(CSS, Left-Right, Style) :-
  122    option(margin_left(Left), CSS, 0),
  123    option(margin_right(Right), CSS, 0),
  124    convlist(inline_style, CSS, Style).
  125
  126inline_style(CSS, Style) :-
  127    font_style(CSS, Style),
  128    !.
  129inline_style(float(right),          float(right))