diff options
author | Eduardo Julián | 2019-04-04 21:10:23 -0400 |
---|---|---|
committer | GitHub | 2019-04-04 21:10:23 -0400 |
commit | 0416ecd9dd79ea8a2d536c11596fc5c60679f6e2 (patch) | |
tree | 9ac14be1804e9ba53fd5899ff161d028f7499ff4 /stdlib/source/lux/tool | |
parent | b4c19578ca9d91c34c5aaba567fadb028a1ec877 (diff) | |
parent | 721e791b9273bb77b762a4dd48b085efc7bedd9b (diff) |
Merge pull request #49 from LuxLang/change-order-of-parameters-in-extensions
Change order of parameters in extensions
Diffstat (limited to '')
7 files changed, 92 insertions, 92 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/syntax.lux b/stdlib/source/lux/tool/compiler/default/syntax.lux index 5f894622b..512c19246 100644 --- a/stdlib/source/lux/tool/compiler/default/syntax.lux +++ b/stdlib/source/lux/tool/compiler/default/syntax.lux @@ -59,7 +59,7 @@ (template [<name> <extension> <diff>] [(template: (<name> value) - (<extension> value <diff>))] + (<extension> <diff> value))] [!inc "lux i64 +" 1] [!inc/2 "lux i64 +" 2] @@ -67,11 +67,11 @@ ) (template: (!clip from to text) - ("lux text clip" text from to)) + ("lux text clip" from to text)) (template [<name> <extension>] [(template: (<name> reference subject) - (<extension> subject reference))] + (<extension> reference subject))] [!n/= "lux i64 ="] [!i/< "lux int <"] @@ -79,7 +79,7 @@ (template [<name> <extension>] [(template: (<name> param subject) - (<extension> subject param))] + (<extension> param subject))] [!n/+ "lux i64 +"] [!n/- "lux i64 -"] @@ -155,7 +155,7 @@ (template: (!with-char+ @source-code-size @source-code @offset @char @else @body) (if (!i/< (:coerce Int @source-code-size) (:coerce Int @offset)) - (let [@char ("lux text char" @source-code @offset)] + (let [@char ("lux text char" @offset @source-code)] @body) @else)) @@ -235,7 +235,7 @@ (#error.Failure error)))))))) (template: (!guarantee-no-new-lines content body) - (case ("lux text index" content (static text.new-line) 0) + (case ("lux text index" 0 (static text.new-line) content) #.None body @@ -243,7 +243,7 @@ (ex.throw ..text-cannot-contain-new-lines content))) (template: (!read-text where offset source-code) - (case ("lux text index" source-code (static ..text-delimiter) offset) + (case ("lux text index" offset (static ..text-delimiter) source-code) (#.Some g!end) (let [g!content (!clip offset g!end source-code)] (<| (!guarantee-no-new-lines g!content) @@ -505,7 +505,7 @@ ## Single-line comment [(~~ (static ..sigil))] - (case ("lux text index" source-code (static text.new-line) (!inc offset/1)) + (case ("lux text index" (!inc offset/1) (static text.new-line) source-code) (#.Some end) (recur [(!new-line where) (!inc end) source-code]) diff --git a/stdlib/source/lux/tool/compiler/name.lux b/stdlib/source/lux/tool/compiler/name.lux index f65113d38..d2841d849 100644 --- a/stdlib/source/lux/tool/compiler/name.lux +++ b/stdlib/source/lux/tool/compiler/name.lux @@ -40,7 +40,7 @@ output ""] (if (n/< name/size idx) (recur (inc idx) - (|> ("lux text char" name idx) !sanitize (format output))) + (|> name ("lux text char" idx) !sanitize (format output))) output)))) (def: #export (definition [module short]) diff --git a/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux b/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux index 18ac68d99..9940273cc 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux @@ -201,10 +201,10 @@ (///bundle.install "=" (binary Text Text Bit)) (///bundle.install "<" (binary Text Text Bit)) (///bundle.install "concat" (binary Text Text Text)) - (///bundle.install "index" (trinary Text Text Nat (type (Maybe Nat)))) + (///bundle.install "index" (trinary Nat Text Text (type (Maybe Nat)))) (///bundle.install "size" (unary Text Nat)) - (///bundle.install "char" (binary Text Nat Nat)) - (///bundle.install "clip" (trinary Text Nat Nat Text)) + (///bundle.install "char" (binary Nat Text Nat)) + (///bundle.install "clip" (trinary Nat Nat Text Text)) ))) (def: #export (bundle eval) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux index 9a065a73e..2ee78f394 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux @@ -60,18 +60,17 @@ (_.apply/* (_.var "String.fromCharCode")))) ## [[Text]] -(def: (text//concat [subjectG paramG]) +(def: (text//concat [leftG rightG]) (Binary Expression) - (|> subjectG (_.do "concat" (list paramG)))) + (|> leftG (_.do "concat" (list rightG)))) -(template [<name> <runtime>] - [(def: (<name> [subjectG paramG extraG]) - (Trinary Expression) - (<runtime> subjectG paramG extraG))] +(def: (text//clip [startG endG subjectG]) + (Trinary Expression) + (///runtime.text//clip startG endG subjectG)) - [text//clip ///runtime.text//clip] - [text//index ///runtime.text//index] - ) +(def: (text//index [startG partG subjectG]) + (Trinary Expression) + (///runtime.text//index startG partG subjectG)) ## [[IO]] (def: (io//log messageG) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux index 8dcdb866a..821633e50 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux @@ -278,13 +278,13 @@ (runtime: i64//one (i64//new (_.i32 +0) (_.i32 +1))) -(runtime: (i64//= left right) - (_.return (_.and (_.= (_.the ..i64-high-field left) - (_.the ..i64-high-field right)) - (_.= (_.the ..i64-low-field left) - (_.the ..i64-low-field right))))) +(runtime: (i64//= reference sample) + (_.return (_.and (_.= (_.the ..i64-high-field reference) + (_.the ..i64-high-field sample)) + (_.= (_.the ..i64-low-field reference) + (_.the ..i64-low-field sample))))) -(runtime: (i64//+ subject parameter) +(runtime: (i64//+ parameter subject) (let [up-16 (_.left-shift (_.i32 +16)) high-16 (_.logic-right-shift (_.i32 +16)) low-16 (_.bit-and (_.i32 (hex "+FFFF"))) @@ -339,7 +339,7 @@ (runtime: (i64//negate value) (_.if (i64//= i64//min value) (_.return i64//min) - (_.return (i64//+ (i64//not value) i64//one)))) + (_.return (i64//+ i64//one (i64//not value))))) (runtime: i64//-one (i64//negate i64//one)) @@ -422,20 +422,20 @@ @i64//logic-right-shift )) -(runtime: (i64//- subject parameter) - (_.return (i64//+ subject (i64//negate parameter)))) +(runtime: (i64//- parameter subject) + (_.return (i64//+ (i64//negate parameter) subject))) -(runtime: (i64//* subject parameter) +(runtime: (i64//* parameter subject) (let [negative? (|>> (_.the ..i64-high-field) (_.< (_.i32 +0)))] (_.cond (list [(negative? subject) (_.if (negative? parameter) ## Both are negative - (_.return (i64//* (i64//negate subject) (i64//negate parameter))) + (_.return (i64//* (i64//negate parameter) (i64//negate subject))) ## Subject is negative - (_.return (i64//negate (i64//* (i64//negate subject) parameter))))] + (_.return (i64//negate (i64//* parameter (i64//negate subject)))))] [(negative? parameter) ## Parameter is negative - (_.return (i64//negate (i64//* subject (i64//negate parameter))))]) + (_.return (i64//negate (i64//* (i64//negate parameter) subject)))]) ## Both are positive (let [up-16 (_.left-shift (_.i32 +16)) high-16 (_.logic-right-shift (_.i32 +16)) @@ -485,7 +485,7 @@ (_.bit-or (up-16 x16) x00))) )))))) -(runtime: (i64//< subject parameter) +(runtime: (i64//< parameter subject) (let [negative? (|>> (_.the ..i64-high-field) (_.< (_.i32 +0)))] (with-vars [-subject? -parameter?] ($_ _.then @@ -495,16 +495,16 @@ (_.return _.true)] [(_.and (_.not -subject?) -parameter?) (_.return _.false)]) - (_.return (negative? (i64//- subject parameter)))))))) + (_.return (negative? (i64//- parameter subject)))))))) -(def: (i64//<= subject param) +(def: (i64//<= param subject) (-> Expression Expression Expression) - (_.or (i64//< subject param) - (i64//= subject param))) + (_.or (i64//< param subject) + (i64//= param subject))) -(runtime: (i64/// subject parameter) +(runtime: (i64/// parameter subject) (let [negative? (function (_ value) - (i64//< value i64//zero)) + (i64//< i64//zero value)) valid-division-check [(i64//= i64//zero parameter) (_.throw (_.string "Cannot divide by zero!"))] short-circuit-check [(i64//= i64//zero subject) @@ -521,39 +521,39 @@ (with-vars [approximation] (let [subject/2 (i64//arithmetic-right-shift subject (_.i32 +1))] ($_ _.then - (_.define approximation (i64//left-shift (i64/// subject/2 - parameter) + (_.define approximation (i64//left-shift (i64/// parameter + subject/2) (_.i32 +1))) (_.if (i64//= i64//zero approximation) (_.return (_.? (negative? parameter) i64//one i64//-one)) - (let [remainder (i64//- subject - (i64//* parameter - approximation))] - (_.return (i64//+ approximation - (i64/// remainder - parameter)))))))))] + (let [remainder (i64//- (i64//* approximation + parameter) + subject)] + (_.return (i64//+ (i64/// parameter + remainder) + approximation))))))))] [(i64//= i64//min parameter) (_.return i64//zero)] [(negative? subject) (_.return (_.? (negative? parameter) - (i64/// (i64//negate subject) - (i64//negate parameter)) - (i64//negate (i64/// (i64//negate subject) - parameter))))] + (i64/// (i64//negate parameter) + (i64//negate subject)) + (i64//negate (i64/// parameter + (i64//negate subject)))))] [(negative? parameter) - (_.return (i64//negate (i64/// subject (i64//negate parameter))))]) + (_.return (i64//negate (i64/// (i64//negate parameter) subject)))]) (with-vars [result remainder] ($_ _.then (_.define result i64//zero) (_.define remainder subject) - (_.while (i64//<= parameter remainder) + (_.while (i64//<= remainder parameter) (with-vars [approximate approximate-result approximate-remainder log2 delta] (let [approximate-result' (i64//from-number approximate) - approx-remainder (i64//* approximate-result parameter)] + approx-remainder (i64//* parameter approximate-result)] ($_ _.then (_.define approximate (|> (i64//to-number remainder) (_./ (i64//to-number parameter)) @@ -572,24 +572,25 @@ (_.define approximate-result approximate-result') (_.define approximate-remainder approx-remainder) (_.while (_.or (negative? approximate-remainder) - (i64//< remainder - approximate-remainder)) + (i64//< approximate-remainder + remainder)) ($_ _.then (_.set approximate (_.- delta approximate)) (_.set approximate-result approximate-result') (_.set approximate-remainder approx-remainder))) - (_.set result (i64//+ result - (_.? (i64//= i64//zero approximate-result) + (_.set result (i64//+ (_.? (i64//= i64//zero approximate-result) i64//one - approximate-result))) - (_.set remainder (i64//- remainder approximate-remainder)))))) + approximate-result) + result)) + (_.set remainder (i64//- approximate-remainder remainder)))))) (_.return result))) ))) -(runtime: (i64//% subject parameter) - (let [flat (i64//* (i64/// subject parameter) - parameter)] - (_.return (i64//- subject flat)))) +(runtime: (i64//% parameter subject) + (let [flat (|> subject + (i64/// parameter) + (i64//* parameter))] + (_.return (i64//- flat subject)))) (def: runtime//i64 Statement @@ -617,7 +618,7 @@ runtime//bit )) -(runtime: (text//index text part start) +(runtime: (text//index start part text) (with-vars [idx] ($_ _.then (_.define idx (|> text (_.do "indexOf" (list part (i64//to-number start))))) @@ -625,11 +626,11 @@ (_.return ..none) (_.return (..some (i64//from-number idx))))))) -(runtime: (text//clip text start end) +(runtime: (text//clip start end text) (_.return (|> text (_.do "substring" (list (_.the ..i64-low-field start) (_.the ..i64-low-field end)))))) -(runtime: (text//char text idx) +(runtime: (text//char idx text) (with-vars [result] ($_ _.then (_.define result (|> text (_.do "charCodeAt" (list (_.the ..i64-low-field idx))))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/python/extension/common.lux b/stdlib/source/lux/tool/compiler/phase/generation/python/extension/common.lux index 43ebd105f..7ff70b393 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/python/extension/common.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/python/extension/common.lux @@ -29,15 +29,15 @@ Bundle (<| (bundle.prefix "i64") (|> bundle.empty - (bundle.install "and" (binary (product.uncurry (function.flip _.bit-and)))) - (bundle.install "or" (binary (product.uncurry (function.flip _.bit-or)))) - (bundle.install "xor" (binary (product.uncurry (function.flip _.bit-xor)))) + (bundle.install "and" (binary (product.uncurry _.bit-and))) + (bundle.install "or" (binary (product.uncurry _.bit-or))) + (bundle.install "xor" (binary (product.uncurry _.bit-xor))) (bundle.install "left-shift" (binary (function.compose ///runtime.i64//64 (product.uncurry _.bit-shl)))) (bundle.install "logical-right-shift" (binary (product.uncurry ///runtime.i64//logic-right-shift))) (bundle.install "arithmetic-right-shift" (binary (product.uncurry _.bit-shr))) - (bundle.install "=" (binary (product.uncurry (function.flip _.=)))) - (bundle.install "+" (binary (product.uncurry (function.flip _.+)))) - (bundle.install "-" (binary (product.uncurry (function.flip _.-)))) + (bundle.install "=" (binary (product.uncurry _.=))) + (bundle.install "+" (binary (product.uncurry _.+))) + (bundle.install "-" (binary (product.uncurry _.-))) ))) (import: #long java/lang/Double @@ -58,10 +58,10 @@ Bundle (<| (bundle.prefix "int") (|> bundle.empty - (bundle.install "<" (binary (product.uncurry (function.flip _.<)))) - (bundle.install "*" (binary (product.uncurry (function.flip _.*)))) - (bundle.install "/" (binary (product.uncurry (function.flip _./)))) - (bundle.install "%" (binary (product.uncurry (function.flip _.%)))) + (bundle.install "<" (binary (product.uncurry _.<))) + (bundle.install "*" (binary (product.uncurry _.*))) + (bundle.install "/" (binary (product.uncurry _./))) + (bundle.install "%" (binary (product.uncurry _.%))) (bundle.install "frac" (unary _.float/1)) (bundle.install "char" (unary _.chr/1))))) @@ -69,13 +69,13 @@ Bundle (<| (bundle.prefix "frac") (|> bundle.empty - (bundle.install "+" (binary (product.uncurry (function.flip _.+)))) - (bundle.install "-" (binary (product.uncurry (function.flip _.-)))) - (bundle.install "*" (binary (product.uncurry (function.flip _.*)))) - (bundle.install "/" (binary (product.uncurry (function.flip _./)))) - (bundle.install "%" (binary (product.uncurry (function.flip _.%)))) - (bundle.install "=" (binary (product.uncurry (function.flip _.=)))) - (bundle.install "<" (binary (product.uncurry (function.flip _.<)))) + (bundle.install "+" (binary (product.uncurry _.+))) + (bundle.install "-" (binary (product.uncurry _.-))) + (bundle.install "*" (binary (product.uncurry _.*))) + (bundle.install "/" (binary (product.uncurry _./))) + (bundle.install "%" (binary (product.uncurry _.%))) + (bundle.install "=" (binary (product.uncurry _.=))) + (bundle.install "<" (binary (product.uncurry _.<))) (bundle.install "smallest" (nullary frac//smallest)) (bundle.install "min" (nullary frac//min)) (bundle.install "max" (nullary frac//max)) @@ -87,11 +87,11 @@ (Binary (Expression Any)) (///runtime.text//char subjectO paramO)) -(def: (text//clip [subjectO paramO extraO]) +(def: (text//clip [paramO extraO subjectO]) (Trinary (Expression Any)) (///runtime.text//clip subjectO paramO extraO)) -(def: (text//index [textO partO startO]) +(def: (text//index [startO partO textO]) (Trinary (Expression Any)) (///runtime.text//index textO partO startO)) @@ -99,9 +99,9 @@ Bundle (<| (bundle.prefix "text") (|> bundle.empty - (bundle.install "=" (binary (product.uncurry (function.flip _.=)))) - (bundle.install "<" (binary (product.uncurry (function.flip _.<)))) - (bundle.install "concat" (binary (product.uncurry (function.flip _.+)))) + (bundle.install "=" (binary (product.uncurry _.=))) + (bundle.install "<" (binary (product.uncurry _.<))) + (bundle.install "concat" (binary (product.uncurry _.+))) (bundle.install "index" (trinary text//index)) (bundle.install "size" (unary _.len/1)) (bundle.install "char" (binary (product.uncurry ///runtime.text//char))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux index a8f601922..36184e21c 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux @@ -308,7 +308,7 @@ (runtime: (text//clip @text @from @to) (_.return (|> @text (_.slice @from (inc @to))))) -(runtime: (text//char text idx) +(runtime: (text//char idx text) (_.if (|> idx (within? (_.len/1 text))) (_.return (..some (_.ord/1 (|> text (_.slice idx (inc idx)))))) (_.return ..none))) |