diff options
author | Eduardo Julian | 2021-10-22 00:54:07 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-10-22 00:54:07 -0400 |
commit | 5b50e2ed51c37f959a06923c8d7dfd99f0c926e4 (patch) | |
tree | 288f71d7e41e17ba1e65085606bc2c0af30cab28 /stdlib/source/library | |
parent | c9d6d6295db5c7a1cf1966cd194f1a045be5c6cb (diff) |
FIXED analysis extensions got reset and new ones would be unavailable.
Diffstat (limited to '')
11 files changed, 266 insertions, 189 deletions
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux index 63f3cf3f6..37e944bb8 100644 --- a/stdlib/source/library/lux/data/collection/list.lux +++ b/stdlib/source/library/lux/data/collection/list.lux @@ -129,15 +129,15 @@ (def: .public (split_at n xs) (All (_ a) (-> Nat (List a) [(List a) (List a)])) - (if (n.> 0 n) - (case xs - {.#End} - [{.#End} {.#End}] - - {.#Item x xs'} - (let [[tail rest] (split_at (-- n) xs')] - [{.#Item x tail} rest])) - [{.#End} xs])) + (case n + 0 [{.#End} xs] + _ (case xs + {.#End} + [{.#End} {.#End}] + + {.#Item x xs'} + (let [[tail rest] (split_at (-- n) xs')] + [{.#Item x tail} rest])))) (def: (split_when' predicate ys xs) (All (_ a) diff --git a/stdlib/source/library/lux/data/format/css.lux b/stdlib/source/library/lux/data/format/css.lux index c4ac78db3..f4dd728df 100644 --- a/stdlib/source/library/lux/data/format/css.lux +++ b/stdlib/source/library/lux/data/format/css.lux @@ -1,26 +1,28 @@ (.using - [library - [lux {"-" and} - [control - ["[0]" maybe]] - [data - [number - ["[0]" nat]] - ["[0]" text - ["%" format {"+" format}] - ["[0]" encoding {"+" Encoding}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [type - abstract] - [world - [net {"+" URL}]]]] - ["[0]" / "_" - ["[1][0]" selector {"+" Selector Combinator}] - ["[1][0]" value {"+" Value Animation Percentage}] - ["[1][0]" font {"+" Font}] - ["[1][0]" style {"+" Style}] - ["[1][0]" query {"+" Query}]]) + [library + [lux {"-" and} + [control + ["[0]" maybe]] + [data + ["[0]" text + ["%" format {"+" format}] + ["[0]" encoding {"+" Encoding}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + [number + ["[0]" nat]]] + [type + [abstract {"-" Frame}]] + [world + [net {"+" URL}]]]] + ["[0]" / "_" + ["[1][0]" selector {"+" Selector Combinator Specializer Generic}] + ["[1][0]" value {"+" Value Animation Percentage}] + ["[1][0]" property {"+" Property}] + ["[1][0]" font {"+" Font}] + ["[1][0]" style] + ["[1][0]" query {"+" Query}]]) (abstract: .public Common Any) (abstract: .public Special Any) @@ -33,12 +35,15 @@ (|>> :representation)) (def: .public empty - (CSS Common) + (CSS Any) (:abstraction "")) + (type: .public Style + (List (Ex (_ brand) [(Property brand) (Value brand)]))) + (def: .public (rule selector style) (-> (Selector Any) Style (CSS Common)) - (:abstraction (format (/selector.selector selector) "{" (/style.inline style) "}"))) + (:abstraction (format (/selector.selector selector) "{" (/style.inline (/style.style style)) "}"))) (def: .public char_set (-> Encoding (CSS Special)) @@ -65,7 +70,7 @@ with_unicode) (list#each (function (_ [property value]) (format property ": " value ";"))) - (text.interposed /style.separator) + text.together (text.enclosed ["{" "}"]) (format "@font-face") :abstraction))) @@ -81,12 +86,12 @@ "") ";"))) - (def: css_separator + (def: separator text.new_line) (type: .public Frame (Record - [#when Percentage + [#when (Value Percentage) #what Style])) (def: .public (key_frames animation frames) @@ -94,33 +99,38 @@ (:abstraction (format "@keyframes " (/value.value animation) " {" (|> frames (list#each (function (_ frame) - (format (/value.percentage (value@ #when frame)) " {" - (/style.inline (value@ #what frame)) + (format (/value.value (value@ #when frame)) " {" + (/style.inline (/style.style (value@ #what frame))) "}"))) - (text.interposed ..css_separator)) + (text.interposed ..separator)) "}"))) (template: (!composite <pre> <post>) - (:abstraction (format (:representation <pre>) ..css_separator - (:representation <post>)))) + [(:abstraction + (format (:representation <pre>) + ..separator + (:representation <post>)))]) (def: .public (and pre post) - (-> (CSS Any) (CSS Any) (CSS Any)) + (All (_ kind) (-> (CSS kind) (CSS kind) (CSS kind))) (!composite pre post)) - (def: .public (alter combinator selector css) + (def: .public (in_context combinator selector css) (-> Combinator (Selector Any) (CSS Common) (CSS Common)) (|> css :representation - (text.all_split_by ..css_separator) - (list#each (|>> (format (/selector.selector (|> selector (combinator (/selector.tag ""))))))) - (text.interposed ..css_separator) + (text.all_split_by ..separator) + (list#each (let [prefix (|> selector + (combinator (/selector.tag "")) + /selector.selector)] + (|>> (format prefix)))) + (text.interposed ..separator) :abstraction)) (def: .public (dependent combinator selector style inner) (-> Combinator (Selector Any) Style (CSS Common) (CSS Common)) (!composite (..rule selector style) - (..alter combinator selector inner))) + (..in_context combinator selector inner))) (template [<name> <combinator>] [(def: .public <name> @@ -130,4 +140,33 @@ [with_descendants /selector.in] [with_children /selector.sub] ) + + (def: .public (in_case specializer selector css) + (All (_ kind) + (-> (Specializer kind) (Selector (Generic Any)) (CSS Common) (CSS Common))) + (|> css + :representation + (text.all_split_by ..separator) + (list#each (let [prefix (|> selector + (specializer (:expected (/selector.tag ""))) + /selector.selector)] + (|>> (format prefix)))) + (text.interposed ..separator) + :abstraction)) + + (def: .public (specialized combinator selector style inner) + (All (_ kind) + (-> (Specializer kind) (Selector (Generic Any)) Style (CSS Common) (CSS Common))) + (!composite (..rule selector style) + (..in_case combinator selector inner))) + + (template [<name> <combinator>] + [(def: .public <name> + (-> (Selector (Generic Any)) Style (CSS Common) (CSS Common)) + (..specialized <combinator>))] + + [with_case /selector.and] + [with_part /selector.at] + [with_element /selector.for] + ) ) diff --git a/stdlib/source/library/lux/data/format/css/property.lux b/stdlib/source/library/lux/data/format/css/property.lux index 707e3edd3..155297f84 100644 --- a/stdlib/source/library/lux/data/format/css/property.lux +++ b/stdlib/source/library/lux/data/format/css/property.lux @@ -1,9 +1,11 @@ (.using [library - [lux {"-" All Cursor} + [lux {"-" All Location} [control [parser ["s" code]]] + [data + ["[0]" text]] [type abstract] [macro @@ -34,7 +36,7 @@ Display Empty Filter Flex_Direction Flex_Wrap - Font Font_Kerning Font_Size Font_Variant + Font Font_Kerning Font_Size Font_Stretch Font_Style Font_Weight Font_Variant Grid Grid_Content Grid_Flow Grid_Span Grid_Template Hanging_Punctuation Hyphens Isolation List_Style_Position List_Style_Type @@ -333,10 +335,17 @@ [] [["font-size"]]] - [Number + [Font_Stretch [] - [["font-size-adjust"] - ["opacity"]]] + [["font-stretch"]]] + + [Font_Style + [] + [["font-style"]]] + + [Font_Weight + [] + [["font-weight"]]] [Font_Variant [] @@ -388,6 +397,11 @@ [] [["list-style-type"]]] + [Number + [] + [["font-size-adjust"] + ["opacity"]]] + [Overflow [] [["overflow"] diff --git a/stdlib/source/library/lux/data/format/css/query.lux b/stdlib/source/library/lux/data/format/css/query.lux index 251429815..8251fcb06 100644 --- a/stdlib/source/library/lux/data/format/css/query.lux +++ b/stdlib/source/library/lux/data/format/css/query.lux @@ -5,7 +5,7 @@ [parser ["s" code]]] [data - [text + ["[0]" text ["%" format {"+" format}]]] [macro ["[0]" template] diff --git a/stdlib/source/library/lux/data/format/css/selector.lux b/stdlib/source/library/lux/data/format/css/selector.lux index bb6656d6e..35893766a 100644 --- a/stdlib/source/library/lux/data/format/css/selector.lux +++ b/stdlib/source/library/lux/data/format/css/selector.lux @@ -1,16 +1,17 @@ (.using [library - [lux {"-" or and for same? not} + [lux {"-" Label or and for same? not} + ["[0]" locale {"+" Locale}] [data ["[0]" text - ["%" format {"+" format}]] + ["%" format {"+" format}]]] + [math [number ["i" int]]] [type abstract] [macro - ["[0]" template]] - ["[0]" locale {"+" Locale}]]]) + ["[0]" template]]]]) (type: .public Label Text) @@ -57,23 +58,23 @@ [class Class "." Can_Chain] ) - (template [<right> <left> <combo> <combinator>+] + (template [<right> <left> <combinator>+] [(`` (template [<combinator> <name>] [(def: .public (<name> right left) - (-> (Selector <right>) (Selector <left>) (Selector <combo>)) + (-> (Selector <right>) (Selector <left>) (Selector Composite)) (:abstraction (format (:representation left) <combinator> (:representation right))))] (~~ (template.spliced <combinator>+))))] - [Can_Chain (Generic Any) Can_Chain + [Can_Chain (Generic Any) [["" and]]] - [Unique (Generic Any) Composite - [["" for]]] - [Specific (Generic Any) Composite + [Specific (Generic Any) [["" at]]] - [Any Any Composite + [Unique (Generic Any) + [["" for]]] + [Any Any [["," or] [" " in] [">" sub] @@ -81,6 +82,9 @@ ["~" later]]] ) + (type: .public (Specializer kind) + (-> (Selector kind) (Selector (Generic Any)) (Selector Composite))) + (type: .public Combinator (-> (Selector Any) (Selector Any) (Selector Composite))) @@ -104,7 +108,7 @@ (template [<kind> <pseudo>+] [(`` (template [<name> <pseudo>] [(def: .public <name> - (Selector Can_Chain) + (Selector <kind>) (:abstraction <pseudo>))] (~~ (template.spliced <pseudo>+))))] @@ -199,8 +203,8 @@ [nth_child ":nth-child"] [nth_last_child ":nth-last-child"] - [nth_last_of_type ":nth-last-of-type"] [nth_of_type ":nth-of-type"] + [nth_last_of_type ":nth-last-of-type"] ) ) ) diff --git a/stdlib/source/library/lux/data/format/css/style.lux b/stdlib/source/library/lux/data/format/css/style.lux index bd8d26787..8ec6a207f 100644 --- a/stdlib/source/library/lux/data/format/css/style.lux +++ b/stdlib/source/library/lux/data/format/css/style.lux @@ -1,14 +1,16 @@ (.using - [library - [lux "*" - [data - [text - ["%" format {"+" format}]]] - [type - abstract]]] - ["[0]" // "_" - ["[1][0]" value {"+" Value}] - ["[1][0]" property {"+" Property}]]) + [library + [lux "*" + [data + [text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" mix)]]] + [type + abstract]]] + ["[0]" // "_" + ["[1][0]" value {"+" Value}] + ["[1][0]" property {"+" Property}]]) (abstract: .public Style Text @@ -17,18 +19,20 @@ Style (:abstraction "")) - (def: .public separator - " ") - (def: .public (with [property value]) (All (_ brand) (-> [(Property brand) (Value brand)] (-> Style Style))) (|>> :representation - (format (//property.name property) ": " (//value.value value) ";" ..separator) + (format (//property.name property) ": " (//value.value value) ";") :abstraction)) (def: .public inline (-> Style Text) (|>> :representation)) + + (def: .public (style config) + (-> (List (Ex (_ brand) [(Property brand) (Value brand)])) + Style) + (list#mix ..with ..empty config)) ) diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux index a68d0b263..9b2de87f3 100644 --- a/stdlib/source/library/lux/data/format/css/value.lux +++ b/stdlib/source/library/lux/data/format/css/value.lux @@ -1,58 +1,59 @@ (.using - [library - [lux {"-" All Cursor and static false true} - [control - ["[0]" maybe] - [parser - ["s" code]]] - [data - ["[0]" color] - ["[0]" product] - [number - ["n" nat] - ["i" int] - ["r" rev] - ["f" frac]] - ["[0]" text - ["%" format {"+" Format format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [type - abstract] - [macro - ["[0]" template] - ["[0]" code] - [syntax {"+" syntax:}]] - [world - [net {"+" URL}]]]] - [// - [selector {"+" Label}]]) - -(syntax: (text_symbol [symbol s.text]) + [library + [lux {"-" Label All Location and static false true} + [control + ["[0]" maybe] + [parser + ["<[0]>" code]]] + [data + ["[0]" color] + ["[0]" product] + ["[0]" text + ["%" format {"+" Format format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [macro + [syntax {"+" syntax:}] + ["[0]" template] + ["[0]" code]] + [math + [number + ["n" nat] + ["i" int] + ["r" rev] + ["f" frac]]] + [type + abstract] + [world + [net {"+" URL}]]]] + [// + [selector {"+" Label}]]) + +(syntax: (text_symbol [symbol <code>.text]) (in (list (code.local_symbol (text.replaced "-" "_" symbol))))) (template: (enumeration: <abstraction> <representation> <out> <sample>+ <definition>+) - (abstract: .public <abstraction> - <representation> + [(abstract: .public <abstraction> + <representation> - (def: .public <out> - (-> <abstraction> <representation>) - (|>> :representation)) + (def: .public <out> + (-> <abstraction> <representation>) + (|>> :representation)) - (`` (template [<name> <value>] - [(def: .public <name> <abstraction> (:abstraction <value>))] + (`` (template [<name> <value>] + [(def: .public <name> <abstraction> (:abstraction <value>))] - (~~ (template.spliced <sample>+)) - )) + (~~ (template.spliced <sample>+)) + )) - (template.spliced <definition>+))) + (template.spliced <definition>+))]) (template: (multi: <multi> <type> <separator>) - (def: .public (<multi> pre post) - (-> (Value <type>) (Value <type>) (Value <type>)) - (:abstraction (format (:representation pre) - <separator> - (:representation post))))) + [(def: .public (<multi> pre post) + (-> (Value <type>) (Value <type>) (Value <type>)) + (:abstraction (format (:representation pre) + <separator> + (:representation post))))]) (def: (%number value) (Format Frac) @@ -75,7 +76,21 @@ [inherit "inherit"] [unset "unset"] ) - + + (abstract: .public (Numeric kind) Any) + + (template [<name>] + [(with_expansions [<name>' (template.symbol [<name> "'"])] + (abstract: .public <name>' Any) + (type: .public <name> + (Numeric <name>')))] + + [Number] + [Length] + [Time] + [Percentage] + ) + (template [<brand> <alias>+ <value>+] [(abstract: .public <brand> Any) @@ -98,18 +113,6 @@ [] []] - [Number - [] - []] - - [Length - [] - []] - - [Time - [] - []] - [Thickness [] [["medium"] @@ -969,49 +972,41 @@ ) ) - (abstract: .public Percentage - Text + (def: percentage_limit Nat (.++ 100)) - (def: .public percentage - (-> Percentage Text) - (|>> :representation)) + (def: .public (%% value) + (-> Nat (Value Percentage)) + (:abstraction (format (%.nat (n.% percentage_limit value)) "%"))) - (def: percentage_limit Nat (.++ 100)) - - (def: .public (%% value) - (-> Nat Percentage) - (:abstraction (format (%.nat (n.% percentage_limit value)) "%"))) - - (def: .public slice_percent/1 - (-> Percentage (Value Slice)) - (|>> :representation (:abstraction Value))) - - (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: .public <name> - (-> <input> (Value Filter)) - (|>> <pre> (list) (..apply <function>)))] - - (~~ (template.spliced <function>+))))] - - [Nat (<| (:representation Value) ..px n.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: .public slice_percent/1 + (-> (Value Percentage) (Value Slice)) + (|>> :transmutation)) + + (def: .public (slice_percent/2 horizontal vertical) + (-> (Value Percentage) (Value Percentage) (Value Slice)) + (:abstraction (format (:representation horizontal) ..slice_separator + (:representation vertical)))) + + (template [<input> <pre> <function>+] + [(`` (template [<name> <function>] + [(def: .public <name> + (-> <input> (Value Filter)) + (|>> <pre> (list) (..apply <function>)))] + + (~~ (template.spliced <function>+))))] + + [Nat (<| :representation ..px n.frac) + [[blur "blur"]]] + [Nat (<| ..angle ..degree) + [[hue_rotate "hue-rotate"]]] + [(Value Percentage) :representation + [[brightness "brightness"] + [contrast "contrast"] + [grayscale "grayscale"] + [invert "invert"] + [opacity "opacity"] + [saturate "saturate"] + [sepia "sepia"]]] ) (def: .public svg_filter @@ -1329,4 +1324,22 @@ (multi: multi_image Image ",") (multi: multi_shadow Shadow ",") (multi: multi_content Content " ") + + ... https://developer.mozilla.org/en-US/docs/Web/CSS/calc() + (template [<name> <parameter>] + [(def: .public (<name> parameter subject) + (.All (_ kind) + (-> (Value <parameter>) (Value (Numeric kind)) + (Value (Numeric kind)))) + (|> (format (:representation subject) + (template.text [" " <name> " "]) + (:representation parameter)) + (text.enclosed ["calc(" ")"]) + :abstraction))] + + [+ (Numeric kind)] + [- (Numeric kind)] + [* Number] + [/ Number] + ) ) diff --git a/stdlib/source/library/lux/macro/syntax/export.lux b/stdlib/source/library/lux/macro/syntax/export.lux index aa482c559..7a87e30fd 100644 --- a/stdlib/source/library/lux/macro/syntax/export.lux +++ b/stdlib/source/library/lux/macro/syntax/export.lux @@ -14,8 +14,8 @@ (def: policy (Parser Code) (do [! <>.monad] - [candiate <code>.next] - (case candiate + [candidate <code>.next] + (case candidate [_ {.#Symbol ["" _]}] (in default_policy) @@ -23,7 +23,7 @@ [_ {.#Symbol _}]) (do ! [_ <code>.any] - (in candiate)) + (in candidate)) _ (in default_policy)))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux index 602aedfd0..a0ed6f3e6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux @@ -193,6 +193,7 @@ [directive directive' /////generation.learn_directive] ) +... TODO: Get rid of this function ASAP. (def: (refresh expander host_analysis) (All (_ anchor expression directive) (-> Expander /////analysis.Bundle (Operation anchor expression directive Any))) @@ -201,12 +202,14 @@ .let [eval (/////analysis/evaluation.evaluator expander (value@ [/////directive.#synthesis /////directive.#state] state) (value@ [/////directive.#generation /////directive.#state] state) - (value@ [/////directive.#generation /////directive.#phase] state))]] + (value@ [/////directive.#generation /////directive.#phase] state)) + previous_analysis_extensions (value@ [/////directive.#analysis /////directive.#state ///.#bundle] state)]] (phase.set_state [bundle (revised@ [/////directive.#analysis /////directive.#state] (: (-> /////analysis.State+ /////analysis.State+) (|>> product.right - [(///analysis.bundle eval host_analysis)])) + [(|> previous_analysis_extensions + (dictionary.merged (///analysis.bundle eval host_analysis)))])) state)]))) (def: (announce_definition! short type) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/version.lux b/stdlib/source/library/lux/tool/compiler/language/lux/version.lux index 733188447..714ceb58a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/version.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/version.lux @@ -6,4 +6,4 @@ (def: .public version Version - 00,06,02) + 00,06,03) diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux index 7c19c1963..de56b54a2 100644 --- a/stdlib/source/library/lux/world/file.lux +++ b/stdlib/source/library/lux/world/file.lux @@ -380,13 +380,13 @@ [process_load [global process mainModule constructor _load]] ) - (def: (require _) - (-> [] (-> ffi.String Any)) + (def: (require module) + (-> ffi.String Any) (case [(normal_require []) (global_require []) (process_load [])] (^or [{.#Some require} _ _] [_ {.#Some require} _] [_ _ {.#Some require}]) - require + (require module) _ (undefined))) @@ -394,7 +394,7 @@ (template [<name> <module> <type>] [(def: (<name> _) (-> [] <type>) - (:as <type> (..require [] <module>)))] + (:as <type> (..require <module>)))] [node_fs "fs" ..Fs] [node_path "path" ..JsPath] |