aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool
diff options
context:
space:
mode:
authorEduardo Julian2020-11-28 19:45:56 -0400
committerEduardo Julian2020-11-28 19:45:56 -0400
commita02b7bf8ff358ccfa35b03272d28537aeac723ae (patch)
tree66f27c97f192d31d7cbee6b87be5ac6546640253 /stdlib/source/lux/tool
parent889139602b77e4387a6e8bfbedacc2a08703e976 (diff)
Added "private" macro to lux/debug.
Diffstat (limited to 'stdlib/source/lux/tool')
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/analysis/module.lux12
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux212
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux26
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux2
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux14
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux56
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/synthesis.lux12
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/synthesis.lux68
12 files changed, 212 insertions, 212 deletions
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux
index 6ad18d63d..8c5b74cff 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux
@@ -9,7 +9,7 @@
["." text
["%" format (#+ format)]]
[collection
- ["." list ("#@." fold monoid monad)]]]
+ ["." list ("#\." fold monoid monad)]]]
["." type
["." check]]
["." meta]]
@@ -37,7 +37,7 @@
["Function" (%.code functionC)]
["Arguments" (|> arguments
list.enumeration
- (list@map (.function (_ [idx argC])
+ (list\map (.function (_ [idx argC])
(format (%.nat idx) " " (%.code argC))))
(text.join-with text.new-line))]))
@@ -89,7 +89,7 @@
(#.Function inputT outputT)
(<| (:: ! map (.function (_ [scope bodyA])
- (#/.Function (list@map (|>> /.variable)
+ (#/.Function (list\map (|>> /.variable)
(//scope.environment scope))
bodyA)))
/.with-scope
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/module.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/module.lux
index 8c1ba3644..582e7d860 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/module.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/module.lux
@@ -7,10 +7,10 @@
["." try]
["." exception (#+ exception:)]]
[data
- ["." text ("#@." equivalence)
+ ["." text ("#\." equivalence)
["%" format (#+ format)]]
[collection
- ["." list ("#@." fold functor)]
+ ["." list ("#\." fold functor)]
[dictionary
["." plist]]]]
["." meta]]
@@ -102,7 +102,7 @@
(function (_ state)
(#try.Success [(update@ #.modules
(plist.update self-name (update@ #.imports (function (_ current)
- (if (list.any? (text@= module)
+ (if (list.any? (text\= module)
current)
current
(#.Cons module current)))))
@@ -254,16 +254,16 @@
(/.throw cannot-declare-tags-for-unnamed-type [tags type]))
_ (ensure-undeclared-tags self-name tags)
_ (///.assert cannot-declare-tags-for-foreign-type [tags type]
- (text@= self-name type-module))]
+ (text\= self-name type-module))]
(///extension.lift
(function (_ state)
(case (|> state (get@ #.modules) (plist.get self-name))
(#.Some module)
- (let [namespaced-tags (list@map (|>> [self-name]) tags)]
+ (let [namespaced-tags (list\map (|>> [self-name]) tags)]
(#try.Success [(update@ #.modules
(plist.update self-name
(|>> (update@ #.tags (function (_ tag-bindings)
- (list@fold (function (_ [idx tag] table)
+ (list\fold (function (_ [idx tag] table)
(plist.put tag [idx namespaced-tags exported? type] table))
tag-bindings
(list.enumeration tags))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension.lux
index 3edad4d3b..f121b78ca 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension.lux
@@ -10,10 +10,10 @@
["." exception (#+ exception:)]]
[data
["." product]
- ["." text ("#@." order)
+ ["." text ("#\." order)
["%" format (#+ Format format)]]
[collection
- ["." list ("#@." functor)]
+ ["." list]
["." dictionary (#+ Dictionary)]]]]
[/////
["//" phase]
@@ -75,7 +75,7 @@
["Extension" (%.text name)]
["Available" (|> bundle
dictionary.keys
- (list.sort text@<)
+ (list.sort text\<)
(exception.enumerate %.text))]))
(type: #export (Extender s i o)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
index 618fbbfc9..0fdaa8c96 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -6,7 +6,7 @@
["." monad (#+ do)]]
[control
pipe
- ["." try (#+ Try) ("#@." monad)]
+ ["." try (#+ Try) ("#\." monad)]
["." exception (#+ exception:)]
["<>" parser
["<c>" code (#+ Parser)]
@@ -16,20 +16,20 @@
["." product]
[number
["n" nat]]
- ["." text ("#@." equivalence)
+ ["." text ("#\." equivalence)
["%" format (#+ format)]]
[collection
- ["." list ("#@." fold monad monoid)]
+ ["." list ("#\." fold monad monoid)]
["." array]
["." dictionary (#+ Dictionary)]]]
["." type
- ["." check (#+ Check) ("#@." monad)]]
+ ["." check (#+ Check) ("#\." monad)]]
[target
["." jvm #_
[".!" reflection]
[encoding
[name (#+ External)]]
- ["#" type (#+ Type Argument Typed) ("#@." equivalence)
+ ["#" type (#+ Type Argument Typed) ("#\." equivalence)
["." category (#+ Void Value' Value Return' Return Primitive Object Class Array Var Parameter Method)]
["." box]
["." reflection]
@@ -52,7 +52,7 @@
["#." synthesis]
[///
[reference (#+)]
- ["." phase ("#@." monad)]
+ ["." phase ("#\." monad)]
[meta
[archive (#+ Archive)
[descriptor (#+ Module)]]]]]]]])
@@ -146,7 +146,7 @@
["Class" class]
["Method" method]
["Arguments" (exception.enumerate ..signature inputsJT)]
- ["Hints" (exception.enumerate %.type (list@map product.left hints))]))]
+ ["Hints" (exception.enumerate %.type (list\map product.left hints))]))]
[no-candidates]
[too-many-candidates]
@@ -275,14 +275,14 @@
(/////analysis.throw ..non-jvm-type luxT))
(^ (#.Primitive (static array.type-name) (list elemT)))
- (phase@map jvm.array (jvm-type elemT))
+ (phase\map jvm.array (jvm-type elemT))
(#.Primitive class parametersT)
(case (dictionary.get class ..boxes)
(#.Some [_ primitive-type])
(case parametersT
#.Nil
- (phase@wrap primitive-type)
+ (phase\wrap primitive-type)
_
(/////analysis.throw ..primitives-cannot-have-type-parameters class))
@@ -304,7 +304,7 @@
(wrap (jvm.class class parametersJT))))
(#.Ex _)
- (phase@wrap (jvm.class ..object-class (list)))
+ (phase\wrap (jvm.class ..object-class (list)))
_
(/////analysis.throw ..non-jvm-type luxT)))
@@ -398,7 +398,7 @@
(#.Primitive name parameters)
(`` (cond (or (~~ (template [<type>]
- [(text@= (..reflection <type>) name)]
+ [(text\= (..reflection <type>) name)]
[jvm.boolean]
[jvm.byte]
@@ -412,14 +412,14 @@
(/////analysis.throw ..non-parameter objectT)
## else
- (phase@wrap (jvm.class name (list)))))
+ (phase\wrap (jvm.class name (list)))))
(#.Named name anonymous)
(check-parameter anonymous)
(^template [<tag>]
[(<tag> id)
- (phase@wrap (jvm.class ..object-class (list)))])
+ (phase\wrap (jvm.class ..object-class (list)))])
([#.Var]
[#.Ex])
@@ -445,8 +445,8 @@
(case objectT
(#.Primitive name #.Nil)
(`` (cond (~~ (template [<type>]
- [(text@= (..reflection <type>) name)
- (phase@wrap <type>)]
+ [(text\= (..reflection <type>) name)
+ (phase\wrap <type>)]
[jvm.boolean]
[jvm.byte]
@@ -458,8 +458,8 @@
[jvm.char]))
(~~ (template [<type>]
- [(text@= (..reflection (jvm.array <type>)) name)
- (phase@wrap (jvm.array <type>))]
+ [(text\= (..reflection (jvm.array <type>)) name)
+ (phase\wrap (jvm.array <type>))]
[jvm.boolean]
[jvm.byte]
@@ -476,18 +476,18 @@
(check-jvm (#.Primitive unprefixed (list)))))
## else
- (phase@wrap (jvm.class name (list)))))
+ (phase\wrap (jvm.class name (list)))))
(^ (#.Primitive (static array.type-name)
(list elementT)))
(|> elementT
check-jvm
- (phase@map jvm.array))
+ (phase\map jvm.array))
(#.Primitive name parameters)
(do {! phase.monad}
[parameters (monad.map ! check-parameter parameters)]
- (phase@wrap (jvm.class name parameters)))
+ (phase\wrap (jvm.class name parameters)))
(#.Named name anonymous)
(check-jvm anonymous)
@@ -515,12 +515,12 @@
[name (:: ! map ..reflection (check-jvm objectT))]
(if (dictionary.contains? name ..boxes)
(/////analysis.throw ..primitives-are-not-objects [name])
- (phase@wrap name))))
+ (phase\wrap name))))
(def: (check-return type)
(-> .Type (Operation (Type Return)))
(if (is? .Any type)
- (phase@wrap jvm.void)
+ (phase\wrap jvm.void)
(check-jvm type)))
(def: (read-primitive-array-handler lux-type jvm-type)
@@ -866,11 +866,11 @@
can-cast? (: (Operation Bit)
(`` (cond (~~ (template [<primitive> <object>]
[(let [=primitive (reflection.reflection <primitive>)]
- (or (and (text@= =primitive from-name)
- (or (text@= <object> to-name)
- (text@= =primitive to-name)))
- (and (text@= <object> from-name)
- (text@= =primitive to-name))))
+ (or (and (text\= =primitive from-name)
+ (or (text\= <object> to-name)
+ (text\= =primitive to-name)))
+ (and (text\= <object> from-name)
+ (text\= =primitive to-name))))
(wrap true)]
[reflection.boolean box.boolean]
@@ -889,23 +889,23 @@
_ (phase.assert ..primitives-are-not-objects [to-name]
(not (dictionary.contains? to-name ..boxes)))
to-class (phase.lift (reflection!.load to-name))
- _ (if (text@= ..inheritance-relationship-type-name from-name)
+ _ (if (text\= ..inheritance-relationship-type-name from-name)
(wrap [])
(do !
[from-class (phase.lift (reflection!.load from-name))]
(phase.assert cannot-cast [fromT toT fromC]
(java/lang/Class::isAssignableFrom from-class to-class))))]
(loop [[current-name currentT] [from-name fromT]]
- (if (text@= to-name current-name)
+ (if (text\= to-name current-name)
(wrap true)
(do !
[candidate-parents (: (Operation (List [[Text .Type] Bit]))
- (if (text@= ..inheritance-relationship-type-name current-name)
+ (if (text\= ..inheritance-relationship-type-name current-name)
(inheritance-candidate-parents currentT to-class toT fromC)
(class-candidate-parents current-name currentT to-name to-class)))]
(case (|> candidate-parents
(list.filter product.right)
- (list@map product.left))
+ (list\map product.left))
(#.Cons [next-name nextT] _)
(recur [next-name nextT])
@@ -1035,7 +1035,7 @@
phase.lift)
#let [modifiers (java/lang/reflect/Method::getModifiers method)
correct-class? (java/lang/Object::equals class (java/lang/reflect/Method::getDeclaringClass method))
- correct-method? (text@= method-name (java/lang/reflect/Method::getName method))
+ correct-method? (text\= method-name (java/lang/reflect/Method::getName method))
static-matches? (case method-style
#Static
(java/lang/reflect/Modifier::isStatic modifiers)
@@ -1050,9 +1050,9 @@
_
true)
arity-matches? (n.= (list.size inputsJT) (list.size parameters))
- inputs-match? (list@fold (function (_ [expectedJC actualJC] prev)
+ inputs-match? (list\fold (function (_ [expectedJC actualJC] prev)
(and prev
- (jvm@= expectedJC (: (Type Value)
+ (jvm\= expectedJC (: (Type Value)
(case (jvm-parser.var? actualJC)
(#.Some name)
(|> aliasing
@@ -1080,9 +1080,9 @@
phase.lift)]
(wrap (and (java/lang/Object::equals class (java/lang/reflect/Constructor::getDeclaringClass constructor))
(n.= (list.size inputsJT) (list.size parameters))
- (list@fold (function (_ [expectedJC actualJC] prev)
+ (list\fold (function (_ [expectedJC actualJC] prev)
(and prev
- (jvm@= expectedJC (: (Type Value)
+ (jvm\= expectedJC (: (Type Value)
(case (jvm-parser.var? actualJC)
(#.Some name)
(|> aliasing
@@ -1101,15 +1101,15 @@
(def: (jvm-type-var-mapping owner-tvars method-tvars)
(-> (List Text) (List Text) [(List .Type) Mapping])
- (let [jvm-tvars (list@compose owner-tvars method-tvars)
+ (let [jvm-tvars (list\compose owner-tvars method-tvars)
lux-tvars (|> jvm-tvars
list.reverse
list.enumeration
- (list@map (function (_ [idx name])
+ (list\map (function (_ [idx name])
[name (idx-to-parameter idx)]))
list.reverse)
num-owner-tvars (list.size owner-tvars)
- owner-tvarsT (|> lux-tvars (list.take num-owner-tvars) (list@map product.right))
+ owner-tvarsT (|> lux-tvars (list.take num-owner-tvars) (list\map product.right))
mapping (dictionary.from-list text.hash lux-tvars)]
[owner-tvarsT mapping]))
@@ -1123,28 +1123,28 @@
_
(|> (java/lang/Class::getTypeParameters owner)
array.to-list
- (list@map (|>> java/lang/reflect/TypeVariable::getName))))
+ (list\map (|>> java/lang/reflect/TypeVariable::getName))))
method-tvars (|> (java/lang/reflect/Method::getTypeParameters method)
array.to-list
- (list@map (|>> java/lang/reflect/TypeVariable::getName)))
+ (list\map (|>> java/lang/reflect/TypeVariable::getName)))
[owner-tvarsT mapping] (jvm-type-var-mapping owner-tvars method-tvars)]
(do {! phase.monad}
[inputsT (|> (java/lang/reflect/Method::getGenericParameterTypes method)
array.to-list
(monad.map ! (|>> reflection!.type phase.lift))
- (phase@map (monad.map ! (..reflection-type mapping)))
- phase@join)
+ (phase\map (monad.map ! (..reflection-type mapping)))
+ phase\join)
outputT (|> method
java/lang/reflect/Method::getGenericReturnType
reflection!.return
phase.lift
- (phase@map (..reflection-return mapping))
- phase@join)
+ (phase\map (..reflection-return mapping))
+ phase\join)
exceptionsT (|> (java/lang/reflect/Method::getGenericExceptionTypes method)
array.to-list
(monad.map ! (|>> reflection!.type phase.lift))
- (phase@map (monad.map ! (..reflection-type mapping)))
- phase@join)
+ (phase\map (monad.map ! (..reflection-type mapping)))
+ phase\join)
#let [methodT (<| (type.univ-q (dictionary.size mapping))
(type.function (case method-style
#Static
@@ -1161,22 +1161,22 @@
(let [owner (java/lang/reflect/Constructor::getDeclaringClass constructor)
owner-tvars (|> (java/lang/Class::getTypeParameters owner)
array.to-list
- (list@map (|>> java/lang/reflect/TypeVariable::getName)))
+ (list\map (|>> java/lang/reflect/TypeVariable::getName)))
method-tvars (|> (java/lang/reflect/Constructor::getTypeParameters constructor)
array.to-list
- (list@map (|>> java/lang/reflect/TypeVariable::getName)))
+ (list\map (|>> java/lang/reflect/TypeVariable::getName)))
[owner-tvarsT mapping] (jvm-type-var-mapping owner-tvars method-tvars)]
(do {! phase.monad}
[inputsT (|> (java/lang/reflect/Constructor::getGenericParameterTypes constructor)
array.to-list
(monad.map ! (|>> reflection!.type phase.lift))
- (phase@map (monad.map ! (reflection-type mapping)))
- phase@join)
+ (phase\map (monad.map ! (reflection-type mapping)))
+ phase\join)
exceptionsT (|> (java/lang/reflect/Constructor::getGenericExceptionTypes constructor)
array.to-list
(monad.map ! (|>> reflection!.type phase.lift))
- (phase@map (monad.map ! (reflection-type mapping)))
- phase@join)
+ (phase\map (monad.map ! (reflection-type mapping)))
+ phase\join)
#let [objectT (#.Primitive (java/lang/Class::getName owner) owner-tvarsT)
constructorT (<| (type.univ-q (dictionary.size mapping))
(type.function inputsT)
@@ -1205,7 +1205,7 @@
(-> <type> (List (Type Var)))
(|>> <method>
array.to-list
- (list@map (|>> java/lang/reflect/TypeVariable::getName jvm.var))))]
+ (list\map (|>> java/lang/reflect/TypeVariable::getName jvm.var))))]
[class-type-variables (java/lang/Class java/lang/Object) java/lang/Class::getTypeParameters]
[constructor-type-variables (java/lang/reflect/Constructor java/lang/Object) java/lang/reflect/Constructor::getTypeParameters]
@@ -1214,8 +1214,8 @@
(def: (aliasing expected actual)
(-> (List (Type Var)) (List (Type Var)) Aliasing)
- (|> (list.zip/2 (list@map jvm-parser.name actual)
- (list@map jvm-parser.name expected))
+ (|> (list.zip/2 (list\map jvm-parser.name actual)
+ (list\map jvm-parser.name expected))
(dictionary.from-list text.hash)))
(def: (method-candidate actual-class-tvars class-name actual-method-tvars method-name method-style inputsJT)
@@ -1226,7 +1226,7 @@
candidates (|> class
java/lang/Class::getDeclaredMethods
array.to-list
- (list.filter (|>> java/lang/reflect/Method::getName (text@= method-name)))
+ (list.filter (|>> java/lang/reflect/Method::getName (text\= method-name)))
(monad.map ! (: (-> java/lang/reflect/Method (Operation Evaluation))
(function (_ method)
(do !
@@ -1295,8 +1295,8 @@
(def: (decorate-inputs typesT inputsA)
(-> (List (Type Value)) (List Analysis) (List Analysis))
(|> inputsA
- (list.zip/2 (list@map (|>> ..signature /////analysis.text) typesT))
- (list@map (function (_ [type value])
+ (list.zip/2 (list\map (|>> ..signature /////analysis.text) typesT))
+ (list\map (function (_ [type value])
(/////analysis.tuple (list type value))))))
(def: type-vars (<c>.tuple (<>.some ..var)))
@@ -1307,9 +1307,9 @@
[($_ <>.and ..type-vars ..member ..type-vars (<>.some ..input))
(function (_ extension-name analyse archive [class-tvars [class method] method-tvars argsTC])
(do phase.monad
- [#let [argsT (list@map product.left argsTC)]
+ [#let [argsT (list\map product.left argsTC)]
[methodT exceptionsT] (method-candidate class-tvars class method-tvars method #Static argsT)
- [outputT argsA] (inferenceA.general archive analyse methodT (list@map product.right argsTC))
+ [outputT argsA] (inferenceA.general archive analyse methodT (list\map product.right argsTC))
outputJT (check-return outputT)]
(wrap (#/////analysis.Extension extension-name (list& (/////analysis.text (..signature (jvm.class class (list))))
(/////analysis.text method)
@@ -1322,9 +1322,9 @@
[($_ <>.and ..type-vars ..member ..type-vars <c>.any (<>.some ..input))
(function (_ extension-name analyse archive [class-tvars [class method] method-tvars objectC argsTC])
(do phase.monad
- [#let [argsT (list@map product.left argsTC)]
+ [#let [argsT (list\map product.left argsTC)]
[methodT exceptionsT] (method-candidate class-tvars class method-tvars method #Virtual argsT)
- [outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list@map product.right argsTC)))
+ [outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list\map product.right argsTC)))
#let [[objectA argsA] (case allA
(#.Cons objectA argsA)
[objectA argsA]
@@ -1344,9 +1344,9 @@
[($_ <>.and ..type-vars ..member ..type-vars <c>.any (<>.some ..input))
(function (_ extension-name analyse archive [class-tvars [class method] method-tvars objectC argsTC])
(do phase.monad
- [#let [argsT (list@map product.left argsTC)]
+ [#let [argsT (list\map product.left argsTC)]
[methodT exceptionsT] (method-candidate class-tvars class method-tvars method #Special argsT)
- [outputT argsA] (inferenceA.general archive analyse methodT (list& objectC (list@map product.right argsTC)))
+ [outputT argsA] (inferenceA.general archive analyse methodT (list& objectC (list\map product.right argsTC)))
outputJT (check-return outputT)]
(wrap (#/////analysis.Extension extension-name (list& (/////analysis.text (..signature (jvm.class class (list))))
(/////analysis.text method)
@@ -1359,12 +1359,12 @@
[($_ <>.and ..type-vars ..member ..type-vars <c>.any (<>.some ..input))
(function (_ extension-name analyse archive [class-tvars [class-name method] method-tvars objectC argsTC])
(do phase.monad
- [#let [argsT (list@map product.left argsTC)]
+ [#let [argsT (list\map product.left argsTC)]
class (phase.lift (reflection!.load class-name))
_ (phase.assert non-interface class-name
(java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers class)))
[methodT exceptionsT] (method-candidate class-tvars class-name method-tvars method #Interface argsT)
- [outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list@map product.right argsTC)))
+ [outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list\map product.right argsTC)))
#let [[objectA argsA] (case allA
(#.Cons objectA argsA)
[objectA argsA]
@@ -1384,9 +1384,9 @@
[($_ <>.and ..type-vars <c>.text ..type-vars (<>.some ..input))
(function (_ extension-name analyse archive [class-tvars class method-tvars argsTC])
(do phase.monad
- [#let [argsT (list@map product.left argsTC)]
+ [#let [argsT (list\map product.left argsTC)]
[methodT exceptionsT] (constructor-candidate class-tvars class method-tvars argsT)
- [outputT argsA] (inferenceA.general archive analyse methodT (list@map product.right argsTC))]
+ [outputT argsA] (inferenceA.general archive analyse methodT (list\map product.right argsTC))]
(wrap (#/////analysis.Extension extension-name (list& (/////analysis.text (..signature (jvm.class class (list))))
(decorate-inputs argsT argsA))))))]))
@@ -1437,7 +1437,7 @@
(def: (annotation-analysis [name parameters])
(-> (Annotation Analysis) Analysis)
(/////analysis.tuple (list& (/////analysis.text name)
- (list@map annotation-parameter-analysis parameters))))
+ (list\map annotation-parameter-analysis parameters))))
(template [<name> <category>]
[(def: <name>
@@ -1492,9 +1492,9 @@
[(def: <name>
(-> (List (Type Class)) (Try (List [Text (Type Method)])))
(|>> (monad.map try.monad (|>> ..reflection reflection!.load))
- (try@map (monad.map try.monad <methods>))
- try@join
- (try@map list@join)))]
+ (try\map (monad.map try.monad <methods>))
+ try\join
+ (try\map list\join)))]
[all-abstract-methods ..abstract-methods]
[all-methods ..methods]
@@ -1601,20 +1601,20 @@
[scope bodyA] (|> arguments'
(#.Cons [self-name selfT])
list.reverse
- (list@fold scope.with-local (analyse archive body))
+ (list\fold scope.with-local (analyse archive body))
(typeA.with-type .Any)
/////analysis.with-scope)]
(wrap (/////analysis.tuple (list (/////analysis.text ..constructor-tag)
(visibility-analysis visibility)
(/////analysis.bit strict-fp?)
- (/////analysis.tuple (list@map annotation-analysis annotationsA))
- (/////analysis.tuple (list@map var-analysis vars))
+ (/////analysis.tuple (list\map annotation-analysis annotationsA))
+ (/////analysis.tuple (list\map var-analysis vars))
(/////analysis.text self-name)
- (/////analysis.tuple (list@map ..argument-analysis arguments))
- (/////analysis.tuple (list@map class-analysis exceptions))
- (/////analysis.tuple (list@map typed-analysis super-arguments))
+ (/////analysis.tuple (list\map ..argument-analysis arguments))
+ (/////analysis.tuple (list\map class-analysis exceptions))
+ (/////analysis.tuple (list\map typed-analysis super-arguments))
(#/////analysis.Function
- (list@map (|>> /////analysis.variable)
+ (list\map (|>> /////analysis.variable)
(scope.environment scope))
(/////analysis.tuple (list bodyA)))
))))))
@@ -1677,7 +1677,7 @@
[scope bodyA] (|> arguments'
(#.Cons [self-name selfT])
list.reverse
- (list@fold scope.with-local (analyse archive body))
+ (list\fold scope.with-local (analyse archive body))
(typeA.with-type returnT)
/////analysis.with-scope)]
(wrap (/////analysis.tuple (list (/////analysis.text ..virtual-tag)
@@ -1685,14 +1685,14 @@
(visibility-analysis visibility)
(/////analysis.bit final?)
(/////analysis.bit strict-fp?)
- (/////analysis.tuple (list@map annotation-analysis annotationsA))
- (/////analysis.tuple (list@map var-analysis vars))
+ (/////analysis.tuple (list\map annotation-analysis annotationsA))
+ (/////analysis.tuple (list\map var-analysis vars))
(/////analysis.text self-name)
- (/////analysis.tuple (list@map ..argument-analysis arguments))
+ (/////analysis.tuple (list\map ..argument-analysis arguments))
(return-analysis return)
- (/////analysis.tuple (list@map class-analysis exceptions))
+ (/////analysis.tuple (list\map class-analysis exceptions))
(#/////analysis.Function
- (list@map (|>> /////analysis.variable)
+ (list\map (|>> /////analysis.variable)
(scope.environment scope))
(/////analysis.tuple (list bodyA)))
))))))
@@ -1750,21 +1750,21 @@
arguments)
[scope bodyA] (|> arguments'
list.reverse
- (list@fold scope.with-local (analyse archive body))
+ (list\fold scope.with-local (analyse archive body))
(typeA.with-type returnT)
/////analysis.with-scope)]
(wrap (/////analysis.tuple (list (/////analysis.text ..static-tag)
(/////analysis.text method-name)
(visibility-analysis visibility)
(/////analysis.bit strict-fp?)
- (/////analysis.tuple (list@map annotation-analysis annotationsA))
- (/////analysis.tuple (list@map var-analysis vars))
- (/////analysis.tuple (list@map ..argument-analysis arguments))
+ (/////analysis.tuple (list\map annotation-analysis annotationsA))
+ (/////analysis.tuple (list\map var-analysis vars))
+ (/////analysis.tuple (list\map ..argument-analysis arguments))
(return-analysis return)
- (/////analysis.tuple (list@map class-analysis
+ (/////analysis.tuple (list\map class-analysis
exceptions))
(#/////analysis.Function
- (list@map (|>> /////analysis.variable)
+ (list\map (|>> /////analysis.variable)
(scope.environment scope))
(/////analysis.tuple (list bodyA)))
))))))
@@ -1826,22 +1826,22 @@
[scope bodyA] (|> arguments'
(#.Cons [self-name selfT])
list.reverse
- (list@fold scope.with-local (analyse archive body))
+ (list\fold scope.with-local (analyse archive body))
(typeA.with-type returnT)
/////analysis.with-scope)]
(wrap (/////analysis.tuple (list (/////analysis.text ..overriden-tag)
(class-analysis parent-type)
(/////analysis.text method-name)
(/////analysis.bit strict-fp?)
- (/////analysis.tuple (list@map annotation-analysis annotationsA))
- (/////analysis.tuple (list@map var-analysis vars))
+ (/////analysis.tuple (list\map annotation-analysis annotationsA))
+ (/////analysis.tuple (list\map var-analysis vars))
(/////analysis.text self-name)
- (/////analysis.tuple (list@map ..argument-analysis arguments))
+ (/////analysis.tuple (list\map ..argument-analysis arguments))
(return-analysis return)
- (/////analysis.tuple (list@map class-analysis
+ (/////analysis.tuple (list\map class-analysis
exceptions))
(#/////analysis.Function
- (list@map (|>> /////analysis.variable)
+ (list\map (|>> /////analysis.variable)
(scope.environment scope))
(/////analysis.tuple (list bodyA)))
))))))
@@ -1864,8 +1864,8 @@
(list.filter (function (_ [sub-name subJT])
(|> super-set
(list.filter (function (_ [super-name superJT])
- (and (text@= super-name sub-name)
- (jvm@= superJT subJT))))
+ (and (text\= super-name sub-name)
+ (jvm\= superJT subJT))))
list.size
(n.= 1)
not))
@@ -1886,12 +1886,12 @@
class (phase.lift (reflection!.load name))
#let [expected-parameters (|> (java/lang/Class::getTypeParameters class)
array.to-list
- (list@map (|>> java/lang/reflect/TypeVariable::getName)))]
+ (list\map (|>> java/lang/reflect/TypeVariable::getName)))]
_ (phase.assert ..class-parameter-mismatch [expected-parameters actual-parameters]
(n.= (list.size expected-parameters)
(list.size actual-parameters)))]
(wrap (|> (list.zip/2 expected-parameters actual-parameters)
- (list@fold (function (_ [expected actual] mapping)
+ (list\fold (function (_ [expected actual] mapping)
(case (jvm-parser.var? actual)
(#.Some actual)
(dictionary.put actual expected mapping)
@@ -1923,7 +1923,7 @@
(do {! phase.monad}
[parameters (typeA.with-env
(..parameter-types parameters))
- #let [mapping (list@fold (function (_ [parameterJ parameterT] mapping)
+ #let [mapping (list\fold (function (_ [parameterJ parameterT] mapping)
(dictionary.put (jvm-parser.name parameterJ)
parameterT
mapping))
@@ -1958,7 +1958,7 @@
body])
(do !
[aliasing (super-aliasing parent-type)]
- (wrap [method-name (|> (jvm.method [(list@map product.right arguments)
+ (wrap [method-name (|> (jvm.method [(list\map product.right arguments)
return
exceptions])
(jvm-alias.method aliasing))])))
@@ -1971,8 +1971,8 @@
(list.empty? invalid-overriden-methods))]
(wrap (#/////analysis.Extension extension-name
(list (class-analysis super-class)
- (/////analysis.tuple (list@map class-analysis super-interfaces))
- (/////analysis.tuple (list@map typed-analysis constructor-argsA+))
+ (/////analysis.tuple (list\map class-analysis super-interfaces))
+ (/////analysis.tuple (list\map typed-analysis constructor-argsA+))
(/////analysis.tuple methodsA))))))]))
(def: bundle::class
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
index 1c50d6eb5..29fb70e63 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
@@ -15,7 +15,7 @@
["." text
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]
+ ["." list ("#\." functor)]
["." dictionary (#+ Dictionary)]]]
[type
["." check]]
@@ -113,9 +113,9 @@
else (typeA.with-type expectedT
(phase archive else))]
(wrap (|> conditionals
- (list@map (function (_ [cases branch])
+ (list\map (function (_ [cases branch])
(////analysis.tuple
- (list (////analysis.tuple (list@map (|>> ////analysis.nat) cases))
+ (list (////analysis.tuple (list\map (|>> ////analysis.nat) cases))
branch))))
(list& input else)
(#////analysis.Extension extension-name)))))])))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
index 8f44551d1..2837d6620 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
@@ -5,7 +5,7 @@
["." monad (#+ do)]]
[control
[pipe (#+ case>)]
- ["<>" parser ("#@." monad)
+ ["<>" parser ("#\." monad)
["<c>" code (#+ Parser)]
["<t>" text]]]
[data
@@ -15,7 +15,7 @@
[text
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor fold)]
+ ["." list ("#\." functor fold)]
["." dictionary]
["." row]]]
[type
@@ -25,7 +25,7 @@
[target
[jvm
["_" bytecode (#+ Bytecode)]
- ["." modifier (#+ Modifier) ("#@." monoid)]
+ ["." modifier (#+ Modifier) ("#\." monoid)]
["." attribute]
["." field]
["." version]
@@ -75,7 +75,7 @@
(Parser (Modifier field.Field))
(`` ($_ <>.either
(~~ (template [<label> <modifier>]
- [(<>.after (<c>.text! <label>) (<>@wrap <modifier>))]
+ [(<>.after (<c>.text! <label>) (<>\wrap <modifier>))]
["public" field.public]
["private" field.private]
@@ -86,7 +86,7 @@
(Parser (Modifier class.Class))
(`` ($_ <>.either
(~~ (template [<label> <modifier>]
- [(<>.after (<c>.text! <label>) (<>@wrap <modifier>))]
+ [(<>.after (<c>.text! <label>) (<>\wrap <modifier>))]
["final" class.final]
["abstract" class.abstract]
@@ -96,7 +96,7 @@
(Parser (Modifier field.Field))
(`` ($_ <>.either
(~~ (template [<label> <modifier>]
- [(<>.after (<c>.text! <label>) (<>@wrap <modifier>))]
+ [(<>.after (<c>.text! <label>) (<>\wrap <modifier>))]
["volatile" field.volatile]
["final" field.final]
@@ -175,7 +175,7 @@
(def: constant::modifier
(Modifier field.Field)
- ($_ modifier@compose
+ ($_ modifier\compose
field.public
field.static
field.final))
@@ -209,7 +209,7 @@
## TODO: Handle annotations.
(#Variable [name visibility state annotations type])
- (field.field (modifier@compose visibility state)
+ (field.field (modifier\compose visibility state)
name type (row.row))))
(def: (method-definition [mapping selfT] [analyse synthesize generate])
@@ -261,7 +261,7 @@
[parameters (directive.lift-analysis
(typeA.with-env
(jvm.parameter-types parameters)))
- #let [mapping (list@fold (function (_ [parameterJ parameterT] mapping)
+ #let [mapping (list\fold (function (_ [parameterJ parameterT] mapping)
(dictionary.put (parser.name parameterJ) parameterT mapping))
luxT.fresh
parameters)]
@@ -273,7 +273,7 @@
(monad.map check.monad
(|>> ..signature (luxT.check (luxT.class mapping)))
super-interfaces)))
- #let [selfT (jvm.inheritance-relationship-type (#.Primitive name (list@map product.right parameters))
+ #let [selfT (jvm.inheritance-relationship-type (#.Primitive name (list\map product.right parameters))
super-classT
super-interfaceT+)]
state (extension.lift phase.get-state)
@@ -286,10 +286,10 @@
## (generation.save! true ["" name]
## [name
## (class.class version.v6_0
- ## (modifier@compose class.public inheritance)
- ## (name.internal name) (list@map (|>> product.left parser.name ..constraint) parameters)
+ ## (modifier\compose class.public inheritance)
+ ## (name.internal name) (list\map (|>> product.left parser.name ..constraint) parameters)
## super-class super-interfaces
- ## (list@map ..field-definition fields)
+ ## (list\map ..field-definition fields)
## (list) ## TODO: Add methods
## (row.row))]))
_ (directive.lift-generation
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
index d8d6ed817..a1adf0041 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
@@ -20,7 +20,7 @@
["." meta]
[macro
["." code]]
- ["." type (#+ :share :by-example) ("#@." equivalence)
+ ["." type (#+ :share)
["." check]]]
["." /// (#+ Extender)
["#." bundle]
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
index 2122a38a4..1485d7230 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
@@ -11,7 +11,7 @@
[number
["f" frac]]
[collection
- ["." list ("#@." functor)]
+ ["." list ("#\." functor)]
["." dictionary]]]
["@" target
["_" js (#+ Literal Expression Statement)]]]
@@ -131,7 +131,7 @@
(monad.map ! (function (_ [chars branch])
(do !
[branchG (phase archive branch)]
- (wrap [(list@map (|>> .int _.int) chars)
+ (wrap [(list\map (|>> .int _.int) chars)
(_.return branchG)])))
conditionals))]
(wrap (_.apply/* (_.closure (list)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
index 5c98aeba1..630e212c3 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
@@ -13,11 +13,11 @@
["." i32]
["f" frac]]
[collection
- ["." list ("#@." monad)]
+ ["." list ("#\." monad)]
["." dictionary]]]
[target
[jvm
- ["_" bytecode (#+ Label Bytecode) ("#@." monad)]
+ ["_" bytecode (#+ Label Bytecode) ("#\." monad)]
[encoding
["." signed (#+ S4)]]
["." type (#+ Type)
@@ -114,7 +114,7 @@
(do !
[branchG (phase archive branch)
@branch ///runtime.forge-label]
- (wrap [(list@map (function (_ char)
+ (wrap [(list\map (function (_ char)
[(try.assume (signed.s4 (.int char))) @branch])
chars)
($_ _.compose
@@ -123,10 +123,10 @@
(_.goto @end))])))
conditionalsS))
#let [table (|> conditionalsG+
- (list@map product.left)
- list@join)
+ (list\map product.left)
+ list\join)
conditionalsG (|> conditionalsG+
- (list@map product.right)
+ (list\map product.right)
(monad.seq _.monad))]]
(wrap (do _.monad
[@else _.new-label]
@@ -308,7 +308,7 @@
(_.invokevirtual ..$String "length" (type.method [(list) type.int (list)]))
..lux-int))
-(def: no-op (Bytecode Any) (_@wrap []))
+(def: no-op (Bytecode Any) (_\wrap []))
(template [<name> <pre-subject> <pre-param> <op> <post>]
[(def: (<name> [paramG subjectG])
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
index e584bd1e4..ee9c3b1a2 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
@@ -11,12 +11,12 @@
[data
["." product]
["." maybe]
- ["." text ("#@." equivalence)
+ ["." text ("#\." equivalence)
["%" format (#+ format)]]
[number
["." i32]]
[collection
- ["." list ("#@." monad)]
+ ["." list ("#\." monad)]
["." dictionary (#+ Dictionary)]
["." set]
["." row]]
@@ -25,14 +25,14 @@
[target
[jvm
["." version]
- ["." modifier ("#@." monoid)]
+ ["." modifier ("#\." monoid)]
["." method (#+ Method)]
["." class (#+ Class)]
[constant
[pool (#+ Resource)]]
[encoding
["." name]]
- ["_" bytecode (#+ Label Bytecode) ("#@." monad)
+ ["_" bytecode (#+ Label Bytecode) ("#\." monad)
["__" instruction (#+ Primitive-Array-Type)]]
["." type (#+ Type Typed Argument)
["." category (#+ Void Value' Value Return' Return Primitive Object Array Var Parameter)]
@@ -580,18 +580,18 @@
(do //////.monad
[valueG (generate archive valueS)]
(wrap (`` (cond (~~ (template [<object> <type> <unwrap>]
- [(and (text@= (..reflection <type>)
+ [(and (text\= (..reflection <type>)
from)
- (text@= <object>
+ (text\= <object>
to))
(let [$<object> (type.class <object> (list))]
($_ _.compose
valueG
(_.invokestatic $<object> "valueOf" (type.method [(list <type>) $<object> (list)]))))
- (and (text@= <object>
+ (and (text\= <object>
from)
- (text@= (..reflection <type>)
+ (text\= (..reflection <type>)
to))
(let [$<object> (type.class <object> (list))]
($_ _.compose
@@ -754,7 +754,7 @@
[inputsTG (monad.map ! (generate-input generate archive) inputsTS)]
(wrap ($_ _.compose
(monad.map _.monad product.right inputsTG)
- (_.invokestatic class method (type.method [(list@map product.left inputsTG) outputT (list)]))
+ (_.invokestatic class method (type.method [(list\map product.left inputsTG) outputT (list)]))
(prepare-output outputT)))))]))
(template [<name> <invoke>]
@@ -770,7 +770,7 @@
objectG
(_.checkcast class)
(monad.map _.monad product.right inputsTG)
- (<invoke> class method (type.method [(list@map product.left inputsTG) outputT (list)]))
+ (<invoke> class method (type.method [(list\map product.left inputsTG) outputT (list)]))
(prepare-output outputT)))))]))]
[invoke::virtual _.invokevirtual]
@@ -789,7 +789,7 @@
(_.new class)
_.dup
(monad.map _.monad product.right inputsTG)
- (_.invokespecial class "<init>" (type.method [(list@map product.left inputsTG) type.void (list)]))))))]))
+ (_.invokespecial class "<init>" (type.method [(list\map product.left inputsTG) type.void (list)]))))))]))
(def: bundle::member
Bundle
@@ -883,7 +883,7 @@
(//////synthesis.variant [lefts right? (recur sub)])
(^ (//////synthesis.tuple members))
- (//////synthesis.tuple (list@map recur members))
+ (//////synthesis.tuple (list\map recur members))
(^ (//////synthesis.variable var))
(|> mapping
@@ -904,13 +904,13 @@
(//////synthesis.branch/get [path (recur recordS)])
(^ (//////synthesis.loop/scope [offset initsS+ bodyS]))
- (//////synthesis.loop/scope [offset (list@map recur initsS+) (recur bodyS)])
+ (//////synthesis.loop/scope [offset (list\map recur initsS+) (recur bodyS)])
(^ (//////synthesis.loop/recur updatesS+))
- (//////synthesis.loop/recur (list@map recur updatesS+))
+ (//////synthesis.loop/recur (list\map recur updatesS+))
(^ (//////synthesis.function/abstraction [environment arity bodyS]))
- (//////synthesis.function/abstraction [(list@map (function (_ local)
+ (//////synthesis.function/abstraction [(list\map (function (_ local)
(case local
(^ (//////synthesis.variable local))
(|> mapping
@@ -925,10 +925,10 @@
bodyS])
(^ (//////synthesis.function/apply [functionS inputsS+]))
- (//////synthesis.function/apply [(recur functionS) (list@map recur inputsS+)])
+ (//////synthesis.function/apply [(recur functionS) (list\map recur inputsS+)])
(#//////synthesis.Extension [name inputsS+])
- (#//////synthesis.Extension [name (list@map recur inputsS+)]))))
+ (#//////synthesis.Extension [name (list\map recur inputsS+)]))))
(def: $Object (type.class "java.lang.Object" (list)))
@@ -953,7 +953,7 @@
(#.Some ($_ _.compose
(_.aload 0)
(monad.map _.monad product.right inputsTG)
- (_.invokespecial super-class "<init>" (type.method [(list@map product.left inputsTG) type.void (list)]))
+ (_.invokespecial super-class "<init>" (type.method [(list\map product.left inputsTG) type.void (list)]))
store-capturedG
_.return)))))
@@ -1015,26 +1015,26 @@
class (type.class anonymous-class-name (list))
total-environment (|> overriden-methods
## Get all the environments.
- (list@map product.left)
+ (list\map product.left)
## Combine them.
- list@join
+ list\join
## Remove duplicates.
(set.from-list //////synthesis.hash)
set.to-list)
global-mapping (|> total-environment
## Give them names as "foreign" variables.
list.enumeration
- (list@map (function (_ [id capture])
+ (list\map (function (_ [id capture])
[capture (#//////variable.Foreign id)]))
(dictionary.from-list //////variable.hash))
- normalized-methods (list@map (function (_ [environment
+ normalized-methods (list\map (function (_ [environment
[ownerT name
strict-fp? annotations vars
self-name arguments returnT exceptionsT
body]])
(let [local-mapping (|> environment
list.enumeration
- (list@map (function (_ [foreign-id capture])
+ (list\map (function (_ [foreign-id capture])
[(#//////variable.Foreign foreign-id)
(|> global-mapping
(dictionary.get capture)
@@ -1053,14 +1053,14 @@
(do !
[bodyG (//////generation.with-context artifact-id
(generate archive bodyS))]
- (wrap (method.method ($_ modifier@compose
+ (wrap (method.method ($_ modifier\compose
method.public
method.final
(if strict-fp?
method.strict
- modifier@identity))
+ modifier\identity))
name
- (type.method [(list@map product.right arguments)
+ (type.method [(list\map product.right arguments)
returnT
exceptionsT])
(list)
@@ -1070,10 +1070,10 @@
normalized-methods)
bytecode (<| (:: ! map (format.run class.writer))
//////.lift
- (class.class version.v6_0 ($_ modifier@compose class.public class.final)
+ (class.class version.v6_0 ($_ modifier\compose class.public class.final)
(name.internal anonymous-class-name)
(name.internal (..reflection super-class))
- (list@map (|>> ..reflection name.internal) super-interfaces)
+ (list\map (|>> ..reflection name.internal) super-interfaces)
(foreign.variables total-environment)
(list& (..with-anonymous-init class total-environment super-class inputsTI)
method-definitions)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis.lux
index e6a587f9f..e4d72cb92 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis.lux
@@ -8,7 +8,7 @@
[data
["." maybe]
[collection
- ["." list ("#@." functor)]
+ ["." list ("#\." functor)]
["." dictionary (#+ Dictionary)]]]]
["." / #_
["#." function]
@@ -22,7 +22,7 @@
[///
[reference (#+)
[variable (#+)]]
- ["." phase ("#@." monad)]]]]])
+ ["." phase ("#\." monad)]]]]])
(def: (primitive analysis)
(-> ///analysis.Primitive /.Primitive)
@@ -49,7 +49,7 @@
(function (optimization' analysis)
(case analysis
(#///analysis.Primitive analysis')
- (phase@wrap (#/.Primitive (..primitive analysis')))
+ (phase\wrap (#/.Primitive (..primitive analysis')))
(#///analysis.Structure structure)
(/.with-currying? false
@@ -62,10 +62,10 @@
(#///analysis.Tuple tuple)
(|> tuple
(monad.map phase.monad optimization')
- (phase@map (|>> /.tuple)))))
+ (phase\map (|>> /.tuple)))))
(#///analysis.Reference reference)
- (phase@wrap (#/.Reference reference))
+ (phase\wrap (#/.Reference reference))
(#///analysis.Case inputA branchesAB+)
(/.with-currying? false
@@ -92,7 +92,7 @@
(#try.Failure _)
(|> args
(monad.map phase.monad optimization')
- (phase@map (|>> [name] #/.Extension))
+ (phase\map (|>> [name] #/.Extension))
(phase.run' state))))))
)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux
index cc1bf4500..0fe2bf712 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux
@@ -11,8 +11,8 @@
["." sum]
["." product]
["." maybe]
- ["." bit ("#@." equivalence)]
- ["." text ("#@." equivalence)
+ ["." bit ("#\." equivalence)]
+ ["." text ("#\." equivalence)
["%" format (#+ Format format)]]
[number
["." i64]
@@ -20,7 +20,7 @@
["i" int]
["f" frac]]
[collection
- ["." list ("#@." functor)]
+ ["." list ("#\." functor)]
["." dictionary (#+ Dictionary)]]]]
[//
["." analysis (#+ Environment Composite Analysis)]
@@ -275,7 +275,7 @@
(^template [<tag> <format>]
[(<tag> cons)
(|> (#.Cons cons)
- (list@map (function (_ [test then])
+ (list\map (function (_ [test then])
(format (<format> test) " " (%path' %then then))))
(text.join-with " ")
(text.enclose ["(? " ")"]))])
@@ -338,7 +338,7 @@
(#analysis.Tuple members)
(|> members
- (list@map %synthesis)
+ (list\map %synthesis)
(text.join-with " ")
(text.enclose ["[" "]"])))
@@ -351,7 +351,7 @@
(case function
(#Abstraction [environment arity body])
(let [environment' (|> environment
- (list@map %synthesis)
+ (list\map %synthesis)
(text.join-with " ")
(text.enclose ["[" "]"]))]
(|> (format environment' " " (%.nat arity) " " (%synthesis body))
@@ -359,7 +359,7 @@
(#Apply func args)
(|> args
- (list@map %synthesis)
+ (list\map %synthesis)
(text.join-with " ")
(format (%synthesis func) " ")
(text.enclose ["(" ")"])))
@@ -376,7 +376,7 @@
(#Get members record)
(|> (format (%.list (%path' %synthesis)
- (list@map (|>> #Member #Access) members))
+ (list\map (|>> #Member #Access) members))
" " (%synthesis record))
(text.enclose ["(#get " ")"]))
@@ -389,7 +389,7 @@
(#Scope scope)
(|> (format (%.nat (get@ #start scope))
" " (|> (get@ #inits scope)
- (list@map %synthesis)
+ (list\map %synthesis)
(text.join-with " ")
(text.enclose ["[" "]"]))
" " (%synthesis (get@ #iteration scope)))
@@ -397,12 +397,12 @@
(#Recur args)
(|> args
- (list@map %synthesis)
+ (list\map %synthesis)
(text.join-with " ")
(text.enclose ["(#recur " ")"]))))
(#Extension [name args])
- (|> (list@map %synthesis args)
+ (|> (list\map %synthesis args)
(text.join-with " ")
(format (%.text name) " ")
(text.enclose ["(" ")"]))))
@@ -419,9 +419,9 @@
(^template [<tag> <eq> <format>]
[[(<tag> reference') (<tag> sample')]
(<eq> reference' sample')])
- ([#Bit bit@= %.bit]
+ ([#Bit bit\= %.bit]
[#F64 f.= %.frac]
- [#Text text@= %.text])
+ [#Text text\= %.text])
[(#I64 reference') (#I64 sample')]
(i.= (.int reference') (.int sample'))
@@ -493,7 +493,7 @@
[(#Bit-Fork reference-when reference-then reference-else)
(#Bit-Fork sample-when sample-then sample-else)]
- (and (bit@= reference-when sample-when)
+ (and (bit\= reference-when sample-when)
(= reference-then sample-then)
(:: (maybe.equivalence =) = reference-else sample-else))
@@ -571,32 +571,32 @@
(n.* 29 (:: super hash body))
)))
-(structure: (branch-equivalence (^open "/@."))
+(structure: (branch-equivalence (^open "\."))
(All [a] (-> (Equivalence a) (Equivalence (Branch a))))
(def: (= reference sample)
(case [reference sample]
[(#Let [reference-input reference-register reference-body])
(#Let [sample-input sample-register sample-body])]
- (and (/@= reference-input sample-input)
+ (and (\= reference-input sample-input)
(n.= reference-register sample-register)
- (/@= reference-body sample-body))
+ (\= reference-body sample-body))
[(#If [reference-test reference-then reference-else])
(#If [sample-test sample-then sample-else])]
- (and (/@= reference-test sample-test)
- (/@= reference-then sample-then)
- (/@= reference-else sample-else))
+ (and (\= reference-test sample-test)
+ (\= reference-then sample-then)
+ (\= reference-else sample-else))
[(#Get [reference-path reference-record])
(#Get [sample-path sample-record])]
(and (:: (list.equivalence ..member-equivalence) = reference-path sample-path)
- (/@= reference-record sample-record))
+ (\= reference-record sample-record))
[(#Case [reference-input reference-path])
(#Case [sample-input sample-path])]
- (and (/@= reference-input sample-input)
- (:: (path'-equivalence /@=) = reference-path sample-path))
+ (and (\= reference-input sample-input)
+ (:: (path'-equivalence \=) = reference-path sample-path))
_
false)))
@@ -632,7 +632,7 @@
(:: (..path'-hash super) hash path))
)))
-(structure: (loop-equivalence (^open "/@."))
+(structure: (loop-equivalence (^open "\."))
(All [a] (-> (Equivalence a) (Equivalence (Loop a))))
(def: (= reference sample)
@@ -640,11 +640,11 @@
[(#Scope [reference-start reference-inits reference-iteration])
(#Scope [sample-start sample-inits sample-iteration])]
(and (n.= reference-start sample-start)
- (:: (list.equivalence /@=) = reference-inits sample-inits)
- (/@= reference-iteration sample-iteration))
+ (:: (list.equivalence \=) = reference-inits sample-inits)
+ (\= reference-iteration sample-iteration))
[(#Recur reference) (#Recur sample)]
- (:: (list.equivalence /@=) = reference sample)
+ (:: (list.equivalence \=) = reference sample)
_
false)))
@@ -668,21 +668,21 @@
(:: (list.hash super) hash resets))
)))
-(structure: (function-equivalence (^open "/@."))
+(structure: (function-equivalence (^open "\."))
(All [a] (-> (Equivalence a) (Equivalence (Function a))))
(def: (= reference sample)
(case [reference sample]
[(#Abstraction [reference-environment reference-arity reference-body])
(#Abstraction [sample-environment sample-arity sample-body])]
- (and (:: (list.equivalence /@=) = reference-environment sample-environment)
+ (and (:: (list.equivalence \=) = reference-environment sample-environment)
(n.= reference-arity sample-arity)
- (/@= reference-body sample-body))
+ (\= reference-body sample-body))
[(#Apply [reference-abstraction reference-arguments])
(#Apply [sample-abstraction sample-arguments])]
- (and (/@= reference-abstraction sample-abstraction)
- (:: (list.equivalence /@=) = reference-arguments sample-arguments))
+ (and (\= reference-abstraction sample-abstraction)
+ (:: (list.equivalence \=) = reference-arguments sample-arguments))
_
false)))
@@ -707,14 +707,14 @@
(:: (list.hash super) hash arguments))
)))
-(structure: (control-equivalence (^open "/@."))
+(structure: (control-equivalence (^open "\."))
(All [a] (-> (Equivalence a) (Equivalence (Control a))))
(def: (= reference sample)
(case [reference sample]
(^template [<tag> <equivalence>]
[[(<tag> reference) (<tag> sample)]
- (:: (<equivalence> /@=) = reference sample)])
+ (:: (<equivalence> \=) = reference sample)])
([#Branch ..branch-equivalence]
[#Loop ..loop-equivalence]
[#Function ..function-equivalence])