diff options
author | Eduardo Julian | 2021-01-28 20:14:11 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-01-28 20:14:11 -0400 |
commit | 1797521191746640e761cc1b4973d46b8c403dee (patch) | |
tree | 197b60bf206f75c32a930b85910101c6d4c0d0f9 /stdlib/source/lux/tool | |
parent | 43d28326ad59c74439b96343cc8f619ed7d90231 (diff) |
Implemented arithmetic right-shift in terms of logic right-shift.
Diffstat (limited to 'stdlib/source/lux/tool')
12 files changed, 102 insertions, 73 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux index 21fc0b343..72642db8d 100644 --- a/stdlib/source/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/lux/tool/compiler/default/platform.lux @@ -95,12 +95,17 @@ write_artifact! (: (-> [Text Binary] (Action Any)) (function (_ [name content]) (ioW.write system static module_id name content)))] - (do ..monad + (do {! ..monad} [_ (ioW.prepare system static module_id) - _ (|> output - row.to_list - (monad.map ..monad write_artifact!) - (: (Action (List Any)))) + _ (for {@.python (|> output + row.to_list + (list.chunk 128) + (monad.map ! (monad.map ! write_artifact!)) + (: (Action (List (List Any)))))} + (|> output + row.to_list + (monad.map ..monad write_artifact!) + (: (Action (List Any))))) document (\ promise.monad wrap (document.check $.key document))] (ioW.cache system static module_id diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux index 0d18884cb..4e6a9f7ff 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux @@ -251,8 +251,7 @@ (///bundle.install "or" (binary I64* I64* I64)) (///bundle.install "xor" (binary I64* I64* I64)) (///bundle.install "left-shift" (binary Nat I64* I64)) - (///bundle.install "logical-right-shift" (binary Nat I64* I64)) - (///bundle.install "arithmetic-right-shift" (binary Nat I64* I64)) + (///bundle.install "right-shift" (binary Nat I64* I64)) (///bundle.install "=" (binary I64* I64* Bit)) (///bundle.install "<" (binary Int Int Bit)) (///bundle.install "+" (binary I64* I64* I64)) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux index 5c10bbc0f..78e1a4f5a 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux @@ -119,6 +119,10 @@ (for {@.python host.Function} Any)) +(def: Dict + (for {@.python host.Dict} + Any)) + (def: object::get Handler (custom @@ -201,13 +205,15 @@ (def: python::exec Handler (custom - [<c>.any - (function (_ extension phase archive codeC) + [($_ <>.and <c>.any <c>.any) + (function (_ extension phase archive [codeC globalsC]) (do phase.monad [codeA (analysis/type.with_type Text (phase archive codeC)) + globalsA (analysis/type.with_type ..Dict + (phase archive globalsC)) _ (analysis/type.infer .Any)] - (wrap (#analysis.Extension extension (list codeA)))))])) + (wrap (#analysis.Extension extension (list codeA globalsA)))))])) (def: #export bundle Bundle diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux index 4c1ab473f..ca0e8daa9 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux @@ -51,9 +51,8 @@ (Binary Expression) (<op> subjectG (//runtime.i64//to_number paramG)))] - [i64//left_shift //runtime.i64//left_shift] - [i64//arithmetic_right_shift //runtime.i64//arithmetic_right_shift] - [i64//logical_right_shift //runtime.i64//logic_right_shift] + [i64//left_shift //runtime.i64//left_shift] + [i64//right_shift //runtime.i64//right_shift] ) ## [[Numbers]] @@ -139,8 +138,7 @@ (/.install "or" (binary (product.uncurry //runtime.i64//or))) (/.install "xor" (binary (product.uncurry //runtime.i64//xor))) (/.install "left-shift" (binary i64//left_shift)) - (/.install "logical-right-shift" (binary i64//logical_right_shift)) - (/.install "arithmetic-right-shift" (binary i64//arithmetic_right_shift)) + (/.install "right-shift" (binary i64//right_shift)) (/.install "=" (binary (product.uncurry //runtime.i64//=))) (/.install "<" (binary (product.uncurry //runtime.i64//<))) (/.install "+" (binary (product.uncurry //runtime.i64//+))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux index 630e212c3..a9251f4d6 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux @@ -181,9 +181,8 @@ shiftG ..jvm-int <op> (///value.wrap type.long)))] - [i64::left-shift _.lshl] - [i64::arithmetic-right-shift _.lshr] - [i64::logical-right-shift _.lushr] + [i64::left-shift _.lshl] + [i64::right-shift _.lushr] ) (template [<name> <type> <op>] @@ -273,8 +272,7 @@ (/////bundle.install "or" (binary ..i64::or)) (/////bundle.install "xor" (binary ..i64::xor)) (/////bundle.install "left-shift" (binary ..i64::left-shift)) - (/////bundle.install "logical-right-shift" (binary ..i64::logical-right-shift)) - (/////bundle.install "arithmetic-right-shift" (binary ..i64::arithmetic-right-shift)) + (/////bundle.install "right-shift" (binary ..i64::right-shift)) (/////bundle.install "=" (binary ..i64::=)) (/////bundle.install "<" (binary ..i64::<)) (/////bundle.install "+" (binary ..i64::+)) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux index 9657fcb66..285499f13 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux @@ -9,7 +9,7 @@ ["<s>" synthesis (#+ Parser)]]] [data ["." product] - [text + ["." text ["%" format (#+ format)]] [collection ["." dictionary] @@ -101,8 +101,7 @@ (/.install "or" (binary (product.uncurry //runtime.i64//or))) (/.install "xor" (binary (product.uncurry //runtime.i64//xor))) (/.install "left-shift" (binary (product.uncurry //runtime.i64//left_shift))) - (/.install "logical-right-shift" (binary (product.uncurry //runtime.i64//logic_right_shift))) - (/.install "arithmetic-right-shift" (binary (product.uncurry _.bit_shr))) + (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shift))) (/.install "<" (binary (product.uncurry _.<))) (/.install "=" (binary (product.uncurry _.=))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux index fcf35aa99..0c1478eea 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux @@ -142,11 +142,12 @@ (def: python::exec (custom - [<s>.any - (function (_ extension phase archive codeS) + [($_ <>.and <s>.any <s>.any) + (function (_ extension phase archive [codeS globalsS]) (do {! ////////phase.monad} - [codeG (phase archive codeS)] - (wrap (//runtime.lux//exec codeG))))])) + [codeG (phase archive codeS) + globalsG (phase archive globalsS)] + (wrap (//runtime.lux//exec codeG globalsG))))])) (def: #export bundle Bundle diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux index c0f697584..5487cc628 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux @@ -66,7 +66,7 @@ (def: #export high (-> (I64 Any) (I64 Any)) - (i64.logic_right_shift 32)) + (i64.right_shift 32)) (def: #export low (-> (I64 Any) (I64 Any)) @@ -453,7 +453,7 @@ low (|> input (_.the ..i64_high_field) (_.arithmetic_right_shift (_.- (_.i32 +32) shift)))] (_.return (..i64 high low)))))) -(runtime: (i64//logic_right_shift input shift) +(runtime: (i64//right_shift input shift) ($_ _.then (..cap_shift! shift) (_.cond (list (..no_shift! shift input) @@ -476,7 +476,7 @@ @i64//not @i64//left_shift @i64//arithmetic_right_shift - @i64//logic_right_shift + @i64//right_shift )) (runtime: (i64//- parameter subject) @@ -576,7 +576,7 @@ [(i64//= i64//min parameter) (_.return i64//one)]) (with_vars [approximation] - (let [subject/2 (i64//arithmetic_right_shift subject (_.i32 +1))] + (let [subject/2 (..i64//arithmetic_right_shift subject (_.i32 +1))] ($_ _.then (_.define approximation (i64//left_shift (i64/// parameter subject/2) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/case.lux index ddaf1fe5b..a1ae27d5e 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/case.lux @@ -93,7 +93,7 @@ [#.Right //runtime.tuple//right]))] (method source))) valueO - pathP)))) + (list.reverse pathP))))) (def: @savepoint (_.var "lux_pm_savepoint")) (def: @cursor (_.var "lux_pm_cursor")) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index ef213fb2c..f32712fc2 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -155,24 +155,23 @@ (~ code))))))))))))) (runtime: (lux//try op) - (with_vars [error value] - (_.try ($_ _.then - (_.set (list value) (_.apply/* op (list unit))) - (_.return (right value))) - (list [(list (_.var "Exception")) error - (_.return (left (_.str/1 error)))])))) + (with_vars [exception] + (_.try (_.return (..right (_.apply/* op (list ..unit)))) + (list [(list (_.var "Exception")) exception + (_.return (..left (_.str/1 exception)))])))) (runtime: (lux//program_args program_args) (with_vars [inputs value] ($_ _.then (_.set (list inputs) ..none) - (<| (_.for_in value program_args) + (<| (_.for_in value (_.apply/* (_.var "reversed") (list program_args))) (_.set (list inputs) - (..some (_.tuple (list value inputs))))) + (..some (_.list (list value inputs))))) (_.return inputs)))) -(runtime: (lux//exec code) - (<| (_.exec code) +(runtime: (lux//exec code globals) + ($_ _.then + (_.exec code (#.Some globals)) (_.return ..unit))) (def: runtime//lux @@ -304,7 +303,7 @@ ..as_nat ..i64//64))) -(runtime: (i64//logic_right_shift param subject) +(runtime: (i64//right_shift param subject) (_.return (|> subject ..as_nat (_.bit_shr param)))) @@ -328,13 +327,13 @@ @i64//top @i64//bottom @i64//64 - @i64//left_shift - @i64//logic_right_shift @i64//nat_top + @i64//left_shift + @i64//right_shift + @i64//remainder @i64//and @i64//or @i64//xor - @i64//remainder )) (runtime: (f64//decode input) @@ -397,11 +396,11 @@ (Statement Any) ($_ _.then runtime//lux + runtime//io runtime//adt runtime//i64 runtime//f64 runtime//text - runtime//io runtime//array )) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/case.lux index b303a258d..6bc35147b 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -386,13 +386,17 @@ (list\fold for_synthesis synthesis_storage environment) (^ (/.branch/case [inputS pathS])) - (|> synthesis_storage (for_synthesis inputS) (for_path pathS)) + (update@ #dependencies + (set.union (get@ #dependencies (for_path pathS synthesis_storage))) + (for_synthesis inputS synthesis_storage)) (^ (/.branch/let [inputS register exprS])) - (list\fold for_synthesis - (update@ #bindings (set.add (#///reference/variable.Local register)) - synthesis_storage) - (list inputS exprS)) + (update@ #dependencies + (set.union (|> synthesis_storage + (update@ #bindings (set.add (#///reference/variable.Local register))) + (for_synthesis exprS) + (get@ #dependencies))) + (for_synthesis inputS synthesis_storage)) (^ (/.branch/if [testS thenS elseS])) (list\fold for_synthesis synthesis_storage (list testS thenS elseS)) @@ -401,7 +405,15 @@ (for_synthesis whole synthesis_storage) (^ (/.loop/scope [start initsS+ iterationS])) - (list\fold for_synthesis synthesis_storage (#.Cons iterationS initsS+)) + (update@ #dependencies + (set.union (|> synthesis_storage + (update@ #bindings (set.union (|> initsS+ + list.enumeration + (list\map (|>> product.left (n.+ start) #///reference/variable.Local)) + (set.from_list ///reference/variable.hash)))) + (for_synthesis iterationS) + (get@ #dependencies))) + (list\fold for_synthesis synthesis_storage initsS+)) (^ (/.loop/recur replacementsS+)) (list\fold for_synthesis synthesis_storage replacementsS+) diff --git a/stdlib/source/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/lux/tool/compiler/language/lux/syntax.lux index 4bd39b8a9..8362c7054 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/syntax.lux @@ -26,6 +26,7 @@ ## location, which is helpful for documentation and debugging. (.module: [lux #* + ["@" target] [abstract monad] [control @@ -48,6 +49,10 @@ ["." rev] ["." frac]]]]) +(template: (inline: <declaration> <type> <body>) + (for {@.python (def: <declaration> <type> <body>)} + (template: <declaration> <body>))) + ## TODO: Implement "lux syntax char case!" as a custom extension. ## That way, it should be possible to obtain the char without wrapping ## it into a java.lang.Long, thereby improving performance. @@ -61,7 +66,8 @@ ## producing the locations only involved building them, without any need ## for pattern-matching and de-structuring. -(type: Char Nat) +(type: Char + Nat) (template [<name> <extension> <diff>] [(template: (<name> value) @@ -142,8 +148,8 @@ (def: amount_of_input_shown 64) -(template: (input_at start input) - ## (-> Offset Text Text) +(inline: (input_at start input) + (-> Offset Text Text) (let [end (|> start (!n/+ amount_of_input_shown) (n.min ("lux text size" input)))] (!clip start end input))) @@ -194,13 +200,13 @@ (!inc offset) source_code]) -(template: (!new_line where) - ## (-> Location Location) +(inline: (!new_line where) + (-> Location Location) (let [[where::file where::line where::column] where] [where::file (!inc where::line) 0])) -(template: (!forward length where) - ## (-> Nat Location Location) +(inline: (!forward length where) + (-> Nat Location Location) (let [[where::file where::line where::column] where] [where::file where::line (!n/+ length where::column)])) @@ -210,8 +216,9 @@ source_code]) (template [<name> <close> <tag>] - [(template: (<name> parse where offset source_code) - ## (-> (Parser Code) (Parser Code)) + [(inline: (<name> parse where offset source_code) + (-> (Parser Code) Location Offset Text + (Either [Source Text] [Source Code])) (loop [source (: Source [(!forward 1 where) offset source_code]) stack (: (List Code) #.Nil)] (case (parse source) @@ -231,8 +238,9 @@ [parse_tuple ..close_tuple #.Tuple] ) -(template: (parse_record parse where offset source_code) - ## (-> (Parser Code) (Parser Code)) +(inline: (parse_record parse where offset source_code) + (-> (Parser Code) Location Offset Text + (Either [Source Text] [Source Code])) (loop [source (: Source [(!forward 1 where) offset source_code]) stack (: (List [Code Code]) #.Nil)] (case (parse source) @@ -256,7 +264,7 @@ (exception.construct ..text_cannot_contain_new_lines content)]))) (def: (parse_text where offset source_code) - (-> Location Nat Text (Either [Source Text] [Source Code])) + (-> Location Offset Text (Either [Source Text] [Source Code])) (case ("lux text index" offset (static ..text_delimiter) source_code) (#.Some g!end) (<| (let [g!content (!clip offset g!end source_code)]) @@ -346,8 +354,9 @@ [..positive_sign] [..negative_sign])] - (template: (parse_frac source_code//size start where offset source_code) - ## (-> Nat Offset (Parser Code)) + (inline: (parse_frac source_code//size start where offset source_code) + (-> Nat Nat Location Offset Text + (Either [Source Text] [Source Code])) (loop [end offset exponent (static ..no_exponent)] (<| (!with_char+ source_code//size source_code end char/0 <frac_output>) @@ -370,8 +379,9 @@ <frac_output>)))) - (template: (parse_signed source_code//size start where offset source_code) - ## (-> Nat Offset (Parser Code)) + (inline: (parse_signed source_code//size start where offset source_code) + (-> Nat Nat Location Offset Text + (Either [Source Text] [Source Code])) (loop [end offset] (<| (!with_char+ source_code//size source_code end char <int_output>) (!if_digit?+ char @@ -384,8 +394,9 @@ ) (template [<parser> <codec> <tag>] - [(template: (<parser> source_code//size start where offset source_code) - ## (-> Nat Nat Location Nat Text (Either [Source Text] [Source Code])) + [(inline: (<parser> source_code//size start where offset source_code) + (-> Nat Nat Location Offset Text + (Either [Source Text] [Source Code])) (loop [g!end offset] (<| (!with_char+ source_code//size source_code g!end g!char (!number_output source_code start g!end <codec> <tag>)) (!if_digit?+ g!char @@ -408,8 +419,9 @@ end source_code] (!clip start end source_code)])] - (template: (parse_name_part start where offset source_code) - ## (-> Offset (Parser Text)) + (inline: (parse_name_part start where offset source_code) + (-> Nat Location Offset Text + (Either [Source Text] [Source Text])) (let [source_code//size ("lux text size" source_code)] (loop [end offset] (<| (!with_char+ source_code//size source_code end char <output>) |