aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool
diff options
context:
space:
mode:
authorEduardo Julian2020-05-06 04:19:54 -0400
committerEduardo Julian2020-05-06 04:19:54 -0400
commit3e524725cfb47cb56466a08ac290ed5a389748be (patch)
tree5ba247673e8a3b6d2e25df194b0f6011c2c0b436 /stdlib/source/lux/tool
parent724372e2b023bccbb93e1fa40e3c92ed2ee7e36c (diff)
Loading the artifacts from the cache and re-populating the analyser's state.
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/tool/compiler/default/init.lux16
-rw-r--r--stdlib/source/lux/tool/compiler/default/platform.lux83
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/analysis.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/generation.lux10
-rw-r--r--stdlib/source/lux/tool/compiler/meta/archive/artifact.lux8
-rw-r--r--stdlib/source/lux/tool/compiler/meta/io.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/meta/io/archive.lux201
8 files changed, 233 insertions, 125 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/init.lux b/stdlib/source/lux/tool/compiler/default/init.lux
index 625931913..3c23bf62c 100644
--- a/stdlib/source/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/lux/tool/compiler/default/init.lux
@@ -44,18 +44,10 @@
[".D" lux]]]]]]
[meta
[archive (#+ Archive)
- ["." signature]
- ["." key (#+ Key)]
["." descriptor (#+ Module)]
["." artifact]
["." document]]]]])
-(def: #export (info host)
- (-> Text Info)
- {#.target host
- #.version ///version.version
- #.mode #.Build})
-
(def: #export (state target module expander host-analysis host generate generation-bundle host-directive-bundle program extender)
(All [anchor expression directive]
(-> Host
@@ -73,7 +65,7 @@
generation-state [generation-bundle (///generation.state host module)]
eval (///analysis/evaluation.evaluator expander synthesis-state generation-state generate)
analysis-state [(analysisE.bundle eval host-analysis)
- (///analysis.state (..info target) host)]]
+ (///analysis.state (///analysis.info ///version.version target))]]
[(dictionary.merge (luxD.bundle expander host-analysis program extender)
host-directive-bundle)
{#///directive.analysis {#///directive.state analysis-state
@@ -280,9 +272,3 @@
temporary-payload (..get-current-payload temporary-payload)]
(..iterate archive expander module source temporary-payload (..module-aliases analysis-module))))))})]))
)))))}))))
-
-(def: #export key
- (Key .Module)
- (key.key {#signature.name (name-of ..compiler)
- #signature.version ///version.version}
- (module.new 0)))
diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux
index 58a2d4b32..7707a154c 100644
--- a/stdlib/source/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/lux/tool/compiler/default/platform.lux
@@ -7,9 +7,7 @@
[control
["." try (#+ Try)]
[concurrency
- ["." promise (#+ Promise) ("#@." monad)]]
- ["<>" parser
- ["<b>" binary (#+ Parser)]]]
+ ["." promise (#+ Promise) ("#@." monad)]]]
[data
["." binary (#+ Binary)]
["." bit]
@@ -35,10 +33,7 @@
["#." generation (#+ Buffer)]
["#." directive]
[phase
- ## TODO: Get rid of this import ASAP
- ["." extension (#+ Extender)]
- [analysis
- ["." module]]]]]
+ [extension (#+ Extender)]]]]
[meta
["." archive (#+ Archive)
["." descriptor (#+ Descriptor Module)]
@@ -76,11 +71,6 @@
(_.and descriptor.writer
(document.writer $.writer)))
- (def: parser
- (Parser [Descriptor (Document .Module)])
- (<>.and descriptor.parser
- (document.parser $.parser)))
-
(def: (cache-module platform host target-dir module-file-name module-id extension [[descriptor document] output])
(All <type-vars>
(-> <Platform> Host Path Path archive.ID Text [[Descriptor (Document Any)] Output]
@@ -96,26 +86,10 @@
(monad.map ..monad write-artifact!)
(: (Action (List Any))))
document (:: promise.monad wrap
- (document.check //init.key document))]
+ (document.check $.key document))]
(ioW.cache system host target-dir module-id
(_.run ..writer [descriptor document])))))
- (def: (load-cache system host target-dir archive)
- (All <type-vars>
- (-> (file.System Promise) Host Path Archive (Promise (Try Archive))))
- (do (try.with promise.monad)
- [all-loaded-caches (|> (archive.reservations archive)
- (monad.map @ (function (_ [module-name module-id])
- (do @
- [data (ioW.load system host target-dir module-id)
- payload (promise@wrap (<b>.run ..parser data))]
- (wrap [module-name payload])))))]
- (promise@wrap (monad.fold try.monad
- (function (_ [module descriptor+document] archive)
- (archive.add module descriptor+document archive))
- archive
- all-loaded-caches))))
-
## TODO: Inline ASAP
(def: initialize-buffer!
(All <type-vars>
@@ -128,9 +102,10 @@
(-> <Platform> (///generation.Operation anchor expression directive Any)))
(get@ #runtime))
- (def: #export (initialize target host module expander host-analysis platform generation-bundle host-directive-bundle program extender)
+ (def: #export (initialize extension target host module expander host-analysis platform generation-bundle host-directive-bundle program extender)
(All <type-vars>
- (-> Path
+ (-> Text
+ Path
Host
Module
Expander
@@ -153,42 +128,18 @@
extender)]
(do (try.with promise.monad)
[_ (ioW.enable (get@ #&file-system platform) host target)
- archive (ioW.thaw (get@ #&file-system platform) host target)
- archive (load-cache (get@ #&file-system platform) host target archive)]
+ [archive analysis-state] (ioW.thaw extension (get@ #host platform) (get@ #&file-system platform) host target)]
(|> (do ///phase.monad
- [_ ..initialize-buffer!
- _ (..compile-runtime! platform)
- buffer ///generation.buffer]
- (wrap [archive buffer]))
- ///directive.lift-generation
+ [_ (///directive.lift-analysis
+ (///analysis.install analysis-state))]
+ (///directive.lift-generation
+ (do ///phase.monad
+ [_ ..initialize-buffer!
+ _ (..compile-runtime! platform)
+ buffer ///generation.buffer]
+ (wrap [archive buffer]))))
(///phase.run' state)
- promise@wrap)))
-
- ## (case (runtimeT.generate ## (initL.compiler (io.run js.init))
- ## (initL.compiler (io.run hostL.init-host))
- ## )
- ## ## (#try.Success [state disk-write])
- ## ## (do @
- ## ## [_ (&io.prepare-target target)
- ## ## _ disk-write
- ## ## ## _ (cache/io.pre-load sources target (commonT.load-definition state))
- ## ## ]
- ## ## (wrap (|> state
- ## ## (set@ [#.info #.mode] #.Build))))
-
- ## (#try.Success [state [runtime-bc function-bc]])
- ## (do @
- ## [_ (&io.prepare-target target)
- ## ## _ (&io.write target (format hostL.runtime-class ".class") runtime-bc)
- ## ## _ (&io.write target (format hostL.function-class ".class") function-bc)
- ## ## _ (cache/io.pre-load sources target (commonT.load-definition state))
- ## ]
- ## (wrap (|> state
- ## (set@ [#.info #.mode] #.Build))))
-
- ## (#try.Failure error)
- ## (io.fail error))
- )
+ promise@wrap))))
(def: #export (compile target partial-host-extension expander platform host configuration archive extension state)
(All <type-vars>
@@ -198,7 +149,7 @@
{<State+>
state}
{(///.Compiler <State+> .Module Any)
- ((//init.compiler expander syntax.prelude (get@ #write platform)) //init.key (list))})]
+ ((//init.compiler expander syntax.prelude (get@ #write platform)) $.key (list))})]
(loop [module source-module
[archive state] [archive state]]
(if (archive.archived? archive module)
diff --git a/stdlib/source/lux/tool/compiler/language/lux.lux b/stdlib/source/lux/tool/compiler/language/lux.lux
index f823c1eaf..d300ec243 100644
--- a/stdlib/source/lux/tool/compiler/language/lux.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux.lux
@@ -5,7 +5,17 @@
["<b>" binary (#+ Parser)]]]
[data
[format
- ["_" binary (#+ Writer)]]]])
+ ["_" binary (#+ Writer)]]]]
+ ["." / #_
+ ["#." version]
+ [phase
+ [analysis
+ ["." module]]]
+ [///
+ [meta
+ [archive
+ ["." signature]
+ ["." key (#+ Key)]]]]])
## TODO: Remove #module-hash, #imports & #module-state ASAP.
## TODO: Not just from this parser, but from the lux.Module type.
@@ -88,3 +98,9 @@
(<b>.maybe <b>.code)
## #module-state
(:: <>.monad wrap #.Cached))))
+
+(def: #export key
+ (Key .Module)
+ (key.key {#signature.name (name-of ..compiler)
+ #signature.version /version.version}
+ (module.new 0)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/lux/tool/compiler/language/lux/analysis.lux
index 8537064a4..59a1cf2eb 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/analysis.lux
@@ -352,6 +352,12 @@
(let [[bundle state] bundle,state]
(#try.Failure (locate-error (get@ #.cursor state) error))))))
+(def: #export (install state)
+ (-> .Lux (Operation Any))
+ (function (_ [bundle _])
+ (#try.Success [[bundle state]
+ []])))
+
(template [<name> <type> <field> <value>]
[(def: #export (<name> value)
(-> <type> (Operation Any))
@@ -380,8 +386,14 @@
#.var-counter 0
#.var-bindings (list)})
-(def: #export (state info host)
- (-> Info Any Lux)
+(def: #export (info version host)
+ (-> Text Text Info)
+ {#.target host
+ #.version version
+ #.mode #.Build})
+
+(def: #export (state info)
+ (-> Info Lux)
{#.info info
#.source ..dummy-source
#.cursor .dummy-cursor
@@ -393,4 +405,4 @@
#.seed 0
#.scope-type-vars (list)
#.extensions []
- #.host host})
+ #.host []})
diff --git a/stdlib/source/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/lux/tool/compiler/language/lux/generation.lux
index b428a851d..e787b032d 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/generation.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/generation.lux
@@ -7,6 +7,7 @@
["." exception (#+ exception:)]
["." function]]
[data
+ [binary (#+ Binary)]
["." product]
["." name ("#@." equivalence)]
["." text ("#@." equivalence)
@@ -49,7 +50,14 @@
(: (-> Text directive (Try Any))
execute!)
(: (-> Context expression (Try [Text Any directive]))
- define!))
+ define!)
+
+ (: (-> Context Binary directive)
+ ingest)
+ (: (-> Context directive (Try Any))
+ re-learn)
+ (: (-> Context directive (Try Any))
+ re-load))
(type: #export (State anchor expression directive)
{#module Module
diff --git a/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux
index 28f01bbcb..cae8c34dc 100644
--- a/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux
+++ b/stdlib/source/lux/tool/compiler/meta/archive/artifact.lux
@@ -19,7 +19,7 @@
(type: #export ID Nat)
-(type: Artifact
+(type: #export Artifact
{#id ID
#name (Maybe Text)})
@@ -34,9 +34,13 @@
(:abstraction {#artifacts row.empty
#resolver (dictionary.new text.hash)}))
+ (def: #export artifacts
+ (-> Registry (Row Artifact))
+ (|>> :representation (get@ #artifacts)))
+
(def: next
(-> Registry ID)
- (|>> :representation (get@ #artifacts) row.size))
+ (|>> ..artifacts row.size))
(def: #export (resource registry)
(-> Registry [ID Registry])
diff --git a/stdlib/source/lux/tool/compiler/meta/io.lux b/stdlib/source/lux/tool/compiler/meta/io.lux
index 271dcb79a..11faee222 100644
--- a/stdlib/source/lux/tool/compiler/meta/io.lux
+++ b/stdlib/source/lux/tool/compiler/meta/io.lux
@@ -1,5 +1,5 @@
(.module:
- [lux (#- Module Code)
+ [lux (#- Code)
[data
["." text]]
[world
@@ -7,8 +7,6 @@
(type: #export Context Path)
-(type: #export Module Text)
-
(type: #export Code Text)
(def: #export (sanitize system)
diff --git a/stdlib/source/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/lux/tool/compiler/meta/io/archive.lux
index a40c8427f..c6865ebc1 100644
--- a/stdlib/source/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/lux/tool/compiler/meta/io/archive.lux
@@ -2,23 +2,39 @@
[lux (#- Module)
["@" target (#+ Host)]
[abstract
- [monad (#+ do)]]
+ ["." monad (#+ do)]]
[control
["." try (#+ Try)]
["." exception (#+ exception:)]
[concurrency
- ["." promise (#+ Promise)]]
+ ["." promise (#+ Promise) ("#@." monad)]]
[security
- ["!" capability (#+ capability:)]]]
+ ["!" capability (#+ capability:)]]
+ ["<>" parser
+ ["<b>" binary (#+ Parser)]]]
[data
[binary (#+ Binary)]
- ["." text
- ["%" format (#+ format)]]]
+ ["." product]
+ ["." text ("#@." equivalence)
+ ["%" format (#+ format)]]
+ [collection
+ ["." list ("#@." functor)]
+ ["." dictionary (#+ Dictionary)]
+ ["." row (#+ Row)]]]
[world
- ["." file (#+ Path File Directory System)]]]
- ["." // (#+ Module)
+ ["." file (#+ Path File Directory)]]]
+ ["." //
["/#" //
- ["." archive (#+ Archive)]]])
+ ["." archive (#+ Archive)
+ ["." artifact (#+ Artifact)]
+ ["." descriptor (#+ Module Descriptor)]
+ ["." document (#+ Document)]]
+ [//
+ [language
+ ["$" lux
+ ["." version]
+ ["." analysis]
+ ["." generation]]]]]])
(exception: #export (cannot-prepare {archive Path}
{module-id archive.ID}
@@ -29,30 +45,30 @@
["Error" error]))
(def: #export (archive system host root)
- (-> (System Promise) Host Path Path)
+ (-> (file.System Promise) Host Path Path)
(format root (:: system separator) host))
(def: #export (lux-archive system host root)
- (-> (System Promise) Host Path Path)
+ (-> (file.System Promise) Host Path Path)
(format (..archive system host root)
(:: system separator)
//.lux-context))
(def: (module system host root module-id)
- (-> (System Promise) Host Path archive.ID Path)
+ (-> (file.System Promise) Host Path archive.ID Path)
(format (..lux-archive system host root)
(:: system separator)
(%.nat module-id)))
(def: #export (artifact system host root module-id name extension)
- (-> (System Promise) Host Path archive.ID Text Text Path)
+ (-> (file.System Promise) Host Path archive.ID Text Text Path)
(format (..module system host root module-id)
(:: system separator)
name
extension))
(def: #export (prepare system host root module-id)
- (-> (System Promise) Host Path archive.ID (Promise (Try Any)))
+ (-> (file.System Promise) Host Path archive.ID (Promise (Try Any)))
(do promise.monad
[#let [module (..module system host root module-id)]
module-exists? (file.exists? promise.monad system module)]
@@ -71,7 +87,7 @@
error])))))))
(def: #export (write system host root module-id name extension content)
- (-> (System Promise) Host Path archive.ID Text Text Binary (Promise (Try Any)))
+ (-> (file.System Promise) Host Path archive.ID Text Text Binary (Promise (Try Any)))
(do (try.with promise.monad)
[artifact (: (Promise (Try (File Promise)))
(file.get-file promise.monad system
@@ -79,7 +95,7 @@
(!.use (:: artifact over-write) content)))
(def: #export (enable system host root)
- (-> (System Promise) Host Path (Promise (Try Any)))
+ (-> (file.System Promise) Host Path (Promise (Try Any)))
(do (try.with promise.monad)
[_ (: (Promise (Try (Directory Promise)))
(file.get-directory promise.monad system root))
@@ -88,49 +104,166 @@
(wrap [])))
(def: (general-descriptor system host root)
- (-> (System Promise) Host Path Path)
+ (-> (file.System Promise) Host Path Path)
(format (..archive system host root)
(:: system separator)
"general-descriptor"))
(def: #export (freeze system host root archive)
- (-> (System Promise) Host Path Archive (Promise (Try Any)))
+ (-> (file.System Promise) Host Path Archive (Promise (Try Any)))
(do (try.with promise.monad)
[file (: (Promise (Try (File Promise)))
(file.get-file promise.monad system (..general-descriptor system host root)))]
(!.use (:: file over-write) (archive.export ///.version archive))))
-(def: #export (thaw system host root)
- (-> (System Promise) Host Path (Promise (Try Archive)))
- (do promise.monad
- [file (!.use (:: system file) (..general-descriptor system host root))]
- (case file
- (#try.Success file)
- (do (try.with promise.monad)
- [binary (!.use (:: file content) [])]
- (:: promise.monad wrap (archive.import ///.version binary)))
-
- (#try.Failure error)
- (wrap (#try.Success archive.empty)))))
+(def: module-descriptor-file
+ "module-descriptor")
(def: (module-descriptor system host root module-id)
- (-> (System Promise) Host Path archive.ID Path)
+ (-> (file.System Promise) Host Path archive.ID Path)
(format (..module system host root module-id)
(:: system separator)
- "module-descriptor"))
+ ..module-descriptor-file))
(def: #export (cache system host root module-id content)
- (-> (System Promise) Host Path archive.ID Binary (Promise (Try Any)))
+ (-> (file.System Promise) Host Path archive.ID Binary (Promise (Try Any)))
(do (try.with promise.monad)
[file (: (Promise (Try (File Promise)))
(file.get-file promise.monad system
(..module-descriptor system host root module-id)))]
(!.use (:: file over-write) content)))
-(def: #export (load system host root module-id)
- (-> (System Promise) Host Path archive.ID (Promise (Try Binary)))
+(def: (read-module-descriptor system host root module-id)
+ (-> (file.System Promise) Host Path archive.ID (Promise (Try Binary)))
(do (try.with promise.monad)
[file (: (Promise (Try (File Promise)))
(file.get-file promise.monad system
(..module-descriptor system host root module-id)))]
(!.use (:: file content) [])))
+
+(def: parser
+ (Parser [Descriptor (Document .Module)])
+ (<>.and descriptor.parser
+ (document.parser $.parser)))
+
+(def: (fresh-analysis-state host)
+ (-> Host .Lux)
+ (analysis.state (analysis.info version.version host)))
+
+(def: (analysis-state host archive)
+ (-> Host Archive (Try .Lux))
+ (do try.monad
+ [modules (: (Try (List [Module .Module]))
+ (monad.map @ (function (_ module)
+ (do @
+ [[descriptor document] (archive.find module archive)
+ content (document.read $.key document)]
+ (wrap [module content])))
+ (archive.archived archive)))]
+ (wrap (set@ #.modules modules (fresh-analysis-state host)))))
+
+(def: (cached-artifacts system host root module-id)
+ (-> (file.System Promise) Host Path archive.ID (Promise (Try (Dictionary Text Binary))))
+ (do (try.with promise.monad)
+ [module-dir (!.use (:: system directory) (..module system host root module-id))
+ cached-files (!.use (:: module-dir files) [])]
+ (|> cached-files
+ (list@map (function (_ file)
+ [(!.use (:: file name) [])
+ (!.use (:: file path) [])]))
+ (list.filter (|>> product.left (text@= ..module-descriptor-file) not))
+ (monad.map @ (function (_ [name path])
+ (do @
+ [file (: (Promise (Try (File Promise)))
+ (!.use (:: system file) path))
+ data (: (Promise (Try Binary))
+ (!.use (:: file content) []))]
+ (wrap [name data]))))
+ (:: @ map (dictionary.from-list text.hash)))))
+
+(def: (loaded-document extension host module-id expected actual document)
+ (All [expression directive]
+ (-> Text (generation.Host expression directive) archive.ID (Row Artifact) (Dictionary Text Binary) (Document .Module)
+ (Try (Document .Module))))
+ (do try.monad
+ [values (|> expected
+ row.to-list
+ (monad.fold @ (function (_ [artifact-id artifact-name] values)
+ (do @
+ [data (try.from-maybe (dictionary.get (format (%.nat artifact-id) extension) actual))
+ #let [context [module-id artifact-id]
+ directive (:: host ingest context data)]]
+ (case artifact-name
+ #.None
+ (do @
+ [_ (:: host re-learn context directive)]
+ (wrap values))
+
+ (#.Some artifact-name)
+ (do @
+ [value (:: host re-load context directive)]
+ (wrap (dictionary.put artifact-name value values))))))
+ (: (Dictionary Text Any)
+ (dictionary.new text.hash))))
+ content (document.read $.key document)
+ definitions (monad.map @ (function (_ [def-name def-global])
+ (case def-global
+ (#.Alias alias)
+ (wrap [def-name (#.Alias alias)])
+
+ (#.Definition [exported? type annotations _])
+ (do @
+ [value (try.from-maybe (dictionary.get def-name values))]
+ (wrap [def-name (#.Definition [exported? type annotations value])]))))
+ (get@ #.definitions content))]
+ (wrap (document.write $.key (set@ #.definitions definitions content)))))
+
+(def: (load-definitions system host root module-id extension host-environment [descriptor document])
+ (All [expression directive]
+ (-> (file.System Promise) Host Path archive.ID Text (generation.Host expression directive)
+ [Descriptor (Document .Module)]
+ (Promise (Try [Descriptor (Document .Module)]))))
+ (do (try.with promise.monad)
+ [actual (cached-artifacts system host root module-id)
+ #let [expected (|> descriptor (get@ #descriptor.registry) artifact.artifacts)]
+ document (promise@wrap (loaded-document extension host-environment module-id expected actual document))]
+ (wrap [descriptor document])))
+
+(def: (load-every-reserved-module extension host-environment system host root archive)
+ (All [expression directive]
+ (-> Text (generation.Host expression directive) (file.System Promise) Host Path Archive (Promise (Try [Archive .Lux]))))
+ (do (try.with promise.monad)
+ [all-loaded-caches (|> archive
+ archive.reservations
+ (monad.map @ (function (_ [module-name module-id])
+ (do @
+ [data (..read-module-descriptor system host root module-id)
+ descriptor,document (promise@wrap (<b>.run ..parser data))
+ descriptor,document (load-definitions system host root module-id extension host-environment descriptor,document)]
+ (wrap [module-name descriptor,document])))))]
+ (promise@wrap
+ (do try.monad
+ [archive (monad.fold try.monad
+ (function (_ [module descriptor+document] archive)
+ (archive.add module descriptor+document archive))
+ archive
+ all-loaded-caches)
+ analysis-state (..analysis-state host archive)]
+ (wrap [archive
+ analysis-state])))))
+
+(def: #export (thaw extension host-environment system host root)
+ (All [expression directive]
+ (-> Text (generation.Host expression directive) (file.System Promise) Host Path (Promise (Try [Archive .Lux]))))
+ (do promise.monad
+ [file (!.use (:: system file) (..general-descriptor system host root))]
+ (case file
+ (#try.Success file)
+ (do (try.with promise.monad)
+ [binary (!.use (:: file content) [])
+ archive (promise@wrap (archive.import ///.version binary))]
+ (..load-every-reserved-module extension host-environment system host root archive))
+
+ (#try.Failure error)
+ (wrap (#try.Success [archive.empty
+ (fresh-analysis-state host)])))))