1:- module(css_write, [css//1,
    2                      write_css/2]).    3
    4:- use_module(library(apply), [foldl/4, partition/4]).    5:- use_module(library(lists), [append/3, last/2]).    6:- use_module(library(list_util), [take/3]).    7:- use_module(library(dcg/high_order), [ sequence//2,
    8                                         sequence//5
    9                                       ]).   10:- use_module(library(yall)).   11:- use_module(library(debug)).   12
   13ensure_list(X, X) :- is_list(X), !.
   14ensure_list(X, [X]).
   15
   16butlast(Ls, Lss) :-
   17    length(Ls, L),
   18    ButL is L - 1,
   19    take(ButL, Ls, Lss).
   20
   21% Copied from list_util:split/3, but addressing
   22% https://github.com/mndrix/list_util/issues/30
   23% which makes joining strings that already have spaces in them fail
   24split([], _, [[]]) :-
   25    !.  % optimization
   26split([Div|T], Div, [[]|Rest]) :-
   27    split(T, Div, Rest),  % implies: dif(Rest, [])
   28    !.  % optimization
   29split([H|T], Div, [[H|First]|Rest]) :-
   31    split(T, Div, [First|Rest])
   31.
   32
 css(+Content)// is det
Generate CSS string from Content.
   36css(Content) -->
   37    css_children(Content), { ! }.
   38
   39css_children([]) --> [], { ! }.
   40css_children([Thing|Things]) -->
   41    css_child(Thing), css_children(Things).
   42
   43css_child(\(Reference)) -->
   44   call(Reference).
   45css_child('@import'(Arg)) --> !, ['@import'(Arg)].
   46css_child('@media'(Query, Children)) -->
   47    !,
   48    [begin_media(Query)],
   49    { ensure_list(Children, Children_) },
   50    css_children(Children_),
   51    [end_media].
   52css_child('@keyframes'(Name, Frames)) -->
   53    !,
   54    { ensure_list(Frames, Frames_),
   55      text_to_string(Name, NameStr),
   56      string_codes(NameStr, NameCodes) },
   57    [begin_animation(NameCodes)],
   58    keyframes(Frames_),
   59    [end_animation].
   60css_child('@supports'(Conditions, Children)) -->
   61    !,
   62    { ensure_list(Children, Children_) },
   63    [begin_supports(Conditions)],
   64    css_children(Children_),
   65    [end_supports].
   66css_child(Thing) -->
   67    { Thing =.. [Sel,StyleOrStyles],
   68      ensure_list(StyleOrStyles, Styles),
   69      text_to_string(Sel, SelStr),
   70      string_codes(SelStr, SelStrCodes) },
   71    [begin_styles(SelStrCodes)],
   72    css_styles(Styles),
   73    [end_styles(SelStrCodes)].
   74css_child(Thing) -->
   75    { Thing =.. [Sel,Styles,Children],
   76      ThingStyles =.. [Sel,Styles] },
   77    css_child(ThingStyles),
   78    { text_to_string(Sel, SelStr),
   79      string_codes(SelStr, SelStrCodes),
   80      ensure_list(Children, Children_) },
   81    [begin_ctx(SelStrCodes)],
   82    css_children(Children_),
   83    [end_ctx(SelStrCodes)].
   84
   85css_styles([]) --> [], { ! }.
   86css_styles([Style|Styles]) -->
   87    css_style(Style), css_styles(Styles).
   88
   89css_style(Style) -->
   90    { Style =.. [Attr, Value],
   91      atom_codes(Attr, AttrCodes),
   92      atom_codes(Value, ValueCodes) },
   93    [style(AttrCodes, ValueCodes)].
   94
   95:- meta_predicate write_css(//, -).
 write_css(+Css, -String) is semidet
True when String is the Css DCG written out as a string.
   99write_css(Css, String) :-
  100    phrase(Css, Elements0),
  101    partition(['@import'(_)]>>true,
  102              Elements0, ImportRules, Elements),
  103    phrase(import_rules(ImportRules), Codes, Codes1),
  104    phrase(css_tokens([], Elements), Codes1), !,
  105    string_codes(String, Codes).
  106
  107import_rules(['@import'(Arg)|Rest]) -->
  108    "@import ",
  109    { ensure_list(Arg, ArgL) }, import_args(ArgL),
  110    ";\n",
  111    import_rules(Rest).
  112import_rules([]) --> [].
  113
  114import_args([url(URL)|Rest]) -->
  115    !,
  116    "url(\"",
  117    { text_to_string(URL, URLStr),
  118      string_codes(URLStr, URLCodes) },
  119    URLCodes, "\")",
  120    import_args(Rest).
  121import_args([X|Rest]) -->
  122    " ",
  123    { text_to_string(X, Str),
  124      string_codes(Str, Codes) },
  125    Codes,
  126    import_args(Rest).
  127import_args([]) --> [].
  128
  129css_tokens(_, []) --> [].
  130css_tokens(Ctx, [begin_styles(S),end_styles(S)|Next]) -->
  131    css_tokens(Ctx, Next), { ! }.
  132css_tokens(Ctx, [begin_styles(SelCodes)|Next]) -->
  133    { append(Ctx, [SelCodes], CombinedCtx),
  134      collapse_ampersands(CombinedCtx, DerivedSels),
  135      split(DerivedSel, 0' , DerivedSels) },
  136    DerivedSel, " {\n", css_tokens(Ctx, Next).
  137css_tokens(Ctx, [end_styles(_)|Next]) -->
  138    "}\n", css_tokens(Ctx, Next).
  139css_tokens(Ctx, [style(Prop, Val)|Next]) -->
  140    "  ", Prop, ": ", Val, ";\n",
  141    css_tokens(Ctx, Next).
  142css_tokens(Ctx, [begin_ctx(AddCtx)|Next]) -->
  143    { append(Ctx, [AddCtx], NewCtx) },
  144    css_tokens(NewCtx, Next).
  145css_tokens(Ctx, [end_ctx(_)|Next]) -->
  146    { butlast(Ctx, NewCtx) },
  147    css_tokens(NewCtx, Next).
  148css_tokens(Ctx, [begin_media(Query)|Next]) -->
  149    "@media ", media_query(Query), " {\n",
  150    css_tokens(Ctx, Next).
  151css_tokens(Ctx, [end_media|Next]) -->
  152    "}\n",
  153    css_tokens(Ctx, Next).
  154css_tokens(Ctx, [begin_animation(Name)|Next]) -->
  155    "@keyframes ", Name, " {\n",
  156    css_tokens(Ctx, Next).
  157css_tokens(Ctx, [begin_keyframe(Pos)|Next]) -->
  158    "  ", Pos, " {\n",
  159    css_tokens(Ctx, Next).
  160css_tokens(Ctx, [begin_supports(Conditions)|Next]) -->
  161    "@supports ", supports_conditions(Conditions), " {\n",
  162    css_tokens(Ctx, Next).
  163css_tokens(Ctx, [end_keyframe|Next]) -->
  164    "  }\n",
  165    css_tokens(Ctx, Next).
  166css_tokens(Ctx, [end_animation|Next]) -->
  167    "}\n",
  168    css_tokens(Ctx, Next).
  169css_tokens(Ctx, [end_supports|Next]) -->
  170    "}\n",
  171    css_tokens(Ctx, Next).
  172
  173media_query(and(Qs)) -->
  174    !, media_query_ands(Qs).
  175media_query(Elt) -->
  176    media_query_elt(Elt).
  177
  178media_query_ands([A,B|Rest]) -->
  179    media_query(A),
  180    " and ",
  181    media_query_ands([B|Rest]).
  182media_query_ands([E]) -->
  183    media_query(E).
  184media_query_ands([]) --> [].
  185
  186media_query_elt(max_width(W)) -->
  187    !,
  188    { text_to_string(W, S),
  189      string_codes(S, Cs) },
  190    "(max-width: ",  Cs, ")".
  191media_query_elt(min_width(W)) -->
  192    !,
  193    { text_to_string(W, S),
  194      string_codes(S, Cs) },
  195    "(min-width: ",  Cs, ")".
  196media_query_elt(color_scheme(Theme)) -->
  197    !,
  198    { text_to_string(Theme, S),
  199      string_codes(S, Cs) },
  200    "(prefers-color-scheme: ",  Cs, ")".
  201media_query_elt(motion(Type)) -->
  202    !,
  203    { text_to_string(Type, S),
  204      string_codes(S, Cs) },
  205    "(prefers-reduced-motion: ",  Cs, ")".
  206media_query_elt(X) -->
  207    { text_to_string(X, S),
  208      string_codes(S, Cs) },
  209    Cs.
  210
  211collapse_ampersands(Sels, CollapsedSels) :-
  212    foldl(add_selector, Sels, [], CollapsedSels).
  213
  214add_selector([0'&|SubSel], Ctx, NewCtx) :-
  215    last(Ctx, Parent),
  216    append(Parent, SubSel, NewSel),
  217    butlast(Ctx, CtxHead),
  218    append(CtxHead, [NewSel], NewCtx), !.
  219add_selector(SubSel, Ctx, NewCtx) :-
  220    append(Ctx, [SubSel], NewCtx).
  221
  222keyframes([]) --> [].
  223keyframes([Frame|Frames]) -->
  224    { Frame =.. [FramePos|Styles],
  225      text_to_string(FramePos, FramePosString),
  226      string_codes(FramePosString, FramePosCodes) },
  227    [begin_keyframe(FramePosCodes)],
  228    css_styles(Styles),
  229    [end_keyframe],
  230    keyframes(Frames).
  231
  232supports_conditions([]) --> [].
  233supports_conditions(not(Rules)) -->
  234    "not ", supports_conditions(Rules).
  235supports_conditions(and(Rules)) -->
  236    sequence("(", supports_conditions, " and ", ")", Rules).
  237supports_conditions(or(Rules)) -->
  238    sequence("(", supports_conditions, " or ", ")", Rules).
  239supports_conditions(Rules) -->
  240    { ensure_list(Rules, Rules_) },
  241    sequence(supports_condition, Rules_).
  242
  243supports_condition(Rule) -->
  244    { string(Rule), !,
  245      string_codes(Rule, RuleC) },
  246    "(", RuleC, ")".
  247supports_condition(Rule) -->
  248    { Rule =.. [Prop, Value],
  249      string_codes(Prop, PropC),
  250      string_codes(Value, ValueC) },
  251    "(", PropC, ": ", ValueC, ")"