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 ]).
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(_, "").
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]).
91one_of([Elt|_], EltAtom) -->
92 Elt,
93 { atom_codes(EltAtom, Elt) }.
94one_of([_|Elts], Match) --> one_of(Elts, Match).
100alternates([Dcg|_]) --> Dcg, !.
101alternates([_|Dcgs]) --> alternates(Dcgs).
106signus(S) --> one_of(["+", "-"], S).
110direction(direction(D)) --> one_of(["t", "r", "b", "l"], D).
114axis(axis(A)) --> one_of(["x", "y"], A).
119auto(auto) --> "auto".
123unset(unset) --> "unset".
127full_100(full_100) --> "full".
131screen_100vh(screen_100vh) --> "screen".
135screen_100vw(screen_100vw) --> "screen".
139min_content(min_content) --> "min".
143max_content(max_content) --> "max".
148num(number(N)) --> number(N).
153fraction(fraction(N)) -->
154 integer(Num), "/", integer(Denom),
155 { N is Num / Denom }.
160percentage(percentage(P)) --> number(P), "%".
165length(length(L, Unit)) -->
166 number(L), length_unit(unit(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), !.
179angle(angle(A, Unit)) -->
180 number(A), one_of(["deg", "grad", "rad", "turn"], Unit).
185time(time(T, Unit)) --> number(T), one_of(["s", "ms"], Unit).
190resolution(res(R, Unit)) -->
191 number(R), one_of(["dpi", "dpcm", "dppx", "x"], Unit)
Tailwind Utils
Collection of utility predicates and DCGS for parsing tailwind.