aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool/compiler/phase
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/tool/compiler/phase')
-rw-r--r--stdlib/source/lux/tool/compiler/phase/extension/statement.lux76
-rw-r--r--stdlib/source/lux/tool/compiler/phase/statement.lux79
2 files changed, 99 insertions, 56 deletions
diff --git a/stdlib/source/lux/tool/compiler/phase/extension/statement.lux b/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
index 172517dd0..e36af0de6 100644
--- a/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
+++ b/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
@@ -1,15 +1,17 @@
(.module:
[lux #*
[control
- [monad (#+ do)]
- pipe]
+ ["." monad (#+ do)]
+ ["p" parser]]
[data
+ ["." error]
[text
format]
[collection
["." list ("#;." functor)]
["." dictionary]]]
- ["." macro]
+ ["." macro
+ ["s" syntax (#+ Syntax)]]
[type (#+ :share :by-example)
["." check]]]
["." //
@@ -22,7 +24,7 @@
["#/" // #_
["#." analysis]
["#." synthesis (#+ Synthesis)]
- ["#." statement (#+ Operation Handler Bundle)]]]])
+ ["#." statement (#+ Import Operation Handler Bundle)]]]])
## TODO: Inline "evaluate!'" into "evaluate!" ASAP
(def: (evaluate!' generate code//type codeS)
@@ -135,9 +137,10 @@
#.None)
valueC)
_ (..define short-name value//type annotationsV valueV)
- #let [_ (log! (format "Definition " (%name full-name)))]]
- (////statement.lift-generation
- (///generation.learn full-name valueN)))
+ #let [_ (log! (format "Definition " (%name full-name)))]
+ _ (////statement.lift-generation
+ (///generation.learn full-name valueN))]
+ (wrap ////statement.no-requirements))
_
(///.throw //.invalid-syntax [extension-name]))))
@@ -148,6 +151,14 @@
[definition (//.lift (macro.find-def def-name))]
(module.define alias definition)))
+(def: imports
+ (Syntax (List Import))
+ (|> (s.tuple (p.and s.text s.text))
+ p.some
+ s.tuple
+ (p.after (s.this (' #.imports)))
+ s.record))
+
(def: def::module
Handler
(function (_ extension-name phase inputsC+)
@@ -155,9 +166,23 @@
(^ (list annotationsC))
(do ///.monad
[[_ annotationsT annotationsV] (evaluate! Code annotationsC)
+ imports (case (s.run (list (:coerce Code annotationsV))
+ ..imports)
+ (#error.Success imports)
+ (wrap imports)
+
+ (#error.Failure error)
+ (///.throw //.invalid-syntax [extension-name]))
_ (////statement.lift-analysis
- (module.set-annotations (:coerce Code annotationsV)))]
- (wrap []))
+ (do ///.monad
+ [_ (monad.map @ (function (_ [module alias])
+ (do @
+ [_ (module.import module)]
+ (module.alias alias module)))
+ imports)]
+ (module.set-annotations (:coerce Code annotationsV))))]
+ (wrap {#////statement.imports imports
+ #////statement.referrals (list)}))
_
(///.throw //.invalid-syntax [extension-name]))))
@@ -167,10 +192,12 @@
(function (_ extension-name phase inputsC+)
(case inputsC+
(^ (list [_ (#.Identifier ["" alias])] [_ (#.Identifier def-name)]))
- (//.lift
- (///.sub [(get@ [#////statement.analysis #////statement.state])
- (set@ [#////statement.analysis #////statement.state])]
- (alias! alias def-name)))
+ (do ///.monad
+ [_ (//.lift
+ (///.sub [(get@ [#////statement.analysis #////statement.state])
+ (set@ [#////statement.analysis #////statement.state])]
+ (alias! alias def-name)))]
+ (wrap ////statement.no-requirements))
_
(///.throw //.invalid-syntax [extension-name]))))
@@ -187,22 +214,23 @@
{(Handler anchor expression statement)
handler}
<type>)
- valueC)]
- (<| <scope>
- (//.install name)
- (:share [anchor expression statement]
- {(Handler anchor expression statement)
- handler}
- {<type>
- (:assume handlerV)})))
+ valueC)
+ _ (<| <scope>
+ (//.install name)
+ (:share [anchor expression statement]
+ {(Handler anchor expression statement)
+ handler}
+ {<type>
+ (:assume handlerV)}))]
+ (wrap ////statement.no-requirements))
_
(///.throw //.invalid-syntax [extension-name]))))]
- [def::analysis ////analysis.Handler ////statement.lift-analysis]
- [def::synthesis ////synthesis.Handler ////statement.lift-synthesis]
+ [def::analysis ////analysis.Handler ////statement.lift-analysis]
+ [def::synthesis ////synthesis.Handler ////statement.lift-synthesis]
[def::generation (///generation.Handler anchor expression statement) ////statement.lift-generation]
- [def::statement (////statement.Handler anchor expression statement) (<|)]
+ [def::statement (////statement.Handler anchor expression statement) (<|)]
)
(def: bundle::def
diff --git a/stdlib/source/lux/tool/compiler/phase/statement.lux b/stdlib/source/lux/tool/compiler/phase/statement.lux
index 7e55e2dc6..1ab3d41ef 100644
--- a/stdlib/source/lux/tool/compiler/phase/statement.lux
+++ b/stdlib/source/lux/tool/compiler/phase/statement.lux
@@ -5,7 +5,9 @@
["." exception (#+ exception:)]]
[data
[text
- format]]
+ format]
+ [collection
+ ["." list ("#;." fold monoid)]]]
["." macro]]
["." //
["#." macro (#+ Expander)]
@@ -20,7 +22,7 @@
(exception.report
["Statement" (%code code)]))
-(exception: #export (not-a-macro-call {code Code})
+(exception: #export (invalid-macro-call {code Code})
(exception.report
["Code" (%code code)]))
@@ -28,35 +30,48 @@
(exception.report
["Name" (%name name)]))
-(def: #export (phase expander)
- (-> Expander Phase)
- (let [analyze (analysisP.phase expander)]
- (function (compile code)
- (case code
- (^ [_ (#.Form (list& [_ (#.Text name)] inputs))])
- (//extension.apply compile [name inputs])
+(with-expansions [<lux_def_module> (as-is [|form-cursor| (#.Form (list& [|text-cursor| (#.Text "lux def module")] annotations))])]
+ (def: #export (phase expander)
+ (-> Expander Phase)
+ (let [analyze (analysisP.phase expander)]
+ (function (compile code)
+ (case code
+ (^ [_ (#.Form (list& [_ (#.Text name)] inputs))])
+ (do //.monad
+ [requirements (//extension.apply compile [name inputs])]
+ (wrap requirements))
- (^ [_ (#.Form (list& macro inputs))])
- (do //.monad
- [expansion (/.lift-analysis
- (do @
- [macroA (type.with-type Macro
- (analyze macro))]
- (case macroA
- (^ (///analysis.constant macro-name))
- (do @
- [?macro (//extension.lift (macro.find-macro macro-name))
- macro (case ?macro
- (#.Some macro)
- (wrap macro)
-
- #.None
- (//.throw macro-was-not-found macro-name))]
- (//extension.lift (//macro.expand expander macro-name macro inputs)))
-
- _
- (//.throw not-a-macro-call code))))]
- (monad.map @ compile expansion))
+ (^ [_ (#.Form (list& macro inputs))])
+ (do //.monad
+ [expansion (/.lift-analysis
+ (do @
+ [macroA (type.with-type Macro
+ (analyze macro))]
+ (case macroA
+ (^ (///analysis.constant macro-name))
+ (do @
+ [?macro (//extension.lift (macro.find-macro macro-name))
+ macro (case ?macro
+ (#.Some macro)
+ (wrap macro)
+
+ #.None
+ (//.throw macro-was-not-found macro-name))]
+ (//extension.lift (//macro.expand expander macro-name macro inputs)))
+
+ _
+ (//.throw invalid-macro-call code))))
+ requirements (case expansion
+ (^ (list& <lux_def_module> referrals))
+ (do @
+ [requirements (compile <lux_def_module>)]
+ (wrap (update@ #/.referrals (list;compose referrals) requirements)))
- _
- (//.throw not-a-statement code)))))
+ _
+ (|> expansion
+ (monad.map @ compile)
+ (:: @ map (list;fold /.merge-requirements /.no-requirements))))]
+ (wrap requirements))
+
+ _
+ (//.throw not-a-statement code))))))