diff options
author | Eduardo Julian | 2021-05-24 11:23:40 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-05-24 11:23:40 -0400 |
commit | 86538182a50390e7882778cc02e69482e846edd5 (patch) | |
tree | 5f2b5800d4f9bd63355d78bc541110aaf0c6b134 /stdlib/source/lux/tool | |
parent | 20a3f2650e2e72b5f4e525bee8a6354a711f575b (diff) |
Almost done with Scheme.
But will have to postpone finishing it because Kawa is not up to snuff.
Diffstat (limited to '')
10 files changed, 665 insertions, 394 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux index cb006d9f7..0ef931275 100644 --- a/stdlib/source/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/lux/tool/compiler/default/platform.lux @@ -171,20 +171,21 @@ <State+> (Try <State+>))) (|> (:share [<type_vars>] - {<State+> - state} - {(///directive.Operation <type_vars> Any) - (do ///phase.monad - [_ (///directive.lift_analysis - (///analysis.install analysis_state)) - _ (///directive.lift_analysis - (extension.with extender analysers)) - _ (///directive.lift_synthesis - (extension.with extender synthesizers)) - _ (///directive.lift_generation - (extension.with extender (:assume generators))) - _ (extension.with extender (:assume directives))] - (wrap []))}) + <State+> + state + + (///directive.Operation <type_vars> Any) + (do ///phase.monad + [_ (///directive.lift_analysis + (///analysis.install analysis_state)) + _ (///directive.lift_analysis + (extension.with extender analysers)) + _ (///directive.lift_synthesis + (extension.with extender synthesizers)) + _ (///directive.lift_generation + (extension.with extender (:assume generators))) + _ (extension.with extender (:assume directives))] + (wrap []))) (///phase.run' state) (\ try.monad map product.left))) @@ -343,70 +344,73 @@ (-> <Compiler> <Importer>))) (let [current (stm.var initial) pending (:share [<type_vars>] - {<Context> - initial} - {(Var (Dictionary Module <Pending>)) - (:assume (stm.var (dictionary.new text.hash)))}) + <Context> + initial + + (Var (Dictionary Module <Pending>)) + (:assume (stm.var (dictionary.new text.hash)))) dependence (: (Var Dependence) (stm.var ..independence))] (function (_ compile) (function (import! importer module) (do {! promise.monad} [[return signal] (:share [<type_vars>] - {<Context> - initial} - {(Promise [<Return> (Maybe [<Context> - archive.ID - <Signal>])]) - (:assume - (stm.commit - (do {! stm.monad} - [dependence (if (text\= archive.runtime_module importer) - (stm.read dependence) - (do ! - [[_ dependence] (stm.update (..depend importer module) dependence)] - (wrap dependence)))] - (case (..verify_dependencies importer module dependence) - (#try.Failure error) - (wrap [(promise.resolved (#try.Failure error)) - #.None]) - - (#try.Success _) - (do ! - [[archive state] (stm.read current)] - (if (archive.archived? archive module) - (wrap [(promise\wrap (#try.Success [archive state])) - #.None]) - (do ! - [@pending (stm.read pending)] - (case (dictionary.get module @pending) - (#.Some [return signal]) - (wrap [return - #.None]) - - #.None - (case (if (archive.reserved? archive module) - (do try.monad - [module_id (archive.id module archive)] - (wrap [module_id archive])) - (archive.reserve module archive)) - (#try.Success [module_id archive]) - (do ! - [_ (stm.write [archive state] current) - #let [[return signal] (:share [<type_vars>] - {<Context> - initial} - {<Pending> - (promise.promise [])})] - _ (stm.update (dictionary.put module [return signal]) pending)] - (wrap [return - (#.Some [[archive state] - module_id - signal])])) - - (#try.Failure error) - (wrap [(promise\wrap (#try.Failure error)) - #.None]))))))))))}) + <Context> + initial + + (Promise [<Return> (Maybe [<Context> + archive.ID + <Signal>])]) + (:assume + (stm.commit + (do {! stm.monad} + [dependence (if (text\= archive.runtime_module importer) + (stm.read dependence) + (do ! + [[_ dependence] (stm.update (..depend importer module) dependence)] + (wrap dependence)))] + (case (..verify_dependencies importer module dependence) + (#try.Failure error) + (wrap [(promise.resolved (#try.Failure error)) + #.None]) + + (#try.Success _) + (do ! + [[archive state] (stm.read current)] + (if (archive.archived? archive module) + (wrap [(promise\wrap (#try.Success [archive state])) + #.None]) + (do ! + [@pending (stm.read pending)] + (case (dictionary.get module @pending) + (#.Some [return signal]) + (wrap [return + #.None]) + + #.None + (case (if (archive.reserved? archive module) + (do try.monad + [module_id (archive.id module archive)] + (wrap [module_id archive])) + (archive.reserve module archive)) + (#try.Success [module_id archive]) + (do ! + [_ (stm.write [archive state] current) + #let [[return signal] (:share [<type_vars>] + <Context> + initial + + <Pending> + (promise.promise []))] + _ (stm.update (dictionary.put module [return signal]) pending)] + (wrap [return + (#.Some [[archive state] + module_id + signal])])) + + (#try.Failure error) + (wrap [(promise\wrap (#try.Failure error)) + #.None]))))))))))) _ (case signal #.None (wrap []) @@ -472,11 +476,12 @@ (-> Import Static Expander <Platform> Compilation <Context> <Return>)) (let [[compilation_sources compilation_libraries compilation_target compilation_module] compilation base_compiler (:share [<type_vars>] - {<Context> - context} - {(///.Compiler <State+> .Module Any) - (:assume - ((//init.compiler expander syntax.prelude (get@ #write platform)) $.key (list)))}) + <Context> + context + + (///.Compiler <State+> .Module Any) + (:assume + ((//init.compiler expander syntax.prelude (get@ #write platform)) $.key (list)))) compiler (..parallel context (function (_ import! module_id [archive state] module) @@ -494,12 +499,13 @@ (let [new_dependencies (get@ #///.dependencies compilation) all_dependencies (list\compose new_dependencies all_dependencies) continue! (:share [<type_vars>] - {<Platform> - platform} - {(-> <Context> (///.Compilation <State+> .Module Any) (List Module) - (Action [Archive <State+>])) - (:assume - recur)})] + <Platform> + platform + + (-> <Context> (///.Compilation <State+> .Module Any) (List Module) + (Action [Archive <State+>])) + (:assume + recur))] (do ! [[archive state] (case new_dependencies #.Nil diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux index 1c0a89df5..ef13cb2ef 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux @@ -27,8 +27,130 @@ [/// ["." phase]]]]]]) +(def: array::new + Handler + (custom + [<c>.any + (function (_ extension phase archive lengthC) + (do phase.monad + [lengthA (analysis/type.with_type Nat + (phase archive lengthC)) + [var_id varT] (analysis/type.with_env check.var) + _ (analysis/type.infer (type (Array varT)))] + (wrap (#analysis.Extension extension (list lengthA)))))])) + +(def: array::length + Handler + (custom + [<c>.any + (function (_ extension phase archive arrayC) + (do phase.monad + [[var_id varT] (analysis/type.with_env check.var) + arrayA (analysis/type.with_type (type (Array varT)) + (phase archive arrayC)) + _ (analysis/type.infer Nat)] + (wrap (#analysis.Extension extension (list arrayA)))))])) + +(def: array::read + Handler + (custom + [(<>.and <c>.any <c>.any) + (function (_ extension phase archive [indexC arrayC]) + (do phase.monad + [indexA (analysis/type.with_type Nat + (phase archive indexC)) + [var_id varT] (analysis/type.with_env check.var) + arrayA (analysis/type.with_type (type (Array varT)) + (phase archive arrayC)) + _ (analysis/type.infer varT)] + (wrap (#analysis.Extension extension (list indexA arrayA)))))])) + +(def: array::write + Handler + (custom + [($_ <>.and <c>.any <c>.any <c>.any) + (function (_ extension phase archive [indexC valueC arrayC]) + (do phase.monad + [indexA (analysis/type.with_type Nat + (phase archive indexC)) + [var_id varT] (analysis/type.with_env check.var) + valueA (analysis/type.with_type varT + (phase archive valueC)) + arrayA (analysis/type.with_type (type (Array varT)) + (phase archive arrayC)) + _ (analysis/type.infer (type (Array varT)))] + (wrap (#analysis.Extension extension (list indexA valueA arrayA)))))])) + +(def: array::delete + Handler + (custom + [($_ <>.and <c>.any <c>.any) + (function (_ extension phase archive [indexC arrayC]) + (do phase.monad + [indexA (analysis/type.with_type Nat + (phase archive indexC)) + [var_id varT] (analysis/type.with_env check.var) + arrayA (analysis/type.with_type (type (Array varT)) + (phase archive arrayC)) + _ (analysis/type.infer (type (Array varT)))] + (wrap (#analysis.Extension extension (list indexA arrayA)))))])) + +(def: bundle::array + Bundle + (<| (bundle.prefix "array") + (|> bundle.empty + (bundle.install "new" array::new) + (bundle.install "length" array::length) + (bundle.install "read" array::read) + (bundle.install "write" array::write) + (bundle.install "delete" array::delete) + ))) + +(def: Nil + (for {@.scheme + host.Nil} + Any)) + +(def: Function + (for {@.scheme host.Function} + Any)) + +(def: bundle::object + Bundle + (<| (bundle.prefix "object") + (|> bundle.empty + (bundle.install "nil" (/.nullary ..Nil)) + (bundle.install "nil?" (/.unary Any Bit)) + ))) + +(def: scheme::constant + Handler + (custom + [<c>.text + (function (_ extension phase archive name) + (do phase.monad + [_ (analysis/type.infer Any)] + (wrap (#analysis.Extension extension (list (analysis.text name))))))])) + +(def: scheme::apply + Handler + (custom + [($_ <>.and <c>.any (<>.some <c>.any)) + (function (_ extension phase archive [abstractionC inputsC]) + (do {! phase.monad} + [abstractionA (analysis/type.with_type ..Function + (phase archive abstractionC)) + inputsA (monad.map ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) + _ (analysis/type.infer Any)] + (wrap (#analysis.Extension extension (list& abstractionA inputsA)))))])) + (def: #export bundle Bundle (<| (bundle.prefix "scheme") (|> bundle.empty + (dictionary.merge bundle::array) + (dictionary.merge bundle::object) + + (bundle.install "constant" scheme::constant) + (bundle.install "apply" scheme::apply) ))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux index 4b84727aa..458b6bcd5 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux @@ -328,10 +328,11 @@ _ (<| <scope> (///.install extender (:coerce Text name)) (:share [anchor expression directive] - {(Handler anchor expression directive) - handler} - {<type> - (:assume handlerV)})) + (Handler anchor expression directive) + handler + + <type> + (:assume handlerV))) _ (/////directive.lift_generation (/////generation.log! (format <description> " " (%.text (:coerce Text name)))))] (wrap /////directive.no_requirements)) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux index 6a13e29bb..71a122eff 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux @@ -54,145 +54,122 @@ (|>> 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} -## [inputG (phase archive input) -## [[context_module context_artifact] elseG] (generation.with_new_context archive -## (phase archive else)) -## @input (\ ! map _.var (generation.gensym "input")) -## conditionalsG (: (Operation (List [Expression Expression])) -## (monad.map ! (function (_ [chars branch]) -## (do ! -## [branchG (phase archive branch)] -## (wrap [(|> chars -## (list\map (|>> .int _.int (_.=== @input))) -## (list\fold (function (_ clause total) -## (if (is? _.null total) -## clause -## (_.or clause total))) -## _.null)) -## branchG]))) -## conditionals)) -## #let [foreigns (|> conditionals -## (list\map (|>> product.right synthesis.path/then //case.dependencies)) -## (list& (//case.dependencies (synthesis.path/then else))) -## list.concat -## (set.from_list _.hash) -## set.to_list) -## @expression (_.constant (reference.artifact [context_module context_artifact])) -## directive (_.define_function @expression (list& (_.parameter @input) (list\map _.reference foreigns)) -## (list\fold (function (_ [test then] else) -## (_.if test (_.return then) else)) -## (_.return elseG) -## conditionalsG))] -## _ (generation.execute! directive) -## _ (generation.save! (%.nat context_artifact) directive)] -## (wrap (_.apply/* (list& inputG foreigns) @expression))))])) - -## (def: lux_procs -## Bundle -## (|> /.empty -## (/.install "syntax char case!" lux::syntax_char_case!) -## (/.install "is" (binary (product.uncurry _.===))) -## (/.install "try" (unary //runtime.lux//try)) -## )) - -## (def: (left_shift [parameter subject]) -## (Binary Expression) -## (_.bit_shl (_.% (_.int +64) parameter) subject)) - -## (def: i64_procs -## Bundle -## (<| (/.prefix "i64") -## (|> /.empty -## (/.install "and" (binary (product.uncurry _.bit_and))) -## (/.install "or" (binary (product.uncurry _.bit_or))) -## (/.install "xor" (binary (product.uncurry _.bit_xor))) -## (/.install "left-shift" (binary ..left_shift)) -## (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shift))) -## (/.install "=" (binary (product.uncurry _.==))) -## (/.install "<" (binary (product.uncurry _.<))) -## (/.install "+" (binary (product.uncurry //runtime.i64//+))) -## (/.install "-" (binary (product.uncurry //runtime.i64//-))) -## (/.install "*" (binary (product.uncurry //runtime.i64//*))) -## (/.install "/" (binary (function (_ [parameter subject]) -## (_.intdiv/2 [subject parameter])))) -## (/.install "%" (binary (product.uncurry _.%))) -## (/.install "f64" (unary (_./ (_.float +1.0)))) -## (/.install "char" (unary //runtime.i64//char)) -## ))) - -## (def: (f64//% [parameter subject]) -## (Binary Expression) -## (_.fmod/2 [subject parameter])) - -## (def: (f64//encode subject) -## (Unary Expression) -## (_.number_format/2 [subject (_.int +17)])) - -## (def: f64_procs -## Bundle -## (<| (/.prefix "f64") -## (|> /.empty -## (/.install "=" (binary (product.uncurry _.==))) -## (/.install "<" (binary (product.uncurry _.<))) -## (/.install "+" (binary (product.uncurry _.+))) -## (/.install "-" (binary (product.uncurry _.-))) -## (/.install "*" (binary (product.uncurry _.*))) -## (/.install "/" (binary (product.uncurry _./))) -## (/.install "%" (binary ..f64//%)) -## (/.install "i64" (unary _.intval/1)) -## (/.install "encode" (unary ..f64//encode)) -## (/.install "decode" (unary //runtime.f64//decode))))) - -## (def: (text//clip [paramO extraO subjectO]) -## (Trinary Expression) -## (//runtime.text//clip paramO extraO subjectO)) - -## (def: (text//index [startO partO textO]) -## (Trinary Expression) -## (//runtime.text//index textO partO startO)) +(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)] + (wrap [(|> chars (list\map (|>> .int _.int (_.=/2 @input))) _.or) + branchG]))) + conditionals))] + (wrap (_.let (list [@input inputG]) + (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 (product.uncurry _.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: i64_procs + Bundle + (<| (/.prefix "i64") + (|> /.empty + (/.install "and" (binary (product.uncurry //runtime.i64//and))) + (/.install "or" (binary (product.uncurry //runtime.i64//or))) + (/.install "xor" (binary (product.uncurry //runtime.i64//xor))) + (/.install "left-shift" (binary (product.uncurry //runtime.i64//left_shift))) + (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shift))) + (/.install "=" (binary (product.uncurry _.=/2))) + (/.install "<" (binary (product.uncurry _.</2))) + (/.install "+" (binary (product.uncurry (..capped _.+/2)))) + (/.install "-" (binary (product.uncurry (..capped _.-/2)))) + (/.install "*" (binary (product.uncurry (..capped _.*/2)))) + (/.install "/" (binary (product.uncurry //runtime.i64//division))) + (/.install "%" (binary (product.uncurry _.remainder/2))) + (/.install "f64" (unary (_.//2 (_.float +1.0)))) + (/.install "char" (unary (|>> _.integer->char/1 (_.make-string/2 (_.int +1))))) + ))) -## (def: text_procs -## Bundle -## (<| (/.prefix "text") -## (|> /.empty -## (/.install "=" (binary (product.uncurry _.==))) -## (/.install "<" (binary (product.uncurry _.<))) -## (/.install "concat" (binary (product.uncurry (function.flip _.concat)))) -## (/.install "index" (trinary ..text//index)) -## (/.install "size" (unary //runtime.text//size)) -## (/.install "char" (binary (product.uncurry //runtime.text//char))) -## (/.install "clip" (trinary ..text//clip)) -## ))) +(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 _.remainder/2))) + (/.install "i64" (unary _.truncate/1)) + (/.install "encode" (unary _.number->string/1)) + (/.install "decode" (unary //runtime.f64//decode))))) + +(def: (text//index [offset sub text]) + (Trinary Expression) + (//runtime.text//index offset sub text)) + +(def: (text//clip [paramO extraO subjectO]) + (Trinary Expression) + (//runtime.text//clip paramO extraO subjectO)) + +(def: text_procs + Bundle + (<| (/.prefix "text") + (|> /.empty + (/.install "=" (binary (product.uncurry _.string=?/2))) + (/.install "<" (binary (product.uncurry _.string<?/2))) + (/.install "concat" (binary (product.uncurry _.string-append/2))) + (/.install "index" (trinary ..text//index)) + (/.install "size" (unary _.string-length/1)) + (/.install "char" (binary (product.uncurry //runtime.text//char))) + (/.install "clip" (trinary ..text//clip)) + ))) -## (def: io//current-time -## (Nullary Expression) -## (|>> _.time/0 -## (_.* (_.int +1,000)))) +(def: (io//log! message) + (Unary Expression) + (_.begin (list (_.display/1 message) + (_.display/1 (_.string text.new_line)) + //runtime.unit))) -## (def: io_procs -## Bundle -## (<| (/.prefix "io") -## (|> /.empty -## (/.install "log" (unary //runtime.io//log!)) -## (/.install "error" (unary //runtime.io//throw!)) -## (/.install "current-time" (nullary ..io//current-time))))) +(def: io_procs + Bundle + (<| (/.prefix "io") + (|> /.empty + (/.install "log" (unary ..io//log!)) + (/.install "error" (unary _.raise/1)) + (/.install "current-time" (nullary (function.constant (//runtime.io//current_time //runtime.unit)))) + ))) (def: #export bundle Bundle (<| (/.prefix "lux") (|> /.empty - ## (dictionary.merge lux_procs) - ## (dictionary.merge i64_procs) - ## (dictionary.merge f64_procs) - ## (dictionary.merge text_procs) - ## (dictionary.merge io_procs) + (dictionary.merge lux_procs) + (dictionary.merge i64_procs) + (dictionary.merge f64_procs) + (dictionary.merge text_procs) + (dictionary.merge io_procs) ))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux index 0a05436c2..55e46ad23 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux @@ -32,8 +32,76 @@ ["//#" /// #_ ["#." phase]]]]]]) +(def: (array::new size) + (Unary Expression) + (_.make-vector/2 size _.nil)) + +(def: array::length + (Unary Expression) + _.vector-length/1) + +(def: (array::read [indexG arrayG]) + (Binary Expression) + (_.vector-ref/2 arrayG indexG)) + +(def: (array::write [indexG valueG arrayG]) + (Trinary Expression) + (//runtime.array//write indexG valueG arrayG)) + +(def: (array::delete [indexG arrayG]) + (Binary Expression) + (//runtime.array//write indexG _.nil arrayG)) + +(def: array + Bundle + (<| (/.prefix "array") + (|> /.empty + (/.install "new" (unary array::new)) + (/.install "length" (unary array::length)) + (/.install "read" (binary array::read)) + (/.install "write" (trinary array::write)) + (/.install "delete" (binary array::delete)) + ))) + +(template [<!> <?> <unit>] + [(def: <!> (Nullary Expression) (function.constant <unit>)) + (def: <?> (Unary Expression) (_.eq?/2 <unit>))] + + [object::nil object::nil? _.nil] + ) + +(def: object + Bundle + (<| (/.prefix "object") + (|> /.empty + (/.install "nil" (nullary object::nil)) + (/.install "nil?" (unary object::nil?)) + ))) + +(def: scheme::constant + (custom + [<s>.text + (function (_ extension phase archive name) + (do ////////phase.monad + [] + (wrap (_.var name))))])) + +(def: scheme::apply + (custom + [($_ <>.and <s>.any (<>.some <s>.any)) + (function (_ extension phase archive [abstractionS inputsS]) + (do {! ////////phase.monad} + [abstractionG (phase archive abstractionS) + inputsG (monad.map ! (phase archive) inputsS)] + (wrap (_.apply/* inputsG abstractionG))))])) + (def: #export bundle Bundle (<| (/.prefix "scheme") (|> /.empty + (dictionary.merge ..array) + (dictionary.merge ..object) + + (/.install "constant" scheme::constant) + (/.install "apply" scheme::apply) ))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index 1638a64ca..ec8ff641f 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -250,19 +250,20 @@ (_.set (list wantedTag) (_.- sum_tag wantedTag)) (_.set (list sum) sum_value)) no_match!)] - (<| (_.while (_.bool true)) - (_.cond (list [(_.= wantedTag sum_tag) - (_.if (_.= wantsLast sum_flag) - (_.return sum_value) - test_recursion!)] + (_.while (_.bool true) + (_.cond (list [(_.= wantedTag sum_tag) + (_.if (_.= wantsLast sum_flag) + (_.return sum_value) + test_recursion!)] - [(_.< wantedTag sum_tag) - test_recursion!] + [(_.< wantedTag sum_tag) + test_recursion!] - [(_.= ..unit wantsLast) - (_.return (variant' (_.- wantedTag sum_tag) sum_flag sum_value))]) + [(_.= ..unit wantsLast) + (_.return (variant' (_.- wantedTag sum_tag) sum_flag sum_value))]) - no_match!)))) + no_match!) + #.None))) (def: runtime//adt (Statement Any) @@ -296,13 +297,8 @@ ## This +- is only necessary to guarantee that values within the limits are always longs in Python 2 (|> input (_.+ ..i64//+limit) (_.- ..i64//+limit)))))))) -(runtime: i64//nat_top - (|> (_.int +1) - (_.bit_shl (_.int +64)) - (_.- (_.int +1)))) - (def: as_nat - (_.% (_.manual "0x10000000000000000"))) + (_.% ..i64//+iteration)) (runtime: (i64//left_shift param subject) (_.return (|> subject @@ -345,14 +341,14 @@ [i64//xor _.bit_xor] ) -(def: version +(def: python_version (Expression Any) (|> (_.__import__/1 (_.unicode "sys")) (_.the "version_info") (_.the "major"))) (runtime: (i64//char value) - (_.return (_.? (_.= (_.int +3) ..version) + (_.return (_.? (_.= (_.int +3) ..python_version) (_.chr/1 value) (_.unichr/1 value)))) @@ -360,7 +356,6 @@ (Statement Any) ($_ _.then @i64//64 - @i64//nat_top @i64//left_shift @i64//right_shift @i64//division diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux index 8f7d8a8b1..884e20c0f 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux @@ -9,6 +9,8 @@ [collection ["." list ("#\." functor fold)] ["." set]]] + [macro + ["." template]] [math [number ["i" int]]] @@ -87,7 +89,7 @@ (def: (pop! var) (-> Var Computation) - (_.set! var var)) + (_.set! var (_.cdr/1 var))) (def: save_cursor! Computation @@ -95,7 +97,8 @@ (def: restore_cursor! Computation - (_.set! @cursor (_.car/1 @savepoint))) + (_.begin (list (_.set! @cursor (_.car/1 @savepoint)) + (_.set! @savepoint (_.cdr/1 @savepoint))))) (def: peek Computation @@ -106,17 +109,20 @@ (pop! @cursor)) (def: pm_error - (_.string "PM-ERROR")) + (_.string (template.with_locals [pm_error] + (template.text [pm_error])))) (def: fail! (_.raise/1 pm_error)) -(def: (pm_catch handler) - (-> Expression Computation) - (_.lambda [(list @alt_error) #.None] - (_.if (|> @alt_error (_.eqv?/2 pm_error)) - handler - (_.raise/1 @alt_error)))) +(def: (try_pm on_failure happy_path) + (-> Expression Expression Computation) + (_.guard @alt_error + (list [(_.and (list (_.string?/1 @alt_error) + (_.string=?/2 ..pm_error @alt_error))) + on_failure]) + #.None + happy_path)) (def: (pattern_matching' expression archive) (Generator Path) @@ -158,49 +164,54 @@ ..peek) then!]))) (#.Cons cons))] - (wrap (_.cond clauses ..fail!)))]) + (wrap (list\fold (function (_ [when then] else) + (_.if when then else)) + ..fail! + clauses)))]) ([#/////synthesis.I64_Fork //primitive.i64 _.=/2] [#/////synthesis.F64_Fork //primitive.f64 _.=/2] - [#/////synthesis.Text_Fork //primitive.text _.eqv?/2]) + [#/////synthesis.Text_Fork //primitive.text _.string=?/2]) (^template [<pm> <flag> <prep>] [(^ (<pm> idx)) - (///////phase\wrap (_.let (list [@temp (|> idx <prep> .int _.int (//runtime.sum//get ..peek <flag>))]) + (///////phase\wrap (_.let (list [@temp (|> idx <prep> .int _.int (//runtime.sum//get ..peek (_.bool <flag>)))]) (_.if (_.null?/1 @temp) ..fail! (push_cursor! @temp))))]) - ([/////synthesis.side/left _.nil (<|)] - [/////synthesis.side/right (_.string "") inc]) + ([/////synthesis.side/left false (<|)] + [/////synthesis.side/right true inc]) + + (^ (/////synthesis.member/left 0)) + (///////phase\wrap (..push_cursor! (_.vector-ref/2 ..peek (_.int +0)))) (^template [<pm> <getter>] - [(^ (<pm> idx)) - (///////phase\wrap (push_cursor! (<getter> (_.int (.int idx)) ..peek)))]) + [(^ (<pm> lefts)) + (///////phase\wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push_cursor!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^template [<tag> <computation>] - [(^ (<tag> leftP rightP)) - (do ///////phase.monad - [leftO (recur leftP) - rightO (recur rightP)] - (wrap <computation>))]) - ([/////synthesis.path/seq (_.begin (list leftO - rightO))] - [/////synthesis.path/alt (_.with_exception_handler - (pm_catch (_.begin (list restore_cursor! - rightO))) - (_.lambda [(list) #.None] - (_.begin (list save_cursor! - leftO))))])))) + (^ (/////synthesis.path/seq leftP rightP)) + (do ///////phase.monad + [leftO (recur leftP) + rightO (recur rightP)] + (wrap (_.begin (list leftO + rightO)))) + + (^ (/////synthesis.path/alt leftP rightP)) + (do {! ///////phase.monad} + [leftO (recur leftP) + rightO (recur rightP)] + (wrap (try_pm (_.begin (list restore_cursor! + rightO)) + (_.begin (list save_cursor! + leftO))))) + ))) (def: (pattern_matching expression archive pathP) (Generator Path) - (do ///////phase.monad - [pattern_matching! (pattern_matching' expression archive pathP)] - (wrap (_.with_exception_handler - (pm_catch (_.raise/1 (_.string "Invalid expression for pattern-matching."))) - (_.lambda [(list) #.None] - pattern_matching!))))) + (\ ///////phase.monad map + (try_pm (_.raise/1 (_.string "Invalid expression for pattern-matching."))) + (pattern_matching' expression archive pathP))) (def: #export (case expression archive [valueS pathP]) (Generator [Synthesis Path]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux index edcdb89b4..380352c5b 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux @@ -89,9 +89,10 @@ output_func_args (//runtime.slice arityO (|> @num_args (_.-/2 arityO)) @curried)] - (|> @self - (apply_poly arity_args) - (apply_poly output_func_args)))) + (_.begin (list ## (_.display/1 (_.string (format "!!! PRE [slice]" text.new_line))) + (|> @self + (apply_poly arity_args) + (apply_poly output_func_args)))))) ## (|> @num_args (_.</2 arityO)) (_.lambda [(list) (#.Some @missing)] (|> @self diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index d6ae1cffd..815b5a8a5 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux @@ -53,41 +53,9 @@ (type: #export (Generator i) (-> Phase Archive i (Operation Expression))) -(def: unit +(def: #export unit (_.string /////synthesis.unit)) -(def: (flag value) - (-> Bit Computation) - (if value - ..unit - _.nil)) - -(def: (variant' tag last? value) - (-> Expression Expression Expression Computation) - (<| (_.cons/2 tag) - (_.cons/2 last?) - value)) - -(def: #export (variant [lefts right? value]) - (-> (Variant Expression) Computation) - (variant' (_.int (.int lefts)) (flag right?) value)) - -(def: #export none - Computation - (variant [0 #0 ..unit])) - -(def: #export some - (-> Expression Computation) - (|>> [0 #1] ..variant)) - -(def: #export left - (-> Expression Computation) - (|>> [0 #0] ..variant)) - -(def: #export right - (-> Expression Computation) - (|>> [0 #1] ..variant)) - (syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} @@ -137,41 +105,6 @@ (_.define_function (~ runtime_name) [(list (~+ inputsC)) #.None] (~ code)))))))))))))) -(runtime: (slice offset length list) - (<| (_.if (_.null?/1 list) - list) - (_.if (|> offset (_.>/2 (_.int +0))) - (slice (|> offset (_.-/2 (_.int +1))) - length - (_.cdr/1 list))) - (_.if (|> length (_.>/2 (_.int +0))) - (_.cons/2 (_.car/1 list) - (slice offset - (|> length (_.-/2 (_.int +1))) - (_.cdr/1 list)))) - _.nil)) - -(runtime: (lux//try op) - (with_vars [error] - (_.with_exception_handler - (_.lambda [(list error) #.None] - (..left error)) - (_.lambda [(list) #.None] - (..right (_.apply/* (list ..unit) op)))))) - -(runtime: (lux//program_args program_args) - (with_vars [@loop @input @output] - (_.letrec (list [@loop (_.lambda [(list @input @output) #.None] - (_.if (_.eqv?/2 _.nil @input) - @output - (_.apply/2 @loop (_.cdr/1 @input) (..some (_.vector/* (list (_.car/1 @input) @output))))))]) - (_.apply/2 @loop (_.reverse/1 program_args) ..none)))) - -(def: runtime//lux - Computation - (_.begin (list @lux//try - @lux//program_args))) - (def: last_index (-> Expression Computation) (|>> _.length/1 (_.-/2 (_.int +1)))) @@ -182,50 +115,62 @@ (list (_.define_constant last_index_right (..last_index tuple)) (_.if (_.>/2 lefts last_index_right) ## No need for recursion - (_.vector_ref/2 tuple lefts) + (_.vector-ref/2 tuple lefts) ## Needs recursion (tuple//left (_.-/2 last_index_right lefts) - (_.vector_ref/2 tuple last_index_right))))))) + (_.vector-ref/2 tuple last_index_right))))))) (runtime: (tuple//right lefts tuple) (with_vars [last_index_right right_index @slice] (_.begin (list (_.define_constant last_index_right (..last_index tuple)) (_.define_constant right_index (_.+/2 (_.int +1) lefts)) - (_.cond (list [(_.=/2 last_index_right right_index) - (_.vector_ref/2 tuple right_index)] - [(_.>/2 last_index_right right_index) - ## Needs recursion. - (tuple//right (_.-/2 last_index_right lefts) - (_.vector_ref/2 tuple last_index_right))]) - (_.begin - (list (_.define_constant @slice (_.make_vector/1 (_.-/2 right_index (_.length/1 tuple)))) - (_.vector_copy!/5 @slice (_.int +0) tuple right_index (_.length/1 tuple)) - @slice)))) + (<| (_.if (_.=/2 last_index_right right_index) + (_.vector-ref/2 tuple right_index)) + (_.if (_.>/2 last_index_right right_index) + ## Needs recursion. + (tuple//right (_.-/2 last_index_right lefts) + (_.vector-ref/2 tuple last_index_right))) + (_.begin + (list (_.define_constant @slice (_.make-vector/1 (_.-/2 right_index (_.length/1 tuple)))) + (_.vector-copy!/5 @slice (_.int +0) tuple right_index (_.length/1 tuple)) + @slice)))) ))) +(def: (variant' tag last? value) + (-> Expression Expression Expression Computation) + ($_ _.cons/2 + tag + last? + value)) + +(runtime: (sum//make tag last? value) + (variant' tag last? value)) + +(def: #export (variant [lefts right? value]) + (-> (Variant Expression) Computation) + (..sum//make (_.int (.int lefts)) (_.bool right?) value)) + (runtime: (sum//get sum last? wanted_tag) - (with_vars [sum_tag sum_flag sum_value] + (with_vars [sum_tag sum_flag sum_value sum_temp sum_dump] (let [no_match _.nil - is_last? (|> sum_flag (_.eqv?/2 ..unit)) - test_recursion (_.if is_last? + test_recursion (_.if sum_flag ## Must recurse. (sum//get sum_value last? (|> wanted_tag (_.-/2 sum_tag))) no_match)] (<| (_.let (list [sum_tag (_.car/1 sum)] - [sum_value (_.cdr/1 sum)])) - (_.let (list [sum_flag (_.car/1 sum_value)] - [sum_value (_.cdr/1 sum_value)])) - (_.if (|> wanted_tag (_.=/2 sum_tag)) - (_.if (|> sum_flag (_.eqv?/2 last?)) + [sum_temp (_.cdr/1 sum)])) + (_.let (list [sum_flag (_.car/1 sum_temp)] + [sum_value (_.cdr/1 sum_temp)])) + (_.if (_.=/2 wanted_tag sum_tag) + (_.if (_.eqv?/2 last? sum_flag) sum_value test_recursion)) - (_.if (|> wanted_tag (_.>/2 sum_tag)) + (_.if (_.</2 wanted_tag sum_tag) test_recursion) - (_.if (_.and (list (|> last? (_.eqv?/2 ..unit)) - (|> wanted_tag (_.</2 sum_tag)))) + (_.if last? (variant' (|> sum_tag (_.-/2 wanted_tag)) sum_flag sum_value)) no_match)))) @@ -233,36 +178,178 @@ Computation (_.begin (list @tuple//left @tuple//right - @sum//get))) + @sum//get + @sum//make))) + +(def: #export none + Computation + (|> ..unit [0 #0] variant)) + +(def: #export some + (-> Expression Computation) + (|>> [1 #1] ..variant)) + +(def: #export left + (-> Expression Computation) + (|>> [0 #0] ..variant)) + +(def: #export right + (-> Expression Computation) + (|>> [1 #1] ..variant)) + +(runtime: (slice offset length list) + (<| (_.if (_.null?/1 list) + list) + (_.if (|> offset (_.>/2 (_.int +0))) + (slice (|> offset (_.-/2 (_.int +1))) + length + (_.cdr/1 list))) + (_.if (|> length (_.>/2 (_.int +0))) + (_.cons/2 (_.car/1 list) + (slice offset + (|> length (_.-/2 (_.int +1))) + (_.cdr/1 list)))) + _.nil)) -(runtime: (i64//logical_right_shift shift input) - (_.if (_.=/2 (_.int +0) shift) - input - (|> input - (_.arithmetic_shift/2 (_.*/2 (_.int -1) shift)) - (_.bit_and/2 (_.int (hex "+7FFFFFFFFFFFFFFF")))))) +(runtime: (lux//try op) + (with_vars [error] + (_.with_exception_handler + (_.lambda [(list error) #.None] + (..left error)) + (_.lambda [(list) #.None] + (..right (_.apply/* (list ..unit) op)))))) -(def: runtime//bit +(runtime: (lux//program_args program_args) + (with_vars [@loop @input @output] + (_.letrec (list [@loop (_.lambda [(list @input @output) #.None] + (_.if (_.null?/1 @input) + @output + (_.apply/2 @loop (_.cdr/1 @input) (..some (_.vector/* (list (_.car/1 @input) @output))))))]) + (_.apply/2 @loop (_.reverse/1 program_args) ..none)))) + +(def: runtime//lux Computation - (_.begin (list @i64//logical_right_shift))) + (_.begin (list @lux//try + @lux//program_args))) + +(def: i64//+limit (_.manual "+9223372036854775807" + ## "+0x7FFFFFFFFFFFFFFF" + )) +(def: i64//-limit (_.manual "-9223372036854775808" + ## "-0x8000000000000000" + )) +(def: i64//+iteration (_.manual "+18446744073709551616" + ## "+0x10000000000000000" + )) +(def: i64//-iteration (_.manual "-18446744073709551616" + ## "-0x10000000000000000" + )) +(def: i64//+cap (_.manual "+9223372036854775808" + ## "+0x8000000000000000" + )) +(def: i64//-cap (_.manual "-9223372036854775809" + ## "-0x8000000000000001" + )) + +(runtime: (i64//64 input) + (with_vars [temp] + (`` (<| (~~ (template [<scenario> <iteration> <cap> <entrance>] + [(_.if (|> input <scenario>) + (_.let (list [temp (_.remainder/2 <iteration> input)]) + (_.if (|> temp <scenario>) + (|> temp (_.-/2 <cap>) (_.+/2 <entrance>)) + temp)))] + + [(_.>/2 ..i64//+limit) ..i64//+iteration ..i64//+cap ..i64//-limit] + [(_.</2 ..i64//-limit) ..i64//-iteration ..i64//-cap ..i64//+limit] + )) + input)))) + +(runtime: (i64//left_shift param subject) + (|> subject + (_.arithmetic-shift/2 (_.remainder/2 (_.int +64) param)) + ..i64//64)) + +(def: as_nat + (_.remainder/2 ..i64//+iteration)) + +(runtime: (i64//right_shift shift subject) + (_.let (list [shift (_.remainder/2 (_.int +64) shift)]) + (_.if (_.=/2 (_.int +0) shift) + subject + (|> subject + ..as_nat + (_.arithmetic-shift/2 (_.-/2 shift (_.int +0))))))) + +(template [<runtime> <host>] + [(runtime: (<runtime> left right) + (..i64//64 (<host> (..as_nat left) (..as_nat right))))] + + [i64//or _.bitwise-ior/2] + [i64//xor _.bitwise-xor/2] + [i64//and _.bitwise-and/2] + ) + +(runtime: (i64//division param subject) + (|> subject (_.//2 param) _.truncate/1 ..i64//64)) -(runtime: (frac//decode input) +(def: runtime//i64 + Computation + (_.begin (list @i64//64 + @i64//left_shift + @i64//right_shift + @i64//or + @i64//xor + @i64//and + @i64//division))) + +(runtime: (f64//decode input) (with_vars [@output] - (_.let (list [@output ((_.apply/1 (_.var "string->number")) input)]) - (_.if (_.and (list (_.not/1 (_.=/2 @output @output)) - (_.not/1 (_.eqv?/2 (_.string "+nan.0") input)))) - ..none - (..some @output))))) + (let [output_is_not_a_number? (_.not/1 (_.=/2 @output @output)) + input_is_not_a_number? (_.string=?/2 (_.string "+nan.0") input)] + (_.let (list [@output (_.string->number/1 input)]) + (_.if (_.and (list output_is_not_a_number? + (_.not/1 input_is_not_a_number?))) + ..none + (..some @output)))))) + +(def: runtime//f64 + Computation + (_.begin (list @f64//decode))) + +(runtime: (text//index offset sub text) + (with_vars [index] + (_.let (list [index (_.string-contains/3 text sub offset)]) + (_.if index + (..some index) + ..none)))) + +(runtime: (text//clip offset length text) + (_.substring/3 text offset (_.+/2 offset length))) + +(runtime: (text//char index text) + (_.char->integer/1 (_.string-ref/2 text index))) + +(def: runtime//text + (_.begin (list @text//index + @text//clip + @text//char))) + +(runtime: (array//write idx value array) + (_.begin (list (_.vector-set!/3 array idx value) + array))) -(def: runtime//frac +(def: runtime//array Computation - (_.begin - (list @frac//decode))) + ($_ _.then + @array//write + )) (runtime: (io//current_time _) (|> (_.apply/0 (_.var "current-second")) (_.*/2 (_.int +1,000)) - _.exact/1)) + _.exact/1 + _.truncate/1)) (def: runtime//io (_.begin (list @io//current_time))) @@ -271,9 +358,11 @@ Computation (_.begin (list @slice runtime//lux - runtime//bit + runtime//i64 runtime//adt - runtime//frac + runtime//f64 + runtime//text + runtime//array runtime//io ))) diff --git a/stdlib/source/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/lux/tool/compiler/meta/packager/script.lux index c874cfd88..95026ae37 100644 --- a/stdlib/source/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/lux/tool/compiler/meta/packager/script.lux @@ -54,10 +54,11 @@ (function (_ content) (sequence so_far (:share [directive] - {directive - so_far} - {directive - (:assume content)})))))) + directive + so_far + + directive + (:assume content))))))) so_far))) (def: #export (package header to_code sequence scope) |