aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/meta/target
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/meta/target')
-rw-r--r--stdlib/source/library/lux/meta/target/js.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/bytecode.lux12
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/bytecode/address.lux4
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/bytecode/environment.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/registry.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/stack.lux4
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/bytecode/instruction.lux4
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/class.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/constant.lux6
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/constant/pool.lux4
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/field.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/index.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/method.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/modifier.lux6
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/reflection.lux8
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type.lux10
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type/alias.lux4
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type/parser.lux4
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type/reflection.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/lua.lux6
-rw-r--r--stdlib/source/library/lux/meta/target/php.lux6
-rw-r--r--stdlib/source/library/lux/meta/target/python.lux4
-rw-r--r--stdlib/source/library/lux/meta/target/ruby.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/scheme.lux4
25 files changed, 53 insertions, 53 deletions
diff --git a/stdlib/source/library/lux/meta/target/js.lux b/stdlib/source/library/lux/meta/target/js.lux
index b2e34c32b..c158d9651 100644
--- a/stdlib/source/library/lux/meta/target/js.lux
+++ b/stdlib/source/library/lux/meta/target/js.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Location Code Label or and function if undefined for comment not int try ++ -- the type_of at , when)
+ [lux (.except Location Code Label or and function if undefined for comment not int try ++ -- the type_of , when)
[control
["[0]" pipe]]
[data
diff --git a/stdlib/source/library/lux/meta/target/jvm/bytecode.lux b/stdlib/source/library/lux/meta/target/jvm/bytecode.lux
index cb236893f..dc51330fa 100644
--- a/stdlib/source/library/lux/meta/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/bytecode.lux
@@ -113,7 +113,7 @@
(function (_ resolver)
(<| (try|do [left_exceptions left_instruction] (left resolver))
(try|do [right_exceptions right_instruction] (right resolver))
- (try|in [(at sequence.monoid composite left_exceptions right_exceptions)
+ (try|in [(of sequence.monoid composite left_exceptions right_exceptions)
(_#composite left_instruction right_instruction)])))))
(def relative_monoid
@@ -698,7 +698,7 @@
(-> Nat (Bytecode Register))
(when (//unsigned.u1 id)
{try.#Success register}
- (at ..monad in register)
+ (of ..monad in register)
{try.#Failure error}
(..except ..invalid_register [id])))
@@ -867,7 +867,7 @@
[(function (_ resolver)
(<| (try|do [expected @to] (..resolve_label label resolver))
(try|do _ (exception.assertion ..mismatched_environments [(symbol <instruction>) label @here expected actual]
- (at /stack.equivalence = expected actual)))
+ (of /stack.equivalence = expected actual)))
(try|do jump (..jump @from @to))
(when jump
{.#Left jump}
@@ -916,7 +916,7 @@
(when (dictionary.value label resolver)
{.#Some [expected {.#Some @to}]}
(<| (try|do _ (exception.assertion ..mismatched_environments [(symbol <instruction>) label @here expected actual]
- (at /stack.equivalence = expected actual)))
+ (of /stack.equivalence = expected actual)))
(try|do jump (..jump @from @to))
(when jump
{.#Left jump}
@@ -975,7 +975,7 @@
(|> afterwards
(monad.each ! get)
(monad.then ! (monad.each ! product.right))
- (at ! each (|>> [@default @at_minimum]))))
+ (of ! each (|>> [@default @at_minimum]))))
{.#Some [@default @at_minimum @afterwards]}
(<| (try|do >default (try#each ..big_jump (..jump @from @default)))
(try|do >at_minimum (try#each ..big_jump (..jump @from @at_minimum)))
@@ -1016,7 +1016,7 @@
(|> cases
(monad.each ! (|>> product.right get))
(monad.then ! (monad.each ! product.right))
- (at ! each (|>> [@default]))))
+ (of ! each (|>> [@default]))))
{.#Some [@default @cases]}
(<| (try|do >default (try#each ..big_jump (..jump @from @default)))
(try|do >cases (|> @cases
diff --git a/stdlib/source/library/lux/meta/target/jvm/bytecode/address.lux b/stdlib/source/library/lux/meta/target/jvm/bytecode/address.lux
index 3e6d4f4c2..6bcb3655a 100644
--- a/stdlib/source/library/lux/meta/target/jvm/bytecode/address.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/bytecode/address.lux
@@ -39,7 +39,7 @@
(-> U2 (-> Address (Try Address)))
(|>> representation
(///unsigned.+/2 distance)
- (at try.functor each (|>> abstraction))))
+ (of try.functor each (|>> abstraction))))
(def with_sign
(-> Address (Try S4))
@@ -61,7 +61,7 @@
(Equivalence Address)
(implementation
(def (= reference subject)
- (at ///unsigned.equivalence =
+ (of ///unsigned.equivalence =
(representation reference)
(representation subject)))))
diff --git a/stdlib/source/library/lux/meta/target/jvm/bytecode/environment.lux b/stdlib/source/library/lux/meta/target/jvm/bytecode/environment.lux
index a7e687751..9fd4d7250 100644
--- a/stdlib/source/library/lux/meta/target/jvm/bytecode/environment.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/bytecode/environment.lux
@@ -74,7 +74,7 @@
(-> Stack Environment (Try [Stack Environment]))
(when (the ..#stack environment)
{.#Some actual}
- (if (at /stack.equivalence = expected actual)
+ (if (of /stack.equivalence = expected actual)
{try.#Success [actual environment]}
(exception.except ..mismatched_stacks [expected actual]))
diff --git a/stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/registry.lux b/stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/registry.lux
index 28c09c0d2..9737de12c 100644
--- a/stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/registry.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/registry.lux
@@ -61,7 +61,7 @@
(def .public equivalence
(Equivalence Registry)
- (at equivalence.functor each
+ (of equivalence.functor each
(|>> representation)
/////unsigned.equivalence))
diff --git a/stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/stack.lux b/stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/stack.lux
index eaf7673f7..7517c2b60 100644
--- a/stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/stack.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/bytecode/environment/limit/stack.lux
@@ -32,7 +32,7 @@
(def .public equivalence
(Equivalence Stack)
- (at equivalence.functor each
+ (of equivalence.functor each
(|>> representation)
/////unsigned.equivalence))
@@ -49,7 +49,7 @@
(-> U2 (-> Stack (Try Stack)))
(|>> representation
(<op> amount)
- (at try.functor each ..stack)))]
+ (of try.functor each ..stack)))]
[/////unsigned.+/2 push]
[/////unsigned.-/2 pop]
diff --git a/stdlib/source/library/lux/meta/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/meta/target/jvm/bytecode/instruction.lux
index d6abb8141..d8a6963ae 100644
--- a/stdlib/source/library/lux/meta/target/jvm/bytecode/instruction.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/bytecode/instruction.lux
@@ -597,7 +597,7 @@
tableswitch_size (try.trusted
(do [! try.monad]
[size (///unsigned.u2 size)]
- (at ! each (|>> estimator ///unsigned.value)
+ (of ! each (|>> estimator ///unsigned.value)
(//address.move size //address.start))))
tableswitch_mutation (is Mutation
(function (_ [offset binary])
@@ -661,7 +661,7 @@
lookupswitch_size (try.trusted
(do [! try.monad]
[size (///unsigned.u2 size)]
- (at ! each (|>> estimator ///unsigned.value)
+ (of ! each (|>> estimator ///unsigned.value)
(//address.move size //address.start))))
lookupswitch_mutation (is Mutation
(function (_ [offset binary])
diff --git a/stdlib/source/library/lux/meta/target/jvm/class.lux b/stdlib/source/library/lux/meta/target/jvm/class.lux
index ba01154b6..5ffb48007 100644
--- a/stdlib/source/library/lux/meta/target/jvm/class.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/class.lux
@@ -106,7 +106,7 @@
attributes (monad.all ! attributes)
@signature (when signature
{.#Some signature}
- (at ! each (|>> {.#Some}) (//attribute.signature signature))
+ (of ! each (|>> {.#Some}) (//attribute.signature signature))
{.#None}
(in {.#None}))]
diff --git a/stdlib/source/library/lux/meta/target/jvm/constant.lux b/stdlib/source/library/lux/meta/target/jvm/constant.lux
index 936e73230..8039a7b47 100644
--- a/stdlib/source/library/lux/meta/target/jvm/constant.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/constant.lux
@@ -54,7 +54,7 @@
(def .public class_equivalence
(Equivalence Class)
- (at equivalence.functor each
+ (of equivalence.functor each
..index
//index.equivalence))
@@ -93,7 +93,7 @@
(All (_ kind)
(-> (Equivalence kind)
(Equivalence (Value kind))))
- (at equivalence.functor each
+ (of equivalence.functor each
(|>> representation)
Equivalence<kind>))
@@ -186,7 +186,7 @@
(when [reference sample]
(^.with_template [<tag> <equivalence>]
[[{<tag> reference} {<tag> sample}]
- (at <equivalence> = reference sample)])
+ (of <equivalence> = reference sample)])
([#UTF8 text.equivalence]
[#Integer (..value_equivalence i32.equivalence)]
[#Long (..value_equivalence int.equivalence)]
diff --git a/stdlib/source/library/lux/meta/target/jvm/constant/pool.lux b/stdlib/source/library/lux/meta/target/jvm/constant/pool.lux
index bb57608a0..46adfd870 100644
--- a/stdlib/source/library/lux/meta/target/jvm/constant/pool.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/constant/pool.lux
@@ -100,7 +100,7 @@
{try.#Success entry}
(when entry
[index {<tag> reference}]
- (if (at <equivalence> = reference <value>')
+ (if (of <equivalence> = reference <value>')
{try.#Success [[current pool]
index]}
<try_again>)
@@ -115,7 +115,7 @@
(|> current
//index.value
(//unsigned.+/2 @new)
- (at try.monad each //index.index))))
+ (of try.monad each //index.index))))
(try|in [[next
(sequence.suffix [current new] pool)]
current]))))))]))
diff --git a/stdlib/source/library/lux/meta/target/jvm/field.lux b/stdlib/source/library/lux/meta/target/jvm/field.lux
index 49c60849e..443d34f16 100644
--- a/stdlib/source/library/lux/meta/target/jvm/field.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/field.lux
@@ -68,7 +68,7 @@
[@name (//constant/pool.utf8 name)
@descriptor (//constant/pool.descriptor (//type.descriptor type))
@signature (if with_signature?
- (at ! each (|>> {.#Some}) (//attribute.signature (//type.signature type)))
+ (of ! each (|>> {.#Some}) (//attribute.signature (//type.signature type)))
(in {.#None}))]
(in [#modifier modifier
#name @name
diff --git a/stdlib/source/library/lux/meta/target/jvm/index.lux b/stdlib/source/library/lux/meta/target/jvm/index.lux
index 7f93bb0ff..522684c1c 100644
--- a/stdlib/source/library/lux/meta/target/jvm/index.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/index.lux
@@ -29,7 +29,7 @@
(def .public equivalence
(All (_ kind) (Equivalence (Index kind)))
- (at equivalence.functor each
+ (of equivalence.functor each
..value
//unsigned.equivalence))
diff --git a/stdlib/source/library/lux/meta/target/jvm/method.lux b/stdlib/source/library/lux/meta/target/jvm/method.lux
index 629aaae94..a4689017a 100644
--- a/stdlib/source/library/lux/meta/target/jvm/method.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/method.lux
@@ -62,7 +62,7 @@
(list.partial (//attribute.signature (//type.signature type)) attributes)
attributes)
(monad.all !)
- (at ! each sequence.of_list))
+ (of ! each sequence.of_list))
attributes (when code
{.#Some code}
(do !
diff --git a/stdlib/source/library/lux/meta/target/jvm/modifier.lux b/stdlib/source/library/lux/meta/target/jvm/modifier.lux
index 9b1b0843e..59359f103 100644
--- a/stdlib/source/library/lux/meta/target/jvm/modifier.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/modifier.lux
@@ -35,7 +35,7 @@
(All (_ of) (Equivalence (Modifier of)))
(implementation
(def (= reference sample)
- (at //unsigned.equivalence =
+ (of //unsigned.equivalence =
(representation reference)
(representation sample)))))
@@ -57,7 +57,7 @@
(let [sub (!representation sub)]
(|> (!representation super)
(i64.and sub)
- (at i64.equivalence = sub))))
+ (of i64.equivalence = sub))))
(def .public monoid
(All (_ of) (Monoid (Modifier of)))
@@ -71,7 +71,7 @@
(def .public empty
Modifier
- (at ..monoid identity))
+ (of ..monoid identity))
(def .public format
(All (_ of) (Format (Modifier of)))
diff --git a/stdlib/source/library/lux/meta/target/jvm/reflection.lux b/stdlib/source/library/lux/meta/target/jvm/reflection.lux
index 2e977d594..d62ce7c3f 100644
--- a/stdlib/source/library/lux/meta/target/jvm/reflection.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/reflection.lux
@@ -163,7 +163,7 @@
java/lang/reflect/ParameterizedType::getActualTypeArguments
(array.list {.#None})
(monad.each ! parameter)
- (at ! each (/.class (|> raw'
+ (of ! each (/.class (|> raw'
(as (java/lang/Class java/lang/Object))
java/lang/Class::getName)))
(exception.with ..cannot_convert_to_a_lux_type [reflection])))
@@ -196,7 +196,7 @@
{try.#Success /.wildcard}
_
- (at try.monad each <kind> (parameter type bound)))])
+ (of try.monad each <kind> (parameter type bound)))])
([[_ {.#Some bound}] /.upper]
[[{.#Some bound} _] /.lower])
@@ -208,7 +208,7 @@
(|> reflection
java/lang/reflect/GenericArrayType::getGenericComponentType
type
- (at try.monad each /.array))
+ (of try.monad each /.array))
_)
(when (ffi.as java/lang/Class reflection)
{.#Some class}
@@ -376,7 +376,7 @@
<then?> (|> fieldJ
java/lang/reflect/Field::getGenericType
..type
- (at ! each (|>> [(java/lang/reflect/Modifier::isFinal modifiers)
+ (of ! each (|>> [(java/lang/reflect/Modifier::isFinal modifiers)
(..deprecated? (java/lang/reflect/Field::getDeclaredAnnotations fieldJ))])))
<else?> (exception.except <exception> [field class]))))]
diff --git a/stdlib/source/library/lux/meta/target/jvm/type.lux b/stdlib/source/library/lux/meta/target/jvm/type.lux
index 9253258f5..0eff5b048 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type.lux
@@ -154,7 +154,7 @@
(All (_ category) (Equivalence (Type category)))
(implementation
(def (= parameter subject)
- (at /signature.equivalence =
+ (of /signature.equivalence =
(..signature parameter)
(..signature subject)))))
@@ -162,13 +162,13 @@
(All (_ category) (Hash (Type category)))
(implementation
(def equivalence ..equivalence)
- (def hash (|>> ..signature (at /signature.hash hash)))))
+ (def hash (|>> ..signature (of /signature.hash hash)))))
(def .public (primitive? type)
(-> (Type Value) (Either (Type Object)
(Type Primitive)))
(if (`` (or (,, (with_template [<type>]
- [(at ..equivalence = (is (Type Value) <type>) type)]
+ [(of ..equivalence = (is (Type Value) <type>) type)]
[..boolean]
[..byte]
@@ -185,7 +185,7 @@
(-> (Type Return) (Either (Type Value)
(Type Void)))
(if (`` (or (,, (with_template [<type>]
- [(at ..equivalence = (is (Type Return) <type>) type)]
+ [(of ..equivalence = (is (Type Return) <type>) type)]
[..void]))))
(|> type (as (Type Void)) {.#Right})
@@ -204,7 +204,7 @@
(n.- suffix_size))]
(|> repr
(text.clip prefix_size name_size)
- (at maybe.monad each (|>> //name.internal //name.external))))
+ (of maybe.monad each (|>> //name.internal //name.external))))
{.#None})))
(def .public format
diff --git a/stdlib/source/library/lux/meta/target/jvm/type/alias.lux b/stdlib/source/library/lux/meta/target/jvm/type/alias.lux
index 99d623d5e..8bc4f29e8 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type/alias.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type/alias.lux
@@ -52,7 +52,7 @@
[(def <name>
(-> (Parser (Type Class)) (Parser (Type Parameter)))
(|>> (<>.after (<text>.this <prefix>))
- (at <>.monad each <bound>)))]
+ (of <>.monad each <bound>)))]
[lower //signature.lower_prefix //.lower ..Lower]
[upper //signature.upper_prefix //.upper ..Upper]
@@ -108,7 +108,7 @@
(def (bound_type_var aliasing)
(-> Aliasing (Parser (Type Var)))
(|> //parser.var_name
- (at <>.monad each //.var)
+ (of <>.monad each //.var)
(<>.before (<>.many (..bound aliasing)))))
(def .public (method aliasing)
diff --git a/stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux b/stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux
index 46e360bae..2327f07b2 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux
@@ -120,6 +120,6 @@
(|> (text.size repr)
(n.- prefix_size)
(n.- suffix_size)))
- (at maybe.monad each ///name.internal)
+ (of maybe.monad each ///name.internal)
maybe.trusted))))))
)
diff --git a/stdlib/source/library/lux/meta/target/jvm/type/parser.lux b/stdlib/source/library/lux/meta/target/jvm/type/parser.lux
index 61c80017c..2ad5b09a2 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type/parser.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type/parser.lux
@@ -68,7 +68,7 @@
(with_template [<type> <name> <head> <tail> <adapter>]
[(def .public <name>
(Parser <type>)
- (at <>.functor each <adapter>
+ (of <>.functor each <adapter>
(<text>.slice (<text>.and! (<text>.one_of! <head>)
(<text>.some! (<text>.one_of! <tail>))))))]
@@ -125,7 +125,7 @@
(def class'
(-> (Parser (Type Parameter)) (Parser (Type Class)))
(|>> ..class''
- (at <>.monad each (product.uncurried //.class))))
+ (of <>.monad each (product.uncurried //.class))))
(def .public array'
(-> (Parser (Type Value)) (Parser (Type Array)))
diff --git a/stdlib/source/library/lux/meta/target/jvm/type/reflection.lux b/stdlib/source/library/lux/meta/target/jvm/type/reflection.lux
index 003030a9b..1478a0494 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type/reflection.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type/reflection.lux
@@ -64,7 +64,7 @@
element'
(,, (with_template [<primitive> <descriptor>]
- [(at ..equivalence = <primitive> element)
+ [(of ..equivalence = <primitive> element)
(//descriptor.descriptor <descriptor>)]
[..boolean //descriptor.boolean]
diff --git a/stdlib/source/library/lux/meta/target/lua.lux b/stdlib/source/library/lux/meta/target/lua.lux
index 0bafbd9ca..84a566839 100644
--- a/stdlib/source/library/lux/meta/target/lua.lux
+++ b/stdlib/source/library/lux/meta/target/lua.lux
@@ -47,13 +47,13 @@
(All (_ brand) (Equivalence (Code brand)))
(implementation
(def (= reference subject)
- (at text.equivalence = (representation reference) (representation subject)))))
+ (of text.equivalence = (representation reference) (representation subject)))))
(def .public hash
(All (_ brand) (Hash (Code brand)))
(implementation
(def equivalence ..equivalence)
- (def hash (|>> representation (at text.hash hash)))))
+ (def hash (|>> representation (of text.hash hash)))))
(def .public manual
(-> Text Code)
@@ -100,7 +100,7 @@
(-> Int Literal)
... Integers must be turned into hexadecimal to avoid quirks in how Lua parses integers.
... In particular, the number -9223372036854775808 will be incorrectly parsed as a float by Lua.
- (.let [to_hex (at n.hex encoded)]
+ (.let [to_hex (of n.hex encoded)]
(|>> .nat
to_hex
(format "0x")
diff --git a/stdlib/source/library/lux/meta/target/php.lux b/stdlib/source/library/lux/meta/target/php.lux
index 44e663934..cb4d0a622 100644
--- a/stdlib/source/library/lux/meta/target/php.lux
+++ b/stdlib/source/library/lux/meta/target/php.lux
@@ -55,13 +55,13 @@
(All (_ brand) (Equivalence (Code brand)))
(implementation
(def (= reference subject)
- (at text.equivalence = (representation reference) (representation subject)))))
+ (of text.equivalence = (representation reference) (representation subject)))))
(def .public hash
(All (_ brand) (Hash (Code brand)))
(implementation
(def equivalence ..equivalence)
- (def hash (|>> representation (at text.hash hash)))))
+ (def hash (|>> representation (of text.hash hash)))))
(def .public manual
(-> Text Code)
@@ -141,7 +141,7 @@
(def .public int
(-> Int Literal)
- (.let [to_hex (at n.hex encoded)]
+ (.let [to_hex (of n.hex encoded)]
(|>> .nat
to_hex
(format "0x")
diff --git a/stdlib/source/library/lux/meta/target/python.lux b/stdlib/source/library/lux/meta/target/python.lux
index 9d426d1ed..a6d0968c5 100644
--- a/stdlib/source/library/lux/meta/target/python.lux
+++ b/stdlib/source/library/lux/meta/target/python.lux
@@ -64,13 +64,13 @@
(All (_ brand) (Equivalence (Code brand)))
(implementation
(.def (= reference subject)
- (at text.equivalence = (representation reference) (representation subject)))))
+ (of text.equivalence = (representation reference) (representation subject)))))
(.def .public hash
(All (_ brand) (Hash (Code brand)))
(implementation
(.def equivalence ..equivalence)
- (.def hash (|>> representation (at text.hash hash)))))
+ (.def hash (|>> representation (of text.hash hash)))))
(.def .public manual
(-> Text Code)
diff --git a/stdlib/source/library/lux/meta/target/ruby.lux b/stdlib/source/library/lux/meta/target/ruby.lux
index 17892b773..82fbaa9b4 100644
--- a/stdlib/source/library/lux/meta/target/ruby.lux
+++ b/stdlib/source/library/lux/meta/target/ruby.lux
@@ -47,7 +47,7 @@
(All (_ brand) (Equivalence (Code brand)))
(implementation
(def (= reference subject)
- (at text.equivalence = (representation reference) (representation subject)))))
+ (of text.equivalence = (representation reference) (representation subject)))))
(def .public manual
(-> Text Code)
diff --git a/stdlib/source/library/lux/meta/target/scheme.lux b/stdlib/source/library/lux/meta/target/scheme.lux
index f9a3a71df..4c8049fce 100644
--- a/stdlib/source/library/lux/meta/target/scheme.lux
+++ b/stdlib/source/library/lux/meta/target/scheme.lux
@@ -39,13 +39,13 @@
(All (_ brand) (Equivalence (Code brand)))
(implementation
(def (= reference subject)
- (at text.equivalence = (representation reference) (representation subject)))))
+ (of text.equivalence = (representation reference) (representation subject)))))
(def .public hash
(All (_ brand) (Hash (Code brand)))
(implementation
(def equivalence ..equivalence)
- (def hash (|>> representation (at text.hash hash)))))
+ (def hash (|>> representation (of text.hash hash)))))
(with_template [<type> <brand> <super>+]
[(nominal.def .public (<brand> brand) Any)