aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/target/jvm
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/target/jvm')
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode.lux44
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/address.lux68
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux16
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux52
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/instruction.lux174
-rw-r--r--stdlib/source/library/lux/target/jvm/class.lux14
-rw-r--r--stdlib/source/library/lux/target/jvm/constant.lux16
-rw-r--r--stdlib/source/library/lux/target/jvm/constant/pool.lux18
-rw-r--r--stdlib/source/library/lux/target/jvm/constant/tag.lux36
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/name.lux20
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/signed.lux26
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/unsigned.lux42
-rw-r--r--stdlib/source/library/lux/target/jvm/index.lux30
-rw-r--r--stdlib/source/library/lux/target/jvm/loader.lux42
-rw-r--r--stdlib/source/library/lux/target/jvm/modifier.lux58
-rw-r--r--stdlib/source/library/lux/target/jvm/reflection.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/type.lux94
-rw-r--r--stdlib/source/library/lux/target/jvm/type/category.lux12
-rw-r--r--stdlib/source/library/lux/target/jvm/type/descriptor.lux68
-rw-r--r--stdlib/source/library/lux/target/jvm/type/parser.lux24
-rw-r--r--stdlib/source/library/lux/target/jvm/type/reflection.lux50
-rw-r--r--stdlib/source/library/lux/target/jvm/type/signature.lux40
22 files changed, 476 insertions, 476 deletions
diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux
index 895d84f7a..a58bce01c 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode.lux
@@ -88,7 +88,7 @@
<then>
failure
- (:expected failure))])
+ (as_expected failure))])
(template: (try|in <it>)
[{try.#Success <it>}])
@@ -213,7 +213,7 @@
... {try.#Failure error}
failure
- (:expected failure)))))
+ (as_expected failure)))))
(implementation: .public monad
(Monad Bytecode)
@@ -234,11 +234,11 @@
... {try.#Failure error}
failure
- (:expected failure))
+ (as_expected failure))
... {try.#Failure error}
failure
- (:expected failure)))))
+ (as_expected failure)))))
(def: .public (when_continuous it)
(-> (Bytecode Any) (Bytecode Any))
@@ -611,17 +611,17 @@
(-> java/lang/Float Int)
(|>> java/lang/Float::floatToRawIntBits
ffi.int_to_long
- (:as Int)))
+ (as Int)))
(def: negative_zero_float_bits
- (|> -0.0 (:as java/lang/Double) ffi.double_to_float ..float_bits))
+ (|> -0.0 (as java/lang/Double) ffi.double_to_float ..float_bits))
(def: .public (float value)
(-> java/lang/Float (Bytecode Any))
(if (i.= ..negative_zero_float_bits
(..float_bits value))
(..arbitrary_float value)
- (case (|> value ffi.float_to_double (:as Frac))
+ (case (|> value ffi.float_to_double (as Frac))
(^.template [<special> <instruction>]
[<special> (..bytecode $0 $1 @_ <instruction> [])])
([+0.0 _.fconst_0]
@@ -651,23 +651,23 @@
(def: (arbitrary_double value)
(-> java/lang/Double (Bytecode Any))
(do ..monad
- [index (..lifted (//constant/pool.double (//constant.double (:as Frac value))))]
+ [index (..lifted (//constant/pool.double (//constant.double (as Frac value))))]
(..bytecode $0 $2 @_ _.ldc2_w/double [index])))
(def: double_bits
(-> java/lang/Double Int)
(|>> java/lang/Double::doubleToRawLongBits
- (:as Int)))
+ (as Int)))
(def: negative_zero_double_bits
- (..double_bits (:as java/lang/Double -0.0)))
+ (..double_bits (as java/lang/Double -0.0)))
(def: .public (double value)
(-> java/lang/Double (Bytecode Any))
(if (i.= ..negative_zero_double_bits
(..double_bits value))
(..arbitrary_double value)
- (case (:as Frac value)
+ (case (as Frac value)
(^.template [<special> <instruction>]
[<special> (..bytecode $0 $2 @_ <instruction> [])])
([+0.0 _.dconst_0]
@@ -950,9 +950,9 @@
(|> (list#mix (..acknowledge_label actual) tracker (list& default at_minimum afterwards))
(has #program_counter program_counter'))]
[(function (_ resolver)
- (let [get (: (-> Label (Maybe [Stack (Maybe Address)]))
- (function (_ label)
- (dictionary.value label resolver)))]
+ (let [get (is (-> Label (Maybe [Stack (Maybe Address)]))
+ (function (_ label)
+ (dictionary.value label resolver)))]
(case (do [! maybe.monad]
[@default (|> default get (monad.then ! product.right))
@at_minimum (|> at_minimum get (monad.then ! product.right))]
@@ -992,9 +992,9 @@
(|> (list#mix (..acknowledge_label actual) tracker (list& default (list#each product.right cases)))
(has #program_counter program_counter'))]
[(function (_ resolver)
- (let [get (: (-> Label (Maybe [Stack (Maybe Address)]))
- (function (_ label)
- (dictionary.value label resolver)))]
+ (let [get (is (-> Label (Maybe [Stack (Maybe Address)]))
+ (function (_ label)
+ (dictionary.value label resolver)))]
(case (do [! maybe.monad]
[@default (|> default get (monad.then ! product.right))]
(|> cases
@@ -1045,10 +1045,10 @@
(def: .public (multianewarray class dimensions)
(-> (Type Object) U1 (Bytecode Any))
(do ..monad
- [_ (: (Bytecode Any)
- (case (|> dimensions //unsigned.value)
- 0 (..except ..multiarray_cannot_be_zero_dimensional [class])
- _ (in [])))
+ [_ (is (Bytecode Any)
+ (case (|> dimensions //unsigned.value)
+ 0 (..except ..multiarray_cannot_be_zero_dimensional [class])
+ _ (in [])))
index (..lifted (//constant/pool.class (//name.internal (..reflection class))))]
(..bytecode (//unsigned.lifted/2 dimensions) $1 @_ _.multianewarray [index dimensions])))
@@ -1170,4 +1170,4 @@
... {try.#Failure error}
failure
- (:expected failure))))
+ (as_expected failure))))
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/address.lux b/stdlib/source/library/lux/target/jvm/bytecode/address.lux
index f91c4025f..f0df22eb4 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/address.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/address.lux
@@ -1,48 +1,48 @@
(.using
- [library
- [lux "*"
- [abstract
- [equivalence {"+" Equivalence}]
- [monad {"+" do}]]
- [control
- ["[0]" try {"+" Try}]]
- [data
- [format
- [binary {"+" Writer}]]
- [text
- ["%" format {"+" Format}]]]
- [math
- [number
- ["n" nat]]]
- [type
- abstract]]]
- ["[0]" // "_"
- [jump {"+" Big_Jump}]
- ["/[1]" // "_"
- [encoding
- ["[1][0]" unsigned {"+" U2}]
- ["[1][0]" signed {"+" S4}]]]])
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [monad {"+" do}]]
+ [control
+ ["[0]" try {"+" Try}]]
+ [data
+ [format
+ [binary {"+" Writer}]]
+ [text
+ ["%" format {"+" Format}]]]
+ [math
+ [number
+ ["n" nat]]]
+ [type
+ [abstract {"-" pattern}]]]]
+ ["[0]" // "_"
+ [jump {"+" Big_Jump}]
+ ["/[1]" // "_"
+ [encoding
+ ["[1][0]" unsigned {"+" U2}]
+ ["[1][0]" signed {"+" S4}]]]])
(abstract: .public Address
U2
(def: .public value
(-> Address U2)
- (|>> :representation))
+ (|>> representation))
(def: .public start
Address
- (|> 0 ///unsigned.u2 try.trusted :abstraction))
+ (|> 0 ///unsigned.u2 try.trusted abstraction))
(def: .public (move distance)
(-> U2 (-> Address (Try Address)))
- (|>> :representation
+ (|>> representation
(///unsigned.+/2 distance)
- (# try.functor each (|>> :abstraction))))
+ (# try.functor each (|>> abstraction))))
(def: with_sign
(-> Address (Try S4))
- (|>> :representation ///unsigned.value .int ///signed.s4))
+ (|>> representation ///unsigned.value .int ///signed.s4))
(def: .public (jump from to)
(-> Address Address (Try Big_Jump))
@@ -53,22 +53,22 @@
(def: .public (after? reference subject)
(-> Address Address Bit)
- (n.> (|> reference :representation ///unsigned.value)
- (|> subject :representation ///unsigned.value)))
+ (n.> (|> reference representation ///unsigned.value)
+ (|> subject representation ///unsigned.value)))
(implementation: .public equivalence
(Equivalence Address)
(def: (= reference subject)
(# ///unsigned.equivalence =
- (:representation reference)
- (:representation subject))))
+ (representation reference)
+ (representation subject))))
(def: .public writer
(Writer Address)
- (|>> :representation ///unsigned.writer/2))
+ (|>> representation ///unsigned.writer/2))
(def: .public format
(Format Address)
- (|>> :representation ///unsigned.value %.nat))
+ (|>> representation ///unsigned.value %.nat))
)
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 4f42ccffc..b7952504e 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
@@ -14,7 +14,7 @@
[number
["n" nat]]]
[type
- abstract]]]
+ [abstract {"-" pattern}]]]]
["[0]" ///// "_"
[encoding
["[1][0]" unsigned {"+" U1 U2}]]
@@ -33,7 +33,7 @@
(def: .public registry
(-> U2 Registry)
- (|>> :abstraction))
+ (|>> abstraction))
(def: (minimal type)
(-> (Type Method) Nat)
@@ -61,18 +61,18 @@
(def: .public equivalence
(Equivalence Registry)
(# equivalence.functor each
- (|>> :representation)
+ (|>> representation)
/////unsigned.equivalence))
(def: .public writer
(Writer Registry)
- (|>> :representation /////unsigned.writer/2))
+ (|>> representation /////unsigned.writer/2))
(def: .public (has needed)
(-> Registry Registry Registry)
- (|>> :representation
- (/////unsigned.max/2 (:representation needed))
- :abstraction))
+ (|>> representation
+ (/////unsigned.max/2 (representation needed))
+ abstraction))
(template [<name> <extra>]
[(def: .public <name>
@@ -81,7 +81,7 @@
(|>> /////unsigned.lifted/2
(/////unsigned.+/2 extra)
try.trusted
- :abstraction)))]
+ abstraction)))]
[for ..normal]
[for_wide ..wide]
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 e67bb157b..4b7b29804 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
@@ -1,21 +1,21 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" equivalence {"+" Equivalence}]]
- [control
- ["[0]" maybe]
- ["[0]" try {"+" Try}]]
- [data
- [text
- ["%" format {"+" Format}]]
- [format
- [binary {"+" Writer}]]]
- [type
- abstract]]]
- ["[0]" ///// "_"
- [encoding
- ["[1][0]" unsigned {"+" U2}]]])
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" equivalence {"+" Equivalence}]]
+ [control
+ ["[0]" maybe]
+ ["[0]" try {"+" Try}]]
+ [data
+ [text
+ ["%" format {"+" Format}]]
+ [format
+ [binary {"+" Writer}]]]
+ [type
+ [abstract {"-" pattern}]]]]
+ ["[0]" ///// "_"
+ [encoding
+ ["[1][0]" unsigned {"+" U2}]]])
(abstract: .public Stack
U2
@@ -23,7 +23,7 @@
(template [<frames> <name>]
[(def: .public <name>
Stack
- (|> <frames> /////unsigned.u2 maybe.trusted :abstraction))]
+ (|> <frames> /////unsigned.u2 maybe.trusted abstraction))]
[0 empty]
[1 catch]
@@ -32,21 +32,21 @@
(def: .public equivalence
(Equivalence Stack)
(# equivalence.functor each
- (|>> :representation)
+ (|>> representation)
/////unsigned.equivalence))
(def: .public writer
(Writer Stack)
- (|>> :representation /////unsigned.writer/2))
+ (|>> representation /////unsigned.writer/2))
(def: stack
(-> U2 Stack)
- (|>> :abstraction))
+ (|>> abstraction))
(template [<op> <name>]
[(def: .public (<name> amount)
(-> U2 (-> Stack (Try Stack)))
- (|>> :representation
+ (|>> representation
(<op> amount)
(# try.functor each ..stack)))]
@@ -56,13 +56,13 @@
(def: .public (max left right)
(-> Stack Stack Stack)
- (:abstraction
- (/////unsigned.max/2 (:representation left)
- (:representation right))))
+ (abstraction
+ (/////unsigned.max/2 (representation left)
+ (representation right))))
(def: .public format
(Format Stack)
- (|>> :representation /////unsigned.value %.nat))
+ (|>> representation /////unsigned.value %.nat))
)
(def: .public length
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
index 4f371461a..237901cf1 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
@@ -23,7 +23,7 @@
[number {"+" hex}
["n" nat]]]
[type
- abstract]]]
+ [abstract {"-" pattern}]]]]
["[0]" // "_"
["[1][0]" address {"+" Address}]
["[1][0]" jump {"+" Jump Big_Jump}]
@@ -227,11 +227,11 @@
(def: code
(-> Primitive_Array_Type U1)
- (|>> :representation))
+ (|>> representation))
(template [<code> <name>]
[(def: .public <name>
- (|> <code> ///unsigned.u1 try.trusted :abstraction))]
+ (|> <code> ///unsigned.u1 try.trusted abstraction))]
[04 t_boolean]
[05 t_char]
@@ -576,18 +576,18 @@
(def: .public tableswitch
[(-> Nat Estimator)
(-> S4 Big_Jump [Big_Jump (List Big_Jump)] Instruction)]
- (let [estimator (: (-> Nat Estimator)
- (function (_ amount_of_afterwards offset)
- (|> ($_ n.+
- (///unsigned.value ..opcode_size)
- (switch_padding (///unsigned.value (//address.value offset)))
- (///unsigned.value ..big_jump_size)
- (///unsigned.value ..integer_size)
- (///unsigned.value ..integer_size)
- (n.* (///unsigned.value ..big_jump_size)
- (++ amount_of_afterwards)))
- ///unsigned.u2
- try.trusted)))]
+ (let [estimator (is (-> Nat Estimator)
+ (function (_ amount_of_afterwards offset)
+ (|> ($_ n.+
+ (///unsigned.value ..opcode_size)
+ (switch_padding (///unsigned.value (//address.value offset)))
+ (///unsigned.value ..big_jump_size)
+ (///unsigned.value ..integer_size)
+ (///unsigned.value ..integer_size)
+ (n.* (///unsigned.value ..big_jump_size)
+ (++ amount_of_afterwards)))
+ ///unsigned.u2
+ try.trusted)))]
[estimator
(function (_ minimum default [at_minimum afterwards])
(let [amount_of_afterwards (list.size afterwards)
@@ -599,40 +599,40 @@
[size (///unsigned.u2 size)]
(# ! each (|>> estimator ///unsigned.value)
(//address.move size //address.start))))
- tableswitch_mutation (: Mutation
- (function (_ [offset binary])
- [(n.+ tableswitch_size offset)
- (try.trusted
- (do [! try.monad]
- [amount_of_afterwards (|> amount_of_afterwards .int ///signed.s4)
- maximum (///signed.+/4 minimum amount_of_afterwards)]
- (in (let [_ (binary.with/1! offset (hex "AA") binary)
- offset (n.+ (///unsigned.value ..opcode_size) offset)
- _ (case padding
- 3 (|> binary
- (binary.with/1! offset 0)
- (binary.with/2! (++ offset) 0))
- 2 (binary.with/2! offset 0 binary)
- 1 (binary.with/1! offset 0 binary)
- _ binary)
- offset (n.+ padding offset)
- _ (binary.with/4! offset (///signed.value default) binary)
- offset (n.+ (///unsigned.value ..big_jump_size) offset)
- _ (binary.with/4! offset (///signed.value minimum) binary)
- offset (n.+ (///unsigned.value ..integer_size) offset)
- _ (binary.with/4! offset (///signed.value maximum) binary)]
- (loop [offset (n.+ (///unsigned.value ..integer_size) offset)
- afterwards (: (List Big_Jump)
- {.#Item at_minimum afterwards})]
- (case afterwards
- {.#End}
- binary
-
- {.#Item head tail}
- (exec
- (binary.with/4! offset (///signed.value head) binary)
- (again (n.+ (///unsigned.value ..big_jump_size) offset)
- tail))))))))]))]
+ tableswitch_mutation (is Mutation
+ (function (_ [offset binary])
+ [(n.+ tableswitch_size offset)
+ (try.trusted
+ (do [! try.monad]
+ [amount_of_afterwards (|> amount_of_afterwards .int ///signed.s4)
+ maximum (///signed.+/4 minimum amount_of_afterwards)]
+ (in (let [_ (binary.with/1! offset (hex "AA") binary)
+ offset (n.+ (///unsigned.value ..opcode_size) offset)
+ _ (case padding
+ 3 (|> binary
+ (binary.with/1! offset 0)
+ (binary.with/2! (++ offset) 0))
+ 2 (binary.with/2! offset 0 binary)
+ 1 (binary.with/1! offset 0 binary)
+ _ binary)
+ offset (n.+ padding offset)
+ _ (binary.with/4! offset (///signed.value default) binary)
+ offset (n.+ (///unsigned.value ..big_jump_size) offset)
+ _ (binary.with/4! offset (///signed.value minimum) binary)
+ offset (n.+ (///unsigned.value ..integer_size) offset)
+ _ (binary.with/4! offset (///signed.value maximum) binary)]
+ (loop [offset (n.+ (///unsigned.value ..integer_size) offset)
+ afterwards (is (List Big_Jump)
+ {.#Item at_minimum afterwards})]
+ (case afterwards
+ {.#End}
+ binary
+
+ {.#Item head tail}
+ (exec
+ (binary.with/4! offset (///signed.value head) binary)
+ (again (n.+ (///unsigned.value ..big_jump_size) offset)
+ tail))))))))]))]
[(n.+ tableswitch_size
size)
(|>> mutation tableswitch_mutation)]))))]))
@@ -642,16 +642,16 @@
(-> Big_Jump (List [S4 Big_Jump]) Instruction)]
(let [case_size (n.+ (///unsigned.value ..integer_size)
(///unsigned.value ..big_jump_size))
- estimator (: (-> Nat Estimator)
- (function (_ amount_of_cases offset)
- (|> ($_ n.+
- (///unsigned.value ..opcode_size)
- (switch_padding (///unsigned.value (//address.value offset)))
- (///unsigned.value ..big_jump_size)
- (///unsigned.value ..integer_size)
- (n.* amount_of_cases case_size))
- ///unsigned.u2
- try.trusted)))]
+ estimator (is (-> Nat Estimator)
+ (function (_ amount_of_cases offset)
+ (|> ($_ n.+
+ (///unsigned.value ..opcode_size)
+ (switch_padding (///unsigned.value (//address.value offset)))
+ (///unsigned.value ..big_jump_size)
+ (///unsigned.value ..integer_size)
+ (n.* amount_of_cases case_size))
+ ///unsigned.u2
+ try.trusted)))]
[estimator
(function (_ default cases)
(let [amount_of_cases (list.size cases)
@@ -663,34 +663,34 @@
[size (///unsigned.u2 size)]
(# ! each (|>> estimator ///unsigned.value)
(//address.move size //address.start))))
- lookupswitch_mutation (: Mutation
- (function (_ [offset binary])
- [(n.+ lookupswitch_size offset)
- (let [_ (binary.with/1! offset (hex "AB") binary)
- offset (n.+ (///unsigned.value ..opcode_size) offset)
- _ (case padding
- 3 (|> binary
- (binary.with/1! offset 0)
- (binary.with/2! (++ offset) 0))
- 2 (binary.with/2! offset 0 binary)
- 1 (binary.with/1! offset 0 binary)
- _ binary)
- offset (n.+ padding offset)
- _ (binary.with/4! offset (///signed.value default) binary)
- offset (n.+ (///unsigned.value ..big_jump_size) offset)
- _ (binary.with/4! offset amount_of_cases binary)]
- (loop [offset (n.+ (///unsigned.value ..integer_size) offset)
- cases cases]
- (case cases
- {.#End}
- binary
-
- {.#Item [value jump] tail}
- (exec
- (binary.with/4! offset (///signed.value value) binary)
- (binary.with/4! (n.+ (///unsigned.value ..integer_size) offset) (///signed.value jump) binary)
- (again (n.+ case_size offset)
- tail)))))]))]
+ lookupswitch_mutation (is Mutation
+ (function (_ [offset binary])
+ [(n.+ lookupswitch_size offset)
+ (let [_ (binary.with/1! offset (hex "AB") binary)
+ offset (n.+ (///unsigned.value ..opcode_size) offset)
+ _ (case padding
+ 3 (|> binary
+ (binary.with/1! offset 0)
+ (binary.with/2! (++ offset) 0))
+ 2 (binary.with/2! offset 0 binary)
+ 1 (binary.with/1! offset 0 binary)
+ _ binary)
+ offset (n.+ padding offset)
+ _ (binary.with/4! offset (///signed.value default) binary)
+ offset (n.+ (///unsigned.value ..big_jump_size) offset)
+ _ (binary.with/4! offset amount_of_cases binary)]
+ (loop [offset (n.+ (///unsigned.value ..integer_size) offset)
+ cases cases]
+ (case cases
+ {.#End}
+ binary
+
+ {.#Item [value jump] tail}
+ (exec
+ (binary.with/4! offset (///signed.value value) binary)
+ (binary.with/4! (n.+ (///unsigned.value ..integer_size) offset) (///signed.value jump) binary)
+ (again (n.+ case_size offset)
+ tail)))))]))]
[(n.+ lookupswitch_size
size)
(|>> mutation lookupswitch_mutation)]))))]))
diff --git a/stdlib/source/library/lux/target/jvm/class.lux b/stdlib/source/library/lux/target/jvm/class.lux
index 73966259f..4d2cf203c 100644
--- a/stdlib/source/library/lux/target/jvm/class.lux
+++ b/stdlib/source/library/lux/target/jvm/class.lux
@@ -77,13 +77,13 @@
(do [! //pool.monad]
[@this (//pool.class this)
@super (//pool.class super)
- @interfaces (: (Resource (Sequence (Index //constant.Class)))
- (monad.mix ! (function (_ interface @interfaces)
- (do !
- [@interface (//pool.class interface)]
- (in (sequence.suffix @interface @interfaces))))
- sequence.empty
- interfaces))]
+ @interfaces (is (Resource (Sequence (Index //constant.Class)))
+ (monad.mix ! (function (_ interface @interfaces)
+ (do !
+ [@interface (//pool.class interface)]
+ (in (sequence.suffix @interface @interfaces))))
+ sequence.empty
+ interfaces))]
(in [@this @super @interfaces])))
(def: .public (class version modifier
diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux
index 71aab1ed3..1afa70f79 100644
--- a/stdlib/source/library/lux/target/jvm/constant.lux
+++ b/stdlib/source/library/lux/target/jvm/constant.lux
@@ -22,7 +22,7 @@
["[0]" int]
["[0]" frac]]]
[type
- abstract]]]
+ [abstract {"-" pattern}]]]]
["[0]" / "_"
["[1][0]" tag]
["/[1]" // "_"
@@ -45,11 +45,11 @@
(def: .public index
(-> Class (Index UTF8))
- (|>> :representation))
+ (|>> representation))
(def: .public class
(-> (Index UTF8) Class)
- (|>> :abstraction))
+ (|>> abstraction))
(def: .public class_equivalence
(Equivalence Class)
@@ -59,7 +59,7 @@
(def: class_writer
(Writer Class)
- (|>> :representation //index.writer))
+ (|>> representation //index.writer))
)
(import: java/lang/Float
@@ -87,14 +87,14 @@
(def: .public value
(All (_ kind) (-> (Value kind) kind))
- (|>> :representation))
+ (|>> representation))
(def: .public (value_equivalence Equivalence<kind>)
(All (_ kind)
(-> (Equivalence kind)
(Equivalence (Value kind))))
(# equivalence.functor each
- (|>> :representation)
+ (|>> representation)
Equivalence<kind>))
(template [<constructor> <type> <marker>]
@@ -103,7 +103,7 @@
(def: .public <constructor>
(-> <marker> <type>)
- (|>> :abstraction))]
+ (|>> abstraction))]
[integer Integer I32]
[float Float java/lang/Float]
@@ -115,7 +115,7 @@
(template [<writer_name> <type> <write> <writer>]
[(def: <writer_name>
(Writer <type>)
- (`` (|>> :representation
+ (`` (|>> representation
(~~ (template.spliced <write>))
(~~ (template.spliced <writer>)))))]
diff --git a/stdlib/source/library/lux/target/jvm/constant/pool.lux b/stdlib/source/library/lux/target/jvm/constant/pool.lux
index 666531963..e2fcfd655 100644
--- a/stdlib/source/library/lux/target/jvm/constant/pool.lux
+++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux
@@ -55,7 +55,7 @@
... {try.#Failure error}
failure
- (:expected failure)))))
+ (as_expected failure)))))
(implementation: .public monad
(Monad Resource)
@@ -74,7 +74,7 @@
... {try.#Failure error}
failure
- (:expected failure)))))
+ (as_expected failure)))))
(template: (try|each <binding> <value> <body>)
[(case <value>
@@ -83,7 +83,7 @@
... {try.#Failure error}
failure
- (:expected failure))])
+ (as_expected failure))])
(template: (try|in <it>)
[{try.#Success <it>}])
@@ -108,11 +108,11 @@
{try.#Failure _}
(<| (let [new {<tag> <value>'}])
(try|each @new (//unsigned.u2 (//.size new)))
- (try|each next (: (Try Index)
- (|> current
- //index.value
- (//unsigned.+/2 @new)
- (# try.monad each //index.index))))
+ (try|each next (is (Try Index)
+ (|> current
+ //index.value
+ (//unsigned.+/2 @new)
+ (# try.monad each //index.index))))
(try|in [[next
(sequence.suffix [current new] pool)]
current]))))))])
@@ -128,7 +128,7 @@
... {try.#Failure error}
failure
- (:expected failure))])
+ (as_expected failure))])
(type: (Adder of)
(-> of (Resource (Index of))))
diff --git a/stdlib/source/library/lux/target/jvm/constant/tag.lux b/stdlib/source/library/lux/target/jvm/constant/tag.lux
index 8d8d162aa..36acb163f 100644
--- a/stdlib/source/library/lux/target/jvm/constant/tag.lux
+++ b/stdlib/source/library/lux/target/jvm/constant/tag.lux
@@ -1,18 +1,18 @@
(.using
- [library
- [lux "*"
- [abstract
- [equivalence {"+" Equivalence}]]
- [control
- ["[0]" try]]
- [data
- [format
- [binary {"+" Writer}]]]
- [type
- abstract]]]
- ["[0]" /// "_"
- [encoding
- ["[1][0]" unsigned {"+" U1} ("u1//[0]" equivalence)]]])
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]]
+ [control
+ ["[0]" try]]
+ [data
+ [format
+ [binary {"+" Writer}]]]
+ [type
+ [abstract {"-" pattern}]]]]
+ ["[0]" /// "_"
+ [encoding
+ ["[1][0]" unsigned {"+" U1} ("u1//[0]" equivalence)]]])
(abstract: .public Tag
U1
@@ -20,13 +20,13 @@
(implementation: .public equivalence
(Equivalence Tag)
(def: (= reference sample)
- (u1//= (:representation reference)
- (:representation sample))))
+ (u1//= (representation reference)
+ (representation sample))))
(template [<code> <name>]
[(def: .public <name>
Tag
- (|> <code> ///unsigned.u1 try.trusted :abstraction))]
+ (|> <code> ///unsigned.u1 try.trusted abstraction))]
[01 utf8]
[03 integer]
@@ -46,5 +46,5 @@
(def: .public writer
(Writer Tag)
- (|>> :representation ///unsigned.writer/1))
+ (|>> 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 c935d07b0..247300884 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/name.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/name.lux
@@ -1,11 +1,11 @@
(.using
- [library
- [lux "*"
- [data
- ["[0]" text
- ["%" format {"+" format}]]]
- [type
- abstract]]])
+ [library
+ [lux "*"
+ [data
+ ["[0]" text
+ ["%" format {"+" format}]]]
+ [type
+ [abstract {"-" pattern}]]]])
(def: .public internal_separator "/")
(def: .public external_separator ".")
@@ -20,15 +20,15 @@
(-> External Internal)
(|>> (text.replaced ..external_separator
..internal_separator)
- :abstraction))
+ abstraction))
(def: .public read
(-> Internal Text)
- (|>> :representation))
+ (|>> representation))
(def: .public external
(-> Internal External)
- (|>> :representation
+ (|>> representation
(text.replaced ..internal_separator
..external_separator))))
diff --git a/stdlib/source/library/lux/target/jvm/encoding/signed.lux b/stdlib/source/library/lux/target/jvm/encoding/signed.lux
index dba35fc11..981d8c3f7 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/signed.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/signed.lux
@@ -20,26 +20,26 @@
["n" nat]
["i" int]]]
[type
- abstract]]])
+ [abstract {"-" pattern}]]]])
(abstract: .public (Signed brand)
Int
(def: .public value
(-> (Signed Any) Int)
- (|>> :representation))
+ (|>> representation))
(implementation: .public equivalence
(All (_ brand) (Equivalence (Signed brand)))
(def: (= reference sample)
- (i.= (:representation reference) (:representation sample))))
+ (i.= (representation reference) (representation sample))))
(implementation: .public order
(All (_ brand) (Order (Signed brand)))
(def: &equivalence ..equivalence)
(def: (< reference sample)
- (i.< (:representation reference) (:representation sample))))
+ (i.< (representation reference) (representation sample))))
(exception: .public (value_exceeds_the_scope [value Int
scope Nat])
@@ -56,31 +56,31 @@
(def: .public <maximum>
<name>
- (|> <bytes> (n.* i64.bits_per_byte) -- i64.mask :abstraction))
+ (|> <bytes> (n.* i64.bits_per_byte) -- i64.mask abstraction))
(def: .public <minimum>
<name>
- (let [it (:representation <maximum>)]
- (:abstraction (-- (i.- it +0)))))
+ (let [it (representation <maximum>)]
+ (abstraction (-- (i.- it +0)))))
(def: .public <constructor>
(-> Int (Try <name>))
- (let [positive (:representation <maximum>)
+ (let [positive (representation <maximum>)
negative (i64.not positive)]
(function (_ value)
(if (i.= (if (i.< +0 value)
(i64.or negative value)
(i64.and positive value))
value)
- {try.#Success (:abstraction value)}
+ {try.#Success (abstraction value)}
(exception.except ..value_exceeds_the_scope [value <size>])))))
(template [<abstract_operation> <concrete_operation>]
[(def: .public (<abstract_operation> parameter subject)
(-> <name> <name> (Try <name>))
(<constructor>
- (<concrete_operation> (:representation parameter)
- (:representation subject))))]
+ (<concrete_operation> (representation parameter)
+ (representation subject))))]
[<+> i.+]
[<-> i.-]
@@ -94,7 +94,7 @@
(template [<name> <from> <to>]
[(def: .public <name>
(-> <from> <to>)
- (|>> :transmutation))]
+ (|>> transmutation))]
[lifted/2 S1 S2]
[lifted/4 S2 S4]
@@ -103,7 +103,7 @@
(template [<writer_name> <type> <writer>]
[(def: .public <writer_name>
(Writer <type>)
- (|>> :representation <writer>))]
+ (|>> representation <writer>))]
[writer/1 S1 format.bits/8]
[writer/2 S2 format.bits/16]
diff --git a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
index 795f30716..d733b0480 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
@@ -19,28 +19,28 @@
["n" nat]
["[0]" i64]]]
[type
- abstract]]])
+ [abstract {"-" pattern}]]]])
(abstract: .public (Unsigned brand)
Nat
(def: .public value
(-> (Unsigned Any) Nat)
- (|>> :representation))
+ (|>> representation))
(implementation: .public equivalence
(All (_ brand) (Equivalence (Unsigned brand)))
(def: (= reference sample)
- (n.= (:representation reference)
- (:representation sample))))
+ (n.= (representation reference)
+ (representation sample))))
(implementation: .public order
(All (_ brand) (Order (Unsigned brand)))
(def: &equivalence ..equivalence)
(def: (< reference sample)
- (n.< (:representation reference)
- (:representation sample))))
+ (n.< (representation reference)
+ (representation sample))))
(exception: .public (value_exceeds_the_maximum [type Symbol
value Nat
@@ -48,7 +48,7 @@
(exception.report
"Type" (%.symbol type)
"Value" (%.nat value)
- "Maximum" (%.nat (:representation maximum))))
+ "Maximum" (%.nat (representation maximum))))
(exception: .public [brand] (subtraction_cannot_yield_negative_value
[type Symbol
@@ -56,8 +56,8 @@
subject (Unsigned brand)])
(exception.report
"Type" (%.symbol type)
- "Parameter" (%.nat (:representation parameter))
- "Subject" (%.nat (:representation subject))))
+ "Parameter" (%.nat (representation parameter))
+ "Subject" (%.nat (representation subject))))
(template [<bytes> <name> <size> <constructor> <maximum> <+> <-> <max>]
[(with_expansions [<raw> (template.symbol [<name> "'"])]
@@ -68,32 +68,32 @@
(def: .public <maximum>
<name>
- (|> <bytes> (n.* i64.bits_per_byte) i64.mask :abstraction))
+ (|> <bytes> (n.* i64.bits_per_byte) i64.mask abstraction))
(def: .public (<constructor> value)
(-> Nat (Try <name>))
- (if (n.> (:representation <maximum>) value)
+ (if (n.> (representation <maximum>) value)
(exception.except ..value_exceeds_the_maximum [(symbol <name>) value <maximum>])
- {try.#Success (:abstraction value)}))
+ {try.#Success (abstraction value)}))
(def: .public (<+> parameter subject)
(-> <name> <name> (Try <name>))
(<constructor>
- (n.+ (:representation parameter)
- (:representation subject))))
+ (n.+ (representation parameter)
+ (representation subject))))
(def: .public (<-> parameter subject)
(-> <name> <name> (Try <name>))
- (let [parameter' (:representation parameter)
- subject' (:representation subject)]
+ (let [parameter' (representation parameter)
+ subject' (representation subject)]
(if (n.> subject' parameter')
(exception.except ..subtraction_cannot_yield_negative_value [(symbol <name>) parameter subject])
- {try.#Success (:abstraction (n.- parameter' subject'))})))
+ {try.#Success (abstraction (n.- parameter' subject'))})))
(def: .public (<max> left right)
(-> <name> <name> <name>)
- (:abstraction (n.max (:representation left)
- (:representation right))))]
+ (abstraction (n.max (representation left)
+ (representation right))))]
[1 U1 bytes/1 u1 maximum/1 +/1 -/1 max/1]
[2 U2 bytes/2 u2 maximum/2 +/2 -/2 max/2]
@@ -103,7 +103,7 @@
(template [<name> <from> <to>]
[(def: .public <name>
(-> <from> <to>)
- (|>> :transmutation))]
+ (|>> transmutation))]
[lifted/2 U1 U2]
[lifted/4 U2 U4]
@@ -112,7 +112,7 @@
(template [<writer_name> <type> <writer>]
[(def: .public <writer_name>
(Writer <type>)
- (|>> :representation <writer>))]
+ (|>> representation <writer>))]
[writer/1 U1 format.bits/8]
[writer/2 U2 format.bits/16]
diff --git a/stdlib/source/library/lux/target/jvm/index.lux b/stdlib/source/library/lux/target/jvm/index.lux
index 8b339bc89..b6a0eb318 100644
--- a/stdlib/source/library/lux/target/jvm/index.lux
+++ b/stdlib/source/library/lux/target/jvm/index.lux
@@ -1,16 +1,16 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" equivalence {"+" Equivalence}]]
- [data
- [format
- [binary {"+" Writer}]]]
- [type
- abstract]]]
- ["[0]" // "_"
- [encoding
- ["[1][0]" unsigned {"+" U2}]]])
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" equivalence {"+" Equivalence}]]
+ [data
+ [format
+ [binary {"+" Writer}]]]
+ [type
+ [abstract {"-" pattern}]]]]
+ ["[0]" // "_"
+ [encoding
+ ["[1][0]" unsigned {"+" U2}]]])
(def: .public length
//unsigned.bytes/2)
@@ -20,11 +20,11 @@
(def: .public index
(All (_ kind) (-> U2 (Index kind)))
- (|>> :abstraction))
+ (|>> abstraction))
(def: .public value
(-> (Index Any) U2)
- (|>> :representation))
+ (|>> representation))
(def: .public equivalence
(All (_ kind) (Equivalence (Index kind)))
@@ -34,5 +34,5 @@
(def: .public writer
(All (_ kind) (Writer (Index kind)))
- (|>> :representation //unsigned.writer/2))
+ (|>> 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 71d6dc712..bff3cb325 100644
--- a/stdlib/source/library/lux/target/jvm/loader.lux
+++ b/stdlib/source/library/lux/target/jvm/loader.lux
@@ -68,13 +68,13 @@
(def: java/lang/ClassLoader::defineClass
java/lang/reflect/Method
(let [signature (|> (ffi.array <elemT> 4)
- (ffi.write! 0 (:as <elemT>
- (ffi.class_for java/lang/String)))
+ (ffi.write! 0 (as <elemT>
+ (ffi.class_for java/lang/String)))
(ffi.write! 1 (java/lang/Object::getClass (ffi.array byte 0)))
- (ffi.write! 2 (:as <elemT>
- (java/lang/Integer::TYPE)))
- (ffi.write! 3 (:as <elemT>
- (java/lang/Integer::TYPE))))]
+ (ffi.write! 2 (as <elemT>
+ (java/lang/Integer::TYPE)))
+ (ffi.write! 3 (as <elemT>
+ (java/lang/Integer::TYPE))))]
(do_to (java/lang/Class::getDeclaredMethod (ffi.as_string "defineClass")
signature
(ffi.class_for java/lang/ClassLoader))
@@ -82,19 +82,19 @@
(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)
- (:as java/lang/Object
- bytecode)
- (:as java/lang/Object
- (|> 0
- (:as (Primitive "java.lang.Long"))
- ffi.long_to_int))
- (:as java/lang/Object
- (|> bytecode
- binary.size
- (:as (Primitive "java.lang.Long"))
- ffi.long_to_int))))]
+ (let [signature (array.of_list (list (as java/lang/Object
+ class_name)
+ (as java/lang/Object
+ bytecode)
+ (as java/lang/Object
+ (|> 0
+ (as (Primitive "java.lang.Long"))
+ ffi.long_to_int))
+ (as java/lang/Object
+ (|> bytecode
+ binary.size
+ (as (Primitive "java.lang.Long"))
+ ffi.long_to_int))))]
(java/lang/reflect/Method::invoke loader signature java/lang/ClassLoader::defineClass)))
(def: .public (new_library _)
@@ -114,13 +114,13 @@
(java/lang/ClassLoader (findClass self [class_name java/lang/String])
(java/lang/Class [? < java/lang/Object])
"throws" [java/lang/ClassNotFoundException]
- (let [class_name (:as Text class_name)
+ (let [class_name (as Text class_name)
classes (|> library atom.read! io.run!)]
(case (dictionary.value class_name classes)
{.#Some bytecode}
(case (..define class_name bytecode (<| <cast> self))
{try.#Success class}
- (:expected class)
+ (as_expected class)
{try.#Failure error}
(panic! (exception.error ..cannot_define [class_name error])))
diff --git a/stdlib/source/library/lux/target/jvm/modifier.lux b/stdlib/source/library/lux/target/jvm/modifier.lux
index bf5d79aa2..24e442a21 100644
--- a/stdlib/source/library/lux/target/jvm/modifier.lux
+++ b/stdlib/source/library/lux/target/jvm/modifier.lux
@@ -1,52 +1,52 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" equivalence {"+" Equivalence}]
- ["[0]" monoid {"+" Monoid}]]
- [control
- ["[0]" try]
- ["<>" parser
- ["<[0]>" code]]]
- [data
- [format
- ["[0]F" binary {"+" Writer}]]]
- [macro {"+" with_symbols}
- [syntax {"+" syntax:}]
- ["[0]" code]]
- [math
- ["[0]" number {"+" hex}
- ["[0]" i64]]]
- [type
- abstract]]]
- ["[0]" // "_"
- [encoding
- ["[1][0]" unsigned]]])
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" equivalence {"+" Equivalence}]
+ ["[0]" monoid {"+" Monoid}]]
+ [control
+ ["[0]" try]
+ ["<>" parser
+ ["<[0]>" code]]]
+ [data
+ [format
+ ["[0]F" binary {"+" Writer}]]]
+ [macro {"+" with_symbols}
+ [syntax {"+" syntax:}]
+ ["[0]" code]]
+ [math
+ ["[0]" number {"+" hex}
+ ["[0]" i64]]]
+ [type
+ [abstract {"-" pattern}]]]]
+ ["[0]" // "_"
+ [encoding
+ ["[1][0]" unsigned]]])
(abstract: .public (Modifier of)
//unsigned.U2
(def: .public code
(-> (Modifier Any) //unsigned.U2)
- (|>> :representation))
+ (|>> representation))
(implementation: .public equivalence
(All (_ of) (Equivalence (Modifier of)))
(def: (= reference sample)
(# //unsigned.equivalence =
- (:representation reference)
- (:representation sample))))
+ (representation reference)
+ (representation sample))))
(template: (!wrap value)
[(|> value
//unsigned.u2
try.trusted
- :abstraction)])
+ abstraction)])
(template: (!unwrap value)
[(|> value
- :representation
+ representation
//unsigned.value)])
(def: .public (has? sub super)
@@ -71,7 +71,7 @@
(def: .public writer
(All (_ of) (Writer (Modifier of)))
- (|>> :representation //unsigned.writer/2))
+ (|>> representation //unsigned.writer/2))
(def: modifier
(-> Nat Modifier)
diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux
index c8daea629..29776163c 100644
--- a/stdlib/source/library/lux/target/jvm/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/reflection.lux
@@ -133,7 +133,7 @@
(<| (case (ffi.check java/lang/Class reflection)
{.#Some class}
(let [class_name (|> class
- (:as (java/lang/Class java/lang/Object))
+ (as (java/lang/Class java/lang/Object))
java/lang/Class::getName)]
(`` (if (or (~~ (template [<reflection>]
[(text#= (/reflection.reflection <reflection>)
@@ -162,7 +162,7 @@
(array.list {.#None})
(monad.each ! parameter)
(# ! each (/.class (|> raw'
- (:as (java/lang/Class java/lang/Object))
+ (as (java/lang/Class java/lang/Object))
java/lang/Class::getName)))
(exception.with ..cannot_convert_to_a_lux_type [reflection])))
@@ -224,7 +224,7 @@
(<| (case (ffi.check java/lang/Class reflection)
{.#Some reflection}
(let [class_name (|> reflection
- (:as (java/lang/Class java/lang/Object))
+ (as (java/lang/Class java/lang/Object))
java/lang/Class::getName)]
(`` (cond (~~ (template [<reflection> <type>]
[(text#= (/reflection.reflection <reflection>)
@@ -257,7 +257,7 @@
(case (ffi.check java/lang/Class reflection)
{.#Some class}
(let [class_name (|> reflection
- (:as (java/lang/Class java/lang/Object))
+ (as (java/lang/Class java/lang/Object))
java/lang/Class::getName)]
(if (text#= (/reflection.reflection /reflection.void)
class_name)
diff --git a/stdlib/source/library/lux/target/jvm/type.lux b/stdlib/source/library/lux/target/jvm/type.lux
index c4de519c3..4343e6ff0 100644
--- a/stdlib/source/library/lux/target/jvm/type.lux
+++ b/stdlib/source/library/lux/target/jvm/type.lux
@@ -1,29 +1,29 @@
(.using
- [library
- [lux {"-" Primitive Type int char}
- [abstract
- [equivalence {"+" Equivalence}]
- [hash {"+" Hash}]]
- [control
- ["[0]" maybe]]
- [data
- ["[0]" text
- ["%" format {"+" Format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor)]]]
- [math
- [number
- ["n" nat]]]
- [type
- abstract]]]
- ["[0]" // "_"
- [encoding
- ["[1][0]" name {"+" External}]]]
- ["[0]" / "_"
- [category {"+" Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration}]
- ["[1][0]" signature {"+" Signature}]
- ["[1][0]" descriptor {"+" Descriptor}]
- ["[1][0]" reflection {"+" Reflection}]])
+ [library
+ [lux {"-" Primitive Type int char}
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]]
+ [control
+ ["[0]" maybe]]
+ [data
+ ["[0]" text
+ ["%" format {"+" Format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]]]
+ [math
+ [number
+ ["n" nat]]]
+ [type
+ [abstract {"-" pattern}]]]]
+ ["[0]" // "_"
+ [encoding
+ ["[1][0]" name {"+" External}]]]
+ ["[0]" / "_"
+ [category {"+" Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration}]
+ ["[1][0]" signature {"+" Signature}]
+ ["[1][0]" descriptor {"+" Descriptor}]
+ ["[1][0]" reflection {"+" Reflection}]])
(abstract: .public (Type category)
[(Signature category)
@@ -45,7 +45,7 @@
(template [<name> <style>]
[(def: .public (<name> type)
(All (_ category) (-> (Type category) (<style> category)))
- (let [[signature descriptor reflection] (:representation type)]
+ (let [[signature descriptor reflection] (representation type)]
<name>))]
[signature Signature]
@@ -56,13 +56,13 @@
(All (_ category)
(-> (Type (<| Return' Value' category))
(Reflection (<| Return' Value' category))))
- (let [[signature descriptor reflection] (:representation type)]
+ (let [[signature descriptor reflection] (representation type)]
reflection))
(template [<category> <name> <signature> <descriptor> <reflection>]
[(def: .public <name>
(Type <category>)
- (:abstraction [<signature> <descriptor> <reflection>]))]
+ (abstraction [<signature> <descriptor> <reflection>]))]
[Void void /signature.void /descriptor.void /reflection.void]
[Primitive boolean /signature.boolean /descriptor.boolean /reflection.boolean]
@@ -77,59 +77,59 @@
(def: .public (array type)
(-> (Type Value) (Type Array))
- (:abstraction
+ (abstraction
[(/signature.array (..signature type))
(/descriptor.array (..descriptor type))
(/reflection.array (..reflection type))]))
(def: .public (class name parameters)
(-> External (List (Type Parameter)) (Type Class))
- (:abstraction
+ (abstraction
[(/signature.class name (list#each ..signature parameters))
(/descriptor.class name)
(/reflection.class name)]))
(def: .public (declaration name variables)
(-> External (List (Type Var)) (Type Declaration))
- (:abstraction
+ (abstraction
[(/signature.declaration name (list#each ..signature variables))
(/descriptor.declaration name)
(/reflection.declaration name)]))
(def: .public (as_class type)
(-> (Type Declaration) (Type Class))
- (:abstraction
- (let [[signature descriptor reflection] (:representation type)]
+ (abstraction
+ (let [[signature descriptor reflection] (representation type)]
[(/signature.as_class signature)
(/descriptor.as_class descriptor)
(/reflection.as_class reflection)])))
(def: .public wildcard
(Type Parameter)
- (:abstraction
+ (abstraction
[/signature.wildcard
/descriptor.wildcard
/reflection.wildcard]))
(def: .public (var name)
(-> Text (Type Var))
- (:abstraction
+ (abstraction
[(/signature.var name)
/descriptor.var
/reflection.var]))
(def: .public (lower bound)
(-> (Type Parameter) (Type Parameter))
- (:abstraction
- (let [[signature descriptor reflection] (:representation bound)]
+ (abstraction
+ (let [[signature descriptor reflection] (representation bound)]
[(/signature.lower signature)
(/descriptor.lower descriptor)
(/reflection.lower reflection)])))
(def: .public (upper bound)
(-> (Type Parameter) (Type Parameter))
- (:abstraction
- (let [[signature descriptor reflection] (:representation bound)]
+ (abstraction
+ (let [[signature descriptor reflection] (representation bound)]
[(/signature.upper signature)
(/descriptor.upper descriptor)
(/reflection.upper reflection)])))
@@ -140,14 +140,14 @@
(Type Return)
(List (Type Class))]
(Type Method))
- (:abstraction
+ (abstraction
[(/signature.method [(list#each ..signature type_variables)
(list#each ..signature inputs)
(..signature output)
(list#each ..signature exceptions)])
(/descriptor.method [(list#each ..descriptor inputs)
(..descriptor output)])
- (:expected ..void)]))
+ (as_expected ..void)]))
(implementation: .public equivalence
(All (_ category) (Equivalence (Type category)))
@@ -167,7 +167,7 @@
(-> (Type Value) (Either (Type Object)
(Type Primitive)))
(if (`` (or (~~ (template [<type>]
- [(# ..equivalence = (: (Type Value) <type>) type)]
+ [(# ..equivalence = (is (Type Value) <type>) type)]
[..boolean]
[..byte]
@@ -177,18 +177,18 @@
[..float]
[..double]
[..char]))))
- (|> type (:as (Type Primitive)) {.#Right})
- (|> type (:as (Type Object)) {.#Left})))
+ (|> type (as (Type Primitive)) {.#Right})
+ (|> type (as (Type Object)) {.#Left})))
(def: .public (void? type)
(-> (Type Return) (Either (Type Value)
(Type Void)))
(if (`` (or (~~ (template [<type>]
- [(# ..equivalence = (: (Type Return) <type>) type)]
+ [(# ..equivalence = (is (Type Return) <type>) type)]
[..void]))))
- (|> type (:as (Type Void)) {.#Right})
- (|> type (:as (Type Value)) {.#Left})))
+ (|> type (as (Type Void)) {.#Right})
+ (|> type (as (Type Value)) {.#Left})))
)
(def: .public (class? type)
diff --git a/stdlib/source/library/lux/target/jvm/type/category.lux b/stdlib/source/library/lux/target/jvm/type/category.lux
index 45128d756..0b740dae1 100644
--- a/stdlib/source/library/lux/target/jvm/type/category.lux
+++ b/stdlib/source/library/lux/target/jvm/type/category.lux
@@ -1,10 +1,10 @@
(.using
- [library
- [lux {"-" Primitive}
- [macro
- ["[0]" template]]
- [type
- abstract]]])
+ [library
+ [lux {"-" Primitive}
+ [macro
+ ["[0]" template]]
+ [type
+ [abstract {"-" pattern}]]]])
(abstract: Void' Any)
(abstract: .public (Value' kind) Any)
diff --git a/stdlib/source/library/lux/target/jvm/type/descriptor.lux b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
index d09a5d94f..c8c8f6f49 100644
--- a/stdlib/source/library/lux/target/jvm/type/descriptor.lux
+++ b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
@@ -1,37 +1,37 @@
(.using
- [library
- [lux {"-" Primitive int char}
- [abstract
- [equivalence {"+" Equivalence}]]
- [control
- ["[0]" maybe]]
- [data
- ["[0]" text ("[1]#[0]" equivalence)
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor)]]]
- [math
- [number
- ["n" nat]]]
- [type
- abstract]]]
- ["[0]" // "_"
- [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration}]
- ["/[1]" // "_"
- [encoding
- ["[1][0]" name {"+" Internal External}]]]])
+ [library
+ [lux {"-" Primitive int char}
+ [abstract
+ [equivalence {"+" Equivalence}]]
+ [control
+ ["[0]" maybe]]
+ [data
+ ["[0]" text ("[1]#[0]" equivalence)
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]]]
+ [math
+ [number
+ ["n" nat]]]
+ [type
+ [abstract {"-" pattern}]]]]
+ ["[0]" // "_"
+ [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration}]
+ ["/[1]" // "_"
+ [encoding
+ ["[1][0]" name {"+" Internal External}]]]])
(abstract: .public (Descriptor category)
Text
(def: .public descriptor
(-> (Descriptor Any) Text)
- (|>> :representation))
+ (|>> representation))
(template [<sigil> <category> <name>]
[(def: .public <name>
(Descriptor <category>)
- (:abstraction <sigil>))]
+ (abstraction <sigil>))]
["V" Void void]
["Z" Primitive boolean]
@@ -52,20 +52,20 @@
(|>> ///name.internal
///name.read
(text.enclosed [..class_prefix ..class_suffix])
- :abstraction))
+ abstraction))
(def: .public (declaration name)
(-> External (Descriptor Declaration))
- (:transmutation (..class name)))
+ (transmutation (..class name)))
(def: .public as_class
(-> (Descriptor Declaration) (Descriptor Class))
- (|>> :transmutation))
+ (|>> transmutation))
(template [<name> <category>]
[(def: .public <name>
(Descriptor <category>)
- (:transmutation
+ (transmutation
(..class "java.lang.Object")))]
[var Var]
@@ -78,40 +78,40 @@
(def: .public upper
(-> (Descriptor Parameter) (Descriptor Parameter))
- (|>> :transmutation))
+ (|>> transmutation))
(def: .public array_prefix "[")
(def: .public array
(-> (Descriptor Value)
(Descriptor Array))
- (|>> :representation
+ (|>> representation
(format ..array_prefix)
- :abstraction))
+ abstraction))
(def: .public (method [inputs output])
(-> [(List (Descriptor Value))
(Descriptor Return)]
(Descriptor Method))
- (:abstraction
+ (abstraction
(format (|> inputs
(list#each ..descriptor)
text.together
(text.enclosed ["(" ")"]))
- (:representation output))))
+ (representation output))))
(implementation: .public equivalence
(All (_ category) (Equivalence (Descriptor category)))
(def: (= parameter subject)
- (text#= (:representation parameter) (:representation subject))))
+ (text#= (representation parameter) (representation subject))))
(def: .public class_name
(-> (Descriptor Object) Internal)
(let [prefix_size (text.size ..class_prefix)
suffix_size (text.size ..class_suffix)]
(function (_ descriptor)
- (let [repr (:representation descriptor)]
+ (let [repr (representation descriptor)]
(if (text.starts_with? ..array_prefix repr)
(///name.internal repr)
(|> repr
diff --git a/stdlib/source/library/lux/target/jvm/type/parser.lux b/stdlib/source/library/lux/target/jvm/type/parser.lux
index 8c896e9f1..a1bea32fc 100644
--- a/stdlib/source/library/lux/target/jvm/type/parser.lux
+++ b/stdlib/source/library/lux/target/jvm/type/parser.lux
@@ -221,18 +221,18 @@
(List (Type Value))
(Type Return)
(List (Type Class))])
- (let [parser (: (Parser [(List (Type Var))
- (List (Type Value))
- (Type Return)
- (List (Type Class))])
- ($_ <>.and
- (|> (<>.some (<>#each product.left ..var_declaration))
- (<>.after (<text>.this //signature.parameters_start))
- (<>.before (<text>.this //signature.parameters_end))
- (<>.else (list)))
- ..inputs
- ..return
- (<>.some ..exception)))]
+ (let [parser (is (Parser [(List (Type Var))
+ (List (Type Value))
+ (Type Return)
+ (List (Type Class))])
+ ($_ <>.and
+ (|> (<>.some (<>#each product.left ..var_declaration))
+ (<>.after (<text>.this //signature.parameters_start))
+ (<>.before (<text>.this //signature.parameters_end))
+ (<>.else (list)))
+ ..inputs
+ ..return
+ (<>.some ..exception)))]
(|>> //.signature
//signature.signature
(<text>.result parser)
diff --git a/stdlib/source/library/lux/target/jvm/type/reflection.lux b/stdlib/source/library/lux/target/jvm/type/reflection.lux
index f4df7e88b..37d7e0dde 100644
--- a/stdlib/source/library/lux/target/jvm/type/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/type/reflection.lux
@@ -1,37 +1,37 @@
(.using
- [library
- [lux {"-" Primitive int char}
- [abstract
- [equivalence {"+" Equivalence}]]
- [data
- ["[0]" text ("[1]#[0]" equivalence)
- ["%" format {"+" format}]]]
- [type
- abstract]]]
- ["[0]" // "_"
- [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration}]
- ["[1][0]" descriptor]
- [//
- [encoding
- ["[1][0]" name {"+" External}]]]])
+ [library
+ [lux {"-" Primitive int char}
+ [abstract
+ [equivalence {"+" Equivalence}]]
+ [data
+ ["[0]" text ("[1]#[0]" equivalence)
+ ["%" format {"+" format}]]]
+ [type
+ [abstract {"-" pattern}]]]]
+ ["[0]" // "_"
+ [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration}]
+ ["[1][0]" descriptor]
+ [//
+ [encoding
+ ["[1][0]" name {"+" External}]]]])
(abstract: .public (Reflection category)
Text
(def: .public reflection
(-> (Reflection Any) Text)
- (|>> :representation))
+ (|>> representation))
(implementation: .public equivalence
(All (_ category) (Equivalence (Reflection category)))
(def: (= parameter subject)
- (text#= (:representation parameter) (:representation subject))))
+ (text#= (representation parameter) (representation subject))))
(template [<category> <name> <reflection>]
[(def: .public <name>
(Reflection <category>)
- (:abstraction <reflection>))]
+ (abstraction <reflection>))]
[Void void "void"]
[Primitive boolean "boolean"]
@@ -46,19 +46,19 @@
(def: .public class
(-> External (Reflection Class))
- (|>> :abstraction))
+ (|>> abstraction))
(def: .public (declaration name)
(-> External (Reflection Declaration))
- (:transmutation (..class name)))
+ (transmutation (..class name)))
(def: .public as_class
(-> (Reflection Declaration) (Reflection Class))
- (|>> :transmutation))
+ (|>> transmutation))
(def: .public (array element)
(-> (Reflection Value) (Reflection Array))
- (let [element' (:representation element)
+ (let [element' (representation element)
elementR (`` (cond (text.starts_with? //descriptor.array_prefix element')
element'
@@ -82,12 +82,12 @@
//name.external_separator))))]
(|> elementR
(format //descriptor.array_prefix)
- :abstraction)))
+ abstraction)))
(template [<name> <category>]
[(def: .public <name>
(Reflection <category>)
- (:transmutation
+ (transmutation
(..class "java.lang.Object")))]
[var Var]
@@ -100,5 +100,5 @@
(def: .public upper
(-> (Reflection Parameter) (Reflection Parameter))
- (|>> :transmutation))
+ (|>> transmutation))
)
diff --git a/stdlib/source/library/lux/target/jvm/type/signature.lux b/stdlib/source/library/lux/target/jvm/type/signature.lux
index e2b00d292..a5b710c59 100644
--- a/stdlib/source/library/lux/target/jvm/type/signature.lux
+++ b/stdlib/source/library/lux/target/jvm/type/signature.lux
@@ -12,7 +12,7 @@
[collection
["[0]" list ("[1]#[0]" functor)]]]
[type
- abstract]]]
+ [abstract {"-" pattern}]]]]
["[0]" // "_"
[category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration Inheritance}]
["[1][0]" descriptor]
@@ -25,12 +25,12 @@
(def: .public signature
(-> (Signature Any) Text)
- (|>> :representation))
+ (|>> representation))
(template [<category> <name> <descriptor>]
[(def: .public <name>
(Signature <category>)
- (:abstraction (//descriptor.descriptor <descriptor>)))]
+ (abstraction (//descriptor.descriptor <descriptor>)))]
[Void void //descriptor.void]
[Primitive boolean //descriptor.boolean]
@@ -45,13 +45,13 @@
(def: .public array
(-> (Signature Value) (Signature Array))
- (|>> :representation
+ (|>> representation
(format //descriptor.array_prefix)
- :abstraction))
+ abstraction))
(def: .public wildcard
(Signature Parameter)
- (:abstraction "*"))
+ (abstraction "*"))
(template [<char> <name>]
[(def: .public <name> <char>)]
@@ -72,7 +72,7 @@
(template [<name> <prefix>]
[(def: .public <name>
(-> (Signature Parameter) (Signature Parameter))
- (|>> :representation (format <prefix>) :abstraction))]
+ (|>> representation (format <prefix>) abstraction))]
[lower ..lower_prefix]
[upper ..upper_prefix]
@@ -81,17 +81,17 @@
(def: .public var
(-> Text (Signature Var))
(|>> (text.enclosed [..var_prefix //descriptor.class_suffix])
- :abstraction))
+ abstraction))
(def: .public var_name
(-> (Signature Var) Text)
- (|>> :representation
+ (|>> representation
(text.replaced ..var_prefix "")
(text.replaced //descriptor.class_suffix "")))
(def: .public (class name parameters)
(-> External (List (Signature Parameter)) (Signature Class))
- (:abstraction
+ (abstraction
(format //descriptor.class_prefix
(|> name ///name.internal ///name.read)
(case parameters
@@ -108,7 +108,7 @@
(def: .public (declaration name variables)
(-> External (List (Signature Var)) (Signature Declaration))
- (:transmutation (..class name variables)))
+ (transmutation (..class name variables)))
(def: class_bound
(|> (..class "java.lang.Object" (list))
@@ -138,16 +138,16 @@
(def: .public (inheritance variables super interfaces)
(-> (List (Signature Var)) (Signature Class) (List (Signature Class)) (Signature Inheritance))
- (:abstraction
+ (abstraction
(format (var_declaration/* variables)
- (:representation super)
+ (representation super)
(|> interfaces
(list#each ..signature)
text.together))))
(def: .public as_class
(-> (Signature Declaration) (Signature Class))
- (|>> :transmutation))
+ (|>> transmutation))
(def: .public (method [type_variables inputs output exceptions])
(-> [(List (Signature Var))
@@ -155,28 +155,28 @@
(Signature Return)
(List (Signature Class))]
(Signature Method))
- (:abstraction
+ (abstraction
(format (var_declaration/* type_variables)
(|> inputs
(list#each ..signature)
text.together
(text.enclosed [..arguments_start
..arguments_end]))
- (:representation output)
+ (representation output)
(|> exceptions
- (list#each (|>> :representation (format ..exception_prefix)))
+ (list#each (|>> representation (format ..exception_prefix)))
text.together))))
(implementation: .public equivalence
(All (_ category) (Equivalence (Signature category)))
(def: (= parameter subject)
- (text#= (:representation parameter)
- (:representation subject))))
+ (text#= (representation parameter)
+ (representation subject))))
(implementation: .public hash
(All (_ category) (Hash (Signature category)))
(def: &equivalence ..equivalence)
- (def: hash (|>> :representation text#hash)))
+ (def: hash (|>> representation text#hash)))
)