1:- module(tw_utils, [value_unit_css/3,
    2                     one_of//2,
    3                     alternates//1,
    4                     signus//1,
    5                     direction//1,
    6                     axis//1,
    7                     auto//1,
    8                     unset//1,
    9                     num//1,
   10                     fraction//1,
   11                     percentage//1,
   12                     length//1,
   13                     length_unit//1,
   14                     angle//1,
   15                     time//1,
   16                     resolution//1
   17                    ]).

Tailwind Utils

Collection of utility predicates and DCGS for parsing tailwind.

author
- James Cash */
   25:- use_module(library(dcg/basics), [integer//1, number//1]).   26:- use_module(library(dcg/high_order), [sequence//3]).   27
   28get_dict_default(K, Dict, V, Default) :-
   29    ( V = Dict.get(K) -> true ; V = Default ).
   30
   31div_4(X, Y) :- Y is X / 4.
   32
   33div_100(X, Y) :- Y is X / 100.
   34
   35mul_100(X, Y) :- Y is X * 100.
   36
   37unit_for(percentage(_), '%') :- !.
   38unit_for(Term, Unit) :-
   39    functor(Term, _, Ar),
   40    Ar == 2, !,
   41    arg(2, Term, Unit).
   42unit_for(_, "").
 value_unit_css(+Value, -CssValue, +Options) is det
Convert a parsed value Value into a CSS value, using the options Options to control the units applied to bare numbers as well as scaling factors.
   49value_unit_css(auto, "auto", _):- !.
   50value_unit_css(none, "none", _):- !.
   51value_unit_css(full, "full", _):- !.
   52value_unit_css(unset, "unset", _):- !.
   53value_unit_css(min_content, "min-content", _):- !.
   54value_unit_css(max_content, "max-content", _):- !.
   55value_unit_css(full_100, "100%", _):- !.
   56value_unit_css(screen_100vw, "100vw", _):- !.
   57value_unit_css(screen_100vh, "100vh", _):- !.
   58value_unit_css(unit(Unit), Css, Opts) :- !,
   59    value_unit_css(length(1, Unit), Css, Opts).
   60value_unit_css(Term, Css, Opts) :-
   61    functor(Term, Type, _),
   62    unit_for(Term, Unit_),
   63    ( ValueFn = Opts.get(Type/value_fn)
   64    -> true
   65    ;  ValueFn = Opts.get(value_fn)
   66    -> true
   67    ;  ValueFn = [X, X]>>true),
   68    arg(1, Term, N),
   69    call(ValueFn, N, Value),
   70    ( Unit = Opts.get(Type/unit)
   71    -> true
   72    ;  Unit = Opts.get(unit)
   73    -> true
   74    ;  Unit = Unit_ ),
   75    ( ZeroUnit = Opts.get(Type/zero_unit)
   76    -> true
   77    ;  get_dict_default(zero_unit, Opts, ZeroUnit, "") ),
   78    get_dict_default(signus, Opts, Signus, +),
   79    number_unit(Value, Unit, ZeroUnit, Signus, Css).
   80
   81number_unit(0, _, Unit, _, Css) :- !,
   82    format(string(Css), "0~w", [Unit]).
   83number_unit(N, Unit, _, Sign, Css) :-
   84    ( Sign == '-' -> V is N * -1 ; V = N ),
   85    format(string(Css), "~w~w", [V, Unit]).
 one_of(+EltsList, -MatchAtom)// is semidet
Finds the first element in EltsList that matches and unifies MatchAtom with the matching element as an atom.
   91one_of([Elt|_], EltAtom) -->
   92    Elt,
   93    { atom_codes(EltAtom, Elt) }.
   94one_of([_|Elts], Match) --> one_of(Elts, Match).
 alternates(+DcgsList)// is semidet
Meta-DCG that finds the first DCG in DcgsList that successfully matches.
  100alternates([Dcg|_]) --> Dcg, !.
  101alternates([_|Dcgs]) --> alternates(Dcgs).
 signus(-Sign)// is semidet
DCG to parse a "sign" value -- + or -
  106signus(S) --> one_of(["+", "-"], S).
 direction(-Dir)// is semidet
DCG to parse a "direction" value -- top, right, bottom, or left.
  110direction(direction(D)) --> one_of(["t", "r", "b", "l"], D).
 axis(-Axis)// is semidet
DCG to parse an axis value -- x or y.
  114axis(axis(A)) --> one_of(["x", "y"], A).
 auto(-Auto)// is semidet
DCG to parse an "auto" value.
  119auto(auto) --> "auto".
 unset(-Unset)// is semidet
DCG to parse an "unset" value.
  123unset(unset) --> "unset".
 full_100(-Full)// is semidet
DCG to parse a "full" value
  127full_100(full_100) --> "full".
 screen_100vh(-Height)// is semidet
DCG to parse a "full-screen" height value.
  131screen_100vh(screen_100vh) --> "screen".
 screen_100vw(-Width)// is semidet
DCG to parse a "full-screen" width value.
  135screen_100vw(screen_100vw) --> "screen".
 min_content(-Min)// is semidet
DCG to parse a min-content value.
  139min_content(min_content) --> "min".
 max_content(-Min)// is semidet
DCG to parse a max-content value.
  143max_content(max_content) --> "max".
 num(-Num)// is semidet
DCG to parse a number.
  148num(number(N)) --> number(N).
 fraction(-Num)// is semidet
DCG to parse a fraction.
  153fraction(fraction(N)) -->
  154    integer(Num), "/", integer(Denom),
  155    { N is Num / Denom }.
 percentage(-Percentage)// is semidet
DCG to parse a percentage value.
  160percentage(percentage(P)) --> number(P), "%".
 length(-Length)// is semidet
DCG to parse a CSS length value.
  165length(length(L, Unit)) -->
  166    number(L), length_unit(unit(Unit)).
 length_unit(-Unit)// is semidet
DCG to parse a CSS length unit.
  171length_unit(unit(Unit)) -->
  172    one_of(["cm", "mm", "in", "pc", "pt", "px",
  173            "em", "ex", "ch", "rem", "lh", "vw", "vh", "vmin", "vmax"],
  174           Unit), !.
 angle(-Angle)// is semidet
DCG to parse a CSS angle value.
  179angle(angle(A, Unit)) -->
  180    number(A), one_of(["deg", "grad", "rad", "turn"], Unit).
 time(-Time)// is semidet
DCG to parse a CSS time value.
  185time(time(T, Unit)) --> number(T), one_of(["s", "ms"], Unit).
 resolution(-Res)// is semidet
DCG to parse a CSS resolution value.
  190resolution(res(R, Unit)) -->
  191    number(R), one_of(["dpi", "dpcm", "dppx", "x"], Unit)