diff options
Diffstat (limited to '')
44 files changed, 2331 insertions, 2206 deletions
| diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index 1c550ec22..0b45af385 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -706,6 +706,41 @@      {#Left msg})))   #0) +("lux def" text#composite + ("lux type check" +  {#Function Text {#Function Text Text}} +  ([_ x] +   ([_ y] +    ("lux text concat" x y)))) + #0) + +("lux def" symbol_separator + ("lux type check" +  Text +  ".") + #0) + +("lux def" symbol#encoded + ("lux type check" +  {#Function Symbol Text} +  ([_ full_name] +   ({[module name] +     ({"" name +       _  (text#composite module (text#composite ..symbol_separator name))} +      module)} +    full_name))) + #0) + +... TODO: Allow asking the compiler for the name of the definition +... currently being defined. That name can then be fed into +... 'wrong_syntax_error' for easier maintenance of the error_messages. +("lux def" wrong_syntax_error + ("lux type check" +  {#Function Symbol Text} +  ([_ it] +   (text#composite "Wrong syntax for " (symbol#encoded it)))) + #0) +  ("lux def" let''   ("lux macro"    ([_ tokens] @@ -769,11 +804,15 @@  ("lux def" as_function   ("lux type check" {#Function Code {#Function {#Apply Code List} {#Function Code Code}}} -  (function'' [self inputs output] -              (form$ {#Item (symbol$ [..prelude_module "function''"]) -                            {#Item self -                                   {#Item (tuple$ inputs) -                                          {#Item output {#End}}}}}))) +  (function'' as_function [self inputs output] +              ({{#End} +                output + +                {#Item head tail} +                (_ann {#Form {#Item (_ann {#Tuple {#Item self {#Item head {#End}}}}) +                                    {#Item (as_function (_ann {#Symbol ["" ""]}) tail output) +                                           {#End}}}})} +               inputs)))   #0)  ("lux def" as_macro @@ -801,40 +840,43 @@                                   {#End}]})                  _ -                (failure "Wrong syntax for def''")} +                (failure "Wrong syntax for def:''")}                 tokens)))   #0) -("lux def" macro:' +("lux def" macro   ("lux macro"    (function'' [tokens] -              ({{#Item export_policy {#Item [_ {#Form {#Item name args}}] {#Item body {#End}}}} -                (meta#in {#Item (as_def name (as_macro (as_function name args body)) -                                        export_policy) +              ({{#Item [_ {#Form {#Item name {#Item head tail}}}] {#Item body {#End}}} +                (meta#in {#Item (as_macro (as_function name {#Item head tail} body))                                  {#End}})                  _ -                (failure "Wrong syntax for macro:'")} +                (failure (wrong_syntax_error [..prelude_module "macro"]))}                 tokens))) - #0) + #1) -(macro:' .public (comment tokens) -         (meta#in {#End})) +(def:'' .public comment +        Macro +        (macro (_ tokens) +          (meta#in {#End}))) -(macro:' .private ($' tokens) -         ({{#Item x {#End}} -           (meta#in tokens) +(def:'' .private $' +        Macro +        (macro (_ tokens) +          ({{#Item x {#End}} +            (meta#in tokens) -           {#Item x {#Item y xs}} -           (meta#in {#Item (form$ {#Item (symbol$ [..prelude_module "$'"]) -                                         {#Item (variant$ {#Item (symbol$ [..prelude_module "#Apply"]) -                                                                 {#Item y {#Item x {#End}}}}) -                                                xs}}) -                           {#End}}) +            {#Item x {#Item y xs}} +            (meta#in {#Item (form$ {#Item (symbol$ [..prelude_module "$'"]) +                                          {#Item (variant$ {#Item (symbol$ [..prelude_module "#Apply"]) +                                                                  {#Item y {#Item x {#End}}}}) +                                                 xs}}) +                            {#End}}) -           _ -           (failure "Wrong syntax for $'")} -          tokens)) +            _ +            (failure "Wrong syntax for $'")} +           tokens)))  (def:'' .private (list#mix f init xs)          ... (All (_ a b) (-> (-> b a a) a (List b) a)) @@ -1085,165 +1127,183 @@                      scopes)}           lux)) -(macro:' .public (All tokens lux) -         ({{#Item [_ {#Form {#Item self_name args}}] -                  {#Item body {#End}}} -           {#Right [lux -                    {#Item ({raw -                             ({[#1] raw -                               [#0] (..quantified raw)} -                              (initialized_quantification? lux))} -                            ({{#End} -                              body - -                              {#Item head tail} -                              (with_correct_quantification -                                (let$ self_name (quantified_type_parameter 0) -                                      ({[_ raw] -                                        raw} -                                       (list#mix (function'' [parameter offset,body'] -                                                             ({[offset body'] -                                                               [("lux i64 +" 2 offset) -                                                                (let$ parameter (quantified_type_parameter ("lux i64 +" offset 1)) -                                                                      (UnivQ$ body'))]} -                                                              offset,body')) -                                                 [0 (with_quantification (list#size args) -                                                      body)] -                                                 args))))} -                             args)) -                           {#End}}]} -            -           _ -           {#Left "Wrong syntax for All"}} -          tokens)) - -(macro:' .public (Ex tokens lux) -         ({{#Item [_ {#Form {#Item self_name args}}] -                  {#Item body {#End}}} -           {#Right [lux -                    {#Item ({raw -                             ({[#1] raw -                               [#0] (..quantified raw)} -                              (initialized_quantification? lux))} -                            ({{#End} -                              body - -                              {#Item head tail} -                              (with_correct_quantification -                                (let$ self_name (quantified_type_parameter 0) -                                      ({[_ raw] -                                        raw} -                                       (list#mix (function'' [parameter offset,body'] -                                                             ({[offset body'] -                                                               [("lux i64 +" 2 offset) -                                                                (let$ parameter (quantified_type_parameter ("lux i64 +" offset 1)) -                                                                      (ExQ$ body'))]} -                                                              offset,body')) -                                                 [0 (with_quantification (list#size args) -                                                      body)] -                                                 args))))} -                             args)) -                           {#End}}]} -            -           _ -           {#Left "Wrong syntax for Ex"}} -          tokens)) - -(macro:' .public (-> tokens) -         ({{#Item output inputs} -           (meta#in {#Item (list#mix ("lux type check" {#Function Code {#Function Code Code}} -                                      (function'' [i o] (variant$ {#Item (symbol$ [..prelude_module "#Function"]) {#Item i {#Item o {#End}}}}))) -                                     output -                                     inputs) -                           {#End}}) -            -           _ -           (failure "Wrong syntax for ->")} -          (list#reversed tokens))) - -(macro:' .public (list xs) -         (meta#in {#Item (list#mix |#Item| |#End| (list#reversed xs)) -                         {#End}})) - -(macro:' .public (partial_list xs) -         ({{#Item last init} -           (meta#in (list (list#mix |#Item| last init))) - -           _ -           (failure "Wrong syntax for partial_list")} -          (list#reversed xs))) - -(macro:' .public (Union tokens) -         ({{#End} -           (meta#in (list (symbol$ [..prelude_module "Nothing"]))) - -           {#Item last prevs} -           (meta#in (list (list#mix (function'' [left right] (variant$ (list (symbol$ [..prelude_module "#Sum"]) left right))) -                                    last -                                    prevs)))} -          (list#reversed tokens))) +(def:'' .public All +        Macro +        (macro (_ tokens lux) +          ({{#Item [_ {#Form {#Item self_name args}}] +                   {#Item body {#End}}} +            {#Right [lux +                     {#Item ({raw +                              ({[#1] raw +                                [#0] (..quantified raw)} +                               (initialized_quantification? lux))} +                             ({{#End} +                               body + +                               {#Item head tail} +                               (with_correct_quantification +                                 (let$ self_name (quantified_type_parameter 0) +                                       ({[_ raw] +                                         raw} +                                        (list#mix (function'' [parameter offset,body'] +                                                              ({[offset body'] +                                                                [("lux i64 +" 2 offset) +                                                                 (let$ parameter (quantified_type_parameter ("lux i64 +" offset 1)) +                                                                       (UnivQ$ body'))]} +                                                               offset,body')) +                                                  [0 (with_quantification (list#size args) +                                                       body)] +                                                  args))))} +                              args)) +                            {#End}}]} +             +            _ +            {#Left "Wrong syntax for All"}} +           tokens))) + +(def:'' .public Ex +        Macro +        (macro (_ tokens lux) +          ({{#Item [_ {#Form {#Item self_name args}}] +                   {#Item body {#End}}} +            {#Right [lux +                     {#Item ({raw +                              ({[#1] raw +                                [#0] (..quantified raw)} +                               (initialized_quantification? lux))} +                             ({{#End} +                               body + +                               {#Item head tail} +                               (with_correct_quantification +                                 (let$ self_name (quantified_type_parameter 0) +                                       ({[_ raw] +                                         raw} +                                        (list#mix (function'' [parameter offset,body'] +                                                              ({[offset body'] +                                                                [("lux i64 +" 2 offset) +                                                                 (let$ parameter (quantified_type_parameter ("lux i64 +" offset 1)) +                                                                       (ExQ$ body'))]} +                                                               offset,body')) +                                                  [0 (with_quantification (list#size args) +                                                       body)] +                                                  args))))} +                              args)) +                            {#End}}]} +             +            _ +            {#Left "Wrong syntax for Ex"}} +           tokens))) + +(def:'' .public -> +        Macro +        (macro (_ tokens) +          ({{#Item output inputs} +            (meta#in {#Item (list#mix ("lux type check" {#Function Code {#Function Code Code}} +                                       (function'' [i o] (variant$ {#Item (symbol$ [..prelude_module "#Function"]) {#Item i {#Item o {#End}}}}))) +                                      output +                                      inputs) +                            {#End}}) +             +            _ +            (failure "Wrong syntax for ->")} +           (list#reversed tokens)))) -(macro:' .public (Tuple tokens) -         ({{#End} -           (meta#in (list (symbol$ [..prelude_module "Any"]))) +(def:'' .public list +        Macro +        (macro (_ xs) +          (meta#in {#Item (list#mix |#Item| |#End| (list#reversed xs)) +                          {#End}}))) -           {#Item last prevs} -           (meta#in (list (list#mix (function'' [left right] (variant$ (list (symbol$ [..prelude_module "#Product"]) left right))) -                                    last -                                    prevs)))} -          (list#reversed tokens))) +(def:'' .public partial_list +        Macro +        (macro (_ xs) +          ({{#Item last init} +            (meta#in (list (list#mix |#Item| last init))) -(macro:' .private (function' tokens) -         (let'' [name tokens'] ({{#Item [[_ {#Symbol ["" name]}] tokens']} -                                 [name tokens'] +            _ +            (failure "Wrong syntax for partial_list")} +           (list#reversed xs)))) + +(def:'' .public Union +        Macro +        (macro (_ tokens) +          ({{#End} +            (meta#in (list (symbol$ [..prelude_module "Nothing"]))) + +            {#Item last prevs} +            (meta#in (list (list#mix (function'' [left right] (variant$ (list (symbol$ [..prelude_module "#Sum"]) left right))) +                                     last +                                     prevs)))} +           (list#reversed tokens)))) + +(def:'' .public Tuple +        Macro +        (macro (_ tokens) +          ({{#End} +            (meta#in (list (symbol$ [..prelude_module "Any"]))) + +            {#Item last prevs} +            (meta#in (list (list#mix (function'' [left right] (variant$ (list (symbol$ [..prelude_module "#Product"]) left right))) +                                     last +                                     prevs)))} +           (list#reversed tokens)))) + +(def:'' .private function' +        Macro +        (macro (_ tokens) +          (let'' [name tokens'] ({{#Item [[_ {#Symbol ["" name]}] tokens']} +                                  [name tokens'] -                                 _ -                                 ["" tokens]} -                                tokens) -                ({{#Item [[_ {#Tuple args}] {#Item [body {#End}]}]} -                  ({{#End} -                    (failure "function' requires a non-empty arguments tuple.") -                     -                    {#Item [harg targs]} -                    (meta#in (list (form$ (list (tuple$ (list (local$ name) -                                                              harg)) -                                                (list#mix (function'' [arg body'] -                                                                      (form$ (list (tuple$ (list (local$ "") -                                                                                                 arg)) -                                                                                   body'))) -                                                          body -                                                          (list#reversed targs))))))} -                   args) +                                  _ +                                  ["" tokens]} +                                 tokens) +                 ({{#Item [[_ {#Tuple args}] {#Item [body {#End}]}]} +                   ({{#End} +                     (failure "function' requires a non-empty arguments tuple.") +                      +                     {#Item [harg targs]} +                     (meta#in (list (form$ (list (tuple$ (list (local$ name) +                                                               harg)) +                                                 (list#mix (function'' [arg body'] +                                                                       (form$ (list (tuple$ (list (local$ "") +                                                                                                  arg)) +                                                                                    body'))) +                                                           body +                                                           (list#reversed targs))))))} +                    args) -                  _ -                  (failure "Wrong syntax for function'")} -                 tokens'))) - -(macro:' .private (def:''' tokens) -         ({{#Item [export_policy -                   {#Item [[_ {#Form {#Item [name args]}}] -                           {#Item [type {#Item [body {#End}]}]}]}]} -           (meta#in (list (form$ (list (text$ "lux def") -                                       name -                                       (form$ (list (text$ "lux type check") -                                                    type -                                                    (form$ (list (symbol$ [..prelude_module "function'"]) -                                                                 name -                                                                 (tuple$ args) -                                                                 body)))) -                                       export_policy)))) - -           {#Item [export_policy {#Item [name {#Item [type {#Item [body {#End}]}]}]}]} -           (meta#in (list (form$ (list (text$ "lux def") -                                       name -                                       (form$ (list (text$ "lux type check") -                                                    type -                                                    body)) -                                       export_policy)))) +                   _ +                   (failure "Wrong syntax for function'")} +                  tokens')))) + +(def:'' .private def:''' +        Macro +        (macro (_ tokens) +          ({{#Item [export_policy +                    {#Item [[_ {#Form {#Item [name args]}}] +                            {#Item [type {#Item [body {#End}]}]}]}]} +            (meta#in (list (form$ (list (text$ "lux def") +                                        name +                                        (form$ (list (text$ "lux type check") +                                                     type +                                                     (form$ (list (symbol$ [..prelude_module "function'"]) +                                                                  name +                                                                  (tuple$ args) +                                                                  body)))) +                                        export_policy)))) + +            {#Item [export_policy {#Item [name {#Item [type {#Item [body {#End}]}]}]}]} +            (meta#in (list (form$ (list (text$ "lux def") +                                        name +                                        (form$ (list (text$ "lux type check") +                                                     type +                                                     body)) +                                        export_policy)))) -           _ -           (failure "Wrong syntax for def:'''")} -          tokens)) +            _ +            (failure "Wrong syntax for def:'''")} +           tokens)))  (def:''' .public Or           Macro @@ -1270,25 +1330,27 @@             {#None}}            xs)) -(macro:' .private (let' tokens) -         ({{#Item [_ {#Tuple bindings}] {#Item body {#End}}} -           ({{#Some bindings} -             (meta#in (list (list#mix ("lux type check" (-> (Tuple Code Code) Code -                                                            Code) -                                       (function' [binding body] -                                                  ({[label value] -                                                    (form$ (list (variant$ (list label body)) value))} -                                                   binding))) -                                      body -                                      (list#reversed bindings)))) -              -             {#None} -             (failure "Wrong syntax for let'")} -            (pairs bindings)) +(def:'' .private let' +        Macro +        (macro (_ tokens) +          ({{#Item [_ {#Tuple bindings}] {#Item body {#End}}} +            ({{#Some bindings} +              (meta#in (list (list#mix ("lux type check" (-> (Tuple Code Code) Code +                                                             Code) +                                        (function' [binding body] +                                                   ({[label value] +                                                     (form$ (list (variant$ (list label body)) value))} +                                                    binding))) +                                       body +                                       (list#reversed bindings)))) +               +              {#None} +              (failure "Wrong syntax for let'")} +             (pairs bindings)) -           _ -           (failure "Wrong syntax for let'")} -          tokens)) +            _ +            (failure "Wrong syntax for let'")} +           tokens)))  (def:''' .private (any? p xs)           (All (_ a) @@ -1337,31 +1399,35 @@           (function' [right left]                      (func left right))) -(macro:' .public (left tokens) -         ({{#Item op tokens'} -           ({{#Item first nexts} -             (meta#in (list (list#mix (function#flipped (right_associativity op)) first nexts))) - -             _ -             (failure "Wrong syntax for left")} -            tokens') -            -           _ -           (failure "Wrong syntax for left")} -          tokens)) - -(macro:' .public (right tokens) -         ({{#Item op tokens'} -           ({{#Item last prevs} -             (meta#in (list (list#mix (right_associativity op) last prevs))) +(def:'' .public left +        Macro +        (macro (_ tokens) +          ({{#Item op tokens'} +            ({{#Item first nexts} +              (meta#in (list (list#mix (function#flipped (right_associativity op)) first nexts))) -             _ -             (failure "Wrong syntax for right")} -            (list#reversed tokens')) -            -           _ -           (failure "Wrong syntax for right")} -          tokens)) +              _ +              (failure "Wrong syntax for left")} +             tokens') +             +            _ +            (failure "Wrong syntax for left")} +           tokens))) + +(def:'' .public right +        Macro +        (macro (_ tokens) +          ({{#Item op tokens'} +            ({{#Item last prevs} +              (meta#in (list (list#mix (right_associativity op) last prevs))) + +              _ +              (failure "Wrong syntax for right")} +             (list#reversed tokens')) +             +            _ +            (failure "Wrong syntax for right")} +           tokens)))  (def:''' .public all Macro ..right) @@ -1411,43 +1477,45 @@                                    (f a state')}                                   (ma state))))]) -(macro:' .private (do tokens) -         ({{#Item monad {#Item [_ {#Tuple bindings}] {#Item body {#End}}}} -           ({{#Some bindings} -             (let' [g!in (local$ "in") -                    g!then (local$ " then ") -                    body' (list#mix ("lux type check" (-> (Tuple Code Code) Code Code) -                                     (function' [binding body'] -                                                (let' [[var value] binding] -                                                      ({[_ {#Symbol [module short]}] -                                                        ({"" -                                                          (form$ (list g!then -                                                                       (form$ (list (tuple$ (list (local$ "") var)) body')) -                                                                       value)) - -                                                          _ -                                                          (form$ (list var value body'))} -                                                         module) -                                                         - -                                                        _ -                                                        (form$ (list g!then -                                                                     (form$ (list (tuple$ (list (local$ "") var)) body')) -                                                                     value))} -                                                       var)))) -                                    body -                                    (list#reversed bindings))] -                   (meta#in (list (form$ (list (variant$ (list (tuple$ (list g!in g!then)) -                                                               body')) -                                               monad))))) -              -             {#None} -             (failure "Wrong syntax for do")} -            (pairs bindings)) +(def:'' .private do +        Macro +        (macro (_ tokens) +          ({{#Item monad {#Item [_ {#Tuple bindings}] {#Item body {#End}}}} +            ({{#Some bindings} +              (let' [g!in (local$ "in") +                     g!then (local$ " then ") +                     body' (list#mix ("lux type check" (-> (Tuple Code Code) Code Code) +                                      (function' [binding body'] +                                                 (let' [[var value] binding] +                                                       ({[_ {#Symbol [module short]}] +                                                         ({"" +                                                           (form$ (list g!then +                                                                        (form$ (list (tuple$ (list (local$ "") var)) body')) +                                                                        value)) + +                                                           _ +                                                           (form$ (list var value body'))} +                                                          module) +                                                          + +                                                         _ +                                                         (form$ (list g!then +                                                                      (form$ (list (tuple$ (list (local$ "") var)) body')) +                                                                      value))} +                                                        var)))) +                                     body +                                     (list#reversed bindings))] +                    (meta#in (list (form$ (list (variant$ (list (tuple$ (list g!in g!then)) +                                                                body')) +                                                monad))))) +               +              {#None} +              (failure "Wrong syntax for do")} +             (pairs bindings)) -           _ -           (failure "Wrong syntax for do")} -          tokens)) +            _ +            (failure "Wrong syntax for do")} +           tokens)))  (def:''' .private (monad#each m f xs)           (All (_ m a b) @@ -1483,15 +1551,17 @@                     (monad#mix m f y' xs'))}                  xs))) -(macro:' .public (if tokens) -         ({{#Item test {#Item then {#Item else {#End}}}} -           (meta#in (list (form$ (list (variant$ (list (bit$ #1)  then -                                                       (bit$ #0) else)) -                                       test)))) +(def:'' .public if +        Macro +        (macro (_ tokens) +          ({{#Item test {#Item then {#Item else {#End}}}} +            (meta#in (list (form$ (list (variant$ (list (bit$ #1)  then +                                                        (bit$ #0) else)) +                                        test)))) -           _ -           (failure "Wrong syntax for if")} -          tokens)) +            _ +            (failure "Wrong syntax for if")} +           tokens)))  (def:''' .private PList           Type @@ -1521,21 +1591,6 @@             (list [k v])}            plist)) -(def:''' .private (text#composite x y) -         (-> Text Text Text) -         ("lux text concat" x y)) - -(def:''' .private symbol_separator -         Text -         ".") - -(def:''' .private (symbol#encoded full_name) -         (-> Symbol Text) -         (let' [[module name] full_name] -               ({"" name -                 _  (all text#composite module ..symbol_separator name)} -                module))) -  (def:''' .private (global_symbol full_name state)           (-> Symbol ($' Meta Symbol))           (let' [[module name] full_name @@ -1680,16 +1735,18 @@               (in [meta output']))}            [replace? token])) -(macro:' .public (Primitive tokens) -         ({{#Item [_ {#Text class_name}] {#End}} -           (meta#in (list (variant$ (list (symbol$ [..prelude_module "#Primitive"]) (text$ class_name) |#End|)))) +(def:'' .public Primitive +        Macro +        (macro (_ tokens) +          ({{#Item [_ {#Text class_name}] {#End}} +            (meta#in (list (variant$ (list (symbol$ [..prelude_module "#Primitive"]) (text$ class_name) |#End|)))) -           {#Item [_ {#Text class_name}] {#Item [_ {#Tuple params}] {#End}}} -           (meta#in (list (variant$ (list (symbol$ [..prelude_module "#Primitive"]) (text$ class_name) (untemplated_list params))))) +            {#Item [_ {#Text class_name}] {#Item [_ {#Tuple params}] {#End}}} +            (meta#in (list (variant$ (list (symbol$ [..prelude_module "#Primitive"]) (text$ class_name) (untemplated_list params))))) -           _ -           (failure "Wrong syntax for Primitive")} -          tokens)) +            _ +            (failure "Wrong syntax for Primitive")} +           tokens)))  (def:'' .private (current_module_name state)          ($' Meta Text) @@ -1705,84 +1762,94 @@             current_module)}           state)) -(macro:' .public (` tokens) -         ({{#Item template {#End}} -           (do meta_monad -             [current_module current_module_name -              =template (untemplated #1 current_module template)] -             (in (list (form$ (list (text$ "lux type check") -                                    (symbol$ [..prelude_module "Code"]) -                                    =template))))) - -           _ -           (failure "Wrong syntax for `")} -          tokens)) - -(macro:' .public (`' tokens) -         ({{#Item template {#End}} -           (do meta_monad -             [=template (untemplated #1 "" template)] -             (in (list (form$ (list (text$ "lux type check") (symbol$ [..prelude_module "Code"]) =template))))) - -           _ -           (failure "Wrong syntax for `")} -          tokens)) - -(macro:' .public (' tokens) -         ({{#Item template {#End}} -           (do meta_monad -             [=template (untemplated #0 "" template)] -             (in (list (form$ (list (text$ "lux type check") (symbol$ [..prelude_module "Code"]) =template))))) - -           _ -           (failure "Wrong syntax for '")} -          tokens)) - -(macro:' .public (|> tokens) -         ({{#Item [init apps]} -           (meta#in (list (list#mix ("lux type check" (-> Code Code Code) -                                     (function' [app acc] -                                                ({[_ {#Variant parts}] -                                                  (variant$ (list#composite parts (list acc))) - -                                                  [_ {#Tuple parts}] -                                                  (tuple$ (list#composite parts (list acc))) - -                                                  [_ {#Form parts}] -                                                  (form$ (list#composite parts (list acc))) +(def:'' .public ` +        Macro +        (macro (_ tokens) +          ({{#Item template {#End}} +            (do meta_monad +              [current_module current_module_name +               =template (untemplated #1 current_module template)] +              (in (list (form$ (list (text$ "lux type check") +                                     (symbol$ [..prelude_module "Code"]) +                                     =template))))) -                                                  _ -                                                  (` ((~ app) (~ acc)))} -                                                 app))) -                                    init -                                    apps))) +            _ +            (failure "Wrong syntax for `")} +           tokens))) -           _ -           (failure "Wrong syntax for |>")} -          tokens)) +(def:'' .public `' +        Macro +        (macro (_ tokens) +          ({{#Item template {#End}} +            (do meta_monad +              [=template (untemplated #1 "" template)] +              (in (list (form$ (list (text$ "lux type check") (symbol$ [..prelude_module "Code"]) =template))))) -(macro:' .public (<| tokens) -         ({{#Item [init apps]} -           (meta#in (list (list#mix ("lux type check" (-> Code Code Code) -                                     (function' [app acc] -                                                ({[_ {#Variant parts}] -                                                  (variant$ (list#composite parts (list acc))) +            _ +            (failure "Wrong syntax for `")} +           tokens))) -                                                  [_ {#Tuple parts}] -                                                  (tuple$ (list#composite parts (list acc))) +(def:'' .public ' +        Macro +        (macro (_ tokens) +          ({{#Item template {#End}} +            (do meta_monad +              [=template (untemplated #0 "" template)] +              (in (list (form$ (list (text$ "lux type check") (symbol$ [..prelude_module "Code"]) =template))))) -                                                  [_ {#Form parts}] -                                                  (form$ (list#composite parts (list acc))) +            _ +            (failure "Wrong syntax for '")} +           tokens))) + +(def:'' .public |> +        Macro +        (macro (_ tokens) +          ({{#Item [init apps]} +            (meta#in (list (list#mix ("lux type check" (-> Code Code Code) +                                      (function' [app acc] +                                                 ({[_ {#Variant parts}] +                                                   (variant$ (list#composite parts (list acc))) + +                                                   [_ {#Tuple parts}] +                                                   (tuple$ (list#composite parts (list acc))) + +                                                   [_ {#Form parts}] +                                                   (form$ (list#composite parts (list acc))) + +                                                   _ +                                                   (` ((~ app) (~ acc)))} +                                                  app))) +                                     init +                                     apps))) -                                                  _ -                                                  (` ((~ app) (~ acc)))} -                                                 app))) -                                    init -                                    apps))) +            _ +            (failure "Wrong syntax for |>")} +           tokens))) + +(def:'' .public <| +        Macro +        (macro (_ tokens) +          ({{#Item [init apps]} +            (meta#in (list (list#mix ("lux type check" (-> Code Code Code) +                                      (function' [app acc] +                                                 ({[_ {#Variant parts}] +                                                   (variant$ (list#composite parts (list acc))) + +                                                   [_ {#Tuple parts}] +                                                   (tuple$ (list#composite parts (list acc))) + +                                                   [_ {#Form parts}] +                                                   (form$ (list#composite parts (list acc))) + +                                                   _ +                                                   (` ((~ app) (~ acc)))} +                                                  app))) +                                     init +                                     apps))) -           _ -           (failure "Wrong syntax for <|")} -          (list#reversed tokens))) +            _ +            (failure "Wrong syntax for <|")} +           (list#reversed tokens))))  (def:''' .private (function#composite f g)           (All (_ a b c) @@ -1873,28 +1940,30 @@             (-> ($' List ($' List a)) ($' List a)))           (list#mix list#composite {#End} (list#reversed xs))) -(macro:' .public (template tokens) -         ({{#Item [[_ {#Tuple bindings}] {#Item [[_ {#Tuple templates}] data]}]} -           ({[{#Some bindings'} {#Some data'}] -             (let' [apply ("lux type check" (-> Replacement_Environment ($' List Code)) -                           (function' [env] (list#each (realized_template env) templates))) -                    num_bindings (list#size bindings')] -                   (if (every? (function' [size] ("lux i64 =" num_bindings size)) -                               (list#each list#size data')) -                     (|> data' -                         (list#each (function#composite apply (replacement_environment bindings'))) -                         list#conjoint -                         meta#in) -                     (failure "Irregular arguments tuples for template."))) +(def:'' .public template +        Macro +        (macro (_ tokens) +          ({{#Item [[_ {#Tuple bindings}] {#Item [[_ {#Tuple templates}] data]}]} +            ({[{#Some bindings'} {#Some data'}] +              (let' [apply ("lux type check" (-> Replacement_Environment ($' List Code)) +                            (function' [env] (list#each (realized_template env) templates))) +                     num_bindings (list#size bindings')] +                    (if (every? (function' [size] ("lux i64 =" num_bindings size)) +                                (list#each list#size data')) +                      (|> data' +                          (list#each (function#composite apply (replacement_environment bindings'))) +                          list#conjoint +                          meta#in) +                      (failure "Irregular arguments tuples for template."))) -             _ -             (failure "Wrong syntax for template")} -            [(monad#each maybe_monad symbol_short bindings) -             (monad#each maybe_monad tuple_list data)]) +              _ +              (failure "Wrong syntax for template")} +             [(monad#each maybe_monad symbol_short bindings) +              (monad#each maybe_monad tuple_list data)]) -           _ -           (failure "Wrong syntax for template")} -          tokens)) +            _ +            (failure "Wrong syntax for template")} +           tokens)))  (def:''' .private (n// param subject)           (-> Nat Nat Nat) @@ -1993,7 +2062,7 @@             #0}            type)) -(def:''' .private (macro'' modules current_module module name) +(def:''' .private (named_macro' modules current_module module name)           (-> ($' List (Tuple Text Module))               Text Text Text               ($' Maybe Macro)) @@ -2002,7 +2071,7 @@              gdef (let' [[..#module_hash _ ..#module_aliases _ ..#definitions bindings ..#imports _ ..#module_state _] ("lux type check" Module $module)]                         (plist#value name bindings))]             ({{#Alias [r_module r_name]} -             (macro'' modules current_module r_module r_name) +             (named_macro' modules current_module r_module r_name)               {#Definition [exported? def_type def_value]}               (if (macro_type? def_type) @@ -2034,7 +2103,7 @@             (meta#in name)}            name)) -(def:''' .private (macro' full_name) +(def:''' .private (named_macro full_name)           (-> Symbol ($' Meta ($' Maybe Macro)))           (do meta_monad             [current_module current_module_name] @@ -2045,14 +2114,14 @@                                 ..#seed   seed ..#expected expected                                 ..#location location ..#extensions extensions                                 ..#scope_type_vars scope_type_vars ..#eval _eval] -                              {#Right state (macro'' modules current_module module name)}} +                              {#Right state (named_macro' modules current_module module name)}}                               state)))))  (def:''' .private (macro? name)           (-> Symbol ($' Meta Bit))           (do meta_monad             [name (normal name) -            output (macro' name)] +            output (named_macro name)]             (in ({{#Some _} #1                   {#None}   #0}                  output)))) @@ -2075,7 +2144,7 @@           ({[_ {#Form {#Item [_ {#Symbol name}] args}}]             (do meta_monad               [name' (normal name) -              ?macro (macro' name')] +              ?macro (named_macro name')]               ({{#Some macro}                 (("lux type as" Macro' macro) args) @@ -2092,7 +2161,7 @@           ({[_ {#Form {#Item [_ {#Symbol name}] args}}]             (do meta_monad               [name' (normal name) -              ?macro (macro' name')] +              ?macro (named_macro name')]               ({{#Some macro}                 (do meta_monad                   [top_level_expansion (("lux type as" Macro' macro) args) @@ -2111,7 +2180,7 @@           (-> (-> Code ($' Meta ($' List Code))) Symbol ($' List Code) ($' Meta ($' List Code)))           (do meta_monad             [name' (normal name) -            ?macro (macro' name')] +            ?macro (named_macro name')]             ({{#Some macro}               (do meta_monad                 [expansion (("lux type as" Macro' macro) args) @@ -2294,44 +2363,50 @@             type}            type)) -(macro:' .public (type tokens) -         ({{#Item type {#End}} -           (do meta_monad -             [initialized_quantification? (function' [lux] {#Right [lux (initialized_quantification? lux)]})] -             (if initialized_quantification? -               (do meta_monad -                 [type+ (full_expansion #0 type)] -                 ({{#Item type' {#End}} -                   (in (list (normal_type type'))) - -                   _ -                   (failure "The expansion of the type-syntax had to yield a single element.")} -                  type+)) -               (in (list (..quantified (` (..type (~ type)))))))) +(def:'' .public type +        Macro +        (macro (_ tokens) +          ({{#Item type {#End}} +            (do meta_monad +              [initialized_quantification? (function' [lux] {#Right [lux (initialized_quantification? lux)]})] +              (if initialized_quantification? +                (do meta_monad +                  [type+ (full_expansion #0 type)] +                  ({{#Item type' {#End}} +                    (in (list (normal_type type'))) + +                    _ +                    (failure "The expansion of the type-syntax had to yield a single element.")} +                   type+)) +                (in (list (..quantified (` (..type (~ type)))))))) -           _ -           (failure "Wrong syntax for type")} -          tokens)) +            _ +            (failure "Wrong syntax for type")} +           tokens))) -(macro:' .public (is tokens) -         ({{#Item type {#Item value {#End}}} -           (meta#in (list (` ("lux type check" -                              (..type (~ type)) -                              (~ value))))) +(def:'' .public is +        Macro +        (macro (_ tokens) +          ({{#Item type {#Item value {#End}}} +            (meta#in (list (` ("lux type check" +                               (..type (~ type)) +                               (~ value))))) -           _ -           (failure "Wrong syntax for :")} -          tokens)) +            _ +            (failure "Wrong syntax for :")} +           tokens))) -(macro:' .public (as tokens) -         ({{#Item type {#Item value {#End}}} -           (meta#in (list (` ("lux type as" -                              (..type (~ type)) -                              (~ value))))) +(def:'' .public as +        Macro +        (macro (_ tokens) +          ({{#Item type {#Item value {#End}}} +            (meta#in (list (` ("lux type as" +                               (..type (~ type)) +                               (~ value))))) -           _ -           (failure "Wrong syntax for as")} -          tokens)) +            _ +            (failure "Wrong syntax for as")} +           tokens)))  (def:''' .private (empty? xs)           (All (_ a) @@ -2365,56 +2440,60 @@                     (local$ (all text#composite "__gensym__" prefix (nat#encoded seed)))}}            state)) -(macro:' .public (exec tokens) -         ({{#Item value actions} -           (let' [dummy (local$ "")] -                 (meta#in (list (list#mix ("lux type check" (-> Code Code Code) -                                           (function' [pre post] (` ({(~ dummy) (~ post)} -                                                                     (~ pre))))) -                                          value -                                          actions)))) +(def:'' .public exec +        Macro +        (macro (_ tokens) +          ({{#Item value actions} +            (let' [dummy (local$ "")] +                  (meta#in (list (list#mix ("lux type check" (-> Code Code Code) +                                            (function' [pre post] (` ({(~ dummy) (~ post)} +                                                                      (~ pre))))) +                                           value +                                           actions)))) -           _ -           (failure "Wrong syntax for exec")} -          (list#reversed tokens))) - -(macro:' .private (def:' tokens) -         (let' [parts (is (Maybe [Code Code (List Code) (Maybe Code) Code]) -                          ({{#Item export_policy {#Item [_ {#Form {#Item name args}}] {#Item type {#Item body {#End}}}}} -                            {#Some [export_policy name args {#Some type} body]} -                             -                            {#Item export_policy {#Item name {#Item type {#Item body {#End}}}}} -                            {#Some [export_policy name {#End} {#Some type} body]} -                             -                            {#Item export_policy {#Item [_ {#Form {#Item name args}}] {#Item body {#End}}}} -                            {#Some [export_policy name args {#None} body]} -                             -                            {#Item export_policy {#Item name {#Item body {#End}}}} -                            {#Some [export_policy name {#End} {#None} body]} +            _ +            (failure "Wrong syntax for exec")} +           (list#reversed tokens)))) + +(def:'' .private def:' +        Macro +        (macro (_ tokens) +          (let' [parts (is (Maybe [Code Code (List Code) (Maybe Code) Code]) +                           ({{#Item export_policy {#Item [_ {#Form {#Item name args}}] {#Item type {#Item body {#End}}}}} +                             {#Some [export_policy name args {#Some type} body]} +                              +                             {#Item export_policy {#Item name {#Item type {#Item body {#End}}}}} +                             {#Some [export_policy name {#End} {#Some type} body]} +                              +                             {#Item export_policy {#Item [_ {#Form {#Item name args}}] {#Item body {#End}}}} +                             {#Some [export_policy name args {#None} body]} +                              +                             {#Item export_policy {#Item name {#Item body {#End}}}} +                             {#Some [export_policy name {#End} {#None} body]} -                            _ -                            {#None}} -                           tokens))] -               ({{#Some [export_policy name args ?type body]} -                 (let' [body' ({{#End} -                                body - -                                _ -                                (` (function' (~ name) [(~+ args)] (~ body)))} -                               args) -                        body'' ({{#Some type} -                                 (` (is (~ type) (~ body'))) -                                  -                                 {#None} -                                 body'} -                                ?type)] -                       (meta#in (list (` ("lux def" (~ name) -                                          (~ body'') -                                          (~ export_policy)))))) -                  -                 {#None} -                 (failure "Wrong syntax for def'")} -                parts))) +                             _ +                             {#None}} +                            tokens))] +                ({{#Some [export_policy name args ?type body]} +                  (let' [body' ({{#End} +                                 body + +                                 _ +                                 (` (function' (~ name) [(~+ args)] (~ body)))} +                                args) +                         body'' ({{#Some type} +                                  (` (is (~ type) (~ body'))) +                                   +                                  {#None} +                                  body'} +                                 ?type)] +                        (meta#in (list (` ("lux def" (~ name) +                                           (~ body'') +                                           (~ export_policy)))))) +                   +                  {#None} +                  (failure "Wrong syntax for def'")} +                 parts))))  (def:' .private (expander branches)         (-> (List Code) (Meta (List Code))) @@ -2449,45 +2528,51 @@                                                                                            (list#mix text#composite ""))))}          branches)) -(macro:' .public (case tokens) -         ({{#Item value branches} -           (do meta_monad -             [expansion (expander branches)] -             (in (list (` ((~ (variant$ expansion)) (~ value)))))) +(def:'' .public case +        Macro +        (macro (_ tokens) +          ({{#Item value branches} +            (do meta_monad +              [expansion (expander branches)] +              (in (list (` ((~ (variant$ expansion)) (~ value)))))) -           _ -           (failure "Wrong syntax for case")} -          tokens)) +            _ +            (failure "Wrong syntax for case")} +           tokens))) -(macro:' .public (pattern tokens) -         (case tokens -           {#Item [_ {#Form {#Item pattern {#End}}}] {#Item body branches}} -           (do meta_monad -             [pattern+ (full_expansion #1 pattern)] -             (case pattern+ -               {#Item pattern' {#End}} -               (in (partial_list pattern' body branches)) -                -               _ -               (failure "`pattern` can only expand to 1 pattern."))) -            -           _ -           (failure "Wrong syntax for `pattern` macro"))) +(def:'' .public pattern +        Macro +        (macro (_ tokens) +          (case tokens +            {#Item [_ {#Form {#Item pattern {#End}}}] {#Item body branches}} +            (do meta_monad +              [pattern+ (full_expansion #1 pattern)] +              (case pattern+ +                {#Item pattern' {#End}} +                (in (partial_list pattern' body branches)) +                 +                _ +                (failure "`pattern` can only expand to 1 pattern."))) +             +            _ +            (failure "Wrong syntax for `pattern` macro")))) -(macro:' .private (pattern#or tokens) -         (case tokens -           (pattern (partial_list [_ {#Form patterns}] body branches)) -           (case patterns -             {#End} -             (failure "pattern#or cannot have 0 patterns") +(def:'' .private pattern#or +        Macro +        (macro (_ tokens) +          (case tokens +            (pattern (partial_list [_ {#Form patterns}] body branches)) +            (case patterns +              {#End} +              (failure "pattern#or cannot have 0 patterns") -             _ -             (let' [pairs (|> patterns -                              (list#each (function' [pattern] (list pattern body))) -                              (list#conjoint))] -                   (meta#in (list#composite pairs branches)))) -           _ -           (failure "Wrong syntax for pattern#or"))) +              _ +              (let' [pairs (|> patterns +                               (list#each (function' [pattern] (list pattern body))) +                               (list#conjoint))] +                    (meta#in (list#composite pairs branches)))) +            _ +            (failure "Wrong syntax for pattern#or"))))  (def:' .private (symbol? code)         (-> Code Bit) @@ -2498,51 +2583,55 @@           _           #0)) -(macro:' .public (let tokens) -         (case tokens -           (pattern (list [_ {#Tuple bindings}] body)) -           (case (..pairs bindings) -             {#Some bindings} -             (|>  bindings -                  list#reversed -                  (list#mix (is (-> [Code Code] Code Code) -                                (function' [lr body'] -                                           (let' [[l r] lr] -                                                 (if (symbol? l) -                                                   (` ({(~ l) (~ body')} (~ r))) -                                                   (` (case (~ r) (~ l) (~ body'))))))) -                            body) -                  list -                  meta#in) - -             {#None} -             (failure "let requires an even number of parts")) +(def:'' .public let +        Macro +        (macro (_ tokens) +          (case tokens +            (pattern (list [_ {#Tuple bindings}] body)) +            (case (..pairs bindings) +              {#Some bindings} +              (|>  bindings +                   list#reversed +                   (list#mix (is (-> [Code Code] Code Code) +                                 (function' [lr body'] +                                            (let' [[l r] lr] +                                                  (if (symbol? l) +                                                    (` ({(~ l) (~ body')} (~ r))) +                                                    (` (case (~ r) (~ l) (~ body'))))))) +                             body) +                   list +                   meta#in) -           _ -           (failure "Wrong syntax for let"))) +              {#None} +              (failure "let requires an even number of parts")) -(macro:' .public (function tokens) -         (case (is (Maybe [Text Code (List Code) Code]) -                   (case tokens -                     (pattern (list [_ {#Form (partial_list [_ {#Symbol ["" name]}] head tail)}] body)) -                     {#Some name head tail body} -                      -                     _ -                     {#None})) -           {#Some g!name head tail body} -           (let [g!blank (local$ "") -                 nest (is (-> Code (-> Code Code Code)) -                          (function' [g!name] -                                     (function' [arg body'] -                                                (if (symbol? arg) -                                                  (` ([(~ g!name) (~ arg)] (~ body'))) -                                                  (` ([(~ g!name) (~ g!blank)] -                                                      (.case (~ g!blank) (~ arg) (~ body'))))))))] -             (meta#in (list (nest (..local$ g!name) head -                                  (list#mix (nest g!blank) body (list#reversed tail)))))) +            _ +            (failure "Wrong syntax for let")))) + +(def:'' .public function +        Macro +        (macro (_ tokens) +          (case (is (Maybe [Text Code (List Code) Code]) +                    (case tokens +                      (pattern (list [_ {#Form (partial_list [_ {#Symbol ["" name]}] head tail)}] body)) +                      {#Some name head tail body} +                       +                      _ +                      {#None})) +            {#Some g!name head tail body} +            (let [g!blank (local$ "") +                  nest (is (-> Code (-> Code Code Code)) +                           (function' [g!name] +                                      (function' [arg body'] +                                                 (if (symbol? arg) +                                                   (` ([(~ g!name) (~ arg)] (~ body'))) +                                                   (` ([(~ g!name) (~ g!blank)] +                                                       (.case (~ g!blank) (~ arg) (~ body'))))))))] +              (meta#in (list (nest (..local$ g!name) head +                                   (list#mix (nest g!blank) body (list#reversed tail)))))) -           {#None} -           (failure "Wrong syntax for function"))) +            {#None} +            (failure "Wrong syntax for function"))))  (def:' .private Parser         Type @@ -2740,7 +2829,7 @@  (template [<parser> <parameter_type> <parameters_parser>]    [(def:' .private (<parser> tokens) -          (-> (List Code) (Maybe [(List Code) [Text (List <parameter_type>)]])) +          (Parser [Text (List <parameter_type>)])            (case tokens              (pattern (partial_list [_ {#Form local_declaration}] tokens'))              (do maybe_monad @@ -2816,57 +2905,41 @@            _ (endP tokens)]           (in [export_policy name parameters ?type body]))) -(macro:' .public (def: tokens) -         (case (definitionP tokens) -           {#Some [export_policy name parameters ?type body]} -           (let [body (case parameters -                        {#End} -                        body - -                        _ -                        (` (function ((~ (..local$ name)) (~+ parameters)) -                             (~ body)))) -                 body (case ?type -                        {#Some type} -                        (` (is (~ type) -                               (~ body))) -                         -                        {#None} -                        body)] -             (meta#in (list (` ("lux def" (~ (..local$ name)) -                                (~ body) -                                (~ export_policy)))))) -            -           {#None} -           (failure "Wrong syntax for def:"))) - -(def:' .private (macroP tokens) -       (-> (List Code) (Maybe [Code Text (List Text) Code])) -       (do maybe_monad -         [% (declarationP tokens) -          .let' [[tokens [export_policy name parameters]] %] -          % (anyP tokens) -          .let' [[tokens body] %] -          _ (endP tokens)] -         (in [export_policy name parameters body]))) +(def:'' .public def: +        Macro +        (macro (_ tokens) +          (case (definitionP tokens) +            {#Some [export_policy name parameters ?type body]} +            (let [body (case parameters +                         {#End} +                         body -(macro:' .public (macro: tokens) -         (case (macroP tokens) -           {#Some [export_policy name args body]} -           (let [name (local$ name) -                 body (case args -                        {#End} -                        body - -                        _ -                        (` ("lux macro" -                            (function ((~ name) (~+ (list#each local$ args))) (~ body)))))] -             (meta#in (list (` ("lux def" (~ name) -                                (~ body) -                                (~ export_policy)))))) +                         _ +                         (` (function ((~ (..local$ name)) (~+ parameters)) +                              (~ body)))) +                  body (case ?type +                         {#Some type} +                         (` (is (~ type) +                                (~ body))) +                          +                         {#None} +                         body)] +              (meta#in (list (` ("lux def" (~ (..local$ name)) +                                 (~ body) +                                 (~ export_policy)))))) +             +            {#None} +            (failure "Wrong syntax for def:")))) -           {#None} -           (failure "Wrong syntax for macro:"))) +(def:'' .public symbol +        Macro +        (macro (_ tokens) +          (case tokens +            (pattern (list [_ {#Symbol [module name]}])) +            (meta#in (list (` [(~ (text$ module)) (~ (text$ name))]))) +             +            _ +            (failure (..wrong_syntax_error [..prelude_module "symbol"])))))  (def: (list#one f xs)    (All (_ a b) @@ -2884,16 +2957,17 @@        {#Some y})))  (template [<name> <form> <message>] -  [(macro: .public (<name> tokens) -     (case (list#reversed tokens) -       (pattern (partial_list last init)) -       (meta#in (list (list#mix (is (-> Code Code Code) -                                    (function (_ pre post) (` <form>))) -                                last -                                init))) -        -       _ -       (failure <message>)))] +  [(def: .public <name> +     (macro (_ tokens) +       (case (list#reversed tokens) +         (pattern (partial_list last init)) +         (meta#in (list (list#mix (is (-> Code Code Code) +                                      (function (_ pre post) (` <form>))) +                                  last +                                  init))) +          +         _ +         (failure <message>))))]    [and (if (~ pre) (~ post) #0) "'and' requires >=1 clauses."]    [or  (if (~ pre) #1 (~ post)) "'or' requires >=1 clauses."]) @@ -2906,20 +2980,21 @@    (-> Text Nothing)    ("lux io error" message)) -(macro: (maybe#else tokens state) -  (case tokens -    (pattern (list else maybe)) -    (let [g!temp (is Code [dummy_location {#Symbol ["" ""]}]) -          code (` (case (~ maybe) -                    {.#Some (~ g!temp)} -                    (~ g!temp) +(def: maybe#else +  (macro (_ tokens state) +    (case tokens +      (pattern (list else maybe)) +      (let [g!temp (is Code [dummy_location {#Symbol ["" ""]}]) +            code (` (case (~ maybe) +                      {.#Some (~ g!temp)} +                      (~ g!temp) -                    {.#None} -                    (~ else)))] -      {#Right [state (list code)]}) +                      {.#None} +                      (~ else)))] +        {#Right [state (list code)]}) -    _ -    {#Left "Wrong syntax for maybe#else"})) +      _ +      {#Left "Wrong syntax for maybe#else"})))  (def: (text#all_split_by splitter input)    (-> Text Text (List Text)) @@ -3198,41 +3273,42 @@      (symbol#encoded name)      )) -(macro: .public (implementation tokens) -  (do meta_monad -    [tokens' (monad#each meta_monad expansion tokens) -     struct_type ..expected_type -     tags+type (record_slots struct_type) -     tags (is (Meta (List Symbol)) -              (case tags+type -                {#Some [tags _]} -                (meta#in tags) +(def: .public implementation +  (macro (_ tokens) +    (do meta_monad +      [tokens' (monad#each meta_monad expansion tokens) +       struct_type ..expected_type +       tags+type (record_slots struct_type) +       tags (is (Meta (List Symbol)) +                (case tags+type +                  {#Some [tags _]} +                  (meta#in tags) -                _ -                (failure (all text#composite -                              "No tags available for type: " -                              (type#encoded struct_type))))) -     .let [tag_mappings (is (List [Text Code]) -                            (list#each (function (_ tag) -                                         [(product#right tag) -                                          (symbol$ tag)]) -                                       tags))] -     members (monad#each meta_monad -                         (is (-> Code (Meta (List Code))) -                             (function (_ token) -                               (case token -                                 (pattern [_ {#Form (list [_ {#Text "lux def"}] [_ {#Symbol ["" slot_name]}] value export_policy)}]) -                                 (case (plist#value slot_name tag_mappings) -                                   {#Some tag} -                                   (in (list tag value)) +                  _ +                  (failure (all text#composite +                                "No tags available for type: " +                                (type#encoded struct_type))))) +       .let [tag_mappings (is (List [Text Code]) +                              (list#each (function (_ tag) +                                           [(product#right tag) +                                            (symbol$ tag)]) +                                         tags))] +       members (monad#each meta_monad +                           (is (-> Code (Meta (List Code))) +                               (function (_ token) +                                 (case token +                                   (pattern [_ {#Form (list [_ {#Text "lux def"}] [_ {#Symbol ["" slot_name]}] value export_policy)}]) +                                   (case (plist#value slot_name tag_mappings) +                                     {#Some tag} +                                     (in (list tag value)) + +                                     _ +                                     (failure (text#composite "Unknown implementation member: " slot_name)))                                     _ -                                   (failure (text#composite "Unknown implementation member: " slot_name))) - -                                 _ -                                 (failure "Invalid implementation member.")))) -                         (list#conjoint tokens'))] -    (in (list (tuple$ (list#conjoint members)))))) +                                   (failure "Invalid implementation member.")))) +                           (list#conjoint tokens'))] +      (in (list (tuple$ (list#conjoint members)))))))  (def: (text#interposed separator parts)    (-> Text (List Text) Text) @@ -3265,22 +3341,23 @@       tokens (remainderP tokens)]      (in [export_policy name parameters type tokens]))) -(macro: .public (implementation: tokens) -  (case (implementationP tokens) -    {#Some [export_policy name args type definitions]} -    (let [usage (case args -                  {#End} -                  (local$ name) - -                  _ -                  (` ((~ (local$ name)) (~+ args))))] -      (meta#in (list (` (..def: (~ export_policy) (~ usage) -                          (~ type) -                          (..implementation -                           (~+ definitions))))))) +(def: .public implementation: +  (macro (_ tokens) +    (case (implementationP tokens) +      {#Some [export_policy name args type definitions]} +      (let [usage (case args +                    {#End} +                    (local$ name) + +                    _ +                    (` ((~ (local$ name)) (~+ args))))] +        (meta#in (list (` (..def: (~ export_policy) (~ usage) +                            (~ type) +                            (..implementation +                             (~+ definitions))))))) -    {#None} -    (failure "Wrong syntax for implementation:"))) +      {#None} +      (failure "Wrong syntax for implementation:"))))  (def: (function#identity value)    (All (_ a) @@ -3319,16 +3396,17 @@      _      {#None})) -(macro: .public (Variant tokens) -  (case (everyP caseP tokens) -    {#Some cases} -    (meta#in (list (` (..Union (~+ (list#each product#right cases)))) -                   (variant$ (list#each (function (_ case) -                                          (text$ (product#left case))) -                                        cases)))) -     -    {#None} -    (failure "Wrong syntax for Variant"))) +(def: .public Variant +  (macro (_ tokens) +    (case (everyP caseP tokens) +      {#Some cases} +      (meta#in (list (` (..Union (~+ (list#each product#right cases)))) +                     (variant$ (list#each (function (_ case) +                                            (text$ (product#left case))) +                                          cases)))) +       +      {#None} +      (failure "Wrong syntax for Variant"))))  (def: (slotP tokens)    (-> (List Code) (Maybe [(List Code) [Text Code]])) @@ -3339,21 +3417,22 @@      _      {#None})) -(macro: .public (Record tokens) -  (case tokens -    (pattern (list [_ {#Tuple record}])) -    (case (everyP slotP record) -      {#Some slots} -      (meta#in (list (` (..Tuple (~+ (list#each product#right slots)))) -                     (tuple$ (list#each (function (_ slot) -                                          (text$ (product#left slot))) -                                        slots)))) -       -      {#None} -      (failure "Wrong syntax for Record")) +(def: .public Record +  (macro (_ tokens) +    (case tokens +      (pattern (list [_ {#Tuple record}])) +      (case (everyP slotP record) +        {#Some slots} +        (meta#in (list (` (..Tuple (~+ (list#each product#right slots)))) +                       (tuple$ (list#each (function (_ slot) +                                            (text$ (product#left slot))) +                                          slots)))) +         +        {#None} +        (failure "Wrong syntax for Record")) -    _ -    (failure "Wrong syntax for Record"))) +      _ +      (failure "Wrong syntax for Record"))))  (def: (typeP tokens)    (-> (List Code) (Maybe [Code Text (List Text) Code])) @@ -3406,50 +3485,51 @@      (meta#in [type {#None}])}     it)) -(macro: .public (type: tokens) -  (case (typeP tokens) -    {#Some [export_policy name args type_codes]} -    (do meta_monad -      [type+labels?? (..type_declaration type_codes) -       module_name current_module_name -       .let' [type_name (local$ name) -              [type labels??] type+labels?? -              type' (is (Maybe Code) -                        (case args -                          {#End} -                          {#Some type} +(def: .public type: +  (macro (_ tokens) +    (case (typeP tokens) +      {#Some [export_policy name args type_codes]} +      (do meta_monad +        [type+labels?? (..type_declaration type_codes) +         module_name current_module_name +         .let' [type_name (local$ name) +                [type labels??] type+labels?? +                type' (is (Maybe Code) +                          (case args +                            {#End} +                            {#Some type} -                          _ -                          {#Some (` (.All ((~ type_name) (~+ (list#each local$ args))) -                                      (~ type)))}))]] -      (case type' -        {#Some type''} -        (let [typeC (` {.#Named [(~ (text$ module_name)) -                                 (~ (text$ name))] -                                (.type (~ type''))})] -          (meta#in (list (case labels?? -                           {#Some labels} -                           (` ("lux def type tagged" (~ type_name) -                               (~ typeC) -                               (~ (case labels -                                    {#Left tags} -                                    (` {(~+ (list#each text$ tags))}) -                                     -                                    {#Right slots} -                                    (` [(~+ (list#each text$ slots))]))) -                               (~ export_policy))) -                            -                           _ -                           (` ("lux def" (~ type_name) -                               ("lux type check type" -                                (~ typeC)) -                               (~ export_policy))))))) +                            _ +                            {#Some (` (.All ((~ type_name) (~+ (list#each local$ args))) +                                        (~ type)))}))]] +        (case type' +          {#Some type''} +          (let [typeC (` {.#Named [(~ (text$ module_name)) +                                   (~ (text$ name))] +                                  (.type (~ type''))})] +            (meta#in (list (case labels?? +                             {#Some labels} +                             (` ("lux def type tagged" (~ type_name) +                                 (~ typeC) +                                 (~ (case labels +                                      {#Left tags} +                                      (` {(~+ (list#each text$ tags))}) +                                       +                                      {#Right slots} +                                      (` [(~+ (list#each text$ slots))]))) +                                 (~ export_policy))) +                              +                             _ +                             (` ("lux def" (~ type_name) +                                 ("lux type check type" +                                  (~ typeC)) +                                 (~ export_policy))))))) -        {#None} -        (failure "Wrong syntax for type:"))) +          {#None} +          (failure "Wrong syntax for type:"))) -    {#None} -    (failure "Wrong syntax for type:"))) +      {#None} +      (failure "Wrong syntax for type:"))))  (type: Referral    [Symbol (List Code)]) @@ -3460,23 +3540,6 @@      #import_alias (Maybe Text)      #import_referrals (List Referral)])) -... TODO: Allow asking the compiler for the name of the definition -... currently being defined. That name can then be fed into -... 'wrong_syntax_error' for easier maintenance of the error_messages. -(def: (wrong_syntax_error it) -  (-> Symbol Text) -  (|> it -      symbol#encoded -      (text#composite "Wrong syntax for "))) - -(macro: .public (symbol tokens) -  (case tokens -    (pattern (list [_ {#Symbol [module name]}])) -    (meta#in (list (` [(~ (text$ module)) (~ (text$ name))]))) -     -    _ -    (failure (..wrong_syntax_error [..prelude_module "symbol"])))) -  (def: referral_parser    (Parser Referral)    (formP (andP symbolP (someP anyP)))) @@ -3762,51 +3825,55 @@    (-> Text Text Code)    (` ("lux def alias" (~ (local$ def)) (~ (symbol$ [imported_module def]))))) -(macro: .public (only tokens) -  (case (..parsed (all ..andP -                       ..textP -                       ..textP -                       ..textP -                       (..someP ..localP)) -                  tokens) -    {.#Some [current_module imported_module import_alias actual]} -    (do meta_monad -      [expected (exported_definitions imported_module) -       _ (test_referrals current_module imported_module expected actual)] -      (in (list#each (..alias_definition imported_module) actual))) +(def: .public only +  (macro (_ tokens) +    (case (..parsed (all ..andP +                         ..textP +                         ..textP +                         ..textP +                         (..someP ..localP)) +                    tokens) +      {.#Some [current_module imported_module import_alias actual]} +      (do meta_monad +        [expected (exported_definitions imported_module) +         _ (test_referrals current_module imported_module expected actual)] +        (in (list#each (..alias_definition imported_module) actual))) -    {.#None} -    (failure (..wrong_syntax_error (symbol ..only))))) +      {.#None} +      (failure (..wrong_syntax_error (symbol ..only)))))) -(macro: .public (|>> tokens) -  (do meta_monad -    [g!_ (..generated_symbol "_") -     g!arg (..generated_symbol "arg")] -    (meta#in (list (` (function ((~ g!_) (~ g!arg)) (|> (~ g!arg) (~+ tokens)))))))) +(def: .public |>> +  (macro (_ tokens) +    (do meta_monad +      [g!_ (..generated_symbol "_") +       g!arg (..generated_symbol "arg")] +      (meta#in (list (` (function ((~ g!_) (~ g!arg)) (|> (~ g!arg) (~+ tokens))))))))) -(macro: .public (<<| tokens) -  (do meta_monad -    [g!_ (..generated_symbol "_") -     g!arg (..generated_symbol "arg")] -    (meta#in (list (` (function ((~ g!_) (~ g!arg)) (<| (~+ tokens) (~ g!arg)))))))) - -(macro: .public (except tokens) -  (case (..parsed (all ..andP -                       ..textP -                       ..textP -                       ..textP -                       (..someP ..localP)) -                  tokens) -    {.#Some [current_module imported_module import_alias actual]} +(def: .public <<| +  (macro (_ tokens)      (do meta_monad -      [expected (exported_definitions imported_module) -       _ (test_referrals current_module imported_module expected actual)] -      (in (|> expected -              (..list#only (|>> (is_member? actual) not)) -              (list#each (..alias_definition imported_module))))) +      [g!_ (..generated_symbol "_") +       g!arg (..generated_symbol "arg")] +      (meta#in (list (` (function ((~ g!_) (~ g!arg)) (<| (~+ tokens) (~ g!arg))))))))) + +(def: .public except +  (macro (_ tokens) +    (case (..parsed (all ..andP +                         ..textP +                         ..textP +                         ..textP +                         (..someP ..localP)) +                    tokens) +      {.#Some [current_module imported_module import_alias actual]} +      (do meta_monad +        [expected (exported_definitions imported_module) +         _ (test_referrals current_module imported_module expected actual)] +        (in (|> expected +                (..list#only (|>> (is_member? actual) not)) +                (list#each (..alias_definition imported_module))))) -    {.#None} -    (failure (..wrong_syntax_error (symbol ..except))))) +      {.#None} +      (failure (..wrong_syntax_error (symbol ..except))))))  (def: (in_env name state)    (-> Text Lux (Maybe Type)) @@ -3973,79 +4040,81 @@      _      (list))) -(macro: .public (open tokens) -  (case tokens -    (pattern (partial_list [_ {#Form (list [_ {#Text alias}])}] body branches)) -    (do meta_monad -      [g!temp (..generated_symbol "temp")] -      (in (partial_list g!temp (` (..open (~ g!temp) (~ (text$ alias)) (~ body))) branches))) - -    (pattern (list [_ {#Symbol name}] [_ {#Text alias}] body)) -    (do meta_monad -      [init_type (type_definition name) -       struct_evidence (record_slots init_type)] -      (case struct_evidence -        {#None} -        (failure (text#composite "Can only 'open' structs: " (type#encoded init_type))) +(def: .public open +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_ {#Form (list [_ {#Text alias}])}] body branches)) +      (do meta_monad +        [g!temp (..generated_symbol "temp")] +        (in (partial_list g!temp (` (..open (~ g!temp) (~ (text$ alias)) (~ body))) branches))) -        {#Some tags&members} -        (do meta_monad -          [full_body ((is (-> Symbol [(List Symbol) (List Type)] Code (Meta Code)) -                          (function (again source [tags members] target) -                            (let [locals (list#each (function (_ [t_module t_name]) -                                                      [[t_module t_name] -                                                       ["" (..module_alias (list t_name) alias)]]) -                                                    tags) -                                  pattern (case locals -                                            (pattern (list [slot binding])) -                                            (symbol$ binding) +      (pattern (list [_ {#Symbol name}] [_ {#Text alias}] body)) +      (do meta_monad +        [init_type (type_definition name) +         struct_evidence (record_slots init_type)] +        (case struct_evidence +          {#None} +          (failure (text#composite "Can only 'open' structs: " (type#encoded init_type))) -                                            _ -                                            (|> locals -                                                (list#each (function (_ [slot binding]) -                                                             (list (symbol$ slot) -                                                                   (symbol$ binding)))) -                                                list#conjoint -                                                tuple$))] -                              (do meta_monad -                                [enhanced_target (monad#mix meta_monad -                                                            (function (_ [[_ m_local] m_type] enhanced_target) -                                                              (do meta_monad -                                                                [m_implementation (record_slots m_type)] -                                                                (case m_implementation -                                                                  {#Some m_tags&members} -                                                                  (again m_local -                                                                         m_tags&members -                                                                         enhanced_target) - -                                                                  {#None} -                                                                  (in enhanced_target)))) -                                                            target -                                                            (zipped_2 locals members))] -                                (in (` ({(~ pattern) (~ enhanced_target)} (~ (symbol$ source))))))))) -                      name tags&members body)] -          (in (list full_body))))) +          {#Some tags&members} +          (do meta_monad +            [full_body ((is (-> Symbol [(List Symbol) (List Type)] Code (Meta Code)) +                            (function (again source [tags members] target) +                              (let [locals (list#each (function (_ [t_module t_name]) +                                                        [[t_module t_name] +                                                         ["" (..module_alias (list t_name) alias)]]) +                                                      tags) +                                    pattern (case locals +                                              (pattern (list [slot binding])) +                                              (symbol$ binding) + +                                              _ +                                              (|> locals +                                                  (list#each (function (_ [slot binding]) +                                                               (list (symbol$ slot) +                                                                     (symbol$ binding)))) +                                                  list#conjoint +                                                  tuple$))] +                                (do meta_monad +                                  [enhanced_target (monad#mix meta_monad +                                                              (function (_ [[_ m_local] m_type] enhanced_target) +                                                                (do meta_monad +                                                                  [m_implementation (record_slots m_type)] +                                                                  (case m_implementation +                                                                    {#Some m_tags&members} +                                                                    (again m_local +                                                                           m_tags&members +                                                                           enhanced_target) + +                                                                    {#None} +                                                                    (in enhanced_target)))) +                                                              target +                                                              (zipped_2 locals members))] +                                  (in (` ({(~ pattern) (~ enhanced_target)} (~ (symbol$ source))))))))) +                        name tags&members body)] +            (in (list full_body))))) -    _ -    (failure "Wrong syntax for open"))) - -(macro: .public (cond tokens) -  (case (list#reversed tokens) -    (pattern (partial_list else branches')) -    (case (pairs branches') -      {#Some branches'} -      (meta#in (list (list#mix (is (-> [Code Code] Code Code) -                                   (function (_ branch else) -                                     (let [[then ?] branch] -                                       (` (if (~ ?) (~ then) (~ else)))))) -                               else -                               branches'))) +      _ +      (failure "Wrong syntax for open")))) + +(def: .public cond +  (macro (_ tokens) +    (case (list#reversed tokens) +      (pattern (partial_list else branches')) +      (case (pairs branches') +        {#Some branches'} +        (meta#in (list (list#mix (is (-> [Code Code] Code Code) +                                     (function (_ branch else) +                                       (let [[then ?] branch] +                                         (` (if (~ ?) (~ then) (~ else)))))) +                                 else +                                 branches'))) -      {#None} -      (failure "cond requires an uneven number of arguments.")) -     -    _ -    (failure "Wrong syntax for cond"))) +        {#None} +        (failure "cond requires an uneven number of arguments.")) +       +      _ +      (failure "Wrong syntax for cond"))))  (def: (enumeration' idx xs)    (All (_ a) @@ -4062,46 +4131,47 @@      (-> (List a) (List [Nat a])))    (enumeration' 0 xs)) -(macro: .public (the tokens) -  (case tokens -    (pattern (list [_ {#Symbol slot'}] record)) -    (do meta_monad -      [slot (normal slot') -       output (..type_slot slot) -       .let [[idx tags exported? type] output] -       g!_ (..generated_symbol "_") -       g!output (..generated_symbol "")] -      (case (interface_methods type) -        {#Some members} -        (let [pattern (|> (zipped_2 tags (enumeration members)) -                          (list#each (is (-> [Symbol [Nat Type]] (List Code)) -                                         (function (_ [[r_module r_name] [r_idx r_type]]) -                                           (list (symbol$ [r_module r_name]) -                                                 (if ("lux i64 =" idx r_idx) -                                                   g!output -                                                   g!_))))) -                          list#conjoint -                          tuple$)] -          (meta#in (list (` ({(~ pattern) (~ g!output)} (~ record)))))) +(def: .public the +  (macro (_ tokens) +    (case tokens +      (pattern (list [_ {#Symbol slot'}] record)) +      (do meta_monad +        [slot (normal slot') +         output (..type_slot slot) +         .let [[idx tags exported? type] output] +         g!_ (..generated_symbol "_") +         g!output (..generated_symbol "")] +        (case (interface_methods type) +          {#Some members} +          (let [pattern (|> (zipped_2 tags (enumeration members)) +                            (list#each (is (-> [Symbol [Nat Type]] (List Code)) +                                           (function (_ [[r_module r_name] [r_idx r_type]]) +                                             (list (symbol$ [r_module r_name]) +                                                   (if ("lux i64 =" idx r_idx) +                                                     g!output +                                                     g!_))))) +                            list#conjoint +                            tuple$)] +            (meta#in (list (` ({(~ pattern) (~ g!output)} (~ record)))))) -        _ -        (failure "the can only use records."))) +          _ +          (failure "the can only use records."))) -    (pattern (list [_ {#Tuple slots}] record)) -    (meta#in (list (list#mix (is (-> Code Code Code) -                                 (function (_ slot inner) -                                   (` (..the (~ slot) (~ inner))))) -                             record -                             slots))) +      (pattern (list [_ {#Tuple slots}] record)) +      (meta#in (list (list#mix (is (-> Code Code Code) +                                   (function (_ slot inner) +                                     (` (..the (~ slot) (~ inner))))) +                               record +                               slots))) -    (pattern (list selector)) -    (do meta_monad -      [g!_ (..generated_symbol "_") -       g!record (..generated_symbol "record")] -      (in (list (` (function ((~ g!_) (~ g!record)) (..the (~ selector) (~ g!record))))))) -     -    _ -    (failure "Wrong syntax for the"))) +      (pattern (list selector)) +      (do meta_monad +        [g!_ (..generated_symbol "_") +         g!record (..generated_symbol "record")] +        (in (list (` (function ((~ g!_) (~ g!record)) (..the (~ selector) (~ g!record))))))) +       +      _ +      (failure "Wrong syntax for the"))))  (def: (open_declaration imported_module alias tags my_tag_index [module short] source type)    (-> Text Text (List Symbol) Nat Symbol Code Type (Meta (List Code))) @@ -4161,62 +4231,63 @@      _      global)) -(macro: .public (open: tokens) -  (case (..parsed (all ..andP -                       (..maybeP (all ..andP -                                      ..textP -                                      ..textP -                                      ..textP)) -                       ..textP -                       (..orP (..manyP ..symbolP) -                              (..manyP ..anyP))) -                  tokens) -    {.#Some [current_module,imported_module,import_alias alias implementations]} -    (let [[current_module imported_module import_alias] -          (case current_module,imported_module,import_alias -            {#Some [current_module imported_module import_alias]} -            [current_module imported_module import_alias] -             -            {#None} -            ["" "" ""])] -      (case implementations -        {#Left implementations} -        (do meta_monad -          [declarations (|> implementations -                            (list#each (localized imported_module)) -                            (monad#each meta_monad (implementation_declarations import_alias alias)))] -          (in (list#conjoint declarations))) -         -        {#Right implementations} -        (do meta_monad -          [pre_defs,implementations (is (Meta [(List Code) (List Code)]) -                                        (monad#mix meta_monad -                                                   (function (_ it [pre_defs implementations]) -                                                     (case it -                                                       [_ {#Symbol _}] -                                                       (in [pre_defs -                                                            {#Item it implementations}]) -                                                        -                                                       _ -                                                       (do meta_monad -                                                         [g!implementation (..generated_symbol "implementation")] -                                                         (in [{#Item (` ("lux def" (~ g!implementation) (~ it) #0)) pre_defs} -                                                              {#Item g!implementation implementations}])))) -                                                   [(list) (list)] -                                                   implementations)) -           .let [[pre_defs implementations] pre_defs,implementations]] -          (in (|> pre_defs -                  {#Item (` (..open: -                              (~ (text$ current_module)) -                              (~ (text$ imported_module)) -                              (~ (text$ import_alias)) -                              (~ (text$ alias)) -                              (~+ implementations)))} -                  list#reversed))))) -     +(def: .public open: +  (macro (_ tokens) +    (case (..parsed (all ..andP +                         (..maybeP (all ..andP +                                        ..textP +                                        ..textP +                                        ..textP)) +                         ..textP +                         (..orP (..manyP ..symbolP) +                                (..manyP ..anyP))) +                    tokens) +      {.#Some [current_module,imported_module,import_alias alias implementations]} +      (let [[current_module imported_module import_alias] +            (case current_module,imported_module,import_alias +              {#Some [current_module imported_module import_alias]} +              [current_module imported_module import_alias] +               +              {#None} +              ["" "" ""])] +        (case implementations +          {#Left implementations} +          (do meta_monad +            [declarations (|> implementations +                              (list#each (localized imported_module)) +                              (monad#each meta_monad (implementation_declarations import_alias alias)))] +            (in (list#conjoint declarations))) +           +          {#Right implementations} +          (do meta_monad +            [pre_defs,implementations (is (Meta [(List Code) (List Code)]) +                                          (monad#mix meta_monad +                                                     (function (_ it [pre_defs implementations]) +                                                       (case it +                                                         [_ {#Symbol _}] +                                                         (in [pre_defs +                                                              {#Item it implementations}]) +                                                          +                                                         _ +                                                         (do meta_monad +                                                           [g!implementation (..generated_symbol "implementation")] +                                                           (in [{#Item (` ("lux def" (~ g!implementation) (~ it) #0)) pre_defs} +                                                                {#Item g!implementation implementations}])))) +                                                     [(list) (list)] +                                                     implementations)) +             .let [[pre_defs implementations] pre_defs,implementations]] +            (in (|> pre_defs +                    {#Item (` (..open: +                                (~ (text$ current_module)) +                                (~ (text$ imported_module)) +                                (~ (text$ import_alias)) +                                (~ (text$ alias)) +                                (~+ implementations)))} +                    list#reversed))))) +       -    {.#None} -    (failure (..wrong_syntax_error (symbol ..open:))))) +      {.#None} +      (failure (..wrong_syntax_error (symbol ..open:))))))  (def: (imported_by? import_name module_name)    (-> Text Text (Meta Bit)) @@ -4247,224 +4318,230 @@                             (list#interposed " ")                             (list#mix text#composite ""))))))) -(macro: (refer tokens) -  (case tokens -    (pattern (partial_list [_ {#Text imported_module}] [_ {#Text alias}] options)) -    (do meta_monad -      [referrals (..referrals imported_module options) -       current_module ..current_module_name] -      (in (list#each (function (_ [macro parameters]) -                       (` ((~ (symbol$ macro)) -                           (~ (text$ current_module)) -                           (~ (text$ imported_module)) -                           (~ (text$ alias)) -                           (~+ parameters)))) -                     referrals))) - -    _ -    (failure (..wrong_syntax_error (symbol ..refer))))) - -(macro: .public (with tokens) -  (case (..parsed (..andP ..anyP ..anyP) -                  tokens) -    {.#Some [implementation expression]} -    (meta#in (list (` (..let [(..open (~ (text$ (alias_stand_in 0)))) (~ implementation)] -                        (~ expression))))) +(def: refer +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_ {#Text imported_module}] [_ {#Text alias}] options)) +      (do meta_monad +        [referrals (..referrals imported_module options) +         current_module ..current_module_name] +        (in (list#each (function (_ [macro parameters]) +                         (` ((~ (symbol$ macro)) +                             (~ (text$ current_module)) +                             (~ (text$ imported_module)) +                             (~ (text$ alias)) +                             (~+ parameters)))) +                       referrals))) -    {.#None} -    (failure (..wrong_syntax_error (symbol ..with))))) +      _ +      (failure (..wrong_syntax_error (symbol ..refer)))))) + +(def: .public with +  (macro (_ tokens) +    (case (..parsed (..andP ..anyP ..anyP) +                    tokens) +      {.#Some [implementation expression]} +      (meta#in (list (` (..let [(..open (~ (text$ (alias_stand_in 0)))) (~ implementation)] +                          (~ expression))))) + +      {.#None} +      (failure (..wrong_syntax_error (symbol ..with)))))) + +(def: .public at +  (macro (_ tokens) +    (case tokens +      (pattern (list implementation [_ {#Symbol member}])) +      (meta#in (list (` (..with (~ implementation) (~ (symbol$ member)))))) + +      (pattern (partial_list struct member args)) +      (meta#in (list (` ((..at (~ struct) (~ member)) (~+ args))))) +       +      _ +      (failure (..wrong_syntax_error (symbol ..at)))))) -(macro: .public (at tokens) -  (case tokens -    (pattern (list implementation [_ {#Symbol member}])) -    (meta#in (list (` (..with (~ implementation) (~ (symbol$ member)))))) +(def: .public has +  (macro (_ tokens) +    (case tokens +      (pattern (list [_ {#Symbol slot'}] value record)) +      (do meta_monad +        [slot (normal slot') +         output (..type_slot slot) +         .let [[idx tags exported? type] output]] +        (case (interface_methods type) +          {#Some members} +          (do meta_monad +            [pattern' (monad#each meta_monad +                                  (is (-> [Symbol [Nat Type]] (Meta [Symbol Nat Code])) +                                      (function (_ [r_slot_name [r_idx r_type]]) +                                        (do meta_monad +                                          [g!slot (..generated_symbol "")] +                                          (meta#in [r_slot_name r_idx g!slot])))) +                                  (zipped_2 tags (enumeration members)))] +            (let [pattern (|> pattern' +                              (list#each (is (-> [Symbol Nat Code] (List Code)) +                                             (function (_ [r_slot_name r_idx r_var]) +                                               (list (symbol$ r_slot_name) +                                                     r_var)))) +                              list#conjoint +                              tuple$) +                  output (|> pattern' +                             (list#each (is (-> [Symbol Nat Code] (List Code)) +                                            (function (_ [r_slot_name r_idx r_var]) +                                              (list (symbol$ r_slot_name) +                                                    (if ("lux i64 =" idx r_idx) +                                                      value +                                                      r_var))))) +                             list#conjoint +                             tuple$)] +              (meta#in (list (` ({(~ pattern) (~ output)} (~ record))))))) -    (pattern (partial_list struct member args)) -    (meta#in (list (` ((..at (~ struct) (~ member)) (~+ args))))) -     -    _ -    (failure (..wrong_syntax_error (symbol ..at))))) +          _ +          (failure "has can only use records."))) -(macro: .public (has tokens) -  (case tokens -    (pattern (list [_ {#Symbol slot'}] value record)) -    (do meta_monad -      [slot (normal slot') -       output (..type_slot slot) -       .let [[idx tags exported? type] output]] -      (case (interface_methods type) -        {#Some members} -        (do meta_monad -          [pattern' (monad#each meta_monad -                                (is (-> [Symbol [Nat Type]] (Meta [Symbol Nat Code])) -                                    (function (_ [r_slot_name [r_idx r_type]]) -                                      (do meta_monad -                                        [g!slot (..generated_symbol "")] -                                        (meta#in [r_slot_name r_idx g!slot])))) -                                (zipped_2 tags (enumeration members)))] -          (let [pattern (|> pattern' -                            (list#each (is (-> [Symbol Nat Code] (List Code)) -                                           (function (_ [r_slot_name r_idx r_var]) -                                             (list (symbol$ r_slot_name) -                                                   r_var)))) -                            list#conjoint -                            tuple$) -                output (|> pattern' -                           (list#each (is (-> [Symbol Nat Code] (List Code)) -                                          (function (_ [r_slot_name r_idx r_var]) -                                            (list (symbol$ r_slot_name) -                                                  (if ("lux i64 =" idx r_idx) -                                                    value -                                                    r_var))))) -                           list#conjoint -                           tuple$)] -            (meta#in (list (` ({(~ pattern) (~ output)} (~ record))))))) +      (pattern (list [_ {#Tuple slots}] value record)) +      (case slots +        {#End} +        (failure "Wrong syntax for has")          _ -        (failure "has can only use records."))) +        (do meta_monad +          [bindings (monad#each meta_monad +                                (is (-> Code (Meta Code)) +                                    (function (_ _) (..generated_symbol "temp"))) +                                slots) +           .let [pairs (zipped_2 slots bindings) +                 update_expr (list#mix (is (-> [Code Code] Code Code) +                                           (function (_ [s b] v) +                                             (` (..has (~ s) (~ v) (~ b))))) +                                       value +                                       (list#reversed pairs)) +                 [_ accesses'] (list#mix (is (-> [Code Code] [Code (List (List Code))] [Code (List (List Code))]) +                                             (function (_ [new_slot new_binding] [old_record accesses']) +                                               [(` (the (~ new_slot) (~ new_binding))) +                                                {#Item (list new_binding old_record) accesses'}])) +                                         [record (is (List (List Code)) {#End})] +                                         pairs) +                 accesses (list#conjoint (list#reversed accesses'))]] +          (in (list (` (let [(~+ accesses)] +                         (~ update_expr))))))) +       +      (pattern (list selector value)) +      (do meta_monad +        [g!_ (..generated_symbol "_") +         g!record (..generated_symbol "record")] +        (in (list (` (function ((~ g!_) (~ g!record)) +                       (..has (~ selector) (~ value) (~ g!record))))))) -    (pattern (list [_ {#Tuple slots}] value record)) -    (case slots -      {#End} -      (failure "Wrong syntax for has") +      (pattern (list selector)) +      (do meta_monad +        [g!_ (..generated_symbol "_") +         g!value (..generated_symbol "value") +         g!record (..generated_symbol "record")] +        (in (list (` (function ((~ g!_) (~ g!value) (~ g!record)) +                       (..has (~ selector) (~ g!value) (~ g!record)))))))        _ -      (do meta_monad -        [bindings (monad#each meta_monad -                              (is (-> Code (Meta Code)) -                                  (function (_ _) (..generated_symbol "temp"))) -                              slots) -         .let [pairs (zipped_2 slots bindings) -               update_expr (list#mix (is (-> [Code Code] Code Code) -                                         (function (_ [s b] v) -                                           (` (..has (~ s) (~ v) (~ b))))) -                                     value -                                     (list#reversed pairs)) -               [_ accesses'] (list#mix (is (-> [Code Code] [Code (List (List Code))] [Code (List (List Code))]) -                                           (function (_ [new_slot new_binding] [old_record accesses']) -                                             [(` (the (~ new_slot) (~ new_binding))) -                                              {#Item (list new_binding old_record) accesses'}])) -                                       [record (is (List (List Code)) {#End})] -                                       pairs) -               accesses (list#conjoint (list#reversed accesses'))]] -        (in (list (` (let [(~+ accesses)] -                       (~ update_expr))))))) -     -    (pattern (list selector value)) -    (do meta_monad -      [g!_ (..generated_symbol "_") -       g!record (..generated_symbol "record")] -      (in (list (` (function ((~ g!_) (~ g!record)) -                     (..has (~ selector) (~ value) (~ g!record))))))) +      (failure "Wrong syntax for has")))) -    (pattern (list selector)) -    (do meta_monad -      [g!_ (..generated_symbol "_") -       g!value (..generated_symbol "value") -       g!record (..generated_symbol "record")] -      (in (list (` (function ((~ g!_) (~ g!value) (~ g!record)) -                     (..has (~ selector) (~ g!value) (~ g!record))))))) +(def: .public revised +  (macro (_ tokens) +    (case tokens +      (pattern (list [_ {#Symbol slot'}] fun record)) +      (do meta_monad +        [slot (normal slot') +         output (..type_slot slot) +         .let [[idx tags exported? type] output]] +        (case (interface_methods type) +          {#Some members} +          (do meta_monad +            [pattern' (monad#each meta_monad +                                  (is (-> [Symbol [Nat Type]] (Meta [Symbol Nat Code])) +                                      (function (_ [r_slot_name [r_idx r_type]]) +                                        (do meta_monad +                                          [g!slot (..generated_symbol "")] +                                          (meta#in [r_slot_name r_idx g!slot])))) +                                  (zipped_2 tags (enumeration members)))] +            (let [pattern (|> pattern' +                              (list#each (is (-> [Symbol Nat Code] (List Code)) +                                             (function (_ [r_slot_name r_idx r_var]) +                                               (list (symbol$ r_slot_name) +                                                     r_var)))) +                              list#conjoint +                              tuple$) +                  output (|> pattern' +                             (list#each (is (-> [Symbol Nat Code] (List Code)) +                                            (function (_ [r_slot_name r_idx r_var]) +                                              (list (symbol$ r_slot_name) +                                                    (if ("lux i64 =" idx r_idx) +                                                      (` ((~ fun) (~ r_var))) +                                                      r_var))))) +                             list#conjoint +                             tuple$)] +              (meta#in (list (` ({(~ pattern) (~ output)} (~ record))))))) -    _ -    (failure "Wrong syntax for has"))) +          _ +          (failure "revised can only use records."))) -(macro: .public (revised tokens) -  (case tokens -    (pattern (list [_ {#Symbol slot'}] fun record)) -    (do meta_monad -      [slot (normal slot') -       output (..type_slot slot) -       .let [[idx tags exported? type] output]] -      (case (interface_methods type) -        {#Some members} -        (do meta_monad -          [pattern' (monad#each meta_monad -                                (is (-> [Symbol [Nat Type]] (Meta [Symbol Nat Code])) -                                    (function (_ [r_slot_name [r_idx r_type]]) -                                      (do meta_monad -                                        [g!slot (..generated_symbol "")] -                                        (meta#in [r_slot_name r_idx g!slot])))) -                                (zipped_2 tags (enumeration members)))] -          (let [pattern (|> pattern' -                            (list#each (is (-> [Symbol Nat Code] (List Code)) -                                           (function (_ [r_slot_name r_idx r_var]) -                                             (list (symbol$ r_slot_name) -                                                   r_var)))) -                            list#conjoint -                            tuple$) -                output (|> pattern' -                           (list#each (is (-> [Symbol Nat Code] (List Code)) -                                          (function (_ [r_slot_name r_idx r_var]) -                                            (list (symbol$ r_slot_name) -                                                  (if ("lux i64 =" idx r_idx) -                                                    (` ((~ fun) (~ r_var))) -                                                    r_var))))) -                           list#conjoint -                           tuple$)] -            (meta#in (list (` ({(~ pattern) (~ output)} (~ record))))))) +      (pattern (list [_ {#Tuple slots}] fun record)) +      (case slots +        {#End} +        (failure "Wrong syntax for revised")          _ -        (failure "revised can only use records."))) - -    (pattern (list [_ {#Tuple slots}] fun record)) -    (case slots -      {#End} -      (failure "Wrong syntax for revised") +        (do meta_monad +          [g!record (..generated_symbol "record") +           g!temp (..generated_symbol "temp")] +          (in (list (` (let [(~ g!record) (~ record) +                             (~ g!temp) (the [(~+ slots)] (~ g!record))] +                         (has [(~+ slots)] ((~ fun) (~ g!temp)) (~ g!record)))))))) -      _ +      (pattern (list selector fun))        (do meta_monad -        [g!record (..generated_symbol "record") -         g!temp (..generated_symbol "temp")] -        (in (list (` (let [(~ g!record) (~ record) -                           (~ g!temp) (the [(~+ slots)] (~ g!record))] -                       (has [(~+ slots)] ((~ fun) (~ g!temp)) (~ g!record)))))))) - -    (pattern (list selector fun)) -    (do meta_monad -      [g!_ (..generated_symbol "_") -       g!record (..generated_symbol "record")] -      (in (list (` (function ((~ g!_) (~ g!record)) -                     (..revised (~ selector) (~ fun) (~ g!record))))))) +        [g!_ (..generated_symbol "_") +         g!record (..generated_symbol "record")] +        (in (list (` (function ((~ g!_) (~ g!record)) +                       (..revised (~ selector) (~ fun) (~ g!record))))))) -    (pattern (list selector)) -    (do meta_monad -      [g!_ (..generated_symbol "_") -       g!fun (..generated_symbol "fun") -       g!record (..generated_symbol "record")] -      (in (list (` (function ((~ g!_) (~ g!fun) (~ g!record)) -                     (..revised (~ selector) (~ g!fun) (~ g!record))))))) -     -    _ -    (failure "Wrong syntax for revised"))) - -(macro: .private (pattern#template tokens) -  (case tokens -    (pattern (partial_list [_ {#Form (list [_ {#Tuple bindings}] -                                           [_ {#Tuple templates}])}] -                           [_ {#Form data}] -                           branches)) -    (case (is (Maybe (List Code)) -              (do maybe_monad -                [bindings' (monad#each maybe_monad symbol_short bindings) -                 data' (monad#each maybe_monad tuple_list data)] -                (let [num_bindings (list#size bindings')] -                  (if (every? (|>> ("lux i64 =" num_bindings)) -                              (list#each list#size data')) -                    (let [apply (is (-> Replacement_Environment (List Code)) -                                    (function (_ env) (list#each (realized_template env) templates)))] -                      (|> data' -                          (list#each (function#composite apply (replacement_environment bindings'))) -                          list#conjoint -                          in)) -                    {#None})))) -      {#Some output} -      (meta#in (list#composite output branches)) +      (pattern (list selector)) +      (do meta_monad +        [g!_ (..generated_symbol "_") +         g!fun (..generated_symbol "fun") +         g!record (..generated_symbol "record")] +        (in (list (` (function ((~ g!_) (~ g!fun) (~ g!record)) +                       (..revised (~ selector) (~ g!fun) (~ g!record))))))) -      {#None} -      (failure "Wrong syntax for pattern#template")) -     -    _ -    (failure "Wrong syntax for pattern#template"))) +      _ +      (failure "Wrong syntax for revised")))) + +(def: .private pattern#template +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_ {#Form (list [_ {#Tuple bindings}] +                                             [_ {#Tuple templates}])}] +                             [_ {#Form data}] +                             branches)) +      (case (is (Maybe (List Code)) +                (do maybe_monad +                  [bindings' (monad#each maybe_monad symbol_short bindings) +                   data' (monad#each maybe_monad tuple_list data)] +                  (let [num_bindings (list#size bindings')] +                    (if (every? (|>> ("lux i64 =" num_bindings)) +                                (list#each list#size data')) +                      (let [apply (is (-> Replacement_Environment (List Code)) +                                      (function (_ env) (list#each (realized_template env) templates)))] +                        (|> data' +                            (list#each (function#composite apply (replacement_environment bindings'))) +                            list#conjoint +                            in)) +                      {#None})))) +        {#Some output} +        (meta#in (list#composite output branches)) +         +        {#None} +        (failure "Wrong syntax for pattern#template")) +       +      _ +      (failure "Wrong syntax for pattern#template"))))  (template [<name> <extension>]    [(def: .public <name> @@ -4522,47 +4599,48 @@      ...     (~ (type_code anonymous))})      (symbol$ [module name]))) -(macro: .public (loop tokens) -  (let [?params (case tokens -                  (pattern (list [_ {#Form (list name [_ {#Tuple bindings}])}] body)) -                  {#Some [name bindings body]} +(def: .public loop +  (macro (_ tokens) +    (let [?params (case tokens +                    (pattern (list [_ {#Form (list name [_ {#Tuple bindings}])}] body)) +                    {#Some [name bindings body]} + +                    _ +                    {#None})] +      (case ?params +        {#Some [name bindings body]} +        (case (pairs bindings) +          {#Some pairs} +          (let [vars (list#each product#left pairs) +                inits (list#each product#right pairs)] +            (if (every? symbol? inits) +              (do meta_monad +                [inits' (is (Meta (List Symbol)) +                            (case (monad#each maybe_monad symbol_name inits) +                              {#Some inits'} (meta#in inits') +                              {#None}        (failure "Wrong syntax for loop"))) +                 init_types (monad#each meta_monad type_definition inits') +                 expected ..expected_type] +                (meta#in (list (` (("lux type check" +                                    (-> (~+ (list#each type_code init_types)) +                                        (~ (type_code expected))) +                                    (function ((~ name) (~+ vars)) +                                      (~ body))) +                                   (~+ inits)))))) +              (do meta_monad +                [aliases (monad#each meta_monad +                                     (is (-> Code (Meta Code)) +                                         (function (_ _) (..generated_symbol ""))) +                                     inits)] +                (meta#in (list (` (..let [(~+ (..interleaved aliases inits))] +                                    (..loop ((~ name) [(~+ (..interleaved vars aliases))]) +                                      (~ body))))))))) -                  _ -                  {#None})] -    (case ?params -      {#Some [name bindings body]} -      (case (pairs bindings) -        {#Some pairs} -        (let [vars (list#each product#left pairs) -              inits (list#each product#right pairs)] -          (if (every? symbol? inits) -            (do meta_monad -              [inits' (is (Meta (List Symbol)) -                          (case (monad#each maybe_monad symbol_name inits) -                            {#Some inits'} (meta#in inits') -                            {#None}        (failure "Wrong syntax for loop"))) -               init_types (monad#each meta_monad type_definition inits') -               expected ..expected_type] -              (meta#in (list (` (("lux type check" -                                  (-> (~+ (list#each type_code init_types)) -                                      (~ (type_code expected))) -                                  (function ((~ name) (~+ vars)) -                                    (~ body))) -                                 (~+ inits)))))) -            (do meta_monad -              [aliases (monad#each meta_monad -                                   (is (-> Code (Meta Code)) -                                       (function (_ _) (..generated_symbol ""))) -                                   inits)] -              (meta#in (list (` (..let [(~+ (..interleaved aliases inits))] -                                  (..loop ((~ name) [(~+ (..interleaved vars aliases))]) -                                    (~ body))))))))) +          {#None} +          (failure "Wrong syntax for loop"))          {#None} -        (failure "Wrong syntax for loop")) - -      {#None} -      (failure "Wrong syntax for loop")))) +        (failure "Wrong syntax for loop")))))  (def: (with_expansions' label tokens target)    (-> Text (List Code) Code (List Code)) @@ -4583,37 +4661,38 @@       [#Variant]       [#Tuple]))) -(macro: .public (with_expansions tokens) -  (case (parsed (andP (tupleP (someP bindingP)) (someP anyP)) tokens) -    {#Some [bindings bodies]} -    (loop (again [bindings bindings -                  map (is (PList (List Code)) -                          (list))]) -      (let [normal (is (-> Code (List Code)) -                       (function (_ it) -                         (list#mix (function (_ [binding expansion] it) -                                     (list#conjoint (list#each (with_expansions' binding expansion) it))) -                                   (list it) -                                   map)))] -        (case bindings -          {#Item [var_name expr] &rest} -          (do meta_monad -            [expansion (case (normal expr) -                         (pattern (list expr)) -                         (single_expansion expr) +(def: .public with_expansions +  (macro (_ tokens) +    (case (parsed (andP (tupleP (someP bindingP)) (someP anyP)) tokens) +      {#Some [bindings bodies]} +      (loop (again [bindings bindings +                    map (is (PList (List Code)) +                            (list))]) +        (let [normal (is (-> Code (List Code)) +                         (function (_ it) +                           (list#mix (function (_ [binding expansion] it) +                                       (list#conjoint (list#each (with_expansions' binding expansion) it))) +                                     (list it) +                                     map)))] +          (case bindings +            {#Item [var_name expr] &rest} +            (do meta_monad +              [expansion (case (normal expr) +                           (pattern (list expr)) +                           (single_expansion expr) -                         _ -                         (failure (all text#composite -                                       "Incorrect expansion in with_expansions" -                                       " | Binding: " (text#encoded var_name) -                                       " | Expression: " (code#encoded expr))))] -            (again &rest (plist#with var_name expansion map))) -           -          {#End} -          (at meta_monad #in (list#conjoint (list#each normal bodies)))))) -     -    {#None} -    (failure "Wrong syntax for with_expansions"))) +                           _ +                           (failure (all text#composite +                                         "Incorrect expansion in with_expansions" +                                         " | Binding: " (text#encoded var_name) +                                         " | Expression: " (code#encoded expr))))] +              (again &rest (plist#with var_name expansion map))) +             +            {#End} +            (at meta_monad #in (list#conjoint (list#each normal bodies)))))) +       +      {#None} +      (failure "Wrong syntax for with_expansions"))))  (def: (flat_alias type)    (-> Type Type) @@ -4678,15 +4757,16 @@      ... (at meta_monad in token)      )) -(macro: .public (static tokens) -  (case tokens -    (pattern (list pattern)) -    (do meta_monad -      [pattern' (static_literal pattern)] -      (in (list pattern'))) -     -    _ -    (failure "Wrong syntax for 'static'."))) +(def: .public static +  (macro (_ tokens) +    (case tokens +      (pattern (list pattern)) +      (do meta_monad +        [pattern' (static_literal pattern)] +        (in (list pattern'))) +       +      _ +      (failure "Wrong syntax for 'static'."))))  (type: Multi_Level_Case    [Code (List [Code Code])]) @@ -4732,85 +4812,89 @@                                       (is (List [Code Code]) (list#reversed levels)))]      (list init_pattern inner_pattern_body))) -(macro: (pattern#multi tokens) -  (case tokens -    (pattern (partial_list [_meta {#Form levels}] body next_branches)) -    (do meta_monad -      [mlc (multi_level_case^ levels) -       .let [initial_bind? (case mlc -                             [[_ {#Symbol _}] _] -                             #1 - -                             _ -                             #0)] -       expected ..expected_type -       g!temp (..generated_symbol "temp")] -      (in (list g!temp -                (` ({{.#Some (~ g!temp)} -                     (~ g!temp) - -                     {.#None} -                     (case (~ g!temp) -                       (~+ next_branches))} -                    ("lux type check" {.#Apply (~ (type_code expected)) Maybe} -                     (case (~ g!temp) -                       (~+ (multi_level_case$ g!temp [mlc body])) - -                       (~+ (if initial_bind? -                             (list) -                             (list g!temp (` {.#None}))))))))))) -     -    _ -    (failure "Wrong syntax for pattern#multi"))) +(def: pattern#multi +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_meta {#Form levels}] body next_branches)) +      (do meta_monad +        [mlc (multi_level_case^ levels) +         .let [initial_bind? (case mlc +                               [[_ {#Symbol _}] _] +                               #1 + +                               _ +                               #0)] +         expected ..expected_type +         g!temp (..generated_symbol "temp")] +        (in (list g!temp +                  (` ({{.#Some (~ g!temp)} +                       (~ g!temp) + +                       {.#None} +                       (case (~ g!temp) +                         (~+ next_branches))} +                      ("lux type check" {.#Apply (~ (type_code expected)) Maybe} +                       (case (~ g!temp) +                         (~+ (multi_level_case$ g!temp [mlc body])) + +                         (~+ (if initial_bind? +                               (list) +                               (list g!temp (` {.#None}))))))))))) +       +      _ +      (failure "Wrong syntax for pattern#multi"))))  (def: .public (same? reference sample)    (All (_ a)      (-> a a Bit))    ("lux is" reference sample)) -(macro: .public (as_expected tokens) -  (case tokens -    (pattern (list expr)) -    (do meta_monad -      [type ..expected_type] -      (in (list (` ("lux type as" (~ (type_code type)) (~ expr)))))) -     -    _ -    (failure (..wrong_syntax_error (symbol ..as_expected))))) +(def: .public as_expected +  (macro (_ tokens) +    (case tokens +      (pattern (list expr)) +      (do meta_monad +        [type ..expected_type] +        (in (list (` ("lux type as" (~ (type_code type)) (~ expr)))))) +       +      _ +      (failure (..wrong_syntax_error (symbol ..as_expected))))))  (def: location    (Meta Location)    (function (_ compiler)      {#Right [compiler (the #location compiler)]})) -(macro: .public (undefined tokens) -  (case tokens -    {#End} -    (do meta_monad -      [location ..location -       .let [[module line column] location -             location (all "lux text concat" (text#encoded module) "," (nat#encoded line) "," (nat#encoded column)) -             message (all "lux text concat" "Undefined behavior @ " location)]] -      (in (list (` (..panic! (~ (text$ message))))))) -     -    _ -    (failure (..wrong_syntax_error (symbol ..undefined))))) +(def: .public undefined +  (macro (_ tokens) +    (case tokens +      {#End} +      (do meta_monad +        [location ..location +         .let [[module line column] location +               location (all "lux text concat" (text#encoded module) "," (nat#encoded line) "," (nat#encoded column)) +               message (all "lux text concat" "Undefined behavior @ " location)]] +        (in (list (` (..panic! (~ (text$ message))))))) +       +      _ +      (failure (..wrong_syntax_error (symbol ..undefined)))))) -(macro: .public (type_of tokens) -  (case tokens -    (pattern (list [_ {#Symbol var_name}])) -    (do meta_monad -      [var_type (type_definition var_name)] -      (in (list (type_code var_type)))) +(def: .public type_of +  (macro (_ tokens) +    (case tokens +      (pattern (list [_ {#Symbol var_name}])) +      (do meta_monad +        [var_type (type_definition var_name)] +        (in (list (type_code var_type)))) -    (pattern (list expression)) -    (do meta_monad -      [g!temp (..generated_symbol "g!temp")] -      (in (list (` (let [(~ g!temp) (~ expression)] -                     (..type_of (~ g!temp))))))) +      (pattern (list expression)) +      (do meta_monad +        [g!temp (..generated_symbol "g!temp")] +        (in (list (` (let [(~ g!temp) (~ expression)] +                       (..type_of (~ g!temp))))))) -    _ -    (failure (..wrong_syntax_error (symbol ..type_of))))) +      _ +      (failure (..wrong_syntax_error (symbol ..type_of))))))  (def: (templateP tokens)    (-> (List Code) (Maybe [Code Text (List Text) (List Code)])) @@ -4822,32 +4906,33 @@       _ (endP tokens)]      (in [export_policy name parameters templates]))) -(macro: .public (template: tokens) -  (case (templateP tokens) -    {#Some [export_policy name args input_templates]} -    (do meta_monad -      [g!tokens (..generated_symbol "tokens") -       g!compiler (..generated_symbol "compiler") -       g!_ (..generated_symbol "_") -       .let [rep_env (list#each (function (_ arg) -                                  [arg (` ((~' ~) (~ (local$ arg))))]) -                                args)] -       this_module current_module_name] -      (in (list (` (macro: (~ export_policy) -                     ((~ (local$ name)) (~ g!tokens) (~ g!compiler)) -                     (case (~ g!tokens) -                       (pattern (list (~+ (list#each local$ args)))) -                       {.#Right [(~ g!compiler) -                                 (list (~+ (list#each (function (_ template) -                                                        (` (`' (~ (with_replacements rep_env -                                                                    template))))) -                                                      input_templates)))]} -                        -                       (~ g!_) -                       {.#Left (~ (text$ (..wrong_syntax_error [this_module name])))})))))) +(def: .public template: +  (macro (_ tokens) +    (case (templateP tokens) +      {#Some [export_policy name args input_templates]} +      (do meta_monad +        [g!tokens (..generated_symbol "tokens") +         g!compiler (..generated_symbol "compiler") +         g!_ (..generated_symbol "_") +         .let [rep_env (list#each (function (_ arg) +                                    [arg (` ((~' ~) (~ (local$ arg))))]) +                                  args)] +         this_module current_module_name] +        (in (list (` (..def: (~ export_policy) (~ (local$ name)) +                       (..macro ((~ (local$ name)) (~ g!tokens) (~ g!compiler)) +                         (case (~ g!tokens) +                           (pattern (list (~+ (list#each local$ args)))) +                           {.#Right [(~ g!compiler) +                                     (list (~+ (list#each (function (_ template) +                                                            (` (`' (~ (with_replacements rep_env +                                                                        template))))) +                                                          input_templates)))]} +                            +                           (~ g!_) +                           {.#Left (~ (text$ (..wrong_syntax_error [this_module name])))}))))))) -    {#None} -    (failure (..wrong_syntax_error (symbol ..template:))))) +      {#None} +      (failure (..wrong_syntax_error (symbol ..template:))))))  (template [<name> <to>]    [(template: .public (<name> it) @@ -4859,19 +4944,21 @@    [rev ..Rev]    ) -(macro: .public (these tokens compiler) -  {#Right [compiler tokens]}) +(def: .public these +  (macro (_ tokens compiler) +    {#Right [compiler tokens]})) -(macro: .public (char tokens compiler) -  (case tokens -    (pattern#multi (pattern (list [_ {#Text input}])) -                   (|> input "lux text size" ("lux i64 =" 1))) -    (|> input ("lux text char" 0) -        nat$ list -        [compiler] {#Right}) +(def: .public char +  (macro (_ tokens compiler) +    (case tokens +      (pattern#multi (pattern (list [_ {#Text input}])) +                     (|> input "lux text size" ("lux i64 =" 1))) +      (|> input ("lux text char" 0) +          nat$ list +          [compiler] {#Right}) -    _ -    {#Left (..wrong_syntax_error (symbol ..char))})) +      _ +      {#Left (..wrong_syntax_error (symbol ..char))})))  (def: target    (Meta Text) @@ -4922,17 +5009,18 @@          (meta#in (list pick))          (target_pick target options' default))))) -(macro: .public (for tokens) -  (case (..parsed (..andP (..someP (..andP ..anyP ..anyP)) -                          (..maybeP ..anyP)) -                  tokens) -    {.#Some [options default]} -    (do meta_monad -      [target ..target] -      (target_pick target options default)) +(def: .public for +  (macro (_ tokens) +    (case (..parsed (..andP (..someP (..andP ..anyP ..anyP)) +                            (..maybeP ..anyP)) +                    tokens) +      {.#Some [options default]} +      (do meta_monad +        [target ..target] +        (target_pick target options default)) -    {.#None} -    (failure (..wrong_syntax_error (symbol ..for))))) +      {.#None} +      (failure (..wrong_syntax_error (symbol ..for))))))  ... TODO: Delete "scope_type_vars" (including the #scope_type_vars Lux state) and "parameter" ASAP.  (for "{old}" (these (def: (scope_type_vars state) @@ -4944,20 +5032,21 @@                           ..#scope_type_vars scope_type_vars ..#eval _eval]                          {#Right [state scope_type_vars]})) -                    (macro: .public (parameter tokens) -                      (case tokens -                        (pattern (list [_ {#Nat idx}])) -                        (do meta_monad -                          [stvs ..scope_type_vars] -                          (case (..item idx (list#reversed stvs)) -                            {#Some var_id} -                            (in (list (` {.#Ex (~ (nat$ var_id))}))) +                    (def: .public parameter +                      (macro (_ tokens) +                        (case tokens +                          (pattern (list [_ {#Nat idx}])) +                          (do meta_monad +                            [stvs ..scope_type_vars] +                            (case (..item idx (list#reversed stvs)) +                              {#Some var_id} +                              (in (list (` {.#Ex (~ (nat$ var_id))}))) -                            {#None} -                            (failure (text#composite "Indexed-type does not exist: " (nat#encoded idx))))) +                              {#None} +                              (failure (text#composite "Indexed-type does not exist: " (nat#encoded idx))))) -                        _ -                        (failure (..wrong_syntax_error (symbol ..$)))))) +                          _ +                          (failure (..wrong_syntax_error (symbol ..$)))))))       (these (def: .public parameter "")))  (def: (refer_code imported_module alias referrals) @@ -4969,31 +5058,32 @@                         (` ((~ (symbol$ macro)) (~+ parameters))))                       referrals))))) -(macro: .public (using _imports) -  (do meta_monad -    [current_module ..current_module_name -     imports (imports_parser #0 current_module {#End} _imports) -     .let [=imports (|> imports -                        (list#each (is (-> Importation Code) -                                       (function (_ [module_name m_alias =refer]) -                                         (` [(~ (text$ module_name)) (~ (text$ (..maybe#else "" m_alias)))])))) -                        tuple$) -           =refers (list#each (is (-> Importation Code) -                                  (function (_ [module_name m_alias =refer]) -                                    (refer_code module_name (..maybe#else "" m_alias) =refer))) -                              imports) -           =module (` ("lux def module" (~ =imports)))] -     g!_ (..generated_symbol "")] -    (in {#Item =module -               (for "Python" -                    ... TODO: Remove this hack once Jython is no longer being used as the Python interpreter. -                    ... Without it, I get this strange error -                    ... {library/lux/tool/compiler/language/lux/generation.no_buffer_for_saving_code} -                    ... Artifact ID: 0 -                    ... Which only ever happens for the Python compiler. -                    (partial_list (` ("lux def" (~ g!_) [] #0)) -                                  =refers) -                    =refers)}))) +(def: .public using +  (macro (_ _imports) +    (do meta_monad +      [current_module ..current_module_name +       imports (imports_parser #0 current_module {#End} _imports) +       .let [=imports (|> imports +                          (list#each (is (-> Importation Code) +                                         (function (_ [module_name m_alias =refer]) +                                           (` [(~ (text$ module_name)) (~ (text$ (..maybe#else "" m_alias)))])))) +                          tuple$) +             =refers (list#each (is (-> Importation Code) +                                    (function (_ [module_name m_alias =refer]) +                                      (refer_code module_name (..maybe#else "" m_alias) =refer))) +                                imports) +             =module (` ("lux def module" (~ =imports)))] +       g!_ (..generated_symbol "")] +      (in {#Item =module +                 (for "Python" +                      ... TODO: Remove this hack once Jython is no longer being used as the Python interpreter. +                      ... Without it, I get this strange error +                      ... {library/lux/tool/compiler/language/lux/generation.no_buffer_for_saving_code} +                      ... Artifact ID: 0 +                      ... Which only ever happens for the Python compiler. +                      (partial_list (` ("lux def" (~ g!_) [] #0)) +                                    =refers) +                      =refers)}))))  (def: (embedded_expansions code)    (-> Code (Meta [(List [Code Code]) Code])) @@ -5016,19 +5106,20 @@      _      (meta#in [(list) code]))) -(macro: .public (`` tokens) -  (case tokens -    (pattern (list raw)) -    (do meta_monad -      [=raw (..embedded_expansions raw) -       .let [[labels labelled] =raw]] -      (in (list (` (with_expansions [(~+ (|> labels -                                             (list#each (function (_ [label expansion]) (list label expansion))) -                                             list#conjoint))] -                     (~ labelled)))))) +(def: .public `` +  (macro (_ tokens) +    (case tokens +      (pattern (list raw)) +      (do meta_monad +        [=raw (..embedded_expansions raw) +         .let [[labels labelled] =raw]] +        (in (list (` (with_expansions [(~+ (|> labels +                                               (list#each (function (_ [label expansion]) (list label expansion))) +                                               list#conjoint))] +                       (~ labelled)))))) -    _ -    (failure (..wrong_syntax_error (symbol ..``))))) +      _ +      (failure (..wrong_syntax_error (symbol ..``))))))  (def: .public false    Bit @@ -5038,17 +5129,18 @@    Bit    #1) -(macro: .public (try tokens) -  (case tokens -    (pattern (list expression)) -    (do meta_monad -      [g!_ (..generated_symbol "g!_")] -      (in (list (` ("lux try" -                    (.function ((~ g!_) (~ g!_)) -                      (~ expression))))))) +(def: .public try +  (macro (_ tokens) +    (case tokens +      (pattern (list expression)) +      (do meta_monad +        [g!_ (..generated_symbol "g!_")] +        (in (list (` ("lux try" +                      (.function ((~ g!_) (~ g!_)) +                        (~ expression))))))) -    _ -    (..failure (..wrong_syntax_error (symbol ..try))))) +      _ +      (..failure (..wrong_syntax_error (symbol ..try))))))  (def: (methodP tokens)    (-> (List Code) (Maybe [(List Code) [Text Code]])) @@ -5062,16 +5154,17 @@      _      {#None})) -(macro: .public (Interface tokens) -  (do meta_monad -    [methods' (monad#each meta_monad expansion tokens)] -    (case (everyP methodP (list#conjoint methods')) -      {#Some methods} -      (in (list (` (..Tuple (~+ (list#each product#right methods)))) -                (tuple$ (list#each (|>> product#left text$) methods)))) +(def: .public Interface +  (macro (_ tokens) +    (do meta_monad +      [methods' (monad#each meta_monad expansion tokens)] +      (case (everyP methodP (list#conjoint methods')) +        {#Some methods} +        (in (list (` (..Tuple (~+ (list#each product#right methods)))) +                  (tuple$ (list#each (|>> product#left text$) methods)))) -      {#None} -      (failure "Wrong syntax for Interface")))) +        {#None} +        (failure "Wrong syntax for Interface")))))  (def: (recursive_type g!self g!dummy name body)    (-> Code Code Text Code Code) @@ -5080,26 +5173,23 @@                  (~ (let$ (local$ name) (` {.#Apply (..Primitive "") (~ g!self)})                           body)))})) -(macro: .public (Rec tokens) -  (case tokens -    (pattern (list [_ {#Symbol "" name}] body)) -    (do meta_monad -      [body' (expansion body) -       g!self (generated_symbol "g!self") -       g!dummy (generated_symbol "g!dummy")] -      (case body' -        (pattern (list body' labels)) -        (in (list (..recursive_type g!self g!dummy name body') labels)) - -        (pattern (list body')) -        (in (list (..recursive_type g!self g!dummy name body'))) +(def: .public Rec +  (macro (_ tokens) +    (case tokens +      (pattern (list [_ {#Symbol "" name}] body)) +      (do meta_monad +        [body' (expansion body) +         g!self (generated_symbol "g!self") +         g!dummy (generated_symbol "g!dummy")] +        (case body' +          (pattern (list body' labels)) +          (in (list (..recursive_type g!self g!dummy name body') labels)) -        _ -        (failure "Wrong syntax for Rec"))) +          (pattern (list body')) +          (in (list (..recursive_type g!self g!dummy name body'))) -    _ -    (failure "Wrong syntax for Rec"))) +          _ +          (failure "Wrong syntax for Rec"))) -(def: .public macro -  (-> Macro Macro') -  (|>> (as Macro'))) +      _ +      (failure "Wrong syntax for Rec")))) diff --git a/stdlib/source/library/lux/abstract/comonad.lux b/stdlib/source/library/lux/abstract/comonad.lux index 5bb928e6a..54f8707a3 100644 --- a/stdlib/source/library/lux/abstract/comonad.lux +++ b/stdlib/source/library/lux/abstract/comonad.lux @@ -23,57 +23,58 @@           (-> (w a) (w (w a))))         disjoint))) -(macro: .public (be tokens state) -  (case (is (Maybe [(Maybe Text) Code (List Code) Code]) -            (case tokens -              (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] comonad)}] [_ {.#Tuple bindings}] body)) -              {.#Some [{.#Some name} comonad bindings body]} -               -              (pattern (list comonad [_ {.#Tuple bindings}] body)) -              {.#Some [{.#None} comonad bindings body]} +(def: .public be +  (macro (_ tokens state) +    (case (is (Maybe [(Maybe Text) Code (List Code) Code]) +              (case tokens +                (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] comonad)}] [_ {.#Tuple bindings}] body)) +                {.#Some [{.#Some name} comonad bindings body]} +                 +                (pattern (list comonad [_ {.#Tuple bindings}] body)) +                {.#Some [{.#None} comonad bindings body]} -              _ -              {.#None})) -    {.#Some [?name comonad bindings body]} -    (case (list.pairs bindings) -      {.#Some bindings} -      (let [[module short] (symbol ..be) -            symbol (is (-> Text Code) -                       (|>> (all "lux text concat" module " " short " ") [""] {.#Symbol} [location.dummy])) -            g!_ (symbol "_") -            g!each (symbol "each") -            g!disjoint (symbol "disjoint") -            body' (list#mix (is (-> [Code Code] Code Code) -                                (function (_ binding body') -                                  (with_expansions [<default> (` (|> (~ value) (~ g!disjoint) ((~ g!each) (function ((~ g!_) (~ var)) (~ body')))))] -                                    (let [[var value] binding] -                                      (case var -                                        [_ {.#Symbol ["" _]}] -                                        <default> +                _ +                {.#None})) +      {.#Some [?name comonad bindings body]} +      (case (list.pairs bindings) +        {.#Some bindings} +        (let [[module short] (symbol ..be) +              symbol (is (-> Text Code) +                         (|>> (all "lux text concat" module " " short " ") [""] {.#Symbol} [location.dummy])) +              g!_ (symbol "_") +              g!each (symbol "each") +              g!disjoint (symbol "disjoint") +              body' (list#mix (is (-> [Code Code] Code Code) +                                  (function (_ binding body') +                                    (with_expansions [<default> (` (|> (~ value) (~ g!disjoint) ((~ g!each) (function ((~ g!_) (~ var)) (~ body')))))] +                                      (let [[var value] binding] +                                        (case var +                                          [_ {.#Symbol ["" _]}] +                                          <default> -                                        [_ {.#Symbol _}] -                                        (` ((~ var) (~ value) (~ body'))) +                                          [_ {.#Symbol _}] +                                          (` ((~ var) (~ value) (~ body'))) -                                        _ -                                        <default>))))) -                            body -                            (list.reversed bindings))] -        {.#Right [state (list (case ?name -                                {.#Some name} -                                (let [name [location.dummy {.#Symbol ["" name]}]] +                                          _ +                                          <default>))))) +                              body +                              (list.reversed bindings))] +          {.#Right [state (list (case ?name +                                  {.#Some name} +                                  (let [name [location.dummy {.#Symbol ["" name]}]] +                                    (` (.case (~ comonad) +                                         (~ name) +                                         (.case (~ name) +                                           [(~ g!each) (~' out) (~ g!disjoint)] +                                           (~ body'))))) + +                                  {.#None}                                    (` (.case (~ comonad) -                                       (~ name) -                                       (.case (~ name) -                                         [(~ g!each) (~' out) (~ g!disjoint)] -                                         (~ body'))))) +                                       [(~ g!each) (~' out) (~ g!disjoint)] +                                       (~ body')))))]}) +         +        {.#None} +        {.#Left "'be' bindings must have an even number of parts."}) -                                {.#None} -                                (` (.case (~ comonad) -                                     [(~ g!each) (~' out) (~ g!disjoint)] -                                     (~ body')))))]}) -              {.#None} -      {.#Left "'be' bindings must have an even number of parts."}) - -    {.#None} -    {.#Left "Wrong syntax for 'be'"})) +      {.#Left "Wrong syntax for 'be'"}))) diff --git a/stdlib/source/library/lux/abstract/monad.lux b/stdlib/source/library/lux/abstract/monad.lux index c4de9243c..18c22027d 100644 --- a/stdlib/source/library/lux/abstract/monad.lux +++ b/stdlib/source/library/lux/abstract/monad.lux @@ -54,57 +54,58 @@           (-> (m (m a)) (m a)))         conjoint))) -(macro: .public (do tokens state) -  (case (is (Maybe [(Maybe Text) Code (List Code) Code]) -            (case tokens -              (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] monad)}] [_ {.#Tuple bindings}] body)) -              {.#Some [{.#Some name} monad bindings body]} -               -              (pattern (list monad [_ {.#Tuple bindings}] body)) -              {.#Some [{.#None} monad bindings body]} - -              _ -              {.#None})) -    {.#Some [?name monad bindings body]} -    (if (|> bindings list#size .int ("lux i64 %" +2) ("lux i64 =" +0)) -      (let [[module short] (symbol ..do) -            symbol (is (-> Text Code) -                       (|>> (.all "lux text concat" module " " short " ") [""] {.#Symbol} [location.dummy])) -            g!_ (symbol "_") -            g!each (symbol "each") -            g!conjoint (symbol "conjoint") -            body' (list#mix (is (-> [Code Code] Code Code) -                                (function (_ binding body') -                                  (with_expansions [<default> (` (|> (~ value) ((~ g!each) (function ((~ g!_) (~ var)) (~ body'))) (~ g!conjoint)))] -                                    (let [[var value] binding] -                                      (case var -                                        [_ {.#Symbol ["" _]}] -                                        <default> - -                                        [_ {.#Symbol _}] -                                        (` ((~ var) (~ value) (~ body'))) - -                                        _ -                                        <default>))))) -                            body -                            (reversed (pairs bindings)))] -        {.#Right [state (list (case ?name -                                {.#Some name} -                                (let [name [location.dummy {.#Symbol ["" name]}]] +(def: .public do +  (macro (_ tokens state) +    (case (is (Maybe [(Maybe Text) Code (List Code) Code]) +              (case tokens +                (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] monad)}] [_ {.#Tuple bindings}] body)) +                {.#Some [{.#Some name} monad bindings body]} +                 +                (pattern (list monad [_ {.#Tuple bindings}] body)) +                {.#Some [{.#None} monad bindings body]} + +                _ +                {.#None})) +      {.#Some [?name monad bindings body]} +      (if (|> bindings list#size .int ("lux i64 %" +2) ("lux i64 =" +0)) +        (let [[module short] (symbol ..do) +              symbol (is (-> Text Code) +                         (|>> (.all "lux text concat" module " " short " ") [""] {.#Symbol} [location.dummy])) +              g!_ (symbol "_") +              g!each (symbol "each") +              g!conjoint (symbol "conjoint") +              body' (list#mix (is (-> [Code Code] Code Code) +                                  (function (_ binding body') +                                    (with_expansions [<default> (` (|> (~ value) ((~ g!each) (function ((~ g!_) (~ var)) (~ body'))) (~ g!conjoint)))] +                                      (let [[var value] binding] +                                        (case var +                                          [_ {.#Symbol ["" _]}] +                                          <default> + +                                          [_ {.#Symbol _}] +                                          (` ((~ var) (~ value) (~ body'))) + +                                          _ +                                          <default>))))) +                              body +                              (reversed (pairs bindings)))] +          {.#Right [state (list (case ?name +                                  {.#Some name} +                                  (let [name [location.dummy {.#Symbol ["" name]}]] +                                    (` (.case (~ monad) +                                         (~ name) +                                         (.case (~ name) +                                           [(~ g!each) (~' in) (~ g!conjoint)] +                                           (~ body'))))) +                                   +                                  {.#None}                                    (` (.case (~ monad) -                                       (~ name) -                                       (.case (~ name) -                                         [(~ g!each) (~' in) (~ g!conjoint)] -                                         (~ body'))))) -                                 -                                {.#None} -                                (` (.case (~ monad) -                                     [(~ g!each) (~' in) (~ g!conjoint)] -                                     (~ body')))))]}) -      {.#Left "'do' bindings must have an even number of parts."}) - -    {.#None} -    {.#Left "Wrong syntax for 'do'"})) +                                       [(~ g!each) (~' in) (~ g!conjoint)] +                                       (~ body')))))]}) +        {.#Left "'do' bindings must have an even number of parts."}) + +      {.#None} +      {.#Left "Wrong syntax for 'do'"})))  (def: .public (then monad f)    (All (_ ! a b) diff --git a/stdlib/source/library/lux/control/concurrency/atom.lux b/stdlib/source/library/lux/control/concurrency/atom.lux index ba861725f..e14e86c01 100644 --- a/stdlib/source/library/lux/control/concurrency/atom.lux +++ b/stdlib/source/library/lux/control/concurrency/atom.lux @@ -17,7 +17,7 @@      [primitive (.except)]      ["[0]" variance (.only Mutable)]]]]) -(with_expansions [<jvm> (these (ffi.import: (java/util/concurrent/atomic/AtomicReference a) +(with_expansions [<jvm> (these (ffi.import (java/util/concurrent/atomic/AtomicReference a)                                   "[1]::[0]"                                   (new [a])                                   (get [] a) diff --git a/stdlib/source/library/lux/control/concurrency/thread.lux b/stdlib/source/library/lux/control/concurrency/thread.lux index c102d4bbf..4428f9daa 100644 --- a/stdlib/source/library/lux/control/concurrency/thread.lux +++ b/stdlib/source/library/lux/control/concurrency/thread.lux @@ -24,32 +24,32 @@   [//    ["[0]" atom (.only Atom)]]) -(with_expansions [<jvm> (these (ffi.import: java/lang/Object +(with_expansions [<jvm> (these (ffi.import java/lang/Object                                   "[1]::[0]") -                               (ffi.import: java/lang/Long +                               (ffi.import java/lang/Long                                   "[1]::[0]") -                               (ffi.import: java/lang/Runtime +                               (ffi.import java/lang/Runtime                                   "[1]::[0]"                                   ("static" getRuntime [] java/lang/Runtime)                                   (availableProcessors [] int)) -                               (ffi.import: java/lang/Runnable +                               (ffi.import java/lang/Runnable                                   "[1]::[0]") -                               (ffi.import: java/util/concurrent/TimeUnit +                               (ffi.import java/util/concurrent/TimeUnit                                   "[1]::[0]"                                   ("enum" MILLISECONDS)) -                               (ffi.import: java/util/concurrent/Executor +                               (ffi.import java/util/concurrent/Executor                                   "[1]::[0]"                                   (execute [java/lang/Runnable] "io" void)) -                               (ffi.import: (java/util/concurrent/ScheduledFuture a) +                               (ffi.import (java/util/concurrent/ScheduledFuture a)                                   "[1]::[0]") -                               (ffi.import: java/util/concurrent/ScheduledThreadPoolExecutor +                               (ffi.import java/util/concurrent/ScheduledThreadPoolExecutor                                   "[1]::[0]"                                   (new [int])                                   (schedule [java/lang/Runnable long java/util/concurrent/TimeUnit] "io" (java/util/concurrent/ScheduledFuture java/lang/Object))))] @@ -57,10 +57,10 @@         @.jvm (these <jvm>)         @.js -       (these (ffi.import: (setTimeout [ffi.Function ffi.Number] "io" Any))) +       (these (ffi.import (setTimeout [ffi.Function ffi.Number] "io" Any)))         @.python -       (ffi.import: threading/Timer +       (ffi.import threading/Timer           "[1]::[0]"           (new [ffi.Float ffi.Function])           (start [] "io" "?" Any)) diff --git a/stdlib/source/library/lux/control/maybe.lux b/stdlib/source/library/lux/control/maybe.lux index dafd471d1..2e255a7ec 100644 --- a/stdlib/source/library/lux/control/maybe.lux +++ b/stdlib/source/library/lux/control/maybe.lux @@ -125,20 +125,21 @@    (All (_ M a) (-> (Monad M) (-> (M a) (M (Maybe a)))))    (at monad each (at ..monad in))) -(macro: .public (else tokens state) -  (case tokens -    (pattern (.list else maybe)) -    (let [g!temp (is Code [location.dummy {.#Symbol ["" ""]}])] -      {.#Right [state (.list (` (.case (~ maybe) -                                  {.#Some (~ g!temp)} -                                  (~ g!temp) - -                                  ... {.#None} -                                  (~ g!temp) -                                  (~ else))))]}) +(def: .public else +  (macro (_ tokens state) +    (case tokens +      (pattern (.list else maybe)) +      (let [g!temp (is Code [location.dummy {.#Symbol ["" ""]}])] +        {.#Right [state (.list (` (.case (~ maybe) +                                    {.#Some (~ g!temp)} +                                    (~ g!temp) + +                                    ... {.#None} +                                    (~ g!temp) +                                    (~ else))))]}) -    _ -    {.#Left "Wrong syntax for 'else'"})) +      _ +      {.#Left "Wrong syntax for 'else'"})))  (def: .public trusted    (All (_ a) (-> (Maybe a) a)) @@ -154,12 +155,13 @@      _      (.list))) -(macro: .public (when tokens state) -  (case tokens -    (pattern (.list test then)) -    {.#Right [state (.list (` (.if (~ test) -                                (~ then) -                                {.#None})))]} +(def: .public when +  (macro (_ tokens state) +    (case tokens +      (pattern (.list test then)) +      {.#Right [state (.list (` (.if (~ test) +                                  (~ then) +                                  {.#None})))]} -    _ -    {.#Left "Wrong syntax for 'when'"})) +      _ +      {.#Left "Wrong syntax for 'when'"}))) diff --git a/stdlib/source/library/lux/control/try.lux b/stdlib/source/library/lux/control/try.lux index 897ae0adf..563d7c114 100644 --- a/stdlib/source/library/lux/control/try.lux +++ b/stdlib/source/library/lux/control/try.lux @@ -138,30 +138,32 @@      {#Failure (`` (("lux in-module" (~~ (static .prelude_module)) .symbol#encoded)                     (symbol ..of_maybe)))})) -(macro: .public (else tokens compiler) -  (case tokens -    (pattern (list else try)) -    {#Success [compiler (list (` (case (~ try) -                                   {..#Success (~' g!temp)} -                                   (~' g!temp) +(def: .public else +  (macro (_ tokens compiler) +    (case tokens +      (pattern (list else try)) +      {#Success [compiler (list (` (case (~ try) +                                     {..#Success (~' g!temp)} +                                     (~' g!temp) + +                                     ... {..#Failure (~' g!temp)} +                                     (~' g!temp) +                                     (~ else))))]} -                                   ... {..#Failure (~' g!temp)} -                                   (~' g!temp) -                                   (~ else))))]} - -    _ -    {#Failure "Wrong syntax for 'else'"})) - -(macro: .public (when tokens state) -  (case tokens -    (pattern (.list test then)) -    (let [code#encoded ("lux in-module" "library/lux" .code#encoded) -          text$ ("lux in-module" "library/lux" .text$)] -      {.#Right [state (.list (` (.if (~ test) -                                  (~ then) -                                  {..#Failure (~ (text$ (all "lux text concat" -                                                             "[" (code#encoded (` .when)) "]" -                                                             " " "Invalid condition:")))})))]}) +      _ +      {#Failure "Wrong syntax for 'else'"}))) + +(def: .public when +  (macro (_ tokens state) +    (case tokens +      (pattern (.list test then)) +      (let [code#encoded ("lux in-module" "library/lux" .code#encoded) +            text$ ("lux in-module" "library/lux" .text$)] +        {.#Right [state (.list (` (.if (~ test) +                                    (~ then) +                                    {..#Failure (~ (text$ (all "lux text concat" +                                                               "[" (code#encoded (` .when)) "]" +                                                               " " "Invalid condition:")))})))]}) -    _ -    {.#Left "Wrong syntax for 'when'"})) +      _ +      {.#Left "Wrong syntax for 'when'"}))) diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux index ba1902276..d29b0889a 100644 --- a/stdlib/source/library/lux/data/collection/list.lux +++ b/stdlib/source/library/lux/data/collection/list.lux @@ -454,85 +454,87 @@          0 output'          _ (again input' output'))))) -(macro: .public (zipped tokens state) -  (case tokens -    (pattern (list [_ {.#Nat num_lists}])) -    (if (n.> 0 num_lists) -      (let [(open "[0]") ..functor -            indices (..indices num_lists) -            type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices)) -            zipped_type (` (.All ((~ (symbol$ "0_")) (~+ type_vars)) -                             (-> (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var))))) -                                           type_vars)) -                                 (List [(~+ type_vars)])))) -            vars+lists (|> indices -                           (each ++) -                           (each (function (_ idx) -                                   (let [base (nat#encoded idx)] -                                     [(symbol$ base) -                                      (symbol$ ("lux text concat" base "'"))])))) -            pattern (` [(~+ (each (function (_ [v vs]) (` {.#Item (~ v) (~ vs)})) -                                  vars+lists))]) -            g!step (symbol$ "0step0") -            g!blank (symbol$ "0,0") -            list_vars (each product.right vars+lists) -            code (` (is (~ zipped_type) -                        (function ((~ g!step) (~+ list_vars)) -                          (case [(~+ list_vars)] -                            (~ pattern) -                            {.#Item [(~+ (each product.left vars+lists))] -                                    ((~ g!step) (~+ list_vars))} - -                            (~ g!blank) -                            {.#End}))))] -        {.#Right [state (list code)]}) -      {.#Left "Cannot zipped 0 lists."}) - -    _ -    {.#Left "Wrong syntax for zipped"})) +(def: .public zipped +  (macro (_ tokens state) +    (case tokens +      (pattern (list [_ {.#Nat num_lists}])) +      (if (n.> 0 num_lists) +        (let [(open "[0]") ..functor +              indices (..indices num_lists) +              type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices)) +              zipped_type (` (.All ((~ (symbol$ "0_")) (~+ type_vars)) +                               (-> (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var))))) +                                             type_vars)) +                                   (List [(~+ type_vars)])))) +              vars+lists (|> indices +                             (each ++) +                             (each (function (_ idx) +                                     (let [base (nat#encoded idx)] +                                       [(symbol$ base) +                                        (symbol$ ("lux text concat" base "'"))])))) +              pattern (` [(~+ (each (function (_ [v vs]) (` {.#Item (~ v) (~ vs)})) +                                    vars+lists))]) +              g!step (symbol$ "0step0") +              g!blank (symbol$ "0,0") +              list_vars (each product.right vars+lists) +              code (` (is (~ zipped_type) +                          (function ((~ g!step) (~+ list_vars)) +                            (case [(~+ list_vars)] +                              (~ pattern) +                              {.#Item [(~+ (each product.left vars+lists))] +                                      ((~ g!step) (~+ list_vars))} + +                              (~ g!blank) +                              {.#End}))))] +          {.#Right [state (list code)]}) +        {.#Left "Cannot zipped 0 lists."}) + +      _ +      {.#Left "Wrong syntax for zipped"})))  (def: .public zipped_2 (zipped 2))  (def: .public zipped_3 (zipped 3)) -(macro: .public (zipped_with tokens state) -  (case tokens -    (pattern (list [_ {.#Nat num_lists}])) -    (if (n.> 0 num_lists) -      (let [(open "[0]") ..functor -            indices (..indices num_lists) -            g!return_type (symbol$ "0return_type0") -            g!func (symbol$ "0func0") -            type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices)) -            zipped_type (` (All ((~ (symbol$ "0_")) (~+ type_vars) (~ g!return_type)) -                             (-> (-> (~+ type_vars) (~ g!return_type)) -                                 (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var))))) -                                           type_vars)) -                                 (List (~ g!return_type))))) -            vars+lists (|> indices -                           (each ++) -                           (each (function (_ idx) -                                   (let [base (nat#encoded idx)] -                                     [(symbol$ base) -                                      (symbol$ ("lux text concat" base "'"))])))) -            pattern (` [(~+ (each (function (_ [v vs]) (` {.#Item (~ v) (~ vs)})) -                                  vars+lists))]) -            g!step (symbol$ "0step0") -            g!blank (symbol$ "0,0") -            list_vars (each product.right vars+lists) -            code (` (is (~ zipped_type) -                        (function ((~ g!step) (~ g!func) (~+ list_vars)) -                          (case [(~+ list_vars)] -                            (~ pattern) -                            {.#Item ((~ g!func) (~+ (each product.left vars+lists))) -                                    ((~ g!step) (~ g!func) (~+ list_vars))} - -                            (~ g!blank) -                            {.#End}))))] -        {.#Right [state (list code)]}) -      {.#Left "Cannot zipped_with 0 lists."}) - -    _ -    {.#Left "Wrong syntax for zipped_with"})) +(def: .public zipped_with +  (macro (_ tokens state) +    (case tokens +      (pattern (list [_ {.#Nat num_lists}])) +      (if (n.> 0 num_lists) +        (let [(open "[0]") ..functor +              indices (..indices num_lists) +              g!return_type (symbol$ "0return_type0") +              g!func (symbol$ "0func0") +              type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices)) +              zipped_type (` (All ((~ (symbol$ "0_")) (~+ type_vars) (~ g!return_type)) +                               (-> (-> (~+ type_vars) (~ g!return_type)) +                                   (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var))))) +                                             type_vars)) +                                   (List (~ g!return_type))))) +              vars+lists (|> indices +                             (each ++) +                             (each (function (_ idx) +                                     (let [base (nat#encoded idx)] +                                       [(symbol$ base) +                                        (symbol$ ("lux text concat" base "'"))])))) +              pattern (` [(~+ (each (function (_ [v vs]) (` {.#Item (~ v) (~ vs)})) +                                    vars+lists))]) +              g!step (symbol$ "0step0") +              g!blank (symbol$ "0,0") +              list_vars (each product.right vars+lists) +              code (` (is (~ zipped_type) +                          (function ((~ g!step) (~ g!func) (~+ list_vars)) +                            (case [(~+ list_vars)] +                              (~ pattern) +                              {.#Item ((~ g!func) (~+ (each product.left vars+lists))) +                                      ((~ g!step) (~ g!func) (~+ list_vars))} + +                              (~ g!blank) +                              {.#End}))))] +          {.#Right [state (list code)]}) +        {.#Left "Cannot zipped_with 0 lists."}) + +      _ +      {.#Left "Wrong syntax for zipped_with"})))  (def: .public zipped_with_2 (zipped_with 2))  (def: .public zipped_with_3 (zipped_with 3)) @@ -606,15 +608,16 @@        {.#Item x xs'}        {.#Item [idx x] (again (++ idx) xs')}))) -(macro: .public (when tokens state) -  (case tokens -    (pattern (.list test then)) -    {.#Right [state (.list (` (.if (~ test) -                                (~ then) -                                (.list))))]} +(def: .public when +  (macro (_ tokens state) +    (case tokens +      (pattern (.list test then)) +      {.#Right [state (.list (` (.if (~ test) +                                  (~ then) +                                  (.list))))]} -    _ -    {.#Left "Wrong syntax for when"})) +      _ +      {.#Left "Wrong syntax for when"})))  (def: .public (revised item revision it)    (All (_ a) (-> Nat (-> a a) (List a) (List a))) diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux index ecc17837e..8e9eccac7 100644 --- a/stdlib/source/library/lux/data/text.lux +++ b/stdlib/source/library/lux/data/text.lux @@ -184,29 +184,31 @@          [[pre post] (..split_by pattern template)]          (in (all "lux text concat" pre replacement post))))) -(for @.js (these (macro: (defined? tokens lux) -                   (case tokens -                     (pattern (list it)) -                     {.#Right [lux (list (` (.case ("js type-of" ("js constant" (~ it))) -                                              "undefined" -                                              .false - -                                              (~' _) -                                              .true)))]} - -                     _ -                     {.#Left ""})) -                 (macro: (if_nashorn tokens lux) -                   (case tokens -                     (pattern (list then else)) -                     {.#Right [lux (list (if (and (..defined? "java") -                                                  (..defined? "java.lang") -                                                  (..defined? "java.lang.Object")) -                                           then -                                           else))]} - -                     _ -                     {.#Left ""}))) +(for @.js (these (def: defined? +                   (macro (_ tokens lux) +                     (case tokens +                       (pattern (list it)) +                       {.#Right [lux (list (` (.case ("js type-of" ("js constant" (~ it))) +                                                "undefined" +                                                .false + +                                                (~' _) +                                                .true)))]} + +                       _ +                       {.#Left ""}))) +                 (def: if_nashorn +                   (macro (_ tokens lux) +                     (case tokens +                       (pattern (list then else)) +                       {.#Right [lux (list (if (and (..defined? "java") +                                                    (..defined? "java.lang") +                                                    (..defined? "java.lang.Object")) +                                             then +                                             else))]} + +                       _ +                       {.#Left ""}))))       (these))  (def: .public (replaced pattern replacement template) diff --git a/stdlib/source/library/lux/data/text/buffer.lux b/stdlib/source/library/lux/data/text/buffer.lux index 5658dcddb..b826a7753 100644 --- a/stdlib/source/library/lux/data/text/buffer.lux +++ b/stdlib/source/library/lux/data/text/buffer.lux @@ -2,7 +2,7 @@   [library    [lux (.except)     ["@" target] -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     [control      ["[0]" function]]     [data @@ -19,31 +19,31 @@      [primitive (.except)]]]]   ["[0]" //]) -(with_expansions [<jvm> (these (import: java/lang/CharSequence +(with_expansions [<jvm> (these (import java/lang/CharSequence                                   "[1]::[0]") -                               (import: java/lang/Appendable +                               (import java/lang/Appendable                                   "[1]::[0]"                                   (append [java/lang/CharSequence] java/lang/Appendable)) -                               (import: java/lang/String +                               (import java/lang/String                                   "[1]::[0]"                                   (new [int])                                   (toString [] java/lang/String)) -                               (import: java/lang/StringBuilder +                               (import java/lang/StringBuilder                                   "[1]::[0]"                                   (new [int])                                   (toString [] java/lang/String)))]    (`` (for @.old (these <jvm>)             @.jvm (these <jvm>) -           @.js (these (import: (JS_Array a) +           @.js (these (import (JS_Array a)                           "[1]::[0]"                           (push [a] a)                           (join [Text] Text))) -           @.lua (these (import: (table/concat [(array.Array Text) Text] Text)) +           @.lua (these (import (table/concat [(array.Array Text) Text] Text))                          ...https://www.lua.org/manual/5.3/manual.html#pdf-table.concat -                        (import: (table/insert [(array.Array Text) Text] "?" Nothing)) +                        (import (table/insert [(array.Array Text) Text] "?" Nothing))                          ... https://www.lua.org/manual/5.3/manual.html#pdf-table.insert                          )             (these)))) diff --git a/stdlib/source/library/lux/data/text/encoding/utf8.lux b/stdlib/source/library/lux/data/text/encoding/utf8.lux index 5ca733dda..91b2cdb36 100644 --- a/stdlib/source/library/lux/data/text/encoding/utf8.lux +++ b/stdlib/source/library/lux/data/text/encoding/utf8.lux @@ -11,7 +11,7 @@      ["[0]" binary (.only Binary)]]]]   ["[0]" //]) -(with_expansions [<jvm> (these (ffi.import: java/lang/String +(with_expansions [<jvm> (these (ffi.import java/lang/String                                   "[1]::[0]"                                   (new [[byte] java/lang/String])                                   (getBytes [java/lang/String] [byte])))] @@ -19,48 +19,48 @@         @.jvm (these <jvm>)         @.js -       (these (ffi.import: Uint8Array +       (these (ffi.import Uint8Array                  "[1]::[0]")                ... On Node -              (ffi.import: Buffer +              (ffi.import Buffer                  "[1]::[0]"                  ("static" from "as" from|encoded [ffi.String ffi.String] Buffer)                  ("static" from "as" from|decoded [Uint8Array] Buffer)                  (toString [ffi.String] ffi.String))                ... On the browser -              (ffi.import: TextEncoder +              (ffi.import TextEncoder                  "[1]::[0]"                  (new [ffi.String])                  (encode [ffi.String] Uint8Array)) -              (ffi.import: TextDecoder +              (ffi.import TextDecoder                  "[1]::[0]"                  (new [ffi.String])                  (decode [Uint8Array] ffi.String)))         @.ruby -       (these (ffi.import: String +       (these (ffi.import String                  "[1]::[0]"                  (encode [Text] String)                  (force_encoding [Text] Text)                  (bytes [] Binary)) -              (ffi.import: Array +              (ffi.import Array                  "[1]::[0]"                  (pack [Text] String)))         @.php -       (these (ffi.import: Almost_Binary) -              (ffi.import: (unpack [ffi.String ffi.String] Almost_Binary)) -              (ffi.import: (array_values [Almost_Binary] Binary)) +       (these (ffi.import Almost_Binary) +              (ffi.import (unpack [ffi.String ffi.String] Almost_Binary)) +              (ffi.import (array_values [Almost_Binary] Binary))                (def: php_byte_array_format "C*"))         @.scheme         ... https://srfi.schemers.org/srfi-140/srfi-140.html -       (these (ffi.import: (string->utf8 [Text] Binary)) -              (ffi.import: (utf8->string [Binary] Text))) +       (these (ffi.import (string->utf8 [Text] Binary)) +              (ffi.import (utf8->string [Binary] Text)))         (these)))  (def: (encoded value) diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux index ca5cc1e67..462f7a4bb 100644 --- a/stdlib/source/library/lux/debug.lux +++ b/stdlib/source/library/lux/debug.lux @@ -3,7 +3,7 @@    [lux (.except type private)     ["@" target]     ["[0]" type] -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     ["[0]" meta]     [abstract      ["[0]" monad (.only do)]] @@ -42,28 +42,28 @@      [month (.only Month)]      [day (.only Day)]]]]) -(with_expansions [<jvm> (these (import: java/lang/String +(with_expansions [<jvm> (these (import java/lang/String                                   "[1]::[0]") -                               (import: (java/lang/Class a) +                               (import (java/lang/Class a)                                   "[1]::[0]"                                   (getCanonicalName [] java/lang/String)) -                               (import: java/lang/Object +                               (import java/lang/Object                                   "[1]::[0]"                                   (new [])                                   (toString [] java/lang/String)                                   (getClass [] (java/lang/Class java/lang/Object))) -                               (import: java/lang/Integer +                               (import java/lang/Integer                                   "[1]::[0]"                                   (longValue [] long)) -                               (import: java/lang/Long +                               (import java/lang/Long                                   "[1]::[0]"                                   (intValue [] int)) -                               (import: java/lang/Number +                               (import java/lang/Number                                   "[1]::[0]"                                   (intValue [] int)                                   (longValue [] long) @@ -72,10 +72,10 @@         @.jvm (these <jvm>)         @.js -       (these (import: JSON +       (these (import JSON                  "[1]::[0]"                  ("static" stringify [.Any] ffi.String)) -              (import: Array +              (import Array                  "[1]::[0]"                  ("static" isArray [.Any] ffi.Boolean))) @@ -83,40 +83,40 @@         (these (type: PyType                  (Primitive "python_type")) -              (import: (type [.Any] PyType)) -              (import: (str [.Any] ffi.String))) +              (import (type [.Any] PyType)) +              (import (str [.Any] ffi.String)))         @.lua -       (these (import: (type [.Any] ffi.String)) -              (import: (tostring [.Any] ffi.String)) +       (these (import (type [.Any] ffi.String)) +              (import (tostring [.Any] ffi.String)) -              (import: math +              (import math                  "[1]::[0]"                  ("static" type [.Any] "?" ffi.String)))         @.ruby -       (these (import: Class +       (these (import Class                  "[1]::[0]") -              (import: Object +              (import Object                  "[1]::[0]"                  (class [] Class)                  (to_s [] ffi.String)))         @.php -       (these (import: (gettype [.Any] ffi.String)) -              (import: (strval [.Any] ffi.String))) +       (these (import (gettype [.Any] ffi.String)) +              (import (strval [.Any] ffi.String)))         @.scheme -       (these (import: (boolean? [.Any] Bit)) -              (import: (integer? [.Any] Bit)) -              (import: (real? [.Any] Bit)) -              (import: (string? [.Any] Bit)) -              (import: (vector? [.Any] Bit)) -              (import: (pair? [.Any] Bit)) -              (import: (car [.Any] .Any)) -              (import: (cdr [.Any] .Any)) -              (import: (format [Text .Any] Text))) +       (these (import (boolean? [.Any] Bit)) +              (import (integer? [.Any] Bit)) +              (import (real? [.Any] Bit)) +              (import (string? [.Any] Bit)) +              (import (vector? [.Any] Bit)) +              (import (pair? [.Any] Bit)) +              (import (car [.Any] .Any)) +              (import (cdr [.Any] .Any)) +              (import (format [Text .Any] Text)))         ))  (def: Inspector diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux index 297b11715..f578c11bb 100644 --- a/stdlib/source/library/lux/ffi.jvm.lux +++ b/stdlib/source/library/lux/ffi.jvm.lux @@ -1659,10 +1659,10 @@        {.#Left _}        (meta.failure (format "Unknown class: " class_name))))) -(syntax: .public (import: [declaration ..declaration^ -                           .let [[class_name class_type_vars] (parser.declaration declaration)] -                           import_format <code>.text -                           members (<>.some (..import_member_decl^ class_type_vars))]) +(syntax: .public (import [declaration ..declaration^ +                          .let [[class_name class_type_vars] (parser.declaration declaration)] +                          import_format <code>.text +                          members (<>.some (..import_member_decl^ class_type_vars))])    (do [! meta.monad]      [kind (class_kind declaration)       =members (|> members diff --git a/stdlib/source/library/lux/ffi.lux b/stdlib/source/library/lux/ffi.lux index 709ba8592..46475ae7d 100644 --- a/stdlib/source/library/lux/ffi.lux +++ b/stdlib/source/library/lux/ffi.lux @@ -557,8 +557,8 @@        (static_method_definition import! class alias namespace (the #member it))        (virtual_method_definition class alias namespace (the #member it)))) -  (syntax: .public (import: [host_module (<>.maybe <code>.text) -                             it ..import]) +  (syntax: .public (import [host_module (<>.maybe <code>.text) +                            it ..import])      (let [host_module_import! (is (List Code)                                    (case host_module                                      {.#Some host_module} diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux index 486f1ade4..1d2603f79 100644 --- a/stdlib/source/library/lux/ffi.old.lux +++ b/stdlib/source/library/lux/ffi.old.lux @@ -1611,9 +1611,9 @@        (meta.failure (format "Cannot load class: " class_name text.new_line                              error))))) -(syntax: .public (import: [class_decl ..class_decl^ -                           import_format <code>.text -                           members (<>.some (..import_member_decl^ (product.right class_decl)))]) +(syntax: .public (import [class_decl ..class_decl^ +                          import_format <code>.text +                          members (<>.some (..import_member_decl^ (product.right class_decl)))])    (do [! meta.monad]      [kind (class_kind class_decl)       =members (|> members diff --git a/stdlib/source/library/lux/ffi.php.lux b/stdlib/source/library/lux/ffi.php.lux index 9efd76f66..b07186a02 100644 --- a/stdlib/source/library/lux/ffi.php.lux +++ b/stdlib/source/library/lux/ffi.php.lux @@ -236,7 +236,7 @@                       (as ..Function (~ source))                       (~+ (list#each (with_null g!temp) g!inputs))))))))))) -(syntax: .public (import: [import ..import]) +(syntax: .public (import [import ..import])    (with_symbols [g!temp]      (case import        {#Class [class alias format members]} diff --git a/stdlib/source/library/lux/ffi.scm.lux b/stdlib/source/library/lux/ffi.scm.lux index c913bb20a..fc6107571 100644 --- a/stdlib/source/library/lux/ffi.scm.lux +++ b/stdlib/source/library/lux/ffi.scm.lux @@ -201,7 +201,7 @@                       (as ..Function (~ source))                       (~+ (list#each (with_nil g!temp) g!inputs))))))))))) -(syntax: .public (import: [import ..import]) +(syntax: .public (import [import ..import])    (with_symbols [g!temp]      (case import        {#Function [name alias inputsT io? try? outputT]} diff --git a/stdlib/source/library/lux/macro.lux b/stdlib/source/library/lux/macro.lux index 4df6e733d..a96545566 100644 --- a/stdlib/source/library/lux/macro.lux +++ b/stdlib/source/library/lux/macro.lux @@ -1,6 +1,6 @@  (.using   [library -  [lux (.except local symbol) +  [lux (.except local symbol function macro)     [abstract      ["[0]" monad (.only do)]]     [data @@ -115,20 +115,21 @@         (text.prefix (text#composite "Wrong syntax for " text.\''))         (text.suffix (text#composite text.\'' ".")))) -(macro: .public (with_symbols tokens) -  (case tokens -    (pattern (list [_ {.#Tuple symbols}] body)) -    (do [! //.monad] -      [symbol_names (monad.each ! ..local symbols) -       .let [symbol_defs (list#conjoint (list#each (is (-> Text (List Code)) -                                                       (function (_ name) (list (code.symbol ["" name]) (` (..symbol (~ (code.text name))))))) -                                                   symbol_names))]] -      (in (list (` ((~! do) (~! //.monad) -                    [(~+ symbol_defs)] -                    (~ body)))))) +(def: .public with_symbols +  (.macro (_ tokens) +    (case tokens +      (pattern (list [_ {.#Tuple symbols}] body)) +      (do [! //.monad] +        [symbol_names (monad.each ! ..local symbols) +         .let [symbol_defs (list#conjoint (list#each (is (-> Text (List Code)) +                                                         (.function (_ name) (list (code.symbol ["" name]) (` (..symbol (~ (code.text name))))))) +                                                     symbol_names))]] +        (in (list (` ((~! do) (~! //.monad) +                      [(~+ symbol_defs)] +                      (~ body)))))) -    _ -    (//.failure (..wrong_syntax_error (.symbol ..with_symbols))))) +      _ +      (//.failure (..wrong_syntax_error (.symbol ..with_symbols))))))  (def: .public (one_expansion token)    (-> Code (Meta Code)) @@ -142,62 +143,73 @@        (//.failure "Macro expanded to more than 1 element."))))  (template [<macro> <func>] -  [(macro: .public (<macro> tokens) -     (let [[module _] (.symbol .._) -           [_ short] (.symbol <macro>) -           macro_name [module short]] -       (case (is (Maybe [Bit Code]) -                 (case tokens -                   (pattern (list [_ {.#Text "omit"}] -                                  token)) -                   {.#Some [#1 token]} - -                   (pattern (list token)) -                   {.#Some [#0 token]} - -                   _ -                   {.#None})) -         {.#Some [omit? token]} -         (do //.monad -           [location //.location -            output (<func> token) -            .let [_ ("lux io log" (all text#composite (symbol#encoded macro_name) " " (location.format location))) -                  _ (list#each (|>> code.format "lux io log") -                               output) -                  _ ("lux io log" "")]] -           (in (if omit? -                 (list) -                 output))) - -         {.#None} -         (//.failure (..wrong_syntax_error macro_name)))))] +  [(def: .public <macro> +     (.macro (_ tokens) +       (let [[module _] (.symbol .._) +             [_ short] (.symbol <macro>) +             macro_name [module short]] +         (case (is (Maybe [Bit Code]) +                   (case tokens +                     (pattern (list [_ {.#Text "omit"}] +                                    token)) +                     {.#Some [#1 token]} + +                     (pattern (list token)) +                     {.#Some [#0 token]} + +                     _ +                     {.#None})) +           {.#Some [omit? token]} +           (do //.monad +             [location //.location +              output (<func> token) +              .let [_ ("lux io log" (all text#composite (symbol#encoded macro_name) " " (location.format location))) +                    _ (list#each (|>> code.format "lux io log") +                                 output) +                    _ ("lux io log" "")]] +             (in (if omit? +                   (list) +                   output))) + +           {.#None} +           (//.failure (..wrong_syntax_error macro_name))))))]    [log_single_expansion! ..single_expansion]    [log_expansion!        ..expansion]    [log_full_expansion!   ..full_expansion]    ) -(macro: .public (times tokens) -  (case tokens -    (pattern (partial_list [_ {.#Nat times}] terms)) -    (loop (again [times times -                  before terms]) -      (case times -        0 -        (at //.monad in before) - -        _ -        (do [! //.monad] -          [after (|> before -                     (monad.each ! ..single_expansion) -                     (at ! each list#conjoint))] -          (again (-- times) after)))) +(def: .public times +  (.macro (_ tokens) +    (case tokens +      (pattern (partial_list [_ {.#Nat times}] terms)) +      (loop (again [times times +                    before terms]) +        (case times +          0 +          (at //.monad in before) + +          _ +          (do [! //.monad] +            [after (|> before +                       (monad.each ! ..single_expansion) +                       (at ! each list#conjoint))] +            (again (-- times) after)))) -    _ -    (//.failure (..wrong_syntax_error (.symbol ..times))))) - -(macro: .public (final it) -  (let [! //.monad] -    (|> it -        (monad.each ! ..expansion) -        (at ! each list#conjoint)))) +      _ +      (//.failure (..wrong_syntax_error (.symbol ..times)))))) + +(def: .public final +  (.macro (_ it) +    (let [! //.monad] +      (|> it +          (monad.each ! ..expansion) +          (at ! each list#conjoint))))) + +(def: .public function +  (-> Macro Macro') +  (|>> (as Macro'))) + +(def: .public macro +  (-> Macro' Macro) +  (|>> (as Macro))) diff --git a/stdlib/source/library/lux/macro/pattern.lux b/stdlib/source/library/lux/macro/pattern.lux index 708d81a18..4e6811c93 100644 --- a/stdlib/source/library/lux/macro/pattern.lux +++ b/stdlib/source/library/lux/macro/pattern.lux @@ -2,15 +2,16 @@   [library    [lux (.except or template let |> `)]]) -(macro: (locally tokens lux) -  (.let [[prelude _] (symbol ._)] -    (case tokens -      (pattern (list [@ {.#Symbol ["" name]}])) -      {.#Right [lux (list (.` ("lux in-module" (~ [@ {.#Text prelude}]) -                               (~ [@ {.#Symbol [prelude name]}]))))]} +(def: locally +  (macro (_ tokens lux) +    (.let [[prelude _] (symbol ._)] +      (case tokens +        (pattern (list [@ {.#Symbol ["" name]}])) +        {.#Right [lux (list (.` ("lux in-module" (~ [@ {.#Text prelude}]) +                                 (~ [@ {.#Symbol [prelude name]}]))))]} -      _ -      {.#Left ""}))) +        _ +        {.#Left ""}))))  (.template [<name>]    [(def: <name> (..locally <name>))] @@ -68,103 +69,108 @@    [frac$]    ) -(macro: .public (or tokens) -  (case tokens -    (pattern (partial_list [_ {.#Form patterns}] body branches)) -    (case patterns -      {.#End} -      (failure (..wrong_syntax_error (symbol ..or))) +(def: .public or +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_ {.#Form patterns}] body branches)) +      (case patterns +        {.#End} +        (failure (..wrong_syntax_error (symbol ..or))) + +        _ +        (.let [pairs (.|> patterns +                          (list#each (function (_ pattern) (list pattern body))) +                          list#conjoint)] +          (meta#in (list#composite pairs branches)))) +      _ +      (failure (..wrong_syntax_error (symbol ..or)))))) +(def: .public template +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_ {.#Form (list [_ {.#Tuple bindings}] +                                              [_ {.#Tuple templates}])}] +                             [_ {.#Form data}] +                             branches)) +      (case (is (Maybe (List Code)) +                (do maybe_monad +                  [bindings' (monad#each maybe_monad symbol_short bindings) +                   data' (monad#each maybe_monad tuple_list data)] +                  (.let [num_bindings (list#size bindings')] +                    (if (every? (|>> ("lux i64 =" num_bindings)) +                                (list#each list#size data')) +                      (.let [apply (is (-> Replacement_Environment (List Code)) +                                       (function (_ env) (list#each (realized_template env) templates)))] +                        (.|> data' +                             (list#each (function#composite apply (replacement_environment bindings'))) +                             list#conjoint +                             in)) +                      {.#None})))) +        {.#Some output} +        (meta#in (list#composite output branches)) +         +        {.#None} +        (failure (..wrong_syntax_error (symbol ..template)))) +              _ -      (.let [pairs (.|> patterns -                        (list#each (function (_ pattern) (list pattern body))) -                        list#conjoint)] -        (meta#in (list#composite pairs branches)))) -    _ -    (failure (..wrong_syntax_error (symbol ..or))))) - -(macro: .public (template tokens) -  (case tokens -    (pattern (partial_list [_ {.#Form (list [_ {.#Tuple bindings}] -                                            [_ {.#Tuple templates}])}] -                           [_ {.#Form data}] -                           branches)) -    (case (is (Maybe (List Code)) -              (do maybe_monad -                [bindings' (monad#each maybe_monad symbol_short bindings) -                 data' (monad#each maybe_monad tuple_list data)] -                (.let [num_bindings (list#size bindings')] -                  (if (every? (|>> ("lux i64 =" num_bindings)) -                              (list#each list#size data')) -                    (.let [apply (is (-> Replacement_Environment (List Code)) -                                     (function (_ env) (list#each (realized_template env) templates)))] -                      (.|> data' -                           (list#each (function#composite apply (replacement_environment bindings'))) -                           list#conjoint -                           in)) -                    {.#None})))) -      {.#Some output} -      (meta#in (list#composite output branches)) +      (failure (..wrong_syntax_error (symbol ..template)))))) + +(def: .public multi +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_meta {.#Form levels}] body next_branches)) +      (do meta_monad +        [mlc (multi_level_case^ levels) +         .let [initial_bind? (case mlc +                               [[_ {.#Symbol _}] _] +                               #1 + +                               _ +                               #0)] +         expected ..expected_type +         g!temp (..generated_symbol "temp")] +        (in (list g!temp +                  (.` ({{.#Some (~ g!temp)} +                        (~ g!temp) + +                        {.#None} +                        (.case (~ g!temp) +                          (~+ next_branches))} +                       ("lux type check" {.#Apply (~ (type_code expected)) Maybe} +                        (.case (~ g!temp) +                          (~+ (multi_level_case$ g!temp [mlc body])) + +                          (~+ (if initial_bind? +                                (list) +                                (list g!temp (.` {.#None}))))))))))) -      {.#None} -      (failure (..wrong_syntax_error (symbol ..template)))) -     -    _ -    (failure (..wrong_syntax_error (symbol ..template))))) - -(macro: .public (multi tokens) -  (case tokens -    (pattern (partial_list [_meta {.#Form levels}] body next_branches)) -    (do meta_monad -      [mlc (multi_level_case^ levels) -       .let [initial_bind? (case mlc -                             [[_ {.#Symbol _}] _] -                             #1 - -                             _ -                             #0)] -       expected ..expected_type -       g!temp (..generated_symbol "temp")] -      (in (list g!temp -                (.` ({{.#Some (~ g!temp)} -                      (~ g!temp) - -                      {.#None} -                      (.case (~ g!temp) -                        (~+ next_branches))} -                     ("lux type check" {.#Apply (~ (type_code expected)) Maybe} -                      (.case (~ g!temp) -                        (~+ (multi_level_case$ g!temp [mlc body])) - -                        (~+ (if initial_bind? -                              (list) -                              (list g!temp (.` {.#None}))))))))))) -     -    _ -    (failure (..wrong_syntax_error (symbol ..multi))))) - -(macro: .public (let tokens) -  (case tokens -    (pattern (partial_list [_meta {.#Form (list [_ {.#Symbol ["" name]}] pattern)}] body branches)) -    (.let [g!whole (local$ name)] -      (meta#in (partial_list g!whole -                             (.` (case (~ g!whole) (~ pattern) (~ body))) -                             branches))) -     -    _ -    (failure (..wrong_syntax_error (symbol ..let))))) - -(macro: .public (|> tokens) -  (case tokens -    (pattern (partial_list [_meta {.#Form (list [_ {.#Symbol ["" name]}] [_ {.#Tuple steps}])}] body branches)) -    (.let [g!name (local$ name)] -      (meta#in (partial_list g!name -                             (.` (.let [(~ g!name) (.|> (~ g!name) (~+ steps))] -                                   (~ body))) -                             branches))) -     -    _ -    (failure (..wrong_syntax_error (symbol ..|>))))) +      _ +      (failure (..wrong_syntax_error (symbol ..multi)))))) + +(def: .public let +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_meta {.#Form (list [_ {.#Symbol ["" name]}] pattern)}] body branches)) +      (.let [g!whole (local$ name)] +        (meta#in (partial_list g!whole +                               (.` (case (~ g!whole) (~ pattern) (~ body))) +                               branches))) +       +      _ +      (failure (..wrong_syntax_error (symbol ..let)))))) + +(def: .public |> +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_meta {.#Form (list [_ {.#Symbol ["" name]}] [_ {.#Tuple steps}])}] body branches)) +      (.let [g!name (local$ name)] +        (meta#in (partial_list g!name +                               (.` (.let [(~ g!name) (.|> (~ g!name) (~+ steps))] +                                     (~ body))) +                               branches))) +       +      _ +      (failure (..wrong_syntax_error (symbol ..|>))))))  (def: (name$ [module name])    (-> Symbol Code) @@ -230,17 +236,18 @@         [.#Tuple ..untemplated_tuple])        ))) -(macro: .public (` tokens) -  (case tokens -    (pattern (partial_list [_meta {.#Form (list template)}] body branches)) -    (do meta_monad -      [pattern (untemplated_pattern template)] -      (in (partial_list pattern body branches))) +(def: .public ` +  (macro (_ tokens) +    (case tokens +      (pattern (partial_list [_meta {.#Form (list template)}] body branches)) +      (do meta_monad +        [pattern (untemplated_pattern template)] +        (in (partial_list pattern body branches))) -    (pattern (list template)) -    (do meta_monad -      [pattern (untemplated_pattern template)] -      (in (list pattern))) +      (pattern (list template)) +      (do meta_monad +        [pattern (untemplated_pattern template)] +        (in (list pattern))) -    _ -    (failure (..wrong_syntax_error (symbol ..`))))) +      _ +      (failure (..wrong_syntax_error (symbol ..`)))))) diff --git a/stdlib/source/library/lux/macro/syntax.lux b/stdlib/source/library/lux/macro/syntax.lux index baec61e09..d8f289bd6 100644 --- a/stdlib/source/library/lux/macro/syntax.lux +++ b/stdlib/source/library/lux/macro/syntax.lux @@ -52,52 +52,55 @@                         (</>.tuple (<>.some </>.any))))          </>.any))) -(macro: .public (syntax: tokens) -  (case (</>.result ..syntax tokens) -    {try.#Success [export_policy [name g!state args] body]} -    (with_symbols [g!tokens g!body g!error] -      (do [! meta.monad] -        [vars+parsers (case (list.pairs args) -                        {.#Some args} -                        (monad.each ! -                                    (is (-> [Code Code] (Meta [Code Code])) -                                        (function (_ [var parser]) -                                          (with_expansions [<default> (in [var -                                                                           (` ((~! ..self_documenting) (' (~ var)) -                                                                               (~ parser)))])] -                                            (case var -                                              [_ {.#Symbol ["" _]}] -                                              <default> +(def: .public syntax: +  (macro (_ tokens) +    (case (</>.result ..syntax tokens) +      {try.#Success [export_policy [name g!state args] body]} +      (with_symbols [g!tokens g!body g!error] +        (do [! meta.monad] +          [vars+parsers (case (list.pairs args) +                          {.#Some args} +                          (monad.each ! +                                      (is (-> [Code Code] (Meta [Code Code])) +                                          (function (_ [var parser]) +                                            (with_expansions [<default> (in [var +                                                                             (` ((~! ..self_documenting) (' (~ var)) +                                                                                 (~ parser)))])] +                                              (case var +                                                [_ {.#Symbol ["" _]}] +                                                <default> -                                              [_ {.#Symbol _}] -                                              (in [var parser]) +                                                [_ {.#Symbol _}] +                                                (in [var parser]) -                                              _ -                                              <default>)))) -                                    args) +                                                _ +                                                <default>)))) +                                      args) -                        _ -                        (meta.failure "Syntax pattern expects pairs of bindings and code-parsers.")) -         g!state (case g!state -                   {.#Some g!state} -                   (in (code.local g!state)) +                          _ +                          (meta.failure "Syntax pattern expects pairs of bindings and code-parsers.")) +           g!state (case g!state +                     {.#Some g!state} +                     (in (code.local g!state)) -                   {.#None} -                   (//.symbol "g!state")) -         this_module meta.current_module_name -         .let [error_msg (code.text (//.wrong_syntax_error [this_module name]))]] -        (in (list (` (.macro: (~ export_policy) ((~ (code.symbol ["" name])) (~ g!tokens) (~ g!state)) -                       (.case ((~! </>.result) -                               (is ((~! </>.Parser) (Meta (List Code))) -                                   ((~! do) (~! <>.monad) -                                    [(~+ (..un_paired vars+parsers))] -                                    ((~' in) (~ body)))) -                               (~ g!tokens)) -                         {try.#Success (~ g!body)} -                         ((~ g!body) (~ g!state)) +                     {.#None} +                     (//.symbol "g!state")) +           this_module meta.current_module_name +           .let [error_msg (code.text (//.wrong_syntax_error [this_module name])) +                 g!name (code.symbol ["" name])]] +          (in (list (` (.def: (~ export_policy) (~ g!name) +                         (.macro ((~ g!name) (~ g!tokens) (~ g!state)) +                           (.case ((~! </>.result) +                                   (is ((~! </>.Parser) (Meta (List Code))) +                                       ((~! do) (~! <>.monad) +                                        [(~+ (..un_paired vars+parsers))] +                                        ((~' in) (~ body)))) +                                   (~ g!tokens)) +                             {try.#Success (~ g!body)} +                             ((~ g!body) (~ g!state)) -                         {try.#Failure (~ g!error)} -                         {try.#Failure ((~! text.interposed) (~! text.new_line) (list (~ error_msg) (~ g!error)))}))))))) -     -    {try.#Failure error} -    (meta.failure (//.wrong_syntax_error (symbol ..syntax:))))) +                             {try.#Failure (~ g!error)} +                             {try.#Failure ((~! text.interposed) (~! text.new_line) (list (~ error_msg) (~ g!error)))})))))))) +       +      {try.#Failure error} +      (meta.failure (//.wrong_syntax_error (symbol ..syntax:)))))) diff --git a/stdlib/source/library/lux/macro/template.lux b/stdlib/source/library/lux/macro/template.lux index a7046844d..7bbc17e84 100644 --- a/stdlib/source/library/lux/macro/template.lux +++ b/stdlib/source/library/lux/macro/template.lux @@ -1,6 +1,6 @@  (.using   [library -  [lux (.except let local macro symbol) +  [lux (.except let local symbol macro)     ["[0]" meta]     [abstract      ["[0]" monad (.only do)]] diff --git a/stdlib/source/library/lux/math/number.lux b/stdlib/source/library/lux/math/number.lux index e3dfe5a3b..3f4fe8c9e 100644 --- a/stdlib/source/library/lux/math/number.lux +++ b/stdlib/source/library/lux/math/number.lux @@ -32,36 +32,37 @@    (text.replaced ..separator ""))  (template [<macro> <nat> <int> <rev> <frac> <error>] -  [(macro: .public (<macro> tokens state) -     (case tokens -       {.#Item [meta {.#Text repr'}] {.#End}} -       (if (..separator_prefixed? repr') -         {try.#Failure <error>} -         (let [repr (..without_separators repr')] -           (case (at <nat> decoded repr) -             {try.#Success value} -             {try.#Success [state (list [meta {.#Nat value}])]} +  [(def: .public <macro> +     (macro (_ tokens state) +       (case tokens +         {.#Item [meta {.#Text repr'}] {.#End}} +         (if (..separator_prefixed? repr') +           {try.#Failure <error>} +           (let [repr (..without_separators repr')] +             (case (at <nat> decoded repr) +               {try.#Success value} +               {try.#Success [state (list [meta {.#Nat value}])]} -             (^.multi {try.#Failure _} -                      [(at <int> decoded repr) -                       {try.#Success value}]) -             {try.#Success [state (list [meta {.#Int value}])]} +               (^.multi {try.#Failure _} +                        [(at <int> decoded repr) +                         {try.#Success value}]) +               {try.#Success [state (list [meta {.#Int value}])]} -             (^.multi {try.#Failure _} -                      [(at <rev> decoded repr) -                       {try.#Success value}]) -             {try.#Success [state (list [meta {.#Rev value}])]} +               (^.multi {try.#Failure _} +                        [(at <rev> decoded repr) +                         {try.#Success value}]) +               {try.#Success [state (list [meta {.#Rev value}])]} -             (^.multi {try.#Failure _} -                      [(at <frac> decoded repr) -                       {try.#Success value}]) -             {try.#Success [state (list [meta {.#Frac value}])]} +               (^.multi {try.#Failure _} +                        [(at <frac> decoded repr) +                         {try.#Success value}]) +               {try.#Success [state (list [meta {.#Frac value}])]} -             _ -             {try.#Failure <error>}))) +               _ +               {try.#Failure <error>}))) -       _ -       {try.#Failure <error>}))] +         _ +         {try.#Failure <error>})))]    [bin /nat.binary /int.binary /rev.binary /frac.binary "Invalid binary syntax."]    [oct /nat.octal  /int.octal  /rev.octal  /frac.octal  "Invalid octal syntax."] diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux index 093f352e0..884945642 100644 --- a/stdlib/source/library/lux/meta.lux +++ b/stdlib/source/library/lux/meta.lux @@ -1,6 +1,6 @@  (.using   [library -  [lux (.except type macro try) +  [lux (.except type try macro)     [abstract      [functor (.only Functor)]      [apply (.only Apply)] diff --git a/stdlib/source/library/lux/meta/location.lux b/stdlib/source/library/lux/meta/location.lux index c66147ba8..99d6ce252 100644 --- a/stdlib/source/library/lux/meta/location.lux +++ b/stdlib/source/library/lux/meta/location.lux @@ -18,18 +18,19 @@     .#line   0     .#column 0]) -(macro: .public (here tokens compiler) -  (case tokens -    {.#End} -    (let [location (the .#location compiler)] -      {.#Right [compiler -                (list (` (.is .Location -                              [.#module (~ [..dummy {.#Text (the .#module location)}]) -                               .#line (~ [..dummy {.#Nat (the .#line location)}]) -                               .#column (~ [..dummy {.#Nat (the .#column location)}])])))]}) - -    _ -    {.#Left (`` (("lux in-module" (~~ (static .prelude_module)) wrong_syntax_error) (symbol ..here)))})) +(def: .public here +  (macro (_ tokens compiler) +    (case tokens +      {.#End} +      (let [location (the .#location compiler)] +        {.#Right [compiler +                  (list (` (.is .Location +                                [.#module (~ [..dummy {.#Text (the .#module location)}]) +                                 .#line (~ [..dummy {.#Nat (the .#line location)}]) +                                 .#column (~ [..dummy {.#Nat (the .#column location)}])])))]}) + +      _ +      {.#Left (`` (("lux in-module" (~~ (static .prelude_module)) wrong_syntax_error) (symbol ..here)))})))  (def: .public (format it)    (-> Location Text) diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux index 5eb093897..e9cf5735d 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode.lux @@ -1,7 +1,7 @@  (.using   [library    [lux (.except Type Label int try except) -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     [abstract      [monoid (.only Monoid)]      [functor (.only Functor)] @@ -560,11 +560,11 @@        {try.#Failure _}        (..bytecode $0 $1 @_ _.ldc_w/string [index])))) -(import: java/lang/Float +(import java/lang/Float    "[1]::[0]"    ("static" floatToRawIntBits "manual" [float] int)) -(import: java/lang/Double +(import java/lang/Double    "[1]::[0]"    ("static" doubleToRawLongBits "manual" [double] long)) diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux index 0ce71dfb1..93b959f5d 100644 --- a/stdlib/source/library/lux/target/jvm/constant.lux +++ b/stdlib/source/library/lux/target/jvm/constant.lux @@ -2,7 +2,7 @@   [library    [lux (.except)     ["@" target] -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     [abstract      [monad (.only do)]      ["[0]" equivalence (.only Equivalence)]] @@ -62,7 +62,7 @@      (|>> representation //index.writer))    ) -(import: java/lang/Float +(import java/lang/Float    "[1]::[0]"    ("static" floatToRawIntBits "manual" [float] int)) @@ -78,7 +78,7 @@            ("jvm object cast" parameter)            ("jvm object cast" subject))))) -(import: java/lang/Double +(import java/lang/Double    "[1]::[0]"    ("static" doubleToRawLongBits [double] long)) diff --git a/stdlib/source/library/lux/target/jvm/loader.lux b/stdlib/source/library/lux/target/jvm/loader.lux index 8a9ef6df3..60b04fb84 100644 --- a/stdlib/source/library/lux/target/jvm/loader.lux +++ b/stdlib/source/library/lux/target/jvm/loader.lux @@ -2,7 +2,7 @@   [library    [lux (.except)     ["@" target] -   ["[0]" ffi (.only import: object do_to)] +   ["[0]" ffi (.only import object do_to)]     [abstract      [monad (.only do)]]     [control @@ -36,30 +36,30 @@     "Class" class     "Error" error)) -(import: java/lang/Object +(import java/lang/Object    "[1]::[0]"    (getClass [] (java/lang/Class java/lang/Object))) -(import: java/lang/String +(import java/lang/String    "[1]::[0]") -(import: java/lang/reflect/Method +(import java/lang/reflect/Method    "[1]::[0]"    (invoke [java/lang/Object [java/lang/Object]] "try" java/lang/Object)) -(import: (java/lang/Class a) +(import (java/lang/Class a)    "[1]::[0]"    (getDeclaredMethod [java/lang/String [(java/lang/Class [? < java/lang/Object])]] java/lang/reflect/Method)) -(import: java/lang/Integer +(import java/lang/Integer    "[1]::[0]"    ("static" TYPE (java/lang/Class java/lang/Integer))) -(import: java/lang/reflect/AccessibleObject +(import java/lang/reflect/AccessibleObject    "[1]::[0]"    (setAccessible [boolean] void)) -(import: java/lang/ClassLoader +(import java/lang/ClassLoader    "[1]::[0]"    (loadClass [java/lang/String]               "io" "try" (java/lang/Class java/lang/Object))) diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux index 4bc91291b..d903e9fa0 100644 --- a/stdlib/source/library/lux/target/jvm/reflection.lux +++ b/stdlib/source/library/lux/target/jvm/reflection.lux @@ -1,7 +1,7 @@  (.using   [library    [lux (.except Primitive type parameter) -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     ["[0]" type]     [abstract      ["[0]" monad (.only do)]] @@ -32,61 +32,61 @@     ["[1][0]" reflection]     ["[1][0]" parser]]]) -(import: java/lang/String +(import java/lang/String    "[1]::[0]") -(import: java/lang/Object +(import java/lang/Object    "[1]::[0]"    (toString [] java/lang/String)    (getClass [] (java/lang/Class java/lang/Object))) -(import: java/lang/reflect/Type +(import java/lang/reflect/Type    "[1]::[0]"    (getTypeName [] java/lang/String)) -(import: java/lang/reflect/GenericArrayType +(import java/lang/reflect/GenericArrayType    "[1]::[0]"    (getGenericComponentType [] java/lang/reflect/Type)) -(import: java/lang/reflect/ParameterizedType +(import java/lang/reflect/ParameterizedType    "[1]::[0]"    (getRawType [] java/lang/reflect/Type)    (getActualTypeArguments [] [java/lang/reflect/Type])) -(import: (java/lang/reflect/TypeVariable d) +(import (java/lang/reflect/TypeVariable d)    "[1]::[0]"    (getName [] java/lang/String)    (getBounds [] [java/lang/reflect/Type])) -(import: (java/lang/reflect/WildcardType d) +(import (java/lang/reflect/WildcardType d)    "[1]::[0]"    (getLowerBounds [] [java/lang/reflect/Type])    (getUpperBounds [] [java/lang/reflect/Type])) -(import: java/lang/reflect/Modifier +(import java/lang/reflect/Modifier    "[1]::[0]"    ("static" isStatic [int] boolean)    ("static" isFinal [int] boolean)    ("static" isInterface [int] boolean)    ("static" isAbstract [int] boolean)) -(import: java/lang/annotation/Annotation +(import java/lang/annotation/Annotation    "[1]::[0]") -(import: java/lang/Deprecated +(import java/lang/Deprecated    "[1]::[0]") -(import: java/lang/reflect/Field +(import java/lang/reflect/Field    "[1]::[0]"    (getDeclaringClass [] (java/lang/Class java/lang/Object))    (getModifiers [] int)    (getGenericType [] java/lang/reflect/Type)    (getDeclaredAnnotations [] [java/lang/annotation/Annotation])) -(import: java/lang/ClassLoader +(import java/lang/ClassLoader    "[1]::[0]") -(import: (java/lang/Class c) +(import (java/lang/Class c)    "[1]::[0]"    ("static" forName [java/lang/String boolean java/lang/ClassLoader] "try" (java/lang/Class java/lang/Object))    (getName [] java/lang/String) diff --git a/stdlib/source/library/lux/target/python.lux b/stdlib/source/library/lux/target/python.lux index ba1007f07..6ce709536 100644 --- a/stdlib/source/library/lux/target/python.lux +++ b/stdlib/source/library/lux/target/python.lux @@ -34,10 +34,10 @@    (-> Text Text)    (text.enclosed ["(" ")"])) -(for @.old (these (ffi.import: java/lang/CharSequence +(for @.old (these (ffi.import java/lang/CharSequence                      "[1]::[0]") -                  (ffi.import: java/lang/String +                  (ffi.import java/lang/String                      "[1]::[0]"                      (replace [java/lang/CharSequence java/lang/CharSequence] java/lang/String)))       (these)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index 2d0bee2fc..2b779791f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -1,7 +1,7 @@  (.using   [library    [lux (.except Type Module Primitive type char int) -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     ["[0]" meta]     [abstract      ["[0]" monad (.only do)] @@ -84,22 +84,22 @@          [module           [descriptor (.only Module)]]]]]]]]]) -(import: java/lang/ClassLoader +(import java/lang/ClassLoader    "[1]::[0]") -(import: java/lang/Object +(import java/lang/Object    "[1]::[0]"    (equals [java/lang/Object] boolean)) -(import: java/lang/reflect/Type +(import java/lang/reflect/Type    "[1]::[0]") -(import: (java/lang/reflect/TypeVariable d) +(import (java/lang/reflect/TypeVariable d)    "[1]::[0]"    (getName [] java/lang/String)    (getBounds [] [java/lang/reflect/Type])) -(import: java/lang/reflect/Modifier +(import java/lang/reflect/Modifier    "[1]::[0]"    ("static" isStatic [int] boolean)    ("static" isFinal [int] boolean) @@ -108,10 +108,10 @@    ("static" isPublic [int] boolean)    ("static" isProtected [int] boolean)) -(import: java/lang/annotation/Annotation +(import java/lang/annotation/Annotation    "[1]::[0]") -(import: java/lang/reflect/Method +(import java/lang/reflect/Method    "[1]::[0]"    (getName [] java/lang/String)    (getModifiers [] int) @@ -126,7 +126,7 @@    (getExceptionTypes [] [(java/lang/Class java/lang/Object)])    (getGenericExceptionTypes [] [java/lang/reflect/Type])) -(import: (java/lang/reflect/Constructor c) +(import (java/lang/reflect/Constructor c)    "[1]::[0]"    (getModifiers [] int)    (getDeclaringClass [] (java/lang/Class c)) @@ -136,7 +136,7 @@    (getGenericExceptionTypes [] [java/lang/reflect/Type])    (getDeclaredAnnotations [] [java/lang/annotation/Annotation])) -(import: (java/lang/Class c) +(import (java/lang/Class c)    "[1]::[0]"    ("static" forName [java/lang/String] "try" (java/lang/Class java/lang/Object))    (getName [] java/lang/String) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux index 5158193ae..c4392ff2a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux @@ -1,7 +1,7 @@  (.using   [library    [lux (.except Type Definition Primitive) -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     [abstract      ["[0]" monad (.only do)]]     [control @@ -963,7 +963,7 @@            _ (generation.log! (format "JVM Interface " (%.text name)))]           (in directive.no_requirements))))])) -(import: java/lang/ClassLoader +(import java/lang/ClassLoader    "[1]::[0]")  (def: .public (bundle class_loader extender) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux index ef7876953..359cfa04b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux @@ -1,7 +1,7 @@  (.using   [library    [lux (.except Definition) -   ["[0]" ffi (.only import: do_to object)] +   ["[0]" ffi (.only import do_to object)]     [abstract      [monad (.only do)]]     [control @@ -47,19 +47,19 @@    ["[1][0]" value]]   ) -(import: java/lang/reflect/Field +(import java/lang/reflect/Field    "[1]::[0]"    (get ["?" java/lang/Object] "try" "?" java/lang/Object)) -(import: (java/lang/Class a) +(import (java/lang/Class a)    "[1]::[0]"    (getField [java/lang/String] "try" java/lang/reflect/Field)) -(import: java/lang/Object +(import java/lang/Object    "[1]::[0]"    (getClass [] (java/lang/Class java/lang/Object))) -(import: java/lang/ClassLoader +(import java/lang/ClassLoader    "[1]::[0]")  (def: value::modifier (all modifier#composite field.public field.final field.static)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux index ee33cf415..21c740700 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux @@ -1,7 +1,7 @@  (.using   [library    [lux (.except i64) -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     [abstract      [monad (.only do)]]     [control @@ -80,7 +80,7 @@  (def: wrap_f64    (_.invokestatic $Double "valueOf" (type.method [(list) (list type.double) $Double (list)]))) -(import: java/lang/Double +(import java/lang/Double    "[1]::[0]"    ("static" doubleToRawLongBits "manual" [double] int)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux index 4ec4330d9..8b5adc004 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux @@ -183,7 +183,7 @@            )))  ... [[Numbers]] -(host.import: java/lang/Double +(host.import java/lang/Double    ("static" MIN_VALUE Double)    ("static" MAX_VALUE Double)) 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 545b80f70..6d4535137 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -1,7 +1,7 @@  (.using   [library    [lux (.except Module Definition) -   ["[0]" ffi (.only import: do_to)] +   ["[0]" ffi (.only import do_to)]     [abstract      ["[0]" monad (.only Monad do)]]     [control @@ -48,72 +48,72 @@          [jvm           ["[0]" runtime (.only Definition)]]]]]]]]]) -(import: java/lang/Object +(import java/lang/Object    "[1]::[0]") -(import: java/lang/String +(import java/lang/String    "[1]::[0]") -(import: java/util/jar/Attributes +(import java/util/jar/Attributes    "[1]::[0]"    (put [java/lang/Object java/lang/Object] "?" java/lang/Object)) -(import: java/util/jar/Attributes$Name +(import java/util/jar/Attributes$Name    "[1]::[0]"    ("static" MAIN_CLASS java/util/jar/Attributes$Name)    ("static" MANIFEST_VERSION java/util/jar/Attributes$Name)) -(import: java/util/jar/Manifest +(import java/util/jar/Manifest    "[1]::[0]"    (new [])    (getMainAttributes [] java/util/jar/Attributes)) -(import: java/io/Flushable +(import java/io/Flushable    "[1]::[0]"    (flush [] void)) -(import: java/io/Closeable +(import java/io/Closeable    "[1]::[0]"    (close [] void)) -(import: java/io/OutputStream +(import java/io/OutputStream    "[1]::[0]"    (write [[byte] int int] void)) -(import: java/io/ByteArrayOutputStream +(import java/io/ByteArrayOutputStream    "[1]::[0]"    (new [int])    (toByteArray [] [byte])) -(import: java/util/zip/ZipEntry +(import java/util/zip/ZipEntry    "[1]::[0]"    (getName [] java/lang/String)    (isDirectory [] boolean)    (getSize [] long)) -(import: java/util/zip/ZipOutputStream +(import java/util/zip/ZipOutputStream    "[1]::[0]"    (write [[byte] int int] void)    (closeEntry [] void)) -(import: java/util/jar/JarEntry +(import java/util/jar/JarEntry    "[1]::[0]"    (new [java/lang/String])) -(import: java/util/jar/JarOutputStream +(import java/util/jar/JarOutputStream    "[1]::[0]"    (new [java/io/OutputStream java/util/jar/Manifest])    (putNextEntry [java/util/zip/ZipEntry] "try" void)) -(import: java/io/ByteArrayInputStream +(import java/io/ByteArrayInputStream    "[1]::[0]"    (new [[byte]])) -(import: java/io/InputStream +(import java/io/InputStream    "[1]::[0]"    (read [[byte] int int] int)) -(import: java/util/jar/JarInputStream +(import java/util/jar/JarInputStream    "[1]::[0]"    (new [java/io/InputStream])    (getNextJarEntry [] "try" "?" java/util/jar/JarEntry)) diff --git a/stdlib/source/library/lux/world/console.lux b/stdlib/source/library/lux/world/console.lux index 27e59b14e..a996fc3ea 100644 --- a/stdlib/source/library/lux/world/console.lux +++ b/stdlib/source/library/lux/world/console.lux @@ -2,7 +2,7 @@   [library    [lux (.except)     ["@" target] -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     [abstract      [monad (.only do)]]     [control @@ -42,22 +42,22 @@  (exception: .public cannot_close) -(with_expansions [<jvm> (these (import: java/lang/String +(with_expansions [<jvm> (these (import java/lang/String                                   "[1]::[0]") -                               (import: java/io/Console +                               (import java/io/Console                                   "[1]::[0]"                                   (readLine [] "io" "try" java/lang/String)) -                               (import: java/io/InputStream +                               (import java/io/InputStream                                   "[1]::[0]"                                   (read [] "io" "try" int)) -                               (import: java/io/PrintStream +                               (import java/io/PrintStream                                   "[1]::[0]"                                   (print [java/lang/String] "io" "try" void)) -                               (import: java/lang/System +                               (import java/lang/System                                   "[1]::[0]"                                   ("static" console [] "io" "?" java/io/Console)                                   ("static" in java/io/InputStream) @@ -96,22 +96,22 @@                                                (|>> (exception.except ..cannot_close) in)))))))))]    (for @.old (these <jvm>)         @.jvm (these <jvm>) -       @.js (these (ffi.import: Buffer +       @.js (these (ffi.import Buffer                       "[1]::[0]"                       (toString [] ffi.String)) -                   (ffi.import: Readable_Stream +                   (ffi.import Readable_Stream                       "[1]::[0]"                       (read [] "?" Buffer)                       (unshift "as" unshift|String [ffi.String] ffi.Boolean)                       (unshift "as" unshift|Buffer [Buffer] ffi.Boolean)) -                   (ffi.import: Writable_Stream +                   (ffi.import Writable_Stream                       "[1]::[0]"                       (write [ffi.String ffi.Function] ffi.Boolean)                       (once [ffi.String ffi.Function] Any)) -                   (ffi.import: process +                   (ffi.import process                       "[1]::[0]"                       ("static" stdout Writable_Stream)                       ("static" stdin Readable_Stream)) diff --git a/stdlib/source/library/lux/world/db/jdbc.lux b/stdlib/source/library/lux/world/db/jdbc.lux index 53d1c80f6..9c64494ad 100644 --- a/stdlib/source/library/lux/world/db/jdbc.lux +++ b/stdlib/source/library/lux/world/db/jdbc.lux @@ -18,36 +18,36 @@     ["[0]" io (.only IO)]     [world      [net (.only URL)]] -   [host (.only import:)]]] +   [host (.only import)]]]   [//    ["[0]" sql]]   ["[0]" /    ["[1][0]" input (.only Input)]    ["[1][0]" output (.only Output)]]) -(import: java/lang/String) +(import java/lang/String) -(import: java/sql/ResultSet +(import java/sql/ResultSet    (getRow [] "try" int)    (next [] "try" boolean)    (close [] "io" "try" void)) -(import: java/sql/Statement +(import java/sql/Statement    ("static" NO_GENERATED_KEYS int)    ("static" RETURN_GENERATED_KEYS int)    (getGeneratedKeys [] "try" java/sql/ResultSet)    (close [] "io" "try" void)) -(import: java/sql/PreparedStatement +(import java/sql/PreparedStatement    (executeUpdate [] "io" "try" int)    (executeQuery [] "io" "try" java/sql/ResultSet)) -(import: java/sql/Connection +(import java/sql/Connection    (prepareStatement [java/lang/String int] "try" java/sql/PreparedStatement)    (isValid [int] "try" boolean)    (close [] "io" "try" void)) -(import: java/sql/DriverManager +(import java/sql/DriverManager    ("static" getConnection [java/lang/String java/lang/String java/lang/String] "io" "try" java/sql/Connection))  (type: .public Credentials diff --git a/stdlib/source/library/lux/world/db/jdbc/input.lux b/stdlib/source/library/lux/world/db/jdbc/input.lux index f3337227d..cf29414bd 100644 --- a/stdlib/source/library/lux/world/db/jdbc/input.lux +++ b/stdlib/source/library/lux/world/db/jdbc/input.lux @@ -1,7 +1,7 @@  (.using   [library    [lux (.except and int) -   [ffi (.only import:)] +   [ffi (.only import)]     [control      [functor (.only Contravariant)]      [monad (.only Monad do)] @@ -12,16 +12,16 @@     [world      [binary (.only Binary)]]]]) -(import: java/lang/String) +(import java/lang/String)  (template [<class>] -  [(import: <class> +  [(import <class>       (new [long]))]    [java/sql/Date] [java/sql/Time] [java/sql/Timestamp]    ) -(`` (import: java/sql/PreparedStatement +(`` (import java/sql/PreparedStatement        (~~ (template [<name> <type>]              [(<name> [int <type>] "try" void)] diff --git a/stdlib/source/library/lux/world/db/jdbc/output.lux b/stdlib/source/library/lux/world/db/jdbc/output.lux index 82c539da1..73d96d9f3 100644 --- a/stdlib/source/library/lux/world/db/jdbc/output.lux +++ b/stdlib/source/library/lux/world/db/jdbc/output.lux @@ -1,7 +1,7 @@  (.using   [library    [lux (.except and int) -   [ffi (.only import:)] +   [ffi (.only import)]     [control      [functor (.only Functor)]      [apply (.only Apply)] @@ -14,16 +14,16 @@     [world      [binary (.only Binary)]]]]) -(import: java/lang/String) +(import java/lang/String) -(import: java/util/Date +(import java/util/Date    (getTime [] long)) -(import: java/sql/Date) -(import: java/sql/Time) -(import: java/sql/Timestamp) +(import java/sql/Date) +(import java/sql/Time) +(import java/sql/Timestamp) -(`` (import: java/sql/ResultSet +(`` (import java/sql/ResultSet        (~~ (template [<method_name> <return_class>]              [(<method_name> [int] "try" <return_class>)] diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux index 4918001c8..cfbc7ce2c 100644 --- a/stdlib/source/library/lux/world/file.lux +++ b/stdlib/source/library/lux/world/file.lux @@ -157,10 +157,10 @@    [cannot_find_directory]    ) -(with_expansions [<for_jvm> (these (ffi.import: java/lang/String +(with_expansions [<for_jvm> (these (ffi.import java/lang/String                                       "[1]::[0]") -                                   (`` (ffi.import: java/io/File +                                   (`` (ffi.import java/io/File                                           "[1]::[0]"                                           (new [java/lang/String])                                           (~~ (template [<name>] @@ -179,24 +179,24 @@                                           (setLastModified [long] "io" "try" boolean)                                           ("static" separator java/lang/String))) -                                   (ffi.import: java/lang/AutoCloseable +                                   (ffi.import java/lang/AutoCloseable                                       "[1]::[0]"                                       (close [] "io" "try" void)) -                                   (ffi.import: java/io/OutputStream +                                   (ffi.import java/io/OutputStream                                       "[1]::[0]"                                       (write [[byte]] "io" "try" void)                                       (flush [] "io" "try" void)) -                                   (ffi.import: java/io/FileOutputStream +                                   (ffi.import java/io/FileOutputStream                                       "[1]::[0]"                                       (new [java/io/File boolean] "io" "try")) -                                   (ffi.import: java/io/InputStream +                                   (ffi.import java/io/InputStream                                       "[1]::[0]"                                       (read [[byte]] "io" "try" int)) -                                   (ffi.import: java/io/FileInputStream +                                   (ffi.import java/io/FileInputStream                                       "[1]::[0]"                                       (new [java/io/File] "io" "try")) @@ -303,28 +303,28 @@         @.jvm (these <for_jvm>)         @.js -       (these (ffi.import: Buffer +       (these (ffi.import Buffer                  "[1]::[0]"                  ("static" from [Binary] ..Buffer)) -              (ffi.import: FileDescriptor +              (ffi.import FileDescriptor                  "[1]::[0]") -              (ffi.import: Stats +              (ffi.import Stats                  "[1]::[0]"                  (size ffi.Number)                  (mtimeMs ffi.Number)                  (isFile [] ffi.Boolean)                  (isDirectory [] ffi.Boolean)) -              (ffi.import: FsConstants +              (ffi.import FsConstants                  "[1]::[0]"                  (F_OK ffi.Number)                  (R_OK ffi.Number)                  (W_OK ffi.Number)                  (X_OK ffi.Number)) -              (ffi.import: Error +              (ffi.import Error                  "[1]::[0]"                  (toString [] ffi.String)) @@ -336,7 +336,7 @@                         <body>                         <read>)))]) -              (ffi.import: Fs +              (ffi.import Fs                  "[1]::[0]"                  (constants FsConstants)                  (readFile [ffi.String ffi.Function] Any) @@ -369,7 +369,7 @@                        {try.#Success (as_expected datum)}                        {try.#Failure (Error::toString error)}))) -              (ffi.import: JsPath +              (ffi.import JsPath                  "[1]::[0]"                  (sep ffi.String)) @@ -512,16 +512,16 @@         (these (type: (Tuple/2 left right)                  (Primitive "python_tuple[2]" [left right])) -              (ffi.import: PyFile +              (ffi.import PyFile                  "[1]::[0]"                  (read [] "io" "try" Binary)                  (write [Binary] "io" "try" "?" Any)                  (close [] "io" "try" "?" Any)) -              (ffi.import: (open [ffi.String ffi.String] "io" "try" PyFile)) -              (ffi.import: (tuple [[ffi.Integer ffi.Integer]] (Tuple/2 ffi.Integer ffi.Integer))) +              (ffi.import (open [ffi.String ffi.String] "io" "try" PyFile)) +              (ffi.import (tuple [[ffi.Integer ffi.Integer]] (Tuple/2 ffi.Integer ffi.Integer))) -              (ffi.import: os +              (ffi.import os                  "[1]::[0]"                  ("static" F_OK ffi.Integer)                  ("static" R_OK ffi.Integer) @@ -536,7 +536,7 @@                  ("static" utime [ffi.String (Tuple/2 ffi.Integer ffi.Integer)] "io" "try" "?" Any)                  ("static" listdir [ffi.String] "io" "try" (Array ffi.String))) -              (ffi.import: os/path +              (ffi.import os/path                  "[1]::[0]"                  ("static" isfile [ffi.String] "io" "try" ffi.Boolean)                  ("static" isdir [ffi.String] "io" "try" ffi.Boolean) @@ -630,18 +630,18 @@                      )))         @.ruby -       (these (ffi.import: Time +       (these (ffi.import Time                  "[1]::[0]"                  ("static" at [Frac] Time)                  (to_f [] Frac)) -              (ffi.import: Stat +              (ffi.import Stat                  "[1]::[0]"                  (executable? [] Bit)                  (size Int)                  (mtime [] Time)) -              (ffi.import: File "as" RubyFile +              (ffi.import File "as" RubyFile                  "[1]::[0]"                  ("static" SEPARATOR ffi.String)                  ("static" open [Path ffi.String] "io" "try" RubyFile) @@ -656,14 +656,14 @@                  (flush [] "io" "try" "?" Any)                  (close [] "io" "try" "?" Any)) -              (ffi.import: Dir +              (ffi.import Dir                  "[1]::[0]"                  ("static" open [Path] "io" "try" Dir)                  (children [] "io" "try" (Array Path))                  (close [] "io" "try" "?" Any)) -              (ffi.import: "fileutils" FileUtils +              (ffi.import "fileutils" FileUtils                  "[1]::[0]"                  ("static" move [Path Path] "io" "try" "?" Any)                  ("static" rmdir [Path] "io" "try" "?" Any) @@ -777,34 +777,34 @@                      )))         ... @.php -       ... (these (ffi.import: (FILE_APPEND Int)) +       ... (these (ffi.import (FILE_APPEND Int))         ...        ... https://www.php.net/manual/en/dir.constants.php -       ...        (ffi.import: (DIRECTORY_SEPARATOR ffi.String)) +       ...        (ffi.import (DIRECTORY_SEPARATOR ffi.String))         ...        ... https://www.php.net/manual/en/function.pack.php         ...        ... https://www.php.net/manual/en/function.unpack.php -       ...        (ffi.import: (unpack [ffi.String ffi.String] Binary)) +       ...        (ffi.import (unpack [ffi.String ffi.String] Binary))         ...        ... https://www.php.net/manual/en/ref.filesystem.php         ...        ... https://www.php.net/manual/en/function.file-get-contents.php -       ...        (ffi.import: (file_get_contents [Path] "io" "try" ffi.String)) +       ...        (ffi.import (file_get_contents [Path] "io" "try" ffi.String))         ...        ... https://www.php.net/manual/en/function.file-put-contents.php -       ...        (ffi.import: (file_put_contents [Path ffi.String Int] "io" "try" ffi.Integer)) -       ...        (ffi.import: (filemtime [Path] "io" "try" ffi.Integer)) -       ...        (ffi.import: (filesize [Path] "io" "try" ffi.Integer)) -       ...        (ffi.import: (is_executable [Path] "io" "try" ffi.Boolean)) -       ...        (ffi.import: (touch [Path ffi.Integer] "io" "try" ffi.Boolean)) -       ...        (ffi.import: (rename [Path Path] "io" "try" ffi.Boolean)) -       ...        (ffi.import: (unlink [Path] "io" "try" ffi.Boolean)) +       ...        (ffi.import (file_put_contents [Path ffi.String Int] "io" "try" ffi.Integer)) +       ...        (ffi.import (filemtime [Path] "io" "try" ffi.Integer)) +       ...        (ffi.import (filesize [Path] "io" "try" ffi.Integer)) +       ...        (ffi.import (is_executable [Path] "io" "try" ffi.Boolean)) +       ...        (ffi.import (touch [Path ffi.Integer] "io" "try" ffi.Boolean)) +       ...        (ffi.import (rename [Path Path] "io" "try" ffi.Boolean)) +       ...        (ffi.import (unlink [Path] "io" "try" ffi.Boolean))         ...        ... https://www.php.net/manual/en/function.rmdir.php -       ...        (ffi.import: (rmdir [Path] "io" "try" ffi.Boolean)) +       ...        (ffi.import (rmdir [Path] "io" "try" ffi.Boolean))         ...        ... https://www.php.net/manual/en/function.scandir.php -       ...        (ffi.import: (scandir [Path] "io" "try" (Array Path))) +       ...        (ffi.import (scandir [Path] "io" "try" (Array Path)))         ...        ... https://www.php.net/manual/en/function.is-file.php -       ...        (ffi.import: (is_file [Path] "io" "try" ffi.Boolean)) +       ...        (ffi.import (is_file [Path] "io" "try" ffi.Boolean))         ...        ... https://www.php.net/manual/en/function.is-dir.php -       ...        (ffi.import: (is_dir [Path] "io" "try" ffi.Boolean)) +       ...        (ffi.import (is_dir [Path] "io" "try" ffi.Boolean))         ...        ... https://www.php.net/manual/en/function.mkdir.php -       ...        (ffi.import: (mkdir [Path] "io" "try" ffi.Boolean)) +       ...        (ffi.import (mkdir [Path] "io" "try" ffi.Boolean))         ...        (def: byte_array_format "C*")         ...        (def: default_separator (..DIRECTORY_SEPARATOR)) diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux index edc65be2f..5b23bf373 100644 --- a/stdlib/source/library/lux/world/file/watch.lux +++ b/stdlib/source/library/lux/world/file/watch.lux @@ -2,7 +2,7 @@   [library    [lux (.except all)     ["@" target] -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     [abstract      [predicate (.only Predicate)]      ["[0]" monad (.only do)]] @@ -262,13 +262,13 @@      [fs       (..polling fs)])) -(with_expansions [<jvm> (these (import: java/lang/Object +(with_expansions [<jvm> (these (import java/lang/Object                                   "[1]::[0]") -                               (import: java/lang/String +                               (import java/lang/String                                   "[1]::[0]") -                               (import: (java/util/List a) +                               (import (java/util/List a)                                   "[1]::[0]"                                   (size [] int)                                   (get [int] a)) @@ -284,22 +284,22 @@                                                        output})                                         output)))) -                               (import: (java/nio/file/WatchEvent$Kind a) +                               (import (java/nio/file/WatchEvent$Kind a)                                   "[1]::[0]") -                               (import: (java/nio/file/WatchEvent a) +                               (import (java/nio/file/WatchEvent a)                                   "[1]::[0]"                                   (kind [] (java/nio/file/WatchEvent$Kind a))) -                               (import: java/nio/file/Watchable +                               (import java/nio/file/Watchable                                   "[1]::[0]") -                               (import: java/nio/file/Path +                               (import java/nio/file/Path                                   "[1]::[0]"                                   (register [java/nio/file/WatchService [(java/nio/file/WatchEvent$Kind [? < java/lang/Object])]] "io" "try" java/nio/file/WatchKey)                                   (toString [] java/lang/String)) -                               (import: java/nio/file/StandardWatchEventKinds +                               (import java/nio/file/StandardWatchEventKinds                                   "[1]::[0]"                                   ("static" ENTRY_CREATE (java/nio/file/WatchEvent$Kind java/nio/file/Path))                                   ("static" ENTRY_MODIFY (java/nio/file/WatchEvent$Kind java/nio/file/Path)) @@ -326,7 +326,7 @@                                           ..none                                           ))) -                               (import: java/nio/file/WatchKey +                               (import java/nio/file/WatchKey                                   "[1]::[0]"                                   (reset [] "io" boolean)                                   (cancel [] "io" void) @@ -340,19 +340,19 @@                                                               (list#each default_event_concern)                                                               (list#mix ..also ..none))))) -                               (import: java/nio/file/WatchService +                               (import java/nio/file/WatchService                                   "[1]::[0]"                                   (poll [] "io" "try" "?" java/nio/file/WatchKey)) -                               (import: java/nio/file/FileSystem +                               (import java/nio/file/FileSystem                                   "[1]::[0]"                                   (newWatchService [] "io" "try" java/nio/file/WatchService)) -                               (import: java/nio/file/FileSystems +                               (import java/nio/file/FileSystems                                   "[1]::[0]"                                   ("static" getDefault [] java/nio/file/FileSystem)) -                               (import: java/io/File +                               (import java/io/File                                   "[1]::[0]"                                   (new [java/lang/String])                                   (toPath [] java/nio/file/Path)) diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux index f2e709dbd..447537f95 100644 --- a/stdlib/source/library/lux/world/net/http/client.lux +++ b/stdlib/source/library/lux/world/net/http/client.lux @@ -69,22 +69,22 @@    (-> Binary [Nat Binary])    [(binary.size data) data]) -(with_expansions [<jvm> (these (ffi.import: java/lang/String +(with_expansions [<jvm> (these (ffi.import java/lang/String                                   "[1]::[0]") -                               (ffi.import: java/lang/AutoCloseable +                               (ffi.import java/lang/AutoCloseable                                   "[1]::[0]"                                   (close [] "io" "try" void)) -                               (ffi.import: java/io/InputStream +                               (ffi.import java/io/InputStream                                   "[1]::[0]") -                               (ffi.import: java/io/OutputStream +                               (ffi.import java/io/OutputStream                                   "[1]::[0]"                                   (flush [] "io" "try" void)                                   (write [[byte]] "io" "try" void)) -                               (ffi.import: java/net/URLConnection +                               (ffi.import java/net/URLConnection                                   "[1]::[0]"                                   (setDoOutput [boolean] "io" "try" void)                                   (setRequestProperty [java/lang/String java/lang/String] "io" "try" void) @@ -93,17 +93,17 @@                                   (getHeaderFieldKey [int] "io" "try" "?" java/lang/String)                                   (getHeaderField [int] "io" "try" "?" java/lang/String)) -                               (ffi.import: java/net/HttpURLConnection +                               (ffi.import java/net/HttpURLConnection                                   "[1]::[0]"                                   (setRequestMethod [java/lang/String] "io" "try" void)                                   (getResponseCode [] "io" "try" int)) -                               (ffi.import: java/net/URL +                               (ffi.import java/net/URL                                   "[1]::[0]"                                   (new [java/lang/String])                                   (openConnection [] "io" "try" java/net/URLConnection)) -                               (ffi.import: java/io/BufferedInputStream +                               (ffi.import java/io/BufferedInputStream                                   "[1]::[0]"                                   (new [java/io/InputStream])                                   (read [[byte] int int] "io" "try" int)) diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux index 985199c64..9afde4c87 100644 --- a/stdlib/source/library/lux/world/program.lux +++ b/stdlib/source/library/lux/world/program.lux @@ -23,7 +23,7 @@                 ["[0]" array (.only Array)]                 ["[0]" dictionary (.only Dictionary)]                 ["[0]" list (.open: "[1]#[0]" functor)]]] -             ["[0]" ffi (.only import:) +             ["[0]" ffi (.only import)                (~~ (.for "JavaScript" (~~ (.these ["[0]" node_js]))                          "{old}" (~~ (.these ["node_js" //math]))                          (~~ (.these))))] @@ -113,23 +113,23 @@  ... Do not trust the values of environment variables  ... https://wiki.sei.cmu.edu/confluence/display/java/ENV02-J.+Do+not+trust+the+values+of+environment+variables -(with_expansions [<jvm> (these (import: java/lang/String +(with_expansions [<jvm> (these (import java/lang/String                                   "[1]::[0]") -                               (import: (java/util/Iterator a) +                               (import (java/util/Iterator a)                                   "[1]::[0]"                                   (hasNext [] boolean)                                   (next [] a)) -                               (import: (java/util/Set a) +                               (import (java/util/Set a)                                   "[1]::[0]"                                   (iterator [] (java/util/Iterator a))) -                               (import: (java/util/Map k v) +                               (import (java/util/Map k v)                                   "[1]::[0]"                                   (keySet [] (java/util/Set k))) -                               (import: java/lang/System +                               (import java/lang/System                                   "[1]::[0]"                                   ("static" getenv [] (java/util/Map java/lang/String java/lang/String))                                   ("static" getenv "as" resolveEnv [java/lang/String] "io" "?" java/lang/String) @@ -149,7 +149,7 @@                       (-> Exit (IO Nothing))                       (|>> %.int panic! io.io)) -                   (import: NodeJs_Process +                   (import NodeJs_Process                       "[1]::[0]"                       (exit [ffi.Number] "io" Nothing)                       (cwd [] "io" Path)) @@ -163,11 +163,11 @@                         {.#None}                         (..default_exit! code))) -                   (import: Browser_Window +                   (import Browser_Window                       "[1]::[0]"                       (close [] Nothing)) -                   (import: Browser_Location +                   (import Browser_Location                       "[1]::[0]"                       (reload [] Nothing)) @@ -194,34 +194,34 @@                         [{.#None} {.#None}]                         (..default_exit! code))) -                   (import: Object +                   (import Object                       "[1]::[0]"                       ("static" entries [Object] (Array (Array ffi.String)))) -                   (import: NodeJs_OS +                   (import NodeJs_OS                       "[1]::[0]"                       (homedir [] "io" Path))) -       @.python (these (import: os +       @.python (these (import os                           "[1]::[0]"                           ("static" getcwd [] "io" ffi.String)                           ("static" _exit [ffi.Integer] "io" Nothing)) -                       (import: os/path +                       (import os/path                           "[1]::[0]"                           ("static" expanduser [ffi.String] "io" ffi.String)) -                       (import: os/environ +                       (import os/environ                           "[1]::[0]"                           ("static" keys [] "io" (Array ffi.String))                           ("static" get [ffi.String] "io" "?" ffi.String))) -       @.lua (these (ffi.import: LuaFile +       @.lua (these (ffi.import LuaFile                        "[1]::[0]"                        (read [ffi.String] "io" "?" ffi.String)                        (close [] "io" ffi.Boolean)) -                    (ffi.import: (io/popen [ffi.String] "io" "try" "?" LuaFile)) -                    (ffi.import: (os/getenv [ffi.String] "io" "?" ffi.String)) -                    (ffi.import: (os/exit [ffi.Integer] "io" Nothing)) +                    (ffi.import (io/popen [ffi.String] "io" "try" "?" LuaFile)) +                    (ffi.import (os/getenv [ffi.String] "io" "?" ffi.String)) +                    (ffi.import (os/exit [ffi.Integer] "io" Nothing))                      (def: (run_command default command)                        (-> Text Text (IO Text)) @@ -241,45 +241,45 @@                            {try.#Failure _}                            (in default))))) -       @.ruby (these (ffi.import: Env +       @.ruby (these (ffi.import Env                         "[1]::[0]"                         ("static" keys [] (Array Text))                         ("static" fetch [Text] "io" "?" Text)) -                     (ffi.import: "fileutils" FileUtils +                     (ffi.import "fileutils" FileUtils                         "[1]::[0]"                         ("static" pwd Path)) -                     (ffi.import: Dir +                     (ffi.import Dir                         "[1]::[0]"                         ("static" home Path)) -                     (ffi.import: Kernel +                     (ffi.import Kernel                         "[1]::[0]"                         ("static" exit [Int] "io" Nothing)))         ... @.php -       ... (these (ffi.import: (exit [Int] "io" Nothing)) +       ... (these (ffi.import (exit [Int] "io" Nothing))         ...        ... https://www.php.net/manual/en/function.exit.php -       ...        (ffi.import: (getcwd [] "io" ffi.String)) +       ...        (ffi.import (getcwd [] "io" ffi.String))         ...        ... https://www.php.net/manual/en/function.getcwd.php -       ...        (ffi.import: (getenv "as" getenv/1 [ffi.String] "io" ffi.String)) -       ...        (ffi.import: (getenv "as" getenv/0 [] "io" (Array ffi.String))) +       ...        (ffi.import (getenv "as" getenv/1 [ffi.String] "io" ffi.String)) +       ...        (ffi.import (getenv "as" getenv/0 [] "io" (Array ffi.String)))         ...        ... https://www.php.net/manual/en/function.getenv.php         ...        ... https://www.php.net/manual/en/function.array-keys.php -       ...        (ffi.import: (array_keys [(Array ffi.String)] (Array ffi.String))) +       ...        (ffi.import (array_keys [(Array ffi.String)] (Array ffi.String)))         ...        )         ... @.scheme -       ... (these (ffi.import: (exit [Int] "io" Nothing)) +       ... (these (ffi.import (exit [Int] "io" Nothing))         ...        ... https://srfi.schemers.org/srfi-98/srfi-98.html         ...        (abstract: Pair Any)         ...        (abstract: PList Any) -       ...        (ffi.import: (get-environment-variables [] "io" PList)) -       ...        (ffi.import: (car [Pair] Text)) -       ...        (ffi.import: (cdr [Pair] Text)) -       ...        (ffi.import: (car "as" head [PList] Pair)) -       ...        (ffi.import: (cdr "as" tail [PList] PList))) +       ...        (ffi.import (get-environment-variables [] "io" PList)) +       ...        (ffi.import (car [Pair] Text)) +       ...        (ffi.import (cdr [Pair] Text)) +       ...        (ffi.import (car "as" head [PList] Pair)) +       ...        (ffi.import (cdr "as" tail [PList] PList)))         (these))) diff --git a/stdlib/source/library/lux/world/shell.lux b/stdlib/source/library/lux/world/shell.lux index 4493832ae..f65320c2d 100644 --- a/stdlib/source/library/lux/world/shell.lux +++ b/stdlib/source/library/lux/world/shell.lux @@ -2,7 +2,7 @@   [library    [lux (.except)     ["@" target] -   ["[0]" ffi (.only import:)] +   ["[0]" ffi (.only import)]     [abstract      [monad (.only do)]]     [control @@ -170,7 +170,7 @@                                 (text.enclosed' text.double_quote)))]      (..policy safe_command safe_argument))) -(with_expansions [<jvm> (these (import: java/lang/String +(with_expansions [<jvm> (these (import java/lang/String                                   "[1]::[0]"                                   (toLowerCase [] java/lang/String)) @@ -184,7 +184,7 @@                                              [0 (ffi.array java/lang/String (list.size arguments))]                                              arguments))) -                               (import: (java/util/Map k v) +                               (import (java/util/Map k v)                                   "[1]::[0]"                                   (put [k v] v)) @@ -201,27 +201,27 @@                                             target                                             (dictionary.entries input))) -                               (import: java/io/Reader +                               (import java/io/Reader                                   "[1]::[0]"                                   (read [] "io" "try" int)) -                               (import: java/io/BufferedReader +                               (import java/io/BufferedReader                                   "[1]::[0]"                                   (new [java/io/Reader])                                   (readLine [] "io" "try" "?" java/lang/String)) -                               (import: java/io/InputStream +                               (import java/io/InputStream                                   "[1]::[0]") -                               (import: java/io/InputStreamReader +                               (import java/io/InputStreamReader                                   "[1]::[0]"                                   (new [java/io/InputStream])) -                               (import: java/io/OutputStream +                               (import java/io/OutputStream                                   "[1]::[0]"                                   (write [[byte]] "io" "try" void)) -                               (import: java/lang/Process +                               (import java/lang/Process                                   "[1]::[0]"                                   (getInputStream [] "io" "try" java/io/InputStream)                                   (getErrorStream [] "io" "try" java/io/InputStream) @@ -269,18 +269,18 @@                                                        [await (<| (at ! each (|>> ffi.of_int)) java/lang/Process::waitFor)]                                                        )))))))) -                               (import: java/io/File +                               (import java/io/File                                   "[1]::[0]"                                   (new [java/lang/String])) -                               (import: java/lang/ProcessBuilder +                               (import java/lang/ProcessBuilder                                   "[1]::[0]"                                   (new [[java/lang/String]])                                   (environment [] "try" (java/util/Map java/lang/String java/lang/String))                                   (directory [java/io/File] java/lang/ProcessBuilder)                                   (start [] "io" "try" java/lang/Process)) -                               (import: java/lang/System +                               (import java/lang/System                                   "[1]::[0]"                                   ("static" getProperty [java/lang/String] "io" "try" java/lang/String)) | 
