aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/generation.lux142
1 files changed, 71 insertions, 71 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
index 67bc8b4c1..b8067a964 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
@@ -39,8 +39,8 @@
["[0]" module (.only)
["[0]" descriptor]]]]]])
-(type .public (Buffer directive)
- (Sequence [artifact.ID (Maybe Text) directive]))
+(type .public (Buffer declaration)
+ (Sequence [artifact.ID (Maybe Text) declaration]))
(exception .public (cannot_interpret [error Text])
(exception.report
@@ -55,28 +55,28 @@
[no_buffer_for_saving_code]
)
-(type .public (Host expression directive)
+(type .public (Host expression declaration)
(Interface
(is (-> unit.ID [(Maybe unit.ID) expression] (Try Any))
evaluate)
- (is (-> directive (Try Any))
+ (is (-> declaration (Try Any))
execute)
- (is (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Try [Text Any directive]))
+ (is (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Try [Text Any declaration]))
define)
- (is (-> unit.ID Binary directive)
+ (is (-> unit.ID Binary declaration)
ingest)
- (is (-> unit.ID (Maybe Text) directive (Try Any))
+ (is (-> unit.ID (Maybe Text) declaration (Try Any))
re_learn)
- (is (-> unit.ID (Maybe Text) directive (Try Any))
+ (is (-> unit.ID (Maybe Text) declaration (Try Any))
re_load)))
-(type .public (State anchor expression directive)
+(type .public (State anchor expression declaration)
(Record
[#module descriptor.Module
#anchor (Maybe anchor)
- #host (Host expression directive)
- #buffer (Maybe (Buffer directive))
+ #host (Host expression declaration)
+ #buffer (Maybe (Buffer declaration))
#registry Registry
#registry_shift Nat
#counter Nat
@@ -85,8 +85,8 @@
#interim_artifacts (List artifact.ID)]))
(with_template [<special> <general>]
- [(type .public (<special> anchor expression directive)
- (<general> (State anchor expression directive) Synthesis expression))]
+ [(type .public (<special> anchor expression declaration)
+ (<general> (State anchor expression declaration) Synthesis expression))]
[State+ extension.State]
[Operation extension.Operation]
@@ -97,10 +97,10 @@
)
(def .public (state host module)
- (All (_ anchor expression directive)
- (-> (Host expression directive)
+ (All (_ anchor expression declaration)
+ (-> (Host expression declaration)
descriptor.Module
- (..State anchor expression directive)))
+ (..State anchor expression declaration)))
[#module module
#anchor {.#None}
#host host
@@ -122,7 +122,7 @@
[(exception .public <exception>)
(def .public <with_declaration>
- (All (_ anchor expression directive output) <with_type>)
+ (All (_ anchor expression declaration output) <with_type>)
(function (_ body)
(function (_ [bundle state])
(case (body [bundle (has <tag> {.#Some <with_value>} state)])
@@ -134,8 +134,8 @@
{try.#Failure error}))))
(def .public <get>
- (All (_ anchor expression directive)
- (Operation anchor expression directive <get_type>))
+ (All (_ anchor expression declaration)
+ (Operation anchor expression declaration <get_type>))
(function (_ (^.let stateE [bundle state]))
(case (the <tag> state)
{.#Some output}
@@ -145,66 +145,66 @@
(exception.except <exception> []))))
(def .public (<set> value)
- (All (_ anchor expression directive)
- (-> <get_type> (Operation anchor expression directive Any)))
+ (All (_ anchor expression declaration)
+ (-> <get_type> (Operation anchor expression declaration Any)))
(function (_ [bundle state])
{try.#Success [[bundle (has <tag> {.#Some value} state)]
[]]}))]
[#anchor
(with_anchor anchor)
- (-> anchor (Operation anchor expression directive output)
- (Operation anchor expression directive output))
+ (-> anchor (Operation anchor expression declaration output)
+ (Operation anchor expression declaration output))
anchor
set_anchor anchor anchor no_anchor]
[#buffer
with_buffer
- (-> (Operation anchor expression directive output)
- (Operation anchor expression directive output))
+ (-> (Operation anchor expression declaration output)
+ (Operation anchor expression declaration output))
..empty_buffer
- set_buffer buffer (Buffer directive) no_active_buffer]
+ set_buffer buffer (Buffer declaration) no_active_buffer]
)
(def .public get_registry
- (All (_ anchor expression directive)
- (Operation anchor expression directive Registry))
+ (All (_ anchor expression declaration)
+ (Operation anchor expression declaration Registry))
(function (_ (^.let stateE [bundle state]))
{try.#Success [stateE (the #registry state)]}))
(def .public (set_registry value)
- (All (_ anchor expression directive)
- (-> Registry (Operation anchor expression directive Any)))
+ (All (_ anchor expression declaration)
+ (-> Registry (Operation anchor expression declaration Any)))
(function (_ [bundle state])
{try.#Success [[bundle (has #registry value state)]
[]]}))
(def .public next
- (All (_ anchor expression directive)
- (Operation anchor expression directive Nat))
+ (All (_ anchor expression declaration)
+ (Operation anchor expression declaration Nat))
(do phase.monad
[count (extension.read (the #counter))
_ (extension.update (revised #counter ++))]
(in count)))
(def .public (symbol prefix)
- (All (_ anchor expression directive)
- (-> Text (Operation anchor expression directive Text)))
+ (All (_ anchor expression declaration)
+ (-> Text (Operation anchor expression declaration Text)))
(at phase.monad each (|>> %.nat (format prefix)) ..next))
(def .public (enter_module module)
- (All (_ anchor expression directive)
- (-> descriptor.Module (Operation anchor expression directive Any)))
+ (All (_ anchor expression declaration)
+ (-> descriptor.Module (Operation anchor expression declaration Any)))
(extension.update (has #module module)))
(def .public module
- (All (_ anchor expression directive)
- (Operation anchor expression directive descriptor.Module))
+ (All (_ anchor expression declaration)
+ (Operation anchor expression declaration descriptor.Module))
(extension.read (the #module)))
(def .public (evaluate! label code)
- (All (_ anchor expression directive)
- (-> unit.ID [(Maybe unit.ID) expression] (Operation anchor expression directive Any)))
+ (All (_ anchor expression declaration)
+ (-> unit.ID [(Maybe unit.ID) expression] (Operation anchor expression declaration Any)))
(function (_ (^.let state+ [bundle state]))
(case (at (the #host state) evaluate label code)
{try.#Success output}
@@ -214,8 +214,8 @@
(exception.except ..cannot_interpret [error]))))
(def .public (execute! code)
- (All (_ anchor expression directive)
- (-> directive (Operation anchor expression directive Any)))
+ (All (_ anchor expression declaration)
+ (-> declaration (Operation anchor expression declaration Any)))
(function (_ (^.let state+ [bundle state]))
(case (at (the #host state) execute code)
{try.#Success output}
@@ -225,8 +225,8 @@
(exception.except ..cannot_interpret error))))
(def .public (define! context custom code)
- (All (_ anchor expression directive)
- (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Operation anchor expression directive [Text Any directive])))
+ (All (_ anchor expression declaration)
+ (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Operation anchor expression declaration [Text Any declaration])))
(function (_ (^.let stateE [bundle state]))
(case (at (the #host state) define context custom code)
{try.#Success output}
@@ -236,8 +236,8 @@
(exception.except ..cannot_interpret error))))
(def .public (save! artifact_id custom code)
- (All (_ anchor expression directive)
- (-> artifact.ID (Maybe Text) directive (Operation anchor expression directive Any)))
+ (All (_ anchor expression declaration)
+ (-> artifact.ID (Maybe Text) declaration (Operation anchor expression declaration Any)))
(do [! phase.monad]
[?buffer (extension.read (the #buffer))]
(case ?buffer
@@ -252,8 +252,8 @@
(with_template [<type> <mandatory?> <inputs> <input_types> <name> <artifact>]
[(`` (def .public (<name> it (~~ (template.spliced <inputs>)) dependencies)
- (All (_ anchor expression directive)
- (-> <type> (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression directive artifact.ID)))
+ (All (_ anchor expression declaration)
+ (-> <type> (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression declaration artifact.ID)))
(function (_ (^.let stateE [bundle state]))
(let [[id registry'] (<artifact> it <mandatory?> dependencies (the #registry state))]
{try.#Success [[bundle (has #registry registry' state)]
@@ -264,7 +264,7 @@
[Text #0 [] [] learn_analyser registry.analyser]
[Text #0 [] [] learn_synthesizer registry.synthesizer]
[Text #0 [] [] learn_generator registry.generator]
- [Text #0 [] [] learn_directive registry.directive]
+ [Text #0 [] [] learn_declaration registry.declaration]
)
(exception .public (unknown_definition [name Symbol
@@ -275,8 +275,8 @@
"Known Definitions" (exception.listing product.left known_definitions)))
(def .public (remember archive name)
- (All (_ anchor expression directive)
- (-> Archive Symbol (Operation anchor expression directive unit.ID)))
+ (All (_ anchor expression declaration)
+ (-> Archive Symbol (Operation anchor expression declaration unit.ID)))
(function (_ (^.let stateE [bundle state]))
(let [[_module _name] name]
(do try.monad
@@ -294,8 +294,8 @@
{try.#Success [stateE [@module id]]})))))
(def .public (definition archive name)
- (All (_ anchor expression directive)
- (-> Archive Symbol (Operation anchor expression directive [unit.ID (Maybe category.Definition)])))
+ (All (_ anchor expression declaration)
+ (-> Archive Symbol (Operation anchor expression declaration [unit.ID (Maybe category.Definition)])))
(function (_ (^.let stateE [bundle state]))
(let [[_module _name] name]
(do try.monad
@@ -315,16 +315,16 @@
(exception .public no_context)
(def .public (module_id module archive)
- (All (_ anchor expression directive)
- (-> descriptor.Module Archive (Operation anchor expression directive module.ID)))
+ (All (_ anchor expression declaration)
+ (-> descriptor.Module Archive (Operation anchor expression declaration module.ID)))
(function (_ (^.let stateE [bundle state]))
(do try.monad
[@module (archive.id module archive)]
(in [stateE @module]))))
(def .public (context archive)
- (All (_ anchor expression directive)
- (-> Archive (Operation anchor expression directive unit.ID)))
+ (All (_ anchor expression declaration)
+ (-> Archive (Operation anchor expression declaration unit.ID)))
(function (_ (^.let stateE [bundle state]))
(case (the #context state)
{.#None}
@@ -336,10 +336,10 @@
(in [stateE [@module id]])))))
(def .public (with_context @artifact body)
- (All (_ anchor expression directive a)
+ (All (_ anchor expression declaration a)
(-> artifact.ID
- (Operation anchor expression directive a)
- (Operation anchor expression directive a)))
+ (Operation anchor expression declaration a)
+ (Operation anchor expression declaration a)))
(function (_ [bundle state])
(do try.monad
[[[bundle' state'] output] (body [bundle (has #context {.#Some @artifact} state)])]
@@ -347,10 +347,10 @@
output]))))
(def .public (with_registry_shift shift body)
- (All (_ anchor expression directive a)
+ (All (_ anchor expression declaration a)
(-> Nat
- (Operation anchor expression directive a)
- (Operation anchor expression directive a)))
+ (Operation anchor expression declaration a)
+ (Operation anchor expression declaration a)))
(function (_ [bundle state])
(do try.monad
[[[bundle' state'] output] (body [bundle (has #registry_shift shift state)])]
@@ -358,9 +358,9 @@
output]))))
(def .public (with_new_context archive dependencies body)
- (All (_ anchor expression directive a)
- (-> Archive (Set unit.ID) (Operation anchor expression directive a)
- (Operation anchor expression directive [unit.ID a])))
+ (All (_ anchor expression declaration a)
+ (-> Archive (Set unit.ID) (Operation anchor expression declaration a)
+ (Operation anchor expression declaration [unit.ID a])))
(function (_ (^.let stateE [bundle state]))
(let [[@artifact registry'] (registry.resource false dependencies (the #registry state))
@artifact (n.+ @artifact (the #registry_shift state))]
@@ -375,17 +375,17 @@
output]])))))
(def .public (log! message)
- (All (_ anchor expression directive a)
- (-> Text (Operation anchor expression directive Any)))
+ (All (_ anchor expression declaration a)
+ (-> Text (Operation anchor expression declaration Any)))
(function (_ [bundle state])
{try.#Success [[bundle
(revised #log (sequence.suffix message) state)]
[]]}))
(def .public (with_interim_artifacts archive body)
- (All (_ anchor expression directive a)
- (-> Archive (Operation anchor expression directive a)
- (Operation anchor expression directive [(List unit.ID) a])))
+ (All (_ anchor expression declaration a)
+ (-> Archive (Operation anchor expression declaration a)
+ (Operation anchor expression declaration [(List unit.ID) a])))
(do phase.monad
[module (extension.read (the #module))]
(function (_ state+)