aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/meta/compiler/default/platform.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/meta/compiler/default/platform.lux56
1 files changed, 28 insertions, 28 deletions
diff --git a/stdlib/source/library/lux/meta/compiler/default/platform.lux b/stdlib/source/library/lux/meta/compiler/default/platform.lux
index 09d58919e..a9a8aaee0 100644
--- a/stdlib/source/library/lux/meta/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/meta/compiler/default/platform.lux
@@ -93,7 +93,7 @@
(try.with async.monad)))
(with_expansions [<Platform> (these (Platform <type_vars>))
- <State+> (these (///declaration.State+ <type_vars>))]
+ <State> (these (///declaration.State <type_vars>))]
(def (format //)
(All (_ a)
@@ -190,10 +190,10 @@
(def (initialize_state analysis_state state)
(All (_ <type_vars>)
- (-> .Lux <State+>
- (Try <State+>)))
+ (-> .Lux <State>
+ (Try <State>)))
(|> (sharing [<type_vars>]
- (is <State+>
+ (is <State>
state)
(is (///declaration.Operation <type_vars> Any)
(do [! ///phase.monad]
@@ -213,7 +213,7 @@
(Program expression declaration)
extension.Extender
Import (List _io.Context) Configuration
- (Async (Try [<State+> Archive ///phase.Wrapper]))))
+ (Async (Try [<State> Archive ///phase.Wrapper]))))
(do [! ..monad]
[.let [phase_wrapper (the #phase_wrapper platform)
state (//init.state (the context.#host context)
@@ -228,7 +228,7 @@
[archive analysis_state bundles] (ioW.thaw (list) compilation_configuration (the #host platform) (the #file_system platform) context import compilation_sources)
.let [with_missing_extensions
(is (All (_ <type_vars>)
- (-> <State+> (Async (Try <State+>))))
+ (-> <State> (Async (Try <State>))))
(function (_ state)
(|> state
(initialize_state analysis_state)
@@ -251,7 +251,7 @@
(def (module_compilation_log module)
(All (_ <type_vars>)
- (-> descriptor.Module <State+> Text))
+ (-> descriptor.Module <State> Text))
(|>> (the [///declaration.#generation
///declaration.#state
///generation.#log])
@@ -261,7 +261,7 @@
(def with_reset_log
(All (_ <type_vars>)
- (-> <State+> <State+>))
+ (-> <State> <State>))
(has [///declaration.#generation
///declaration.#state
///generation.#log]
@@ -405,12 +405,12 @@
(type (Compiler state)
(-> (List ///.Custom) descriptor.Module (Importer state) module.ID (Context state) descriptor.Module (Return state)))
- (with_expansions [Lux_Context (..Context <State+>)
- Lux_Return (..Return <State+>)
- Lux_Signal (..Signal <State+>)
- Lux_Pending (..Pending <State+>)
- Lux_Importer (..Importer <State+>)
- Lux_Compiler (..Compiler <State+>)]
+ (with_expansions [Lux_Context (..Context <State>)
+ Lux_Return (..Return <State>)
+ Lux_Signal (..Signal <State>)
+ Lux_Pending (..Pending <State>)
+ Lux_Importer (..Importer <State>)
+ Lux_Compiler (..Compiler <State>)]
(def (parallel initial)
(All (_ <type_vars>)
(-> Lux_Context
@@ -505,7 +505,7 @@
... TODO: Find a better way, as this only works for the Lux compiler.
(def (updated_state archive extended_states state)
(All (_ <type_vars>)
- (-> Archive (List <State+>) <State+> (Try <State+>)))
+ (-> Archive (List <State>) <State> (Try <State>)))
(do [! try.monad]
[modules (monad.each ! (function (_ module)
(do !
@@ -519,7 +519,7 @@
(list#each product.left)
(set.of_list text.hash))
with_modules (is (All (_ <type_vars>)
- (-> <State+> <State+>))
+ (-> <State> <State>))
(revised [///declaration.#analysis
///declaration.#state]
(is (All (_ a) (-> a a))
@@ -537,7 +537,7 @@
(def (set_current_module module state)
(All (_ <type_vars>)
- (-> descriptor.Module <State+> <State+>))
+ (-> descriptor.Module <State> <State>))
(|> (///declaration.set_current_module module)
(///phase.result' state)
try.trusted
@@ -588,7 +588,7 @@
(def (after_lux_imports customs import! module duplicates new_dependencies [archive state])
(All (_ <type_vars>)
(-> (List ///.Custom) Lux_Importer descriptor.Module (Set descriptor.Module) (List descriptor.Module) Lux_Context
- (..Return [<State+> (List Text)])))
+ (..Return [<State> (List Text)])))
(do ..monad
[[archive state/* errors] (after_imports customs import! module duplicates new_dependencies archive)]
(when errors
@@ -607,9 +607,9 @@
(def (next_compilation module [archive state] compilation)
(All (_ <type_vars>)
- (-> descriptor.Module Lux_Context (///.Compilation <State+> .Module)
- (Try [<State+> (Either (///.Compilation <State+> .Module)
- (archive.Entry Any))])))
+ (-> descriptor.Module Lux_Context (///.Compilation <State> .Module)
+ (Try [<State> (Either (///.Compilation <State> .Module)
+ (archive.Entry Any))])))
((the ///.#process compilation)
... TODO: The "///declaration.set_current_module" below shouldn't be necessary. Remove it ASAP.
... TODO: The context shouldn't need to be re-set either.
@@ -625,7 +625,7 @@
(-> (Program expression declaration) (-> Archive Symbol (///generation.Operation <type_vars> expression))
///phase.Wrapper (Extender <type_vars>) Expander <Platform> Text (Maybe Module)
(//init.Extensions <type_vars>)
- (///.Compiler <State+> .Module)))
+ (///.Compiler <State> .Module)))
(let [instancer (//init.compiler program global phase_wrapper extender expander syntax.prelude (the #write platform) program_module program_definition
all_extensions)]
(instancer $.key (list))))
@@ -634,7 +634,7 @@
compiler custom_key custom_format custom_compilation)
(All (_ <type_vars>
state document)
- (-> Import context.Context <Platform> (List _io.Context) Configuration (///.Compiler <State+> .Module)
+ (-> Import context.Context <Platform> (List _io.Context) Configuration (///.Compiler <State> .Module)
(Key document) (Format document) (///.Compilation state document)
(-> (List ///.Custom) descriptor.Module Lux_Importer module.ID (..Context state) descriptor.Module (..Return state))))
(function (_ customs importer import! @module [archive state] module)
@@ -679,8 +679,8 @@
(-> context.Context <Platform>
(Set descriptor.Module)
module.ID Text (archive.Entry Any)
- Archive <State+>
- (Return <State+>)))
+ Archive <State>
+ (Return <State>)))
(do ..monad
[_ (let [report (..module_compilation_log module state)]
(with_expansions [<else> (in (debug.log! report))]
@@ -701,8 +701,8 @@
(def (lux_compiler import context platform compilation_sources configuration compiler compilation)
(All (_ <type_vars>)
- (-> Import context.Context <Platform> (List _io.Context) Configuration (///.Compiler <State+> .Module)
- (///.Compilation <State+> .Module)
+ (-> Import context.Context <Platform> (List _io.Context) Configuration (///.Compiler <State> .Module)
+ (///.Compilation <State> .Module)
Lux_Compiler))
(function (_ customs importer import! @module [archive state] module)
(loop (again [[archive state] [archive (..set_current_module module state)]
@@ -747,7 +747,7 @@
(def (serial_compiler import context platform compilation_sources configuration compiler)
(All (_ <type_vars>)
- (-> Import context.Context <Platform> (List _io.Context) Configuration (///.Compiler <State+> .Module)
+ (-> Import context.Context <Platform> (List _io.Context) Configuration (///.Compiler <State> .Module)
Lux_Compiler))
(function (_ all_customs importer import! @module [archive lux_state] module)
(do [! ..monad]