aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data/format/css/value.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/data/format/css/value.lux')
-rw-r--r--stdlib/source/library/lux/data/format/css/value.lux176
1 files changed, 88 insertions, 88 deletions
diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux
index b48718568..dad95e9b8 100644
--- a/stdlib/source/library/lux/data/format/css/value.lux
+++ b/stdlib/source/library/lux/data/format/css/value.lux
@@ -23,7 +23,7 @@
["r" rev]
["f" frac]]]
[type
- abstract]
+ [abstract {"-" pattern}]]
[world
[net {"+" URL}]]]]
[//
@@ -38,10 +38,10 @@
(def: .public <out>
(-> <abstraction> <representation>)
- (|>> :representation))
+ (|>> representation))
(`` (template [<name> <value>]
- [(def: .public <name> <abstraction> (:abstraction <value>))]
+ [(def: .public <name> <abstraction> (abstraction <value>))]
(~~ (template.spliced <sample>+))
))
@@ -51,9 +51,9 @@
(template: (multi: <multi> <type> <separator>)
[(def: .public (<multi> pre post)
(-> (Value <type>) (Value <type>) (Value <type>))
- (:abstraction (format (:representation pre)
- <separator>
- (:representation post))))])
+ (abstraction (format (representation pre)
+ <separator>
+ (representation post))))])
(def: (%number value)
(Format Frac)
@@ -67,10 +67,10 @@
(def: .public value
(-> (Value Any) Text)
- (|>> :representation))
+ (|>> representation))
(template [<name> <value>]
- [(def: .public <name> Value (:abstraction <value>))]
+ [(def: .public <name> Value (abstraction <value>))]
[initial "initial"]
[inherit "inherit"]
@@ -97,7 +97,7 @@
(`` (template [<name> <value>]
[(def: .public <name>
(Value <brand>)
- (:abstraction <value>))]
+ (abstraction <value>))]
(~~ (template.spliced <alias>+))))
@@ -105,7 +105,7 @@
(template [<value>]
[(`` (def: .public (~~ (..text_symbol <value>))
(Value <brand>)
- (:abstraction <value>)))]
+ (abstraction <value>)))]
<rows>))]
@@ -788,7 +788,7 @@
(text.interposed ..value_separator)
(text.enclosed ["(" ")"])
(format name)
- :abstraction))
+ abstraction))
(enumeration: Step Text
step
@@ -809,7 +809,7 @@
(template [<name> <brand>]
[(def: .public <name>
(-> Nat (Value <brand>))
- (|>> %.nat :abstraction))]
+ (|>> %.nat abstraction))]
[iteration Iteration]
[count Count]
@@ -819,7 +819,7 @@
(def: .public animation
(-> Label (Value Animation))
- (|>> :abstraction))
+ (|>> abstraction))
(def: .public (rgb color)
(-> color.Color (Value Color))
@@ -842,7 +842,7 @@
(template [<name> <suffix>]
[(def: .public (<name> value)
(-> Frac (Value Length))
- (:abstraction (format (%number value) <suffix>)))]
+ (abstraction (format (%number value) <suffix>)))]
[em "em"]
[ex "ex"]
@@ -871,10 +871,10 @@
(template [<name> <suffix>]
[(def: .public (<name> value)
(-> Int (Value Time))
- (:abstraction (format (if (i.< +0 value)
- (%.int value)
- (%.nat (.nat value)))
- <suffix>)))]
+ (abstraction (format (if (i.< +0 value)
+ (%.int value)
+ (%.nat (.nat value)))
+ <suffix>)))]
[seconds "s"]
@@ -883,50 +883,50 @@
(def: .public thickness
(-> (Value Length) (Value Thickness))
- (|>> :transmutation))
+ (|>> transmutation))
(def: slice_separator " ")
(def: .public (slice_number/2 horizontal vertical)
(-> Nat Nat (Value Slice))
- (:abstraction (format (%.nat horizontal) ..slice_separator
- (%.nat vertical))))
+ (abstraction (format (%.nat horizontal) ..slice_separator
+ (%.nat vertical))))
(abstract: .public Stop
Text
(def: .public stop
(-> (Value Color) Stop)
- (|>> (:representation Value) (:abstraction Stop)))
+ (|>> (representation Value) (abstraction Stop)))
(def: stop_separator " ")
(def: .public (single_stop length color)
(-> (Value Length) (Value Color) Stop)
- (:abstraction (format (:representation Value color) ..stop_separator
- (:representation Value length))))
+ (abstraction (format (representation Value color) ..stop_separator
+ (representation Value length))))
(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))))
+ (abstraction (format (representation Value color) ..stop_separator
+ (representation Value start) ..stop_separator
+ (representation Value end))))
(abstract: .public Hint
Text
(def: .public hint
(-> (Value Length) Hint)
- (|>> (:representation Value) (:abstraction Hint)))
+ (|>> (representation Value) (abstraction Hint)))
(def: (with_hint [hint stop])
(-> [(Maybe Hint) Stop] Text)
(case hint
{.#None}
- (:representation Stop stop)
+ (representation Stop stop)
{.#Some hint}
- (format (:representation Hint hint) ..value_separator (:representation Stop stop))))))
+ (format (representation Hint hint) ..value_separator (representation Stop stop))))))
(type: .public (List/1 a)
[a (List a)])
@@ -936,17 +936,17 @@
(def: .public angle
(-> Angle Text)
- (|>> :representation))
+ (|>> representation))
(def: .public (turn value)
(-> Rev Angle)
- (:abstraction (format (%.rev value) "turn")))
+ (abstraction (format (%.rev value) "turn")))
(def: degree_limit Nat 360)
(def: .public (degree value)
(-> Nat Angle)
- (:abstraction (format (%.nat (n.% ..degree_limit value)) "deg")))
+ (abstraction (format (%.nat (n.% ..degree_limit value)) "deg")))
(template [<degree> <name>]
[(def: .public <name>
@@ -963,7 +963,7 @@
[(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)
+ (..apply <function> (list& (representation Angle angle)
(with_hint now)
(list#each with_hint after)))))]
@@ -976,16 +976,16 @@
(def: .public (%% value)
(-> Nat (Value Percentage))
- (:abstraction (format (%.nat (n.% percentage_limit value)) "%")))
+ (abstraction (format (%.nat (n.% percentage_limit value)) "%")))
(def: .public slice_percent/1
(-> (Value Percentage) (Value Slice))
- (|>> :transmutation))
+ (|>> transmutation))
(def: .public (slice_percent/2 horizontal vertical)
(-> (Value Percentage) (Value Percentage) (Value Slice))
- (:abstraction (format (:representation horizontal) ..slice_separator
- (:representation vertical))))
+ (abstraction (format (representation horizontal) ..slice_separator
+ (representation vertical))))
(template [<input> <pre> <function>+]
[(`` (template [<name> <function>]
@@ -995,11 +995,11 @@
(~~ (template.spliced <function>+))))]
- [Nat (<| :representation ..px n.frac)
+ [Nat (<| representation ..px n.frac)
[[blur "blur"]]]
[Nat (<| ..angle ..degree)
[[hue_rotate "hue-rotate"]]]
- [(Value Percentage) :representation
+ [(Value Percentage) representation
[[brightness "brightness"]
[contrast "contrast"]
[grayscale "grayscale"]
@@ -1020,11 +1020,11 @@
(Maybe (Value Length)) (Maybe (Value Length))
(Value Color)
(Value Filter))
- (|> (list (:representation horizontal)
- (:representation vertical)
- (|> blur (maybe.else ..default_shadow_length) :representation)
- (|> spread (maybe.else ..default_shadow_length) :representation)
- (:representation color))
+ (|> (list (representation horizontal)
+ (representation vertical)
+ (|> blur (maybe.else ..default_shadow_length) representation)
+ (|> spread (maybe.else ..default_shadow_length) representation)
+ (representation color))
(text.interposed " ")
(list)
(..apply "drop-shadow")))
@@ -1034,9 +1034,9 @@
(template [<name> <type>]
[(def: .public (<name> horizontal vertical)
(-> (Value Length) (Value Length) (Value <type>))
- (:abstraction (format (:representation horizontal)
- ..length_separator
- (:representation vertical))))]
+ (abstraction (format (representation horizontal)
+ ..length_separator
+ (representation vertical))))]
[location Location]
[fit Fit]
@@ -1071,7 +1071,7 @@
(-> Shape (Maybe Extent) (Value Location)
Stop (List/1 [(Maybe Hint) Stop])
(Value Image))
- (let [after_extent (format "at " (:representation location))
+ (let [after_extent (format "at " (representation location))
with_extent (case extent
{.#Some extent}
(format (..extent extent) " " after_extent)
@@ -1096,14 +1096,14 @@
(let [with_inset (if inset?
(list "inset")
(list))]
- (|> (list& (:representation horizontal)
- (:representation vertical)
- (|> blur (maybe.else ..default_shadow_length) :representation)
- (|> spread (maybe.else ..default_shadow_length) :representation)
- (:representation color)
+ (|> (list& (representation horizontal)
+ (representation vertical)
+ (|> blur (maybe.else ..default_shadow_length) representation)
+ (|> spread (maybe.else ..default_shadow_length) representation)
+ (representation color)
with_inset)
(text.interposed " ")
- :abstraction)))
+ abstraction)))
(type: .public Rectangle
(Record
@@ -1115,21 +1115,21 @@
(def: .public (clip rectangle)
(-> Rectangle (Value Clip))
(`` (..apply "rect" (list (~~ (template [<side>]
- [(:representation (the <side> rectangle))]
+ [(representation (the <side> rectangle))]
[#top] [#right] [#bottom] [#left]))))))
(def: .public counter
(-> Label (Value Counter))
- (|>> :abstraction))
+ (|>> abstraction))
(def: .public current_count
(-> (Value Counter) (Value Content))
- (|>> :representation (list) (..apply "counter")))
+ (|>> representation (list) (..apply "counter")))
(def: .public text
(-> Text (Value Content))
- (|>> %.text :abstraction))
+ (|>> %.text abstraction))
(def: .public attribute
(-> Label (Value Content))
@@ -1148,7 +1148,7 @@
[monospace "monospace"]]
[(def: .public font
(-> Text Font)
- (|>> %.text :abstraction))
+ (|>> %.text abstraction))
(def: .public (font_family options)
(-> (List Font) (Value Font))
@@ -1157,57 +1157,57 @@
(|> options
(list#each ..font_name)
(text.interposed ",")
- (:abstraction Value))
+ (abstraction Value))
{.#End}
..initial))])
(def: .public font_size
(-> (Value Length) (Value Font_Size))
- (|>> :transmutation))
+ (|>> transmutation))
(def: .public number
(-> Frac (Value Number))
- (|>> %number :abstraction))
+ (|>> %number abstraction))
(def: .public grid
(-> Label (Value Grid))
- (|>> :abstraction))
+ (|>> abstraction))
(def: .public fit_content
(-> (Value Length) (Value Grid_Content))
- (|>> :representation (list) (..apply "fit-content")))
+ (|>> representation (list) (..apply "fit-content")))
(def: .public (min_max min max)
(-> (Value Grid_Content) (Value Grid_Content) (Value Grid_Content))
- (..apply "minmax" (list (:representation min)
- (:representation max))))
+ (..apply "minmax" (list (representation min)
+ (representation max))))
(def: .public grid_span
(-> Nat (Value Grid_Span))
- (|>> %.nat (format "span ") :abstraction))
+ (|>> %.nat (format "span ") abstraction))
(def: grid_column_separator " ")
(def: grid_row_separator " ")
(def: .public grid_template
(-> (List (List (Maybe (Value Grid)))) (Value Grid_Template))
- (let [empty (: (Value Grid)
- (:abstraction "."))]
+ (let [empty (is (Value Grid)
+ (abstraction "."))]
(|>> (list#each (|>> (list#each (|>> (maybe.else empty)
- :representation))
+ representation))
(text.interposed ..grid_column_separator)
(text.enclosed ["'" "'"])))
(text.interposed ..grid_row_separator)
- :abstraction)))
+ abstraction)))
(def: .public (resolution dpi)
(-> Nat (Value Resolution))
- (:abstraction (format (%.nat dpi) "dpi")))
+ (abstraction (format (%.nat dpi) "dpi")))
(def: .public (ratio numerator denominator)
(-> Nat Nat (Value Ratio))
- (:abstraction (format (%.nat numerator) "/" (%.nat denominator))))
+ (abstraction (format (%.nat numerator) "/" (%.nat denominator))))
(enumeration: Quote Text
quote_text
@@ -1224,7 +1224,7 @@
[low_double_quote "\201E"]]
[(def: .public quote
(-> Text Quote)
- (|>> :abstraction))])
+ (|>> abstraction))])
(def: quote_separator " ")
@@ -1233,7 +1233,7 @@
(|> (list left0 right0 left1 right1)
(list#each (|>> ..quote_text %.text))
(text.interposed ..quote_separator)
- :abstraction))
+ abstraction))
(def: .public (matrix_2d [a b] [c d] [tx ty])
(-> [Frac Frac]
@@ -1302,24 +1302,24 @@
(def: .public (origin_2d x y)
(-> (Value Length) (Value Length) (Value Transform_Origin))
- (:abstraction (format (:representation x) ..origin_separator
- (:representation y))))
+ (abstraction (format (representation x) ..origin_separator
+ (representation y))))
(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))))
+ (abstraction (format (representation x) ..origin_separator
+ (representation y) ..origin_separator
+ (representation z))))
(def: .public vertical_align
(-> (Value Length) (Value Vertical_Align))
- (|>> :transmutation))
+ (|>> transmutation))
(def: .public (z_index index)
(-> Int (Value Z_Index))
- (:abstraction (if (i.< +0 index)
- (%.int index)
- (%.nat (.nat index)))))
+ (abstraction (if (i.< +0 index)
+ (%.int index)
+ (%.nat (.nat index)))))
(multi: multi_image Image ",")
(multi: multi_shadow Shadow ",")
@@ -1331,11 +1331,11 @@
(.All (_ kind)
(-> (Value <parameter>) (Value (Numeric kind))
(Value (Numeric kind))))
- (|> (format (:representation subject)
+ (|> (format (representation subject)
(template.text [" " <name> " "])
- (:representation parameter))
+ (representation parameter))
(text.enclosed ["calc(" ")"])
- :abstraction))]
+ abstraction))]
[+ (Numeric kind)]
[- (Numeric kind)]