aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/target/jvm
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/target/jvm/attribute.lux2
-rw-r--r--stdlib/source/lux/target/jvm/attribute/code.lux10
-rw-r--r--stdlib/source/lux/target/jvm/bytecode.lux16
-rw-r--r--stdlib/source/lux/target/jvm/bytecode/environment/limit.lux4
-rw-r--r--stdlib/source/lux/target/jvm/bytecode/environment/limit/registry.lux18
-rw-r--r--stdlib/source/lux/target/jvm/class.lux4
-rw-r--r--stdlib/source/lux/target/jvm/constant.lux6
-rw-r--r--stdlib/source/lux/target/jvm/constant/pool.lux12
-rw-r--r--stdlib/source/lux/target/jvm/constant/tag.lux6
-rw-r--r--stdlib/source/lux/target/jvm/field.lux4
-rw-r--r--stdlib/source/lux/target/jvm/method.lux6
-rw-r--r--stdlib/source/lux/target/jvm/modifier.lux4
-rw-r--r--stdlib/source/lux/target/jvm/reflection.lux28
-rw-r--r--stdlib/source/lux/target/jvm/type.lux12
-rw-r--r--stdlib/source/lux/target/jvm/type/alias.lux2
-rw-r--r--stdlib/source/lux/target/jvm/type/descriptor.lux8
-rw-r--r--stdlib/source/lux/target/jvm/type/lux.lux56
-rw-r--r--stdlib/source/lux/target/jvm/type/parser.lux10
-rw-r--r--stdlib/source/lux/target/jvm/type/reflection.lux4
-rw-r--r--stdlib/source/lux/target/jvm/type/signature.lux16
20 files changed, 113 insertions, 115 deletions
diff --git a/stdlib/source/lux/target/jvm/attribute.lux b/stdlib/source/lux/target/jvm/attribute.lux
index 083ebaa15..99ceeafb5 100644
--- a/stdlib/source/lux/target/jvm/attribute.lux
+++ b/stdlib/source/lux/target/jvm/attribute.lux
@@ -11,7 +11,7 @@
[number
["n" nat]]
[format
- [".F" binary (#+ Writer) ("#@." monoid)]]]]
+ [".F" binary (#+ Writer)]]]]
["." // #_
["#." index (#+ Index)]
[encoding
diff --git a/stdlib/source/lux/target/jvm/attribute/code.lux b/stdlib/source/lux/target/jvm/attribute/code.lux
index 3a9629c1f..012c25809 100644
--- a/stdlib/source/lux/target/jvm/attribute/code.lux
+++ b/stdlib/source/lux/target/jvm/attribute/code.lux
@@ -8,9 +8,9 @@
[number
["n" nat]]
[format
- [".F" binary (#+ Writer) ("#@." monoid)]]
+ [".F" binary (#+ Writer) ("#//." monoid)]]
[collection
- ["." row (#+ Row) ("#@." functor fold)]]]]
+ ["." row (#+ Row) ("#//." functor fold)]]]]
["." /// #_
[bytecode
[environment
@@ -48,8 +48,8 @@
## attribute_info attributes[attributes_count];
(|> code
(get@ #attributes)
- (row@map length)
- (row@fold n.+ 0))))
+ (row//map length)
+ (row//fold n.+ 0))))
(def: #export (equivalence attribute-equivalence)
(All [attribute]
@@ -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)
(All [Attribute] (-> (Writer Attribute) (Writer (Code Attribute))))
- ($_ binaryF@compose
+ ($_ binaryF//compose
## u2 max_stack;
## u2 max_locals;
(///limit.writer (get@ #limit code))
diff --git a/stdlib/source/lux/target/jvm/bytecode.lux b/stdlib/source/lux/target/jvm/bytecode.lux
index 2b3d600f7..31b99e9cf 100644
--- a/stdlib/source/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/lux/target/jvm/bytecode.lux
@@ -20,7 +20,7 @@
["i" int]
["." i32 (#+ I32)]]
[collection
- ["." list ("#@." functor fold)]
+ ["." list ("#//." functor fold)]
["." dictionary (#+ Dictionary)]
["." row (#+ Row)]]]
[macro
@@ -28,7 +28,7 @@
["." / #_
["#." address (#+ Address)]
["#." jump (#+ Jump Big-Jump)]
- ["_" instruction (#+ Primitive-Array-Type Instruction Estimator) ("#@." monoid)]
+ ["_" instruction (#+ Primitive-Array-Type Instruction Estimator) ("#//." monoid)]
["#." environment (#+ Environment)
[limit
["/." registry (#+ Register Registry)]
@@ -93,7 +93,7 @@
[[left-exceptions left-instruction] (left resolver)
[right-exceptions right-instruction] (right resolver)]
(wrap [(:: row.monoid compose left-exceptions right-exceptions)
- (_@compose left-instruction right-instruction)]))))))
+ (_//compose left-instruction right-instruction)]))))))
(type: #export (Bytecode a)
(State' Try [Pool Environment Tracker] (Writer Relative a)))
@@ -843,7 +843,7 @@
(wrap (let [@from (get@ #program-counter tracker)]
[[pool
environment'
- (|> (list@fold (..acknowledge-label actual) tracker (list& default at-minimum afterwards))
+ (|> (list//fold (..acknowledge-label actual) tracker (list& default at-minimum afterwards))
(set@ #program-counter program-counter'))]
[(function (_ resolver)
(let [get (: (-> Label (Maybe [Stack (Maybe Address)]))
@@ -886,7 +886,7 @@
(wrap (let [@from (get@ #program-counter tracker)]
[[pool
environment'
- (|> (list@fold (..acknowledge-label actual) tracker (list& default (list@map product.right cases)))
+ (|> (list//fold (..acknowledge-label actual) tracker (list& default (list//map product.right cases)))
(set@ #program-counter program-counter'))]
[(function (_ resolver)
(let [get (: (-> Label (Maybe [Stack (Maybe Address)]))
@@ -903,7 +903,7 @@
[>default (:: ! map ..big-jump (..jump @from @default))
>cases (|> @cases
(monad.map ! (|>> (..jump @from) (:: ! map ..big-jump)))
- (:: ! map (|>> (list.zip/2 (list@map product.left cases)))))]
+ (:: ! map (|>> (list.zip/2 (list//map product.left cases)))))]
(wrap [..no-exceptions (bytecode >default >cases)]))
#.None
@@ -970,8 +970,8 @@
{#//constant/pool.name method
#//constant/pool.descriptor (type.descriptor type)})
#let [consumption (|> inputs
- (list@map ..type-size)
- (list@fold n.+ (if <static?> 0 1))
+ (list//map ..type-size)
+ (list//fold n.+ (if <static?> 0 1))
//unsigned.u1
try.assume)
production (|> output ..type-size //unsigned.u1 try.assume)]]
diff --git a/stdlib/source/lux/target/jvm/bytecode/environment/limit.lux b/stdlib/source/lux/target/jvm/bytecode/environment/limit.lux
index 1bbb40e15..7ca0f0e83 100644
--- a/stdlib/source/lux/target/jvm/bytecode/environment/limit.lux
+++ b/stdlib/source/lux/target/jvm/bytecode/environment/limit.lux
@@ -9,7 +9,7 @@
[number
["n" nat]]
["." format #_
- ["#" binary (#+ Writer) ("#@." monoid)]]]]
+ ["#" binary (#+ Writer) ("#//." monoid)]]]]
["." / #_
["#." stack (#+ Stack)]
["#." registry (#+ Registry)]
@@ -49,7 +49,7 @@
(def: #export (writer limit)
(Writer Limit)
- ($_ format@compose
+ ($_ format//compose
(/stack.writer (get@ #stack limit))
(/registry.writer (get@ #registry limit))
))
diff --git a/stdlib/source/lux/target/jvm/bytecode/environment/limit/registry.lux b/stdlib/source/lux/target/jvm/bytecode/environment/limit/registry.lux
index 8156c46c0..c192a3fdd 100644
--- a/stdlib/source/lux/target/jvm/bytecode/environment/limit/registry.lux
+++ b/stdlib/source/lux/target/jvm/bytecode/environment/limit/registry.lux
@@ -3,14 +3,14 @@
[abstract
["." equivalence (#+ Equivalence)]]
[control
- ["." try (#+ Try) ("#@." functor)]]
+ ["." try (#+ Try) ("#//." functor)]]
[data
[number
["n" nat]]
[format
[binary (#+ Writer)]]
[collection
- ["." list ("#@." functor fold)]]]
+ ["." list ("#//." functor fold)]]]
[type
abstract]]
["." ///// #_
@@ -36,12 +36,12 @@
(-> (Type Method) Nat)
(let [[inputs output exceptions] (/////type/parser.method type)]
(|> inputs
- (list@map (function (_ input)
- (if (or (is? /////type.long input)
- (is? /////type.double input))
- ..wide
- ..normal)))
- (list@fold n.+ 0))))
+ (list//map (function (_ input)
+ (if (or (is? /////type.long input)
+ (is? /////type.double input))
+ ..wide
+ ..normal)))
+ (list//fold n.+ 0))))
(template [<start> <name>]
[(def: #export <name>
@@ -49,7 +49,7 @@
(|>> ..minimal
(n.+ <start>)
/////unsigned.u2
- (try@map ..registry)))]
+ (try//map ..registry)))]
[0 static]
[1 virtual]
diff --git a/stdlib/source/lux/target/jvm/class.lux b/stdlib/source/lux/target/jvm/class.lux
index 5a975cf8a..08bd81e56 100644
--- a/stdlib/source/lux/target/jvm/class.lux
+++ b/stdlib/source/lux/target/jvm/class.lux
@@ -11,7 +11,7 @@
[number (#+)
[i64 (#+)]]
[format
- [".F" binary (#+ Writer) ("#@." monoid)]]
+ [".F" binary (#+ Writer) ("#//." monoid)]]
[collection
["." row (#+ Row)]]]
[type
@@ -115,7 +115,7 @@
(def: #export (writer class)
(Writer Class)
- (`` ($_ binaryF@compose
+ (`` ($_ binaryF//compose
(~~ (template [<writer> <slot>]
[(<writer> (get@ <slot> class))]
diff --git a/stdlib/source/lux/target/jvm/constant.lux b/stdlib/source/lux/target/jvm/constant.lux
index b114ba945..d62100634 100644
--- a/stdlib/source/lux/target/jvm/constant.lux
+++ b/stdlib/source/lux/target/jvm/constant.lux
@@ -13,7 +13,7 @@
["." frac]]
["." text]
[format
- [".F" binary (#+ Writer) ("#@." monoid)]]
+ [".F" binary (#+ Writer) ("#//." monoid)]]
[collection
["." row (#+ Row)]]]
[type
@@ -234,7 +234,7 @@
(case value
(^template [<case> <tag> <writer>]
(<case> value)
- (binaryF@compose (/tag.writer <tag>)
- (<writer> value)))
+ (binaryF//compose (/tag.writer <tag>)
+ (<writer> value)))
(<constants>)
))))
diff --git a/stdlib/source/lux/target/jvm/constant/pool.lux b/stdlib/source/lux/target/jvm/constant/pool.lux
index 2d2b1b940..17e3f0302 100644
--- a/stdlib/source/lux/target/jvm/constant/pool.lux
+++ b/stdlib/source/lux/target/jvm/constant/pool.lux
@@ -15,9 +15,9 @@
["." frac]]
["." text]
["." format #_
- ["#" binary (#+ Writer) ("specification@." monoid)]]
+ ["#" binary (#+ Writer) ("specification//." monoid)]]
[collection
- ["." row (#+ Row) ("#@." fold)]]]
+ ["." row (#+ Row) ("#//." fold)]]]
[type
abstract]
[macro
@@ -144,10 +144,10 @@
(def: #export writer
(Writer Pool)
(function (_ [next pool])
- (row@fold (function (_ [_index post] pre)
- (specification@compose pre (//.writer post)))
- (format.bits/16 (!index next))
- pool)))
+ (row//fold (function (_ [_index post] pre)
+ (specification//compose pre (//.writer post)))
+ (format.bits/16 (!index next))
+ pool)))
(def: #export empty
Pool
diff --git a/stdlib/source/lux/target/jvm/constant/tag.lux b/stdlib/source/lux/target/jvm/constant/tag.lux
index ce1b7d20a..fc2311ab9 100644
--- a/stdlib/source/lux/target/jvm/constant/tag.lux
+++ b/stdlib/source/lux/target/jvm/constant/tag.lux
@@ -11,7 +11,7 @@
abstract]]
["." /// #_
[encoding
- ["#." unsigned (#+ U1) ("u1@." equivalence)]]])
+ ["#." unsigned (#+ U1) ("u1//." equivalence)]]])
(abstract: #export Tag
U1
@@ -19,8 +19,8 @@
(structure: #export equivalence
(Equivalence Tag)
(def: (= reference sample)
- (u1@= (:representation reference)
- (:representation sample))))
+ (u1//= (:representation reference)
+ (:representation sample))))
(template [<code> <name>]
[(def: #export <name>
diff --git a/stdlib/source/lux/target/jvm/field.lux b/stdlib/source/lux/target/jvm/field.lux
index 8541076f7..c5231ea26 100644
--- a/stdlib/source/lux/target/jvm/field.lux
+++ b/stdlib/source/lux/target/jvm/field.lux
@@ -8,7 +8,7 @@
[number (#+)
[i64 (#+)]]
[format
- [".F" binary (#+ Writer) ("#@." monoid)]]
+ [".F" binary (#+ Writer) ("#//." monoid)]]
[collection
["." row (#+ Row)]]]
[type
@@ -51,7 +51,7 @@
(def: #export (writer field)
(Writer Field)
- (`` ($_ binaryF@compose
+ (`` ($_ binaryF//compose
(~~ (template [<writer> <slot>]
[(<writer> (get@ <slot> field))]
diff --git a/stdlib/source/lux/target/jvm/method.lux b/stdlib/source/lux/target/jvm/method.lux
index daae88521..823cb1e11 100644
--- a/stdlib/source/lux/target/jvm/method.lux
+++ b/stdlib/source/lux/target/jvm/method.lux
@@ -10,13 +10,13 @@
[number (#+)
[i64 (#+)]]
["." format #_
- ["#" binary (#+ Writer) ("#@." monoid)]]
+ ["#" binary (#+ Writer) ("#//." monoid)]]
[collection
["." row (#+ Row)]]]
[type
[abstract (#+)]]]
["." // #_
- ["#." modifier (#+ Modifier modifiers:) ("#@." monoid)]
+ ["#." modifier (#+ Modifier modifiers:)]
["#." index (#+ Index)]
["#." attribute (#+ Attribute)
["#/." code]]
@@ -95,7 +95,7 @@
(def: #export (writer field)
(Writer Method)
- (`` ($_ format@compose
+ (`` ($_ format//compose
(~~ (template [<writer> <slot>]
[(<writer> (get@ <slot> field))]
diff --git a/stdlib/source/lux/target/jvm/modifier.lux b/stdlib/source/lux/target/jvm/modifier.lux
index c9fd34125..cd6d2671f 100644
--- a/stdlib/source/lux/target/jvm/modifier.lux
+++ b/stdlib/source/lux/target/jvm/modifier.lux
@@ -11,9 +11,7 @@
["." number (#+ hex)
["." i64]]
[format
- [".F" binary (#+ Writer)]]
- [collection
- ["." list ("#@." functor)]]]
+ [".F" binary (#+ Writer)]]]
[type
abstract]
[meta (#+ with-gensyms)]
diff --git a/stdlib/source/lux/target/jvm/reflection.lux b/stdlib/source/lux/target/jvm/reflection.lux
index 9cbcd4535..b87230b07 100644
--- a/stdlib/source/lux/target/jvm/reflection.lux
+++ b/stdlib/source/lux/target/jvm/reflection.lux
@@ -12,10 +12,10 @@
[data
[number
["n" nat]]
- ["." text ("#@." equivalence)
+ ["." text ("#//." equivalence)
["%" format (#+ format)]]
[collection
- ["." list ("#@." fold functor)]
+ ["." list ("#//." fold functor)]
["." array]
["." dictionary]]]]
["." // #_
@@ -131,8 +131,8 @@
(:coerce (java/lang/Class java/lang/Object))
java/lang/Class::getName)]
(`` (if (or (~~ (template [<reflection>]
- [(text@= (/reflection.reflection <reflection>)
- class-name)]
+ [(text//= (/reflection.reflection <reflection>)
+ class-name)]
[/reflection.boolean]
[/reflection.byte]
@@ -210,8 +210,8 @@
(:coerce (java/lang/Class java/lang/Object))
java/lang/Class::getName)]
(`` (cond (~~ (template [<reflection> <type>]
- [(text@= (/reflection.reflection <reflection>)
- class-name)
+ [(text//= (/reflection.reflection <reflection>)
+ class-name)
(#try.Success <type>)]
[/reflection.boolean /.boolean]
@@ -244,8 +244,8 @@
(let [class-name (|> reflection
(:coerce (java/lang/Class java/lang/Object))
java/lang/Class::getName)]
- (if (text@= (/reflection.reflection /reflection.void)
- class-name)
+ (if (text//= (/reflection.reflection /reflection.void)
+ class-name)
(#try.Success /.void)
<else>))
@@ -280,14 +280,14 @@
class-params (array.to-list (java/lang/Class::getTypeParameters class))
num-class-params (list.size class-params)
num-type-params (list.size params)]
- (if (text@= class-name name)
+ (if (text//= class-name name)
(if (n.= num-class-params num-type-params)
(|> params
- (list.zip/2 (list@map (|>> java/lang/reflect/TypeVariable::getName)
- class-params))
- (list@fold (function (_ [name paramT] mapping)
- (dictionary.put name paramT mapping))
- /lux.fresh)
+ (list.zip/2 (list//map (|>> java/lang/reflect/TypeVariable::getName)
+ class-params))
+ (list//fold (function (_ [name paramT] mapping)
+ (dictionary.put name paramT mapping))
+ /lux.fresh)
#try.Success)
(exception.throw ..type-parameter-mismatch [num-class-params num-type-params class type]))
(exception.throw ..cannot-correspond [class type])))
diff --git a/stdlib/source/lux/target/jvm/type.lux b/stdlib/source/lux/target/jvm/type.lux
index 613c8f5c3..9dbcb12c2 100644
--- a/stdlib/source/lux/target/jvm/type.lux
+++ b/stdlib/source/lux/target/jvm/type.lux
@@ -10,7 +10,7 @@
[number
["n" nat]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#//." functor)]]]
[type
abstract]]
["." // #_
@@ -79,14 +79,14 @@
(def: #export (class name parameters)
(-> External (List (Type Parameter)) (Type Class))
(:abstraction
- [(/signature.class name (list@map ..signature parameters))
+ [(/signature.class name (list//map ..signature parameters))
(/descriptor.class name)
(/reflection.class name)]))
(def: #export (declaration name variables)
(-> External (List (Type Var)) (Type Declaration))
(:abstraction
- [(/signature.declaration name (list@map ..signature variables))
+ [(/signature.declaration name (list//map ..signature variables))
(/descriptor.declaration name)
(/reflection.declaration name)]))
@@ -134,10 +134,10 @@
(List (Type Class))]
(Type Method))
(:abstraction
- [(/signature.method [(list@map ..signature inputs)
+ [(/signature.method [(list//map ..signature inputs)
(..signature output)
- (list@map ..signature exceptions)])
- (/descriptor.method [(list@map ..descriptor inputs)
+ (list//map ..signature exceptions)])
+ (/descriptor.method [(list//map ..descriptor inputs)
(..descriptor output)])
(:assume ..void)]))
diff --git a/stdlib/source/lux/target/jvm/type/alias.lux b/stdlib/source/lux/target/jvm/type/alias.lux
index d21cbc1c2..f384a0ea1 100644
--- a/stdlib/source/lux/target/jvm/type/alias.lux
+++ b/stdlib/source/lux/target/jvm/type/alias.lux
@@ -5,7 +5,7 @@
[control
["." try]
["." exception (#+ exception:)]
- ["<>" parser ("#@." monad)
+ ["<>" parser
["<t>" text (#+ Parser)]]]
[data
["." maybe]
diff --git a/stdlib/source/lux/target/jvm/type/descriptor.lux b/stdlib/source/lux/target/jvm/type/descriptor.lux
index abcbfbbb9..27e44ec7f 100644
--- a/stdlib/source/lux/target/jvm/type/descriptor.lux
+++ b/stdlib/source/lux/target/jvm/type/descriptor.lux
@@ -6,10 +6,10 @@
["." maybe]
[number
["n" nat]]
- ["." text ("#@." equivalence)
+ ["." text ("#//." equivalence)
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#//." functor)]]]
[type
abstract]]
["." // #_
@@ -92,7 +92,7 @@
(Descriptor Method))
(:abstraction
(format (|> inputs
- (list@map ..descriptor)
+ (list//map ..descriptor)
(text.join-with "")
(text.enclose ["(" ")"]))
(:representation output))))
@@ -101,7 +101,7 @@
(All [category] (Equivalence (Descriptor category)))
(def: (= parameter subject)
- (text@= (:representation parameter) (:representation subject))))
+ (text//= (:representation parameter) (:representation subject))))
(def: #export class-name
(-> (Descriptor Object) Internal)
diff --git a/stdlib/source/lux/target/jvm/type/lux.lux b/stdlib/source/lux/target/jvm/type/lux.lux
index 83a61de01..cbaf50a99 100644
--- a/stdlib/source/lux/target/jvm/type/lux.lux
+++ b/stdlib/source/lux/target/jvm/type/lux.lux
@@ -5,18 +5,18 @@
[control
["." try]
["." exception (#+ exception:)]
- ["<>" parser ("#@." monad)
+ ["<>" parser ("#//." monad)
["<t>" text (#+ Parser)]]]
[data
["." product]
- ["." text ("#@." equivalence)
+ ["." text ("#//." equivalence)
["%" format (#+ format)]]
[collection
["." array]
["." dictionary (#+ Dictionary)]]]
[type
abstract
- ["." check (#+ Check) ("#@." monad)]]]
+ ["." check (#+ Check) ("#//." monad)]]]
["." //
[category (#+ Void Value Return Method Primitive Object Class Array Var Parameter)]
["#." descriptor]
@@ -47,13 +47,13 @@
(def: void
(Parser (Check Type))
(<>.after //parser.void
- (<>@wrap (check@wrap .Any))))
+ (<>//wrap (check//wrap .Any))))
(template [<name> <parser> <reflection>]
[(def: <name>
(Parser (Check Type))
(<>.after <parser>
- (<>@wrap (check@wrap (#.Primitive (//reflection.reflection <reflection>) #.Nil)))))]
+ (<>//wrap (check//wrap (#.Primitive (//reflection.reflection <reflection>) #.Nil)))))]
[boolean //parser.boolean //reflection.boolean]
[byte //parser.byte //reflection.byte]
@@ -81,8 +81,8 @@
(def: wildcard
(Parser (Check Type))
(<>.after //parser.wildcard
- (<>@wrap (check@map product.right
- check.existential))))
+ (<>//wrap (check//map product.right
+ check.existential))))
(def: (var mapping)
(-> Mapping (Parser (Check Type)))
@@ -93,7 +93,7 @@
(check.throw ..unknown-var [var])
(#.Some type)
- (check@wrap type)))))
+ (check//wrap type)))))
(def: (class' parameter)
(-> (Parser (Check Type)) (Parser (Check Type)))
@@ -114,7 +114,7 @@
(-> (Parser (Check Type)) (Parser (Check Type)))
(|> (<>.after (<t>.this <prefix>))
## TODO: Re-enable Lower and Upper, instead of using the simplified limit.
- ## (<>@map (check@map (|>> <ctor> .type)))
+ ## (<>//map (check//map (|>> <ctor> .type)))
))]
[lower //signature.lower-prefix ..Lower]
@@ -140,25 +140,25 @@
(def: array
(-> (Parser (Check Type)) (Parser (Check Type)))
- (|>> (<>@map (check@map (function (_ elementT)
- (case elementT
- (#.Primitive name #.Nil)
- (if (`` (or (~~ (template [<reflection>]
- [(text@= (//reflection.reflection <reflection>) name)]
-
- [//reflection.boolean]
- [//reflection.byte]
- [//reflection.short]
- [//reflection.int]
- [//reflection.long]
- [//reflection.float]
- [//reflection.double]
- [//reflection.char]))))
- (#.Primitive (|> name //reflection.class //reflection.array //reflection.reflection) #.Nil)
- (|> elementT array.Array .type))
-
- _
- (|> elementT array.Array .type)))))
+ (|>> (<>//map (check//map (function (_ elementT)
+ (case elementT
+ (#.Primitive name #.Nil)
+ (if (`` (or (~~ (template [<reflection>]
+ [(text//= (//reflection.reflection <reflection>) name)]
+
+ [//reflection.boolean]
+ [//reflection.byte]
+ [//reflection.short]
+ [//reflection.int]
+ [//reflection.long]
+ [//reflection.float]
+ [//reflection.double]
+ [//reflection.char]))))
+ (#.Primitive (|> name //reflection.class //reflection.array //reflection.reflection) #.Nil)
+ (|> elementT array.Array .type))
+
+ _
+ (|> elementT array.Array .type)))))
(<>.after (<t>.this //descriptor.array-prefix))))
(def: #export (type mapping)
diff --git a/stdlib/source/lux/target/jvm/type/parser.lux b/stdlib/source/lux/target/jvm/type/parser.lux
index 499776376..d57bd41a3 100644
--- a/stdlib/source/lux/target/jvm/type/parser.lux
+++ b/stdlib/source/lux/target/jvm/type/parser.lux
@@ -5,7 +5,7 @@
[control
["." try]
["." function]
- ["<>" parser ("#@." monad)
+ ["<>" parser ("#//." monad)
["<t>" text (#+ Parser)]]]
[data
["." product]
@@ -25,7 +25,7 @@
[(def: #export <name>
(Parser (Type <category>))
(<>.after (<t>.this (//signature.signature <signature>))
- (<>@wrap <type>)))]
+ (<>//wrap <type>)))]
[Void void //signature.void //.void]
[Primitive boolean //signature.boolean //.boolean]
@@ -86,7 +86,7 @@
(def: #export var
(Parser (Type Var))
- (<>@map //.var ..var'))
+ (<>//map //.var ..var'))
(def: #export var?
(-> (Type Value) (Maybe Text))
@@ -106,7 +106,7 @@
[(def: <name>
(-> (Parser (Type Class)) (Parser (Type Parameter)))
(|>> (<>.after (<t>.this <prefix>))
- (<>@map <constructor>)))]
+ (<>//map <constructor>)))]
[lower //signature.lower-prefix //.lower]
[upper //signature.upper-prefix //.upper]
@@ -145,7 +145,7 @@
(def: #export array'
(-> (Parser (Type Value)) (Parser (Type Array)))
(|>> (<>.after (<t>.this //descriptor.array-prefix))
- (<>@map //.array)))
+ (<>//map //.array)))
(def: #export class
(Parser (Type Class))
diff --git a/stdlib/source/lux/target/jvm/type/reflection.lux b/stdlib/source/lux/target/jvm/type/reflection.lux
index 4ad2caf70..a0e0b0f5e 100644
--- a/stdlib/source/lux/target/jvm/type/reflection.lux
+++ b/stdlib/source/lux/target/jvm/type/reflection.lux
@@ -3,7 +3,7 @@
[abstract
[equivalence (#+ Equivalence)]]
[data
- ["." text ("#@." equivalence)
+ ["." text ("#//." equivalence)
["%" format (#+ format)]]]
[type
abstract]]
@@ -25,7 +25,7 @@
(All [category] (Equivalence (Reflection category)))
(def: (= parameter subject)
- (text@= (:representation parameter) (:representation subject))))
+ (text//= (:representation parameter) (:representation subject))))
(template [<category> <name> <reflection>]
[(def: #export <name>
diff --git a/stdlib/source/lux/target/jvm/type/signature.lux b/stdlib/source/lux/target/jvm/type/signature.lux
index 5fd3c3487..2fc8aa7c7 100644
--- a/stdlib/source/lux/target/jvm/type/signature.lux
+++ b/stdlib/source/lux/target/jvm/type/signature.lux
@@ -4,10 +4,10 @@
[equivalence (#+ Equivalence)]
[hash (#+ Hash)]]
[data
- ["." text ("#@." hash)
+ ["." text ("#//." hash)
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#//." functor)]]]
[type
abstract]]
["." // #_
@@ -84,7 +84,7 @@
_
(format ..parameters-start
(|> parameters
- (list@map ..signature)
+ (list//map ..signature)
(text.join-with ""))
..parameters-end))
//descriptor.class-suffix)))
@@ -109,25 +109,25 @@
(Signature Method))
(:abstraction
(format (|> inputs
- (list@map ..signature)
+ (list//map ..signature)
(text.join-with "")
(text.enclose [..arguments-start
..arguments-end]))
(:representation output)
(|> exceptions
- (list@map (|>> :representation (format ..exception-prefix)))
+ (list//map (|>> :representation (format ..exception-prefix)))
(text.join-with "")))))
(structure: #export equivalence
(All [category] (Equivalence (Signature category)))
(def: (= parameter subject)
- (text@= (:representation parameter)
- (:representation subject))))
+ (text//= (:representation parameter)
+ (:representation subject))))
(structure: #export hash
(All [category] (Hash (Signature category)))
(def: &equivalence ..equivalence)
- (def: hash (|>> :representation text@hash)))
+ (def: hash (|>> :representation text//hash)))
)