From f07effd9faf3fdaa677f659d6bbccf98931c5e5a Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Tue, 22 Feb 2022 16:29:17 -0400 Subject: No more automatic conversions of primitive types in JVM FFI. --- .../library/lux/control/concurrency/atom.lux | 35 ++-- .../library/lux/control/concurrency/thread.lux | 7 +- stdlib/source/library/lux/data/text/buffer.lux | 43 ++--- .../source/library/lux/data/text/encoding/utf8.lux | 13 +- stdlib/source/library/lux/debug.lux | 13 +- stdlib/source/library/lux/ffi.jvm.lux | 148 +++++++++------- stdlib/source/library/lux/ffi.old.lux | 33 +++- stdlib/source/library/lux/target/jvm/constant.lux | 4 +- stdlib/source/library/lux/target/jvm/loader.lux | 4 +- .../compiler/language/lux/analysis/inference.lux | 6 +- .../tool/compiler/language/lux/phase/analysis.lux | 190 ++++++++++----------- .../language/lux/phase/analysis/complex.lux | 39 +++-- .../compiler/meta/archive/artifact/category.lux | 2 +- .../lux/tool/compiler/meta/packager/jvm.lux | 15 +- stdlib/source/library/lux/world/console.lux | 41 ++--- stdlib/source/library/lux/world/file.lux | 70 ++++---- stdlib/source/library/lux/world/file/watch.lux | 9 +- .../source/library/lux/world/net/http/client.lux | 20 ++- stdlib/source/library/lux/world/program.lux | 98 ++++++----- stdlib/source/library/lux/world/shell.lux | 84 ++++----- 20 files changed, 462 insertions(+), 412 deletions(-) (limited to 'stdlib/source/library') diff --git a/stdlib/source/library/lux/control/concurrency/atom.lux b/stdlib/source/library/lux/control/concurrency/atom.lux index a30b3bc73..c865b8e33 100644 --- a/stdlib/source/library/lux/control/concurrency/atom.lux +++ b/stdlib/source/library/lux/control/concurrency/atom.lux @@ -1,19 +1,19 @@ (.using - [library - [lux "*" - ["@" target] - ["[0]" ffi] - [abstract - [monad {"+" do}]] - [control - ["[0]" function] - ["[0]" io {"+" IO} ("[1]#[0]" functor)]] - [data - ["[0]" product] - [collection - ["[0]" array]]] - [type - abstract]]]) + [library + [lux "*" + ["@" target] + ["[0]" ffi] + [abstract + [monad {"+" do}]] + [control + ["[0]" function] + ["[0]" io {"+" IO} ("[1]#[0]" functor)]] + [data + ["[0]" product] + [collection + ["[0]" array]]] + [type + abstract]]]) (with_expansions [ (as_is (ffi.import: (java/util/concurrent/atomic/AtomicReference a) ["[1]::[0]" @@ -68,12 +68,13 @@ (def: .public (compare_and_swap! current new atom) (All (_ a) (-> a a (Atom a) (IO Bit))) - (io.io (with_expansions [ (java/util/concurrent/atomic/AtomicReference::compareAndSet current new (:representation atom))] + (io.io (with_expansions [ (ffi.of_boolean (java/util/concurrent/atomic/AtomicReference::compareAndSet current new (:representation atom)))] (for [@.old @.jvm ] (let [old ( 0 (:representation atom))] (if (same? old current) - (exec ( 0 new (:representation atom)) + (exec + ( 0 new (:representation atom)) true) false)))))) )) diff --git a/stdlib/source/library/lux/control/concurrency/thread.lux b/stdlib/source/library/lux/control/concurrency/thread.lux index 9d91b6ee8..07de8c1c7 100644 --- a/stdlib/source/library/lux/control/concurrency/thread.lux +++ b/stdlib/source/library/lux/control/concurrency/thread.lux @@ -23,6 +23,7 @@ ["[0]" atom {"+" Atom}]]) (with_expansions [ (as_is (ffi.import: java/lang/Object) + (ffi.import: java/lang/Long) (ffi.import: java/lang/Runtime ["[1]::[0]" @@ -69,6 +70,7 @@ Nat (with_expansions [ (|> (java/lang/Runtime::getRuntime) (java/lang/Runtime::availableProcessors) + ffi.of_int .nat)] (for [@.old @.jvm ] @@ -77,7 +79,10 @@ (with_expansions [ (as_is (def: runner java/util/concurrent/ScheduledThreadPoolExecutor - (java/util/concurrent/ScheduledThreadPoolExecutor::new (.int ..parallelism))))] + (|> ..parallelism + .int + ffi.as_int + java/util/concurrent/ScheduledThreadPoolExecutor::new)))] (for [@.old @.jvm @.js (as_is) diff --git a/stdlib/source/library/lux/data/text/buffer.lux b/stdlib/source/library/lux/data/text/buffer.lux index 30c6714fd..a07e65250 100644 --- a/stdlib/source/library/lux/data/text/buffer.lux +++ b/stdlib/source/library/lux/data/text/buffer.lux @@ -1,23 +1,23 @@ (.using - [library - [lux "*" - ["@" target] - ["[0]" ffi {"+" import:}] - [control - ["[0]" function]] - [data - ["[0]" product] - [text - ["%" format {"+" format}]] - [collection - ["[0]" array] - ["[0]" sequence {"+" Sequence} ("[1]#[0]" mix)]]] - [math - [number - ["n" nat]]] - [type - abstract]]] - ["[0]" //]) + [library + [lux "*" + ["@" target] + ["[0]" ffi {"+" import:}] + [control + ["[0]" function]] + [data + ["[0]" product] + [text + ["%" format {"+" format}]] + [collection + ["[0]" array] + ["[0]" sequence {"+" Sequence} ("[1]#[0]" mix)]]] + [math + [number + ["n" nat]]] + [type + abstract]]] + ["[0]" //]) (with_expansions [ (as_is (import: java/lang/CharSequence) @@ -113,9 +113,10 @@ (def: .public (text buffer) (-> Buffer Text) (with_expansions [ (let [[capacity transform] (:representation buffer)] - (|> (java/lang/StringBuilder::new (.int capacity)) + (|> (java/lang/StringBuilder::new (ffi.as_int (.int capacity))) transform - java/lang/StringBuilder::toString))] + java/lang/StringBuilder::toString + ffi.of_string))] (for [@.old @.jvm @.js (let [[capacity transform] (:representation buffer)] diff --git a/stdlib/source/library/lux/data/text/encoding/utf8.lux b/stdlib/source/library/lux/data/text/encoding/utf8.lux index baef37aa1..bcc1a0ee2 100644 --- a/stdlib/source/library/lux/data/text/encoding/utf8.lux +++ b/stdlib/source/library/lux/data/text/encoding/utf8.lux @@ -65,15 +65,12 @@ (def: (encoded value) (-> Text Binary) (for [@.old - (java/lang/String::getBytes (//.name //.utf_8) - ... TODO: Remove coercion below. - ... The coercion below may seem - ... gratuitous, but removing it - ... causes a grave compilation problem. - (:as java/lang/String value)) + (java/lang/String::getBytes (ffi.as_string (//.name //.utf_8)) + (ffi.as_string value)) @.jvm - (java/lang/String::getBytes (//.name //.utf_8) value) + (java/lang/String::getBytes (ffi.as_string (//.name //.utf_8)) + (ffi.as_string value)) @.js (cond ffi.on_nashorn? @@ -113,7 +110,7 @@ (def: (decoded value) (-> Binary (Try Text)) - (with_expansions [ {try.#Success (java/lang/String::new value (//.name //.utf_8))}] + (with_expansions [ {try.#Success (ffi.of_string (java/lang/String::new value (ffi.as_string (//.name //.utf_8))))}] (for [@.old @.jvm diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux index e042ad9d1..2e4e790fe 100644 --- a/stdlib/source/library/lux/debug.lux +++ b/stdlib/source/library/lux/debug.lux @@ -147,12 +147,13 @@ [(case (ffi.check object) {.#Some value} (`` (|> value (~~ (template.spliced )))) + {.#None})] - [java/lang/Boolean [(:as .Bit) %.bit]] - [java/lang/Long [(:as .Int) %.int]] - [java/lang/Number [java/lang/Number::doubleValue %.frac]] - [java/lang/String [(:as .Text) %.text]] + [java/lang/Boolean [ffi.of_boolean %.bit]] + [java/lang/Long [ffi.of_long %.int]] + [java/lang/Number [java/lang/Number::doubleValue ffi.of_double %.frac]] + [java/lang/String [ffi.of_string %.text]] )) (case (ffi.check [java/lang/Object] object) {.#Some value} @@ -166,7 +167,7 @@ (let [last? (case last? {.#Some _} #1 {.#None} #0)] - (|> (%.format (%.nat (.nat (java/lang/Integer::longValue tag))) + (|> (%.format (%.nat (.nat (ffi.of_long (java/lang/Integer::longValue tag)))) " " (%.bit last?) " " (inspection choice)) (text.enclosed ["(" ")"]))) @@ -174,7 +175,7 @@ _ (tuple_inspection inspection value))) {.#None}) - (java/lang/Object::toString object))))] + (ffi.of_string (java/lang/Object::toString object)))))] (for [@.old @.jvm diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux index 46ffa8021..8439ae24a 100644 --- a/stdlib/source/library/lux/ffi.jvm.lux +++ b/stdlib/source/library/lux/ffi.jvm.lux @@ -1,42 +1,42 @@ (.using - [library - ["[0]" lux {"-" Primitive Type type int char :as} - ["[1]_[0]" type ("[1]#[0]" equivalence)] - [abstract - ["[0]" monad {"+" Monad do}] - ["[0]" enum]] - [control - ["[0]" function] - ["[0]" io] - ["[0]" maybe] - ["[0]" try {"+" Try}] - ["[0]" exception {"+" Exception exception:}] - ["<>" parser ("[1]#[0]" monad) - ["<[0]>" code {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [collection - ["[0]" array] - ["[0]" list ("[1]#[0]" monad mix monoid)] - ["[0]" dictionary {"+" Dictionary}]]] - [macro {"+" with_symbols} - [syntax {"+" syntax:}] - ["[0]" code] - ["[0]" template]] - ["[0]" meta] - [target - [jvm - [encoding - ["[0]" name {"+" External}]] - ["[0]" type {"+" Type Argument Typed} - ["[0]" category {"+" Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration}] - ["[0]" box] - ["[0]" descriptor] - ["[0]" signature] - ["[0]" reflection] - ["[0]" parser]]]]]]) + [library + ["[0]" lux {"-" Primitive Type type int char :as} + ["[1]_[0]" type ("[1]#[0]" equivalence)] + [abstract + ["[0]" monad {"+" Monad do}] + ["[0]" enum]] + [control + ["[0]" function] + ["[0]" io] + ["[0]" maybe] + ["[0]" try {"+" Try}] + ["[0]" exception {"+" Exception exception:}] + ["<>" parser ("[1]#[0]" monad) + ["<[0]>" code {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [collection + ["[0]" array] + ["[0]" list ("[1]#[0]" monad mix monoid)] + ["[0]" dictionary {"+" Dictionary}]]] + [macro {"+" with_symbols} + [syntax {"+" syntax:}] + ["[0]" code] + ["[0]" template]] + ["[0]" meta] + [target + [jvm + [encoding + ["[0]" name {"+" External}]] + ["[0]" type {"+" Type Argument Typed} + ["[0]" category {"+" Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration}] + ["[0]" box] + ["[0]" descriptor] + ["[0]" signature] + ["[0]" reflection] + ["[0]" parser]]]]]]) (def: internal (-> External Text) @@ -66,6 +66,7 @@ [Float box.float] [Double box.double] [Character box.char] + [String "java.lang.String"] ) (template [ ] @@ -1396,9 +1397,6 @@ [with_return_io #import_member_io? (` ((~! io.io) (~ return_term)))] ) -(def: $String - (type.class "java.lang.String" (list))) - (template [ ] [(def: ( mode [unboxed raw]) (-> Primitive_Mode [(Type Value) Code] Code) @@ -1409,10 +1407,10 @@ {#AutoPrM} (with_expansions [' (template.spliced ) - (template [
 ]
-                                                                        [(# type.equivalence =  unboxed)
+                                                          (template [ 
 ]
+                                                                        [(# type.equivalence =  unboxed)
                                                                          (with_expansions [' (template.spliced )]
-                                                                           [
+                                                                           [
                                                                             (` (.|> (~ raw) (~+ 
)))
                                                                             (list ')])]
 
@@ -1438,29 +1436,21 @@
          (` (.|> (~ unboxed/boxed) (~+ post))))))]
 
   [#1 with_automatic_input_conversion ..unbox
-   [[type.boolean type.boolean (list (` (.: .Bit)) (` (.:as (.Primitive (~ (code.text box.boolean)))))) []]
-    [type.byte type.byte (list (` (.: .Int)) (` (.:as (.Primitive (~ (code.text box.long))))) (` ..long_to_byte)) []]
-    [type.short type.short (list (` (.: .Int)) (` (.:as (.Primitive (~ (code.text box.long))))) (` ..long_to_short)) []]
-    [type.int type.int (list (` (.: .Int)) (` (.:as (.Primitive (~ (code.text box.long))))) (` ..long_to_int)) []]
-    [type.long type.long (list (` (.: .Int)) (` (.:as (.Primitive (~ (code.text box.long)))))) []]
-    [type.float type.float (list (` (.: .Frac)) (` (.:as (.Primitive (~ (code.text box.double))))) (` ..double_to_float)) []]
-    [type.double type.double (list (` (.: .Frac)) (` (.:as (.Primitive (~ (code.text box.double)))))) []]
-    [..$String ..$String (list (` (.: .Text)) (` (.:as (.Primitive (~ (code.text (..reflection ..$String))))))) []]
-    [(type.class box.boolean (list)) (type.class box.boolean (list)) (list (` (.: .Bit)) (` (.:as (.Primitive (~ (code.text box.boolean)))))) []]
-    [(type.class box.long (list)) (type.class box.long (list)) (list (` (.: .Int)) (` (.:as (.Primitive (~ (code.text box.long)))))) []]
-    [(type.class box.double (list)) (type.class box.double (list)) (list (` (.: .Frac)) (` (.:as (.Primitive (~ (code.text box.double)))))) []]]]
+   [[type.boolean (list (` (.:as (.Primitive (~ (code.text box.boolean)))))) []]
+    [type.byte (list (` (.:as (.Primitive (~ (code.text box.byte)))))) []]
+    [type.short (list (` (.:as (.Primitive (~ (code.text box.short)))))) []]
+    [type.int (list (` (.: (.Primitive (~ (code.text box.int)))))) []]
+    [type.long (list (` (.:as (.Primitive (~ (code.text box.long)))))) []]
+    [type.float (list (` (.:as (.Primitive (~ (code.text box.float)))))) []]
+    [type.double (list (` (.:as (.Primitive (~ (code.text box.double)))))) []]]]
   [#0 with_automatic_output_conversion ..box
-   [[type.boolean type.boolean (list) [(` (.: (.Primitive (~ (code.text box.boolean))))) (` (.:as .Bit))]]
-    [type.byte type.long (list (` "jvm conversion byte-to-long")) [(` (.: (.Primitive (~ (code.text box.long))))) (` (.:as .Int))]]
-    [type.short type.long (list (` "jvm conversion short-to-long")) [(` (.: (.Primitive (~ (code.text box.long))))) (` (.:as .Int))]]
-    [type.int type.long (list (` "jvm conversion int-to-long")) [(` (.: (.Primitive (~ (code.text box.long))))) (` (.:as .Int))]]
-    [type.long type.long (list) [(` (.: (.Primitive (~ (code.text box.long))))) (` (.:as .Int))]]
-    [type.float type.double (list (` "jvm conversion float-to-double")) [(` (.: (.Primitive (~ (code.text box.double))))) (` (.:as .Frac))]]
-    [type.double type.double (list) [(` (.: (.Primitive (~ (code.text box.double))))) (` (.:as .Frac))]]
-    [..$String ..$String (list) [(` (.: (.Primitive (~ (code.text (..reflection ..$String)))))) (` (.:as .Text))]]
-    [(type.class box.boolean (list)) (type.class box.boolean (list)) (list) [(` (.: (.Primitive (~ (code.text box.boolean))))) (` (.:as .Bit))]]
-    [(type.class box.long (list)) (type.class box.long (list)) (list) [(` (.: (.Primitive (~ (code.text box.long))))) (` (.:as .Int))]]
-    [(type.class box.double (list)) (type.class box.double (list)) (list) [(` (.: (.Primitive (~ (code.text box.double))))) (` (.:as .Frac))]]]]
+   [[type.boolean (list) [(` (.: (.Primitive (~ (code.text box.boolean)))))]]
+    [type.byte (list) [(` (.: (.Primitive (~ (code.text box.byte)))))]]
+    [type.short (list) [(` (.: (.Primitive (~ (code.text box.short)))))]]
+    [type.int (list) [(` (.: (.Primitive (~ (code.text box.int)))))]]
+    [type.long (list) [(` (.: (.Primitive (~ (code.text box.long)))))]]
+    [type.float (list) [(` (.: (.Primitive (~ (code.text box.float)))))]]
+    [type.double (list) [(` (.: (.Primitive (~ (code.text box.double)))))]]]]
   )
 
 (def: (un_quoted quoted)
@@ -1930,3 +1920,29 @@
 
     _
     (meta.failure (exception.error ..cannot_cast_to_non_object [type]))))
+
+(template [   ]
+  [(template: .public ( it)
+     [(|> it (: ) (:as ))])
+
+   (template: .public ( it)
+     [(|> it (: ) (:as ))])]
+
+  [as_boolean .Bit ..Boolean of_boolean]
+  [as_long .Int ..Long of_long]
+  [as_double .Frac ..Double of_double]
+  [as_string .Text ..String of_string]
+  )
+
+(template [  <$>  <$'>  ]
+  [(template: .public ( it)
+     [(|> it (: ) (:as ) <$> (: ))])
+
+   (template: .public ( it)
+     [(|> it (: ) <$'> (: ) (:as ))])]
+
+  [as_byte .Int ..long_to_byte ..Long ..byte_to_long ..Byte of_byte]
+  [as_short .Int ..long_to_short ..Long ..short_to_long ..Short of_short]
+  [as_int .Int ..long_to_int ..Long ..int_to_long ..Integer of_int]
+  [as_float .Frac ..double_to_float ..Double ..float_to_double ..Float of_float]
+  )
diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux
index 3b8fdc613..ec3693ece 100644
--- a/stdlib/source/library/lux/ffi.old.lux
+++ b/stdlib/source/library/lux/ffi.old.lux
@@ -62,6 +62,32 @@
   [char_to_long "jvm convert char-to-long" "java.lang.Character" "java.lang.Long"]
   )
 
+(template [   ]
+  [(template: .public ( it)
+     [(|> it (: ) (:as (Primitive )))])
+
+   (template: .public ( it)
+     [(|> it (: (Primitive )) (:as ))])]
+
+  [as_boolean .Bit "java.lang.Boolean" of_boolean]
+  [as_long .Int "java.lang.Long" of_long]
+  [as_double .Frac "java.lang.Double" of_double]
+  [as_string .Text "java.lang.String" of_string]
+  )
+
+(template [  <$>  <$'>  ]
+  [(template: .public ( it)
+     [(|> it (: ) (:as (Primitive )) <$> (: (Primitive )))])
+
+   (template: .public ( it)
+     [(|> it (: (Primitive )) <$'> (: (Primitive )) (:as ))])]
+
+  [as_byte .Int ..long_to_byte "java.lang.Long" ..byte_to_long "java.lang.Byte" of_byte]
+  [as_short .Int ..long_to_short "java.lang.Long" ..short_to_long "java.lang.Short" of_short]
+  [as_int .Int ..long_to_int "java.lang.Long" ..int_to_long "java.lang.Integer" of_int]
+  [as_float .Frac ..double_to_float "java.lang.Double" ..float_to_double "java.lang.Float" of_float]
+  )
+
 ... [Utils]
 (def: constructor_method_name "")
 (def: member_separator "::")
@@ -1396,12 +1422,7 @@
        expression
        
        {#AutoPrM}
-       (case class
-         "byte"  (` ( (~ expression)))
-         "short" (` ( (~ expression)))
-         "int"   (` ( (~ expression)))
-         "float" (` ( (~ expression)))
-         _       expression)))]
+       expression))]
 
   [auto_convert_input  long_to_byte long_to_short long_to_int double_to_float]
   [auto_convert_output byte_to_long short_to_long int_to_long float_to_double]
diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux
index 370dbdabb..8f6358470 100644
--- a/stdlib/source/library/lux/target/jvm/constant.lux
+++ b/stdlib/source/library/lux/target/jvm/constant.lux
@@ -119,9 +119,9 @@
                 (~~ (template.spliced )))))]
 
     [integer_writer Integer [] [binaryF.bits/32]]
-    [float_writer Float [java/lang/Float::floatToRawIntBits ffi.int_to_long (:as I64)] [i32.i32 binaryF.bits/32]]
+    [float_writer Float [java/lang/Float::floatToRawIntBits ffi.of_int .i64] [i32.i32 binaryF.bits/32]]
     [long_writer Long [] [binaryF.bits/64]]
-    [double_writer Double [java/lang/Double::doubleToRawLongBits] [binaryF.bits/64]]
+    [double_writer Double [java/lang/Double::doubleToRawLongBits ffi.of_long] [binaryF.bits/64]]
     [string_writer String [] [//index.writer]]
     )
   )
diff --git a/stdlib/source/library/lux/target/jvm/loader.lux b/stdlib/source/library/lux/target/jvm/loader.lux
index 99a4573bc..26e67f2e9 100644
--- a/stdlib/source/library/lux/target/jvm/loader.lux
+++ b/stdlib/source/library/lux/target/jvm/loader.lux
@@ -74,7 +74,7 @@
                                            (java/lang/Integer::TYPE)))
                         (ffi.write! 3 (:as 
                                            (java/lang/Integer::TYPE))))]
-      (do_to (java/lang/Class::getDeclaredMethod "defineClass"
+      (do_to (java/lang/Class::getDeclaredMethod (ffi.as_string "defineClass")
                                                  signature
                                                  (ffi.class_for java/lang/ClassLoader))
         (java/lang/reflect/AccessibleObject::setAccessible true)))))
@@ -140,4 +140,4 @@
 (def: .public (load name loader)
   (-> Text java/lang/ClassLoader
       (IO (Try (java/lang/Class java/lang/Object))))
-  (java/lang/ClassLoader::loadClass name loader))
+  (java/lang/ClassLoader::loadClass (ffi.as_string name) loader))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux
index 6ca7137d2..fa9e2e0fb 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux
@@ -80,9 +80,9 @@
     ([.#UnivQ]
      [.#ExQ])
 
-    (^or {.#Parameter @}
-         {.#Ex @}
-         {.#Named name anonymous})
+    (^or {.#Parameter _}
+         {.#Ex _}
+         {.#Named _})
     :it:))
 
 ... Type-inference works by applying some (potentially quantified) type
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 657096c10..085e071a7 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
@@ -10,6 +10,8 @@
      ["%" format {"+" format}]]
     [collection
      ["[0]" list]]]
+   [macro
+    ["[0]" code]]
    [math
     [number
      ["n" nat]]]
@@ -33,105 +35,97 @@
      [meta
       [archive {"+" Archive}]]]]]])
 
-(exception: .public (unrecognized_syntax [code Code])
+(exception: .public (invalid [syntax 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
-
-(type: (Fix a)
-  (-> a a))
-
-(def: (compile|literal archive compile else code')
-  (-> Archive Phase (Fix (-> (Code' (Ann Location)) (Operation Analysis))))
-  (case code'
-    (^template [ ]
-      [{ value}
-       ( value)])
-    ([.#Bit  /simple.bit]
-     [.#Nat  /simple.nat]
-     [.#Int  /simple.int]
-     [.#Rev  /simple.rev]
-     [.#Frac /simple.frac]
-     [.#Text /simple.text])
-
-    (^ {.#Variant (list& [_ {.#Symbol tag}]
-                         values)})
-    (case values
-      {.#Item value {.#End}}
-      (/complex.variant compile tag archive value)
-
-      _
-      (/complex.variant compile tag archive (` [(~+ values)])))
-
-    (^ {.#Variant (list& [_ {.#Nat lefts}] [_ {.#Bit right?}]
-                         values)})
-    (case values
-      {.#Item value {.#End}}
-      (/complex.sum compile lefts right? archive value)
-
-      _
-      (/complex.sum compile lefts right? archive (` [(~+ values)])))
-
-    (^ {.#Tuple elems})
-    (/complex.record compile archive elems)
-
-    _
-    (else code')))
-
-(def: (compile|others expander archive compile code')
-  (-> Expander Archive Phase (-> (Code' (Ann Location)) (Operation Analysis)))
-  (case code'
-    {.#Symbol reference}
-    (/reference.reference reference)
-
-    (^ {.#Form (list [_ {.#Variant branches}] input)})
-    (case (list.pairs branches)
-      {.#Some branches}
-      (/case.case compile branches archive input)
-
-      {.#None}
-      (//.except ..unrecognized_syntax [location.dummy code']))
-
-    (^ {.#Form (list& [_ {.#Text extension_name}] extension_args)})
-    (//extension.apply archive compile [extension_name extension_args])
-
-    (^ {.#Form (list [_ {.#Tuple (list [_ {.#Symbol ["" function_name]}]
-                                       [_ {.#Symbol ["" arg_name]}])}]
-                     body)})
-    (/function.function compile function_name arg_name archive body)
-
-    (^ {.#Form (list& functionC argsC+)})
-    (do [! //.monad]
-      [[functionT functionA] (/type.inferring
-                              (compile archive functionC))]
-      (case functionA
-        {/.#Reference {reference.#Constant def_name}}
-        (do !
-          [?macro (//extension.lifted (meta.macro def_name))]
-          (case ?macro
-            {.#Some macro}
-            (do !
-              [expansion (//extension.lifted (/macro.single_expansion expander def_name macro argsC+))]
-              (compile archive expansion))
-
-            _
-            (/function.apply compile argsC+ functionT functionA archive functionC)))
-
-        _
-        (/function.apply compile argsC+ functionT functionA archive functionC)))
-
-    _
-    (//.except ..unrecognized_syntax [location.dummy code'])))
+   ["Syntax" (%.code syntax)]))
+
+(template: (variant_analysis analysis archive tag values)
+  ... (-> Phase Archive Symbol (List Code) (Operation Analysis))
+  [(case values
+     (^ (list value))
+     (/complex.variant analysis tag archive value)
+
+     _
+     (/complex.variant analysis tag archive (code.tuple values)))])
+
+(template: (sum_analysis analysis archive lefts right? values)
+  ... (-> Phase Archive Nat Bit (List Code) (Operation Analysis))
+  [(case values
+     (^ (list value))
+     (/complex.sum analysis lefts right? archive value)
+
+     _
+     (/complex.sum analysis lefts right? archive (code.tuple values)))])
+
+(template: (case_analysis analysis archive input branches code)
+  ... (-> Phase Archive Code (List Code) Code (Operation Analysis))
+  [(case (list.pairs branches)
+     {.#Some branches}
+     (/case.case analysis branches archive input)
+
+     {.#None}
+     (//.except ..invalid [code]))])
+
+(template: (apply_analysis expander analysis archive functionC argsC+)
+  ... (-> Expander Phase Archive Code (List Code) (Operation Analysis))
+  [(do [! //.monad]
+     [[functionT functionA] (/type.inferring
+                             (analysis archive functionC))]
+     (case functionA
+       (^ (/.constant def_name))
+       (do !
+         [?macro (//extension.lifted (meta.macro def_name))]
+         (case ?macro
+           {.#Some macro}
+           (do !
+             [expansion (//extension.lifted (/macro.single_expansion expander def_name macro argsC+))]
+             (analysis archive expansion))
+
+           _
+           (/function.apply analysis argsC+ functionT functionA archive functionC)))
+
+       _
+       (/function.apply analysis argsC+ functionT functionA archive functionC)))])
 
 (def: .public (phase expander)
   (-> 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.
-      (/.with_location location
-        (compile|literal archive compile
-                         (compile|others expander archive compile)
-                         code')))))
+  (function (analysis archive code)
+    (<| (let [[location code'] code])
+        ... The location must be set in the state for the sake
+        ... of having useful error messages.
+        (/.with_location location)
+        (case code
+          (^template [ ]
+            [[_ { value}]
+             ( value)])
+          ([.#Symbol /reference.reference]
+           [.#Text /simple.text]
+           [.#Nat  /simple.nat]
+           [.#Bit  /simple.bit]
+           [.#Frac /simple.frac]
+           [.#Int  /simple.int]
+           [.#Rev  /simple.rev])
+
+          (^code [(~+ elems)])
+          (/complex.record analysis archive elems)
+
+          (^code {(~ [_ {.#Symbol tag}]) (~+ values)})
+          (..variant_analysis analysis archive tag values)
+
+          (^code ({(~+ branches)} (~ input)))
+          (..case_analysis analysis archive input branches code)
+
+          (^code ([(~ [_ {.#Symbol ["" function_name]}]) (~ [_ {.#Symbol ["" arg_name]}])] (~ body)))
+          (/function.function analysis function_name arg_name archive body)
+
+          (^code ((~ [_ {.#Text extension_name}]) (~+ extension_args)))
+          (//extension.apply archive analysis [extension_name extension_args])
+
+          (^code ((~ functionC) (~+ argsC+)))
+          (..apply_analysis expander analysis archive functionC argsC+)
+
+          (^code {(~ [_ {.#Nat lefts}]) (~ [_ {.#Bit right?}]) (~+ values)})
+          (..sum_analysis analysis archive lefts right? values)
+
+          _
+          (//.except ..invalid [code])))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux
index 1bf6a48b9..54b2cf1dd 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux
@@ -134,15 +134,17 @@
                 _
                 (/.except ..cannot_infer_sum [expectedT lefts right? valueC])))
 
-            (^template [ ]
-              [{ _}
-               (do !
-                 [[@instance :instance:] (/type.check )]
-                 (<| (/type.expecting (maybe.trusted (type.applied (list :instance:) expectedT)))
-                     (again valueC)))])
-            ([.#UnivQ check.existential]
-             [.#ExQ check.var])
-
+            {.#UnivQ _}
+            (do !
+              [[@instance :instance:] (/type.check check.existential)]
+              (<| (/type.expecting (maybe.trusted (type.applied (list :instance:) expectedT)))
+                  (again valueC)))
+            {.#ExQ _}
+            (<| /type.with_var
+                (function (_ [@instance :instance:]))
+                (/type.expecting (maybe.trusted (type.applied (list :instance:) expectedT)))
+                (again valueC))
+            
             {.#Apply inputT funT}
             (case funT
               {.#Var funT_id}
@@ -247,14 +249,17 @@
                                            (type.tuple (list#each product.left membersTA))))]
               (in (/.tuple (list#each product.right membersTA))))))
 
-        (^template [ ]
-          [{ _}
-           (do !
-             [[@instance :instance:] (/type.check )]
-             (<| (/type.expecting (maybe.trusted (type.applied (list :instance:) expectedT)))
-                 (product analyse archive membersC)))])
-        ([.#UnivQ check.existential]
-         [.#ExQ check.var])
+        {.#UnivQ _}
+        (do !
+          [[@instance :instance:] (/type.check check.existential)]
+          (<| (/type.expecting (maybe.trusted (type.applied (list :instance:) expectedT)))
+              (product analyse archive membersC)))
+
+        {.#ExQ _}
+        (<| /type.with_var
+            (function (_ [@instance :instance:]))
+            (/type.expecting (maybe.trusted (type.applied (list :instance:) expectedT)))
+            (product analyse archive membersC))
 
         {.#Apply inputT funT}
         (case funT
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux
index 526a8bce1..61698487d 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux
@@ -17,7 +17,7 @@
 (type: .public Definition
   [Text (Maybe [Arity [Nat Nat]])])
 
-(def: definition_equivalence
+(def: .public definition_equivalence
   (Equivalence Definition)
   ($_ product.equivalence
       text.equivalence
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 7f672fd92..4b5a82a43 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
@@ -148,7 +148,7 @@
     (do try.monad
       [_ (java/util/jar/JarOutputStream::putNextEntry (java/util/jar/JarEntry::new class_path) sink)]
       (in (do_to sink
-            (java/util/zip/ZipOutputStream::write content +0 (.int (binary.size content)))
+            (java/util/zip/ZipOutputStream::write content (ffi.as_int +0) (ffi.as_int (.int (binary.size content))))
             (java/io/Flushable::flush)
             (java/util/zip/ZipOutputStream::closeEntry))))))
 
@@ -168,16 +168,16 @@
   (-> java/util/jar/JarInputStream [Nat Binary])
   (let [chunk (binary.empty ..mebi_byte)
         chunk_size (.int ..mebi_byte)
-        buffer (java/io/ByteArrayOutputStream::new chunk_size)]
+        buffer (java/io/ByteArrayOutputStream::new (ffi.as_int chunk_size))]
     (loop [so_far 0]
-      (case (java/io/InputStream::read chunk 0 chunk_size input)
+      (case (ffi.of_int (java/io/InputStream::read chunk (ffi.as_int +0) (ffi.as_int chunk_size) input))
         -1
         [so_far
          (java/io/ByteArrayOutputStream::toByteArray buffer)]
         
         bytes_read
         (exec
-          (java/io/OutputStream::write chunk +0 bytes_read buffer)
+          (java/io/OutputStream::write chunk (ffi.as_int +0) (ffi.as_int bytes_read) buffer)
           (again (|> bytes_read .nat (n.+ so_far))))))))
 
 (def: (read_jar_entry_with_known_size expected_size input)
@@ -185,7 +185,8 @@
   (let [buffer (binary.empty expected_size)]
     (loop [so_far 0]
       (let [so_far' (|> input
-                        (java/io/InputStream::read buffer (.int so_far) (.int (n.- so_far expected_size)))
+                        (java/io/InputStream::read buffer (ffi.as_int (.int so_far)) (ffi.as_int (.int (n.- so_far expected_size))))
+                        ffi.of_int
                         .nat
                         (n.+ so_far))]
         (if (n.= expected_size so_far')
@@ -241,7 +242,7 @@
                   (again (set.has entry_path entries)
                          duplicates
                          (do_to sink
-                           (java/util/zip/ZipOutputStream::write entry_data +0 (.int entry_size))
+                           (java/util/zip/ZipOutputStream::write entry_data (ffi.as_int +0) (ffi.as_int (.int entry_size)))
                            (java/io/Flushable::flush)
                            (java/util/zip/ZipOutputStream::closeEntry)))))
               (again entries
@@ -254,7 +255,7 @@
     (do [! try.monad]
       [.let [necessary_dependencies (cache/artifact.necessary_dependencies archive)]
        order (cache/module.load_order $.key archive)
-       .let [buffer (java/io/ByteArrayOutputStream::new (.int ..mebi_byte))]
+       .let [buffer (java/io/ByteArrayOutputStream::new (ffi.as_int (.int ..mebi_byte)))]
        sink (|> order
                 (list#each (function (_ [module [module_id entry]])
                              [module_id (value@ archive.#output entry)]))
diff --git a/stdlib/source/library/lux/world/console.lux b/stdlib/source/library/lux/world/console.lux
index c10521e74..cf75af0a5 100644
--- a/stdlib/source/library/lux/world/console.lux
+++ b/stdlib/source/library/lux/world/console.lux
@@ -1,21 +1,21 @@
 (.using
-  [library
-   [lux "*"
-    ["@" target]
-    ["[0]" ffi {"+" import:}]
-    [abstract
-     [monad {"+" do}]]
-    [control
-     ["[0]" maybe]
-     ["[0]" try {"+" Try}]
-     ["[0]" exception {"+" exception:}]
-     ["[0]" io {"+" IO io}]
-     [concurrency
-      ["[0]" async {"+" Async} ("[1]#[0]" monad)]
-      ["[0]" atom]]]
-    [data
-     ["[0]" text {"+" Char}
-      ["%" format {"+" format}]]]]])
+ [library
+  [lux "*"
+   ["@" target]
+   ["[0]" ffi {"+" import:}]
+   [abstract
+    [monad {"+" do}]]
+   [control
+    ["[0]" maybe]
+    ["[0]" try {"+" Try} ("[1]#[0]" functor)]
+    ["[0]" exception {"+" exception:}]
+    ["[0]" io {"+" IO io} ("[1]#[0]" functor)]
+    [concurrency
+     ["[0]" async {"+" Async} ("[1]#[0]" monad)]
+     ["[0]" atom]]]
+   [data
+    ["[0]" text {"+" Char}
+     ["%" format {"+" format}]]]]])
 
 (type: .public (Console !)
   (Interface
@@ -82,13 +82,14 @@
                                             (def: (read _)
                                               (|> jvm_input
                                                   java/io/InputStream::read
-                                                  (# (try.with io.monad) each .nat)))
+                                                  (# (try.with io.monad) each (|>> ffi.of_int .nat))))
                                             
                                             (def: (read_line _)
-                                              (java/io/Console::readLine jvm_console))
+                                              (io#each (try#each (|>> ffi.of_string))
+                                                       (java/io/Console::readLine jvm_console)))
                                             
                                             (def: (write message)
-                                              (java/io/PrintStream::print message jvm_output))
+                                              (java/io/PrintStream::print (ffi.as_string message) jvm_output))
                                             
                                             (def: close
                                               (|>> (exception.except ..cannot_close) in)))))))))]
diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux
index 5fc2b5e2c..d597ee7da 100644
--- a/stdlib/source/library/lux/world/file.lux
+++ b/stdlib/source/library/lux/world/file.lux
@@ -155,17 +155,9 @@
 
   [cannot_make_directory]
   [cannot_find_directory]
-  
-  [cannot_read_all_data]
   )
 
-(with_expansions [ (as_is (exception: .public (cannot_modify_file [instant Instant
-                                                                            file Path])
-                                     (exception.report
-                                      ["Instant" (%.instant instant)]
-                                      ["Path" file]))
-
-                                   (ffi.import: java/lang/String)
+(with_expansions [ (as_is (ffi.import: java/lang/String)
 
                                    (`` (ffi.import: java/io/File
                                          ["[1]::[0]"
@@ -211,33 +203,34 @@
                                          (System IO)
 
                                          (def: separator
-                                           (java/io/File::separator))
+                                           (ffi.of_string (java/io/File::separator)))
 
                                          (~~ (template [ ]
                                                [(def: 
-                                                  (|>> java/io/File::new
+                                                  (|>> ffi.as_string
+                                                       java/io/File::new
                                                        
-                                                       (io#each (|>> (try.else false)))))]
+                                                       (io#each (|>> (try#each (|>> ffi.of_boolean)) (try.else false)))))]
 
                                                [file? java/io/File::isFile]
                                                [directory? java/io/File::isDirectory]
                                                ))
 
-                                         (def: (make_directory path)
-                                           (|> path
-                                               java/io/File::new
-                                               java/io/File::mkdir))
+                                         (def: make_directory
+                                           (|>> ffi.as_string
+                                                java/io/File::new
+                                                java/io/File::mkdir))
 
                                          (~~ (template [ ]
                                                [(def: ( path)
                                                   (do [! (try.with io.monad)]
-                                                    [?children (java/io/File::listFiles (java/io/File::new path))]
+                                                    [?children (java/io/File::listFiles (java/io/File::new (ffi.as_string path)))]
                                                     (case ?children
                                                       {.#Some children}
                                                       (|> children
                                                           (array.list {.#None})
-                                                          (monad.only ! (|>> ))
-                                                          (# ! each (monad.each ! (|>> java/io/File::getAbsolutePath)))
+                                                          (monad.only ! (|>>  (# ! each (|>> ffi.of_boolean))))
+                                                          (# ! each (monad.each ! (|>> java/io/File::getAbsolutePath (# ! each (|>> ffi.of_string)))))
                                                           (# ! conjoint))
 
                                                       {.#None}
@@ -248,57 +241,62 @@
                                                ))
 
                                          (def: file_size
-                                           (|>> java/io/File::new
+                                           (|>> ffi.as_string
+                                                java/io/File::new
                                                 java/io/File::length
-                                                (# (try.with io.monad) each .nat)))
+                                                (# (try.with io.monad) each (|>> ffi.of_long .nat))))
 
                                          (def: last_modified
-                                           (|>> java/io/File::new
+                                           (|>> ffi.as_string
+                                                java/io/File::new
                                                 (java/io/File::lastModified)
-                                                (# (try.with io.monad) each (|>> duration.of_millis instant.absolute))))
+                                                (# (try.with io.monad) each (|>> ffi.of_long duration.of_millis instant.absolute))))
 
                                          (def: can_execute?
-                                           (|>> java/io/File::new
-                                                java/io/File::canExecute))
+                                           (|>> ffi.as_string
+                                                java/io/File::new
+                                                java/io/File::canExecute
+                                                (io#each (try#each (|>> ffi.of_boolean)))))
 
                                          (def: (read path)
                                            (do (try.with io.monad)
-                                             [.let [file (java/io/File::new path)]
+                                             [.let [file (java/io/File::new (ffi.as_string path))]
                                               size (java/io/File::length file)
-                                              .let [data (binary.empty (.nat size))]
                                               stream (java/io/FileInputStream::new file)
+                                              .let [data (binary.empty (.nat (ffi.of_long size)))]
                                               bytes_read (java/io/InputStream::read data stream)
                                               _ (java/lang/AutoCloseable::close stream)]
-                                             (if (i.= size bytes_read)
-                                               (in data)
-                                               (# io.monad in (exception.except ..cannot_read_all_data path)))))
+                                             (in data)))
 
                                          (def: (delete path)
                                            (|> path
+                                               ffi.as_string
                                                java/io/File::new
                                                java/io/File::delete))
 
                                          (def: (modify time_stamp path)
                                            (|> path
+                                               ffi.as_string
                                                java/io/File::new
-                                               (java/io/File::setLastModified (|> time_stamp instant.relative duration.millis))))
+                                               (java/io/File::setLastModified (|> time_stamp instant.relative duration.millis ffi.as_long))))
                                          
-                                         (~~ (template [ ]
+                                         (~~ (template [ ]
                                                [(def: ( data path)
                                                   (do (try.with io.monad)
-                                                    [stream (java/io/FileOutputStream::new (java/io/File::new path) )
+                                                    [stream (java/io/FileOutputStream::new (java/io/File::new (ffi.as_string path)) (ffi.as_boolean ))
                                                      _ (java/io/OutputStream::write data stream)
                                                      _ (java/io/OutputStream::flush stream)]
                                                     (java/lang/AutoCloseable::close stream)))]
 
-                                               [write #0]
-                                               [append #1]
+                                               [#0 write]
+                                               [#1 append]
                                                ))
 
                                          (def: (move destination origin)
                                            (|> origin
+                                               ffi.as_string
                                                java/io/File::new
-                                               (java/io/File::renameTo (java/io/File::new destination))))
+                                               (java/io/File::renameTo (java/io/File::new (ffi.as_string destination)))))
                                          )))]
   (for [@.old (as_is )
         @.jvm (as_is )
diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux
index a4c5cfa57..c26923c54 100644
--- a/stdlib/source/library/lux/world/file/watch.lux
+++ b/stdlib/source/library/lux/world/file/watch.lux
@@ -273,12 +273,12 @@
 
                                (def: (default_list list)
                                  (All (_ a) (-> (java/util/List a) (List a)))
-                                 (let [size (.nat (java/util/List::size list))]
+                                 (let [size (.nat (ffi.of_int (java/util/List::size list)))]
                                    (loop [idx 0
                                           output {.#End}]
                                      (if (n.< size idx)
                                        (again (++ idx)
-                                              {.#Item (java/util/List::get (.int idx) list)
+                                              {.#Item (java/util/List::get (ffi.as_int (.int idx)) list)
                                                       output})
                                        output))))
                                
@@ -366,7 +366,7 @@
                                    (async.future
                                     (java/nio/file/Path::register watcher
                                                                   watch_events'
-                                                                  (|> path java/io/File::new java/io/File::toPath)))))
+                                                                  (|> path ffi.as_string java/io/File::new java/io/File::toPath)))))
 
                                (def: (default_poll watcher)
                                  (-> java/nio/file/WatchService (IO (Try (List [Concern //.Path]))))
@@ -378,12 +378,13 @@
                                        {.#Some key}
                                        (do [! io.monad]
                                          [valid? (java/nio/file/WatchKey::reset key)]
-                                         (if valid?
+                                         (if (ffi.of_boolean valid?)
                                            (do !
                                              [.let [path (|> key
                                                              java/nio/file/WatchKey::watchable
                                                              (:as java/nio/file/Path)
                                                              java/nio/file/Path::toString
+                                                             ffi.of_string
                                                              (:as //.Path))]
                                               the_concern (..default_key_concern key)]
                                              (again {.#Item [the_concern path]
diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux
index fd5709140..9dd11a62f 100644
--- a/stdlib/source/library/lux/world/net/http/client.lux
+++ b/stdlib/source/library/lux/world/net/http/client.lux
@@ -133,7 +133,8 @@
                                                  (loop [so_far +0]
                                                    (do [! (try.with io.monad)]
                                                      [.let [remaining (i.- so_far (.int buffer_size))]
-                                                      bytes_read (java/io/BufferedInputStream::read buffer so_far remaining input)]
+                                                      bytes_read (# ! each (|>> ffi.of_int)
+                                                                    (java/io/BufferedInputStream::read buffer (ffi.as_int so_far) (ffi.as_int remaining) input))]
                                                      (case bytes_read
                                                        -1 (do !
                                                             [_ (java/lang/AutoCloseable::close input)]
@@ -146,7 +147,8 @@
                                                         output (# binary.monoid identity)]
                                                    (do [! (try.with io.monad)]
                                                      [.let [remaining (i.- so_far (.int buffer_size))]
-                                                      bytes_read (java/io/BufferedInputStream::read buffer so_far remaining input)]
+                                                      bytes_read (# ! each (|>> ffi.of_int)
+                                                                    (java/io/BufferedInputStream::read buffer (ffi.as_int so_far) (ffi.as_int remaining) input))]
                                                      (case bytes_read
                                                        -1 (do !
                                                             [_ (java/lang/AutoCloseable::close input)]
@@ -170,13 +172,13 @@
                                  (loop [index +0
                                         headers //.empty]
                                    (do [! (try.with io.monad)]
-                                     [?name (java/net/URLConnection::getHeaderFieldKey index connection)]
+                                     [?name (java/net/URLConnection::getHeaderFieldKey (ffi.as_int index) connection)]
                                      (case ?name
                                        {.#Some name}
                                        (do !
-                                         [?value (java/net/URLConnection::getHeaderField index connection)]
+                                         [?value (java/net/URLConnection::getHeaderField (ffi.as_int index) connection)]
                                          (again (++ index)
-                                                (dictionary.has name (maybe.else "" ?value) headers)))
+                                                (dictionary.has (ffi.of_string name) (maybe.else "" (maybe#each (|>> ffi.of_string) ?value)) headers)))
 
                                        {.#None}
                                        (in headers)))))
@@ -187,11 +189,11 @@
                                  (def: (request method url headers data)
                                    (: (IO (Try (//.Response IO)))
                                       (do [! (try.with io.monad)]
-                                        [connection (|> url java/net/URL::new java/net/URL::openConnection)
+                                        [connection (|> url ffi.as_string java/net/URL::new java/net/URL::openConnection)
                                          .let [connection (:as java/net/HttpURLConnection connection)]
-                                         _ (java/net/HttpURLConnection::setRequestMethod (..jvm_method method) connection)
+                                         _ (java/net/HttpURLConnection::setRequestMethod (ffi.as_string (..jvm_method method)) connection)
                                          _ (monad.each ! (function (_ [name value])
-                                                           (java/net/URLConnection::setRequestProperty name value connection))
+                                                           (java/net/URLConnection::setRequestProperty (ffi.as_string name) (ffi.as_string value) connection))
                                                        (dictionary.entries headers))
                                          _ (case data
                                              {.#Some data}
@@ -210,7 +212,7 @@
                                          input (|> connection
                                                    java/net/URLConnection::getInputStream
                                                    (# ! each (|>> java/io/BufferedInputStream::new)))]
-                                        (in [(.nat status)
+                                        (in [(.nat (ffi.of_int status))
                                              [//.#headers headers
                                               //.#body (..default_body input)]]))))))]
   (for [@.old (as_is )
diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux
index 5fdc9cc21..2eb9e3f62 100644
--- a/stdlib/source/library/lux/world/program.lux
+++ b/stdlib/source/library/lux/world/program.lux
@@ -1,39 +1,39 @@
 (.using
-  [library
-   [lux "*"
-    ["@" target]
-    ["[0]" ffi {"+" import:}]
-    [abstract
-     ["[0]" monad {"+" Monad do}]]
-    [control
-     ["[0]" function]
-     ["[0]" io {"+" IO}]
-     ["[0]" maybe]
-     ["[0]" try {"+" Try}]
-     ["[0]" exception {"+" exception:}]
-     [concurrency
-      ["[0]" atom]
-      ["[0]" async {"+" Async}]]
-     [parser
-      ["[0]" environment {"+" Environment}]]]
-    [data
-     ["[0]" bit ("[1]#[0]" equivalence)]
-     ["[0]" text
-      ["%" format {"+" format}]]
-     [collection
-      ["[0]" array {"+" Array}]
-      ["[0]" dictionary {"+" Dictionary}]
-      ["[0]" list ("[1]#[0]" functor)]]]
-    ["[0]" macro
-     ["[0]" template]]
-    [math
-     [number
-      ["i" int]]]
-    [type
-     abstract]]]
-  [//
-   [file {"+" Path}]
-   [shell {"+" Exit}]])
+ [library
+  [lux "*"
+   ["@" target]
+   ["[0]" ffi {"+" import:}]
+   [abstract
+    ["[0]" monad {"+" Monad do}]]
+   [control
+    ["[0]" function]
+    ["[0]" io {"+" IO}]
+    ["[0]" maybe ("[1]#[0]" functor)]
+    ["[0]" try {"+" Try}]
+    ["[0]" exception {"+" exception:}]
+    [concurrency
+     ["[0]" atom]
+     ["[0]" async {"+" Async}]]
+    [parser
+     ["[0]" environment {"+" Environment}]]]
+   [data
+    ["[0]" bit ("[1]#[0]" equivalence)]
+    ["[0]" text
+     ["%" format {"+" format}]]
+    [collection
+     ["[0]" array {"+" Array}]
+     ["[0]" dictionary {"+" Dictionary}]
+     ["[0]" list ("[1]#[0]" functor)]]]
+   ["[0]" macro
+    ["[0]" template]]
+   [math
+    [number
+     ["i" int]]]
+   [type
+    abstract]]]
+ [//
+  [file {"+" Path}]
+  [shell {"+" Exit}]])
 
 (exception: .public (unknown_environment_variable [name Text])
   (exception.report
@@ -136,7 +136,7 @@
 
                                (def: (jvm##consume iterator)
                                  (All (_ a) (-> (java/util/Iterator a) (List a)))
-                                 (if (java/util/Iterator::hasNext iterator)
+                                 (if (ffi.of_boolean (java/util/Iterator::hasNext iterator))
                                    {.#Item (java/util/Iterator::next iterator)
                                            (jvm##consume iterator)}
                                    {.#End}))
@@ -347,16 +347,16 @@
             ])))
 
   (def: (variable name)
-    (template.let [(!fetch )
+    (template.let [(!fetch  )
                    [(do io.monad
-                      [value ( name)]
+                      [value (|> name )]
                       (in (case value
                             {.#Some value}
-                            {try.#Success value}
+                            {try.#Success ( value)}
 
                             {.#None}
                             (exception.except ..unknown_environment_variable [name]))))]]
-      (with_expansions [ (!fetch java/lang/System::resolveEnv)]
+      (with_expansions [ (!fetch (<| java/lang/System::resolveEnv ffi.as_string) ffi.of_string)]
         (for [@.old 
               @.jvm 
               @.js (io.io (if ffi.on_node_js?
@@ -370,15 +370,18 @@
                               {.#None}
                               (exception.except ..unknown_environment_variable [name]))
                             (exception.except ..unknown_environment_variable [name])))
-              @.python (!fetch os/environ::get)
-              @.lua (!fetch os/getenv)
-              @.ruby (!fetch RubyEnv::fetch)
+              @.python (!fetch os/environ::get |>)
+              @.lua (!fetch os/getenv |>)
+              @.ruby (!fetch RubyEnv::fetch |>)
               ]))))
   
   (def: home
     (io.run!
      (with_expansions [ (io.io "~")
-                        (io.io (maybe.else "" (java/lang/System::getProperty "user.home")))]
+                        (|> (java/lang/System::getProperty (ffi.as_string "user.home"))
+                                 (maybe#each (|>> ffi.of_string))
+                                 (maybe.else "")
+                                 io.io)]
        (for [@.old 
              @.jvm 
              @.js (if ffi.on_node_js?
@@ -401,7 +404,10 @@
   (def: directory
     (io.run!
      (with_expansions [ "."
-                        (io.io (maybe.else "" (java/lang/System::getProperty "user.dir")))]
+                        (|> (java/lang/System::getProperty (ffi.as_string "user.dir"))
+                                 (maybe#each (|>> ffi.of_string))
+                                 (maybe.else "")
+                                 io.io)]
        (for [@.old 
              @.jvm 
              @.js (if ffi.on_node_js?
@@ -431,7 +437,7 @@
   
   (def: (exit code)
     (with_expansions [ (do io.monad
-                              [_ (java/lang/System::exit code)]
+                              [_ (java/lang/System::exit (ffi.as_int code))]
                               (in (undefined)))]
       (for [@.old 
             @.jvm 
diff --git a/stdlib/source/library/lux/world/shell.lux b/stdlib/source/library/lux/world/shell.lux
index cba2e4d7e..22f63e05b 100644
--- a/stdlib/source/library/lux/world/shell.lux
+++ b/stdlib/source/library/lux/world/shell.lux
@@ -1,37 +1,37 @@
 (.using
-  [library
-   [lux "*"
-    ["@" target]
-    ["jvm" ffi {"+" import:}]
-    [abstract
-     [monad {"+" do}]]
-    [control
-     ["[0]" function]
-     ["[0]" try {"+" Try}]
-     ["[0]" exception {"+" exception:}]
-     ["[0]" io {"+" IO}]
-     [security
-      ["?" policy {"+" Context Safety Safe}]]
-     [concurrency
-      ["[0]" atom {"+" Atom}]
-      ["[0]" async {"+" Async}]]
-     [parser
-      [environment {"+" Environment}]]]
-    [data
-     ["[0]" product]
-     ["[0]" text
-      ["%" format {"+" format}]
-      [encoding
-       ["[0]" utf8]]]
-     [collection
-      ["[0]" array {"+" Array}]
-      ["[0]" list ("[1]#[0]" mix functor)]
-      ["[0]" dictionary]]]
-    [math
-     [number {"+" hex}
-      ["n" nat]]]]]
-  [//
-   [file {"+" Path}]])
+ [library
+  [lux "*"
+   ["@" target]
+   ["[0]" ffi {"+" import:}]
+   [abstract
+    [monad {"+" do}]]
+   [control
+    ["[0]" function]
+    ["[0]" try {"+" Try}]
+    ["[0]" exception {"+" exception:}]
+    ["[0]" io {"+" IO}]
+    [security
+     ["?" policy {"+" Context Safety Safe}]]
+    [concurrency
+     ["[0]" atom {"+" Atom}]
+     ["[0]" async {"+" Async}]]
+    [parser
+     [environment {"+" Environment}]]]
+   [data
+    ["[0]" product]
+    ["[0]" text
+     ["%" format {"+" format}]
+     [encoding
+      ["[0]" utf8]]]
+    [collection
+     ["[0]" array {"+" Array}]
+     ["[0]" list ("[1]#[0]" mix functor)]
+     ["[0]" dictionary]]]
+   [math
+    [number {"+" hex}
+     ["n" nat]]]]]
+ [//
+  [file {"+" Path}]])
 
 (type: .public Exit
   Int)
@@ -178,10 +178,10 @@
                                  (-> (List Argument) (Array java/lang/String))
                                  (product.right
                                   (list#mix (function (_ argument [idx output])
-                                              [(++ idx) (jvm.write! idx
-                                                                    (:as java/lang/String argument)
+                                              [(++ idx) (ffi.write! idx
+                                                                    (ffi.as_string argument)
                                                                     output)])
-                                            [0 (jvm.array java/lang/String (list.size arguments))]
+                                            [0 (ffi.array java/lang/String (list.size arguments))]
                                             arguments)))
 
                                (import: (java/util/Map k v)
@@ -250,7 +250,7 @@
                                                           [output (java/io/BufferedReader::readLine )]
                                                           (case output
                                                             {.#Some output}
-                                                            (in output)
+                                                            (in (ffi.of_string output))
 
                                                             {.#None}
                                                             (# io.monad in (exception.except ..no_more_output [])))))]
@@ -262,10 +262,10 @@
                                                  (java/io/OutputStream::write (# utf8.codec encoded message) jvm_output))
                                                (~~ (template [ ]
                                                      [(def: ( _)
-                                                        ( process))]
+                                                        (|> process ))]
 
                                                      [destroy java/lang/Process::destroy]
-                                                     [await java/lang/Process::waitFor]
+                                                     [await (<| (# ! each (|>> ffi.of_int)) java/lang/Process::waitFor)]
                                                      ))))))))
 
                                (import: java/io/File
@@ -287,8 +287,8 @@
                                (def: windows?
                                  (IO (Try Bit))
                                  (# (try.with io.monad) each
-                                    (|>> java/lang/String::toLowerCase (text.starts_with? "windows"))
-                                    (java/lang/System::getProperty "os.name")))
+                                    (|>> java/lang/String::toLowerCase ffi.of_string (text.starts_with? "windows"))
+                                    (java/lang/System::getProperty (ffi.as_string "os.name"))))
 
                                (implementation: .public default
                                  (Shell IO)
@@ -298,7 +298,7 @@
                                      [.let [builder (|> (list& the_command arguments)
                                                         ..jvm::arguments_array
                                                         java/lang/ProcessBuilder::new
-                                                        (java/lang/ProcessBuilder::directory (java/io/File::new working_directory)))]
+                                                        (java/lang/ProcessBuilder::directory (java/io/File::new (ffi.as_string working_directory))))]
                                       _ (|> builder
                                             java/lang/ProcessBuilder::environment
                                             (# try.functor each (..jvm::load_environment environment))
-- 
cgit v1.2.3