diff options
Diffstat (limited to 'stdlib/source/library/lux/data/format/css/value.lux')
-rw-r--r-- | stdlib/source/library/lux/data/format/css/value.lux | 162 |
1 files changed, 87 insertions, 75 deletions
diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux index 6dbf1c3f4..ed2d75319 100644 --- a/stdlib/source/library/lux/data/format/css/value.lux +++ b/stdlib/source/library/lux/data/format/css/value.lux @@ -32,15 +32,17 @@ (in (list (code.local_identifier (text.replace_all "-" "_" identifier))))) (template: (enumeration: <abstraction> <representation> <out> <sample>+ <definition>+) - (abstract: #export <abstraction> + (abstract: .public <abstraction> + {} + <representation> - (def: #export <out> + (def: .public <out> (-> <abstraction> <representation>) (|>> :representation)) (`` (template [<name> <value>] - [(def: #export <name> <abstraction> (:abstraction <value>))] + [(def: .public <name> <abstraction> (:abstraction <value>))] (~~ (template.spliced <sample>+)) )) @@ -48,7 +50,7 @@ (template.spliced <definition>+))) (template: (multi: <multi> <type> <separator>) - (def: #export (<multi> pre post) + (def: .public (<multi> pre post) (-> (Value <type>) (Value <type>) (Value <type>)) (:abstraction (format (:representation pre) <separator> @@ -61,15 +63,17 @@ raw (|> raw (text.split 1) maybe.assume product.right)))) -(abstract: #export (Value brand) +(abstract: .public (Value brand) + {} + Text - (def: #export value + (def: .public value (-> (Value Any) Text) (|>> :representation)) (template [<name> <value>] - [(def: #export <name> Value (:abstraction <value>))] + [(def: .public <name> Value (:abstraction <value>))] [initial "initial"] [inherit "inherit"] @@ -77,10 +81,10 @@ ) (template [<brand> <alias>+ <value>+] - [(abstract: #export <brand> Any) + [(abstract: .public <brand> {} Any) (`` (template [<name> <value>] - [(def: #export <name> + [(def: .public <name> (Value <brand>) (:abstraction <value>))] @@ -88,7 +92,7 @@ (with_expansions [<rows> (template.spliced <value>+)] (template [<value>] - [(`` (def: #export (~~ (..text_identifier <value>)) + [(`` (def: .public (~~ (..text_identifier <value>)) (Value <brand>) (:abstraction <value>)))] @@ -793,18 +797,18 @@ [end "end"]] []) - (def: #export (steps intervals step) + (def: .public (steps intervals step) (-> Nat Step (Value Timing)) (..apply "steps" (list (%.nat intervals) (..step step)))) - (def: #export (cubic_bezier p0 p1 p2 p3) + (def: .public (cubic_bezier p0 p1 p2 p3) (-> Frac Frac Frac Frac (Value Timing)) (|> (list p0 p1 p2 p3) (list\map %number) (..apply "cubic-bezier"))) (template [<name> <brand>] - [(def: #export <name> + [(def: .public <name> (-> Nat (Value <brand>)) (|>> %.nat :abstraction))] @@ -814,18 +818,18 @@ [span_line Grid_Span] ) - (def: #export animation + (def: .public animation (-> Label (Value Animation)) (|>> :abstraction)) - (def: #export (rgb color) + (def: .public (rgb color) (-> color.Color (Value Color)) (let [[red green blue] (color.rgb color)] (..apply "rgb" (list (%.nat red) (%.nat green) (%.nat blue))))) - (def: #export (rgba pigment) + (def: .public (rgba pigment) (-> color.Pigment (Value Color)) (let [(^slots [#color.color #color.alpha]) pigment [red green blue] (color.rgb color)] @@ -837,7 +841,7 @@ (format "0" (%.rev alpha))))))) (template [<name> <suffix>] - [(def: #export (<name> value) + [(def: .public (<name> value) (-> Frac (Value Length)) (:abstraction (format (%number value) <suffix>)))] @@ -866,7 +870,7 @@ (%.nat (.nat value)))) (template [<name> <suffix>] - [(def: #export (<name> value) + [(def: .public (<name> value) (-> Int (Value Time)) (:abstraction (format (if (i.< +0 value) (%.int value) @@ -878,41 +882,45 @@ [milli_seconds "ms"] ) - (def: #export thickness + (def: .public thickness (-> (Value Length) (Value Thickness)) (|>> :transmutation)) (def: slice_separator " ") - (def: #export (slice_number/2 horizontal vertical) + (def: .public (slice_number/2 horizontal vertical) (-> Nat Nat (Value Slice)) (:abstraction (format (%.nat horizontal) ..slice_separator (%.nat vertical)))) - (abstract: #export Stop + (abstract: .public Stop + {} + Text - (def: #export stop + (def: .public stop (-> (Value Color) Stop) (|>> (:representation Value) (:abstraction Stop))) (def: stop_separator " ") - (def: #export (single_stop length color) + (def: .public (single_stop length color) (-> (Value Length) (Value Color) Stop) (:abstraction (format (:representation Value color) ..stop_separator (:representation Value length)))) - (def: #export (double_stop start end color) + (def: .public (double_stop start end color) (-> (Value Length) (Value Length) (Value Color) Stop) (:abstraction (format (:representation Value color) ..stop_separator (:representation Value start) ..stop_separator (:representation Value end)))) - (abstract: #export Hint + (abstract: .public Hint + {} + Text - (def: #export hint + (def: .public hint (-> (Value Length) Hint) (|>> (:representation Value) (:abstraction Hint))) @@ -925,28 +933,30 @@ (#.Some hint) (format (:representation Hint hint) ..value_separator (:representation Stop stop)))))) - (type: #export (List/1 a) + (type: .public (List/1 a) [a (List a)]) - (abstract: #export Angle + (abstract: .public Angle + {} + Text - (def: #export angle + (def: .public angle (-> Angle Text) (|>> :representation)) - (def: #export (turn value) + (def: .public (turn value) (-> Rev Angle) (:abstraction (format (%.rev value) "turn"))) (def: degree_limit Nat 360) - (def: #export (degree value) + (def: .public (degree value) (-> Nat Angle) (:abstraction (format (%.nat (n.% ..degree_limit value)) "deg"))) (template [<degree> <name>] - [(def: #export <name> + [(def: .public <name> Angle (..degree <degree>))] @@ -957,7 +967,7 @@ ) (template [<name> <function>] - [(def: #export (<name> angle start next) + [(def: .public (<name> angle start next) (-> Angle Stop (List/1 [(Maybe Hint) Stop]) (Value Image)) (let [[now after] next] (..apply <function> (list& (:representation Angle angle) @@ -969,31 +979,33 @@ ) ) - (abstract: #export Percentage + (abstract: .public Percentage + {} + Text - (def: #export percentage + (def: .public percentage (-> Percentage Text) (|>> :representation)) (def: percentage_limit Nat (.inc 100)) - (def: #export (%% value) + (def: .public (%% value) (-> Nat Percentage) (:abstraction (format (%.nat (n.% percentage_limit value)) "%"))) - (def: #export slice_percent/1 + (def: .public slice_percent/1 (-> Percentage (Value Slice)) (|>> :representation (:abstraction Value))) - (def: #export (slice_percent/2 horizontal vertical) + (def: .public (slice_percent/2 horizontal vertical) (-> Percentage Percentage (Value Slice)) (:abstraction Value (format (:representation horizontal) ..slice_separator (:representation vertical)))) (template [<input> <pre> <function>+] [(`` (template [<name> <function>] - [(def: #export <name> + [(def: .public <name> (-> <input> (Value Filter)) (|>> <pre> (list) (..apply <function>)))] @@ -1014,13 +1026,13 @@ ) ) - (def: #export svg_filter + (def: .public svg_filter (-> URL (Value Filter)) (|>> (list) (..apply "url"))) (def: default_shadow_length (px +0.0)) - (def: #export (drop_shadow horizontal vertical blur spread color) + (def: .public (drop_shadow horizontal vertical blur spread color) (-> (Value Length) (Value Length) (Maybe (Value Length)) (Maybe (Value Length)) (Value Color) @@ -1037,7 +1049,7 @@ (def: length_separator " ") (template [<name> <type>] - [(def: #export (<name> horizontal vertical) + [(def: .public (<name> horizontal vertical) (-> (Value Length) (Value Length) (Value <type>)) (:abstraction (format (:representation horizontal) ..length_separator @@ -1047,11 +1059,11 @@ [fit Fit] ) - (def: #export (fit/1 length) + (def: .public (fit/1 length) (-> (Value Length) (Value Fit)) (..fit length length)) - (def: #export image + (def: .public image (-> URL (Value Image)) (|>> %.text (list) @@ -1072,7 +1084,7 @@ []) (template [<name> <function>] - [(def: #export (<name> shape extent location start next) + [(def: .public (<name> shape extent location start next) (-> Shape (Maybe Extent) (Value Location) Stop (List/1 [(Maybe Hint) Stop]) (Value Image)) @@ -1093,7 +1105,7 @@ [repeating_radial_gradient "repeating-radial-gradient"] ) - (def: #export (shadow horizontal vertical blur spread color inset?) + (def: .public (shadow horizontal vertical blur spread color inset?) (-> (Value Length) (Value Length) (Maybe (Value Length)) (Maybe (Value Length)) (Value Color) Bit @@ -1110,36 +1122,36 @@ (text.join_with " ") :abstraction))) - (type: #export Rectangle + (type: .public Rectangle {#top (Value Length) #right (Value Length) #bottom (Value Length) #left (Value Length)}) - (def: #export (clip rectangle) + (def: .public (clip rectangle) (-> Rectangle (Value Clip)) (`` (..apply "rect" (list (~~ (template [<side>] [(:representation (get@ <side> rectangle))] [#top] [#right] [#bottom] [#left])))))) - (def: #export counter + (def: .public counter (-> Label (Value Counter)) (|>> :abstraction)) - (def: #export current_count + (def: .public current_count (-> (Value Counter) (Value Content)) (|>> :representation (list) (..apply "counter"))) - (def: #export text + (def: .public text (-> Text (Value Content)) (|>> %.text :abstraction)) - (def: #export attribute + (def: .public attribute (-> Label (Value Content)) (|>> (list) (..apply "attr"))) - (def: #export media + (def: .public media (-> URL (Value Content)) (|>> (list) (..apply "url"))) @@ -1150,11 +1162,11 @@ [cursive "cursive"] [fantasy "fantasy"] [monospace "monospace"]] - [(def: #export font + [(def: .public font (-> Text Font) (|>> %.text :abstraction)) - (def: #export (font_family options) + (def: .public (font_family options) (-> (List Font) (Value Font)) (case options (#.Item _) @@ -1166,35 +1178,35 @@ #.End ..initial))]) - (def: #export font_size + (def: .public font_size (-> (Value Length) (Value Font_Size)) (|>> :transmutation)) - (def: #export number + (def: .public number (-> Frac (Value Number)) (|>> %number :abstraction)) - (def: #export grid + (def: .public grid (-> Label (Value Grid)) (|>> :abstraction)) - (def: #export fit_content + (def: .public fit_content (-> (Value Length) (Value Grid_Content)) (|>> :representation (list) (..apply "fit-content"))) - (def: #export (min_max min max) + (def: .public (min_max min max) (-> (Value Grid_Content) (Value Grid_Content) (Value Grid_Content)) (..apply "minmax" (list (:representation min) (:representation max)))) - (def: #export grid_span + (def: .public grid_span (-> Nat (Value Grid_Span)) (|>> %.nat (format "span ") :abstraction)) (def: grid_column_separator " ") (def: grid_row_separator " ") - (def: #export grid_template + (def: .public grid_template (-> (List (List (Maybe (Value Grid)))) (Value Grid_Template)) (let [empty (: (Value Grid) (:abstraction "."))] @@ -1205,11 +1217,11 @@ (text.join_with ..grid_row_separator) :abstraction))) - (def: #export (resolution dpi) + (def: .public (resolution dpi) (-> Nat (Value Resolution)) (:abstraction (format (%.nat dpi) "dpi"))) - (def: #export (ratio numerator denominator) + (def: .public (ratio numerator denominator) (-> Nat Nat (Value Ratio)) (:abstraction (format (%.nat numerator) "/" (%.nat denominator)))) @@ -1226,20 +1238,20 @@ [double_left_quote "\201C"] [double_right_quote "\201D"] [low_double_quote "\201E"]] - [(def: #export quote + [(def: .public quote (-> Text Quote) (|>> :abstraction))]) (def: quote_separator " ") - (def: #export (quotes [left0 right0] [left1 right1]) + (def: .public (quotes [left0 right0] [left1 right1]) (-> [Quote Quote] [Quote Quote] (Value Quotes)) (|> (list left0 right0 left1 right1) (list\map (|>> ..quote_text %.text)) (text.join_with ..quote_separator) :abstraction)) - (def: #export (matrix_2d [a b] [c d] [tx ty]) + (def: .public (matrix_2d [a b] [c d] [tx ty]) (-> [Frac Frac] [Frac Frac] [Frac Frac] @@ -1248,7 +1260,7 @@ (list\map %number) (..apply "matrix"))) - (def: #export (matrix_3d [a0 b0 c0 d0] [a1 b1 c1 d1] [a2 b2 c2 d2] [a3 b3 c3 d3]) + (def: .public (matrix_3d [a0 b0 c0 d0] [a1 b1 c1 d1] [a2 b2 c2 d2] [a3 b3 c3 d3]) (-> [Frac Frac Frac Frac] [Frac Frac Frac Frac] [Frac Frac Frac Frac] @@ -1259,7 +1271,7 @@ (..apply "matrix3d"))) (template [<name> <function> <input_types> <input_values>] - [(`` (def: #export (<name> [(~~ (template.spliced <input_values>))]) + [(`` (def: .public (<name> [(~~ (template.spliced <input_values>))]) (-> [(~~ (template.spliced <input_types>))] (Value Transform)) (|> (list (~~ (template.spliced <input_values>))) (list\map %number) @@ -1281,7 +1293,7 @@ ) (template [<name> <function> <input_types> <input_values>] - [(`` (def: #export (<name> [(~~ (template.spliced <input_values>))]) + [(`` (def: .public (<name> [(~~ (template.spliced <input_values>))]) (-> [(~~ (template.spliced <input_types>))] (Value Transform)) (|> (list (~~ (template.spliced <input_values>))) (list\map ..angle) @@ -1297,29 +1309,29 @@ [skew_y "skewY" [Angle] [angle]] ) - (def: #export (rotate_3d [x y z angle]) + (def: .public (rotate_3d [x y z angle]) (-> [Frac Frac Frac Angle] (Value Transform)) (..apply "rotate3d" (list (%number x) (%number y) (%number z) (..angle angle)))) (def: origin_separator " ") - (def: #export (origin_2d x y) + (def: .public (origin_2d x y) (-> (Value Length) (Value Length) (Value Transform_Origin)) (:abstraction (format (:representation x) ..origin_separator (:representation y)))) - (def: #export (origin_3d x y z) + (def: .public (origin_3d x y z) (-> (Value Length) (Value Length) (Value Length) (Value Transform_Origin)) (:abstraction (format (:representation x) ..origin_separator (:representation y) ..origin_separator (:representation z)))) - (def: #export vertical_align + (def: .public vertical_align (-> (Value Length) (Value Vertical_Align)) (|>> :transmutation)) - (def: #export (z_index index) + (def: .public (z_index index) (-> Int (Value Z_Index)) (:abstraction (if (i.< +0 index) (%.int index) |