diff options
Diffstat (limited to 'stdlib/source')
-rw-r--r-- | stdlib/source/lux/data/format/css.lux | 88 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/css/font.lux | 22 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/css/property.lux | 127 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/css/selector.lux | 206 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/css/style.lux | 32 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/css/value.lux | 471 | ||||
-rw-r--r-- | stdlib/source/lux/locale/language.lux | 5 | ||||
-rw-r--r-- | stdlib/source/lux/locale/territory.lux | 5 | ||||
-rw-r--r-- | stdlib/source/lux/macro.lux | 8 | ||||
-rw-r--r-- | stdlib/source/lux/macro/template.lux | 11 |
10 files changed, 742 insertions, 233 deletions
diff --git a/stdlib/source/lux/data/format/css.lux b/stdlib/source/lux/data/format/css.lux index feb6fc8a9..78165b4af 100644 --- a/stdlib/source/lux/data/format/css.lux +++ b/stdlib/source/lux/data/format/css.lux @@ -1,56 +1,68 @@ (.module: - [lux (#- Name and) + [lux (#- and) [data - ["." color (#+ Color Pigment)] + ["." maybe] ["." number] ["." text format ["." encoding (#+ Encoding)]] [collection - ["." list ("list/." Functor<List> Monoid<List>)]]] + [list ("list/." Functor<List>)]]] [type abstract] [world [net (#+ URL)]]] [/ - ["." selector (#+ Selector Combinator)] - ["." value (#+ Value)] - ["." property (#+ Property)]]) - -(abstract: #export Style - {#.doc "The style associated with a CSS selector."} - - Text - - (def: #export empty Style (:abstraction "")) - - (def: property-separator " ") - - (def: #export (with [property value]) - (All [brand] - (-> [(Property brand) (Value brand)] - (-> Style Style))) - (|>> :representation - (format (property.name property) ": " (value.value value) ";" ..property-separator) - :abstraction)) - - (def: #export inline - (-> Style Text) - (|>> :representation)) - ) + ["/." selector (#+ Selector Combinator)] + ["/." value (#+ Value)] + ["/." font (#+ Font)] + ["/." style (#+ Style)]]) (abstract: #export CSS {} Text + (def: #export empty CSS (:abstraction "")) + (def: #export (rule selector style) - (-> Selector Style CSS) - (:abstraction (format (selector.selector selector) " " "{" (..inline style) "}"))) + (-> (Selector Any) Style CSS) + (:abstraction (format (/selector.selector selector) "{" (/style.inline style) "}"))) - (def: #export (char-set encoding) + (def: #export char-set (-> Encoding CSS) - (:abstraction (format "@charset" " " (%t (encoding.name encoding)) ";"))) + (|>> encoding.name + %t + (text.enclose ["@charset " ";"]) + :abstraction)) + + (def: #export (font font) + (-> Font CSS) + (let [with-unicode (case (get@ #/font.unicode-range font) + (#.Some unicode-range) + (let [unicode-range' (format "U+" (:: number.Hex@Codec<Text,Nat> encode (get@ #/font.start unicode-range)) + "-" (:: number.Hex@Codec<Text,Nat> encode (get@ #/font.end unicode-range)))] + (list ["unicode-range" unicode-range'])) + + #.None + (list))] + (|> (list& ["font-family" (get@ #/font.family font)] + ["src" (format "url(" (get@ #/font.source font) ")")] + ["font-stretch" (|> font (get@ #/font.stretch) (maybe.default /value.normal-stretch) /value.value)] + ["font-style" (|> font (get@ #/font.style) (maybe.default /value.normal-style) /value.value)] + ["font-weight" (|> font (get@ #/font.weight) (maybe.default /value.normal-weight) /value.value)] + with-unicode) + (list/map (function (_ [property value]) + (format property ": " value ";"))) + (text.join-with /style.separator) + (text.enclose ["{" "}"]) + (format "@font-face") + :abstraction))) + + (def: #export (import url) + (-> URL CSS) + (:abstraction (format (format "@import url(" (%t url) ")") + ";"))) (def: css-separator text.new-line) @@ -60,25 +72,25 @@ (:representation post)))) (def: #export (alter combinator selector css) - (-> Combinator Selector CSS CSS) + (-> Combinator (Selector Any) CSS CSS) (|> css :representation (text.split-all-with ..css-separator) - (list/map (|>> (format (selector.selector (combinator selector (selector.tag "")))))) + (list/map (|>> (format (/selector.selector (combinator selector (/selector.tag "")))))) (text.join-with ..css-separator) :abstraction)) (def: #export (dependent combinator selector style inner) - (-> Combinator Selector Style CSS CSS) + (-> Combinator (Selector Any) Style CSS CSS) (..and (..rule selector style) (..alter combinator selector inner))) (do-template [<name> <combinator>] [(def: #export <name> - (-> Selector Style CSS CSS) + (-> (Selector Any) Style CSS CSS) (..dependent <combinator>))] - [scope selector.in] - [complex selector.sub] + [with-descendants /selector.in] + [with-children /selector.sub] ) ) diff --git a/stdlib/source/lux/data/format/css/font.lux b/stdlib/source/lux/data/format/css/font.lux new file mode 100644 index 000000000..d7615043a --- /dev/null +++ b/stdlib/source/lux/data/format/css/font.lux @@ -0,0 +1,22 @@ +(.module: + [lux #* + [type + abstract] + ["." macro + ["s" syntax (#+ syntax:)]] + [world + [net (#+ URL)]]] + [// + ["//." value (#+ Value Font-Stretch Font-Style Font-Weight)]]) + +(type: #export Unicode-Range + {#start Nat + #end Nat}) + +(type: #export Font + {#family Text + #source URL + #stretch (Maybe (Value Font-Stretch)) + #style (Maybe (Value Font-Style)) + #weight (Maybe (Value Font-Weight)) + #unicode-range (Maybe Unicode-Range)}) diff --git a/stdlib/source/lux/data/format/css/property.lux b/stdlib/source/lux/data/format/css/property.lux index b6a97cea4..8282b6528 100644 --- a/stdlib/source/lux/data/format/css/property.lux +++ b/stdlib/source/lux/data/format/css/property.lux @@ -1,25 +1,20 @@ (.module: [lux (#- All Cursor) [data - ["." color (#+ Color)] - ["." number] - ["." text - format] - [collection - ["." list ("list/." Functor<List> Monoid<List>)]]] + [color (#+ Color)]] [type abstract] - ["." macro + [macro + ["." template] ["." code] - ["s" syntax (#+ syntax:)]] - [world - [net (#+ URL)]]] + ["s" syntax (#+ syntax:)]]] [// [value (#+ All + Number Length Thickness Time Location Area Slice - Alignment Direction + Alignment Animation-Direction Animation Animation-Fill Column-Fill Column-Span Iteration Count @@ -28,10 +23,17 @@ Blend Span Image Angle Repeat Border Collapse Break Caption - Clear + Float Clear Content Cursor - Shadow Clip)]]) + Shadow Clip + Text-Direction + Display Empty + Filter + Flex-Direction Flex-Wrap + Font Font-Kerning Font-Size Font-Variant + Grid Grid-Content Grid-Flow Grid-Span Grid-Template + Hanging-Punctuation Hyphens)]]) (syntax: (text-identifier {identifier s.text}) (wrap (list (code.local-identifier identifier)))) @@ -51,9 +53,9 @@ (Property <brand>) (:abstraction <property>))] - (~~ (macro.multi <alias>+)))) + (~~ (template.splice <alias>+)))) - (with-expansions [<rows> (macro.multi <property>+)] + (with-expansions [<rows> (template.splice <property>+)] (do-template [<property>] [(`` (def: #export (~~ (text-identifier <property>)) (Property <brand>) @@ -71,7 +73,12 @@ ["border-image-width"] ["bottom"] ["column-gap"] - ["column-width"]]] + ["column-width"] + ["flex-basis"] + ["grid-column-gap"] + ["grid-gap"] + ["grid-row-gap"] + ["height"]]] [Time [] @@ -99,7 +106,7 @@ ["align-items"] ["align-self"]]] - [Direction + [Animation-Direction [] [["animation-direction"]]] @@ -125,7 +132,9 @@ [Count [] - [["column-count"]]] + [["column-count"] + ["flex-grow"] + ["flex-shrink"]]] [Play [] @@ -227,5 +236,87 @@ [Cursor [] [["cursor"]]] + + [Text-Direction + [[text-direction "direction"]] + []] + + [Display + [] + [["display"]]] + + [Empty + [] + [["empty-cells"]]] + + [Filter + [] + [["filter"]]] + + [Flex-Direction + [] + [["flex-direction"]]] + + [Flex-Wrap + [] + [["flex-wrap"]]] + + [Float + [] + [["float"]]] + + [Font + [] + [["font-family"]]] + + [Font-Kerning + [] + [["font-kerning"]]] + + [Font-Size + [] + [["font-size"]]] + + [Number + [] + [["font-size-adjust"]]] + + [Font-Variant + [] + [["font-variant"]]] + + [Grid + [] + [["grid-area"]]] + + [Grid-Content + [] + [["grid-auto-columns"] + ["grid-auto-rows"] + ["grid-template-columns"] + ["grid-template-rows"]]] + + [Grid-Flow + [] + [["grid-auto-flow"]]] + + [Grid-Span + [] + [["grid-column-end"] + ["grid-column-start"] + ["grid-row-end"] + ["grid-row-start"]]] + + [Grid-Template + [] + [["grid-template-areas"]]] + + [Hanging-Punctuation + [] + [["hanging-punctuation"]]] + + [Hyphens + [] + [["hyphens"]]] ) ) diff --git a/stdlib/source/lux/data/format/css/selector.lux b/stdlib/source/lux/data/format/css/selector.lux index 23d19b9a5..653d74c56 100644 --- a/stdlib/source/lux/data/format/css/selector.lux +++ b/stdlib/source/lux/data/format/css/selector.lux @@ -1,128 +1,158 @@ (.module: - [lux (#- and id is? not) + [lux (#- or and for id is? not) [data ["." text format]] [type abstract] + [macro + ["." template]] ["." locale (#+ Locale)]]) -(type: #export Tag Text) -(type: #export ID Text) -(type: #export Class Text) -(type: #export Attribute Text) +(type: #export Label Text) -(abstract: #export Selector +(type: #export Tag Label) +(type: #export ID Label) +(type: #export Class Label) +(type: #export Attribute Label) + +(abstract: #export (Generic brand) {} Any) + +(do-template [<generic> <brand>] + [(abstract: <brand> {} Any) + (type: #export <generic> (Generic <brand>))] + + [Can-Chain Can-Chain'] + [Cannot-Chain Cannot-Chain'] + ) + +(abstract: #export Specific {} Any) +(abstract: #export Composite {} Any) + +(abstract: #export (Selector kind) {} Text (def: #export selector - (-> Selector Text) + (-> (Selector Any) Text) (|>> :representation)) (def: #export any - Selector + (Selector Cannot-Chain) (:abstraction "*")) (def: #export tag - (-> Tag Selector) + (-> Tag (Selector Cannot-Chain)) (|>> :abstraction)) - (do-template [<name> <type> <prefix>] + (do-template [<name> <type> <prefix> <kind>] [(def: #export <name> - (-> <type> Selector) + (-> <type> (Selector <kind>)) (|>> (format <prefix>) :abstraction))] - [id ID "#"] - [class Class "."] + [id ID "#" Specific] + [class Class "." Can-Chain] ) - (type: #export Combinator - (-> Selector Selector Selector)) - - (do-template [<name> <combinator>] - [(def: #export (<name> left right) - Combinator - (:abstraction (format (:representation left) - <combinator> - (:representation right))))] - - [and ","] - [in " "] - [sub ">"] - [after "+"] - [later "~"] + (do-template [<left> <right> <combo> <combinator>+] + [(`` (do-template [<combinator> <name>] + [(def: #export (<name> left right) + (-> (Selector <left>) (Selector <right>) (Selector <combo>)) + (:abstraction (format (:representation left) + <combinator> + (:representation right))))] + + (~~ (template.splice <combinator>+))))] + + [(Generic Any) Can-Chain Can-Chain + [["" and]]] + [(Generic Any) Specific Composite + [["" for]]] + [Any Any Composite + [["," or] + [" " in] + [">" sub] + ["+" next] + ["~" later]]] ) - (def: #export (with attribute) - (-> Attribute Selector) + (type: #export Combinator + (-> (Selector Any) (Selector Any) (Selector Composite))) + + (def: #export (with? attribute) + (-> Attribute (Selector Can-Chain)) (:abstraction (format "[" attribute "]"))) - (do-template [<name> <check>] - [(def: #export (<name> attribute value base) - (-> Attribute Text Selector Selector) - (:abstraction (format (:representation base) "[" attribute <check> value "]")))] - - [is? "="] - [has? "~="] - [has-start? "|="] - [starts? "^="] - [ends? "$="] - [contains? "*="] + (do-template [<check> <name>] + [(def: #export (<name> attribute value) + (-> Attribute Text (Selector Can-Chain)) + (:abstraction (format "[" attribute <check> value "]")))] + + ["=" is?] + ["~=" has?] + ["|=" has-start?] + ["^=" starts?] + ["$=" ends?] + ["*=" contains?] ) - (do-template [<name> <pseudo>] - [(def: #export (<name> base) - (-> Selector Selector) - (:abstraction (format (:representation base) <pseudo>)))] - - [active ":active"] - [after! "::after"] - [before! "::before"] - - [checked ":checked"] - [default ":default"] - [disabled ":disabled"] - [empty ":empty"] - [enabled ":enabled"] - [first-child ":first-child"] - [first-letter "::first-letter"] - [first-line "::first-line"] - [first-of-type ":first-of-type"] - [focused ":focus"] - [hovered ":hover"] - [in-range ":in-range"] - [indeterminate ":indeterminate"] - [invalid ":invalid"] - [last-child ":last-child"] - [last-of-type ":last-of-type"] - [link ":link"] - [only-of-type ":only-of-type"] - [only-child ":only-child"] - [optional ":optional"] - [out-of-range ":out-of-range"] - [placeholder "::placeholder"] - [read-only ":read-only"] - [read-write ":read-write"] - [required ":required"] - [root ":root"] - [selection "::selection"] - [target ":target"] - [valid ":valid"] - [visited ":visited"] + (do-template [<kind> <pseudo>+] + [(`` (do-template [<name> <pseudo>] + [(def: #export <name> + (Selector Can-Chain) + (:abstraction <pseudo>))] + + (~~ (template.splice <pseudo>+))))] + + [Can-Chain + [[active ":active"] + [checked ":checked"] + [default ":default"] + [disabled ":disabled"] + [empty ":empty"] + [enabled ":enabled"] + [first-child ":first-child"] + [first-of-type ":first-of-type"] + [focused ":focus"] + [hovered ":hover"] + [in-range ":in-range"] + [indeterminate ":indeterminate"] + [invalid ":invalid"] + [last-child ":last-child"] + [last-of-type ":last-of-type"] + [link ":link"] + [only-of-type ":only-of-type"] + [only-child ":only-child"] + [optional ":optional"] + [out-of-range ":out-of-range"] + [read-only ":read-only"] + [read-write ":read-write"] + [required ":required"] + [root ":root"] + [target ":target"] + [valid ":valid"] + [visited ":visited"]]] + + [Specific + [[after "::after"] + [before "::before"] + [first-letter "::first-letter"] + [first-line "::first-line"] + [placeholder "::placeholder"] + [selection "::selection"]]] ) - (def: #export (language locale base) - (-> Locale Selector Selector) + (def: #export (language locale) + (-> Locale (Selector Can-Chain)) (|> locale locale.code (text.enclose ["(" ")"]) - (format (:representation base) ":lang") + (format ":lang") :abstraction)) (def: #export not - (-> Selector Selector) + (-> (Selector Any) (Selector Can-Chain)) (|>> :representation (text.enclose ["(" ")"]) (format ":not") @@ -133,7 +163,7 @@ Text - (def: #export simple + (def: #export index (-> Nat Index) (|>> %n :abstraction)) @@ -157,11 +187,11 @@ (%i constant))))) (do-template [<name> <pseudo>] - [(def: #export (<name> index base) - (-> Index Selector Selector) + [(def: #export (<name> index) + (-> Index (Selector Can-Chain)) (|> (:representation index) (text.enclose ["(" ")"]) - (format (:representation Selector base) <pseudo>) + (format <pseudo>) (:abstraction Selector)))] [nth-child ":nth-child"] diff --git a/stdlib/source/lux/data/format/css/style.lux b/stdlib/source/lux/data/format/css/style.lux new file mode 100644 index 000000000..37979e8b8 --- /dev/null +++ b/stdlib/source/lux/data/format/css/style.lux @@ -0,0 +1,32 @@ +(.module: + [lux #* + [data + [text + format]] + [type + abstract]] + [// + ["//." value (#+ Value)] + ["//." property (#+ Property)]]) + +(abstract: #export Style + {#.doc "The style associated with a CSS selector."} + + Text + + (def: #export empty Style (:abstraction "")) + + (def: #export separator " ") + + (def: #export (with [property value]) + (All [brand] + (-> [(Property brand) (Value brand)] + (-> Style Style))) + (|>> :representation + (format (//property.name property) ": " (//value.value value) ";" ..separator) + :abstraction)) + + (def: #export inline + (-> Style Text) + (|>> :representation)) + ) diff --git a/stdlib/source/lux/data/format/css/value.lux b/stdlib/source/lux/data/format/css/value.lux index 8f485f429..9350b6b98 100644 --- a/stdlib/source/lux/data/format/css/value.lux +++ b/stdlib/source/lux/data/format/css/value.lux @@ -1,7 +1,8 @@ (.module: - [lux (#- All Cursor and) + [lux (#- All Cursor and false true) [data ["." color (#+ Color Pigment)] + ["." product] ["." maybe] ["." number] ["." text @@ -10,16 +11,19 @@ ["." list ("list/." Functor<List>)]]] [type abstract] - ["." macro + [macro + ["." template] ["." code] ["s" syntax (#+ syntax:)]] [world - [net (#+ URL)]]]) + [net (#+ URL)]]] + [// + [selector (#+ Label)]]) (syntax: (text-identifier {identifier s.text}) (wrap (list (code.local-identifier identifier)))) -(template: (enumeration: <abstraction> <representation> <out> <sample>+) +(template: (enumeration: <abstraction> <representation> <out> <sample>+ <definition>+) (abstract: #export <abstraction> {} @@ -32,8 +36,10 @@ (`` (do-template [<name> <value>] [(def: #export <name> <abstraction> (:abstraction <value>))] - (~~ (macro.multi <sample>+)) - )))) + (~~ (template.splice <sample>+)) + )) + + (template.splice <definition>+))) (template: (multi: <multi> <type> <separator>) (def: #export (<multi> pre post) @@ -42,6 +48,13 @@ <separator> (:representation post))))) +(def: (%number value) + (Format Frac) + (let [raw (%f value)] + (if (f/< +0.0 value) + raw + (|> raw (text.split 1) maybe.assume product.right)))) + (abstract: #export (Value brand) {} @@ -56,6 +69,7 @@ [initial "initial"] [inherit "inherit"] + [unset "unset"] ) (do-template [<brand> <alias>+ <value>+] @@ -66,9 +80,9 @@ (Value <brand>) (:abstraction <value>))] - (~~ (macro.multi <alias>+)))) + (~~ (template.splice <alias>+)))) - (with-expansions [<rows> (macro.multi <value>+)] + (with-expansions [<rows> (template.splice <value>+)] (do-template [<value>] [(`` (def: #export (~~ (text-identifier <value>)) (Value <brand>) @@ -78,7 +92,11 @@ [All [] - [["unset"]]] + []] + + [Number + [] + []] [Length [] @@ -108,7 +126,7 @@ ["space-between"] ["space-around"]]] - [Direction + [Animation-Direction [[normal-direction "normal"]] [["reverse"] ["alternate"] @@ -241,6 +259,11 @@ [["top"] ["bottom"]]] + [Float + [[float-left "left"] + [float-right "right"]] + []] + [Clear [[clear-left "left"] [clear-right "right"] @@ -259,7 +282,8 @@ ["no-close-quote"]]] [Cursor - [[horizontal-text "text"]] + [[horizontal-text "text"] + [no-cursor "none"]] [["alias"] ["all-scroll"] ["cell"] @@ -281,7 +305,6 @@ ["nw-resize"] ["nwse-resize"] ["no-drop"] - ["none"] ["not-allowed"] ["pointer"] ["progress"] @@ -302,6 +325,181 @@ [Clip [] []] + + [Text-Direction + [[left-to-right "ltr"] + [right-to-left "rtl"]] + []] + + [Display + [[grid-display "grid"]] + [["inline"] + ["block"] + ["contents"] + ["flex"] + ["inline-block"] + ["inline-flex"] + ["inline-grid"] + ["inline-table"] + ["list-item"] + ["run-in"] + ["table"] + ["table-caption"] + ["table-column-group"] + ["table-header-group"] + ["table-footer-group"] + ["table-row-group"] + ["table-cell"] + ["table-column"] + ["table-row"] + ["none"]]] + + [Empty + [] + [["show"] + ["hide"]]] + + [Filter + [] + []] + + [Flex-Direction + [] + [["row"] + ["row-reverse"] + ["column"] + ["column-reverse"]]] + + [Flex-Wrap + [[no-wrap "nowrap"]] + [["wrap"] + ["wrap-reverse"]]] + + [Font-Kerning + [[auto-kerning "auto"] + [normal-kerning "normal"] + [no-kerning "none"]] + []] + + [Font-Size + [[medium-size "medium"] + [xx-small-size "xx-small"] + [x-small-size "x-small"] + [small-size "small"] + [large-size "large"] + [x-large-size "x-large"] + [xx-large-size "xx-large"] + [smaller-size "smaller"] + [larger-size "larger"]] + []] + + [Font-Stretch + [[normal-stretch "normal"]] + [["condensed"] + ["ultra-condensed"] + ["extra-condensed"] + ["semi-condensed"] + ["expanded"] + ["semi-expanded"] + ["extra-expanded"] + ["ultra-expanded"]]] + + [Font-Style + [[normal-style "normal"]] + [["italic"] + ["oblique"]]] + + [Font-Weight + [[normal-weight "normal"] + [weight-100 "100"] + [weight-200 "200"] + [weight-300 "300"] + [weight-400 "400"] + [weight-500 "500"] + [weight-600 "600"] + [weight-700 "700"] + [weight-800 "800"] + [weight-900 "900"]] + [["bold"]]] + + [Font-Variant + [[normal-font "normal"]] + [["small-caps"]]] + + [Grid + [] + []] + + [Grid-Content + [[auto-content "auto"]] + [["max-content"] + ["min-content"]]] + + [Grid-Flow + [[row-flow "row"] + [column-flow "column"] + [dense-flow "dense"] + [row-dense-flow "row dense"] + [column-dense-flow "column dense"]] + []] + + [Grid-Span + [[auto-span "auto"]] + []] + + [Grid-Template + [] + []] + + [Hanging-Punctuation + [[no-hanging-punctuation "none"]] + [["first"] + ["last"] + ["allow-end"] + ["force-end"]]] + + [Hyphens + [[no-hyphens "none"] + [manual-hyphens "manual"] + [auto-hyphens "auto"]] + []] + + [Orientation + [] + [["portrait"] + ["landscape"]]] + + [Resolution + [] + []] + + [Scan + [] + [["interlace"] + ["progressive"]]] + + [Boolean + [[false "0"] + [true "1"]] + []] + + [Update + [[no-update "none"] + [slow-update "slow"] + [fast-update "fast"]] + []] + + [Block-Overflow + [[no-block-overflow "none"] + [scroll-block-overflow "scroll"] + [optional-paged-block-overflow "optional-paged"] + [paged-block-overflow "paged"]] + []] + + [Inline-Overflow + [[no-inline-overflow "none"] + [scroll-inline-overflow "scroll"]] + []] ) (def: value-separator ",") @@ -317,7 +515,8 @@ (enumeration: Step Text step [[start "start"] - [end "end"]]) + [end "end"]] + []) (def: #export (steps intervals step) (-> Nat Step (Value Timing)) @@ -326,19 +525,22 @@ (def: #export (cubic-bezier p0 p1 p2 p3) (-> Frac Frac Frac Frac (Value Timing)) (|> (list p0 p1 p2 p3) - (list/map %f) + (list/map %number) (..apply "cubic-bezier"))) - (def: #export iteration - (-> Nat (Value Iteration)) - (|>> %n :abstraction)) + (do-template [<name> <brand>] + [(def: #export <name> + (-> Nat (Value <brand>)) + (|>> %n :abstraction))] - (def: #export count - (-> Nat (Value Count)) - (|>> %n :abstraction)) + [iteration Iteration] + [count Count] + [slice-number/1 Slice] + [span-line Grid-Span] + ) (def: #export animation - (-> Text (Value Animation)) + (-> Label (Value Animation)) (|>> :abstraction)) (def: #export (rgb color) @@ -362,7 +564,7 @@ (do-template [<name> <suffix>] [(def: #export (<name> value) (-> Frac (Value Length)) - (:abstraction (format (%f value) <suffix>)))] + (:abstraction (format (%number value) <suffix>)))] [em "em"] [ex "ex"] @@ -379,6 +581,7 @@ [px "px"] [pt "pt"] [pc "pc"] + [fr "fr"] ) (def: (%int value) @@ -404,10 +607,6 @@ (-> (Value Length) (Value Thickness)) (|>> :transmutation)) - (def: #export slice-number/1 - (-> Nat (Value Slice)) - (|>> %n :abstraction)) - (def: slice-separator " ") (def: #export (slice-number/2 horizontal vertical) @@ -415,44 +614,6 @@ (:abstraction (format (%n horizontal) ..slice-separator (%n vertical)))) - (def: percent-limit Nat (.inc 100)) - - (def: (percentage value) - (-> Nat Text) - (format (%n (n/% percent-limit value)) "%")) - - (def: #export slice-percent/1 - (-> Nat (Value Slice)) - (|>> percentage :abstraction)) - - (def: #export (slice-percent/2 horizontal vertical) - (-> Nat Nat (Value Slice)) - (:abstraction (format (..percentage horizontal) ..slice-separator - (..percentage vertical)))) - - (def: length-separator " ") - - (do-template [<name> <type>] - [(def: #export (<name> horizontal vertical) - (-> (Value Length) (Value Length) (Value <type>)) - (:abstraction (format (:representation horizontal) - ..length-separator - (:representation vertical))))] - - [location Location] - [area Area] - ) - - (def: #export (area/1 length) - (-> (Value Length) (Value Area)) - (..area length length)) - - (def: #export image - (-> URL (Value Image)) - (|>> %t - (list) - (..apply "url"))) - (abstract: #export Stop {} @@ -501,6 +662,10 @@ Text + (def: #export angle + (-> Angle Text) + (|>> :representation)) + (def: #export (turn value) (-> Rev Angle) (:abstraction (format (%r value) "turn"))) @@ -511,13 +676,13 @@ (-> Nat Angle) (:abstraction (format (%n (n/% ..degree-limit value)) "deg"))) - (do-template [<name> <degree>] + (do-template [<degree> <name>] [(def: #export <name> Angle (..degree <degree>))] - [to-top 0] - [to-right 90] - [to-bottom 180] - [to-left 270] + [000 to-top] + [090 to-right] + [180 to-bottom] + [270 to-left] ) (do-template [<name> <function>] @@ -533,17 +698,105 @@ ) ) + (abstract: #export Percentage + {} + + Text + + (def: percentage-limit Nat (.inc 100)) + + (def: #export (%% value) + (-> Nat Percentage) + (:abstraction (format (%n (n/% percentage-limit value)) "%"))) + + (def: #export slice-percent/1 + (-> Percentage (Value Slice)) + (|>> :representation (:abstraction Value))) + + (def: #export (slice-percent/2 horizontal vertical) + (-> Percentage Percentage (Value Slice)) + (:abstraction Value (format (:representation horizontal) ..slice-separator + (:representation vertical)))) + + (do-template [<input> <pre> <function>+] + [(`` (do-template [<name> <function>] + [(def: #export <name> + (-> <input> (Value Filter)) + (|>> <pre> (list) (..apply <function>)))] + + (~~ (template.splice <function>+))))] + + [Nat (<| (:representation Value) ..px nat-to-frac) + [[blur "blur"]]] + [Nat (<| ..angle ..degree) + [[hue-rotate "hue-rotate"]]] + [Percentage (:representation Percentage) + [[brightness "brightness"] + [contrast "contrast"] + [grayscale "grayscale"] + [invert "invert"] + [opacity "opacity"] + [saturate "saturate"] + [sepia "sepia"]]] + ) + ) + + (def: #export svg-filter + (-> URL (Value Filter)) + (|>> (list) (..apply "url"))) + + (def: default-shadow-length (px +0.0)) + + (def: #export (drop-shadow horizontal vertical blur spread color) + (-> (Value Length) (Value Length) + (Maybe (Value Length)) (Maybe (Value Length)) + (Value Color) + (Value Filter)) + (|> (list (:representation horizontal) + (:representation vertical) + (|> blur (maybe.default ..default-shadow-length) :representation) + (|> spread (maybe.default ..default-shadow-length) :representation) + (:representation color)) + (text.join-with " ") + (list) + (..apply "drop-shadow"))) + + (def: length-separator " ") + + (do-template [<name> <type>] + [(def: #export (<name> horizontal vertical) + (-> (Value Length) (Value Length) (Value <type>)) + (:abstraction (format (:representation horizontal) + ..length-separator + (:representation vertical))))] + + [location Location] + [area Area] + ) + + (def: #export (area/1 length) + (-> (Value Length) (Value Area)) + (..area length length)) + + (def: #export image + (-> URL (Value Image)) + (|>> %t + (list) + (..apply "url"))) + (enumeration: Shape Text shape [[ellipse "ellipse"] - [circle "circle"]]) + [circle "circle"]] + []) (enumeration: Extent Text extent [[closest-side "closest-side"] [closest-corner "closest-corner"] [farthest-side "farthest-side"] - [farthest-corner "farthest-corner"]]) + [farthest-corner "farthest-corner"]] + []) (do-template [<name> <function>] [(def: #export (<name> shape extent location start next) @@ -567,8 +820,6 @@ [repeating-radial-gradient "repeating-radial-gradient"] ) - (def: default-length (px +0.0)) - (def: #export (shadow horizontal vertical blur spread color inset?) (-> (Value Length) (Value Length) (Maybe (Value Length)) (Maybe (Value Length)) @@ -579,8 +830,8 @@ (list))] (|> (list& (:representation horizontal) (:representation vertical) - (|> blur (maybe.default ..default-length) :representation) - (|> spread (maybe.default ..default-length) :representation) + (|> blur (maybe.default ..default-shadow-length) :representation) + (|> spread (maybe.default ..default-shadow-length) :representation) (:representation color) with-inset) (text.join-with " ") @@ -600,7 +851,7 @@ [#top] [#right] [#bottom] [#left])))))) (def: #export counter - (-> Text (Value Counter)) + (-> Label (Value Counter)) (|>> :abstraction)) (def: #export current-count @@ -612,13 +863,79 @@ (|>> %t :abstraction)) (def: #export attribute - (-> Text (Value Content)) + (-> Label (Value Content)) (|>> (list) (..apply "attr"))) (def: #export media (-> URL (Value Content)) (|>> (list) (..apply "url"))) + (enumeration: Font Text + font-name + [[serif "serif"] + [sans-serif "sans-serif"] + [cursive "cursive"] + [fantasy "fantasy"] + [monospace "monospace"]] + [(def: #export font + (-> Text Font) + (|>> %t :abstraction)) + + (def: #export (font-family options) + (-> (List Font) (Value Font)) + (case options + (#.Cons _) + (|> options + (list/map ..font-name) + (text.join-with ",") + (:abstraction Value)) + + #.Nil + ..initial))]) + + (def: #export font-size + (-> (Value Length) (Value Font-Size)) + (|>> :transmutation)) + + (def: #export number + (-> Frac (Value Number)) + (|>> %number :abstraction)) + + (def: #export grid + (-> Label (Value Grid)) + (|>> :abstraction)) + + (def: #export fit-content + (-> (Value Length) (Value Grid-Content)) + (|>> :representation (list) (..apply "fit-content"))) + + (def: #export (min-max min max) + (-> (Value Grid-Content) (Value Grid-Content) (Value Grid-Content)) + (..apply "minmax" (list (:representation min) + (:representation max)))) + + (def: #export grid-span + (-> Nat (Value Grid-Span)) + (|>> %n (format "span ") :abstraction)) + + (def: grid-column-separator " ") + (def: grid-row-separator " ") + + (def: #export grid-template + (-> (List (List (Maybe (Value Grid)))) (Value Grid-Template)) + (let [empty (: (Value Grid) + (:abstraction "."))] + (|>> (list/map (|>> (list/map (|>> (maybe.default empty) + :representation)) + (text.join-with ..grid-column-separator) + (text.enclose ["'" "'"]))) + (text.join-with ..grid-row-separator) + :abstraction))) + + (def: #export (resolution dpi) + (-> Nat (Value Resolution)) + (:abstraction (format (%n dpi) "dpi"))) + (multi: multi-image Image ",") (multi: multi-shadow Shadow ",") (multi: multi-content Content " ") diff --git a/stdlib/source/lux/locale/language.lux b/stdlib/source/lux/locale/language.lux index 3075eba16..8c37efaef 100644 --- a/stdlib/source/lux/locale/language.lux +++ b/stdlib/source/lux/locale/language.lux @@ -7,7 +7,8 @@ ["." text]] [type abstract] - ["." macro]]) + [macro + ["." template]]]) ## https://en.wikipedia.org/wiki/List_of_ISO_639-2_codes (abstract: #export Language @@ -24,7 +25,7 @@ (`` (do-template [<alias>] [(def: #export <alias> Language <name>)] - (~~ (macro.multi <alias>+))))] + (~~ (template.splice <alias>+))))] ["mis" uncoded []] ["mul" multiple []] diff --git a/stdlib/source/lux/locale/territory.lux b/stdlib/source/lux/locale/territory.lux index ece06b9d6..8c1f802ed 100644 --- a/stdlib/source/lux/locale/territory.lux +++ b/stdlib/source/lux/locale/territory.lux @@ -7,7 +7,8 @@ ["." text]] [type abstract] - ["." macro]]) + [macro + ["." template]]]) ## https://en.wikipedia.org/wiki/ISO_3166-1 (abstract: #export Territory @@ -41,7 +42,7 @@ (`` (do-template [<neighbor>] [(def: #export <neighbor> Territory <main>)] - (~~ (macro.multi <neighbor>+))))] + (~~ (template.splice <neighbor>+))))] ["AF" "AFG" 004 "Afghanistan" afghanistan []] ["AX" "ALA" 248 "Ă…land Islands" aland-islands []] diff --git a/stdlib/source/lux/macro.lux b/stdlib/source/lux/macro.lux index a2e17e2d9..7ad35eec9 100644 --- a/stdlib/source/lux/macro.lux +++ b/stdlib/source/lux/macro.lux @@ -736,11 +736,3 @@ [log-expand-all! expand-all] [log-expand-once! expand-once] ) - -(macro: #export (multi tokens) - (case tokens - (^ (list [_ (#.Tuple parts)])) - (:: Monad<Meta> wrap parts) - - _ - (fail (..wrong-syntax-error (name-of ..multi))))) diff --git a/stdlib/source/lux/macro/template.lux b/stdlib/source/lux/macro/template.lux new file mode 100644 index 000000000..b5fca4e69 --- /dev/null +++ b/stdlib/source/lux/macro/template.lux @@ -0,0 +1,11 @@ +(.module: + [lux #*] + ["." // ("meta/." Monad<Meta>)]) + +(macro: #export (splice tokens) + (case tokens + (^ (list [_ (#.Tuple parts)])) + (meta/wrap parts) + + _ + (//.fail (//.wrong-syntax-error (name-of ..splice))))) |