From 9e2f1e76f2c8df01ed7687d934c3210fcf676bd6 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Thu, 16 Jun 2022 00:48:19 -0400 Subject: De-sigil-ification: suffix : [Part 13] --- .../source/library/lux/data/format/css/value.lux | 166 ++++++++++----------- 1 file changed, 83 insertions(+), 83 deletions(-) (limited to 'stdlib/source/library/lux/data/format/css/value.lux') diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux index 66c82fe50..79afc29d6 100644 --- a/stdlib/source/library/lux/data/format/css/value.lux +++ b/stdlib/source/library/lux/data/format/css/value.lux @@ -29,28 +29,28 @@ [// [selector (.only Label)]]) -(def: text_symbol +(def text_symbol (syntax (_ [symbol .text]) (in (list (code.local (text.replaced "-" "_" symbol)))))) -(def: enumeration +(def enumeration (template (_ + +) [(primitive .public - (def: .public + (def .public (-> ) (|>> representation)) (`` (with_template [ ] - [(def: .public (abstraction ))] + [(def .public (abstraction ))] (~~ (template.spliced +)) )) (template.spliced +))])) -(def: (%number value) +(def (%number value) (Format Frac) (let [raw (%.frac value)] (if (f.< +0.0 value) @@ -60,12 +60,12 @@ (primitive .public (Value brand) Text - (def: .public value + (def .public value (-> (Value Any) Text) (|>> representation)) (with_template [ ] - [(def: .public Value (abstraction ))] + [(def .public Value (abstraction ))] [initial "initial"] [inherit "inherit"] @@ -90,7 +90,7 @@ [(primitive .public Any) (`` (with_template [ ] - [(def: .public + [(def .public (Value ) (abstraction ))] @@ -98,7 +98,7 @@ (with_expansions [ (template.spliced +)] (with_template [] - [(`` (def: .public (~~ (..text_symbol )) + [(`` (def .public (~~ (..text_symbol )) (Value ) (abstraction )))] @@ -775,9 +775,9 @@ []] ) - (def: value_separator ",") + (def value_separator ",") - (def: (apply name inputs) + (def (apply name inputs) (-> Text (List Text) Value) (|> inputs (text.interposed ..value_separator) @@ -793,18 +793,18 @@ [end "end"]] []) - (def: .public (steps intervals step) + (def .public (steps intervals step) (-> Nat Step (Value Timing)) (..apply "steps" (list (%.nat intervals) (..step step)))) - (def: .public (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#each %number) (..apply "cubic-bezier"))) (with_template [ ] - [(def: .public + [(def .public (-> Nat (Value )) (|>> %.nat abstraction))] @@ -814,18 +814,18 @@ [span_line Grid_Span] ) - (def: .public animation + (def .public animation (-> Label (Value Animation)) (|>> abstraction)) - (def: .public (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: .public (rgba pigment) + (def .public (rgba pigment) (-> color.Pigment (Value Color)) (let [(open "_[0]") pigment [red green blue] (color.rgb _#color)] @@ -837,7 +837,7 @@ (format "0" (%.rev _#alpha))))))) (with_template [ ] - [(def: .public ( value) + [(def .public ( value) (-> Frac (Value Length)) (abstraction (format (%number value) )))] @@ -859,14 +859,14 @@ [fr "fr"] ) - (def: (%int value) + (def (%int value) (Format Int) (if (i.< +0 value) (%.int value) (%.nat (.nat value)))) (with_template [ ] - [(def: .public ( value) + [(def .public ( value) (-> Int (Value Time)) (abstraction (format (if (i.< +0 value) (%.int value) @@ -878,13 +878,13 @@ [milli_seconds "ms"] ) - (def: .public thickness + (def .public thickness (-> (Value Length) (Value Thickness)) (|>> transmutation)) - (def: slice_separator " ") + (def slice_separator " ") - (def: .public (slice_number/2 horizontal vertical) + (def .public (slice_number/2 horizontal vertical) (-> Nat Nat (Value Slice)) (abstraction (format (%.nat horizontal) ..slice_separator (%.nat vertical)))) @@ -892,18 +892,18 @@ (primitive .public Stop Text - (def: .public stop + (def .public stop (-> (Value Color) Stop) (|>> (representation Value) (abstraction Stop))) - (def: stop_separator " ") + (def stop_separator " ") - (def: .public (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: .public (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 @@ -912,11 +912,11 @@ (primitive .public Hint Text - (def: .public hint + (def .public hint (-> (Value Length) Hint) (|>> (representation Value) (abstraction Hint))) - (def: (with_hint [hint stop]) + (def (with_hint [hint stop]) (-> [(Maybe Hint) Stop] Text) (case hint {.#None} @@ -931,22 +931,22 @@ (primitive .public Angle Text - (def: .public angle + (def .public angle (-> Angle Text) (|>> representation)) - (def: .public (turn value) + (def .public (turn value) (-> Rev Angle) (abstraction (format (%.rev value) "turn"))) - (def: degree_limit Nat 360) + (def degree_limit Nat 360) - (def: .public (degree value) + (def .public (degree value) (-> Nat Angle) (abstraction (format (%.nat (n.% ..degree_limit value)) "deg"))) (with_template [ ] - [(def: .public + [(def .public Angle (..degree ))] @@ -957,7 +957,7 @@ ) (with_template [ ] - [(def: .public ( angle start next) + [(def .public ( angle start next) (-> Angle Stop (List/1 [(Maybe Hint) Stop]) (Value Image)) (let [[now after] next] (..apply (list.partial (representation Angle angle) @@ -969,24 +969,24 @@ ) ) - (def: percentage_limit Nat (.++ 100)) + (def percentage_limit Nat (.++ 100)) - (def: .public (%% value) + (def .public (%% value) (-> Nat (Value Percentage)) (abstraction (format (%.nat (n.% percentage_limit value)) "%"))) - (def: .public slice_percent/1 + (def .public slice_percent/1 (-> (Value Percentage) (Value Slice)) (|>> transmutation)) - (def: .public (slice_percent/2 horizontal vertical) + (def .public (slice_percent/2 horizontal vertical) (-> (Value Percentage) (Value Percentage) (Value Slice)) (abstraction (format (representation horizontal) ..slice_separator (representation vertical)))) (with_template [
 +]
     [(`` (with_template [ ]
-           [(def: .public 
+           [(def .public 
               (->  (Value Filter))
               (|>> 
 (list) (..apply )))]
 
@@ -1006,13 +1006,13 @@
       [sepia "sepia"]]]
     )
 
-  (def: .public svg_filter
+  (def .public svg_filter
     (-> URL (Value Filter))
     (|>> (list) (..apply "url")))
 
-  (def: default_shadow_length (px +0.0))
+  (def default_shadow_length (px +0.0))
 
-  (def: .public (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)
@@ -1026,10 +1026,10 @@
         (list)
         (..apply "drop-shadow")))
 
-  (def: length_separator " ")
+  (def length_separator " ")
 
   (with_template [ ]
-    [(def: .public ( horizontal vertical)
+    [(def .public ( horizontal vertical)
        (-> (Value Length) (Value Length) (Value ))
        (abstraction (format (representation horizontal)
                             ..length_separator
@@ -1039,11 +1039,11 @@
     [fit Fit]
     )
 
-  (def: .public (fit/1 length)
+  (def .public (fit/1 length)
     (-> (Value Length) (Value Fit))
     (..fit length length))
 
-  (def: .public image
+  (def .public image
     (-> URL (Value Image))
     (|>> %.text
          (list)
@@ -1068,7 +1068,7 @@
    [])
 
   (with_template [ ]
-    [(def: .public ( shape extent location start next)
+    [(def .public ( shape extent location start next)
        (-> Shape (Maybe Extent) (Value Location)
            Stop (List/1 [(Maybe Hint) Stop])
            (Value Image))
@@ -1089,7 +1089,7 @@
     [repeating_radial_gradient "repeating-radial-gradient"]
     )
 
-  (def: .public (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
@@ -1113,30 +1113,30 @@
       #bottom (Value Length)
       #left (Value Length)]))
 
-  (def: .public (clip rectangle)
+  (def .public (clip rectangle)
     (-> Rectangle (Value Clip))
     (`` (..apply "rect" (list (~~ (with_template []
                                     [(representation (the  rectangle))]
 
                                     [#top] [#right] [#bottom] [#left]))))))
 
-  (def: .public counter
+  (def .public counter
     (-> Label (Value Counter))
     (|>> abstraction))
 
-  (def: .public current_count
+  (def .public current_count
     (-> (Value Counter) (Value Content))
     (|>> representation (list) (..apply "counter")))
 
-  (def: .public text
+  (def .public text
     (-> Text (Value Content))
     (|>> %.text abstraction))
 
-  (def: .public attribute
+  (def .public attribute
     (-> Label (Value Content))
     (|>> (list) (..apply "attr")))
 
-  (def: .public media
+  (def .public media
     (-> URL (Value Content))
     (|>> (list) (..apply "url")))
 
@@ -1149,11 +1149,11 @@
     [cursive "cursive"]
     [fantasy "fantasy"]
     [monospace "monospace"]]
-   [(def: .public font
+   [(def .public font
       (-> Text Font)
       (|>> %.text abstraction))
 
-    (def: .public (font_family options)
+    (def .public (font_family options)
       (-> (List Font) (Value Font))
       (case options
         {.#Item _}
@@ -1165,35 +1165,35 @@
         {.#End}
         ..initial))])
 
-  (def: .public font_size
+  (def .public font_size
     (-> (Value Length) (Value Font_Size))
     (|>> transmutation))
 
-  (def: .public number
+  (def .public number
     (-> Frac (Value Number))
     (|>> %number abstraction))
 
-  (def: .public grid
+  (def .public grid
     (-> Label (Value Grid))
     (|>> abstraction))
 
-  (def: .public fit_content
+  (def .public fit_content
     (-> (Value Length) (Value Grid_Content))
     (|>> representation (list) (..apply "fit-content")))
 
-  (def: .public (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: .public grid_span
+  (def .public grid_span
     (-> Nat (Value Grid_Span))
     (|>> %.nat (format "span ") abstraction))
 
-  (def: grid_column_separator " ")
-  (def: grid_row_separator " ")
+  (def grid_column_separator " ")
+  (def grid_row_separator " ")
 
-  (def: .public grid_template
+  (def .public grid_template
     (-> (List (List (Maybe (Value Grid)))) (Value Grid_Template))
     (let [empty (is (Value Grid)
                     (abstraction "."))]
@@ -1204,11 +1204,11 @@
            (text.interposed ..grid_row_separator)
            abstraction)))
 
-  (def: .public (resolution dpi)
+  (def .public (resolution dpi)
     (-> Nat (Value Resolution))
     (abstraction (format (%.nat dpi) "dpi")))
 
-  (def: .public (ratio numerator denominator)
+  (def .public (ratio numerator denominator)
     (-> Nat Nat (Value Ratio))
     (abstraction (format (%.nat numerator) "/" (%.nat denominator))))
 
@@ -1227,20 +1227,20 @@
     [double_left_quote "\201C"]
     [double_right_quote "\201D"]
     [low_double_quote "\201E"]]
-   [(def: .public quote
+   [(def .public quote
       (-> Text Quote)
       (|>> abstraction))])
 
-  (def: quote_separator " ")
+  (def quote_separator " ")
 
-  (def: .public (quotes [left0 right0] [left1 right1])
+  (def .public (quotes [left0 right0] [left1 right1])
     (-> [Quote Quote] [Quote Quote] (Value Quotes))
     (|> (list left0 right0 left1 right1)
         (list#each (|>> ..quote_text %.text))
         (text.interposed ..quote_separator)
         abstraction))
 
-  (def: .public (matrix_2d [a b] [c d] [tx ty])
+  (def .public (matrix_2d [a b] [c d] [tx ty])
     (-> [Frac Frac]
         [Frac Frac]
         [Frac Frac]
@@ -1249,7 +1249,7 @@
         (list#each %number)
         (..apply "matrix")))
 
-  (def: .public (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]
@@ -1260,7 +1260,7 @@
         (..apply "matrix3d")))
 
   (with_template [   ]
-    [(`` (def: .public ( [(~~ (template.spliced ))])
+    [(`` (def .public ( [(~~ (template.spliced ))])
            (-> [(~~ (template.spliced ))] (Value Transform))
            (|> (list (~~ (template.spliced )))
                (list#each %number)
@@ -1282,7 +1282,7 @@
     )
 
   (with_template [   ]
-    [(`` (def: .public ( [(~~ (template.spliced ))])
+    [(`` (def .public ( [(~~ (template.spliced ))])
            (-> [(~~ (template.spliced ))] (Value Transform))
            (|> (list (~~ (template.spliced )))
                (list#each ..angle)
@@ -1298,36 +1298,36 @@
     [skew_y "skewY" [Angle] [angle]]
     )
 
-  (def: .public (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 origin_separator " ")
 
-  (def: .public (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: .public (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: .public vertical_align
+  (def .public vertical_align
     (-> (Value Length) (Value Vertical_Align))
     (|>> transmutation))
 
-  (def: .public (z_index index)
+  (def .public (z_index index)
     (-> Int (Value Z_Index))
     (abstraction (if (i.< +0 index)
                    (%.int index)
                    (%.nat (.nat index)))))
 
   (with_template [  ]
-    [(def: .public ( pre post)
+    [(def .public ( pre post)
        (-> (Value ) (Value ) (Value ))
        (abstraction (format (representation pre)
                             
@@ -1340,7 +1340,7 @@
 
   ... https://developer.mozilla.org/en-US/docs/Web/CSS/calc()
   (with_template [ ]
-    [(def: .public ( parameter subject)
+    [(def .public ( parameter subject)
        (.All (_ kind)
          (-> (Value ) (Value (Numeric kind))
              (Value (Numeric kind))))
-- 
cgit v1.2.3