aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/target
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/target.lux6
-rw-r--r--stdlib/source/library/lux/target/common_lisp.lux98
-rw-r--r--stdlib/source/library/lux/target/js.lux112
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute.lux24
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute/code.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute/code/exception.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute/constant.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode.lux134
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/address.lux20
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment.lux20
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux20
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux16
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/instruction.lux58
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/jump.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/class.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/constant.lux34
-rw-r--r--stdlib/source/library/lux/target/jvm/constant/pool.lux42
-rw-r--r--stdlib/source/library/lux/target/jvm/constant/tag.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/name.lux14
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/signed.lux26
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/unsigned.lux28
-rw-r--r--stdlib/source/library/lux/target/jvm/field.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/index.lux10
-rw-r--r--stdlib/source/library/lux/target/jvm/loader.lux12
-rw-r--r--stdlib/source/library/lux/target/jvm/magic.lux4
-rw-r--r--stdlib/source/library/lux/target/jvm/method.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/modifier.lux28
-rw-r--r--stdlib/source/library/lux/target/jvm/reflection.lux22
-rw-r--r--stdlib/source/library/lux/target/jvm/type.lux42
-rw-r--r--stdlib/source/library/lux/target/jvm/type/alias.lux24
-rw-r--r--stdlib/source/library/lux/target/jvm/type/box.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/type/descriptor.lux32
-rw-r--r--stdlib/source/library/lux/target/jvm/type/lux.lux36
-rw-r--r--stdlib/source/library/lux/target/jvm/type/parser.lux60
-rw-r--r--stdlib/source/library/lux/target/jvm/type/reflection.lux22
-rw-r--r--stdlib/source/library/lux/target/jvm/type/signature.lux44
-rw-r--r--stdlib/source/library/lux/target/jvm/version.lux6
-rw-r--r--stdlib/source/library/lux/target/lua.lux100
-rw-r--r--stdlib/source/library/lux/target/php.lux132
-rw-r--r--stdlib/source/library/lux/target/python.lux112
-rw-r--r--stdlib/source/library/lux/target/r.lux92
-rw-r--r--stdlib/source/library/lux/target/ruby.lux114
-rw-r--r--stdlib/source/library/lux/target/scheme.lux84
44 files changed, 845 insertions, 845 deletions
diff --git a/stdlib/source/library/lux/target.lux b/stdlib/source/library/lux/target.lux
index 66e8ea31b..cee1e3084 100644
--- a/stdlib/source/library/lux/target.lux
+++ b/stdlib/source/library/lux/target.lux
@@ -1,12 +1,12 @@
(.using
- [library
- [lux (.except)]])
+ [library
+ [lux (.except)]])
(type: .public Target
Text)
(with_template [<name> <value>]
- [(def: .public <name>
+ [(def .public <name>
Target
<value>)]
diff --git a/stdlib/source/library/lux/target/common_lisp.lux b/stdlib/source/library/lux/target/common_lisp.lux
index a95e1df67..b0107d234 100644
--- a/stdlib/source/library/lux/target/common_lisp.lux
+++ b/stdlib/source/library/lux/target/common_lisp.lux
@@ -16,18 +16,18 @@
[type
[primitive (.except)]]]])
-(def: as_form
+(def as_form
(-> Text Text)
(text.enclosed ["(" ")"]))
(primitive .public (Code brand)
Text
- (def: .public manual
+ (def .public manual
(-> Text Code)
(|>> abstraction))
- (def: .public code
+ (def .public code
(-> (Code Any) Text)
(|>> representation))
@@ -62,29 +62,29 @@
[#input Var/*
#output (Expression Any)]))
- (def: .public nil
+ (def .public nil
Literal
(abstraction "()"))
(with_template [<prefix> <name>]
- [(def: .public <name>
+ [(def .public <name>
(-> Text Literal)
(|>> (format <prefix>) abstraction))]
["'" symbol]
[":" keyword])
- (def: .public bool
+ (def .public bool
(-> Bit Literal)
(|>> (pipe.case
#0 ..nil
#1 (..symbol "t"))))
- (def: .public int
+ (def .public int
(-> Int Literal)
(|>> %.int abstraction))
- (def: .public float
+ (def .public float
(-> Frac Literal)
(|>> (pipe.cond [(f.= f.positive_infinity)]
[(pipe.new "(/ 1.0 0.0)" [])]
@@ -99,7 +99,7 @@
[%.frac])
abstraction))
- (def: .public (double value)
+ (def .public (double value)
(-> Frac Literal)
(abstraction
(.cond (f.= f.positive_infinity value)
@@ -117,7 +117,7 @@
(text.replaced_once "E" "d" raw)
(format raw "d0"))))))
- (def: safe
+ (def safe
(-> Text Text)
(`` (|>> (~~ (with_template [<find> <replace>]
[(text.replaced <find> <replace>)]
@@ -134,24 +134,24 @@
))
)))
- (def: .public string
+ (def .public string
(-> Text Literal)
(|>> ..safe
(text.enclosed' text.double_quote)
abstraction))
- (def: .public var
+ (def .public var
(-> Text Var/1)
(|>> abstraction))
- (def: .public args
+ (def .public args
(-> (List Var/1) Var/*)
(|>> (list#each ..code)
(text.interposed " ")
..as_form
abstraction))
- (def: .public (args& singles rest)
+ (def .public (args& singles rest)
(-> (List Var/1) Var/1 Var/*)
(|> (case singles
{.#End}
@@ -166,19 +166,19 @@
..as_form
abstraction))
- (def: form
+ (def form
(-> (List (Expression Any)) Expression)
(|>> (list#each ..code)
(text.interposed " ")
..as_form
abstraction))
- (def: .public (call/* func)
+ (def .public (call/* func)
(-> (Expression Any) (-> (List (Expression Any)) (Computation Any)))
(|>> {.#Item func} ..form))
(with_template [<name> <function>]
- [(def: .public <name>
+ [(def .public <name>
(-> (List (Expression Any)) (Computation Any))
(..call/* (..var <function>)))]
@@ -186,7 +186,7 @@
[list/* "list"]
)
- (def: .public (labels definitions body)
+ (def .public (labels definitions body)
(-> (List [Var/1 Lambda]) (Expression Any) (Computation Any))
(..form (list (..var "labels")
(..form (list#each (function (_ [def_name [def_args def_body]])
@@ -194,19 +194,19 @@
definitions))
body)))
- (def: .public (destructuring_bind [bindings expression] body)
+ (def .public (destructuring_bind [bindings expression] body)
(-> [Var/* (Expression Any)] (List (Expression Any)) (Computation Any))
(..form (list.partial (..var "destructuring-bind")
(transmutation bindings) expression
body)))
(with_template [<call> <input_var>+ <input_type>+ <function>+]
- [(`` (def: .public (<call> [(~~ (template.spliced <input_var>+))] function)
+ [(`` (def .public (<call> [(~~ (template.spliced <input_var>+))] function)
(-> [(~~ (template.spliced <input_type>+))] (Expression Any) (Computation Any))
(..call/* function (list (~~ (template.spliced <input_var>+))))))
(`` (with_template [<lux_name> <host_name>]
- [(def: .public (<lux_name> args)
+ [(def .public (<lux_name> args)
(-> [(~~ (template.spliced <input_type>+))] (Computation Any))
(<call> args (..var <host_name>)))]
@@ -264,7 +264,7 @@
(with_template [<call> <input_type>+ <function>+]
[(`` (with_template [<lux_name> <host_name>]
- [(def: .public (<lux_name> args)
+ [(def .public (<lux_name> args)
(-> [(~~ (template.spliced <input_type>+))] (Access Any))
(transmutation (<call> args (..var <host_name>))))]
@@ -281,29 +281,29 @@
[gethash/2 "gethash"]]]
)
- (def: .public (make_hash_table/with_size size)
+ (def .public (make_hash_table/with_size size)
(-> (Expression Any) (Computation Any))
(..call/* (..var "make-hash-table")
(list (..keyword "size")
size)))
- (def: .public (funcall/+ [func args])
+ (def .public (funcall/+ [func args])
(-> [(Expression Any) (List (Expression Any))] (Computation Any))
(..call/* (..var "funcall") (list.partial func args)))
- (def: .public (search/3 [reference space start])
+ (def .public (search/3 [reference space start])
(-> [(Expression Any) (Expression Any) (Expression Any)] (Computation Any))
(..call/* (..var "search")
(list reference
space
(..keyword "start2") start)))
- (def: .public (concatenate/2|string [left right])
+ (def .public (concatenate/2|string [left right])
(-> [(Expression Any) (Expression Any)] (Computation Any))
(concatenate/3 [(..symbol "string") left right]))
(with_template [<lux_name> <host_name>]
- [(def: .public (<lux_name> left right)
+ [(def .public (<lux_name> left right)
(-> (Expression Any) (Expression Any) (Computation Any))
(..form (list (..var <host_name>) left right)))]
@@ -312,7 +312,7 @@
)
(with_template [<lux_name> <host_name>]
- [(def: .public (<lux_name> [param subject])
+ [(def .public (<lux_name> [param subject])
(-> [(Expression Any) (Expression Any)] (Computation Any))
(..form (list (..var <host_name>) subject param)))]
@@ -332,20 +332,20 @@
[logxor/2 "logxor"]
)
- (def: .public (if test then else)
+ (def .public (if test then else)
(-> (Expression Any) (Expression Any) (Expression Any) (Computation Any))
(..form (list (..var "if") test then else)))
- (def: .public (when test then)
+ (def .public (when test then)
(-> (Expression Any) (Expression Any) (Computation Any))
(..form (list (..var "when") test then)))
- (def: .public (lambda input body)
+ (def .public (lambda input body)
(-> Var/* (Expression Any) Literal)
(..form (list (..var "lambda") (transmutation input) body)))
(with_template [<lux_name> <host_name>]
- [(def: .public (<lux_name> bindings body)
+ [(def .public (<lux_name> bindings body)
(-> (List [Var/1 (Expression Any)]) (List (Expression Any)) (Computation Any))
(..form (list.partial (..var <host_name>)
(|> bindings
@@ -358,16 +358,16 @@
[let* "let*"]
)
- (def: .public (defparameter name body)
+ (def .public (defparameter name body)
(-> Var/1 (Expression Any) (Expression Any))
(..form (list (..var "defparameter") name body)))
- (def: .public (defun name inputs body)
+ (def .public (defun name inputs body)
(-> Var/1 Var/* (Expression Any) (Expression Any))
(..form (list (..var "defun") name (transmutation inputs) body)))
(with_template [<name> <symbol>]
- [(def: .public <name>
+ [(def .public <name>
(-> (List (Expression Any)) (Computation Any))
(|>> (list.partial (..var <symbol>)) ..form))]
@@ -376,11 +376,11 @@
[values/* "values"]
)
- (def: .public (setq name value)
+ (def .public (setq name value)
(-> Var/1 (Expression Any) (Expression Any))
(..form (list (..var "setq") name value)))
- (def: .public (setf access value)
+ (def .public (setf access value)
(-> (Access Any) (Expression Any) (Expression Any))
(..form (list (..var "setf") access value)))
@@ -390,7 +390,7 @@
#condition Var/1
#body (Expression Any)]))
- (def: .public (handler_case handlers body)
+ (def .public (handler_case handlers body)
(-> (List Handler) (Expression Any) (Computation Any))
(..form (list.partial (..var "handler-case")
body
@@ -401,7 +401,7 @@
handlers))))
(with_template [<name> <prefix>]
- [(def: .public (<name> conditions expression)
+ [(def .public (<name> conditions expression)
(-> (List Text) (Expression Any) (Expression Any))
(case conditions
{.#End}
@@ -421,23 +421,23 @@
[conditional+ "#+"]
[conditional- "#-"])
- (def: .public label
+ (def .public label
(-> Text Label)
(|>> abstraction))
- (def: .public (block name body)
+ (def .public (block name body)
(-> Label (List (Expression Any)) (Computation Any))
(..form (list.partial (..var "block") (transmutation name) body)))
- (def: .public (return_from target value)
+ (def .public (return_from target value)
(-> Label (Expression Any) (Computation Any))
(..form (list (..var "return-from") (transmutation target) value)))
- (def: .public (return value)
+ (def .public (return value)
(-> (Expression Any) (Computation Any))
(..form (list (..var "return") value)))
- (def: .public (cond clauses else)
+ (def .public (cond clauses else)
(-> (List [(Expression Any) (Expression Any)]) (Expression Any) (Computation Any))
(..form (list.partial (..var "cond")
(list#composite (list#each (function (_ [test then])
@@ -445,28 +445,28 @@
clauses)
(list (..form (list (..bool true) else)))))))
- (def: .public tag
+ (def .public tag
(-> Text Tag)
(|>> abstraction))
- (def: .public go
+ (def .public go
(-> Tag (Expression Any))
(|>> (list (..var "go"))
..form))
- (def: .public values_list/1
+ (def .public values_list/1
(-> (Expression Any) (Expression Any))
(|>> (list (..var "values-list"))
..form))
- (def: .public (multiple_value_setq bindings values)
+ (def .public (multiple_value_setq bindings values)
(-> Var/* (Expression Any) (Expression Any))
(..form (list (..var "multiple-value-setq")
(transmutation bindings)
values)))
)
-(def: .public (while condition body)
+(def .public (while condition body)
(-> (Expression Any) (Expression Any) (Computation Any))
(..form (list (..var "loop") (..var "while") condition
(..var "do") body)))
diff --git a/stdlib/source/library/lux/target/js.lux b/stdlib/source/library/lux/target/js.lux
index ae5ffe9d1..5b057a697 100644
--- a/stdlib/source/library/lux/target/js.lux
+++ b/stdlib/source/library/lux/target/js.lux
@@ -17,18 +17,18 @@
[type
[primitive (.except)]]]])
-(def: expression
+(def expression
(text.enclosed ["(" ")"]))
-(def: element
+(def element
(text.enclosed ["[" "]"]))
... Added the carriage return for better Windows compatibility.
-(def: \n+
+(def \n+
Text
(format text.carriage_return text.new_line))
-(def: nested
+(def nested
(-> Text Text)
(|>> (format \n+)
(text.replaced text.new_line (format text.new_line text.tab))))
@@ -36,7 +36,7 @@
(primitive .public (Code brand)
Text
- (def: .public code
+ (def .public code
(-> (Code Any) Text)
(|>> representation))
@@ -64,20 +64,20 @@
)
(with_template [<name> <literal>]
- [(def: .public <name> Literal (abstraction <literal>))]
+ [(def .public <name> Literal (abstraction <literal>))]
[null "null"]
[undefined "undefined"]
)
- (def: .public boolean
+ (def .public boolean
(-> Bit Literal)
(|>> (pipe.case
#0 "false"
#1 "true")
abstraction))
- (def: .public (number value)
+ (def .public (number value)
(-> Frac Literal)
(abstraction
(cond (f.not_a_number? value)
@@ -92,7 +92,7 @@
... else
(|> value %.frac ..expression))))
- (def: safe
+ (def safe
(-> Text Text)
(`` (|>> (~~ (with_template [<replace> <find>]
[(text.replaced <find> <replace>)]
@@ -110,36 +110,36 @@
))
)))
- (def: .public string
+ (def .public string
(-> Text Literal)
(|>> ..safe
(text.enclosed [text.double_quote text.double_quote])
abstraction))
- (def: argument_separator ", ")
- (def: field_separator ": ")
- (def: statement_suffix ";")
+ (def argument_separator ", ")
+ (def field_separator ": ")
+ (def statement_suffix ";")
- (def: .public array
+ (def .public array
(-> (List Expression) Computation)
(|>> (list#each ..code)
(text.interposed ..argument_separator)
..element
abstraction))
- (def: .public var
+ (def .public var
(-> Text Var)
(|>> abstraction))
- (def: .public (at index array_or_object)
+ (def .public (at index array_or_object)
(-> Expression Expression Access)
(abstraction (format (representation array_or_object) (..element (representation index)))))
- (def: .public (the field object)
+ (def .public (the field object)
(-> Text Expression Access)
(abstraction (format (representation object) "." field)))
- (def: .public (apply function inputs)
+ (def .public (apply function inputs)
(-> Expression (List Expression) Computation)
(|> inputs
(list#each ..code)
@@ -148,11 +148,11 @@
(format (representation function))
abstraction))
- (def: .public (do method inputs object)
+ (def .public (do method inputs object)
(-> Text (List Expression) Expression Computation)
(apply (..the method object) inputs))
- (def: .public object
+ (def .public object
(-> (List [Text Expression]) Computation)
(|>> (list#each (.function (_ [key val])
(format (representation (..string key)) ..field_separator (representation val))))
@@ -161,19 +161,19 @@
..expression
abstraction))
- (def: .public (, pre post)
+ (def .public (, pre post)
(-> Expression Expression Computation)
(|> (format (representation pre) ..argument_separator (representation post))
..expression
abstraction))
- (def: .public (then pre post)
+ (def .public (then pre post)
(-> Statement Statement Statement)
(abstraction (format (representation pre)
\n+
(representation post))))
- (def: block
+ (def block
(-> Statement Text)
(let [close (format \n+ "}")]
(|>> representation
@@ -181,7 +181,7 @@
(text.enclosed ["{"
close]))))
- (def: .public (function_definition name inputs body)
+ (def .public (function_definition name inputs body)
(-> Var (List Var) Statement Statement)
(|> body
..block
@@ -193,14 +193,14 @@
" ")
abstraction))
- (def: .public (function name inputs body)
+ (def .public (function name inputs body)
(-> Var (List Var) Statement Computation)
(|> (..function_definition name inputs body)
representation
..expression
abstraction))
- (def: .public (closure inputs body)
+ (def .public (closure inputs body)
(-> (List Var) Statement Computation)
(|> body
..block
@@ -214,7 +214,7 @@
abstraction))
(with_template [<name> <op>]
- [(def: .public (<name> param subject)
+ [(def .public (<name> param subject)
(-> Expression Expression Computation)
(|> (format (representation subject) " " <op> " " (representation param))
..expression
@@ -244,7 +244,7 @@
)
(with_template [<prefix> <name>]
- [(def: .public <name>
+ [(def .public <name>
(-> Expression Computation)
(|>> representation (text.prefix <prefix>) ..expression abstraction))]
@@ -255,7 +255,7 @@
(with_template [<name> <input> <format>]
[... A 32-bit integer expression.
- (def: .public (<name> value)
+ (def .public (<name> value)
(-> <input> Computation)
(abstraction (..expression (format (<format> value) "|0"))))]
@@ -263,13 +263,13 @@
[i32 Int %.int]
)
- (def: .public (int value)
+ (def .public (int value)
(-> Int Literal)
(abstraction (.if (i.< +0 value)
(%.int value)
(%.nat (.nat value)))))
- (def: .public (? test then else)
+ (def .public (? test then else)
(-> Expression Expression Expression Computation)
(|> (format (representation test)
" ? " (representation then)
@@ -277,14 +277,14 @@
..expression
abstraction))
- (def: .public type_of
+ (def .public type_of
(-> Expression Computation)
(|>> representation
(format "typeof ")
..expression
abstraction))
- (def: .public (new constructor inputs)
+ (def .public (new constructor inputs)
(-> Expression (List Expression) Computation)
(|> (format "new " (representation constructor)
(|> inputs
@@ -294,71 +294,71 @@
..expression
abstraction))
- (def: .public statement
+ (def .public statement
(-> Expression Statement)
(|>> representation (text.suffix ..statement_suffix) abstraction))
- (def: .public use_strict
+ (def .public use_strict
Statement
(abstraction (format text.double_quote "use strict" text.double_quote ..statement_suffix)))
- (def: .public (declare name)
+ (def .public (declare name)
(-> Var Statement)
(abstraction (format "var " (representation name) ..statement_suffix)))
- (def: .public (define name value)
+ (def .public (define name value)
(-> Var Expression Statement)
(abstraction (format "var " (representation name) " = " (representation value) ..statement_suffix)))
- (def: .public (set name value)
+ (def .public (set name value)
(-> Location Expression Statement)
(abstraction (format (representation name) " = " (representation value) ..statement_suffix)))
- (def: .public (throw message)
+ (def .public (throw message)
(-> Expression Statement)
(abstraction (format "throw " (representation message) ..statement_suffix)))
- (def: .public (return value)
+ (def .public (return value)
(-> Expression Statement)
(abstraction (format "return " (representation value) ..statement_suffix)))
- (def: .public delete
+ (def .public delete
(-> Location Expression)
(|>> representation
(format "delete ")
..expression
abstraction))
- (def: .public (if test then! else!)
+ (def .public (if test then! else!)
(-> Expression Statement Statement Statement)
(abstraction (format "if(" (representation test) ") "
(..block then!)
" else "
(..block else!))))
- (def: .public (when test then!)
+ (def .public (when test then!)
(-> Expression Statement Statement)
(abstraction (format "if(" (representation test) ") "
(..block then!))))
- (def: .public (while test body)
+ (def .public (while test body)
(-> Expression Statement Loop)
(abstraction (format "while(" (representation test) ") "
(..block body))))
- (def: .public (do_while test body)
+ (def .public (do_while test body)
(-> Expression Statement Loop)
(abstraction (format "do " (..block body)
" while(" (representation test) ")" ..statement_suffix)))
- (def: .public (try body [exception catch])
+ (def .public (try body [exception catch])
(-> Statement [Var Statement] Statement)
(abstraction (format "try "
(..block body)
" catch(" (representation exception) ") "
(..block catch))))
- (def: .public (for var init condition update iteration)
+ (def .public (for var init condition update iteration)
(-> Var Expression Expression Expression Statement Loop)
(abstraction (format "for(" (representation (..define var init))
" " (representation condition)
@@ -366,20 +366,20 @@
")"
(..block iteration))))
- (def: .public label
+ (def .public label
(-> Text Label)
(|>> abstraction))
- (def: .public (with_label label loop)
+ (def .public (with_label label loop)
(-> Label Loop Statement)
(abstraction (format (representation label) ": " (representation loop))))
(with_template [<keyword> <0> <1>]
- [(def: .public <0>
+ [(def .public <0>
Statement
(abstraction (format <keyword> ..statement_suffix)))
- (def: .public (<1> label)
+ (def .public (<1> label)
(-> Label Statement)
(abstraction (format <keyword> " " (representation label) ..statement_suffix)))]
@@ -388,7 +388,7 @@
)
(with_template [<name> <js>]
- [(def: .public <name>
+ [(def .public <name>
(-> Location Expression)
(|>> representation
(text.suffix <js>)
@@ -398,11 +398,11 @@
[-- "--"]
)
- (def: .public (comment commentary on)
+ (def .public (comment commentary on)
(All (_ kind) (-> Text (Code kind) (Code kind)))
(abstraction (format "/* " commentary " */" " " (representation on))))
- (def: .public (switch input cases default)
+ (def .public (switch input cases default)
(-> Expression (List [(List Literal) Statement]) (Maybe Statement) Statement)
(abstraction (format "switch (" (representation input) ") "
(|> (format (|> cases
@@ -425,13 +425,13 @@
)
(with_template [<apply> <arg>+ <type>+ <function>+]
- [(`` (def: .public (<apply> function)
+ [(`` (def .public (<apply> function)
(-> Expression (~~ (template.spliced <type>+)) Computation)
(.function (_ (~~ (template.spliced <arg>+)))
(..apply function (list (~~ (template.spliced <arg>+)))))))
(`` (with_template [<definition> <function>]
- [(def: .public <definition> (<apply> (..var <function>)))]
+ [(def .public <definition> (<apply> (..var <function>)))]
(~~ (template.spliced <function>+))))]
diff --git a/stdlib/source/library/lux/target/jvm/attribute.lux b/stdlib/source/library/lux/target/jvm/attribute.lux
index 30a3fe5f3..eb6fd8566 100644
--- a/stdlib/source/library/lux/target/jvm/attribute.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute.lux
@@ -35,7 +35,7 @@
#length U4
#info about]))
-(def: .public (info_equivalence Equivalence<about>)
+(def .public (info_equivalence Equivalence<about>)
(All (_ about)
(-> (Equivalence about)
(Equivalence (Info about))))
@@ -44,7 +44,7 @@
//unsigned.equivalence
Equivalence<about>))
-(def: (info_writer writer)
+(def (info_writer writer)
(All (_ about)
(-> (Writer about)
(Writer (Info about))))
@@ -67,7 +67,7 @@
<Code>)
)
-(def: .public equivalence
+(def .public equivalence
(Equivalence Attribute)
(equivalence.rec
(function (_ equivalence)
@@ -77,7 +77,7 @@
(info_equivalence //index.equivalence)
))))
-(def: common_attribute_length
+(def common_attribute_length
(all n.+
... u2 attribute_name_index;
//unsigned.bytes/2
@@ -85,7 +85,7 @@
//unsigned.bytes/4
))
-(def: (length attribute)
+(def (length attribute)
(-> Attribute Nat)
(case attribute
(^.with_template [<tag>]
@@ -96,19 +96,19 @@
[#Signature])))
... TODO: Inline ASAP
-(def: (constant' index @name)
+(def (constant' index @name)
(-> (Constant Any) (Index UTF8) Attribute)
{#Constant [#name @name
... https://docs.oracle.com/javase/specs/jvms/se7/html/jvms-4.html#jvms-4.7.2
#length (|> /constant.length //unsigned.u4 try.trusted)
#info index]})
-(def: .public (constant index)
+(def .public (constant index)
(-> (Constant Any) (Resource Attribute))
(//pool#each (constant' index) (//pool.utf8 "ConstantValue")))
... TODO: Inline ASAP
-(def: (code' specification @name)
+(def (code' specification @name)
(-> Code (Index UTF8) Attribute)
{#Code [#name @name
... https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-4.html#jvms-4.7.3
@@ -118,26 +118,26 @@
try.trusted)
#info specification]})
-(def: .public (code specification)
+(def .public (code specification)
(-> Code (Resource Attribute))
(//pool#each (code' specification) (//pool.utf8 "Code")))
... TODO: Inline ASAP
-(def: (signature' it @name)
+(def (signature' it @name)
(-> (Index UTF8) (Index UTF8) Attribute)
{#Signature [#name @name
... https://docs.oracle.com/javase/specs/jvms/se7/html/jvms-4.html#jvms-4.7.9
#length (|> //index.length //unsigned.u4 try.trusted)
#info it]})
-(def: .public (signature it)
+(def .public (signature it)
(All (_ category)
(-> (Signature category) (Resource Attribute)))
(do [! //pool.monad]
[it (|> it //signature.signature //pool.utf8)]
(at ! each (signature' it) (//pool.utf8 "Signature"))))
-(def: .public (writer it)
+(def .public (writer it)
(Writer Attribute)
(case it
{#Constant it}
diff --git a/stdlib/source/library/lux/target/jvm/attribute/code.lux b/stdlib/source/library/lux/target/jvm/attribute/code.lux
index cc795b920..835b6726a 100644
--- a/stdlib/source/library/lux/target/jvm/attribute/code.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute/code.lux
@@ -29,7 +29,7 @@
#exception_table (Sequence Exception)
#attributes (Sequence Attribute)]))
-(def: .public (length length code)
+(def .public (length length code)
(All (_ Attribute) (-> (-> Attribute Nat) (Code Attribute) Nat))
(all n.+
... u2 max_stack;
@@ -54,7 +54,7 @@
(sequence#each length)
(sequence#mix n.+ 0))))
-(def: .public (equivalence attribute_equivalence)
+(def .public (equivalence attribute_equivalence)
(All (_ attribute)
(-> (Equivalence attribute) (Equivalence (Code attribute))))
(all product.equivalence
@@ -65,7 +65,7 @@
))
... https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-4.html#jvms-4.7.3
-(def: .public (writer writer code)
+(def .public (writer writer code)
(All (_ Attribute) (-> (Writer Attribute) (Writer (Code Attribute))))
(all binaryF#composite
... u2 max_stack;
diff --git a/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux b/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux
index b71573669..f71d52cfd 100644
--- a/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux
@@ -26,7 +26,7 @@
#handler Address
#catch (Index Class)]))
-(def: .public equivalence
+(def .public equivalence
(Equivalence Exception)
(all product.equivalence
////address.equivalence
@@ -36,7 +36,7 @@
))
... https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-4.html#jvms-4.7.3
-(def: .public length
+(def .public length
Nat
(all n.+
... u2 start_pc;
@@ -49,7 +49,7 @@
////unsigned.bytes/2
))
-(def: .public writer
+(def .public writer
(Writer Exception)
(all \\format.and
////address.writer
diff --git a/stdlib/source/library/lux/target/jvm/attribute/constant.lux b/stdlib/source/library/lux/target/jvm/attribute/constant.lux
index 6e20c2ad1..34c8582ca 100644
--- a/stdlib/source/library/lux/target/jvm/attribute/constant.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute/constant.lux
@@ -15,13 +15,13 @@
(type: .public (Constant a)
(Index (Value a)))
-(def: .public equivalence
+(def .public equivalence
(All (_ a) (Equivalence (Constant a)))
///index.equivalence)
-(def: .public length
+(def .public length
///index.length)
-(def: .public writer
+(def .public writer
(All (_ a) (Writer (Constant a)))
///index.writer)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux
index 882c0dfdf..99901a4a3 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode.lux
@@ -64,7 +64,7 @@
#next Label
#known Resolver]))
-(def: fresh
+(def fresh
Tracker
[#program_counter /address.start
#next 0
@@ -73,16 +73,16 @@
(type: .public Relative
(-> Resolver (Try [(Sequence Exception) Instruction])))
-(def: no_exceptions
+(def no_exceptions
(Sequence Exception)
sequence.empty)
-(def: relative#identity
+(def relative#identity
Relative
(function (_ _)
{try.#Success [..no_exceptions _.empty]}))
-(def: try|do
+(def try|do
(template (_ <binding> <term> <then>)
[(.case <term>
{try.#Success <binding>}
@@ -91,11 +91,11 @@
failure
(as_expected failure))]))
-(def: try|in
+(def try|in
(template (_ <it>)
[{try.#Success <it>}]))
-(def: (relative#composite left right)
+(def (relative#composite left right)
(-> Relative Relative Relative)
(cond (same? ..relative#identity left)
right
@@ -110,16 +110,16 @@
(try|in [(at sequence.monoid composite left_exceptions right_exceptions)
(_#composite left_instruction right_instruction)])))))
-(def: relative_monoid
+(def relative_monoid
(Monoid Relative)
(implementation
- (def: identity ..relative#identity)
- (def: composite ..relative#composite)))
+ (def identity ..relative#identity)
+ (def composite ..relative#composite)))
(type: .public (Bytecode a)
(+State Try [Pool Environment Tracker] (Writer Relative a)))
-(def: .public new_label
+(def .public new_label
(Bytecode Label)
(function (_ [pool environment tracker])
{try.#Success [[pool
@@ -144,7 +144,7 @@
"Expected" (/stack.format expected)
"Actual" (/stack.format actual)))
-(def: .public (set? label)
+(def .public (set? label)
(-> Label (Bytecode (Maybe [Stack Address])))
(function (_ state)
(let [[pool environment tracker] state]
@@ -157,7 +157,7 @@
_
{.#None})]]})))
-(def: .public (acknowledged? label)
+(def .public (acknowledged? label)
(-> Label (Bytecode (Maybe Stack)))
(function (_ state)
(let [[pool environment tracker] state]
@@ -170,7 +170,7 @@
_
{.#None})]]})))
-(def: .public stack
+(def .public stack
(Bytecode (Maybe Stack))
(function (_ state)
(let [[pool environment tracker] state]
@@ -185,7 +185,7 @@
tracker)]
[..relative#identity
[]]]))]
- (def: .public (set_label label)
+ (def .public (set_label label)
(-> Label (Bytecode Any))
(function (_ [pool environment tracker])
(let [@here (the #program_counter tracker)]
@@ -205,10 +205,10 @@
environment))
<success>))))))
-(def: .public functor
+(def .public functor
(Functor Bytecode)
(implementation
- (def: (each $ it)
+ (def (each $ it)
(function (_ state)
(case (it state)
{try.#Success [state' [relative it]]}
@@ -218,16 +218,16 @@
failure
(as_expected failure))))))
-(def: .public monad
+(def .public monad
(Monad Bytecode)
(implementation
- (def: functor ..functor)
+ (def functor ..functor)
- (def: (in it)
+ (def (in it)
(function (_ state)
{try.#Success [state [relative#identity it]]}))
- (def: (conjoint ^^it)
+ (def (conjoint ^^it)
(function (_ state)
(case (^^it state)
{try.#Success [state' [left ^it]]}
@@ -243,7 +243,7 @@
failure
(as_expected failure))))))
-(def: .public (when_continuous it)
+(def .public (when_continuous it)
(-> (Bytecode Any) (Bytecode Any))
(do ..monad
[stack ..stack]
@@ -255,7 +255,7 @@
_
(in []))))
-(def: .public (when_acknowledged @ it)
+(def .public (when_acknowledged @ it)
(-> Label (Bytecode Any) (Bytecode Any))
(do ..monad
[?@ (..acknowledged? @)]
@@ -267,27 +267,27 @@
_
(in []))))
-(def: .public (failure error)
+(def .public (failure error)
(-> Text Bytecode)
(function (_ _)
{try.#Failure error}))
-(def: .public (except exception value)
+(def .public (except exception value)
(All (_ e) (-> (exception.Exception e) e Bytecode))
(..failure (exception.error exception value)))
-(def: .public (resolve environment bytecode)
+(def .public (resolve environment bytecode)
(All (_ a) (-> Environment (Bytecode a) (Resource [Environment (Sequence Exception) Instruction a])))
(function (_ pool)
(<| (try|do [[pool environment tracker] [relative output]] (bytecode [pool environment ..fresh]))
(try|do [exceptions instruction] (relative (the #known tracker)))
(try|in [pool [environment exceptions instruction output]]))))
-(def: (step estimator counter)
+(def (step estimator counter)
(-> Estimator Address (Try Address))
(/address.move (estimator counter) counter))
-(def: (bytecode consumption production registry [estimator bytecode] input)
+(def (bytecode consumption production registry [estimator bytecode] input)
(All (_ a) (-> U2 U2 Registry [Estimator (-> [a] Instruction)] a (Bytecode Any)))
(function (_ [pool environment tracker])
(<| (try|do environment' (|> environment
@@ -304,7 +304,7 @@
[]]]))))
(with_template [<name> <frames>]
- [(def: <name> U2
+ [(def <name> U2
(|> <frames> //unsigned.u2 try.trusted))]
[$0 0]
@@ -317,7 +317,7 @@
)
(with_template [<name> <registry>]
- [(def: <name> Registry (|> <registry> //unsigned.u2 try.trusted /registry.registry))]
+ [(def <name> Registry (|> <registry> //unsigned.u2 try.trusted /registry.registry))]
[@_ 0]
[@0 1]
@@ -328,7 +328,7 @@
)
(with_template [<name> <consumption> <production> <registry> <instruction>]
- [(def: .public <name>
+ [(def .public <name>
(Bytecode Any)
(..bytecode <consumption>
<production>
@@ -511,7 +511,7 @@
[monitorexit $1 $0 @_ _.monitorexit]
)
-(def: discontinuity!
+(def discontinuity!
(Bytecode Any)
(function (_ [pool environment tracker])
(<| (try|do _ (/environment.stack environment))
@@ -522,7 +522,7 @@
[]]]))))
(with_template [<name> <consumption> <instruction>]
- [(def: .public <name>
+ [(def .public <name>
(Bytecode Any)
(do ..monad
[_ (..bytecode <consumption> $0 @_ <instruction> [])]
@@ -538,11 +538,11 @@
[athrow $1 _.athrow]
)
-(def: .public (bipush byte)
+(def .public (bipush byte)
(-> S1 (Bytecode Any))
(..bytecode $0 $1 @_ _.bipush [byte]))
-(def: (lifted resource)
+(def (lifted resource)
(All (_ a)
(-> (Resource a)
(Bytecode a)))
@@ -552,7 +552,7 @@
[..relative#identity
output]]))))
-(def: .public (string value)
+(def .public (string value)
(-> //constant.UTF8 (Bytecode Any))
(do ..monad
[index (..lifted (//constant/pool.string value))]
@@ -572,7 +572,7 @@
("static" doubleToRawLongBits "manual" [double] long))
(with_template [<name> <type> <constructor> <constant> <wide> <to_lux> <specializations>]
- [(def: .public (<name> value)
+ [(def .public (<name> value)
(-> <type> (Bytecode Any))
(case (|> value <to_lux>)
(^.with_template [<special> <instruction>]
@@ -599,7 +599,7 @@
[+5 _.iconst_5])]
)
-(def: (arbitrary_float value)
+(def (arbitrary_float value)
(-> java/lang/Float (Bytecode Any))
(do ..monad
[index (..lifted (//constant/pool.float (//constant.float value)))]
@@ -610,16 +610,16 @@
{try.#Failure _}
(..bytecode $0 $1 @_ _.ldc_w/float [index]))))
-(def: float_bits
+(def float_bits
(-> java/lang/Float Int)
(|>> java/lang/Float::floatToRawIntBits
ffi.int_to_long
(as Int)))
-(def: negative_zero_float_bits
+(def negative_zero_float_bits
(|> -0.0 (as java/lang/Double) ffi.double_to_float ..float_bits))
-(def: .public (float value)
+(def .public (float value)
(-> java/lang/Float (Bytecode Any))
(if (i.= ..negative_zero_float_bits
(..float_bits value))
@@ -634,7 +634,7 @@
_ (..arbitrary_float value))))
(with_template [<name> <type> <constructor> <constant> <wide> <to_lux> <specializations>]
- [(def: .public (<name> value)
+ [(def .public (<name> value)
(-> <type> (Bytecode Any))
(case (|> value <to_lux>)
(^.with_template [<special> <instruction>]
@@ -651,21 +651,21 @@
[+1 _.lconst_1])]
)
-(def: (arbitrary_double value)
+(def (arbitrary_double value)
(-> java/lang/Double (Bytecode Any))
(do ..monad
[index (..lifted (//constant/pool.double (//constant.double (as Frac value))))]
(..bytecode $0 $2 @_ _.ldc2_w/double [index])))
-(def: double_bits
+(def double_bits
(-> java/lang/Double Int)
(|>> java/lang/Double::doubleToRawLongBits
(as Int)))
-(def: negative_zero_double_bits
+(def negative_zero_double_bits
(..double_bits (as java/lang/Double -0.0)))
-(def: .public (double value)
+(def .public (double value)
(-> java/lang/Double (Bytecode Any))
(if (i.= ..negative_zero_double_bits
(..double_bits value))
@@ -682,7 +682,7 @@
(exception.report
"ID" (%.nat id)))
-(def: (register id)
+(def (register id)
(-> Nat (Bytecode Register))
(case (//unsigned.u1 id)
{try.#Success register}
@@ -692,7 +692,7 @@
(..except ..invalid_register [id])))
(with_template [<for> <size> <name> <general> <specials>]
- [(def: .public (<name> local)
+ [(def .public (<name> local)
(-> Nat (Bytecode Any))
(with_expansions [<specials>' (template.spliced <specials>)]
(`` (case local
@@ -732,7 +732,7 @@
)
(with_template [<for> <size> <name> <general> <specials>]
- [(def: .public (<name> local)
+ [(def .public (<name> local)
(-> Nat (Bytecode Any))
(with_expansions [<specials>' (template.spliced <specials>)]
(`` (case local
@@ -772,7 +772,7 @@
)
(with_template [<consumption> <production> <name> <instruction> <input>]
- [(def: .public <name>
+ [(def .public <name>
(-> <input> (Bytecode Any))
(..bytecode <consumption> <production> @_ <instruction>))]
@@ -796,7 +796,7 @@
(Either Big_Jump
Jump))
-(def: (jump @from @to)
+(def (jump @from @to)
(-> Address Address (Try Any_Jump))
(<| (try|do jump (try#each //signed.value
(/address.jump @from @to)))
@@ -812,7 +812,7 @@
(exception.report
"Label" (%.nat label)))
-(def: (resolve_label label resolver)
+(def (resolve_label label resolver)
(-> Label Resolver (Try [Stack Address]))
(case (dictionary.value label resolver)
{.#Some [actual {.#Some address}]}
@@ -825,7 +825,7 @@
_
(exception.except ..unknown_label [label])))
-(def: (acknowledge_label stack label tracker)
+(def (acknowledge_label stack label tracker)
(-> Stack Label Tracker Tracker)
(case (dictionary.value label (the #known tracker))
{.#Some _}
@@ -836,7 +836,7 @@
(revised #known (dictionary.has label [stack {.#None}]) tracker)))
(with_template [<consumption> <name> <instruction>]
- [(def: .public (<name> label)
+ [(def .public (<name> label)
(-> Label (Bytecode Any))
(let [[estimator bytecode] <instruction>]
(function (_ [pool environment tracker])
@@ -886,7 +886,7 @@
)
(with_template [<name> <instruction> <on_long_jump> <on_short_jump>]
- [(def: .public (<name> label)
+ [(def .public (<name> label)
(-> Label (Bytecode Any))
(let [[estimator bytecode] <instruction>]
(function (_ [pool environment tracker])
@@ -928,7 +928,7 @@
(try|in [..no_exceptions (bytecode (/jump.lifted jump))])]
)
-(def: (big_jump jump)
+(def (big_jump jump)
(-> Any_Jump Big_Jump)
(case jump
{.#Left big}
@@ -939,7 +939,7 @@
(exception: .public invalid_tableswitch)
-(def: .public (tableswitch minimum default [at_minimum afterwards])
+(def .public (tableswitch minimum default [at_minimum afterwards])
(-> S4 Label [Label (List Label)] (Bytecode Any))
(let [[estimator bytecode] _.tableswitch]
(function (_ [pool environment tracker])
@@ -977,7 +977,7 @@
(exception: .public invalid_lookupswitch)
-(def: .public (lookupswitch default cases)
+(def .public (lookupswitch default cases)
(-> Label (List [S4 Label]) (Bytecode Any))
(let [cases (list.sorted (function (_ [left _] [right _])
(i.< (//signed.value left)
@@ -1016,13 +1016,13 @@
(exception.except ..invalid_lookupswitch []))))
[]]]))))))
-(def: reflection
+(def reflection
(All (_ category)
(-> (Type (<| Return' Value' category)) Text))
(|>> type.reflection reflection.reflection))
(with_template [<consumption> <production> <name> <category> <instruction>]
- [(def: .public (<name> class)
+ [(def .public (<name> class)
(-> (Type <category>) (Bytecode Any))
(do ..monad
[... TODO: Make sure it's impossible to have indexes greater than U2.
@@ -1035,7 +1035,7 @@
[$1 $1 instanceof Object _.instanceof]
)
-(def: .public (iinc register increase)
+(def .public (iinc register increase)
(-> Nat U1 (Bytecode Any))
(do ..monad
[register (..register register)]
@@ -1045,7 +1045,7 @@
(exception.report
"Class" (..reflection class)))
-(def: .public (multianewarray class dimensions)
+(def .public (multianewarray class dimensions)
(-> (Type Object) U1 (Bytecode Any))
(do ..monad
[_ (is (Bytecode Any)
@@ -1055,7 +1055,7 @@
index (..lifted (//constant/pool.class (//name.internal (..reflection class))))]
(..bytecode (//unsigned.lifted/2 dimensions) $1 @_ _.multianewarray [index dimensions])))
-(def: (type_size type)
+(def (type_size type)
(-> (Type Return) Nat)
(cond (same? type.void type)
0
@@ -1068,7 +1068,7 @@
1))
(with_template [<static?> <name> <instruction> <method>]
- [(def: .public (<name> class method type)
+ [(def .public (<name> class method type)
(-> (Type Class) Text (Type Method) (Bytecode Any))
(let [[type_variables inputs output exceptions] (parser.method type)]
(do ..monad
@@ -1094,7 +1094,7 @@
)
(with_template [<consumption> <name> <1> <2>]
- [(def: .public (<name> class field type)
+ [(def .public (<name> class field type)
(-> (Type Class) Text (Type Value) (Bytecode Any))
(do ..monad
[index (<| ..lifted
@@ -1111,7 +1111,7 @@
)
(with_template [<name> <consumption/1> <1> <consumption/2> <2>]
- [(def: .public (<name> class field type)
+ [(def .public (<name> class field type)
(-> (Type Class) Text (Type Value) (Bytecode Any))
(do [! ..monad]
[index (<| ..lifted
@@ -1133,7 +1133,7 @@
"Start" (|> start /address.value //unsigned.value %.nat)
"End" (|> end /address.value //unsigned.value %.nat)))
-(def: .public (try @start @end @handler catch)
+(def .public (try @start @end @handler catch)
(-> Label Label Label (Type Class) (Bytecode Any))
(do ..monad
[@catch (..lifted (//constant/pool.class (//name.internal (..reflection catch))))]
@@ -1157,7 +1157,7 @@
_.empty])))
[]]]})))
-(def: .public (composite pre post)
+(def .public (composite pre post)
(All (_ pre post)
(-> (Bytecode pre) (Bytecode post) (Bytecode post)))
(function (_ state)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/address.lux b/stdlib/source/library/lux/target/jvm/bytecode/address.lux
index ddb1331dc..5c2dd04d2 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/address.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/address.lux
@@ -26,49 +26,49 @@
(primitive .public Address
U2
- (def: .public value
+ (def .public value
(-> Address U2)
(|>> representation))
- (def: .public start
+ (def .public start
Address
(|> 0 ///unsigned.u2 try.trusted abstraction))
- (def: .public (move distance)
+ (def .public (move distance)
(-> U2 (-> Address (Try Address)))
(|>> representation
(///unsigned.+/2 distance)
(at try.functor each (|>> abstraction))))
- (def: with_sign
+ (def with_sign
(-> Address (Try S4))
(|>> representation ///unsigned.value .int ///signed.s4))
- (def: .public (jump from to)
+ (def .public (jump from to)
(-> Address Address (Try Big_Jump))
(do try.monad
[from (with_sign from)
to (with_sign to)]
(///signed.-/4 from to)))
- (def: .public (after? reference subject)
+ (def .public (after? reference subject)
(-> Address Address Bit)
(n.> (|> reference representation ///unsigned.value)
(|> subject representation ///unsigned.value)))
- (def: .public equivalence
+ (def .public equivalence
(Equivalence Address)
(implementation
- (def: (= reference subject)
+ (def (= reference subject)
(at ///unsigned.equivalence =
(representation reference)
(representation subject)))))
- (def: .public writer
+ (def .public writer
(Writer Address)
(|>> representation ///unsigned.writer/2))
- (def: .public format
+ (def .public format
(Format Address)
(|>> representation ///unsigned.value %.nat))
)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
index cc3ff123c..14e8d5543 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
@@ -23,7 +23,7 @@
#stack (Maybe Stack)]))
(with_template [<name> <limit>]
- [(def: .public (<name> type)
+ [(def .public (<name> type)
(-> (Type Method) (Try Environment))
(do try.monad
[limit (<limit> type)]
@@ -37,13 +37,13 @@
(type: .public Condition
(-> Environment (Try Environment)))
-(def: .public monoid
+(def .public monoid
(Monoid Condition)
(implementation
- (def: identity
+ (def identity
(|>> {try.#Success}))
- (def: (composite left right)
+ (def (composite left right)
(function (_ environment)
(do try.monad
[environment (left environment)]
@@ -51,7 +51,7 @@
(exception: .public discontinuity)
-(def: .public (stack environment)
+(def .public (stack environment)
(-> Environment (Try Stack))
(case (the ..#stack environment)
{.#Some stack}
@@ -60,7 +60,7 @@
{.#None}
(exception.except ..discontinuity [])))
-(def: .public discontinue
+(def .public discontinue
(-> Environment Environment)
(.has ..#stack {.#None}))
@@ -70,7 +70,7 @@
"Expected" (/stack.format expected)
"Actual" (/stack.format actual)))
-(def: .public (continue expected environment)
+(def .public (continue expected environment)
(-> Stack Environment (Try [Stack Environment]))
(case (the ..#stack environment)
{.#Some actual}
@@ -81,7 +81,7 @@
{.#None}
{try.#Success [expected (.has ..#stack {.#Some expected} environment)]}))
-(def: .public (consumes amount)
+(def .public (consumes amount)
(-> U2 Condition)
... TODO: Revisit this definition once lenses/optics have been implemented,
... since it can probably be simplified with them.
@@ -91,7 +91,7 @@
current (/stack.pop amount previous)]
(in (.has ..#stack {.#Some current} environment)))))
-(def: .public (produces amount)
+(def .public (produces amount)
(-> U2 Condition)
(function (_ environment)
(do try.monad
@@ -104,7 +104,7 @@
(.has ..#stack {.#Some current})
(.has [..#limit /limit.#stack] limit))))))
-(def: .public (has registry)
+(def .public (has registry)
(-> Registry Condition)
(|>> (revised [..#limit /limit.#registry] (/registry.has registry))
{try.#Success}))
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
index 7702e24e7..261e9a5ce 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
@@ -26,7 +26,7 @@
#registry Registry]))
(with_template [<name> <registry>]
- [(def: .public (<name> type)
+ [(def .public (<name> type)
(-> (Type Method) (Try Limit))
(do try.monad
[registry (<registry> type)]
@@ -37,21 +37,21 @@
[virtual /registry.virtual]
)
-(def: .public length
+(def .public length
(all n.+
... u2 max_stack;
/stack.length
... u2 max_locals;
/registry.length))
-(def: .public equivalence
+(def .public equivalence
(Equivalence Limit)
(all product.equivalence
/stack.equivalence
/registry.equivalence
))
-(def: .public (writer limit)
+(def .public (writer limit)
(Writer Limit)
(all \\format#composite
(/stack.writer (the #stack limit))
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux
index 6e3642501..3aae9a289 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux
@@ -25,17 +25,17 @@
(type: .public Register
U1)
-(def: normal 1)
-(def: wide 2)
+(def normal 1)
+(def wide 2)
(primitive .public Registry
U2
- (def: .public registry
+ (def .public registry
(-> U2 Registry)
(|>> abstraction))
- (def: (minimal type)
+ (def (minimal type)
(-> (Type Method) Nat)
(let [[type_variables inputs output exceptions] (/////type/parser.method type)]
(|> inputs
@@ -47,7 +47,7 @@
(list#mix n.+ 0))))
(with_template [<start> <name>]
- [(def: .public <name>
+ [(def .public <name>
(-> (Type Method) (Try Registry))
(|>> ..minimal
(n.+ <start>)
@@ -58,24 +58,24 @@
[1 virtual]
)
- (def: .public equivalence
+ (def .public equivalence
(Equivalence Registry)
(at equivalence.functor each
(|>> representation)
/////unsigned.equivalence))
- (def: .public writer
+ (def .public writer
(Writer Registry)
(|>> representation /////unsigned.writer/2))
- (def: .public (has needed)
+ (def .public (has needed)
(-> Registry Registry Registry)
(|>> representation
(/////unsigned.max/2 (representation needed))
abstraction))
(with_template [<name> <extra>]
- [(def: .public <name>
+ [(def .public <name>
(-> Register Registry)
(let [extra (|> <extra> /////unsigned.u2 try.trusted)]
(|>> /////unsigned.lifted/2
@@ -88,5 +88,5 @@
)
)
-(def: .public length
+(def .public length
/////unsigned.bytes/2)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux
index a3cec4224..59c3c50ce 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux
@@ -21,7 +21,7 @@
U2
(with_template [<frames> <name>]
- [(def: .public <name>
+ [(def .public <name>
Stack
(|> <frames> /////unsigned.u2 maybe.trusted abstraction))]
@@ -29,22 +29,22 @@
[1 catch]
)
- (def: .public equivalence
+ (def .public equivalence
(Equivalence Stack)
(at equivalence.functor each
(|>> representation)
/////unsigned.equivalence))
- (def: .public writer
+ (def .public writer
(Writer Stack)
(|>> representation /////unsigned.writer/2))
- (def: stack
+ (def stack
(-> U2 Stack)
(|>> abstraction))
(with_template [<op> <name>]
- [(def: .public (<name> amount)
+ [(def .public (<name> amount)
(-> U2 (-> Stack (Try Stack)))
(|>> representation
(<op> amount)
@@ -54,16 +54,16 @@
[/////unsigned.-/2 pop]
)
- (def: .public (max left right)
+ (def .public (max left right)
(-> Stack Stack Stack)
(abstraction
(/////unsigned.max/2 (representation left)
(representation right))))
- (def: .public format
+ (def .public format
(Format Stack)
(|>> representation /////unsigned.value %.nat))
)
-(def: .public length
+(def .public length
/////unsigned.bytes/2)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
index 9345f2ec2..ca4dfcff6 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
@@ -44,18 +44,18 @@
(type: .public Estimator
(-> Address Size))
-(def: fixed
+(def fixed
(-> Size Estimator)
function.constant)
(type: .public Instruction
(-> Specification Specification))
-(def: .public empty
+(def .public empty
Instruction
function.identity)
-(def: .public result
+(def .public result
(-> Instruction Specification)
(function.on \\format.no_op))
@@ -63,7 +63,7 @@
Nat)
(with_template [<size> <name>]
- [(def: <name> Size (|> <size> ///unsigned.u2 try.trusted))]
+ [(def <name> Size (|> <size> ///unsigned.u2 try.trusted))]
[1 opcode_size]
[1 register_size]
@@ -73,14 +73,14 @@
[4 integer_size]
)
-(def: (nullary' opcode)
+(def (nullary' opcode)
(-> Opcode Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value ..opcode_size)
offset)
(binary.has_8! offset opcode binary)]))
-(def: nullary
+(def nullary
[Estimator (-> Opcode Instruction)]
[(..fixed ..opcode_size)
(function (_ opcode [size mutation])
@@ -89,7 +89,7 @@
(|>> mutation ((nullary' opcode)))])])
(with_template [<name> <size>]
- [(def: <name>
+ [(def <name>
Size
(|> ..opcode_size
(///unsigned.+/2 <size>)
@@ -102,7 +102,7 @@
(with_template [<shift> <name> <inputT> <writer> <unwrap>]
[(with_expansions [<private> (template.symbol ["'" <name>])]
- (def: (<private> opcode input0)
+ (def (<private> opcode input0)
(-> Opcode <inputT> Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value <shift>) offset)
@@ -111,7 +111,7 @@
(<writer> (n.+ (///unsigned.value ..opcode_size) offset)
(<unwrap> input0)))]))
- (def: <name>
+ (def <name>
[Estimator (-> Opcode <inputT> Instruction)]
[(..fixed <shift>)
(function (_ opcode input0 [size mutation])
@@ -126,7 +126,7 @@
(with_template [<shift> <name> <inputT> <writer>]
[(with_expansions [<private> (template.symbol ["'" <name>])]
- (def: (<private> opcode input0)
+ (def (<private> opcode input0)
(-> Opcode <inputT> Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value <shift>) offset)
@@ -135,7 +135,7 @@
(<writer> (n.+ (///unsigned.value ..opcode_size) offset)
(///signed.value input0)))]))
- (def: <name>
+ (def <name>
[Estimator (-> Opcode <inputT> Instruction)]
[(..fixed <shift>)
(function (_ opcode input0 [size mutation])
@@ -146,13 +146,13 @@
[..size/2 unary/2' S2 binary.has_16!]
)
-(def: size/11
+(def size/11
Size
(|> ..opcode_size
(///unsigned.+/2 ..register_size) try.trusted
(///unsigned.+/2 ..byte_size) try.trusted))
-(def: (binary/11' opcode input0 input1)
+(def (binary/11' opcode input0 input1)
(-> Opcode U1 U1 Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value ..size/11) offset)
@@ -163,20 +163,20 @@
(binary.has_8! (n.+ (///unsigned.value ..size/1) offset)
(///unsigned.value input1)))]))
-(def: binary/11
+(def binary/11
[Estimator (-> Opcode U1 U1 Instruction)]
[(..fixed ..size/11)
(function (_ opcode input0 input1 [size mutation])
[(n.+ (///unsigned.value ..size/11) size)
(|>> mutation ((binary/11' opcode input0 input1)))])])
-(def: size/21
+(def size/21
Size
(|> ..opcode_size
(///unsigned.+/2 ..index_size) try.trusted
(///unsigned.+/2 ..byte_size) try.trusted))
-(def: (binary/21' opcode input0 input1)
+(def (binary/21' opcode input0 input1)
(-> Opcode U2 U1 Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value ..size/21) offset)
@@ -187,21 +187,21 @@
(binary.has_8! (n.+ (///unsigned.value ..size/2) offset)
(///unsigned.value input1)))]))
-(def: binary/21
+(def binary/21
[Estimator (-> Opcode U2 U1 Instruction)]
[(..fixed ..size/21)
(function (_ opcode input0 input1 [size mutation])
[(n.+ (///unsigned.value ..size/21) size)
(|>> mutation ((binary/21' opcode input0 input1)))])])
-(def: size/211
+(def size/211
Size
(|> ..opcode_size
(///unsigned.+/2 ..index_size) try.trusted
(///unsigned.+/2 ..byte_size) try.trusted
(///unsigned.+/2 ..byte_size) try.trusted))
-(def: (trinary/211' opcode input0 input1 input2)
+(def (trinary/211' opcode input0 input1 input2)
(-> Opcode U2 U1 U1 Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value ..size/211) offset)
@@ -214,7 +214,7 @@
(binary.has_8! (n.+ (///unsigned.value ..size/21) offset)
(///unsigned.value input2)))]))
-(def: trinary/211
+(def trinary/211
[Estimator (-> Opcode U2 U1 U1 Instruction)]
[(..fixed ..size/211)
(function (_ opcode input0 input1 input2 [size mutation])
@@ -224,12 +224,12 @@
(primitive .public Primitive_Array_Type
U1
- (def: code
+ (def code
(-> Primitive_Array_Type U1)
(|>> representation))
(with_template [<code> <name>]
- [(def: .public <name>
+ [(def .public <name>
(|> <code> ///unsigned.u1 try.trusted abstraction))]
[04 t_boolean]
@@ -481,7 +481,7 @@
[<input_name>]
<inputs>')]
- (def: .public <name>
+ (def .public <name>
[Estimator (-> [<input_types>] Instruction)]
(let [[estimator <arity>'] <arity>]
[estimator
@@ -564,7 +564,7 @@
[["B9" invokeinterface [[index (Index (Reference Method))] [count U1] [output_count U1]] [(///index.value index) count (try.trusted (///unsigned.u1 0))]]]]
))
-(def: (switch_padding offset)
+(def (switch_padding offset)
(-> Nat Nat)
(let [parameter_start (n.+ (///unsigned.value ..opcode_size)
offset)]
@@ -572,7 +572,7 @@
(n.- (n.% 4 parameter_start)
4))))
-(def: .public tableswitch
+(def .public tableswitch
[(-> Nat Estimator)
(-> S4 Big_Jump [Big_Jump (List Big_Jump)] Instruction)]
(let [estimator (is (-> Nat Estimator)
@@ -636,7 +636,7 @@
size)
(|>> mutation tableswitch_mutation)]))))]))
-(def: .public lookupswitch
+(def .public lookupswitch
[(-> Nat Estimator)
(-> Big_Jump (List [S4 Big_Jump]) Instruction)]
(let [case_size (n.+ (///unsigned.value ..integer_size)
@@ -694,10 +694,10 @@
size)
(|>> mutation lookupswitch_mutation)]))))]))
-(def: .public monoid
+(def .public monoid
(Monoid Instruction)
(implementation
- (def: identity ..empty)
+ (def identity ..empty)
- (def: (composite left right)
+ (def (composite left right)
(|>> left right))))
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/jump.lux b/stdlib/source/library/lux/target/jvm/bytecode/jump.lux
index 7d608a8e5..676930f65 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/jump.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/jump.lux
@@ -13,17 +13,17 @@
(type: .public Jump
S2)
-(def: .public equivalence
+(def .public equivalence
(Equivalence Jump)
///signed.equivalence)
-(def: .public writer
+(def .public writer
(Writer Jump)
///signed.writer/2)
(type: .public Big_Jump
S4)
-(def: .public lifted
+(def .public lifted
(-> Jump Big_Jump)
///signed.lifted/4)
diff --git a/stdlib/source/library/lux/target/jvm/class.lux b/stdlib/source/library/lux/target/jvm/class.lux
index f93320b4c..cbbc47502 100644
--- a/stdlib/source/library/lux/target/jvm/class.lux
+++ b/stdlib/source/library/lux/target/jvm/class.lux
@@ -57,7 +57,7 @@
["4000" enum]
)
-(def: .public equivalence
+(def .public equivalence
(Equivalence Class)
(all product.equivalence
//unsigned.equivalence
@@ -72,7 +72,7 @@
(sequence.equivalence //method.equivalence)
(sequence.equivalence //attribute.equivalence)))
-(def: (install_classes this super interfaces)
+(def (install_classes this super interfaces)
(-> Internal Internal (List Internal)
(Resource [(Index //constant.Class) (Index //constant.Class) (Sequence (Index //constant.Class))]))
(do [! //pool.monad]
@@ -87,7 +87,7 @@
interfaces))]
(in [@this @super @interfaces])))
-(def: .public (class version modifier
+(def .public (class version modifier
this signature super interfaces
fields methods attributes)
(-> Major (Modifier Class)
@@ -127,7 +127,7 @@
{.#None}
attributes)])))
-(def: .public (writer class)
+(def .public (writer class)
(Writer Class)
(`` (all binaryF#composite
(~~ (with_template [<writer> <slot>]
diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux
index 8539fbf13..ebeccfaa4 100644
--- a/stdlib/source/library/lux/target/jvm/constant.lux
+++ b/stdlib/source/library/lux/target/jvm/constant.lux
@@ -36,28 +36,28 @@
(type: .public UTF8
Text)
-(def: utf8_writer
+(def utf8_writer
(Writer UTF8)
binaryF.utf8_16)
(primitive .public Class
(Index UTF8)
- (def: .public index
+ (def .public index
(-> Class (Index UTF8))
(|>> representation))
- (def: .public class
+ (def .public class
(-> (Index UTF8) Class)
(|>> abstraction))
- (def: .public class_equivalence
+ (def .public class_equivalence
(Equivalence Class)
(at equivalence.functor each
..index
//index.equivalence))
- (def: class_writer
+ (def class_writer
(Writer Class)
(|>> representation //index.writer))
)
@@ -66,10 +66,10 @@
"[1]::[0]"
("static" floatToRawIntBits "manual" [float] int))
-(def: .public float_equivalence
+(def .public float_equivalence
(Equivalence java/lang/Float)
(implementation
- (def: (= parameter subject)
+ (def (= parameter subject)
(for @.old
("jvm feq" parameter subject)
@@ -85,11 +85,11 @@
(primitive .public (Value kind)
kind
- (def: .public value
+ (def .public value
(All (_ kind) (-> (Value kind) kind))
(|>> representation))
- (def: .public (value_equivalence Equivalence<kind>)
+ (def .public (value_equivalence Equivalence<kind>)
(All (_ kind)
(-> (Equivalence kind)
(Equivalence (Value kind))))
@@ -101,7 +101,7 @@
[(type: .public <type>
(Value <marker>))
- (def: .public <constructor>
+ (def .public <constructor>
(-> <marker> <type>)
(|>> abstraction))]
@@ -113,7 +113,7 @@
)
(with_template [<writer_name> <type> <write> <writer>]
- [(def: <writer_name>
+ [(def <writer_name>
(Writer <type>)
(`` (|>> representation
(~~ (template.spliced <write>))
@@ -138,13 +138,13 @@
#name_and_type (Index (Name_And_Type of))]))
(with_template [<type> <equivalence> <writer>]
- [(def: .public <equivalence>
+ [(def .public <equivalence>
(Equivalence (<type> Any))
(all product.equivalence
//index.equivalence
//index.equivalence))
- (def: <writer>
+ (def <writer>
(Writer (<type> Any))
(all binaryF.and
//index.writer
@@ -168,7 +168,7 @@
{#Interface_Method (Reference //category.Method)}
{#Name_And_Type (Name_And_Type Any)}))
-(def: .public (size constant)
+(def .public (size constant)
(-> Constant Nat)
(case constant
(^.or {#Long _} {#Double _})
@@ -177,12 +177,12 @@
_
1))
-(def: .public equivalence
+(def .public equivalence
(Equivalence Constant)
... TODO: Delete the explicit "implementation" and use the combinator
... version below as soon as the new format for variants is implemented.
(implementation
- (def: (= reference sample)
+ (def (= reference sample)
(case [reference sample]
(^.with_template [<tag> <equivalence>]
[[{<tag> reference} {<tag> sample}]
@@ -223,7 +223,7 @@
... )
)
-(def: .public writer
+(def .public writer
(Writer Constant)
(with_expansions [<constants> (these [#UTF8 /tag.utf8 ..utf8_writer]
[#Integer /tag.integer ..integer_writer]
diff --git a/stdlib/source/library/lux/target/jvm/constant/pool.lux b/stdlib/source/library/lux/target/jvm/constant/pool.lux
index b953600bf..787af5c99 100644
--- a/stdlib/source/library/lux/target/jvm/constant/pool.lux
+++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux
@@ -35,7 +35,7 @@
(type: .public Pool
[Index (Sequence [Index Constant])])
-(def: .public equivalence
+(def .public equivalence
(Equivalence Pool)
(product.equivalence //index.equivalence
(sequence.equivalence (product.equivalence //index.equivalence
@@ -44,10 +44,10 @@
(type: .public (Resource a)
(+State Try Pool a))
-(def: .public functor
+(def .public functor
(Functor Resource)
(implementation
- (def: (each $ it)
+ (def (each $ it)
(|>> it
(pipe.case
{try.#Success [state output]}
@@ -57,16 +57,16 @@
failure
(as_expected failure))))))
-(def: .public monad
+(def .public monad
(Monad Resource)
(implementation
- (def: functor ..functor)
+ (def functor ..functor)
- (def: (in it)
+ (def (in it)
(function (_ state)
{try.#Success [state it]}))
- (def: (conjoint it)
+ (def (conjoint it)
(function (_ state)
(case (it state)
{try.#Success [state' it']}
@@ -76,7 +76,7 @@
failure
(as_expected failure))))))
-(def: try|each
+(def try|each
(template (_ <binding> <value> <body>)
[(case <value>
{try.#Success <binding>}
@@ -86,11 +86,11 @@
failure
(as_expected failure))]))
-(def: try|in
+(def try|in
(template (_ <it>)
[{try.#Success <it>}]))
-(def: !add
+(def !add
(template (_ <state> <tag> <equivalence> <value>)
[(let [[current pool] <state>
<value>' <value>]
@@ -120,12 +120,12 @@
(sequence.suffix [current new] pool)]
current]))))))]))
-(def: /|do
+(def /|do
(template (_ <state> <body>)
[(function (_ <state>)
<body>)]))
-(def: /|each
+(def /|each
(template (_ <state> <binding> <value> <body>)
[(case (<value> <state>)
{try.#Success [<state> <binding>]}
@@ -139,7 +139,7 @@
(-> of (Resource (Index of))))
(with_template [<name> <type> <tag> <equivalence>]
- [(def: .public (<name> value)
+ [(def .public (<name> value)
(Adder <type>)
(<| (/|do %)
(!add % <tag> <equivalence> value)))]
@@ -151,21 +151,21 @@
[utf8 UTF8 //.#UTF8 text.equivalence]
)
-(def: .public (string value)
+(def .public (string value)
(-> Text (Resource (Index String)))
(<| (/|do %)
(/|each % @value (utf8 value))
(let [value (//.string @value)])
(!add % //.#String (//.value_equivalence //index.equivalence) value)))
-(def: .public (class name)
+(def .public (class name)
(-> Internal (Resource (Index Class)))
(<| (/|do %)
(/|each % @name (utf8 (//name.read name)))
(let [value (//.class @name)])
(!add % //.#Class //.class_equivalence value)))
-(def: .public (descriptor value)
+(def .public (descriptor value)
(All (_ kind)
(-> (Descriptor kind)
(Resource (Index (Descriptor kind)))))
@@ -178,7 +178,7 @@
[#name UTF8
#descriptor (Descriptor of)]))
-(def: .public (name_and_type [name descriptor])
+(def .public (name_and_type [name descriptor])
(All (_ of)
(-> (Member of) (Resource (Index (Name_And_Type of)))))
(<| (/|do %)
@@ -187,7 +187,7 @@
(!add % //.#Name_And_Type //.name_and_type_equivalence [//.#name @name //.#descriptor @descriptor])))
(with_template [<name> <tag> <of>]
- [(def: .public (<name> class member)
+ [(def .public (<name> class member)
(-> External (Member <of>) (Resource (Index (Reference <of>))))
(<| (/|do %)
(/|each % @class (..class (//name.internal class)))
@@ -199,11 +199,11 @@
[interface_method //.#Interface_Method Method]
)
-(def: !index
+(def !index
(template (_ <index>)
[(|> <index> //index.value //unsigned.value)]))
-(def: .public writer
+(def .public writer
(Writer Pool)
(function (_ [next pool])
(sequence#mix (function (_ [_index post] pre)
@@ -211,7 +211,7 @@
(\\format.bits_16 (!index next))
pool)))
-(def: .public empty
+(def .public empty
Pool
[(|> 1 //unsigned.u2 try.trusted //index.index)
sequence.empty])
diff --git a/stdlib/source/library/lux/target/jvm/constant/tag.lux b/stdlib/source/library/lux/target/jvm/constant/tag.lux
index 2ac10790f..58684f493 100644
--- a/stdlib/source/library/lux/target/jvm/constant/tag.lux
+++ b/stdlib/source/library/lux/target/jvm/constant/tag.lux
@@ -17,15 +17,15 @@
(primitive .public Tag
U1
- (def: .public equivalence
+ (def .public equivalence
(Equivalence Tag)
(implementation
- (def: (= reference sample)
+ (def (= reference sample)
(u1//= (representation reference)
(representation sample)))))
(with_template [<code> <name>]
- [(def: .public <name>
+ [(def .public <name>
Tag
(|> <code> ///unsigned.u1 try.trusted abstraction))]
@@ -45,7 +45,7 @@
[18 invoke_dynamic]
)
- (def: .public writer
+ (def .public writer
(Writer Tag)
(|>> representation ///unsigned.writer/1))
)
diff --git a/stdlib/source/library/lux/target/jvm/encoding/name.lux b/stdlib/source/library/lux/target/jvm/encoding/name.lux
index 2a322bace..068c11a36 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/name.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/name.lux
@@ -7,8 +7,8 @@
[type
[primitive (.except)]]]])
-(def: .public internal_separator "/")
-(def: .public external_separator ".")
+(def .public internal_separator "/")
+(def .public external_separator ".")
(type: .public External
Text)
@@ -16,26 +16,26 @@
(primitive .public Internal
Text
- (def: .public internal
+ (def .public internal
(-> External Internal)
(|>> (text.replaced ..external_separator
..internal_separator)
abstraction))
- (def: .public read
+ (def .public read
(-> Internal Text)
(|>> representation))
- (def: .public external
+ (def .public external
(-> Internal External)
(|>> representation
(text.replaced ..internal_separator
..external_separator))))
-(def: .public safe
+(def .public safe
(-> Text External)
(|>> ..internal ..external))
-(def: .public (qualify package class)
+(def .public (qualify package class)
(-> Text External External)
(format (..safe package) ..external_separator class))
diff --git a/stdlib/source/library/lux/target/jvm/encoding/signed.lux b/stdlib/source/library/lux/target/jvm/encoding/signed.lux
index 822e420b2..b00ff6ba3 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/signed.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/signed.lux
@@ -25,21 +25,21 @@
(primitive .public (Signed brand)
Int
- (def: .public value
+ (def .public value
(-> (Signed Any) Int)
(|>> representation))
- (def: .public equivalence
+ (def .public equivalence
(All (_ brand) (Equivalence (Signed brand)))
(implementation
- (def: (= reference sample)
+ (def (= reference sample)
(i.= (representation reference) (representation sample)))))
- (def: .public order
+ (def .public order
(All (_ brand) (Order (Signed brand)))
(implementation
- (def: equivalence ..equivalence)
- (def: (< reference sample)
+ (def equivalence ..equivalence)
+ (def (< reference sample)
(i.< (representation reference) (representation sample)))))
(exception: .public (value_exceeds_the_scope [value Int
@@ -53,18 +53,18 @@
(primitive <raw> Any)
(type: .public <name> (Signed <raw>)))
- (def: .public <size> <bytes>)
+ (def .public <size> <bytes>)
- (def: .public <maximum>
+ (def .public <maximum>
<name>
(|> <bytes> (n.* i64.bits_per_byte) -- i64.mask abstraction))
- (def: .public <minimum>
+ (def .public <minimum>
<name>
(let [it (representation <maximum>)]
(abstraction (-- (i.- it +0)))))
- (def: .public <constructor>
+ (def .public <constructor>
(-> Int (Try <name>))
(let [positive (representation <maximum>)
negative (i64.not positive)]
@@ -77,7 +77,7 @@
(exception.except ..value_exceeds_the_scope [value <size>])))))
(with_template [<abstract_operation> <concrete_operation>]
- [(def: .public (<abstract_operation> parameter subject)
+ [(def .public (<abstract_operation> parameter subject)
(-> <name> <name> (Try <name>))
(<constructor>
(<concrete_operation> (representation parameter)
@@ -93,7 +93,7 @@
)
(with_template [<name> <from> <to>]
- [(def: .public <name>
+ [(def .public <name>
(-> <from> <to>)
(|>> transmutation))]
@@ -102,7 +102,7 @@
)
(with_template [<writer_name> <type> <writer>]
- [(def: .public <writer_name>
+ [(def .public <writer_name>
(Writer <type>)
(|>> representation <writer>))]
diff --git a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
index bdda3b8a5..0d2a16d52 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
@@ -24,22 +24,22 @@
(primitive .public (Unsigned brand)
Nat
- (def: .public value
+ (def .public value
(-> (Unsigned Any) Nat)
(|>> representation))
- (def: .public equivalence
+ (def .public equivalence
(All (_ brand) (Equivalence (Unsigned brand)))
(implementation
- (def: (= reference sample)
+ (def (= reference sample)
(n.= (representation reference)
(representation sample)))))
- (def: .public order
+ (def .public order
(All (_ brand) (Order (Unsigned brand)))
(implementation
- (def: equivalence ..equivalence)
- (def: (< reference sample)
+ (def equivalence ..equivalence)
+ (def (< reference sample)
(n.< (representation reference)
(representation sample)))))
@@ -65,25 +65,25 @@
(primitive .public <raw> Any)
(type: .public <name> (Unsigned <raw>)))
- (def: .public <size> <bytes>)
+ (def .public <size> <bytes>)
- (def: .public <maximum>
+ (def .public <maximum>
<name>
(|> <bytes> (n.* i64.bits_per_byte) i64.mask abstraction))
- (def: .public (<constructor> value)
+ (def .public (<constructor> value)
(-> Nat (Try <name>))
(if (n.> (representation <maximum>) value)
(exception.except ..value_exceeds_the_maximum [(symbol <name>) value <maximum>])
{try.#Success (abstraction value)}))
- (def: .public (<+> parameter subject)
+ (def .public (<+> parameter subject)
(-> <name> <name> (Try <name>))
(<constructor>
(n.+ (representation parameter)
(representation subject))))
- (def: .public (<-> parameter subject)
+ (def .public (<-> parameter subject)
(-> <name> <name> (Try <name>))
(let [parameter' (representation parameter)
subject' (representation subject)]
@@ -91,7 +91,7 @@
(exception.except ..subtraction_cannot_yield_negative_value [(symbol <name>) parameter subject])
{try.#Success (abstraction (n.- parameter' subject'))})))
- (def: .public (<max> left right)
+ (def .public (<max> left right)
(-> <name> <name> <name>)
(abstraction (n.max (representation left)
(representation right))))]
@@ -102,7 +102,7 @@
)
(with_template [<name> <from> <to>]
- [(def: .public <name>
+ [(def .public <name>
(-> <from> <to>)
(|>> transmutation))]
@@ -111,7 +111,7 @@
)
(with_template [<writer_name> <type> <writer>]
- [(def: .public <writer_name>
+ [(def .public <writer_name>
(Writer <type>)
(|>> representation <writer>))]
diff --git a/stdlib/source/library/lux/target/jvm/field.lux b/stdlib/source/library/lux/target/jvm/field.lux
index b41782db2..fa84b191b 100644
--- a/stdlib/source/library/lux/target/jvm/field.lux
+++ b/stdlib/source/library/lux/target/jvm/field.lux
@@ -41,7 +41,7 @@
["4000" enum]
)
-(def: .public equivalence
+(def .public equivalence
(Equivalence Field)
(all product.equivalence
modifier.equivalence
@@ -49,7 +49,7 @@
//index.equivalence
(sequence.equivalence //attribute.equivalence)))
-(def: .public (writer field)
+(def .public (writer field)
(Writer Field)
(`` (all binaryF#composite
(~~ (with_template [<writer> <slot>]
@@ -61,7 +61,7 @@
[(binaryF.sequence_16 //attribute.writer) #attributes]))
)))
-(def: .public (field modifier name with_signature? type attributes)
+(def .public (field modifier name with_signature? type attributes)
(-> (Modifier Field) UTF8 Bit (Type Value) (Sequence Attribute)
(Resource Field))
(do [! //constant/pool.monad]
diff --git a/stdlib/source/library/lux/target/jvm/index.lux b/stdlib/source/library/lux/target/jvm/index.lux
index e3421fd14..f21318b91 100644
--- a/stdlib/source/library/lux/target/jvm/index.lux
+++ b/stdlib/source/library/lux/target/jvm/index.lux
@@ -12,27 +12,27 @@
[encoding
["[1][0]" unsigned (.only U2)]]])
-(def: .public length
+(def .public length
//unsigned.bytes/2)
(primitive .public (Index kind)
U2
- (def: .public index
+ (def .public index
(All (_ kind) (-> U2 (Index kind)))
(|>> abstraction))
- (def: .public value
+ (def .public value
(-> (Index Any) U2)
(|>> representation))
- (def: .public equivalence
+ (def .public equivalence
(All (_ kind) (Equivalence (Index kind)))
(at equivalence.functor each
..value
//unsigned.equivalence))
- (def: .public writer
+ (def .public writer
(All (_ kind) (Writer (Index kind)))
(|>> representation //unsigned.writer/2))
)
diff --git a/stdlib/source/library/lux/target/jvm/loader.lux b/stdlib/source/library/lux/target/jvm/loader.lux
index ee54b8aef..a16372f06 100644
--- a/stdlib/source/library/lux/target/jvm/loader.lux
+++ b/stdlib/source/library/lux/target/jvm/loader.lux
@@ -65,7 +65,7 @@
"io" "try" (java/lang/Class java/lang/Object)))
(with_expansions [<elemT> (these (java/lang/Class java/lang/Object))]
- (def: java/lang/ClassLoader::defineClass
+ (def java/lang/ClassLoader::defineClass
java/lang/reflect/Method
(let [signature (|> (ffi.array <elemT> 4)
(ffi.write! 0 (as <elemT>
@@ -80,7 +80,7 @@
(ffi.class_for java/lang/ClassLoader))
(java/lang/reflect/AccessibleObject::setAccessible true)))))
-(def: .public (define class_name bytecode loader)
+(def .public (define class_name bytecode loader)
(-> Text Binary java/lang/ClassLoader (Try java/lang/Object))
(let [signature (array.of_list (list (as java/lang/Object
class_name)
@@ -97,11 +97,11 @@
ffi.long_to_int))))]
(java/lang/reflect/Method::invoke loader signature java/lang/ClassLoader::defineClass)))
-(def: .public (new_library _)
+(def .public (new_library _)
(-> Any Library)
(atom.atom (dictionary.empty text.hash)))
-(def: .public (memory library)
+(def .public (memory library)
(-> Library java/lang/ClassLoader)
(with_expansions [<cast> (for @.old
(<|)
@@ -128,7 +128,7 @@
{.#None}
(panic! (exception.error ..unknown [class_name])))))))))
-(def: .public (store name bytecode library)
+(def .public (store name bytecode library)
(-> Text Binary Library (IO (Try Any)))
(do [! io.monad]
[library' (atom.read! library)]
@@ -138,7 +138,7 @@
[_ (atom.update! (dictionary.has name bytecode) library)]
(in {try.#Success []})))))
-(def: .public (load name loader)
+(def .public (load name loader)
(-> Text java/lang/ClassLoader
(IO (Try (java/lang/Class java/lang/Object))))
(java/lang/ClassLoader::loadClass (ffi.as_string name) loader))
diff --git a/stdlib/source/library/lux/target/jvm/magic.lux b/stdlib/source/library/lux/target/jvm/magic.lux
index 72f5ef52c..a4064361e 100644
--- a/stdlib/source/library/lux/target/jvm/magic.lux
+++ b/stdlib/source/library/lux/target/jvm/magic.lux
@@ -12,11 +12,11 @@
(type: .public Magic
U4)
-(def: .public code
+(def .public code
Magic
(|> (hex "CAFEBABE")
//unsigned.u4
try.trusted))
-(def: .public writer
+(def .public writer
//unsigned.writer/4)
diff --git a/stdlib/source/library/lux/target/jvm/method.lux b/stdlib/source/library/lux/target/jvm/method.lux
index bdbe58f87..082ede18b 100644
--- a/stdlib/source/library/lux/target/jvm/method.lux
+++ b/stdlib/source/library/lux/target/jvm/method.lux
@@ -52,7 +52,7 @@
["1000" synthetic]
)
-(def: .public (method modifier name with_signature? type attributes code)
+(def .public (method modifier name with_signature? type attributes code)
(-> (Modifier Method) UTF8 Bit (Type //category.Method) (List (Resource Attribute)) (Maybe (Bytecode Any))
(Resource Method))
(do [! //pool.monad]
@@ -89,7 +89,7 @@
#descriptor @descriptor
#attributes attributes])))
-(def: .public equivalence
+(def .public equivalence
(Equivalence Method)
(all product.equivalence
//modifier.equivalence
@@ -98,7 +98,7 @@
(sequence.equivalence //attribute.equivalence)
))
-(def: .public (writer field)
+(def .public (writer field)
(Writer Method)
(`` (all \\format#composite
(~~ (with_template [<writer> <slot>]
diff --git a/stdlib/source/library/lux/target/jvm/modifier.lux b/stdlib/source/library/lux/target/jvm/modifier.lux
index 04db97f3f..1034f5cab 100644
--- a/stdlib/source/library/lux/target/jvm/modifier.lux
+++ b/stdlib/source/library/lux/target/jvm/modifier.lux
@@ -26,66 +26,66 @@
(primitive .public (Modifier of)
//unsigned.U2
- (def: .public code
+ (def .public code
(-> (Modifier Any) //unsigned.U2)
(|>> representation))
- (def: .public equivalence
+ (def .public equivalence
(All (_ of) (Equivalence (Modifier of)))
(implementation
- (def: (= reference sample)
+ (def (= reference sample)
(at //unsigned.equivalence =
(representation reference)
(representation sample)))))
- (def: !wrap
+ (def !wrap
(template (_ value)
[(|> value
//unsigned.u2
try.trusted
abstraction)]))
- (def: !unwrap
+ (def !unwrap
(template (_ value)
[(|> value
representation
//unsigned.value)]))
- (def: .public (has? sub super)
+ (def .public (has? sub super)
(All (_ of) (-> (Modifier of) (Modifier of) Bit))
(let [sub (!unwrap sub)]
(|> (!unwrap super)
(i64.and sub)
(at i64.equivalence = sub))))
- (def: .public monoid
+ (def .public monoid
(All (_ of) (Monoid (Modifier of)))
(implementation
- (def: identity
+ (def identity
(!wrap (hex "0000")))
- (def: (composite left right)
+ (def (composite left right)
(!wrap (i64.or (!unwrap left) (!unwrap right))))))
- (def: .public empty
+ (def .public empty
Modifier
(at ..monoid identity))
- (def: .public writer
+ (def .public writer
(All (_ of) (Writer (Modifier of)))
(|>> representation //unsigned.writer/2))
- (def: modifier
+ (def modifier
(-> Nat Modifier)
(|>> !wrap))
)
-(def: .public modifiers
+(def .public modifiers
(syntax (_ [ofT <code>.any
options (<>.many <code>.any)])
(with_symbols [g!modifier g!code]
(in (list (` (with_template [(~ g!code) (~ g!modifier)]
- [(def: (~' .public) (~ g!modifier)
+ [(def (~' .public) (~ g!modifier)
(..Modifier (~ ofT))
((~! ..modifier) ((~! number.hex) (~ g!code))))]
diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux
index 8369ce2f0..e09c3d85a 100644
--- a/stdlib/source/library/lux/target/jvm/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/reflection.lux
@@ -109,7 +109,7 @@
[cannot_convert_to_a_lux_type]
)
-(def: .public (load class_loader name)
+(def .public (load class_loader name)
(-> java/lang/ClassLoader External (Try (java/lang/Class java/lang/Object)))
(case (java/lang/Class::forName name false class_loader)
{try.#Failure _}
@@ -118,14 +118,14 @@
success
success))
-(def: .public (sub? class_loader super sub)
+(def .public (sub? class_loader super sub)
(-> java/lang/ClassLoader External External (Try Bit))
(do try.monad
[super (..load class_loader super)
sub (..load class_loader sub)]
(in (java/lang/Class::isAssignableFrom sub super))))
-(def: (class' parameter reflection)
+(def (class' parameter reflection)
(-> (-> java/lang/reflect/Type (Try (/.Type Parameter)))
java/lang/reflect/Type
(Try (/.Type Class)))
@@ -171,7 +171,7 @@
... else
(exception.except ..cannot_convert_to_a_lux_type [reflection])))
-(def: .public (parameter type reflection)
+(def .public (parameter type reflection)
(-> (-> java/lang/reflect/Type (Try (/.Type Value)))
(-> java/lang/reflect/Type (Try (/.Type Parameter))))
(<| (case (ffi.as java/lang/reflect/TypeVariable reflection)
@@ -218,7 +218,7 @@
_)
(..class' (parameter type) reflection)))
-(def: .public (type reflection)
+(def .public (type reflection)
(-> java/lang/reflect/Type (Try (/.Type Value)))
(<| (case (ffi.as java/lang/Class reflection)
{.#Some reflection}
@@ -245,12 +245,12 @@
... else
(..parameter type reflection)))
-(def: .public class
+(def .public class
(-> java/lang/reflect/Type
(Try (/.Type Class)))
(..class' (..parameter ..type)))
-(def: .public (return reflection)
+(def .public (return reflection)
(-> java/lang/reflect/Type (Try (/.Type Return)))
(with_expansions [<else> (these (..type reflection))]
(case (ffi.as java/lang/Class reflection)
@@ -286,7 +286,7 @@
(exception.report
"Type" (%.type type)))
-(def: .public (correspond class type)
+(def .public (correspond class type)
(-> (java/lang/Class java/lang/Object) Type (Try Mapping))
(case type
(pattern {.#Primitive (static array.type_name) (list :member:)})
@@ -346,7 +346,7 @@
[not_a_virtual_field]
)
-(def: .public (field field target)
+(def .public (field field target)
(-> Text (java/lang/Class java/lang/Object) (Try java/lang/reflect/Field))
(case (java/lang/Class::getDeclaredField field target)
{try.#Success field}
@@ -358,7 +358,7 @@
{try.#Failure _}
(exception.except ..unknown_field [field target])))
-(def: .public deprecated?
+(def .public deprecated?
(-> (array.Array java/lang/annotation/Annotation) Bit)
(|>> (array.list {.#None})
(list.all (|>> (ffi.as java/lang/Deprecated)))
@@ -366,7 +366,7 @@
not))
(with_template [<name> <exception> <then?> <else?>]
- [(def: .public (<name> field class)
+ [(def .public (<name> field class)
(-> Text (java/lang/Class java/lang/Object) (Try [Bit Bit (/.Type Value)]))
(do [! try.monad]
[fieldJ (..field field class)
diff --git a/stdlib/source/library/lux/target/jvm/type.lux b/stdlib/source/library/lux/target/jvm/type.lux
index 18c21263c..3734c5e99 100644
--- a/stdlib/source/library/lux/target/jvm/type.lux
+++ b/stdlib/source/library/lux/target/jvm/type.lux
@@ -43,7 +43,7 @@
#super_interfaces (List (Type Class))]))
(with_template [<name> <style>]
- [(def: .public (<name> type)
+ [(def .public (<name> type)
(All (_ category) (-> (Type category) (<style> category)))
(let [[signature descriptor reflection] (representation type)]
<name>))]
@@ -52,7 +52,7 @@
[descriptor Descriptor]
)
- (def: .public (reflection type)
+ (def .public (reflection type)
(All (_ category)
(-> (Type (<| Return' Value' category))
(Reflection (<| Return' Value' category))))
@@ -60,7 +60,7 @@
reflection))
(with_template [<category> <name> <signature> <descriptor> <reflection>]
- [(def: .public <name>
+ [(def .public <name>
(Type <category>)
(abstraction [<signature> <descriptor> <reflection>]))]
@@ -75,28 +75,28 @@
[Primitive char /signature.char /descriptor.char /reflection.char]
)
- (def: .public (array type)
+ (def .public (array type)
(-> (Type Value) (Type Array))
(abstraction
[(/signature.array (..signature type))
(/descriptor.array (..descriptor type))
(/reflection.array (..reflection type))]))
- (def: .public (class name parameters)
+ (def .public (class name parameters)
(-> External (List (Type Parameter)) (Type Class))
(abstraction
[(/signature.class name (list#each ..signature parameters))
(/descriptor.class name)
(/reflection.class name)]))
- (def: .public (declaration name variables)
+ (def .public (declaration name variables)
(-> External (List (Type Var)) (Type Declaration))
(abstraction
[(/signature.declaration name (list#each ..signature variables))
(/descriptor.declaration name)
(/reflection.declaration name)]))
- (def: .public (as_class type)
+ (def .public (as_class type)
(-> (Type Declaration) (Type Class))
(abstraction
(let [[signature descriptor reflection] (representation type)]
@@ -104,21 +104,21 @@
(/descriptor.as_class descriptor)
(/reflection.as_class reflection)])))
- (def: .public wildcard
+ (def .public wildcard
(Type Parameter)
(abstraction
[/signature.wildcard
/descriptor.wildcard
/reflection.wildcard]))
- (def: .public (var name)
+ (def .public (var name)
(-> Text (Type Var))
(abstraction
[(/signature.var name)
/descriptor.var
/reflection.var]))
- (def: .public (lower bound)
+ (def .public (lower bound)
(-> (Type Parameter) (Type Parameter))
(abstraction
(let [[signature descriptor reflection] (representation bound)]
@@ -126,7 +126,7 @@
(/descriptor.lower descriptor)
(/reflection.lower reflection)])))
- (def: .public (upper bound)
+ (def .public (upper bound)
(-> (Type Parameter) (Type Parameter))
(abstraction
(let [[signature descriptor reflection] (representation bound)]
@@ -134,7 +134,7 @@
(/descriptor.upper descriptor)
(/reflection.upper reflection)])))
- (def: .public (method [type_variables inputs output exceptions])
+ (def .public (method [type_variables inputs output exceptions])
(-> [(List (Type Var))
(List (Type Value))
(Type Return)
@@ -149,21 +149,21 @@
(..descriptor output)])
(as_expected ..void)]))
- (def: .public equivalence
+ (def .public equivalence
(All (_ category) (Equivalence (Type category)))
(implementation
- (def: (= parameter subject)
+ (def (= parameter subject)
(at /signature.equivalence =
(..signature parameter)
(..signature subject)))))
- (def: .public hash
+ (def .public hash
(All (_ category) (Hash (Type category)))
(implementation
- (def: equivalence ..equivalence)
- (def: hash (|>> ..signature (at /signature.hash hash)))))
+ (def equivalence ..equivalence)
+ (def hash (|>> ..signature (at /signature.hash hash)))))
- (def: .public (primitive? type)
+ (def .public (primitive? type)
(-> (Type Value) (Either (Type Object)
(Type Primitive)))
(if (`` (or (~~ (with_template [<type>]
@@ -180,7 +180,7 @@
(|> type (as (Type Primitive)) {.#Right})
(|> type (as (Type Object)) {.#Left})))
- (def: .public (void? type)
+ (def .public (void? type)
(-> (Type Return) (Either (Type Value)
(Type Void)))
(if (`` (or (~~ (with_template [<type>]
@@ -191,7 +191,7 @@
(|> type (as (Type Value)) {.#Left})))
)
-(def: .public (class? type)
+(def .public (class? type)
(-> (Type Value) (Maybe External))
(let [repr (|> type ..descriptor /descriptor.descriptor)]
(if (and (text.starts_with? /descriptor.class_prefix repr)
@@ -206,6 +206,6 @@
(at maybe.monad each (|>> //name.internal //name.external))))
{.#None})))
-(def: .public format
+(def .public format
(All (_ a) (Format (Type a)))
(|>> ..signature /signature.signature))
diff --git a/stdlib/source/library/lux/target/jvm/type/alias.lux b/stdlib/source/library/lux/target/jvm/type/alias.lux
index 89e4148c6..0ec86571b 100644
--- a/stdlib/source/library/lux/target/jvm/type/alias.lux
+++ b/stdlib/source/library/lux/target/jvm/type/alias.lux
@@ -27,11 +27,11 @@
(type: .public Aliasing
(Dictionary Text Text))
-(def: .public fresh
+(def .public fresh
Aliasing
(dictionary.empty text.hash))
-(def: (var aliasing)
+(def (var aliasing)
(-> Aliasing (Parser (Type Var)))
(do <>.monad
[var //parser.var']
@@ -40,7 +40,7 @@
(maybe.else var)
//.var))))
-(def: (class parameter)
+(def (class parameter)
(-> (Parser (Type Parameter)) (Parser (Type Class)))
(|> (do <>.monad
[name //parser.class_name
@@ -53,7 +53,7 @@
(<>.before (<text>.this //descriptor.class_suffix))))
(with_template [<name> <prefix> <bound> <constructor>]
- [(def: <name>
+ [(def <name>
(-> (Parser (Type Class)) (Parser (Type Parameter)))
(|>> (<>.after (<text>.this <prefix>))
(at <>.monad each <bound>)))]
@@ -62,7 +62,7 @@
[upper //signature.upper_prefix //.upper ..Upper]
)
-(def: (parameter aliasing)
+(def (parameter aliasing)
(-> Aliasing (Parser (Type Parameter)))
(<>.rec
(function (_ parameter)
@@ -75,7 +75,7 @@
class
)))))
-(def: (value aliasing)
+(def (value aliasing)
(-> Aliasing (Parser (Type Value)))
(<>.rec
(function (_ value)
@@ -85,37 +85,37 @@
(//parser.array' value)
))))
-(def: (inputs aliasing)
+(def (inputs aliasing)
(-> Aliasing (Parser (List (Type Value))))
(|> (<>.some (..value aliasing))
(<>.after (<text>.this //signature.arguments_start))
(<>.before (<text>.this //signature.arguments_end))))
-(def: (return aliasing)
+(def (return aliasing)
(-> Aliasing (Parser (Type Return)))
(all <>.either
//parser.void
(..value aliasing)
))
-(def: (exception aliasing)
+(def (exception aliasing)
(-> Aliasing (Parser (Type Class)))
(|> (..class (..parameter aliasing))
(<>.after (<text>.this //signature.exception_prefix))))
-(def: (bound aliasing)
+(def (bound aliasing)
(-> Aliasing (Parser (Type Class)))
(do <>.monad
[_ (<text>.this ":")]
(..class (..parameter aliasing))))
-(def: (bound_type_var aliasing)
+(def (bound_type_var aliasing)
(-> Aliasing (Parser (Type Var)))
(|> //parser.var_name
(at <>.monad each //.var)
(<>.before (<>.many (..bound aliasing)))))
-(def: .public (method aliasing)
+(def .public (method aliasing)
(-> Aliasing (-> (Type Method) (Type Method)))
(|>> //.signature
//signature.signature
diff --git a/stdlib/source/library/lux/target/jvm/type/box.lux b/stdlib/source/library/lux/target/jvm/type/box.lux
index 08a6e1213..051f45391 100644
--- a/stdlib/source/library/lux/target/jvm/type/box.lux
+++ b/stdlib/source/library/lux/target/jvm/type/box.lux
@@ -6,7 +6,7 @@
[name (.only External)]]])
(with_template [<name> <box>]
- [(def: .public <name> External <box>)]
+ [(def .public <name> External <box>)]
[boolean "java.lang.Boolean"]
[byte "java.lang.Byte"]
diff --git a/stdlib/source/library/lux/target/jvm/type/descriptor.lux b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
index 99b3987d5..3de5b4483 100644
--- a/stdlib/source/library/lux/target/jvm/type/descriptor.lux
+++ b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
@@ -24,12 +24,12 @@
(primitive .public (Descriptor category)
Text
- (def: .public descriptor
+ (def .public descriptor
(-> (Descriptor Any) Text)
(|>> representation))
(with_template [<sigil> <category> <name>]
- [(def: .public <name>
+ [(def .public <name>
(Descriptor <category>)
(abstraction <sigil>))]
@@ -44,26 +44,26 @@
["C" Primitive char]
)
- (def: .public class_prefix "L")
- (def: .public class_suffix ";")
+ (def .public class_prefix "L")
+ (def .public class_suffix ";")
- (def: .public class
+ (def .public class
(-> External (Descriptor Class))
(|>> ///name.internal
///name.read
(text.enclosed [..class_prefix ..class_suffix])
abstraction))
- (def: .public (declaration name)
+ (def .public (declaration name)
(-> External (Descriptor Declaration))
(transmutation (..class name)))
- (def: .public as_class
+ (def .public as_class
(-> (Descriptor Declaration) (Descriptor Class))
(|>> transmutation))
(with_template [<name> <category>]
- [(def: .public <name>
+ [(def .public <name>
(Descriptor <category>)
(transmutation
(..class "java.lang.Object")))]
@@ -72,24 +72,24 @@
[wildcard Parameter]
)
- (def: .public (lower descriptor)
+ (def .public (lower descriptor)
(-> (Descriptor Parameter) (Descriptor Parameter))
..wildcard)
- (def: .public upper
+ (def .public upper
(-> (Descriptor Parameter) (Descriptor Parameter))
(|>> transmutation))
- (def: .public array_prefix "[")
+ (def .public array_prefix "[")
- (def: .public array
+ (def .public array
(-> (Descriptor Value)
(Descriptor Array))
(|>> representation
(format ..array_prefix)
abstraction))
- (def: .public (method [inputs output])
+ (def .public (method [inputs output])
(-> [(List (Descriptor Value))
(Descriptor Return)]
(Descriptor Method))
@@ -100,13 +100,13 @@
(text.enclosed ["(" ")"]))
(representation output))))
- (def: .public equivalence
+ (def .public equivalence
(All (_ category) (Equivalence (Descriptor category)))
(implementation
- (def: (= parameter subject)
+ (def (= parameter subject)
(text#= (representation parameter) (representation subject)))))
- (def: .public class_name
+ (def .public class_name
(-> (Descriptor Object) Internal)
(let [prefix_size (text.size ..class_prefix)
suffix_size (text.size ..class_suffix)]
diff --git a/stdlib/source/library/lux/target/jvm/type/lux.lux b/stdlib/source/library/lux/target/jvm/type/lux.lux
index ea7951cee..3490eaed9 100644
--- a/stdlib/source/library/lux/target/jvm/type/lux.lux
+++ b/stdlib/source/library/lux/target/jvm/type/lux.lux
@@ -38,7 +38,7 @@
(type: .public Mapping
(Dictionary Text Type))
-(def: .public fresh
+(def .public fresh
Mapping
(dictionary.empty text.hash))
@@ -46,13 +46,13 @@
(exception.report
"Var" (%.text var)))
-(def: void
+(def void
(Parser (Check Type))
(<>.after //parser.void
(<>#in (check#in .Any))))
(with_template [<name> <parser> <reflection>]
- [(def: <name>
+ [(def <name>
(Parser (Check Type))
(<>.after <parser>
(<>#in (check#in {.#Primitive (//reflection.reflection <reflection>) {.#End}}))))]
@@ -68,7 +68,7 @@
)
(with_template [<name> <parser> <box>]
- [(def: <name>
+ [(def <name>
(Parser (Check Type))
(<>.after <parser>
(<>#in (check#in {.#Primitive <box> {.#End}}))))]
@@ -83,7 +83,7 @@
[boxed_char //parser.char //box.char]
)
-(def: primitive
+(def primitive
(Parser (Check Type))
(all <>.either
..boolean
@@ -96,7 +96,7 @@
..char
))
-(def: boxed_primitive
+(def boxed_primitive
(Parser (Check Type))
(all <>.either
..boxed_boolean
@@ -109,13 +109,13 @@
..boxed_char
))
-(def: wildcard
+(def wildcard
(Parser (Check Type))
(<>.after //parser.wildcard
(<>#in (check#each product.right
check.existential))))
-(def: (var mapping)
+(def (var mapping)
(-> Mapping (Parser (Check Type)))
(do <>.monad
[var //parser.var']
@@ -126,7 +126,7 @@
{.#Some type}
(check#in type)))))
-(def: (class' parameter)
+(def (class' parameter)
(-> (Parser (Check Type)) (Parser (Check Type)))
(|> (do <>.monad
[name //parser.class_name
@@ -141,7 +141,7 @@
(<>.before (<text>.this //descriptor.class_suffix))))
(with_template [<name> <prefix> <constructor>]
- [(def: <name>
+ [(def <name>
(-> (Parser (Check Type)) (Parser (Check Type)))
(|> (<>.after (<text>.this <prefix>))
... TODO: Re-enable Lower and Upper, instead of using the simplified limit.
@@ -152,7 +152,7 @@
[upper //signature.upper_prefix ..Upper]
)
-(def: (parameter mapping)
+(def (parameter mapping)
(-> Mapping (Parser (Check Type)))
(<>.rec
(function (_ parameter)
@@ -165,11 +165,11 @@
class
)))))
-(def: .public class
+(def .public class
(-> Mapping (Parser (Check Type)))
(|>> ..parameter ..class'))
-(def: array
+(def array
(-> (Parser (Check Type)) (Parser (Check Type)))
(|>> (<>#each (check#each (function (_ elementT)
(case elementT
@@ -192,7 +192,7 @@
(|> elementT array.Array .type)))))
(<>.after (<text>.this //descriptor.array_prefix))))
-(def: .public (type mapping)
+(def .public (type mapping)
(-> Mapping (Parser (Check Type)))
(<>.rec
(function (_ type)
@@ -202,7 +202,7 @@
(..array type)
))))
-(def: .public (boxed_type mapping)
+(def .public (boxed_type mapping)
(-> Mapping (Parser (Check Type)))
(<>.rec
(function (_ type)
@@ -212,21 +212,21 @@
(..array type)
))))
-(def: .public (return mapping)
+(def .public (return mapping)
(-> Mapping (Parser (Check Type)))
(all <>.either
..void
(..type mapping)
))
-(def: .public (boxed_return mapping)
+(def .public (boxed_return mapping)
(-> Mapping (Parser (Check Type)))
(all <>.either
..void
(..boxed_type mapping)
))
-(def: .public (check operation input)
+(def .public (check operation input)
(All (_ a) (-> (Parser (Check a)) Text (Check a)))
(case (<text>.result operation input)
{try.#Success check}
diff --git a/stdlib/source/library/lux/target/jvm/type/parser.lux b/stdlib/source/library/lux/target/jvm/type/parser.lux
index 999cb620f..9eb9db150 100644
--- a/stdlib/source/library/lux/target/jvm/type/parser.lux
+++ b/stdlib/source/library/lux/target/jvm/type/parser.lux
@@ -23,7 +23,7 @@
["[1][0]" name (.only External)]]]])
(with_template [<category> <name> <signature> <type>]
- [(def: .public <name>
+ [(def .public <name>
(Parser (Type <category>))
(<>.after (<text>.this (//signature.signature <signature>))
(<>#in <type>)))]
@@ -40,7 +40,7 @@
[Parameter wildcard //signature.wildcard //.wildcard]
)
-(def: .public primitive
+(def .public primitive
(Parser (Type Primitive))
(all <>.either
..boolean
@@ -53,20 +53,20 @@
..char
))
-(def: var/head
+(def var/head
(format "abcdefghijklmnopqrstuvwxyz"
"ABCDEFGHIJKLMNOPQRSTUVWXYZ"
"_"))
-(def: var/tail
+(def var/tail
(format var/head
"0123456789$"))
-(def: class/set
+(def class/set
(format var/tail //name.internal_separator))
(with_template [<type> <name> <head> <tail> <adapter>]
- [(def: .public <name>
+ [(def .public <name>
(Parser <type>)
(at <>.functor each <adapter>
(<text>.slice (<text>.and! (<text>.one_of! <head>)
@@ -76,24 +76,24 @@
[Text var_name var/head var/tail function.identity]
)
-(def: .public var'
+(def .public var'
(Parser Text)
(|> ..var_name
(<>.after (<text>.this //signature.var_prefix))
(<>.before (<text>.this //descriptor.class_suffix))))
-(def: .public var
+(def .public var
(Parser (Type Var))
(<>#each //.var ..var'))
-(def: .public var?
+(def .public var?
(-> (Type Value) (Maybe Text))
(|>> //.signature
//signature.signature
(<text>.result ..var')
try.maybe))
-(def: .public name
+(def .public name
(-> (Type Var) Text)
(|>> //.signature
//signature.signature
@@ -101,7 +101,7 @@
try.trusted))
(with_template [<name> <prefix> <constructor>]
- [(def: <name>
+ [(def <name>
(-> (Parser (Type Parameter)) (Parser (Type Parameter)))
(|>> (<>.after (<text>.this <prefix>))
(<>#each <constructor>)))]
@@ -110,7 +110,7 @@
[upper //signature.upper_prefix //.upper]
)
-(def: (class'' parameter)
+(def (class'' parameter)
(-> (Parser (Type Parameter)) (Parser [External (List (Type Parameter))]))
(|> (do <>.monad
[name ..class_name
@@ -122,17 +122,17 @@
(<>.after (<text>.this //descriptor.class_prefix))
(<>.before (<text>.this //descriptor.class_suffix))))
-(def: class'
+(def class'
(-> (Parser (Type Parameter)) (Parser (Type Class)))
(|>> ..class''
(at <>.monad each (product.uncurried //.class))))
-(def: .public array'
+(def .public array'
(-> (Parser (Type Value)) (Parser (Type Array)))
(|>> (<>.after (<text>.this //descriptor.array_prefix))
(<>#each //.array)))
-(def: (parameter' value)
+(def (parameter' value)
(-> (Parser (Type Value)) (Parser (Type Parameter)))
(<>.rec
(function (_ parameter)
@@ -146,7 +146,7 @@
class
)))))
-(def: .public value
+(def .public value
(Parser (Type Value))
(<>.rec
(function (_ value)
@@ -155,16 +155,16 @@
(..parameter' value)
))))
-(def: .public parameter
+(def .public parameter
(Parser (Type Parameter))
(..parameter' ..value))
-(def: .public class
+(def .public class
(Parser (Type Class))
(..class' ..parameter))
(with_template [<name> <prefix> <constructor>]
- [(def: .public <name>
+ [(def .public <name>
(-> (Type Value) (Maybe (Type Parameter)))
(|>> //.signature
//signature.signature
@@ -175,39 +175,39 @@
[upper? //signature.upper_prefix //.upper]
)
-(def: .public read_class
+(def .public read_class
(-> (Type Class) [External (List (Type Parameter))])
(|>> //.signature
//signature.signature
(<text>.result (..class'' ..parameter))
try.trusted))
-(def: .public array
+(def .public array
(Parser (Type Array))
(..array' ..value))
-(def: .public object
+(def .public object
(Parser (Type Object))
(all <>.either
..class
..array))
-(def: inputs
+(def inputs
(|> (<>.some ..value)
(<>.after (<text>.this //signature.arguments_start))
(<>.before (<text>.this //signature.arguments_end))))
-(def: .public return
+(def .public return
(Parser (Type Return))
(<>.either ..void
..value))
-(def: exception
+(def exception
(Parser (Type Class))
(|> ..class
(<>.after (<text>.this //signature.exception_prefix))))
-(def: .public var_declaration
+(def .public var_declaration
(Parser [(Type Var) (Type Class)])
(do <>.monad
[name ..var_name
@@ -215,7 +215,7 @@
type ..class]
(in [(//.var name) type])))
-(def: .public method
+(def .public method
(-> (Type Method)
[(List (Type Var))
(List (Type Value))
@@ -239,7 +239,7 @@
try.trusted)))
(with_template [<name> <category> <parser>]
- [(def: .public <name>
+ [(def .public <name>
(-> (Type Value) (Maybe <category>))
(|>> //.signature
//signature.signature
@@ -259,7 +259,7 @@
[object? (Type Object) ..object]
)
-(def: .public declaration'
+(def .public declaration'
(Parser [External (List (Type Var))])
(|> (<>.and ..class_name
(|> (<>.some ..var)
@@ -269,7 +269,7 @@
(<>.after (<text>.this //descriptor.class_prefix))
(<>.before (<text>.this //descriptor.class_suffix))))
-(def: .public declaration
+(def .public declaration
(-> (Type Declaration) [External (List (Type Var))])
(|>> //.signature
//signature.signature
diff --git a/stdlib/source/library/lux/target/jvm/type/reflection.lux b/stdlib/source/library/lux/target/jvm/type/reflection.lux
index 7794fedc3..cfd7be86b 100644
--- a/stdlib/source/library/lux/target/jvm/type/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/type/reflection.lux
@@ -18,18 +18,18 @@
(primitive .public (Reflection category)
Text
- (def: .public reflection
+ (def .public reflection
(-> (Reflection Any) Text)
(|>> representation))
- (def: .public equivalence
+ (def .public equivalence
(All (_ category) (Equivalence (Reflection category)))
(implementation
- (def: (= parameter subject)
+ (def (= parameter subject)
(text#= (representation parameter) (representation subject)))))
(with_template [<category> <name> <reflection>]
- [(def: .public <name>
+ [(def .public <name>
(Reflection <category>)
(abstraction <reflection>))]
@@ -44,19 +44,19 @@
[Primitive char "char"]
)
- (def: .public class
+ (def .public class
(-> External (Reflection Class))
(|>> abstraction))
- (def: .public (declaration name)
+ (def .public (declaration name)
(-> External (Reflection Declaration))
(transmutation (..class name)))
- (def: .public as_class
+ (def .public as_class
(-> (Reflection Declaration) (Reflection Class))
(|>> transmutation))
- (def: .public (array element)
+ (def .public (array element)
(-> (Reflection Value) (Reflection Array))
(let [element' (representation element)
elementR (`` (cond (text.starts_with? //descriptor.array_prefix element')
@@ -85,7 +85,7 @@
abstraction)))
(with_template [<name> <category>]
- [(def: .public <name>
+ [(def .public <name>
(Reflection <category>)
(transmutation
(..class "java.lang.Object")))]
@@ -94,11 +94,11 @@
[wildcard Parameter]
)
- (def: .public (lower reflection)
+ (def .public (lower reflection)
(-> (Reflection Parameter) (Reflection Parameter))
..wildcard)
- (def: .public upper
+ (def .public upper
(-> (Reflection Parameter) (Reflection Parameter))
(|>> transmutation))
)
diff --git a/stdlib/source/library/lux/target/jvm/type/signature.lux b/stdlib/source/library/lux/target/jvm/type/signature.lux
index 610706176..288b0a75e 100644
--- a/stdlib/source/library/lux/target/jvm/type/signature.lux
+++ b/stdlib/source/library/lux/target/jvm/type/signature.lux
@@ -23,12 +23,12 @@
(primitive .public (Signature category)
Text
- (def: .public signature
+ (def .public signature
(-> (Signature Any) Text)
(|>> representation))
(with_template [<category> <name> <descriptor>]
- [(def: .public <name>
+ [(def .public <name>
(Signature <category>)
(abstraction (//descriptor.descriptor <descriptor>)))]
@@ -43,18 +43,18 @@
[Primitive char //descriptor.char]
)
- (def: .public array
+ (def .public array
(-> (Signature Value) (Signature Array))
(|>> representation
(format //descriptor.array_prefix)
abstraction))
- (def: .public wildcard
+ (def .public wildcard
(Signature Parameter)
(abstraction "*"))
(with_template [<char> <name>]
- [(def: .public <name> <char>)]
+ [(def .public <name> <char>)]
["T" var_prefix]
["-" lower_prefix]
@@ -70,7 +70,7 @@
)
(with_template [<name> <prefix>]
- [(def: .public <name>
+ [(def .public <name>
(-> (Signature Parameter) (Signature Parameter))
(|>> representation (format <prefix>) abstraction))]
@@ -78,18 +78,18 @@
[upper ..upper_prefix]
)
- (def: .public var
+ (def .public var
(-> Text (Signature Var))
(|>> (text.enclosed [..var_prefix //descriptor.class_suffix])
abstraction))
- (def: .public var_name
+ (def .public var_name
(-> (Signature Var) Text)
(|>> representation
(text.replaced ..var_prefix "")
(text.replaced //descriptor.class_suffix "")))
- (def: .public (class name parameters)
+ (def .public (class name parameters)
(-> External (List (Signature Parameter)) (Signature Class))
(abstraction
(format //descriptor.class_prefix
@@ -106,28 +106,28 @@
..parameters_end))
//descriptor.class_suffix)))
- (def: .public (declaration name variables)
+ (def .public (declaration name variables)
(-> External (List (Signature Var)) (Signature Declaration))
(transmutation (..class name variables)))
- (def: class_bound
+ (def class_bound
(|> (..class "java.lang.Object" (list))
..signature
(format ..format_type_parameter_infix)))
- (def: var_declaration/1
+ (def var_declaration/1
(-> (Signature Var) Text)
(|>> ..var_name
(text.suffix ..class_bound)))
- (def: var_declaration/+
+ (def var_declaration/+
(-> (List (Signature Var)) Text)
(|>> (list#each ..var_declaration/1)
text.together
(text.enclosed [..parameters_start
..parameters_end])))
- (def: var_declaration/*
+ (def var_declaration/*
(-> (List (Signature Var)) Text)
(|>> (pipe.case
{.#End}
@@ -136,7 +136,7 @@
it
(..var_declaration/+ it))))
- (def: .public (inheritance variables super interfaces)
+ (def .public (inheritance variables super interfaces)
(-> (List (Signature Var)) (Signature Class) (List (Signature Class)) (Signature Inheritance))
(abstraction
(format (var_declaration/* variables)
@@ -145,11 +145,11 @@
(list#each ..signature)
text.together))))
- (def: .public as_class
+ (def .public as_class
(-> (Signature Declaration) (Signature Class))
(|>> transmutation))
- (def: .public (method [type_variables inputs output exceptions])
+ (def .public (method [type_variables inputs output exceptions])
(-> [(List (Signature Var))
(List (Signature Value))
(Signature Return)
@@ -167,16 +167,16 @@
(list#each (|>> representation (format ..exception_prefix)))
text.together))))
- (def: .public equivalence
+ (def .public equivalence
(All (_ category) (Equivalence (Signature category)))
(implementation
- (def: (= parameter subject)
+ (def (= parameter subject)
(text#= (representation parameter)
(representation subject)))))
- (def: .public hash
+ (def .public hash
(All (_ category) (Hash (Signature category)))
(implementation
- (def: equivalence ..equivalence)
- (def: hash (|>> representation text#hash))))
+ (def equivalence ..equivalence)
+ (def hash (|>> representation text#hash))))
)
diff --git a/stdlib/source/library/lux/target/jvm/version.lux b/stdlib/source/library/lux/target/jvm/version.lux
index 60778c7f7..9b23f8fff 100644
--- a/stdlib/source/library/lux/target/jvm/version.lux
+++ b/stdlib/source/library/lux/target/jvm/version.lux
@@ -11,14 +11,14 @@
(type: .public Minor Version)
(type: .public Major Version)
-(def: .public default_minor
+(def .public default_minor
Minor
(|> 0
//unsigned.u2
try.trusted))
(with_template [<number> <name>]
- [(def: .public <name>
+ [(def .public <name>
Major
(|> <number>
//unsigned.u2
@@ -38,5 +38,5 @@
[56 v12]
)
-(def: .public writer
+(def .public writer
//unsigned.writer/2)
diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux
index 67986980d..7ac944f82 100644
--- a/stdlib/source/library/lux/target/lua.lux
+++ b/stdlib/source/library/lux/target/lua.lux
@@ -28,38 +28,38 @@
[primitive (.except)]]]])
... Added the carriage return for better Windows compatibility.
-(def: \n+
+(def \n+
Text
(format text.carriage_return text.new_line))
-(def: nested
+(def nested
(-> Text Text)
(.let [nested_new_line (format text.new_line text.tab)]
(|>> (format \n+)
(text.replaced text.new_line nested_new_line))))
-(def: input_separator ", ")
+(def input_separator ", ")
(primitive .public (Code brand)
Text
- (def: .public equivalence
+ (def .public equivalence
(All (_ brand) (Equivalence (Code brand)))
(implementation
- (def: (= reference subject)
+ (def (= reference subject)
(at text.equivalence = (representation reference) (representation subject)))))
- (def: .public hash
+ (def .public hash
(All (_ brand) (Hash (Code brand)))
(implementation
- (def: equivalence ..equivalence)
- (def: hash (|>> representation (at text.hash hash)))))
+ (def equivalence ..equivalence)
+ (def hash (|>> representation (at text.hash hash)))))
- (def: .public manual
+ (def .public manual
(-> Text Code)
(|>> abstraction))
- (def: .public code
+ (def .public code
(-> (Code Any) Text)
(|>> representation))
@@ -85,18 +85,18 @@
[Label [Code]]
)
- (def: .public nil
+ (def .public nil
Literal
(abstraction "nil"))
- (def: .public boolean
+ (def .public boolean
(-> Bit Literal)
(|>> (pipe.case
#0 "false"
#1 "true")
abstraction))
- (def: .public int
+ (def .public int
(-> Int Literal)
... Integers must be turned into hexadecimal to avoid quirks in how Lua parses integers.
... In particular, the number -9223372036854775808 will be incorrectly parsed as a float by Lua.
@@ -106,7 +106,7 @@
(format "0x")
abstraction)))
- (def: .public float
+ (def .public float
(-> Frac Literal)
(|>> (pipe.cond [(f.= f.positive_infinity)]
[(pipe.new "(1.0/0.0)" [])]
@@ -121,7 +121,7 @@
[%.frac (text.replaced "+" "")])
abstraction))
- (def: safe
+ (def safe
(-> Text Text)
(`` (|>> (~~ (with_template [<find> <replace>]
[(text.replaced <find> <replace>)]
@@ -138,24 +138,24 @@
))
)))
- (def: .public string
+ (def .public string
(-> Text Literal)
(|>> ..safe (text.enclosed' text.double_quote) abstraction))
- (def: .public multi
+ (def .public multi
(-> (List Expression) Expression)
(|>> (list#each ..code)
(text.interposed ..input_separator)
abstraction))
- (def: .public array
+ (def .public array
(-> (List Expression) Literal)
(|>> (list#each ..code)
(text.interposed ..input_separator)
(text.enclosed ["{" "}"])
abstraction))
- (def: .public table
+ (def .public table
(-> (List [Text Expression]) Literal)
(|>> (list#each (.function (_ [key value])
(format key " = " (representation value))))
@@ -163,21 +163,21 @@
(text.enclosed ["({" "})"])
abstraction))
- (def: .public (item idx array)
+ (def .public (item idx array)
(-> Expression Expression Access)
(abstraction (format "(" (representation array) ")[" (representation idx) "]")))
- (def: .public (the field table)
+ (def .public (the field table)
(-> Text Expression Access)
(abstraction (format (representation table) "." field)))
- (def: .public length
+ (def .public length
(-> Expression Computation)
(|>> representation
(text.enclosed ["#(" ")"])
abstraction))
- (def: .public (apply args func)
+ (def .public (apply args func)
(-> (List Expression) Expression Computation)
(|> args
(list#each ..code)
@@ -186,7 +186,7 @@
(format (representation func))
abstraction))
- (def: .public (do method args table)
+ (def .public (do method args table)
(-> Text (List Expression) Expression Computation)
(|> args
(list#each ..code)
@@ -196,7 +196,7 @@
abstraction))
(with_template [<op> <name>]
- [(def: .public (<name> parameter subject)
+ [(def .public (<name> parameter subject)
(-> Expression Expression Expression)
(abstraction (format "("
(representation subject)
@@ -229,7 +229,7 @@
)
(with_template [<name> <unary>]
- [(def: .public (<name> subject)
+ [(def .public (<name> subject)
(-> Expression Expression)
(abstraction (format "(" <unary> " " (representation subject) ")")))]
@@ -238,7 +238,7 @@
)
(with_template [<name> <type>]
- [(def: .public <name>
+ [(def .public <name>
(-> Text <type>)
(|>> abstraction))]
@@ -246,66 +246,66 @@
[label Label]
)
- (def: .public statement
+ (def .public statement
(-> Expression Statement)
(|>> representation abstraction))
- (def: .public (then pre! post!)
+ (def .public (then pre! post!)
(-> Statement Statement Statement)
(abstraction
(format (representation pre!)
\n+
(representation post!))))
- (def: locations
+ (def locations
(-> (List Location) Text)
(|>> (list#each ..code)
(text.interposed ..input_separator)))
- (def: .public (local vars)
+ (def .public (local vars)
(-> (List Var) Statement)
(abstraction (format "local " (..locations vars))))
- (def: .public (set vars value)
+ (def .public (set vars value)
(-> (List Location) Expression Statement)
(abstraction (format (..locations vars) " = " (representation value))))
- (def: .public (let vars value)
+ (def .public (let vars value)
(-> (List Var) Expression Statement)
(abstraction (format "local " (..locations vars) " = " (representation value))))
- (def: .public (local/1 var value)
+ (def .public (local/1 var value)
(-> Var Expression Statement)
(abstraction (format "local " (representation var) " = " (representation value))))
- (def: .public (if test then! else!)
+ (def .public (if test then! else!)
(-> Expression Statement Statement Statement)
(abstraction (format "if " (representation test)
\n+ "then" (..nested (representation then!))
\n+ "else" (..nested (representation else!))
\n+ "end")))
- (def: .public (when test then!)
+ (def .public (when test then!)
(-> Expression Statement Statement)
(abstraction (format "if " (representation test)
\n+ "then" (..nested (representation then!))
\n+ "end")))
- (def: .public (while test body!)
+ (def .public (while test body!)
(-> Expression Statement Statement)
(abstraction
(format "while " (representation test) " do"
(..nested (representation body!))
\n+ "end")))
- (def: .public (repeat until body!)
+ (def .public (repeat until body!)
(-> Expression Statement Statement)
(abstraction
(format "repeat"
(..nested (representation body!))
\n+ "until " (representation until))))
- (def: .public (for_in vars source body!)
+ (def .public (for_in vars source body!)
(-> (List Var) Expression Statement Statement)
(abstraction
(format "for " (|> vars
@@ -315,7 +315,7 @@
(..nested (representation body!))
\n+ "end")))
- (def: .public (for_step var from to step body!)
+ (def .public (for_step var from to step body!)
(-> Var Expression Expression Expression Statement
Statement)
(abstraction
@@ -326,11 +326,11 @@
(..nested (representation body!))
\n+ "end")))
- (def: .public (return value)
+ (def .public (return value)
(-> Expression Statement)
(abstraction (format "return " (representation value))))
- (def: .public (closure args body!)
+ (def .public (closure args body!)
(-> (List Var) Statement Expression)
(|> (format "function " (|> args
..locations
@@ -341,7 +341,7 @@
abstraction))
(with_template [<name> <code> <binding>]
- [(def: .public (<name> name args body!)
+ [(def .public (<name> name args body!)
(-> <binding> (List Var) Statement Statement)
(abstraction
(format <code> " " (representation name)
@@ -355,25 +355,25 @@
[local_function "local function" Var]
)
- (def: .public break
+ (def .public break
Statement
(abstraction "break"))
- (def: .public (set_label label)
+ (def .public (set_label label)
(-> Label Statement)
(abstraction (format "::" (representation label) "::")))
- (def: .public (go_to label)
+ (def .public (go_to label)
(-> Label Statement)
(abstraction (format "goto " (representation label))))
... https://www.lua.org/pil/1.3.html
- (def: .public (comment commentary on)
+ (def .public (comment commentary on)
(All (_ kind) (-> Text (Code kind) (Code kind)))
(abstraction (format "-- " commentary \n+ (representation on))))
)
-(def: arity_inputs
+(def arity_inputs
(syntax (_ [arity <code>.nat])
(in (case arity
0 (.list)
@@ -381,7 +381,7 @@
(enum.range n.enum 0)
(list#each (|>> %.nat code.local)))))))
-(def: arity_types
+(def arity_types
(syntax (_ [arity <code>.nat])
(in (list.repeated arity (` ..Expression)))))
@@ -390,7 +390,7 @@
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
(with_template [<function>]
- [(`` (def: .public ((~~ (template.symbol [<function> "/" <arity>])) <inputs>)
+ [(`` (def .public ((~~ (template.symbol [<function> "/" <arity>])) <inputs>)
(-> <types> Computation)
(..apply (.list <inputs>) (..var <function>))))]
diff --git a/stdlib/source/library/lux/target/php.lux b/stdlib/source/library/lux/target/php.lux
index 892b98a25..c7ec0f9f5 100644
--- a/stdlib/source/library/lux/target/php.lux
+++ b/stdlib/source/library/lux/target/php.lux
@@ -26,48 +26,48 @@
[type
[primitive (.except)]]]])
-(def: input_separator ", ")
-(def: statement_suffix ";")
+(def input_separator ", ")
+(def statement_suffix ";")
... Added the carriage return for better Windows compatibility.
-(def: \n+
+(def \n+
Text
(format text.carriage_return text.new_line))
-(def: nested
+(def nested
(-> Text Text)
(.let [nested_new_line (format text.new_line text.tab)]
(|>> (format \n+)
(text.replaced text.new_line nested_new_line))))
-(def: block
+(def block
(-> Text Text)
(|>> ..nested (text.enclosed ["{" (format \n+ "}")])))
-(def: group
+(def group
(-> Text Text)
(text.enclosed ["(" ")"]))
(primitive .public (Code brand)
Text
- (def: .public equivalence
+ (def .public equivalence
(All (_ brand) (Equivalence (Code brand)))
(implementation
- (def: (= reference subject)
+ (def (= reference subject)
(at text.equivalence = (representation reference) (representation subject)))))
- (def: .public hash
+ (def .public hash
(All (_ brand) (Hash (Code brand)))
(implementation
- (def: equivalence ..equivalence)
- (def: hash (|>> representation (at text.hash hash)))))
+ (def equivalence ..equivalence)
+ (def hash (|>> representation (at text.hash hash)))))
- (def: .public manual
+ (def .public manual
(-> Text Code)
(|>> abstraction))
- (def: .public code
+ (def .public code
(-> (Code Any) Text)
(|>> representation))
@@ -100,18 +100,18 @@
[#reference? Bit
#var Var]))
- (def: .public ;
+ (def .public ;
(-> Expression Statement)
(|>> representation
(text.suffix ..statement_suffix)
abstraction))
- (def: .public var
+ (def .public var
(-> Text Var)
(|>> (format "$") abstraction))
(with_template [<name> <type>]
- [(def: .public <name>
+ [(def .public <name>
(-> Text <type>)
(|>> abstraction))]
@@ -119,27 +119,27 @@
[label Label]
)
- (def: .public (set_label label)
+ (def .public (set_label label)
(-> Label Statement)
(abstraction (format (representation label) ":")))
- (def: .public (go_to label)
+ (def .public (go_to label)
(-> Label Statement)
(abstraction
(format "goto " (representation label) ..statement_suffix)))
- (def: .public null
+ (def .public null
Literal
(abstraction "NULL"))
- (def: .public bool
+ (def .public bool
(-> Bit Literal)
(|>> (pipe.case
#0 "false"
#1 "true")
abstraction))
- (def: .public int
+ (def .public int
(-> Int Literal)
(.let [to_hex (at n.hex encoded)]
(|>> .nat
@@ -147,7 +147,7 @@
(format "0x")
abstraction)))
- (def: .public float
+ (def .public float
(-> Frac Literal)
(|>> (pipe.cond [(f.= f.positive_infinity)]
[(pipe.new "+INF" [])]
@@ -162,7 +162,7 @@
[%.frac])
abstraction))
- (def: safe
+ (def safe
(-> Text Text)
(`` (|>> (~~ (with_template [<find> <replace>]
[(text.replaced <find> <replace>)]
@@ -180,27 +180,27 @@
))
)))
- (def: .public string
+ (def .public string
(-> Text Literal)
(|>> ..safe
(text.enclosed [text.double_quote text.double_quote])
abstraction))
- (def: arguments
+ (def arguments
(-> (List Expression) Text)
(|>> (list#each ..code) (text.interposed ..input_separator) ..group))
- (def: .public (apply args func)
+ (def .public (apply args func)
(-> (List Expression) Expression Computation)
(|> (format (representation func) (..arguments args))
abstraction))
... TODO: Remove when no longer using JPHP.
- (def: .public (apply' args func)
+ (def .public (apply' args func)
(-> (List Expression) Expression Computation)
(apply (list.partial func args) (..constant "call_user_func")))
- (def: parameters
+ (def parameters
(-> (List Argument) Text)
(|>> (list#each (function (_ [reference? var])
(.if reference?
@@ -210,7 +210,7 @@
..group))
(with_template [<name> <reference?>]
- [(def: .public <name>
+ [(def .public <name>
(-> Var Argument)
(|>> [<reference?>]))]
@@ -218,7 +218,7 @@
[reference #1]
)
- (def: .public (closure uses arguments body!)
+ (def .public (closure uses arguments body!)
(-> (List Argument) (List Argument) Statement Literal)
(let [uses (case uses
{.#End}
@@ -232,7 +232,7 @@
..group
abstraction)))
- (def: arity_inputs
+ (def arity_inputs
(syntax (_ [arity <code>.nat])
(in (case arity
0 (.list)
@@ -240,7 +240,7 @@
(enum.range n.enum 0)
(list#each (|>> %.nat code.local)))))))
- (def: arity_types
+ (def arity_types
(syntax (_ [arity <code>.nat])
(in (list.repeated arity (` ..Expression)))))
@@ -249,12 +249,12 @@
<inputs> (arity_inputs <arity>)
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
- (def: .public (<apply> function [<inputs>])
+ (def .public (<apply> function [<inputs>])
(-> Expression [<types>] Computation)
(..apply (.list <inputs>) function))
(with_template [<function>]
- [(`` (def: .public (~~ (template.symbol [<function> "/" <arity>]))
+ [(`` (def .public (~~ (template.symbol [<function> "/" <arity>]))
(<apply> (..constant <function>))))]
<definitions>))]
@@ -309,11 +309,11 @@
["iconv_substr"] ["substr"]]]
)
- (def: .public (key_value key value)
+ (def .public (key_value key value)
(-> Expression Expression Expression)
(abstraction (format (representation key) " => " (representation value))))
- (def: .public (array/* values)
+ (def .public (array/* values)
(-> (List Expression) Literal)
(|> values
(list#each ..code)
@@ -322,11 +322,11 @@
(format "array")
abstraction))
- (def: .public (array_merge/+ required optionals)
+ (def .public (array_merge/+ required optionals)
(-> Expression (List Expression) Computation)
(..apply (list.partial required optionals) (..constant "array_merge")))
- (def: .public (array/** kvs)
+ (def .public (array/** kvs)
(-> (List [Expression Expression]) Literal)
(|> kvs
(list#each (function (_ [key value])
@@ -336,32 +336,32 @@
(format "array")
abstraction))
- (def: .public (new constructor inputs)
+ (def .public (new constructor inputs)
(-> Constant (List Expression) Computation)
(|> (format "new " (representation constructor) (arguments inputs))
abstraction))
- (def: .public (the field object)
+ (def .public (the field object)
(-> Text Expression Computation)
(|> (format (representation object) "->" field)
abstraction))
- (def: .public (do method inputs object)
+ (def .public (do method inputs object)
(-> Text (List Expression) Expression Computation)
(|> (format (representation (..the method object))
(..arguments inputs))
abstraction))
- (def: .public (item idx array)
+ (def .public (item idx array)
(-> Expression Expression Access)
(|> (format (representation array) "[" (representation idx) "]")
abstraction))
- (def: .public (global name)
+ (def .public (global name)
(-> Text Global)
(|> (..var "GLOBALS") (..item (..string name)) transmutation))
- (def: .public (? test then else)
+ (def .public (? test then else)
(-> Expression Expression Expression Computation)
(|> (format (..group (representation test)) " ? "
(..group (representation then)) " : "
@@ -370,7 +370,7 @@
abstraction))
(with_template [<name> <op>]
- [(def: .public (<name> parameter subject)
+ [(def .public (<name> parameter subject)
(-> Expression Expression Computation)
(|> (format (representation subject) " " <op> " " (representation parameter))
..group
@@ -398,7 +398,7 @@
)
(with_template [<unary> <name>]
- [(def: .public <name>
+ [(def .public <name>
(-> Computation Computation)
(|>> representation (format <unary>) abstraction))]
@@ -407,22 +407,22 @@
["-" opposite]
)
- (def: .public (set var value)
+ (def .public (set var value)
(-> Location Expression Computation)
(|> (format (representation var) " = " (representation value))
..group
abstraction))
- (def: .public (set! var value)
+ (def .public (set! var value)
(-> Location Expression Statement)
(abstraction (format (representation var) " = " (representation value) ";")))
- (def: .public (set? var)
+ (def .public (set? var)
(-> Var Computation)
(..apply/1 [var] (..constant "isset")))
(with_template [<name> <modifier>]
- [(def: .public <name>
+ [(def .public <name>
(-> Var Statement)
(|>> representation (format <modifier> " ") (text.suffix ..statement_suffix) abstraction))]
@@ -430,7 +430,7 @@
)
(with_template [<name> <modifier> <location>]
- [(def: .public (<name> location value)
+ [(def .public (<name> location value)
(-> <location> Expression Statement)
(abstraction (format <modifier> " " (representation location)
" = " (representation value)
@@ -440,7 +440,7 @@
[define_constant "const" Constant]
)
- (def: .public (if test then! else!)
+ (def .public (if test then! else!)
(-> Expression Statement Statement Statement)
(abstraction
(format "if" (..group (representation test)) " "
@@ -448,33 +448,33 @@
" else "
(..block (representation else!)))))
- (def: .public (when test then!)
+ (def .public (when test then!)
(-> Expression Statement Statement)
(abstraction
(format "if" (..group (representation test)) " "
(..block (representation then!)))))
- (def: .public (then pre! post!)
+ (def .public (then pre! post!)
(-> Statement Statement Statement)
(abstraction
(format (representation pre!)
\n+
(representation post!))))
- (def: .public (while test body!)
+ (def .public (while test body!)
(-> Expression Statement Statement)
(abstraction
(format "while" (..group (representation test)) " "
(..block (representation body!)))))
- (def: .public (do_while test body!)
+ (def .public (do_while test body!)
(-> Expression Statement Statement)
(abstraction
(format "do " (..block (representation body!))
" while" (..group (representation test))
..statement_suffix)))
- (def: .public (for_each array value body!)
+ (def .public (for_each array value body!)
(-> Expression Var Statement Statement)
(abstraction
(format "foreach(" (representation array)
@@ -487,14 +487,14 @@
#exception Var
#handler Statement]))
- (def: (catch except)
+ (def (catch except)
(-> Except Text)
(let [declaration (format (representation (.the #class except))
" " (representation (.the #exception except)))]
(format "catch" (..group declaration) " "
(..block (representation (.the #handler except))))))
- (def: .public (try body! excepts)
+ (def .public (try body! excepts)
(-> Statement (List Except) Statement)
(abstraction
(format "try " (..block (representation body!))
@@ -504,7 +504,7 @@
(text.interposed \n+)))))
(with_template [<name> <keyword>]
- [(def: .public <name>
+ [(def .public <name>
(-> Expression Statement)
(|>> representation (format <keyword> " ") (text.suffix ..statement_suffix) abstraction))]
@@ -513,13 +513,13 @@
[echo "echo"]
)
- (def: .public (define name value)
+ (def .public (define name value)
(-> Constant Expression Expression)
(..apply/2 (..constant "define")
[(|> name representation ..string)
value]))
- (def: .public (define_function name arguments body!)
+ (def .public (define_function name arguments body!)
(-> Constant (List Argument) Statement Statement)
(abstraction
(format "function " (representation name)
@@ -528,7 +528,7 @@
(..block (representation body!)))))
(with_template [<name> <keyword>]
- [(def: .public <name>
+ [(def .public <name>
Statement
(|> <keyword>
(text.suffix ..statement_suffix)
@@ -538,18 +538,18 @@
[continue "continue"]
)
- (def: .public splat
+ (def .public splat
(-> Expression Expression)
(|>> representation (format "...") abstraction))
)
-(def: .public (cond clauses else!)
+(def .public (cond clauses else!)
(-> (List [Expression Statement]) Statement Statement)
(list#mix (function (_ [test then!] next!)
(..if test then! next!))
else!
(list.reversed clauses)))
-(def: .public command_line_arguments
+(def .public command_line_arguments
Var
(..var "argv"))
diff --git a/stdlib/source/library/lux/target/python.lux b/stdlib/source/library/lux/target/python.lux
index 4e85ea258..54a9dbd9c 100644
--- a/stdlib/source/library/lux/target/python.lux
+++ b/stdlib/source/library/lux/target/python.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux (.except Location Code not or and list if int comment exec try the is)
+ [lux (.except Location Code not or and list if int comment exec try the is def)
["@" target]
["[0]" ffi]
[abstract
@@ -27,10 +27,10 @@
[type
[primitive (.except)]]]])
-(def: input_separator
+(.def input_separator
", ")
-(def: expression
+(.def expression
(-> Text Text)
(text.enclosed ["(" ")"]))
@@ -43,11 +43,11 @@
(these))
... Added the carriage return for better Windows compatibility.
-(def: \n+
+(.def \n+
Text
(format text.carriage_return text.new_line))
-(def: nested
+(.def nested
(-> Text Text)
(.let [nested_new_line (format text.new_line text.tab)]
(for @.old (|>> (format \n+)
@@ -60,23 +60,23 @@
(primitive .public (Code brand)
Text
- (def: .public equivalence
+ (.def .public equivalence
(All (_ brand) (Equivalence (Code brand)))
(implementation
- (def: (= reference subject)
+ (.def (= reference subject)
(at text.equivalence = (representation reference) (representation subject)))))
- (def: .public hash
+ (.def .public hash
(All (_ brand) (Hash (Code brand)))
(implementation
- (def: equivalence ..equivalence)
- (def: hash (|>> representation (at text.hash hash)))))
+ (.def equivalence ..equivalence)
+ (.def hash (|>> representation (at text.hash hash)))))
- (def: .public manual
+ (.def .public manual
(-> Text Code)
(|>> abstraction))
- (def: .public code
+ (.def .public code
(-> (Code Any) Text)
(|>> representation))
@@ -113,12 +113,12 @@
[KVar Keyword]
)
- (def: .public var
+ (.def .public var
(-> Text SVar)
(|>> abstraction))
(with_template [<name> <brand> <prefix>]
- [(def: .public <name>
+ [(.def .public <name>
(-> SVar (Var <brand>))
(|>> representation (format <prefix>) abstraction))]
@@ -126,26 +126,26 @@
[keyword Keyword "**"]
)
- (def: .public none
+ (.def .public none
Literal
(abstraction "None"))
- (def: .public bool
+ (.def .public bool
(-> Bit Literal)
(|>> (pipe.case
#0 "False"
#1 "True")
abstraction))
- (def: .public int
+ (.def .public int
(-> Int Literal)
(|>> %.int abstraction))
- (def: .public (long value)
+ (.def .public (long value)
(-> Int Literal)
(abstraction (format (%.int value) "L")))
- (def: .public float
+ (.def .public float
(-> Frac Literal)
(`` (|>> (pipe.cond (~~ (with_template [<test> <python>]
[[<test>]
@@ -160,7 +160,7 @@
[%.frac])
abstraction)))
- (def: safe
+ (.def safe
(-> Text Text)
(`` (|>> (~~ (with_template [<find> <replace>]
[(text.replaced <find> <replace>)]
@@ -177,20 +177,20 @@
))
)))
- (def: .public string
+ (.def .public string
(-> Text Literal)
(|>> ..safe
(text.enclosed [text.double_quote text.double_quote])
abstraction))
- (def: .public unicode
+ (.def .public unicode
(-> Text Literal)
(|>> ..string
representation
(format "u")
abstraction))
- (def: (composite_literal left_delimiter right_delimiter entry_serializer)
+ (.def (composite_literal left_delimiter right_delimiter entry_serializer)
(All (_ a)
(-> Text Text (-> a Text)
(-> (List a) Literal)))
@@ -204,7 +204,7 @@
right_delimiter))))
(with_template [<name> <pre> <post>]
- [(def: .public <name>
+ [(.def .public <name>
(-> (List (Expression Any)) Literal)
(composite_literal <pre> <post> ..code))]
@@ -212,23 +212,23 @@
[list "[" "]"]
)
- (def: .public (slice from to list)
+ (.def .public (slice from to list)
(-> (Expression Any) (Expression Any) (Expression Any) Access)
(<| abstraction
... ..expression
(format (representation list) "[" (representation from) ":" (representation to) "]")))
- (def: .public (slice_from from list)
+ (.def .public (slice_from from list)
(-> (Expression Any) (Expression Any) Access)
(<| abstraction
... ..expression
(format (representation list) "[" (representation from) ":]")))
- (def: .public dict
+ (.def .public dict
(-> (List [(Expression Any) (Expression Any)]) (Computation Any))
(composite_literal "{" "}" (.function (_ [k v]) (format (representation k) " : " (representation v)))))
- (def: .public (apply args func)
+ (.def .public (apply args func)
(-> (List (Expression Any)) (Expression Any) (Computation Any))
(<| abstraction
... ..expression
@@ -238,7 +238,7 @@
")")))
(with_template [<name> <brand> <prefix>]
- [(def: .public <name>
+ [(.def .public <name>
(-> (Expression Any) (Expression Any))
(|>> representation
(format <prefix>)
@@ -248,28 +248,28 @@
[splat_keyword Keyword "**"]
)
- (def: .public (the name object)
+ (.def .public (the name object)
(-> Text (Expression Any) Access)
(abstraction (format (representation object) "." name)))
- (def: .public (do method args object)
+ (.def .public (do method args object)
(-> Text (List (Expression Any)) (Expression Any) (Computation Any))
(|> object
(..the method)
(..apply args)))
- (def: .public (item idx array)
+ (.def .public (item idx array)
(-> (Expression Any) (Expression Any) Access)
(abstraction (format (representation array) "[" (representation idx) "]")))
- (def: .public (? test then else)
+ (.def .public (? test then else)
(-> (Expression Any) (Expression Any) (Expression Any) (Computation Any))
(<| abstraction
..expression
(format (representation then) " if " (representation test) " else " (representation else))))
(with_template [<name> <op>]
- [(def: .public (<name> param subject)
+ [(.def .public (<name> param subject)
(-> (Expression Any) (Expression Any) (Computation Any))
(<| abstraction
..expression
@@ -301,7 +301,7 @@
)
(with_template [<name> <unary>]
- [(def: .public (<name> subject)
+ [(.def .public (<name> subject)
(-> (Expression Any) (Computation Any))
(<| abstraction
... ..expression
@@ -311,31 +311,31 @@
[opposite "-"]
)
- (def: .public (lambda arguments body)
+ (.def .public (lambda arguments body)
(-> (List (Var Any)) (Expression Any) (Computation Any))
(<| abstraction
..expression
(format "lambda " (|> arguments (list#each ..code) (text.interposed ..input_separator))
": " (representation body))))
- (def: .public (set vars value)
+ (.def .public (set vars value)
(-> (List (Location Any)) (Expression Any) (Statement Any))
(abstraction
(format (|> vars (list#each ..code) (text.interposed ..input_separator))
" = "
(representation value))))
- (def: .public multi
+ (.def .public multi
(-> (List (Expression Any)) (Expression Any))
(|>> (list#each ..code)
(text.interposed ..input_separator)
abstraction))
- (def: .public (delete where)
+ (.def .public (delete where)
(-> (Location Any) (Statement Any))
(abstraction (format "del " (representation where))))
- (def: .public (if test then! else!)
+ (.def .public (if test then! else!)
(-> (Expression Any) (Statement Any) (Statement Any) (Statement Any))
(abstraction
(format "if " (representation test) ":"
@@ -343,13 +343,13 @@
\n+ "else:"
(..nested (representation else!)))))
- (def: .public (when test then!)
+ (.def .public (when test then!)
(-> (Expression Any) (Statement Any) (Statement Any))
(abstraction
(format "if " (representation test) ":"
(..nested (representation then!)))))
- (def: .public (then pre! post!)
+ (.def .public (then pre! post!)
(-> (Statement Any) (Statement Any) (Statement Any))
(abstraction
(format (representation pre!)
@@ -357,7 +357,7 @@
(representation post!))))
(with_template [<keyword> <0>]
- [(def: .public <0>
+ [(.def .public <0>
(Statement Any)
(abstraction <keyword>))]
@@ -365,7 +365,7 @@
["continue" continue]
)
- (def: .public (while test body! else!)
+ (.def .public (while test body! else!)
(-> (Expression Any) (Statement Any) (Maybe (Statement Any)) Loop)
(abstraction
(format "while " (representation test) ":"
@@ -378,17 +378,17 @@
{.#None}
""))))
- (def: .public (for_in var inputs body!)
+ (.def .public (for_in var inputs body!)
(-> SVar (Expression Any) (Statement Any) Loop)
(abstraction
(format "for " (representation var) " in " (representation inputs) ":"
(..nested (representation body!)))))
- (def: .public statement
+ (.def .public statement
(-> (Expression Any) (Statement Any))
(|>> transmutation))
- (def: .public pass
+ (.def .public pass
(Statement Any)
(abstraction "pass"))
@@ -398,7 +398,7 @@
#exception SVar
#handler (Statement Any)]))
- (def: .public (try body! excepts)
+ (.def .public (try body! excepts)
(-> (Statement Any) (List Except) (Statement Any))
(abstraction
(format "try:"
@@ -411,7 +411,7 @@
text.together))))
(with_template [<name> <keyword> <pre>]
- [(def: .public (<name> value)
+ [(.def .public (<name> value)
(-> (Expression Any) (Statement Any))
(abstraction
(format <keyword> (<pre> (representation value)))))]
@@ -421,7 +421,7 @@
[print "print" ..expression]
)
- (def: .public (exec globals code)
+ (.def .public (exec globals code)
(-> (Maybe (Expression Any)) (Expression Any) (Statement Any))
(let [extra (case globals
{.#Some globals}
@@ -432,7 +432,7 @@
(abstraction
(format "exec" (representation (..tuple (list.partial code extra)))))))
- (def: .public (def name args body)
+ (.def .public (def name args body)
(-> SVar (List (Ex (_ k) (Var k))) (Statement Any) (Statement Any))
(abstraction
(format "def " (representation name)
@@ -441,17 +441,17 @@
"):"
(..nested (representation body)))))
- (def: .public (import module_name)
+ (.def .public (import module_name)
(-> Text (Statement Any))
(abstraction (format "import " module_name)))
- (def: .public (comment commentary on)
+ (.def .public (comment commentary on)
(All (_ brand) (-> Text (Code brand) (Code brand)))
(abstraction (format "# " (text.replaced text.\n "\n" commentary) \n+
(representation on))))
)
-(def: arity_inputs
+(.def arity_inputs
(syntax (_ [arity <code>.nat])
(in (case arity
0 (.list)
@@ -459,7 +459,7 @@
(enum.range n.enum 0)
(list#each (|>> %.nat code.local)))))))
-(def: arity_types
+(.def arity_types
(syntax (_ [arity <code>.nat])
(in (list.repeated arity (` (Expression Any))))))
@@ -467,7 +467,7 @@
[(with_expansions [<inputs> (arity_inputs <arity>)
<definitions> (template.spliced <function>+)]
(with_template [<function>]
- [(`` (def: .public ((~~ (template.symbol [<function> "/" <arity>])) <inputs>)
+ [(`` (.def .public ((~~ (template.symbol [<function> "/" <arity>])) <inputs>)
(-> (~~ (arity_types <arity>)) (Computation Any))
(..apply (.list <inputs>) (..var <function>))))]
diff --git a/stdlib/source/library/lux/target/r.lux b/stdlib/source/library/lux/target/r.lux
index 4956df9c0..f31a950fe 100644
--- a/stdlib/source/library/lux/target/r.lux
+++ b/stdlib/source/library/lux/target/r.lux
@@ -49,45 +49,45 @@
[PVar Poly]
)
- (def: .public var
+ (def .public var
(-> Text SVar)
(|>> abstraction))
- (def: .public var_args
+ (def .public var_args
PVar
(abstraction "..."))
- (def: .public manual
+ (def .public manual
(-> Text Code)
(|>> abstraction))
- (def: .public code
+ (def .public code
(-> (Code Any) Text)
(|>> representation))
- (def: (self_contained code)
+ (def (self_contained code)
(-> Text Expression)
(abstraction
(format "(" code ")")))
... Added the carriage return for better Windows compatibility.
- (def: \n+
+ (def \n+
Text
(format text.carriage_return text.new_line))
- (def: nested_new_line
+ (def nested_new_line
(format text.new_line text.tab))
- (def: nested
+ (def nested
(-> Text Text)
(|>> (text.replaced text.new_line ..nested_new_line)
(format text.carriage_return ..nested_new_line)))
- (def: (_block expression)
+ (def (_block expression)
(-> Text Text)
(format "{" (nested expression) \n+ "}"))
- (def: .public (block expression)
+ (def .public (block expression)
(-> Expression Expression)
(abstraction
(format "{"
@@ -95,7 +95,7 @@
\n+ "}")))
(with_template [<name> <r>]
- [(def: .public <name>
+ [(def .public <name>
Expression
(abstraction <r>))]
@@ -104,25 +104,25 @@
)
(with_template [<name>]
- [(def: .public <name> Expression n/a)]
+ [(def .public <name> Expression n/a)]
[not_available]
[not_applicable]
[no_answer]
)
- (def: .public bool
+ (def .public bool
(-> Bit Expression)
(|>> (pipe.case
#0 "FALSE"
#1 "TRUE")
abstraction))
- (def: .public int
+ (def .public int
(-> Int Expression)
(|>> %.int abstraction))
- (def: .public float
+ (def .public float
(-> Frac Expression)
(|>> (pipe.cond [(f.= f.positive_infinity)]
[(pipe.new "1.0/0.0" [])]
@@ -137,7 +137,7 @@
[%.frac])
..self_contained))
- (def: safe
+ (def safe
(-> Text Text)
(`` (|>> (~~ (with_template [<find> <replace>]
[(text.replaced <find> <replace>)]
@@ -153,23 +153,23 @@
))
)))
- (def: .public string
+ (def .public string
(-> Text Expression)
(|>> ..safe %.text abstraction))
- (def: .public (slice from to list)
+ (def .public (slice from to list)
(-> Expression Expression Expression Expression)
(..self_contained
(format (representation list)
"[" (representation from) ":" (representation to) "]")))
- (def: .public (slice_from from list)
+ (def .public (slice_from from list)
(-> Expression Expression Expression)
(..self_contained
(format (representation list)
"[-1" ":-" (representation from) "]")))
- (def: .public (apply args func)
+ (def .public (apply args func)
(-> (List Expression) Expression Expression)
(let [func (representation func)
spacing (|> " "
@@ -184,7 +184,7 @@
")"))))
(with_template [<name> <function>]
- [(def: .public (<name> members)
+ [(def .public (<name> members)
(-> (List Expression) Expression)
(..apply members (..var <function>)))]
@@ -192,13 +192,13 @@
[list "list"]
)
- (def: .public named_list
+ (def .public named_list
(-> (List [Text Expression]) Expression)
(|>> (list#each (.function (_ [key value])
(abstraction (format key "=" (representation value)))))
..list))
- (def: .public (apply_kw args kw_args func)
+ (def .public (apply_kw args kw_args func)
(-> (List Expression) (List [Text Expression]) Expression Expression)
(..self_contained
(format (representation func)
@@ -209,7 +209,7 @@
kw_args))
")"))))
- (def: arity_inputs
+ (def arity_inputs
(syntax (_ [arity <code>.nat])
(in (case arity
0 (.list)
@@ -217,7 +217,7 @@
list.indices
(list#each (|>> %.nat code.local)))))))
- (def: arity_types
+ (def arity_types
(syntax (_ [arity <code>.nat])
(in (list.repeated arity (` ..Expression)))))
@@ -226,12 +226,12 @@
<inputs> (arity_inputs <arity>)
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
- (def: .public (<apply> function [<inputs>])
+ (def .public (<apply> function [<inputs>])
(-> Expression [<types>] Expression)
(..apply (.list <inputs>) function))
(with_template [<function>]
- [(`` (def: .public (~~ (template.symbol [<function> "/" <arity>]))
+ [(`` (def .public (~~ (template.symbol [<function> "/" <arity>]))
(-> [<types>] Expression)
(<apply> (..var <function>))))]
@@ -245,30 +245,30 @@
[["paste"]]]
)
- (def: .public as::integer
+ (def .public as::integer
(-> Expression Expression)
(..apply/1 (..var "as.integer")))
- (def: .public (item idx list)
+ (def .public (item idx list)
(-> Expression Expression Expression)
(..self_contained
(format (representation list) "[[" (representation idx) "]]")))
- (def: .public (if test then else)
+ (def .public (if test then else)
(-> Expression Expression Expression Expression)
(abstraction
(format "if(" (representation test) ")"
" " (.._block (representation then))
" else " (.._block (representation else)))))
- (def: .public (when test then)
+ (def .public (when test then)
(-> Expression Expression Expression)
(abstraction
(format "if(" (representation test) ") {"
(.._block (representation then))
\n+ "}")))
- (def: .public (cond clauses else)
+ (def .public (cond clauses else)
(-> (List [Expression Expression]) Expression Expression)
(list#mix (.function (_ [test then] next)
(if test then next))
@@ -276,7 +276,7 @@
(list.reversed clauses)))
(with_template [<name> <op>]
- [(def: .public (<name> param subject)
+ [(def .public (<name> param subject)
(-> Expression Expression Expression)
(..self_contained
(format (representation subject)
@@ -299,7 +299,7 @@
)
(with_template [<name> <func>]
- [(def: .public (<name> param subject)
+ [(def .public (<name> param subject)
(-> Expression Expression Expression)
(..apply (.list subject param) (..var <func>)))]
@@ -310,12 +310,12 @@
[bit_ushr "bitwShiftR"]
)
- (def: .public (bit_not subject)
+ (def .public (bit_not subject)
(-> Expression Expression)
(..apply (.list subject) (..var "bitwNot")))
(with_template [<name> <op>]
- [(def: .public <name>
+ [(def .public <name>
(-> Expression Expression)
(|>> representation (format <op>) ..self_contained))]
@@ -323,23 +323,23 @@
[negate "-"]
)
- (def: .public (length list)
+ (def .public (length list)
(-> Expression Expression)
(..apply (.list list) (..var "length")))
- (def: .public (range from to)
+ (def .public (range from to)
(-> Expression Expression Expression)
(..self_contained
(format (representation from) ":" (representation to))))
- (def: .public (function inputs body)
+ (def .public (function inputs body)
(-> (List (Ex (_ k) (Var k))) Expression Expression)
(let [args (|> inputs (list#each ..code) (text.interposed ", "))]
(..self_contained
(format "function(" args ") "
(.._block (representation body))))))
- (def: .public (try body warning error finally)
+ (def .public (try body warning error finally)
(-> Expression (Maybe Expression) (Maybe Expression) (Maybe Expression) Expression)
(let [optional (is (-> Text (Maybe Expression) (-> Text Text) Text)
(.function (_ parameter value preparation)
@@ -354,20 +354,20 @@
(optional "finally" finally .._block)
")"))))
- (def: .public (while test body)
+ (def .public (while test body)
(-> Expression Expression Expression)
(..self_contained
(format "while (" (representation test) ") "
(.._block (representation body)))))
- (def: .public (for_in var inputs body)
+ (def .public (for_in var inputs body)
(-> SVar Expression Expression Expression)
(..self_contained
(format "for (" (representation var) " in " (representation inputs) ")"
(.._block (representation body)))))
(with_template [<name> <keyword>]
- [(def: .public (<name> message)
+ [(def .public (<name> message)
(-> Expression Expression)
(..apply (.list message) (..var <keyword>)))]
@@ -375,17 +375,17 @@
[print "print"]
)
- (def: .public (set! var value)
+ (def .public (set! var value)
(-> SVar Expression Expression)
(..self_contained
(format (representation var) " <- " (representation value))))
- (def: .public (set_item! idx value list)
+ (def .public (set_item! idx value list)
(-> Expression Expression SVar Expression)
(..self_contained
(format (representation list) "[[" (representation idx) "]] <- " (representation value))))
- (def: .public (then pre post)
+ (def .public (then pre post)
(-> Expression Expression Expression)
(abstraction
(format (representation pre)
diff --git a/stdlib/source/library/lux/target/ruby.lux b/stdlib/source/library/lux/target/ruby.lux
index ae928f407..d196e2308 100644
--- a/stdlib/source/library/lux/target/ruby.lux
+++ b/stdlib/source/library/lux/target/ruby.lux
@@ -26,15 +26,15 @@
[type
[primitive (.except)]]]])
-(def: input_separator ", ")
-(def: statement_suffix ";")
+(def input_separator ", ")
+(def statement_suffix ";")
... Added the carriage return for better Windows compatibility.
-(def: \n+
+(def \n+
Text
(format text.carriage_return text.new_line))
-(def: nested
+(def nested
(-> Text Text)
(.let [nested_new_line (format text.new_line text.tab)]
(|>> (format \n+)
@@ -43,17 +43,17 @@
(primitive .public (Code brand)
Text
- (def: .public equivalence
+ (def .public equivalence
(All (_ brand) (Equivalence (Code brand)))
(implementation
- (def: (= reference subject)
+ (def (= reference subject)
(at text.equivalence = (representation reference) (representation subject)))))
- (def: .public manual
+ (def .public manual
(-> Text Code)
(|>> abstraction))
- (def: .public code
+ (def .public code
(-> (Code Any) Text)
(|>> representation))
@@ -86,7 +86,7 @@
)
(with_template [<var> <prefix> <constructor>]
- [(def: .public <constructor>
+ [(def .public <constructor>
(-> Text <var>)
(|>> (format <prefix>) abstraction))]
@@ -99,7 +99,7 @@
(with_template [<var> <prefix> <modifier> <unpacker>]
[(with_template [<name> <input> <output>]
- [(def: .public <name>
+ [(def .public <name>
(-> <input> <output>)
(|>> representation (format <prefix>) abstraction))]
@@ -112,7 +112,7 @@
)
(with_template [<ruby_name> <lux_name>]
- [(def: .public <lux_name>
+ [(def .public <lux_name>
GVar
(..global <ruby_name>))]
@@ -134,31 +134,31 @@
)
(with_template [<ruby_name> <lux_name>]
- [(def: .public <lux_name>
+ [(def .public <lux_name>
CVar
(..manual <ruby_name>))]
["ARGV" command_line_arguments]
)
- (def: .public multi
+ (def .public multi
(-> (List Expression) Expression)
(|>> (list#each ..code)
(text.interposed ..input_separator)
abstraction))
- (def: .public nil
+ (def .public nil
Literal
(abstraction "nil"))
- (def: .public bool
+ (def .public bool
(-> Bit Literal)
(|>> (pipe.case
#0 "false"
#1 "true")
abstraction))
- (def: safe
+ (def safe
(-> Text Text)
(`` (|>> (~~ (with_template [<find> <replace>]
[(text.replaced <find> <replace>)]
@@ -176,7 +176,7 @@
)))
(with_template [<format> <name> <type> <prep>]
- [(def: .public <name>
+ [(def .public <name>
(-> <type> Literal)
(|>> <prep> <format> abstraction))]
@@ -185,7 +185,7 @@
[(<|) symbol Text (format ":")]
)
- (def: .public float
+ (def .public float
(-> Frac Literal)
(|>> (pipe.cond [(f.= f.positive_infinity)]
[(pipe.new "(+1.0/0.0)" [])]
@@ -200,21 +200,21 @@
[%.frac])
abstraction))
- (def: .public (array_range from to array)
+ (def .public (array_range from to array)
(-> Expression Expression Expression Computation)
(|> (format (representation from) ".." (representation to))
(text.enclosed ["[" "]"])
(format (representation array))
abstraction))
- (def: .public array
+ (def .public array
(-> (List Expression) Computation)
(|>> (list#each (|>> representation (text.suffix ..input_separator)))
text.together
(text.enclosed ["[" "]"])
abstraction))
- (def: .public hash
+ (def .public hash
(-> (List [Expression Expression]) Computation)
(|>> (list#each (.function (_ [k v])
(format (representation k) " => " (representation v) ..input_separator)))
@@ -222,7 +222,7 @@
(text.enclosed ["{" "}"])
abstraction))
- (def: (control_structure content)
+ (def (control_structure content)
(-> Text Text)
(format content
\n+ "end" ..statement_suffix))
@@ -232,7 +232,7 @@
[#parameters (List Var)
#body Statement]))
- (def: (block it)
+ (def (block it)
(-> Block Text)
(|> (format (|> (.the #parameters it)
(list#each (|>> representation))
@@ -241,7 +241,7 @@
(..nested (representation (.the #body it))))
(text.enclosed ["{" "}"])))
- (def: .public (apply arguments block func)
+ (def .public (apply arguments block func)
(-> (List Expression) (Maybe Block) Expression Computation)
(let [arguments (|> arguments
(list#each (|>> representation))
@@ -263,18 +263,18 @@
(text.enclosed' "|")))))]
(abstraction (format (representation func) arguments block))))
- (def: .public (the field object)
+ (def .public (the field object)
(-> Text Expression Access)
(abstraction (format (representation object) "." field)))
- (def: .public (item idx array)
+ (def .public (item idx array)
(-> Expression Expression Access)
(|> (representation idx)
(text.enclosed ["[" "]"])
(format (representation array))
abstraction))
- (def: .public (? test then else)
+ (def .public (? test then else)
(-> Expression Expression Expression Computation)
(|> (format (representation test) " ? "
(representation then) " : "
@@ -282,20 +282,20 @@
(text.enclosed ["(" ")"])
abstraction))
- (def: .public statement
+ (def .public statement
(-> Expression Statement)
(|>> representation
(text.suffix ..statement_suffix)
abstraction))
- (def: .public (then pre! post!)
+ (def .public (then pre! post!)
(-> Statement Statement Statement)
(abstraction
(format (representation pre!)
\n+
(representation post!))))
- (def: .public (set vars value)
+ (def .public (set vars value)
(-> (List Location) Expression Statement)
(abstraction
(format (|> vars
@@ -303,7 +303,7 @@
(text.interposed ..input_separator))
" = " (representation value) ..statement_suffix)))
- (def: .public (if test then! else!)
+ (def .public (if test then! else!)
(-> Expression Statement Statement Statement)
(<| abstraction
..control_structure
@@ -313,7 +313,7 @@
(..nested (representation else!)))))
(with_template [<name> <control_structure>]
- [(def: .public (<name> test then!)
+ [(def .public (<name> test then!)
(-> Expression Statement Statement)
(<| abstraction
..control_structure
@@ -324,7 +324,7 @@
[while "while"]
)
- (def: .public (for_in var array iteration!)
+ (def .public (for_in var array iteration!)
(-> LVar Expression Statement Statement)
(<| abstraction
..control_structure
@@ -339,7 +339,7 @@
#exception LVar
#rescue Statement]))
- (def: .public (begin body! rescues)
+ (def .public (begin body! rescues)
(-> Statement (List Rescue) Statement)
(<| abstraction
..control_structure
@@ -351,22 +351,22 @@
(..nested (representation rescue)))))
(text.interposed \n+)))))
- (def: .public (catch expectation block)
+ (def .public (catch expectation block)
(-> Expression Block Expression)
(<| abstraction
(format "catch(" (representation expectation) ") "
(..block block))))
- (def: .public (return value)
+ (def .public (return value)
(-> Expression Statement)
(abstraction (format "return " (representation value) ..statement_suffix)))
- (def: .public (raise message)
+ (def .public (raise message)
(-> Expression Expression)
(abstraction (format "raise " (representation message))))
(with_template [<name> <keyword>]
- [(def: .public <name>
+ [(def .public <name>
Statement
(|> <keyword>
(text.suffix ..statement_suffix)
@@ -377,11 +377,11 @@
[break "break"]
)
- (def: .public initialize
+ (def .public initialize
LVar
(..manual "initialize"))
- (def: .public (function name args body!)
+ (def .public (function name args body!)
(-> LVar (List LVar) Statement Statement)
(<| abstraction
..control_structure
@@ -392,7 +392,7 @@
(text.enclosed ["(" ")"]))
(..nested (representation body!)))))
- (def: .public (lambda name block)
+ (def .public (lambda name block)
(-> (Maybe LVar) Block Literal)
(let [proc (format "lambda " (..block block))]
(|> (case name
@@ -405,7 +405,7 @@
abstraction)))
(with_template [<op> <name>]
- [(def: .public (<name> parameter subject)
+ [(def .public (<name> parameter subject)
(-> Expression Expression Computation)
(abstraction (format "(" (representation subject) " " <op> " " (representation parameter) ")")))]
@@ -433,7 +433,7 @@
)
(with_template [<unary> <name>]
- [(def: .public (<name> subject)
+ [(def .public (<name> subject)
(-> Expression Computation)
(abstraction (format "(" <unary> (representation subject) ")")))]
@@ -442,13 +442,13 @@
["-" opposite]
)
- (def: .public (comment commentary on)
+ (def .public (comment commentary on)
(All (_ brand) (-> Text (Code brand) (Code brand)))
(abstraction (format "# " (..safe commentary) \n+
(representation on))))
(with_template [<name>]
- [(`` (def: .public ((~~ (template.symbol [<name> "/*"])) attributes)
+ [(`` (def .public ((~~ (template.symbol [<name> "/*"])) attributes)
(-> (List Text) Statement)
(..statement
(..apply (list#each ..string attributes) {.#None} (..manual <name>)))))]
@@ -458,30 +458,30 @@
["attr_accessor"])
)
-(def: .public (do method arguments block object)
+(def .public (do method arguments block object)
(-> Text (List Expression) (Maybe Block) Expression Computation)
(|> object (..the method) (..apply arguments block)))
-(def: .public new
+(def .public new
(-> (List Expression) (Maybe Block) Expression Computation)
(..do "new"))
-(def: .public (class definition)
+(def .public (class definition)
(-> Block Computation)
(|> (..manual "Class")
(..new (list) {.#Some definition})))
-(def: .public (module definition)
+(def .public (module definition)
(-> Block Computation)
(|> (..manual "Module")
(..new (list) {.#Some definition})))
-(def: .public (apply_lambda args lambda)
+(def .public (apply_lambda args lambda)
(-> (List Expression) Expression Computation)
(|> lambda
(..do "call" args {.#None})))
-(def: arity_inputs
+(def arity_inputs
(syntax (_ [arity <code>.nat])
(in (case arity
0 (.list)
@@ -489,7 +489,7 @@
(enum.range n.enum 0)
(list#each (|>> %.nat code.local)))))))
-(def: arity_types
+(def arity_types
(syntax (_ [arity <code>.nat])
(in (list.repeated arity (` ..Expression)))))
@@ -499,7 +499,7 @@
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
(with_template [<function>]
- [(`` (def: .public ((~~ (template.symbol [<function> "/" <arity>])) <inputs>)
+ [(`` (def .public ((~~ (template.symbol [<function> "/" <arity>])) <inputs>)
(-> <types> Computation)
(..apply (.list <inputs>) {.#None} (..manual <function>))))]
@@ -520,18 +520,18 @@
["alias_method"]]]
)
-(def: .public (throw/1 error)
+(def .public (throw/1 error)
(-> Expression Statement)
(..statement (..apply (list error) {.#None} (..manual "throw"))))
-(def: .public (throw/2 tag value)
+(def .public (throw/2 tag value)
(-> Expression Expression Statement)
(..statement (..apply (list tag value) {.#None} (..manual "throw"))))
-(def: .public (class_variable_set var value object)
+(def .public (class_variable_set var value object)
(-> SVar Expression Expression Computation)
(..do "class_variable_set" (list (..string (..code var)) value) {.#None} object))
-(def: .public (class_variable_get var object)
+(def .public (class_variable_get var object)
(-> SVar Expression Computation)
(..do "class_variable_get" (list (..string (..code var))) {.#None} object))
diff --git a/stdlib/source/library/lux/target/scheme.lux b/stdlib/source/library/lux/target/scheme.lux
index c0632b5be..c3d1722b1 100644
--- a/stdlib/source/library/lux/target/scheme.lux
+++ b/stdlib/source/library/lux/target/scheme.lux
@@ -22,11 +22,11 @@
[primitive (.except)]]]])
... Added the carriage return for better Windows compatibility.
-(def: \n+
+(def \n+
Text
(format text.carriage_return text.new_line))
-(def: nested
+(def nested
(-> Text Text)
(.let [nested_new_line (format text.new_line text.tab)]
(text.replaced text.new_line nested_new_line)))
@@ -34,17 +34,17 @@
(primitive .public (Code k)
Text
- (def: .public equivalence
+ (def .public equivalence
(All (_ brand) (Equivalence (Code brand)))
(implementation
- (def: (= reference subject)
+ (def (= reference subject)
(at text.equivalence = (representation reference) (representation subject)))))
- (def: .public hash
+ (def .public hash
(All (_ brand) (Hash (Code brand)))
(implementation
- (def: equivalence ..equivalence)
- (def: hash (|>> representation (at text.hash hash)))))
+ (def equivalence ..equivalence)
+ (def hash (|>> representation (at text.hash hash)))))
(with_template [<type> <brand> <super>+]
[(primitive .public (<brand> brand) Any)
@@ -66,19 +66,19 @@
[#mandatory (List Var)
#rest (Maybe Var)]))
- (def: .public manual
+ (def .public manual
(-> Text Code)
(|>> abstraction))
- (def: .public code
+ (def .public code
(-> (Code Any) Text)
(|>> representation))
- (def: .public var
+ (def .public var
(-> Text Var)
(|>> abstraction))
- (def: (arguments [mandatory rest])
+ (def (arguments [mandatory rest])
(-> Arguments (Code Any))
(case rest
{.#Some rest}
@@ -101,22 +101,22 @@
(text.enclosed ["(" ")"])
abstraction)))
- (def: .public nil
+ (def .public nil
Computation
(abstraction "'()"))
- (def: .public bool
+ (def .public bool
(-> Bit Computation)
(|>> (pipe.case
#0 "#f"
#1 "#t")
abstraction))
- (def: .public int
+ (def .public int
(-> Int Computation)
(|>> %.int abstraction))
- (def: .public float
+ (def .public float
(-> Frac Computation)
(|>> (pipe.cond [(f.= f.positive_infinity)]
[(pipe.new "+inf.0" [])]
@@ -131,11 +131,11 @@
[%.frac])
abstraction))
- (def: .public positive_infinity Computation (..float f.positive_infinity))
- (def: .public negative_infinity Computation (..float f.negative_infinity))
- (def: .public not_a_number Computation (..float f.not_a_number))
+ (def .public positive_infinity Computation (..float f.positive_infinity))
+ (def .public negative_infinity Computation (..float f.negative_infinity))
+ (def .public not_a_number Computation (..float f.not_a_number))
- (def: safe
+ (def safe
(-> Text Text)
(`` (|>> (~~ (with_template [<find> <replace>]
[(text.replaced <find> <replace>)]
@@ -151,15 +151,15 @@
))
)))
- (def: .public string
+ (def .public string
(-> Text Computation)
(|>> ..safe %.text abstraction))
- (def: .public symbol
+ (def .public symbol
(-> Text Computation)
(|>> (format "'") abstraction))
- (def: form
+ (def form
(-> (List (Code Any)) Code)
(.let [nested_new_line (format \n+ text.tab)]
(|>> (pipe.case
@@ -174,12 +174,12 @@
(text.enclosed ["(" ")"])
abstraction)))))
- (def: .public (apply args func)
+ (def .public (apply args func)
(-> (List Expression) Expression Computation)
(..form {.#Item func args}))
(with_template [<name> <function>]
- [(def: .public (<name> members)
+ [(def .public (<name> members)
(-> (List Expression) Computation)
(..apply members (..var <function>)))]
@@ -187,25 +187,25 @@
[list/* "list"]
)
- (def: .public apply/0
+ (def .public apply/0
(-> Expression Computation)
(..apply (list)))
(with_template [<lux_name> <scheme_name>]
- [(def: .public <lux_name>
+ [(def .public <lux_name>
(apply/0 (..var <scheme_name>)))]
[newline/0 "newline"]
)
(with_template [<apply> <arg>+ <type>+ <function>+]
- [(`` (def: .public (<apply> procedure)
+ [(`` (def .public (<apply> procedure)
(-> Expression (~~ (template.spliced <type>+)) Computation)
(function (_ (~~ (template.spliced <arg>+)))
(..apply (list (~~ (template.spliced <arg>+))) procedure))))
(`` (with_template [<definition> <function>]
- [(def: .public <definition> (<apply> (..var <function>)))]
+ [(def .public <definition> (<apply> (..var <function>)))]
(~~ (template.spliced <function>+))))]
@@ -269,12 +269,12 @@
... 1. To carry on, and then, when it's time to compile the compiler
... itself into Scheme, switch from 'invoke' to normal 'vector-ref'.
... Either way, the 'invoke' needs to go away.
- (def: .public (vector_ref/2 vector index)
+ (def .public (vector_ref/2 vector index)
(-> Expression Expression Computation)
(..form (list (..var "invoke") vector (..symbol "getRaw") index)))
(with_template [<lux_name> <scheme_name>]
- [(def: .public (<lux_name> param subject)
+ [(def .public (<lux_name> param subject)
(-> Expression Expression Computation)
(..apply/2 (..var <scheme_name>) subject param))]
@@ -302,7 +302,7 @@
)
(with_template [<lux_name> <scheme_name>]
- [(def: .public <lux_name>
+ [(def .public <lux_name>
(-> (List Expression) Computation)
(|>> (list.partial (..var <scheme_name>)) ..form))]
@@ -311,7 +311,7 @@
)
(with_template [<lux_name> <scheme_name> <var> <pre>]
- [(def: .public (<lux_name> bindings body)
+ [(def .public (<lux_name> bindings body)
(-> (List [<var> Expression]) Expression Computation)
(..form (list (..var <scheme_name>)
(|> bindings
@@ -329,21 +329,21 @@
[letrec_values "letrec-values" Arguments ..arguments]
)
- (def: .public (if test then else)
+ (def .public (if test then else)
(-> Expression Expression Expression Computation)
(..form (list (..var "if") test then else)))
- (def: .public (when test then)
+ (def .public (when test then)
(-> Expression Expression Computation)
(..form (list (..var "when") test then)))
- (def: .public (lambda arguments body)
+ (def .public (lambda arguments body)
(-> Arguments Expression Computation)
(..form (list (..var "lambda")
(..arguments arguments)
body)))
- (def: .public (define_function name arguments body)
+ (def .public (define_function name arguments body)
(-> Var Arguments Expression Computation)
(..form (list (..var "define")
(|> arguments
@@ -351,27 +351,27 @@
..arguments)
body)))
- (def: .public (define_constant name value)
+ (def .public (define_constant name value)
(-> Var Expression Computation)
(..form (list (..var "define") name value)))
- (def: .public begin
+ (def .public begin
(-> (List Expression) Computation)
(|>> {.#Item (..var "begin")} ..form))
- (def: .public (set! name value)
+ (def .public (set! name value)
(-> Var Expression Computation)
(..form (list (..var "set!") name value)))
- (def: .public (with_exception_handler handler body)
+ (def .public (with_exception_handler handler body)
(-> Expression Expression Computation)
(..form (list (..var "with-exception-handler") handler body)))
- (def: .public (call_with_current_continuation body)
+ (def .public (call_with_current_continuation body)
(-> Expression Computation)
(..form (list (..var "call-with-current-continuation") body)))
- (def: .public (guard variable clauses else body)
+ (def .public (guard variable clauses else body)
(-> Var (List [Expression Expression]) (Maybe Expression) Expression Computation)
(..form (list (..var "guard")
(..form (|> (case else