aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler
diff options
context:
space:
mode:
authorEduardo Julian2022-06-26 18:37:05 -0400
committerEduardo Julian2022-06-26 18:37:05 -0400
commit9f6505491e8a5c8a159ce094fe0af6f4fef0c5cf (patch)
treed497c163e477406a388460eedea80fdd6ee9748a /stdlib/source/library/lux/tool/compiler
parent3053fd79bc6ae42415298ee056a268dc2c9b690c (diff)
Re-named "format/lux/data/binary.Writer" to "Format".
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux24
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux.lux18
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux18
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux54
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux22
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/export.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux2
16 files changed, 103 insertions, 103 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index d20ddcc8a..0f893a1dc 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -18,7 +18,7 @@
["[0]" bit]
["[0]" product]
["[0]" binary (.only Binary)
- ["_" \\format (.only Writer)]]
+ ["_" \\format (.only Format)]]
["[0]" text (.use "[1]#[0]" equivalence)
["%" \\format (.only format)]]
[collection
@@ -95,21 +95,21 @@
<State+> (these (///directive.State+ <type_vars>))
<Bundle> (these (///generation.Bundle <type_vars>))]
- (def (writer //)
+ (def (format //)
(All (_ a)
- (-> (Writer a)
- (Writer [(module.Module a) Registry])))
+ (-> (Format a)
+ (Format [(module.Module a) Registry])))
(all _.and
(all _.and
_.nat
- descriptor.writer
- (document.writer //))
- registry.writer
+ descriptor.format
+ (document.format //))
+ registry.format
))
(def (cache_module context platform @module key format entry)
(All (_ <type_vars> document)
- (-> context.Context <Platform> module.ID (Key document) (Writer document) (archive.Entry document)
+ (-> context.Context <Platform> module.ID (Key document) (Format document) (archive.Entry document)
(Async (Try Any))))
(let [system (the #file_system platform)
write_artifact! (is (-> [artifact.ID (Maybe Text) Binary] (Action Any))
@@ -137,7 +137,7 @@
(the archive.#module)
(has module.#document document))
(the archive.#registry entry)]
- (_.result (..writer format))
+ (_.result (..format format))
(cache/module.cache! system context @module))))))
... TODO: Inline ASAP
@@ -295,7 +295,7 @@
[[state [archive payload]] (|> (..process_runtime archive platform)
(///phase.result' state)
async#in)
- _ (..cache_module context platform 0 $.key $.writer payload)
+ _ (..cache_module context platform 0 $.key $.format payload)
[phase_wrapper state] (with_missing_extensions platform program state)]
(in [state archive phase_wrapper])))))
@@ -705,7 +705,7 @@
(All (_ <type_vars>
state document object)
(-> Import context.Context <Platform> (List _io.Context) (///.Compiler <State+> .Module Any)
- (Key document) (Writer document) (///.Compilation state document object)
+ (Key document) (Format document) (///.Compilation state document object)
(-> (List ///.Custom) descriptor.Module Lux_Importer module.ID (..Context state) descriptor.Module (..Return state))))
(function (_ customs importer import! @module [archive state] module)
(loop (again [[archive state] [archive state]
@@ -780,7 +780,7 @@
(console.write_line report console)))
<else>)))
.let [entry (has [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)]
- _ (..cache_module context platform @module $.key $.writer (as (archive.Entry .Module) entry))]
+ _ (..cache_module context platform @module $.key $.format (as (archive.Entry .Module) entry))]
(async#in (do try.monad
[archive (archive.has module entry archive)]
(in [archive
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux.lux
index b9d334818..14adeb6d6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux.lux
@@ -5,7 +5,7 @@
["<>" parser]]
[data
["[0]" binary
- ["_" \\format (.only Writer)]
+ ["_" \\format (.only Format)]
["<[1]>" \\parser (.only Parser)]]]
[meta
["[0]" version]]]]
@@ -20,20 +20,20 @@
... TODO: Remove #module_hash, #imports & #module_state ASAP.
... TODO: Not just from this parser, but from the lux.Module type.
-(def .public writer
- (Writer .Module)
- (let [definition (is (Writer Definition)
+(def .public format
+ (Format .Module)
+ (let [definition (is (Format Definition)
(all _.and _.bit _.type _.any))
- labels (is (Writer [Text (List Text)])
+ labels (is (Format [Text (List Text)])
(_.and _.text (_.list _.text)))
- global_type (is (Writer [Bit Type (Either [Text (List Text)]
+ global_type (is (Format [Bit Type (Either [Text (List Text)]
[Text (List Text)])])
(all _.and _.bit _.type (_.or labels labels)))
- global_label (is (Writer .Label)
+ global_label (is (Format .Label)
(all _.and _.bit _.type (_.list _.text) _.nat))
- alias (is (Writer Alias)
+ alias (is (Format Alias)
(_.and _.text _.text))
- global (is (Writer Global)
+ global (is (Format Global)
(all _.or
definition
global_type
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 16cb9e777..4696b3104 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
@@ -2468,7 +2468,7 @@
(let [signature (signature.inheritance (list#each jvm.signature parameters)
(jvm.signature super)
(list#each jvm.signature interfaces))]
- (try#each (|>> (\\format.result class.writer)
+ (try#each (|>> (\\format.result class.format)
[name])
(class.class version.v6_0
(all modifier#composite
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 05da344e7..39104d42d 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
@@ -687,7 +687,7 @@
(let [signature (signature.inheritance (list#each type.signature parameters)
(type.signature super)
(list#each type.signature interfaces))]
- (try#each (|>> (\\format.result class.writer)
+ (try#each (|>> (\\format.result class.format)
[name])
(class.class version.v6_0
(all modifier#composite
@@ -904,7 +904,7 @@
(the [directive.#generation directive.#phase] state)])
methods)
.let [all_dependencies (cache.all (list#each product.left methods))]
- bytecode (<| (at ! each (\\format.result class.writer))
+ bytecode (<| (at ! each (\\format.result class.format))
phase.lifted
(class.class version.v6_0
(all modifier#composite
@@ -943,7 +943,7 @@
(function (_ extension_name phase archive [[name parameters] supers annotations method_declarations])
(directive.lifted_generation
(do [! phase.monad]
- [bytecode (<| (at ! each (\\format.result class.writer))
+ [bytecode (<| (at ! each (\\format.result class.format))
phase.lifted
(class.class version.v6_0
(all modifier#composite
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
index 2cebcc690..73c27d038 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
@@ -1350,7 +1350,7 @@
methods! (|> overriden_methods
(list#each (normalized_method global_mapping))
(monad.each ! (method_definition generate archive artifact_id)))
- bytecode (<| (at ! each (\\format.result class.writer))
+ bytecode (<| (at ! each (\\format.result class.format))
//////.lifted
(class.class version.v6_0 (all modifier#composite class.public class.final)
(name.internal anonymous_class_name)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux
index 3f2474f4e..200b4db2e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux
@@ -115,14 +115,14 @@
.let [function_class (//runtime.class_name function_context)]
[fields methods instance] (..with generate archive @begin function_class environment arity bodyG)
class (phase.lifted (class.class version.v6_0
- ..modifier
- (name.internal function_class)
- {.#None}
- (..internal /abstract.class) (list)
- fields
- methods
- (sequence.sequence)))
- .let [bytecode [function_class (\\format.result class.writer class)]]
+ ..modifier
+ (name.internal function_class)
+ {.#None}
+ (..internal /abstract.class) (list)
+ fields
+ methods
+ (sequence.sequence)))
+ .let [bytecode [function_class (\\format.result class.format class)]]
_ (generation.execute! bytecode)
_ (generation.save! (product.right function_context) {.#None} bytecode)]
(in instance)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux
index 61bd54986..9e33db858 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux
@@ -131,7 +131,7 @@
_.return)}))
(sequence.sequence))]
(io.run! (do [! (try.with io.monad)]
- [bytecode (at ! each (\\format.result class.writer)
+ [bytecode (at ! each (\\format.result class.format)
(io.io bytecode))
_ (loader.store eval_class bytecode library)
class (loader.load eval_class loader)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
index 2a89c066d..f902c5261 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
@@ -155,14 +155,14 @@
_.return)})
class (artifact_name context)]
[class
- (<| (\\format.result class.writer)
+ (<| (\\format.result class.format)
try.trusted
(class.class version.v6_0
- ..program::modifier
- (name.internal class)
- {.#None}
- super_class
- (list)
- (list)
- (list main)
- (sequence.sequence)))]))
+ ..program::modifier
+ (name.internal class)
+ {.#None}
+ super_class
+ (list)
+ (list)
+ (list main)
+ (sequence.sequence)))]))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
index a182ed733..7f11b6f25 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
@@ -545,27 +545,27 @@
(all modifier#composite
class.public
class.final))
- bytecode (<| (\\format.result class.writer)
+ bytecode (<| (\\format.result class.format)
try.trusted
(class.class jvm/version.v6_0
- modifier
- (name.internal class)
- {.#None}
- (name.internal (..reflection ^Object)) (list)
- (list)
- (let [[left_projection::method right_projection::method] projection::method2]
- (list ..decode_frac::method
- ..variant::method
-
- ..pm_failure::method
-
- ..push::method
- ..case::method
- left_projection::method
- right_projection::method
-
- ..try::method))
- sequence.empty))]
+ modifier
+ (name.internal class)
+ {.#None}
+ (name.internal (..reflection ^Object)) (list)
+ (list)
+ (let [[left_projection::method right_projection::method] projection::method2]
+ (list ..decode_frac::method
+ ..variant::method
+
+ ..pm_failure::method
+
+ ..push::method
+ ..case::method
+ left_projection::method
+ right_projection::method
+
+ ..try::method))
+ sequence.empty))]
(do ////.monad
[_ (generation.execute! [class bytecode])
_ (generation.save! ..artifact_id {.#None} [class bytecode])]
@@ -618,16 +618,16 @@
//function/count.field
#0 //function/count.type
sequence.empty))
- bytecode (<| (\\format.result class.writer)
+ bytecode (<| (\\format.result class.format)
try.trusted
(class.class jvm/version.v6_0
- modifier
- (name.internal class)
- {.#None}
- (name.internal (..reflection ^Object)) (list)
- (list partial_count)
- (list.partial <init>::method apply::method+)
- sequence.empty))]
+ modifier
+ (name.internal class)
+ {.#None}
+ (name.internal (..reflection ^Object)) (list)
+ (list partial_count)
+ (list.partial <init>::method apply::method+)
+ sequence.empty))]
(do ////.monad
[_ (generation.execute! [class bytecode])
... _ (generation.save! //function.artifact_id {.#None} [class bytecode])
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
index 0b4e012cc..fd8a0c817 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
@@ -13,10 +13,10 @@
[data
["[0]" product]
["[0]" binary (.only Binary)
- ["[0]" \\format (.only Writer)]
+ ["[0]" \\format (.only Format)]
["<[1]>" \\parser (.only Parser)]]
["[0]" text (.only)
- ["%" \\format (.only format)]]
+ ["%" \\format]]
[collection
["[0]" list (.use "[1]#[0]" functor mix)]
["[0]" dictionary (.only Dictionary)]
@@ -226,8 +226,8 @@
<binary>.nat
(<binary>.list (<>.and <binary>.text <binary>.nat))))
- (def writer
- (Writer ..Frozen)
+ (def format
+ (Format ..Frozen)
(all \\format.and
\\format.nat
\\format.nat
@@ -243,7 +243,7 @@
{.#Some _} {.#Some [module id]}
{.#None} {.#None})))
[version /#next]
- (\\format.result ..writer))))
+ (\\format.result ..format))))
(exception .public (version_mismatch [expected Version
actual Version])
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux
index c67c50d15..b3e186b92 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux
@@ -9,7 +9,7 @@
["[0]" product]
["[0]" text]
["[0]" binary
- ["[0]" \\format (.only Writer)]
+ ["[0]" \\format (.only Format)]
["<[1]>" \\parser (.only Parser)]]
[collection
["[0]" set (.only Set)]]]
@@ -61,8 +61,8 @@
set.equivalence
))
-(def .public writer
- (Writer Descriptor)
+(def .public format
+ (Format Descriptor)
(all \\format.and
\\format.text
\\format.text
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux
index 4653591a7..64fae1ab4 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux
@@ -12,7 +12,7 @@
["[0]" dictionary (.only Dictionary)]]
["[0]" binary
[\\parser (.only Parser)]
- ["[1]" \\format (.only Writer)]]]
+ ["[1]" \\format (.only Format)]]]
[type (.only sharing)
[primitive (.except)]]]]
[///
@@ -59,12 +59,12 @@
(-> (Document Any) Signature)
(|>> representation (the #signature)))
- (def .public (writer content)
- (All (_ d) (-> (Writer d) (Writer (Document d))))
- (let [writer (all binary.and
- signature.writer
+ (def .public (format content)
+ (All (_ d) (-> (Format d) (Format (Document d))))
+ (let [format (all binary.and
+ signature.format
content)]
- (|>> representation writer)))
+ (|>> representation format)))
(def .public (parser key it)
(All (_ d) (-> (Key d) (Parser d) (Parser (Document d))))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
index 9c889fada..f93624fbc 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
@@ -11,10 +11,10 @@
[data
["[0]" product]
["[0]" binary
- ["[1]" \\format (.only Writer)]
+ ["[1]" \\format (.only Format)]
["<[1]>" \\parser (.only Parser)]]
["[0]" text (.only)
- ["%" \\format (.only format)]]
+ ["%" \\format]]
[collection
[set (.only Set)]
["[0]" list]
@@ -104,9 +104,9 @@
(-> Text Registry (Maybe ID))
(maybe#each product.left (find_definition name registry)))
- (def .public writer
- (Writer Registry)
- (let [definition (is (Writer //category.Definition)
+ (def .public format
+ (Format Registry)
+ (let [definition (is (Format //category.Definition)
(all binary.and
binary.text
(binary.maybe
@@ -116,12 +116,12 @@
binary.nat
))
))
- category (is (Writer Category)
+ category (is (Format Category)
(function (_ value)
(case value
- (^.with_template [<nat> <tag> <writer>]
+ (^.with_template [<nat> <tag> <format>]
[{<tag> value}
- ((binary.and binary.nat <writer>) [<nat> value])])
+ ((binary.and binary.nat <format>) [<nat> value])])
([0 //category.#Anonymous binary.any]
[1 //category.#Definition definition]
[2 //category.#Analyser binary.text]
@@ -130,11 +130,11 @@
[5 //category.#Directive binary.text]
[6 //category.#Custom binary.text]))))
mandatory? binary.bit
- dependency (is (Writer unit.ID)
+ dependency (is (Format unit.ID)
(binary.and binary.nat binary.nat))
- dependencies (is (Writer (Set unit.ID))
+ dependencies (is (Format (Set unit.ID))
(binary.set dependency))
- artifacts (is (Writer (Sequence [Category Bit (Set unit.ID)]))
+ artifacts (is (Format (Sequence [Category Bit (Set unit.ID)]))
(binary.sequence_64 (all binary.and category mandatory? dependencies)))]
(|>> representation
(the #artifacts)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux
index 086b11c12..e9220d028 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux
@@ -8,10 +8,10 @@
[data
["[0]" product]
["[0]" binary
- ["[1]" \\format (.only Writer)]
+ ["[1]" \\format (.only Format)]
["<[1]>" \\parser (.only Parser)]]
["[0]" text (.only)
- ["%" \\format (.only format)]]]
+ ["%" \\format]]]
[math
[number
["[0]" nat]]]
@@ -33,10 +33,10 @@
(def .public (description signature)
(-> Signature Text)
- (format (%.symbol (the #name signature)) " " (version.format (the #version signature))))
+ (%.format (%.symbol (the #name signature)) " " (version.format (the #version signature))))
-(def .public writer
- (Writer Signature)
+(def .public format
+ (Format Signature)
(all binary.and
(binary.and binary.text binary.text)
binary.nat))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/export.lux b/stdlib/source/library/lux/tool/compiler/meta/export.lux
index 4b0621fb9..942391568 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/export.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/export.lux
@@ -70,6 +70,6 @@
(do [! (try.with async.monad)]
[tar (|> sources
(..library fs)
- (at ! each (binary.result tar.writer)))
+ (at ! each (binary.result tar.format)))
.let [/ (at fs separator)]]
(at fs write (format target / ..file) tar)))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
index 48ba3ea69..86960acb0 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
@@ -128,4 +128,4 @@
entries (monad.each ! (..write_module now mapping) order)]
(in (|> entries
sequence.of_list
- (binary.result tar.writer))))))
+ (binary.result tar.format))))))