aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/target
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/target')
-rw-r--r--stdlib/source/library/lux/target/js.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode.lux12
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/address.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/instruction.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/class.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/constant.lux14
-rw-r--r--stdlib/source/library/lux/target/jvm/constant/pool.lux4
-rw-r--r--stdlib/source/library/lux/target/jvm/field.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/index.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/method.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/modifier.lux10
-rw-r--r--stdlib/source/library/lux/target/jvm/reflection.lux14
-rw-r--r--stdlib/source/library/lux/target/jvm/type.lux14
-rw-r--r--stdlib/source/library/lux/target/jvm/type/alias.lux4
-rw-r--r--stdlib/source/library/lux/target/jvm/type/descriptor.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/type/parser.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/type/reflection.lux2
-rw-r--r--stdlib/source/library/lux/target/lua.lux6
-rw-r--r--stdlib/source/library/lux/target/php.lux6
-rw-r--r--stdlib/source/library/lux/target/python.lux4
-rw-r--r--stdlib/source/library/lux/target/ruby.lux2
-rw-r--r--stdlib/source/library/lux/target/scheme.lux4
26 files changed, 77 insertions, 77 deletions
diff --git a/stdlib/source/library/lux/target/js.lux b/stdlib/source/library/lux/target/js.lux
index 708ba4abe..e1d894f56 100644
--- a/stdlib/source/library/lux/target/js.lux
+++ b/stdlib/source/library/lux/target/js.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux (.except Location Code Label or and function if undefined for comment not int try ++ -- the type_of)
+ [lux (.except Location Code Label or and function if undefined for comment not int try ++ -- the type_of at)
[control
["[0]" pipe]]
[data
diff --git a/stdlib/source/library/lux/target/jvm/attribute.lux b/stdlib/source/library/lux/target/jvm/attribute.lux
index 4819f19ea..2d356943d 100644
--- a/stdlib/source/library/lux/target/jvm/attribute.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute.lux
@@ -135,7 +135,7 @@
(-> (Signature category) (Resource Attribute)))
(do [! //pool.monad]
[it (|> it //signature.signature //pool.utf8)]
- (# ! each (signature' it) (//pool.utf8 "Signature"))))
+ (at ! each (signature' it) (//pool.utf8 "Signature"))))
(def: .public (writer it)
(Writer Attribute)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux
index 4963f5151..5eb093897 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode.lux
@@ -105,7 +105,7 @@
(function (_ resolver)
(<| (try|do [left_exceptions left_instruction] (left resolver))
(try|do [right_exceptions right_instruction] (right resolver))
- (try|in [(# sequence.monoid composite left_exceptions right_exceptions)
+ (try|in [(at sequence.monoid composite left_exceptions right_exceptions)
(_#composite left_instruction right_instruction)])))))
(implementation: relative_monoid
@@ -683,7 +683,7 @@
(-> Nat (Bytecode Register))
(case (//unsigned.u1 id)
{try.#Success register}
- (# ..monad in register)
+ (at ..monad in register)
{try.#Failure error}
(..except ..invalid_register [id])))
@@ -851,7 +851,7 @@
[(function (_ resolver)
(<| (try|do [expected @to] (..resolve_label label resolver))
(try|do _ (exception.assertion ..mismatched_environments [(symbol <instruction>) label @here expected actual]
- (# /stack.equivalence = expected actual)))
+ (at /stack.equivalence = expected actual)))
(try|do jump (..jump @from @to))
(case jump
{.#Left jump}
@@ -900,7 +900,7 @@
(case (dictionary.value label resolver)
{.#Some [expected {.#Some @to}]}
(<| (try|do _ (exception.assertion ..mismatched_environments [(symbol <instruction>) label @here expected actual]
- (# /stack.equivalence = expected actual)))
+ (at /stack.equivalence = expected actual)))
(try|do jump (..jump @from @to))
(case jump
{.#Left jump}
@@ -959,7 +959,7 @@
(|> afterwards
(monad.each ! get)
(monad.then ! (monad.each ! product.right))
- (# ! each (|>> [@default @at_minimum]))))
+ (at ! 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)))
@@ -1000,7 +1000,7 @@
(|> cases
(monad.each ! (|>> product.right get))
(monad.then ! (monad.each ! product.right))
- (# ! each (|>> [@default]))))
+ (at ! 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/target/jvm/bytecode/address.lux b/stdlib/source/library/lux/target/jvm/bytecode/address.lux
index cf35e0da3..eac99cd2c 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/address.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/address.lux
@@ -38,7 +38,7 @@
(-> U2 (-> Address (Try Address)))
(|>> representation
(///unsigned.+/2 distance)
- (# try.functor each (|>> abstraction))))
+ (at try.functor each (|>> abstraction))))
(def: with_sign
(-> Address (Try S4))
@@ -60,9 +60,9 @@
(Equivalence Address)
(def: (= reference subject)
- (# ///unsigned.equivalence =
- (representation reference)
- (representation subject))))
+ (at ///unsigned.equivalence =
+ (representation reference)
+ (representation subject))))
(def: .public writer
(Writer Address)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
index 7b354ce1e..f2ff4b9f9 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
@@ -74,7 +74,7 @@
(-> Stack Environment (Try [Stack Environment]))
(case (the ..#stack environment)
{.#Some actual}
- (if (# /stack.equivalence = expected actual)
+ (if (at /stack.equivalence = expected actual)
{try.#Success [actual environment]}
(exception.except ..mismatched_stacks [expected actual]))
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 b8ae7a3c3..336ab6035 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
@@ -60,9 +60,9 @@
(def: .public equivalence
(Equivalence Registry)
- (# equivalence.functor each
- (|>> representation)
- /////unsigned.equivalence))
+ (at equivalence.functor each
+ (|>> representation)
+ /////unsigned.equivalence))
(def: .public writer
(Writer Registry)
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 9de0d677b..3c8e419fb 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
@@ -31,9 +31,9 @@
(def: .public equivalence
(Equivalence Stack)
- (# equivalence.functor each
- (|>> representation)
- /////unsigned.equivalence))
+ (at equivalence.functor each
+ (|>> representation)
+ /////unsigned.equivalence))
(def: .public writer
(Writer Stack)
@@ -48,7 +48,7 @@
(-> U2 (-> Stack (Try Stack)))
(|>> representation
(<op> amount)
- (# try.functor each ..stack)))]
+ (at try.functor each ..stack)))]
[/////unsigned.+/2 push]
[/////unsigned.-/2 pop]
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
index 04756e267..028a60f47 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
@@ -597,8 +597,8 @@
tableswitch_size (try.trusted
(do [! try.monad]
[size (///unsigned.u2 size)]
- (# ! each (|>> estimator ///unsigned.value)
- (//address.move size //address.start))))
+ (at ! each (|>> estimator ///unsigned.value)
+ (//address.move size //address.start))))
tableswitch_mutation (is Mutation
(function (_ [offset binary])
[(n.+ tableswitch_size offset)
@@ -661,8 +661,8 @@
lookupswitch_size (try.trusted
(do [! try.monad]
[size (///unsigned.u2 size)]
- (# ! each (|>> estimator ///unsigned.value)
- (//address.move size //address.start))))
+ (at ! each (|>> estimator ///unsigned.value)
+ (//address.move size //address.start))))
lookupswitch_mutation (is Mutation
(function (_ [offset binary])
[(n.+ lookupswitch_size offset)
diff --git a/stdlib/source/library/lux/target/jvm/class.lux b/stdlib/source/library/lux/target/jvm/class.lux
index 6c4531ed5..9c224c715 100644
--- a/stdlib/source/library/lux/target/jvm/class.lux
+++ b/stdlib/source/library/lux/target/jvm/class.lux
@@ -104,7 +104,7 @@
=methods (monad.all ! methods)
@signature (case signature
{.#Some signature}
- (# ! each (|>> {.#Some}) (//attribute.signature signature))
+ (at ! each (|>> {.#Some}) (//attribute.signature signature))
{.#None}
(in {.#None}))]
diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux
index 98fb0ba60..0ce71dfb1 100644
--- a/stdlib/source/library/lux/target/jvm/constant.lux
+++ b/stdlib/source/library/lux/target/jvm/constant.lux
@@ -53,9 +53,9 @@
(def: .public class_equivalence
(Equivalence Class)
- (# equivalence.functor each
- ..index
- //index.equivalence))
+ (at equivalence.functor each
+ ..index
+ //index.equivalence))
(def: class_writer
(Writer Class)
@@ -93,9 +93,9 @@
(All (_ kind)
(-> (Equivalence kind)
(Equivalence (Value kind))))
- (# equivalence.functor each
- (|>> representation)
- Equivalence<kind>))
+ (at equivalence.functor each
+ (|>> representation)
+ Equivalence<kind>))
(template [<constructor> <type> <marker>]
[(type: .public <type>
@@ -186,7 +186,7 @@
(case [reference sample]
(^.template [<tag> <equivalence>]
[[{<tag> reference} {<tag> sample}]
- (# <equivalence> = reference sample)])
+ (at <equivalence> = reference sample)])
([#UTF8 text.equivalence]
[#Integer (..value_equivalence i32.equivalence)]
[#Long (..value_equivalence int.equivalence)]
diff --git a/stdlib/source/library/lux/target/jvm/constant/pool.lux b/stdlib/source/library/lux/target/jvm/constant/pool.lux
index 2d6c1e4e5..129659e05 100644
--- a/stdlib/source/library/lux/target/jvm/constant/pool.lux
+++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux
@@ -97,7 +97,7 @@
{try.#Success entry}
(case entry
[index {<tag> reference}]
- (if (# <equivalence> = reference <value>')
+ (if (at <equivalence> = reference <value>')
{try.#Success [[current pool]
index]}
<try_again>)
@@ -112,7 +112,7 @@
(|> current
//index.value
(//unsigned.+/2 @new)
- (# try.monad each //index.index))))
+ (at try.monad each //index.index))))
(try|in [[next
(sequence.suffix [current new] pool)]
current]))))))])
diff --git a/stdlib/source/library/lux/target/jvm/field.lux b/stdlib/source/library/lux/target/jvm/field.lux
index 1b8407723..196bd76f2 100644
--- a/stdlib/source/library/lux/target/jvm/field.lux
+++ b/stdlib/source/library/lux/target/jvm/field.lux
@@ -67,7 +67,7 @@
[@name (//constant/pool.utf8 name)
@descriptor (//constant/pool.descriptor (//type.descriptor type))
@signature (if with_signature?
- (# ! each (|>> {.#Some}) (//attribute.signature (//type.signature type)))
+ (at ! each (|>> {.#Some}) (//attribute.signature (//type.signature type)))
(in {.#None}))]
(in [#modifier modifier
#name @name
diff --git a/stdlib/source/library/lux/target/jvm/index.lux b/stdlib/source/library/lux/target/jvm/index.lux
index 9874c56aa..22f4645e3 100644
--- a/stdlib/source/library/lux/target/jvm/index.lux
+++ b/stdlib/source/library/lux/target/jvm/index.lux
@@ -28,9 +28,9 @@
(def: .public equivalence
(All (_ kind) (Equivalence (Index kind)))
- (# equivalence.functor each
- ..value
- //unsigned.equivalence))
+ (at equivalence.functor each
+ ..value
+ //unsigned.equivalence))
(def: .public writer
(All (_ kind) (Writer (Index kind)))
diff --git a/stdlib/source/library/lux/target/jvm/method.lux b/stdlib/source/library/lux/target/jvm/method.lux
index bf2b73cdb..261ae04f6 100644
--- a/stdlib/source/library/lux/target/jvm/method.lux
+++ b/stdlib/source/library/lux/target/jvm/method.lux
@@ -60,7 +60,7 @@
(partial_list (//attribute.signature (//type.signature type)) attributes)
attributes)
(monad.all !)
- (# ! each sequence.of_list))
+ (at ! each sequence.of_list))
attributes (case code
{.#Some code}
(do !
diff --git a/stdlib/source/library/lux/target/jvm/modifier.lux b/stdlib/source/library/lux/target/jvm/modifier.lux
index c15029f4e..d1cb2807b 100644
--- a/stdlib/source/library/lux/target/jvm/modifier.lux
+++ b/stdlib/source/library/lux/target/jvm/modifier.lux
@@ -34,9 +34,9 @@
(All (_ of) (Equivalence (Modifier of)))
(def: (= reference sample)
- (# //unsigned.equivalence =
- (representation reference)
- (representation sample))))
+ (at //unsigned.equivalence =
+ (representation reference)
+ (representation sample))))
(template: (!wrap value)
[(|> value
@@ -54,7 +54,7 @@
(let [sub (!unwrap sub)]
(|> (!unwrap super)
(i64.and sub)
- (# i64.equivalence = sub))))
+ (at i64.equivalence = sub))))
(implementation: .public monoid
(All (_ of) (Monoid (Modifier of)))
@@ -67,7 +67,7 @@
(def: .public empty
Modifier
- (# ..monoid identity))
+ (at ..monoid identity))
(def: .public writer
(All (_ of) (Writer (Modifier of)))
diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux
index 0941e09b1..4bc91291b 100644
--- a/stdlib/source/library/lux/target/jvm/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/reflection.lux
@@ -161,9 +161,9 @@
java/lang/reflect/ParameterizedType::getActualTypeArguments
(array.list {.#None})
(monad.each ! parameter)
- (# ! each (/.class (|> raw'
- (as (java/lang/Class java/lang/Object))
- java/lang/Class::getName)))
+ (at ! each (/.class (|> raw'
+ (as (java/lang/Class java/lang/Object))
+ java/lang/Class::getName)))
(exception.with ..cannot_convert_to_a_lux_type [reflection])))
_
@@ -194,7 +194,7 @@
{try.#Success /.wildcard}
_
- (# try.monad each <kind> (parameter type bound)))])
+ (at try.monad each <kind> (parameter type bound)))])
([[_ {.#Some bound}] /.upper]
[[{.#Some bound} _] /.lower])
@@ -206,7 +206,7 @@
(|> reflection
java/lang/reflect/GenericArrayType::getGenericComponentType
type
- (# try.monad each /.array))
+ (at try.monad each /.array))
_)
(case (ffi.as java/lang/Class reflection)
{.#Some class}
@@ -376,8 +376,8 @@
<then?> (|> fieldJ
java/lang/reflect/Field::getGenericType
..type
- (# ! each (|>> [(java/lang/reflect/Modifier::isFinal modifiers)
- (..deprecated? (java/lang/reflect/Field::getDeclaredAnnotations fieldJ))])))
+ (at ! each (|>> [(java/lang/reflect/Modifier::isFinal modifiers)
+ (..deprecated? (java/lang/reflect/Field::getDeclaredAnnotations fieldJ))])))
<else?> (exception.except <exception> [field class]))))]
[static_field ..not_a_static_field #1 #0]
diff --git a/stdlib/source/library/lux/target/jvm/type.lux b/stdlib/source/library/lux/target/jvm/type.lux
index 21528b3a3..cdf8690e9 100644
--- a/stdlib/source/library/lux/target/jvm/type.lux
+++ b/stdlib/source/library/lux/target/jvm/type.lux
@@ -153,21 +153,21 @@
(All (_ category) (Equivalence (Type category)))
(def: (= parameter subject)
- (# /signature.equivalence =
- (..signature parameter)
- (..signature subject))))
+ (at /signature.equivalence =
+ (..signature parameter)
+ (..signature subject))))
(implementation: .public hash
(All (_ category) (Hash (Type category)))
(def: equivalence ..equivalence)
- (def: hash (|>> ..signature (# /signature.hash hash))))
+ (def: hash (|>> ..signature (at /signature.hash hash))))
(def: .public (primitive? type)
(-> (Type Value) (Either (Type Object)
(Type Primitive)))
(if (`` (or (~~ (template [<type>]
- [(# ..equivalence = (is (Type Value) <type>) type)]
+ [(at ..equivalence = (is (Type Value) <type>) type)]
[..boolean]
[..byte]
@@ -184,7 +184,7 @@
(-> (Type Return) (Either (Type Value)
(Type Void)))
(if (`` (or (~~ (template [<type>]
- [(# ..equivalence = (is (Type Return) <type>) type)]
+ [(at ..equivalence = (is (Type Return) <type>) type)]
[..void]))))
(|> type (as (Type Void)) {.#Right})
@@ -203,7 +203,7 @@
(n.- suffix_size))]
(|> repr
(text.clip prefix_size name_size)
- (# maybe.monad each (|>> //name.internal //name.external))))
+ (at maybe.monad each (|>> //name.internal //name.external))))
{.#None})))
(def: .public format
diff --git a/stdlib/source/library/lux/target/jvm/type/alias.lux b/stdlib/source/library/lux/target/jvm/type/alias.lux
index 7313b1e8b..26462ac28 100644
--- a/stdlib/source/library/lux/target/jvm/type/alias.lux
+++ b/stdlib/source/library/lux/target/jvm/type/alias.lux
@@ -56,7 +56,7 @@
[(def: <name>
(-> (Parser (Type Class)) (Parser (Type Parameter)))
(|>> (<>.after (<text>.this <prefix>))
- (# <>.monad each <bound>)))]
+ (at <>.monad each <bound>)))]
[lower //signature.lower_prefix //.lower ..Lower]
[upper //signature.upper_prefix //.upper ..Upper]
@@ -112,7 +112,7 @@
(def: (bound_type_var aliasing)
(-> Aliasing (Parser (Type Var)))
(|> //parser.var_name
- (# <>.monad each //.var)
+ (at <>.monad each //.var)
(<>.before (<>.many (..bound aliasing)))))
(def: .public (method aliasing)
diff --git a/stdlib/source/library/lux/target/jvm/type/descriptor.lux b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
index 7ded981d8..ba72068a8 100644
--- a/stdlib/source/library/lux/target/jvm/type/descriptor.lux
+++ b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
@@ -119,6 +119,6 @@
(|> (text.size repr)
(n.- prefix_size)
(n.- suffix_size)))
- (# maybe.monad each ///name.internal)
+ (at maybe.monad each ///name.internal)
maybe.trusted))))))
)
diff --git a/stdlib/source/library/lux/target/jvm/type/parser.lux b/stdlib/source/library/lux/target/jvm/type/parser.lux
index a58a6d8d7..54be9b30b 100644
--- a/stdlib/source/library/lux/target/jvm/type/parser.lux
+++ b/stdlib/source/library/lux/target/jvm/type/parser.lux
@@ -68,9 +68,9 @@
(template [<type> <name> <head> <tail> <adapter>]
[(def: .public <name>
(Parser <type>)
- (# <>.functor each <adapter>
- (<text>.slice (<text>.and! (<text>.one_of! <head>)
- (<text>.some! (<text>.one_of! <tail>))))))]
+ (at <>.functor each <adapter>
+ (<text>.slice (<text>.and! (<text>.one_of! <head>)
+ (<text>.some! (<text>.one_of! <tail>))))))]
[External class_name class/set class/set (|>> //name.internal //name.external)]
[Text var_name var/head var/tail function.identity]
@@ -125,7 +125,7 @@
(def: class'
(-> (Parser (Type Parameter)) (Parser (Type Class)))
(|>> ..class''
- (# <>.monad each (product.uncurried //.class))))
+ (at <>.monad each (product.uncurried //.class))))
(def: .public array'
(-> (Parser (Type Value)) (Parser (Type Array)))
diff --git a/stdlib/source/library/lux/target/jvm/type/reflection.lux b/stdlib/source/library/lux/target/jvm/type/reflection.lux
index 47c5d7d73..de9afb234 100644
--- a/stdlib/source/library/lux/target/jvm/type/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/type/reflection.lux
@@ -63,7 +63,7 @@
element'
(~~ (template [<primitive> <descriptor>]
- [(# ..equivalence = <primitive> element)
+ [(at ..equivalence = <primitive> element)
(//descriptor.descriptor <descriptor>)]
[..boolean //descriptor.boolean]
diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux
index f334dbc83..9ececec5f 100644
--- a/stdlib/source/library/lux/target/lua.lux
+++ b/stdlib/source/library/lux/target/lua.lux
@@ -47,13 +47,13 @@
(All (_ brand) (Equivalence (Code brand)))
(def: (= reference subject)
- (# text.equivalence = (representation reference) (representation subject))))
+ (at text.equivalence = (representation reference) (representation subject))))
(implementation: .public hash
(All (_ brand) (Hash (Code brand)))
(def: equivalence ..equivalence)
- (def: hash (|>> representation (# text.hash hash))))
+ (def: hash (|>> representation (at 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 (# n.hex encoded)]
+ (.let [to_hex (at n.hex encoded)]
(|>> .nat
to_hex
(format "0x")
diff --git a/stdlib/source/library/lux/target/php.lux b/stdlib/source/library/lux/target/php.lux
index 52f872a04..efb4674c4 100644
--- a/stdlib/source/library/lux/target/php.lux
+++ b/stdlib/source/library/lux/target/php.lux
@@ -55,13 +55,13 @@
(All (_ brand) (Equivalence (Code brand)))
(def: (= reference subject)
- (# text.equivalence = (representation reference) (representation subject))))
+ (at text.equivalence = (representation reference) (representation subject))))
(implementation: .public hash
(All (_ brand) (Hash (Code brand)))
(def: equivalence ..equivalence)
- (def: hash (|>> representation (# text.hash hash))))
+ (def: hash (|>> representation (at text.hash hash))))
(def: .public manual
(-> Text Code)
@@ -141,7 +141,7 @@
(def: .public int
(-> Int Literal)
- (.let [to_hex (# n.hex encoded)]
+ (.let [to_hex (at n.hex encoded)]
(|>> .nat
to_hex
(format "0x")
diff --git a/stdlib/source/library/lux/target/python.lux b/stdlib/source/library/lux/target/python.lux
index ae5014d34..ba1007f07 100644
--- a/stdlib/source/library/lux/target/python.lux
+++ b/stdlib/source/library/lux/target/python.lux
@@ -64,13 +64,13 @@
(All (_ brand) (Equivalence (Code brand)))
(def: (= reference subject)
- (# text.equivalence = (representation reference) (representation subject))))
+ (at text.equivalence = (representation reference) (representation subject))))
(implementation: .public hash
(All (_ brand) (Hash (Code brand)))
(def: equivalence ..equivalence)
- (def: hash (|>> representation (# text.hash hash))))
+ (def: hash (|>> representation (at text.hash hash))))
(def: .public manual
(-> Text Code)
diff --git a/stdlib/source/library/lux/target/ruby.lux b/stdlib/source/library/lux/target/ruby.lux
index 356906d27..e48a96d1b 100644
--- a/stdlib/source/library/lux/target/ruby.lux
+++ b/stdlib/source/library/lux/target/ruby.lux
@@ -47,7 +47,7 @@
(All (_ brand) (Equivalence (Code brand)))
(def: (= reference subject)
- (# text.equivalence = (representation reference) (representation subject))))
+ (at text.equivalence = (representation reference) (representation subject))))
(def: .public manual
(-> Text Code)
diff --git a/stdlib/source/library/lux/target/scheme.lux b/stdlib/source/library/lux/target/scheme.lux
index e77a76d6d..09d717980 100644
--- a/stdlib/source/library/lux/target/scheme.lux
+++ b/stdlib/source/library/lux/target/scheme.lux
@@ -38,13 +38,13 @@
(All (_ brand) (Equivalence (Code brand)))
(def: (= reference subject)
- (# text.equivalence = (representation reference) (representation subject))))
+ (at text.equivalence = (representation reference) (representation subject))))
(implementation: .public hash
(All (_ brand) (Hash (Code brand)))
(def: equivalence ..equivalence)
- (def: hash (|>> representation (# text.hash hash))))
+ (def: hash (|>> representation (at text.hash hash))))
(template [<type> <brand> <super>+]
[(primitive: .public (<brand> brand) Any)