diff options
author | Eduardo Julian | 2021-08-09 23:02:01 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-08-09 23:02:01 -0400 |
commit | 464b6e8f5e6c62f58fa8c7ff61ab2ad215e98bd1 (patch) | |
tree | 1ae9d95956cee4251cd29a3e24c246c4360d567d /stdlib/source/library/lux/tool/compiler | |
parent | f621a133e6e0a516c0586270fea8eaffb4829d82 (diff) |
Improved single-line comment syntax (from "##" to "...").
Diffstat (limited to '')
87 files changed, 764 insertions, 749 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index e2fd13208..6127ea59a 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -154,7 +154,7 @@ (in [analysis_module [final_buffer final_registry]]))) -## TODO: Inline ASAP +... TODO: Inline ASAP (def: (get_current_payload _) (All [directive] (-> (Payload directive) @@ -168,7 +168,7 @@ ///generation.get_registry)] (in [buffer registry]))) -## TODO: Inline ASAP +... TODO: Inline ASAP (def: (process_directive archive expander pre_payoad code) (All [directive] (-> Archive Expander (Payload directive) Code diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index dac25756c..814e6dfd2 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -75,11 +75,11 @@ #phase_wrapper (-> Archive (<Operation> Phase_Wrapper)) #write (-> directive Binary)}) - ## TODO: Get rid of this + ... TODO: Get rid of this (type: (Action a) (Async (Try a))) - ## TODO: Get rid of this + ... TODO: Get rid of this (def: monad (:as (Monad Action) (try.with async.monad))) @@ -117,13 +117,13 @@ (ioW.cache system static module_id (_.run ..writer [descriptor document]))))) - ## TODO: Inline ASAP + ... TODO: Inline ASAP (def: initialize_buffer! (All [<type_vars>] (///generation.Operation <type_vars> Any)) (///generation.set_buffer ///generation.empty_buffer)) - ## TODO: Inline ASAP + ... TODO: Inline ASAP (def: (compile_runtime! platform) (All [<type_vars>] (-> <Platform> (///generation.Operation <type_vars> [Registry Output]))) @@ -380,7 +380,7 @@ (..circular_dependency? importer importee dependence) (exception.except ..cannot_import_circular_dependency [importer importee]) - ## else + ... else (#try.Success []))) (with_expansions [<Context> (as_is [Archive <State+>]) @@ -485,7 +485,7 @@ (in [])))] return))))) - ## TODO: Find a better way, as this only works for the Lux compiler. + ... TODO: Find a better way, as this only works for the Lux compiler. (def: (updated_state archive state) (All [<type_vars>] (-> Archive <State+> (Try <State+>))) @@ -558,9 +558,9 @@ (-> <Context> (///.Compilation <State+> .Module Any) (Set Module) (Action [Archive <State+>])) (:assume recur)) - ## TODO: Come up with a less hacky way to prevent duplicate imports. - ## This currently assumes that all imports will be specified once in a single .module: form. - ## This might not be the case in the future. + ... TODO: Come up with a less hacky way to prevent duplicate imports. + ... This currently assumes that all imports will be specified once in a single .module: form. + ... This might not be the case in the future. [all_dependencies duplicates _] (: [(Set Module) (Set Module) Bit] (list\fold (function (_ new [all duplicates seen_prelude?]) (if (set.member? all new) @@ -590,8 +590,8 @@ (..updated_state archive state))]))) (async\in (exception.except ..cannot_import_twice [module duplicates])))] (case ((get@ #///.process compilation) - ## TODO: The "///directive.set_current_module" below shouldn't be necessary. Remove it ASAP. - ## TODO: The context shouldn't need to be re-set either. + ... TODO: The "///directive.set_current_module" below shouldn't be necessary. Remove it ASAP. + ... TODO: The context shouldn't need to be re-set either. (|> (///directive.set_current_module module) (///phase.run' state) try.assumed diff --git a/stdlib/source/library/lux/tool/compiler/language/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux.lux index 34e1bbbb7..e86bd51aa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux.lux @@ -18,8 +18,8 @@ ["." signature] ["." key (#+ Key)]]]]]) -## TODO: Remove #module_hash, #imports & #module_state ASAP. -## TODO: Not just from this parser, but from the lux.Module type. +... TODO: Remove #module_hash, #imports & #module_state ASAP. +... TODO: Not just from this parser, but from the lux.Module type. (def: .public writer (Writer .Module) (let [definition (: (Writer Definition) @@ -43,21 +43,21 @@ _.bit _.type))] ($_ _.and - ## #module_hash + ... #module_hash _.nat - ## #module_aliases + ... #module_aliases (_.list alias) - ## #definitions + ... #definitions (_.list (_.and _.text global)) - ## #imports + ... #imports (_.list _.text) - ## #tags + ... #tags (_.list (_.and _.text tag)) - ## #types + ... #types (_.list (_.and _.text type)) - ## #module_annotations + ... #module_annotations (_.maybe _.code) - ## #module_state + ... #module_state _.any))) (def: .public parser @@ -83,21 +83,21 @@ <b>.bit <b>.type))] ($_ <>.and - ## #module_hash + ... #module_hash <b>.nat - ## #module_aliases + ... #module_aliases (<b>.list alias) - ## #definitions + ... #definitions (<b>.list (<>.and <b>.text global)) - ## #imports + ... #imports (<b>.list <b>.text) - ## #tags + ... #tags (<b>.list (<>.and <b>.text tag)) - ## #types + ... #types (<b>.list (<>.and <b>.text type)) - ## #module_annotations + ... #module_annotations (<b>.maybe <b>.code) - ## #module_state + ... #module_state (\ <>.monad in #.Cached)))) (def: .public key diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux index b099446ea..74cadee55 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux @@ -31,7 +31,7 @@ (def: (context [module_id artifact_id]) (-> Context Context) - ## TODO: Find a better way that doesn't rely on clever tricks. + ... TODO: Find a better way that doesn't rely on clever tricks. [(n.- module_id 0) artifact_id]) (def: .public (evaluator expander synthesis_state generation_state generate) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux index f32b12865..315424e3c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -228,7 +228,7 @@ [?buffer (extension.read (get@ #buffer))] (case ?buffer (#.Some buffer) - ## TODO: Optimize by no longer checking for overwrites... + ... TODO: Optimize by no longer checking for overwrites... (if (row.any? (|>> product.left (n.= artifact_id)) buffer) (phase.except ..cannot_overwrite_output [artifact_id]) (extension.update (set@ #buffer (#.Some (row.add [artifact_id custom code] buffer))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux index d760db44f..b9b230b42 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux @@ -31,8 +31,8 @@ (exception: .public (unrecognized_syntax {code Code}) (exception.report ["Code" (%.code code)])) -## TODO: Had to split the 'compile' function due to compilation issues -## with old-luxc. Must re-combine all the code ASAP +... TODO: Had to split the 'compile' function due to compilation issues +... with old-luxc. Must re-combine all the code ASAP (type: (Fix a) (-> a a)) @@ -136,8 +136,8 @@ (-> Expander Phase) (function (compile archive code) (let [[location code'] code] - ## The location must be set in the state for the sake - ## of having useful error messages. + ... The location must be set in the state for the sake + ... of having useful error messages. (/.with_location location (compile|primitive (compile|structure archive compile (compile|others expander archive compile)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux index 0d106fe5a..11c4ba626 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -68,13 +68,13 @@ (#.Item head tail) (re_quantify tail (#.UnivQ head baseT)))) -## Type-checking on the input value is done during the analysis of a -## "case" expression, to ensure that the patterns being used make -## sense for the type of the input value. -## Sometimes, that input value is complex, by depending on -## type-variables or quantifications. -## This function makes it easier for "case" analysis to properly -## type-check the input with respect to the patterns. +... Type-checking on the input value is done during the analysis of a +... "case" expression, to ensure that the patterns being used make +... sense for the type of the input value. +... Sometimes, that input value is complex, by depending on +... type-variables or quantifications. +... This function makes it easier for "case" analysis to properly +... type-check the input with respect to the patterns. (def: (simplify_case caseT) (-> Type (Operation Type)) (loop [envs (: (List (List Type)) @@ -146,22 +146,22 @@ outputA next] (in [output outputA])))) -## This function handles several concerns at once, but it must be that -## way because those concerns are interleaved when doing -## pattern-matching and they cannot be separated. -## The pattern is analysed in order to get a general feel for what is -## expected of the input value. This, in turn, informs the -## type-checking of the input. -## A kind of "continuation" value is passed around which signifies -## what needs to be done _after_ analysing a pattern. -## In general, this is done to analyse the "body" expression -## associated to a particular pattern _in the context of_ said -## pattern. -## The reason why *context* is important is because patterns may bind -## values to local variables, which may in turn be referenced in the -## body expressions. -## That is why the body must be analysed in the context of the -## pattern, and not separately. +... This function handles several concerns at once, but it must be that +... way because those concerns are interleaved when doing +... pattern-matching and they cannot be separated. +... The pattern is analysed in order to get a general feel for what is +... expected of the input value. This, in turn, informs the +... type-checking of the input. +... A kind of "continuation" value is passed around which signifies +... what needs to be done _after_ analysing a pattern. +... In general, this is done to analyse the "body" expression +... associated to a particular pattern _in the context of_ said +... pattern. +... The reason why *context* is important is because patterns may bind +... values to local variables, which may in turn be referenced in the +... body expressions. +... That is why the body must be analysed in the context of the +... pattern, and not separately. (def: (analyse_pattern num_tags inputT pattern next) (All [a] (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a]))) (.case pattern @@ -205,7 +205,7 @@ (let [[prefix suffix] (list.split (dec num_subs) sub_patterns)] (list.zipped/2 subs (list\compose prefix (list (code.tuple suffix))))) - ## (n.= num_subs num_sub_patterns) + ... (n.= num_subs num_sub_patterns) (list.zipped/2 subs sub_patterns))] (do ! [[memberP+ thenA] (list\fold (: (All [a] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux index 6b949ea29..7dd813c09 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux @@ -35,18 +35,18 @@ (-> Nat Bit) (n.> 0)) -## The coverage of a pattern-matching expression summarizes how well -## all the possible values of an input are being covered by the -## different patterns involved. -## Ideally, the pattern-matching has "exhaustive" coverage, which just -## means that every possible value can be matched by at least 1 -## pattern. -## Every other coverage is considered partial, and it would be valued -## as insuficient (since it could lead to runtime errors due to values -## not being handled by any pattern). -## The #Partial tag covers arbitrary partial coverages in a general -## way, while the other tags cover more specific cases for bits -## and variants. +... The coverage of a pattern-matching expression summarizes how well +... all the possible values of an input are being covered by the +... different patterns involved. +... Ideally, the pattern-matching has "exhaustive" coverage, which just +... means that every possible value can be matched by at least 1 +... pattern. +... Every other coverage is considered partial, and it would be valued +... as insuficient (since it could lead to runtime errors due to values +... not being handled by any pattern). +... The #Partial tag covers arbitrary partial coverages in a general +... way, while the other tags cover more specific cases for bits +... and variants. (type: .public #rec Coverage #Partial (#Bit Bit) @@ -101,8 +101,8 @@ (#/.Bind _)) (////\in #Exhaustive) - ## Primitive patterns always have partial coverage because there - ## are too many possibilities as far as values go. + ... Primitive patterns always have partial coverage because there + ... are too many possibilities as far as values go. (^template [<tag>] [(#/.Simple (<tag> _)) (////\in #Partial)]) @@ -112,14 +112,14 @@ [#/.Frac] [#/.Text]) - ## Bits are the exception, since there is only "#1" and - ## "#0", which means it is possible for bit - ## pattern-matching to become exhaustive if complementary parts meet. + ... Bits are the exception, since there is only "#1" and + ... "#0", which means it is possible for bit + ... pattern-matching to become exhaustive if complementary parts meet. (#/.Simple (#/.Bit value)) (////\in (#Bit value)) - ## Tuple patterns can be exhaustive if there is exhaustiveness for all of - ## their sub-patterns. + ... Tuple patterns can be exhaustive if there is exhaustiveness for all of + ... their sub-patterns. (#/.Complex (#/.Tuple membersP+)) (case (list.reversed membersP+) (^or #.End (#.Item _ #.End)) @@ -140,8 +140,8 @@ (in (#Seq leftC rightC))))) lastC prevsP+))) - ## Variant patterns can be shown to be exhaustive if all the possible - ## cases are handled exhaustively. + ... Variant patterns can be shown to be exhaustive if all the possible + ... cases are handled exhaustively. (#/.Complex (#/.Variant [lefts right? value])) (do ////.monad [value_coverage (determine value) @@ -159,12 +159,12 @@ (or (and left (not right)) (and (not left) right))) -## The coverage checker not only verifies that pattern-matching is -## exhaustive, but also that there are no redundant patterns. -## Redundant patterns will never be executed, since there will -## always be a pattern prior to them that would match the input. -## Because of that, the presence of redundant patterns is assumed to -## be a bug, likely due to programmer carelessness. +... The coverage checker not only verifies that pattern-matching is +... exhaustive, but also that there are no redundant patterns. +... Redundant patterns will never be executed, since there will +... always be a pattern prior to them that would match the input. +... Because of that, the presence of redundant patterns is assumed to +... be a bug, likely due to programmer carelessness. (exception: .public (redundant_pattern {so_far Coverage} {addition Coverage}) (exception.report ["Coverage so-far" (%coverage so_far)] @@ -215,17 +215,17 @@ ["So-far Cases" (%.nat so_far_cases)] ["Addition Cases" (%.nat addition_cases)])) -## After determining the coverage of each individual pattern, it is -## necessary to merge them all to figure out if the entire -## pattern-matching expression is exhaustive and whether it contains -## redundant patterns. +... After determining the coverage of each individual pattern, it is +... necessary to merge them all to figure out if the entire +... pattern-matching expression is exhaustive and whether it contains +... redundant patterns. (def: .public (merged addition so_far) (-> Coverage Coverage (Try Coverage)) (case [addition so_far] [#Partial #Partial] (try\in #Partial) - ## 2 bit coverages are exhaustive if they complement one another. + ... 2 bit coverages are exhaustive if they complement one another. (^multi [(#Bit sideA) (#Bit sideSF)] (xor sideA sideSF)) (try\in #Exhaustive) @@ -241,7 +241,7 @@ (\ (dictionary.equivalence ..equivalence) = casesSF casesA) (exception.except ..redundant_pattern [so_far addition]) - ## else + ... else (do {! try.monad} [casesM (monad.fold ! (function (_ [tagA coverageA] casesSF') @@ -270,58 +270,58 @@ [(#Seq leftA rightA) (#Seq leftSF rightSF)] (case [(coverage/= leftSF leftA) (coverage/= rightSF rightA)] - ## Same prefix + ... Same prefix [#1 #0] (do try.monad [rightM (merged rightA rightSF)] (if (exhaustive? rightM) - ## If all that follows is exhaustive, then it can be safely dropped - ## (since only the "left" part would influence whether the - ## merged coverage is exhaustive or not). + ... If all that follows is exhaustive, then it can be safely dropped + ... (since only the "left" part would influence whether the + ... merged coverage is exhaustive or not). (in leftSF) (in (#Seq leftSF rightM)))) - ## Same suffix + ... Same suffix [#0 #1] (do try.monad [leftM (merged leftA leftSF)] (in (#Seq leftM rightA))) - ## The 2 sequences cannot possibly be merged. + ... The 2 sequences cannot possibly be merged. [#0 #0] (try\in (#Alt so_far addition)) - ## There is nothing the addition adds to the coverage. + ... There is nothing the addition adds to the coverage. [#1 #1] (exception.except ..redundant_pattern [so_far addition])) - ## The addition cannot possibly improve the coverage. + ... The addition cannot possibly improve the coverage. [_ #Exhaustive] (exception.except ..redundant_pattern [so_far addition]) - ## The addition completes the coverage. + ... The addition completes the coverage. [#Exhaustive _] (try\in #Exhaustive) - ## The left part will always match, so the addition is redundant. + ... The left part will always match, so the addition is redundant. (^multi [(#Seq left right) single] (coverage/= left single)) (exception.except ..redundant_pattern [so_far addition]) - ## The right part is not necessary, since it can always match the left. + ... The right part is not necessary, since it can always match the left. (^multi [single (#Seq left right)] (coverage/= left single)) (try\in single) - ## When merging a new coverage against one based on Alt, it may be - ## that one of the many coverages in the Alt is complementary to - ## the new one, so effort must be made to fuse carefully, to match - ## the right coverages together. - ## If one of the Alt sub-coverages matches the new one, the cycle - ## must be repeated, in case the resulting coverage can now match - ## other ones in the original Alt. - ## This process must be repeated until no further productive - ## merges can be done. + ... When merging a new coverage against one based on Alt, it may be + ... that one of the many coverages in the Alt is complementary to + ... the new one, so effort must be made to fuse carefully, to match + ... the right coverages together. + ... If one of the Alt sub-coverages matches the new one, the cycle + ... must be repeated, in case the resulting coverage can now match + ... other ones in the original Alt. + ... This process must be repeated until no further productive + ... merges can be done. [_ (#Alt leftS rightS)] (do {! try.monad} [.let [fuse_once (: (-> Coverage (List Coverage) @@ -369,7 +369,7 @@ _ (if (coverage/= so_far addition) - ## The addition cannot possibly improve the coverage. + ... The addition cannot possibly improve the coverage. (exception.except ..redundant_pattern [so_far addition]) - ## There are now 2 alternative paths. + ... There are now 2 alternative paths. (try\in (#Alt so_far addition))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux index 3797288ae..265311550 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -76,7 +76,7 @@ (#.Some expectedT') (recur expectedT') - ## Inference + ... Inference _ (do ! [[input_id inputT] (//type.with_env check.var) @@ -94,8 +94,8 @@ (//scope.environment scope)) bodyA))) /.with_scope - ## Functions have access not only to their argument, but - ## also to themselves, through a local variable. + ... Functions have access not only to their argument, but + ... also to themselves, through a local variable. (//scope.with_local [function_name expectedT]) (//scope.with_local [arg_name inputT]) (//type.with_type outputT) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux index f7980c7ec..a07afe1fa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux @@ -100,13 +100,13 @@ [ex_id _] (//type.with_env check.existential)] (in (named_type location ex_id)))) -## Type-inference works by applying some (potentially quantified) type -## to a sequence of values. -## Function types are used for this, although inference is not always -## done for function application (alternative uses may be records and -## tagged variants). -## But, so long as the type being used for the inference can be treated -## as a function type, this method of inference should work. +... Type-inference works by applying some (potentially quantified) type +... to a sequence of values. +... Function types are used for this, although inference is not always +... done for function application (alternative uses may be records and +... tagged variants). +... But, so long as the type being used for the inference can be treated +... as a function type, this method of inference should work. (def: .public (general archive analyse inferT args) (-> Archive Phase Type (List Code) (Operation [Type (List Analysis)])) (case args @@ -149,13 +149,13 @@ #.None (/.except ..invalid_type_application inferT)) - ## Arguments are inferred back-to-front because, by convention, - ## Lux functions take the most important arguments *last*, which - ## means that the most information for doing proper inference is - ## located in the last arguments to a function call. - ## By inferring back-to-front, a lot of type-annotations can be - ## avoided in Lux code, since the inference algorithm can piece - ## things together more easily. + ... Arguments are inferred back-to-front because, by convention, + ... Lux functions take the most important arguments *last*, which + ... means that the most information for doing proper inference is + ... located in the last arguments to a function call. + ... By inferring back-to-front, a lot of type-annotations can be + ... avoided in Lux code, since the inference algorithm can piece + ... things together more easily. (#.Function inputT outputT) (do ///.monad [[outputT' args'A] (general archive analyse outputT args') @@ -203,7 +203,7 @@ _ base))) -## Turns a record type into the kind of function type suitable for inference. +... Turns a record type into the kind of function type suitable for inference. (def: (record' target originalT inferT) (-> Nat Type Type (Operation Type)) (case inferT @@ -238,7 +238,7 @@ (-> Type (Operation Type)) (record' (n.- 2 0) inferT inferT)) -## Turns a variant type into the kind of function type suitable for inference. +... Turns a variant type into the kind of function type suitable for inference. (def: .public (variant tag expected_size inferT) (-> Nat Nat Type (Operation Type)) (loop [depth 0 @@ -286,7 +286,7 @@ (type.function (list (replace' caseT)) (replace' currentT)))))) - ## else + ... else (/.except ..variant_tag_out_of_bounds [expected_size tag inferT]))) (#.Apply inputT funcT) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux index 2906b9fe8..097f47cce 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux (#- local) [abstract monad] [control @@ -174,8 +174,7 @@ output]) (#try.Failure error) - (#try.Failure error))) - )) + (#try.Failure error))))) (exception: .public cannot_get_next_reference_when_there_is_no_scope) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux index 50afd0eed..6ff5f7ce4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -125,9 +125,9 @@ (//type.with_type expectedT' (recur valueC)) - ## Cannot do inference when the tag is numeric. - ## This is because there is no way of knowing how many - ## cases the inferred sum type would have. + ... Cannot do inference when the tag is numeric. + ... This is because there is no way of knowing how many + ... cases the inferred sum type would have. _ (/.except ..cannot_infer_numeric_tag [expectedT tag valueC]))) @@ -215,7 +215,7 @@ (product archive analyse membersC)) _ - ## Must do inference... + ... Must do inference... (do ! [membersTA (monad.map ! (|>> (analyse archive) //type.with_inference) membersC) @@ -277,10 +277,10 @@ _ (..sum analyse lefts right? archive valueC)))) -## There cannot be any ambiguity or improper syntax when analysing -## records, so they must be normalized for further analysis. -## Normalization just means that all the tags get resolved to their -## canonical form (with their corresponding module identified). +... There cannot be any ambiguity or improper syntax when analysing +... records, so they must be normalized for further analysis. +... Normalization just means that all the tags get resolved to their +... canonical form (with their corresponding module identified). (def: .public (normal record) (-> (List [Code Code]) (Operation (List [Name Code]))) (monad.map ///.monad @@ -295,13 +295,13 @@ (/.except ..record_keys_must_be_tags [key record]))) record)) -## Lux already possesses the means to analyse tuples, so -## re-implementing the same functionality for records makes no sense. -## Records, thus, get transformed into tuples by ordering the elements. +... Lux already possesses the means to analyse tuples, so +... re-implementing the same functionality for records makes no sense. +... Records, thus, get transformed into tuples by ordering the elements. (def: .public (order record) (-> (List [Name Code]) (Operation [(List Code) Type])) (case record - ## empty_record = empty_tuple = unit = [] + ... empty_record = empty_tuple = unit = [] #.End (\ ///.monad in [(list) Any]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux index b085da3c0..16a8764d5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux @@ -196,7 +196,7 @@ [($_ <>.and <c>.nat <c>.any) (function (_ extension phase archive [arity abstractionC]) (do phase.monad - [.let [inputT (type.tuple (list.repeat arity Any))] + [.let [inputT (type.tuple (list.repeated arity Any))] abstractionA (analysis/type.with_type (-> inputT Any) (phase archive abstractionC)) _ (analysis/type.infer (for {@.js ffi.Function} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index b98b2732a..d74b18019 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -161,12 +161,12 @@ (#.Primitive ..inheritance_relationship_type_name (list& class super_class super_interfaces))) -## TODO: Get rid of this template block and use the definition in -## lux/ffi.jvm.lux ASAP +... TODO: Get rid of this template block and use the definition in +... lux/ffi.jvm.lux ASAP (template [<name> <class>] [(def: .public <name> .Type (#.Primitive <class> #.End))] - ## Boxes + ... Boxes [Boolean box.boolean] [Byte box.byte] [Short box.short] @@ -177,7 +177,7 @@ [Character box.char] [String "java.lang.String"] - ## Primitives + ... Primitives [boolean (reflection.reflection reflection.boolean)] [byte (reflection.reflection reflection.byte)] [short (reflection.reflection reflection.short)] @@ -496,7 +496,7 @@ (text.starts_with? descriptor.array_prefix name)) (/////analysis.except ..non_parameter objectT) - ## else + ... else (phase\in (jvm.class name (list))))) (#.Named name anonymous) @@ -560,7 +560,7 @@ (\ phase.monad map jvm.array (check_jvm (#.Primitive unprefixed (list))))) - ## else + ... else (phase\in (jvm.class name (list))))) (^ (#.Primitive (static array.type_name) @@ -928,7 +928,7 @@ [reflection.double box.double] [reflection.char box.char])) - ## else + ... else (do ! [_ (phase.assertion ..primitives_are_not_objects [source_name] (not (dictionary.key? ..boxes source_name))) @@ -1633,7 +1633,7 @@ Strictness (List (Annotation a)) (List (Type Var)) - (List (Type Class)) ## Exceptions + (List (Type Class)) ... Exceptions Text (List Argument) (List (Typed a)) @@ -1715,7 +1715,7 @@ Text (List Argument) (Type Return) - (List (Type Class)) ## Exceptions + (List (Type Class)) ... Exceptions a]) (def: virtual_tag "virtual") @@ -1789,7 +1789,7 @@ Strictness (List (Annotation a)) (List (Type Var)) - (List (Type Class)) ## Exceptions + (List (Type Class)) ... Exceptions (List Argument) (Type Return) a]) @@ -2079,7 +2079,7 @@ (def: (anonymous_class_name module id) (-> Module Nat Text) - (let [global (text.replace_all .module_separator ..jvm_package_separator module) + (let [global (text.replaced .module_separator ..jvm_package_separator module) local (format "anonymous-class" (%.nat id))] (format global ..jvm_package_separator local))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux index 2fe863c2a..9428404aa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux @@ -228,7 +228,7 @@ [($_ <>.and <code>.nat <code>.any) (function (_ extension phase archive [arity abstractionC]) (do phase.monad - [.let [inputT (type.tuple (list.repeat arity Any))] + [.let [inputT (type.tuple (list.repeated arity Any))] abstractionA (analysis/type.with_type (-> inputT Any) (phase archive abstractionC)) _ (analysis/type.infer ..Function)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux index b3f48d4ce..5a76b1804 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux @@ -79,7 +79,7 @@ (-> Type Type Type Type Handler) (simple (list subjectT param0T param1T) outputT)) -## TODO: Get rid of this ASAP +... TODO: Get rid of this ASAP (as_is (exception: .public (char_text_must_be_size_1 {text Text}) (exception.report @@ -121,7 +121,7 @@ (list& input else) (#////analysis.Extension extension_name)))))]))) -## "lux is" represents reference/pointer equality. +... "lux is" represents reference/pointer equality. (def: lux::is Handler (function (_ extension_name analyse archive args) @@ -130,8 +130,8 @@ ((binary varT varT Bit extension_name) analyse archive args)))) -## "lux try" provides a simple way to interact with the host platform's -## error_handling facilities. +... "lux try" provides a simple way to interact with the host platform's +... error_handling facilities. (def: lux::try Handler (function (_ extension_name analyse archive args) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux index 915933925..5fb859b4a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux @@ -196,7 +196,7 @@ [($_ <>.and <code>.nat <code>.any) (function (_ extension phase archive [arity abstractionC]) (do phase.monad - [.let [inputT (type.tuple (list.repeat arity Any))] + [.let [inputT (type.tuple (list.repeated arity Any))] abstractionA (analysis/type.with_type (-> inputT Any) (phase archive abstractionC)) _ (analysis/type.infer ..Function)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux index 00ed63ebf..505ae3bd3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux @@ -185,7 +185,7 @@ (def: (field_definition field) (-> Field (Resource field.Field)) (case field - ## TODO: Handle annotations. + ... TODO: Handle annotations. (#Constant [name annotations type value]) (case value (^template [<tag> <type> <constant>] @@ -205,11 +205,11 @@ [#.Text (type.class "java.lang.String" (list)) [pool.string]] ) - ## TODO: Tighten this pattern-matching so this catch-all clause isn't necessary. + ... TODO: Tighten this pattern-matching so this catch-all clause isn't necessary. _ (undefined)) - ## TODO: Handle annotations. + ... TODO: Handle annotations. (#Variable [name visibility state annotations type]) (field.field (modifier\compose visibility state) name type (row.row)))) @@ -255,7 +255,7 @@ super_class super_interfaces inheritance - ## TODO: Handle annotations. + ... TODO: Handle annotations. annotations fields methods]) @@ -284,16 +284,16 @@ generate (get@ [#directive.generation #directive.phase] state)] methods (monad.map ! (..method_definition [mapping selfT] [analyse synthesize generate]) methods) - ## _ (directive.lift_generation - ## (generation.save! true ["" name] - ## [name - ## (class.class version.v6_0 - ## (modifier\compose class.public inheritance) - ## (name.internal name) (list\map (|>> product.left parser.name ..constraint) parameters) - ## super_class super_interfaces - ## (list\map ..field_definition fields) - ## (list) ## TODO: Add methods - ## (row.row))])) + ... _ (directive.lift_generation + ... (generation.save! true ["" name] + ... [name + ... (class.class version.v6_0 + ... (modifier\compose class.public inheritance) + ... (name.internal name) (list\map (|>> product.left parser.name ..constraint) parameters) + ... super_class super_interfaces + ... (list\map ..field_definition fields) + ... (list) ... TODO: Add methods + ... (row.row))])) _ (directive.lift_generation (generation.log! (format "Class " name)))] (in directive.no_requirements)))])) @@ -302,6 +302,6 @@ (Bundle Anchor (Bytecode Any) Definition) (<| (bundle.prefix "jvm") (|> bundle.empty - ## TODO: Finish handling methods and un-comment. - ## (dictionary.put "class" jvm::class) + ... TODO: Finish handling methods and un-comment. + ... (dictionary.put "class" jvm::class) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux index 2861e1201..5c130e466 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux @@ -63,10 +63,10 @@ (def: (context [module_id artifact_id]) (-> Context Context) - ## TODO: Find a better way that doesn't rely on clever tricks. + ... TODO: Find a better way that doesn't rely on clever tricks. [module_id (n.- (inc artifact_id) 0)]) -## TODO: Inline "evaluate!'" into "evaluate!" ASAP +... TODO: Inline "evaluate!'" into "evaluate!" ASAP (def: (evaluate!' archive generate code//type codeS) (All [anchor expression directive] (-> Archive @@ -100,7 +100,7 @@ (synthesize archive codeA))] (evaluate!' archive generate type codeS))) -## TODO: Inline "definition'" into "definition" ASAP +... TODO: Inline "definition'" into "definition" ASAP (def: (definition' archive generate [module name] code//type codeS) (All [anchor expression directive] (-> Archive @@ -149,7 +149,7 @@ (definition' archive generate name code//type codeS))) (template [<full> <partial> <learn>] - [## TODO: Inline "<partial>" into "<full>" ASAP + [... TODO: Inline "<partial>" into "<full>" ASAP (def: (<partial> archive generate extension codeT codeS) (All [anchor expression directive] (-> Archive @@ -366,9 +366,9 @@ ..directive] ) -## TODO; Both "prepare-program" and "define-program" exist only -## because the old compiler couldn't handle a fully-inlined definition -## for "def::program". Inline them ASAP. +... TODO; Both "prepare-program" and "define-program" exist only +... because the old compiler couldn't handle a fully-inlined definition +... for "def::program". Inline them ASAP. (def: (prepare_program archive analyse synthesize programC) (All [anchor expression directive output] (-> Archive diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux index 13b4a40e4..bfe808472 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux @@ -54,44 +54,44 @@ (template: (!unary function) (|>> list _.apply/* (|> (_.constant function)))) -## ## TODO: Get rid of this ASAP -## (def: lux::syntax_char_case! -## (..custom [($_ <>.and -## <s>.any -## <s>.any -## (<>.some (<s>.tuple ($_ <>.and -## (<s>.tuple (<>.many <s>.i64)) -## <s>.any)))) -## (function (_ extension_name phase archive [input else conditionals]) -## (do {! /////.monad} -## [@input (\ ! map _.var (generation.gensym "input")) -## inputG (phase archive input) -## elseG (phase archive else) -## conditionalsG (: (Operation (List [Expression Expression])) -## (monad.map ! (function (_ [chars branch]) -## (do ! -## [branchG (phase archive branch)] -## (in [(|> chars (list\map (|>> .int _.int (_.=/2 @input))) _.or) -## branchG]))) -## conditionals))] -## (in (_.let (list [@input inputG]) -## (list (list\fold (function (_ [test then] else) -## (_.if test then else)) -## elseG -## conditionalsG))))))])) +... ... TODO: Get rid of this ASAP +... (def: lux::syntax_char_case! +... (..custom [($_ <>.and +... <s>.any +... <s>.any +... (<>.some (<s>.tuple ($_ <>.and +... (<s>.tuple (<>.many <s>.i64)) +... <s>.any)))) +... (function (_ extension_name phase archive [input else conditionals]) +... (do {! /////.monad} +... [@input (\ ! map _.var (generation.gensym "input")) +... inputG (phase archive input) +... elseG (phase archive else) +... conditionalsG (: (Operation (List [Expression Expression])) +... (monad.map ! (function (_ [chars branch]) +... (do ! +... [branchG (phase archive branch)] +... (in [(|> chars (list\map (|>> .int _.int (_.=/2 @input))) _.or) +... branchG]))) +... conditionals))] +... (in (_.let (list [@input inputG]) +... (list (list\fold (function (_ [test then] else) +... (_.if test then else)) +... elseG +... conditionalsG))))))])) (def: lux_procs Bundle (|> /.empty - ## (/.install "syntax char case!" lux::syntax_char_case!) + ... (/.install "syntax char case!" lux::syntax_char_case!) (/.install "is" (binary _.eq/2)) - ## (/.install "try" (unary //runtime.lux//try)) + ... (/.install "try" (unary //runtime.lux//try)) )) -## (def: (capped operation parameter subject) -## (-> (-> Expression Expression Expression) -## (-> Expression Expression Expression)) -## (//runtime.i64//64 (operation parameter subject))) +... (def: (capped operation parameter subject) +... (-> (-> Expression Expression Expression) +... (-> Expression Expression Expression)) +... (//runtime.i64//64 (operation parameter subject))) (def: i64_procs Bundle @@ -109,7 +109,7 @@ (/.install "*" (binary _.*/2)) (/.install "/" (binary _.floor/2)) (/.install "%" (binary _.rem/2)) - ## (/.install "f64" (unary (_.//2 (_.float +1.0)))) + ... (/.install "f64" (unary (_.//2 (_.float +1.0)))) (/.install "char" (unary (|>> _.code_char/1 _.string/1))) ))) @@ -117,16 +117,16 @@ Bundle (<| (/.prefix "f64") (|> /.empty - ## (/.install "=" (binary (product.uncurry _.=/2))) - ## (/.install "<" (binary (product.uncurry _.</2))) - ## (/.install "+" (binary (product.uncurry _.+/2))) - ## (/.install "-" (binary (product.uncurry _.-/2))) - ## (/.install "*" (binary (product.uncurry _.*/2))) - ## (/.install "/" (binary (product.uncurry _.//2))) - ## (/.install "%" (binary (product.uncurry _.rem/2))) - ## (/.install "i64" (unary _.truncate/1)) + ... (/.install "=" (binary (product.uncurry _.=/2))) + ... (/.install "<" (binary (product.uncurry _.</2))) + ... (/.install "+" (binary (product.uncurry _.+/2))) + ... (/.install "-" (binary (product.uncurry _.-/2))) + ... (/.install "*" (binary (product.uncurry _.*/2))) + ... (/.install "/" (binary (product.uncurry _.//2))) + ... (/.install "%" (binary (product.uncurry _.rem/2))) + ... (/.install "i64" (unary _.truncate/1)) (/.install "encode" (unary _.write_to_string/1)) - ## (/.install "decode" (unary //runtime.f64//decode)) + ... (/.install "decode" (unary //runtime.f64//decode)) ))) (def: (text//index [offset sub text]) @@ -146,7 +146,7 @@ (<| (/.prefix "text") (|> /.empty (/.install "=" (binary _.string=/2)) - ## (/.install "<" (binary (product.uncurry _.string<?/2))) + ... (/.install "<" (binary (product.uncurry _.string<?/2))) (/.install "concat" (binary (function (_ [left right]) (_.concatenate/3 [(_.symbol "string") left right])))) (/.install "index" (trinary ..text//index)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux index af7b75366..f17ea75a3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux @@ -45,8 +45,8 @@ (#try.Failure error) (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -## [Procedures] -## [[Bits]] +... [Procedures] +... [[Bits]] (template [<name> <op>] [(def: (<name> [paramG subjectG]) (Binary Expression) @@ -56,7 +56,7 @@ [i64//right_shifted //runtime.i64//right_shifted] ) -## [[Numbers]] +... [[Numbers]] (def: f64//decode (Unary Expression) (|>> list @@ -71,7 +71,7 @@ (list) (_.apply/* (_.var "String.fromCharCode")))) -## [[Text]] +... [[Text]] (def: (text//concat [leftG rightG]) (Binary Expression) (|> leftG (_.do "concat" (list rightG)))) @@ -84,14 +84,14 @@ (Trinary Expression) (//runtime.text//index startG partG subjectG)) -## [[IO]] +... [[IO]] (def: (io//log messageG) (Unary Expression) ($_ _., (//runtime.io//log messageG) //runtime.unit)) -## TODO: Get rid of this ASAP +... TODO: Get rid of this ASAP (def: lux::syntax_char_case! (..custom [($_ <>.and <s>.any @@ -117,7 +117,7 @@ (#.Some (_.return elseG)))) (list)))))])) -## [Bundles] +... [Bundles] (def: lux_procs Bundle (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux index 9daf4b072..b2c84251e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux @@ -136,7 +136,7 @@ (|>> generation.gensym (\ ! map _.var)))] g!inputs (monad.map ! (function (_ _) (variable "input")) - (list.repeat (.nat arity) [])) + (list.repeated (.nat arity) [])) g!abstraction (variable "abstraction")] (in (_.closure g!inputs ($_ _.then diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux index b21b16ad4..4bd10e9ec 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux @@ -96,7 +96,7 @@ (_.set_label @end) ))) -## TODO: Get rid of this ASAP +... TODO: Get rid of this ASAP (def: lux::syntax_char_case! (..custom [($_ <>.and <s>.any diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index b3f22b503..953a4b88a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -608,7 +608,7 @@ [box.float type.float "floatValue"] [box.double type.double "doubleValue"] [box.char type.char "charValue"])) - ## else + ... else valueG)))))])) (def: bundle::object @@ -931,11 +931,12 @@ (#//////synthesis.Extension [name inputsS+]) (#//////synthesis.Extension [name (list\map recur inputsS+)])))) -(def: $Object (type.class "java.lang.Object" (list))) +(def: $Object + (type.class "java.lang.Object" (list))) (def: (anonymous_init_method env) (-> (Environment Synthesis) (Type category.Method)) - (type.method [(list.repeat (list.size env) ..$Object) + (type.method [(list.repeated (list.size env) ..$Object) type.void (list)])) @@ -995,7 +996,7 @@ (\ type.equivalence = type.float returnT) _.freturn - ## (\ type.equivalence = type.double returnT) + ... (\ type.equivalence = type.double returnT) _.dreturn)))) (def: class::anonymous @@ -1015,15 +1016,15 @@ anonymous_class_name (///runtime.class_name context) class (type.class anonymous_class_name (list)) total_environment (|> overriden_methods - ## Get all the environments. + ... Get all the environments. (list\map product.left) - ## Combine them. + ... Combine them. list\join - ## Remove duplicates. + ... Remove duplicates. (set.from_list //////synthesis.hash) set.list) global_mapping (|> total_environment - ## Give them names as "foreign" variables. + ... Give them names as "foreign" variables. list.enumeration (list\map (function (_ [id capture]) [capture (#//////variable.Foreign id)])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux index 656ccac5c..1ef715e28 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux @@ -51,7 +51,7 @@ (template: (!unary function) (|>> list _.apply/* (|> (_.var function)))) -## TODO: Get rid of this ASAP +... TODO: Get rid of this ASAP (def: lux::syntax_char_case! (..custom [($_ <>.and <s>.any @@ -151,9 +151,9 @@ (/.install "concat" (binary (product.uncurry (function.flip _.concat)))) (/.install "index" (trinary ..text//index)) (/.install "size" (unary //runtime.text//size)) - ## TODO: Use version below once the Lua compiler becomes self-hosted. - ## (/.install "size" (unary (for {@.lua (!unary "utf8.len")} - ## (!unary "string.len")))) + ... TODO: Use version below once the Lua compiler becomes self-hosted. + ... (/.install "size" (unary (for {@.lua (!unary "utf8.len")} + ... (!unary "string.len")))) (/.install "char" (binary ..text//char)) (/.install "clip" (trinary ..text//clip)) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux index 1a633675d..e3363fe01 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux @@ -175,7 +175,7 @@ (\ ! map _.var)))] g!inputs (monad.map ! (function (_ _) (variable "input")) - (list.repeat (.nat arity) []))] + (list.repeated (.nat arity) []))] (in (<| (_.closure g!inputs) _.statement (case (.nat arity) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux index 11be7a215..b061d4cc1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux @@ -54,7 +54,7 @@ (template: (!unary function) (|>> list _.apply/* (|> (_.constant function)))) -## TODO: Get rid of this ASAP +... TODO: Get rid of this ASAP (def: lux::syntax_char_case! (..custom [($_ <>.and <s>.any diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux index 4f6c64210..7d32ad88a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux @@ -48,7 +48,7 @@ (#try.Failure error) (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -## TODO: Get rid of this ASAP +... TODO: Get rid of this ASAP (def: lux::syntax_char_case! (..custom [($_ <>.and <s>.any diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux index 349186b55..81d1373d6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux @@ -134,7 +134,7 @@ (|>> generation.gensym (\ ! map _.var)))] g!inputs (monad.map ! (function (_ _) (variable "input")) - (list.repeat (.nat arity) []))] + (list.repeated (.nat arity) []))] (in (_.lambda g!inputs (case (.nat arity) 0 (_.apply/1 abstractionG //runtime.unit) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux index f547703e3..f14017891 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux @@ -51,129 +51,129 @@ (#try.Failure error) (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -## (template: (!unary function) -## (|>> list _.apply/* (|> (_.constant function)))) +... (template: (!unary function) +... (|>> list _.apply/* (|> (_.constant function)))) -## ## ## TODO: Get rid of this ASAP -## ## (def: lux::syntax_char_case! -## ## (..custom [($_ <>.and -## ## <s>.any -## ## <s>.any -## ## (<>.some (<s>.tuple ($_ <>.and -## ## (<s>.tuple (<>.many <s>.i64)) -## ## <s>.any)))) -## ## (function (_ extension_name phase archive [input else conditionals]) -## ## (do {! /////.monad} -## ## [@input (\ ! map _.var (generation.gensym "input")) -## ## inputG (phase archive input) -## ## elseG (phase archive else) -## ## conditionalsG (: (Operation (List [Expression Expression])) -## ## (monad.map ! (function (_ [chars branch]) -## ## (do ! -## ## [branchG (phase archive branch)] -## ## (in [(|> chars (list\map (|>> .int _.int (_.=/2 @input))) _.or) -## ## branchG]))) -## ## conditionals))] -## ## (in (_.let (list [@input inputG]) -## ## (list (list\fold (function (_ [test then] else) -## ## (_.if test then else)) -## ## elseG -## ## conditionalsG))))))])) +... ... ... TODO: Get rid of this ASAP +... ... (def: lux::syntax_char_case! +... ... (..custom [($_ <>.and +... ... <s>.any +... ... <s>.any +... ... (<>.some (<s>.tuple ($_ <>.and +... ... (<s>.tuple (<>.many <s>.i64)) +... ... <s>.any)))) +... ... (function (_ extension_name phase archive [input else conditionals]) +... ... (do {! /////.monad} +... ... [@input (\ ! map _.var (generation.gensym "input")) +... ... inputG (phase archive input) +... ... elseG (phase archive else) +... ... conditionalsG (: (Operation (List [Expression Expression])) +... ... (monad.map ! (function (_ [chars branch]) +... ... (do ! +... ... [branchG (phase archive branch)] +... ... (in [(|> chars (list\map (|>> .int _.int (_.=/2 @input))) _.or) +... ... branchG]))) +... ... conditionals))] +... ... (in (_.let (list [@input inputG]) +... ... (list (list\fold (function (_ [test then] else) +... ... (_.if test then else)) +... ... elseG +... ... conditionalsG))))))])) -## (def: lux_procs -## Bundle -## (|> /.empty -## ## (/.install "syntax char case!" lux::syntax_char_case!) -## (/.install "is" (binary _.eq/2)) -## ## (/.install "try" (unary //runtime.lux//try)) -## )) +... (def: lux_procs +... Bundle +... (|> /.empty +... ... (/.install "syntax char case!" lux::syntax_char_case!) +... (/.install "is" (binary _.eq/2)) +... ... (/.install "try" (unary //runtime.lux//try)) +... )) -## ## (def: (capped operation parameter subject) -## ## (-> (-> Expression Expression Expression) -## ## (-> Expression Expression Expression)) -## ## (//runtime.i64//64 (operation parameter subject))) +... ... (def: (capped operation parameter subject) +... ... (-> (-> Expression Expression Expression) +... ... (-> Expression Expression Expression)) +... ... (//runtime.i64//64 (operation parameter subject))) (def: i64_procs Bundle (<| (/.prefix "i64") (|> /.empty - ## (/.install "and" (binary _.logand/2)) - ## (/.install "or" (binary _.logior/2)) - ## (/.install "xor" (binary _.logxor/2)) - ## (/.install "left-shift" (binary _.ash/2)) - ## (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shift))) - ## (/.install "=" (binary _.=/2)) - ## (/.install "<" (binary _.</2)) - ## (/.install "+" (binary _.+/2)) - ## (/.install "-" (binary _.-/2)) - ## (/.install "*" (binary _.*/2)) - ## (/.install "/" (binary _.floor/2)) - ## (/.install "%" (binary _.rem/2)) - ## (/.install "f64" (unary (_.//2 (_.float +1.0)))) + ... (/.install "and" (binary _.logand/2)) + ... (/.install "or" (binary _.logior/2)) + ... (/.install "xor" (binary _.logxor/2)) + ... (/.install "left-shift" (binary _.ash/2)) + ... (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shift))) + ... (/.install "=" (binary _.=/2)) + ... (/.install "<" (binary _.</2)) + ... (/.install "+" (binary _.+/2)) + ... (/.install "-" (binary _.-/2)) + ... (/.install "*" (binary _.*/2)) + ... (/.install "/" (binary _.floor/2)) + ... (/.install "%" (binary _.rem/2)) + ... (/.install "f64" (unary (_.//2 (_.float +1.0)))) (/.install "char" (unary (|>> //runtime.i64_low _.intToUtf8/1))) ))) -## (def: f64_procs -## Bundle -## (<| (/.prefix "f64") -## (|> /.empty -## ## (/.install "=" (binary (product.uncurry _.=/2))) -## ## (/.install "<" (binary (product.uncurry _.</2))) -## ## (/.install "+" (binary (product.uncurry _.+/2))) -## ## (/.install "-" (binary (product.uncurry _.-/2))) -## ## (/.install "*" (binary (product.uncurry _.*/2))) -## ## (/.install "/" (binary (product.uncurry _.//2))) -## ## (/.install "%" (binary (product.uncurry _.rem/2))) -## ## (/.install "i64" (unary _.truncate/1)) -## (/.install "encode" (unary _.write_to_string/1)) -## ## (/.install "decode" (unary //runtime.f64//decode)) -## ))) +... (def: f64_procs +... Bundle +... (<| (/.prefix "f64") +... (|> /.empty +... ... (/.install "=" (binary (product.uncurry _.=/2))) +... ... (/.install "<" (binary (product.uncurry _.</2))) +... ... (/.install "+" (binary (product.uncurry _.+/2))) +... ... (/.install "-" (binary (product.uncurry _.-/2))) +... ... (/.install "*" (binary (product.uncurry _.*/2))) +... ... (/.install "/" (binary (product.uncurry _.//2))) +... ... (/.install "%" (binary (product.uncurry _.rem/2))) +... ... (/.install "i64" (unary _.truncate/1)) +... (/.install "encode" (unary _.write_to_string/1)) +... ... (/.install "decode" (unary //runtime.f64//decode)) +... ))) -## (def: (text//index [offset sub text]) -## (Trinary (Expression Any)) -## (//runtime.text//index offset sub text)) +... (def: (text//index [offset sub text]) +... (Trinary (Expression Any)) +... (//runtime.text//index offset sub text)) -## (def: (text//clip [offset length text]) -## (Trinary (Expression Any)) -## (//runtime.text//clip offset length text)) +... (def: (text//clip [offset length text]) +... (Trinary (Expression Any)) +... (//runtime.text//clip offset length text)) -## (def: (text//char [index text]) -## (Binary (Expression Any)) -## (_.char_code/1 (_.char/2 [text index]))) +... (def: (text//char [index text]) +... (Binary (Expression Any)) +... (_.char_code/1 (_.char/2 [text index]))) (def: text_procs Bundle (<| (/.prefix "text") (|> /.empty - ## (/.install "=" (binary _.string=/2)) - ## (/.install "<" (binary (product.uncurry _.string<?/2))) + ... (/.install "=" (binary _.string=/2)) + ... (/.install "<" (binary (product.uncurry _.string<?/2))) (/.install "concat" (binary _.paste/2)) - ## (/.install "index" (trinary ..text//index)) - ## (/.install "size" (unary _.length/1)) - ## (/.install "char" (binary ..text//char)) - ## (/.install "clip" (trinary ..text//clip)) + ... (/.install "index" (trinary ..text//index)) + ... (/.install "size" (unary _.length/1)) + ... (/.install "char" (binary ..text//char)) + ... (/.install "clip" (trinary ..text//clip)) ))) -## (def: (io//log! message) -## (Unary (Expression Any)) -## (_.progn (list (_.write_line/1 message) -## //runtime.unit))) +... (def: (io//log! message) +... (Unary (Expression Any)) +... (_.progn (list (_.write_line/1 message) +... //runtime.unit))) -## (def: io_procs -## Bundle -## (<| (/.prefix "io") -## (|> /.empty -## (/.install "log" (unary ..io//log!)) -## (/.install "error" (unary _.error/1)) -## ))) +... (def: io_procs +... Bundle +... (<| (/.prefix "io") +... (|> /.empty +... (/.install "log" (unary ..io//log!)) +... (/.install "error" (unary _.error/1)) +... ))) (def: .public bundle Bundle (<| (/.prefix "lux") (|> /.empty - ## (dictionary.merged lux_procs) + ... (dictionary.merged lux_procs) (dictionary.merged i64_procs) - ## (dictionary.merged f64_procs) + ... (dictionary.merged f64_procs) (dictionary.merged text_procs) - ## (dictionary.merged io_procs) + ... (dictionary.merged io_procs) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux index c1f9be2b9..cfe4e85e6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux @@ -48,7 +48,7 @@ (#try.Failure error) (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -## TODO: Get rid of this ASAP +... TODO: Get rid of this ASAP (def: lux::syntax_char_case! (..custom [($_ <>.and <s>.any diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux index c04ee1e90..c90072ef1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux @@ -54,7 +54,7 @@ (template: (!unary function) (|>> list _.apply/* (|> (_.constant function)))) -## TODO: Get rid of this ASAP +... TODO: Get rid of this ASAP (def: lux::syntax_char_case! (..custom [($_ <>.and <s>.any diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux index 2ca666bd4..9731cb94c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux @@ -95,7 +95,7 @@ (_.apply/2 [(_.apply/2 [(_.function/1 @self) arity_inputs]) extra_inputs]))]) - ## (|> @num_args (_.< arityG)) + ... (|> @num_args (_.< arityG)) (_.lambda (_.args& (list) @missing) (_.apply/2 [(_.function/1 @self) (_.append/2 [@curried @missing])])))))]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux index b17b5fd09..7258dc416 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux @@ -35,11 +35,11 @@ (def: .public (scope expression archive [start initsS+ bodyS]) (Generator (Scope Synthesis)) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [@scope (\ ! map (|>> %.nat (format "loop_scope") _.tag) /////generation.next) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux index 0c557720d..32b090ae1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux @@ -90,7 +90,7 @@ (syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} - [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] + [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars (list.zipped/2 ids) (list\map (function (_ [id var]) @@ -144,7 +144,7 @@ (..left (_.format/3 [_.nil (_.string "~A") error]))]) (..right (_.funcall/+ [op (list ..unit)]))))) -## TODO: Use Common Lisp's swiss-army loop macro instead. +... TODO: Use Common Lisp's swiss-army loop macro instead. (runtime: (lux//program_args inputs) (with_vars [loop input tail] (_.labels (list [loop [(_.args (list input tail)) @@ -176,9 +176,9 @@ (with_vars [last_index_right] (_.let (list [last_index_right (..last_index tuple)]) (list (_.if (_.>/2 [lefts last_index_right]) - ## No need for recursion + ... No need for recursion (_.elt/2 [tuple lefts]) - ## Needs recursion + ... Needs recursion (!recur tuple//left)))))) (runtime: (tuple//right lefts tuple) @@ -188,18 +188,18 @@ (list (_.cond (list [(_.=/2 [last_index_right right_index]) (_.elt/2 [tuple right_index])] [(_.>/2 [last_index_right right_index]) - ## Needs recursion. + ... Needs recursion. (!recur tuple//right)]) (_.subseq/3 [tuple right_index (_.length/1 tuple)]))))))) -## TODO: Find a way to extract parts of the sum without "nth", which -## does a linear search, and is thus expensive. +... TODO: Find a way to extract parts of the sum without "nth", which +... does a linear search, and is thus expensive. (runtime: (sum//get sum wantsLast wantedTag) (with_vars [sum_tag sum_flag] (let [no_match! (_.return sum) sum_value (_.nth/2 [(_.int +2) sum]) test_recursion! (_.if sum_flag - ## Must iterate. + ... Must iterate. (_.progn (list (_.setq wantedTag (_.-/2 [sum_tag wantedTag])) (_.setq sum sum_value))) no_match!)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux index 95121edc4..5d8406d48 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux @@ -22,7 +22,7 @@ ["#" phase]]]]) (syntax: (Vector {size s.nat} elemT) - (in (list (` [(~+ (list.repeat size elemT))])))) + (in (list (` [(~+ (list.repeated size elemT))])))) (type: .public (Nullary of) (-> (Vector 0 of) of)) (type: .public (Unary of) (-> (Vector 1 of) of)) @@ -33,7 +33,7 @@ (syntax: (arity: {arity s.nat} {name s.local_identifier} type) (with_gensyms [g!_ g!extension g!name g!phase g!archive g!inputs g!of g!anchor g!expression g!directive] (do {! meta.monad} - [g!input+ (monad.seq ! (list.repeat arity (macro.gensym "input")))] + [g!input+ (monad.seq ! (list.repeated arity (macro.gensym "input")))] (in (list (` (def: .public ((~ (code.local_identifier name)) (~ g!extension)) (All [(~ g!anchor) (~ g!expression) (~ g!directive)] (-> ((~ type) (~ g!expression)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux index 51e58fb51..6671f1e3f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux @@ -40,7 +40,7 @@ (do ///////phase.monad [valueO (expression archive valueS) bodyO (expression archive bodyS)] - ## TODO: Find some way to do 'let' without paying the price of the closure. + ... TODO: Find some way to do 'let' without paying the price of the closure. (in (_.apply/* (_.closure (list (..register register)) (_.return bodyO)) (list valueO))))) @@ -172,7 +172,7 @@ (^ (/////synthesis.member/left 0)) (///////phase\in (#.Some (push_cursor! (_.at (_.i32 +0) ..peek_cursor)))) - ## Extra optimization + ... Extra optimization (^ (/////synthesis.path/seq (/////synthesis.member/left 0) (/////synthesis.!bind_top register thenP))) @@ -182,7 +182,7 @@ (_.define (..register register) (_.at (_.i32 +0) ..peek_cursor)) then!)))) - ## Extra optimization + ... Extra optimization (^template [<pm> <getter>] [(^ (/////synthesis.path/seq (<pm> lefts) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux index 00ac84cf8..75b54ebe7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux @@ -107,7 +107,7 @@ (_.return (|> @self (apply_poly arity_inputs) (apply_poly extra_inputs))))]) - ## (|> @num_args (_.< arityO)) + ... (|> @num_args (_.< arityO)) (let [all_inputs (|> (_.array (list)) (_.the "slice") (_.do "call" (list @@arguments)))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux index 602ef1191..08a3a7c80 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux @@ -44,11 +44,11 @@ (def: .public (scope! statement expression archive [start initsS+ bodyS]) (Generator! (Scope Synthesis)) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (statement expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [@scope (\ ! map ..@scope /////generation.next) @@ -63,11 +63,11 @@ (def: .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [loop! (scope! statement expression archive [start initsS+ bodyS])] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux index 5d09cbd16..815ee4a36 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux @@ -88,7 +88,7 @@ (syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} - [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] + [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars (list.zipped/2 ids) (list\map (function (_ [id var]) @@ -153,9 +153,9 @@ ($_ _.then (_.define last_index_right (..last_index tuple)) (_.if (_.> lefts last_index_right) - ## No need for recursion + ... No need for recursion (_.return (_.at lefts tuple)) - ## Needs recursion + ... Needs recursion <recur>))))) (runtime: (tuple//right lefts tuple) @@ -167,7 +167,7 @@ (_.cond (list [(_.= last_index_right right_index) (_.return (_.at right_index tuple))] [(_.> last_index_right right_index) - ## Needs recursion. + ... Needs recursion. <recur>]) (_.return (_.do "slice" (list right_index) tuple))) ))))) @@ -198,7 +198,7 @@ is_last? (_.= ..unit sum_flag) extact_match! (_.return sum_value) test_recursion! (_.if is_last? - ## Must recurse. + ... Must recurse. ($_ _.then (_.set wanted_tag (_.- sum_tag wanted_tag)) (_.set sum sum_value)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux index 37f9134fb..d7a20b360 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux @@ -41,7 +41,7 @@ 0 (_\in []) 1 _.pop 2 _.pop2 - _ ## (n.> 2) + _ ... (n.> 2) ($_ _.compose _.pop2 (pop_alt (n.- 2 stack_depth))))) @@ -140,7 +140,7 @@ ([synthesis.member/left ..left_projection] [synthesis.member/right ..right_projection]) - ## Extra optimization + ... Extra optimization (^ (synthesis.path/seq (synthesis.member/left 0) (synthesis.!bind_top register thenP))) @@ -154,7 +154,7 @@ (_.astore register) thenG))) - ## Extra optimization + ... Extra optimization (^template [<pm> <projection>] [(^ (synthesis.path/seq (<pm> lefts) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux index 10dbc1bcc..1fb4d7d86 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux @@ -25,7 +25,7 @@ (def: .public (closure environment) (-> (Environment Synthesis) (List (Type Value))) - (list.repeat (list.size environment) //.type)) + (list.repeated (list.size environment) //.type)) (def: .public (get class register) (-> (Type Class) Register (Bytecode Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux index adc3da6c8..0b4208bec 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux @@ -34,7 +34,7 @@ (-> Nat (Bytecode Any)) ($_ _.compose (|> _.aconst_null - (list.repeat amount) + (list.repeated amount) (monad.seq _.monad)) (_\in []))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux index 9f4bc4e13..f90f1999b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux @@ -95,7 +95,7 @@ [@default _.new_label @labelsH _.new_label @labelsT (|> _.new_label - (list.repeat (dec num_partials)) + (list.repeated (dec num_partials)) (monad.seq _.monad)) .let [cases (|> (list\compose (#.Item [@labelsH @labelsT]) (list @default)) @@ -132,12 +132,12 @@ (apply (n.+ ..this_offset arity_inputs) additional_inputs) _.areturn)) - ## (i.< over_extent (.int stage)) + ... (i.< over_extent (.int stage)) (let [current_environment (|> (list.indices (list.size environment)) (list\map (///foreign.get class)) (monad.seq _.monad)) missing_partials (|> _.aconst_null - (list.repeat (|> num_partials (n.- apply_arity) (n.- stage))) + (list.repeated (|> num_partials (n.- apply_arity) (n.- stage))) (monad.seq _.monad))] ($_ _.compose (_.new class) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux index 07473f901..a43a4c0bc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux @@ -22,7 +22,7 @@ (def: .public (type arity) (-> Arity (Type category.Method)) - (type.method [(list.repeat arity ////type.value) + (type.method [(list.repeated arity ////type.value) ////type.value (list)])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux index b99f5661a..ac11c1cf3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux @@ -45,7 +45,7 @@ (def: (partials arity) (-> Arity (List (Type Value))) - (list.repeat (dec arity) ////type.value)) + (list.repeated (dec arity) ////type.value)) (def: .public (type environment arity) (-> (Environment Synthesis) Arity (Type category.Method)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux index b58414fd9..c3d119ec4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux @@ -99,7 +99,7 @@ (def: (evaluate! library loader eval_class valueG) (-> Library java/lang/ClassLoader Text (Bytecode Any) (Try [Any Definition])) - (let [bytecode_name (text.replace_all class_path_separator .module_separator eval_class) + (let [bytecode_name (text.replaced class_path_separator .module_separator eval_class) bytecode (class.class version.v6_0 class.public (encoding/name.internal bytecode_name) @@ -125,7 +125,7 @@ (def: (execute! library loader temp_label [class_name class_bytecode]) (-> Library java/lang/ClassLoader Text Definition (Try Any)) (io.run (do (try.with io.monad) - [existing_class? (|> (atom.read library) + [existing_class? (|> (atom.read! library) (\ io.monad map (function (_ library) (dictionary.key? library class_name))) (try.lift io.monad) @@ -137,7 +137,7 @@ (def: (define! library loader [module name] valueG) (-> Library java/lang/ClassLoader Name (Bytecode Any) (Try [Text Any Definition])) - (let [class_name (format (text.replace_all .module_separator class_path_separator module) + (let [class_name (format (text.replaced .module_separator class_path_separator module) class_path_separator (name.normal name) "___" (%.nat (text\hash name)))] (do try.monad @@ -151,7 +151,7 @@ (: //runtime.Host (implementation (def: (evaluate! temp_label valueG) - (let [eval_class (|> temp_label name.normal (text.replace_all " " "$"))] + (let [eval_class (|> temp_label name.normal (text.replaced " " "$"))] (\ try.monad map product.left (..evaluate! library loader eval_class valueG)))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux index 857066e4b..3e009b116 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux @@ -54,14 +54,14 @@ .let [storeG (_.astore register)]] (in [fetchG storeG]))))))] (in ($_ _.compose - ## It may look weird that first I fetch all the values separately, - ## and then I store them all. - ## It must be done that way in order to avoid a potential bug. - ## Let's say that you'll recur with 2 expressions: X and Y. - ## If Y depends on the value of X, and you don't perform fetches - ## and stores separately, then by the time Y is evaluated, it - ## will refer to the new value of X, instead of the old value, as - ## should be the case. + ... It may look weird that first I fetch all the values separately, + ... and then I store them all. + ... It must be done that way in order to avoid a potential bug. + ... Let's say that you'll recur with 2 expressions: X and Y. + ... If Y depends on the value of X, and you don't perform fetches + ... and stores separately, then by the time Y is evaluated, it + ... will refer to the new value of X, instead of the old value, as + ... should be the case. (|> updatesG (list\map product.left) (monad.seq _.monad)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux index 7c35b11de..7a5e65744 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux @@ -42,8 +42,8 @@ _ _.i2l] ..wrap_i64)]) ([-1 _.iconst_m1] - ## [+0 _.iconst_0] - ## [+1 _.iconst_1] + ... [+0 _.iconst_0] + ... [+1 _.iconst_1] [+2 _.iconst_2] [+3 _.iconst_3] [+4 _.iconst_4] @@ -101,8 +101,8 @@ _ _.i2d] ..wrap_f64)]) ([-1.0 _.iconst_m1] - ## [+0.0 _.iconst_0] - ## [+1.0 _.iconst_1] + ... [+0.0 _.iconst_0] + ... [+1.0 _.iconst_1] [+2.0 _.iconst_2] [+3.0 _.iconst_3] [+4.0 _.iconst_4] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux index 757716fe7..dff909982 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux @@ -120,11 +120,11 @@ (def: (set! index value) (-> (Bytecode Any) (Bytecode Any) (Bytecode Any)) ($_ _.compose - ## A - _.dup ## AA - index ## AAI - value ## AAIV - _.aastore ## A + ... A + _.dup ... AA + index ... AAI + value ... AAIV + _.aastore ... A )) (def: .public unit (_.string synthesis.unit)) @@ -150,10 +150,10 @@ ..variant::type (list) (#.Some ($_ _.compose - new_variant ## A[3] - (..set! ..variant_tag $tag) ## A[3] - (..set! ..variant_last? $last?) ## A[3] - (..set! ..variant_value $value) ## A[3] + new_variant ... A[3] + (..set! ..variant_tag $tag) ... A[3] + (..set! ..variant_last? $last?) ... A[3] + (..set! ..variant_value $value) ... A[3] _.areturn))))) (def: .public left_flag _.aconst_null) @@ -316,20 +316,20 @@ recur (: (-> Label (Bytecode Any)) (function (_ @loop_start) ($_ _.compose - ## tag, sumT - update_$variant ## tag, sumT - update_$tag ## sub_tag + ... tag, sumT + update_$variant ... tag, sumT + update_$tag ... sub_tag (_.goto @loop_start)))) super_nested_tag ($_ _.compose - ## tag, sumT - _.swap ## sumT, tag + ... tag, sumT + _.swap ... sumT, tag _.isub) super_nested ($_ _.compose - ## tag, sumT - super_nested_tag ## super_tag - $variant ::last? ## super_tag, super_last - $variant ::value ## super_tag, super_last, super_value + ... tag, sumT + super_nested_tag ... super_tag + $variant ::last? ... super_tag, super_last + $variant ::value ... super_tag, super_last, super_value ..variant)]] ($_ _.compose $tag @@ -337,23 +337,23 @@ $variant ::tag _.dup2 (_.if_icmpeq @tags_match!) _.dup2 (_.if_icmpgt @maybe_nested) - $last? (_.ifnull @mismatch!) ## tag, sumT - super_nested ## super_variant + $last? (_.ifnull @mismatch!) ... tag, sumT + super_nested ... super_variant _.areturn - (_.set_label @tags_match!) ## tag, sumT - $last? ## tag, sumT, wants_last? - $variant ::last? ## tag, sumT, wants_last?, is_last? - (_.if_acmpeq @perfect_match!) ## tag, sumT - (_.set_label @maybe_nested) ## tag, sumT - $variant ::last? ## tag, sumT, last? - (_.ifnull @mismatch!) ## tag, sumT + (_.set_label @tags_match!) ... tag, sumT + $last? ... tag, sumT, wants_last? + $variant ::last? ... tag, sumT, wants_last?, is_last? + (_.if_acmpeq @perfect_match!) ... tag, sumT + (_.set_label @maybe_nested) ... tag, sumT + $variant ::last? ... tag, sumT, last? + (_.ifnull @mismatch!) ... tag, sumT (recur @loop) - (_.set_label @perfect_match!) ## tag, sumT - ## _.pop2 + (_.set_label @perfect_match!) ... tag, sumT + ... _.pop2 $variant ::value _.areturn - (_.set_label @mismatch!) ## tag, sumT - ## _.pop2 + (_.set_label @mismatch!) ... tag, sumT + ... _.pop2 not_found _.areturn ))))) @@ -405,7 +405,7 @@ $tuple ::left _.areturn (_.set_label @recursive) - ## Recursive + ... Recursive (recur @loop))))) right_projection::method @@ -432,12 +432,12 @@ (_.set_label @loop) $last_right $right _.dup2 (_.if_icmpne @not_tail) - ## _.pop + ... _.pop $::nested _.areturn (_.set_label @not_tail) (_.if_icmpgt @slice) - ## Must recurse + ... Must recurse (recur @loop) (_.set_label @slice) super_nested @@ -449,7 +449,7 @@ (def: .public (apply::type arity) (-> Arity (Type category.Method)) - (type.method [(list) (list.repeat arity //type.value) //type.value (list)])) + (type.method [(list) (list.repeated arity //type.value) //type.value (list)])) (def: .public apply (_.invokevirtual //function.class ..apply::name (..apply::type 1))) @@ -479,25 +479,25 @@ ^PrintWriter (type.class "java.io.PrintWriter" (list)) print_writer ($_ _.compose - ## WTW - (_.new ^PrintWriter) ## WTWP - _.dup_x1 ## WTPWP - _.swap ## WTPPW - ..true ## WTPPWZ + ... WTW + (_.new ^PrintWriter) ... WTWP + _.dup_x1 ... WTPWP + _.swap ... WTPPW + ..true ... WTPPWZ (_.invokespecial ^PrintWriter "<init>" (type.method [(list) (list (type.class "java.io.Writer" (list)) type.boolean) type.void (list)])) - ## WTP + ... WTP )]] ($_ _.compose (_.try @try @handler @handler //type.error) (_.set_label @try) $unsafe unit ..apply ..right_injection _.areturn - (_.set_label @handler) ## T - string_writer ## TW - _.dup_x1 ## WTW - print_writer ## WTP - (_.invokevirtual //type.error "printStackTrace" (type.method [(list) (list ^PrintWriter) type.void (list)])) ## W - (_.invokevirtual ^StringWriter "toString" (type.method [(list) (list) //type.text (list)])) ## S + (_.set_label @handler) ... T + string_writer ... TW + _.dup_x1 ... WTW + print_writer ... WTP + (_.invokevirtual //type.error "printStackTrace" (type.method [(list) (list ^PrintWriter) type.void (list)])) ... W + (_.invokevirtual ^StringWriter "toString" (type.method [(list) (list) //type.text (list)])) ... S ..left_injection _.areturn ))))) @@ -605,7 +605,7 @@ (def: .public forge_label (Operation Label) (let [shift (n./ 4 i64.width)] - ## This shift is done to avoid the possibility of forged labels - ## to be in the range of the labels that are generated automatically - ## during the evaluation of Bytecode expressions. + ... This shift is done to avoid the possibility of forged labels + ... to be in the range of the labels that are generated automatically + ... during the evaluation of Bytecode expressions. (\ ////.monad map (i64.left_shifted shift) generation.next))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux index 138a9d2fb..fa7627b97 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux @@ -24,7 +24,7 @@ [type.float <float>] [type.double <double>] [type.char <char>])) - ## else + ... else (undefined))))] [primitive_wrapper diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux index db4de757c..589d9191d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux @@ -43,7 +43,7 @@ (do ///////phase.monad [valueO (expression archive valueS) bodyO (expression archive bodyS)] - ## TODO: Find some way to do 'let' without paying the price of the closure. + ... TODO: Find some way to do 'let' without paying the price of the closure. (in (|> bodyO _.return (_.closure (list (..register register))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux index e26940c60..83db2505d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux @@ -113,7 +113,7 @@ (_.return (|> @self (_.apply/* (list (unpack arity_inputs))) (_.apply/* (list (unpack extra_inputs))))))]) - ## (|> @num_args (_.< arityO)) + ... (|> @num_args (_.< arityO)) (_.return (_.closure (list @var_args) (let [@extra_args (_.var "extra_args")] ($_ _.then diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux index d19421620..ddc716045 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux @@ -48,17 +48,17 @@ body)))) (def: .public (scope! statement expression archive as_expression? [start initsS+ bodyS]) - ## (Generator! (Scope Synthesis)) + ... (Generator! (Scope Synthesis)) (-> Phase! Phase Archive Bit (Scope Synthesis) (Operation [(List Expression) Statement])) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (|> bodyS (statement expression archive) (\ ///////phase.monad map (|>> [(list)]))) - ## true loop + ... true loop _ (do {! ///////phase.monad} [@scope (\ ! map ..@scope /////generation.next) @@ -74,11 +74,11 @@ (def: .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [[[artifact_module artifact_id] [initsO+ scope!]] (/////generation.with_new_context archive diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux index d77a51d8a..bfb1ab115 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux @@ -105,7 +105,7 @@ (syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} - [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] + [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars (list.zipped/2 ids) (list\map (function (_ [id var]) @@ -174,9 +174,9 @@ ($_ _.then (_.local/1 last_index_right (..last_index tuple)) (_.if (_.> lefts last_index_right) - ## No need for recursion + ... No need for recursion (_.return (..item lefts tuple)) - ## Needs recursion + ... Needs recursion <recur>))))) (runtime: (tuple//right lefts tuple) @@ -188,7 +188,7 @@ (_.cond (list [(_.= last_index_right right_index) (_.return (..item right_index tuple))] [(_.> last_index_right right_index) - ## Needs recursion. + ... Needs recursion. <recur>]) (_.return (_.apply/* (list tuple (_.+ (_.int +1) right_index) @@ -206,7 +206,7 @@ is_last? (_.= ..unit sum_flag) extact_match! (_.return sum_value) test_recursion! (_.if is_last? - ## Must recurse. + ... Must recurse. ($_ _.then (_.set (list wanted_tag) (_.- sum_tag wanted_tag)) (_.set (list sum) sum_value)) @@ -319,7 +319,7 @@ (-> Expression Expression) (_.- (_.int +1))) -## TODO: Remove this once the Lua compiler becomes self-hosted. +... TODO: Remove this once the Lua compiler becomes self-hosted. (def: on_rembulan? (_.= (_.string "Lua 5.3") (_.var "_VERSION"))) @@ -353,7 +353,7 @@ text (..byte_index text offset) (|> (_.+ offset length) - ## (_.+ (_.int +1)) + ... (_.+ (_.int +1)) (..byte_index text) (_.- (_.int +1)))))] (for {@.lua <normal>} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux index 2906c63ed..9b99a1ca6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux @@ -231,13 +231,13 @@ (_.set! (..register register) ..peek_and_pop) then!))) - ## (^ (/////synthesis.!multi_pop nextP)) - ## (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] - ## (do ///////phase.monad - ## [next! (recur nextP')] - ## (///////phase\in ($_ _.then - ## (..multi_pop! (n.+ 2 extra_pops)) - ## next!)))) + ... (^ (/////synthesis.!multi_pop nextP)) + ... (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] + ... (do ///////phase.monad + ... [next! (recur nextP')] + ... (///////phase\in ($_ _.then + ... (..multi_pop! (n.+ 2 extra_pops)) + ... next!)))) (^template [<tag> <combinator>] [(^ (<tag> preP postP)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux index f4df9c34b..f8746bdf2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux @@ -104,7 +104,7 @@ extra_inputs (_.array_slice/2 [@curried arityG]) next (_.call_user_func_array/2 [@selfL arity_inputs])] (_.return (_.call_user_func_array/2 [next extra_inputs])))]) - ## (|> @num_args (_.< arityG)) + ... (|> @num_args (_.< arityG)) (let [@missing (_.var "missing")] (_.return (<| (_.closure (list (_.reference @selfL) (_.reference @curried)) (list)) ($_ _.then diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux index 32e6346cf..9f66b15b3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux @@ -50,11 +50,11 @@ (def: .public (scope! statement expression archive [start initsS+ bodyS]) (Generator! (Scope Synthesis)) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (statement expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [@scope (\ ! map ..@scope /////generation.next) @@ -69,11 +69,11 @@ (def: .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [[[loop_module loop_artifact] scope!] (/////generation.with_new_context archive diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux index 4a5b7b5e0..f1c4c0eb6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux @@ -73,7 +73,7 @@ (syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} - [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] + [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars (list.zipped/2 ids) (list\map (function (_ [id var]) @@ -155,7 +155,7 @@ (_.=== (_.string "5.6.99") (_.phpversion/0 []))) (runtime: (array//length array) - ## TODO: Get rid of this as soon as JPHP is no longer necessary. + ... TODO: Get rid of this as soon as JPHP is no longer necessary. (_.if ..jphp? (_.return (..tuple_size array)) (_.return (_.count/1 array)))) @@ -186,11 +186,11 @@ ($_ _.then (_.set! (..tuple_size values) size) (_.return values)) - ## https://www.php.net/manual/en/language.operators.assignment.php - ## https://www.php.net/manual/en/language.references.php - ## https://www.php.net/manual/en/functions.arguments.php - ## https://www.php.net/manual/en/language.oop5.references.php - ## https://www.php.net/manual/en/class.arrayobject.php + ... https://www.php.net/manual/en/language.operators.assignment.php + ... https://www.php.net/manual/en/language.references.php + ... https://www.php.net/manual/en/functions.arguments.php + ... https://www.php.net/manual/en/language.oop5.references.php + ... https://www.php.net/manual/en/class.arrayobject.php (_.return (_.new (_.constant "ArrayObject") (list values))))) (runtime: (tuple//left lefts tuple) @@ -201,12 +201,12 @@ (_.set! last_index_right (..jphp_last_index tuple)) (_.set! last_index_right (..normal_last_index tuple))) (_.if (_.> lefts last_index_right) - ## No need for recursion + ... No need for recursion (_.return (_.item lefts tuple)) - ## Needs recursion + ... Needs recursion <recur>))))) - ## TODO: Get rid of this as soon as JPHP is no longer necessary. + ... TODO: Get rid of this as soon as JPHP is no longer necessary. (runtime: (tuple//slice offset input) (with_vars [size index output] ($_ _.then @@ -232,7 +232,7 @@ (_.cond (list [(_.=== last_index_right right_index) (_.return (_.item right_index tuple))] [(_.> last_index_right right_index) - ## Needs recursion. + ... Needs recursion. <recur>]) (_.if ..jphp? (_.return (..tuple//make (_.- right_index (..tuple_size tuple)) @@ -275,14 +275,14 @@ (runtime: (sum//get sum wantsLast wantedTag) (let [no_match! (_.return _.null) sum_tag (_.item (_.string ..variant_tag_field) sum) - ## sum_tag (_.item (_.int +0) sum) + ... sum_tag (_.item (_.int +0) sum) sum_flag (_.item (_.string ..variant_flag_field) sum) - ## sum_flag (_.item (_.int +1) sum) + ... sum_flag (_.item (_.int +1) sum) sum_value (_.item (_.string ..variant_value_field) sum) - ## sum_value (_.item (_.int +2) sum) + ... sum_value (_.item (_.int +2) sum) is_last? (_.=== ..unit sum_flag) test_recursion! (_.if is_last? - ## Must recurse. + ... Must recurse. ($_ _.then (_.set! wantedTag (_.- sum_tag wantedTag)) (_.set! sum sum_value)) @@ -346,13 +346,13 @@ (|>> (i64.and mask)))) (runtime: (i64//right_shifted param subject) - (let [## The mask has to be calculated this way instead of in a more straightforward way - ## because in some languages, 1<<63 = max_negative_value - ## and max_negative_value-1 = max_positive_value. - ## And bitwise, max_positive_value works out to the mask that is desired when param = 0. - ## However, in PHP, max_negative_value-1 underflows and gets cast into a float. - ## And this messes up the computation. - ## This slightly more convoluted calculation avoids that problem. + (let [... The mask has to be calculated this way instead of in a more straightforward way + ... because in some languages, 1<<63 = max_negative_value + ... and max_negative_value-1 = max_positive_value. + ... And bitwise, max_positive_value works out to the mask that is desired when param = 0. + ... However, in PHP, max_negative_value-1 underflows and gets cast into a float. + ... And this messes up the computation. + ... This slightly more convoluted calculation avoids that problem. mask (|> (_.int +1) (_.bit_shl (_.- param (_.int +63))) (_.- (_.int +1)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux index 84bc0c2ca..137623c8a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux @@ -52,7 +52,7 @@ (do ///////phase.monad [valueO (expression archive valueS) bodyO (expression archive bodyS)] - ## TODO: Find some way to do 'let' without paying the price of the closure. + ... TODO: Find some way to do 'let' without paying the price of the closure. (in (_.apply/* (_.lambda (list (..register register)) bodyO) (list valueO))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux index 0b4ecc5e6..0304e7a58 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux @@ -100,7 +100,7 @@ (_.return (|> @self (apply_poly arity_inputs) (apply_poly extra_inputs))))]) - ## (|> @num_args (_.< arityO)) + ... (|> @num_args (_.< arityO)) (let [@next (_.var "next") @missing (_.var "missing")] ($_ _.then diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux index b627e5c44..4332539e5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux @@ -50,11 +50,11 @@ (def: .public (scope! statement expression archive [start initsS+ bodyS]) (Generator! (Scope Synthesis)) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (statement expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [initsO+ (monad.map ! (expression archive) initsS+) @@ -67,11 +67,11 @@ (def: .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [initsO+ (monad.map ! (expression archive) initsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index 49507ed33..2cd100ce9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -112,7 +112,7 @@ (syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} - [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] + [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars (list.zipped/2 ids) (list\map (function (_ [id var]) @@ -216,9 +216,9 @@ ($_ _.then (_.set (list last_index_right) (..last_index tuple)) (_.if (_.> lefts last_index_right) - ## No need for recursion + ... No need for recursion (_.return (_.item lefts tuple)) - ## Needs recursion + ... Needs recursion <recur>)) #.None))) @@ -231,7 +231,7 @@ (_.cond (list [(_.= last_index_right right_index) (_.return (_.item right_index tuple))] [(_.> last_index_right right_index) - ## Needs recursion. + ... Needs recursion. <recur>]) (_.return (_.slice_from right_index tuple)))) #.None)))) @@ -243,7 +243,7 @@ sum_value (_.item (_.int +2) sum) is_last? (_.= ..unit sum_flag) test_recursion! (_.if is_last? - ## Must recurse. + ... Must recurse. ($_ _.then (_.set (list wantedTag) (_.- sum_tag wantedTag)) (_.set (list sum) sum_value)) @@ -292,7 +292,7 @@ [(_.< ..i64::-limit) ..i64::-iteration ..i64::-cap ..i64::+limit] )) (_.return (for {@.python input} - ## This +- is only necessary to guarantee that values within the limits are always longs in Python 2 + ... This +- is only necessary to guarantee that values within the limits are always longs in Python 2 (|> input (_.+ ..i64::+limit) (_.- ..i64::+limit)))))))) (def: as_nat diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux index bbfa2e83d..34334c668 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux @@ -106,7 +106,7 @@ (|> $self (apply_poly arity_args) (apply_poly output_func_args)))]) - ## (|> $num_args (_.< arityO)) + ... (|> $num_args (_.< arityO)) (let [$missing (_.var "missing")] (_.function (list _.var_args) ($_ _.then diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux index 32ec3b041..cdbaf6e1f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux @@ -36,11 +36,11 @@ (def: .public (scope expression archive [offset initsS+ bodyS]) (Generator (Scope Synthesis)) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [$scope (\ ! map _.var (/////generation.gensym "loop_scope")) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux index 037259b8a..c257a2c0c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux @@ -24,7 +24,7 @@ [".T" function] [".T" loop])) -## [Types] +... [Types] (type: .public Translator (-> ls.Synthesis (Meta Expression))) @@ -35,7 +35,7 @@ (Dict Text Proc)) (syntax: (Vector {size s.nat} elemT) - (in (list (` [(~+ (list.repeat size elemT))])))) + (in (list (` [(~+ (list.repeated size elemT))])))) (type: .public Nullary (-> (Vector +0 Expression) Expression)) (type: .public Unary (-> (Vector +1 Expression) Expression)) @@ -43,7 +43,7 @@ (type: .public Trinary (-> (Vector +3 Expression) Expression)) (type: .public Variadic (-> (List Expression) Expression)) -## [Utils] +... [Utils] (def: .public (install name unnamed) (-> Text (-> Text Proc) (-> Bundle Bundle)) @@ -65,7 +65,7 @@ (syntax: (arity: {name s.local_identifier} {arity s.nat}) (with_gensyms [g!_ g!proc g!name g!translate g!inputs] (do {@ macro.monad} - [g!input+ (monad.seq @ (list.repeat arity (macro.gensym "input")))] + [g!input+ (monad.seq @ (list.repeated arity (macro.gensym "input")))] (in (list (` (def: .public ((~ (code.local_identifier name)) (~ g!proc)) (-> (-> (..Vector (~ (code.nat arity)) Expression) Expression) (-> Text ..Proc)) @@ -96,8 +96,8 @@ [inputsI (monad.map @ translate inputsS)] (in (proc inputsI)))))) -## [Procedures] -## [[Lux]] +... [Procedures] +... [[Lux]] (def: (lux//is [leftO rightO]) Binary (r.apply (list leftO rightO) @@ -147,7 +147,7 @@ (install "recur" lux//recur) )) -## [[Bits]] +... [[Bits]] (template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary @@ -180,7 +180,7 @@ (install "arithmetic-right-shift" (binary bit//arithmetic_right_shifted)) ))) -## [[Numbers]] +... [[Numbers]] (host.import: java/lang/Double (#static MIN_VALUE Double) (#static MAX_VALUE Double)) @@ -276,7 +276,7 @@ (install "encode" (unary frac//encode)) (install "decode" (unary runtimeT.frac//decode))))) -## [[Text]] +... [[Text]] (def: (text//concat [subjectO paramO]) Binary (r.apply (list subjectO paramO) (r.global "paste0"))) @@ -306,7 +306,7 @@ (install "clip" (trinary text//clip)) ))) -## [[IO]] +... [[IO]] (def: (io//exit input) Unary (r.apply_kw (list) @@ -327,7 +327,7 @@ (install "current-time" (nullary (function (_ _) (runtimeT.io//current_time! runtimeT.unit))))))) -## [Bundles] +... [Bundles] (def: .public procedures Bundle (<| (prefix "lux") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux index c99ceb072..db45a04fc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux @@ -15,76 +15,76 @@ (/// [".T" runtime]) (// ["@" common])) -## (template [<name> <lua>] -## [(def: (<name> _) @.Nullary <lua>)] +... (template [<name> <lua>] +... [(def: (<name> _) @.Nullary <lua>)] -## [lua//nil "nil"] -## [lua//table "{}"] -## ) +... [lua//nil "nil"] +... [lua//table "{}"] +... ) -## (def: (lua//global proc translate inputs) -## (-> Text @.Proc) -## (case inputs -## (^ (list [_ (#.Text name)])) -## (do macro.Monad<Meta> -## [] -## (in name)) +... (def: (lua//global proc translate inputs) +... (-> Text @.Proc) +... (case inputs +... (^ (list [_ (#.Text name)])) +... (do macro.Monad<Meta> +... [] +... (in name)) -## _ -## (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs)))) +... _ +... (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs)))) -## (def: (lua//call proc translate inputs) -## (-> Text @.Proc) -## (case inputs -## (^ (list& functionS argsS+)) -## (do {@ macro.Monad<Meta>} -## [functionO (translate functionS) -## argsO+ (monad.map @ translate argsS+)] -## (in (lua.apply functionO argsO+))) +... (def: (lua//call proc translate inputs) +... (-> Text @.Proc) +... (case inputs +... (^ (list& functionS argsS+)) +... (do {@ macro.Monad<Meta>} +... [functionO (translate functionS) +... argsO+ (monad.map @ translate argsS+)] +... (in (lua.apply functionO argsO+))) -## _ -## (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs)))) +... _ +... (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs)))) -## (def: lua_procs -## @.Bundle -## (|> (dict.empty text.Hash<Text>) -## (@.install "nil" (@.nullary lua//nil)) -## (@.install "table" (@.nullary lua//table)) -## (@.install "global" lua//global) -## (@.install "call" lua//call))) +... (def: lua_procs +... @.Bundle +... (|> (dict.empty text.Hash<Text>) +... (@.install "nil" (@.nullary lua//nil)) +... (@.install "table" (@.nullary lua//table)) +... (@.install "global" lua//global) +... (@.install "call" lua//call))) -## (def: (table//call proc translate inputs) -## (-> Text @.Proc) -## (case inputs -## (^ (list& tableS [_ (#.Text field)] argsS+)) -## (do {@ macro.Monad<Meta>} -## [tableO (translate tableS) -## argsO+ (monad.map @ translate argsS+)] -## (in (lua.method field tableO argsO+))) +... (def: (table//call proc translate inputs) +... (-> Text @.Proc) +... (case inputs +... (^ (list& tableS [_ (#.Text field)] argsS+)) +... (do {@ macro.Monad<Meta>} +... [tableO (translate tableS) +... argsO+ (monad.map @ translate argsS+)] +... (in (lua.method field tableO argsO+))) -## _ -## (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs)))) +... _ +... (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs)))) -## (def: (table//get [fieldO tableO]) -## @.Binary -## (runtimeT.lua//get tableO fieldO)) +... (def: (table//get [fieldO tableO]) +... @.Binary +... (runtimeT.lua//get tableO fieldO)) -## (def: (table//set [fieldO valueO tableO]) -## @.Trinary -## (runtimeT.lua//set tableO fieldO valueO)) +... (def: (table//set [fieldO valueO tableO]) +... @.Trinary +... (runtimeT.lua//set tableO fieldO valueO)) -## (def: table_procs -## @.Bundle -## (<| (@.prefix "table") -## (|> (dict.empty text.Hash<Text>) -## (@.install "call" table//call) -## (@.install "get" (@.binary table//get)) -## (@.install "set" (@.trinary table//set))))) +... (def: table_procs +... @.Bundle +... (<| (@.prefix "table") +... (|> (dict.empty text.Hash<Text>) +... (@.install "call" table//call) +... (@.install "get" (@.binary table//get)) +... (@.install "set" (@.trinary table//set))))) (def: .public procedures @.Bundle (<| (@.prefix "lua") (dict.empty text.Hash<Text>) - ## (|> lua_procs - ## (dict.merged table_procs)) + ... (|> lua_procs + ... (dict.merged table_procs)) )) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux index 446f2ba72..b416fc128 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux @@ -73,13 +73,13 @@ (n.> half_32 input) (|> post_32 (n.- input) .int (i.* -1)) - ## else + ... else (.int input))) (syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} - [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] + [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars (list.zipped/2 ids) (list\map (function (_ [id var]) @@ -580,9 +580,9 @@ ($_ _.then (_.set! $index_min_length (minimum_index_length index)) (_.if (|> (_.length product) (_.> $index_min_length)) - ## No need for recursion + ... No need for recursion (product_element product index) - ## Needs recursion + ... Needs recursion (tuple::left (updated_index $index_min_length product) (product_tail product)))))) @@ -590,14 +590,14 @@ (let [$index_min_length (_.var "index_min_length")] ($_ _.then (_.set! $index_min_length (minimum_index_length index)) - (_.cond (list [## Last element. + (_.cond (list [... Last element. (|> (_.length product) (_.= $index_min_length)) (product_element product index)] - [## Needs recursion + [... Needs recursion (|> (_.length product) (_.< $index_min_length)) (tuple::right (updated_index $index_min_length product) (product_tail product))]) - ## Must slice + ... Must slice (|> product (_.slice_from index)))))) (runtime: (sum::get sum wants_last? wanted_tag) @@ -607,7 +607,7 @@ sum_value (|> sum (_.item (_.string ..variant_value_field))) is_last? (|> sum_flag (_.= (_.string ""))) test_recursion (_.if is_last? - ## Must recurse. + ... Must recurse. (|> wanted_tag (_.- sum_tag) (sum::get sum_value wants_last?)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux index 7ae3e429a..608bffb04 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux @@ -15,16 +15,16 @@ [meta [archive (#+ Archive)]]]]) -## This universe constant is for languages where one can't just turn all compiled definitions -## into the local variables of some scoping function. +... This universe constant is for languages where one can't just turn all compiled definitions +... into the local variables of some scoping function. (def: .public universe - (for {## In the case of Lua, there is a limit of 200 locals in a function's scope. + (for {... In the case of Lua, there is a limit of 200 locals in a function's scope. @.lua (not ("lua script universe")) - ## Cannot make all definitions be local variables because of limitations with JRuby. + ... Cannot make all definitions be local variables because of limitations with JRuby. @.ruby (not ("ruby script universe")) - ## Cannot make all definitions be local variables because of limitations with PHP itself. + ... Cannot make all definitions be local variables because of limitations with PHP itself. @.php (not ("php script universe")) - ## Cannot make all definitions be local variables because of limitations with Kawa. + ... Cannot make all definitions be local variables because of limitations with Kawa. @.scheme (not ("scheme script universe"))} #0)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux index 0eca3ec0b..253bec114 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux @@ -53,7 +53,7 @@ (do ///////phase.monad [valueO (expression archive valueS) bodyO (expression archive bodyS)] - ## TODO: Find some way to do 'let' without paying the price of the closure. + ... TODO: Find some way to do 'let' without paying the price of the closure. (in (|> bodyO _.return (_.lambda #.None (list (..register register))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux index 11199e5b4..dc39ac6f7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux @@ -99,7 +99,7 @@ (_.return (|> @self (_.apply_lambda/* (list arity_args)) (_.apply_lambda/* (list output_func_args)))))]) - ## (|> @num_args (_.< arityO)) + ... (|> @num_args (_.< arityO)) (let [@missing (_.local "missing")] (_.return (_.lambda #.None (list (_.variadic @missing)) (_.return (|> @self diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux index 89daa0b5f..9e2a43500 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux @@ -51,11 +51,11 @@ (def: .public (scope! statement expression archive [start initsS+ bodyS]) (Generator! (Scope Synthesis)) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (statement expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [initsO+ (monad.map ! (expression archive) initsS+) @@ -68,11 +68,11 @@ (def: .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [body! (scope! statement expression archive [start initsS+ bodyS])] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux index ed17f4d1d..9de984f61 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux @@ -74,7 +74,7 @@ (syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} - [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] + [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars (list.zipped/2 ids) (list\map (function (_ [id var]) @@ -139,9 +139,9 @@ ($_ _.then (_.set (list last_index_right) (..last_index tuple)) (_.if (_.> lefts last_index_right) - ## No need for recursion + ... No need for recursion (_.return (_.item lefts tuple)) - ## Needs recursion + ... Needs recursion <recur>))))) (runtime: (tuple//right lefts tuple) @@ -153,7 +153,7 @@ (_.cond (list [(_.= last_index_right right_index) (_.return (_.item right_index tuple))] [(_.> last_index_right right_index) - ## Needs recursion. + ... Needs recursion. <recur>]) (_.return (_.array_range right_index (..tuple_size tuple) tuple))) ))))) @@ -194,7 +194,7 @@ sum_value (_.item (_.string ..variant_value_field) sum) is_last? (_.= ..unit sum_flag) test_recursion! (_.if is_last? - ## Must recurse. + ... Must recurse. ($_ _.then (_.set (list wantedTag) (_.- sum_tag wantedTag)) (_.set (list sum) sum_value)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux index 89acab685..95e2f1edb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux @@ -29,7 +29,7 @@ ["#." synthesis (#+ Synthesis)]]]]) (syntax: (Vector {size s.nat} elemT) - (in (list (` [(~+ (list.repeat size elemT))])))) + (in (list (` [(~+ (list.repeated size elemT))])))) (type: .public Nullary (-> (Vector 0 Expression) Computation)) (type: .public Unary (-> (Vector 1 Expression) Computation)) @@ -40,7 +40,7 @@ (syntax: (arity: {name s.local_identifier} {arity s.nat}) (with_gensyms [g!_ g!extension g!name g!phase g!inputs] (do {! macro.monad} - [g!input+ (monad.seq ! (list.repeat arity (macro.gensym "input")))] + [g!input+ (monad.seq ! (list.repeated arity (macro.gensym "input")))] (in (list (` (def: .public ((~ (code.local_identifier name)) (~ g!extension)) (-> (-> (..Vector (~ (code.nat arity)) Expression) Computation) Handler) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux index 9998edab9..d52f5d920 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux @@ -93,7 +93,7 @@ (_.begin (list (|> @self (apply_poly arity_args) (apply_poly output_func_args)))))) - ## (|> @num_args (_.</2 arityO)) + ... (|> @num_args (_.</2 arityO)) (_.lambda [(list) (#.Some @missing)] (|> @self (apply_poly (_.append/2 @curried @missing))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux index 32da9a0de..fb9add0aa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux @@ -39,11 +39,11 @@ (def: .public (scope expression archive [start initsS+ bodyS]) (Generator (Scope Synthesis)) (case initsS+ - ## function/false/non-independent loop + ... function/false/non-independent loop #.End (expression archive bodyS) - ## true loop + ... true loop _ (do {! ///////phase.monad} [initsO+ (monad.map ! (expression archive) initsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index 5e17c3324..e61519d16 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux @@ -61,7 +61,7 @@ (syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} - [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] + [ids (monad.seq ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars (list.zipped/2 ids) (list\map (function (_ [id var]) @@ -114,9 +114,9 @@ (_.begin (list (_.define_constant last_index_right (..last_index tuple)) (_.if (_.>/2 lefts last_index_right) - ## No need for recursion + ... No need for recursion (_.vector_ref/2 tuple lefts) - ## Needs recursion + ... Needs recursion (tuple//left (_.-/2 last_index_right lefts) (_.vector_ref/2 tuple last_index_right))))))) @@ -128,7 +128,7 @@ (<| (_.if (_.=/2 last_index_right right_index) (_.vector_ref/2 tuple right_index)) (_.if (_.>/2 last_index_right right_index) - ## Needs recursion. + ... Needs recursion. (tuple//right (_.-/2 last_index_right lefts) (_.vector_ref/2 tuple last_index_right))) (_.begin @@ -155,7 +155,7 @@ (with_vars [sum_tag sum_flag sum_value sum_temp sum_dump] (let [no_match _.nil test_recursion (_.if sum_flag - ## Must recurse. + ... Must recurse. (sum//get sum_value last? (|> wanted_tag (_.-/2 sum_tag))) @@ -233,22 +233,22 @@ @lux//program_args))) (def: i64//+limit (_.manual "+9223372036854775807" - ## "+0x7FFFFFFFFFFFFFFF" + ... "+0x7FFFFFFFFFFFFFFF" )) (def: i64//-limit (_.manual "-9223372036854775808" - ## "-0x8000000000000000" + ... "-0x8000000000000000" )) (def: i64//+iteration (_.manual "+18446744073709551616" - ## "+0x10000000000000000" + ... "+0x10000000000000000" )) (def: i64//-iteration (_.manual "-18446744073709551616" - ## "-0x10000000000000000" + ... "-0x10000000000000000" )) (def: i64//+cap (_.manual "+9223372036854775808" - ## "+0x8000000000000000" + ... "+0x8000000000000000" )) (def: i64//-cap (_.manual "-9223372036854775809" - ## "-0x8000000000000001" + ... "-0x8000000000000001" )) (runtime: (i64//64 input) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux index aa9c0a757..46189fb26 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -231,9 +231,9 @@ (in (/.branch/case [input (list\fold weave headSP tailSP+)])))) (template: (!masking <variable> <output>) - [[(#///analysis.Bind <variable>) - (#///analysis.Reference (///reference.local <output>))] - (list)]) + [[[(#///analysis.Bind <variable>) + (#///analysis.Reference (///reference.local <output>))] + (list)]]) (def: .public (synthesize_let synthesize archive input @variable body) (-> Phase Archive Synthesis Register Analysis (Operation Synthesis)) @@ -256,9 +256,9 @@ (in (/.branch/if [test then else])))) (template: (!get <patterns> <output>) - [[(///analysis.pattern/tuple <patterns>) - (#///analysis.Reference (///reference.local <output>))] - (.list)]) + [[[(///analysis.pattern/tuple <patterns>) + (#///analysis.Reference (///reference.local <output>))] + (.list)]]) (def: .public (synthesize_get synthesize archive input patterns @member) (-> Phase Archive Synthesis (///analysis.Tuple ///analysis.Pattern) Register (Operation Synthesis)) @@ -325,12 +325,12 @@ {#bindings (set.empty n.hash) #dependencies (set.empty ///reference/variable.hash)}) -## TODO: Use this to declare all local variables at the beginning of -## script functions. -## That way, it should be possible to do cheap "let" expressions, -## since the variable will exist beforehand, so no closure will need -## to be created for it. -## Apply this trick to JS, Python et al. +... TODO: Use this to declare all local variables at the beginning of +... script functions. +... That way, it should be possible to do cheap "let" expressions, +... since the variable will exist beforehand, so no closure will need +... to be created for it. +... Apply this trick to JS, Python et al. (def: .public (storage path) (-> Path Storage) (loop for_path diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux index 39d934d96..83822639e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -39,7 +39,7 @@ (list\map (|>> /.variable/local)))) (template: .public (self_reference) - (/.variable/local 0)) + [(/.variable/local 0)]) (def: (expanded_nested_self_reference arity) (-> Arity Synthesis) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index 7f2f025f7..6ba15c700 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -51,8 +51,8 @@ (^or (#/.Seq (#/.Access (#/.Member member)) (#/.Seq (#/.Bind register) post)) - ## This alternative form should never occur in practice. - ## Yet, it is "technically" possible to construct it. + ... This alternative form should never occur in practice. + ... Yet, it is "technically" possible to construct it. (#/.Seq (#/.Seq (#/.Access (#/.Member member)) (#/.Bind register)) post)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux index 212181b2d..6615d49a9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -1,29 +1,29 @@ -## This is LuxC's parser. -## It takes the source code of a Lux file in raw text form and -## extracts the syntactic structure of the code from it. -## It only produces Lux Code nodes, and thus removes any white-space -## and comments while processing its inputs. - -## Another important aspect of the parser is that it keeps track of -## its position within the input data. -## That is, the parser takes into account the line and column -## information in the input text (it doesn't really touch the -## file-name aspect of the location, leaving it intact in whatever -## base-line location it is given). - -## This particular piece of functionality is not located in one -## function, but it is instead scattered throughout several parsers, -## since the logic for how to update the location varies, depending on -## what is being parsed, and the rules involved. - -## You will notice that several parsers have a "where" parameter, that -## tells them the location position prior to the parser being run. -## They are supposed to produce some parsed output, alongside an -## updated location pointing to the end position, after the parser was run. - -## Lux Code nodes/tokens are annotated with location meta-data -## [file-name, line, column] to keep track of their provenance and -## location, which is helpful for documentation and debugging. +... This is LuxC's parser. +... It takes the source code of a Lux file in raw text form and +... extracts the syntactic structure of the code from it. +... It only produces Lux Code nodes, and thus removes any white-space +... and comments while processing its inputs. + +... Another important aspect of the parser is that it keeps track of +... its position within the input data. +... That is, the parser takes into account the line and column +... information in the input text (it doesn't really touch the +... file-name aspect of the location, leaving it intact in whatever +... base-line location it is given). + +... This particular piece of functionality is not located in one +... function, but it is instead scattered throughout several parsers, +... since the logic for how to update the location varies, depending on +... what is being parsed, and the rules involved. + +... You will notice that several parsers have a "where" parameter, that +... tells them the location position prior to the parser being run. +... They are supposed to produce some parsed output, alongside an +... updated location pointing to the end position, after the parser was run. + +... Lux Code nodes/tokens are annotated with location meta-data +... [file-name, line, column] to keep track of their provenance and +... location, which is helpful for documentation and debugging. (.module: [library [lux #* @@ -54,18 +54,18 @@ [(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. +... 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. -## TODO: Make an extension to take advantage of java/lang/String::indexOf<int,int> -## to get better performance than the current "lux text index" extension. +... TODO: Make an extension to take advantage of java/lang/String::indexOf<int,int> +... to get better performance than the current "lux text index" extension. -## TODO: Instead of always keeping a "where" location variable, keep the -## individual components (i.e. file, line and column) separate, so -## that updated the "where" only involved updating the components, and -## producing the locations only involved building them, without any need -## for pattern-matching and de-structuring. +... TODO: Instead of always keeping a "where" location variable, keep the +... individual components (i.e. file, line and column) separate, so +... that updated the "where" only involved updating the components, and +... producing the locations only involved building them, without any need +... for pattern-matching and de-structuring. (type: Char Nat) @@ -113,15 +113,15 @@ (template [<char> <definition>] [(def: .public <definition> <char>)] - ## Form delimiters + ... Form delimiters ["(" open_form] [")" close_form] - ## Tuple delimiters + ... Tuple delimiters ["[" open_tuple] ["]" close_tuple] - ## Record delimiters + ... Record delimiters ["{" open_record] ["}" close_record] @@ -134,13 +134,13 @@ ["." frac_separator] - ## The parts of a name are separated by a single mark. - ## E.g. module.short. - ## Only one such mark may be used in an name, since there - ## can only be 2 parts to a name (the module [before the - ## mark], and the short [after the mark]). - ## There are also some extra rules regarding name syntax, - ## encoded in the parser. + ... The parts of a name are separated by a single mark. + ... E.g. module.short. + ... Only one such mark may be used in an name, since there + ... can only be 2 parts to a name (the module [before the + ... mark], and the short [after the mark]). + ... There are also some extra rules regarding name syntax, + ... encoded in the parser. ["." name_separator] ) @@ -193,7 +193,7 @@ (#.Right <binding>) <body> - ## (#.Left error) + ... (#.Left error) <<otherwise>> (:assume <<otherwise>>))]) @@ -233,9 +233,9 @@ [where (<tag> (list.reversed stack))]]) (#.Left [source' error])))))] - ## Form and tuple syntax is mostly the same, differing only in the - ## delimiters involved. - ## They may have an arbitrary number of arbitrary Code nodes as elements. + ... Form and tuple syntax is mostly the same, differing only in the + ... delimiters involved. + ... They may have an arbitrary number of arbitrary Code nodes as elements. [form_parser ..close_form #.Form] [tuple_parser ..close_tuple #.Tuple] ) @@ -299,7 +299,7 @@ [[<digits>] @then] - ## else + ... else @else)]) (template: (!if_digit?+ @char @then @else_options @else) @@ -309,7 +309,7 @@ (~~ (template.spliced @else_options))] - ## else + ... else @else))]) (`` (template: (!if_name_char?|tail @char @then @else) @@ -317,7 +317,7 @@ [[<non_name_chars>] @else] - ## else + ... else @then)])) (`` (template: (!if_name_char?|head @char @then @else) @@ -325,14 +325,14 @@ [[<non_name_chars> <digits>] @else] - ## else + ... else @then)])) ) (template: (!number_output <source_code> <start> <end> <codec> <tag>) [(case (|> <source_code> (!clip <start> <end>) - (text.replace_all ..digit_separator "") + (text.replaced ..digit_separator "") (\ <codec> decode)) (#.Right output) (#.Right [[(let [[where::file where::line where::column] where] @@ -377,7 +377,7 @@ (recur (!n/+ 3 end) char/0) [] <failure>))] - ## else + ... else <failure>))) <frac_output>)] @@ -477,10 +477,10 @@ [(!letE [source' full_name] (..full_name_parser @aliases @offset @source) (#.Right [source' [@where (@tag full_name)]]))]) -## TODO: Grammar macro for specifying syntax. -## (grammar: lux_grammar -## [expression ...] -## [form "(" [#* expression] ")"]) +... TODO: Grammar macro for specifying syntax. +... (grammar: lux_grammar +... [expression ...] +... [form "(" [#* expression] ")"]) (with_expansions [<consume_1> (as_is where (!inc offset/0) source_code) <move_1> (as_is [(!forward 1 where) (!inc offset/0) source_code]) @@ -499,8 +499,8 @@ (def: .public (parse current_module aliases source_code//size) (-> Text Aliases Nat (Parser Code)) - ## The "exec []" is only there to avoid function fusion. - ## This is to preserve the loop as much as possible and keep it tight. + ... The "exec []" is only there to avoid function fusion. + ... This is to preserve the loop as much as possible and keep it tight. (exec [] (function (recur [where offset/0 source_code]) @@ -522,17 +522,17 @@ (~~ (static text.carriage_return))] (recur (!horizontal where offset/0 source_code)) - ## New line + ... New line [(~~ (static text.new_line))] (recur (!vertical where offset/0 source_code)) <composites> - ## Text + ... Text [(~~ (static ..text_delimiter))] (text_parser where (!inc offset/0) source_code) - ## Special code + ... Special code [(~~ (static ..sigil))] (<| (let [offset/1 (!inc offset/0)]) (!with_char+ source_code//size source_code offset/1 char/1 @@ -541,15 +541,6 @@ [[(~~ (static ..name_separator))] (!short_name_parser source_code//size current_module <move_2> where #.Tag) - ## Single_line comment - [(~~ (static ..sigil))] - (case ("lux text index" (!inc offset/1) (static text.new_line) source_code) - (#.Some end) - (recur (!vertical where end source_code)) - - _ - (!end_of_file where offset/1 source_code current_module)) - (~~ (template [<char> <bit>] [[<char>] (..bit_syntax <bit> [where offset/0 source_code])] @@ -557,33 +548,57 @@ ["0" #0] ["1" #1]))] - ## else + ... else (!if_name_char?|head char/1 - ## Tag + ... Tag (!full_name_parser offset/1 <move_2> where aliases #.Tag) (!failure ..parse where offset/0 source_code)))) - ## Coincidentally (= ..name_separator ..frac_separator) + ... Coincidentally (= ..name_separator ..frac_separator) [(~~ (static ..name_separator)) - ## (~~ (static ..frac_separator)) + ... (~~ (static ..frac_separator)) ] - (<| (let [offset/1 (!inc offset/0)]) - (!with_char+ source_code//size source_code offset/1 char/1 - (!end_of_file where offset/1 source_code current_module)) - (!if_digit? char/1 - (rev_parser source_code//size offset/0 where (!inc offset/1) source_code) - (!short_name_parser source_code//size current_module [where offset/1 source_code] where #.Identifier))) + ... It's either a Rev, an identifier, or a comment. + (with_expansions [<rev_parser> (rev_parser source_code//size offset/0 where (!inc offset/1) source_code) + <short_name_parser> (!short_name_parser source_code//size current_module [where offset/1 source_code] where #.Identifier) + <comment_parser> (case ("lux text index" (!inc offset/1) (static text.new_line) source_code) + (#.Some end) + (recur (!vertical where end source_code)) + + _ + (!end_of_file where offset/1 source_code current_module))] + (<| (let [offset/1 (!inc offset/0)]) + (!with_char+ source_code//size source_code offset/1 char/1 + (!end_of_file where offset/1 source_code current_module)) + (!if_digit? char/1 + ... It's a Rev. + <rev_parser> + ... It's either an identifier, or a comment. + ("lux syntax char case!" char/1 + [[(~~ (static ..name_separator))] + ... It's either an identifier, or a comment. + (<| (let [offset/2 (!inc offset/1)]) + (!with_char+ source_code//size source_code offset/2 char/2 + (!end_of_file where offset/2 source_code current_module)) + ("lux syntax char case!" char/2 + [[(~~ (static ..name_separator))] + ... It's a comment. + <comment_parser>] + ... It's an identifier. + <short_name_parser>))] + ... It's an identifier. + <short_name_parser>)))) [(~~ (static ..positive_sign)) (~~ (static ..negative_sign))] (!signed_parser source_code//size offset/0 where source_code aliases (!end_of_file where offset/0 source_code current_module))] - ## else + ... else (!if_digit? char/0 - ## Natural number + ... Natural number (nat_parser source_code//size offset/0 where (!inc offset/0) source_code) - ## Identifier + ... Identifier (!full_name_parser offset/0 [<consume_1>] where aliases #.Identifier)) ))) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux index 3112e5b74..0f02d37be 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -39,7 +39,7 @@ (type: .public State {#locals Nat - ## https://en.wikipedia.org/wiki/Currying + ... https://en.wikipedia.org/wiki/Currying #currying? Bit}) (def: .public fresh_resolver @@ -790,13 +790,13 @@ #..Pop nextP)]) -## TODO: There are sister patterns to the simple side checks for tuples. -## These correspond to the situation where tuple members are accessed -## and bound to variables, but those variables are never used, so they -## become POPs. -## After re-implementing unused-variable-elimination, must add those -## pattern-optimizations again, since a lot of BINDs will become POPs -## and thus will result in useless code being generated. +... TODO: There are sister patterns to the simple side checks for tuples. +... These correspond to the situation where tuple members are accessed +... and bound to variables, but those variables are never used, so they +... become POPs. +... After re-implementing unused-variable-elimination, must add those +... pattern-optimizations again, since a lot of BINDs will become POPs +... and thus will result in useless code being generated. (template [<name> <side>] [(template: .public (<name> idx nextP) [($_ ..path/seq diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index 8efda7f03..e42b2d2c5 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -127,7 +127,7 @@ (#.Some [id (#.Some [existing_descriptor existing_document existing_output])]) (if (is? document existing_document) - ## TODO: Find out why this code allows for the same module to be added more than once. It looks fishy... + ... TODO: Find out why this code allows for the same module to be added more than once. It looks fishy... (#try.Success archive) (exception.except ..cannot_replace_document [module existing_document document])) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io.lux b/stdlib/source/library/lux/tool/compiler/meta/io.lux index 5aa0d7331..72f98b3d9 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io.lux @@ -14,7 +14,7 @@ (def: .public (safe system) (All [m] (-> (System m) Text Text)) - (text.replace_all "/" (\ system separator))) + (text.replaced "/" (\ system separator))) (def: .public lux_context "lux") diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux index 81ac25578..e65ede1eb 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -73,8 +73,8 @@ (def: (find_local_source_file fs importer import contexts partial_host_extension module) (-> (file.System Async) Module Import (List Context) Extension Module (Async (Try [file.Path Binary]))) - ## Preference is explicitly being given to Lux files that have a host extension. - ## Normal Lux files (i.e. without a host extension) are then picked as fallback files. + ... Preference is explicitly being given to Lux files that have a host extension. + ... Normal Lux files (i.e. without a host extension) are then picked as fallback files. (do {! async.monad} [outcome (..find_source_file fs importer contexts module (..full_host_extension partial_host_extension))] (case outcome @@ -109,8 +109,8 @@ (def: (find_any_source_file fs importer import contexts partial_host_extension module) (-> (file.System Async) Module Import (List Context) Extension Module (Async (Try [file.Path Binary]))) - ## Preference is explicitly being given to Lux files that have a host extension. - ## Normal Lux files (i.e. without a host extension) are then picked as fallback files. + ... Preference is explicitly being given to Lux files that have a host extension. + ... Normal Lux files (i.e. without a host extension) are then picked as fallback files. (do {! async.monad} [outcome (find_local_source_file fs importer import contexts partial_host_extension module)] (case outcome diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux index bf5ed12f9..a36b2fda0 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -118,11 +118,11 @@ (def: byte 1) -## https://en.wikipedia.org/wiki/Kibibyte +... https://en.wikipedia.org/wiki/Kibibyte (def: kibi_byte (n.* 1,024 byte)) -## https://en.wikipedia.org/wiki/Mebibyte +... https://en.wikipedia.org/wiki/Mebibyte (def: mebi_byte (n.* 1,024 kibi_byte)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux index ee2dd3415..f3bfea5b0 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -44,7 +44,7 @@ ["$" lux [generation (#+ Context)]]]]]]) -## TODO: Delete ASAP +... TODO: Delete ASAP (type: (Action ! a) (! (Try a))) |