diff options
author | Eduardo Julian | 2020-12-29 00:38:21 -0400 |
---|---|---|
committer | Eduardo Julian | 2020-12-29 00:38:21 -0400 |
commit | 832a9361b632331e82a64c07baa560487ca8abde (patch) | |
tree | 5fec882399315def4d789ecef1746d90e761df93 /stdlib/source/program | |
parent | 92dca9f487c625d27f6c291784ef709b0cc13a72 (diff) |
Moved "lux/data/number" to "lux/math/number".
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/program/aedifex.lux | 8 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/command/build.lux | 3 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/command/deploy.lux | 5 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/command/test.lux | 3 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/dependency/resolution.lux | 14 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/hash.lux | 7 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/metadata/artifact.lux | 5 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/metadata/snapshot.lux | 5 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/parser.lux | 3 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/pom.lux | 3 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/profile.lux | 3 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/repository.lux | 133 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/repository/remote.lux | 138 | ||||
-rw-r--r-- | stdlib/source/program/compositor.lux | 54 | ||||
-rw-r--r-- | stdlib/source/program/compositor/static.lux | 4 |
15 files changed, 206 insertions, 182 deletions
diff --git a/stdlib/source/program/aedifex.lux b/stdlib/source/program/aedifex.lux index 67c4e89f3..6a4deb3c3 100644 --- a/stdlib/source/program/aedifex.lux +++ b/stdlib/source/program/aedifex.lux @@ -44,10 +44,10 @@ ["#." parser] ["#." pom] ["#." cli] - ["#." cache] - ["#." repository (#+ Address Repository)] ["#." dependency #_ ["#" resolution (#+ Resolution)]] + ["#." repository (#+ Repository) + ["#/." remote (#+ Address)]] ["#." command (#+ Command) ["#/." version] ["#/." clean] @@ -63,7 +63,7 @@ (-> /.Profile (List (Repository Promise))) (|>> (get@ #/.repositories) set.to_list - (list\map (|>> (/repository.remote #.None) /repository.async)))) + (list\map (|>> (/repository/remote.repository #.None) /repository.async)))) (def: (with_dependencies program console command profile) (All [a] @@ -149,7 +149,7 @@ (dictionary.get repository (get@ #/.deploy_repositories profile))] [(#.Some artifact) (#.Some repository)] (/command/deploy.do! console - (/repository.async (/repository.remote (#.Some identity) repository)) + (/repository.async (/repository/remote.repository (#.Some identity) repository)) (file.async file.default) artifact profile) diff --git a/stdlib/source/program/aedifex/command/build.lux b/stdlib/source/program/aedifex/command/build.lux index cb4465edd..a05d7ad85 100644 --- a/stdlib/source/program/aedifex/command/build.lux +++ b/stdlib/source/program/aedifex/command/build.lux @@ -18,7 +18,8 @@ [collection ["." list ("#\." functor)] ["." dictionary] - ["." set]] + ["." set]]] + [math [number ["i" int]]] [world diff --git a/stdlib/source/program/aedifex/command/deploy.lux b/stdlib/source/program/aedifex/command/deploy.lux index 1f84567f0..b00f964d7 100644 --- a/stdlib/source/program/aedifex/command/deploy.lux +++ b/stdlib/source/program/aedifex/command/deploy.lux @@ -37,7 +37,8 @@ ["#." pom] ["#." hash] ["#." repository (#+ Repository) - [identity (#+ Identity)]] + [identity (#+ Identity)] + ["#/." remote]] ["#." metadata ["#/." artifact] ["#/." snapshot]] @@ -93,7 +94,7 @@ (def: #export (do! console repository fs artifact profile) (-> (Console Promise) (Repository Promise) (file.System Promise) Artifact (Command Any)) (let [deploy! (: (-> Extension Binary (Action Any)) - (|>> (///repository.uri artifact) + (|>> (///repository/remote.uri artifact) (\ repository upload))) fully_deploy! (: (-> Extension Binary (Action Any)) (function (_ extension payload) diff --git a/stdlib/source/program/aedifex/command/test.lux b/stdlib/source/program/aedifex/command/test.lux index 2727fc461..dff9b14ee 100644 --- a/stdlib/source/program/aedifex/command/test.lux +++ b/stdlib/source/program/aedifex/command/test.lux @@ -9,7 +9,8 @@ ["!" capability]]] [data [text - ["%" format (#+ format)]] + ["%" format (#+ format)]]] + [math [number ["i" int]]] [world diff --git a/stdlib/source/program/aedifex/dependency/resolution.lux b/stdlib/source/program/aedifex/dependency/resolution.lux index e9d457ac9..1b40a3004 100644 --- a/stdlib/source/program/aedifex/dependency/resolution.lux +++ b/stdlib/source/program/aedifex/dependency/resolution.lux @@ -19,14 +19,15 @@ [text ["%" format (#+ format)] ["." encoding]] - [number - ["." i64] - ["n" nat]] [format ["." xml (#+ Tag XML)]] [collection ["." dictionary (#+ Dictionary)] ["." set]]] + [math + [number + ["n" nat] + ["." i64]]] [world [net (#+ URL) ["." uri]]]] @@ -39,7 +40,8 @@ ["#." package (#+ Package)] ["#." artifact (#+ Artifact) ["#/." extension (#+ Extension)]] - ["#." repository (#+ Address Repository) + ["#." repository (#+ Repository) + ["#/." remote (#+ Address)] ["#/." origin (#+ Origin)]]]]) (template [<name>] @@ -60,7 +62,7 @@ (Exception [Artifact Extension Text]) (Promise (Try (Hash h))))) (do (try.with promise.monad) - [actual (\ repository download (///repository.uri artifact extension))] + [actual (\ repository download (///repository/remote.uri artifact extension))] (\ promise.monad wrap (do try.monad [output (\ encoding.utf8 decode actual) @@ -72,7 +74,7 @@ (def: (hashed repository artifact extension) (-> (Repository Promise) Artifact Extension (Promise (Try [Binary Status]))) (do (try.with promise.monad) - [data (\ repository download (///repository.uri artifact extension)) + [data (\ repository download (///repository/remote.uri artifact extension)) sha-1 (..verified_hash data repository artifact (format extension ///artifact/extension.sha-1) ///hash.sha-1 ///hash.sha-1_codec ..sha-1_does_not_match) diff --git a/stdlib/source/program/aedifex/hash.lux b/stdlib/source/program/aedifex/hash.lux index 2c0c6df25..336d9bc96 100644 --- a/stdlib/source/program/aedifex/hash.lux +++ b/stdlib/source/program/aedifex/hash.lux @@ -12,10 +12,11 @@ ["." binary (#+ Binary)] ["." text ["%" format (#+ Format format)] - ["." encoding]] + ["." encoding]]] + [math [number - ["." i64] - ["n" nat]]] + ["n" nat] + ["." i64]]] [type abstract]]) diff --git a/stdlib/source/program/aedifex/metadata/artifact.lux b/stdlib/source/program/aedifex/metadata/artifact.lux index cf9a34b58..5762bf49d 100644 --- a/stdlib/source/program/aedifex/metadata/artifact.lux +++ b/stdlib/source/program/aedifex/metadata/artifact.lux @@ -11,12 +11,13 @@ ["." product] ["." text ["%" format (#+ format)]] - [number - ["n" nat]] [format ["." xml (#+ XML)]] [collection ["." list ("#\." functor)]]] + [math + [number + ["n" nat]]] ["." time (#+ Time) ["." instant (#+ Instant)] ["." date (#+ Date)] diff --git a/stdlib/source/program/aedifex/metadata/snapshot.lux b/stdlib/source/program/aedifex/metadata/snapshot.lux index ea6ce4719..38af9a729 100644 --- a/stdlib/source/program/aedifex/metadata/snapshot.lux +++ b/stdlib/source/program/aedifex/metadata/snapshot.lux @@ -12,12 +12,13 @@ ["." product] ["." text ["%" format (#+ format)]] - [number - ["n" nat]] [format ["." xml (#+ XML)]] [collection ["." list ("#\." functor)]]] + [math + [number + ["n" nat]]] ["." time (#+ Time) ["." instant (#+ Instant)] ["." date (#+ Date)] diff --git a/stdlib/source/program/aedifex/parser.lux b/stdlib/source/program/aedifex/parser.lux index 8f95cc6a4..4a21b341a 100644 --- a/stdlib/source/program/aedifex/parser.lux +++ b/stdlib/source/program/aedifex/parser.lux @@ -21,7 +21,8 @@ ["/" profile] ["#." project (#+ Project)] ["#." dependency] - ["#." repository] + ["#." repository #_ + ["#" remote]] ["#." artifact (#+ Artifact) ["#/." type]]]) diff --git a/stdlib/source/program/aedifex/pom.lux b/stdlib/source/program/aedifex/pom.lux index d1787d07c..f085e2808 100644 --- a/stdlib/source/program/aedifex/pom.lux +++ b/stdlib/source/program/aedifex/pom.lux @@ -19,8 +19,9 @@ ["." dictionary]]]] ["." // #_ ["/" profile] - ["#." repository (#+ Address)] ["#." dependency (#+ Dependency)] + [repository + [remote (#+ Address)]] ["#." artifact (#+ Artifact) ["#/." type]]]) diff --git a/stdlib/source/program/aedifex/profile.lux b/stdlib/source/program/aedifex/profile.lux index adf1b049e..fa49e41cd 100644 --- a/stdlib/source/program/aedifex/profile.lux +++ b/stdlib/source/program/aedifex/profile.lux @@ -24,7 +24,8 @@ [// ["." artifact (#+ Artifact)] ["." dependency] - ["." repository]]) + ["." repository #_ + ["#" remote (#+ Address)]]]) (type: #export Distribution #Repo diff --git a/stdlib/source/program/aedifex/repository.lux b/stdlib/source/program/aedifex/repository.lux index 582144ad4..230888cef 100644 --- a/stdlib/source/program/aedifex/repository.lux +++ b/stdlib/source/program/aedifex/repository.lux @@ -1,38 +1,18 @@ (.module: [lux #* - ["." host (#+ import:)] [abstract [monad (#+ do)]] [control - ["." io (#+ IO)] + [io (#+ IO)] ["." try (#+ Try)] - ["." exception (#+ exception:)] [concurrency ["." promise (#+ Promise)] ["." stm]]] [data - ["." binary (#+ Binary)] - ["." text - ["%" format (#+ format)]] - [number - ["n" nat]]] - [tool - [compiler - ["." version] - ["." language #_ - ["#/." lux #_ - ["#" version]]]]] + [binary (#+ Binary)]] [world - [net (#+ URL) - ["." uri (#+ URI)]]]] - ["." / #_ - ["#." identity (#+ Identity)] - ["/#" // #_ - ["#." artifact (#+ Artifact) - ["#/." extension (#+ Extension)]]]]) - -(type: #export Address - URL) + [net + [uri (#+ URI)]]]]) (signature: #export (Repository !) (: (-> URI (! (Try Binary))) @@ -86,108 +66,3 @@ (#try.Failure error) (wrap (#try.Failure error)))))) ))) - -(import: java/lang/String) - -(import: java/lang/AutoCloseable - ["#::." - (close [] #io #try void)]) - -(import: java/io/InputStream) - -(import: java/io/OutputStream - ["#::." - (flush [] #io #try void) - (write [[byte]] #io #try void)]) - -(import: java/net/URLConnection - ["#::." - (setDoOutput [boolean] #io #try void) - (setRequestProperty [java/lang/String java/lang/String] #io #try void) - (getInputStream [] #io #try java/io/InputStream) - (getOutputStream [] #io #try java/io/OutputStream)]) - -(import: java/net/HttpURLConnection - ["#::." - (setRequestMethod [java/lang/String] #io #try void) - (getResponseCode [] #io #try int)]) - -(import: java/net/URL - ["#::." - (new [java/lang/String]) - (openConnection [] #io #try java/net/URLConnection)]) - -(import: java/io/BufferedInputStream - ["#::." - (new [java/io/InputStream]) - (read [[byte] int int] #io #try int)]) - -(exception: #export (no_credentials {address Address}) - (exception.report - ["Address" (%.text address)])) - -(exception: #export (deployment_failure {code Int}) - (exception.report - ["Code" (%.int code)])) - -(def: #export (uri artifact extension) - (-> Artifact Extension URI) - (format (//artifact.uri artifact) extension)) - -(def: buffer_size - (n.* 512 1,024)) - -(def: user_agent - (format "LuxAedifex/" (version.format language/lux.version))) - -(structure: #export (remote identity address) - (All [s] (-> (Maybe Identity) Address (Repository IO))) - - (def: (download uri) - (do {! (try.with io.monad)} - [connection (|> (format address uri) - java/net/URL::new - java/net/URL::openConnection) - #let [connection (:coerce java/net/HttpURLConnection connection)] - _ (java/net/HttpURLConnection::setRequestMethod "GET" connection) - _ (java/net/URLConnection::setRequestProperty "User-Agent" ..user_agent connection) - input (|> connection - java/net/URLConnection::getInputStream - (\ ! map (|>> java/io/BufferedInputStream::new))) - #let [buffer (binary.create ..buffer_size)]] - (loop [output (\ binary.monoid identity)] - (do ! - [bytes_read (java/io/BufferedInputStream::read buffer +0 (.int ..buffer_size) input)] - (case bytes_read - -1 (do ! - [_ (java/lang/AutoCloseable::close input)] - (wrap output)) - _ (if (n.= ..buffer_size bytes_read) - (recur (\ binary.monoid compose output buffer)) - (do ! - [chunk (\ io.monad wrap (binary.slice 0 (.nat bytes_read) buffer))] - (recur (\ binary.monoid compose output chunk))))))))) - - (def: (upload uri content) - (case identity - #.None - (\ io.monad wrap (exception.throw ..no_credentials [address])) - - (#.Some [user password]) - (do (try.with io.monad) - [connection (|> (format address uri) - java/net/URL::new - java/net/URL::openConnection) - #let [connection (:coerce java/net/HttpURLConnection connection)] - _ (java/net/HttpURLConnection::setRequestMethod "PUT" connection) - _ (java/net/URLConnection::setDoOutput true connection) - _ (java/net/URLConnection::setRequestProperty "Authorization" (/identity.basic_auth user password) connection) - stream (java/net/URLConnection::getOutputStream connection) - _ (java/io/OutputStream::write content stream) - _ (java/io/OutputStream::flush stream) - _ (java/lang/AutoCloseable::close stream) - code (java/net/HttpURLConnection::getResponseCode connection)] - (case code - +201 (wrap []) - _ (\ io.monad wrap (exception.throw ..deployment_failure [code])))))) - ) diff --git a/stdlib/source/program/aedifex/repository/remote.lux b/stdlib/source/program/aedifex/repository/remote.lux new file mode 100644 index 000000000..4979e5429 --- /dev/null +++ b/stdlib/source/program/aedifex/repository/remote.lux @@ -0,0 +1,138 @@ +(.module: + [lux #* + [host (#+ import:)] + [abstract + [monad (#+ do)]] + [control + ["." io (#+ IO)] + ["." try] + ["." exception (#+ exception:)]] + [data + ["." binary] + ["." text + ["%" format (#+ format)]]] + [math + [number + ["n" nat]]] + [tool + [compiler + ["." version] + ["." language #_ + ["#/." lux #_ + ["#" version]]]]] + [world + [net (#+ URL) + [uri (#+ URI)]]]] + ["." // + ["#." identity (#+ Identity)] + ["/#" // #_ + ["#." artifact (#+ Artifact) + [extension (#+ Extension)]]]]) + +(type: #export Address + URL) + +(import: java/lang/String) + +(import: java/lang/AutoCloseable + ["#::." + (close [] #io #try void)]) + +(import: java/io/InputStream) + +(import: java/io/OutputStream + ["#::." + (flush [] #io #try void) + (write [[byte]] #io #try void)]) + +(import: java/net/URLConnection + ["#::." + (setDoOutput [boolean] #io #try void) + (setRequestProperty [java/lang/String java/lang/String] #io #try void) + (getInputStream [] #io #try java/io/InputStream) + (getOutputStream [] #io #try java/io/OutputStream)]) + +(import: java/net/HttpURLConnection + ["#::." + (setRequestMethod [java/lang/String] #io #try void) + (getResponseCode [] #io #try int)]) + +(import: java/net/URL + ["#::." + (new [java/lang/String]) + (openConnection [] #io #try java/net/URLConnection)]) + +(import: java/io/BufferedInputStream + ["#::." + (new [java/io/InputStream]) + (read [[byte] int int] #io #try int)]) + +(exception: #export (no_credentials {address Address}) + (exception.report + ["Address" (%.text address)])) + +(exception: #export (deployment_failure {code Int}) + (exception.report + ["Code" (%.int code)])) + +(def: #export (uri artifact extension) + (-> Artifact Extension URI) + (format (///artifact.uri artifact) extension)) + +(def: buffer_size + (n.* 512 1,024)) + +(def: user_agent + (format "LuxAedifex/" (version.format language/lux.version))) + +(structure: #export (repository identity address) + (All [s] (-> (Maybe Identity) Address (//.Repository IO))) + + (def: (download uri) + (do {! (try.with io.monad)} + [connection (|> (format address uri) + java/net/URL::new + java/net/URL::openConnection) + #let [connection (:coerce java/net/HttpURLConnection connection)] + _ (java/net/HttpURLConnection::setRequestMethod "GET" connection) + _ (java/net/URLConnection::setRequestProperty "User-Agent" ..user_agent connection) + input (|> connection + java/net/URLConnection::getInputStream + (\ ! map (|>> java/io/BufferedInputStream::new))) + #let [buffer (binary.create ..buffer_size)]] + (loop [output (\ binary.monoid identity)] + (do ! + [bytes_read (java/io/BufferedInputStream::read buffer +0 (.int ..buffer_size) input)] + (case bytes_read + -1 (do ! + [_ (java/lang/AutoCloseable::close input)] + (wrap output)) + _ (if (n.= ..buffer_size bytes_read) + (recur (\ binary.monoid compose output buffer)) + (do ! + [chunk (\ io.monad wrap (binary.slice 0 (.nat bytes_read) buffer))] + (recur (\ binary.monoid compose output chunk))))))))) + + (def: (upload uri content) + (case identity + #.None + (\ io.monad wrap (exception.throw ..no_credentials [address])) + + (#.Some [user password]) + (do (try.with io.monad) + [connection (|> (format address uri) + java/net/URL::new + java/net/URL::openConnection) + #let [connection (:coerce java/net/HttpURLConnection connection)] + _ (java/net/HttpURLConnection::setRequestMethod "PUT" connection) + _ (java/net/URLConnection::setDoOutput true connection) + _ (java/net/URLConnection::setRequestProperty "Authorization" (//identity.basic_auth user password) connection) + stream (java/net/URLConnection::getOutputStream connection) + _ (java/io/OutputStream::write content stream) + _ (java/io/OutputStream::flush stream) + _ (java/lang/AutoCloseable::close stream) + code (java/net/HttpURLConnection::getResponseCode connection)] + (case code + +201 (wrap []) + _ (\ io.monad wrap (exception.throw ..deployment_failure [code])))))) + ) diff --git a/stdlib/source/program/compositor.lux b/stdlib/source/program/compositor.lux index fdd985f2a..6c1a9202c 100644 --- a/stdlib/source/program/compositor.lux +++ b/stdlib/source/program/compositor.lux @@ -57,54 +57,54 @@ ["#." export] ["#." import]]) -(def: (or-crash! failure-description action) +(def: (or_crash! failure_description action) (All [a] (-> Text (Promise (Try a)) (Promise a))) (do promise.monad [?output action] (case ?output (#try.Failure error) - (exec (log! (format text.new-line - failure-description text.new-line - error text.new-line)) + (exec (log! (format text.new_line + failure_description text.new_line + error text.new_line)) (io.run (\ world/program.default exit +1))) (#try.Success output) (wrap output)))) -(def: (package! monad file-system [packager package] static archive context) +(def: (package! monad file_system [packager package] static archive context) (All [!] (-> (Monad !) (file.System !) [Packager Path] Static Archive Context (! (Try Any)))) (for {@.old (do (try.with monad) [#let [packager (:share [!] {(Monad !) monad} {(Packager !) packager})] - content (packager monad file-system static archive context) + content (packager monad file_system static archive context) package (:share [!] {(Monad !) monad} {(! (Try (File !))) - (:assume (file.get-file monad file-system package))})] + (:assume (file.get_file monad file_system package))})] (!.use (\ (:share [!] {(Monad !) monad} {(File !) (:assume package)}) - over-write) + over_write) [content]))} - ## TODO: Fix whatever type-checker bug is forcing me into this compromise... + ## TODO: Fix whatever type_checker bug is forcing me into this compromise... (:assume (: (Promise (Try Any)) (let [monad (:coerce (Monad Promise) monad) - file-system (:coerce (file.System Promise) file-system) + file_system (:coerce (file.System Promise) file_system) packager (:coerce (Packager Promise) packager)] (do (try.with monad) - [content (packager monad file-system static archive context) + [content (packager monad file_system static archive context) package (: (Promise (Try (File Promise))) - (file.get-file monad file-system package))] - (!.use (\ (: (File Promise) package) over-write) [content]))))))) + (file.get_file monad file_system package))] + (!.use (\ (: (File Promise) package) over_write) [content]))))))) -(with-expansions [<parameters> (as-is anchor expression artifact)] +(with_expansions [<parameters> (as_is anchor expression artifact)] (def: #export (compiler static - expander host-analysis platform generation-bundle host-directive-bundle program anchorT,expressionT,directiveT extender + expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender service packager,package) (All [<parameters>] @@ -124,41 +124,41 @@ [platform (promise.future platform)] (case service (#/cli.Compilation compilation) - (<| (or-crash! "Compilation failed:") + (<| (or_crash! "Compilation failed:") (do (try.with promise.monad) - [#let [[compilation-sources compilation-libraries compilation-target compilation-module] compilation] - import (/import.import (get@ #platform.&file-system platform) compilation-libraries) + [#let [[compilation_sources compilation_libraries compilation_target compilation_module] compilation] + import (/import.import (get@ #platform.&file_system platform) compilation_libraries) [state archive] (:share [<parameters>] {(Platform <parameters>) platform} {(Promise (Try [(directive.State+ <parameters>) Archive])) - (:assume (platform.initialize static compilation-module expander host-analysis platform generation-bundle host-directive-bundle program anchorT,expressionT,directiveT extender - import compilation-sources))}) + (:assume (platform.initialize static compilation_module expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender + import compilation_sources))}) [archive state] (:share [<parameters>] {(Platform <parameters>) platform} {(Promise (Try [Archive (directive.State+ <parameters>)])) (:assume (platform.compile import static expander platform compilation [archive state]))}) - _ (ioW.freeze (get@ #platform.&file-system platform) static archive) - program-context (promise\wrap ($/program.context archive)) - _ (promise.future (..package! io.monad file.default packager,package static archive program-context))] + _ (ioW.freeze (get@ #platform.&file_system platform) static archive) + program_context (promise\wrap ($/program.context archive)) + _ (promise.future (..package! io.monad file.default packager,package static archive program_context))] (wrap (log! "Compilation complete!")))) (#/cli.Export export) - (<| (or-crash! "Export failed:") + (<| (or_crash! "Export failed:") (do (try.with promise.monad) - [_ (/export.export (get@ #platform.&file-system platform) + [_ (/export.export (get@ #platform.&file_system platform) export)] (wrap (log! "Export complete!")))) (#/cli.Interpretation interpretation) ## TODO: Fix the interpreter... (undefined) - ## (<| (or-crash! "Interpretation failed:") + ## (<| (or_crash! "Interpretation failed:") ## (do {! promise.monad} ## [console (|> console.default ## promise.future ## (\ ! map (|>> try.assume console.async)))] - ## (interpreter.run (try.with promise.monad) console platform interpretation generation-bundle))) + ## (interpreter.run (try.with promise.monad) console platform interpretation generation_bundle))) )))) diff --git a/stdlib/source/program/compositor/static.lux b/stdlib/source/program/compositor/static.lux index 3fdd8727e..51bbef0e9 100644 --- a/stdlib/source/program/compositor/static.lux +++ b/stdlib/source/program/compositor/static.lux @@ -6,6 +6,6 @@ (type: #export Static {#host Host - #host-module-extension Text + #host_module_extension Text #target Path - #artifact-extension Text}) + #artifact_extension Text}) |