aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/target/jvm/type.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/target/jvm/type.lux')
-rw-r--r--stdlib/source/library/lux/target/jvm/type.lux94
1 files changed, 47 insertions, 47 deletions
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)