aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler/language/lux/phase
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux30
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux32
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux46
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux38
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux82
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux44
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux28
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux22
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux6
57 files changed, 277 insertions, 277 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux
index b2a5e9fc6..faa4089a1 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux
@@ -59,7 +59,7 @@
(^ (#.Form (list& [_ (#.Tag tag)]
values)))
(case values
- (#.Cons value #.Nil)
+ (#.Item value #.End)
(/structure.tagged_sum compile tag archive value)
_
@@ -68,7 +68,7 @@
(^ (#.Form (list& [_ (#.Nat lefts)] [_ (#.Bit right?)]
values)))
(case values
- (#.Cons value #.Nil)
+ (#.Item value #.End)
(/structure.sum compile lefts right? archive value)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
index fb8d67bf5..e48d2b1f8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
@@ -62,10 +62,10 @@
(def: (re_quantify envs baseT)
(-> (List (List Type)) Type Type)
(.case envs
- #.Nil
+ #.End
baseT
- (#.Cons head tail)
+ (#.Item head tail)
(re_quantify tail (#.UnivQ head baseT))))
## Type-checking on the input value is done during the analysis of a
@@ -96,7 +96,7 @@
(recur envs unnamedT)
(#.UnivQ env unquantifiedT)
- (recur (#.Cons env envs) unquantifiedT)
+ (recur (#.Item env envs) unquantifiedT)
(#.ExQ _)
(do ///.monad
@@ -182,7 +182,7 @@
[Rev (#.Rev pattern_value) (#/.Rev pattern_value)]
[Frac (#.Frac pattern_value) (#/.Frac pattern_value)]
[Text (#.Text pattern_value) (#/.Text pattern_value)]
- [Any (#.Tuple #.Nil) #/.Unit])
+ [Any (#.Tuple #.End) #/.Unit])
(^ [location (#.Tuple (list singleton))])
(analyse_pattern #.None inputT singleton next)
@@ -301,7 +301,7 @@
(def: #export (case analyse branches archive inputC)
(-> Phase (List [Code Code]) Phase)
(.case branches
- (#.Cons [patternH bodyH] branchesT)
+ (#.Item [patternH bodyH] branchesT)
(do {! ///.monad}
[[inputT inputA] (//type.with_inference
(analyse archive inputC))
@@ -321,5 +321,5 @@
(/.failure error))]
(in (#/.Case inputA [outputH outputT])))
- #.Nil
+ #.End
(/.except ..cannot_have_empty_branches "")))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
index 37177e7ba..9a34b72aa 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
@@ -122,10 +122,10 @@
## their sub-patterns.
(#/.Complex (#/.Tuple membersP+))
(case (list.reverse membersP+)
- (^or #.Nil (#.Cons _ #.Nil))
+ (^or #.End (#.Item _ #.End))
(/.except ..invalid_tuple_pattern [])
- (#.Cons lastP prevsP+)
+ (#.Item lastP prevsP+)
(do ////.monad
[lastC (determine lastP)]
(monad.fold ////.monad
@@ -328,17 +328,17 @@
(function (_ coverageA possibilitiesSF)
(loop [altsSF possibilitiesSF]
(case altsSF
- #.Nil
+ #.End
(in [#.None (list coverageA)])
- (#.Cons altSF altsSF')
+ (#.Item altSF altsSF')
(case (merge coverageA altSF)
(#try.Success altMSF)
(case altMSF
(#Alt _)
(do !
[[success altsSF+] (recur altsSF')]
- (in [success (#.Cons altSF altsSF+)]))
+ (in [success (#.Item altSF altsSF+)]))
_
(in [(#.Some altMSF) altsSF']))
@@ -357,12 +357,12 @@
#.None
(case (list.reverse possibilitiesSF)
- (#.Cons last prevs)
+ (#.Item last prevs)
(in (list\fold (function (_ left right) (#Alt left right))
last
prevs))
- #.Nil
+ #.End
(undefined)))))
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux
index abdf5b806..05a147c3d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux
@@ -110,12 +110,12 @@
(def: #export (general archive analyse inferT args)
(-> Archive Phase Type (List Code) (Operation [Type (List Analysis)]))
(case args
- #.Nil
+ #.End
(do ///.monad
[_ (//type.infer inferT)]
(in [inferT (list)]))
- (#.Cons argC args')
+ (#.Item argC args')
(case inferT
(#.Named name unnamedT)
(general archive analyse unnamedT args)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
index 1ae1152bd..eccae999a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
@@ -106,7 +106,7 @@
(if (list.any? (text\= module)
current)
current
- (#.Cons module current)))))
+ (#.Item module current)))))
state)
[]])))))
@@ -118,7 +118,7 @@
(function (_ state)
(#try.Success [(update@ #.modules
(plist.update self_name (update@ #.module_aliases (: (-> (List [Text Text]) (List [Text Text]))
- (|>> (#.Cons [alias module])))))
+ (|>> (#.Item [alias module])))))
state)
[]])))))
@@ -145,7 +145,7 @@
(plist.put self_name
(update@ #.definitions
(: (-> (List [Text Global]) (List [Text Global]))
- (|>> (#.Cons [name definition])))
+ (|>> (#.Item [name definition])))
self))
state)
[]])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux
index ab202ed61..863975408 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux
@@ -51,12 +51,12 @@
(loop [idx 0
mappings (get@ [#.captured #.mappings] scope)]
(case mappings
- (#.Cons [_name [_source_type _source_ref]] mappings')
+ (#.Item [_name [_source_type _source_ref]] mappings')
(if (text\= name _name)
(#.Some [_source_type (#variable.Foreign idx)])
(recur (inc idx) mappings'))
- #.Nil
+ #.End
#.None)))
(def: (reference? name scope)
@@ -81,22 +81,22 @@
(get@ #.scopes)
(list.split_with (|>> (reference? name) not)))]
(case outer
- #.Nil
+ #.End
(#.Right [state #.None])
- (#.Cons top_outer _)
+ (#.Item top_outer _)
(let [[ref_type init_ref] (maybe.default (undefined)
(..reference name top_outer))
[ref inner'] (list\fold (: (-> Scope [Variable (List Scope)] [Variable (List Scope)])
(function (_ scope ref+inner)
[(#variable.Foreign (get@ [#.captured #.counter] scope))
- (#.Cons (update@ #.captured
+ (#.Item (update@ #.captured
(: (-> Foreign Foreign)
(|>> (update@ #.counter inc)
(update@ #.mappings (plist.put name [ref_type (product.left ref+inner)]))))
scope)
(product.right ref+inner))]))
- [init_ref #.Nil]
+ [init_ref #.End]
(list.reverse inner))
scopes (list\compose inner' outer)]
(#.Right [(set@ #.scopes scopes state)
@@ -110,7 +110,7 @@
(All [a] (-> [Text Type] (Operation a) (Operation a)))
(function (_ [bundle state])
(case (get@ #.scopes state)
- (#.Cons head tail)
+ (#.Item head tail)
(let [old_mappings (get@ [#.locals #.mappings] head)
new_var_id (get@ [#.locals #.counter] head)
new_head (update@ #.locals
@@ -118,12 +118,12 @@
(|>> (update@ #.counter inc)
(update@ #.mappings (plist.put name [type new_var_id]))))
head)]
- (case (///.run' [bundle (set@ #.scopes (#.Cons new_head tail) state)]
+ (case (///.run' [bundle (set@ #.scopes (#.Item new_head tail) state)]
action)
(#try.Success [[bundle' state'] output])
(case (get@ #.scopes state')
- (#.Cons head' tail')
- (let [scopes' (#.Cons (set@ #.locals (get@ #.locals head) head')
+ (#.Item head' tail')
+ (let [scopes' (#.Item (set@ #.locals (get@ #.locals head) head')
tail')]
(#try.Success [[bundle' (set@ #.scopes scopes' state')]
output]))
@@ -159,13 +159,13 @@
(All [a] (-> Text (Operation a) (Operation a)))
(function (_ [bundle state])
(let [parent_name (case (get@ #.scopes state)
- #.Nil
+ #.End
(list)
- (#.Cons top _)
+ (#.Item top _)
(get@ #.name top))]
(case (action [bundle (update@ #.scopes
- (|>> (#.Cons (scope parent_name name)))
+ (|>> (#.Item (scope parent_name name)))
state)])
(#try.Success [[bundle' state'] output])
(#try.Success [[bundle' (update@ #.scopes
@@ -184,10 +184,10 @@
(///extension.lift
(function (_ state)
(case (get@ #.scopes state)
- (#.Cons top _)
+ (#.Item top _)
(#try.Success [state (get@ [#.locals #.counter] top)])
- #.Nil
+ #.End
(exception.except ..cannot_get_next_reference_when_there_is_no_scope [])))))
(def: (ref_to_variable ref)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
index 449ac9606..f3e9d30a1 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
@@ -173,20 +173,20 @@
(loop [membersT+ (type.flat_tuple expectedT)
membersC+ members]
(case [membersT+ membersC+]
- [(#.Cons memberT #.Nil) _]
+ [(#.Item memberT #.End) _]
(//type.with_type memberT
(\ ! map (|>> list) (analyse archive (code.tuple membersC+))))
- [_ (#.Cons memberC #.Nil)]
+ [_ (#.Item memberC #.End)]
(//type.with_type (type.tuple membersT+)
(\ ! map (|>> list) (analyse archive memberC)))
- [(#.Cons memberT membersT+') (#.Cons memberC membersC+')]
+ [(#.Item memberT membersT+') (#.Item memberC membersC+')]
(do !
[memberA (//type.with_type memberT
(analyse archive memberC))
memberA+ (recur membersT+' membersC+')]
- (in (#.Cons memberA memberA+)))
+ (in (#.Item memberA memberA+)))
_
(/.except ..cannot_analyse_tuple [expectedT members]))))]
@@ -302,10 +302,10 @@
(-> (List [Name Code]) (Operation [(List Code) Type]))
(case record
## empty_record = empty_tuple = unit = []
- #.Nil
+ #.End
(\ ///.monad in [(list) Any])
- (#.Cons [head_k head_v] _)
+ (#.Item [head_k head_v] _)
(do {! ///.monad}
[head_k (///extension.lift (meta.normal head_k))
[_ tag_set recordT] (///extension.lift (meta.resolve_tag head_k))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
index 6ff584f36..b34743db7 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -164,7 +164,7 @@
## TODO: Get rid of this template block and use the definition in
## lux/ffi.jvm.lux ASAP
(template [<name> <class>]
- [(def: #export <name> .Type (#.Primitive <class> #.Nil))]
+ [(def: #export <name> .Type (#.Primitive <class> #.End))]
## Boxes
[Boolean box.boolean]
@@ -366,7 +366,7 @@
(case (dictionary.get class ..boxes)
(#.Some [_ primitive_type])
(case parametersT
- #.Nil
+ #.End
(phase\in primitive_type)
_
@@ -528,7 +528,7 @@
(def: (check_jvm objectT)
(-> .Type (Operation (Type Value)))
(case objectT
- (#.Primitive name #.Nil)
+ (#.Primitive name #.End)
(`` (cond (~~ (template [<type>]
[(text\= (..reflection <type>) name)
(phase\in <type>)]
@@ -878,7 +878,7 @@
#.None
(if (java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers from_class))
- (#.Cons (:as java/lang/reflect/Type (ffi.class_for java/lang/Object))
+ (#.Item (:as java/lang/reflect/Type (ffi.class_for java/lang/Object))
(array.to_list (java/lang/Class::getGenericInterfaces from_class)))
(array.to_list (java/lang/Class::getGenericInterfaces from_class)))))))
@@ -952,10 +952,10 @@
(case (|> candidate_parents
(list.only product.right)
(list\map product.left))
- (#.Cons [next_name nextT] _)
+ (#.Item [next_name nextT] _)
(recur [next_name nextT])
- #.Nil
+ #.End
(in false)))))))))]
(if can_cast?
(in (#/////analysis.Extension extension_name (list (/////analysis.text from_name)
@@ -1303,10 +1303,10 @@
(|>> #Hint))
(method_signature method_style method)))))))]
(case (list.all pass! candidates)
- (#.Cons method #.Nil)
+ (#.Item method #.End)
(in method)
- #.Nil
+ #.End
(/////analysis.except ..no_candidates [class_name method_name inputsJT (list.all hint! candidates)])
candidates
@@ -1333,10 +1333,10 @@
(if passes? (|>> #Pass) (|>> #Hint))
(constructor_signature constructor))))))]
(case (list.all pass! candidates)
- (#.Cons constructor #.Nil)
+ (#.Item constructor #.End)
(in constructor)
- #.Nil
+ #.End
(/////analysis.except ..no_candidates [class_name ..constructor_method inputsJT (list.all hint! candidates)])
candidates
@@ -1398,7 +1398,7 @@
(not deprecated?))
[outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list\map product.right argsTC)))
#let [[objectA argsA] (case allA
- (#.Cons objectA argsA)
+ (#.Item objectA argsA)
[objectA argsA]
_
@@ -1444,7 +1444,7 @@
(not deprecated?))
[outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list\map product.right argsTC)))
#let [[objectA argsA] (case allA
- (#.Cons objectA argsA)
+ (#.Item objectA argsA)
[objectA argsA]
_
@@ -1685,7 +1685,7 @@
(in [name luxT])))
arguments)
[scope bodyA] (|> arguments'
- (#.Cons [self_name selfT])
+ (#.Item [self_name selfT])
list.reverse
(list\fold scope.with_local (analyse archive body))
(typeA.with_type .Any)
@@ -1761,7 +1761,7 @@
(in [name luxT])))
arguments)
[scope bodyA] (|> arguments'
- (#.Cons [self_name selfT])
+ (#.Item [self_name selfT])
list.reverse
(list\fold scope.with_local (analyse archive body))
(typeA.with_type returnT)
@@ -2001,7 +2001,7 @@
arguments)
returnT (boxed_reflection_return mapping return)
[scope bodyA] (|> arguments'
- (#.Cons [self_name selfT])
+ (#.Item [self_name selfT])
list.reverse
(list\fold scope.with_local (analyse archive body))
(typeA.with_type returnT)
@@ -2153,7 +2153,7 @@
(analyse archive term))]
(in [type termA])))
constructor_args)
- #let [supers (#.Cons super_class super_interfaces)]
+ #let [supers (#.Item super_class super_interfaces)]
_ (..require_complete_method_concretion class_loader supers methods)
methodsA (monad.map ! (analyse_overriden_method analyse archive selfT mapping supers) methods)]
(in (#/////analysis.Extension extension_name
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux
index ec91d1e10..4fd8d5842 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux
@@ -110,7 +110,7 @@
(/.install "/" (binary _.floor/2))
(/.install "%" (binary _.rem/2))
## (/.install "f64" (unary (_.//2 (_.float +1.0))))
- (/.install "char" (unary (|>> _.code-char/1 _.string/1)))
+ (/.install "char" (unary (|>> _.code_char/1 _.string/1)))
)))
(def: f64_procs
@@ -125,7 +125,7 @@
## (/.install "/" (binary (product.uncurry _.//2)))
## (/.install "%" (binary (product.uncurry _.rem/2)))
## (/.install "i64" (unary _.truncate/1))
- (/.install "encode" (unary _.write-to-string/1))
+ (/.install "encode" (unary _.write_to_string/1))
## (/.install "decode" (unary //runtime.f64//decode))
)))
@@ -139,7 +139,7 @@
(def: (text//char [index text])
(Binary (Expression Any))
- (_.char-code/1 (_.char/2 [text index])))
+ (_.char_code/1 (_.char/2 [text index])))
(def: text_procs
Bundle
@@ -157,7 +157,7 @@
(def: (io//log! message)
(Unary (Expression Any))
- (_.progn (list (_.write-line/1 message)
+ (_.progn (list (_.write_line/1 message)
//runtime.unit)))
(def: io_procs
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux
index 2025fe4e2..3663f845a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux
@@ -110,7 +110,7 @@
(/.install "/" (binary (product.uncurry //runtime.i64//division)))
(/.install "%" (binary (product.uncurry _.remainder/2)))
(/.install "f64" (unary (_.//2 (_.float +1.0))))
- (/.install "char" (unary (|>> _.integer->char/1 (_.make-string/2 (_.int +1)))))
+ (/.install "char" (unary (|>> _.integer->char/1 (_.make_string/2 (_.int +1)))))
)))
(def: f64_procs
@@ -142,9 +142,9 @@
(|> /.empty
(/.install "=" (binary (product.uncurry _.string=?/2)))
(/.install "<" (binary (product.uncurry _.string<?/2)))
- (/.install "concat" (binary (product.uncurry _.string-append/2)))
+ (/.install "concat" (binary (product.uncurry _.string_append/2)))
(/.install "index" (trinary ..text//index))
- (/.install "size" (unary _.string-length/1))
+ (/.install "size" (unary _.string_length/1))
(/.install "char" (binary (product.uncurry //runtime.text//char)))
(/.install "clip" (trinary ..text//clip))
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux
index 33a9624c3..23f6056ae 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux
@@ -35,15 +35,15 @@
(def: (array::new size)
(Unary Expression)
- (_.make-vector/2 size _.nil))
+ (_.make_vector/2 size _.nil))
(def: array::length
(Unary Expression)
- _.vector-length/1)
+ _.vector_length/1)
(def: (array::read [indexG arrayG])
(Binary Expression)
- (_.vector-ref/2 arrayG indexG))
+ (_.vector_ref/2 arrayG indexG))
(def: (array::write [indexG valueG arrayG])
(Trinary Expression)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
index 45e2a3bba..098674e45 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
@@ -171,7 +171,7 @@
then!))))
(^template [<tag> <format> <=>]
- [(<tag> cons)
+ [(<tag> item)
(do {! ///////phase.monad}
[clauses (monad.map ! (function (_ [match then])
(do !
@@ -179,7 +179,7 @@
(in [(<=> [(|> match <format>)
..peek])
then!])))
- (#.Cons cons))]
+ (#.Item item))]
(in (list\fold (function (_ [when then] else)
(_.if when then else))
(_.go @fail)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux
index baac3e891..1853971a6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux
@@ -12,7 +12,7 @@
[collection
["." dictionary]]]
[target
- ["_" common-lisp (#+ Expression)]]]]
+ ["_" common_lisp (#+ Expression)]]]]
["." /// #_
["#." runtime (#+ Operation Phase Handler Bundle)]
["#." primitive]
@@ -23,35 +23,35 @@
[extension
["." bundle]]]]])
-(def: lux-procs
+(def: lux_procs
Bundle
(|> bundle.empty
(bundle.install "is" (binary (product.uncurry _.eq)))
(bundle.install "try" (unary ///runtime.lux//try))))
-(def: (i64//left-shift [paramG subjectG])
+(def: (i64//left_shift [paramG subjectG])
(Binary (Expression Any))
(_.ash (_.rem (_.int +64) paramG) subjectG))
-(def: (i64//arithmetic-right-shift [paramG subjectG])
+(def: (i64//arithmetic_right_shift [paramG subjectG])
(Binary (Expression Any))
(_.ash (|> paramG (_.rem (_.int +64)) (_.* (_.int -1)))
subjectG))
-(def: (i64//logic-right-shift [paramG subjectG])
+(def: (i64//logic_right_shift [paramG subjectG])
(Binary (Expression Any))
- (///runtime.i64//logic-right-shift (_.rem (_.int +64) paramG) subjectG))
+ (///runtime.i64//logic_right_shift (_.rem (_.int +64) paramG) subjectG))
-(def: i64-procs
+(def: i64_procs
Bundle
(<| (bundle.prefix "i64")
(|> bundle.empty
(bundle.install "and" (binary (product.uncurry _.logand)))
(bundle.install "or" (binary (product.uncurry _.logior)))
(bundle.install "xor" (binary (product.uncurry _.logxor)))
- (bundle.install "left-shift" (binary i64//left-shift))
- (bundle.install "logical-right-shift" (binary i64//logic-right-shift))
- (bundle.install "arithmetic-right-shift" (binary i64//arithmetic-right-shift))
+ (bundle.install "left-shift" (binary i64//left_shift))
+ (bundle.install "logical-right-shift" (binary i64//logic_right_shift))
+ (bundle.install "arithmetic-right-shift" (binary i64//arithmetic_right_shift))
(bundle.install "=" (binary (product.uncurry _.=)))
(bundle.install "<" (binary (product.uncurry _.<)))
(bundle.install "+" (binary (product.uncurry _.+)))
@@ -61,10 +61,10 @@
(bundle.install "%" (binary (product.uncurry _.rem)))
(bundle.install "f64" (unary (function (_ value)
(_.coerce/2 [value (_.symbol "double-float")]))))
- (bundle.install "char" (unary (|>> _.code-char/1 _.string/1)))
+ (bundle.install "char" (unary (|>> _.code_char/1 _.string/1)))
)))
-(def: f64-procs
+(def: f64_procs
Bundle
(<| (bundle.prefix "f64")
(|> bundle.empty
@@ -76,12 +76,12 @@
(bundle.install "=" (binary (product.uncurry _.=)))
(bundle.install "<" (binary (product.uncurry _.<)))
(bundle.install "i64" (unary _.floor/1))
- (bundle.install "encode" (unary _.write-to-string/1))
+ (bundle.install "encode" (unary _.write_to_string/1))
(bundle.install "decode" (unary (let [@temp (_.var "temp")]
(function (_ input)
- (_.let (list [@temp (_.read-from-string/1 input)])
+ (_.let (list [@temp (_.read_from_string/1 input)])
(_.if (_.equal (_.symbol "DOUBLE-FLOAT")
- (_.type-of/1 @temp))
+ (_.type_of/1 @temp))
(///runtime.some @temp)
///runtime.none)))))))))
@@ -99,7 +99,7 @@
(Trinary (Expression Any))
(///runtime.text//index textO partO startO))
-(def: text-procs
+(def: text_procs
Bundle
(<| (bundle.prefix "text")
(|> bundle.empty
@@ -108,7 +108,7 @@
(bundle.install "concat" (binary _.concatenate/2|string))
(bundle.install "index" (trinary text//index))
(bundle.install "size" (unary _.length/1))
- (bundle.install "char" (binary (|>> _.char/2 _.char-int/1)))
+ (bundle.install "char" (binary (|>> _.char/2 _.char_int/1)))
(bundle.install "clip" (trinary text//clip))
)))
@@ -118,7 +118,7 @@
code
///runtime.unit))
-(def: io-procs
+(def: io_procs
Bundle
(<| (bundle.prefix "io")
(|> bundle.empty
@@ -129,9 +129,9 @@
(def: #export bundle
Bundle
(<| (bundle.prefix "lux")
- (|> lux-procs
- (dictionary.merge i64-procs)
- (dictionary.merge f64-procs)
- (dictionary.merge text-procs)
- (dictionary.merge io-procs)
+ (|> lux_procs
+ (dictionary.merge i64_procs)
+ (dictionary.merge f64_procs)
+ (dictionary.merge text_procs)
+ (dictionary.merge io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux
index a43c24bc8..fab6fe24c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux
@@ -43,7 +43,7 @@
(def: (with_closure inits function_definition)
(-> (List (Expression Any)) (Expression Any) (Operation (Expression Any)))
(case inits
- #.Nil
+ #.End
(\ ///////phase.monad in function_definition)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux
index 5d7faa8f8..bbb46cba2 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux
@@ -36,7 +36,7 @@
(Generator (Scope Synthesis))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(expression archive bodyS)
## true loop
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux
index b9b97fdbe..fd0e7a780 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux
@@ -139,7 +139,7 @@
(runtime: (lux//try op)
(with_vars [error]
- (_.handler-case
+ (_.handler_case
(list [(_.bool true) error
(..left (_.format/3 [_.nil (_.string "~A") error]))])
(..right (_.funcall/+ [op (list ..unit)])))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux
index 6cfd16cc4..a0b6b78e9 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux
@@ -17,10 +17,10 @@
(def: #export (tuple expression archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
- #.Nil
+ #.End
(///////phase\in (//primitive.text /////synthesis.unit))
- (#.Cons singletonS #.Nil)
+ (#.Item singletonS #.End)
(expression archive singletonS)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
index 8c0ef681a..7beef96cb 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
@@ -251,7 +251,7 @@
else!
then!))))
- (#/////synthesis.I64_Fork cons)
+ (#/////synthesis.I64_Fork item)
(do {! ///////phase.monad}
[clauses (monad.map ! (function (_ [match then])
(do !
@@ -259,15 +259,15 @@
(in [(//runtime.i64//= (//primitive.i64 (.int match))
..peek_cursor)
then!])))
- (#.Cons cons))]
+ (#.Item item))]
(in (_.cond clauses ..fail_pm!)))
(^template [<tag> <format>]
- [(<tag> cons)
+ [(<tag> item)
(do {! ///////phase.monad}
[cases (monad.map ! (function (_ [match then])
(\ ! map (|>> [(list (<format> match))]) (recur then)))
- (#.Cons cons))]
+ (#.Item item))]
(in (_.switch ..peek_cursor
cases
(#.Some ..fail_pm!))))])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux
index b06f9e347..d4b81f29b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux
@@ -41,7 +41,7 @@
(def: (with_closure @self inits body!)
(-> Var (List Expression) Statement [Statement Expression])
(case inits
- #.Nil
+ #.End
[(_.function! @self (list) body!)
@self]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
index 8e9f4265c..de6b0a500 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
@@ -45,7 +45,7 @@
(Generator! (Scope Synthesis))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(statement expression archive bodyS)
## true loop
@@ -64,7 +64,7 @@
(-> Phase! (Generator (Scope Synthesis)))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(expression archive bodyS)
## true loop
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux
index 1b3f8e526..5cbacf111 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux
@@ -17,10 +17,10 @@
(def: #export (tuple generate archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
- #.Nil
+ #.End
(///////phase\in //runtime.unit)
- (#.Cons singletonS #.Nil)
+ (#.Item singletonS #.End)
(generate archive singletonS)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux
index cfe49a36b..d3e13091a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux
@@ -97,7 +97,7 @@
@labelsT (|> _.new_label
(list.repeat (dec num_partials))
(monad.seq _.monad))
- #let [cases (|> (list\compose (#.Cons [@labelsH @labelsT])
+ #let [cases (|> (list\compose (#.Item [@labelsH @labelsT])
(list @default))
list.enumeration
(list\map (function (_ [stage @case])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux
index b997af01d..06b60b6c1 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux
@@ -29,10 +29,10 @@
(def: #export (tuple generate archive membersS)
(Generator (Tuple Synthesis))
(case membersS
- #.Nil
+ #.End
(\ phase.monad in //runtime.unit)
- (#.Cons singletonS #.Nil)
+ (#.Item singletonS #.End)
(generate archive singletonS)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
index 94b086149..2114acc89 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
@@ -190,7 +190,7 @@
then!))))
(^template [<tag> <format>]
- [(<tag> cons)
+ [(<tag> item)
(do {! ///////phase.monad}
[clauses (monad.map ! (function (_ [match then])
(do !
@@ -198,7 +198,7 @@
(in [(_.= (|> match <format>)
..peek)
then!])))
- (#.Cons cons))]
+ (#.Item item))]
(in (_.cond clauses ..fail!)))])
([#/////synthesis.I64_Fork (<| _.int .int)]
[#/////synthesis.F64_Fork _.float]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
index 66f2aa0c4..9affe12f6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
@@ -43,7 +43,7 @@
(def: (with_closure inits @self @args body!)
(-> (List Expression) Var (List Var) Statement [Statement Expression])
(case inits
- #.Nil
+ #.End
[(_.function @self @args body!)
@self]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
index 7d063fa09..5d44bcc3c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
@@ -53,7 +53,7 @@
(Operation [(List Expression) Statement]))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(|> bodyS
(statement expression archive)
(\ ///////phase.monad map (|>> [(list)])))
@@ -75,7 +75,7 @@
(-> Phase! (Generator (Scope Synthesis)))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(expression archive bodyS)
## true loop
@@ -93,7 +93,7 @@
(set.of_list _.hash)
(set.difference (set.of_list _.hash locals))
set.to_list)
- #.Nil
+ #.End
[(_.function @loop locals
scope!)
@loop]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux
index 56954873e..8b070c7a3 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux
@@ -17,10 +17,10 @@
(def: #export (tuple generate archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
- #.Nil
+ #.End
(///////phase\in (//primitive.text /////synthesis.unit))
- (#.Cons singletonS #.Nil)
+ (#.Item singletonS #.End)
(generate archive singletonS)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux
index 12714b2cd..aad40560a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux
@@ -59,7 +59,7 @@
(//////phase\map _.return (/function.function statement expression archive abstraction))
))
-(exception: #export cannot-recur-as-an-expression)
+(exception: #export cannot_recur_as_an_expression)
(def: #export (expression archive synthesis)
Phase
@@ -93,7 +93,7 @@
[////synthesis.function/abstraction /function.function])
(^ (////synthesis.loop/recur _))
- (//////phase.except ..cannot-recur-as-an-expression [])
+ (//////phase.except ..cannot_recur_as_an_expression [])
(#////synthesis.Extension extension)
(///extension.apply archive expression extension)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
index 48a05b104..af27eb9fc 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
@@ -190,7 +190,7 @@
then!))))
(^template [<tag> <format>]
- [(<tag> cons)
+ [(<tag> item)
(do {! ///////phase.monad}
[clauses (monad.map ! (function (_ [match then])
(do !
@@ -198,7 +198,7 @@
(in [(_.=== (|> match <format>)
..peek)
then!])))
- (#.Cons cons))]
+ (#.Item item))]
(in (_.cond clauses ..fail!)))])
([#/////synthesis.I64_Fork //primitive.i64]
[#/////synthesis.F64_Fork //primitive.f64]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
index 5eaccf0aa..8da358393 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
@@ -24,28 +24,28 @@
[extension
["." bundle]]]]])
-(def: lux-procs
+(def: lux_procs
Bundle
(|> bundle.empty
(bundle.install "is" (binary (product.uncurry _.=)))
(bundle.install "try" (unary ///runtime.lux//try))))
-(def: i64-procs
+(def: i64_procs
Bundle
(<| (bundle.prefix "i64")
(|> bundle.empty
- (bundle.install "and" (binary (product.uncurry _.bit-and)))
- (bundle.install "or" (binary (product.uncurry _.bit-or)))
- (bundle.install "xor" (binary (product.uncurry _.bit-xor)))
- (bundle.install "left-shift" (binary (product.uncurry _.bit-shl)))
- (bundle.install "logical-right-shift" (binary (product.uncurry ///runtime.i64//logic-right-shift)))
- (bundle.install "arithmetic-right-shift" (binary (product.uncurry _.bit-shr)))
+ (bundle.install "and" (binary (product.uncurry _.bit_and)))
+ (bundle.install "or" (binary (product.uncurry _.bit_or)))
+ (bundle.install "xor" (binary (product.uncurry _.bit_xor)))
+ (bundle.install "left-shift" (binary (product.uncurry _.bit_shl)))
+ (bundle.install "logical-right-shift" (binary (product.uncurry ///runtime.i64//logic_right_shift)))
+ (bundle.install "arithmetic-right-shift" (binary (product.uncurry _.bit_shr)))
(bundle.install "=" (binary (product.uncurry _.=)))
(bundle.install "+" (binary (product.uncurry _.+)))
(bundle.install "-" (binary (product.uncurry _.-)))
)))
-(def: int-procs
+(def: int_procs
Bundle
(<| (bundle.prefix "int")
(|> bundle.empty
@@ -56,7 +56,7 @@
(bundle.install "frac" (unary _.floatval/1))
(bundle.install "char" (unary _.chr/1)))))
-(def: frac-procs
+(def: frac_procs
Bundle
(<| (bundle.prefix "frac")
(|> bundle.empty
@@ -76,7 +76,7 @@
(Trinary (Expression Any))
(///runtime.text//index textO partO startO))
-(def: text-procs
+(def: text_procs
Bundle
(<| (bundle.prefix "text")
(|> bundle.empty
@@ -91,11 +91,11 @@
(_.substr/3 [text from (_.- from to)]))))
)))
-(def: io-procs
+(def: io_procs
Bundle
(<| (bundle.prefix "io")
(|> bundle.empty
- (bundle.install "log" (unary (|>> (_.concat (_.string text.new-line)) _.print/1)))
+ (bundle.install "log" (unary (|>> (_.concat (_.string text.new_line)) _.print/1)))
(bundle.install "error" (unary ///runtime.io//throw!))
(bundle.install "exit" (unary _.exit/1))
(bundle.install "current-time" (nullary (|>> _.time/0 (_.* (_.int +1,000))))))))
@@ -103,10 +103,10 @@
(def: #export bundle
Bundle
(<| (bundle.prefix "lux")
- (|> lux-procs
- (dictionary.merge i64-procs)
- (dictionary.merge int-procs)
- (dictionary.merge frac-procs)
- (dictionary.merge text-procs)
- (dictionary.merge io-procs)
+ (|> lux_procs
+ (dictionary.merge i64_procs)
+ (dictionary.merge int_procs)
+ (dictionary.merge frac_procs)
+ (dictionary.merge text_procs)
+ (dictionary.merge io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux
index d1cfcea2e..9f02325d3 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux
@@ -50,7 +50,7 @@
(def: (with_closure inits @selfG @selfL body!)
(-> (List Expression) Global Var Statement [Statement Expression])
(case inits
- #.Nil
+ #.End
[($_ _.then
(_.set! @selfL (_.closure (list (_.reference @selfL)) (list) body!))
(_.set! @selfG @selfL))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
index 4952b71ab..82fe69b94 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
@@ -51,7 +51,7 @@
(Generator! (Scope Synthesis))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(statement expression archive bodyS)
## true loop
@@ -70,7 +70,7 @@
(-> Phase! (Generator (Scope Synthesis)))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(expression archive bodyS)
## true loop
@@ -92,7 +92,7 @@
(list\fold set.union (referenced_variables bodyS))
(set.difference loop_variables)
set.to_list)
- #.Nil
+ #.End
[(_.define_function @loop (list) scope!)
@loop]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux
index 5d01a16c6..601361f31 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux
@@ -20,10 +20,10 @@
(def: #export (tuple expression archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
- #.Nil
+ #.End
(///////phase\in (//primitive.text /////synthesis.unit))
- (#.Cons singletonS #.Nil)
+ (#.Item singletonS #.End)
(expression archive singletonS)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux
index d88f2eb0c..1d01ba8b0 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux
@@ -59,7 +59,7 @@
(//////phase\map _.return (/function.function statement expression archive abstraction))
))
-(exception: #export cannot-recur-as-an-expression)
+(exception: #export cannot_recur_as_an_expression)
(def: #export (expression archive synthesis)
Phase
@@ -97,7 +97,7 @@
(/loop.scope ..statement expression archive scope)
(^ (////synthesis.loop/recur updates))
- (//////phase.except ..cannot-recur-as-an-expression [])
+ (//////phase.except ..cannot_recur_as_an_expression [])
(^ (////synthesis.function/abstraction abstraction))
(/function.function ..statement expression archive abstraction)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
index 71e856034..a3f993150 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
@@ -197,14 +197,14 @@
then!)))))
(^template [<tag> <format>]
- [(<tag> cons)
+ [(<tag> item)
(do {! ///////phase.monad}
[clauses (monad.map ! (function (_ [match then])
(\ ! map
(|>> [(_.= (|> match <format>)
..peek)])
(recur then)))
- (#.Cons cons))]
+ (#.Item item))]
(in (#.Some (_.cond clauses
..fail_pm!))))])
([#/////synthesis.I64_Fork (<| //primitive.i64 .int)]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux
index 3c114a935..58d814dcc 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux
@@ -45,7 +45,7 @@
(def: (with_closure function_id @function inits function_definition)
(-> artifact.ID SVar (List (Expression Any)) (Statement Any) (Operation (Expression Any)))
(case inits
- #.Nil
+ #.End
(do ///////phase.monad
[_ (/////generation.execute! function_definition)
_ (/////generation.save! function_id #.None function_definition)]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
index 45dbaf999..066925e96 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
@@ -51,7 +51,7 @@
(Generator! (Scope Synthesis))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(statement expression archive bodyS)
## true loop
@@ -68,7 +68,7 @@
(-> Phase! (Generator (Scope Synthesis)))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(expression archive bodyS)
## true loop
@@ -91,7 +91,7 @@
(set.of_list _.hash)
(set.difference (set.of_list _.hash locals))
set.to_list)
- #.Nil
+ #.End
[actual_loop
@loop]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux
index 394804f3e..4e7bc841d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux
@@ -17,10 +17,10 @@
(def: #export (tuple generate archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
- #.Nil
+ #.End
(///////phase\in (//primitive.text /////synthesis.unit))
- (#.Cons singletonS #.Nil)
+ (#.Item singletonS #.End)
(generate archive singletonS)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux
index 1026bd0fe..133ce1fa8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux
@@ -162,7 +162,7 @@
then!))))
(^template [<tag> <format> <=>]
- [(<tag> cons)
+ [(<tag> item)
(do {! ///////phase.monad}
[clauses (monad.map ! (function (_ [match then])
(do !
@@ -170,7 +170,7 @@
(in [(<=> (|> match <format>)
..peek)
then!])))
- (#.Cons cons))]
+ (#.Item item))]
(in (list\fold (function (_ [when then] else)
(_.if when then else))
..fail!
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux
index ed2ef6a5d..a6497d206 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux
@@ -42,7 +42,7 @@
(def: (with_closure function_id $function inits function_definition)
(-> artifact.ID SVar (List Expression) Expression (Operation Expression))
(case inits
- #.Nil
+ #.End
(do ///////phase.monad
[_ (/////generation.execute! function_definition)
_ (/////generation.save! (%.nat function_id)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux
index 84d61fb44..47bb19e87 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux
@@ -37,7 +37,7 @@
(Generator (Scope Synthesis))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(expression archive bodyS)
## true loop
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
index 557d5b572..225d32a81 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
@@ -10,7 +10,7 @@
[number]
(coll [list "list/" Functor<List>]
(dictionary ["dict" unordered #+ Dict])))
- [macro #+ with-gensyms]
+ [macro #+ with_gensyms]
(macro [code]
["s" syntax #+ syntax:])
[host])
@@ -54,19 +54,19 @@
(|> bundle
dict.entries
(list/map (function (_ [key val]) [(format prefix " " key) val]))
- (dict.from-list text.Hash<Text>)))
+ (dict.from_list text.Hash<Text>)))
-(def: (wrong-arity proc expected actual)
+(def: (wrong_arity proc expected actual)
(-> Text Nat Nat Text)
(format "Wrong number of arguments for " (%t proc) "\n"
"Expected: " (|> expected .int %i) "\n"
" Actual: " (|> actual .int %i)))
-(syntax: (arity: {name s.local-identifier} {arity s.nat})
- (with-gensyms [g!_ g!proc g!name g!translate g!inputs]
+(syntax: (arity: {name s.local_identifier} {arity s.nat})
+ (with_gensyms [g!_ g!proc g!name g!translate g!inputs]
(do {@ macro.monad}
[g!input+ (monad.seq @ (list.repeat arity (macro.gensym "input")))]
- (in (list (` (def: #export ((~ (code.local-identifier name)) (~ g!proc))
+ (in (list (` (def: #export ((~ (code.local_identifier name)) (~ g!proc))
(-> (-> (..Vector (~ (code.nat arity)) Expression) Expression)
(-> Text ..Proc))
(function ((~ g!_) (~ g!name))
@@ -81,7 +81,7 @@
((~' in) ((~ g!proc) [(~+ g!input+)])))
(~' _)
- (macro.failure (wrong-arity (~ g!name) +1 (list.size (~ g!inputs))))))))))))))
+ (macro.failure (wrong_arity (~ g!name) +1 (list.size (~ g!inputs))))))))))))))
(arity: nullary +0)
(arity: unary +1)
@@ -90,7 +90,7 @@
(def: #export (variadic proc)
(-> Variadic (-> Text Proc))
- (function (_ proc-name)
+ (function (_ proc_name)
(function (_ translate inputsS)
(do {@ macro.Monad<Meta>}
[inputsI (monad.map @ translate inputsS)]
@@ -105,39 +105,39 @@
(def: (lux//if [testO thenO elseO])
Trinary
- (caseT.translate-if testO thenO elseO))
+ (caseT.translate_if testO thenO elseO))
(def: (lux//try riskyO)
Unary
(runtimeT.lux//try riskyO))
-(exception: #export (Wrong-Syntax {message Text})
+(exception: #export (Wrong_Syntax {message Text})
message)
-(def: #export (wrong-syntax procedure args)
+(def: #export (wrong_syntax procedure args)
(-> Text (List ls.Synthesis) Text)
(format "Procedure: " procedure "\n"
"Arguments: " (%code (code.tuple args))))
(def: lux//loop
(-> Text Proc)
- (function (_ proc-name)
+ (function (_ proc_name)
(function (_ translate inputsS)
(case (s.run inputsS ($_ p.seq s.nat (s.tuple (p.many s.any)) s.any))
(#e.Success [offset initsS+ bodyS])
- (loopT.translate-loop translate offset initsS+ bodyS)
+ (loopT.translate_loop translate offset initsS+ bodyS)
(#e.Error error)
- (&.throw Wrong-Syntax (wrong-syntax proc-name inputsS)))
+ (&.throw Wrong_Syntax (wrong_syntax proc_name inputsS)))
)))
(def: lux//recur
(-> Text Proc)
- (function (_ proc-name)
+ (function (_ proc_name)
(function (_ translate inputsS)
- (loopT.translate-recur translate inputsS))))
+ (loopT.translate_recur translate inputsS))))
-(def: lux-procs
+(def: lux_procs
Bundle
(|> (dict.new text.Hash<Text>)
(install "is" (binary lux//is))
@@ -161,23 +161,23 @@
(template [<name> <op>]
[(def: (<name> [subjectO paramO])
Binary
- (<op> (runtimeT.int64-low paramO) subjectO))]
+ (<op> (runtimeT.int64_low paramO) subjectO))]
- [bit//left-shift runtimeT.bit//left-shift]
- [bit//arithmetic-right-shift runtimeT.bit//arithmetic-right-shift]
- [bit//logical-right-shift runtimeT.bit//logical-right-shift]
+ [bit//left_shift runtimeT.bit//left_shift]
+ [bit//arithmetic_right_shift runtimeT.bit//arithmetic_right_shift]
+ [bit//logical_right_shift runtimeT.bit//logical_right_shift]
)
-(def: bit-procs
+(def: bit_procs
Bundle
(<| (prefix "bit")
(|> (dict.new text.Hash<Text>)
(install "and" (binary bit//and))
(install "or" (binary bit//or))
(install "xor" (binary bit//xor))
- (install "left-shift" (binary bit//left-shift))
- (install "logical-right-shift" (binary bit//logical-right-shift))
- (install "arithmetic-right-shift" (binary bit//arithmetic-right-shift))
+ (install "left-shift" (binary bit//left_shift))
+ (install "logical-right-shift" (binary bit//logical_right_shift))
+ (install "arithmetic-right-shift" (binary bit//arithmetic_right_shift))
)))
## [[Numbers]]
@@ -238,9 +238,9 @@
(function (_ value)
(r.apply (list value) func)))
-(def: int//char (|>> runtimeT.int64-low (apply1 (r.global "intToUtf8"))))
+(def: int//char (|>> runtimeT.int64_low (apply1 (r.global "intToUtf8"))))
-(def: int-procs
+(def: int_procs
Bundle
(<| (prefix "int")
(|> (dict.new text.Hash<Text>)
@@ -251,14 +251,14 @@
(install "%" (binary int//rem))
(install "=" (binary int//=))
(install "<" (binary int//<))
- (install "to-frac" (unary runtimeT.int//to-float))
+ (install "to-frac" (unary runtimeT.int//to_float))
(install "char" (unary int//char)))))
(def: (frac//encode value)
(-> Expression Expression)
(r.apply (list (r.string "%f") value) (r.global "sprintf")))
-(def: frac-procs
+(def: frac_procs
Bundle
(<| (prefix "frac")
(|> (dict.new text.Hash<Text>)
@@ -293,7 +293,7 @@
Trinary
(runtimeT.text//index textO partO startO))
-(def: text-procs
+(def: text_procs
Bundle
(<| (prefix "text")
(|> (dict.new text.Hash<Text>)
@@ -301,7 +301,7 @@
(install "<" (binary text//<))
(install "concat" (binary text//concat))
(install "index" (trinary text//index))
- (install "size" (unary (|>> (apply1 (r.global "nchar")) runtimeT.int//from-float)))
+ (install "size" (unary (|>> (apply1 (r.global "nchar")) runtimeT.int//from_float)))
(install "char" (binary text//char))
(install "clip" (trinary text//clip))
)))
@@ -309,15 +309,15 @@
## [[IO]]
(def: (io//exit input)
Unary
- (r.apply-kw (list)
- (list ["status" (runtimeT.int//to-float input)])
+ (r.apply_kw (list)
+ (list ["status" (runtimeT.int//to_float input)])
(r.global "quit")))
(def: (void code)
(-> Expression Expression)
(r.block (r.then code runtimeT.unit)))
-(def: io-procs
+(def: io_procs
Bundle
(<| (prefix "io")
(|> (dict.new text.Hash<Text>)
@@ -325,16 +325,16 @@
(install "error" (unary r.stop))
(install "exit" (unary io//exit))
(install "current-time" (nullary (function (_ _)
- (runtimeT.io//current-time! runtimeT.unit)))))))
+ (runtimeT.io//current_time! runtimeT.unit)))))))
## [Bundles]
(def: #export procedures
Bundle
(<| (prefix "lux")
- (|> lux-procs
- (dict.merge bit-procs)
- (dict.merge int-procs)
- (dict.merge frac-procs)
- (dict.merge text-procs)
- (dict.merge io-procs)
+ (|> lux_procs
+ (dict.merge bit_procs)
+ (dict.merge int_procs)
+ (dict.merge frac_procs)
+ (dict.merge text_procs)
+ (dict.merge io_procs)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux
index 74dc0231e..cb0f5e48d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux
@@ -31,7 +31,7 @@
## (in name))
## _
-## (&.throw @.Wrong-Syntax (@.wrong-syntax proc inputs))))
+## (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs))))
## (def: (lua//call proc translate inputs)
## (-> Text @.Proc)
@@ -43,9 +43,9 @@
## (in (lua.apply functionO argsO+)))
## _
-## (&.throw @.Wrong-Syntax (@.wrong-syntax proc inputs))))
+## (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs))))
-## (def: lua-procs
+## (def: lua_procs
## @.Bundle
## (|> (dict.new text.Hash<Text>)
## (@.install "nil" (@.nullary lua//nil))
@@ -63,7 +63,7 @@
## (in (lua.method field tableO argsO+)))
## _
-## (&.throw @.Wrong-Syntax (@.wrong-syntax proc inputs))))
+## (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs))))
## (def: (table//get [fieldO tableO])
## @.Binary
@@ -73,7 +73,7 @@
## @.Trinary
## (runtimeT.lua//set tableO fieldO valueO))
-## (def: table-procs
+## (def: table_procs
## @.Bundle
## (<| (@.prefix "table")
## (|> (dict.new text.Hash<Text>)
@@ -85,6 +85,6 @@
@.Bundle
(<| (@.prefix "lua")
(dict.new text.Hash<Text>)
- ## (|> lua-procs
- ## (dict.merge table-procs))
+ ## (|> lua_procs
+ ## (dict.merge table_procs))
))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux
index 1853aa963..4ea0f31a2 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux
@@ -20,10 +20,10 @@
(def: #export (tuple expression archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
- #.Nil
+ #.End
(///////phase\in (//primitive.text /////synthesis.unit))
- (#.Cons singletonS #.Nil)
+ (#.Item singletonS #.End)
(expression archive singletonS)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux
index f4c393a19..3a80031eb 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux
@@ -59,7 +59,7 @@
(//////phase\map _.return (/function.function statement expression archive abstraction))
))
-(exception: #export cannot-recur-as-an-expression)
+(exception: #export cannot_recur_as_an_expression)
(def: (expression archive synthesis)
Phase
@@ -92,7 +92,7 @@
[////synthesis.function/abstraction /function.function])
(^ (////synthesis.loop/recur _))
- (//////phase.except ..cannot-recur-as-an-expression [])
+ (//////phase.except ..cannot_recur_as_an_expression [])
(#////synthesis.Reference value)
(//reference.reference /reference.system archive value)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
index edb00ae21..69df6f104 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
@@ -206,14 +206,14 @@
then!)))))
(^template [<tag> <format>]
- [(<tag> cons)
+ [(<tag> item)
(do {! ///////phase.monad}
[clauses (monad.map ! (function (_ [match then])
(\ ! map
(|>> [(_.= (|> match <format>)
..peek)])
(recur then)))
- (#.Cons cons))]
+ (#.Item item))]
(in (#.Some (_.cond clauses
..fail!))))])
([#/////synthesis.I64_Fork (<| //primitive.i64 .int)]
@@ -261,14 +261,14 @@
then!))))
(^template [<tag> <format>]
- [(<tag> cons)
+ [(<tag> item)
(do {! ///////phase.monad}
[clauses (monad.map ! (function (_ [match then])
(\ ! map
(|>> [(_.= (|> match <format>)
..peek)])
(recur then)))
- (#.Cons cons))]
+ (#.Item item))]
(in (_.cond clauses
..fail!)))])
([#/////synthesis.I64_Fork (<| //primitive.i64 .int)]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
index eae79b459..8c849da68 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
@@ -45,7 +45,7 @@
(def: (with_closure inits self function_definition)
(-> (List Expression) Text Expression [Statement Expression])
(case inits
- #.Nil
+ #.End
(let [@self (_.global self)]
[(_.set (list @self) function_definition)
@self])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux
index 14f55ae91..ed5370a68 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux
@@ -52,7 +52,7 @@
(Generator! (Scope Synthesis))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(statement expression archive bodyS)
## true loop
@@ -69,7 +69,7 @@
(-> Phase! (Generator (Scope Synthesis)))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(expression archive bodyS)
## true loop
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux
index e5d1da1ea..eaf6add62 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux
@@ -17,10 +17,10 @@
(def: #export (tuple generate archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
- #.Nil
+ #.End
(///////phase\in (//primitive.text /////synthesis.unit))
- (#.Cons singletonS #.Nil)
+ (#.Item singletonS #.End)
(generate archive singletonS)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux
index 43409b31d..9d9c62b18 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux
@@ -156,7 +156,7 @@
then!))))
(^template [<tag> <format> <=>]
- [(<tag> cons)
+ [(<tag> item)
(do {! ///////phase.monad}
[clauses (monad.map ! (function (_ [match then])
(do !
@@ -164,7 +164,7 @@
(in [(<=> (|> match <format>)
..peek)
then!])))
- (#.Cons cons))]
+ (#.Item item))]
(in (list\fold (function (_ [when then] else)
(_.if when then else))
..fail!
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux
index 74362d6ad..6b976b9b6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux
@@ -15,7 +15,7 @@
[collection
["." list ("#\." functor)]
["dict" dictionary (#+ Dictionary)]]]
- ["." macro (#+ with-gensyms)
+ ["." macro (#+ with_gensyms)
["." code]
[syntax (#+ syntax:)]]
[target
@@ -37,11 +37,11 @@
(type: #export Trinary (-> (Vector 3 Expression) Computation))
(type: #export Variadic (-> (List Expression) Computation))
-(syntax: (arity: {name s.local-identifier} {arity s.nat})
- (with-gensyms [g!_ g!extension g!name g!phase g!inputs]
+(syntax: (arity: {name s.local_identifier} {arity s.nat})
+ (with_gensyms [g!_ g!extension g!name g!phase g!inputs]
(do {! macro.monad}
[g!input+ (monad.seq ! (list.repeat arity (macro.gensym "input")))]
- (in (list (` (def: #export ((~ (code.local-identifier name)) (~ g!extension))
+ (in (list (` (def: #export ((~ (code.local_identifier name)) (~ g!extension))
(-> (-> (..Vector (~ (code.nat arity)) Expression) Computation)
Handler)
(function ((~ g!_) (~ g!name) (~ g!phase) (~ g!inputs))
@@ -55,7 +55,7 @@
((~' in) ((~ g!extension) [(~+ g!input+)])))
(~' _)
- (/////.except /////extension.incorrect-arity [(~ g!name) 1 (list.size (~ g!inputs))]))))))))))
+ (/////.except /////extension.incorrect_arity [(~ g!name) 1 (list.size (~ g!inputs))]))))))))))
(arity: nullary 0)
(arity: unary 1)
@@ -64,7 +64,7 @@
(def: #export (variadic extension)
(-> Variadic Handler)
- (function (_ extension-name)
+ (function (_ extension_name)
(function (_ phase inputsS)
(do {! /////.monad}
[inputsI (monad.map ! phase inputsS)]
@@ -81,24 +81,24 @@
Binary
(<op> paramO subjectO))]
- [i64::and _.bit-and/2]
- [i64::or _.bit-or/2]
- [i64::xor _.bit-xor/2]
+ [i64::and _.bit_and/2]
+ [i64::or _.bit_or/2]
+ [i64::xor _.bit_xor/2]
)
-(def: (i64::left-shift [subjectO paramO])
+(def: (i64::left_shift [subjectO paramO])
Binary
- (_.arithmetic-shift/2 (_.remainder/2 (_.int +64) paramO)
+ (_.arithmetic_shift/2 (_.remainder/2 (_.int +64) paramO)
subjectO))
-(def: (i64::arithmetic-right-shift [subjectO paramO])
+(def: (i64::arithmetic_right_shift [subjectO paramO])
Binary
- (_.arithmetic-shift/2 (|> paramO (_.remainder/2 (_.int +64)) (_.*/2 (_.int -1)))
+ (_.arithmetic_shift/2 (|> paramO (_.remainder/2 (_.int +64)) (_.*/2 (_.int -1)))
subjectO))
-(def: (i64::logical-right-shift [subjectO paramO])
+(def: (i64::logical_right_shift [subjectO paramO])
Binary
- (///runtime.i64//logical-right-shift (_.remainder/2 (_.int +64) paramO) subjectO))
+ (///runtime.i64//logical_right_shift (_.remainder/2 (_.int +64) paramO) subjectO))
(template [<name> <op>]
[(def: (<name> [subjectO paramO])
@@ -147,9 +147,9 @@
(bundle.install "and" (binary i64::and))
(bundle.install "or" (binary i64::or))
(bundle.install "xor" (binary i64::xor))
- (bundle.install "left-shift" (binary i64::left-shift))
- (bundle.install "logical-right-shift" (binary i64::logical-right-shift))
- (bundle.install "arithmetic-right-shift" (binary i64::arithmetic-right-shift))
+ (bundle.install "left-shift" (binary i64::left_shift))
+ (bundle.install "logical-right-shift" (binary i64::logical_right_shift))
+ (bundle.install "arithmetic-right-shift" (binary i64::arithmetic_right_shift))
(bundle.install "+" (binary i64::+))
(bundle.install "-" (binary i64::-))
(bundle.install "*" (binary i64::*))
@@ -177,7 +177,7 @@
(def: (text::char [subjectO paramO])
Binary
- (_.string/1 (_.string-ref/2 subjectO paramO)))
+ (_.string/1 (_.string_ref/2 subjectO paramO)))
(def: (text::clip [subjectO startO endO])
Trinary
@@ -189,8 +189,8 @@
(|> bundle.empty
(bundle.install "=" (binary text::=))
(bundle.install "<" (binary text::<))
- (bundle.install "concat" (binary (product.uncurry _.string-append/2)))
- (bundle.install "size" (unary _.string-length/1))
+ (bundle.install "concat" (binary (product.uncurry _.string_append/2)))
+ (bundle.install "size" (unary _.string_length/1))
(bundle.install "char" (binary text::char))
(bundle.install "clip" (trinary text::clip)))))
@@ -210,7 +210,7 @@
(bundle.install "log" (unary (|>> io::log ..void)))
(bundle.install "error" (unary _.raise/1))
(bundle.install "exit" (unary _.exit/1))
- (bundle.install "current-time" (nullary (function (_ _) (///runtime.io//current-time (_.string //////synthesis.unit))))))))
+ (bundle.install "current-time" (nullary (function (_ _) (///runtime.io//current_time (_.string //////synthesis.unit))))))))
(def: #export bundle
Bundle
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux
index dbf2c47b9..dd19db665 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux
@@ -44,7 +44,7 @@
(-> (List Expression) Computation (Operation Computation))
(///////phase\in
(case inits
- #.Nil
+ #.End
function_definition
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux
index 3010bf016..25b0feb46 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux
@@ -40,7 +40,7 @@
(Generator (Scope Synthesis))
(case initsS+
## function/false/non-independent loop
- #.Nil
+ #.End
(expression archive bodyS)
## true loop
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux
index de05f8c6e..140b72106 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux
@@ -115,10 +115,10 @@
(list (_.define_constant last_index_right (..last_index tuple))
(_.if (_.>/2 lefts last_index_right)
## No need for recursion
- (_.vector-ref/2 tuple lefts)
+ (_.vector_ref/2 tuple lefts)
## Needs recursion
(tuple//left (_.-/2 last_index_right lefts)
- (_.vector-ref/2 tuple last_index_right)))))))
+ (_.vector_ref/2 tuple last_index_right)))))))
(runtime: (tuple//right lefts tuple)
(with_vars [last_index_right right_index @slice]
@@ -126,14 +126,14 @@
(list (_.define_constant last_index_right (..last_index tuple))
(_.define_constant right_index (_.+/2 (_.int +1) lefts))
(<| (_.if (_.=/2 last_index_right right_index)
- (_.vector-ref/2 tuple right_index))
+ (_.vector_ref/2 tuple right_index))
(_.if (_.>/2 last_index_right right_index)
## Needs recursion.
(tuple//right (_.-/2 last_index_right lefts)
- (_.vector-ref/2 tuple last_index_right)))
+ (_.vector_ref/2 tuple last_index_right)))
(_.begin
- (list (_.define_constant @slice (_.make-vector/1 (_.-/2 right_index (_.length/1 tuple))))
- (_.vector-copy!/5 @slice (_.int +0) tuple right_index (_.length/1 tuple))
+ (list (_.define_constant @slice (_.make_vector/1 (_.-/2 right_index (_.length/1 tuple))))
+ (_.vector_copy!/5 @slice (_.int +0) tuple right_index (_.length/1 tuple))
@slice))))
)))
@@ -267,7 +267,7 @@
(runtime: (i64//left_shift param subject)
(|> subject
- (_.arithmetic-shift/2 (_.remainder/2 (_.int +64) param))
+ (_.arithmetic_shift/2 (_.remainder/2 (_.int +64) param))
..i64//64))
(def: as_nat
@@ -279,15 +279,15 @@
subject
(|> subject
..as_nat
- (_.arithmetic-shift/2 (_.-/2 shift (_.int +0)))))))
+ (_.arithmetic_shift/2 (_.-/2 shift (_.int +0)))))))
(template [<runtime> <host>]
[(runtime: (<runtime> left right)
(..i64//64 (<host> (..as_nat left) (..as_nat right))))]
- [i64//or _.bitwise-ior/2]
- [i64//xor _.bitwise-xor/2]
- [i64//and _.bitwise-and/2]
+ [i64//or _.bitwise_ior/2]
+ [i64//xor _.bitwise_xor/2]
+ [i64//and _.bitwise_and/2]
)
(runtime: (i64//division param subject)
@@ -319,7 +319,7 @@
(runtime: (text//index offset sub text)
(with_vars [index]
- (_.let (list [index (_.string-contains/3 text sub offset)])
+ (_.let (list [index (_.string_contains/3 text sub offset)])
(_.if index
(..some index)
..none))))
@@ -328,7 +328,7 @@
(_.substring/3 text offset (_.+/2 offset length)))
(runtime: (text//char index text)
- (_.char->integer/1 (_.string-ref/2 text index)))
+ (_.char->integer/1 (_.string_ref/2 text index)))
(def: runtime//text
(_.begin (list @text//index
@@ -336,7 +336,7 @@
@text//char)))
(runtime: (array//write idx value array)
- (_.begin (list (_.vector-set!/3 array idx value)
+ (_.begin (list (_.vector_set!/3 array idx value)
array)))
(def: runtime//array
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux
index 46237d2a2..3cf04831b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux
@@ -20,10 +20,10 @@
(def: #export (tuple expression archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
- #.Nil
+ #.End
(///////phase\in (//primitive.text /////synthesis.unit))
- (#.Cons singletonS #.Nil)
+ (#.Item singletonS #.End)
(expression archive singletonS)
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
index d004e97ef..dc22dc355 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
@@ -101,16 +101,16 @@
[[old_test (weave new_then old_then)] old_tail]
[[old_test old_then]
(case old_tail
- #.Nil
+ #.End
(list [new_test new_then])
- (#.Cons old_cons)
- (#.Cons (weave_branch weave equivalence [new_test new_then] old_cons)))]))
+ (#.Item old_item)
+ (#.Item (weave_branch weave equivalence [new_test new_then] old_item)))]))
(def: (weave_fork weave equivalence new_fork old_fork)
(All [a] (-> (-> Path Path Path) (Equivalence a) (/.Fork a Path) (/.Fork a Path)
(/.Fork a Path)))
- (list\fold (..weave_branch weave equivalence) old_fork (#.Cons new_fork)))
+ (list\fold (..weave_branch weave equivalence) old_fork (#.Item new_fork)))
(def: (weave new old)
(-> Path Path Path)
@@ -199,10 +199,10 @@
(#.Right (dec lefts))
(#.Left lefts)))]
(case patterns
- #.Nil
+ #.End
<failure>
- (#.Cons head tail)
+ (#.Item head tail)
(case head
(#///analysis.Simple #///analysis.Unit)
<continue>
@@ -214,7 +214,7 @@
(#///analysis.Complex (#///analysis.Tuple sub_patterns))
(case (get sub_patterns @selection)
- #.Nil
+ #.End
<continue>
sub_members
@@ -263,7 +263,7 @@
(def: #export (synthesize_get synthesize archive input patterns @member)
(-> Phase Archive Synthesis (///analysis.Tuple ///analysis.Pattern) Register (Operation Synthesis))
(case (..get patterns @member)
- #.Nil
+ #.End
(..synthesize_case synthesize archive input (!get patterns @member))
path
@@ -283,7 +283,7 @@
(..synthesize_masking synthesize^ archive inputS @variable @output)
[[(#///analysis.Bind @variable) body]
- #.Nil]
+ #.End]
(..synthesize_let synthesize^ archive inputS @variable body)
(^or (^ [[(///analysis.pattern/bit #1) then]
@@ -356,7 +356,7 @@
(^or (#/.I64_Fork forks)
(#/.F64_Fork forks)
(#/.Text_Fork forks))
- (|> (#.Cons forks)
+ (|> (#.Item forks)
(list\map product.right)
(list\fold for_path path_storage))
@@ -384,7 +384,7 @@
(update@ #dependencies (set.add var) synthesis_storage)
(^ (/.function/apply [functionS argsS]))
- (list\fold for_synthesis synthesis_storage (#.Cons functionS argsS))
+ (list\fold for_synthesis synthesis_storage (#.Item functionS argsS))
(^ (/.function/abstraction [environment arity bodyS]))
(list\fold for_synthesis synthesis_storage environment)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux
index 074790e37..956c59cd6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux
@@ -197,16 +197,16 @@
(All [a] (-> (Optimization a) (Optimization (List a))))
(function (recur [redundancy values])
(case values
- #.Nil
+ #.End
(#try.Success [redundancy
values])
- (#.Cons head tail)
+ (#.Item head tail)
(do try.monad
[[redundancy head] (optimization [redundancy head])
[redundancy tail] (recur [redundancy tail])]
(in [redundancy
- (#.Cons head tail)])))))
+ (#.Item head tail)])))))
(template [<name>]
[(exception: #export (<name> {register Register})