aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
authorEduardo Julian2022-02-06 03:15:39 -0400
committerEduardo Julian2022-02-06 03:15:39 -0400
commit290de8ebcb7edc92877f2ccc333171214e5eae23 (patch)
tree7307b79865b242a057d35a3b654d8906a8b8c97e /stdlib/source/library
parent54bb56a07e6d8f1e76bd447436fb721a74f09f66 (diff)
Finishing the meta-compiler [Part 1]
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux.lux13
-rw-r--r--stdlib/source/library/lux/control/parser/code.lux121
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux51
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux7
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux (renamed from stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux)164
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux31
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux36
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux5
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux11
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cli.lux126
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux8
14 files changed, 308 insertions, 281 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 4f14a2ada..e6a3e5e6f 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -427,13 +427,15 @@
... {#Captured Nat})
("lux def type tagged" Ref
{#Named [..prelude_module "Ref"]
- {#Sum ... Local
+ {#Sum
+ ... Local
Nat
... Captured
Nat}}
{"#Local" "#Captured"}
.public)
+... TODO: Get rid of both #name & #inner
... (type: .public Scope
... (Record
... [#name (List Text)
@@ -442,11 +444,14 @@
... #captured (Bindings Text [Type Ref])]))
("lux def type tagged" Scope
{#Named [..prelude_module "Scope"]
- {#Product ... name
+ {#Product
+ ... name
{#Apply Text List}
- {#Product ... inner
+ {#Product
+ ... inner
Nat
- {#Product ... locals
+ {#Product
+ ... locals
{#Apply {#Product Type Nat} {#Apply Text Bindings}}
... captured
{#Apply {#Product Type Ref} {#Apply Text Bindings}}}}}}
diff --git a/stdlib/source/library/lux/control/parser/code.lux b/stdlib/source/library/lux/control/parser/code.lux
index f17a1551d..910d7f449 100644
--- a/stdlib/source/library/lux/control/parser/code.lux
+++ b/stdlib/source/library/lux/control/parser/code.lux
@@ -1,26 +1,26 @@
(.using
- [library
- [lux {"-" nat int rev local not symbol}
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" try {"+" Try}]]
- [data
- ["[0]" bit]
- ["[0]" text ("[1]#[0]" monoid)]
- [collection
- ["[0]" list ("[1]#[0]" functor)]]]
- [macro
- ["[0]" code ("[1]#[0]" equivalence)]]
- [math
- [number
- ["[0]" nat]
- ["[0]" int]
- ["[0]" rev]
- ["[0]" frac]]]
- [meta
- ["[0]" symbol]]]]
- ["[0]" //])
+ [library
+ [lux {"-" nat int rev local not symbol}
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" try {"+" Try}]]
+ [data
+ ["[0]" bit]
+ ["[0]" text ("[1]#[0]" monoid)]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]]]
+ [macro
+ ["[0]" code ("[1]#[0]" equivalence)]]
+ [math
+ [number
+ ["[0]" nat]
+ ["[0]" int]
+ ["[0]" rev]
+ ["[0]" frac]]]
+ [meta
+ ["[0]" symbol]]]]
+ ["[0]" //])
(def: (un_paired pairs)
(All (_ a) (-> (List [a a]) (List a)))
@@ -103,32 +103,57 @@
_
{try.#Failure "There are no tokens to parse!"})))
-(template [<query> <check> <tag> <eq> <desc>]
- [(with_expansions [<failure> (as_is {try.#Failure ($_ text#composite "Cannot parse " <desc> (remaining_inputs tokens))})]
- (def: .public <query>
- (Parser Text)
- (function (_ tokens)
- (case tokens
- {.#Item [[_ {<tag> ["" x]}] tokens']}
- {try.#Success [tokens' x]}
-
- _
- <failure>)))
-
- (def: .public (<check> expected)
- (-> Text (Parser Any))
- (function (_ tokens)
- (case tokens
- {.#Item [[_ {<tag> ["" actual]}] tokens']}
- (if (# <eq> = expected actual)
- {try.#Success [tokens' []]}
- <failure>)
-
- _
- <failure>))))]
-
- [local_symbol local_symbol! .#Symbol text.equivalence "local symbol"]
- )
+(with_expansions [<failure> (as_is {try.#Failure ($_ text#composite "Cannot parse local symbol" (remaining_inputs tokens))})]
+ (def: .public local_symbol
+ (Parser Text)
+ (function (_ tokens)
+ (case tokens
+ {.#Item [[_ {.#Symbol ["" x]}] tokens']}
+ {try.#Success [tokens' x]}
+
+ _
+ <failure>)))
+
+ (def: .public (local_symbol! expected)
+ (-> Text (Parser Any))
+ (function (_ tokens)
+ (case tokens
+ {.#Item [[_ {.#Symbol ["" actual]}] tokens']}
+ (if (# text.equivalence = expected actual)
+ {try.#Success [tokens' []]}
+ <failure>)
+
+ _
+ <failure>))))
+
+(with_expansions [<failure> (as_is {try.#Failure ($_ text#composite "Cannot parse local symbol" (remaining_inputs tokens))})]
+ (def: .public global_symbol
+ (Parser Symbol)
+ (function (_ tokens)
+ (case tokens
+ {.#Item [[_ {.#Symbol ["" short]}] tokens']}
+ <failure>
+
+ {.#Item [[_ {.#Symbol it}] tokens']}
+ {try.#Success [tokens' it]}
+
+ _
+ <failure>)))
+
+ (def: .public (global_symbol! expected)
+ (-> Symbol (Parser Any))
+ (function (_ tokens)
+ (case tokens
+ {.#Item [[_ {.#Symbol ["" actual]}] tokens']}
+ <failure>
+
+ {.#Item [[_ {.#Symbol it}] tokens']}
+ (if (# symbol.equivalence = expected it)
+ {try.#Success [tokens' []]}
+ <failure>)
+
+ _
+ <failure>))))
(template [<name> <tag> <desc>]
[(def: .public (<name> p)
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index dc9ff4533..02b35d0e7 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -720,7 +720,7 @@
(def: .public (compile phase_wrapper import static expander platform compilation context)
(All (_ <type_vars>)
(-> ///phase.Wrapper Import Static Expander <Platform> Compilation <Context> <Return>))
- (let [[sources host_dependencies libraries target module] compilation
+ (let [[host_dependencies libraries compilers sources target module] compilation
compiler (|> (..compiler phase_wrapper expander platform)
(serial_compiler import static platform sources)
(..parallel context))]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
index 643a1b428..116d84299 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
@@ -259,49 +259,6 @@
{try.#Failure error}
{try.#Failure error}))))
-(def: fresh_bindings
- (All (_ k v) (Bindings k v))
- [.#counter 0
- .#mappings (list)])
-
-(def: fresh_scope
- Scope
- [.#name (list)
- .#inner 0
- .#locals fresh_bindings
- .#captured fresh_bindings])
-
-(def: .public (with_scope action)
- (All (_ a) (-> (Operation a) (Operation [Scope a])))
- (function (_ [bundle state])
- (.case (action [bundle (revised@ .#scopes (|>> {.#Item fresh_scope}) state)])
- {try.#Success [[bundle' state'] output]}
- (.case (value@ .#scopes state')
- {.#Item head tail}
- {try.#Success [[bundle' (with@ .#scopes tail state')]
- [head output]]}
-
- {.#End}
- {try.#Failure "Impossible error: Drained scopes!"})
-
- {try.#Failure error}
- {try.#Failure error})))
-
-(def: scope_reset
- (List Scope)
- (list fresh_scope))
-
-(def: .public (without_scopes action)
- (All (_ a) (-> (Operation a) (Operation a)))
- (function (_ [bundle state])
- (.case (action [bundle (with@ .#scopes ..scope_reset state)])
- {try.#Success [[bundle' state'] output]}
- {try.#Success [[bundle' (with@ .#scopes (value@ .#scopes state) state')]
- output]}
-
- {try.#Failure error}
- {try.#Failure error})))
-
(def: .public (with_current_module name)
(All (_ a) (-> Text (Operation a) (Operation a)))
(extension.localized (value@ .#current_module)
@@ -347,12 +304,12 @@
(function (_ bundle,state)
(.case (exception.with exception message
(action bundle,state))
- {try.#Success output}
- {try.#Success output}
-
{try.#Failure error}
(let [[bundle state] bundle,state]
- {try.#Failure (locate_error (value@ .#location state) error)}))))
+ {try.#Failure (locate_error (value@ .#location state) error)})
+
+ output
+ output)))
(def: .public (install state)
(-> .Lux (Operation Any))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux
index 0a7138dca..d27d54fe7 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux
@@ -14,8 +14,9 @@
["n" nat]
["[0]" i64]]]]]
["[0]" // {"+" Operation}
- ["[0]" type]
[macro {"+" Expander}]
+ ["[1][0]" type]
+ ["[1][0]" scope]
[//
[phase
["[0]P" extension]
@@ -44,8 +45,8 @@
(do phase.monad
[count (extensionP.lifted
meta.seed)
- exprA (<| (type.expecting type)
- //.without_scopes
+ exprA (<| (//type.expecting type)
+ //scope.reset
(analyze archive exprC))
module (extensionP.lifted
meta.current_module_name)]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
index 0d24cd44d..838c2c362 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
@@ -1,27 +1,27 @@
(.using
- [library
- [lux {"-" local}
- [abstract
- monad]
- [control
- ["[0]" maybe ("[1]#[0]" monad)]
- ["[0]" try]
- ["[0]" exception {"+" exception:}]]
- [data
- ["[0]" text ("[1]#[0]" equivalence)]
- ["[0]" product]
- [collection
- ["[0]" list ("[1]#[0]" functor mix monoid)]
- [dictionary
- ["[0]" plist]]]]]]
- ["[0]" /// "_"
- ["[1][0]" extension]
- [//
- ["/" analysis {"+" Operation Phase}]
- [///
- [reference
- ["[0]" variable {"+" Register Variable}]]
- ["[1]" phase]]]])
+ [library
+ [lux {"-" local}
+ [abstract
+ monad]
+ [control
+ ["[0]" maybe ("[1]#[0]" monad)]
+ ["[0]" try]
+ ["[0]" exception {"+" exception:}]]
+ [data
+ ["[0]" text ("[1]#[0]" equivalence)]
+ ["[0]" product]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix monoid)]
+ [dictionary
+ ["[0]" plist]]]]]]
+ ["/" // {"+" Environment Operation Phase}
+ [//
+ [phase
+ ["[0]" extension]]
+ [///
+ ["[0]" phase]
+ [reference
+ ["[0]" variable {"+" Register Variable}]]]]])
(type: Local
(Bindings Text [Type Register]))
@@ -78,7 +78,7 @@
(def: .public (find name)
(-> Text (Operation (Maybe [Type Variable])))
- (///extension.lifted
+ (extension.lifted
(function (_ state)
(let [[inner outer] (|> state
(value@ .#scopes)
@@ -106,8 +106,8 @@
{.#Some [ref_type ref]}]})
)))))
-(exception: .public cannot_create_local_binding_without_a_scope)
-(exception: .public invalid_scope_alteration)
+(exception: .public no_scope)
+(exception: .public drained)
(def: .public (with_local [name type] action)
(All (_ a) (-> [Text Type] (Operation a) (Operation a)))
@@ -121,8 +121,8 @@
(|>> (revised@ .#counter ++)
(revised@ .#mappings (plist.has name [type new_var_id]))))
head)]
- (case (///.result' [bundle (with@ .#scopes {.#Item new_head tail} state)]
- action)
+ (case (phase.result' [bundle (with@ .#scopes {.#Item new_head tail} state)]
+ action)
{try.#Success [[bundle' state'] output]}
(case (value@ .#scopes state')
{.#Item head' tail'}
@@ -132,77 +132,63 @@
output]})
_
- (exception.except ..invalid_scope_alteration []))
+ (exception.except ..drained []))
{try.#Failure error}
{try.#Failure error}))
_
- (exception.except ..cannot_create_local_binding_without_a_scope []))
- ))
-
-(template [<name> <val_type>]
- [(def: <name>
- (Bindings Text [Type <val_type>])
- [.#counter 0
- .#mappings (list)])]
-
- [init_locals Nat]
- [init_captured Variable]
- )
-
-(def: (scope parent_name child_name)
- (-> (List Text) Text Scope)
- [.#name (list& child_name parent_name)
- .#inner 0
- .#locals init_locals
- .#captured init_captured])
-
-(def: .public (with_scope name action)
- (All (_ a) (-> Text (Operation a) (Operation a)))
+ (exception.except ..no_scope []))))
+
+(def: empty
+ Scope
+ (let [bindings (: Bindings
+ [.#counter 0
+ .#mappings (list)])]
+ [.#name (list)
+ .#inner 0
+ .#locals bindings
+ .#captured bindings]))
+
+(def: .public (reset action)
+ (All (_ a) (-> (Operation a) (Operation a)))
(function (_ [bundle state])
- (let [parent_name (case (value@ .#scopes state)
- {.#End}
- (list)
-
- {.#Item top _}
- (value@ .#name top))]
- (case (action [bundle (revised@ .#scopes
- (|>> {.#Item (scope parent_name name)})
- state)])
- {try.#Success [[bundle' state'] output]}
- {try.#Success [[bundle' (revised@ .#scopes
- (|>> list.tail (maybe.else (list)))
- state')]
- output]}
-
- {try.#Failure error}
- {try.#Failure error}))))
-
-(exception: .public cannot_get_next_reference_when_there_is_no_scope)
-
-(def: .public next_local
+ (case (action [bundle (with@ .#scopes (list ..empty) state)])
+ {try.#Success [[bundle' state'] output]}
+ {try.#Success [[bundle' (with@ .#scopes (value@ .#scopes state) state')]
+ output]}
+
+ failure
+ failure)))
+
+(def: .public (with action)
+ (All (_ a) (-> (Operation a) (Operation [Scope a])))
+ (function (_ [bundle state])
+ (case (action [bundle (revised@ .#scopes (|>> {.#Item ..empty}) state)])
+ {try.#Success [[bundle' state'] output]}
+ (case (value@ .#scopes state')
+ {.#Item head tail}
+ {try.#Success [[bundle' (with@ .#scopes tail state')]
+ [head output]]}
+
+ {.#End}
+ (exception.except ..drained []))
+
+ {try.#Failure error}
+ {try.#Failure error})))
+
+(def: .public next
(Operation Register)
- (///extension.lifted
+ (extension.lifted
(function (_ state)
(case (value@ .#scopes state)
{.#Item top _}
{try.#Success [state (value@ [.#locals .#counter] top)]}
{.#End}
- (exception.except ..cannot_get_next_reference_when_there_is_no_scope [])))))
-
-(def: (ref_variable ref)
- (-> Ref Variable)
- (case ref
- {.#Local register}
- {variable.#Local register}
-
- {.#Captured register}
- {variable.#Foreign register}))
-
-(def: .public (environment scope)
- (-> Scope (List Variable))
- (|> scope
- (value@ [.#captured .#mappings])
- (list#each (function (_ [_ [_ ref]]) (ref_variable ref)))))
+ (exception.except ..no_scope [])))))
+
+(def: .public environment
+ (-> Scope (Environment Variable))
+ (|>> (value@ [.#captured .#mappings])
+ (list#each (function (_ [_ [_ ref]]) ref))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
index 3eab189d4..e1b1a8c07 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
@@ -24,7 +24,6 @@
["[0]" / "_"
["[1][0]" coverage {"+" Coverage}]
["/[1]" // "_"
- ["[1][0]" scope]
["[1][0]" complex]
["/[1]" // "_"
["[1][0]" extension]
@@ -33,7 +32,8 @@
["[1][0]" simple]
["[1][0]" complex]
["[1][0]" pattern {"+" Pattern}]
- ["[1][0]" type]]
+ ["[1][0]" type]
+ ["[1][0]" scope]]
[///
["[1]" phase]]]]]])
@@ -225,9 +225,9 @@
[location {.#Symbol ["" name]}]
(/.with_location location
(do ///.monad
- [outputA (//scope.with_local [name inputT]
+ [outputA (/scope.with_local [name inputT]
next)
- idx //scope.next_local]
+ idx /scope.next]
(in [{/pattern.#Bind idx} outputA])))
(^template [<type> <input> <output>]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux
index 5a2018656..63c315954 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux
@@ -14,18 +14,17 @@
["[0]" list ("[1]#[0]" monoid monad)]]]
["[0]" type
["[0]" check]]]]
- ["[0]" // "_"
- ["[1][0]" scope]
- ["/[1]" // "_"
- ["[1][0]" extension]
- [//
- ["/" analysis {"+" Analysis Operation Phase}
- ["[1][0]" type]
- ["[1][0]" inference]]
- [///
- ["[1]" phase]
- [reference {"+"}
- [variable {"+"}]]]]]])
+ ["[0]" /// "_"
+ ["[1][0]" extension]
+ [//
+ ["/" analysis {"+" Analysis Operation Phase}
+ ["[1][0]" type]
+ ["[1][0]" inference]
+ ["[1][0]" scope]]
+ [///
+ ["[1]" phase]
+ [reference {"+"}
+ [variable {"+"}]]]]])
(exception: .public (cannot_analyse [expected Type
function Text
@@ -93,13 +92,13 @@
{.#Function inputT outputT}
(<| (# ! each (.function (_ [scope bodyA])
{/.#Function (list#each (|>> /.variable)
- (//scope.environment scope))
+ (/scope.environment scope))
bodyA}))
- /.with_scope
+ /scope.with
... Functions have access not only to their argument, but
... also to themselves, through a local variable.
- (//scope.with_local [function_name expectedT])
- (//scope.with_local [arg_name inputT])
+ (/scope.with_local [function_name expectedT])
+ (/scope.with_local [arg_name inputT])
(/type.expecting outputT)
(analyse archive body))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux
index 223f0c07f..8fdf78aa8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux
@@ -10,12 +10,12 @@
["[0]" text ("[1]#[0]" equivalence)
["%" format {"+" format}]]]]]
["[0]" // "_"
- ["[1][0]" scope]
["/[1]" // "_"
["[1][0]" extension]
[//
["/" analysis {"+" Analysis Operation}
- ["[1][0]" type]]
+ ["[1][0]" type]
+ ["[1][0]" scope]]
[///
["[1][0]" reference]
["[1]" phase]]]]])
@@ -84,7 +84,7 @@
(def: (variable var_name)
(-> Text (Operation (Maybe Analysis)))
(do [! ///.monad]
- [?var (//scope.find var_name)]
+ [?var (/scope.find var_name)]
(case ?var
{.#Some [actualT ref]}
(do !
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
index 4d6c7e712..21980f491 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -47,22 +47,20 @@
["[1][0]" lux {"+" custom}]
["/[1]" //
["[1][0]" bundle]
- ["/[1]" // "_"
- [analysis
+ ["//[1]" /// "_"
+ ["[1][0]" synthesis]
+ ["[1][0]" analysis {"+" Analysis Operation Phase Handler Bundle}
+ ["[1]/[0]" complex]
+ ["[1]/[0]" pattern]
+ ["[0]A" type]
+ ["[0]A" inference]
["[0]" scope]]
- ["/[1]" // "_"
- ["[1][0]" analysis {"+" Analysis Operation Phase Handler Bundle}
- ["[1]/[0]" complex]
- ["[1]/[0]" pattern]
- ["[0]A" type]
- ["[0]A" inference]]
- ["[1][0]" synthesis]
- [///
- ["[0]" phase ("[1]#[0]" monad)]
- [meta
- [archive {"+" Archive}
- [module
- [descriptor {"+" Module}]]]]]]]]])
+ [///
+ ["[0]" phase ("[1]#[0]" monad)]
+ [meta
+ [archive {"+" Archive}
+ [module
+ [descriptor {"+" Module}]]]]]]]])
(import: java/lang/ClassLoader)
@@ -1810,7 +1808,7 @@
list.reversed
(list#mix scope.with_local (analyse archive body))
(typeA.expecting .Any)
- /////analysis.with_scope)]
+ scope.with)]
(in (/////analysis.tuple (list (/////analysis.text ..constructor_tag)
(visibility_analysis visibility)
(/////analysis.bit strict_fp?)
@@ -1907,7 +1905,7 @@
list.reversed
(list#mix scope.with_local (analyse archive body))
(typeA.expecting returnT)
- /////analysis.with_scope)]
+ scope.with)]
(in (/////analysis.tuple (list (/////analysis.text ..virtual_tag)
(/////analysis.text method_name)
(visibility_analysis visibility)
@@ -1980,7 +1978,7 @@
list.reversed
(list#mix scope.with_local (analyse archive body))
(typeA.expecting returnT)
- /////analysis.with_scope)]
+ scope.with)]
(in (/////analysis.tuple (list (/////analysis.text ..static_tag)
(/////analysis.text method_name)
(visibility_analysis visibility)
@@ -2150,7 +2148,7 @@
list.reversed
(list#mix scope.with_local (analyse archive body))
(typeA.expecting returnT)
- /////analysis.with_scope)]
+ scope.with)]
(in (/////analysis.tuple (list (/////analysis.text ..overriden_tag)
(class_analysis parent_type)
(/////analysis.text method_name)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
index 1e3b1eabc..5641140a4 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
@@ -67,10 +67,9 @@
["[0]" generation]
["[0]" directive {"+" Handler Bundle}]
["[0]" analysis {"+" Analysis}
- ["[0]A" type]]
+ ["[0]A" type]
+ ["[0]A" scope]]
[phase
- [analysis
- ["[0]A" scope]]
[generation
[jvm
["[0]" runtime {"+" Anchor Definition Extender}]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
index 99bcd7e85..04006e52f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
@@ -37,7 +37,8 @@
[macro {"+" Expander}]
["[1]/[0]" evaluation]
["[0]A" type]
- ["[0]A" module]]
+ ["[0]A" module]
+ ["[0]" scope]]
["[1][0]" synthesis {"+" Synthesis}]
["[1][0]" generation]
["[1][0]" directive {"+" Import Requirements Phase Operation Handler Bundle}]
@@ -100,7 +101,7 @@
synthesize (value@ [/////directive.#synthesis /////directive.#phase] state)
generate (value@ [/////directive.#generation /////directive.#phase] state)]
[_ codeA] (<| /////directive.lifted_analysis
- /////analysis.with_scope
+ scope.with
typeA.fresh
(typeA.expecting type)
(analyse archive codeC))
@@ -138,7 +139,7 @@
synthesize (value@ [/////directive.#synthesis /////directive.#phase] state)
generate (value@ [/////directive.#generation /////directive.#phase] state)]
[_ code//type codeA] (/////directive.lifted_analysis
- (/////analysis.with_scope
+ (scope.with
(typeA.fresh
(case expected
{.#None}
@@ -191,7 +192,7 @@
synthesize (value@ [/////directive.#synthesis /////directive.#phase] state)
generate (value@ [/////directive.#generation /////directive.#phase] state)]
[_ codeA] (<| /////directive.lifted_analysis
- /////analysis.with_scope
+ scope.with
typeA.fresh
(typeA.expecting codeT)
(analyse archive codeC))
@@ -481,7 +482,7 @@
(Operation anchor expression directive Synthesis)))
(do phase.monad
[[_ programA] (<| /////directive.lifted_analysis
- /////analysis.with_scope
+ scope.with
typeA.fresh
(typeA.expecting (type (-> (List Text) (IO Any))))
(analyse archive programC))]
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli.lux b/stdlib/source/library/lux/tool/compiler/meta/cli.lux
index c4d5eb819..eee8d719c 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cli.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cli.lux
@@ -1,10 +1,24 @@
(.using
[library
[lux {"-" Module Source}
+ [abstract
+ [monad {"+" do}]
+ [equivalence {"+" Equivalence}]]
[control
[pipe {"+" case>}]
["<>" parser
- ["<[0]>" cli {"+" Parser}]]]
+ ["<[0]>" cli {"+" Parser}]
+ ["<[0]>" text]]]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]]]
+ [math
+ [number {"+" hex}]]
+ [meta
+ ["[0]" symbol]]
[tool
[compiler
[meta
@@ -14,15 +28,57 @@
[world
[file {"+" Path}]]]])
-(type: .public Source
- Path)
-
(type: .public Host_Dependency
Path)
(type: .public Library
Path)
+(type: .public Compiler
+ (Record
+ [#definition Symbol
+ #parameters (List Text)]))
+
+(def: .public compiler_equivalence
+ (Equivalence Compiler)
+ ($_ product.equivalence
+ symbol.equivalence
+ (list.equivalence text.equivalence)
+ ))
+
+(template [<ascii> <name>]
+ [(def: <name>
+ Text
+ (text.of_char (hex <ascii>)))]
+
+ ["02" parameter_start]
+ ["03" parameter_end]
+ )
+
+(def: compiler_parameter
+ (-> Text Text)
+ (text.enclosed [..parameter_start ..parameter_end]))
+
+(def: .public (compiler_format [[module short] parameters])
+ (%.Format Compiler)
+ (%.format (..compiler_parameter module) (..compiler_parameter short)
+ (text.together (list#each ..compiler_parameter parameters))))
+
+(def: compiler_parser'
+ (<text>.Parser Compiler)
+ (let [parameter (: (<text>.Parser Text)
+ (<| (<>.after (<text>.this ..parameter_start))
+ (<>.before (<text>.this ..parameter_end))
+ (<text>.slice (<text>.many! (<text>.none_of! ..parameter_end)))))]
+ (do <>.monad
+ [module parameter
+ short parameter
+ parameters (<>.some parameter)]
+ (in [[module short] parameters]))))
+
+(type: .public Source
+ Path)
+
(type: .public Target
Path)
@@ -31,9 +87,10 @@
(type: .public Compilation
(Record
- [#sources (List Source)
- #host_dependencies (List Host_Dependency)
+ [#host_dependencies (List Host_Dependency)
#libraries (List Library)
+ #compilers (List Compiler)
+ #sources (List Source)
#target Target
#module Module]))
@@ -49,44 +106,43 @@
{#Interpretation Interpretation}
{#Export Export}))
-(template [<name> <long> <type>]
+(template [<name> <long> <type> <parser>]
[(def: <name>
(Parser <type>)
- (<cli>.named <long> <cli>.any))]
+ (<cli>.named <long> <parser>))]
- [source_parser "--source" Source]
- [host_dependency_parser "--host_dependency" Host_Dependency]
- [library_parser "--library" Library]
- [target_parser "--target" Target]
- [module_parser "--module" Module]
+ [host_dependency_parser "--host_dependency" Host_Dependency <cli>.any]
+ [library_parser "--library" Library <cli>.any]
+ [compiler_parser "--compiler" Compiler (<text>.then ..compiler_parser' <cli>.any)]
+ [source_parser "--source" Source <cli>.any]
+ [target_parser "--target" Target <cli>.any]
+ [module_parser "--module" Module <cli>.any]
)
(def: .public service
(Parser Service)
- ($_ <>.or
- (<>.after (<cli>.this "build")
- ($_ <>.and
- (<>.some ..source_parser)
- (<>.some ..host_dependency_parser)
- (<>.some ..library_parser)
- ..target_parser
- ..module_parser))
- (<>.after (<cli>.this "repl")
- ($_ <>.and
- (<>.some ..source_parser)
- (<>.some ..host_dependency_parser)
- (<>.some ..library_parser)
- ..target_parser
- ..module_parser))
- (<>.after (<cli>.this "export")
- ($_ <>.and
- (<>.some ..source_parser)
- ..target_parser))
- ))
+ (let [compiler (: (Parser Compilation)
+ ($_ <>.and
+ (<>.some ..host_dependency_parser)
+ (<>.some ..library_parser)
+ (<>.some ..compiler_parser)
+ (<>.some ..source_parser)
+ ..target_parser
+ ..module_parser))]
+ ($_ <>.or
+ (<>.after (<cli>.this "build")
+ compiler)
+ (<>.after (<cli>.this "repl")
+ compiler)
+ (<>.after (<cli>.this "export")
+ ($_ <>.and
+ (<>.some ..source_parser)
+ ..target_parser))
+ )))
(def: .public target
(-> Service Target)
- (|>> (case> (^or {#Compilation [sources host_dependencies libraries target module]}
- {#Interpretation [sources host_dependencies libraries target module]}
+ (|>> (case> (^or {#Compilation [host_dependencies libraries compilers sources target module]}
+ {#Interpretation [host_dependencies libraries compilers sources target module]}
{#Export [sources target]})
target)))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux
index 658c0e886..1bfd062fe 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux
@@ -33,10 +33,10 @@
["[0]" archive {"+" Output}
[registry {"+" Registry}]
["[0]" artifact]
- ["[0]" module]
- ["[0]" descriptor]
- ["[0]" document {"+" Document}]
- ["[0]" unit]]
+ ["[0]" unit]
+ ["[0]" module
+ ["[0]" descriptor]
+ ["[0]" document {"+" Document}]]]
["[0]" cache "_"
["[1]/[0]" module {"+" Order}]
["[1]/[0]" artifact]]