From 7da7c963aa7b01ed8256d143bd27872d1ecdf989 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sat, 27 Apr 2019 21:35:04 -0400 Subject: Re-named "lux/tool/compiler/host" to "lux/target". --- stdlib/source/lux/control/concurrency/atom.lux | 8 +- stdlib/source/lux/control/concurrency/process.lux | 8 +- stdlib/source/lux/control/parser/cli.lux | 11 +- stdlib/source/lux/control/thread.lux | 8 +- stdlib/source/lux/data/collection/array.lux | 28 +- stdlib/source/lux/data/collection/list.lux | 8 +- stdlib/source/lux/data/collection/row.lux | 6 +- stdlib/source/lux/data/text.lux | 28 +- stdlib/source/lux/data/text/encoding.lux | 21 +- stdlib/source/lux/math.lux | 8 +- stdlib/source/lux/target.lux | 21 ++ stdlib/source/lux/tool/compiler/default/init.lux | 22 +- stdlib/source/lux/tool/compiler/host.lux | 21 -- .../lux/tool/compiler/phase/extension/analysis.lux | 6 +- .../tool/compiler/phase/generation/js/runtime.lux | 7 +- .../compiler/phase/generation/lua/function.lux | 4 +- .../tool/compiler/phase/generation/lua/loop.lux | 2 +- .../tool/compiler/phase/generation/lua/runtime.lux | 3 +- .../tool/compiler/phase/generation/php/runtime.lux | 3 +- .../tool/compiler/phase/generation/python/case.lux | 2 +- .../compiler/phase/generation/python/function.lux | 4 +- .../tool/compiler/phase/generation/python/loop.lux | 2 +- .../compiler/phase/generation/python/runtime.lux | 5 +- .../compiler/phase/generation/ruby/runtime.lux | 3 +- .../compiler/phase/generation/scheme/runtime.lux | 3 +- stdlib/source/lux/world/file.lux | 377 +++++++++++---------- stdlib/source/lux/world/net/tcp.old.lux | 190 +++++------ stdlib/source/lux/world/net/udp.old.lux | 160 +++++---- 28 files changed, 482 insertions(+), 487 deletions(-) create mode 100644 stdlib/source/lux/target.lux delete mode 100644 stdlib/source/lux/tool/compiler/host.lux (limited to 'stdlib/source') diff --git a/stdlib/source/lux/control/concurrency/atom.lux b/stdlib/source/lux/control/concurrency/atom.lux index 4de104212..cb252066a 100644 --- a/stdlib/source/lux/control/concurrency/atom.lux +++ b/stdlib/source/lux/control/concurrency/atom.lux @@ -1,16 +1,14 @@ (.module: [lux #* + [host (#+ import:)] + ["@" target] [abstract [monad (#+ do)]] [control ["." function] ["." io (#- run)]] [type - abstract] - [tool - [compiler - ["@" host]]] - [host (#+ import:)]]) + abstract]]) (`` (for {(~~ (static @.old)) (import: #long (java/util/concurrent/atomic/AtomicReference a) diff --git a/stdlib/source/lux/control/concurrency/process.lux b/stdlib/source/lux/control/concurrency/process.lux index 074ea96ac..400dcf2c8 100644 --- a/stdlib/source/lux/control/concurrency/process.lux +++ b/stdlib/source/lux/control/concurrency/process.lux @@ -1,5 +1,7 @@ (.module: [lux #* + ["@" target] + ["." host (#+ import: object)] [abstract ["." monad (#+ do)]] [control @@ -7,11 +9,7 @@ ["." io (#+ IO io)]] [data [collection - ["." list]]] - [tool - [compiler - ["@" host]]] - ["." host (#+ import: object)]] + ["." list]]]] [// ["." atom (#+ Atom)]]) diff --git a/stdlib/source/lux/control/parser/cli.lux b/stdlib/source/lux/control/parser/cli.lux index 38f22602f..e1e932569 100644 --- a/stdlib/source/lux/control/parser/cli.lux +++ b/stdlib/source/lux/control/parser/cli.lux @@ -1,5 +1,6 @@ (.module: [lux #* + ["@" target] [abstract [monad (#+ do)]] [data @@ -10,10 +11,7 @@ ["." error (#+ Error)]] [macro (#+ with-gensyms) ["." code] - [syntax (#+ syntax:)]] - [tool - [compiler - ["." host]]]] + [syntax (#+ syntax:)]]] ["." // ["s" code] [// @@ -161,7 +159,10 @@ (~ g!_) ..end] ((~' wrap) ((~! do) (~! io.monad) [(~ g!output) (~ body) - (~+ (`` (for {(~~ (static host.old)) + (~+ (`` (for {(~~ (static @.old)) + (list) + + (~~ (static @.jvm)) (list)} (list g!_ (` process.run!)))))] diff --git a/stdlib/source/lux/control/thread.lux b/stdlib/source/lux/control/thread.lux index db351d87b..ec9650664 100644 --- a/stdlib/source/lux/control/thread.lux +++ b/stdlib/source/lux/control/thread.lux @@ -1,5 +1,6 @@ (.module: [lux #* + ["@" target] [abstract [functor (#+ Functor)] [apply (#+ Apply)] @@ -10,10 +11,7 @@ [collection ["." array (#+ Array)]]] [type - abstract] - [tool - [compiler - ["." host]]]]) + abstract]]) (type: #export (Thread ! a) (-> ! a)) @@ -33,7 +31,7 @@ (def: #export (read box) (All [! a] (-> (Box ! a) (Thread ! a))) (function (_ !) - (`` (for {(~~ (static host.old)) + (`` (for {(~~ (static @.old)) ("jvm aaload" (:representation box) 0)})))) (def: #export (write value box) diff --git a/stdlib/source/lux/data/collection/array.lux b/stdlib/source/lux/data/collection/array.lux index d73ca2e7f..aeb0cc55f 100644 --- a/stdlib/source/lux/data/collection/array.lux +++ b/stdlib/source/lux/data/collection/array.lux @@ -1,5 +1,6 @@ (.module: [lux #* + ["@" target] [abstract [monoid (#+ Monoid)] [functor (#+ Functor)] @@ -10,10 +11,7 @@ ["." product] ["." maybe] [collection - ["." list ("#@." fold)]]] - [tool - [compiler - ["." host]]]]) + ["." list ("#@." fold)]]]]) (def: #export type-name "#Array") @@ -24,7 +22,7 @@ (with-expansions [ (primitive "java.lang.Long") (primitive "java.lang.Object") (type (Array ))] - (`` (for {(~~ (static host.jvm)) + (`` (for {(~~ (static @.jvm)) (template: (!int value) (|> value (:coerce ) @@ -34,10 +32,10 @@ (def: #export (new size) (All [a] (-> Nat (Array a))) - (`` (for {(~~ (static host.old)) + (`` (for {(~~ (static @.old)) (:assume ("jvm anewarray" "(java.lang.Object )" size)) - (~~ (static host.jvm)) + (~~ (static @.jvm)) (|> size !int "jvm array new" @@ -46,10 +44,10 @@ (def: #export (size array) (All [a] (-> (Array a) Nat)) - (`` (for {(~~ (static host.old)) + (`` (for {(~~ (static @.old)) ("jvm arraylength" array) - (~~ (static host.jvm)) + (~~ (static @.jvm)) (|> array (:coerce ) "jvm array length" @@ -62,13 +60,13 @@ (All [a] (-> Nat (Array a) (Maybe a))) (if (n/< (size array) index) - (`` (for {(~~ (static host.old)) + (`` (for {(~~ (static @.old)) (let [value ("jvm aaload" array index)] (if ("jvm object null?" value) #.None (#.Some value))) - (~~ (static host.jvm)) + (~~ (static @.jvm)) (let [value (|> array (:coerce ) ("jvm array read" (!int index)))] @@ -80,10 +78,10 @@ (def: #export (write index value array) (All [a] (-> Nat a (Array a) (Array a))) - (`` (for {(~~ (static host.old)) + (`` (for {(~~ (static @.old)) ("jvm aastore" array index value) - (~~ (static host.jvm)) + (~~ (static @.jvm)) (|> array (:coerce ) ("jvm array write" (!int index) (:coerce value)) @@ -93,10 +91,10 @@ (All [a] (-> Nat (Array a) (Array a))) (if (n/< (size array) index) - (`` (for {(~~ (static host.old)) + (`` (for {(~~ (static @.old)) (write index (:assume ("jvm object null")) array) - (~~ (static host.jvm)) + (~~ (static @.jvm)) (write index (:assume (: ("jvm object null"))) array)})) array)) ) diff --git a/stdlib/source/lux/data/collection/list.lux b/stdlib/source/lux/data/collection/list.lux index fa18cfd19..ff6739076 100644 --- a/stdlib/source/lux/data/collection/list.lux +++ b/stdlib/source/lux/data/collection/list.lux @@ -1,5 +1,6 @@ (.module: [lux #* + ["@" target] [abstract [monoid (#+ Monoid)] ["." functor (#+ Functor)] @@ -10,10 +11,7 @@ [predicate (#+ Predicate)]] [data ["." bit] - ["." product]] - [tool - [compiler - ["." host]]]]) + ["." product]]]) ## (type: (List a) ## #Nil @@ -554,7 +552,7 @@ (do monad [lMla MlMla ## TODO: Remove this version ASAP and use one below. - lla (`` (for {(~~ (static host.old)) + lla (`` (for {(~~ (static @.old)) (: (($ 0) (List (List ($ 1)))) (monad.seq @ lMla))} (monad.seq @ lMla)))] diff --git a/stdlib/source/lux/data/collection/row.lux b/stdlib/source/lux/data/collection/row.lux index 722526e26..71bb5202a 100644 --- a/stdlib/source/lux/data/collection/row.lux +++ b/stdlib/source/lux/data/collection/row.lux @@ -1,5 +1,6 @@ (.module: [lux #* + ["@" target] [abstract [functor (#+ Functor)] [apply (#+ Apply)] @@ -21,10 +22,7 @@ ["." array (#+ Array) ("#@." functor fold)]]] [macro (#+ with-gensyms) ["." code] - [syntax (#+ syntax:)]] - [tool - [compiler - ["@" host]]]]) + [syntax (#+ syntax:)]]]) (type: (Node a) (#Base (Array a)) diff --git a/stdlib/source/lux/data/text.lux b/stdlib/source/lux/data/text.lux index df3dad17e..856481560 100644 --- a/stdlib/source/lux/data/text.lux +++ b/stdlib/source/lux/data/text.lux @@ -1,5 +1,6 @@ (.module: [lux #* + ["@" target] [abstract hash [monoid (#+ Monoid)] @@ -12,10 +13,7 @@ [number ["." i64]] [collection - ["." list ("#@." fold)]]] - [tool - [compiler - ["." host]]]]) + ["." list ("#@." fold)]]]]) (type: #export Char Nat) @@ -89,10 +87,10 @@ (-> Text Text Bit) (case (index-of prefix x) (#.Some 0) - #1 + true _ - #0)) + false)) (def: #export (ends-with? postfix x) (-> Text Text Bit) @@ -102,16 +100,16 @@ (n/+ (size postfix) n)) _ - #0)) + false)) (def: #export (contains? sub text) (-> Text Text Bit) (case ("lux text index" 0 sub text) (#.Some _) - #1 + true _ - #0)) + false)) (def: #export (clip from to input) (-> Nat Nat Text (Maybe Text)) @@ -189,14 +187,14 @@ (def: &equivalence ..equivalence) (def: (hash input) - (`` (for {(~~ (static host.old)) + (`` (for {(~~ (static @.old)) (|> input (: (primitive "java.lang.String" [])) "jvm invokevirtual:java.lang.String:hashCode:" "jvm convert int-to-long" (:coerce Nat)) - (~~ (static host.jvm)) + (~~ (static @.jvm)) (|> input (:coerce (primitive "java.lang.String")) ("jvm member invoke virtual" "java.lang.String" "hashCode") @@ -228,8 +226,8 @@ (def: #export (empty? text) (-> Text Bit) (case text - "" #1 - _ #0)) + "" true + _ false)) (def: #export (prefix param subject) (-> Text Text Text) @@ -263,7 +261,7 @@ (^ (char (~~ (static ..new-line)))) (^ (char (~~ (static ..carriage-return)))) (^ (char (~~ (static ..form-feed))))) - #1 + true _ - #0))) + false))) diff --git a/stdlib/source/lux/data/text/encoding.lux b/stdlib/source/lux/data/text/encoding.lux index aae640382..470265081 100644 --- a/stdlib/source/lux/data/text/encoding.lux +++ b/stdlib/source/lux/data/text/encoding.lux @@ -1,5 +1,6 @@ (.module: [lux #* + ["@" target] [abstract [codec (#+ Codec)]] [data @@ -8,9 +9,6 @@ abstract] [world [binary (#+ Binary)]] - [tool - [compiler - ["_" host]]] [host (#+ import:)]]) ## https://docs.oracle.com/javase/8/docs/technotes/guides/intl/encoding.doc.html @@ -173,19 +171,30 @@ (|>> :representation)) ) -(`` (for {(~~ (static _.old)) +(`` (for {(~~ (static @.old)) + (as-is (import: #long java/lang/String + (new [(Array byte) java/lang/String]) + (getBytes [java/lang/String] (Array byte)))) + + (~~ (static @.jvm)) (as-is (import: #long java/lang/String (new [(Array byte) java/lang/String]) (getBytes [java/lang/String] (Array byte))))})) (def: #export (to-utf8 value) (-> Text Binary) - (`` (for {(~~ (static _.old)) + (`` (for {(~~ (static @.old)) + (java/lang/String::getBytes (..name ..utf-8) (:coerce java/lang/String value)) + + (~~ (static @.jvm)) (java/lang/String::getBytes (..name ..utf-8) (:coerce java/lang/String value))}))) (def: #export (from-utf8 value) (-> Binary (Error Text)) - (`` (for {(~~ (static _.old)) + (`` (for {(~~ (static @.old)) + (#error.Success (java/lang/String::new value (..name ..utf-8))) + + (~~ (static @.jvm)) (#error.Success (java/lang/String::new value (..name ..utf-8)))}))) (structure: #export UTF-8 (Codec Binary Text) diff --git a/stdlib/source/lux/math.lux b/stdlib/source/lux/math.lux index 3916622cf..712e2bf70 100644 --- a/stdlib/source/lux/math.lux +++ b/stdlib/source/lux/math.lux @@ -1,8 +1,6 @@ (.module: {#.doc "Common mathematical constants and functions."} [lux #* - [tool - [compiler - ["." host]]]]) + ["@" target]]) (template [ ] [(def: #export @@ -15,7 +13,7 @@ [tau +6.28318530717958647692 "The ratio of a circle's circumference to its radius."] ) -(`` (for {(~~ (static host.old)) +(`` (for {(~~ (static @.old)) (as-is (template [ ] [(def: #export ( input) (-> Frac Frac) @@ -39,7 +37,7 @@ (-> Frac Frac Frac) ("jvm invokestatic:java.lang.Math:pow:double,double" subject param))) - (~~ (static host.jvm)) + (~~ (static @.jvm)) (as-is (template: (!double value) (|> value (:coerce (primitive "java.lang.Double")) "jvm object cast")) (template: (!frac value) (|> value "jvm object cast" (: (primitive "java.lang.Double")) (:coerce Frac))) (template [ ] diff --git a/stdlib/source/lux/target.lux b/stdlib/source/lux/target.lux new file mode 100644 index 000000000..06c4c7efe --- /dev/null +++ b/stdlib/source/lux/target.lux @@ -0,0 +1,21 @@ +(.module: + lux) + +(type: #export Host Text) + +(template [ ] + [(def: #export Host )] + + ## TODO: Delete ASAP + [old "{old}"] + + [common-lisp "Common Lisp"] + [js "JavaScript"] + [jvm "JVM"] + [lua "Lua"] + [php "PHP"] + [python "Python"] + [r "R"] + [ruby "Ruby"] + [scheme "Scheme"] + ) diff --git a/stdlib/source/lux/tool/compiler/default/init.lux b/stdlib/source/lux/tool/compiler/default/init.lux index 604fd8551..5cb857d65 100644 --- a/stdlib/source/lux/tool/compiler/default/init.lux +++ b/stdlib/source/lux/tool/compiler/default/init.lux @@ -1,5 +1,6 @@ (.module: [lux (#- Module) + ["@" target] [type (#+ :share)] [abstract ["." monad (#+ do)]] @@ -24,7 +25,6 @@ ["#." analysis] ["#." synthesis] ["#." statement (#+ Requirements)] - ["#." host] ["#." phase [macro (#+ Expander)] [".P" analysis @@ -45,16 +45,16 @@ (def: #export info Info - {#.target (`` (for {(~~ (static ///host.common-lisp)) ///host.common-lisp - (~~ (static ///host.js)) ///host.js - (~~ (static ///host.old)) ///host.jvm - (~~ (static ///host.jvm)) ///host.jvm - (~~ (static ///host.lua)) ///host.lua - (~~ (static ///host.php)) ///host.php - (~~ (static ///host.python)) ///host.python - (~~ (static ///host.r)) ///host.r - (~~ (static ///host.ruby)) ///host.ruby - (~~ (static ///host.scheme)) ///host.scheme})) + {#.target (`` (for {(~~ (static @.common-lisp)) @.common-lisp + (~~ (static @.js)) @.js + (~~ (static @.old)) @.jvm + (~~ (static @.jvm)) @.jvm + (~~ (static @.lua)) @.lua + (~~ (static @.php)) @.php + (~~ (static @.python)) @.python + (~~ (static @.r)) @.r + (~~ (static @.ruby)) @.ruby + (~~ (static @.scheme)) @.scheme})) #.version //.version #.mode #.Build}) diff --git a/stdlib/source/lux/tool/compiler/host.lux b/stdlib/source/lux/tool/compiler/host.lux deleted file mode 100644 index 06c4c7efe..000000000 --- a/stdlib/source/lux/tool/compiler/host.lux +++ /dev/null @@ -1,21 +0,0 @@ -(.module: - lux) - -(type: #export Host Text) - -(template [ ] - [(def: #export Host )] - - ## TODO: Delete ASAP - [old "{old}"] - - [common-lisp "Common Lisp"] - [js "JavaScript"] - [jvm "JVM"] - [lua "Lua"] - [php "PHP"] - [python "Python"] - [r "R"] - [ruby "Ruby"] - [scheme "Scheme"] - ) diff --git a/stdlib/source/lux/tool/compiler/phase/extension/analysis.lux b/stdlib/source/lux/tool/compiler/phase/extension/analysis.lux index 446e769f1..ca2d75e4d 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension/analysis.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension/analysis.lux @@ -1,11 +1,9 @@ (.`` (.module: [lux #* + ["@" target] [data [collection - ["." dictionary]]] - [tool - [compiler - ["@" host]]]] + ["." dictionary]]]] [//// [default [evaluation (#+ Eval)]] diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux index c94b68337..314fe300d 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux @@ -739,7 +739,8 @@ (Operation Any) (///.with-buffer (do ////.monad - [_ (///.save! ["" ..prefix] ($_ _.then - _.use-strict - ..runtime))] + [_ (///.save! true ["" ..prefix] + ($_ _.then + _.use-strict + ..runtime))] (///.save-buffer! ..artifact)))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/lua/function.lux b/stdlib/source/lux/tool/compiler/phase/generation/lua/function.lux index 517af6550..9fa8a3c7d 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/lua/function.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/lua/function.lux @@ -39,14 +39,14 @@ (case inits #.Nil (do ////.monad - [_ (///.save! ["" function-name] + [_ (///.save! true ["" function-name] function-definition)] (wrap (|> (_.var function-name) (_.apply/* inits)))) _ (do ////.monad [@closure (:: @ map _.var (///.gensym "closure")) - _ (///.save! ["" (_.code @closure)] + _ (///.save! true ["" (_.code @closure)] (_.function @closure (|> (list.enumerate inits) (list@map (|>> product.left ..capture))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/lua/loop.lux b/stdlib/source/lux/tool/compiler/phase/generation/lua/loop.lux index 41ebb4766..39c983dcc 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/lua/loop.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/lua/loop.lux @@ -25,7 +25,7 @@ initsO+ (monad.map @ generate initsS+) bodyO (///.with-anchor @loop (generate bodyS)) - _ (///.save! ["" (_.code @loop)] + _ (///.save! true ["" (_.code @loop)] (_.function @loop (|> initsS+ list.enumerate (list@map (|>> product.left (n/+ start) //case.register))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/lua/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/lua/runtime.lux index 6eeddc5ff..57f8e11df 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/lua/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/lua/runtime.lux @@ -358,5 +358,6 @@ (Operation Any) (///.with-buffer (do ////.monad - [_ (///.save! ["" ..prefix] ..runtime)] + [_ (///.save! true ["" ..prefix] + ..runtime)] (///.save-buffer! ..artifact)))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/php/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/php/runtime.lux index e29b7622a..8d3a2138a 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/php/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/php/runtime.lux @@ -301,5 +301,6 @@ (Operation Any) (///.with-buffer (do ////.monad - [_ (///.save! true ["" ..prefix] ..runtime)] + [_ (///.save! true ["" ..prefix] + ..runtime)] (///.save-buffer! ..artifact)))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/python/case.lux b/stdlib/source/lux/tool/compiler/phase/generation/python/case.lux index 3aa95d673..dc908eae7 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/python/case.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/python/case.lux @@ -230,7 +230,7 @@ (#reference.Foreign register) (..capture register)))))] - _ (///.save! ["" (_.code @case)] + _ (///.save! true ["" (_.code @case)] (_.def @case (list& @init @dependencies+) ($_ _.then (_.set (list @cursor) (_.list (list @init))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/python/function.lux b/stdlib/source/lux/tool/compiler/phase/generation/python/function.lux index a5f918dc1..2631f629c 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/python/function.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/python/function.lux @@ -39,14 +39,14 @@ (case inits #.Nil (do ////.monad - [_ (///.save! ["" function-name] + [_ (///.save! true ["" function-name] function-definition)] (wrap (_.apply/* (_.var function-name) inits))) _ (do ////.monad [@closure (:: @ map _.var (///.gensym "closure")) - _ (///.save! ["" (_.code @closure)] + _ (///.save! true ["" (_.code @closure)] (_.def @closure (|> (list.enumerate inits) (list@map (|>> product.left ..capture))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/python/loop.lux b/stdlib/source/lux/tool/compiler/phase/generation/python/loop.lux index 12d83b756..9dae1b6dc 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/python/loop.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/python/loop.lux @@ -25,7 +25,7 @@ initsO+ (monad.map @ generate initsS+) bodyO (///.with-anchor @loop (generate bodyS)) - _ (///.save! ["" (_.code @loop)] + _ (///.save! true ["" (_.code @loop)] (_.def @loop (|> initsS+ list.enumerate (list@map (|>> product.left (n/+ start) //case.register))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux index 44b9d290f..b2135a625 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux @@ -364,6 +364,7 @@ (Operation Any) (///.with-buffer (do ////.monad - [_ (///.save! ["" ..prefix] (<| (_.comment "-*- coding: utf-8 -*-") - ..runtime))] + [_ (///.save! true ["" ..prefix] + (<| (_.comment "-*- coding: utf-8 -*-") + ..runtime))] (///.save-buffer! ..artifact)))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/ruby/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/ruby/runtime.lux index 8858e9d4f..b63571ddc 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/ruby/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/ruby/runtime.lux @@ -290,5 +290,6 @@ (Operation Any) (///.with-buffer (do ////.monad - [_ (///.save! ["" ..prefix] ..runtime)] + [_ (///.save! true ["" ..prefix] + ..runtime)] (///.save-buffer! ..artifact)))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.lux index bda2f7783..c22906d2d 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.lux @@ -319,5 +319,6 @@ (Operation Any) (///.with-buffer (do ////.monad - [_ (///.save! ["" ..prefix] ..runtime)] + [_ (///.save! true ["" ..prefix] + ..runtime)] (///.save-buffer! "")))) diff --git a/stdlib/source/lux/world/file.lux b/stdlib/source/lux/world/file.lux index ec3cee16f..6fa386f05 100644 --- a/stdlib/source/lux/world/file.lux +++ b/stdlib/source/lux/world/file.lux @@ -1,5 +1,7 @@ (.module: [lux #* + [host (#+ import:)] + ["@" target] [abstract ["." monad (#+ Monad do)]] [control @@ -23,11 +25,7 @@ [macro ["." template]] [world - ["." binary (#+ Binary)]] - [host (#+ import:)] - [tool - [compiler - ["." host]]]]) + ["." binary (#+ Binary)]]]) (type: #export Path Text) @@ -184,189 +182,192 @@ (ex.report ["Instant" (%instant instant)] ["Path" file])) -(template: (!delete path exception) - (do io.monad - [outcome (java/io/File::delete (java/io/File::new path))] - (case outcome - (#error.Success #1) - (wrap (#error.Success [])) - - _ - (io.io (ex.throw exception [path]))))) - -(`` (for {(~~ (static host.old)) - (as-is (import: #long java/io/File - (new [String]) - (~~ (template [] - [( [] #io #try boolean)] - - [createNewFile] [mkdir] - [exists] [delete] - [isFile] [isDirectory] - [canRead] [canWrite] [canExecute])) - - (length [] #io #try long) - (listFiles [] #io #try #? (Array java/io/File)) - (getAbsolutePath [] #io #try String) - (renameTo [java/io/File] #io #try boolean) - (lastModified [] #io #try long) - (setLastModified [long] #io #try boolean) - (#static separator String)) - - (import: java/lang/AutoCloseable - (close [] #io #try void)) - - (import: java/io/OutputStream - (write [(Array byte)] #io #try void) - (flush [] #io #try void)) - - (import: java/io/FileOutputStream - (new [java/io/File boolean] #io #try)) - - (import: java/io/InputStream - (read [(Array byte)] #io #try int)) - - (import: java/io/FileInputStream - (new [java/io/File] #io #try)) - - (structure: (file path) - (-> Path (File IO)) - - (~~ (template [ ] - [(def: - (..can-modify - (function ( data) - (do (error.with io.monad) - [stream (FileOutputStream::new (java/io/File::new path) ) - _ (OutputStream::write data stream) - _ (OutputStream::flush stream)] - (AutoCloseable::close stream)))))] - - [over-write #0] - [append #1] - )) - - (def: content - (..can-query - (function (content _) - (do (error.with io.monad) - [#let [file (java/io/File::new path)] - size (java/io/File::length file) - #let [data (binary.create (.nat size))] - stream (FileInputStream::new file) - bytes-read (InputStream::read data stream) - _ (AutoCloseable::close stream)] - (if (i/= size bytes-read) - (wrap data) - (io.io (ex.throw cannot-read-all-data path))))))) - - (def: size - (..can-query - (function (size _) - (|> path - java/io/File::new - java/io/File::length - (:: (error.with io.monad) map .nat))))) - - (def: last-modified - (..can-query - (function (last-modified _) - (|> path - java/io/File::new - (java/io/File::lastModified) - (:: (error.with io.monad) map (|>> duration.from-millis instant.absolute)))))) - - (def: can-execute? - (..can-query - (function (can-execute? _) - (|> path - java/io/File::new - java/io/File::canExecute)))) - - (def: move - (..can-open - (function (move destination) - (do io.monad - [outcome (java/io/File::renameTo (java/io/File::new destination) - (java/io/File::new path))] - (case outcome - (#error.Success #1) - (wrap (#error.Success (file destination))) - - _ - (io.io (ex.throw cannot-move [destination path]))))))) - - (def: modify - (..can-modify - (function (modify time-stamp) - (do io.monad - [outcome (java/io/File::setLastModified (|> time-stamp instant.relative duration.to-millis) - (java/io/File::new path))] - (case outcome - (#error.Success #1) - (wrap (#error.Success [])) - - _ - (io.io (ex.throw cannot-modify [time-stamp path]))))))) - - (def: delete - (..can-delete - (function (delete _) - (!delete path cannot-delete-file))))) - - (structure: (directory path) - (-> Path (Directory IO)) - - (~~ (template [ ] - [(def: - (..can-query - (function ( _) - (do (error.with io.monad) - [?children (java/io/File::listFiles (java/io/File::new path))] - (case ?children - (#.Some children) - (|> children - array.to-list - (monad.filter @ (|>> )) - (:: @ map (monad.map @ (|>> java/io/File::getAbsolutePath (:: @ map )))) - (:: @ join)) - - #.None - (io.io (ex.throw not-a-directory [path])))))))] - - [files java/io/File::isFile file] - [directories java/io/File::isDirectory directory] - )) - - (def: discard - (..can-delete - (function (discard _) - (!delete path cannot-discard-directory))))) - - (structure: #export system (System IO) - (~~ (template [ ] - [(def: - (..can-open - (function ( path) - (do io.monad - [#let [file (java/io/File::new path)] - outcome ( file)] - (case outcome - (#error.Success #1) - (wrap (#error.Success ( path))) - - _ - (wrap (ex.throw [path])))))))] - - [file java/io/File::isFile ..file cannot-find-file] - [create-file java/io/File::createNewFile ..file cannot-create-file] - [directory java/io/File::isDirectory ..directory cannot-find-directory] - [create-directory java/io/File::mkdir ..directory cannot-create-directory] - )) - - (def: separator (java/io/File::separator)) - )) - })) +(with-expansions [ (as-is (import: #long java/io/File + (new [String]) + (~~ (template [] + [( [] #io #try boolean)] + + [createNewFile] [mkdir] + [exists] [delete] + [isFile] [isDirectory] + [canRead] [canWrite] [canExecute])) + + (length [] #io #try long) + (listFiles [] #io #try #? (Array java/io/File)) + (getAbsolutePath [] #io #try String) + (renameTo [java/io/File] #io #try boolean) + (lastModified [] #io #try long) + (setLastModified [long] #io #try boolean) + (#static separator String)) + + (template: (!delete path exception) + (do io.monad + [outcome (java/io/File::delete (java/io/File::new path))] + (case outcome + (#error.Success #1) + (wrap (#error.Success [])) + + _ + (io.io (ex.throw exception [path]))))) + + (import: java/lang/AutoCloseable + (close [] #io #try void)) + + (import: java/io/OutputStream + (write [(Array byte)] #io #try void) + (flush [] #io #try void)) + + (import: java/io/FileOutputStream + (new [java/io/File boolean] #io #try)) + + (import: java/io/InputStream + (read [(Array byte)] #io #try int)) + + (import: java/io/FileInputStream + (new [java/io/File] #io #try)) + + (structure: (file path) + (-> Path (File IO)) + + (~~ (template [ ] + [(def: + (..can-modify + (function ( data) + (do (error.with io.monad) + [stream (FileOutputStream::new (java/io/File::new path) ) + _ (OutputStream::write data stream) + _ (OutputStream::flush stream)] + (AutoCloseable::close stream)))))] + + [over-write #0] + [append #1] + )) + + (def: content + (..can-query + (function (content _) + (do (error.with io.monad) + [#let [file (java/io/File::new path)] + size (java/io/File::length file) + #let [data (binary.create (.nat size))] + stream (FileInputStream::new file) + bytes-read (InputStream::read data stream) + _ (AutoCloseable::close stream)] + (if (i/= size bytes-read) + (wrap data) + (io.io (ex.throw cannot-read-all-data path))))))) + + (def: size + (..can-query + (function (size _) + (|> path + java/io/File::new + java/io/File::length + (:: (error.with io.monad) map .nat))))) + + (def: last-modified + (..can-query + (function (last-modified _) + (|> path + java/io/File::new + (java/io/File::lastModified) + (:: (error.with io.monad) map (|>> duration.from-millis instant.absolute)))))) + + (def: can-execute? + (..can-query + (function (can-execute? _) + (|> path + java/io/File::new + java/io/File::canExecute)))) + + (def: move + (..can-open + (function (move destination) + (do io.monad + [outcome (java/io/File::renameTo (java/io/File::new destination) + (java/io/File::new path))] + (case outcome + (#error.Success #1) + (wrap (#error.Success (file destination))) + + _ + (io.io (ex.throw cannot-move [destination path]))))))) + + (def: modify + (..can-modify + (function (modify time-stamp) + (do io.monad + [outcome (java/io/File::setLastModified (|> time-stamp instant.relative duration.to-millis) + (java/io/File::new path))] + (case outcome + (#error.Success #1) + (wrap (#error.Success [])) + + _ + (io.io (ex.throw cannot-modify [time-stamp path]))))))) + + (def: delete + (..can-delete + (function (delete _) + (!delete path cannot-delete-file))))) + + (structure: (directory path) + (-> Path (Directory IO)) + + (~~ (template [ ] + [(def: + (..can-query + (function ( _) + (do (error.with io.monad) + [?children (java/io/File::listFiles (java/io/File::new path))] + (case ?children + (#.Some children) + (|> children + array.to-list + (monad.filter @ (|>> )) + (:: @ map (monad.map @ (|>> java/io/File::getAbsolutePath (:: @ map )))) + (:: @ join)) + + #.None + (io.io (ex.throw not-a-directory [path])))))))] + + [files java/io/File::isFile file] + [directories java/io/File::isDirectory directory] + )) + + (def: discard + (..can-delete + (function (discard _) + (!delete path cannot-discard-directory))))) + + (structure: #export system (System IO) + (~~ (template [ ] + [(def: + (..can-open + (function ( path) + (do io.monad + [#let [file (java/io/File::new path)] + outcome ( file)] + (case outcome + (#error.Success #1) + (wrap (#error.Success ( path))) + + _ + (wrap (ex.throw [path])))))))] + + [file java/io/File::isFile ..file cannot-find-file] + [create-file java/io/File::createNewFile ..file cannot-create-file] + [directory java/io/File::isDirectory ..directory cannot-find-directory] + [create-directory java/io/File::mkdir ..directory cannot-create-directory] + )) + + (def: separator (java/io/File::separator)) + ))] + (`` (for {(~~ (static @.old)) + (as-is ) + + (~~ (static @.jvm)) + (as-is )}))) (template [ ] [(def: #export ( monad system path) diff --git a/stdlib/source/lux/world/net/tcp.old.lux b/stdlib/source/lux/world/net/tcp.old.lux index 1b7a8af18..85d306799 100644 --- a/stdlib/source/lux/world/net/tcp.old.lux +++ b/stdlib/source/lux/world/net/tcp.old.lux @@ -1,5 +1,7 @@ (.module: [lux #* + [host (#+ import:)] + ["@" target] [abstract monad] [control @@ -12,38 +14,9 @@ [data ["." error (#+ Error)]] [world - ["." binary (#+ Binary)]] - [host (#+ import:)] - [tool - [compiler - ["." host]]]] + ["." binary (#+ Binary)]]] ["." // (#+ Can-Read Can-Write Can-Close)]) -(import: java/lang/AutoCloseable - (close [] #io #try void)) - -(import: java/io/Flushable - (flush [] #io #try void)) - -(import: java/io/InputStream - (read [(Array byte) int int] #io #try int)) - -(import: java/io/OutputStream - (write [(Array byte) int int] #io #try void)) - -(import: java/net/Socket - (new [String int] #io #try) - (getInputStream [] #try InputStream) - (getOutputStream [] #try OutputStream)) - -(import: java/net/ServerSocket - (new [int] #io #try) - (accept [] #io #try Socket)) - -############################################################ -############################################################ -############################################################ - (signature: #export (TCP !) (: (Can-Read ! [Nat Binary]) read) @@ -63,69 +36,94 @@ [write //.can-write] [close //.can-close]))))) -(`` (for {(~~ (static host.old)) - (as-is (def: (tcp socket) - (-> Socket (Error (TCP IO))) - (do error.monad - [input (Socket::getInputStream socket) - output (Socket::getOutputStream socket)] - (wrap (: (TCP IO) - (structure (def: read - (//.can-read - (function (read size) - (do (error.with io.monad) - [#let [data (binary.create size)] - bytes-read (InputStream::read data +0 (.int size) input)] - (wrap [(.nat bytes-read) - data]))))) - - (def: write - (//.can-write - (function (write data) - (do (error.with io.monad) - [_ (OutputStream::write data +0 (.int (binary.size data)) - output)] - (Flushable::flush output))))) - - (def: close - (//.can-close - (function (close _) - (do (error.with io.monad) - [_ (AutoCloseable::close input) - _ (AutoCloseable::close output)] - (AutoCloseable::close socket)))))))))) - - (def: #export (client address port) - (-> //.Address //.Port (IO (Error (TCP IO)))) - (do (error.with io.monad) - [socket (Socket::new address (.int port))] - (io.io (tcp socket)))) - - (def: #export (server port) - (-> //.Port (IO (Error [(Resolver Any) - (Channel (TCP IO))]))) - (do (error.with io.monad) - [server (ServerSocket::new (.int port)) - #let [[close-signal close-resolver] (: [(Promise Any) (Resolver Any)] - (promise.promise [])) - _ (promise.await (function (_ _) - (AutoCloseable::close server)) - close-signal) - [output sink] (: [(Channel (TCP IO)) (Sink (TCP IO))] - (frp.channel [])) - _ (: (Promise Any) - (promise.future - (loop [_ []] - (do io.monad - [?client (do (error.with io.monad) - [socket (ServerSocket::accept server)] - (io.io (tcp socket)))] - (case ?client - (#error.Failure error) - (wrap []) - - (#error.Success client) - (do @ - [_ (:: sink feed client)] - (recur [])))))))]] - (wrap [close-resolver output]))))})) +(with-expansions [ (as-is (import: java/lang/AutoCloseable + (close [] #io #try void)) + + (import: java/io/Flushable + (flush [] #io #try void)) + + (import: java/io/InputStream + (read [(Array byte) int int] #io #try int)) + + (import: java/io/OutputStream + (write [(Array byte) int int] #io #try void)) + + (import: java/net/Socket + (new [String int] #io #try) + (getInputStream [] #try InputStream) + (getOutputStream [] #try OutputStream)) + + (import: java/net/ServerSocket + (new [int] #io #try) + (accept [] #io #try Socket)) + + (def: (tcp socket) + (-> Socket (Error (TCP IO))) + (do error.monad + [input (Socket::getInputStream socket) + output (Socket::getOutputStream socket)] + (wrap (: (TCP IO) + (structure (def: read + (//.can-read + (function (read size) + (do (error.with io.monad) + [#let [data (binary.create size)] + bytes-read (InputStream::read data +0 (.int size) input)] + (wrap [(.nat bytes-read) + data]))))) + + (def: write + (//.can-write + (function (write data) + (do (error.with io.monad) + [_ (OutputStream::write data +0 (.int (binary.size data)) + output)] + (Flushable::flush output))))) + + (def: close + (//.can-close + (function (close _) + (do (error.with io.monad) + [_ (AutoCloseable::close input) + _ (AutoCloseable::close output)] + (AutoCloseable::close socket)))))))))) + + (def: #export (client address port) + (-> //.Address //.Port (IO (Error (TCP IO)))) + (do (error.with io.monad) + [socket (Socket::new address (.int port))] + (io.io (tcp socket)))) + + (def: #export (server port) + (-> //.Port (IO (Error [(Resolver Any) + (Channel (TCP IO))]))) + (do (error.with io.monad) + [server (ServerSocket::new (.int port)) + #let [[close-signal close-resolver] (: [(Promise Any) (Resolver Any)] + (promise.promise [])) + _ (promise.await (function (_ _) + (AutoCloseable::close server)) + close-signal) + [output sink] (: [(Channel (TCP IO)) (Sink (TCP IO))] + (frp.channel [])) + _ (: (Promise Any) + (promise.future + (loop [_ []] + (do io.monad + [?client (do (error.with io.monad) + [socket (ServerSocket::accept server)] + (io.io (tcp socket)))] + (case ?client + (#error.Failure error) + (wrap []) + + (#error.Success client) + (do @ + [_ (:: sink feed client)] + (recur [])))))))]] + (wrap [close-resolver output]))))] + (`` (for {(~~ (static @.old)) + (as-is ) + + (~~ (static @.jvm)) + (as-is )}))) diff --git a/stdlib/source/lux/world/net/udp.old.lux b/stdlib/source/lux/world/net/udp.old.lux index 9c58404fb..1f78f4b0d 100644 --- a/stdlib/source/lux/world/net/udp.old.lux +++ b/stdlib/source/lux/world/net/udp.old.lux @@ -1,5 +1,7 @@ (.module: [lux #* + [host (#+ import:)] + ["@" target] [abstract monad] [control @@ -15,40 +17,9 @@ [collection ["." array]]] [world - ["." binary (#+ Binary)]] - [host (#+ import:)] - [tool - [compiler - ["." host]]]] + ["." binary (#+ Binary)]]] ["." // (#+ Location Can-Read Can-Write Can-Close)]) -(import: java/lang/AutoCloseable - (close [] #io #try void)) - -(import: java/io/Flushable - (flush [] #io #try void)) - -(import: java/net/InetAddress - (#static getAllByName [String] #io #try (Array InetAddress)) - (getHostAddress [] String)) - -(import: java/net/DatagramPacket - (new #as new|send [(Array byte) int int InetAddress int]) - (new #as new|receive [(Array byte) int int]) - (getAddress [] InetAddress) - (getPort [] int) - (getLength [] int)) - -(import: java/net/DatagramSocket - (new #as new|client [] #io #try) - (new #as new|server [int] #io #try) - (receive [DatagramPacket] #io #try void) - (send [DatagramPacket] #io #try void)) - -############################################################ -############################################################ -############################################################ - (exception: #export (cannot-resolve-address {address //.Address}) (ex.report ["Address" address])) @@ -74,53 +45,80 @@ [write //.can-write] [close //.can-close]))))) -(`` (for {(~~ (static host.old)) - (as-is (def: (resolve address) - (-> //.Address (IO (Error InetAddress))) - (do (error.with io.monad) - [addresses (InetAddress::getAllByName address)] - (: (IO (Error InetAddress)) - (case (array.size addresses) - 0 (io.io (ex.throw cannot-resolve-address address)) - 1 (wrap (maybe.assume (array.read 0 addresses))) - _ (io.io (ex.throw multiple-candidate-addresses address)))))) - - (def: (udp socket) - (-> DatagramSocket (UDP IO)) - (structure (def: read - (//.can-read - (function (read size) - (let [data (binary.create size) - packet (DatagramPacket::new|receive data +0 (.int size))] +(with-expansions [ (as-is (import: java/lang/AutoCloseable + (close [] #io #try void)) + + (import: java/io/Flushable + (flush [] #io #try void)) + + (import: java/net/InetAddress + (#static getAllByName [String] #io #try (Array InetAddress)) + (getHostAddress [] String)) + + (import: java/net/DatagramPacket + (new #as new|send [(Array byte) int int InetAddress int]) + (new #as new|receive [(Array byte) int int]) + (getAddress [] InetAddress) + (getPort [] int) + (getLength [] int)) + + (import: java/net/DatagramSocket + (new #as new|client [] #io #try) + (new #as new|server [int] #io #try) + (receive [DatagramPacket] #io #try void) + (send [DatagramPacket] #io #try void)) + + (def: (resolve address) + (-> //.Address (IO (Error InetAddress))) (do (error.with io.monad) - [_ (DatagramSocket::receive packet socket) - #let [bytes-read (.nat (DatagramPacket::getLength packet))]] - (wrap [bytes-read - {#//.address (|> packet DatagramPacket::getAddress InetAddress::getHostAddress) - #//.port (.nat (DatagramPacket::getPort packet))} - data])))))) - - (def: write - (//.can-write - (function (write [location data]) - (do (error.with io.monad) - [address (resolve (get@ #//.address location))] - (DatagramSocket::send (DatagramPacket::new|send data +0 (.int (binary.size data)) address (.int (get@ #//.port location))) - socket))))) - - (def: close - (//.can-close - (function (close _) - (AutoCloseable::close socket)))))) - - (def: #export client - (IO (Error (UDP IO))) - (|> (DatagramSocket::new|client) - (:: (error.with io.monad) map ..udp))) - - (def: #export server - (-> //.Port (IO (Error (UDP IO)))) - (|>> .int - DatagramSocket::new|server - (:: (error.with io.monad) map ..udp))) - )})) + [addresses (InetAddress::getAllByName address)] + (: (IO (Error InetAddress)) + (case (array.size addresses) + 0 (io.io (ex.throw cannot-resolve-address address)) + 1 (wrap (maybe.assume (array.read 0 addresses))) + _ (io.io (ex.throw multiple-candidate-addresses address)))))) + + (def: (udp socket) + (-> DatagramSocket (UDP IO)) + (structure (def: read + (//.can-read + (function (read size) + (let [data (binary.create size) + packet (DatagramPacket::new|receive data +0 (.int size))] + (do (error.with io.monad) + [_ (DatagramSocket::receive packet socket) + #let [bytes-read (.nat (DatagramPacket::getLength packet))]] + (wrap [bytes-read + {#//.address (|> packet DatagramPacket::getAddress InetAddress::getHostAddress) + #//.port (.nat (DatagramPacket::getPort packet))} + data])))))) + + (def: write + (//.can-write + (function (write [location data]) + (do (error.with io.monad) + [address (resolve (get@ #//.address location))] + (DatagramSocket::send (DatagramPacket::new|send data +0 (.int (binary.size data)) address (.int (get@ #//.port location))) + socket))))) + + (def: close + (//.can-close + (function (close _) + (AutoCloseable::close socket)))))) + + (def: #export client + (IO (Error (UDP IO))) + (|> (DatagramSocket::new|client) + (:: (error.with io.monad) map ..udp))) + + (def: #export server + (-> //.Port (IO (Error (UDP IO)))) + (|>> .int + DatagramSocket::new|server + (:: (error.with io.monad) map ..udp))) + )] + (`` (for {(~~ (static @.old)) + (as-is ) + + (~~ (static @.jvm)) + (as-is )}))) -- cgit v1.2.3