aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool
diff options
context:
space:
mode:
authorEduardo Julian2020-11-26 19:37:11 -0400
committerEduardo Julian2020-11-26 19:37:11 -0400
commitdbb658bd7976c073a2bf314f194b36b30c45784b (patch)
tree4771bab5e41fe2ba3939bb3a12941a558b68e712 /stdlib/source/lux/tool
parentc4bbfea18d995948012f45a6afda7a6e6ba56f84 (diff)
Allow name formatting for JVM imports, similar to Lux module imports.
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/directive.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/case.lux20
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/function.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/loop.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/runtime.lux23
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux8
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux10
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux15
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/structure.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux12
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux8
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux2
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux8
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux3
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux14
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux16
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux8
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/case.lux26
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/function.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/loop.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux19
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/case.lux30
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/function.lux6
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/loop.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux26
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/structure.lux8
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/reference.lux6
37 files changed, 201 insertions, 187 deletions
diff --git a/stdlib/source/lux/tool/compiler/language/lux/directive.lux b/stdlib/source/lux/tool/compiler/language/lux/directive.lux
index 11dc98bef..788b8fc4a 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/directive.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/directive.lux
@@ -4,7 +4,7 @@
[monad (#+ do)]]
[data
[collection
- ["." list ("#@." monoid)]]]]
+ ["." list ("#\." monoid)]]]]
[//
["." analysis]
["." synthesis]
@@ -44,8 +44,8 @@
(def: #export (merge-requirements left right)
(-> Requirements Requirements Requirements)
- {#imports (list@compose (get@ #imports left) (get@ #imports right))
- #referrals (list@compose (get@ #referrals left) (get@ #referrals right))})
+ {#imports (list\compose (get@ #imports left) (get@ #imports right))
+ #referrals (list\compose (get@ #referrals left) (get@ #referrals right))})
(template [<special> <general>]
[(type: #export (<special> anchor expression directive)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp.lux
index ad04cefdb..975301cef 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp.lux
@@ -6,7 +6,7 @@
[runtime (#+ Phase)]
["." primitive]
["." structure]
- ["." reference ("#@." system)]
+ ["." reference ("#\." system)]
["." case]
["." loop]
["." function]
@@ -34,7 +34,7 @@
(structure.tuple generate members)
(#synthesis.Reference value)
- (reference@reference value)
+ (reference\reference value)
(^ (synthesis.branch/case case))
(case.case generate case)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/case.lux
index dcd47a26d..6c6858ea9 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/case.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/case.lux
@@ -9,7 +9,7 @@
[number
["n" nat]]
[collection
- ["." list ("#@." functor fold)]
+ ["." list ("#\." functor fold)]
["." set]]]
[target
["_" common-lisp (#+ Expression Var/1)]]]
@@ -19,7 +19,7 @@
["#." primitive]
["#/" //
["#." reference]
- ["#/" // ("#@." monad)
+ ["#/" // ("#\." monad)
[synthesis
["." case]]
["#/" // #_
@@ -46,7 +46,7 @@
(Operation (Expression Any)))
(do ////.monad
[valueG (generate valueS)]
- (wrap (list@fold (function (_ side source)
+ (wrap (list\fold (function (_ side source)
(.let [method (.case side
(^template [<side> <accessor>]
[(<side> lefts)
@@ -137,14 +137,14 @@
(:: ////.monad map (_.return-from ..@done) (generate bodyS))
#/////synthesis.Pop
- (////@wrap ..pop!)
+ (////\wrap ..pop!)
(#/////synthesis.Bind register)
- (////@wrap (_.setq (..register register) ..peek))
+ (////\wrap (_.setq (..register register) ..peek))
(^template [<tag> <format> <=>]
[(^ (<tag> value))
- (////@wrap (_.if (|> value <format> (<=> ..peek))
+ (////\wrap (_.if (|> value <format> (<=> ..peek))
_.nil
fail!))])
([/////synthesis.path/bit //primitive.bit _.equal]
@@ -154,7 +154,7 @@
(^template [<complex> <simple> <choice>]
[(^ (<complex> idx))
- (////@wrap (<choice> false idx))
+ (////\wrap (<choice> false idx))
(^ (<simple> idx nextP))
(|> nextP
@@ -164,11 +164,11 @@
[/////synthesis.side/right /////synthesis.simple-right-side ..right-choice])
(^ (/////synthesis.member/left 0))
- (////@wrap (..push! (_.elt/2 [..peek (_.int +0)])))
+ (////\wrap (..push! (_.elt/2 [..peek (_.int +0)])))
(^template [<pm> <getter>]
[(^ (<pm> lefts))
- (////@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))])
+ (////\wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))])
([/////synthesis.member/left //runtime.tuple//left]
[/////synthesis.member/right //runtime.tuple//right])
@@ -176,7 +176,7 @@
(.let [[extra-pops nextP'] (case.count-pops nextP)]
(do ////.monad
[next! (pattern-matching' generate nextP')]
- (////@wrap ($_ _.progn
+ (////\wrap ($_ _.progn
(..multi-pop! (n.+ 2 extra-pops))
next!))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/function.lux
index 196938917..8853de638 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/function.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/function.lux
@@ -7,7 +7,7 @@
[data
["." product]
[collection
- ["." list ("#@." functor fold)]]]
+ ["." list ("#\." functor fold)]]]
[target
["_" common-lisp (#+ Expression)]]]
["." // #_
@@ -43,7 +43,7 @@
(do {! ////.monad}
[@closure (:: ! map _.var (///.gensym "closure"))]
(wrap (_.labels (list [@closure [(|> (list.enumeration inits)
- (list@map (|>> product.left ..capture))
+ (list\map (|>> product.left ..capture))
_.args)
function-definition]])
(_.funcall/+ [(_.function/1 @closure) inits]))))))
@@ -68,7 +68,7 @@
@self (_.var function-name)
initialize-self! [(//case.register 0) (_.function/1 @self)]
initialize! [(|> (list.indices arity)
- (list@map ..input)
+ (list\map ..input)
_.args)
@curried]]]
(with-closure function-name closureG+
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/loop.lux
index 3c3232e64..e3c6d4279 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/loop.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/loop.lux
@@ -9,7 +9,7 @@
[text
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#\." functor)]]]
[target
["_" common-lisp (#+ Expression)]]]
["." // #_
@@ -29,7 +29,7 @@
(generate bodyS))]
(wrap (_.labels (list [@scope {#_.input (|> initsS+
list.enumeration
- (list@map (|>> product.left (n.+ start) //case.register))
+ (list\map (|>> product.left (n.+ start) //case.register))
_.args)
#_.output bodyG}])
(_.funcall/+ [(_.function/1 @scope) initsG+])))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/runtime.lux
index dc8fe6e92..2d9017bcb 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/runtime.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/runtime.lux
@@ -12,7 +12,7 @@
["." text
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#\." functor)]]]
["." macro
["." code]
[syntax (#+ syntax:)]]
@@ -84,7 +84,7 @@
(syntax: #export (with-vars {vars (s.tuple (p.some s.local-identifier))}
body)
(wrap (list (` (let [(~+ (|> vars
- (list@map (function (_ var)
+ (list\map (function (_ var)
(list (code.local-identifier var)
(` (_.var (~ (code.text (/////name.normalize var))))))))
list.concat))]
@@ -109,8 +109,8 @@
(#.Right [name inputs])
(let [code-nameC (code.local-identifier (format "@" name))
runtime-nameC (` (runtime-name (~ (code.text name))))
- inputsC (list@map code.local-identifier inputs)
- inputs-typesC (list@map (function.constant (` (_.Expression Any)))
+ inputsC (list\map code.local-identifier inputs)
+ inputs-typesC (list\map (function.constant (` (_.Expression Any)))
inputs)]
(wrap (list (` (def: #export ((~ (code.local-identifier name)) (~+ inputsC))
(-> (~+ inputs-typesC) (_.Computation Any))
@@ -146,7 +146,8 @@
(def: runtime//lux
($_ _.progn
@lux//try
- @lux//program-args))
+ @lux//program-args
+ ))
(def: last-index
(|>> _.length/1 (_.- (_.int +1))))
@@ -215,7 +216,8 @@
($_ _.progn
@tuple//left
@tuple//right
- @sum//get))
+ @sum//get
+ ))
(runtime: (i64//logic-right-shift shift input)
(_.if (_.= (_.int +0) shift)
@@ -226,7 +228,8 @@
(def: runtime//i64
($_ _.progn
- @i64//logic-right-shift))
+ @i64//logic-right-shift
+ ))
(runtime: (text//clip from to text)
(_.subseq/3 [text from to]))
@@ -241,7 +244,8 @@
(def: runtime//text
($_ _.progn
@text//index
- @text//clip))
+ @text//clip
+ ))
(runtime: (io//exit code)
($_ _.progn
@@ -262,7 +266,8 @@
(def: runtime//io
($_ _.progn
@io//exit
- @io//current-time))
+ @io//current-time
+ ))
(def: runtime
($_ _.progn
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux
index 50730cdda..ce9625452 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/case.lux
@@ -10,7 +10,7 @@
[number
["n" nat]]
[collection
- ["." list ("#@." functor fold)]]]
+ ["." list ("#\." functor fold)]]]
[target
["_" js (#+ Expression Computation Var Statement)]]]
["." // #_
@@ -27,7 +27,7 @@
["//#" /// #_
[reference
[variable (#+ Register)]]
- ["#." phase ("#@." monad)]
+ ["#." phase ("#\." monad)]
[meta
[archive (#+ Archive)]]]]]]])
@@ -74,7 +74,7 @@
(Generator [(List Member) Synthesis])
(do ///////phase.monad
[valueO (generate archive valueS)]
- (wrap (list@fold (function (_ side source)
+ (wrap (list\fold (function (_ side source)
(.let [method (.case side
(^template [<side> <accessor>]
[(<side> lefts)
@@ -168,7 +168,7 @@
[/////synthesis.simple-right-side ..right-choice])
(^ (/////synthesis.member/left 0))
- (///////phase@wrap (#.Some (push-cursor! (_.at (_.i32 +0) ..peek-cursor))))
+ (///////phase\wrap (#.Some (push-cursor! (_.at (_.i32 +0) ..peek-cursor))))
## Extra optimization
(^ (/////synthesis.path/seq
@@ -209,7 +209,7 @@
next!)))))
_
- (///////phase@wrap #.None)))
+ (///////phase\wrap #.None)))
(def: (pattern-matching' statement expression archive)
(-> Phase! Phase Archive
@@ -224,10 +224,10 @@
#.None
(.case pathP
#/////synthesis.Pop
- (///////phase@wrap pop-cursor!)
+ (///////phase\wrap pop-cursor!)
(#/////synthesis.Bind register)
- (///////phase@wrap (_.define (..register register) ..peek-cursor))
+ (///////phase\wrap (_.define (..register register) ..peek-cursor))
(#/////synthesis.Bit-Fork when thenP elseP)
(do {! ///////phase.monad}
@@ -274,13 +274,13 @@
(^template [<complex> <choice>]
[(^ (<complex> idx))
- (///////phase@wrap (<choice> false idx))])
+ (///////phase\wrap (<choice> false idx))])
([/////synthesis.side/left ..left-choice]
[/////synthesis.side/right ..right-choice])
(^template [<pm> <getter>]
[(^ (<pm> lefts))
- (///////phase@wrap (push-cursor! (<getter> (_.i32 (.int lefts)) ..peek-cursor)))])
+ (///////phase\wrap (push-cursor! (<getter> (_.i32 (.int lefts)) ..peek-cursor)))])
([/////synthesis.member/left //runtime.tuple//left]
[/////synthesis.member/right //runtime.tuple//right])
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux
index 0f311d61b..12e328a11 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/function.lux
@@ -9,7 +9,7 @@
[text
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor fold)]]]
+ ["." list ("#\." functor fold)]]]
[target
["_" js (#+ Expression Computation Var Statement)]]]
["." // #_
@@ -26,7 +26,7 @@
[arity (#+ Arity)]
[reference
[variable (#+ Register Variable)]]
- ["#." phase ("#@." monad)]]]]])
+ ["#." phase ("#\." monad)]]]]])
(def: #export (apply generate archive [functionS argsS+])
(Generator (Application Synthesis))
@@ -47,7 +47,7 @@
(|>> (///reference.foreign //reference.system) :assume))]
[(_.function! @self
(|> (list.enumeration inits)
- (list@map (|>> product.left capture)))
+ (list\map (|>> product.left capture)))
(_.return (_.function @self (list) function-body)))
(_.apply/* @self inits)])))
@@ -78,7 +78,7 @@
apply-poly (.function (_ args func)
(|> func (_.do "apply" (list _.null args))))
initialize-self! (_.define (//case.register 0) @self)
- initialize! (list@fold (.function (_ post pre!)
+ initialize! (list\fold (.function (_ post pre!)
($_ _.then
pre!
(_.define (..input post) (_.at (_.i32 (.int post)) @@arguments))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
index 07169e856..5e810a551 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
@@ -9,7 +9,7 @@
[number
["n" nat]]
[collection
- ["." list ("#@." functor fold)]]]
+ ["." list ("#\." functor fold)]]]
[target
["_" js (#+ Computation Var Expression Statement)]]]
["." // #_
@@ -31,13 +31,13 @@
(-> Bit Register (List Expression) Statement Statement)
(|> bindings
list.enumeration
- (list@map (function (_ [register value])
+ (list\map (function (_ [register value])
(let [variable (//case.register (n.+ offset register))]
(if initial?
(_.define variable value)
(_.set variable value)))))
list.reverse
- (list@fold _.then body)))
+ (list\fold _.then body)))
(def: #export (scope! statement expression archive [start initsS+ bodyS])
(Generator! (Scope Synthesis))
@@ -75,7 +75,7 @@
#let [closure (_.closure
(|> initsS+
list.enumeration
- (list@map (|>> product.left (n.+ start) //case.register)))
+ (list\map (|>> product.left (n.+ start) //case.register)))
(_.with-label (_.label @scope)
(_.do-while (_.boolean true)
body!)))]]
@@ -93,6 +93,6 @@
(..setup false offset
(|> argsO+
list.enumeration
- (list@map (function (_ [idx _])
+ (list\map (function (_ [idx _])
(_.at (_.i32 (.int idx)) @temp))))
(_.continue-at (_.label @scope)))))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
index f73decb82..632cc91c2 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
@@ -10,11 +10,11 @@
["." product]
[number (#+ hex)
["." i64]]
- ["." text ("#@." hash)
+ ["." text ("#\." hash)
["%" format (#+ format)]
["." encoding]]
[collection
- ["." list ("#@." functor)]
+ ["." list ("#\." functor)]
["." row]]]
["." macro
["." code]
@@ -89,7 +89,7 @@
[ids (monad.seq ! (list.repeat (list.size vars) macro.count))]
(wrap (list (` (let [(~+ (|> vars
(list.zip/2 ids)
- (list@map (function (_ [id var])
+ (list\map (function (_ [id var])
(list (code.local-identifier var)
(` (_.var (~ (code.text (format "v" (%.nat id)))))))))
list.concat))]
@@ -99,7 +99,7 @@
(-> Text [Code Code])
(let [identifier (format ..prefix
"_" (%.nat $.version)
- "_" (%.nat (text@hash name)))]
+ "_" (%.nat (text\hash name)))]
[(` (_.var (~ (code.text identifier))))
(code.local-identifier identifier)]))
@@ -130,8 +130,8 @@
(let [[runtime-nameC runtime-nameC!] (..runtime-name name)
nameC (code.local-identifier name)
code-nameC (code.local-identifier (format "@" name))
- inputsC (list@map code.local-identifier inputs)
- inputs-typesC (list@map (function.constant (` _.Expression)) inputs)]
+ inputsC (list\map code.local-identifier inputs)
+ inputs-typesC (list\map (function.constant (` _.Expression)) inputs)]
(wrap (list (` (def: ((~ runtime-nameC!) (~+ inputsC))
(-> (~+ inputs-typesC) Computation)
(_.apply/* (~ runtime-nameC) (list (~+ inputsC)))))
@@ -751,7 +751,8 @@
Statement
($_ _.then
@array//write
- @array//delete))
+ @array//delete
+ ))
(def: runtime
Statement
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/structure.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/structure.lux
index acd36a5ba..a90b81f7d 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/structure.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/js/structure.lux
@@ -11,13 +11,13 @@
[analysis (#+ Variant Tuple)]
["#." synthesis (#+ Synthesis)]
["//#" ///
- ["#." phase ("#@." monad)]]]])
+ ["#." phase ("#\." monad)]]]])
(def: #export (tuple generate archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
#.Nil
- (///////phase@wrap //runtime.unit)
+ (///////phase\wrap //runtime.unit)
(#.Cons singletonS #.Nil)
(generate archive singletonS)
@@ -32,6 +32,6 @@
(let [tag (if right?
(inc lefts)
lefts)]
- (///////phase@map (//runtime.variant (_.i32 (.int tag))
+ (///////phase\map (//runtime.variant (_.i32 (.int tag))
(//runtime.flag right?))
(generate archive valueS))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
index 7e7cccc72..010f97349 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
@@ -9,10 +9,10 @@
["." i32]
["n" nat]]
[collection
- ["." list ("#@." fold)]]]
+ ["." list ("#\." fold)]]]
[target
[jvm
- ["_" bytecode (#+ Label Bytecode) ("#@." monad)]
+ ["_" bytecode (#+ Label Bytecode) ("#\." monad)]
["." type (#+ Type)
[category (#+ Method)]]]]]
["." // #_
@@ -24,7 +24,7 @@
["." synthesis (#+ Path Synthesis)]
["." generation]
[///
- ["." phase ("operation@." monad)]
+ ["." phase ("operation\." monad)]
[reference
[variable (#+ Register)]]]]])
@@ -37,7 +37,7 @@
(def: (pop-alt stack-depth)
(-> Nat (Bytecode Any))
(.case stack-depth
- 0 (_@wrap [])
+ 0 (_\wrap [])
1 _.pop
2 _.pop2
_ ## (n.> 2)
@@ -92,10 +92,10 @@
(-> Nat Label Label (Generator Path))
(.case path
#synthesis.Pop
- (operation@wrap ..pop)
+ (operation\wrap ..pop)
(#synthesis.Bind register)
- (operation@wrap ($_ _.compose
+ (operation\wrap ($_ _.compose
..peek
(_.astore register)))
@@ -109,7 +109,7 @@
(^template [<pattern> <right?>]
[(^ (<pattern> lefts))
- (operation@wrap
+ (operation\wrap
(do _.monad
[@success _.new-label
@fail _.new-label]
@@ -132,7 +132,7 @@
(^template [<pattern> <projection>]
[(^ (<pattern> lefts))
- (operation@wrap ($_ _.compose
+ (operation\wrap ($_ _.compose
..peek
(<projection> lefts)
//runtime.push))])
@@ -240,7 +240,7 @@
(Generator [(List synthesis.Member) Synthesis])
(do phase.monad
[recordG (phase archive recordS)]
- (wrap (list@fold (function (_ step so-far)
+ (wrap (list\fold (function (_ step so-far)
(.let [next (.case step
(#.Left lefts)
(..left-projection lefts)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux
index a2c46f8fd..a456644b8 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux
@@ -7,17 +7,17 @@
["." i32]
["n" nat]]
[collection
- ["." list ("#@." monoid functor)]
+ ["." list ("#\." monoid functor)]
["." row]]
["." format #_
["#" binary]]]
[target
[jvm
["." version]
- ["." modifier (#+ Modifier) ("#@." monoid)]
+ ["." modifier (#+ Modifier) ("#\." monoid)]
["." field (#+ Field)]
["." method (#+ Method)]
- ["_" bytecode (#+ Label Bytecode) ("#@." monad)]
+ ["_" bytecode (#+ Label Bytecode) ("#\." monad)]
["." class (#+ Class)]
["." type (#+ Type)
[category (#+ Return' Value')]
@@ -65,7 +65,7 @@
(let [classT (type.class class (list))
fields (: (List (Resource Field))
(list& /arity.constant
- (list@compose (/foreign.variables environment)
+ (list\compose (/foreign.variables environment)
(/partial.variables arity))))
methods (: (List (Resource Method))
(list& (/init.method classT environment arity)
@@ -73,7 +73,7 @@
(if (arity.multiary? arity)
(|> (n.min arity /arity.maximum)
list.indices
- (list@map (|>> inc (/apply.method classT environment arity @begin body)))
+ (list\map (|>> inc (/apply.method classT environment arity @begin body)))
(list& (/implementation.method arity @begin body)))
(list (/implementation.method' //runtime.apply::name arity @begin body)))))]
(do phase.monad
@@ -82,7 +82,7 @@
(def: modifier
(Modifier Class)
- ($_ modifier@compose
+ ($_ modifier\compose
class.public
class.final))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux
index dd8144ea8..f3b4a4720 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux
@@ -6,7 +6,7 @@
[target
[jvm
["." field (#+ Field)]
- ["." modifier (#+ Modifier) ("#@." monoid)]
+ ["." modifier (#+ Modifier) ("#\." monoid)]
[type (#+ Type)
[category (#+ Value)]]
[constant
@@ -14,7 +14,7 @@
(def: modifier
(Modifier Field)
- ($_ modifier@compose
+ ($_ modifier\compose
field.public
field.static
field.final
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux
index 13865b17e..478f9d454 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux
@@ -2,11 +2,11 @@
[lux (#- Type type)
[data
[collection
- ["." list ("#@." functor)]
+ ["." list ("#\." functor)]
["." row]]]
[target
[jvm
- ["." modifier (#+ Modifier) ("#@." monoid)]
+ ["." modifier (#+ Modifier) ("#\." monoid)]
["." field (#+ Field)]
["_" bytecode (#+ Bytecode)]
[type (#+ Type)
@@ -38,7 +38,7 @@
(def: modifier
(Modifier Field)
- ($_ modifier@compose
+ ($_ modifier\compose
field.private
field.final
))
@@ -51,5 +51,5 @@
(-> (-> Register Text) Nat (List (Resource Field)))
(|> amount
list.indices
- (list@map (function (_ register)
+ (list\map (function (_ register)
(..variable (naming register) ..type)))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux
index cbea98db2..1c6bf6455 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux
@@ -2,7 +2,7 @@
[lux (#- Type)
[data
[collection
- ["." list ("#@." functor)]
+ ["." list]
["." row]]]
[target
[jvm
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux
index 57271de30..ff1599a0c 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux
@@ -6,12 +6,12 @@
[number
["n" nat]]
[collection
- ["." list ("#@." functor)]
+ ["." list ("#\." functor)]
["." row]]]
[target
[jvm
["." field (#+ Field)]
- ["_" bytecode (#+ Label Bytecode) ("#@." monad)]
+ ["_" bytecode (#+ Label Bytecode) ("#\." monad)]
[type (#+ Type)
[category (#+ Class)]]
[constant
@@ -35,7 +35,7 @@
(|> _.aconst-null
(list.repeat amount)
(monad.seq _.monad))
- (_@wrap [])))
+ (_\wrap [])))
(def: #export (get class register)
(-> (Type Class) Register (Bytecode Any))
@@ -55,4 +55,4 @@
($_ _.compose
/count.initial
(initial (n.- ///arity.minimum arity)))
- (_@wrap [])))
+ (_\wrap [])))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux
index 2fd419d18..a6de97cc3 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux
@@ -2,12 +2,12 @@
[lux #*
[target
[jvm
- ["." modifier (#+ Modifier) ("#@." monoid)]
+ ["." modifier (#+ Modifier) ("#\." monoid)]
["." method (#+ Method)]]]])
(def: #export modifier
(Modifier Method)
- ($_ modifier@compose
+ ($_ modifier\compose
method.public
method.strict
))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux
index 9e88895f5..581cce970 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux
@@ -10,10 +10,10 @@
["i" int]
["." i32]]
[collection
- ["." list ("#@." monoid functor)]]]
+ ["." list ("#\." monoid functor)]]]
[target
[jvm
- ["_" bytecode (#+ Label Bytecode) ("#@." monad)]
+ ["_" bytecode (#+ Label Bytecode) ("#\." monad)]
["." method (#+ Method)]
[constant
[pool (#+ Resource)]]
@@ -58,7 +58,7 @@
(|> amount
list.indices
(monad.map _.monad (|>> (n.+ offset) _.aload)))
- (_@wrap [])
+ (_\wrap [])
))
(def: (apply offset amount)
@@ -71,7 +71,7 @@
(if (n.> ///arity.maximum amount)
(apply (n.+ ///arity.maximum offset)
(n.- ///arity.maximum amount))
- (_@wrap []))
+ (_\wrap []))
)))
(def: this-offset 1)
@@ -96,12 +96,12 @@
@labelsT (|> _.new-label
(list.repeat (dec num-partials))
(monad.seq _.monad))
- #let [cases (|> (list@compose (#.Cons [@labelsH @labelsT])
+ #let [cases (|> (list\compose (#.Cons [@labelsH @labelsT])
(list @default))
list.enumeration
- (list@map (function (_ [stage @case])
+ (list\map (function (_ [stage @case])
(let [current-partials (|> (list.indices stage)
- (list@map (///partial.get class))
+ (list\map (///partial.get class))
(monad.seq _.monad))
already-partial? (n.> 0 stage)
exact-match? (i.= over-extent (.int stage))
@@ -113,7 +113,7 @@
////reference.this
(if already-partial?
(_.invokevirtual class //reset.name (//reset.type class))
- (_@wrap []))
+ (_\wrap []))
current-partials
(..inputs ..this-offset apply-arity)
(_.invokevirtual class //implementation.name (//implementation.type function-arity))
@@ -133,7 +133,7 @@
## (i.< over-extent (.int stage))
(let [current-environment (|> (list.indices (list.size environment))
- (list@map (///foreign.get class))
+ (list\map (///foreign.get class))
(monad.seq _.monad))
missing-partials (|> _.aconst-null
(list.repeat (|> num-partials (n.- apply-arity) (n.- stage)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux
index 8649123ff..fe8b824c9 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux
@@ -8,7 +8,7 @@
[number
["n" nat]]
[collection
- ["." list ("#@." monoid functor)]]]
+ ["." list ("#\." monoid functor)]]]
[target
[jvm
["_" bytecode (#+ Bytecode)]
@@ -48,7 +48,7 @@
(def: #export (type environment arity)
(-> (Environment Synthesis) Arity (Type category.Method))
- (type.method [(list@compose (///foreign.closure environment)
+ (type.method [(list\compose (///foreign.closure environment)
(if (arity.multiary? arity)
(list& ///arity.type (..partials arity))
(list)))
@@ -72,7 +72,7 @@
(-> Register Register)
(Bytecode Any))
(|> (list.indices amount)
- (list@map (function (_ register)
+ (list\map (function (_ register)
(put register
(_.aload (offset register)))))
(monad.seq _.monad)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux
index 1800064a2..7bf1b0bd8 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux
@@ -6,10 +6,9 @@
[number
["n" nat]]
[collection
- ["." list ("#@." monoid)]]]
+ ["." list]]]
[target
[jvm
- ["." modifier (#+ Modifier) ("#@." monoid)]
["." field (#+ Field)]
["." method (#+ Method)]
["_" bytecode (#+ Bytecode)]
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux
index 7373bf984..9793da801 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux
@@ -2,7 +2,7 @@
[lux (#- Type type)
[data
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#\." functor)]]]
[target
[jvm
["." method (#+ Method)]
@@ -35,7 +35,7 @@
(-> (Type Class) (Environment Synthesis) (List (Bytecode Any)))
(|>> list.size
list.indices
- (list@map (///foreign.get class))))
+ (list\map (///foreign.get class))))
(def: #export (method class environment arity)
(-> (Type Class) (Environment Synthesis) Arity (Resource Method))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux
index 8eaafb3a5..2640f28ce 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux
@@ -9,10 +9,10 @@
[number
["n" nat]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#\." functor)]]]
[target
[jvm
- ["_" bytecode (#+ Label Bytecode) ("#@." monad)]]]]
+ ["_" bytecode (#+ Label Bytecode) ("#\." monad)]]]]
["." // #_
["#." runtime (#+ Operation Phase Generator)]
["#." value]
@@ -34,7 +34,7 @@
false))
(def: no-op
- (_@wrap []))
+ (_\wrap []))
(def: #export (recur translate archive updatesS)
(Generator (List Synthesis))
@@ -42,7 +42,7 @@
[[@begin offset] generation.anchor
updatesG (|> updatesS
list.enumeration
- (list@map (function (_ [index updateS])
+ (list\map (function (_ [index updateS])
[(n.+ offset index) updateS]))
(monad.map ! (function (_ [register updateS])
(if (invariant? register updateS)
@@ -62,11 +62,11 @@
## will refer to the new value of X, instead of the old value, as
## should be the case.
(|> updatesG
- (list@map product.left)
+ (list\map product.left)
(monad.seq _.monad))
(|> updatesG
list.reverse
- (list@map product.right)
+ (list\map product.right)
(monad.seq _.monad))
(_.goto @begin)))))
@@ -78,7 +78,7 @@
iterationG (generation.with-anchor [@begin offset]
(translate archive iterationS))
#let [initializationG (|> (list.enumeration initsI+)
- (list@map (function (_ [index initG])
+ (list\map (function (_ [index initG])
($_ _.compose
initG
(_.astore (n.+ offset index)))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
index c5f10a9a6..6166f14c1 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
@@ -12,7 +12,7 @@
[target
[jvm
["_" bytecode (#+ Bytecode)]
- ["." modifier (#+ Modifier) ("#@." monoid)]
+ ["." modifier (#+ Modifier) ("#\." monoid)]
["." method (#+ Method)]
["." version]
["." class (#+ Class)]
@@ -34,7 +34,7 @@
(def: main::modifier
(Modifier Method)
- ($_ modifier@compose
+ ($_ modifier\compose
method.public
method.static
method.strict
@@ -42,7 +42,7 @@
(def: program::modifier
(Modifier Class)
- ($_ modifier@compose
+ ($_ modifier\compose
class.public
class.final
))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
index 679599858..57d45f6c3 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
@@ -12,7 +12,7 @@
["." i64]
["n" nat]]
[collection
- ["." list ("#@." functor)]
+ ["." list ("#\." functor)]
["." row]]
["." format #_
["#" binary]]
@@ -21,7 +21,7 @@
[target
["." jvm #_
["_" bytecode (#+ Label Bytecode)]
- ["." modifier (#+ Modifier) ("#@." monoid)]
+ ["." modifier (#+ Modifier) ("#\." monoid)]
["." field (#+ Field)]
["." method (#+ Method)]
["#/." version]
@@ -95,7 +95,7 @@
(def: modifier
(Modifier Method)
- ($_ modifier@compose
+ ($_ modifier\compose
method.public
method.static
method.strict
@@ -506,7 +506,7 @@
(Operation Any)
(let [class (..reflection ..class)
modifier (: (Modifier Class)
- ($_ modifier@compose
+ ($_ modifier\compose
class.public
class.final))
bytecode (<| (format.run class.writer)
@@ -538,7 +538,7 @@
(let [apply::method+ (|> (enum.range n.enum
(inc //function/arity.minimum)
//function/arity.maximum)
- (list@map (function (_ arity)
+ (list\map (function (_ arity)
(method.method method.public ..apply::name (..apply::type arity)
(list)
(#.Some
@@ -552,7 +552,7 @@
(_.aload arity)
(_.invokevirtual //function.class ..apply::name (..apply::type //function/arity.minimum))
_.areturn))))))
- (list& (method.method (modifier@compose method.public method.abstract)
+ (list& (method.method (modifier\compose method.public method.abstract)
..apply::name (..apply::type //function/arity.minimum)
(list)
#.None)))
@@ -568,12 +568,12 @@
(_.putfield //function.class //function/count.field //function/count.type)
_.return))))
modifier (: (Modifier Class)
- ($_ modifier@compose
+ ($_ modifier\compose
class.public
class.abstract))
class (..reflection //function.class)
partial-count (: (Resource Field)
- (field.field (modifier@compose field.public field.final)
+ (field.field (modifier\compose field.public field.final)
//function/count.field
//function/count.type
(row.row)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux
index 462c625c9..206af53b8 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux
@@ -3,7 +3,7 @@
[target
[jvm
["_" bytecode (#+ Bytecode)]
- ["." type (#+ Type) ("#@." equivalence)
+ ["." type (#+ Type) ("#\." equivalence)
[category (#+ Primitive)]
["." box]]]]])
@@ -13,7 +13,7 @@
[(def: (<name> type)
(-> (Type Primitive) Text)
(`` (cond (~~ (template [<type> <output>]
- [(type@= <type> type) <output>]
+ [(type\= <type> type) <output>]
[type.boolean <boolean>]
[type.byte <byte>]
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux
index c6cd63bf3..f28998159 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua.lux
@@ -6,7 +6,7 @@
[runtime (#+ Phase)]
["#." primitive]
["#." structure]
- ["#." reference ("#@." system)]
+ ["#." reference ("#\." system)]
["#." case]
["#." loop]
["#." function]
@@ -16,14 +16,14 @@
[analysis (#+)]
["." synthesis]
["//#" /// #_
- ["#." phase ("#@." monad)]]]]])
+ ["#." phase ("#\." monad)]]]]])
(def: #export (generate archive synthesis)
Phase
(case synthesis
(^template [<tag> <generator>]
[(^ (<tag> value))
- (//////phase@wrap (<generator> value))])
+ (//////phase\wrap (<generator> value))])
([synthesis.bit /primitive.bit]
[synthesis.i64 /primitive.i64]
[synthesis.f64 /primitive.f64]
@@ -36,7 +36,7 @@
(/structure.tuple generate archive members)
(#synthesis.Reference value)
- (/reference@reference archive value)
+ (/reference\reference archive value)
(^ (synthesis.branch/case case))
(/case.case generate archive case)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/case.lux
index 738912f52..5ef6bb4b3 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/case.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/case.lux
@@ -12,7 +12,7 @@
["n" nat]
["i" int]]
[collection
- ["." list ("#@." functor fold)]
+ ["." list ("#\." functor fold)]
["." set]]]
[target
["_" php (#+ Var Expression Statement)]]]
@@ -22,7 +22,7 @@
["#." primitive]
["#/" //
["#." reference]
- ["#/" // ("#@." monad)
+ ["#/" // ("#\." monad)
[synthesis
["." case]]
["#/" // #_
@@ -51,7 +51,7 @@
(Operation (Expression Any)))
(do ////.monad
[valueG (generate valueS)]
- (wrap (list@fold (function (_ side source)
+ (wrap (list\fold (function (_ side source)
(.let [method (.case side
(^template [<side> <accessor>]
[(<side> lefts)
@@ -143,14 +143,14 @@
(:: ////.monad map _.return (generate bodyS))
#/////synthesis.Pop
- (////@wrap ..pop!)
+ (////\wrap ..pop!)
(#/////synthesis.Bind register)
- (////@wrap (_.; (_.set (..register register) ..peek)))
+ (////\wrap (_.; (_.set (..register register) ..peek)))
(^template [<tag> <format>]
[(^ (<tag> value))
- (////@wrap (_.when (|> value <format> (_.= ..peek) _.not)
+ (////\wrap (_.when (|> value <format> (_.= ..peek) _.not)
fail!))])
([/////synthesis.path/bit //primitive.bit]
[/////synthesis.path/i64 //primitive.i64]
@@ -159,7 +159,7 @@
(^template [<complex> <simple> <choice>]
[(^ (<complex> idx))
- (////@wrap (<choice> false idx))
+ (////\wrap (<choice> false idx))
(^ (<simple> idx nextP))
(|> nextP
@@ -169,18 +169,18 @@
[/////synthesis.side/right /////synthesis.simple-right-side ..right-choice])
(^ (/////synthesis.member/left 0))
- (////@wrap (|> ..peek (_.nth (_.int +0)) ..push!))
+ (////\wrap (|> ..peek (_.nth (_.int +0)) ..push!))
(^template [<pm> <getter>]
[(^ (<pm> lefts))
- (////@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))])
+ (////\wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))])
([/////synthesis.member/left //runtime.tuple//left]
[/////synthesis.member/right //runtime.tuple//right])
(^ (/////synthesis.!bind-top register thenP))
(do ////.monad
[then! (pattern-matching' generate thenP)]
- (////@wrap ($_ _.then
+ (////\wrap ($_ _.then
(_.; (_.set (..register register) ..peek-and-pop))
then!)))
@@ -188,7 +188,7 @@
## (.let [[extra-pops nextP'] (case.count-pops nextP)]
## (do ////.monad
## [next! (pattern-matching' generate nextP')]
- ## (////@wrap ($_ _.then
+ ## (////\wrap ($_ _.then
## (..multi-pop! (n.+ 2 extra-pops))
## next!))))
@@ -226,7 +226,7 @@
#let [@dependencies+ (|> (case.storage pathP)
(get@ #case.dependencies)
set.to-list
- (list@map (function (_ variable)
+ (list\map (function (_ variable)
[#0 (.case variable
(#reference.Local register)
(..register register)
@@ -245,5 +245,5 @@
(_.; (_.set @caseG @caseL)))]
_ (///.execute! directive)
_ (///.save! @case directive)]
- (wrap (_.apply/* (list& initG (list@map product.right @dependencies+))
+ (wrap (_.apply/* (list& initG (list\map product.right @dependencies+))
@caseG))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/function.lux
index 58fb0a4b9..e021f5234 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/function.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/function.lux
@@ -8,7 +8,7 @@
["." product]
["." text]
[collection
- ["." list ("#@." functor fold)]]]
+ ["." list ("#\." functor fold)]]]
[target
["_" php (#+ Argument Expression Statement)]]]
["." // #_
@@ -55,7 +55,7 @@
@selfG (_.global function-name)
@selfL (_.var function-name)
initialize-self! (_.; (_.set (//case.register 0) @selfL))
- initialize! (list@fold (.function (_ post pre!)
+ initialize! (list\fold (.function (_ post pre!)
($_ _.then
pre!
(_.; (_.set (..input post) (_.nth (|> post .int _.int) @curried)))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
index 000789484..f94470be8 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
@@ -9,7 +9,7 @@
[text
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#\." functor)]]]
[target
["_" php (#+ Expression)]]]
["." // #_
@@ -35,7 +35,7 @@
(_.closure (list (_.reference @loopL))
(|> initsS+
list.enumeration
- (list@map (|>> product.left (n.+ start) //case.register [#0])))
+ (list\map (|>> product.left (n.+ start) //case.register [#0])))
(_.return bodyO)))
(_.; (_.set @loopG @loopL)))]
_ (///.execute! directive)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux
index c7a8a4eeb..88a8897f2 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux
@@ -12,7 +12,7 @@
["." text
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#\." functor)]]]
["." macro
["." code]
[syntax (#+ syntax:)]]
@@ -91,7 +91,7 @@
(syntax: #export (with-vars {vars (s.tuple (p.some s.local-identifier))}
body)
(wrap (list (` (let [(~+ (|> vars
- (list@map (function (_ var)
+ (list\map (function (_ var)
(list (code.local-identifier var)
(` (_.var (~ (code.text (/////name.normalize var))))))))
list.concat))]
@@ -116,8 +116,8 @@
(#.Right [name inputs])
(let [code-nameC (code.local-identifier (format "@" name))
runtime-nameC (` (runtime-name (~ (code.text name))))
- inputsC (list@map code.local-identifier inputs)
- inputs-typesC (list@map (function.constant (` (_.Expression Any)))
+ inputsC (list\map code.local-identifier inputs)
+ inputs-typesC (list\map (function.constant (` (_.Expression Any)))
inputs)]
(wrap (list (` (def: #export ((~ (code.local-identifier name)) (~+ inputsC))
(-> (~+ inputs-typesC) (_.Computation Any))
@@ -133,7 +133,7 @@
(_.set (~ g!L))
(_.closure (list (_.reference (~ g!L)))
(list (~+ (|> inputsC
- (list@map (function (_ inputC)
+ (list\map (function (_ inputC)
(` [#0 (~ inputC)]))))))
(~ code)))
(_.; (_.set (~ g!G) (~ g!L)))
@@ -161,7 +161,8 @@
Statement
($_ _.then
@lux//try
- @lux//program-args))
+ @lux//program-args
+ ))
(runtime: (io//throw! message)
($_ _.then
@@ -171,7 +172,8 @@
(def: runtime//io
Statement
($_ _.then
- @io//throw!))
+ @io//throw!
+ ))
(def: tuple-size
_.count/1)
@@ -245,7 +247,8 @@
($_ _.then
@tuple//left
@tuple//right
- @sum//get))
+ @sum//get
+ ))
(runtime: (i64//logic-right-shift param subject)
(let [mask (|> (_.int +1)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/case.lux
index e25155d4a..4d5fc7f06 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/case.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/case.lux
@@ -11,7 +11,7 @@
["n" nat]
["i" int]]
[collection
- ["." list ("#@." functor fold)]
+ ["." list ("#\." functor fold)]
["." set]]]
[target
["_" python (#+ Expression SVar Statement)]]]
@@ -28,7 +28,7 @@
["#." generation]
["//#" /// #_
["#." reference (#+ Register)]
- ["#." phase ("#@." monad)]
+ ["#." phase ("#\." monad)]
[meta
[archive (#+ Archive)]]]]]]])
@@ -52,7 +52,7 @@
(Generator [Synthesis (List (Either Nat Nat))])
(do ///////phase.monad
[valueO (generate archive valueS)]
- (wrap (list@fold (function (_ side source)
+ (wrap (list\fold (function (_ side source)
(.let [method (.case side
(^template [<side> <accessor>]
[(<side> lefts)
@@ -138,17 +138,17 @@
(-> Phase Archive Path (Operation (Statement Any)))
(.case pathP
(^ (/////synthesis.path/then bodyS))
- (///////phase@map _.return (generate archive bodyS))
+ (///////phase\map _.return (generate archive bodyS))
#/////synthesis.Pop
- (///////phase@wrap ..pop!)
+ (///////phase\wrap ..pop!)
(#/////synthesis.Bind register)
- (///////phase@wrap (_.set (list (..register register)) ..peek))
+ (///////phase\wrap (_.set (list (..register register)) ..peek))
(^template [<tag> <format>]
[(^ (<tag> value))
- (///////phase@wrap (_.when (|> value <format> (_.= ..peek) _.not)
+ (///////phase\wrap (_.when (|> value <format> (_.= ..peek) _.not)
fail-pm!))])
([/////synthesis.path/bit //primitive.bit]
[/////synthesis.path/i64 //primitive.i64]
@@ -157,28 +157,28 @@
(^template [<complex> <simple> <choice>]
[(^ (<complex> idx))
- (///////phase@wrap (<choice> false idx))
+ (///////phase\wrap (<choice> false idx))
(^ (<simple> idx nextP))
(|> nextP
(pattern-matching' generate archive)
- (///////phase@map (_.then (<choice> true idx))))])
+ (///////phase\map (_.then (<choice> true idx))))])
([/////synthesis.side/left /////synthesis.simple-left-side ..left-choice]
[/////synthesis.side/right /////synthesis.simple-right-side ..right-choice])
(^ (/////synthesis.member/left 0))
- (///////phase@wrap (|> ..peek (_.nth (_.int +0)) ..push!))
+ (///////phase\wrap (|> ..peek (_.nth (_.int +0)) ..push!))
(^template [<pm> <getter>]
[(^ (<pm> lefts))
- (///////phase@wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))])
+ (///////phase\wrap (|> ..peek (<getter> (_.int (.int lefts))) ..push!))])
([/////synthesis.member/left //runtime.tuple//left]
[/////synthesis.member/right //runtime.tuple//right])
(^ (/////synthesis.!bind-top register thenP))
(do ///////phase.monad
[then! (pattern-matching' generate archive thenP)]
- (///////phase@wrap ($_ _.then
+ (///////phase\wrap ($_ _.then
(_.set (list (..register register)) ..peek-and-pop)
then!)))
@@ -186,7 +186,7 @@
(.let [[extra-pops nextP'] (case.count-pops nextP)]
(do ///////phase.monad
[next! (pattern-matching' generate archive nextP')]
- (///////phase@wrap ($_ _.then
+ (///////phase\wrap ($_ _.then
(..multi-pop! (n.+ 2 extra-pops))
next!))))
@@ -210,7 +210,7 @@
(def: (gensym prefix)
(-> Text (Operation SVar))
- (///////phase@map (|>> %.nat (format prefix) _.var) /////generation.next))
+ (///////phase\map (|>> %.nat (format prefix) _.var) /////generation.next))
(def: #export (case generate archive [valueS pathP])
(Generator [Synthesis Path])
@@ -222,7 +222,7 @@
#let [@dependencies+ (|> (case.storage pathP)
(get@ #case.dependencies)
set.to-list
- (list@map (function (_ variable)
+ (list\map (function (_ variable)
(.case variable
(#///////reference.Local register)
(..register register)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/function.lux
index 043941530..28e8867a0 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/function.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/function.lux
@@ -7,7 +7,7 @@
[data
["." product]
[collection
- ["." list ("#@." functor fold)]]]
+ ["." list ("#\." functor fold)]]]
[target
["_" python (#+ Expression Statement)]]]
["." // #_
@@ -49,7 +49,7 @@
[@closure (:: ! map _.var (/////generation.gensym "closure"))
#let [directive (_.def @closure
(|> (list.enumeration inits)
- (list@map (|>> product.left ..capture)))
+ (list\map (|>> product.left ..capture)))
($_ _.then
function-definition
(_.return (_.var function-name))))]
@@ -79,7 +79,7 @@
apply-poly (.function (_ args func)
(_.apply-poly (list) args func))
initialize-self! (_.set (list (//case.register 0)) @self)
- initialize! (list@fold (.function (_ post pre!)
+ initialize! (list\fold (.function (_ post pre!)
($_ _.then
pre!
(_.set (list (..input post)) (_.nth (|> post .int _.int) @curried))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
index 49fd86575..e8f2bd5f7 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
@@ -9,7 +9,7 @@
[text
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#\." functor)]]]
[target
["_" python (#+ Expression SVar)]]]
["." // #_
@@ -34,7 +34,7 @@
(generate archive bodyS))
#let [directive (_.def @loop (|> initsS+
list.enumeration
- (list@map (|>> product.left (n.+ start) //case.register)))
+ (list\map (|>> product.left (n.+ start) //case.register)))
(_.return bodyO))]
_ (/////generation.execute! directive)
_ (/////generation.save! (_.code @loop) directive)]
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
index aa49950f0..7469aaa7d 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
@@ -12,7 +12,7 @@
["." text
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]]]
+ ["." list ("#\." functor)]]]
["." macro
["." code]
[syntax (#+ syntax:)]]
@@ -90,7 +90,7 @@
(syntax: #export (with-vars {vars (s.tuple (p.some s.local-identifier))}
body)
(wrap (list (` (let [(~+ (|> vars
- (list@map (function (_ var)
+ (list\map (function (_ var)
(list (code.local-identifier var)
(` (_.var (~ (code.text (///reference.sanitize var))))))))
list.concat))]
@@ -118,8 +118,8 @@
(let [nameC (code.local-identifier name)
code-nameC (code.local-identifier (format "@" name))
runtime-nameC (` (runtime-name (~ (code.text name))))
- inputsC (list@map code.local-identifier inputs)
- inputs-typesC (list@map (function.constant (` (_.Expression Any)))
+ inputsC (list\map code.local-identifier inputs)
+ inputs-typesC (list\map (function.constant (` (_.Expression Any)))
inputs)]
(wrap (list (` (def: #export ((~ nameC) (~+ inputsC))
(-> (~+ inputs-typesC) (Computation Any))
@@ -153,7 +153,8 @@
(Statement Any)
($_ _.then
@lux//try
- @lux//program-args))
+ @lux//program-args
+ ))
(runtime: (io//log! message)
($_ _.then
@@ -185,7 +186,8 @@
@io//log!
@io//throw!
@io//exit!
- @io//current-time!))
+ @io//current-time!
+ ))
(def: last-index
(|>> _.len/1 (_.- (_.int +1))))
@@ -247,7 +249,8 @@
($_ _.then
@tuple//left
@tuple//right
- @sum//get))
+ @sum//get
+ ))
(def: full-64-bits
Literal
@@ -279,7 +282,8 @@
(Statement Any)
($_ _.then
@i64//64
- @i64//logic-right-shift))
+ @i64//logic-right-shift
+ ))
(runtime: (frac//decode input)
(with-vars [ex]
@@ -291,7 +295,8 @@
(def: runtime//frac
(Statement Any)
($_ _.then
- @frac//decode))
+ @frac//decode
+ ))
(runtime: (text//index subject param start)
(with-vars [idx]
@@ -321,7 +326,8 @@
($_ _.then
@text//index
@text//clip
- @text//char))
+ @text//char
+ ))
(def: runtime
(Statement Any)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/structure.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/structure.lux
index b564b1d3c..c5edce4a7 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/structure.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/python/structure.lux
@@ -11,13 +11,13 @@
[analysis (#+ Variant Tuple)]
["#." synthesis (#+ Synthesis)]
["//#" /// #_
- ["#." phase ("#@." monad)]]]])
+ ["#." phase ("#\." monad)]]]])
(def: #export (tuple generate archive elemsS+)
(Generator (Tuple Synthesis))
(case elemsS+
#.Nil
- (///////phase@wrap (//primitive.text /////synthesis.unit))
+ (///////phase\wrap (//primitive.text /////synthesis.unit))
(#.Cons singletonS #.Nil)
(generate archive singletonS)
@@ -25,12 +25,12 @@
_
(|> elemsS+
(monad.map ///////phase.monad (generate archive))
- (///////phase@map _.list))))
+ (///////phase\map _.list))))
(def: #export (variant generate archive [lefts right? valueS])
(Generator (Variant Synthesis))
(let [tag (if right?
(inc lefts)
lefts)]
- (///////phase@map (//runtime.variant tag right?)
+ (///////phase\map (//runtime.variant tag right?)
(generate archive valueS))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/reference.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/reference.lux
index a28e1918f..b587d2963 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/reference.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/reference.lux
@@ -9,7 +9,7 @@
["//#" /// #_
["." reference (#+ Reference)
["." variable (#+ Register Variable)]]
- ["." phase ("#@." monad)]
+ ["." phase ("#\." monad)]
[meta
[archive (#+ Archive)]]]])
@@ -30,7 +30,7 @@
(All [anchor expression directive]
(-> (System expression) Archive Name
(////generation.Operation anchor expression directive expression)))
- (phase@map (|>> ..artifact (:: system constant))
+ (phase\map (|>> ..artifact (:: system constant))
(////generation.remember archive name)))
(template [<sigil> <name>]
@@ -62,4 +62,4 @@
(..constant system archive value)
(#reference.Variable value)
- (phase@wrap (..variable system value))))
+ (phase\wrap (..variable system value))))