aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/target
diff options
context:
space:
mode:
authorEduardo Julian2021-08-08 17:56:15 -0400
committerEduardo Julian2021-08-08 17:56:15 -0400
commitf621a133e6e0a516c0586270fea8eaffb4829d82 (patch)
tree399396ee2f6a10df10cea9b78c51c76679b70e59 /stdlib/source/library/lux/target
parent17e7566be51df5e428a6b10e6469201a8a9468da (diff)
No more #export magic syntax.
Diffstat (limited to 'stdlib/source/library/lux/target')
-rw-r--r--stdlib/source/library/lux/target/common_lisp.lux108
-rw-r--r--stdlib/source/library/lux/target/js.lux112
-rw-r--r--stdlib/source/library/lux/target/jvm.lux60
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute.lux16
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute/code.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute/code/exception.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute/constant.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode.lux86
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/address.lux20
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment.lux24
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux10
-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.lux18
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/instruction.lux24
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/jump.lux10
-rw-r--r--stdlib/source/library/lux/target/jvm/class.lux10
-rw-r--r--stdlib/source/library/lux/target/jvm/constant.lux40
-rw-r--r--stdlib/source/library/lux/target/jvm/constant/pool.lux84
-rw-r--r--stdlib/source/library/lux/target/jvm/constant/tag.lux10
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/name.lux20
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/signed.lux28
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/unsigned.lux34
-rw-r--r--stdlib/source/library/lux/target/jvm/field.lux10
-rw-r--r--stdlib/source/library/lux/target/jvm/index.lux14
-rw-r--r--stdlib/source/library/lux/target/jvm/loader.lux18
-rw-r--r--stdlib/source/library/lux/target/jvm/magic.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/method.lux10
-rw-r--r--stdlib/source/library/lux/target/jvm/modifier.lux34
-rw-r--r--stdlib/source/library/lux/target/jvm/modifier/inner.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/reflection.lux34
-rw-r--r--stdlib/source/library/lux/target/jvm/type.lux46
-rw-r--r--stdlib/source/library/lux/target/jvm/type/alias.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/type/box.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/type/category.lux28
-rw-r--r--stdlib/source/library/lux/target/jvm/type/descriptor.lux34
-rw-r--r--stdlib/source/library/lux/target/jvm/type/lux.lux20
-rw-r--r--stdlib/source/library/lux/target/jvm/type/parser.lux40
-rw-r--r--stdlib/source/library/lux/target/jvm/type/reflection.lux24
-rw-r--r--stdlib/source/library/lux/target/jvm/type/signature.lux46
-rw-r--r--stdlib/source/library/lux/target/jvm/version.lux12
-rw-r--r--stdlib/source/library/lux/target/lua.lux96
-rw-r--r--stdlib/source/library/lux/target/php.lux120
-rw-r--r--stdlib/source/library/lux/target/python.lux110
-rw-r--r--stdlib/source/library/lux/target/r.lux90
-rw-r--r--stdlib/source/library/lux/target/ruby.lux100
-rw-r--r--stdlib/source/library/lux/target/scheme.lux82
46 files changed, 894 insertions, 848 deletions
diff --git a/stdlib/source/library/lux/target/common_lisp.lux b/stdlib/source/library/lux/target/common_lisp.lux
index ed040a6b4..3bd089fa6 100644
--- a/stdlib/source/library/lux/target/common_lisp.lux
+++ b/stdlib/source/library/lux/target/common_lisp.lux
@@ -20,21 +20,23 @@
(-> Text Text)
(text.enclosed ["(" ")"]))
-(abstract: #export (Code brand)
+(abstract: .public (Code brand)
+ {}
+
Text
- (def: #export manual
+ (def: .public manual
(-> Text Code)
(|>> :abstraction))
- (def: #export code
+ (def: .public code
(-> (Code Any) Text)
(|>> :representation))
(template [<type> <super>]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (`` (abstract: #export (<brand> brand) Any))
- (`` (type: #export (<type> brand)
+ (`` (abstract: .public (<brand> brand) {} Any))
+ (`` (type: .public (<type> brand)
(<super> (<brand> brand)))))]
[Expression Code]
@@ -47,8 +49,8 @@
(template [<type> <super>]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (`` (abstract: #export <brand> Any))
- (`` (type: #export <type> (<super> <brand>))))]
+ (`` (abstract: .public <brand> {} Any))
+ (`` (type: .public <type> (<super> <brand>))))]
[Label Code]
[Tag Expression]
@@ -57,32 +59,32 @@
[Var/* Input]
)
- (type: #export Lambda
+ (type: .public Lambda
{#input Var/*
#output (Expression Any)})
- (def: #export nil
+ (def: .public nil
Literal
(:abstraction "()"))
(template [<prefix> <name>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Text Literal)
(|>> (format <prefix>) :abstraction))]
["'" symbol]
[":" keyword])
- (def: #export bool
+ (def: .public bool
(-> Bit Literal)
(|>> (case> #0 ..nil
#1 (..symbol "t"))))
- (def: #export int
+ (def: .public int
(-> Int Literal)
(|>> %.int :abstraction))
- (def: #export float
+ (def: .public float
(-> Frac Literal)
(|>> (cond> [(f.= f.positive_infinity)]
[(new> "(/ 1.0 0.0)" [])]
@@ -97,7 +99,7 @@
[%.frac])
:abstraction))
- (def: #export (double value)
+ (def: .public (double value)
(-> Frac Literal)
(:abstraction
(.cond (f.= f.positive_infinity value)
@@ -132,24 +134,24 @@
))
)))
- (def: #export string
+ (def: .public string
(-> Text Literal)
(|>> ..safe
(text.enclosed' text.double_quote)
:abstraction))
- (def: #export var
+ (def: .public var
(-> Text Var/1)
(|>> :abstraction))
- (def: #export args
+ (def: .public args
(-> (List Var/1) Var/*)
(|>> (list\map ..code)
(text.join_with " ")
..as_form
:abstraction))
- (def: #export (args& singles rest)
+ (def: .public (args& singles rest)
(-> (List Var/1) Var/1 Var/*)
(|> (case singles
#.End
@@ -171,12 +173,12 @@
..as_form
:abstraction))
- (def: #export (call/* func)
+ (def: .public (call/* func)
(-> (Expression Any) (-> (List (Expression Any)) (Computation Any)))
(|>> (#.Item func) ..form))
(template [<name> <function>]
- [(def: #export <name>
+ [(def: .public <name>
(-> (List (Expression Any)) (Computation Any))
(..call/* (..var <function>)))]
@@ -184,7 +186,7 @@
[list/* "list"]
)
- (def: #export (labels definitions body)
+ (def: .public (labels definitions body)
(-> (List [Var/1 Lambda]) (Expression Any) (Computation Any))
(..form (list (..var "labels")
(..form (list\map (function (_ [def_name [def_args def_body]])
@@ -192,19 +194,19 @@
definitions))
body)))
- (def: #export (destructuring_bind [bindings expression] body)
+ (def: .public (destructuring_bind [bindings expression] body)
(-> [Var/* (Expression Any)] (List (Expression Any)) (Computation Any))
(..form (list& (..var "destructuring-bind")
(:transmutation bindings) expression
body)))
(template [<call> <input_var>+ <input_type>+ <function>+]
- [(`` (def: #export (<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>+))))))
(`` (template [<lux_name> <host_name>]
- [(def: #export (<lux_name> args)
+ [(def: .public (<lux_name> args)
(-> [(~~ (template.spliced <input_type>+))] (Computation Any))
(<call> args (..var <host_name>)))]
@@ -262,7 +264,7 @@
(template [<call> <input_type>+ <function>+]
[(`` (template [<lux_name> <host_name>]
- [(def: #export (<lux_name> args)
+ [(def: .public (<lux_name> args)
(-> [(~~ (template.spliced <input_type>+))] (Access Any))
(:transmutation (<call> args (..var <host_name>))))]
@@ -279,29 +281,29 @@
[gethash/2 "gethash"]]]
)
- (def: #export (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: #export (funcall/+ [func args])
+ (def: .public (funcall/+ [func args])
(-> [(Expression Any) (List (Expression Any))] (Computation Any))
(..call/* (..var "funcall") (list& func args)))
- (def: #export (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: #export (concatenate/2|string [left right])
+ (def: .public (concatenate/2|string [left right])
(-> [(Expression Any) (Expression Any)] (Computation Any))
(concatenate/3 [(..symbol "string") left right]))
(template [<lux_name> <host_name>]
- [(def: #export (<lux_name> left right)
+ [(def: .public (<lux_name> left right)
(-> (Expression Any) (Expression Any) (Computation Any))
(..form (list (..var <host_name>) left right)))]
@@ -310,7 +312,7 @@
)
(template [<lux_name> <host_name>]
- [(def: #export (<lux_name> [param subject])
+ [(def: .public (<lux_name> [param subject])
(-> [(Expression Any) (Expression Any)] (Computation Any))
(..form (list (..var <host_name>) subject param)))]
@@ -330,20 +332,20 @@
[logxor/2 "logxor"]
)
- (def: #export (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: #export (when test then)
+ (def: .public (when test then)
(-> (Expression Any) (Expression Any) (Computation Any))
(..form (list (..var "when") test then)))
- (def: #export (lambda input body)
+ (def: .public (lambda input body)
(-> Var/* (Expression Any) Literal)
(..form (list (..var "lambda") (:transmutation input) body)))
(template [<lux_name> <host_name>]
- [(def: #export (<lux_name> bindings body)
+ [(def: .public (<lux_name> bindings body)
(-> (List [Var/1 (Expression Any)]) (List (Expression Any)) (Computation Any))
(..form (list& (..var <host_name>)
(|> bindings
@@ -356,16 +358,16 @@
[let* "let*"]
)
- (def: #export (defparameter name body)
+ (def: .public (defparameter name body)
(-> Var/1 (Expression Any) (Expression Any))
(..form (list (..var "defparameter") name body)))
- (def: #export (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)))
(template [<name> <symbol>]
- [(def: #export <name>
+ [(def: .public <name>
(-> (List (Expression Any)) (Computation Any))
(|>> (list& (..var <symbol>)) ..form))]
@@ -374,20 +376,20 @@
[values/* "values"]
)
- (def: #export (setq name value)
+ (def: .public (setq name value)
(-> Var/1 (Expression Any) (Expression Any))
(..form (list (..var "setq") name value)))
- (def: #export (setf access value)
+ (def: .public (setf access value)
(-> (Access Any) (Expression Any) (Expression Any))
(..form (list (..var "setf") access value)))
- (type: #export Handler
+ (type: .public Handler
{#condition_type (Expression Any)
#condition Var/1
#body (Expression Any)})
- (def: #export (handler_case handlers body)
+ (def: .public (handler_case handlers body)
(-> (List Handler) (Expression Any) (Computation Any))
(..form (list& (..var "handler-case")
body
@@ -398,7 +400,7 @@
handlers))))
(template [<name> <prefix>]
- [(def: #export (<name> conditions expression)
+ [(def: .public (<name> conditions expression)
(-> (List Text) (Expression Any) (Expression Any))
(case conditions
#.End
@@ -418,23 +420,23 @@
[conditional+ "#+"]
[conditional- "#-"])
- (def: #export label
+ (def: .public label
(-> Text Label)
(|>> :abstraction))
- (def: #export (block name body)
+ (def: .public (block name body)
(-> Label (List (Expression Any)) (Computation Any))
(..form (list& (..var "block") (:transmutation name) body)))
- (def: #export (return_from target value)
+ (def: .public (return_from target value)
(-> Label (Expression Any) (Computation Any))
(..form (list (..var "return-from") (:transmutation target) value)))
- (def: #export (return value)
+ (def: .public (return value)
(-> (Expression Any) (Computation Any))
(..form (list (..var "return") value)))
- (def: #export (cond clauses else)
+ (def: .public (cond clauses else)
(-> (List [(Expression Any) (Expression Any)]) (Expression Any) (Computation Any))
(..form (list& (..var "cond")
(list\compose (list\map (function (_ [test then])
@@ -442,28 +444,28 @@
clauses)
(list (..form (list (..bool true) else)))))))
- (def: #export tag
+ (def: .public tag
(-> Text Tag)
(|>> :abstraction))
- (def: #export go
+ (def: .public go
(-> Tag (Expression Any))
(|>> (list (..var "go"))
..form))
- (def: #export values_list/1
+ (def: .public values_list/1
(-> (Expression Any) (Expression Any))
(|>> (list (..var "values-list"))
..form))
- (def: #export (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: #export (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 1ef296cdf..27e77e1fd 100644
--- a/stdlib/source/library/lux/target/js.lux
+++ b/stdlib/source/library/lux/target/js.lux
@@ -28,17 +28,19 @@
(|>> (format text.new_line)
(text.replace_all text.new_line (format text.new_line text.tab))))
-(abstract: #export (Code brand)
+(abstract: .public (Code brand)
+ {}
+
Text
- (def: #export code
+ (def: .public code
(-> (Code Any) Text)
(|>> :representation))
(template [<type> <super>+]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (abstract: (<brand> brand) Any)
- (`` (type: #export <type> (|> Any <brand> (~~ (template.spliced <super>+))))))]
+ (abstract: (<brand> brand) {} Any)
+ (`` (type: .public <type> (|> Any <brand> (~~ (template.spliced <super>+))))))]
[Expression [Code]]
[Computation [Expression' Code]]
@@ -48,8 +50,8 @@
(template [<type> <super>+]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (abstract: #export <brand> Any)
- (`` (type: #export <type> (|> <brand> (~~ (template.spliced <super>+))))))]
+ (abstract: .public <brand> {} Any)
+ (`` (type: .public <type> (|> <brand> (~~ (template.spliced <super>+))))))]
[Var [Location' Computation' Expression' Code]]
[Access [Location' Computation' Expression' Code]]
@@ -59,20 +61,20 @@
)
(template [<name> <literal>]
- [(def: #export <name> Literal (:abstraction <literal>))]
+ [(def: .public <name> Literal (:abstraction <literal>))]
[null "null"]
[undefined "undefined"]
)
- (def: #export boolean
+ (def: .public boolean
(-> Bit Literal)
(|>> (case>
#0 "false"
#1 "true")
:abstraction))
- (def: #export (number value)
+ (def: .public (number value)
(-> Frac Literal)
(:abstraction
(.cond (f.not_a_number? value)
@@ -105,7 +107,7 @@
))
)))
- (def: #export string
+ (def: .public string
(-> Text Literal)
(|>> ..safe
(text.enclosed [text.double_quote text.double_quote])
@@ -115,26 +117,26 @@
(def: field_separator ": ")
(def: statement_suffix ";")
- (def: #export array
+ (def: .public array
(-> (List Expression) Computation)
(|>> (list\map ..code)
(text.join_with ..argument_separator)
..element
:abstraction))
- (def: #export var
+ (def: .public var
(-> Text Var)
(|>> :abstraction))
- (def: #export (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: #export (the field object)
+ (def: .public (the field object)
(-> Text Expression Access)
(:abstraction (format (:representation object) "." field)))
- (def: #export (apply/* function inputs)
+ (def: .public (apply/* function inputs)
(-> Expression (List Expression) Computation)
(|> inputs
(list\map ..code)
@@ -143,11 +145,11 @@
(format (:representation function))
:abstraction))
- (def: #export (do method inputs object)
+ (def: .public (do method inputs object)
(-> Text (List Expression) Expression Computation)
(apply/* (..the method object) inputs))
- (def: #export object
+ (def: .public object
(-> (List [Text Expression]) Computation)
(|>> (list\map (.function (_ [key val])
(format (:representation (..string key)) ..field_separator (:representation val))))
@@ -156,13 +158,13 @@
..expression
:abstraction))
- (def: #export (, pre post)
+ (def: .public (, pre post)
(-> Expression Expression Computation)
(|> (format (:representation pre) ..argument_separator (:representation post))
..expression
:abstraction))
- (def: #export (then pre post)
+ (def: .public (then pre post)
(-> Statement Statement Statement)
(:abstraction (format (:representation pre)
text.new_line
@@ -176,7 +178,7 @@
(text.enclosed ["{"
close]))))
- (def: #export (function! name inputs body)
+ (def: .public (function! name inputs body)
(-> Var (List Var) Statement Statement)
(|> body
..block
@@ -188,14 +190,14 @@
" ")
:abstraction))
- (def: #export (function name inputs body)
+ (def: .public (function name inputs body)
(-> Var (List Var) Statement Computation)
(|> (..function! name inputs body)
:representation
..expression
:abstraction))
- (def: #export (closure inputs body)
+ (def: .public (closure inputs body)
(-> (List Var) Statement Computation)
(|> body
..block
@@ -209,7 +211,7 @@
:abstraction))
(template [<name> <op>]
- [(def: #export (<name> param subject)
+ [(def: .public (<name> param subject)
(-> Expression Expression Computation)
(|> (format (:representation subject) " " <op> " " (:representation param))
..expression
@@ -239,7 +241,7 @@
)
(template [<name> <prefix>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Expression Computation)
(|>> :representation (text.prefix <prefix>) ..expression :abstraction))]
@@ -249,7 +251,7 @@
)
(template [<name> <input> <format>]
- [(def: #export (<name> value)
+ [(def: .public (<name> value)
{#.doc "A 32-bit integer expression."}
(-> <input> Computation)
(:abstraction (..expression (format (<format> value) "|0"))))]
@@ -258,13 +260,13 @@
[i32 Int %.int]
)
- (def: #export (int value)
+ (def: .public (int value)
(-> Int Literal)
(:abstraction (.if (i.< +0 value)
(%.int value)
(%.nat (.nat value)))))
- (def: #export (? test then else)
+ (def: .public (? test then else)
(-> Expression Expression Expression Computation)
(|> (format (:representation test)
" ? " (:representation then)
@@ -272,14 +274,14 @@
..expression
:abstraction))
- (def: #export type_of
+ (def: .public type_of
(-> Expression Computation)
(|>> :representation
(format "typeof ")
..expression
:abstraction))
- (def: #export (new constructor inputs)
+ (def: .public (new constructor inputs)
(-> Expression (List Expression) Computation)
(|> (format "new " (:representation constructor)
(|> inputs
@@ -289,76 +291,76 @@
..expression
:abstraction))
- (def: #export statement
+ (def: .public statement
(-> Expression Statement)
(|>> :representation (text.suffix ..statement_suffix) :abstraction))
- (def: #export use_strict
+ (def: .public use_strict
Statement
(:abstraction (format text.double_quote "use strict" text.double_quote ..statement_suffix)))
- (def: #export (declare name)
+ (def: .public (declare name)
(-> Var Statement)
(:abstraction (format "var " (:representation name) ..statement_suffix)))
- (def: #export (define name value)
+ (def: .public (define name value)
(-> Var Expression Statement)
(:abstraction (format "var " (:representation name) " = " (:representation value) ..statement_suffix)))
- (def: #export (set' name value)
+ (def: .public (set' name value)
(-> Location Expression Expression)
(:abstraction (..expression (format (:representation name) " = " (:representation value)))))
- (def: #export (set name value)
+ (def: .public (set name value)
(-> Location Expression Statement)
(:abstraction (format (:representation name) " = " (:representation value) ..statement_suffix)))
- (def: #export (throw message)
+ (def: .public (throw message)
(-> Expression Statement)
(:abstraction (format "throw " (:representation message) ..statement_suffix)))
- (def: #export (return value)
+ (def: .public (return value)
(-> Expression Statement)
(:abstraction (format "return " (:representation value) ..statement_suffix)))
- (def: #export (delete' value)
+ (def: .public (delete' value)
(-> Location Expression)
(:abstraction (format "delete " (:representation value))))
- (def: #export (delete value)
+ (def: .public (delete value)
(-> Location Statement)
(:abstraction (format (:representation (delete' value)) ..statement_suffix)))
- (def: #export (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: #export (when test then!)
+ (def: .public (when test then!)
(-> Expression Statement Statement)
(:abstraction (format "if(" (:representation test) ") "
(..block then!))))
- (def: #export (while test body)
+ (def: .public (while test body)
(-> Expression Statement Loop)
(:abstraction (format "while(" (:representation test) ") "
(..block body))))
- (def: #export (do_while test body)
+ (def: .public (do_while test body)
(-> Expression Statement Loop)
(:abstraction (format "do " (..block body)
" while(" (:representation test) ")" ..statement_suffix)))
- (def: #export (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: #export (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 +368,20 @@
")"
(..block iteration))))
- (def: #export label
+ (def: .public label
(-> Text Label)
(|>> :abstraction))
- (def: #export (with_label label loop)
+ (def: .public (with_label label loop)
(-> Label Loop Statement)
(:abstraction (format (:representation label) ": " (:representation loop))))
(template [<keyword> <0> <1>]
- [(def: #export <0>
+ [(def: .public <0>
Statement
(:abstraction (format <keyword> ..statement_suffix)))
- (def: #export (<1> label)
+ (def: .public (<1> label)
(-> Label Statement)
(:abstraction (format <keyword> " " (:representation label) ..statement_suffix)))]
@@ -388,7 +390,7 @@
)
(template [<name> <js>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Location Expression)
(|>> :representation
(text.suffix <js>)
@@ -398,11 +400,11 @@
[-- "--"]
)
- (def: #export (comment commentary on)
+ (def: .public (comment commentary on)
(All [kind] (-> Text (Code kind) (Code kind)))
(:abstraction (format "/* " commentary " */" " " (:representation on))))
- (def: #export (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
@@ -423,7 +425,7 @@
..block))))
)
-(def: #export (cond clauses else!)
+(def: .public (cond clauses else!)
(-> (List [Expression Statement]) Statement Statement)
(list\fold (.function (_ [test then!] next!)
(..if test then! next!))
@@ -431,13 +433,13 @@
(list.reversed clauses)))
(template [<apply> <arg>+ <type>+ <function>+]
- [(`` (def: #export (<apply> function)
+ [(`` (def: .public (<apply> function)
(-> Expression (~~ (template.spliced <type>+)) Computation)
(.function (_ (~~ (template.spliced <arg>+)))
(..apply/* function (list (~~ (template.spliced <arg>+)))))))
(`` (template [<definition> <function>]
- [(def: #export <definition> (<apply> (..var <function>)))]
+ [(def: .public <definition> (<apply> (..var <function>)))]
(~~ (template.spliced <function>+))))]
diff --git a/stdlib/source/library/lux/target/jvm.lux b/stdlib/source/library/lux/target/jvm.lux
index b470abea9..1ada0da04 100644
--- a/stdlib/source/library/lux/target/jvm.lux
+++ b/stdlib/source/library/lux/target/jvm.lux
@@ -9,7 +9,7 @@
[type (#+ Type)
["." category (#+ Primitive Class Value Method)]]]]]])
-(type: #export Literal
+(type: .public Literal
(#Boolean Bit)
(#Int Int)
(#Long Int)
@@ -17,7 +17,7 @@
(#Char Nat)
(#String Text))
-(type: #export Constant
+(type: .public Constant
(#BIPUSH Int)
(#SIPUSH Int)
@@ -44,7 +44,7 @@
(#LDC Literal))
-(type: #export Int_Arithmetic
+(type: .public Int_Arithmetic
#IADD
#ISUB
#IMUL
@@ -52,7 +52,7 @@
#IREM
#INEG)
-(type: #export Long_Arithmetic
+(type: .public Long_Arithmetic
#LADD
#LSUB
#LMUL
@@ -60,7 +60,7 @@
#LREM
#LNEG)
-(type: #export Float_Arithmetic
+(type: .public Float_Arithmetic
#FADD
#FSUB
#FMUL
@@ -68,7 +68,7 @@
#FREM
#FNEG)
-(type: #export Double_Arithmetic
+(type: .public Double_Arithmetic
#DADD
#DSUB
#DMUL
@@ -76,13 +76,13 @@
#DREM
#DNEG)
-(type: #export Arithmetic
+(type: .public Arithmetic
(#Int_Arithmetic Int_Arithmetic)
(#Long_Arithmetic Long_Arithmetic)
(#Float_Arithmetic Float_Arithmetic)
(#Double_Arithmetic Double_Arithmetic))
-(type: #export Int_Bitwise
+(type: .public Int_Bitwise
#IOR
#IXOR
#IAND
@@ -90,7 +90,7 @@
#ISHR
#IUSHR)
-(type: #export Long_Bitwise
+(type: .public Long_Bitwise
#LOR
#LXOR
#LAND
@@ -98,11 +98,11 @@
#LSHR
#LUSHR)
-(type: #export Bitwise
+(type: .public Bitwise
(#Int_Bitwise Int_Bitwise)
(#Long_Bitwise Long_Bitwise))
-(type: #export Conversion
+(type: .public Conversion
#I2B
#I2S
#I2L
@@ -122,7 +122,7 @@
#D2L
#D2F)
-(type: #export Array
+(type: .public Array
#ARRAYLENGTH
(#NEWARRAY (Type Primitive))
@@ -152,7 +152,7 @@
#AALOAD
#AASTORE)
-(type: #export Object
+(type: .public Object
(#GETSTATIC (Type Class) Text (Type Value))
(#PUTSTATIC (Type Class) Text (Type Value))
@@ -169,29 +169,29 @@
(#INVOKESTATIC (Type Class) Text (Type Method))
(#INVOKEVIRTUAL (Type Class) Text (Type Method)))
-(type: #export Register Nat)
+(type: .public Register Nat)
-(type: #export Local_Int
+(type: .public Local_Int
(#ILOAD Register)
(#ISTORE Register))
-(type: #export Local_Long
+(type: .public Local_Long
(#LLOAD Register)
(#LSTORE Register))
-(type: #export Local_Float
+(type: .public Local_Float
(#FLOAD Register)
(#FSTORE Register))
-(type: #export Local_Double
+(type: .public Local_Double
(#DLOAD Register)
(#DSTORE Register))
-(type: #export Local_Object
+(type: .public Local_Object
(#ALOAD Register)
(#ASTORE Register))
-(type: #export Local
+(type: .public Local
(#Local_Int Local_Int)
(#IINC Register)
(#Local_Long Local_Long)
@@ -199,7 +199,7 @@
(#Local_Double Local_Double)
(#Local_Object Local_Object))
-(type: #export Stack
+(type: .public Stack
#DUP
#DUP_X1
#DUP_X2
@@ -210,7 +210,7 @@
#POP
#POP2)
-(type: #export Comparison
+(type: .public Comparison
#LCMP
#FCMPG
@@ -219,9 +219,9 @@
#DCMPG
#DCMPL)
-(type: #export Label Nat)
+(type: .public Label Nat)
-(type: #export (Branching label)
+(type: .public (Branching label)
(#IF_ICMPEQ label)
(#IF_ICMPGE label)
(#IF_ICMPGT label)
@@ -243,15 +243,15 @@
(#IFNONNULL label)
(#IFNULL label))
-(type: #export (Exception label)
+(type: .public (Exception label)
(#Try label label label (Type Class))
#ATHROW)
-(type: #export Concurrency
+(type: .public Concurrency
#MONITORENTER
#MONITOREXIT)
-(type: #export Return
+(type: .public Return
#RETURN
#IRETURN
#LRETURN
@@ -259,14 +259,14 @@
#DRETURN
#ARETURN)
-(type: #export (Control label)
+(type: .public (Control label)
(#GOTO label)
(#Branching (Branching label))
(#Exception (Exception label))
(#Concurrency Concurrency)
(#Return Return))
-(type: #export (Instruction embedded label)
+(type: .public (Instruction embedded label)
#NOP
(#Constant Constant)
(#Arithmetic Arithmetic)
@@ -280,5 +280,5 @@
(#Control (Control label))
(#Embedded embedded))
-(type: #export (Bytecode embedded label)
+(type: .public (Bytecode embedded label)
(Row (Instruction embedded label)))
diff --git a/stdlib/source/library/lux/target/jvm/attribute.lux b/stdlib/source/library/lux/target/jvm/attribute.lux
index 6d94c1b5b..0aa919723 100644
--- a/stdlib/source/library/lux/target/jvm/attribute.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute.lux
@@ -25,12 +25,12 @@
["#." constant (#+ Constant)]
["#." code]])
-(type: #export (Info about)
+(type: .public (Info about)
{#name (Index UTF8)
#length U4
#info about})
-(def: #export (info_equivalence Equivalence<about>)
+(def: .public (info_equivalence Equivalence<about>)
(All [about]
(-> (Equivalence about)
(Equivalence (Info about))))
@@ -51,15 +51,15 @@
(|>> nameT lengthT infoT)])))
(with_expansions [<Code> (as_is (/code.Code Attribute))]
- (type: #export #rec Attribute
+ (type: .public #rec Attribute
(#Constant (Info (Constant Any)))
(#Code (Info <Code>)))
- (type: #export Code
+ (type: .public Code
<Code>)
)
-(def: #export equivalence
+(def: .public equivalence
(Equivalence Attribute)
(equivalence.rec
(function (_ equivalence)
@@ -90,7 +90,7 @@
#length (|> /constant.length //unsigned.u4 try.assumed)
#info index}))
-(def: #export (constant index)
+(def: .public (constant index)
(-> (Constant Any) (Resource Attribute))
(do //constant/pool.monad
[@name (//constant/pool.utf8 "ConstantValue")]
@@ -107,13 +107,13 @@
try.assumed)
#info specification}))
-(def: #export (code specification)
+(def: .public (code specification)
(-> Code (Resource Attribute))
(do //constant/pool.monad
[@name (//constant/pool.utf8 "Code")]
(in (code' @name specification))))
-(def: #export (writer value)
+(def: .public (writer value)
(Writer Attribute)
(case value
(#Constant attribute)
diff --git a/stdlib/source/library/lux/target/jvm/attribute/code.lux b/stdlib/source/library/lux/target/jvm/attribute/code.lux
index 2f80d96d2..733fd4d7c 100644
--- a/stdlib/source/library/lux/target/jvm/attribute/code.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute/code.lux
@@ -22,13 +22,13 @@
["." / #_
["#." exception (#+ Exception)]])
-(type: #export (Code Attribute)
+(type: .public (Code Attribute)
{#limit Limit
#code Binary
#exception_table (Row Exception)
#attributes (Row Attribute)})
-(def: #export (length length code)
+(def: .public (length length code)
(All [Attribute] (-> (-> Attribute Nat) (Code Attribute) Nat))
($_ n.+
## u2 max_stack;
@@ -53,7 +53,7 @@
(row\map length)
(row\fold n.+ 0))))
-(def: #export (equivalence attribute_equivalence)
+(def: .public (equivalence attribute_equivalence)
(All [attribute]
(-> (Equivalence attribute) (Equivalence (Code attribute))))
($_ product.equivalence
@@ -64,7 +64,7 @@
))
## https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-4.html#jvms-4.7.3
-(def: #export (writer writer code)
+(def: .public (writer writer code)
(All [Attribute] (-> (Writer Attribute) (Writer (Code Attribute))))
($_ binaryF\compose
## 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 e2aa089b0..42bb8ebb9 100644
--- a/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux
@@ -19,13 +19,13 @@
[encoding
["#." unsigned (#+ U2)]]]])
-(type: #export Exception
+(type: .public Exception
{#start Address
#end Address
#handler Address
#catch (Index Class)})
-(def: #export equivalence
+(def: .public equivalence
(Equivalence Exception)
($_ product.equivalence
////address.equivalence
@@ -35,7 +35,7 @@
))
## https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-4.html#jvms-4.7.3
-(def: #export length
+(def: .public length
Nat
($_ n.+
## u2 start_pc;
@@ -48,7 +48,7 @@
////unsigned.bytes/2
))
-(def: #export writer
+(def: .public writer
(Writer Exception)
($_ 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 d9f26d418..8d7a0a26a 100644
--- a/stdlib/source/library/lux/target/jvm/attribute/constant.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute/constant.lux
@@ -12,16 +12,16 @@
[encoding
["#." unsigned (#+ U2 U4)]]])
-(type: #export (Constant a)
+(type: .public (Constant a)
(Index (Value a)))
-(def: #export equivalence
+(def: .public equivalence
(All [a] (Equivalence (Constant a)))
///index.equivalence)
-(def: #export length
+(def: .public length
///index.length)
-(def: #export 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 a22ff102b..fa48223ae 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode.lux
@@ -51,11 +51,11 @@
["." reflection]
["." parser]]]])
-(type: #export Label Nat)
+(type: .public Label Nat)
-(type: #export Resolver (Dictionary Label [Stack (Maybe Address)]))
+(type: .public Resolver (Dictionary Label [Stack (Maybe Address)]))
-(type: #export Tracker
+(type: .public Tracker
{#program_counter Address
#next Label
#known Resolver})
@@ -66,7 +66,7 @@
#next 0
#known (dictionary.empty n.hash)})
-(type: #export Relative
+(type: .public Relative
(-> Resolver (Try [(Row Exception) Instruction])))
(def: no_exceptions
@@ -97,10 +97,10 @@
(in [(\ row.monoid compose left_exceptions right_exceptions)
(_\compose left_instruction right_instruction)]))))))
-(type: #export (Bytecode a)
+(type: .public (Bytecode a)
(+State Try [Pool Environment Tracker] (Writer Relative a)))
-(def: #export new_label
+(def: .public new_label
(Bytecode Label)
(function (_ [pool environment tracker])
(#try.Success [[pool
@@ -109,11 +109,11 @@
[..relative_identity
(get@ #next tracker)]])))
-(exception: #export (label_has_already_been_set {label Label})
+(exception: .public (label_has_already_been_set {label Label})
(exception.report
["Label" (%.nat label)]))
-(exception: #export (mismatched_environments {instruction Name}
+(exception: .public (mismatched_environments {instruction Name}
{label Label}
{address Address}
{expected Stack}
@@ -132,7 +132,7 @@
tracker)]
[..relative_identity
[]]]))]
- (def: #export (set_label label)
+ (def: .public (set_label label)
(-> Label (Bytecode Any))
(function (_ [pool environment tracker])
(let [@here (get@ #program_counter tracker)]
@@ -153,7 +153,7 @@
environment)]
<success>))))))
-(def: #export monad
+(def: .public monad
(Monad Bytecode)
(<| (:as (Monad Bytecode))
(writer.with ..relative_monoid)
@@ -162,15 +162,15 @@
(: (Monad Try))
try.monad))
-(def: #export failure
+(def: .public failure
(-> Text Bytecode)
(|>> #try.Failure function.constant))
-(def: #export (except exception value)
+(def: .public (except exception value)
(All [e] (-> (exception.Exception e) e Bytecode))
(..failure (exception.error exception value)))
-(def: #export (resolve environment bytecode)
+(def: .public (resolve environment bytecode)
(All [a] (-> Environment (Bytecode a) (Resource [Environment (Row Exception) Instruction a])))
(function (_ pool)
(do try.monad
@@ -221,7 +221,7 @@
)
(template [<name> <consumption> <production> <registry> <instruction>]
- [(def: #export <name>
+ [(def: .public <name>
(Bytecode Any)
(..bytecode <consumption>
<production>
@@ -416,7 +416,7 @@
[]]]))))
(template [<name> <consumption> <instruction>]
- [(def: #export <name>
+ [(def: .public <name>
(Bytecode Any)
(do ..monad
[_ (..bytecode <consumption> $0 @_ <instruction> [])]
@@ -432,7 +432,7 @@
[athrow $1 _.athrow]
)
-(def: #export (bipush byte)
+(def: .public (bipush byte)
(-> S1 (Bytecode Any))
(..bytecode $0 $1 @_ _.bipush [byte]))
@@ -447,7 +447,7 @@
[..relative_identity
output]]))))
-(def: #export (string value)
+(def: .public (string value)
(-> //constant.UTF8 (Bytecode Any))
(do ..monad
[index (..lift (//constant/pool.string value))]
@@ -467,7 +467,7 @@
(#static doubleToRawLongBits #manual [double] long)])
(template [<name> <type> <constructor> <constant> <wide> <to_lux> <specializations>]
- [(def: #export (<name> value)
+ [(def: .public (<name> value)
(-> <type> (Bytecode Any))
(case (|> value <to_lux>)
(^template [<special> <instruction>]
@@ -514,7 +514,7 @@
(def: negative_zero_float_bits
(|> -0.0 (:as java/lang/Double) ffi.double_to_float ..float_bits))
-(def: #export (float value)
+(def: .public (float value)
(-> java/lang/Float (Bytecode Any))
(if (i.= ..negative_zero_float_bits
(..float_bits value))
@@ -529,7 +529,7 @@
_ (..arbitrary_float value))))
(template [<name> <type> <constructor> <constant> <wide> <to_lux> <specializations>]
- [(def: #export (<name> value)
+ [(def: .public (<name> value)
(-> <type> (Bytecode Any))
(case (|> value <to_lux>)
(^template [<special> <instruction>]
@@ -560,7 +560,7 @@
(def: negative_zero_double_bits
(..double_bits (:as java/lang/Double -0.0)))
-(def: #export (double value)
+(def: .public (double value)
(-> java/lang/Double (Bytecode Any))
(if (i.= ..negative_zero_double_bits
(..double_bits value))
@@ -573,7 +573,7 @@
_ (..arbitrary_double value))))
-(exception: #export (invalid_register {id Nat})
+(exception: .public (invalid_register {id Nat})
(exception.report
["ID" (%.nat id)]))
@@ -587,7 +587,7 @@
(..except ..invalid_register [id])))
(template [<for> <size> <name> <general> <specials>]
- [(def: #export (<name> local)
+ [(def: .public (<name> local)
(-> Nat (Bytecode Any))
(with_expansions [<specials>' (template.spliced <specials>)]
(`` (case local
@@ -627,7 +627,7 @@
)
(template [<for> <size> <name> <general> <specials>]
- [(def: #export (<name> local)
+ [(def: .public (<name> local)
(-> Nat (Bytecode Any))
(with_expansions [<specials>' (template.spliced <specials>)]
(`` (case local
@@ -667,7 +667,7 @@
)
(template [<consumption> <production> <name> <instruction> <input>]
- [(def: #export <name>
+ [(def: .public <name>
(-> <input> (Bytecode Any))
(..bytecode <consumption> <production> @_ <instruction>))]
@@ -675,11 +675,11 @@
[$0 $1 sipush _.sipush S2]
)
-(exception: #export (unknown_label {label Label})
+(exception: .public (unknown_label {label Label})
(exception.report
["Label" (%.nat label)]))
-(exception: #export (cannot_do_a_big_jump {label Label}
+(exception: .public (cannot_do_a_big_jump {label Label}
{@from Address}
{jump Big_Jump})
(exception.report
@@ -703,7 +703,7 @@
(\ ! map (|>> #.Left) (//signed.s4 jump))
(\ ! map (|>> #.Right) (//signed.s2 jump))))))
-(exception: #export (unset_label {label Label})
+(exception: .public (unset_label {label Label})
(exception.report
["Label" (%.nat label)]))
@@ -729,7 +729,7 @@
(update@ #known (dictionary.put label [stack #.None]) tracker)))
(template [<consumption> <name> <instruction>]
- [(def: #export (<name> label)
+ [(def: .public (<name> label)
(-> Label (Bytecode Any))
(let [[estimator bytecode] <instruction>]
(function (_ [pool environment tracker])
@@ -781,7 +781,7 @@
)
(template [<name> <instruction> <on_long_jump> <on_short_jump>]
- [(def: #export (<name> label)
+ [(def: .public (<name> label)
(-> Label (Bytecode Any))
(let [[estimator bytecode] <instruction>]
(function (_ [pool environment tracker])
@@ -833,9 +833,9 @@
(#.Right small)
(/jump.lift small)))
-(exception: #export invalid_tableswitch)
+(exception: .public invalid_tableswitch)
-(def: #export (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])
@@ -872,9 +872,9 @@
(exception.except ..invalid_tableswitch []))))
[]]]))))))
-(exception: #export invalid_lookupswitch)
+(exception: .public invalid_lookupswitch)
-(def: #export (lookupswitch default cases)
+(def: .public (lookupswitch default cases)
(-> Label (List [S4 Label]) (Bytecode Any))
(let [cases (list.sort (function (_ [left _] [right _])
(i.< (//signed.value left)
@@ -920,7 +920,7 @@
(|>> type.reflection reflection.reflection))
(template [<consumption> <production> <name> <category> <instruction>]
- [(def: #export (<name> class)
+ [(def: .public (<name> class)
(-> (Type <category>) (Bytecode Any))
(do ..monad
[## TODO: Make sure it's impossible to have indexes greater than U2.
@@ -933,16 +933,16 @@
[$1 $1 instanceof Object _.instanceof]
)
-(def: #export (iinc register increase)
+(def: .public (iinc register increase)
(-> Nat U1 (Bytecode Any))
(do ..monad
[register (..register register)]
(..bytecode $0 $0 (/registry.for register) _.iinc [register increase])))
-(exception: #export (multiarray_cannot_be_zero_dimensional {class (Type Object)})
+(exception: .public (multiarray_cannot_be_zero_dimensional {class (Type Object)})
(exception.report ["Class" (..reflection class)]))
-(def: #export (multianewarray class dimensions)
+(def: .public (multianewarray class dimensions)
(-> (Type Object) U1 (Bytecode Any))
(do ..monad
[_ (: (Bytecode Any)
@@ -965,7 +965,7 @@
1))
(template [<static?> <name> <instruction> <method>]
- [(def: #export (<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
@@ -991,7 +991,7 @@
)
(template [<consumption> <name> <1> <2>]
- [(def: #export (<name> class field type)
+ [(def: .public (<name> class field type)
(-> (Type Class) Text (Type Value) (Bytecode Any))
(do ..monad
[index (<| ..lift
@@ -1009,12 +1009,12 @@
[$2 putfield _.putfield/1 _.putfield/2]
)
-(exception: #export (invalid_range_for_try {start Address} {end Address})
+(exception: .public (invalid_range_for_try {start Address} {end Address})
(exception.report
["Start" (|> start /address.value //unsigned.value %.nat)]
["End" (|> end /address.value //unsigned.value %.nat)]))
-(def: #export (try @start @end @handler catch)
+(def: .public (try @start @end @handler catch)
(-> Label Label Label (Type Class) (Bytecode Any))
(do ..monad
[@catch (..lift (//constant/pool.class (//name.internal (..reflection catch))))]
@@ -1038,7 +1038,7 @@
_.empty])))
[]]]))))
-(def: #export (compose pre post)
+(def: .public (compose pre post)
(All [pre post]
(-> (Bytecode pre) (Bytecode post) (Bytecode post)))
(do ..monad
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/address.lux b/stdlib/source/library/lux/target/jvm/bytecode/address.lux
index 8a42afb41..d7f2f612f 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/address.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/address.lux
@@ -23,18 +23,20 @@
["#." unsigned (#+ U2)]
["#." signed (#+ S4)]]]])
-(abstract: #export Address
+(abstract: .public Address
+ {}
+
U2
- (def: #export value
+ (def: .public value
(-> Address U2)
(|>> :representation))
- (def: #export start
+ (def: .public start
Address
(|> 0 ///unsigned.u2 try.assumed :abstraction))
- (def: #export (move distance)
+ (def: .public (move distance)
(-> U2 (-> Address (Try Address)))
(|>> :representation
(///unsigned.+/2 distance)
@@ -44,19 +46,19 @@
(-> Address (Try S4))
(|>> :representation ///unsigned.value .int ///signed.s4))
- (def: #export (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: #export (after? reference subject)
+ (def: .public (after? reference subject)
(-> Address Address Bit)
(n.> (|> reference :representation ///unsigned.value)
(|> subject :representation ///unsigned.value)))
- (implementation: #export equivalence
+ (implementation: .public equivalence
(Equivalence Address)
(def: (= reference subject)
@@ -64,11 +66,11 @@
(:representation reference)
(:representation subject))))
- (def: #export writer
+ (def: .public writer
(Writer Address)
(|>> :representation ///unsigned.writer/2))
- (def: #export 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 6fbdadfa3..d426726e3 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
@@ -17,12 +17,12 @@
[type (#+ Type)
[category (#+ Method)]]]])
-(type: #export Environment
+(type: .public Environment
{#limit Limit
#stack (Maybe Stack)})
(template [<name> <limit>]
- [(def: #export (<name> type)
+ [(def: .public (<name> type)
(-> (Type Method) (Try Environment))
(do try.monad
[limit (<limit> type)]
@@ -33,10 +33,10 @@
[virtual /limit.virtual]
)
-(type: #export Condition
+(type: .public Condition
(-> Environment (Try Environment)))
-(implementation: #export monoid
+(implementation: .public monoid
(Monoid Condition)
(def: identity (|>> #try.Success))
@@ -47,9 +47,9 @@
[environment (left environment)]
(right environment)))))
-(exception: #export discontinuity)
+(exception: .public discontinuity)
-(def: #export (stack environment)
+(def: .public (stack environment)
(-> Environment (Try Stack))
(case (get@ #..stack environment)
(#.Some stack)
@@ -58,17 +58,17 @@
#.None
(exception.except ..discontinuity [])))
-(def: #export discontinue
+(def: .public discontinue
(-> Environment Environment)
(set@ #..stack #.None))
-(exception: #export (mismatched_stacks {expected Stack}
+(exception: .public (mismatched_stacks {expected Stack}
{actual Stack})
(exception.report
["Expected" (/stack.format expected)]
["Actual" (/stack.format actual)]))
-(def: #export (continue expected environment)
+(def: .public (continue expected environment)
(-> Stack Environment (Try [Stack Environment]))
(case (get@ #..stack environment)
(#.Some actual)
@@ -79,7 +79,7 @@
#.None
(#try.Success [expected (set@ #..stack (#.Some expected) environment)])))
-(def: #export (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.
@@ -89,7 +89,7 @@
current (/stack.pop amount previous)]
(in (set@ #..stack (#.Some current) environment)))))
-(def: #export (produces amount)
+(def: .public (produces amount)
(-> U2 Condition)
(function (_ environment)
(do try.monad
@@ -102,7 +102,7 @@
(set@ #..stack (#.Some current))
(set@ [#..limit #/limit.stack] limit))))))
-(def: #export (has registry)
+(def: .public (has registry)
(-> Registry Condition)
(|>> (update@ [#..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 fad7c9dae..d8117947e 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
@@ -20,12 +20,12 @@
[type (#+ Type)
[category (#+ Method)]]]])
-(type: #export Limit
+(type: .public Limit
{#stack Stack
#registry Registry})
(template [<name> <registry>]
- [(def: #export (<name> type)
+ [(def: .public (<name> type)
(-> (Type Method) (Try Limit))
(do try.monad
[registry (<registry> type)]
@@ -36,21 +36,21 @@
[virtual /registry.virtual]
)
-(def: #export length
+(def: .public length
($_ n.+
## u2 max_stack;
/stack.length
## u2 max_locals;
/registry.length))
-(def: #export equivalence
+(def: .public equivalence
(Equivalence Limit)
($_ product.equivalence
/stack.equivalence
/registry.equivalence
))
-(def: #export (writer limit)
+(def: .public (writer limit)
(Writer Limit)
($_ format\compose
(/stack.writer (get@ #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 3773b4333..7db606a0b 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
@@ -22,15 +22,17 @@
[category (#+ Method)]
["#/." parser]]])
-(type: #export Register U1)
+(type: .public Register U1)
(def: normal 1)
(def: wide 2)
-(abstract: #export Registry
+(abstract: .public Registry
+ {}
+
U2
- (def: #export registry
+ (def: .public registry
(-> U2 Registry)
(|>> :abstraction))
@@ -46,7 +48,7 @@
(list\fold n.+ 0))))
(template [<start> <name>]
- [(def: #export <name>
+ [(def: .public <name>
(-> (Type Method) (Try Registry))
(|>> ..minimal
(n.+ <start>)
@@ -57,24 +59,24 @@
[1 virtual]
)
- (def: #export equivalence
+ (def: .public equivalence
(Equivalence Registry)
(\ equivalence.functor map
(|>> :representation)
/////unsigned.equivalence))
- (def: #export writer
+ (def: .public writer
(Writer Registry)
(|>> :representation /////unsigned.writer/2))
- (def: #export (has needed)
+ (def: .public (has needed)
(-> Registry Registry Registry)
(|>> :representation
(/////unsigned.max/2 (:representation needed))
:abstraction))
(template [<name> <extra>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Register Registry)
(let [extra (|> <extra> /////unsigned.u2 try.assumed)]
(|>> /////unsigned.lift/2
@@ -87,5 +89,5 @@
)
)
-(def: #export 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 99a560347..a825e6699 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
@@ -17,11 +17,13 @@
[encoding
["#." unsigned (#+ U2)]]])
-(abstract: #export Stack
+(abstract: .public Stack
+ {}
+
U2
(template [<frames> <name>]
- [(def: #export <name>
+ [(def: .public <name>
Stack
(|> <frames> /////unsigned.u2 maybe.assume :abstraction))]
@@ -29,13 +31,13 @@
[1 catch]
)
- (def: #export equivalence
+ (def: .public equivalence
(Equivalence Stack)
(\ equivalence.functor map
(|>> :representation)
/////unsigned.equivalence))
- (def: #export writer
+ (def: .public writer
(Writer Stack)
(|>> :representation /////unsigned.writer/2))
@@ -44,7 +46,7 @@
(|>> :abstraction))
(template [<op> <name>]
- [(def: #export (<name> amount)
+ [(def: .public (<name> amount)
(-> U2 (-> Stack (Try Stack)))
(|>> :representation
(<op> amount)
@@ -54,16 +56,16 @@
[/////unsigned.-/2 pop]
)
- (def: #export (max left right)
+ (def: .public (max left right)
(-> Stack Stack Stack)
(:abstraction
(/////unsigned.max/2 (:representation left)
(:representation right))))
- (def: #export format
+ (def: .public format
(Format Stack)
(|>> :representation /////unsigned.value %.nat))
)
-(def: #export 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 3302b60dc..5aee5816a 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
@@ -36,23 +36,23 @@
[type
[category (#+ Value Method)]]]])
-(type: #export Size U2)
+(type: .public Size U2)
-(type: #export Estimator
+(type: .public Estimator
(-> Address Size))
(def: fixed
(-> Size Estimator)
function.constant)
-(type: #export Instruction
+(type: .public Instruction
(-> Specification Specification))
-(def: #export empty
+(def: .public empty
Instruction
function.identity)
-(def: #export run
+(def: .public run
(-> Instruction Specification)
(function.apply format.no_op))
@@ -232,7 +232,9 @@
[(n.+ (///unsigned.value ..size/211) size)
(|>> mutation ((trinary/211' opcode input0 input1 input2)))])])
-(abstract: #export Primitive_Array_Type
+(abstract: .public Primitive_Array_Type
+ {}
+
U1
(def: code
@@ -240,7 +242,7 @@
(|>> :representation))
(template [<code> <name>]
- [(def: #export <name> (|> <code> ///unsigned.u1 try.assumed :abstraction))]
+ [(def: .public <name> (|> <code> ///unsigned.u1 try.assumed :abstraction))]
[04 t_boolean]
[05 t_char]
@@ -491,7 +493,7 @@
[<input_name>]
<inputs>')]
- (def: #export <name>
+ (def: .public <name>
[Estimator (-> [<input_types>] Instruction)]
(let [[estimator <arity>'] <arity>]
[estimator
@@ -582,7 +584,7 @@
(n.- (n.% 4 parameter_start)
4))))
-(def: #export tableswitch
+(def: .public tableswitch
[(-> Nat Estimator)
(-> S4 Big_Jump [Big_Jump (List Big_Jump)] Instruction)]
(let [estimator (: (-> Nat Estimator)
@@ -646,7 +648,7 @@
size)
(|>> mutation tableswitch_mutation)]))))]))
-(def: #export lookupswitch
+(def: .public lookupswitch
[(-> Nat Estimator)
(-> Big_Jump (List [S4 Big_Jump]) Instruction)]
(let [case_size (n.+ (///unsigned.value ..integer_size)
@@ -706,7 +708,7 @@
size)
(|>> mutation lookupswitch_mutation)]))))]))
-(implementation: #export monoid
+(implementation: .public monoid
(Monoid Instruction)
(def: identity ..empty)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/jump.lux b/stdlib/source/library/lux/target/jvm/bytecode/jump.lux
index 2873ef781..53fdd6081 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/jump.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/jump.lux
@@ -10,18 +10,18 @@
[encoding
["#." signed (#+ S2 S4)]]])
-(type: #export Jump S2)
+(type: .public Jump S2)
-(def: #export equivalence
+(def: .public equivalence
(Equivalence Jump)
///signed.equivalence)
-(def: #export writer
+(def: .public writer
(Writer Jump)
///signed.writer/2)
-(type: #export Big_Jump S4)
+(type: .public Big_Jump S4)
-(def: #export lift
+(def: .public lift
(-> Jump Big_Jump)
///signed.lift/4)
diff --git a/stdlib/source/library/lux/target/jvm/class.lux b/stdlib/source/library/lux/target/jvm/class.lux
index 2e4b8eb15..17561fa0d 100644
--- a/stdlib/source/library/lux/target/jvm/class.lux
+++ b/stdlib/source/library/lux/target/jvm/class.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux #*
+ [lux (#- public private)
[abstract
[equivalence (#+ Equivalence)]
["." monad (#+ do)]]
@@ -27,7 +27,7 @@
["#." constant (#+ Constant)
["#/." pool (#+ Pool Resource)]]])
-(type: #export #rec Class
+(type: .public #rec Class
{#magic Magic
#minor_version Minor
#major_version Major
@@ -51,7 +51,7 @@
["4000" enum]
)
-(def: #export equivalence
+(def: .public equivalence
(Equivalence Class)
($_ product.equivalence
//unsigned.equivalence
@@ -81,7 +81,7 @@
interfaces))]
(in [@this @super @interfaces])))
-(def: #export (class version modifier
+(def: .public (class version modifier
this super interfaces
fields methods attributes)
(-> Major (Modifier Class)
@@ -110,7 +110,7 @@
#methods (row.of_list =methods)
#attributes attributes})))
-(def: #export (writer class)
+(def: .public (writer class)
(Writer Class)
(`` ($_ binaryF\compose
(~~ (template [<writer> <slot>]
diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux
index 7f2a7aa26..229dd247f 100644
--- a/stdlib/source/library/lux/target/jvm/constant.lux
+++ b/stdlib/source/library/lux/target/jvm/constant.lux
@@ -34,24 +34,26 @@
[encoding
["#." unsigned]]]])
-(type: #export UTF8 Text)
+(type: .public UTF8 Text)
(def: utf8_writer
(Writer UTF8)
binaryF.utf8/16)
-(abstract: #export Class
+(abstract: .public Class
+ {}
+
(Index UTF8)
- (def: #export index
+ (def: .public index
(-> Class (Index UTF8))
(|>> :representation))
- (def: #export class
+ (def: .public class
(-> (Index UTF8) Class)
(|>> :abstraction))
- (def: #export class_equivalence
+ (def: .public class_equivalence
(Equivalence Class)
(\ equivalence.functor map
..index
@@ -66,7 +68,7 @@
["#::."
(#static floatToRawIntBits #manual [float] int)])
-(implementation: #export float_equivalence
+(implementation: .public float_equivalence
(Equivalence java/lang/Float)
(def: (= parameter subject)
@@ -82,14 +84,16 @@
["#::."
(#static doubleToRawLongBits [double] long)])
-(abstract: #export (Value kind)
+(abstract: .public (Value kind)
+ {}
+
kind
- (def: #export value
+ (def: .public value
(All [kind] (-> (Value kind) kind))
(|>> :representation))
- (def: #export (value_equivalence Equivalence<kind>)
+ (def: .public (value_equivalence Equivalence<kind>)
(All [kind]
(-> (Equivalence kind)
(Equivalence (Value kind))))
@@ -98,9 +102,9 @@
Equivalence<kind>))
(template [<constructor> <type> <marker>]
- [(type: #export <type> (Value <marker>))
+ [(type: .public <type> (Value <marker>))
- (def: #export <constructor>
+ (def: .public <constructor>
(-> <marker> <type>)
(|>> :abstraction))]
@@ -126,16 +130,16 @@
)
)
-(type: #export (Name_And_Type of)
+(type: .public (Name_And_Type of)
{#name (Index UTF8)
#descriptor (Index (Descriptor of))})
-(type: #export (Reference of)
+(type: .public (Reference of)
{#class (Index Class)
#name_and_type (Index (Name_And_Type of))})
(template [<type> <equivalence> <writer>]
- [(def: #export <equivalence>
+ [(def: .public <equivalence>
(Equivalence (<type> Any))
($_ product.equivalence
//index.equivalence
@@ -151,7 +155,7 @@
[Reference reference_equivalence reference_writer]
)
-(type: #export Constant
+(type: .public Constant
(#UTF8 UTF8)
(#Integer Integer)
(#Float Float)
@@ -164,7 +168,7 @@
(#Interface_Method (Reference //category.Method))
(#Name_And_Type (Name_And_Type Any)))
-(def: #export (size constant)
+(def: .public (size constant)
(-> Constant Nat)
(case constant
(^or (#Long _) (#Double _))
@@ -173,7 +177,7 @@
_
1))
-(def: #export 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.
@@ -219,7 +223,7 @@
## )
)
-(def: #export writer
+(def: .public writer
(Writer Constant)
(with_expansions [<constants> (as_is [#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 d050b1e34..a82683e1b 100644
--- a/stdlib/source/library/lux/target/jvm/constant/pool.lux
+++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux
@@ -35,59 +35,59 @@
[category (#+ Value Method)]
["#." descriptor (#+ Descriptor)]]]])
-(type: #export Pool [Index (Row [Index Constant])])
+(type: .public Pool [Index (Row [Index Constant])])
-(def: #export equivalence
+(def: .public equivalence
(Equivalence Pool)
(product.equivalence //index.equivalence
(row.equivalence (product.equivalence //index.equivalence
//.equivalence))))
-(type: #export (Resource a)
+(type: .public (Resource a)
(+State Try Pool a))
-(def: #export monad
+(def: .public monad
(Monad Resource)
(state.with try.monad))
(template: (!add <tag> <equivalence> <value>)
- (function (_ [current pool])
- (let [<value>' <value>]
- (with_expansions [<try_again> (as_is (recur (.inc idx)))]
- (loop [idx 0]
- (case (row.item idx pool)
- (#try.Success entry)
- (case entry
- [index (<tag> reference)]
- (if (\ <equivalence> = reference <value>')
- (#try.Success [[current pool]
- index])
- <try_again>)
-
- _
- <try_again>)
-
- (#try.Failure _)
- (let [new (<tag> <value>')]
- (do {! try.monad}
- [@new (//unsigned.u2 (//.size new))
- next (: (Try Index)
- (|> current
- //index.value
- (//unsigned.+/2 @new)
- (\ ! map //index.index)))]
- (in [[next
- (row.add [current new] pool)]
- current])))))))))
+ [(function (_ [current pool])
+ (let [<value>' <value>]
+ (with_expansions [<try_again> (as_is (recur (.inc idx)))]
+ (loop [idx 0]
+ (case (row.item idx pool)
+ (#try.Success entry)
+ (case entry
+ [index (<tag> reference)]
+ (if (\ <equivalence> = reference <value>')
+ (#try.Success [[current pool]
+ index])
+ <try_again>)
+
+ _
+ <try_again>)
+
+ (#try.Failure _)
+ (let [new (<tag> <value>')]
+ (do {! try.monad}
+ [@new (//unsigned.u2 (//.size new))
+ next (: (Try Index)
+ (|> current
+ //index.value
+ (//unsigned.+/2 @new)
+ (\ ! map //index.index)))]
+ (in [[next
+ (row.add [current new] pool)]
+ current]))))))))])
(template: (!index <index>)
- (|> <index> //index.value //unsigned.value))
+ [(|> <index> //index.value //unsigned.value)])
(type: (Adder of)
(-> of (Resource (Index of))))
(template [<name> <type> <tag> <equivalence>]
- [(def: #export (<name> value)
+ [(def: .public (<name> value)
(Adder <type>)
(!add <tag> <equivalence> value))]
@@ -98,32 +98,32 @@
[utf8 UTF8 #//.UTF8 text.equivalence]
)
-(def: #export (string value)
+(def: .public (string value)
(-> Text (Resource (Index String)))
(do ..monad
[@value (utf8 value)
.let [value (//.string @value)]]
(!add #//.String (//.value_equivalence //index.equivalence) value)))
-(def: #export (class name)
+(def: .public (class name)
(-> Internal (Resource (Index Class)))
(do ..monad
[@name (utf8 (//name.read name))
.let [value (//.class @name)]]
(!add #//.Class //.class_equivalence value)))
-(def: #export (descriptor value)
+(def: .public (descriptor value)
(All [kind]
(-> (Descriptor kind)
(Resource (Index (Descriptor kind)))))
(let [value (//descriptor.descriptor value)]
(!add #//.UTF8 text.equivalence value)))
-(type: #export (Member of)
+(type: .public (Member of)
{#name UTF8
#descriptor (Descriptor of)})
-(def: #export (name_and_type [name descriptor])
+(def: .public (name_and_type [name descriptor])
(All [of]
(-> (Member of) (Resource (Index (Name_And_Type of)))))
(do ..monad
@@ -132,7 +132,7 @@
(!add #//.Name_And_Type //.name_and_type_equivalence {#//.name @name #//.descriptor @descriptor})))
(template [<name> <tag> <of>]
- [(def: #export (<name> class member)
+ [(def: .public (<name> class member)
(-> External (Member <of>) (Resource (Index (Reference <of>))))
(do ..monad
[@class (..class (//name.internal class))
@@ -144,7 +144,7 @@
[interface_method #//.Interface_Method Method]
)
-(def: #export writer
+(def: .public writer
(Writer Pool)
(function (_ [next pool])
(row\fold (function (_ [_index post] pre)
@@ -152,7 +152,7 @@
(format.bits/16 (!index next))
pool)))
-(def: #export empty
+(def: .public empty
Pool
[(|> 1 //unsigned.u2 try.assumed //index.index)
row.empty])
diff --git a/stdlib/source/library/lux/target/jvm/constant/tag.lux b/stdlib/source/library/lux/target/jvm/constant/tag.lux
index 0eba9788e..7d53837f0 100644
--- a/stdlib/source/library/lux/target/jvm/constant/tag.lux
+++ b/stdlib/source/library/lux/target/jvm/constant/tag.lux
@@ -14,17 +14,19 @@
[encoding
["#." unsigned (#+ U1) ("u1//." equivalence)]]])
-(abstract: #export Tag
+(abstract: .public Tag
+ {}
+
U1
- (implementation: #export equivalence
+ (implementation: .public equivalence
(Equivalence Tag)
(def: (= reference sample)
(u1//= (:representation reference)
(:representation sample))))
(template [<code> <name>]
- [(def: #export <name>
+ [(def: .public <name>
Tag
(|> <code> ///unsigned.u1 try.assumed :abstraction))]
@@ -44,7 +46,7 @@
[18 invoke_dynamic]
)
- (def: #export 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 02507ceb6..a0761950e 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/name.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/name.lux
@@ -7,34 +7,36 @@
[type
abstract]]])
-(def: #export internal_separator "/")
-(def: #export external_separator ".")
+(def: .public internal_separator "/")
+(def: .public external_separator ".")
-(type: #export External Text)
+(type: .public External Text)
-(abstract: #export Internal
+(abstract: .public Internal
+ {}
+
Text
- (def: #export internal
+ (def: .public internal
(-> External Internal)
(|>> (text.replace_all ..external_separator
..internal_separator)
:abstraction))
- (def: #export read
+ (def: .public read
(-> Internal Text)
(|>> :representation))
- (def: #export external
+ (def: .public external
(-> Internal External)
(|>> :representation
(text.replace_all ..internal_separator
..external_separator))))
-(def: #export safe
+(def: .public safe
(-> Text External)
(|>> ..internal ..external))
-(def: #export (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 dfdcedbb6..196f60380 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/signed.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/signed.lux
@@ -22,26 +22,28 @@
[type
abstract]]])
-(abstract: #export (Signed brand)
+(abstract: .public (Signed brand)
+ {}
+
Int
- (def: #export value
+ (def: .public value
(-> (Signed Any) Int)
(|>> :representation))
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [brand] (Equivalence (Signed brand)))
(def: (= reference sample)
(i.= (:representation reference) (:representation sample))))
- (implementation: #export order
+ (implementation: .public order
(All [brand] (Order (Signed brand)))
(def: &equivalence ..equivalence)
(def: (< reference sample)
(i.< (:representation reference) (:representation sample))))
- (exception: #export (value_exceeds_the_scope {value Int}
+ (exception: .public (value_exceeds_the_scope {value Int}
{scope Nat})
(exception.report
["Value" (%.int value)]
@@ -49,16 +51,16 @@
(template [<bytes> <name> <size> <constructor> <maximum> <+> <->]
[(with_expansions [<raw> (template.identifier [<name> "'"])]
- (abstract: #export <raw> Any)
- (type: #export <name> (Signed <raw>)))
+ (abstract: .public <raw> {} Any)
+ (type: .public <name> (Signed <raw>)))
- (def: #export <size> <bytes>)
+ (def: .public <size> <bytes>)
- (def: #export <maximum>
+ (def: .public <maximum>
<name>
(|> <bytes> (n.* i64.bits_per_byte) dec i64.mask :abstraction))
- (def: #export <constructor>
+ (def: .public <constructor>
(-> Int (Try <name>))
(let [positive (|> <bytes> (n.* i64.bits_per_byte) i64.mask)
negative (|> positive .int (i.right_shifted 1) i64.not)]
@@ -71,7 +73,7 @@
(exception.except ..value_exceeds_the_scope [value <size>])))))
(template [<abstract_operation> <concrete_operation>]
- [(def: #export (<abstract_operation> parameter subject)
+ [(def: .public (<abstract_operation> parameter subject)
(-> <name> <name> (Try <name>))
(<constructor>
(<concrete_operation> (:representation parameter)
@@ -87,7 +89,7 @@
)
(template [<name> <from> <to>]
- [(def: #export <name>
+ [(def: .public <name>
(-> <from> <to>)
(|>> :transmutation))]
@@ -96,7 +98,7 @@
)
(template [<writer_name> <type> <writer>]
- [(def: #export <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 546d4f516..e9084bb9d 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
@@ -21,20 +21,22 @@
[type
abstract]]])
-(abstract: #export (Unsigned brand)
+(abstract: .public (Unsigned brand)
+ {}
+
Nat
- (def: #export value
+ (def: .public value
(-> (Unsigned Any) Nat)
(|>> :representation))
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [brand] (Equivalence (Unsigned brand)))
(def: (= reference sample)
(n.= (:representation reference)
(:representation sample))))
- (implementation: #export order
+ (implementation: .public order
(All [brand] (Order (Unsigned brand)))
(def: &equivalence ..equivalence)
@@ -42,7 +44,7 @@
(n.< (:representation reference)
(:representation sample))))
- (exception: #export (value_exceeds_the_maximum {type Name}
+ (exception: .public (value_exceeds_the_maximum {type Name}
{value Nat}
{maximum (Unsigned Any)})
(exception.report
@@ -50,7 +52,7 @@
["Value" (%.nat value)]
["Maximum" (%.nat (:representation maximum))]))
- (exception: #export [brand] (subtraction_cannot_yield_negative_value
+ (exception: .public [brand] (subtraction_cannot_yield_negative_value
{type Name}
{parameter (Unsigned brand)}
{subject (Unsigned brand)})
@@ -61,28 +63,28 @@
(template [<bytes> <name> <size> <constructor> <maximum> <+> <-> <max>]
[(with_expansions [<raw> (template.identifier [<name> "'"])]
- (abstract: #export <raw> Any)
- (type: #export <name> (Unsigned <raw>)))
+ (abstract: .public <raw> {} Any)
+ (type: .public <name> (Unsigned <raw>)))
- (def: #export <size> <bytes>)
+ (def: .public <size> <bytes>)
- (def: #export <maximum>
+ (def: .public <maximum>
<name>
(|> <bytes> (n.* i64.bits_per_byte) i64.mask :abstraction))
- (def: #export (<constructor> value)
+ (def: .public (<constructor> value)
(-> Nat (Try <name>))
(if (n.<= (:representation <maximum>) value)
(#try.Success (:abstraction value))
(exception.except ..value_exceeds_the_maximum [(name_of <name>) value <maximum>])))
- (def: #export (<+> parameter subject)
+ (def: .public (<+> parameter subject)
(-> <name> <name> (Try <name>))
(<constructor>
(n.+ (:representation parameter)
(:representation subject))))
- (def: #export (<-> parameter subject)
+ (def: .public (<-> parameter subject)
(-> <name> <name> (Try <name>))
(let [parameter' (:representation parameter)
subject' (:representation subject)]
@@ -90,7 +92,7 @@
(#try.Success (:abstraction (n.- parameter' subject')))
(exception.except ..subtraction_cannot_yield_negative_value [(name_of <name>) parameter subject]))))
- (def: #export (<max> left right)
+ (def: .public (<max> left right)
(-> <name> <name> <name>)
(:abstraction (n.max (:representation left)
(:representation right))))]
@@ -101,7 +103,7 @@
)
(template [<name> <from> <to>]
- [(def: #export <name>
+ [(def: .public <name>
(-> <from> <to>)
(|>> :transmutation))]
@@ -110,7 +112,7 @@
)
(template [<writer_name> <type> <writer>]
- [(def: #export <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 93cda4c5e..a9d783621 100644
--- a/stdlib/source/library/lux/target/jvm/field.lux
+++ b/stdlib/source/library/lux/target/jvm/field.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux (#- Type static)
+ [lux (#- Type static public private)
[abstract
[equivalence (#+ Equivalence)]
["." monad (#+ do)]]
@@ -20,7 +20,7 @@
[category (#+ Value)]
[descriptor (#+ Descriptor)]]])
-(type: #export #rec Field
+(type: .public #rec Field
{#modifier (Modifier Field)
#name (Index UTF8)
#descriptor (Index (Descriptor Value))
@@ -38,7 +38,7 @@
["4000" enum]
)
-(def: #export equivalence
+(def: .public equivalence
(Equivalence Field)
($_ product.equivalence
modifier.equivalence
@@ -46,7 +46,7 @@
//index.equivalence
(row.equivalence //attribute.equivalence)))
-(def: #export (writer field)
+(def: .public (writer field)
(Writer Field)
(`` ($_ binaryF\compose
(~~ (template [<writer> <slot>]
@@ -58,7 +58,7 @@
[(binaryF.row/16 //attribute.writer) #attributes]))
)))
-(def: #export (field modifier name type attributes)
+(def: .public (field modifier name type attributes)
(-> (Modifier Field) UTF8 (Type Value) (Row 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 851d6903f..66df65314 100644
--- a/stdlib/source/library/lux/target/jvm/index.lux
+++ b/stdlib/source/library/lux/target/jvm/index.lux
@@ -12,27 +12,29 @@
[encoding
["#." unsigned (#+ U2)]]])
-(def: #export length
+(def: .public length
//unsigned.bytes/2)
-(abstract: #export (Index kind)
+(abstract: .public (Index kind)
+ {}
+
U2
- (def: #export index
+ (def: .public index
(All [kind] (-> U2 (Index kind)))
(|>> :abstraction))
- (def: #export value
+ (def: .public value
(-> (Index Any) U2)
(|>> :representation))
- (def: #export equivalence
+ (def: .public equivalence
(All [kind] (Equivalence (Index kind)))
(\ equivalence.functor map
..value
//unsigned.equivalence))
- (def: #export 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 ec7931743..3a38d9bb8 100644
--- a/stdlib/source/library/lux/target/jvm/loader.lux
+++ b/stdlib/source/library/lux/target/jvm/loader.lux
@@ -19,18 +19,18 @@
["." array]
["." dictionary (#+ Dictionary)]]]]])
-(type: #export Library
+(type: .public Library
(Atom (Dictionary Text Binary)))
-(exception: #export (already_stored {class Text})
+(exception: .public (already_stored {class Text})
(exception.report
["Class" class]))
-(exception: #export (unknown {class Text})
+(exception: .public (unknown {class Text})
(exception.report
["Class" class]))
-(exception: #export (cannot_define {class Text} {error Text})
+(exception: .public (cannot_define {class Text} {error Text})
(exception.report
["Class" class]
["Error" error]))
@@ -78,7 +78,7 @@
(ffi.class_for java/lang/ClassLoader))
(java/lang/reflect/AccessibleObject::setAccessible true)))))
-(def: #export (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)
@@ -95,11 +95,11 @@
ffi.long_to_int))))]
(java/lang/reflect/Method::invoke loader signature java/lang/ClassLoader::defineClass)))
-(def: #export (new_library _)
+(def: .public (new_library _)
(-> Any Library)
(atom.atom (dictionary.empty text.hash)))
-(def: #export (memory library)
+(def: .public (memory library)
(-> Library java/lang/ClassLoader)
(with_expansions [<cast> (for {@.old
(<|)
@@ -126,7 +126,7 @@
#.None
(error! (exception.error ..unknown [class_name])))))))))
-(def: #export (store name bytecode library)
+(def: .public (store name bytecode library)
(-> Text Binary Library (IO (Try Any)))
(do {! io.monad}
[library' (atom.read library)]
@@ -136,7 +136,7 @@
[_ (atom.update (dictionary.put name bytecode) library)]
(in (#try.Success []))))))
-(def: #export (load name loader)
+(def: .public (load name loader)
(-> Text java/lang/ClassLoader
(IO (Try (java/lang/Class java/lang/Object))))
(java/lang/ClassLoader::loadClass name loader))
diff --git a/stdlib/source/library/lux/target/jvm/magic.lux b/stdlib/source/library/lux/target/jvm/magic.lux
index fee2c425a..c08360f9e 100644
--- a/stdlib/source/library/lux/target/jvm/magic.lux
+++ b/stdlib/source/library/lux/target/jvm/magic.lux
@@ -9,12 +9,12 @@
[encoding
["#." unsigned (#+ U4)]]])
-(type: #export Magic
+(type: .public Magic
U4)
-(def: #export code
+(def: .public code
Magic
(|> (hex "CAFEBABE") //unsigned.u4 try.assumed))
-(def: #export 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 a2868b2ac..54aee2e60 100644
--- a/stdlib/source/library/lux/target/jvm/method.lux
+++ b/stdlib/source/library/lux/target/jvm/method.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux (#- Type static)
+ [lux (#- Type static public private)
[abstract
[equivalence (#+ Equivalence)]
["." monad (#+ do)]]
@@ -26,7 +26,7 @@
["#/." category]
["#." descriptor (#+ Descriptor)]]])
-(type: #export #rec Method
+(type: .public #rec Method
{#modifier (Modifier Method)
#name (Index UTF8)
#descriptor (Index (Descriptor //type/category.Method))
@@ -47,7 +47,7 @@
["1000" synthetic]
)
-(def: #export (method modifier name type attributes code)
+(def: .public (method modifier name type attributes code)
(-> (Modifier Method) UTF8 (Type //type/category.Method) (List (Resource Attribute)) (Maybe (Bytecode Any))
(Resource Method))
(do {! //constant/pool.monad}
@@ -82,7 +82,7 @@
#descriptor @descriptor
#attributes attributes})))
-(def: #export equivalence
+(def: .public equivalence
(Equivalence Method)
($_ product.equivalence
//modifier.equivalence
@@ -91,7 +91,7 @@
(row.equivalence //attribute.equivalence)
))
-(def: #export (writer field)
+(def: .public (writer field)
(Writer Method)
(`` ($_ format\compose
(~~ (template [<writer> <slot>]
diff --git a/stdlib/source/library/lux/target/jvm/modifier.lux b/stdlib/source/library/lux/target/jvm/modifier.lux
index d6fae89ed..92aeafec2 100644
--- a/stdlib/source/library/lux/target/jvm/modifier.lux
+++ b/stdlib/source/library/lux/target/jvm/modifier.lux
@@ -23,14 +23,16 @@
[encoding
["#." unsigned]]])
-(abstract: #export (Modifier of)
+(abstract: .public (Modifier of)
+ {}
+
//unsigned.U2
- (def: #export code
+ (def: .public code
(-> (Modifier Any) //unsigned.U2)
(|>> :representation))
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [of] (Equivalence (Modifier of)))
(def: (= reference sample)
@@ -39,24 +41,24 @@
(:representation sample))))
(template: (!wrap value)
- (|> value
- //unsigned.u2
- try.assumed
- :abstraction))
+ [(|> value
+ //unsigned.u2
+ try.assumed
+ :abstraction)])
(template: (!unwrap value)
- (|> value
- :representation
- //unsigned.value))
+ [(|> value
+ :representation
+ //unsigned.value)])
- (def: #export (has? sub super)
+ (def: .public (has? sub super)
(All [of] (-> (Modifier of) (Modifier of) Bit))
(let [sub (!unwrap sub)]
(|> (!unwrap super)
(i64.and sub)
(\ i64.equivalence = sub))))
- (implementation: #export monoid
+ (implementation: .public monoid
(All [of] (Monoid (Modifier of)))
(def: identity
@@ -65,11 +67,11 @@
(def: (compose left right)
(!wrap (i64.or (!unwrap left) (!unwrap right)))))
- (def: #export empty
+ (def: .public empty
Modifier
(\ ..monoid identity))
- (def: #export writer
+ (def: .public writer
(All [of] (Writer (Modifier of)))
(|>> :representation //unsigned.writer/2))
@@ -78,10 +80,10 @@
(|>> !wrap))
)
-(syntax: #export (modifiers: ofT {options (<>.many <c>.any)})
+(syntax: .public (modifiers: ofT {options (<>.many <c>.any)})
(with_gensyms [g!modifier g!code]
(in (list (` (template [(~ g!code) (~ g!modifier)]
- [(def: (~' #export) (~ g!modifier)
+ [(def: (~' .public) (~ g!modifier)
(..Modifier (~ ofT))
((~! ..modifier) ((~! number.hex) (~ g!code))))]
diff --git a/stdlib/source/library/lux/target/jvm/modifier/inner.lux b/stdlib/source/library/lux/target/jvm/modifier/inner.lux
index fc9bc982c..6a7e9ae7c 100644
--- a/stdlib/source/library/lux/target/jvm/modifier/inner.lux
+++ b/stdlib/source/library/lux/target/jvm/modifier/inner.lux
@@ -5,7 +5,7 @@
abstract]]]
[// (#+ modifiers:)])
-(abstract: #export Inner Any)
+(abstract: .public Inner {} Any)
(modifiers: Inner
["0001" public]
diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux
index 6827f2be9..bdb8249f2 100644
--- a/stdlib/source/library/lux/target/jvm/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/reflection.lux
@@ -111,12 +111,12 @@
(getConstructors [] [(java/lang/reflect/Constructor java/lang/Object)])
(getDeclaredMethods [] [java/lang/reflect/Method])])
-(exception: #export (unknown_class {class External})
+(exception: .public (unknown_class {class External})
(exception.report
["Class" (%.text class)]))
(template [<name>]
- [(exception: #export (<name> {jvm_type java/lang/reflect/Type})
+ [(exception: .public (<name> {jvm_type java/lang/reflect/Type})
(exception.report
["Type" (java/lang/reflect/Type::getTypeName jvm_type)]
["Class" (|> jvm_type java/lang/Object::getClass java/lang/Object::toString)]))]
@@ -125,7 +125,7 @@
[cannot_convert_to_a_lux_type]
)
-(def: #export (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.Success class)
@@ -134,7 +134,7 @@
(#try.Failure _)
(exception.except ..unknown_class name)))
-(def: #export (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)
@@ -187,7 +187,7 @@
## else
(exception.except ..cannot_convert_to_a_lux_type reflection)))
-(def: #export (parameter reflection)
+(def: .public (parameter reflection)
(-> java/lang/reflect/Type (Try (/.Type Parameter)))
(<| (case (ffi.check java/lang/reflect/TypeVariable reflection)
(#.Some reflection)
@@ -217,12 +217,12 @@
_)
(..class' parameter reflection)))
-(def: #export class
+(def: .public class
(-> java/lang/reflect/Type
(Try (/.Type Class)))
(..class' ..parameter))
-(def: #export (type reflection)
+(def: .public (type reflection)
(-> java/lang/reflect/Type (Try (/.Type Value)))
(<| (case (ffi.check java/lang/Class reflection)
(#.Some reflection)
@@ -256,7 +256,7 @@
## else
(..parameter reflection)))
-(def: #export (return reflection)
+(def: .public (return reflection)
(-> java/lang/reflect/Type (Try (/.Type Return)))
(with_expansions [<else> (as_is (..type reflection))]
(case (ffi.check java/lang/Class reflection)
@@ -272,13 +272,13 @@
#.None
<else>)))
-(exception: #export (cannot_correspond {class (java/lang/Class java/lang/Object)}
+(exception: .public (cannot_correspond {class (java/lang/Class java/lang/Object)}
{type Type})
(exception.report
["Class" (java/lang/Object::toString class)]
["Type" (%.type type)]))
-(exception: #export (type_parameter_mismatch {expected Nat}
+(exception: .public (type_parameter_mismatch {expected Nat}
{actual Nat}
{class (java/lang/Class java/lang/Object)}
{type Type})
@@ -288,11 +288,11 @@
["Class" (java/lang/Object::toString class)]
["Type" (%.type type)]))
-(exception: #export (non_jvm_type {type Type})
+(exception: .public (non_jvm_type {type Type})
(exception.report
["Type" (%.type type)]))
-(def: #export (correspond class type)
+(def: .public (correspond class type)
(-> (java/lang/Class java/lang/Object) Type (Try Mapping))
(case type
(#.Primitive name params)
@@ -326,7 +326,7 @@
_
(exception.except ..non_jvm_type [type])))
-(exception: #export (mistaken_field_owner {field java/lang/reflect/Field}
+(exception: .public (mistaken_field_owner {field java/lang/reflect/Field}
{owner (java/lang/Class java/lang/Object)}
{target (java/lang/Class java/lang/Object)})
(exception.report
@@ -335,7 +335,7 @@
["Target" (java/lang/Object::toString target)]))
(template [<name>]
- [(exception: #export (<name> {field Text}
+ [(exception: .public (<name> {field Text}
{class (java/lang/Class java/lang/Object)})
(exception.report
["Field" (%.text field)]
@@ -346,7 +346,7 @@
[not_a_virtual_field]
)
-(def: #export (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: #export deprecated?
+(def: .public deprecated?
(-> (array.Array java/lang/annotation/Annotation) Bit)
(|>> array.list
(list.all (|>> (ffi.check java/lang/Deprecated)))
@@ -366,7 +366,7 @@
not))
(template [<name> <exception> <then?> <else?>]
- [(def: #export (<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 9b29382c7..c4a5abd0b 100644
--- a/stdlib/source/library/lux/target/jvm/type.lux
+++ b/stdlib/source/library/lux/target/jvm/type.lux
@@ -24,22 +24,24 @@
["#." descriptor (#+ Descriptor)]
["#." reflection (#+ Reflection)]])
-(abstract: #export (Type category)
+(abstract: .public (Type category)
+ {}
+
[(Signature category) (Descriptor category) (Reflection category)]
- (type: #export Argument
+ (type: .public Argument
[Text (Type Value)])
- (type: #export (Typed a)
+ (type: .public (Typed a)
[(Type Value) a])
- (type: #export Constraint
+ (type: .public Constraint
{#name Text
#super_class (Type Class)
#super_interfaces (List (Type Class))})
(template [<name> <style>]
- [(def: #export (<name> type)
+ [(def: .public (<name> type)
(All [category] (-> (Type category) (<style> category)))
(let [[signature descriptor reflection] (:representation type)]
<name>))]
@@ -48,7 +50,7 @@
[descriptor Descriptor]
)
- (def: #export (reflection type)
+ (def: .public (reflection type)
(All [category]
(-> (Type (<| Return' Value' category))
(Reflection (<| Return' Value' category))))
@@ -56,7 +58,7 @@
reflection))
(template [<category> <name> <signature> <descriptor> <reflection>]
- [(def: #export <name>
+ [(def: .public <name>
(Type <category>)
(:abstraction [<signature> <descriptor> <reflection>]))]
@@ -71,28 +73,28 @@
[Primitive char /signature.char /descriptor.char /reflection.char]
)
- (def: #export (array type)
+ (def: .public (array type)
(-> (Type Value) (Type Array))
(:abstraction
[(/signature.array (..signature type))
(/descriptor.array (..descriptor type))
(/reflection.array (..reflection type))]))
- (def: #export (class name parameters)
+ (def: .public (class name parameters)
(-> External (List (Type Parameter)) (Type Class))
(:abstraction
[(/signature.class name (list\map ..signature parameters))
(/descriptor.class name)
(/reflection.class name)]))
- (def: #export (declaration name variables)
+ (def: .public (declaration name variables)
(-> External (List (Type Var)) (Type Declaration))
(:abstraction
[(/signature.declaration name (list\map ..signature variables))
(/descriptor.declaration name)
(/reflection.declaration name)]))
- (def: #export (as_class type)
+ (def: .public (as_class type)
(-> (Type Declaration) (Type Class))
(:abstraction
(let [[signature descriptor reflection] (:representation type)]
@@ -100,21 +102,21 @@
(/descriptor.as_class descriptor)
(/reflection.as_class reflection)])))
- (def: #export wildcard
+ (def: .public wildcard
(Type Parameter)
(:abstraction
[/signature.wildcard
/descriptor.wildcard
/reflection.wildcard]))
- (def: #export (var name)
+ (def: .public (var name)
(-> Text (Type Var))
(:abstraction
[(/signature.var name)
/descriptor.var
/reflection.var]))
- (def: #export (lower bound)
+ (def: .public (lower bound)
(-> (Type Class) (Type Parameter))
(:abstraction
(let [[signature descriptor reflection] (:representation bound)]
@@ -122,7 +124,7 @@
(/descriptor.lower descriptor)
(/reflection.lower reflection)])))
- (def: #export (upper bound)
+ (def: .public (upper bound)
(-> (Type Class) (Type Parameter))
(:abstraction
(let [[signature descriptor reflection] (:representation bound)]
@@ -130,7 +132,7 @@
(/descriptor.upper descriptor)
(/reflection.upper reflection)])))
- (def: #export (method [type_variables inputs output exceptions])
+ (def: .public (method [type_variables inputs output exceptions])
(-> [(List (Type Var))
(List (Type Value))
(Type Return)
@@ -145,7 +147,7 @@
(..descriptor output)])
(:assume ..void)]))
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [category] (Equivalence (Type category)))
(def: (= parameter subject)
@@ -153,13 +155,13 @@
(..signature parameter)
(..signature subject))))
- (implementation: #export hash
+ (implementation: .public hash
(All [category] (Hash (Type category)))
(def: &equivalence ..equivalence)
(def: hash (|>> ..signature (\ /signature.hash hash))))
- (def: #export (primitive? type)
+ (def: .public (primitive? type)
(-> (Type Value) (Either (Type Object)
(Type Primitive)))
(if (`` (or (~~ (template [<type>]
@@ -176,7 +178,7 @@
(|> type (:as (Type Primitive)) #.Right)
(|> type (:as (Type Object)) #.Left)))
- (def: #export (void? type)
+ (def: .public (void? type)
(-> (Type Return) (Either (Type Value)
(Type Void)))
(if (`` (or (~~ (template [<type>]
@@ -187,7 +189,7 @@
(|> type (:as (Type Value)) #.Left)))
)
-(def: #export (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)
@@ -202,6 +204,6 @@
(\ maybe.monad map (|>> //name.internal //name.external))))
#.None)))
-(def: #export 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 e4c4ccca3..05ecd1f29 100644
--- a/stdlib/source/library/lux/target/jvm/type/alias.lux
+++ b/stdlib/source/library/lux/target/jvm/type/alias.lux
@@ -24,10 +24,10 @@
[encoding
["#." name]]]])
-(type: #export Aliasing
+(type: .public Aliasing
(Dictionary Text Text))
-(def: #export fresh
+(def: .public fresh
Aliasing
(dictionary.empty text.hash))
@@ -115,7 +115,7 @@
(\ <>.monad map //.var)
(<>.before (<>.many (..bound aliasing)))))
-(def: #export (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 9479ef218..44ab2a6ee 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 (#+ External)]]])
(template [<name> <box>]
- [(def: #export <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/category.lux b/stdlib/source/library/lux/target/jvm/type/category.lux
index 7f492290d..c42a007f2 100644
--- a/stdlib/source/library/lux/target/jvm/type/category.lux
+++ b/stdlib/source/library/lux/target/jvm/type/category.lux
@@ -6,25 +6,25 @@
[type
abstract]]])
-(abstract: #export Void' Any)
-(abstract: #export (Value' kind) Any)
-(abstract: #export (Return' kind) Any)
-(abstract: #export Method Any)
+(abstract: .public Void' {} Any)
+(abstract: .public (Value' kind) {} Any)
+(abstract: .public (Return' kind) {} Any)
+(abstract: .public Method {} Any)
-(type: #export Return (<| Return' Any))
-(type: #export Value (<| Return' Value' Any))
-(type: #export Void (<| Return' Void'))
+(type: .public Return (<| Return' Any))
+(type: .public Value (<| Return' Value' Any))
+(type: .public Void (<| Return' Void'))
-(abstract: #export (Object' brand) Any)
-(type: #export Object (<| Return' Value' Object' Any))
+(abstract: .public (Object' brand) {} Any)
+(type: .public Object (<| Return' Value' Object' Any))
-(abstract: #export (Parameter' brand) Any)
-(type: #export Parameter (<| Return' Value' Object' Parameter' Any))
+(abstract: .public (Parameter' brand) {} Any)
+(type: .public Parameter (<| Return' Value' Object' Parameter' Any))
(template [<parents> <child>]
[(with_expansions [<raw> (template.identifier [<child> "'"])]
- (abstract: #export <raw> Any)
- (type: #export <child>
+ (abstract: .public <raw> {} Any)
+ (type: .public <child>
(`` (<| Return' Value' (~~ (template.spliced <parents>)) <raw>))))]
[[] Primitive]
@@ -33,4 +33,4 @@
[[Object'] Array]
)
-(abstract: #export Declaration Any)
+(abstract: .public Declaration {} Any)
diff --git a/stdlib/source/library/lux/target/jvm/type/descriptor.lux b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
index 6f36f544b..df751407b 100644
--- a/stdlib/source/library/lux/target/jvm/type/descriptor.lux
+++ b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
@@ -20,15 +20,17 @@
[encoding
["#." name (#+ Internal External)]]]])
-(abstract: #export (Descriptor category)
+(abstract: .public (Descriptor category)
+ {}
+
Text
- (def: #export descriptor
+ (def: .public descriptor
(-> (Descriptor Any) Text)
(|>> :representation))
(template [<sigil> <category> <name>]
- [(def: #export <name>
+ [(def: .public <name>
(Descriptor <category>)
(:abstraction <sigil>))]
@@ -43,26 +45,26 @@
["C" Primitive char]
)
- (def: #export class_prefix "L")
- (def: #export class_suffix ";")
+ (def: .public class_prefix "L")
+ (def: .public class_suffix ";")
- (def: #export class
+ (def: .public class
(-> External (Descriptor Class))
(|>> ///name.internal
///name.read
(text.enclosed [..class_prefix ..class_suffix])
:abstraction))
- (def: #export (declaration name)
+ (def: .public (declaration name)
(-> External (Descriptor Declaration))
(:transmutation (..class name)))
- (def: #export as_class
+ (def: .public as_class
(-> (Descriptor Declaration) (Descriptor Class))
(|>> :transmutation))
(template [<name> <category>]
- [(def: #export <name>
+ [(def: .public <name>
(Descriptor <category>)
(:transmutation
(..class "java.lang.Object")))]
@@ -71,24 +73,24 @@
[wildcard Parameter]
)
- (def: #export (lower descriptor)
+ (def: .public (lower descriptor)
(-> (Descriptor Class) (Descriptor Parameter))
..wildcard)
- (def: #export upper
+ (def: .public upper
(-> (Descriptor Class) (Descriptor Parameter))
(|>> :transmutation))
- (def: #export array_prefix "[")
+ (def: .public array_prefix "[")
- (def: #export array
+ (def: .public array
(-> (Descriptor Value)
(Descriptor Array))
(|>> :representation
(format ..array_prefix)
:abstraction))
- (def: #export (method [inputs output])
+ (def: .public (method [inputs output])
(-> [(List (Descriptor Value))
(Descriptor Return)]
(Descriptor Method))
@@ -99,13 +101,13 @@
(text.enclosed ["(" ")"]))
(:representation output))))
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [category] (Equivalence (Descriptor category)))
(def: (= parameter subject)
(text\= (:representation parameter) (:representation subject))))
- (def: #export 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 86184ebbd..5a58e3dc0 100644
--- a/stdlib/source/library/lux/target/jvm/type/lux.lux
+++ b/stdlib/source/library/lux/target/jvm/type/lux.lux
@@ -30,19 +30,19 @@
["#." name]]]])
(template [<name>]
- [(abstract: #export (<name> class) Any)]
+ [(abstract: .public (<name> class) {} Any)]
[Lower] [Upper]
)
-(type: #export Mapping
+(type: .public Mapping
(Dictionary Text Type))
-(def: #export fresh
+(def: .public fresh
Mapping
(dictionary.empty text.hash))
-(exception: #export (unknown_var {var Text})
+(exception: .public (unknown_var {var Text})
(exception.report
["Var" (%.text var)]))
@@ -165,7 +165,7 @@
class
)))))
-(def: #export class
+(def: .public class
(-> Mapping (Parser (Check Type)))
(|>> ..parameter ..class'))
@@ -192,7 +192,7 @@
(|> elementT array.Array .type)))))
(<>.after (<text>.this //descriptor.array_prefix))))
-(def: #export (type mapping)
+(def: .public (type mapping)
(-> Mapping (Parser (Check Type)))
(<>.rec
(function (_ type)
@@ -202,7 +202,7 @@
(..array type)
))))
-(def: #export (boxed_type mapping)
+(def: .public (boxed_type mapping)
(-> Mapping (Parser (Check Type)))
(<>.rec
(function (_ type)
@@ -212,21 +212,21 @@
(..array type)
))))
-(def: #export (return mapping)
+(def: .public (return mapping)
(-> Mapping (Parser (Check Type)))
($_ <>.either
..void
(..type mapping)
))
-(def: #export (boxed_return mapping)
+(def: .public (boxed_return mapping)
(-> Mapping (Parser (Check Type)))
($_ <>.either
..void
(..boxed_type mapping)
))
-(def: #export (check operation input)
+(def: .public (check operation input)
(All [a] (-> (Parser (Check a)) Text (Check a)))
(case (<text>.run 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 5dbada115..f54b961cc 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 @@
["#." name (#+ External)]]]])
(template [<category> <name> <signature> <type>]
- [(def: #export <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: #export primitive
+(def: .public primitive
(Parser (Type Primitive))
($_ <>.either
..boolean
@@ -66,7 +66,7 @@
(format var/tail //name.internal_separator))
(template [<type> <name> <head> <tail> <adapter>]
- [(def: #export <name>
+ [(def: .public <name>
(Parser <type>)
(\ <>.functor map <adapter>
(<text>.slice (<text>.and! (<text>.one_of! <head>)
@@ -76,24 +76,24 @@
[Text var_name var/head var/tail function.identity]
)
-(def: #export var'
+(def: .public var'
(Parser Text)
(|> ..var_name
(<>.after (<text>.this //signature.var_prefix))
(<>.before (<text>.this //descriptor.class_suffix))))
-(def: #export var
+(def: .public var
(Parser (Type Var))
(<>\map //.var ..var'))
-(def: #export var?
+(def: .public var?
(-> (Type Value) (Maybe Text))
(|>> //.signature
//signature.signature
(<text>.run ..var')
try.maybe))
-(def: #export name
+(def: .public name
(-> (Type Var) Text)
(|>> //.signature
//signature.signature
@@ -127,7 +127,7 @@
(|>> ..class''
(\ <>.monad map (product.uncurry //.class))))
-(def: #export parameter
+(def: .public parameter
(Parser (Type Parameter))
(<>.rec
(function (_ parameter)
@@ -140,17 +140,17 @@
class
)))))
-(def: #export array'
+(def: .public array'
(-> (Parser (Type Value)) (Parser (Type Array)))
(|>> (<>.after (<text>.this //descriptor.array_prefix))
(<>\map //.array)))
-(def: #export class
+(def: .public class
(Parser (Type Class))
(..class' ..parameter))
(template [<name> <prefix> <constructor>]
- [(def: #export <name>
+ [(def: .public <name>
(-> (Type Value) (Maybe (Type Class)))
(|>> //.signature
//signature.signature
@@ -161,14 +161,14 @@
[upper? //signature.upper_prefix //.upper]
)
-(def: #export read_class
+(def: .public read_class
(-> (Type Class) [External (List (Type Parameter))])
(|>> //.signature
//signature.signature
(<text>.run (..class'' ..parameter))
try.assumed))
-(def: #export value
+(def: .public value
(Parser (Type Value))
(<>.rec
(function (_ value)
@@ -178,11 +178,11 @@
(..array' value)
))))
-(def: #export array
+(def: .public array
(Parser (Type Array))
(..array' ..value))
-(def: #export object
+(def: .public object
(Parser (Type Object))
($_ <>.either
..class
@@ -193,7 +193,7 @@
(<>.after (<text>.this //signature.arguments_start))
(<>.before (<text>.this //signature.arguments_end))))
-(def: #export return
+(def: .public return
(Parser (Type Return))
(<>.either ..void
..value))
@@ -203,7 +203,7 @@
(|> (..class' ..parameter)
(<>.after (<text>.this //signature.exception_prefix))))
-(def: #export method
+(def: .public method
(-> (Type Method)
[(List (Type Var))
(List (Type Value))
@@ -227,7 +227,7 @@
try.assumed)))
(template [<name> <category> <parser>]
- [(def: #export <name>
+ [(def: .public <name>
(-> (Type Value) (Maybe <category>))
(|>> //.signature
//signature.signature
@@ -247,7 +247,7 @@
[object? (Type Object) ..object]
)
-(def: #export declaration'
+(def: .public declaration'
(Parser [External (List (Type Var))])
(|> (<>.and ..class_name
(|> (<>.some ..var)
@@ -257,7 +257,7 @@
(<>.after (<text>.this //descriptor.class_prefix))
(<>.before (<text>.this //descriptor.class_suffix))))
-(def: #export 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 78ef5a45c..f92b41ae5 100644
--- a/stdlib/source/library/lux/target/jvm/type/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/type/reflection.lux
@@ -15,21 +15,23 @@
[encoding
["#." name (#+ External)]]]])
-(abstract: #export (Reflection category)
+(abstract: .public (Reflection category)
+ {}
+
Text
- (def: #export reflection
+ (def: .public reflection
(-> (Reflection Any) Text)
(|>> :representation))
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [category] (Equivalence (Reflection category)))
(def: (= parameter subject)
(text\= (:representation parameter) (:representation subject))))
(template [<category> <name> <reflection>]
- [(def: #export <name>
+ [(def: .public <name>
(Reflection <category>)
(:abstraction <reflection>))]
@@ -44,19 +46,19 @@
[Primitive char "char"]
)
- (def: #export class
+ (def: .public class
(-> External (Reflection Class))
(|>> :abstraction))
- (def: #export (declaration name)
+ (def: .public (declaration name)
(-> External (Reflection Declaration))
(:transmutation (..class name)))
- (def: #export as_class
+ (def: .public as_class
(-> (Reflection Declaration) (Reflection Class))
(|>> :transmutation))
- (def: #export (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 +87,7 @@
:abstraction)))
(template [<name> <category>]
- [(def: #export <name>
+ [(def: .public <name>
(Reflection <category>)
(:transmutation
(..class "java.lang.Object")))]
@@ -94,11 +96,11 @@
[wildcard Parameter]
)
- (def: #export (lower reflection)
+ (def: .public (lower reflection)
(-> (Reflection Class) (Reflection Parameter))
..wildcard)
- (def: #export upper
+ (def: .public upper
(-> (Reflection Class) (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 84a6a5982..4ebdb9248 100644
--- a/stdlib/source/library/lux/target/jvm/type/signature.lux
+++ b/stdlib/source/library/lux/target/jvm/type/signature.lux
@@ -18,15 +18,17 @@
[encoding
["#." name (#+ External)]]]])
-(abstract: #export (Signature category)
+(abstract: .public (Signature category)
+ {}
+
Text
- (def: #export signature
+ (def: .public signature
(-> (Signature Any) Text)
(|>> :representation))
(template [<category> <name> <descriptor>]
- [(def: #export <name>
+ [(def: .public <name>
(Signature <category>)
(:abstraction (//descriptor.descriptor <descriptor>)))]
@@ -41,34 +43,34 @@
[Primitive char //descriptor.char]
)
- (def: #export array
+ (def: .public array
(-> (Signature Value) (Signature Array))
(|>> :representation
(format //descriptor.array_prefix)
:abstraction))
- (def: #export wildcard
+ (def: .public wildcard
(Signature Parameter)
(:abstraction "*"))
- (def: #export var_prefix "T")
+ (def: .public var_prefix "T")
- (def: #export var
+ (def: .public var
(-> Text (Signature Var))
(|>> (text.enclosed [..var_prefix //descriptor.class_suffix])
:abstraction))
- (def: #export var_name
+ (def: .public var_name
(-> (Signature Var) Text)
(|>> :representation
(text.replace_all ..var_prefix "")
(text.replace_all //descriptor.class_suffix "")))
- (def: #export lower_prefix "-")
- (def: #export upper_prefix "+")
+ (def: .public lower_prefix "-")
+ (def: .public upper_prefix "+")
(template [<name> <prefix>]
- [(def: #export <name>
+ [(def: .public <name>
(-> (Signature Class) (Signature Parameter))
(|>> :representation (format <prefix>) :abstraction))]
@@ -76,10 +78,10 @@
[upper ..upper_prefix]
)
- (def: #export parameters_start "<")
- (def: #export parameters_end ">")
+ (def: .public parameters_start "<")
+ (def: .public parameters_end ">")
- (def: #export (class name parameters)
+ (def: .public (class name parameters)
(-> External (List (Signature Parameter)) (Signature Class))
(:abstraction
(format //descriptor.class_prefix
@@ -96,25 +98,25 @@
..parameters_end))
//descriptor.class_suffix)))
- (def: #export (declaration name variables)
+ (def: .public (declaration name variables)
(-> External (List (Signature Var)) (Signature Declaration))
(:transmutation (..class name variables)))
- (def: #export as_class
+ (def: .public as_class
(-> (Signature Declaration) (Signature Class))
(|>> :transmutation))
- (def: #export arguments_start "(")
- (def: #export arguments_end ")")
+ (def: .public arguments_start "(")
+ (def: .public arguments_end ")")
- (def: #export exception_prefix "^")
+ (def: .public exception_prefix "^")
(def: class_bound
(|> (..class "java.lang.Object" (list))
..signature
(format ":")))
- (def: #export (method [type_variables inputs output exceptions])
+ (def: .public (method [type_variables inputs output exceptions])
(-> [(List (Signature Var))
(List (Signature Value))
(Signature Return)
@@ -141,14 +143,14 @@
(list\map (|>> :representation (format ..exception_prefix)))
(text.join_with "")))))
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [category] (Equivalence (Signature category)))
(def: (= parameter subject)
(text\= (:representation parameter)
(:representation subject))))
- (implementation: #export hash
+ (implementation: .public hash
(All [category] (Hash (Signature category)))
(def: &equivalence ..equivalence)
diff --git a/stdlib/source/library/lux/target/jvm/version.lux b/stdlib/source/library/lux/target/jvm/version.lux
index d22ca84e2..f5db348ef 100644
--- a/stdlib/source/library/lux/target/jvm/version.lux
+++ b/stdlib/source/library/lux/target/jvm/version.lux
@@ -7,16 +7,16 @@
[encoding
["#." unsigned (#+ U2)]]])
-(type: #export Version U2)
-(type: #export Minor Version)
-(type: #export Major Version)
+(type: .public Version U2)
+(type: .public Minor Version)
+(type: .public Major Version)
-(def: #export default_minor
+(def: .public default_minor
Minor
(|> 0 //unsigned.u2 try.assumed))
(template [<number> <name>]
- [(def: #export <name>
+ [(def: .public <name>
Major
(|> <number> //unsigned.u2 try.assumed))]
@@ -34,5 +34,5 @@
[56 v12]
)
-(def: #export 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 0f24e59e4..a94c483f6 100644
--- a/stdlib/source/library/lux/target/lua.lux
+++ b/stdlib/source/library/lux/target/lua.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux (#- Location Code int if cond function or and not let ^)
+ [lux (#- Location Code int if cond function or and not let ^ local)
["@" target]
[abstract
[equivalence (#+ Equivalence)]
@@ -35,33 +35,35 @@
(def: input_separator ", ")
-(abstract: #export (Code brand)
+(abstract: .public (Code brand)
+ {}
+
Text
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [brand] (Equivalence (Code brand)))
(def: (= reference subject)
(\ text.equivalence = (:representation reference) (:representation subject))))
- (implementation: #export hash
+ (implementation: .public hash
(All [brand] (Hash (Code brand)))
(def: &equivalence ..equivalence)
(def: hash (|>> :representation (\ text.hash hash))))
- (def: #export manual
+ (def: .public manual
(-> Text Code)
(|>> :abstraction))
- (def: #export code
+ (def: .public code
(-> (Code Any) Text)
(|>> :representation))
(template [<type> <super>+]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (abstract: (<brand> brand) Any)
- (`` (type: #export <type> (|> Any <brand> (~~ (template.spliced <super>+))))))]
+ (abstract: (<brand> brand) {} Any)
+ (`` (type: .public <type> (|> Any <brand> (~~ (template.spliced <super>+))))))]
[Expression [Code]]
[Computation [Expression' Code]]
@@ -71,8 +73,8 @@
(template [<type> <super>+]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (abstract: #export <brand> Any)
- (`` (type: #export <type> (|> <brand> (~~ (template.spliced <super>+))))))]
+ (abstract: .public <brand> {} Any)
+ (`` (type: .public <type> (|> <brand> (~~ (template.spliced <super>+))))))]
[Literal [Computation' Expression' Code]]
[Var [Location' Computation' Expression' Code]]
@@ -80,17 +82,17 @@
[Label [Code]]
)
- (def: #export nil
+ (def: .public nil
Literal
(:abstraction "nil"))
- (def: #export bool
+ (def: .public bool
(-> Bit Literal)
(|>> (case> #0 "false"
#1 "true")
:abstraction))
- (def: #export 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.
@@ -100,7 +102,7 @@
(format "0x")
:abstraction)))
- (def: #export float
+ (def: .public float
(-> Frac Literal)
(|>> (cond> [(f.= f.positive_infinity)]
[(new> "(1.0/0.0)" [])]
@@ -132,24 +134,24 @@
))
)))
- (def: #export string
+ (def: .public string
(-> Text Literal)
(|>> ..safe (text.enclosed' text.double_quote) :abstraction))
- (def: #export multi
+ (def: .public multi
(-> (List Expression) Literal)
(|>> (list\map ..code)
(text.join_with ..input_separator)
:abstraction))
- (def: #export array
+ (def: .public array
(-> (List Expression) Literal)
(|>> (list\map ..code)
(text.join_with ..input_separator)
(text.enclosed ["{" "}"])
:abstraction))
- (def: #export table
+ (def: .public table
(-> (List [Text Expression]) Literal)
(|>> (list\map (.function (_ [key value])
(format key " = " (:representation value))))
@@ -157,21 +159,21 @@
(text.enclosed ["{" "}"])
:abstraction))
- (def: #export (nth idx array)
+ (def: .public (nth idx array)
(-> Expression Expression Access)
(:abstraction (format (:representation array) "[" (:representation idx) "]")))
- (def: #export (the field table)
+ (def: .public (the field table)
(-> Text Expression Computation)
(:abstraction (format (:representation table) "." field)))
- (def: #export length
+ (def: .public length
(-> Expression Computation)
(|>> :representation
(text.enclosed ["#(" ")"])
:abstraction))
- (def: #export (apply/* args func)
+ (def: .public (apply/* args func)
(-> (List Expression) Expression Computation)
(|> args
(list\map ..code)
@@ -180,7 +182,7 @@
(format (:representation func))
:abstraction))
- (def: #export (do method args table)
+ (def: .public (do method args table)
(-> Text (List Expression) Expression Computation)
(|> args
(list\map ..code)
@@ -190,7 +192,7 @@
:abstraction))
(template [<op> <name>]
- [(def: #export (<name> parameter subject)
+ [(def: .public (<name> parameter subject)
(-> Expression Expression Expression)
(:abstraction (format "("
(:representation subject)
@@ -223,7 +225,7 @@
)
(template [<name> <unary>]
- [(def: #export (<name> subject)
+ [(def: .public (<name> subject)
(-> Expression Expression)
(:abstraction (format "(" <unary> " " (:representation subject) ")")))]
@@ -232,7 +234,7 @@
)
(template [<name> <type>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Text <type>)
(|>> :abstraction))]
@@ -240,11 +242,11 @@
[label Label]
)
- (def: #export statement
+ (def: .public statement
(-> Expression Statement)
(|>> :representation :abstraction))
- (def: #export (then pre! post!)
+ (def: .public (then pre! post!)
(-> Statement Statement Statement)
(:abstraction
(format (:representation pre!)
@@ -256,50 +258,50 @@
(|>> (list\map ..code)
(text.join_with ..input_separator)))
- (def: #export (local vars)
+ (def: .public (local vars)
(-> (List Var) Statement)
(:abstraction (format "local " (..locations vars))))
- (def: #export (set vars value)
+ (def: .public (set vars value)
(-> (List Location) Expression Statement)
(:abstraction (format (..locations vars) " = " (:representation value))))
- (def: #export (let vars value)
+ (def: .public (let vars value)
(-> (List Var) Expression Statement)
(:abstraction (format "local " (..locations vars) " = " (:representation value))))
- (def: #export (local/1 var value)
+ (def: .public (local/1 var value)
(-> Var Expression Statement)
(:abstraction (format "local " (:representation var) " = " (:representation value))))
- (def: #export (if test then! else!)
+ (def: .public (if test then! else!)
(-> Expression Statement Statement Statement)
(:abstraction (format "if " (:representation test)
text.new_line "then" (..nested (:representation then!))
text.new_line "else" (..nested (:representation else!))
text.new_line "end")))
- (def: #export (when test then!)
+ (def: .public (when test then!)
(-> Expression Statement Statement)
(:abstraction (format "if " (:representation test)
text.new_line "then" (..nested (:representation then!))
text.new_line "end")))
- (def: #export (while test body!)
+ (def: .public (while test body!)
(-> Expression Statement Statement)
(:abstraction
(format "while " (:representation test) " do"
(..nested (:representation body!))
text.new_line "end")))
- (def: #export (repeat until body!)
+ (def: .public (repeat until body!)
(-> Expression Statement Statement)
(:abstraction
(format "repeat"
(..nested (:representation body!))
text.new_line "until " (:representation until))))
- (def: #export (for_in vars source body!)
+ (def: .public (for_in vars source body!)
(-> (List Var) Expression Statement Statement)
(:abstraction
(format "for " (|> vars
@@ -309,7 +311,7 @@
(..nested (:representation body!))
text.new_line "end")))
- (def: #export (for_step var from to step body!)
+ (def: .public (for_step var from to step body!)
(-> Var Expression Expression Expression Statement
Statement)
(:abstraction
@@ -320,11 +322,11 @@
(..nested (:representation body!))
text.new_line "end")))
- (def: #export (return value)
+ (def: .public (return value)
(-> Expression Statement)
(:abstraction (format "return " (:representation value))))
- (def: #export (closure args body!)
+ (def: .public (closure args body!)
(-> (List Var) Statement Expression)
(|> (format "function " (|> args
..locations
@@ -335,7 +337,7 @@
:abstraction))
(template [<name> <code>]
- [(def: #export (<name> name args body!)
+ [(def: .public (<name> name args body!)
(-> Var (List Var) Statement Statement)
(:abstraction
(format <code> " " (:representation name)
@@ -349,20 +351,20 @@
[local_function "local function"]
)
- (def: #export break
+ (def: .public break
Statement
(:abstraction "break"))
- (def: #export (set_label label)
+ (def: .public (set_label label)
(-> Label Statement)
(:abstraction (format "::" (:representation label) "::")))
- (def: #export (go_to label)
+ (def: .public (go_to label)
(-> Label Statement)
(:abstraction (format "goto " (:representation label))))
)
-(def: #export (cond clauses else!)
+(def: .public (cond clauses else!)
(-> (List [Expression Statement]) Statement Statement)
(list\fold (.function (_ [test then!] next!)
(..if test then! next!))
@@ -384,12 +386,12 @@
<inputs> (arity_inputs <arity>)
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
- (def: #export (<apply> function <inputs>)
+ (def: .public (<apply> function <inputs>)
(-> Expression <types> Computation)
(..apply/* (.list <inputs>) function))
(template [<function>]
- [(`` (def: #export (~~ (template.identifier [<function> "/" <arity>]))
+ [(`` (def: .public (~~ (template.identifier [<function> "/" <arity>]))
(<apply> (..var <function>))))]
<definitions>))]
diff --git a/stdlib/source/library/lux/target/php.lux b/stdlib/source/library/lux/target/php.lux
index e80fdbecd..c1056e777 100644
--- a/stdlib/source/library/lux/target/php.lux
+++ b/stdlib/source/library/lux/target/php.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux (#- Location Code Global static int if cond or and not comment for try)
+ [lux (#- Location Code Global static int if cond or and not comment for try global)
["@" target]
[abstract
[equivalence (#+ Equivalence)]
@@ -43,33 +43,35 @@
(-> Text Text)
(text.enclosed ["(" ")"]))
-(abstract: #export (Code brand)
+(abstract: .public (Code brand)
+ {}
+
Text
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [brand] (Equivalence (Code brand)))
(def: (= reference subject)
(\ text.equivalence = (:representation reference) (:representation subject))))
- (implementation: #export hash
+ (implementation: .public hash
(All [brand] (Hash (Code brand)))
(def: &equivalence ..equivalence)
(def: hash (|>> :representation (\ text.hash hash))))
- (def: #export manual
+ (def: .public manual
(-> Text Code)
(|>> :abstraction))
- (def: #export code
+ (def: .public code
(-> (Code Any) Text)
(|>> :representation))
(template [<type> <super>+]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (abstract: (<brand> brand) Any)
- (`` (type: #export <type> (|> Any <brand> (~~ (template.spliced <super>+))))))]
+ (abstract: (<brand> brand) {} Any)
+ (`` (type: .public <type> (|> Any <brand> (~~ (template.spliced <super>+))))))]
[Expression [Code]]
[Computation [Expression' Code]]
@@ -79,8 +81,8 @@
(template [<type> <super>+]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (abstract: #export <brand> Any)
- (`` (type: #export <type> (|> <brand> (~~ (template.spliced <super>+))))))]
+ (abstract: .public <brand> {} Any)
+ (`` (type: .public <type> (|> <brand> (~~ (template.spliced <super>+))))))]
[Literal [Computation' Expression' Code]]
[Var [Location' Computation' Expression' Code]]
@@ -90,22 +92,22 @@
[Label [Code]]
)
- (type: #export Argument
+ (type: .public Argument
{#reference? Bit
#var Var})
- (def: #export ;
+ (def: .public ;
(-> Expression Statement)
(|>> :representation
(text.suffix ..statement_suffix)
:abstraction))
- (def: #export var
+ (def: .public var
(-> Text Var)
(|>> (format "$") :abstraction))
(template [<name> <type>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Text <type>)
(|>> :abstraction))]
@@ -113,26 +115,26 @@
[label Label]
)
- (def: #export (set_label label)
+ (def: .public (set_label label)
(-> Label Statement)
(:abstraction (format (:representation label) ":")))
- (def: #export (go_to label)
+ (def: .public (go_to label)
(-> Label Statement)
(:abstraction
(format "goto " (:representation label) ..statement_suffix)))
- (def: #export null
+ (def: .public null
Literal
(:abstraction "NULL"))
- (def: #export bool
+ (def: .public bool
(-> Bit Literal)
(|>> (case> #0 "false"
#1 "true")
:abstraction))
- (def: #export int
+ (def: .public int
(-> Int Literal)
(.let [to_hex (\ n.hex encode)]
(|>> .nat
@@ -140,7 +142,7 @@
(format "0x")
:abstraction)))
- (def: #export float
+ (def: .public float
(-> Frac Literal)
(|>> (cond> [(f.= f.positive_infinity)]
[(new> "+INF" [])]
@@ -173,7 +175,7 @@
))
)))
- (def: #export string
+ (def: .public string
(-> Text Literal)
(|>> ..safe
(text.enclosed [text.double_quote text.double_quote])
@@ -183,13 +185,13 @@
(-> (List Expression) Text)
(|>> (list\map ..code) (text.join_with ..input_separator) ..group))
- (def: #export (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: #export (apply/*' args func)
+ (def: .public (apply/*' args func)
(-> (List Expression) Expression Computation)
(apply/* (list& func args) (..constant "call_user_func")))
@@ -203,7 +205,7 @@
..group))
(template [<name> <reference?>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Var Argument)
(|>> [<reference?>]))]
@@ -211,7 +213,7 @@
[reference #1]
)
- (def: #export (closure uses arguments body!)
+ (def: .public (closure uses arguments body!)
(-> (List Argument) (List Argument) Statement Literal)
(let [uses (case uses
#.End
@@ -240,12 +242,12 @@
<inputs> (arity_inputs <arity>)
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
- (def: #export (<apply> function [<inputs>])
+ (def: .public (<apply> function [<inputs>])
(-> Expression [<types>] Computation)
(..apply/* (.list <inputs>) function))
(template [<function>]
- [(`` (def: #export (~~ (template.identifier [<function> "/" <arity>]))
+ [(`` (def: .public (~~ (template.identifier [<function> "/" <arity>]))
(<apply> (..constant <function>))))]
<definitions>))]
@@ -300,11 +302,11 @@
["iconv_substr"] ["substr"]]]
)
- (def: #export (key_value key value)
+ (def: .public (key_value key value)
(-> Expression Expression Expression)
(:abstraction (format (:representation key) " => " (:representation value))))
- (def: #export (array/* values)
+ (def: .public (array/* values)
(-> (List Expression) Literal)
(|> values
(list\map ..code)
@@ -313,11 +315,11 @@
(format "array")
:abstraction))
- (def: #export (array_merge/+ required optionals)
+ (def: .public (array_merge/+ required optionals)
(-> Expression (List Expression) Computation)
(..apply/* (list& required optionals) (..constant "array_merge")))
- (def: #export (array/** kvs)
+ (def: .public (array/** kvs)
(-> (List [Expression Expression]) Literal)
(|> kvs
(list\map (function (_ [key value])
@@ -327,32 +329,32 @@
(format "array")
:abstraction))
- (def: #export (new constructor inputs)
+ (def: .public (new constructor inputs)
(-> Constant (List Expression) Computation)
(|> (format "new " (:representation constructor) (arguments inputs))
:abstraction))
- (def: #export (the field object)
+ (def: .public (the field object)
(-> Text Expression Computation)
(|> (format (:representation object) "->" field)
:abstraction))
- (def: #export (do method inputs object)
+ (def: .public (do method inputs object)
(-> Text (List Expression) Expression Computation)
(|> (format (:representation (..the method object))
(..arguments inputs))
:abstraction))
- (def: #export (item idx array)
+ (def: .public (item idx array)
(-> Expression Expression Access)
(|> (format (:representation array) "[" (:representation idx) "]")
:abstraction))
- (def: #export (global name)
+ (def: .public (global name)
(-> Text Global)
(|> (..var "GLOBALS") (..item (..string name)) :transmutation))
- (def: #export (? test then else)
+ (def: .public (? test then else)
(-> Expression Expression Expression Computation)
(|> (format (..group (:representation test)) " ? "
(..group (:representation then)) " : "
@@ -361,7 +363,7 @@
:abstraction))
(template [<name> <op>]
- [(def: #export (<name> parameter subject)
+ [(def: .public (<name> parameter subject)
(-> Expression Expression Computation)
(|> (format (:representation subject) " " <op> " " (:representation parameter))
..group
@@ -389,7 +391,7 @@
)
(template [<unary> <name>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Computation Computation)
(|>> :representation (format <unary>) :abstraction))]
@@ -398,22 +400,22 @@
["-" opposite]
)
- (def: #export (set var value)
+ (def: .public (set var value)
(-> Location Expression Computation)
(|> (format (:representation var) " = " (:representation value))
..group
:abstraction))
- (def: #export (set! var value)
+ (def: .public (set! var value)
(-> Location Expression Statement)
(:abstraction (format (:representation var) " = " (:representation value) ";")))
- (def: #export (set? var)
+ (def: .public (set? var)
(-> Var Computation)
(..apply/1 [var] (..constant "isset")))
(template [<name> <modifier>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Var Statement)
(|>> :representation (format <modifier> " ") (text.suffix ..statement_suffix) :abstraction))]
@@ -421,7 +423,7 @@
)
(template [<name> <modifier> <location>]
- [(def: #export (<name> location value)
+ [(def: .public (<name> location value)
(-> <location> Expression Statement)
(:abstraction (format <modifier> " " (:representation location)
" = " (:representation value)
@@ -431,7 +433,7 @@
[define_constant "const" Constant]
)
- (def: #export (if test then! else!)
+ (def: .public (if test then! else!)
(-> Expression Statement Statement Statement)
(:abstraction
(format "if" (..group (:representation test)) " "
@@ -439,40 +441,40 @@
" else "
(..block (:representation else!)))))
- (def: #export (when test then!)
+ (def: .public (when test then!)
(-> Expression Statement Statement)
(:abstraction
(format "if" (..group (:representation test)) " "
(..block (:representation then!)))))
- (def: #export (then pre! post!)
+ (def: .public (then pre! post!)
(-> Statement Statement Statement)
(:abstraction
(format (:representation pre!)
text.new_line
(:representation post!))))
- (def: #export (while test body!)
+ (def: .public (while test body!)
(-> Expression Statement Statement)
(:abstraction
(format "while" (..group (:representation test)) " "
(..block (:representation body!)))))
- (def: #export (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: #export (for_each array value body!)
+ (def: .public (for_each array value body!)
(-> Expression Var Statement Statement)
(:abstraction
(format "foreach(" (:representation array)
" as " (:representation value)
") " (..block (:representation body!)))))
- (type: #export Except
+ (type: .public Except
{#class Constant
#exception Var
#handler Statement})
@@ -484,7 +486,7 @@
(format "catch" (..group declaration) " "
(..block (:representation (get@ #handler except))))))
- (def: #export (try body! excepts)
+ (def: .public (try body! excepts)
(-> Statement (List Except) Statement)
(:abstraction
(format "try " (..block (:representation body!))
@@ -494,7 +496,7 @@
(text.join_with text.new_line)))))
(template [<name> <keyword>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Expression Statement)
(|>> :representation (format <keyword> " ") (text.suffix ..statement_suffix) :abstraction))]
@@ -503,13 +505,13 @@
[echo "echo"]
)
- (def: #export (define name value)
+ (def: .public (define name value)
(-> Constant Expression Expression)
(..apply/2 (..constant "define")
[(|> name :representation ..string)
value]))
- (def: #export (define_function name arguments body!)
+ (def: .public (define_function name arguments body!)
(-> Constant (List Argument) Statement Statement)
(:abstraction
(format "function " (:representation name)
@@ -518,7 +520,7 @@
(..block (:representation body!)))))
(template [<name> <keyword>]
- [(def: #export <name>
+ [(def: .public <name>
Statement
(|> <keyword>
(text.suffix ..statement_suffix)
@@ -528,18 +530,18 @@
[continue "continue"]
)
- (def: #export splat
+ (def: .public splat
(-> Expression Expression)
(|>> :representation (format "...") :abstraction))
)
-(def: #export (cond clauses else!)
+(def: .public (cond clauses else!)
(-> (List [Expression Statement]) Statement Statement)
(list\fold (function (_ [test then!] next!)
(..if test then! next!))
else!
(list.reversed clauses)))
-(def: #export 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 d507ba886..55d0eecea 100644
--- a/stdlib/source/library/lux/target/python.lux
+++ b/stdlib/source/library/lux/target/python.lux
@@ -47,33 +47,35 @@
(|>> (format text.new_line)
(text.replace_all text.new_line nested_new_line)))))
-(abstract: #export (Code brand)
+(abstract: .public (Code brand)
+ {}
+
Text
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [brand] (Equivalence (Code brand)))
(def: (= reference subject)
(\ text.equivalence = (:representation reference) (:representation subject))))
- (implementation: #export hash
+ (implementation: .public hash
(All [brand] (Hash (Code brand)))
(def: &equivalence ..equivalence)
(def: hash (|>> :representation (\ text.hash hash))))
- (def: #export manual
+ (def: .public manual
(-> Text Code)
(|>> :abstraction))
- (def: #export code
+ (def: .public code
(-> (Code Any) Text)
(|>> :representation))
(template [<type> <super>]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (`` (abstract: #export (<brand> brand) Any))
- (`` (type: #export (<type> brand)
+ (`` (abstract: .public (<brand> brand) {} Any))
+ (`` (type: .public (<type> brand)
(<super> (<brand> brand)))))]
[Expression Code]
@@ -85,8 +87,8 @@
(template [<type> <super>]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (`` (abstract: #export <brand> Any))
- (`` (type: #export <type> (<super> <brand>))))]
+ (`` (abstract: .public <brand> {} Any))
+ (`` (type: .public <type> (<super> <brand>))))]
[Literal Computation]
[Access Location]
@@ -95,21 +97,21 @@
)
(template [<var> <brand>]
- [(abstract: #export <brand> Any)
+ [(abstract: .public <brand> {} Any)
- (type: #export <var> (Var <brand>))]
+ (type: .public <var> (Var <brand>))]
[SVar Single]
[PVar Poly]
[KVar Keyword]
)
- (def: #export var
+ (def: .public var
(-> Text SVar)
(|>> :abstraction))
(template [<name> <brand> <prefix>]
- [(def: #export <name>
+ [(def: .public <name>
(-> SVar (Var <brand>))
(|>> :representation (format <prefix>) :abstraction))]
@@ -117,25 +119,25 @@
[keyword Keyword "**"]
)
- (def: #export none
+ (def: .public none
Literal
(:abstraction "None"))
- (def: #export bool
+ (def: .public bool
(-> Bit Literal)
(|>> (case> #0 "False"
#1 "True")
:abstraction))
- (def: #export int
+ (def: .public int
(-> Int Literal)
(|>> %.int :abstraction))
- (def: #export (long value)
+ (def: .public (long value)
(-> Int Literal)
(:abstraction (format (%.int value) "L")))
- (def: #export float
+ (def: .public float
(-> Frac Literal)
(`` (|>> (cond> (~~ (template [<test> <python>]
[[<test>]
@@ -167,13 +169,13 @@
))
)))
- (def: #export string
+ (def: .public string
(-> Text Literal)
(|>> ..safe
(text.enclosed [text.double_quote text.double_quote])
:abstraction))
- (def: #export unicode
+ (def: .public unicode
(-> Text Literal)
(|>> ..string
:representation
@@ -194,7 +196,7 @@
right_delimiter))))
(template [<name> <pre> <post>]
- [(def: #export <name>
+ [(def: .public <name>
(-> (List (Expression Any)) Literal)
(composite_literal <pre> <post> ..code))]
@@ -202,23 +204,23 @@
[list "[" "]"]
)
- (def: #export (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: #export (slice_from from list)
+ (def: .public (slice_from from list)
(-> (Expression Any) (Expression Any) Access)
(<| :abstraction
## ..expression
(format (:representation list) "[" (:representation from) ":]")))
- (def: #export dict
+ (def: .public dict
(-> (List [(Expression Any) (Expression Any)]) (Computation Any))
(composite_literal "{" "}" (.function (_ [k v]) (format (:representation k) " : " (:representation v)))))
- (def: #export (apply/* func args)
+ (def: .public (apply/* func args)
(-> (Expression Any) (List (Expression Any)) (Computation Any))
(<| :abstraction
## ..expression
@@ -234,7 +236,7 @@
)
(template [<name> <splat>]
- [(def: #export (<name> args extra func)
+ [(def: .public (<name> args extra func)
(-> (List (Expression Any)) (Expression Any) (Expression Any) (Computation Any))
(<| :abstraction
## ..expression
@@ -248,16 +250,16 @@
[apply_keyword splat_keyword]
)
- (def: #export (the name object)
+ (def: .public (the name object)
(-> Text (Expression Any) (Computation Any))
(:abstraction (format (:representation object) "." name)))
- (def: #export (do method args object)
+ (def: .public (do method args object)
(-> Text (List (Expression Any)) (Expression Any) (Computation Any))
(..apply/* (..the method object) args))
(template [<name> <apply>]
- [(def: #export (<name> args extra method)
+ [(def: .public (<name> args extra method)
(-> (List (Expression Any)) (Expression Any) Text
(-> (Expression Any) (Computation Any)))
(|>> (..the method) (<apply> args extra)))]
@@ -266,18 +268,18 @@
[do_keyword apply_keyword]
)
- (def: #export (nth idx array)
+ (def: .public (nth idx array)
(-> (Expression Any) (Expression Any) Location)
(:abstraction (format (:representation array) "[" (:representation idx) "]")))
- (def: #export (? 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))))
(template [<name> <op>]
- [(def: #export (<name> param subject)
+ [(def: .public (<name> param subject)
(-> (Expression Any) (Expression Any) (Computation Any))
(<| :abstraction
..expression
@@ -307,7 +309,7 @@
)
(template [<name> <unary>]
- [(def: #export (<name> subject)
+ [(def: .public (<name> subject)
(-> (Expression Any) (Computation Any))
(<| :abstraction
## ..expression
@@ -317,25 +319,25 @@
[opposite "-"]
)
- (def: #export (lambda arguments body)
+ (def: .public (lambda arguments body)
(-> (List (Var Any)) (Expression Any) (Computation Any))
(<| :abstraction
..expression
(format "lambda " (|> arguments (list\map ..code) (text.join_with ", ")) ": "
(:representation body))))
- (def: #export (set vars value)
+ (def: .public (set vars value)
(-> (List (Location Any)) (Expression Any) (Statement Any))
(:abstraction
(format (|> vars (list\map ..code) (text.join_with ", "))
" = "
(:representation value))))
- (def: #export (delete where)
+ (def: .public (delete where)
(-> (Location Any) (Statement Any))
(:abstraction (format "del " (:representation where))))
- (def: #export (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 +345,13 @@
text.new_line "else:"
(..nested (:representation else!)))))
- (def: #export (when test then!)
+ (def: .public (when test then!)
(-> (Expression Any) (Statement Any) (Statement Any))
(:abstraction
(format "if " (:representation test) ":"
(..nested (:representation then!)))))
- (def: #export (then pre! post!)
+ (def: .public (then pre! post!)
(-> (Statement Any) (Statement Any) (Statement Any))
(:abstraction
(format (:representation pre!)
@@ -357,7 +359,7 @@
(:representation post!))))
(template [<keyword> <0>]
- [(def: #export <0>
+ [(def: .public <0>
(Statement Any)
(:abstraction <keyword>))]
@@ -365,7 +367,7 @@
["continue" continue]
)
- (def: #export (while test body! else!)
+ (def: .public (while test body! else!)
(-> (Expression Any) (Statement Any) (Maybe (Statement Any)) Loop)
(:abstraction
(format "while " (:representation test) ":"
@@ -378,26 +380,26 @@
#.None
""))))
- (def: #export (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: #export statement
+ (def: .public statement
(-> (Expression Any) (Statement Any))
(|>> :transmutation))
- (def: #export pass
+ (def: .public pass
(Statement Any)
(:abstraction "pass"))
- (type: #export Except
+ (type: .public Except
{#classes (List SVar)
#exception SVar
#handler (Statement Any)})
- (def: #export (try body! excepts)
+ (def: .public (try body! excepts)
(-> (Statement Any) (List Except) (Statement Any))
(:abstraction
(format "try:"
@@ -410,7 +412,7 @@
(text.join_with "")))))
(template [<name> <keyword> <pre>]
- [(def: #export (<name> value)
+ [(def: .public (<name> value)
(-> (Expression Any) (Statement Any))
(:abstraction
(format <keyword> (<pre> (:representation value)))))]
@@ -420,7 +422,7 @@
[print "print" ..expression]
)
- (def: #export (exec code globals)
+ (def: .public (exec code globals)
(-> (Expression Any) (Maybe (Expression Any)) (Statement Any))
(let [extra (case globals
(#.Some globals)
@@ -431,24 +433,24 @@
(:abstraction
(format "exec" (:representation (..tuple (list& code extra)))))))
- (def: #export (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)
"(" (|> args (list\map ..code) (text.join_with ", ")) "):"
(..nested (:representation body)))))
- (def: #export (import module_name)
+ (def: .public (import module_name)
(-> Text (Statement Any))
(:abstraction (format "import " module_name)))
- (def: #export (comment commentary on)
+ (def: .public (comment commentary on)
(All [brand] (-> Text (Code brand) (Code brand)))
(:abstraction (format "# " (..safe commentary) text.new_line
(:representation on))))
)
-(def: #export (cond clauses else!)
+(def: .public (cond clauses else!)
(-> (List [(Expression Any) (Statement Any)]) (Statement Any) (Statement Any))
(list\fold (.function (_ [test then!] next!)
(..if test then! next!))
@@ -470,12 +472,12 @@
<inputs> (arity_inputs <arity>)
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
- (def: #export (<apply> function <inputs>)
+ (def: .public (<apply> function <inputs>)
(-> (Expression Any) <types> (Computation Any))
(..apply/* function (.list <inputs>)))
(template [<function>]
- [(`` (def: #export (~~ (template.identifier [<function> "/" <arity>]))
+ [(`` (def: .public (~~ (template.identifier [<function> "/" <arity>]))
(<apply> (..var <function>))))]
<definitions>))]
diff --git a/stdlib/source/library/lux/target/r.lux b/stdlib/source/library/lux/target/r.lux
index 20aeb8d4b..3b6601179 100644
--- a/stdlib/source/library/lux/target/r.lux
+++ b/stdlib/source/library/lux/target/r.lux
@@ -22,48 +22,48 @@
[type
abstract]]])
-(abstract: #export (Code kind)
+(abstract: .public (Code kind)
Text
{}
(template [<type> <super>+]
[(with_expansions [<kind> (template.identifier [<type> "'"])]
- (abstract: #export (<kind> kind) Any)
- (`` (type: #export <type> (|> Any <kind> (~~ (template.spliced <super>+))))))]
+ (abstract: .public (<kind> kind) Any)
+ (`` (type: .public <type> (|> Any <kind> (~~ (template.spliced <super>+))))))]
[Expression [Code]]
)
(template [<type> <super>+]
[(with_expansions [<kind> (template.identifier [<type> "'"])]
- (abstract: #export (<kind> kind) Any)
- (`` (type: #export (<type> <brand>) (|> <brand> <kind> (~~ (template.spliced <super>+))))))]
+ (abstract: .public (<kind> kind) Any)
+ (`` (type: .public (<type> <brand>) (|> <brand> <kind> (~~ (template.spliced <super>+))))))]
[Var [Expression' Code]]
)
(template [<var> <kind>]
- [(abstract: #export <kind> Any)
- (type: #export <var> (Var <kind>))]
+ [(abstract: .public <kind> Any)
+ (type: .public <var> (Var <kind>))]
[SVar Single]
[PVar Poly]
)
- (def: #export var
+ (def: .public var
(-> Text SVar)
(|>> :abstraction))
- (def: #export var_args
+ (def: .public var_args
PVar
(:abstraction "..."))
- (def: #export manual
+ (def: .public manual
(-> Text Code)
(|>> :abstraction))
- (def: #export code
+ (def: .public code
(-> (Code Any) Text)
(|>> :representation))
@@ -84,7 +84,7 @@
(-> Text Text)
(format "{" (nested expression) text.new_line "}"))
- (def: #export (block expression)
+ (def: .public (block expression)
(-> Expression Expression)
(:abstraction
(format "{"
@@ -92,7 +92,7 @@
text.new_line "}")))
(template [<name> <r>]
- [(def: #export <name>
+ [(def: .public <name>
Expression
(:abstraction <r>))]
@@ -101,24 +101,24 @@
)
(template [<name>]
- [(def: #export <name> Expression n/a)]
+ [(def: .public <name> Expression n/a)]
[not_available]
[not_applicable]
[no_answer]
)
- (def: #export bool
+ (def: .public bool
(-> Bit Expression)
(|>> (case> #0 "FALSE"
#1 "TRUE")
:abstraction))
- (def: #export int
+ (def: .public int
(-> Int Expression)
(|>> %.int :abstraction))
- (def: #export float
+ (def: .public float
(-> Frac Expression)
(|>> (cond> [(f.= f.positive_infinity)]
[(new> "1.0/0.0" [])]
@@ -149,23 +149,23 @@
))
)))
- (def: #export string
+ (def: .public string
(-> Text Expression)
(|>> ..safe %.text :abstraction))
- (def: #export (slice from to list)
+ (def: .public (slice from to list)
(-> Expression Expression Expression Expression)
(..self_contained
(format (:representation list)
"[" (:representation from) ":" (:representation to) "]")))
- (def: #export (slice_from from list)
+ (def: .public (slice_from from list)
(-> Expression Expression Expression)
(..self_contained
(format (:representation list)
"[-1" ":-" (:representation from) "]")))
- (def: #export (apply args func)
+ (def: .public (apply args func)
(-> (List Expression) Expression Expression)
(let [func (:representation func)
spacing (|> " " (list.repeat (text.size func)) (text.join_with ""))]
@@ -178,7 +178,7 @@
")"))))
(template [<name> <function>]
- [(def: #export (<name> members)
+ [(def: .public (<name> members)
(-> (List Expression) Expression)
(..apply members (..var <function>)))]
@@ -186,13 +186,13 @@
[list "list"]
)
- (def: #export named_list
+ (def: .public named_list
(-> (List [Text Expression]) Expression)
(|>> (list\map (.function (_ [key value])
(:abstraction (format key "=" (:representation value)))))
..list))
- (def: #export (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)
@@ -218,12 +218,12 @@
<inputs> (arity_inputs <arity>)
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
- (def: #export (<apply> function [<inputs>])
+ (def: .public (<apply> function [<inputs>])
(-> Expression [<types>] Expression)
(..apply (.list <inputs>) function))
(template [<function>]
- [(`` (def: #export (~~ (template.identifier [<function> "/" <arity>]))
+ [(`` (def: .public (~~ (template.identifier [<function> "/" <arity>]))
(-> [<types>] Expression)
(<apply> (..var <function>))))]
@@ -237,30 +237,30 @@
[["paste"]]]
)
- (def: #export as::integer
+ (def: .public as::integer
(-> Expression Expression)
(..apply/1 (..var "as.integer")))
- (def: #export (item idx list)
+ (def: .public (item idx list)
(-> Expression Expression Expression)
(..self_contained
(format (:representation list) "[[" (:representation idx) "]]")))
- (def: #export (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: #export (when test then)
+ (def: .public (when test then)
(-> Expression Expression Expression)
(:abstraction
(format "if(" (:representation test) ") {"
(.._block (:representation then))
text.new_line "}")))
- (def: #export (cond clauses else)
+ (def: .public (cond clauses else)
(-> (List [Expression Expression]) Expression Expression)
(list\fold (.function (_ [test then] next)
(if test then next))
@@ -268,7 +268,7 @@
(list.reversed clauses)))
(template [<name> <op>]
- [(def: #export (<name> param subject)
+ [(def: .public (<name> param subject)
(-> Expression Expression Expression)
(..self_contained
(format (:representation subject)
@@ -291,7 +291,7 @@
)
(template [<name> <func>]
- [(def: #export (<name> param subject)
+ [(def: .public (<name> param subject)
(-> Expression Expression Expression)
(..apply (.list subject param) (..var <func>)))]
@@ -302,12 +302,12 @@
[bit_ushr "bitwShiftR"]
)
- (def: #export (bit_not subject)
+ (def: .public (bit_not subject)
(-> Expression Expression)
(..apply (.list subject) (..var "bitwNot")))
(template [<name> <op>]
- [(def: #export <name>
+ [(def: .public <name>
(-> Expression Expression)
(|>> :representation (format <op>) ..self_contained))]
@@ -315,23 +315,23 @@
[negate "-"]
)
- (def: #export (length list)
+ (def: .public (length list)
(-> Expression Expression)
(..apply (.list list) (..var "length")))
- (def: #export (range from to)
+ (def: .public (range from to)
(-> Expression Expression Expression)
(..self_contained
(format (:representation from) ":" (:representation to))))
- (def: #export (function inputs body)
+ (def: .public (function inputs body)
(-> (List (Ex [k] (Var k))) Expression Expression)
(let [args (|> inputs (list\map ..code) (text.join_with ", "))]
(..self_contained
(format "function(" args ") "
(.._block (:representation body))))))
- (def: #export (try body warning error finally)
+ (def: .public (try body warning error finally)
(-> Expression (Maybe Expression) (Maybe Expression) (Maybe Expression) Expression)
(let [optional (: (-> Text (Maybe Expression) (-> Text Text) Text)
(.function (_ parameter value preparation)
@@ -346,20 +346,20 @@
(optional "finally" finally .._block)
")"))))
- (def: #export (while test body)
+ (def: .public (while test body)
(-> Expression Expression Expression)
(..self_contained
(format "while (" (:representation test) ") "
(.._block (:representation body)))))
- (def: #export (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)))))
(template [<name> <keyword>]
- [(def: #export (<name> message)
+ [(def: .public (<name> message)
(-> Expression Expression)
(..apply (.list message) (..var <keyword>)))]
@@ -367,17 +367,17 @@
[print "print"]
)
- (def: #export (set! var value)
+ (def: .public (set! var value)
(-> SVar Expression Expression)
(..self_contained
(format (:representation var) " <- " (:representation value))))
- (def: #export (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: #export (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 43f2c0243..fc08c16fa 100644
--- a/stdlib/source/library/lux/target/ruby.lux
+++ b/stdlib/source/library/lux/target/ruby.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux (#- Location Code static int if cond function or and not comment)
+ [lux (#- Location Code static int if cond function or and not comment local global)
["@" target]
[abstract
[equivalence (#+ Equivalence)]
@@ -35,33 +35,35 @@
(|>> (format text.new_line)
(text.replace_all text.new_line nested_new_line))))
-(abstract: #export (Code brand)
+(abstract: .public (Code brand)
+ {}
+
Text
- (implementation: #export code_equivalence
+ (implementation: .public code_equivalence
(All [brand] (Equivalence (Code brand)))
(def: (= reference subject)
(\ text.equivalence = (:representation reference) (:representation subject))))
- (implementation: #export code_hash
+ (implementation: .public code_hash
(All [brand] (Hash (Code brand)))
(def: &equivalence ..code_equivalence)
(def: hash (|>> :representation (\ text.hash hash))))
- (def: #export manual
+ (def: .public manual
(-> Text Code)
(|>> :abstraction))
- (def: #export code
+ (def: .public code
(-> (Code Any) Text)
(|>> :representation))
(template [<type> <super>+]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (abstract: (<brand> brand) Any)
- (`` (type: #export <type> (|> Any <brand> (~~ (template.spliced <super>+))))))]
+ (abstract: (<brand> brand) {} Any)
+ (`` (type: .public <type> (|> Any <brand> (~~ (template.spliced <super>+))))))]
[Expression [Code]]
[Computation [Expression' Code]]
@@ -73,8 +75,8 @@
(template [<type> <super>+]
[(with_expansions [<brand> (template.identifier [<type> "'"])]
- (abstract: #export <brand> Any)
- (`` (type: #export <type> (|> <brand> (~~ (template.spliced <super>+))))))]
+ (abstract: .public <brand> {} Any)
+ (`` (type: .public <type> (|> <brand> (~~ (template.spliced <super>+))))))]
[Literal [Computation' Expression' Code]]
[Access [Location' Computation' Expression' Code]]
@@ -86,7 +88,7 @@
)
(template [<var> <prefix> <constructor>]
- [(def: #export <constructor>
+ [(def: .public <constructor>
(-> Text <var>)
(|>> (format <prefix>) :abstraction))]
@@ -95,13 +97,13 @@
[SVar "@@" static]
)
- (def: #export local
+ (def: .public local
(-> Text LVar)
(|>> :abstraction))
(template [<var> <prefix> <modifier> <unpacker>]
[(template [<name> <input> <output>]
- [(def: #export <name>
+ [(def: .public <name>
(-> <input> <output>)
(|>> :representation (format <prefix>) :abstraction))]
@@ -114,7 +116,7 @@
)
(template [<ruby_name> <lux_name>]
- [(def: #export <lux_name>
+ [(def: .public <lux_name>
(..global <ruby_name>))]
["@" latest_error]
@@ -131,17 +133,17 @@
)
(template [<ruby_name> <lux_name>]
- [(def: #export <lux_name>
+ [(def: .public <lux_name>
(..local <ruby_name>))]
["ARGV" command_line_arguments]
)
- (def: #export nil
+ (def: .public nil
Literal
(:abstraction "nil"))
- (def: #export bool
+ (def: .public bool
(-> Bit Literal)
(|>> (case> #0 "false"
#1 "true")
@@ -165,7 +167,7 @@
)))
(template [<format> <name> <type> <prep>]
- [(def: #export <name>
+ [(def: .public <name>
(-> <type> Literal)
(|>> <prep> <format> :abstraction))]
@@ -174,7 +176,7 @@
[(<|) symbol Text (format ":")]
)
- (def: #export float
+ (def: .public float
(-> Frac Literal)
(|>> (cond> [(f.= f.positive_infinity)]
[(new> "(+1.0/0.0)" [])]
@@ -189,21 +191,21 @@
[%.frac])
:abstraction))
- (def: #export (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: #export array
+ (def: .public array
(-> (List Expression) Literal)
(|>> (list\map (|>> :representation))
(text.join_with ..input_separator)
(text.enclosed ["[" "]"])
:abstraction))
- (def: #export hash
+ (def: .public hash
(-> (List [Expression Expression]) Literal)
(|>> (list\map (.function (_ [k v])
(format (:representation k) " => " (:representation v))))
@@ -211,7 +213,7 @@
(text.enclosed ["{" "}"])
:abstraction))
- (def: #export (apply/* args func)
+ (def: .public (apply/* args func)
(-> (List Expression) Expression Computation)
(|> args
(list\map (|>> :representation))
@@ -220,7 +222,7 @@
(format (:representation func))
:abstraction))
- (def: #export (apply_lambda/* args lambda)
+ (def: .public (apply_lambda/* args lambda)
(-> (List Expression) Expression Computation)
(|> args
(list\map (|>> :representation))
@@ -229,18 +231,18 @@
(format (:representation lambda))
:abstraction))
- (def: #export (the field object)
+ (def: .public (the field object)
(-> Text Expression Access)
(:abstraction (format (:representation object) "." field)))
- (def: #export (nth idx array)
+ (def: .public (nth idx array)
(-> Expression Expression Access)
(|> (:representation idx)
(text.enclosed ["[" "]"])
(format (:representation array))
:abstraction))
- (def: #export (? test then else)
+ (def: .public (? test then else)
(-> Expression Expression Expression Computation)
(|> (format (:representation test) " ? "
(:representation then) " : "
@@ -248,20 +250,20 @@
(text.enclosed ["(" ")"])
:abstraction))
- (def: #export statement
+ (def: .public statement
(-> Expression Statement)
(|>> :representation
(text.suffix ..statement_suffix)
:abstraction))
- (def: #export (then pre! post!)
+ (def: .public (then pre! post!)
(-> Statement Statement Statement)
(:abstraction
(format (:representation pre!)
text.new_line
(:representation post!))))
- (def: #export (set vars value)
+ (def: .public (set vars value)
(-> (List Location) Expression Statement)
(:abstraction
(format (|> vars
@@ -274,7 +276,7 @@
(format content
text.new_line "end" ..statement_suffix))
- (def: #export (if test then! else!)
+ (def: .public (if test then! else!)
(-> Expression Statement Statement Statement)
(<| :abstraction
..block
@@ -284,7 +286,7 @@
(..nested (:representation else!)))))
(template [<name> <block>]
- [(def: #export (<name> test then!)
+ [(def: .public (<name> test then!)
(-> Expression Statement Statement)
(<| :abstraction
..block
@@ -295,7 +297,7 @@
[while "while"]
)
- (def: #export (for_in var array iteration!)
+ (def: .public (for_in var array iteration!)
(-> LVar Expression Statement Statement)
(<| :abstraction
..block
@@ -304,12 +306,12 @@
" do "
(..nested (:representation iteration!)))))
- (type: #export Rescue
+ (type: .public Rescue
{#classes (List Text)
#exception LVar
#rescue Statement})
- (def: #export (begin body! rescues)
+ (def: .public (begin body! rescues)
(-> Statement (List Rescue) Statement)
(<| :abstraction
..block
@@ -321,23 +323,23 @@
(..nested (:representation rescue)))))
(text.join_with text.new_line)))))
- (def: #export (catch expectation body!)
+ (def: .public (catch expectation body!)
(-> Expression Statement Statement)
(<| :abstraction
..block
(format "catch(" (:representation expectation) ") do"
(..nested (:representation body!)))))
- (def: #export (return value)
+ (def: .public (return value)
(-> Expression Statement)
(:abstraction (format "return " (:representation value) ..statement_suffix)))
- (def: #export (raise message)
+ (def: .public (raise message)
(-> Expression Computation)
(:abstraction (format "raise " (:representation message))))
(template [<name> <keyword>]
- [(def: #export <name>
+ [(def: .public <name>
Statement
(|> <keyword>
(text.suffix ..statement_suffix)
@@ -348,7 +350,7 @@
[break "break"]
)
- (def: #export (function name args body!)
+ (def: .public (function name args body!)
(-> LVar (List LVar) Statement Statement)
(<| :abstraction
..block
@@ -359,7 +361,7 @@
(text.enclosed ["(" ")"]))
(..nested (:representation body!)))))
- (def: #export (lambda name args body!)
+ (def: .public (lambda name args body!)
(-> (Maybe LVar) (List Var) Statement Literal)
(let [proc (|> (format (|> args
(list\map (|>> :representation))
@@ -378,7 +380,7 @@
:abstraction)))
(template [<op> <name>]
- [(def: #export (<name> parameter subject)
+ [(def: .public (<name> parameter subject)
(-> Expression Expression Computation)
(:abstraction (format "(" (:representation subject) " " <op> " " (:representation parameter) ")")))]
@@ -406,7 +408,7 @@
)
(template [<unary> <name>]
- [(def: #export (<name> subject)
+ [(def: .public (<name> subject)
(-> Expression Computation)
(:abstraction (format "(" <unary> (:representation subject) ")")))]
@@ -414,17 +416,17 @@
["-" opposite]
)
- (def: #export (comment commentary on)
+ (def: .public (comment commentary on)
(All [brand] (-> Text (Code brand) (Code brand)))
(:abstraction (format "# " (..safe commentary) text.new_line
(:representation on))))
)
-(def: #export (do method args object)
+(def: .public (do method args object)
(-> Text (List Expression) Expression Computation)
(|> object (..the method) (..apply/* args)))
-(def: #export (cond clauses else!)
+(def: .public (cond clauses else!)
(-> (List [Expression Statement]) Statement Statement)
(list\fold (.function (_ [test then!] next!)
(..if test then! next!))
@@ -446,12 +448,12 @@
<inputs> (arity_inputs <arity>)
<types> (arity_types <arity>)
<definitions> (template.spliced <function>+)]
- (def: #export (<apply> function <inputs>)
+ (def: .public (<apply> function <inputs>)
(-> Expression <types> Computation)
(..apply/* (.list <inputs>) function))
(template [<function>]
- [(`` (def: #export (~~ (template.identifier [<function> "/" <arity>]))
+ [(`` (def: .public (~~ (template.identifier [<function> "/" <arity>]))
(<apply> (..local <function>))))]
<definitions>))]
@@ -467,7 +469,7 @@
[["print"]]]
)
-(def: #export throw/1
+(def: .public throw/1
(-> Expression Statement)
(|>> (..apply/1 (..local "throw"))
..statement))
diff --git a/stdlib/source/library/lux/target/scheme.lux b/stdlib/source/library/lux/target/scheme.lux
index fc60d76f7..011f681f9 100644
--- a/stdlib/source/library/lux/target/scheme.lux
+++ b/stdlib/source/library/lux/target/scheme.lux
@@ -26,49 +26,51 @@
(.let [nested_new_line (format text.new_line text.tab)]
(text.replace_all text.new_line nested_new_line)))
-(abstract: #export (Code k)
+(abstract: .public (Code k)
+ {}
+
Text
- (implementation: #export equivalence
+ (implementation: .public equivalence
(All [brand] (Equivalence (Code brand)))
(def: (= reference subject)
(\ text.equivalence = (:representation reference) (:representation subject))))
- (implementation: #export hash
+ (implementation: .public hash
(All [brand] (Hash (Code brand)))
(def: &equivalence ..equivalence)
(def: hash (|>> :representation (\ text.hash hash))))
(template [<type> <brand> <super>+]
- [(abstract: #export (<brand> brand) Any)
- (`` (type: #export <type> (|> Any <brand> (~~ (template.spliced <super>+)))))]
+ [(abstract: .public (<brand> brand) {} Any)
+ (`` (type: .public <type> (|> Any <brand> (~~ (template.spliced <super>+)))))]
[Expression Expression' [Code]]
)
(template [<type> <brand> <super>+]
- [(abstract: #export <brand> Any)
- (`` (type: #export <type> (|> <brand> (~~ (template.spliced <super>+)))))]
+ [(abstract: .public <brand> {} Any)
+ (`` (type: .public <type> (|> <brand> (~~ (template.spliced <super>+)))))]
[Var Var' [Expression' Code]]
[Computation Computation' [Expression' Code]]
)
- (type: #export Arguments
+ (type: .public Arguments
{#mandatory (List Var)
#rest (Maybe Var)})
- (def: #export manual
+ (def: .public manual
(-> Text Code)
(|>> :abstraction))
- (def: #export code
+ (def: .public code
(-> (Code Any) Text)
(|>> :representation))
- (def: #export var
+ (def: .public var
(-> Text Var)
(|>> :abstraction))
@@ -95,21 +97,21 @@
(text.enclosed ["(" ")"])
:abstraction)))
- (def: #export nil
+ (def: .public nil
Computation
(:abstraction "'()"))
- (def: #export bool
+ (def: .public bool
(-> Bit Computation)
(|>> (case> #0 "#f"
#1 "#t")
:abstraction))
- (def: #export int
+ (def: .public int
(-> Int Computation)
(|>> %.int :abstraction))
- (def: #export float
+ (def: .public float
(-> Frac Computation)
(|>> (cond> [(f.= f.positive_infinity)]
[(new> "+inf.0" [])]
@@ -124,9 +126,9 @@
[%.frac])
:abstraction))
- (def: #export positive_infinity Computation (..float f.positive_infinity))
- (def: #export negative_infinity Computation (..float f.negative_infinity))
- (def: #export 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
(-> Text Text)
@@ -144,11 +146,11 @@
))
)))
- (def: #export string
+ (def: .public string
(-> Text Computation)
(|>> ..safe %.text :abstraction))
- (def: #export symbol
+ (def: .public symbol
(-> Text Computation)
(|>> (format "'") :abstraction))
@@ -166,12 +168,12 @@
(text.enclosed ["(" ")"])
:abstraction)))))
- (def: #export (apply/* args func)
+ (def: .public (apply/* args func)
(-> (List Expression) Expression Computation)
(..form (#.Item func args)))
(template [<name> <function>]
- [(def: #export (<name> members)
+ [(def: .public (<name> members)
(-> (List Expression) Computation)
(..apply/* members (..var <function>)))]
@@ -179,25 +181,25 @@
[list/* "list"]
)
- (def: #export apply/0
+ (def: .public apply/0
(-> Expression Computation)
(..apply/* (list)))
(template [<lux_name> <scheme_name>]
- [(def: #export <lux_name>
+ [(def: .public <lux_name>
(apply/0 (..var <scheme_name>)))]
[newline/0 "newline"]
)
(template [<apply> <arg>+ <type>+ <function>+]
- [(`` (def: #export (<apply> procedure)
+ [(`` (def: .public (<apply> procedure)
(-> Expression (~~ (template.spliced <type>+)) Computation)
(function (_ (~~ (template.spliced <arg>+)))
(..apply/* (list (~~ (template.spliced <arg>+))) procedure))))
(`` (template [<definition> <function>]
- [(def: #export <definition> (<apply> (..var <function>)))]
+ [(def: .public <definition> (<apply> (..var <function>)))]
(~~ (template.spliced <function>+))))]
@@ -261,12 +263,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: #export (vector_ref/2 vector index)
+ (def: .public (vector_ref/2 vector index)
(-> Expression Expression Computation)
(..form (list (..var "invoke") vector (..symbol "getRaw") index)))
(template [<lux_name> <scheme_name>]
- [(def: #export (<lux_name> param subject)
+ [(def: .public (<lux_name> param subject)
(-> Expression Expression Computation)
(..apply/2 (..var <scheme_name>) subject param))]
@@ -294,7 +296,7 @@
)
(template [<lux_name> <scheme_name>]
- [(def: #export <lux_name>
+ [(def: .public <lux_name>
(-> (List Expression) Computation)
(|>> (list& (..var <scheme_name>)) ..form))]
@@ -303,7 +305,7 @@
)
(template [<lux_name> <scheme_name> <var> <pre>]
- [(def: #export (<lux_name> bindings body)
+ [(def: .public (<lux_name> bindings body)
(-> (List [<var> Expression]) Expression Computation)
(..form (list (..var <scheme_name>)
(|> bindings
@@ -321,21 +323,21 @@
[letrec_values "letrec-values" Arguments ..arguments]
)
- (def: #export (if test then else)
+ (def: .public (if test then else)
(-> Expression Expression Expression Computation)
(..form (list (..var "if") test then else)))
- (def: #export (when test then)
+ (def: .public (when test then)
(-> Expression Expression Computation)
(..form (list (..var "when") test then)))
- (def: #export (lambda arguments body)
+ (def: .public (lambda arguments body)
(-> Arguments Expression Computation)
(..form (list (..var "lambda")
(..arguments arguments)
body)))
- (def: #export (define_function name arguments body)
+ (def: .public (define_function name arguments body)
(-> Var Arguments Expression Computation)
(..form (list (..var "define")
(|> arguments
@@ -343,27 +345,27 @@
..arguments)
body)))
- (def: #export (define_constant name value)
+ (def: .public (define_constant name value)
(-> Var Expression Computation)
(..form (list (..var "define") name value)))
- (def: #export begin
+ (def: .public begin
(-> (List Expression) Computation)
(|>> (#.Item (..var "begin")) ..form))
- (def: #export (set! name value)
+ (def: .public (set! name value)
(-> Var Expression Computation)
(..form (list (..var "set!") name value)))
- (def: #export (with_exception_handler handler body)
+ (def: .public (with_exception_handler handler body)
(-> Expression Expression Computation)
(..form (list (..var "with-exception-handler") handler body)))
- (def: #export (call_with_current_continuation body)
+ (def: .public (call_with_current_continuation body)
(-> Expression Computation)
(..form (list (..var "call-with-current-continuation") body)))
- (def: #export (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