aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/host.old.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/host.old.lux92
1 files changed, 46 insertions, 46 deletions
diff --git a/stdlib/source/lux/host.old.lux b/stdlib/source/lux/host.old.lux
index 39fe0034c..4c12d8774 100644
--- a/stdlib/source/lux/host.old.lux
+++ b/stdlib/source/lux/host.old.lux
@@ -521,14 +521,14 @@
(-> Text Text (Parser Code))
(do p.monad
[#let [dotted-name (format "::" field-name)]
- _ (s.this (code.identifier ["" dotted-name]))]
+ _ (s.this! (code.identifier ["" dotted-name]))]
(wrap (`' ((~ (code.text (format "jvm getstatic" ":" class-name ":" field-name))))))))
(def: (make-get-var-parser class-name field-name)
(-> Text Text (Parser Code))
(do p.monad
[#let [dotted-name (format "::" field-name)]
- _ (s.this (code.identifier ["" dotted-name]))]
+ _ (s.this! (code.identifier ["" dotted-name]))]
(wrap (`' ((~ (code.text (format "jvm getfield" ":" class-name ":" field-name))) _jvm_this)))))
(def: (make-put-var-parser class-name field-name)
@@ -536,7 +536,7 @@
(do p.monad
[#let [dotted-name (format "::" field-name)]
[_ _ value] (: (Parser [Any Any Code])
- (s.form ($_ p.and (s.this (' :=)) (s.this (code.identifier ["" dotted-name])) s.any)))]
+ (s.form ($_ p.and (s.this! (' :=)) (s.this! (code.identifier ["" dotted-name])) s.any)))]
(wrap (`' ((~ (code.text (format "jvm putfield" ":" class-name ":" field-name))) _jvm_this (~ value))))))
(def: (pre-walk-replace f input)
@@ -581,7 +581,7 @@
(-> (List Type-Paramameter) Text (List ArgDecl) (Parser Code))
(do p.monad
[args (: (Parser (List Code))
- (s.form (p.after (s.this (' ::new!))
+ (s.form (p.after (s.this! (' ::new!))
(s.tuple (p.exactly (list.size arg-decls) s.any)))))
#let [arg-decls' (: (List Text) (list@map (|>> product.right (simple-class$ params)) arg-decls))]]
(wrap (` ((~ (code.text (format "jvm new" ":" class-name ":" (text.join-with "," arg-decls'))))
@@ -592,7 +592,7 @@
(do p.monad
[#let [dotted-name (format "::" method-name "!")]
args (: (Parser (List Code))
- (s.form (p.after (s.this (code.identifier ["" dotted-name]))
+ (s.form (p.after (s.this! (code.identifier ["" dotted-name]))
(s.tuple (p.exactly (list.size arg-decls) s.any)))))
#let [arg-decls' (: (List Text) (list@map (|>> product.right (simple-class$ params)) arg-decls))]]
(wrap (`' ((~ (code.text (format "jvm invokestatic" ":" class-name ":" method-name ":" (text.join-with "," arg-decls'))))
@@ -604,7 +604,7 @@
(do p.monad
[#let [dotted-name (format "::" method-name "!")]
args (: (Parser (List Code))
- (s.form (p.after (s.this (code.identifier ["" dotted-name]))
+ (s.form (p.after (s.this! (code.identifier ["" dotted-name]))
(s.tuple (p.exactly (list.size arg-decls) s.any)))))
#let [arg-decls' (: (List Text) (list@map (|>> product.right (simple-class$ params)) arg-decls))]]
(wrap (`' ((~ (code.text (format <jvm-op> ":" class-name ":" method-name ":" (text.join-with "," arg-decls'))))
@@ -644,23 +644,23 @@
(Parser PrivacyModifier)
(let [(^open ".") p.monad]
($_ p.or
- (s.this (' #public))
- (s.this (' #private))
- (s.this (' #protected))
+ (s.this! (' #public))
+ (s.this! (' #private))
+ (s.this! (' #protected))
(wrap []))))
(def: inheritance-modifier^
(Parser InheritanceModifier)
(let [(^open ".") p.monad]
($_ p.or
- (s.this (' #final))
- (s.this (' #abstract))
+ (s.this! (' #final))
+ (s.this! (' #abstract))
(wrap []))))
(def: bound-kind^
(Parser BoundKind)
- (p.or (s.this (' <))
- (s.this (' >))))
+ (p.or (s.this! (' <))
+ (s.this! (' >))))
(def: (assert-no-periods name)
(-> Text (Parser Any))
@@ -671,10 +671,10 @@
(-> Class-Imports (List Type-Paramameter) (Parser GenericType))
($_ p.either
(do p.monad
- [_ (s.this (' ?))]
+ [_ (s.this! (' ?))]
(wrap (#GenericWildcard #.None)))
(s.tuple (do p.monad
- [_ (s.this (' ?))
+ [_ (s.this! (' ?))
bound-kind bound-kind^
bound (generic-type^ imports type-vars)]
(wrap (#GenericWildcard (#.Some [bound-kind bound])))))
@@ -685,7 +685,7 @@
(wrap (#GenericTypeVar name))
(wrap (#GenericClass name (list)))))
(s.form (do p.monad
- [name (s.this (' Array))
+ [name (s.this! (' Array))
component (generic-type^ imports type-vars)]
(case component
(^template [<class> <name>]
@@ -718,7 +718,7 @@
(wrap [param-name (list)]))
(s.tuple (do p.monad
[param-name s.local-identifier
- _ (s.this (' <))
+ _ (s.this! (' <))
bounds (p.many (generic-type^ imports (list)))]
(wrap [param-name bounds])))))
@@ -766,7 +766,7 @@
(def: (annotations^' imports)
(-> Class-Imports (Parser (List Annotation)))
(do p.monad
- [_ (s.this (' #ann))]
+ [_ (s.this! (' #ann))]
(s.tuple (p.some (annotation^ imports)))))
(def: (annotations^ imports)
@@ -778,7 +778,7 @@
(def: (throws-decl'^ imports type-vars)
(-> Class-Imports (List Type-Paramameter) (Parser (List GenericType)))
(do p.monad
- [_ (s.this (' #throws))]
+ [_ (s.this! (' #throws))]
(s.tuple (p.some (generic-type^ imports type-vars)))))
(def: (throws-decl^ imports type-vars)
@@ -804,14 +804,14 @@
(def: state-modifier^
(Parser StateModifier)
($_ p.or
- (s.this (' #volatile))
- (s.this (' #final))
+ (s.this! (' #volatile))
+ (s.this! (' #final))
(:: p.monad wrap [])))
(def: (field-decl^ imports type-vars)
(-> Class-Imports (List Type-Paramameter) (Parser [Member-Declaration FieldDecl]))
(p.either (s.form (do p.monad
- [_ (s.this (' #const))
+ [_ (s.this! (' #const))
name s.local-identifier
anns (annotations^ imports)
type (generic-type^ imports type-vars)
@@ -846,10 +846,10 @@
(-> Class-Imports (List Type-Paramameter) (Parser [Member-Declaration Method-Definition]))
(s.form (do p.monad
[pm privacy-modifier^
- strict-fp? (s.this? (' #strict))
+ strict-fp? (p.parses? (s.this! (' #strict)))
method-vars (p.default (list) (type-params^ imports))
#let [total-vars (list@compose class-vars method-vars)]
- [_ arg-decls] (s.form (p.and (s.this (' new))
+ [_ arg-decls] (s.form (p.and (s.this! (' new))
(arg-decls^ imports total-vars)))
constructor-args (constructor-args^ imports total-vars)
exs (throws-decl^ imports total-vars)
@@ -864,8 +864,8 @@
(-> Class-Imports (List Type-Paramameter) (Parser [Member-Declaration Method-Definition]))
(s.form (do p.monad
[pm privacy-modifier^
- strict-fp? (s.this? (' #strict))
- final? (s.this? (' #final))
+ strict-fp? (p.parses? (s.this! (' #strict)))
+ final? (p.parses? (s.this! (' #final)))
method-vars (p.default (list) (type-params^ imports))
#let [total-vars (list@compose class-vars method-vars)]
[name this-name arg-decls] (s.form ($_ p.and
@@ -887,7 +887,7 @@
(def: (overriden-method-def^ imports)
(-> Class-Imports (Parser [Member-Declaration Method-Definition]))
(s.form (do p.monad
- [strict-fp? (s.this? (' #strict))
+ [strict-fp? (p.parses? (s.this! (' #strict)))
owner-class (class-decl^ imports)
method-vars (p.default (list) (type-params^ imports))
#let [total-vars (list@compose (product.right owner-class) method-vars)]
@@ -911,8 +911,8 @@
(-> Class-Imports (Parser [Member-Declaration Method-Definition]))
(s.form (do p.monad
[pm privacy-modifier^
- strict-fp? (s.this? (' #strict))
- _ (s.this (' #static))
+ strict-fp? (p.parses? (s.this! (' #strict)))
+ _ (s.this! (' #static))
method-vars (p.default (list) (type-params^ imports))
#let [total-vars method-vars]
[name arg-decls] (s.form (p.and s.local-identifier
@@ -930,7 +930,7 @@
(-> Class-Imports (Parser [Member-Declaration Method-Definition]))
(s.form (do p.monad
[pm privacy-modifier^
- _ (s.this (' #abstract))
+ _ (s.this! (' #abstract))
method-vars (p.default (list) (type-params^ imports))
#let [total-vars method-vars]
[name arg-decls] (s.form (p.and s.local-identifier
@@ -947,7 +947,7 @@
(-> Class-Imports (Parser [Member-Declaration Method-Definition]))
(s.form (do p.monad
[pm privacy-modifier^
- _ (s.this (' #native))
+ _ (s.this! (' #native))
method-vars (p.default (list) (type-params^ imports))
#let [total-vars method-vars]
[name arg-decls] (s.form (p.and s.local-identifier
@@ -977,42 +977,42 @@
(def: class-kind^
(Parser Class-Kind)
(p.either (do p.monad
- [_ (s.this (' #class))]
+ [_ (s.this! (' #class))]
(wrap #Class))
(do p.monad
- [_ (s.this (' #interface))]
+ [_ (s.this! (' #interface))]
(wrap #Interface))
))
(def: import-member-alias^
(Parser (Maybe Text))
(p.maybe (do p.monad
- [_ (s.this (' #as))]
+ [_ (s.this! (' #as))]
s.local-identifier)))
(def: (import-member-args^ imports type-vars)
(-> Class-Imports (List Type-Paramameter) (Parser (List [Bit GenericType])))
- (s.tuple (p.some (p.and (s.this? (' #?)) (generic-type^ imports type-vars)))))
+ (s.tuple (p.some (p.and (p.parses? (s.this! (' #?))) (generic-type^ imports type-vars)))))
(def: import-member-return-flags^
(Parser [Bit Bit Bit])
- ($_ p.and (s.this? (' #io)) (s.this? (' #try)) (s.this? (' #?))))
+ ($_ p.and (p.parses? (s.this! (' #io))) (p.parses? (s.this! (' #try))) (p.parses? (s.this! (' #?)))))
(def: primitive-mode^
(Parser Primitive-Mode)
- (p.or (s.this (' #manual))
- (s.this (' #auto))))
+ (p.or (s.this! (' #manual))
+ (s.this! (' #auto))))
(def: (import-member-decl^ imports owner-vars)
(-> Class-Imports (List Type-Paramameter) (Parser Import-Member-Declaration))
($_ p.either
(s.form (do p.monad
- [_ (s.this (' #enum))
+ [_ (s.this! (' #enum))
enum-members (p.some s.local-identifier)]
(wrap (#EnumDecl enum-members))))
(s.form (do p.monad
[tvars (p.default (list) (type-params^ imports))
- _ (s.this (' new))
+ _ (s.this! (' new))
?alias import-member-alias^
#let [total-vars (list@compose owner-vars tvars)]
?prim-mode (p.maybe primitive-mode^)
@@ -1030,7 +1030,7 @@
))
(s.form (do p.monad
[kind (: (Parser ImportMethodKind)
- (p.or (s.this (' #static))
+ (p.or (s.this! (' #static))
(wrap [])))
tvars (p.default (list) (type-params^ imports))
name s.local-identifier
@@ -1052,12 +1052,12 @@
#import-method-return return
}]))))
(s.form (do p.monad
- [static? (s.this? (' #static))
+ [static? (p.parses? (s.this! (' #static)))
name s.local-identifier
?prim-mode (p.maybe primitive-mode^)
gtype (generic-type^ imports owner-vars)
- maybe? (s.this? (' #?))
- setter? (s.this? (' #!))]
+ maybe? (p.parses? (s.this! (' #?)))
+ setter? (p.parses? (s.this! (' #!)))]
(wrap (#FieldAccessDecl {#import-field-mode (maybe.default #AutoPrM ?prim-mode)
#import-field-name name
#import-field-static? static?
@@ -1221,7 +1221,7 @@
(#OverridenMethod strict-fp? class-decl type-vars this-name arg-decls return-type body exs)
(let [super-replacer (parser->replacer (s.form (do p.monad
- [_ (s.this (' ::super!))
+ [_ (s.this! (' ::super!))
args (s.tuple (p.exactly (list.size arg-decls) s.any))
#let [arg-decls' (: (List Text) (list@map (|>> product.right (simple-class$ (list)))
arg-decls))]]
@@ -1797,7 +1797,7 @@
(syntax: #export (import:
{#let [imports (class-imports *compiler*)]}
- {long-name? (s.this? (' #long))}
+ {long-name? (p.parses? (s.this! (' #long)))}
{class-decl (class-decl^ imports)}
{#let [full-class-name (product.left class-decl)
imports (add-import [(short-class-name full-class-name) full-class-name]