diff options
author | Eduardo Julian | 2020-11-17 20:23:53 -0400 |
---|---|---|
committer | Eduardo Julian | 2020-11-17 20:23:53 -0400 |
commit | d89d837de3475b75587a4293e094d755d2cd4626 (patch) | |
tree | 0975a487d987cfe855c4f6e87f05478346913a16 /stdlib/source/lux/tool | |
parent | 2e5852abb1ac0ae5abdd8709238aca447f62520e (diff) |
Made the syntax of ^template more consistent.
Diffstat (limited to '')
38 files changed, 436 insertions, 436 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/init.lux b/stdlib/source/lux/tool/compiler/default/init.lux index 441be4bed..43614dce3 100644 --- a/stdlib/source/lux/tool/compiler/default/init.lux +++ b/stdlib/source/lux/tool/compiler/default/init.lux @@ -9,13 +9,13 @@ [data [binary (#+ Binary)] ["." product] - ["." text ("#//." hash) + ["." text ("#\." hash) ["%" format (#+ format)]] [collection - ["." list ("#//." functor)] + ["." list ("#\." functor)] ["." dictionary] ["." set] - ["." row ("#//." functor)]]] + ["." row ("#\." functor)]]] ["." meta] [world ["." file]]] @@ -208,7 +208,7 @@ (def: (default-dependencies prelude input) (-> Module ///.Input (List Module)) (list& archive.runtime-module - (if (text//= prelude (get@ #///.module input)) + (if (text\= prelude (get@ #///.module input)) (list) (list prelude)))) @@ -226,7 +226,7 @@ {#///.dependencies dependencies #///.process (function (_ state archive) (do {! try.monad} - [#let [hash (text//hash (get@ #///.code input))] + [#let [hash (text\hash (get@ #///.code input))] [state [source buffer]] (<| (///phase.run' state) (..begin dependencies hash input)) #let [module (get@ #///.module input)]] @@ -247,15 +247,15 @@ (wrap [state (#.Right [[descriptor (document.write key analysis-module)] (|> final-buffer - (row//map (function (_ [name directive]) - [name (write-directive directive)])))])])) + (row\map (function (_ [name directive]) + [name (write-directive directive)])))])])) (#.Some [source requirements temporary-payload]) (let [[temporary-buffer temporary-registry] temporary-payload] (wrap [state (#.Left {#///.dependencies (|> requirements (get@ #///directive.imports) - (list//map product.left)) + (list\map product.left)) #///.process (function (_ state archive) (recur (<| (///phase.run' state) (do {! ///phase.monad} diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux index 3e9d7a647..b2225c718 100644 --- a/stdlib/source/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/lux/tool/compiler/default/platform.lux @@ -9,20 +9,20 @@ ["." try (#+ Try)] ["." exception (#+ exception:)] [concurrency - ["." promise (#+ Promise Resolver) ("#//." monad)] + ["." promise (#+ Promise Resolver) ("#\." monad)] ["." stm (#+ Var STM)]]] [data ["." binary (#+ Binary)] ["." bit] ["." product] ["." maybe] - ["." text ("#//." equivalence) + ["." text ("#\." equivalence) ["%" format (#+ format)]] [collection ["." dictionary (#+ Dictionary)] - ["." row (#+ Row) ("#//." fold)] + ["." row (#+ Row) ("#\." fold)] ["." set (#+ Set)] - ["." list ("#//." monoid functor fold)]] + ["." list ("#\." monoid functor fold)]] [format ["_" binary (#+ Writer)]]] [world @@ -210,13 +210,13 @@ extender)] _ (ioW.enable (get@ #&file-system platform) static) [archive analysis-state bundles] (ioW.thaw (get@ #host platform) (get@ #&file-system platform) static import compilation-sources) - state (promise//wrap (initialize-state extender bundles analysis-state state))] + state (promise\wrap (initialize-state extender bundles analysis-state state))] (if (archive.archived? archive archive.runtime-module) (wrap [state archive]) (do (try.with promise.monad) [[state [archive payload]] (|> (..process-runtime archive platform) (///phase.run' state) - promise//wrap) + promise\wrap) _ (..cache-module static platform 0 payload)] (wrap [state archive]))))) @@ -228,9 +228,9 @@ #///directive.state #extension.state #///generation.log]) - (row//fold (function (_ right left) - (format left text.new-line right)) - ""))) + (row\fold (function (_ right left) + (format left text.new-line right)) + ""))) (def: with-reset-log (All [<type-vars>] @@ -277,10 +277,10 @@ (|> mapping (dictionary.upsert source ..empty (set.add target)) (dictionary.update source (set.union forward)))] - (list//fold (function (_ previous) - (dictionary.upsert previous ..empty (set.add target))) - with-dependence+transitives - (set.to-list backward))))))] + (list\fold (function (_ previous) + (dictionary.upsert previous ..empty (set.add target))) + with-dependence+transitives + (set.to-list backward))))))] (|> dependence (update@ #depends-on (update-dependence @@ -315,7 +315,7 @@ (def: (verify-dependencies importer importee dependence) (-> Module Module Dependence (Try Any)) - (cond (text//= importer importee) + (cond (text\= importer importee) (exception.throw ..module-cannot-import-itself [importer]) (..circular-dependency? importer importee dependence) @@ -355,7 +355,7 @@ (:assume (stm.commit (do {! stm.monad} - [dependence (if (text//= archive.runtime-module importer) + [dependence (if (text\= archive.runtime-module importer) (stm.read dependence) (do ! [[_ dependence] (stm.update (..depend importer module) dependence)] @@ -369,7 +369,7 @@ (do ! [[archive state] (stm.read current)] (if (archive.archived? archive module) - (wrap [(promise//wrap (#try.Success [archive state])) + (wrap [(promise\wrap (#try.Success [archive state])) #.None]) (do ! [@pending (stm.read pending)] @@ -399,7 +399,7 @@ signal])])) (#try.Failure error) - (wrap [(promise//wrap (#try.Failure error)) + (wrap [(promise\wrap (#try.Failure error)) #.None]))))))))))}) _ (case signal #.None @@ -435,7 +435,7 @@ (wrap [module lux-module]))) (archive.archived archive)) #let [additions (|> modules - (list//map product.left) + (list\map product.left) (set.from-list text.hash))]] (wrap (update@ [#extension.state #///directive.analysis @@ -445,11 +445,11 @@ (|> analysis-state (:coerce .Lux) (update@ #.modules (function (_ current) - (list//compose (list.filter (|>> product.left - (set.member? additions) - not) - current) - modules))) + (list\compose (list.filter (|>> product.left + (set.member? additions) + not) + current) + modules))) :assume)) state)))) @@ -486,7 +486,7 @@ all-dependencies (: (List Module) (list))] (let [new-dependencies (get@ #///.dependencies compilation) - all-dependencies (list//compose new-dependencies all-dependencies) + all-dependencies (list\compose new-dependencies all-dependencies) continue! (:share [<type-vars>] {<Platform> platform} @@ -502,11 +502,11 @@ (#.Cons _) (do ! [archive,document+ (|> new-dependencies - (list//map (import! module)) + (list\map (import! module)) (monad.seq ..monad)) #let [archive (|> archive,document+ - (list//map product.left) - (list//fold archive.merge archive))]] + (list\map product.left) + (list\fold archive.merge archive))]] (wrap [archive (try.assume (..updated-state archive state))])))] (case ((get@ #///.process compilation) @@ -533,11 +533,11 @@ (..with-reset-log state)]) (#try.Failure error) - (promise//wrap (#try.Failure error))))) + (promise\wrap (#try.Failure error))))) (#try.Failure error) (do ! [_ (ioW.freeze (get@ #&file-system platform) static archive)] - (promise//wrap (#try.Failure error))))))))))] + (promise\wrap (#try.Failure error))))))))))] (compiler archive.runtime-module compilation-module))) )) diff --git a/stdlib/source/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/lux/tool/compiler/language/lux/analysis.lux index 18189b405..07cd29140 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/analysis.lux @@ -29,9 +29,9 @@ [/// [arity (#+ Arity)] [version (#+ Version)] + ["." phase] ["." reference (#+ Reference) - ["." variable (#+ Register Variable)]] - ["." phase]]]) + ["." variable (#+ Register Variable)]]]]) (type: #export #rec Primitive #Unit @@ -114,8 +114,8 @@ true (^template [<tag> <=>] - [(<tag> reference) (<tag> sample)] - (<=> reference sample)) + [[(<tag> reference) (<tag> sample)] + (<=> reference sample)]) ([#Bit bit@=] [#Nat n.=] [#Int i.=] @@ -336,8 +336,8 @@ "[]" (^template [<tag> <format>] - (<tag> value) - (<format> value)) + [(<tag> value) + (<format> value)]) ([#Bit %.bit] [#Nat %.nat] [#Int %.int] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis.lux index 2d3b61280..3d71e7c51 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis.lux @@ -40,8 +40,8 @@ (Fix (-> (Code' (Ann Location)) (Operation Analysis))) (case code' (^template [<tag> <analyser>] - (<tag> value) - (<analyser> value)) + [(<tag> value) + (<analyser> value)]) ([#.Bit /primitive.bit] [#.Nat /primitive.nat] [#.Int /primitive.int] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux index 2996ed6d0..b71d60f05 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -169,8 +169,8 @@ (wrap [(#/.Bind idx) outputA]))) (^template [<type> <input> <output>] - [location <input>] - (analyse-primitive <type> inputT location (#/.Simple <output>) next)) + [[location <input>] + (analyse-primitive <type> inputT location (#/.Simple <output>) next)]) ([Bit (#.Bit pattern-value) (#/.Bit pattern-value)] [Nat (#.Nat pattern-value) (#/.Nat pattern-value)] [Int (#.Int pattern-value) (#/.Int pattern-value)] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux index 792a779ab..9d1c396e9 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux @@ -102,8 +102,8 @@ ## Primitive patterns always have partial coverage because there ## are too many possibilities as far as values go. (^template [<tag>] - (#/.Simple (<tag> _)) - (////@wrap #Partial)) + [(#/.Simple (<tag> _)) + (////@wrap #Partial)]) ([#/.Nat] [#/.Int] [#/.Rev] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux index e06265806..6ad18d63d 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -60,10 +60,10 @@ (/.fail (ex.construct cannot-analyse [expectedT function-name arg-name body]))) (^template [<tag> <instancer>] - (<tag> _) - (do ! - [[_ instanceT] (//type.with-env <instancer>)] - (recur (maybe.assume (type.apply (list instanceT) expectedT))))) + [(<tag> _) + (do ! + [[_ instanceT] (//type.with-env <instancer>)] + (recur (maybe.assume (type.apply (list instanceT) expectedT))))]) ([#.UnivQ check.existential] [#.ExQ check.var]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/inference.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/inference.lux index 839fe1617..7c4d49340 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/inference.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/inference.lux @@ -63,9 +63,9 @@ (#.Primitive name (list@map (replace parameter-idx replacement) params)) (^template [<tag>] - (<tag> left right) - (<tag> (replace parameter-idx replacement left) - (replace parameter-idx replacement right))) + [(<tag> left right) + (<tag> (replace parameter-idx replacement left) + (replace parameter-idx replacement right))]) ([#.Sum] [#.Product] [#.Function] @@ -77,9 +77,9 @@ type) (^template [<tag>] - (<tag> env quantified) - (<tag> (list@map (replace parameter-idx replacement) env) - (replace (n.+ 2 parameter-idx) replacement quantified))) + [(<tag> env quantified) + (<tag> (list@map (replace parameter-idx replacement) env) + (replace (n.+ 2 parameter-idx) replacement quantified))]) ([#.UnivQ] [#.ExQ]) @@ -184,8 +184,8 @@ (#.Primitive name (list@map recur parameters)) (^template [<tag>] - (<tag> left right) - (<tag> (recur left) (recur right))) + [(<tag> left right) + (<tag> (recur left) (recur right))]) ([#.Sum] [#.Product] [#.Function] [#.Apply]) (#.Parameter index) @@ -194,8 +194,8 @@ base) (^template [<tag>] - (<tag> environment quantified) - (<tag> (list@map recur environment) quantified)) + [(<tag> environment quantified) + (<tag> (list@map recur environment) quantified)]) ([#.UnivQ] [#.ExQ]) _ @@ -209,10 +209,10 @@ (record' target originalT unnamedT) (^template [<tag>] - (<tag> env bodyT) - (do ///.monad - [bodyT+ (record' (n.+ 2 target) originalT bodyT)] - (wrap (<tag> env bodyT+)))) + [(<tag> env bodyT) + (do ///.monad + [bodyT+ (record' (n.+ 2 target) originalT bodyT)] + (wrap (<tag> env bodyT+)))]) ([#.UnivQ] [#.ExQ]) @@ -248,10 +248,10 @@ (wrap unnamedT+)) (^template [<tag>] - (<tag> env bodyT) - (do ///.monad - [bodyT+ (recur (inc depth) bodyT)] - (wrap (<tag> env bodyT+)))) + [(<tag> env bodyT) + (do ///.monad + [bodyT+ (recur (inc depth) bodyT)] + (wrap (<tag> env bodyT+)))]) ([#.UnivQ] [#.ExQ]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/structure.lux index 3f8f023aa..03ce1c90b 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -130,11 +130,11 @@ (/.throw ..cannot-infer-numeric-tag [expectedT tag valueC]))) (^template [<tag> <instancer>] - (<tag> _) - (do ! - [[instance-id instanceT] (//type.with-env <instancer>)] - (//type.with-type (maybe.assume (type.apply (list instanceT) expectedT)) - (recur valueC)))) + [(<tag> _) + (do ! + [[instance-id instanceT] (//type.with-env <instancer>)] + (//type.with-type (maybe.assume (type.apply (list instanceT) expectedT)) + (recur valueC)))]) ([#.UnivQ check.existential] [#.ExQ check.var]) @@ -223,11 +223,11 @@ (wrap (/.tuple (list@map product.right membersTA)))))) (^template [<tag> <instancer>] - (<tag> _) - (do ! - [[instance-id instanceT] (//type.with-env <instancer>)] - (//type.with-type (maybe.assume (type.apply (list instanceT) expectedT)) - (product archive analyse membersC)))) + [(<tag> _) + (do ! + [[instance-id instanceT] (//type.with-env <instancer>)] + (//type.with-type (maybe.assume (type.apply (list instanceT) expectedT)) + (product archive analyse membersC)))]) ([#.UnivQ check.existential] [#.ExQ check.var]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index cd8784056..618fbbfc9 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -418,14 +418,14 @@ (check-parameter anonymous) (^template [<tag>] - (<tag> id) - (phase@wrap (jvm.class ..object-class (list)))) + [(<tag> id) + (phase@wrap (jvm.class ..object-class (list)))]) ([#.Var] [#.Ex]) (^template [<tag>] - (<tag> env unquantified) - (check-parameter unquantified)) + [(<tag> env unquantified) + (check-parameter unquantified)]) ([#.UnivQ] [#.ExQ]) @@ -493,8 +493,8 @@ (check-jvm anonymous) (^template [<tag>] - (<tag> env unquantified) - (check-jvm unquantified)) + [(<tag> env unquantified) + (check-jvm unquantified)]) ([#.UnivQ] [#.ExQ]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux index b86c2488c..8f44551d1 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux @@ -187,11 +187,11 @@ (#Constant [name annotations type value]) (case value (^template [<tag> <type> <constant>] - [_ (<tag> value)] - (do pool.monad - [constant (`` (|> value (~~ (template.splice <constant>)))) - attribute (attribute.constant constant)] - (field.field ..constant::modifier name <type> (row.row attribute)))) + [[_ (<tag> value)] + (do pool.monad + [constant (`` (|> value (~~ (template.splice <constant>)))) + attribute (attribute.constant constant)] + (field.field ..constant::modifier name <type> (row.row attribute)))]) ([#.Bit type.boolean [(case> #0 +0 #1 +1) .i64 i32.i32 constant.integer pool.integer]] [#.Int type.byte [.i64 i32.i32 constant.integer pool.integer]] [#.Int type.short [.i64 i32.i32 constant.integer pool.integer]] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index f0f2fa635..e584bd1e4 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -854,14 +854,14 @@ (//////synthesis.path/then (normalize bodyS)) (^template [<tag>] - (^ (<tag> leftP rightP)) - (<tag> (recur leftP) (recur rightP))) + [(^ (<tag> leftP rightP)) + (<tag> (recur leftP) (recur rightP))]) ([#//////synthesis.Alt] [#//////synthesis.Seq]) (^template [<tag>] - (^ (<tag> value)) - path) + [(^ (<tag> value)) + path]) ([#//////synthesis.Pop] [#//////synthesis.Bind] [#//////synthesis.Access]) @@ -874,8 +874,8 @@ (function (recur body) (case body (^template [<tag>] - (^ (<tag> value)) - body) + [(^ (<tag> value)) + body]) ([#//////synthesis.Primitive] [//////synthesis.constant]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp.lux index 6d3500416..ad04cefdb 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp.lux @@ -20,8 +20,8 @@ Phase (case synthesis (^template [<tag> <generator>] - (^ (<tag> value)) - (:: ///.monad wrap (<generator> value))) + [(^ (<tag> value)) + (:: ///.monad wrap (<generator> value))]) ([synthesis.bit primitive.bit] [synthesis.i64 primitive.i64] [synthesis.f64 primitive.f64] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/case.lux index 6fdb37e34..dcd47a26d 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/case.lux @@ -49,8 +49,8 @@ (wrap (list@fold (function (_ side source) (.let [method (.case side (^template [<side> <accessor>] - (<side> lefts) - (<accessor> (_.int (.int lefts)))) + [(<side> lefts) + (<accessor> (_.int (.int lefts)))]) ([#.Left //runtime.tuple//left] [#.Right //runtime.tuple//right]))] (method source))) @@ -143,23 +143,23 @@ (////@wrap (_.setq (..register register) ..peek)) (^template [<tag> <format> <=>] - (^ (<tag> value)) - (////@wrap (_.if (|> value <format> (<=> ..peek)) - _.nil - fail!))) + [(^ (<tag> value)) + (////@wrap (_.if (|> value <format> (<=> ..peek)) + _.nil + fail!))]) ([/////synthesis.path/bit //primitive.bit _.equal] [/////synthesis.path/i64 //primitive.i64 _.=] [/////synthesis.path/f64 //primitive.f64 _.=] [/////synthesis.path/text //primitive.text _.string=]) (^template [<complex> <simple> <choice>] - (^ (<complex> idx)) - (////@wrap (<choice> false idx)) + [(^ (<complex> idx)) + (////@wrap (<choice> false idx)) - (^ (<simple> idx nextP)) - (|> nextP - (pattern-matching' generate) - (:: ////.monad map (_.progn (<choice> true idx))))) + (^ (<simple> idx nextP)) + (|> nextP + (pattern-matching' generate) + (:: ////.monad map (_.progn (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple-left-side ..left-choice] [/////synthesis.side/right /////synthesis.simple-right-side ..right-choice]) @@ -167,8 +167,8 @@ (////@wrap (..push! (_.elt/2 [..peek (_.int +0)]))) (^template [<pm> <getter>] - (^ (<pm> lefts)) - (////@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))) + [(^ (<pm> lefts)) + (////@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) @@ -181,11 +181,11 @@ next!)))) (^template [<tag> <combinator>] - (^ (<tag> preP postP)) - (do ////.monad - [pre! (pattern-matching' generate preP) - post! (pattern-matching' generate postP)] - (wrap (<combinator> pre! post!)))) + [(^ (<tag> preP postP)) + (do ////.monad + [pre! (pattern-matching' generate preP) + post! (pattern-matching' generate postP)] + (wrap (<combinator> pre! post!)))]) ([/////synthesis.path/alt ..alternation] [/////synthesis.path/seq _.progn]))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js.lux index 76496ae82..e9ecc6435 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js.lux @@ -30,8 +30,8 @@ Phase! (case synthesis (^template [<tag>] - (^ (<tag> value)) - (//////phase@map _.return (expression archive synthesis))) + [(^ (<tag> value)) + (//////phase@map _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] [synthesis.f64] @@ -66,8 +66,8 @@ Phase (case synthesis (^template [<tag> <generator>] - (^ (<tag> value)) - (//////phase@wrap (<generator> value))) + [(^ (<tag> value)) + (//////phase@wrap (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux index 6d66678ac..50730cdda 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux @@ -77,8 +77,8 @@ (wrap (list@fold (function (_ side source) (.let [method (.case side (^template [<side> <accessor>] - (<side> lefts) - (<accessor> (_.i32 (.int lefts)))) + [(<side> lefts) + (<accessor> (_.i32 (.int lefts)))]) ([#.Left //runtime.tuple//left] [#.Right //runtime.tuple//right]))] (method source))) @@ -160,10 +160,10 @@ (-> Path (Operation (Maybe Statement)))) (.case pathP (^template [<simple> <choice>] - (^ (<simple> idx nextP)) - (|> nextP - recur - (:: ///////phase.monad map (|>> (_.then (<choice> true idx)) #.Some)))) + [(^ (<simple> idx nextP)) + (|> nextP + recur + (:: ///////phase.monad map (|>> (_.then (<choice> true idx)) #.Some)))]) ([/////synthesis.simple-left-side ..left-choice] [/////synthesis.simple-right-side ..right-choice]) @@ -182,14 +182,14 @@ ## Extra optimization (^template [<pm> <getter>] - (^ (/////synthesis.path/seq - (<pm> lefts) - (/////synthesis.!bind-top register thenP))) - (do ///////phase.monad - [then! (recur thenP)] - (wrap (#.Some ($_ _.then - (_.define (..register register) (<getter> (_.i32 (.int lefts)) ..peek-cursor)) - then!))))) + [(^ (/////synthesis.path/seq + (<pm> lefts) + (/////synthesis.!bind-top register thenP))) + (do ///////phase.monad + [then! (recur thenP)] + (wrap (#.Some ($_ _.then + (_.define (..register register) (<getter> (_.i32 (.int lefts)) ..peek-cursor)) + then!))))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) @@ -258,14 +258,14 @@ (wrap (_.cond clauses ..fail-pm!))) (^template [<tag> <format> <type>] - (<tag> cons) - (do {! ///////phase.monad} - [cases (monad.map ! (function (_ [match then]) - (:: ! map (|>> [(list (<format> match))]) (recur then))) - (#.Cons cons))] - (wrap (_.switch ..peek-cursor - cases - (#.Some ..fail-pm!))))) + [(<tag> cons) + (do {! ///////phase.monad} + [cases (monad.map ! (function (_ [match then]) + (:: ! map (|>> [(list (<format> match))]) (recur then))) + (#.Cons cons))] + (wrap (_.switch ..peek-cursor + cases + (#.Some ..fail-pm!))))]) ([#/////synthesis.F64-Fork //primitive.f64 Frac] [#/////synthesis.Text-Fork //primitive.text Text]) @@ -273,23 +273,23 @@ (statement expression archive bodyS) (^template [<complex> <choice>] - (^ (<complex> idx)) - (///////phase@wrap (<choice> false idx))) + [(^ (<complex> idx)) + (///////phase@wrap (<choice> false idx))]) ([/////synthesis.side/left ..left-choice] [/////synthesis.side/right ..right-choice]) (^template [<pm> <getter>] - (^ (<pm> lefts)) - (///////phase@wrap (push-cursor! (<getter> (_.i32 (.int lefts)) ..peek-cursor)))) + [(^ (<pm> lefts)) + (///////phase@wrap (push-cursor! (<getter> (_.i32 (.int lefts)) ..peek-cursor)))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) (^template [<tag> <combinator>] - (^ (<tag> leftP rightP)) - (do ///////phase.monad - [left! (recur leftP) - right! (recur rightP)] - (wrap (<combinator> left! right!)))) + [(^ (<tag> leftP rightP)) + (do ///////phase.monad + [left! (recur leftP) + right! (recur rightP)] + (wrap (<combinator> left! right!)))]) ([/////synthesis.path/seq _.then] [/////synthesis.path/alt ..alternation])))))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm.lux index 5ede5f926..c93bced64 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm.lux @@ -23,8 +23,8 @@ Phase (case synthesis (^template [<tag> <generator>] - (^ (<tag> value)) - (///@wrap (<generator> value))) + [(^ (<tag> value)) + (///@wrap (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux index a81e9f244..7e7cccc72 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux @@ -108,34 +108,34 @@ (_.goto @end)))) (^template [<pattern> <right?>] - (^ (<pattern> lefts)) - (operation@wrap - (do _.monad - [@success _.new-label - @fail _.new-label] - ($_ _.compose - ..peek - (_.checkcast //type.variant) - (//structure.tag lefts <right?>) - (//structure.flag <right?>) - //runtime.case - _.dup - (_.ifnull @fail) - (_.goto @success) - (_.set-label @fail) - _.pop - (_.goto @else) - (_.set-label @success) - //runtime.push)))) + [(^ (<pattern> lefts)) + (operation@wrap + (do _.monad + [@success _.new-label + @fail _.new-label] + ($_ _.compose + ..peek + (_.checkcast //type.variant) + (//structure.tag lefts <right?>) + (//structure.flag <right?>) + //runtime.case + _.dup + (_.ifnull @fail) + (_.goto @success) + (_.set-label @fail) + _.pop + (_.goto @else) + (_.set-label @success) + //runtime.push)))]) ([synthesis.side/left false] [synthesis.side/right true]) (^template [<pattern> <projection>] - (^ (<pattern> lefts)) - (operation@wrap ($_ _.compose - ..peek - (<projection> lefts) - //runtime.push))) + [(^ (<pattern> lefts)) + (operation@wrap ($_ _.compose + ..peek + (<projection> lefts) + //runtime.push))]) ([synthesis.member/left ..left-projection] [synthesis.member/right ..right-projection]) @@ -155,18 +155,18 @@ ## Extra optimization (^template [<pm> <projection>] - (^ (synthesis.path/seq - (<pm> lefts) - (synthesis.!bind-top register thenP))) - (do phase.monad - [then! (path' stack-depth @else @end phase archive thenP)] - (wrap ($_ _.compose - ..peek - (_.checkcast //type.tuple) - (..int lefts) - <projection> - (_.astore register) - then!)))) + [(^ (synthesis.path/seq + (<pm> lefts) + (synthesis.!bind-top register thenP))) + (do phase.monad + [then! (path' stack-depth @else @end phase archive thenP)] + (wrap ($_ _.compose + ..peek + (_.checkcast //type.tuple) + (..int lefts) + <projection> + (_.astore register) + then!)))]) ([synthesis.member/left //runtime.left-projection] [synthesis.member/right //runtime.right-projection]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux index b6004b6c6..3b12fe741 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux @@ -27,19 +27,19 @@ (-> (I64 Any) (Bytecode Any)) (case (.int value) (^template [<int> <instruction>] - <int> - (do _.monad - [_ <instruction>] - ..wrap-i64)) + [<int> + (do _.monad + [_ <instruction>] + ..wrap-i64)]) ([+0 _.lconst-0] [+1 _.lconst-1]) (^template [<int> <instruction>] - <int> - (do _.monad - [_ <instruction> - _ _.i2l] - ..wrap-i64)) + [<int> + (do _.monad + [_ <instruction> + _ _.i2l] + ..wrap-i64)]) ([-1 _.iconst-m1] ## [+0 _.iconst-0] ## [+1 _.iconst-1] @@ -79,26 +79,26 @@ (-> Frac (Bytecode Any)) (case value (^template [<int> <instruction>] - <int> - (do _.monad - [_ <instruction>] - ..wrap-f64)) + [<int> + (do _.monad + [_ <instruction>] + ..wrap-f64)]) ([+1.0 _.dconst-1]) (^template [<int> <instruction>] - <int> - (do _.monad - [_ <instruction> - _ _.f2d] - ..wrap-f64)) + [<int> + (do _.monad + [_ <instruction> + _ _.f2d] + ..wrap-f64)]) ([+2.0 _.fconst-2]) (^template [<int> <instruction>] - <int> - (do _.monad - [_ <instruction> - _ _.i2d] - ..wrap-f64)) + [<int> + (do _.monad + [_ <instruction> + _ _.i2d] + ..wrap-f64)]) ([-1.0 _.iconst-m1] ## [+0.0 _.iconst-0] ## [+1.0 _.iconst-1] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux index a455b13b9..c6cd63bf3 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux @@ -22,8 +22,8 @@ Phase (case synthesis (^template [<tag> <generator>] - (^ (<tag> value)) - (//////phase@wrap (<generator> value))) + [(^ (<tag> value)) + (//////phase@wrap (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/case.lux index 6271955ed..f13750e56 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/case.lux @@ -52,8 +52,8 @@ (wrap (list@fold (function (_ side source) (.let [method (.case side (^template [<side> <accessor>] - (<side> lefts) - (<accessor> (_.int (.int lefts)))) + [(<side> lefts) + (<accessor> (_.int (.int lefts)))]) ([#.Left //runtime.tuple//left] [#.Right //runtime.tuple//right]))] (method source))) @@ -144,22 +144,22 @@ (///////phase@wrap (_.let (list (..register register)) ..peek)) (^template [<tag> <format>] - (^ (<tag> value)) - (///////phase@wrap (_.when (|> value <format> (_.= ..peek) _.not) - fail!))) + [(^ (<tag> value)) + (///////phase@wrap (_.when (|> value <format> (_.= ..peek) _.not) + fail!))]) ([/////synthesis.path/bit //primitive.bit] [/////synthesis.path/i64 //primitive.i64] [/////synthesis.path/f64 //primitive.f64] [/////synthesis.path/text //primitive.text]) (^template [<complex> <simple> <choice>] - (^ (<complex> idx)) - (///////phase@wrap (<choice> false idx)) + [(^ (<complex> idx)) + (///////phase@wrap (<choice> false idx)) - (^ (<simple> idx nextP)) - (|> nextP - (pattern-matching' generate archive) - (///////phase@map (_.then (<choice> true idx))))) + (^ (<simple> idx nextP)) + (|> nextP + (pattern-matching' generate archive) + (///////phase@map (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple-left-side ..left-choice] [/////synthesis.side/right /////synthesis.simple-right-side ..right-choice]) @@ -167,8 +167,8 @@ (///////phase@wrap (|> ..peek (_.nth (_.int +1)) ..push!)) (^template [<pm> <getter>] - (^ (<pm> lefts)) - (///////phase@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))) + [(^ (<pm> lefts)) + (///////phase@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) @@ -180,11 +180,11 @@ then!))) (^template [<tag> <combinator>] - (^ (<tag> preP postP)) - (do ///////phase.monad - [pre! (pattern-matching' generate archive preP) - post! (pattern-matching' generate archive postP)] - (wrap (<combinator> pre! post!)))) + [(^ (<tag> preP postP)) + (do ///////phase.monad + [pre! (pattern-matching' generate archive preP) + post! (pattern-matching' generate archive postP)] + (wrap (<combinator> pre! post!)))]) ([/////synthesis.path/seq _.then] [/////synthesis.path/alt ..alternation]))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php.lux index 6d3500416..ad04cefdb 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php.lux @@ -20,8 +20,8 @@ Phase (case synthesis (^template [<tag> <generator>] - (^ (<tag> value)) - (:: ///.monad wrap (<generator> value))) + [(^ (<tag> value)) + (:: ///.monad wrap (<generator> value))]) ([synthesis.bit primitive.bit] [synthesis.i64 primitive.i64] [synthesis.f64 primitive.f64] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/case.lux index 811ce3c93..738912f52 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/case.lux @@ -54,8 +54,8 @@ (wrap (list@fold (function (_ side source) (.let [method (.case side (^template [<side> <accessor>] - (<side> lefts) - (<accessor> (_.int (.int lefts)))) + [(<side> lefts) + (<accessor> (_.int (.int lefts)))]) ([#.Left //runtime.tuple//left] [#.Right //runtime.tuple//right]))] (method source))) @@ -149,22 +149,22 @@ (////@wrap (_.; (_.set (..register register) ..peek))) (^template [<tag> <format>] - (^ (<tag> value)) - (////@wrap (_.when (|> value <format> (_.= ..peek) _.not) - fail!))) + [(^ (<tag> value)) + (////@wrap (_.when (|> value <format> (_.= ..peek) _.not) + fail!))]) ([/////synthesis.path/bit //primitive.bit] [/////synthesis.path/i64 //primitive.i64] [/////synthesis.path/f64 //primitive.f64] [/////synthesis.path/text //primitive.text]) (^template [<complex> <simple> <choice>] - (^ (<complex> idx)) - (////@wrap (<choice> false idx)) + [(^ (<complex> idx)) + (////@wrap (<choice> false idx)) - (^ (<simple> idx nextP)) - (|> nextP - (pattern-matching' generate) - (:: ////.monad map (_.then (<choice> true idx))))) + (^ (<simple> idx nextP)) + (|> nextP + (pattern-matching' generate) + (:: ////.monad map (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple-left-side ..left-choice] [/////synthesis.side/right /////synthesis.simple-right-side ..right-choice]) @@ -172,8 +172,8 @@ (////@wrap (|> ..peek (_.nth (_.int +0)) ..push!)) (^template [<pm> <getter>] - (^ (<pm> lefts)) - (////@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))) + [(^ (<pm> lefts)) + (////@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) @@ -193,11 +193,11 @@ ## next!)))) (^template [<tag> <combinator>] - (^ (<tag> preP postP)) - (do ////.monad - [pre! (pattern-matching' generate preP) - post! (pattern-matching' generate postP)] - (wrap (<combinator> pre! post!)))) + [(^ (<tag> preP postP)) + (do ////.monad + [pre! (pattern-matching' generate preP) + post! (pattern-matching' generate postP)] + (wrap (<combinator> pre! post!)))]) ([/////synthesis.path/seq _.then] [/////synthesis.path/alt ..alternation]))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python.lux index 19013715b..f2bfbd4d5 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python.lux @@ -22,8 +22,8 @@ Phase (case synthesis (^template [<tag> <generator>] - (^ (<tag> value)) - (//////phase@wrap (<generator> value))) + [(^ (<tag> value)) + (//////phase@wrap (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] [////synthesis.f64 /primitive.f64] 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 dd99cb47a..e25155d4a 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 @@ -55,8 +55,8 @@ (wrap (list@fold (function (_ side source) (.let [method (.case side (^template [<side> <accessor>] - (<side> lefts) - (<accessor> (_.int (.int lefts)))) + [(<side> lefts) + (<accessor> (_.int (.int lefts)))]) ([#.Left //runtime.tuple//left] [#.Right //runtime.tuple//right]))] (method source))) @@ -147,22 +147,22 @@ (///////phase@wrap (_.set (list (..register register)) ..peek)) (^template [<tag> <format>] - (^ (<tag> value)) - (///////phase@wrap (_.when (|> value <format> (_.= ..peek) _.not) - fail-pm!))) + [(^ (<tag> value)) + (///////phase@wrap (_.when (|> value <format> (_.= ..peek) _.not) + fail-pm!))]) ([/////synthesis.path/bit //primitive.bit] [/////synthesis.path/i64 //primitive.i64] [/////synthesis.path/f64 //primitive.f64] [/////synthesis.path/text //primitive.text]) (^template [<complex> <simple> <choice>] - (^ (<complex> idx)) - (///////phase@wrap (<choice> false idx)) + [(^ (<complex> idx)) + (///////phase@wrap (<choice> false idx)) - (^ (<simple> idx nextP)) - (|> nextP - (pattern-matching' generate archive) - (///////phase@map (_.then (<choice> true idx))))) + (^ (<simple> idx nextP)) + (|> nextP + (pattern-matching' generate archive) + (///////phase@map (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple-left-side ..left-choice] [/////synthesis.side/right /////synthesis.simple-right-side ..right-choice]) @@ -170,8 +170,8 @@ (///////phase@wrap (|> ..peek (_.nth (_.int +0)) ..push!)) (^template [<pm> <getter>] - (^ (<pm> lefts)) - (///////phase@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))) + [(^ (<pm> lefts)) + (///////phase@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) @@ -191,11 +191,11 @@ next!)))) (^template [<tag> <combinator>] - (^ (<tag> preP postP)) - (do ///////phase.monad - [pre! (pattern-matching' generate archive preP) - post! (pattern-matching' generate archive postP)] - (wrap (<combinator> pre! post!)))) + [(^ (<tag> preP postP)) + (do ///////phase.monad + [pre! (pattern-matching' generate archive preP) + post! (pattern-matching' generate archive postP)] + (wrap (<combinator> pre! post!)))]) ([/////synthesis.path/seq _.then] [/////synthesis.path/alt ..alternation]))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby.lux index 19013715b..f2bfbd4d5 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby.lux @@ -22,8 +22,8 @@ Phase (case synthesis (^template [<tag> <generator>] - (^ (<tag> value)) - (//////phase@wrap (<generator> value))) + [(^ (<tag> value)) + (//////phase@wrap (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] [////synthesis.f64 /primitive.f64] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux index 082f9c334..921769c00 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux @@ -55,8 +55,8 @@ (wrap (list@fold (function (_ side source) (.let [method (.case side (^template [<side> <accessor>] - (<side> lefts) - (<accessor> (_.int (.int lefts)))) + [(<side> lefts) + (<accessor> (_.int (.int lefts)))]) ([#.Left //runtime.tuple//left] [#.Right //runtime.tuple//right]))] (method source))) @@ -148,22 +148,22 @@ (///////phase@wrap (_.set (list (..register register)) ..peek)) (^template [<tag> <format>] - (^ (<tag> value)) - (///////phase@wrap (_.when (|> value <format> (_.= ..peek) _.not) - fail!))) + [(^ (<tag> value)) + (///////phase@wrap (_.when (|> value <format> (_.= ..peek) _.not) + fail!))]) ([/////synthesis.path/bit //primitive.bit] [/////synthesis.path/i64 //primitive.i64] [/////synthesis.path/f64 //primitive.f64] [/////synthesis.path/text //primitive.text]) (^template [<complex> <simple> <choice>] - (^ (<complex> idx)) - (///////phase@wrap (<choice> false idx)) + [(^ (<complex> idx)) + (///////phase@wrap (<choice> false idx)) - (^ (<simple> idx nextP)) - (|> nextP - (pattern-matching' generate archive) - (///////phase@map (_.then (<choice> true idx))))) + (^ (<simple> idx nextP)) + (|> nextP + (pattern-matching' generate archive) + (///////phase@map (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple-left-side ..left-choice] [/////synthesis.side/right /////synthesis.simple-right-side ..right-choice]) @@ -171,8 +171,8 @@ (///////phase@wrap (|> ..peek (_.nth (_.int +0)) ..push!)) (^template [<pm> <getter>] - (^ (<pm> lefts)) - (///////phase@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))) + [(^ (<pm> lefts)) + (///////phase@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) @@ -192,11 +192,11 @@ next!)))) (^template [<tag> <combinator>] - (^ (<tag> preP postP)) - (do ///////phase.monad - [pre! (pattern-matching' generate archive preP) - post! (pattern-matching' generate archive postP)] - (wrap (<combinator> pre! post!)))) + [(^ (<tag> preP postP)) + (do ///////phase.monad + [pre! (pattern-matching' generate archive preP) + post! (pattern-matching' generate archive postP)] + (wrap (<combinator> pre! post!)))]) ([/////synthesis.path/seq _.then] [/////synthesis.path/alt ..alternation]))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme.lux index 0152ffbcd..950b3b74b 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme.lux @@ -20,8 +20,8 @@ Phase (case synthesis (^template [<tag> <generator>] - (^ (<tag> value)) - (:: ///.monad wrap (<generator> value))) + [(^ (<tag> value)) + (:: ///.monad wrap (<generator> value))]) ([synthesis.bit primitive.bit] [synthesis.i64 primitive.i64] [synthesis.f64 primitive.f64] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux index 034c72a19..a6f3b3760 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux @@ -41,8 +41,8 @@ (wrap (list@fold (function (_ side source) (.let [method (.case side (^template [<side> <accessor>] - (<side> lefts) - (<accessor> (_.int (.int lefts)))) + [(<side> lefts) + (<accessor> (_.int (.int lefts)))]) ([#.Left //runtime.tuple//left] [#.Right //runtime.tuple//right]))] (method source))) @@ -98,9 +98,9 @@ (def: (pm-catch handler) (-> Expression Computation) (_.lambda [(list @alt-error) #.None] - (_.if (|> @alt-error (_.eqv?/2 pm-error)) - handler - (_.raise/1 @alt-error)))) + (_.if (|> @alt-error (_.eqv?/2 pm-error)) + handler + (_.raise/1 @alt-error)))) (def: (pattern-matching' generate pathP) (-> Phase Path (Operation Expression)) @@ -115,43 +115,43 @@ (////@wrap (_.define-constant (..register register) ..cursor-top)) (^template [<tag> <format> <=>] - (^ (<tag> value)) - (////@wrap (_.when (|> value <format> (<=> cursor-top) _.not/1) - fail-pm!))) + [(^ (<tag> value)) + (////@wrap (_.when (|> value <format> (<=> cursor-top) _.not/1) + fail-pm!))]) ([/////synthesis.path/bit //primitive.bit _.eqv?/2] [/////synthesis.path/i64 (<| //primitive.i64 .int) _.=/2] [/////synthesis.path/f64 //primitive.f64 _.=/2] [/////synthesis.path/text //primitive.text _.eqv?/2]) (^template [<pm> <flag> <prep>] - (^ (<pm> idx)) - (////@wrap (_.let (list [@temp (|> idx <prep> .int _.int (//runtime.sum//get cursor-top <flag>))]) - (_.if (_.null?/1 @temp) - fail-pm! - (push-cursor! @temp))))) + [(^ (<pm> idx)) + (////@wrap (_.let (list [@temp (|> idx <prep> .int _.int (//runtime.sum//get cursor-top <flag>))]) + (_.if (_.null?/1 @temp) + fail-pm! + (push-cursor! @temp))))]) ([/////synthesis.side/left _.nil (<|)] [/////synthesis.side/right (_.string "") inc]) (^template [<pm> <getter>] - (^ (<pm> idx)) - (////@wrap (push-cursor! (<getter> (_.int (.int idx)) cursor-top)))) + [(^ (<pm> idx)) + (////@wrap (push-cursor! (<getter> (_.int (.int idx)) cursor-top)))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) (^template [<tag> <computation>] - (^ (<tag> leftP rightP)) - (do ////.monad - [leftO (pattern-matching' generate leftP) - rightO (pattern-matching' generate rightP)] - (wrap <computation>))) + [(^ (<tag> leftP rightP)) + (do ////.monad + [leftO (pattern-matching' generate leftP) + rightO (pattern-matching' generate rightP)] + (wrap <computation>))]) ([/////synthesis.path/seq (_.begin (list leftO rightO))] [/////synthesis.path/alt (_.with-exception-handler (pm-catch (_.begin (list restore-cursor! rightO))) (_.lambda [(list) #.None] - (_.begin (list save-cursor! - leftO))))]))) + (_.begin (list save-cursor! + leftO))))]))) (def: (pattern-matching generate pathP) (-> Phase Path (Operation Computation)) @@ -160,7 +160,7 @@ (wrap (_.with-exception-handler (pm-catch (_.raise/1 (_.string "Invalid expression for pattern-matching."))) (_.lambda [(list) #.None] - pattern-matching!))))) + pattern-matching!))))) (def: #export (case generate [valueS pathP]) (-> Phase [Synthesis Path] (Operation Computation)) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis.lux index 497261cf0..e6a587f9f 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis.lux @@ -31,15 +31,15 @@ (#/.Text /.unit) (^template [<analysis> <synthesis>] - (<analysis> value) - (<synthesis> value)) + [(<analysis> value) + (<synthesis> value)]) ([#///analysis.Bit #/.Bit] [#///analysis.Frac #/.F64] [#///analysis.Text #/.Text]) (^template [<analysis> <synthesis>] - (<analysis> value) - (<synthesis> (.i64 value))) + [(<analysis> value) + (<synthesis> (.i64 value))]) ([#///analysis.Nat #/.I64] [#///analysis.Int #/.I64] [#///analysis.Rev #/.I64]))) 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 268937c12..448c37b02 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 @@ -45,10 +45,10 @@ thenC) (^template [<from> <to> <conversion>] - (<from> test) - (///@map (function (_ then) - (<to> [(<conversion> test) then] (list))) - thenC)) + [(<from> test) + (///@map (function (_ then) + (<to> [(<conversion> test) then] (list))) + thenC)]) ([#///analysis.Nat #/.I64-Fork .i64] [#///analysis.Int #/.I64-Fork .i64] [#///analysis.Rev #/.I64-Fork .i64] @@ -161,18 +161,18 @@ (weave new-then old-else))))) (^template [<tag> <equivalence>] - [(<tag> new-fork) (<tag> old-fork)] - (<tag> (..weave-fork weave <equivalence> new-fork old-fork))) + [[(<tag> new-fork) (<tag> old-fork)] + (<tag> (..weave-fork weave <equivalence> new-fork old-fork))]) ([#/.I64-Fork i64.equivalence] [#/.F64-Fork frac.equivalence] [#/.Text-Fork text.equivalence]) (^template [<access> <side>] - [(#/.Access (<access> (<side> newL))) - (#/.Access (<access> (<side> oldL)))] - (if (n.= newL oldL) - old - <default>)) + [[(#/.Access (<access> (<side> newL))) + (#/.Access (<access> (<side> oldL)))] + (if (n.= newL oldL) + old + <default>)]) ([#/.Side #.Left] [#/.Side #.Right] [#/.Member #.Left] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/function.lux index 6c70612b4..864001655 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -95,11 +95,11 @@ (phase@wrap (#/.Bind (inc register))) (^template [<tag>] - (<tag> left right) - (do phase.monad - [left' (grow-path grow left) - right' (grow-path grow right)] - (wrap (<tag> left' right')))) + [(<tag> left right) + (do phase.monad + [left' (grow-path grow left) + right' (grow-path grow right)] + (wrap (<tag> left' right')))]) ([#/.Alt] [#/.Seq]) (#/.Bit-Fork when then else) @@ -114,15 +114,15 @@ (wrap (#/.Bit-Fork when then else))) (^template [<tag>] - (<tag> [[test then] elses]) - (do {! phase.monad} - [then (grow-path grow then) - elses (monad.map ! (function (_ [else-test else-then]) - (do ! - [else-then (grow-path grow else-then)] - (wrap [else-test else-then]))) - elses)] - (wrap (<tag> [[test then] elses])))) + [(<tag> [[test then] elses]) + (do {! phase.monad} + [then (grow-path grow then) + elses (monad.map ! (function (_ [else-test else-then]) + (do ! + [else-then (grow-path grow else-then)] + (wrap [else-test else-then]))) + elses)] + (wrap (<tag> [[test then] elses])))]) ([#/.I64-Fork] [#/.F64-Fork] [#/.Text-Fork]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index eca662b25..f2559460a 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -31,11 +31,11 @@ (#.Some (#/.Bind (register-optimization offset register))) (^template [<tag>] - (<tag> left right) - (do maybe.monad - [left' (recur left) - right' (recur right)] - (wrap (<tag> left' right')))) + [(<tag> left right) + (do maybe.monad + [left' (recur left) + right' (recur right)] + (wrap (<tag> left' right')))]) ([#/.Alt] [#/.Seq]) (#/.Bit-Fork when then else) @@ -50,15 +50,15 @@ (wrap (#/.Bit-Fork when then else))) (^template [<tag>] - (<tag> [[test then] elses]) - (do {! maybe.monad} - [then (recur then) - elses (monad.map ! (function (_ [else-test else-then]) - (do ! - [else-then (recur else-then)] - (wrap [else-test else-then]))) - elses)] - (wrap (<tag> [[test then] elses])))) + [(<tag> [[test then] elses]) + (do {! maybe.monad} + [then (recur then) + elses (monad.map ! (function (_ [else-test else-then]) + (do ! + [else-then (recur else-then)] + (wrap [else-test else-then]))) + elses)] + (wrap (<tag> [[test then] elses])))]) ([#/.I64-Fork] [#/.F64-Fork] [#/.Text-Fork]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index ab0858583..c18c26246 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -63,8 +63,8 @@ (recur post)))) (^template [<tag>] - (<tag> left right) - (<tag> (recur left) (recur right))) + [(<tag> left right) + (<tag> (recur left) (recur right))]) ([#/.Seq] [#/.Alt]) @@ -72,11 +72,11 @@ (#/.Bit-Fork when (recur then) (maybe@map recur else)) (^template [<tag>] - (<tag> [[test then] tail]) - (<tag> [[test (recur then)] - (list@map (function (_ [test' then']) - [test' (recur then')]) - tail)])) + [(<tag> [[test then] tail]) + (<tag> [[test (recur then)] + (list@map (function (_ [test' then']) + [test' (recur then')]) + tail)])]) ([#/.I64-Fork] [#/.F64-Fork] [#/.Text-Fork]) @@ -265,16 +265,16 @@ (wrap [redundancy (#/.Bit-Fork when then else)])) (^template [<tag> <type>] - (<tag> [[test then] elses]) - (do {! try.monad} - [[redundancy then] (recur [redundancy then]) - [redundancy elses] (..list-optimization (: (Optimization [<type> Path]) - (function (_ [redundancy [else-test else-then]]) - (do ! - [[redundancy else-then] (recur [redundancy else-then])] - (wrap [redundancy [else-test else-then]])))) - [redundancy elses])] - (wrap [redundancy (<tag> [[test then] elses])]))) + [(<tag> [[test then] elses]) + (do {! try.monad} + [[redundancy then] (recur [redundancy then]) + [redundancy elses] (..list-optimization (: (Optimization [<type> Path]) + (function (_ [redundancy [else-test else-then]]) + (do ! + [[redundancy else-then] (recur [redundancy else-then])] + (wrap [redundancy [else-test else-then]])))) + [redundancy elses])] + (wrap [redundancy (<tag> [[test then] elses])]))]) ([#/.I64-Fork (I64 Any)] [#/.F64-Fork Frac] [#/.Text-Fork Text]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux index 2c6b8ab6f..cc1bf4500 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux @@ -273,12 +273,12 @@ ")") (^template [<tag> <format>] - (<tag> cons) - (|> (#.Cons cons) - (list@map (function (_ [test then]) - (format (<format> test) " " (%path' %then then)))) - (text.join-with " ") - (text.enclose ["(? " ")"]))) + [(<tag> cons) + (|> (#.Cons cons) + (list@map (function (_ [test then]) + (format (<format> test) " " (%path' %then then)))) + (text.join-with " ") + (text.enclose ["(? " ")"]))]) ([#I64-Fork (|>> .int %.int)] [#F64-Fork %.frac] [#Text-Fork %.text]) @@ -320,8 +320,8 @@ (#Primitive primitive) (case primitive (^template [<pattern> <format>] - (<pattern> value) - (<format> value)) + [(<pattern> value) + (<format> value)]) ([#Bit %.bit] [#F64 %.frac] [#Text %.text]) @@ -417,8 +417,8 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <eq> <format>] - [(<tag> reference') (<tag> sample')] - (<eq> reference' sample')) + [[(<tag> reference') (<tag> sample')] + (<eq> reference' sample')]) ([#Bit bit@= %.bit] [#F64 f.= %.frac] [#Text text@= %.text]) @@ -436,8 +436,8 @@ (def: hash (|>> (case> (^template [<tag> <hash>] - (<tag> value') - (:: <hash> hash value')) + [(<tag> value') + (:: <hash> hash value')]) ([#Bit bit.hash] [#F64 f.hash] [#Text text.hash] @@ -461,8 +461,8 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <equivalence>] - [(<tag> reference) (<tag> sample)] - (:: <equivalence> = reference sample)) + [[(<tag> reference) (<tag> sample)] + (:: <equivalence> = reference sample)]) ([#Side ..side-equivalence] [#Member ..member-equivalence]) @@ -478,8 +478,8 @@ (let [sub-hash (sum.hash n.hash n.hash)] (case value (^template [<tag>] - (<tag> value) - (:: sub-hash hash value)) + [(<tag> value) + (:: sub-hash hash value)]) ([#Side] [#Member]))))) @@ -498,18 +498,18 @@ (:: (maybe.equivalence =) = reference-else sample-else)) (^template [<tag> <equivalence>] - [(<tag> reference-cons) - (<tag> sample-cons)] - (:: (list.equivalence (equivalence.product <equivalence> =)) = - (#.Cons reference-cons) - (#.Cons sample-cons))) + [[(<tag> reference-cons) + (<tag> sample-cons)] + (:: (list.equivalence (equivalence.product <equivalence> =)) = + (#.Cons reference-cons) + (#.Cons sample-cons))]) ([#I64-Fork i64.equivalence] [#F64-Fork f.equivalence] [#Text-Fork text.equivalence]) (^template [<tag> <equivalence>] - [(<tag> reference') (<tag> sample')] - (:: <equivalence> = reference' sample')) + [[(<tag> reference') (<tag> sample')] + (:: <equivalence> = reference' sample')]) ([#Access ..access-equivalence] [#Then equivalence]) @@ -517,9 +517,9 @@ (n.= reference' sample') (^template [<tag>] - [(<tag> leftR rightR) (<tag> leftS rightS)] - (and (= leftR leftS) - (= rightR rightS))) + [[(<tag> leftR rightR) (<tag> leftS rightS)] + (and (= leftR leftS) + (= rightR rightS))]) ([#Alt] [#Seq]) @@ -550,20 +550,20 @@ (:: (maybe.hash (path'-hash super)) hash else)) (^template [<factor> <tag> <hash>] - (<tag> cons) - (let [case-hash (product.hash <hash> - (path'-hash super)) - cons-hash (product.hash case-hash (list.hash case-hash))] - (n.* <factor> (:: cons-hash hash cons)))) + [(<tag> cons) + (let [case-hash (product.hash <hash> + (path'-hash super)) + cons-hash (product.hash case-hash (list.hash case-hash))] + (n.* <factor> (:: cons-hash hash cons)))]) ([11 #I64-Fork i64.hash] [13 #F64-Fork f.hash] [17 #Text-Fork text.hash]) (^template [<factor> <tag>] - (<tag> fork) - (let [recur-hash (path'-hash super) - fork-hash (product.hash recur-hash recur-hash)] - (n.* <factor> (:: fork-hash hash fork)))) + [(<tag> fork) + (let [recur-hash (path'-hash super) + fork-hash (product.hash recur-hash recur-hash)] + (n.* <factor> (:: fork-hash hash fork)))]) ([19 #Alt] [23 #Seq]) @@ -713,8 +713,8 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <equivalence>] - [(<tag> reference) (<tag> sample)] - (:: (<equivalence> /@=) = reference sample)) + [[(<tag> reference) (<tag> sample)] + (:: (<equivalence> /@=) = reference sample)]) ([#Branch ..branch-equivalence] [#Loop ..loop-equivalence] [#Function ..function-equivalence]) @@ -731,8 +731,8 @@ (def: (hash value) (case value (^template [<factor> <tag> <hash>] - (<tag> value) - (n.* <factor> (:: (<hash> super) hash value))) + [(<tag> value) + (n.* <factor> (:: (<hash> super) hash value))]) ([2 #Branch ..branch-hash] [3 #Loop ..loop-hash] [5 #Function ..function-hash]) @@ -744,8 +744,8 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <equivalence>] - [(<tag> reference') (<tag> sample')] - (:: <equivalence> = reference' sample')) + [[(<tag> reference') (<tag> sample')] + (:: <equivalence> = reference' sample')]) ([#Primitive ..primitive-equivalence] [#Structure (analysis.composite-equivalence =)] [#Reference reference.equivalence] @@ -768,8 +768,8 @@ (let [recur-hash [..equivalence hash]] (case value (^template [<tag> <hash>] - (<tag> value) - (:: <hash> hash value)) + [(<tag> value) + (:: <hash> hash value)]) ([#Primitive ..primitive-hash] [#Structure (analysis.composite-hash recur-hash)] [#Reference reference.hash] diff --git a/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux index f34f72acd..1af87d6fc 100644 --- a/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux @@ -103,7 +103,7 @@ (function (_ value) (case value (^template [<nat> <tag> <writer>] - (<tag> value) ((binary.and binary.nat <writer>) [<nat> value])) + [(<tag> value) ((binary.and binary.nat <writer>) [<nat> value])]) ([0 #Anonymous binary.any] [1 #Definition binary.text] [2 #Analyser binary.text] @@ -142,8 +142,8 @@ (..resource registry) (^template [<tag> <create>] - (<tag> name) - (<create> name registry)) + [(<tag> name) + (<create> name registry)]) ([#Definition ..definition] [#Analyser ..analyser] [#Synthesizer ..synthesizer] diff --git a/stdlib/source/lux/tool/compiler/reference.lux b/stdlib/source/lux/tool/compiler/reference.lux index e67b946b8..5ade63e39 100644 --- a/stdlib/source/lux/tool/compiler/reference.lux +++ b/stdlib/source/lux/tool/compiler/reference.lux @@ -27,8 +27,8 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <equivalence>] - [(<tag> reference) (<tag> sample)] - (:: <equivalence> = reference sample)) + [[(<tag> reference) (<tag> sample)] + (:: <equivalence> = reference sample)]) ([#Variable /variable.equivalence] [#Constant name.equivalence]) @@ -44,9 +44,9 @@ (def: (hash value) (case value (^template [<factor> <tag> <hash>] - (<tag> value) - ($_ n.* <factor> - (:: <hash> hash value))) + [(<tag> value) + ($_ n.* <factor> + (:: <hash> hash value))]) ([2 #Variable /variable.hash] [3 #Constant name.hash]) ))) diff --git a/stdlib/source/lux/tool/compiler/reference/variable.lux b/stdlib/source/lux/tool/compiler/reference/variable.lux index 0350463bd..e97974596 100644 --- a/stdlib/source/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/lux/tool/compiler/reference/variable.lux @@ -25,8 +25,8 @@ (def: (= reference sample) (case [reference sample] (^template [<tag>] - [(<tag> reference') (<tag> sample')] - (n.= reference' sample')) + [[(<tag> reference') (<tag> sample')] + (n.= reference' sample')]) ([#Local] [#Foreign]) _ @@ -40,9 +40,9 @@ (def: hash (|>> (case> (^template [<factor> <tag>] - (<tag> register) - ($_ n.* <factor> - (:: n.hash hash register))) + [(<tag> register) + ($_ n.* <factor> + (:: n.hash hash register))]) ([2 #Local] [3 #Foreign]))))) |