From 6066515f7a9736210a04652636a634179939d185 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Mon, 10 Apr 2017 23:09:48 -0400 Subject: - Renamed _lux_lambda to _lux_function. --- stdlib/source/lux.lux | 144 +++++++++++++++++++++++++------------------------- 1 file changed, 72 insertions(+), 72 deletions(-) (limited to 'stdlib/source/lux.lux') diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux index 4d5885393..bb66813cc 100644 --- a/stdlib/source/lux.lux +++ b/stdlib/source/lux.lux @@ -676,8 +676,8 @@ (_lux_: (#LambdaT (#AppT AST' (#AppT Meta Cursor)) AST) - (_lux_lambda _ data - [_cursor data])) + (_lux_function _ data + [_cursor data])) #Nil) (_lux_def return @@ -687,9 +687,9 @@ (#AppT (#AppT Either Text) (#ProdT Compiler (#BoundT +1)))))) - (_lux_lambda _ val - (_lux_lambda _ state - (#Right state val)))) + (_lux_function _ val + (_lux_function _ state + (#Right state val)))) #Nil) (_lux_def fail @@ -699,69 +699,69 @@ (#AppT (#AppT Either Text) (#ProdT Compiler (#BoundT +1)))))) - (_lux_lambda _ msg - (_lux_lambda _ state - (#Left msg)))) + (_lux_function _ msg + (_lux_function _ state + (#Left msg)))) #Nil) (_lux_def bool$ (_lux_: (#LambdaT Bool AST) - (_lux_lambda _ value (_meta (#BoolS value)))) + (_lux_function _ value (_meta (#BoolS value)))) #Nil) (_lux_def nat$ (_lux_: (#LambdaT Nat AST) - (_lux_lambda _ value (_meta (#NatS value)))) + (_lux_function _ value (_meta (#NatS value)))) #Nil) (_lux_def int$ (_lux_: (#LambdaT Int AST) - (_lux_lambda _ value (_meta (#IntS value)))) + (_lux_function _ value (_meta (#IntS value)))) #Nil) (_lux_def deg$ (_lux_: (#LambdaT Deg AST) - (_lux_lambda _ value (_meta (#DegS value)))) + (_lux_function _ value (_meta (#DegS value)))) #Nil) (_lux_def real$ (_lux_: (#LambdaT Real AST) - (_lux_lambda _ value (_meta (#RealS value)))) + (_lux_function _ value (_meta (#RealS value)))) #Nil) (_lux_def char$ (_lux_: (#LambdaT Char AST) - (_lux_lambda _ value (_meta (#CharS value)))) + (_lux_function _ value (_meta (#CharS value)))) #Nil) (_lux_def text$ (_lux_: (#LambdaT Text AST) - (_lux_lambda _ text (_meta (#TextS text)))) + (_lux_function _ text (_meta (#TextS text)))) #Nil) (_lux_def symbol$ (_lux_: (#LambdaT Ident AST) - (_lux_lambda _ ident (_meta (#SymbolS ident)))) + (_lux_function _ ident (_meta (#SymbolS ident)))) #Nil) (_lux_def tag$ (_lux_: (#LambdaT Ident AST) - (_lux_lambda _ ident (_meta (#TagS ident)))) + (_lux_function _ ident (_meta (#TagS ident)))) #Nil) (_lux_def form$ (_lux_: (#LambdaT (#AppT List AST) AST) - (_lux_lambda _ tokens (_meta (#FormS tokens)))) + (_lux_function _ tokens (_meta (#FormS tokens)))) #Nil) (_lux_def tuple$ (_lux_: (#LambdaT (#AppT List AST) AST) - (_lux_lambda _ tokens (_meta (#TupleS tokens)))) + (_lux_function _ tokens (_meta (#TupleS tokens)))) #Nil) (_lux_def record$ (_lux_: (#LambdaT (#AppT List (#ProdT AST AST)) AST) - (_lux_lambda _ tokens (_meta (#RecordS tokens)))) + (_lux_function _ tokens (_meta (#RecordS tokens)))) #Nil) (_lux_def default-macro-meta @@ -772,53 +772,53 @@ (_lux_def let'' (_lux_: Macro - (_lux_lambda _ tokens - (_lux_case tokens - (#Cons lhs (#Cons rhs (#Cons body #Nil))) - (return (#Cons (form$ (#Cons (symbol$ ["" "_lux_case"]) - (#Cons rhs (#Cons lhs (#Cons body #Nil))))) - #Nil)) + (_lux_function _ tokens + (_lux_case tokens + (#Cons lhs (#Cons rhs (#Cons body #Nil))) + (return (#Cons (form$ (#Cons (symbol$ ["" "_lux_case"]) + (#Cons rhs (#Cons lhs (#Cons body #Nil))))) + #Nil)) - _ - (fail "Wrong syntax for let''")))) + _ + (fail "Wrong syntax for let''")))) default-macro-meta) (_lux_def function'' (_lux_: Macro - (_lux_lambda _ tokens - (_lux_case tokens - (#Cons [_ (#TupleS (#Cons arg args'))] (#Cons body #Nil)) - (return (#Cons (_meta (#FormS (#Cons (_meta (#SymbolS "" "_lux_lambda")) - (#Cons (_meta (#SymbolS "" "")) - (#Cons arg - (#Cons (_lux_case args' - #Nil - body - - _ - (_meta (#FormS (#Cons (_meta (#SymbolS "lux" "function''")) - (#Cons (_meta (#TupleS args')) - (#Cons body #Nil)))))) - #Nil)))))) - #Nil)) - - (#Cons [_ (#SymbolS "" self)] (#Cons [_ (#TupleS (#Cons arg args'))] (#Cons body #Nil))) - (return (#Cons (_meta (#FormS (#Cons (_meta (#SymbolS "" "_lux_lambda")) - (#Cons (_meta (#SymbolS "" self)) - (#Cons arg - (#Cons (_lux_case args' - #Nil - body - - _ - (_meta (#FormS (#Cons (_meta (#SymbolS "lux" "function''")) - (#Cons (_meta (#TupleS args')) - (#Cons body #Nil)))))) - #Nil)))))) - #Nil)) - - _ - (fail "Wrong syntax for function''")))) + (_lux_function _ tokens + (_lux_case tokens + (#Cons [_ (#TupleS (#Cons arg args'))] (#Cons body #Nil)) + (return (#Cons (_meta (#FormS (#Cons (_meta (#SymbolS "" "_lux_function")) + (#Cons (_meta (#SymbolS "" "")) + (#Cons arg + (#Cons (_lux_case args' + #Nil + body + + _ + (_meta (#FormS (#Cons (_meta (#SymbolS "lux" "function''")) + (#Cons (_meta (#TupleS args')) + (#Cons body #Nil)))))) + #Nil)))))) + #Nil)) + + (#Cons [_ (#SymbolS "" self)] (#Cons [_ (#TupleS (#Cons arg args'))] (#Cons body #Nil))) + (return (#Cons (_meta (#FormS (#Cons (_meta (#SymbolS "" "_lux_function")) + (#Cons (_meta (#SymbolS "" self)) + (#Cons arg + (#Cons (_lux_case args' + #Nil + body + + _ + (_meta (#FormS (#Cons (_meta (#SymbolS "lux" "function''")) + (#Cons (_meta (#TupleS args')) + (#Cons body #Nil)))))) + #Nil)))))) + #Nil)) + + _ + (fail "Wrong syntax for function''")))) default-macro-meta) (_lux_def export?-meta @@ -1338,11 +1338,11 @@ (fail "function' requires a non-empty arguments tuple.") (#Cons [harg targs]) - (return (list (form$ (list (symbol$ ["" "_lux_lambda"]) + (return (list (form$ (list (symbol$ ["" "_lux_function"]) (symbol$ ["" name]) harg (fold (function'' [arg body'] - (form$ (list (symbol$ ["" "_lux_lambda"]) + (form$ (list (symbol$ ["" "_lux_function"]) (symbol$ ["" ""]) arg body'))) @@ -1584,7 +1584,7 @@ _ (form$ (list g!bind - (form$ (list (symbol$ ["" "_lux_lambda"]) (symbol$ ["" ""]) var body')) + (form$ (list (symbol$ ["" "_lux_function"]) (symbol$ ["" ""]) var body')) value)))))) body (reverse (as-pairs bindings)))] @@ -1876,7 +1876,7 @@ (list [["lux" "doc"] (#TextA "## Hygienic quasi-quotation as a macro. Unquote (~) and unquote-splice (~@) must also be used as forms. ## All unprefixed macros will receive their parent module's prefix if imported; otherwise will receive the prefix of the module on which the quasi-quote is being used. (` (def: (~ name) - (lambda [(~@ args)] + (function [(~@ args)] (~ body))))")]) (_lux_case tokens (#Cons template #Nil) @@ -1891,7 +1891,7 @@ (macro:' #export (`' tokens) (list [["lux" "doc"] (#TextA "## Unhygienic quasi-quotation as a macro. Unquote (~) and unquote-splice (~@) must also be used as forms. (`' (def: (~ name) - (lambda [(~@ args)] + (function [(~@ args)] (~ body))))")]) (_lux_case tokens (#Cons template #Nil) @@ -2912,14 +2912,14 @@ body+ (fold (: (-> AST AST AST) (function' [arg body'] (if (symbol? arg) - (` (;_lux_lambda (~ g!blank) (~ arg) (~ body'))) - (` (;_lux_lambda (~ g!blank) (~ g!blank) - (case (~ g!blank) (~ arg) (~ body'))))))) + (` (;_lux_function (~ g!blank) (~ arg) (~ body'))) + (` (;_lux_function (~ g!blank) (~ g!blank) + (case (~ g!blank) (~ arg) (~ body'))))))) body (reverse tail))] (return (list (if (symbol? head) - (` (;_lux_lambda (~ g!name) (~ head) (~ body+))) - (` (;_lux_lambda (~ g!name) (~ g!blank) (case (~ g!blank) (~ head) (~ body+)))))))) + (` (;_lux_function (~ g!name) (~ head) (~ body+))) + (` (;_lux_function (~ g!name) (~ g!blank) (case (~ g!blank) (~ head) (~ body+)))))))) #None (fail "Wrong syntax for function"))) -- cgit v1.2.3