diff options
author | Eduardo Julian | 2020-12-02 06:42:20 -0400 |
---|---|---|
committer | Eduardo Julian | 2020-12-02 06:42:20 -0400 |
commit | 34e310622bdeb1d0588c0664c0e78cbaa84f837c (patch) | |
tree | eb7c04185b57c781f45d0ccdb955bc9afc2aa8dc /stdlib/source/lux/tool | |
parent | 982a19e0c5d57b53f9726b780fec4c18f0787b4f (diff) |
Re-named "::" and ":::" macros to "\" and "\\", to be consistent with the convention that only macros that deal with types may start with a colon.
Diffstat (limited to '')
60 files changed, 355 insertions, 340 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux index b2225c718..7a99aa09b 100644 --- a/stdlib/source/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/lux/tool/compiler/default/platform.lux @@ -100,8 +100,8 @@ row.to-list (monad.map ..monad write-artifact!) (: (Action (List Any)))) - document (:: promise.monad wrap - (document.check $.key document))] + document (\ promise.monad wrap + (document.check $.key document))] (ioW.cache system static module-id (_.run ..writer [descriptor document]))))) @@ -180,7 +180,7 @@ _ (extension.with extender (:assume directives))] (wrap []))}) (///phase.run' state) - (:: try.monad map product.left))) + (\ try.monad map product.left))) (def: #export (initialize static module expander host-analysis platform generation-bundle host-directive-bundle program anchorT,expressionT,directiveT extender import compilation-sources) diff --git a/stdlib/source/lux/tool/compiler/language/lux.lux b/stdlib/source/lux/tool/compiler/language/lux.lux index d300ec243..0d77cbe6c 100644 --- a/stdlib/source/lux/tool/compiler/language/lux.lux +++ b/stdlib/source/lux/tool/compiler/language/lux.lux @@ -97,7 +97,7 @@ ## #module-annotations (<b>.maybe <b>.code) ## #module-state - (:: <>.monad wrap #.Cached)))) + (\ <>.monad wrap #.Cached)))) (def: #export key (Key .Module) diff --git a/stdlib/source/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/lux/tool/compiler/language/lux/analysis.lux index 34d8005e1..e6fea4ef1 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/analysis.lux @@ -138,7 +138,7 @@ (/\= reference-value sample-value)) [(#Tuple reference) (#Tuple sample)] - (:: (list.equivalence /\=) = reference sample) + (\ (list.equivalence /\=) = reference sample) _ false))) @@ -147,19 +147,19 @@ (All [a] (-> (Hash a) (Hash (Composite a)))) (def: &equivalence - (..composite-equivalence (:: super &equivalence))) + (..composite-equivalence (\ super &equivalence))) (def: (hash value) (case value (#Variant [lefts right? value]) ($_ n.* 2 - (:: n.hash hash lefts) - (:: bit.hash hash right?) - (:: super hash value)) + (\ n.hash hash lefts) + (\ bit.hash hash right?) + (\ super hash value)) (#Tuple members) ($_ n.* 3 - (:: (list.hash super) hash members)) + (\ (list.hash super) hash members)) ))) (structure: pattern-equivalence @@ -168,10 +168,10 @@ (def: (= reference sample) (case [reference sample] [(#Simple reference) (#Simple sample)] - (:: primitive-equivalence = reference sample) + (\ primitive-equivalence = reference sample) [(#Complex reference) (#Complex sample)] - (:: (composite-equivalence =) = reference sample) + (\ (composite-equivalence =) = reference sample) [(#Bind reference) (#Bind sample)] (n.= reference sample) @@ -183,8 +183,8 @@ (-> (Equivalence Analysis) (Equivalence Branch)) (def: (= [reference-pattern reference-body] [sample-pattern sample-body]) - (and (:: pattern-equivalence = reference-pattern sample-pattern) - (:: equivalence = reference-body sample-body)))) + (and (\ pattern-equivalence = reference-pattern sample-pattern) + (\ equivalence = reference-body sample-body)))) (structure: #export equivalence (Equivalence Analysis) @@ -192,23 +192,23 @@ (def: (= reference sample) (case [reference sample] [(#Primitive reference) (#Primitive sample)] - (:: primitive-equivalence = reference sample) + (\ primitive-equivalence = reference sample) [(#Structure reference) (#Structure sample)] - (:: (composite-equivalence =) = reference sample) + (\ (composite-equivalence =) = reference sample) [(#Reference reference) (#Reference sample)] - (:: reference.equivalence = reference sample) + (\ reference.equivalence = reference sample) [(#Case [reference-analysis reference-match]) (#Case [sample-analysis sample-match])] (and (= reference-analysis sample-analysis) - (:: (list.equivalence (branch-equivalence =)) = (#.Cons reference-match) (#.Cons sample-match))) + (\ (list.equivalence (branch-equivalence =)) = (#.Cons reference-match) (#.Cons sample-match))) [(#Function [reference-environment reference-analysis]) (#Function [sample-environment sample-analysis])] (and (= reference-analysis sample-analysis) - (:: (list.equivalence =) = reference-environment sample-environment)) + (\ (list.equivalence =) = reference-environment sample-environment)) [(#Apply [reference-input reference-abstraction]) (#Apply [sample-input sample-abstraction])] @@ -216,7 +216,7 @@ (= reference-abstraction sample-abstraction)) [(#Extension reference) (#Extension sample)] - (:: (extension.equivalence =) = reference sample) + (\ (extension.equivalence =) = reference sample) _ false))) @@ -474,7 +474,7 @@ (def: #export (assert exception parameters condition) (All [e] (-> (Exception e) e Bit (Operation Any))) (if condition - (:: phase.monad wrap []) + (\ phase.monad wrap []) (..throw exception parameters))) (def: #export (fail' error) diff --git a/stdlib/source/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/lux/tool/compiler/language/lux/generation.lux index 0b4ab70b2..da24f66f3 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/generation.lux @@ -171,7 +171,7 @@ (def: #export (gensym prefix) (All [anchor expression directive] (-> Text (Operation anchor expression directive Text))) - (:: phase.monad map (|>> %.nat (format prefix)) ..next)) + (\ phase.monad map (|>> %.nat (format prefix)) ..next)) (def: #export (enter-module module) (All [anchor expression directive] @@ -187,7 +187,7 @@ (All [anchor expression directive] (-> Context expression (Operation anchor expression directive Any))) (function (_ (^@ state+ [bundle state])) - (case (:: (get@ #host state) evaluate! label code) + (case (\ (get@ #host state) evaluate! label code) (#try.Success output) (#try.Success [state+ output]) @@ -198,7 +198,7 @@ (All [anchor expression directive] (-> directive (Operation anchor expression directive Any))) (function (_ (^@ state+ [bundle state])) - (case (:: (get@ #host state) execute! code) + (case (\ (get@ #host state) execute! code) (#try.Success output) (#try.Success [state+ output]) @@ -209,7 +209,7 @@ (All [anchor expression directive] (-> Context expression (Operation anchor expression directive [Text Any directive]))) (function (_ (^@ stateE [bundle state])) - (case (:: (get@ #host state) define! context code) + (case (\ (get@ #host state) define! context code) (#try.Success output) (#try.Success [stateE output]) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux index b550f9c5a..33cf36f32 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -127,10 +127,10 @@ type.flatten-tuple (list\map (re-quantify envs)) type.tuple - (:: ///.monad wrap)) + (\ ///.monad wrap)) _ - (:: ///.monad wrap (re-quantify envs caseT))))) + (\ ///.monad wrap (re-quantify envs caseT))))) (def: (analyse-primitive type inputT location output next) (All [a] (-> Type Type Location Pattern (Operation a) (Operation [Pattern a]))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux index adf935a89..136decfa8 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux @@ -188,7 +188,7 @@ [(#Variant allR casesR) (#Variant allS casesS)] (and (n.= (cases allR) (cases allS)) - (:: (dictionary.equivalence =) = casesR casesS)) + (\ (dictionary.equivalence =) = casesR casesS)) [(#Seq leftR rightR) (#Seq leftS rightS)] (and (= leftR leftS) @@ -234,7 +234,7 @@ (not (n.= addition-cases so-far-cases))) (ex.throw variants-do-not-match [addition-cases so-far-cases]) - (:: (dictionary.equivalence ..equivalence) = casesSF casesA) + (\ (dictionary.equivalence ..equivalence) = casesSF casesA) (ex.throw redundant-pattern [so-far addition]) ## else diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux index 8c5b74cff..b4c9ec016 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -88,10 +88,10 @@ )) (#.Function inputT outputT) - (<| (:: ! map (.function (_ [scope bodyA]) - (#/.Function (list\map (|>> /.variable) - (//scope.environment scope)) - bodyA))) + (<| (\ ! map (.function (_ [scope bodyA]) + (#/.Function (list\map (|>> /.variable) + (//scope.environment scope)) + bodyA))) /.with-scope ## Functions have access not only to their argument, but ## also to themselves, through a local variable. diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/structure.lux index 848d0e96b..a306b178b 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -173,11 +173,11 @@ (case [membersT+ membersC+] [(#.Cons memberT #.Nil) _] (//type.with-type memberT - (:: ! map (|>> list) (analyse archive (code.tuple membersC+)))) + (\ ! map (|>> list) (analyse archive (code.tuple membersC+)))) [_ (#.Cons memberC #.Nil)] (//type.with-type (type.tuple membersT+) - (:: ! map (|>> list) (analyse archive memberC))) + (\ ! map (|>> list) (analyse archive memberC))) [(#.Cons memberT membersT+') (#.Cons memberC membersC+')] (do ! @@ -301,7 +301,7 @@ (case record ## empty-record = empty-tuple = unit = [] #.Nil - (:: ///.monad wrap [(list) Any]) + (\ ///.monad wrap [(list) Any]) (#.Cons [head-k head-v] _) (do {! ///.monad} diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/directive.lux index 2bde38a7d..7bcb4a39b 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/directive.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/directive.lux @@ -66,12 +66,12 @@ (case expansion (^ (list& <lux_def_module> referrals)) (|> (recur archive <lux_def_module>) - (:: ! map (update@ #/.referrals (list\compose referrals)))) + (\ ! map (update@ #/.referrals (list\compose referrals)))) _ (|> expansion (monad.map ! (recur archive)) - (:: ! map (list\fold /.merge-requirements /.no-requirements))))) + (\ ! map (list\fold /.merge-requirements /.no-requirements))))) _ (//.throw ..not-a-directive code)))))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index 0fdaa8c96..c6899c4e8 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -472,8 +472,8 @@ (text.starts-with? descriptor.array-prefix name) (let [[_ unprefixed] (maybe.assume (text.split-with descriptor.array-prefix name))] - (:: phase.monad map jvm.array - (check-jvm (#.Primitive unprefixed (list))))) + (\ phase.monad map jvm.array + (check-jvm (#.Primitive unprefixed (list))))) ## else (phase\wrap (jvm.class name (list))))) @@ -512,7 +512,7 @@ (def: (check-object objectT) (-> .Type (Operation External)) (do {! phase.monad} - [name (:: ! map ..reflection (check-jvm objectT))] + [name (\ ! map ..reflection (check-jvm objectT))] (if (dictionary.contains? name ..boxes) (/////analysis.throw ..primitives-are-not-objects [name]) (phase\wrap name)))) @@ -756,47 +756,53 @@ (/////analysis.throw cannot-possibly-be-an-instance (format sub-class " !<= " object-class)))))])) (import: java/lang/Object - (equals [java/lang/Object] boolean)) + ["#::." + (equals [java/lang/Object] boolean)]) (import: java/lang/reflect/Type) (import: (java/lang/reflect/TypeVariable d) - (getName [] java/lang/String) - (getBounds [] [java/lang/reflect/Type])) + ["#::." + (getName [] java/lang/String) + (getBounds [] [java/lang/reflect/Type])]) (import: java/lang/reflect/Modifier - (#static isStatic [int] boolean) - (#static isFinal [int] boolean) - (#static isInterface [int] boolean) - (#static isAbstract [int] boolean)) + ["#::." + (#static isStatic [int] boolean) + (#static isFinal [int] boolean) + (#static isInterface [int] boolean) + (#static isAbstract [int] boolean)]) (import: java/lang/reflect/Method - (getName [] java/lang/String) - (getModifiers [] int) - (getDeclaringClass [] (java/lang/Class java/lang/Object)) - (getTypeParameters [] [(java/lang/reflect/TypeVariable java/lang/reflect/Method)]) - (getGenericParameterTypes [] [java/lang/reflect/Type]) - (getGenericReturnType [] java/lang/reflect/Type) - (getGenericExceptionTypes [] [java/lang/reflect/Type])) + ["#::." + (getName [] java/lang/String) + (getModifiers [] int) + (getDeclaringClass [] (java/lang/Class java/lang/Object)) + (getTypeParameters [] [(java/lang/reflect/TypeVariable java/lang/reflect/Method)]) + (getGenericParameterTypes [] [java/lang/reflect/Type]) + (getGenericReturnType [] java/lang/reflect/Type) + (getGenericExceptionTypes [] [java/lang/reflect/Type])]) (import: (java/lang/reflect/Constructor c) - (getModifiers [] int) - (getDeclaringClass [] (java/lang/Class c)) - (getTypeParameters [] [(java/lang/reflect/TypeVariable (java/lang/reflect/Constructor c))]) - (getGenericParameterTypes [] [java/lang/reflect/Type]) - (getGenericExceptionTypes [] [java/lang/reflect/Type])) + ["#::." + (getModifiers [] int) + (getDeclaringClass [] (java/lang/Class c)) + (getTypeParameters [] [(java/lang/reflect/TypeVariable (java/lang/reflect/Constructor c))]) + (getGenericParameterTypes [] [java/lang/reflect/Type]) + (getGenericExceptionTypes [] [java/lang/reflect/Type])]) (import: (java/lang/Class c) - (#static forName [java/lang/String] #try (java/lang/Class java/lang/Object)) - (getName [] java/lang/String) - (getModifiers [] int) - (isAssignableFrom [(java/lang/Class java/lang/Object)] boolean) - (getTypeParameters [] [(java/lang/reflect/TypeVariable (java/lang/Class c))]) - (getGenericInterfaces [] [java/lang/reflect/Type]) - (getGenericSuperclass [] #? java/lang/reflect/Type) - (getDeclaredField [java/lang/String] #try java/lang/reflect/Field) - (getConstructors [] [(java/lang/reflect/Constructor java/lang/Object)]) - (getDeclaredMethods [] [java/lang/reflect/Method])) + ["#::." + (#static forName [java/lang/String] #try (java/lang/Class java/lang/Object)) + (getName [] java/lang/String) + (getModifiers [] int) + (isAssignableFrom [(java/lang/Class java/lang/Object)] boolean) + (getTypeParameters [] [(java/lang/reflect/TypeVariable (java/lang/Class c))]) + (getGenericInterfaces [] [java/lang/reflect/Type]) + (getGenericSuperclass [] #? java/lang/reflect/Type) + (getDeclaredField [java/lang/String] #try java/lang/reflect/Field) + (getConstructors [] [(java/lang/reflect/Constructor java/lang/Object)]) + (getDeclaredMethods [] [java/lang/reflect/Method])]) (template [<name> <category> <parser>] [(def: (<name> mapping typeJ) @@ -843,7 +849,7 @@ (monad.map phase.monad (function (_ superT) (do {! phase.monad} - [super-name (:: ! map ..reflection (check-jvm superT)) + [super-name (\ ! map ..reflection (check-jvm superT)) super-class (phase.lift (reflection!.load super-name))] (wrap [[super-name superT] (java/lang/Class::isAssignableFrom super-class to-class)]))) @@ -859,10 +865,10 @@ (^ (list fromC)) (do {! phase.monad} [toT (///.lift meta.expected-type) - to-name (:: ! map ..reflection (check-jvm toT)) + to-name (\ ! map ..reflection (check-jvm toT)) [fromT fromA] (typeA.with-inference (analyse archive fromC)) - from-name (:: ! map ..reflection (check-jvm fromT)) + from-name (\ ! map ..reflection (check-jvm fromT)) can-cast? (: (Operation Bit) (`` (cond (~~ (template [<primitive> <object>] [(let [=primitive (reflection.reflection <primitive>)] @@ -1234,10 +1240,10 @@ aliasing (dictionary.merge (..aliasing expected-class-tvars actual-class-tvars) (..aliasing expected-method-tvars actual-method-tvars))] passes? (check-method aliasing class method-name method-style inputsJT method)] - (:: ! map (if passes? - (|>> #Pass) - (|>> #Hint)) - (method-signature method-style method)))))))] + (\ ! map (if passes? + (|>> #Pass) + (|>> #Hint)) + (method-signature method-style method)))))))] (case (list.all pass! candidates) (#.Cons method #.Nil) (wrap method) @@ -1264,9 +1270,9 @@ aliasing (dictionary.merge (..aliasing expected-class-tvars actual-class-tvars) (..aliasing expected-method-tvars actual-method-tvars))] passes? (check-constructor aliasing class inputsJT constructor)] - (:: ! map - (if passes? (|>> #Pass) (|>> #Hint)) - (constructor-signature constructor))))))] + (\ ! map + (if passes? (|>> #Pass) (|>> #Hint)) + (constructor-signature constructor))))))] (case (list.all pass! candidates) (#.Cons constructor #.Nil) (wrap constructor) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux index 29fb70e63..70a32ea7e 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux @@ -164,8 +164,8 @@ (^ (list typeC valueC)) (do {! ////.monad} [count (///.lift meta.count) - actualT (:: ! map (|>> (:coerce Type)) - (eval archive count Type typeC)) + actualT (\ ! map (|>> (:coerce Type)) + (eval archive count Type typeC)) _ (typeA.infer actualT)] (typeA.with-type actualT (analyse archive valueC))) @@ -180,8 +180,8 @@ (^ (list typeC valueC)) (do {! ////.monad} [count (///.lift meta.count) - actualT (:: ! map (|>> (:coerce Type)) - (eval archive count Type typeC)) + actualT (\ ! map (|>> (:coerce Type)) + (eval archive count Type typeC)) _ (typeA.infer actualT) [valueT valueA] (typeA.with-inference (analyse archive valueC))] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux index f7cc747ff..0aeea4cd2 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux @@ -135,7 +135,7 @@ [abstractionG (phase archive abstractionS) #let [variable (: (-> Text (Operation Var)) (|>> generation.gensym - (:: ! map _.var)))] + (\ ! map _.var)))] g!inputs (monad.map ! (function (_ _) (variable "input")) (list.repeat (.nat arity) [])) g!abstraction (variable "abstraction")] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index ee9c3b1a2..c1418b2ce 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -743,7 +743,7 @@ ..unitG (#.Left outputT) - (:: _.monad wrap []))) + (\ _.monad wrap []))) (def: invoke::static Handler @@ -981,20 +981,20 @@ _.areturn) (#.Right returnT) - (cond (or (:: type.equivalence = type.boolean returnT) - (:: type.equivalence = type.byte returnT) - (:: type.equivalence = type.short returnT) - (:: type.equivalence = type.int returnT) - (:: type.equivalence = type.char returnT)) + (cond (or (\ type.equivalence = type.boolean returnT) + (\ type.equivalence = type.byte returnT) + (\ type.equivalence = type.short returnT) + (\ type.equivalence = type.int returnT) + (\ type.equivalence = type.char returnT)) _.ireturn - (:: type.equivalence = type.long returnT) + (\ type.equivalence = type.long returnT) _.lreturn - (:: type.equivalence = type.float returnT) + (\ type.equivalence = type.float returnT) _.freturn - ## (:: type.equivalence = type.double returnT) + ## (\ type.equivalence = type.double returnT) _.dreturn)))) (def: class::anonymous @@ -1068,7 +1068,7 @@ bodyG (returnG returnT))))))) normalized-methods) - bytecode (<| (:: ! map (format.run class.writer)) + bytecode (<| (\ ! map (format.run class.writer)) //////.lift (class.class version.v6_0 ($_ modifier\compose class.public class.final) (name.internal anonymous-class-name) 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 975301cef..43d449402 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 @@ -21,7 +21,7 @@ (case synthesis (^template [<tag> <generator>] [(^ (<tag> value)) - (:: ///.monad wrap (<generator> value))]) + (\ ///.monad wrap (<generator> value))]) ([synthesis.bit primitive.bit] [synthesis.i64 primitive.i64] [synthesis.f64 primitive.f64] 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 6c6858ea9..6953a9987 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 @@ -134,7 +134,7 @@ (-> Phase Path (Operation (Expression Any))) (.case pathP (^ (/////synthesis.path/then bodyS)) - (:: ////.monad map (_.return-from ..@done) (generate bodyS)) + (\ ////.monad map (_.return-from ..@done) (generate bodyS)) #/////synthesis.Pop (////\wrap ..pop!) @@ -159,7 +159,7 @@ (^ (<simple> idx nextP)) (|> nextP (pattern-matching' generate) - (:: ////.monad map (_.progn (<choice> true idx))))]) + (\ ////.monad map (_.progn (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple-left-side ..left-choice] [/////synthesis.side/right /////synthesis.simple-right-side ..right-choice]) 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 8853de638..d68f22ef0 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 @@ -37,11 +37,11 @@ (-> Text (List (Expression Any)) (Expression Any) (Operation (Expression Any))) (case inits #.Nil - (:: ////.monad wrap function-definition) + (\ ////.monad wrap function-definition) _ (do {! ////.monad} - [@closure (:: ! map _.var (///.gensym "closure"))] + [@closure (\ ! map _.var (///.gensym "closure"))] (wrap (_.labels (list [@closure [(|> (list.enumeration inits) (list\map (|>> product.left ..capture)) _.args) @@ -60,7 +60,7 @@ (///.with-anchor (_.var function-name) (generate bodyS)))) closureG+ (: (Operation (List (Expression Any))) - (monad.map ! (:: //reference.system variable) environment)) + (monad.map ! (\ //reference.system variable) environment)) #let [@curried (_.var "curried") @missing (_.var "missing") arityG (|> arity .int _.int) @@ -87,7 +87,7 @@ extra-inputs]))]) ## (|> @num-args (_.< arityG)) (_.lambda (_.args& (list) @missing) - (_.apply/2 [(_.function/1 @self) - (_.append/2 [@curried @missing])]))))]]) + (_.apply/2 [(_.function/1 @self) + (_.append/2 [@curried @missing])]))))]]) (_.function/1 @self))) )) 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 e3c6d4279..bc214399e 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 @@ -23,7 +23,7 @@ (def: #export (scope generate [start initsS+ bodyS]) (-> Phase (Scope Synthesis) (Operation (Expression Any))) (do {! ////.monad} - [@scope (:: ! map (|>> %.nat (format "scope") _.var) ///.next) + [@scope (\ ! map (|>> %.nat (format "scope") _.var) ///.next) initsG+ (monad.map ! generate initsS+) bodyG (///.with-anchor @scope (generate bodyS))] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/structure.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/structure.lux index ef29d33dc..45241a601 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/structure.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/structure.lux @@ -16,7 +16,7 @@ (-> Phase (Tuple Synthesis) (Operation (Expression Any))) (case elemsS+ #.Nil - (:: ////.monad wrap (//primitive.text /////synthesis.unit)) + (\ ////.monad wrap (//primitive.text /////synthesis.unit)) (#.Cons singletonS #.Nil) (generate singletonS) @@ -24,13 +24,13 @@ _ (|> elemsS+ (monad.map ////.monad generate) - (:: ////.monad map _.vector/*)))) + (\ ////.monad map _.vector/*)))) (def: #export (variant generate [lefts right? valueS]) (-> Phase (Variant Synthesis) (Operation (Expression Any))) - (:: ////.monad map - (//runtime.variant (if right? - (inc lefts) - lefts) - right?) - (generate valueS))) + (\ ////.monad map + (//runtime.variant (if right? + (inc lefts) + lefts) + right?) + (generate valueS))) 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 ce9625452..13038972b 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 @@ -163,7 +163,7 @@ [(^ (<simple> idx nextP)) (|> nextP recur - (:: ///////phase.monad map (|>> (_.then (<choice> true idx)) #.Some)))]) + (\ ///////phase.monad map (|>> (_.then (<choice> true idx)) #.Some)))]) ([/////synthesis.simple-left-side ..left-choice] [/////synthesis.simple-right-side ..right-choice]) @@ -261,7 +261,7 @@ [(<tag> cons) (do {! ///////phase.monad} [cases (monad.map ! (function (_ [match then]) - (:: ! map (|>> [(list (<format> match))]) (recur then))) + (\ ! map (|>> [(list (<format> match))]) (recur then))) (#.Cons cons))] (wrap (_.switch ..peek-cursor cases 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 12e328a11..c939b36a6 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 @@ -67,8 +67,8 @@ (do {! ///////phase.monad} [[function-name body!] (/////generation.with-new-context archive (do ! - [scope (:: ! map ..@scope - (/////generation.context archive))] + [scope (\ ! map ..@scope + (/////generation.context archive))] (/////generation.with-anchor [1 scope] (statement expression archive bodyS)))) #let [arityO (|> arity .int _.i32) 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 5e810a551..29cdc1180 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 @@ -49,7 +49,7 @@ ## true loop _ (do {! ///////phase.monad} - [@scope (:: ! map ..@scope /////generation.next) + [@scope (\ ! map ..@scope /////generation.next) initsO+ (monad.map ! (expression archive) initsS+) body! (/////generation.with-anchor [start @scope] (statement expression archive bodyS))] @@ -68,7 +68,7 @@ ## true loop _ (do {! ///////phase.monad} - [@scope (:: ! map ..@scope /////generation.next) + [@scope (\ ! map ..@scope /////generation.next) initsO+ (monad.map ! (expression archive) initsS+) body! (/////generation.with-anchor [start @scope] (statement expression archive bodyS)) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux index 657566813..f429b0442 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux @@ -23,7 +23,7 @@ [outcome (do (try.with @) [file (: (IO (Try (File IO))) (file.get-file io.monad file.default file-path))] - (!.use (:: file over-write) bytecode))] + (!.use (\ file over-write) bytecode))] (wrap (case outcome (#try.Success definition) file-path diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux index b13e1c63f..c87f00333 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux @@ -112,11 +112,11 @@ _.return)))) (row.row))] (io.run (do {! (try.with io.monad)} - [bytecode (:: ! map (format.run class.writer) - (io.io bytecode)) + [bytecode (\ ! map (format.run class.writer) + (io.io bytecode)) _ (loader.store eval-class bytecode library) class (loader.load eval-class loader) - value (:: io.monad wrap (class-value eval-class class))] + value (\ io.monad wrap (class-value eval-class class))] (wrap [value [eval-class bytecode]]))))) @@ -124,7 +124,7 @@ (-> Library java/lang/ClassLoader Text Definition (Try Any)) (io.run (do (try.with io.monad) [existing-class? (|> (atom.read library) - (:: io.monad map (dictionary.contains? class-name)) + (\ io.monad map (dictionary.contains? class-name)) (try.lift io.monad) (: (IO (Try Bit)))) _ (if existing-class? @@ -149,8 +149,8 @@ (structure (def: (evaluate! temp-label valueG) (let [eval-class (|> temp-label name.normalize (text.replace-all " " "$"))] - (:: try.monad map product.left - (..evaluate! library loader eval-class valueG)))) + (\ try.monad map product.left + (..evaluate! library loader eval-class valueG)))) (def: execute! (..execute! library loader)) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux index e74488d08..edffd87ff 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux @@ -41,8 +41,8 @@ (def: (foreign archive variable) (-> Archive Register (Operation (Bytecode Any))) (do {! ////.monad} - [bytecode-name (:: ! map //runtime.class-name - (generation.context archive))] + [bytecode-name (\ ! map //runtime.class-name + (generation.context archive))] (wrap ($_ _.compose ..this (_.getfield (type.class bytecode-name (list)) @@ -61,6 +61,6 @@ (def: #export (constant archive name) (-> Archive Name (Operation (Bytecode Any))) (do {! ////.monad} - [bytecode-name (:: ! map //runtime.class-name - (generation.remember archive name))] + [bytecode-name (\ ! map //runtime.class-name + (generation.remember archive name))] (wrap (_.getstatic (type.class bytecode-name (list)) //value.field //type.value)))) 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 57d45f6c3..22db73c91 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 @@ -602,4 +602,4 @@ ## This shift is done to avoid the possibility of forged labels ## to be in the range of the labels that are generated automatically ## during the evaluation of Bytecode expressions. - (:: ////.monad map (i64.left-shift shift) generation.next))) + (\ ////.monad map (i64.left-shift shift) generation.next))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux index bbf8f252c..b89bbca35 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux @@ -29,7 +29,7 @@ (Generator (Tuple Synthesis)) (case membersS #.Nil - (:: phase.monad wrap //runtime.unit) + (\ phase.monad wrap //runtime.unit) (#.Cons singletonS #.Nil) (generate archive singletonS) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/function.lux index 98c60d243..0d97b3b8c 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/function.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/function.lux @@ -46,7 +46,7 @@ _ (do {! ///////phase.monad} - [@closure (:: ! map _.var (/////generation.gensym "closure")) + [@closure (\ ! map _.var (/////generation.gensym "closure")) #let [directive (_.function @closure (|> (list.enumeration inits) (list\map (|>> product.left ..capture))) @@ -65,12 +65,12 @@ (do {! ///////phase.monad} [[function-name bodyO] (/////generation.with-new-context (do ! - [function-name (:: ! map ///reference.artifact-name - /////generation.context)] + [function-name (\ ! map ///reference.artifact-name + /////generation.context)] (/////generation.with-anchor (_.var function-name) (generate archive bodyS)))) closureO+ (: (Operation (List (Expression Any))) - (monad.map ! (:: //reference.system variable) environment)) + (monad.map ! (\ //reference.system variable) environment)) #let [function-name (///reference.artifact-name function-name) @curried (_.var "curried") arityO (|> arity .int _.int) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux index e04186c17..4b405a8af 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux @@ -28,7 +28,7 @@ (def: #export (scope generate archive [start initsS+ bodyS]) (Generator (Scope Synthesis)) (do {! ///////phase.monad} - [@loop (:: ! map ..loop-name /////generation.next) + [@loop (\ ! map ..loop-name /////generation.next) initsO+ (monad.map ! (generate archive) initsS+) bodyO (/////generation.with-anchor @loop (generate archive bodyS)) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php.lux index 975301cef..43d449402 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php.lux @@ -21,7 +21,7 @@ (case synthesis (^template [<tag> <generator>] [(^ (<tag> value)) - (:: ///.monad wrap (<generator> value))]) + (\ ///.monad wrap (<generator> value))]) ([synthesis.bit primitive.bit] [synthesis.i64 primitive.i64] [synthesis.f64 primitive.f64] 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 5ef6bb4b3..141f651f8 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 @@ -140,7 +140,7 @@ (-> Phase Path (Operation Statement)) (.case pathP (^ (/////synthesis.path/then bodyS)) - (:: ////.monad map _.return (generate bodyS)) + (\ ////.monad map _.return (generate bodyS)) #/////synthesis.Pop (////\wrap ..pop!) @@ -164,7 +164,7 @@ (^ (<simple> idx nextP)) (|> nextP (pattern-matching' generate) - (:: ////.monad map (_.then (<choice> true idx))))]) + (\ ////.monad map (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple-left-side ..left-choice] [/////synthesis.side/right /////synthesis.simple-right-side ..right-choice]) @@ -212,7 +212,7 @@ (def: (gensym prefix) (-> Text (Operation Text)) - (:: ////.monad map (|>> %.nat (format prefix)) ///.next)) + (\ ////.monad map (|>> %.nat (format prefix)) ///.next)) (def: #export (case generate [valueS pathP]) (-> Phase [Synthesis Path] (Operation (Expression Any))) @@ -222,7 +222,7 @@ @case (..gensym "case") #let [@caseG (_.global @case) @caseL (_.var @case)] - @init (:: ! map _.var (..gensym "init")) + @init (\ ! map _.var (..gensym "init")) #let [@dependencies+ (|> (case.storage pathP) (get@ #case.dependencies) set.to-list 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 e021f5234..33660380c 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 @@ -46,8 +46,8 @@ (///.with-anchor (_.var function-name) (generate bodyS)))) closureG+ (: (Operation (List Argument)) - (monad.map ! (|>> (:: //reference.system variable) - (:: ! map _.reference)) + (monad.map ! (|>> (\ //reference.system variable) + (\ ! map _.reference)) environment)) #let [@curried (_.var "curried") arityG (|> arity .int _.int) 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 f94470be8..a3482d8a7 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 @@ -23,7 +23,7 @@ (def: #export (scope generate [start initsS+ bodyS]) (-> Phase (Scope Synthesis) (Operation (Expression Any))) (do {! ////.monad} - [@loop (:: ! map (|>> %.nat (format "loop")) ///.next) + [@loop (\ ! map (|>> %.nat (format "loop")) ///.next) #let [@loopG (_.global @loop) @loopL (_.var @loop)] initsO+ (monad.map ! generate initsS+) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/structure.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/structure.lux index 8ea387fa2..9748ede02 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/structure.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/structure.lux @@ -16,7 +16,7 @@ (-> Phase (Tuple Synthesis) (Operation (Expression Any))) (case elemsS+ #.Nil - (:: ////.monad wrap (//primitive.text /////synthesis.unit)) + (\ ////.monad wrap (//primitive.text /////synthesis.unit)) (#.Cons singletonS #.Nil) (generate singletonS) @@ -24,13 +24,13 @@ _ (|> elemsS+ (monad.map ////.monad generate) - (:: ////.monad map _.array/*)))) + (\ ////.monad map _.array/*)))) (def: #export (variant generate [lefts right? valueS]) (-> Phase (Variant Synthesis) (Operation (Expression Any))) - (:: ////.monad map - (//runtime.variant (if right? - (inc lefts) - lefts) - right?) - (generate valueS))) + (\ ////.monad map + (//runtime.variant (if right? + (inc lefts) + lefts) + right?) + (generate valueS))) 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 28e8867a0..5ce811dfd 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 @@ -46,7 +46,7 @@ _ (do {! ///////phase.monad} - [@closure (:: ! map _.var (/////generation.gensym "closure")) + [@closure (\ ! map _.var (/////generation.gensym "closure")) #let [directive (_.def @closure (|> (list.enumeration inits) (list\map (|>> product.left ..capture))) @@ -65,12 +65,12 @@ (do {! ///////phase.monad} [[function-name bodyO] (/////generation.with-new-context (do ! - [function-name (:: ! map ///reference.artifact-name - /////generation.context)] + [function-name (\ ! map ///reference.artifact-name + /////generation.context)] (/////generation.with-anchor (_.var function-name) (generate archive bodyS)))) closureO+ (: (Operation (List (Expression Any))) - (monad.map ! (:: //reference.system variable) environment)) + (monad.map ! (\ //reference.system variable) environment)) #let [function-name (///reference.artifact-name function-name) @curried (_.var "curried") arityO (|> arity .int _.int) 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 e8f2bd5f7..14868757d 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 @@ -28,7 +28,7 @@ (def: #export (scope generate archive [start initsS+ bodyS]) (Generator (Scope Synthesis)) (do {! ///////phase.monad} - [@loop (:: ! map ..loop-name /////generation.next) + [@loop (\ ! map ..loop-name /////generation.next) initsO+ (monad.map ! (generate archive) initsS+) bodyO (/////generation.with-anchor @loop (generate archive bodyS)) 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 b587d2963..0bb5694b7 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 @@ -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>] @@ -38,7 +38,7 @@ (All [expression] (-> (System expression) (-> Register expression))) - (|>> %.nat (format <sigil>) (:: system variable)))] + (|>> %.nat (format <sigil>) (\ system variable)))] ["f" foreign] ["l" local] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux index 942829635..091c8fb6a 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux @@ -57,12 +57,12 @@ (do {! ///////phase.monad} [[function-name bodyO] (/////generation.with-new-context (do ! - [function-name (:: ! map ///reference.artifact-name - /////generation.context)] + [function-name (\ ! map ///reference.artifact-name + /////generation.context)] (/////generation.with-anchor (_.local function-name) (generate archive bodyS)))) closureO+ (: (Operation (List (Expression Any))) - (monad.map ! (:: //reference.system variable) environment)) + (monad.map ! (\ //reference.system variable) environment)) #let [function-name (///reference.artifact-name function-name) @curried (_.local "curried") arityO (|> arity .int _.int) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux index 42d048ed5..cecea44e9 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux @@ -28,7 +28,7 @@ (def: #export (scope generate archive [start initsS+ bodyS]) (Generator (Scope Synthesis)) (do {! ///////phase.monad} - [@loop (:: ! map ..loop-name /////generation.next) + [@loop (\ ! map ..loop-name /////generation.next) initsO+ (monad.map ! (generate archive) initsS+) bodyO (/////generation.with-anchor @loop (generate archive bodyS))] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme.lux index d6d33999b..e7f50ee82 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme.lux @@ -21,7 +21,7 @@ (case synthesis (^template [<tag> <generator>] [(^ (<tag> value)) - (:: ///.monad wrap (<generator> value))]) + (\ ///.monad wrap (<generator> value))]) ([synthesis.bit primitive.bit] [synthesis.i64 primitive.i64] [synthesis.f64 primitive.f64] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux index b25ac6bed..5f460b749 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux @@ -166,6 +166,6 @@ (-> Phase [Synthesis Path] (Operation Computation)) (do {! ////.monad} [valueO (generate valueS)] - (<| (:: ! map (_.let (list [@cursor (_.list/* (list valueO))] - [@savepoint (_.list/* (list))]))) + (<| (\ ! map (_.let (list [@cursor (_.list/* (list valueO))] + [@savepoint (_.list/* (list))]))) (pattern-matching generate pathP)))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux index 7206c23d5..97725a8f2 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux @@ -66,7 +66,7 @@ (///.with-anchor (_.var function-name) (generate bodyS)))) closureO+ (: (Operation (List Expression)) - (monad.map ! (:: //reference.system variable) environment)) + (monad.map ! (\ //reference.system variable) environment)) #let [arityO (|> arity .int _.int) apply-poly (.function (_ args func) (_.apply/2 (_.global "apply") func args)) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux index 18a74a4a3..bb11d2e1f 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux @@ -16,7 +16,7 @@ (-> Phase (Tuple Synthesis) (Operation Expression)) (case elemsS+ #.Nil - (:: ///.monad wrap (primitive.text synthesis.unit)) + (\ ///.monad wrap (primitive.text synthesis.unit)) (#.Cons singletonS #.Nil) (generate singletonS) diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/case.lux index ff740e751..c9b1757ce 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -56,7 +56,7 @@ [#///analysis.Text #/.Text-Fork |>])) (#///analysis.Bind register) - (<| (:: ///.monad map (|>> (#/.Seq (#/.Bind register)))) + (<| (\ ///.monad map (|>> (#/.Seq (#/.Bind register)))) /.with-new-local thenC) @@ -95,7 +95,7 @@ (def: (weave-branch weave equivalence [new-test new-then] [[old-test old-then] old-tail]) (All [a] (-> (-> Path Path Path) (Equivalence a) [a Path] (/.Fork a Path) (/.Fork a Path))) - (if (:: equivalence = new-test old-test) + (if (\ equivalence = new-test old-test) [[old-test (weave new-then old-then)] old-tail] [[old-test old-then] (case old-tail diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/function.lux index 2831b2605..2359e03b8 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -107,7 +107,7 @@ [then (grow-path grow then) else (case else (#.Some else) - (:: ! map (|>> #.Some) (grow-path grow else)) + (\ ! map (|>> #.Some) (grow-path grow else)) #.None (wrap #.None))] @@ -254,10 +254,10 @@ (^ (/.function/abstraction [env' down-arity' bodyS'])) (|> bodyS' (grow env') - (:: ! map (function (_ body) - {#/.environment environment - #/.arity (inc down-arity') - #/.body body}))) + (\ ! map (function (_ body) + {#/.environment environment + #/.arity (inc down-arity') + #/.body body}))) _ (wrap {#/.environment environment diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index 3c99cdef9..80ce194d6 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -43,7 +43,7 @@ [then (recur then) else (case else (#.Some else) - (:: ! map (|>> #.Some) (recur else)) + (\ ! map (|>> #.Some) (recur else)) #.None (wrap #.None))] diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index 4055f70e7..1312f9ed7 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -255,10 +255,10 @@ [[redundancy then] (recur [redundancy then]) [redundancy else] (case else (#.Some else) - (:: ! map - (function (_ [redundancy else]) - [redundancy (#.Some else)]) - (recur [redundancy else])) + (\ ! map + (function (_ [redundancy else]) + [redundancy (#.Some else)]) + (recur [redundancy else])) #.None (wrap [redundancy #.None]))] @@ -438,4 +438,4 @@ (-> Synthesis (Try Synthesis)) (|>> [..initial] optimization' - (:: try.monad map product.right))) + (\ try.monad map product.right))) diff --git a/stdlib/source/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/lux/tool/compiler/language/lux/syntax.lux index f2c9a4afa..766e5cbf2 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/syntax.lux @@ -306,7 +306,7 @@ (case (|> source-code (!clip <start> <end>) (text.replace-all ..digit-separator "") - (:: <codec> decode)) + (\ <codec> decode)) (#.Right output) (#.Right [[(update@ #.column (|>> (!n/+ (!n/- <start> <end>))) where) <end> diff --git a/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux index 0fe2bf712..5b631ab1b 100644 --- a/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/lux/tool/compiler/language/lux/synthesis.lux @@ -437,7 +437,7 @@ (def: hash (|>> (case> (^template [<tag> <hash>] [(<tag> value') - (:: <hash> hash value')]) + (\ <hash> hash value')]) ([#Bit bit.hash] [#F64 f.hash] [#Text text.hash] @@ -462,7 +462,7 @@ (case [reference sample] (^template [<tag> <equivalence>] [[(<tag> reference) (<tag> sample)] - (:: <equivalence> = reference sample)]) + (\ <equivalence> = reference sample)]) ([#Side ..side-equivalence] [#Member ..member-equivalence]) @@ -479,7 +479,7 @@ (case value (^template [<tag>] [(<tag> value) - (:: sub-hash hash value)]) + (\ sub-hash hash value)]) ([#Side] [#Member]))))) @@ -495,21 +495,21 @@ (#Bit-Fork sample-when sample-then sample-else)] (and (bit\= reference-when sample-when) (= reference-then sample-then) - (:: (maybe.equivalence =) = reference-else sample-else)) + (\ (maybe.equivalence =) = reference-else sample-else)) (^template [<tag> <equivalence>] [[(<tag> reference-cons) (<tag> sample-cons)] - (:: (list.equivalence (equivalence.product <equivalence> =)) = - (#.Cons reference-cons) - (#.Cons sample-cons))]) + (\ (list.equivalence (equivalence.product <equivalence> =)) = + (#.Cons reference-cons) + (#.Cons sample-cons))]) ([#I64-Fork i64.equivalence] [#F64-Fork f.equivalence] [#Text-Fork text.equivalence]) (^template [<tag> <equivalence>] [[(<tag> reference') (<tag> sample')] - (:: <equivalence> = reference' sample')]) + (\ <equivalence> = reference' sample')]) ([#Access ..access-equivalence] [#Then equivalence]) @@ -530,7 +530,7 @@ (All [a] (-> (Hash a) (Hash (Path' a)))) (def: &equivalence - (..path'-equivalence (:: super &equivalence))) + (..path'-equivalence (\ super &equivalence))) (def: (hash value) (case value @@ -538,23 +538,23 @@ 2 (#Access access) - (n.* 3 (:: ..access-hash hash access)) + (n.* 3 (\ ..access-hash hash access)) (#Bind register) - (n.* 5 (:: n.hash hash register)) + (n.* 5 (\ n.hash hash register)) (#Bit-Fork when then else) ($_ n.* 7 - (:: bit.hash hash when) + (\ bit.hash hash when) (hash then) - (:: (maybe.hash (path'-hash super)) hash else)) + (\ (maybe.hash (path'-hash super)) hash else)) (^template [<factor> <tag> <hash>] [(<tag> cons) (let [case-hash (product.hash <hash> (path'-hash super)) cons-hash (product.hash case-hash (list.hash case-hash))] - (n.* <factor> (:: cons-hash hash cons)))]) + (n.* <factor> (\ cons-hash hash cons)))]) ([11 #I64-Fork i64.hash] [13 #F64-Fork f.hash] [17 #Text-Fork text.hash]) @@ -563,12 +563,12 @@ [(<tag> fork) (let [recur-hash (path'-hash super) fork-hash (product.hash recur-hash recur-hash)] - (n.* <factor> (:: fork-hash hash fork)))]) + (n.* <factor> (\ fork-hash hash fork)))]) ([19 #Alt] [23 #Seq]) (#Then body) - (n.* 29 (:: super hash body)) + (n.* 29 (\ super hash body)) ))) (structure: (branch-equivalence (^open "\.")) @@ -590,13 +590,13 @@ [(#Get [reference-path reference-record]) (#Get [sample-path sample-record])] - (and (:: (list.equivalence ..member-equivalence) = reference-path sample-path) + (and (\ (list.equivalence ..member-equivalence) = reference-path sample-path) (\= reference-record sample-record)) [(#Case [reference-input reference-path]) (#Case [sample-input sample-path])] (and (\= reference-input sample-input) - (:: (path'-equivalence \=) = reference-path sample-path)) + (\ (path'-equivalence \=) = reference-path sample-path)) _ false))) @@ -605,31 +605,31 @@ (All [a] (-> (Hash a) (Hash (Branch a)))) (def: &equivalence - (..branch-equivalence (:: super &equivalence))) + (..branch-equivalence (\ super &equivalence))) (def: (hash value) (case value (#Let [input register body]) ($_ n.* 2 - (:: super hash input) - (:: n.hash hash register) - (:: super hash body)) + (\ super hash input) + (\ n.hash hash register) + (\ super hash body)) (#If [test then else]) ($_ n.* 3 - (:: super hash test) - (:: super hash then) - (:: super hash else)) + (\ super hash test) + (\ super hash then) + (\ super hash else)) (#Get [path record]) ($_ n.* 5 - (:: (list.hash ..member-hash) hash path) - (:: super hash record)) + (\ (list.hash ..member-hash) hash path) + (\ super hash record)) (#Case [input path]) ($_ n.* 7 - (:: super hash input) - (:: (..path'-hash super) hash path)) + (\ super hash input) + (\ (..path'-hash super) hash path)) ))) (structure: (loop-equivalence (^open "\.")) @@ -640,11 +640,11 @@ [(#Scope [reference-start reference-inits reference-iteration]) (#Scope [sample-start sample-inits sample-iteration])] (and (n.= reference-start sample-start) - (:: (list.equivalence \=) = reference-inits sample-inits) + (\ (list.equivalence \=) = reference-inits sample-inits) (\= reference-iteration sample-iteration)) [(#Recur reference) (#Recur sample)] - (:: (list.equivalence \=) = reference sample) + (\ (list.equivalence \=) = reference sample) _ false))) @@ -653,19 +653,19 @@ (All [a] (-> (Hash a) (Hash (Loop a)))) (def: &equivalence - (..loop-equivalence (:: super &equivalence))) + (..loop-equivalence (\ super &equivalence))) (def: (hash value) (case value (#Scope [start inits iteration]) ($_ n.* 2 - (:: n.hash hash start) - (:: (list.hash super) hash inits) - (:: super hash iteration)) + (\ n.hash hash start) + (\ (list.hash super) hash inits) + (\ super hash iteration)) (#Recur resets) ($_ n.* 3 - (:: (list.hash super) hash resets)) + (\ (list.hash super) hash resets)) ))) (structure: (function-equivalence (^open "\.")) @@ -675,14 +675,14 @@ (case [reference sample] [(#Abstraction [reference-environment reference-arity reference-body]) (#Abstraction [sample-environment sample-arity sample-body])] - (and (:: (list.equivalence \=) = reference-environment sample-environment) + (and (\ (list.equivalence \=) = reference-environment sample-environment) (n.= reference-arity sample-arity) (\= reference-body sample-body)) [(#Apply [reference-abstraction reference-arguments]) (#Apply [sample-abstraction sample-arguments])] (and (\= reference-abstraction sample-abstraction) - (:: (list.equivalence \=) = reference-arguments sample-arguments)) + (\ (list.equivalence \=) = reference-arguments sample-arguments)) _ false))) @@ -691,20 +691,20 @@ (All [a] (-> (Hash a) (Hash (Function a)))) (def: &equivalence - (..function-equivalence (:: super &equivalence))) + (..function-equivalence (\ super &equivalence))) (def: (hash value) (case value (#Abstraction [environment arity body]) ($_ n.* 2 - (:: (list.hash super) hash environment) - (:: n.hash hash arity) - (:: super hash body)) + (\ (list.hash super) hash environment) + (\ n.hash hash arity) + (\ super hash body)) (#Apply [abstraction arguments]) ($_ n.* 3 - (:: super hash abstraction) - (:: (list.hash super) hash arguments)) + (\ super hash abstraction) + (\ (list.hash super) hash arguments)) ))) (structure: (control-equivalence (^open "\.")) @@ -714,7 +714,7 @@ (case [reference sample] (^template [<tag> <equivalence>] [[(<tag> reference) (<tag> sample)] - (:: (<equivalence> \=) = reference sample)]) + (\ (<equivalence> \=) = reference sample)]) ([#Branch ..branch-equivalence] [#Loop ..loop-equivalence] [#Function ..function-equivalence]) @@ -726,13 +726,13 @@ (All [a] (-> (Hash a) (Hash (Control a)))) (def: &equivalence - (..control-equivalence (:: super &equivalence))) + (..control-equivalence (\ super &equivalence))) (def: (hash value) (case value (^template [<factor> <tag> <hash>] [(<tag> value) - (n.* <factor> (:: (<hash> super) hash value))]) + (n.* <factor> (\ (<hash> super) hash value))]) ([2 #Branch ..branch-hash] [3 #Loop ..loop-hash] [5 #Function ..function-hash]) @@ -745,7 +745,7 @@ (case [reference sample] (^template [<tag> <equivalence>] [[(<tag> reference') (<tag> sample')] - (:: <equivalence> = reference' sample')]) + (\ <equivalence> = reference' sample')]) ([#Primitive ..primitive-equivalence] [#Structure (analysis.composite-equivalence =)] [#Reference reference.equivalence] @@ -769,7 +769,7 @@ (case value (^template [<tag> <hash>] [(<tag> value) - (:: <hash> hash value)]) + (\ <hash> hash value)]) ([#Primitive ..primitive-hash] [#Structure (analysis.composite-hash recur-hash)] [#Reference reference.hash] diff --git a/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux index dec8938b3..319b23169 100644 --- a/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux @@ -127,28 +127,28 @@ (do {! <>.monad} [tag <b>.nat] (case tag - 0 (:: ! map (|>> #Anonymous) <b>.any) - 1 (:: ! map (|>> #Definition) <b>.text) - 2 (:: ! map (|>> #Analyser) <b>.text) - 3 (:: ! map (|>> #Synthesizer) <b>.text) - 4 (:: ! map (|>> #Generator) <b>.text) - 5 (:: ! map (|>> #Directive) <b>.text) + 0 (\ ! map (|>> #Anonymous) <b>.any) + 1 (\ ! map (|>> #Definition) <b>.text) + 2 (\ ! map (|>> #Analyser) <b>.text) + 3 (\ ! map (|>> #Synthesizer) <b>.text) + 4 (\ ! map (|>> #Generator) <b>.text) + 5 (\ ! map (|>> #Directive) <b>.text) _ (<>.fail (exception.construct ..invalid-category [tag])))))] (|> (<b>.row/64 category) - (:: <>.monad map (row\fold (function (_ artifact registry) - (product.right - (case artifact - #Anonymous - (..resource registry) - - (^template [<tag> <create>] - [(<tag> name) - (<create> name registry)]) - ([#Definition ..definition] - [#Analyser ..analyser] - [#Synthesizer ..synthesizer] - [#Generator ..generator] - [#Directive ..directive]) - ))) - ..empty))))) + (\ <>.monad map (row\fold (function (_ artifact registry) + (product.right + (case artifact + #Anonymous + (..resource registry) + + (^template [<tag> <create>] + [(<tag> name) + (<create> name registry)]) + ([#Definition ..definition] + [#Analyser ..analyser] + [#Synthesizer ..synthesizer] + [#Generator ..generator] + [#Directive ..directive]) + ))) + ..empty))))) ) diff --git a/stdlib/source/lux/tool/compiler/meta/archive/descriptor.lux b/stdlib/source/lux/tool/compiler/meta/archive/descriptor.lux index 987aa5fbf..2ae89cf4e 100644 --- a/stdlib/source/lux/tool/compiler/meta/archive/descriptor.lux +++ b/stdlib/source/lux/tool/compiler/meta/archive/descriptor.lux @@ -42,7 +42,7 @@ <b>.text <b>.text <b>.nat - (:: <>.monad wrap #.Cached) + (\ <>.monad wrap #.Cached) (<b>.set text.hash <b>.text) artifact.parser )) diff --git a/stdlib/source/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/lux/tool/compiler/meta/archive/document.lux index bc6fc5288..a8c656ff9 100644 --- a/stdlib/source/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/lux/tool/compiler/meta/archive/document.lux @@ -31,9 +31,9 @@ (def: #export (read key document) (All [d] (-> (Key d) (Document Any) (Try d))) (let [[document//signature document//content] (:representation document)] - (if (:: signature.equivalence = - (key.signature key) - document//signature) + (if (\ signature.equivalence = + (key.signature key) + document//signature) (#try.Success (:share [e] {(Key e) key} @@ -66,5 +66,5 @@ (def: #export parser (All [d] (-> (Parser d) (Parser (Document d)))) (|>> (<>.and signature.parser) - (:: <>.monad map (|>> :abstraction)))) + (\ <>.monad map (|>> :abstraction)))) ) diff --git a/stdlib/source/lux/tool/compiler/meta/io.lux b/stdlib/source/lux/tool/compiler/meta/io.lux index 41481d0fa..0a7927aa0 100644 --- a/stdlib/source/lux/tool/compiler/meta/io.lux +++ b/stdlib/source/lux/tool/compiler/meta/io.lux @@ -13,7 +13,7 @@ (def: #export (sanitize system) (All [m] (-> (System m) Text Text)) - (text.replace-all "/" (:: system separator))) + (text.replace-all "/" (\ system separator))) (def: #export lux-context "lux") diff --git a/stdlib/source/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/lux/tool/compiler/meta/io/archive.lux index 63639f444..e2c046449 100644 --- a/stdlib/source/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/lux/tool/compiler/meta/io/archive.lux @@ -61,31 +61,31 @@ (def: (archive system static) (All [!] (-> (file.System !) Static Path)) (format (get@ #static.target static) - (:: system separator) + (\ system separator) (get@ #static.host static))) (def: (unversioned-lux-archive system static) (All [!] (-> (file.System !) Static Path)) (format (..archive system static) - (:: system separator) + (\ system separator) //.lux-context)) (def: (versioned-lux-archive system static) (All [!] (-> (file.System !) Static Path)) (format (..unversioned-lux-archive system static) - (:: system separator) + (\ system separator) (%.nat version.version))) (def: (module system static module-id) (All [!] (-> (file.System !) Static archive.ID Path)) (format (..versioned-lux-archive system static) - (:: system separator) + (\ system separator) (%.nat module-id))) (def: #export (artifact system static module-id name) (All [!] (-> (file.System !) Static archive.ID Text Path)) (format (..module system static module-id) - (:: system separator) + (\ system separator) name (get@ #static.artifact-extension static))) @@ -99,7 +99,7 @@ (do ! [_ (file.get-directory ! system (..unversioned-lux-archive system static)) _ (file.get-directory ! system (..versioned-lux-archive system static)) - outcome (!.use (:: system create-directory) module)] + outcome (!.use (\ system create-directory) module)] (case outcome (#try.Success output) (wrap (#try.Success [])) @@ -115,7 +115,7 @@ [artifact (: (Promise (Try (File Promise))) (file.get-file promise.monad system (..artifact system static module-id name)))] - (!.use (:: artifact over-write) content))) + (!.use (\ artifact over-write) content))) (def: #export (enable system static) (-> (file.System Promise) Static (Promise (Try Any))) @@ -129,7 +129,7 @@ (def: (general-descriptor system static) (-> (file.System Promise) Static Path) (format (..archive system static) - (:: system separator) + (\ system separator) "general-descriptor")) (def: #export (freeze system static archive) @@ -137,7 +137,7 @@ (do (try.with promise.monad) [file (: (Promise (Try (File Promise))) (file.get-file promise.monad system (..general-descriptor system static)))] - (!.use (:: file over-write) (archive.export ///.version archive)))) + (!.use (\ file over-write) (archive.export ///.version archive)))) (def: module-descriptor-file "module-descriptor") @@ -145,7 +145,7 @@ (def: (module-descriptor system static module-id) (-> (file.System Promise) Static archive.ID Path) (format (..module system static module-id) - (:: system separator) + (\ system separator) ..module-descriptor-file)) (def: #export (cache system static module-id content) @@ -154,7 +154,7 @@ [file (: (Promise (Try (File Promise))) (file.get-file promise.monad system (..module-descriptor system static module-id)))] - (!.use (:: file over-write) content))) + (!.use (\ file over-write) content))) (def: (read-module-descriptor system static module-id) (-> (file.System Promise) Static archive.ID (Promise (Try Binary))) @@ -162,7 +162,7 @@ [file (: (Promise (Try (File Promise))) (file.get-file promise.monad system (..module-descriptor system static module-id)))] - (!.use (:: file content) []))) + (!.use (\ file content) []))) (def: parser (Parser [Descriptor (Document .Module)]) @@ -188,21 +188,21 @@ (def: (cached-artifacts system static module-id) (-> (file.System Promise) Static archive.ID (Promise (Try (Dictionary Text Binary)))) (do {! (try.with promise.monad)} - [module-dir (!.use (:: system directory) (..module system static module-id)) - cached-files (!.use (:: module-dir files) [])] + [module-dir (!.use (\ system directory) (..module system static module-id)) + cached-files (!.use (\ module-dir files) [])] (|> cached-files (list\map (function (_ file) - [(!.use (:: file name) []) - (!.use (:: file path) [])])) + [(!.use (\ file name) []) + (!.use (\ file path) [])])) (list.filter (|>> product.left (text\= ..module-descriptor-file) not)) (monad.map ! (function (_ [name path]) (do ! [file (: (Promise (Try (File Promise))) - (!.use (:: system file) path)) + (!.use (\ system file) path)) data (: (Promise (Try Binary)) - (!.use (:: file content) []))] + (!.use (\ file content) []))] (wrap [name data])))) - (:: ! map (dictionary.from-list text.hash))))) + (\ ! map (dictionary.from-list text.hash))))) (type: Definitions (Dictionary Text Any)) (type: Analysers (Dictionary Text analysis.Handler)) @@ -239,11 +239,11 @@ (case (do ! [data (try.from-maybe (dictionary.get (format (%.nat artifact-id) extension) actual)) #let [context [module-id artifact-id] - directive (:: host ingest context data)]] + directive (\ host ingest context data)]] (case artifact-category #artifact.Anonymous (do ! - [_ (:: host re-learn context directive)] + [_ (\ host re-learn context directive)] (wrap [definitions [analysers synthesizers @@ -258,7 +258,7 @@ generators directives]]) (do ! - [value (:: host re-load context directive)] + [value (\ host re-load context directive)] (wrap [(dictionary.put name value definitions) [analysers synthesizers @@ -267,7 +267,7 @@ (#artifact.Analyser extension) (do ! - [value (:: host re-load context directive)] + [value (\ host re-load context directive)] (wrap [definitions [(dictionary.put extension (:coerce analysis.Handler value) analysers) synthesizers @@ -276,7 +276,7 @@ (#artifact.Synthesizer extension) (do ! - [value (:: host re-load context directive)] + [value (\ host re-load context directive)] (wrap [definitions [analysers (dictionary.put extension (:coerce synthesis.Handler value) synthesizers) @@ -285,7 +285,7 @@ (#artifact.Generator extension) (do ! - [value (:: host re-load context directive)] + [value (\ host re-load context directive)] (wrap [definitions [analysers synthesizers @@ -294,7 +294,7 @@ (#artifact.Directive extension) (do ! - [value (:: host re-load context directive)] + [value (\ host re-load context directive)] (wrap [definitions [analysers synthesizers @@ -337,12 +337,12 @@ (def: (purge! system static [module-name module-id]) (-> (file.System Promise) Static [Module archive.ID] (Promise (Try Any))) (do {! (try.with promise.monad)} - [cache (!.use (:: system directory) [(..module system static module-id)]) - artifacts (!.use (:: cache files) []) + [cache (!.use (\ system directory) [(..module system static module-id)]) + artifacts (!.use (\ cache files) []) _ (monad.map ! (function (_ artifact) - (!.use (:: artifact delete) [])) + (!.use (\ artifact delete) [])) artifacts)] - (!.use (:: cache discard) []))) + (!.use (\ cache discard) []))) (def: (valid-cache? expected actual) (-> Descriptor Input Bit) @@ -408,8 +408,8 @@ (function (_ [module [module-id descriptor,document]] archive) (archive.add module descriptor,document archive)) archive) - (:: try.monad map (dependency.load-order $.key)) - (:: try.monad join) + (\ try.monad map (dependency.load-order $.key)) + (\ try.monad join) promise\wrap) #let [purge (..full-purge pre-loaded-caches load-order)] _ (|> purge @@ -447,11 +447,11 @@ (-> (generation.Host expression directive) (file.System Promise) Static Import (List Context) (Promise (Try [Archive .Lux Bundles])))) (do promise.monad - [file (!.use (:: system file) (..general-descriptor system static))] + [file (!.use (\ system file) (..general-descriptor system static))] (case file (#try.Success file) (do (try.with promise.monad) - [binary (!.use (:: file content) []) + [binary (!.use (\ file content) []) archive (promise\wrap (archive.import ///.version binary))] (..load-every-reserved-module host-environment system static import contexts archive)) diff --git a/stdlib/source/lux/tool/compiler/meta/io/context.lux b/stdlib/source/lux/tool/compiler/meta/io/context.lux index 572905325..74f0b4bd8 100644 --- a/stdlib/source/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/lux/tool/compiler/meta/io/context.lux @@ -49,7 +49,7 @@ (All [m] (-> (file.System m) Context Module Path)) (|> module (//.sanitize system) - (format context (:: system separator)))) + (format context (\ system separator)))) (def: (find-source-file system contexts module extension) (-> (file.System Promise) (List Context) Module Extension @@ -61,7 +61,7 @@ (#.Cons context contexts') (do promise.monad [#let [path (format (..path system context module) extension)] - file (!.use (:: system file) [path])] + file (!.use (\ system file) [path])] (case file (#try.Success file) (wrap (#try.Success [path file])) @@ -83,13 +83,13 @@ (case outcome (#try.Success [path file]) (do (try.with !) - [data (!.use (:: file content) [])] + [data (!.use (\ file content) [])] (wrap [path data])) (#try.Failure _) (do (try.with !) [[path file] (..find-source-file system contexts module ..lux-extension) - data (!.use (:: file content) [])] + data (!.use (\ file content) [])] (wrap [path data]))))) (def: (find-library-source-file import partial-host-extension module) @@ -147,7 +147,7 @@ (def: (clean-path system context path) (All [!] (-> (file.System !) Context Path (Try Path))) - (let [prefix (format context (:: system separator))] + (let [prefix (format context (\ system separator))] (case (text.split-with prefix path) #.None (exception.throw ..cannot-clean-path [prefix path]) @@ -158,23 +158,23 @@ (def: (enumerate-context system context enumeration) (-> (file.System Promise) Context Enumeration (Promise (Try Enumeration))) (do {! (try.with promise.monad)} - [directory (!.use (:: system directory) [context])] + [directory (!.use (\ system directory) [context])] (loop [directory directory enumeration enumeration] (do ! - [files (!.use (:: directory files) []) + [files (!.use (\ directory files) []) enumeration (monad.fold ! (function (_ file enumeration) - (let [path (!.use (:: file path) [])] + (let [path (!.use (\ file path) [])] (if (text.ends-with? ..lux-extension path) (do ! [path (promise\wrap (..clean-path system context path)) - source-code (!.use (:: file content) [])] + source-code (!.use (\ file content) [])] (promise\wrap (dictionary.try-put path source-code enumeration))) (wrap enumeration)))) enumeration files) - directories (!.use (:: directory directories) [])] + directories (!.use (\ directory directories) [])] (monad.fold ! recur enumeration directories))))) (def: Action diff --git a/stdlib/source/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/lux/tool/compiler/meta/packager/jvm.lux index f5838cf80..fa63bedab 100644 --- a/stdlib/source/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/lux/tool/compiler/meta/packager/jvm.lux @@ -49,40 +49,49 @@ (import: java/lang/String) (import: java/util/jar/Attributes - (put [java/lang/Object java/lang/Object] #? java/lang/Object)) + ["#::." + (put [java/lang/Object java/lang/Object] #? java/lang/Object)]) (import: java/util/jar/Attributes$Name - (#static MAIN_CLASS java/util/jar/Attributes$Name) - (#static MANIFEST_VERSION java/util/jar/Attributes$Name)) + ["#::." + (#static MAIN_CLASS java/util/jar/Attributes$Name) + (#static MANIFEST_VERSION java/util/jar/Attributes$Name)]) (import: java/util/jar/Manifest - (new []) - (getMainAttributes [] java/util/jar/Attributes)) + ["#::." + (new []) + (getMainAttributes [] java/util/jar/Attributes)]) (import: java/io/Flushable - (flush [] void)) + ["#::." + (flush [] void)]) (import: java/io/Closeable - (close [] void)) + ["#::." + (close [] void)]) (import: java/io/OutputStream) (import: java/io/ByteArrayOutputStream - (new [int]) - (toByteArray [] [byte])) + ["#::." + (new [int]) + (toByteArray [] [byte])]) (import: java/util/zip/ZipEntry) (import: java/util/zip/ZipOutputStream - (write [[byte] int int] void) - (closeEntry [] void)) + ["#::." + (write [[byte] int int] void) + (closeEntry [] void)]) (import: java/util/jar/JarEntry - (new [java/lang/String])) + ["#::." + (new [java/lang/String])]) (import: java/util/jar/JarOutputStream - (new [java/io/OutputStream java/util/jar/Manifest]) - (putNextEntry [java/util/zip/ZipEntry] void)) + ["#::." + (new [java/io/OutputStream java/util/jar/Manifest]) + (putNextEntry [java/util/zip/ZipEntry] void)]) (def: byte 1) ## https://en.wikipedia.org/wiki/Kibibyte @@ -110,8 +119,8 @@ (Action ! java/util/jar/JarOutputStream))) (do (try.with monad) [artifact (let [[module artifact] context] - (!.use (:: file-system file) [(io.artifact file-system static module (%.nat artifact))])) - content (!.use (:: artifact content) []) + (!.use (\ file-system file) [(io.artifact file-system static module (%.nat artifact))])) + content (!.use (\ artifact content) []) #let [class-path (format (runtime.class-name context) (get@ #static.artifact-extension static))]] (wrap (do-to sink (java/util/jar/JarOutputStream::putNextEntry (java/util/jar/JarEntry::new class-path)) @@ -136,7 +145,7 @@ {(Monad !) monad} {(! (Try (Directory !))) - (:assume (!.use (:: file-system directory) [(get@ #static.target static)]))}) + (:assume (!.use (\ file-system directory) [(get@ #static.target static)]))}) order (|> archive archive.archived (monad.map try.monad (function (_ module) @@ -149,7 +158,7 @@ row.to-list (list\map (|>> (get@ #artifact.id))) [module-id]))))) - (:: monad wrap)) + (\ monad wrap)) #let [buffer (java/io/ByteArrayOutputStream::new (.int ..mebi-byte)) sink (java/util/jar/JarOutputStream::new buffer (..manifest program))] sink (monad.fold ! (..write-module monad file-system static) sink order) diff --git a/stdlib/source/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/lux/tool/compiler/meta/packager/script.lux index b40873ace..5b826a4e0 100644 --- a/stdlib/source/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/lux/tool/compiler/meta/packager/script.lux @@ -44,8 +44,8 @@ (Action ! Binary))) (do (try.with monad) [artifact (let [[module artifact] context] - (!.use (:: file-system file) [(io.artifact file-system static module (%.nat artifact))]))] - (!.use (:: artifact content) []))) + (!.use (\ file-system file) [(io.artifact file-system static module (%.nat artifact))]))] + (!.use (\ artifact content) []))) (def: (write-module monad file-system static sequence [module artifacts] so-far) (All [! directive] @@ -55,7 +55,7 @@ (function (_ artifact so-far) (do (try.with monad) [content (..write-artifact monad file-system static [module artifact]) - content (:: monad wrap (encoding.from-utf8 content))] + content (\ monad wrap (encoding.from-utf8 content))] (wrap (sequence so-far (:share [directive] {directive @@ -73,8 +73,8 @@ (Packager !))) (function (package monad file-system static archive program) (do {! (try.with monad)} - [cache (!.use (:: file-system directory) [(get@ #static.target static)]) - order (:: monad wrap (dependency.load-order $.key archive))] + [cache (!.use (\ file-system directory) [(get@ #static.target static)]) + order (\ monad wrap (dependency.load-order $.key archive))] (|> order (list\map (function (_ [module [module-id [descriptor document]]]) [module-id @@ -84,4 +84,4 @@ row.to-list (list\map (|>> (get@ #artifact.id))))])) (monad.fold ! (..write-module monad file-system static sequence) header) - (:: ! map (|>> to-code encoding.to-utf8)))))) + (\ ! map (|>> to-code encoding.to-utf8)))))) diff --git a/stdlib/source/lux/tool/compiler/phase.lux b/stdlib/source/lux/tool/compiler/phase.lux index 312428ff7..847faaefa 100644 --- a/stdlib/source/lux/tool/compiler/phase.lux +++ b/stdlib/source/lux/tool/compiler/phase.lux @@ -42,7 +42,7 @@ (-> s (Operation s o) (Try o))) (|> state operation - (:: try.monad map product.right))) + (\ try.monad map product.right))) (def: #export get-state (All [s o] @@ -81,7 +81,7 @@ (syntax: #export (assert exception message test) (wrap (list (` (if (~ test) - (:: ..monad (~' wrap) []) + (\ ..monad (~' wrap) []) (..throw (~ exception) (~ message))))))) (def: #export identity diff --git a/stdlib/source/lux/tool/compiler/reference.lux b/stdlib/source/lux/tool/compiler/reference.lux index 5ade63e39..62ec9e3ca 100644 --- a/stdlib/source/lux/tool/compiler/reference.lux +++ b/stdlib/source/lux/tool/compiler/reference.lux @@ -28,7 +28,7 @@ (case [reference sample] (^template [<tag> <equivalence>] [[(<tag> reference) (<tag> sample)] - (:: <equivalence> = reference sample)]) + (\ <equivalence> = reference sample)]) ([#Variable /variable.equivalence] [#Constant name.equivalence]) @@ -46,7 +46,7 @@ (^template [<factor> <tag> <hash>] [(<tag> value) ($_ n.* <factor> - (:: <hash> hash value))]) + (\ <hash> hash value))]) ([2 #Variable /variable.hash] [3 #Constant name.hash]) ))) diff --git a/stdlib/source/lux/tool/compiler/reference/variable.lux b/stdlib/source/lux/tool/compiler/reference/variable.lux index e97974596..2a4d1424d 100644 --- a/stdlib/source/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/lux/tool/compiler/reference/variable.lux @@ -42,7 +42,7 @@ (|>> (case> (^template [<factor> <tag>] [(<tag> register) ($_ n.* <factor> - (:: n.hash hash register))]) + (\ n.hash hash register))]) ([2 #Local] [3 #Foreign]))))) diff --git a/stdlib/source/lux/tool/interpreter.lux b/stdlib/source/lux/tool/interpreter.lux index a8c2fe0b6..e18a27c47 100644 --- a/stdlib/source/lux/tool/interpreter.lux +++ b/stdlib/source/lux/tool/interpreter.lux @@ -77,9 +77,9 @@ #.info #.mode] #.Interpreter state)) - [state _] (:: (get@ #platform.file-system platform) - lift (phase.run' state enter-module)) - _ (:: Console<!> write ..welcome-message)] + [state _] (\ (get@ #platform.file-system platform) + lift (phase.run' state enter-module)) + _ (\ Console<!> write ..welcome-message)] (wrap state))) (with-expansions [<Interpretation> (as-is (Operation anchor expression directive [Type Any]))] @@ -201,16 +201,16 @@ multi-line? #0] (do ! [_ (if multi-line? - (:: Console<!> write " ") - (:: Console<!> write "> ")) - line (:: Console<!> read-line)] + (\ Console<!> write " ") + (\ Console<!> write "> ")) + line (\ Console<!> read-line)] (if (and (not multi-line?) (text\= ..exit-command line)) - (:: Console<!> write ..farewell-message) + (\ Console<!> write ..farewell-message) (case (read-eval-print (update@ #source (add-line line) context)) (#try.Success [context' representation]) (do ! - [_ (:: Console<!> write representation)] + [_ (\ Console<!> write representation)] (recur context' #0)) (#try.Failure error) |