diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/data/format/css.lux | 62 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/css/property.lux | 231 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/css/query.lux | 137 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/css/selector.lux | 15 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/css/value.lux | 449 |
5 files changed, 816 insertions, 78 deletions
diff --git a/stdlib/source/lux/data/format/css.lux b/stdlib/source/lux/data/format/css.lux index 78165b4af..3623a2f5d 100644 --- a/stdlib/source/lux/data/format/css.lux +++ b/stdlib/source/lux/data/format/css.lux @@ -14,30 +14,34 @@ [net (#+ URL)]]] [/ ["/." selector (#+ Selector Combinator)] - ["/." value (#+ Value)] + ["/." value (#+ Value Animation Percentage)] ["/." font (#+ Font)] - ["/." style (#+ Style)]]) + ["/." style (#+ Style)] + ["/." query (#+ Query)]]) -(abstract: #export CSS +(abstract: #export Common {} Any) +(abstract: #export Special {} Any) + +(abstract: #export (CSS brand) {} Text - (def: #export empty CSS (:abstraction "")) + (def: #export empty (CSS Common) (:abstraction "")) (def: #export (rule selector style) - (-> (Selector Any) Style CSS) + (-> (Selector Any) Style (CSS Common)) (:abstraction (format (/selector.selector selector) "{" (/style.inline style) "}"))) (def: #export char-set - (-> Encoding CSS) + (-> Encoding (CSS Special)) (|>> encoding.name %t (text.enclose ["@charset " ";"]) :abstraction)) (def: #export (font font) - (-> Font CSS) + (-> Font (CSS Special)) (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)) @@ -59,20 +63,44 @@ (format "@font-face") :abstraction))) - (def: #export (import url) - (-> URL CSS) + (def: #export (import url query) + (-> URL (Maybe Query) (CSS Special)) (:abstraction (format (format "@import url(" (%t url) ")") + (case query + (#.Some query) + (format " " (/query.query query)) + + #.None + "") ";"))) (def: css-separator text.new-line) + (type: #export Frame + {#when Percentage + #what Style}) + + (def: #export (key-frames animation frames) + (-> (Value Animation) (List Frame) (CSS Special)) + (:abstraction (format "@keyframes " (/value.value animation) " {" + (|> frames + (list/map (function (_ frame) + (format (/value.percentage (get@ #when frame)) " {" + (/style.inline (get@ #what frame)) + "}"))) + (text.join-with ..css-separator)) + "}"))) + + (template: (!compose <pre> <post>) + (:abstraction (format (:representation <pre>) ..css-separator + (:representation <post>)))) + (def: #export (and pre post) - (-> CSS CSS CSS) - (:abstraction (format (:representation pre) ..css-separator - (:representation post)))) + (-> (CSS Any) (CSS Any) (CSS Any)) + (!compose pre post)) (def: #export (alter combinator selector css) - (-> Combinator (Selector Any) CSS CSS) + (-> Combinator (Selector Any) (CSS Common) (CSS Common)) (|> css :representation (text.split-all-with ..css-separator) @@ -81,13 +109,13 @@ :abstraction)) (def: #export (dependent combinator selector style inner) - (-> Combinator (Selector Any) Style CSS CSS) - (..and (..rule selector style) - (..alter combinator selector inner))) + (-> Combinator (Selector Any) Style (CSS Common) (CSS Common)) + (!compose (..rule selector style) + (..alter combinator selector inner))) (do-template [<name> <combinator>] [(def: #export <name> - (-> (Selector Any) Style CSS CSS) + (-> (Selector Any) Style (CSS Common) (CSS Common)) (..dependent <combinator>))] [with-descendants /selector.in] diff --git a/stdlib/source/lux/data/format/css/property.lux b/stdlib/source/lux/data/format/css/property.lux index 8282b6528..b9e178ede 100644 --- a/stdlib/source/lux/data/format/css/property.lux +++ b/stdlib/source/lux/data/format/css/property.lux @@ -1,7 +1,5 @@ (.module: [lux (#- All Cursor) - [data - [color (#+ Color)]] [type abstract] [macro @@ -12,7 +10,8 @@ [value (#+ All Number Length Thickness Time - Location Area + Color + Location Fit Slice Alignment Animation-Direction Animation Animation-Fill @@ -22,7 +21,7 @@ Timing Visibility Attachment Blend Span Image Angle Repeat Border - Collapse Break Caption + Collapse Box-Decoration-Break Caption Float Clear Content Cursor @@ -33,7 +32,21 @@ Flex-Direction Flex-Wrap Font Font-Kerning Font-Size Font-Variant Grid Grid-Content Grid-Flow Grid-Span Grid-Template - Hanging-Punctuation Hyphens)]]) + Hanging-Punctuation Hyphens Isolation + List-Style-Position List-Style-Type + Overflow Page-Break Pointer-Events + Position + Quotes + Resize Scroll-Behavior Table-Layout + Text-Align Text-Align-Last + Text-Decoration-Line Text-Decoration-Style + Text-Justification Text-Overflow Text-Transform + Transform Transform-Origin Transform-Style + Transition + Bidi User-Select + Vertical-Align + White-Space Word-Break Word-Wrap Writing-Mode + Z-Index)]]) (syntax: (text-identifier {identifier s.text}) (wrap (list (code.local-identifier identifier)))) @@ -78,12 +91,38 @@ ["grid-column-gap"] ["grid-gap"] ["grid-row-gap"] - ["height"]]] + ["height"] + ["left"] + ["letter-spacing"] + ["line-height"] + ["margin"] + ["margin-bottom"] + ["margin-left"] + ["margin-right"] + ["margin-top"] + ["max-height"] + ["max-width"] + ["min-height"] + ["min-width"] + ["outline-offset"] + ["padding"] + ["padding-bottom"] + ["padding-left"] + ["padding-right"] + ["padding-top"] + ["perspective"] + ["right"] + ["text-indent"] + ["top"] + ["width"] + ["word-spacing"]]] [Time [] [["animation-delay"] - ["animation-duration"]]] + ["animation-duration"] + ["transition-delay"] + ["transition-duration"]]] [Slice [] @@ -98,22 +137,25 @@ ["border-right-color"] ["border-top-color"] ["caret-color"] - ["column-rule-color"]]] + ["column-rule-color"] + ["outline-color"] + ["text-decoration-color"]]] [Alignment [] [["align-content"] ["align-items"] - ["align-self"]]] + ["align-self"] + ["justify-content"]]] + + [Animation + [] + [["animation-name"]]] [Animation-Direction [] [["animation-direction"]]] - [Animation - [] - [["animation-name"]]] - [Animation-Fill [] [["animation-fill-mode"]]] @@ -134,7 +176,9 @@ [] [["column-count"] ["flex-grow"] - ["flex-shrink"]]] + ["flex-shrink"] + ["order"] + ["tab-size"]]] [Play [] @@ -142,11 +186,13 @@ [Timing [] - [["animation-timing-function"]]] + [["animation-timing-function"] + ["transition-timing-function"]]] [Visibility [] - [["backface-visibility"]]] + [["backface-visibility"] + ["visibility"]]] [Attachment [] @@ -154,12 +200,14 @@ [Blend [] - [["background-blend-mode"]]] + [["background-blend-mode"] + ["mix-blend-mode"]]] [Image [] [["background-image"] - ["border-image-source"]]] + ["border-image-source"] + ["list-style-image"]]] [Span [] @@ -169,14 +217,16 @@ [Location [] - [["background-position"]]] + [["background-position"] + ["object-position"] + ["perspective-origin"]]] [Repeat [] [["background-repeat"] ["border-image-repeat"]]] - [Area + [Fit [] [["background-size"] ["border-radius"] @@ -184,7 +234,8 @@ ["border-bottom-right-radius"] ["border-top-left-radius"] ["border-top-right-radius"] - ["border-spacing"]]] + ["border-spacing"] + ["object-fit"]]] [Border [] @@ -193,7 +244,8 @@ ["border-left-style"] ["border-right-style"] ["border-top-style"] - ["column-rule-style"]]] + ["column-rule-style"] + ["outline-style"]]] [Thickness [] @@ -202,13 +254,14 @@ ["border-left-width"] ["border-right-width"] ["border-top-width"] - ["column-rule-width"]]] + ["column-rule-width"] + ["outline-width"]]] [Collapse [] [["border-collapse"]]] - [Break + [Box-Decoration-Break [] [["box-decoration-break"]]] @@ -222,7 +275,8 @@ [Shadow [] - [["box-shadow"]]] + [["box-shadow"] + ["text-shadow"]]] [Clip [] @@ -279,7 +333,8 @@ [Number [] - [["font-size-adjust"]]] + [["font-size-adjust"] + ["opacity"]]] [Font-Variant [] @@ -318,5 +373,129 @@ [Hyphens [] [["hyphens"]]] + + [Isolation + [] + [["isolation"]]] + + [List-Style-Position + [] + [["list-style-position"]]] + + [List-Style-Type + [] + [["list-style-type"]]] + + [Overflow + [] + [["overflow"] + ["overflow-x"] + ["overflow-y"]]] + + [Page-Break + [] + [["page-break-after"] + ["page-break-before"] + ["page-break-inside"]]] + + [Pointer-Events + [] + [["pointer-events"]]] + + [Position + [] + [["position"]]] + + [Quotes + [] + [["quotes"]]] + + [Resize + [] + [["resize"]]] + + [Scroll-Behavior + [] + [["scroll-behavior"]]] + + [Table-Layout + [] + [["table-layout"]]] + + [Text-Align + [] + [["text-align"]]] + + [Text-Align-Last + [] + [["text-align-last"]]] + + [Text-Decoration-Line + [] + [["text-decoration-line"]]] + + [Text-Decoration-Style + [] + [["text-decoration-style"]]] + + [Text-Justification + [] + [["text-justify"]]] + + [Text-Overflow + [] + [["text-overflow"]]] + + [Text-Transform + [] + [["text-transform"]]] + + [Transform + [] + [["transform"]]] + + [Transform-Origin + [] + [["transform-origin"]]] + + [Transform-Style + [] + [["transform-style"]]] + + [Transition + [] + [["transition-property"]]] + + [Bidi + [] + [["unicode-bidi"]]] + + [User-Select + [] + [["user-select"]]] + + [Vertical-Align + [] + [["vertical-align"]]] + + [White-Space + [] + [["white-space"]]] + + [Word-Break + [] + [["word-break"]]] + + [Word-Wrap + [] + [["word-wrap"]]] + + [Writing-Mode + [] + [["writing-mode"]]] + + [Z-Index + [] + [["z-index"]]] ) ) diff --git a/stdlib/source/lux/data/format/css/query.lux b/stdlib/source/lux/data/format/css/query.lux new file mode 100644 index 000000000..a29073240 --- /dev/null +++ b/stdlib/source/lux/data/format/css/query.lux @@ -0,0 +1,137 @@ +(.module: + [lux (#- and or not) + [data + [text + format]] + [macro + ["." template] + ["." code] + ["s" syntax (#+ syntax:)]] + [type + abstract]] + [// + ["//." value (#+ Value Length Count Resolution Ratio + Orientation Scan Boolean Update + Block-Overflow Inline-Overflow + Display-Mode Color-Gamut Inverted-Colors + Pointer Hover + Light Scripting Motion Color-Scheme)]]) + +(syntax: (text-identifier {identifier s.text}) + (wrap (list (code.local-identifier identifier)))) + +(abstract: #export Media + {} + + Text + + (def: #export media + (-> Media Text) + (|>> :representation)) + + (do-template [<media>] + [(`` (def: #export (~~ (text-identifier <media>)) + Media + (:abstraction <media>)))] + + ["all"] + ["print"] + ["screen"] + ["speech"] + )) + +(abstract: #export Feature + {} + + Text + + (def: #export feature + (-> Feature Text) + (|>> :representation)) + + (do-template [<feature> <brand>] + [(`` (def: #export ((~~ (text-identifier <feature>)) input) + (-> (Value <brand>) Feature) + (:abstraction (format "(" <feature> ": " (//value.value input) ")"))))] + + ["min-color" Count] + ["color" Count] + ["max-color" Count] + + ["min-color-index" Count] + ["color-index" Count] + ["max-color-index" Count] + + ["min-monochrome" Count] + ["monochrome" Count] + ["max-monochrome" Count] + + ["min-height" Length] + ["height" Length] + ["max-height" Length] + + ["min-width" Length] + ["width" Length] + ["max-width" Length] + + ["min-resolution" Resolution] + ["resolution" Resolution] + ["max-resolution" Resolution] + + ["aspect-ratio" Ratio] + ["max-aspect-ratio" Ratio] + ["min-aspect-ratio" Ratio] + + ["display-mode" Display-Mode] + ["color-gamut" Color-Gamut] + ["grid" Boolean] + ["orientation" Orientation] + ["overflow-block" Block-Overflow] + ["overflow-inline" Inline-Overflow] + ["scan" Scan] + ["update" Update] + ["inverted-colors" Inverted-Colors] + ["pointer" Pointer] + ["any-pointer" Pointer] + ["hover" Hover] + ["any-hover" Hover] + ["light-level" Light] + ["scripting" Scripting] + ["prefers-reduced-motion" Motion] + ["prefers-color-scheme" Color-Scheme] + ) + ) + +(abstract: #export Query + {} + + Text + + (def: #export query + (-> Query Text) + (|>> :representation)) + + (do-template [<name> <operator>] + [(def: #export <name> + (-> Media Query) + (|>> ..media (format <operator>) :abstraction))] + + [except "not "] + [only "only "] + ) + + (def: #export not + (-> Feature Query) + (|>> ..feature (format "not ") :abstraction)) + + (do-template [<name> <operator>] + [(def: #export (<name> left right) + (-> Query Query Query) + (:abstraction (format (:representation left) + <operator> + (:representation right))))] + + [and " and "] + [or " or "] + ) + ) diff --git a/stdlib/source/lux/data/format/css/selector.lux b/stdlib/source/lux/data/format/css/selector.lux index 653d74c56..905012aeb 100644 --- a/stdlib/source/lux/data/format/css/selector.lux +++ b/stdlib/source/lux/data/format/css/selector.lux @@ -26,6 +26,7 @@ [Cannot-Chain Cannot-Chain'] ) +(abstract: #export Unique {} Any) (abstract: #export Specific {} Any) (abstract: #export Composite {} Any) @@ -51,24 +52,26 @@ (-> <type> (Selector <kind>)) (|>> (format <prefix>) :abstraction))] - [id ID "#" Specific] + [id ID "#" Unique] [class Class "." Can-Chain] ) - (do-template [<left> <right> <combo> <combinator>+] + (do-template [<right> <left> <combo> <combinator>+] [(`` (do-template [<combinator> <name>] - [(def: #export (<name> left right) - (-> (Selector <left>) (Selector <right>) (Selector <combo>)) + [(def: #export (<name> right left) + (-> (Selector <right>) (Selector <left>) (Selector <combo>)) (:abstraction (format (:representation left) <combinator> (:representation right))))] (~~ (template.splice <combinator>+))))] - [(Generic Any) Can-Chain Can-Chain + [Can-Chain (Generic Any) Can-Chain [["" and]]] - [(Generic Any) Specific Composite + [Unique (Generic Any) Composite [["" for]]] + [Specific (Generic Any) Composite + [["" at]]] [Any Any Composite [["," or] [" " in] diff --git a/stdlib/source/lux/data/format/css/value.lux b/stdlib/source/lux/data/format/css/value.lux index 9350b6b98..0d1c773be 100644 --- a/stdlib/source/lux/data/format/css/value.lux +++ b/stdlib/source/lux/data/format/css/value.lux @@ -1,7 +1,7 @@ (.module: - [lux (#- All Cursor and false true) + [lux (#- All Cursor and static false true) [data - ["." color (#+ Color Pigment)] + ["." color] ["." product] ["." maybe] ["." number] @@ -113,8 +113,8 @@ ["thick"]]] [Slice - [] - [["fill"]]] + [[full-slice "fill"]] + []] [Alignment [[auto-alignment "auto"]] @@ -126,16 +126,16 @@ ["space-between"] ["space-around"]]] + [Animation + [] + []] + [Animation-Direction [[normal-direction "normal"]] [["reverse"] ["alternate"] ["alternate-reverse"]]] - [Animation - [] - []] - [Animation-Fill [[fill-forwards "forwards"] [fill-backwards "backwards"] @@ -175,14 +175,15 @@ ["step-end"]]] [Visibility - [[invisible "hidden"]] + [[invisible "hidden"] + [collapse-visibility "collapse"]] [["visible"]]] [Attachment - [] - [["scroll"] - ["fixed"] - ["local"]]] + [[scroll-attachment "scroll"] + [fixed-attachment "fixed"] + [local-attachment "local"]] + []] [Blend [[normal-blend "normal"]] @@ -192,6 +193,10 @@ ["darken"] ["lighten"] ["color-dodge"] + ["color-burn"] + ["difference"] + ["exclusion"] + ["hue"] ["saturation"] ["color"] ["luminosity"]]] @@ -227,10 +232,12 @@ [center-bottom "center bottom"]] []] - [Area - [] - [["cover"] - ["contain"]]] + [Fit + [[no-fit "none"]] + [["fill"] + ["cover"] + ["contain"] + ["scale-down"]]] [Border [] @@ -249,7 +256,7 @@ [["separate"] ["collapse"]]] - [Break + [Box-Decoration-Break [] [["slice"] ["clone"]]] @@ -332,7 +339,8 @@ []] [Display - [[grid-display "grid"]] + [[grid-display "grid"] + [no-display "none"]] [["inline"] ["block"] ["contents"] @@ -351,8 +359,7 @@ ["table-row-group"] ["table-cell"] ["table-column"] - ["table-row"] - ["none"]]] + ["table-row"]]] [Empty [] @@ -500,6 +507,270 @@ [[no-inline-overflow "none"] [scroll-inline-overflow "scroll"]] []] + + [Display-Mode + [] + [["fullscreen"] + ["standalone"] + ["minimal-ui"] + ["browser"]]] + + [Color-Gamut + [] + [["srgb"] + ["p3"] + ["rec2020"]]] + + [Inverted-Colors + [[no-inverted-colors "none"] + [inverted-colors "inverted"]] + []] + + [Pointer + [[no-pointer "none"] + [coarse-pointer "coarse"] + [fine-pointer "fine"]] + []] + + [Hover + [[no-hover "none"]] + [["hover"]]] + + [Light + [[dim-light "dim"] + [normal-light "normal"] + [washed-light "washed"]] + []] + + [Ratio + [] + []] + + [Scripting + [[no-scripting "none"] + [initial-scripting-only "initial-only"] + [scripting-enabled "enabled"]] + []] + + [Motion + [[no-motion-preference "no-preference"] + [reduced-motion "reduce"]] + []] + + [Color-Scheme + [[no-color-scheme-preference "no-preference"] + [light-color-scheme "light"] + [dark-color-scheme "dark"]] + []] + + [Isolation + [[auto-isolation "auto"]] + [["isolate"]]] + + [List-Style-Position + [] + [["inside"] + ["outside"]]] + + [List-Style-Type + [[no-list-style "none"]] + [["disc"] + ["armenian"] + ["circle"] + ["cjk-ideographic"] + ["decimal"] + ["decimal-leading-zero"] + ["georgian"] + ["hebrew"] + ["hiragana"] + ["hiragana-iroha"] + ["katakana"] + ["katakana-iroha"] + ["lower-alpha"] + ["lower-greek"] + ["lower-latin"] + ["lower-roman"] + ["square"] + ["upper-alpha"] + ["upper-greek"] + ["upper-latin"] + ["upper-roman"]]] + + [Color + [] + []] + + [Overflow + [[visible-overflow "visible"] + [hidden-overflow "hidden"] + [scroll-overflow "scroll"] + [auto-overflow "auto"]] + []] + + [Page-Break + [[auto-page-break "auto"] + [always-page-break "always"] + [avoid-page-break "avoid"] + [left-page-break "left"] + [right-page-break "right"]] + []] + + [Pointer-Events + [[auto-pointer-events "auto"] + [no-pointer-events "none"]] + []] + + [Position + [] + [["static"] + ["absolute"] + ["fixed"] + ["relative"] + ["sticky"]]] + + [Quotes + [[no-quotes "none"]] + []] + + [Resize + [[resize-none "none"] + [resize-both "both"] + [resize-horizontal "horizontal"] + [resize-vertical "vertical"]] + []] + + [Scroll-Behavior + [[auto-scroll-behavior "auto"] + [smooth-scroll-behavior "smooth"]] + []] + + [Table-Layout + [[auto-table-layout "auto"] + [fixed-table-layout "fixed"]] + []] + + [Text-Align + [[left-text-align "left"] + [right-text-align "right"] + [center-text-align "center"] + [justify-text-align "justify"]] + []] + + [Text-Align-Last + [[auto-text-align-last "auto"] + [left-text-align-last "left"] + [right-text-align-last "right"] + [center-text-align-last "center"] + [justify-text-align-last "justify"] + [start-text-align-last "start"] + [end-text-align-last "end"]] + []] + + [Text-Decoration-Line + [[no-text-decoration-line "none"] + [underline-text-decoration-line "underline"] + [overline-text-decoration-line "overline"] + [line-through-text-decoration-line "line-through"]] + []] + + [Text-Decoration-Style + [[solid-text-decoration-style "solid"] + [double-text-decoration-style "double"] + [dotted-text-decoration-style "dotted"] + [dashed-text-decoration-style "dashed"] + [wavy-text-decoration-style "wavy"]] + []] + + [Text-Justification + [[auto-text-justification "auto"] + [inter-word-text-justification "inter-word"] + [inter-character-text-justification "inter-character"] + [no-text-justification "none"]] + []] + + [Text-Overflow + [[clip-text-overflow "clip"] + [ellipsis-text-overflow "ellipsis"]] + []] + + [Text-Transform + [[no-text-transform "none"]] + [["capitalize"] + ["uppercase"] + ["lowercase"]]] + + [Transform + [[no-transform "none"]] + []] + + [Transform-Origin + [] + []] + + [Transform-Style + [] + [["flat"] + ["preserve-3d"]]] + + [Transition + [[transition-none "none"] + [transition-all "all"]] + []] + + [Bidi + [[bidi-normal "normal"] + [bidi-embed "embed"] + [bidi-isolate "isolate"] + [bidi-isolate-override "isolate-override"] + [bidi-plaintext "plaintext"]] + [["bidi-override"]]] + + [User-Select + [[user-select-auto "auto"] + [user-select-none "none"] + [user-select-text "text"] + [user-select-all "all"]] + []] + + [Vertical-Align + [[vertical-align-baseline "baseline"] + [vertical-align-sub "sub"] + [vertical-align-super "super"] + [vertical-align-top "top"] + [vertical-align-text-top "text-top"] + [vertical-align-middle "middle"] + [vertical-align-bottom "bottom"] + [vertical-align-text-bottom "text-bottom"]] + []] + + [White-Space + [[normal-white-space "normal"] + [no-wrap-white-space "nowrap"] + [pre-white-space "pre"] + [pre-line-white-space "pre-line"] + [pre-wrap-white-space "pre-wrap"]] + []] + + [Word-Break + [[normal-word-break "normal"]] + [["break-all"] + ["keep-all"] + ["break-word"]]] + + [Word-Wrap + [[normal-word-wrap "normal"] + [break-word-word-wrap "break-word"]] + []] + + [Writing-Mode + [[top-to-bottom-writing-mode "horizontal-tb"] + [left-to-right-writing-mode "vertical-rl"] + [right-to-left-writing-mode "vertical-lr"]] + []] + + [Z-Index + [] + []] ) (def: value-separator ",") @@ -544,14 +815,14 @@ (|>> :abstraction)) (def: #export (rgb color) - (-> Color (Value Color)) + (-> color.Color (Value Color)) (let [[red green blue] (color.to-rgb color)] (..apply "rgb" (list (%n red) (%n green) (%n blue))))) (def: #export (rgba pigment) - (-> Pigment (Value Color)) + (-> color.Pigment (Value Color)) (let [(^slots [#color.color #color.alpha]) pigment [red green blue] (color.to-rgb color)] (..apply "rgba" (list (%n red) @@ -703,6 +974,10 @@ Text + (def: #export percentage + (-> Percentage Text) + (|>> :representation)) + (def: percentage-limit Nat (.inc 100)) (def: #export (%% value) @@ -771,12 +1046,12 @@ (:representation vertical))))] [location Location] - [area Area] + [fit Fit] ) - (def: #export (area/1 length) - (-> (Value Length) (Value Area)) - (..area length length)) + (def: #export (fit/1 length) + (-> (Value Length) (Value Fit)) + (..fit length length)) (def: #export image (-> URL (Value Image)) @@ -786,8 +1061,8 @@ (enumeration: Shape Text shape - [[ellipse "ellipse"] - [circle "circle"]] + [[ellipse-shape "ellipse"] + [circle-shape "circle"]] []) (enumeration: Extent Text @@ -936,6 +1211,122 @@ (-> Nat (Value Resolution)) (:abstraction (format (%n dpi) "dpi"))) + (def: #export (ratio numerator denominator) + (-> Nat Nat (Value Ratio)) + (:abstraction (format (%n numerator) "/" (%n denominator)))) + + (enumeration: Quote Text + quote-text + [[double-quote "\0022"] + [single-quote "\0027"] + [single-left-angle-quote "\2039"] + [single-right-angle-quote "\203A"] + [double-left-angle-quote "\00AB"] + [double-right-angle-quote "\00BB"] + [single-left-quote "\2018"] + [single-right-quote "\2019"] + [double-left-quote "\201C"] + [double-right-quote "\201D"] + [low-double-quote "\201E"]] + [(def: #export quote + (-> Text Quote) + (|>> :abstraction))]) + + (def: quote-separator " ") + + (def: #export (quotes [left0 right0] [left1 right1]) + (-> [Quote Quote] [Quote Quote] (Value Quotes)) + (|> (list left0 right0 left1 right1) + (list/map (|>> ..quote-text %t)) + (text.join-with ..quote-separator) + :abstraction)) + + (def: #export (matrix-2d [a b] [c d] [tx ty]) + (-> [Frac Frac] + [Frac Frac] + [Frac Frac] + (Value Transform)) + (|> (list a b c d tx ty) + (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]) + (-> [Frac Frac Frac Frac] + [Frac Frac Frac Frac] + [Frac Frac Frac Frac] + [Frac Frac Frac Frac] + (Value Transform)) + (|> (list a0 b0 c0 d0 a1 b1 c1 d1 a2 b2 c2 d2 a3 b3 c3 d3) + (list/map %number) + (..apply "matrix3d"))) + + (do-template [<name> <function> <input-types> <input-values>] + [(`` (def: #export (<name> [(~~ (template.splice <input-values>))]) + (-> [(~~ (template.splice <input-types>))] (Value Transform)) + (|> (list (~~ (template.splice <input-values>))) + (list/map %number) + (..apply <function>))))] + + [translate-2d "translate" [Frac Frac] [x y]] + [translate-3d "translate3d" [Frac Frac Frac] [x y z]] + [translate-x "translateX" [Frac] [value]] + [translate-y "translateY" [Frac] [value]] + [translate-z "translateZ" [Frac] [value]] + + [scale-2d "scale" [Frac Frac] [x y]] + [scale-3d "scale3d" [Frac Frac Frac] [x y z]] + [scale-x "scaleX" [Frac] [value]] + [scale-y "scaleY" [Frac] [value]] + [scale-z "scaleZ" [Frac] [value]] + + [perspective "perspective" [Frac] [value]] + ) + + (do-template [<name> <function> <input-types> <input-values>] + [(`` (def: #export (<name> [(~~ (template.splice <input-values>))]) + (-> [(~~ (template.splice <input-types>))] (Value Transform)) + (|> (list (~~ (template.splice <input-values>))) + (list/map ..angle) + (..apply <function>))))] + + [rotate-2d "rotate" [Angle] [angle]] + [rotate-x "rotateX" [Angle] [angle]] + [rotate-y "rotateY" [Angle] [angle]] + [rotate-z "rotateZ" [Angle] [angle]] + + [skew "skew" [Angle Angle] [x-angle y-angle]] + [skew-x "skewX" [Angle] [angle]] + [skew-y "skewY" [Angle] [angle]] + ) + + (def: #export (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) + (-> (Value Length) (Value Length) (Value Transform-Origin)) + (:abstraction (format (:representation x) ..origin-separator + (:representation y)))) + + (def: #export (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 + (-> (Value Length) (Value Vertical-Align)) + (|>> :transmutation)) + + (def: #export (z-index index) + (-> Int (Value Z-Index)) + (:abstraction (if (i/< +0 index) + (%i index) + (%n (.nat index))))) + (multi: multi-image Image ",") (multi: multi-shadow Shadow ",") (multi: multi-content Content " ") |