diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/language/compiler/extension.lux (renamed from stdlib/source/lux/lang/compiler/extension.lux) | 0 | ||||
-rw-r--r-- | stdlib/source/lux/language/compiler/extension/analysis.lux (renamed from stdlib/source/lux/lang/compiler/extension/analysis.lux) | 0 | ||||
-rw-r--r-- | stdlib/source/lux/language/compiler/extension/analysis/common.lux (renamed from stdlib/source/lux/lang/compiler/extension/analysis/common.lux) | 20 | ||||
-rw-r--r-- | stdlib/source/lux/language/compiler/extension/analysis/host.jvm.lux (renamed from stdlib/source/lux/lang/compiler/extension/analysis/host.jvm.lux) | 200 | ||||
-rw-r--r-- | stdlib/source/lux/language/compiler/extension/bundle.lux (renamed from stdlib/source/lux/lang/compiler/extension/bundle.lux) | 0 | ||||
-rw-r--r-- | stdlib/source/lux/language/compiler/extension/synthesis.lux (renamed from stdlib/source/lux/lang/compiler/extension/synthesis.lux) | 0 | ||||
-rw-r--r-- | stdlib/source/lux/language/compiler/extension/translation.lux (renamed from stdlib/source/lux/lang/compiler/extension/translation.lux) | 0 |
7 files changed, 110 insertions, 110 deletions
diff --git a/stdlib/source/lux/lang/compiler/extension.lux b/stdlib/source/lux/language/compiler/extension.lux index e23e9b511..e23e9b511 100644 --- a/stdlib/source/lux/lang/compiler/extension.lux +++ b/stdlib/source/lux/language/compiler/extension.lux diff --git a/stdlib/source/lux/lang/compiler/extension/analysis.lux b/stdlib/source/lux/language/compiler/extension/analysis.lux index 9f48c79b4..9f48c79b4 100644 --- a/stdlib/source/lux/lang/compiler/extension/analysis.lux +++ b/stdlib/source/lux/language/compiler/extension/analysis.lux diff --git a/stdlib/source/lux/lang/compiler/extension/analysis/common.lux b/stdlib/source/lux/language/compiler/extension/analysis/common.lux index 62a01cee7..a0525cf12 100644 --- a/stdlib/source/lux/lang/compiler/extension/analysis/common.lux +++ b/stdlib/source/lux/language/compiler/extension/analysis/common.lux @@ -9,8 +9,8 @@ (collection [list "list/" Functor<List>] [array] ["dict" dictionary #+ Dictionary])) - [lang] - (lang (type ["tc" check])) + [language] + (language (type ["tc" check])) [io #+ IO]) [////] (//// [analysis #+ Analysis] @@ -38,7 +38,7 @@ (analyse argC))) (list.zip2 inputsT+ args))] (wrap (#///.Extension extension argsA))) - (lang.throw ///bundle.incorrect-arity [extension num-expected num-actual])))))) + (language.throw ///bundle.incorrect-arity [extension num-expected num-actual])))))) (def: #export (nullary valueT extension) (-> Type Text ..Handler) @@ -81,18 +81,18 @@ (wrap (#///.Extension extension (list opA)))) _ - (lang.throw ///bundle.incorrect-arity [extension +1 (list.size args)])))) + (language.throw ///bundle.incorrect-arity [extension +1 (list.size args)])))) (def: (lux//in-module extension) (-> Text ..Handler) (function (_ analyse argsC+) (case argsC+ (^ (list [_ (#.Text module-name)] exprC)) - (lang.with-current-module module-name + (language.with-current-module module-name (analyse exprC)) _ - (lang.throw ///bundle.invalid-syntax [extension])))) + (language.throw ///bundle.invalid-syntax [extension])))) ## (do-template [<name> <type>] ## [(def: (<name> extension) @@ -107,7 +107,7 @@ ## (analyse valueC))) ## _ -## (lang.throw ///bundle.incorrect-arity [extension +2 (list.size args)]))))] +## (language.throw ///bundle.incorrect-arity [extension +2 (list.size args)]))))] ## [lux//check (:coerce Type actualT)] ## [lux//coerce Any] @@ -125,7 +125,7 @@ (wrap valueA)) _ - (lang.throw ///bundle.incorrect-arity [extension +1 (list.size args)])))) + (language.throw ///bundle.incorrect-arity [extension +1 (list.size args)])))) (def: bundle/lux ///.Bundle @@ -280,7 +280,7 @@ (wrap (#///.Extension extension (list initA)))) _ - (lang.throw ///bundle.incorrect-arity [extension +1 (list.size args)])))) + (language.throw ///bundle.incorrect-arity [extension +1 (list.size args)])))) (def: (atom-read extension) (-> Text ..Handler) @@ -320,7 +320,7 @@ (wrap (#///.Extension extension (list initA)))) _ - (lang.throw ///bundle.incorrect-arity [extension +1 (list.size args)])))) + (language.throw ///bundle.incorrect-arity [extension +1 (list.size args)])))) (def: (box//read extension) (-> Text ..Handler) diff --git a/stdlib/source/lux/lang/compiler/extension/analysis/host.jvm.lux b/stdlib/source/lux/language/compiler/extension/analysis/host.jvm.lux index 265836e66..c11a6d5f4 100644 --- a/stdlib/source/lux/lang/compiler/extension/analysis/host.jvm.lux +++ b/stdlib/source/lux/language/compiler/extension/analysis/host.jvm.lux @@ -16,9 +16,9 @@ [macro "macro/" Monad<Meta>] (macro [code] ["s" syntax]) - [lang] - (lang [type] - (type ["tc" check])) + [language] + (language [type] + (type ["tc" check])) [host]) ["/" //common] (//// [".L" analysis #+ Analysis] @@ -222,7 +222,7 @@ (wrap (#analysisL.Extension proc (list arrayA)))) _ - (lang.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) (def: (array//new proc) (-> Text ///.Analysis) @@ -243,7 +243,7 @@ (recur outputT level) #.None - (lang.throw non-array expectedT)) + (language.throw non-array expectedT)) (^ (#.Primitive "#Array" (list elemT))) (recur elemT (inc level)) @@ -252,16 +252,16 @@ (wrap [level class]) _ - (lang.throw non-array expectedT)))) + (language.throw non-array expectedT)))) _ (if (n/> +0 level) (wrap []) - (lang.throw non-array expectedT))] + (language.throw non-array expectedT))] (wrap (#analysisL.Extension proc (list (analysisL.nat (dec level)) (analysisL.text elem-class) lengthA)))) _ - (lang.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) (def: (check-jvm objectT) (-> Type (Meta Text)) @@ -287,17 +287,17 @@ (check-jvm outputT) #.None - (lang.throw non-object objectT)) + (language.throw non-object objectT)) _ - (lang.throw non-object objectT))) + (language.throw non-object objectT))) (def: (check-object objectT) (-> Type (Meta Text)) (do macro.Monad<Meta> [name (check-jvm objectT)] (if (dict.contains? name boxes) - (lang.throw primitives-are-not-objects name) + (language.throw primitives-are-not-objects name) (macro/wrap name)))) (def: (box-array-element-type elemT) @@ -311,11 +311,11 @@ (#.Primitive name _) (if (dict.contains? name boxes) - (lang.throw primitives-cannot-have-type-parameters name) + (language.throw primitives-cannot-have-type-parameters name) (macro/wrap [elemT name])) _ - (lang.throw invalid-type-for-array-element (%type elemT)))) + (language.throw invalid-type-for-array-element (%type elemT)))) (def: (array//read proc) (-> Text ///.Analysis) @@ -335,7 +335,7 @@ (wrap (#analysisL.Extension proc (list (analysisL.text elem-class) idxA arrayA)))) _ - (lang.throw /.incorrect-extension-arity [proc +2 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +2 (list.size args)])))) (def: (array//write proc) (-> Text ///.Analysis) @@ -357,7 +357,7 @@ (wrap (#analysisL.Extension proc (list (analysisL.text elem-class) idxA valueA arrayA)))) _ - (lang.throw /.incorrect-extension-arity [proc +3 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +3 (list.size args)])))) (def: array-procs /.Bundle @@ -380,7 +380,7 @@ (wrap (#analysisL.Extension proc (list)))) _ - (lang.throw /.incorrect-extension-arity [proc +0 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +0 (list.size args)])))) (def: (object//null? proc) (-> Text ///.Analysis) @@ -395,7 +395,7 @@ (wrap (#analysisL.Extension proc (list objectA)))) _ - (lang.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) (def: (object//synchronized proc) (-> Text ///.Analysis) @@ -410,7 +410,7 @@ (wrap (#analysisL.Extension proc (list monitorA exprA)))) _ - (lang.throw /.incorrect-extension-arity [proc +2 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +2 (list.size args)])))) (host.import: java/lang/Object (equals [Object] boolean)) @@ -480,7 +480,7 @@ (wrap class) (#e.Error error) - (lang.throw unknown-class name)))) + (language.throw unknown-class name)))) (def: (sub-class? super sub) (-> Text Text (Meta Bool)) @@ -503,11 +503,11 @@ _ (: (Meta Any) (if ? (wrap []) - (lang.throw non-throwable exception-class)))] + (language.throw non-throwable exception-class)))] (wrap (#analysisL.Extension proc (list exceptionA)))) _ - (lang.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) (def: (object//class proc) (-> Text ///.Analysis) @@ -522,10 +522,10 @@ (wrap (#analysisL.Extension proc (list (analysisL.text class))))) _ - (lang.throw /.invalid-syntax [proc args])) + (language.throw /.invalid-syntax [proc args])) _ - (lang.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +1 (list.size args)])))) (def: (object//instance? proc) (-> Text ///.Analysis) @@ -542,13 +542,13 @@ ? (sub-class? class object-class)] (if ? (wrap (#analysisL.Extension proc (list (analysisL.text class)))) - (lang.throw cannot-possibly-be-an-instance (format object-class " !<= " class)))) + (language.throw cannot-possibly-be-an-instance (format object-class " !<= " class)))) _ - (lang.throw /.invalid-syntax [proc args])) + (language.throw /.invalid-syntax [proc args])) _ - (lang.throw /.incorrect-extension-arity [proc +2 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +2 (list.size args)])))) (def: (java-type-to-class type) (-> java/lang/reflect/Type (Meta Text)) @@ -559,7 +559,7 @@ (java-type-to-class (ParameterizedType::getRawType [] (:coerce ParameterizedType type))) ## else - (lang.throw cannot-convert-to-a-class (jvm-type-name type)))) + (language.throw cannot-convert-to-a-class (jvm-type-name type)))) (type: Mappings (Dictionary Text Type)) @@ -575,7 +575,7 @@ (macro/wrap var-type) #.None - (lang.throw unknown-type-var var-name))) + (language.throw unknown-type-var var-name))) (host.instance? WildcardType java-type) (let [java-type (:coerce WildcardType java-type)] @@ -612,7 +612,7 @@ (monad.map @ (java-type-to-lux-type mappings)))] (macro/wrap (#.Primitive (Class::getName [] (:coerce (Class Object) raw)) paramsT))) - (lang.throw jvm-type-is-not-a-class raw))) + (language.throw jvm-type-is-not-a-class raw))) (host.instance? GenericArrayType java-type) (do macro.Monad<Meta> @@ -622,7 +622,7 @@ (wrap (#.Primitive "#Array" (list innerT)))) ## else - (lang.throw cannot-convert-to-a-lux-type (jvm-type-name java-type)))) + (language.throw cannot-convert-to-a-lux-type (jvm-type-name java-type)))) (def: (correspond-type-params class type) (-> (Class Object) Type (Meta Mappings)) @@ -633,16 +633,16 @@ num-class-params (list.size class-params) num-type-params (list.size params)] (cond (not (text/= class-name name)) - (lang.throw cannot-correspond-type-with-a-class - (format "Class = " class-name "\n" - "Type = " (%type type))) + (language.throw cannot-correspond-type-with-a-class + (format "Class = " class-name "\n" + "Type = " (%type type))) (not (n/= num-class-params num-type-params)) - (lang.throw type-parameter-mismatch - (format "Expected: " (%i (.int num-class-params)) "\n" - " Actual: " (%i (.int num-type-params)) "\n" - " Class: " class-name "\n" - " Type: " (%type type))) + (language.throw type-parameter-mismatch + (format "Expected: " (%i (.int num-class-params)) "\n" + " Actual: " (%i (.int num-type-params)) "\n" + " Class: " class-name "\n" + " Type: " (%type type))) ## else (macro/wrap (|> params @@ -651,7 +651,7 @@ )) _ - (lang.throw non-jvm-type type))) + (language.throw non-jvm-type type))) (def: (object//cast proc) (-> Text ///.Analysis) @@ -683,10 +683,10 @@ _ (do @ - [_ (lang.assert primitives-are-not-objects from-name - (not (dict.contains? from-name boxes))) - _ (lang.assert primitives-are-not-objects to-name - (not (dict.contains? to-name boxes))) + [_ (language.assert primitives-are-not-objects from-name + (not (dict.contains? from-name boxes))) + _ (language.assert primitives-are-not-objects to-name + (not (dict.contains? to-name boxes))) to-class (load-class to-name)] (loop [[current-name currentT] [from-name valueT]] (if (text/= to-name current-name) @@ -695,10 +695,10 @@ (wrap true)) (do @ [current-class (load-class current-name) - _ (lang.assert cannot-cast (format "From class/primitive: " current-name "\n" - " To class/primitive: " to-name "\n" - " For value: " (%code valueC) "\n") - (Class::isAssignableFrom [current-class] to-class)) + _ (language.assert cannot-cast (format "From class/primitive: " current-name "\n" + " To class/primitive: " to-name "\n" + " For value: " (%code valueC) "\n") + (Class::isAssignableFrom [current-class] to-class)) candiate-parents (monad.map @ (function (_ java-type) (do @ @@ -717,20 +717,20 @@ (recur [next-name nextT])) #.Nil - (lang.throw cannot-cast (format "From class/primitive: " from-name "\n" - " To class/primitive: " to-name "\n" - " For value: " (%code valueC) "\n"))) + (language.throw cannot-cast (format "From class/primitive: " from-name "\n" + " To class/primitive: " to-name "\n" + " For value: " (%code valueC) "\n"))) ))))))] (if can-cast? (wrap (#analysisL.Extension proc (list (analysisL.text from-name) (analysisL.text to-name) valueA))) - (lang.throw cannot-cast (format "From class/primitive: " from-name "\n" - " To class/primitive: " to-name "\n" - " For value: " (%code valueC) "\n")))) + (language.throw cannot-cast (format "From class/primitive: " from-name "\n" + " To class/primitive: " to-name "\n" + " For value: " (%code valueC) "\n")))) _ - (lang.throw /.invalid-syntax [proc args])))) + (language.throw /.invalid-syntax [proc args])))) (def: object-procs /.Bundle @@ -754,13 +754,13 @@ (let [owner (Field::getDeclaringClass [] field)] (if (is? owner class) (wrap [class field]) - (lang.throw mistaken-field-owner - (format " Field: " field-name "\n" - " Owner Class: " (Class::getName [] owner) "\n" - "Target Class: " class-name "\n")))) + (language.throw mistaken-field-owner + (format " Field: " field-name "\n" + " Owner Class: " (Class::getName [] owner) "\n" + "Target Class: " class-name "\n")))) (#e.Error _) - (lang.throw unknown-field (format class-name "#" field-name))))) + (language.throw unknown-field (format class-name "#" field-name))))) (def: (static-field class-name field-name) (-> Text Text (Meta [Type Bool])) @@ -772,7 +772,7 @@ (do @ [fieldT (java-type-to-lux-type fresh-mappings fieldJT)] (wrap [fieldT (Modifier::isFinal [modifiers])]))) - (lang.throw not-a-static-field (format class-name "#" field-name))))) + (language.throw not-a-static-field (format class-name "#" field-name))))) (def: (virtual-field class-name field-name objectT) (-> Text Text Type (Meta [Type Bool])) @@ -792,20 +792,20 @@ (do @ [#let [num-params (list.size _class-params) num-vars (list.size var-names)] - _ (lang.assert type-parameter-mismatch - (format "Expected: " (%i (.int num-params)) "\n" - " Actual: " (%i (.int num-vars)) "\n" - " Class: " _class-name "\n" - " Type: " (%type objectT)) - (n/= num-params num-vars))] + _ (language.assert type-parameter-mismatch + (format "Expected: " (%i (.int num-params)) "\n" + " Actual: " (%i (.int num-vars)) "\n" + " Class: " _class-name "\n" + " Type: " (%type objectT)) + (n/= num-params num-vars))] (wrap (|> (list.zip2 var-names _class-params) (dict.from-list text.Hash<Text>)))) _ - (lang.throw non-object objectT))) + (language.throw non-object objectT))) fieldT (java-type-to-lux-type mappings fieldJT)] (wrap [fieldT (Modifier::isFinal [modifiers])])) - (lang.throw not-a-virtual-field (format class-name "#" field-name))))) + (language.throw not-a-virtual-field (format class-name "#" field-name))))) (def: (static//get proc) (-> Text ///.Analysis) @@ -819,10 +819,10 @@ (wrap (#analysisL.Extension proc (list (analysisL.text class) (analysisL.text field))))) _ - (lang.throw /.invalid-syntax [proc args])) + (language.throw /.invalid-syntax [proc args])) _ - (lang.throw /.incorrect-extension-arity [proc +2 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +2 (list.size args)])))) (def: (static//put proc) (-> Text ///.Analysis) @@ -834,17 +834,17 @@ (do macro.Monad<Meta> [_ (typeA.infer Any) [fieldT final?] (static-field class field) - _ (lang.assert cannot-set-a-final-field (format class "#" field) - (not final?)) + _ (language.assert cannot-set-a-final-field (format class "#" field) + (not final?)) valueA (typeA.with-type fieldT (analyse valueC))] (wrap (#analysisL.Extension proc (list (analysisL.text class) (analysisL.text field) valueA)))) _ - (lang.throw /.invalid-syntax [proc args])) + (language.throw /.invalid-syntax [proc args])) _ - (lang.throw /.incorrect-extension-arity [proc +3 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +3 (list.size args)])))) (def: (virtual//get proc) (-> Text ///.Analysis) @@ -860,10 +860,10 @@ (wrap (#analysisL.Extension proc (list (analysisL.text class) (analysisL.text field) objectA)))) _ - (lang.throw /.invalid-syntax [proc args])) + (language.throw /.invalid-syntax [proc args])) _ - (lang.throw /.incorrect-extension-arity [proc +3 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +3 (list.size args)])))) (def: (virtual//put proc) (-> Text ///.Analysis) @@ -877,17 +877,17 @@ (analyse objectC)) _ (typeA.infer objectT) [fieldT final?] (virtual-field class field objectT) - _ (lang.assert cannot-set-a-final-field (format class "#" field) - (not final?)) + _ (language.assert cannot-set-a-final-field (format class "#" field) + (not final?)) valueA (typeA.with-type fieldT (analyse valueC))] (wrap (#analysisL.Extension proc (list (analysisL.text class) (analysisL.text field) valueA objectA)))) _ - (lang.throw /.invalid-syntax [proc args])) + (language.throw /.invalid-syntax [proc args])) _ - (lang.throw /.incorrect-extension-arity [proc +4 (list.size args)])))) + (language.throw /.incorrect-extension-arity [proc +4 (list.size args)])))) (def: (java-type-to-parameter type) (-> java/lang/reflect/Type (Meta Text)) @@ -907,7 +907,7 @@ (wrap (format componentP "[]"))) ## else - (lang.throw cannot-convert-to-a-parameter (jvm-type-name type)))) + (language.throw cannot-convert-to-a-parameter (jvm-type-name type)))) (type: Method-style #Static @@ -1056,17 +1056,17 @@ #Fail)))))))] (case (list.search-all pass! candidates) #.Nil - (lang.throw no-candidates [class-name method-name - (|> candidates - (list.search-all hint!) - (list/map (method-to-type method-style)))]) + (language.throw no-candidates [class-name method-name + (|> candidates + (list.search-all hint!) + (list/map (method-to-type method-style)))]) (#.Cons method #.Nil) (method-to-type method-style method) candidates - (lang.throw too-many-candidates [class-name method-name - (list/map (method-to-type method-style) candidates)])))) + (language.throw too-many-candidates [class-name method-name + (list/map (method-to-type method-style) candidates)])))) (def: (constructor-to-type constructor) (-> (Constructor Object) (Meta [Type (List Type)])) @@ -1118,17 +1118,17 @@ (wrap [passes? constructor])))))] (case (list.search-all pass! candidates) #.Nil - (lang.throw no-candidates [class-name ..constructor-method - (|> candidates - (list.search-all hint!) - (list/map constructor-to-type))]) + (language.throw no-candidates [class-name ..constructor-method + (|> candidates + (list.search-all hint!) + (list/map constructor-to-type))]) (#.Cons constructor #.Nil) (constructor-to-type constructor) candidates - (lang.throw too-many-candidates [class-name ..constructor-method - (list/map constructor-to-type candidates)])))) + (language.throw too-many-candidates [class-name ..constructor-method + (list/map constructor-to-type candidates)])))) (def: (decorate-inputs typesT inputsA) (-> (List Text) (List Analysis) (List Analysis)) @@ -1152,7 +1152,7 @@ (analysisL.text outputJC) (decorate-inputs argsT argsA))))) _ - (lang.throw /.invalid-syntax [proc args])))) + (language.throw /.invalid-syntax [proc args])))) (def: (invoke//virtual proc) (-> Text ///.Analysis) @@ -1175,7 +1175,7 @@ (analysisL.text outputJC) objectA (decorate-inputs argsT argsA))))) _ - (lang.throw /.invalid-syntax [proc args])))) + (language.throw /.invalid-syntax [proc args])))) (def: (invoke//special proc) (-> Text ///.Analysis) @@ -1192,7 +1192,7 @@ (analysisL.text outputJC) (decorate-inputs argsT argsA))))) _ - (lang.throw /.invalid-syntax [proc args])))) + (language.throw /.invalid-syntax [proc args])))) (def: (invoke//interface proc) (-> Text ///.Analysis) @@ -1203,8 +1203,8 @@ (do macro.Monad<Meta> [#let [argsT (list/map product.left argsTC)] class (load-class class-name) - _ (lang.assert non-interface class-name - (Modifier::isInterface [(Class::getModifiers [] class)])) + _ (language.assert non-interface class-name + (Modifier::isInterface [(Class::getModifiers [] class)])) [methodT exceptionsT] (method-candidate class-name method #Interface argsT) [outputT argsA] (inferenceA.general analyse methodT (list& objectC (list/map product.right argsTC))) outputJC (check-jvm outputT)] @@ -1213,7 +1213,7 @@ (decorate-inputs argsT argsA))))) _ - (lang.throw /.invalid-syntax [proc args])))) + (language.throw /.invalid-syntax [proc args])))) (def: (invoke//constructor proc) (-> Text ///.Analysis) @@ -1228,7 +1228,7 @@ (wrap (#analysisL.Extension proc (list& (analysisL.text class) (decorate-inputs argsT argsA))))) _ - (lang.throw /.invalid-syntax [proc args])))) + (language.throw /.invalid-syntax [proc args])))) (def: member-procs /.Bundle diff --git a/stdlib/source/lux/lang/compiler/extension/bundle.lux b/stdlib/source/lux/language/compiler/extension/bundle.lux index 4e011d2ca..4e011d2ca 100644 --- a/stdlib/source/lux/lang/compiler/extension/bundle.lux +++ b/stdlib/source/lux/language/compiler/extension/bundle.lux diff --git a/stdlib/source/lux/lang/compiler/extension/synthesis.lux b/stdlib/source/lux/language/compiler/extension/synthesis.lux index 48073d012..48073d012 100644 --- a/stdlib/source/lux/lang/compiler/extension/synthesis.lux +++ b/stdlib/source/lux/language/compiler/extension/synthesis.lux diff --git a/stdlib/source/lux/lang/compiler/extension/translation.lux b/stdlib/source/lux/language/compiler/extension/translation.lux index ae05fd61c..ae05fd61c 100644 --- a/stdlib/source/lux/lang/compiler/extension/translation.lux +++ b/stdlib/source/lux/language/compiler/extension/translation.lux |