aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux')
-rw-r--r--stdlib/source/library/lux/data/format/markdown.lux2
-rw-r--r--stdlib/source/library/lux/meta/compiler/default/platform.lux10
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/field/variable/foreign.lux6
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/implementation.lux11
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux2
-rw-r--r--stdlib/source/library/lux/meta/compiler/meta/archive/unit.lux3
-rw-r--r--stdlib/source/library/lux/meta/compiler/meta/cache.lux35
-rw-r--r--stdlib/source/library/lux/meta/compiler/meta/cache/archive.lux20
-rw-r--r--stdlib/source/library/lux/meta/compiler/meta/cache/artifact.lux17
-rw-r--r--stdlib/source/library/lux/meta/compiler/meta/cache/module.lux69
-rw-r--r--stdlib/source/library/lux/meta/compiler/meta/cache/purge.lux17
-rw-r--r--stdlib/source/library/lux/meta/compiler/meta/io/archive.lux8
-rw-r--r--stdlib/source/library/lux/web/css/value.lux2
-rw-r--r--stdlib/source/library/lux/web/html.lux2
14 files changed, 113 insertions, 91 deletions
diff --git a/stdlib/source/library/lux/data/format/markdown.lux b/stdlib/source/library/lux/data/format/markdown.lux
index a45bbf5fd..2aada87ba 100644
--- a/stdlib/source/library/lux/data/format/markdown.lux
+++ b/stdlib/source/library/lux/data/format/markdown.lux
@@ -3,7 +3,7 @@
(.require
[library
- [lux (.except and)
+ [lux (.except and quote)
[data
["[0]" text (.only)
["%" \\format (.only format)]]
diff --git a/stdlib/source/library/lux/meta/compiler/default/platform.lux b/stdlib/source/library/lux/meta/compiler/default/platform.lux
index 488e04e79..17e50c28a 100644
--- a/stdlib/source/library/lux/meta/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/meta/compiler/default/platform.lux
@@ -122,7 +122,7 @@
(cache/artifact.cache! system context @module artifact_id content))))]
(do [! ..monad]
[_ (is (Async (Try Any))
- (cache/module.enable! async.monad system context @module))
+ (cache/module.enable! async.monad system @module))
_ (for @.python (|> entry
(the archive.#output)
sequence.list
@@ -142,7 +142,7 @@
(has module.#document document))
(the archive.#registry entry)]
(_.result (..format format))
- (cache/module.cache! system context @module))))))
+ (cache/module.cache! system @module))))))
... TODO: Inline ASAP
(def initialize_buffer!
@@ -237,7 +237,7 @@
(the #host platform)
(the #phase platform))]
_ (is (Async (Try Any))
- (cache.enable! async.monad (the #file_system platform) context))
+ (cache.enable! async.monad (the #file_system platform)))
[archive analysis_state] (ioW.thaw (list) compilation_configuration (the #host platform) (the #file_system platform) context import compilation_sources)
.let [with_missing_extensions
(is (All (_ <type_vars>)
@@ -652,7 +652,7 @@
[all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)]
[archive _ errors] (after_imports customs import! module duplicates new_dependencies archive)]
(with_expansions [<cache_and_fail> (these (do !
- [_ (cache/archive.cache! (the #file_system platform) configuration context archive)]
+ [_ (cache/archive.cache! (the #file_system platform) configuration archive)]
(async#in {try.#Failure error})))]
(when errors
(list.partial error _)
@@ -719,7 +719,7 @@
[all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)]
[archive state errors] (after_lux_imports customs import! module duplicates new_dependencies [archive state])]
(with_expansions [<cache_and_fail> (these (do !
- [_ (cache/archive.cache! (the #file_system platform) configuration context archive)]
+ [_ (cache/archive.cache! (the #file_system platform) configuration archive)]
(async#in {try.#Failure error})))]
(when errors
(list.partial error _)
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/field/variable/foreign.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/field/variable/foreign.lux
index ec17663b7..c0961eeb8 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/field/variable/foreign.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/field/variable/foreign.lux
@@ -30,7 +30,8 @@
(def .public (closure environment)
(-> (Environment synthesis.Term)
(List (Type Value)))
- (list.repeated (list.size environment) //.type))
+ (list.repeated (list.size environment)
+ //.type))
(def .public (get class register)
(-> (Type Class) Register
@@ -45,4 +46,5 @@
(def .public variables
(-> (Environment synthesis.Term)
(List (Resource Field)))
- (|>> list.size (//.variables /////reference.foreign_name)))
+ (|>> list.size
+ (//.variables /////reference.foreign_name)))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/implementation.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/implementation.lux
index 80491cbe4..c6f954e85 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/implementation.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/function/method/implementation.lux
@@ -34,20 +34,22 @@
(def .public name "impl")
(def .public (type :it: arity)
- (-> (Type Class) Arity (Type category.Method))
+ (-> (Type Class) Arity
+ (Type category.Method))
(type.method [(list)
(list.partial :it: (list.repeated arity ////type.value))
////type.value
(list)]))
-(def modifier
+(def .public modifier
(all modifier#composite
method.static
//.modifier
))
(def .public (method :it: arity @begin body)
- (-> (Type Class) Arity Label (Bytecode Any) (Resource Method))
+ (-> (Type Class) Arity Label (Bytecode Any)
+ (Resource Method))
(method.method ..modifier
..name
false (..type :it: arity)
@@ -59,5 +61,6 @@
)}))
(def .public (call :it: arity)
- (-> (Type Class) Arity (Bytecode Any))
+ (-> (Type Class) Arity
+ (Bytecode Any))
(_.invokestatic :it: ..name (..type :it: arity)))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux
index be90a4867..46a680e92 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux
@@ -24,7 +24,6 @@
["[0]" i32]
["[0]" i64]]]
[meta
- ["[0]" version]
[compiler
[target
["[0]" jvm
@@ -102,7 +101,6 @@
(def .public (class_name [module id])
(-> unit.ID Text)
(format "lux"
- "." (%.nat version.latest)
"." (%.nat module)
"." (%.nat id)))
diff --git a/stdlib/source/library/lux/meta/compiler/meta/archive/unit.lux b/stdlib/source/library/lux/meta/compiler/meta/archive/unit.lux
index 0179f7642..4910524db 100644
--- a/stdlib/source/library/lux/meta/compiler/meta/archive/unit.lux
+++ b/stdlib/source/library/lux/meta/compiler/meta/archive/unit.lux
@@ -29,7 +29,8 @@
(Hash ID)
(all product.hash
nat.hash
- nat.hash))
+ nat.hash
+ ))
(def .public equivalence
(Equivalence ID)
diff --git a/stdlib/source/library/lux/meta/compiler/meta/cache.lux b/stdlib/source/library/lux/meta/compiler/meta/cache.lux
index 17f74ccb8..97e0aa792 100644
--- a/stdlib/source/library/lux/meta/compiler/meta/cache.lux
+++ b/stdlib/source/library/lux/meta/compiler/meta/cache.lux
@@ -8,30 +8,25 @@
[monad (.only Monad do)]]
[control
["[0]" try (.only Try)]]
- [data
- [text
- ["%" \\format (.only format)]]]
[world
- ["[0]" file]]]]
- ["[0]" // (.only)
- ["[0]" context (.only Context)]
- [//
- ["[0]" version]]])
+ ["[0]" file]]]])
-(def .public (path fs context)
- (All (_ !) (-> (file.System !) Context file.Path))
- (let [/ (of fs separator)]
- (format (the context.#host context)
- / (version.format //.version))))
+(def .public path
+ file.Path
+ "cache")
-(def .public (enabled? fs context)
- (All (_ !) (-> (file.System !) Context (! Bit)))
- (of fs directory? (..path fs context)))
+(def .public (enabled? fs)
+ (All (_ !)
+ (-> (file.System !)
+ (! Bit)))
+ (of fs directory? ..path))
-(def .public (enable! ! fs context)
- (All (_ !) (-> (Monad !) (file.System !) Context (! (Try Any))))
+(def .public (enable! ! fs)
+ (All (_ !)
+ (-> (Monad !) (file.System !)
+ (! (Try Any))))
(do !
- [? (..enabled? fs context)]
+ [? (..enabled? fs)]
(if ?
(in {try.#Success []})
- (file.make_directories ! fs (..path fs context)))))
+ (file.make_directories ! fs ..path))))
diff --git a/stdlib/source/library/lux/meta/compiler/meta/cache/archive.lux b/stdlib/source/library/lux/meta/compiler/meta/cache/archive.lux
index 0b48b95dd..fa6f273b3 100644
--- a/stdlib/source/library/lux/meta/compiler/meta/cache/archive.lux
+++ b/stdlib/source/library/lux/meta/compiler/meta/cache/archive.lux
@@ -18,12 +18,16 @@
[context (.only Context)]
["[0]" archive (.only Archive)]]])
-(def .public (descriptor fs context)
- (All (_ !) (-> (file.System !) Context file.Path))
- (%.format (//.path fs context)
- (of fs separator)
- "descriptor"))
+(def .public (descriptor fs)
+ (All (_ !)
+ (-> (file.System !)
+ file.Path))
+ (let [/ (of fs separator)]
+ (%.format //.path
+ / "descriptor")))
-(def .public (cache! fs configuration context it)
- (All (_ !) (-> (file.System !) Configuration Context Archive (! (Try Any))))
- (of fs write (..descriptor fs context) (archive.export ///.version configuration it)))
+(def .public (cache! fs configuration it)
+ (All (_ !)
+ (-> (file.System !) Configuration Archive
+ (! (Try Any))))
+ (of fs write (..descriptor fs) (archive.export ///.version configuration it)))
diff --git a/stdlib/source/library/lux/meta/compiler/meta/cache/artifact.lux b/stdlib/source/library/lux/meta/compiler/meta/cache/artifact.lux
index 55dd3345c..c0e7ecd16 100644
--- a/stdlib/source/library/lux/meta/compiler/meta/cache/artifact.lux
+++ b/stdlib/source/library/lux/meta/compiler/meta/cache/artifact.lux
@@ -27,18 +27,21 @@
(def .public (path fs context @module @artifact)
(All (_ !)
- (-> (file.System !) Context module.ID artifact.ID file.Path))
- (format (//module.path fs context @module)
- (of fs separator)
- (%.nat @artifact)
- (the context.#artifact_extension context)))
+ (-> (file.System !) Context module.ID artifact.ID
+ file.Path))
+ (let [/ (of fs separator)]
+ (format (//module.path fs @module)
+ / (%.nat @artifact)
+ (the context.#artifact_extension context))))
(def .public (cache fs context @module @artifact)
(All (_ !)
- (-> (file.System !) Context module.ID artifact.ID (! (Try Binary))))
+ (-> (file.System !) Context module.ID artifact.ID
+ (! (Try Binary))))
(of fs read (..path fs context @module @artifact)))
(def .public (cache! fs context @module @artifact content)
(All (_ !)
- (-> (file.System !) Context module.ID artifact.ID Binary (! (Try Any))))
+ (-> (file.System !) Context module.ID artifact.ID Binary
+ (! (Try Any))))
(of fs write (..path fs context @module @artifact) content))
diff --git a/stdlib/source/library/lux/meta/compiler/meta/cache/module.lux b/stdlib/source/library/lux/meta/compiler/meta/cache/module.lux
index 050da13ff..50df408fa 100644
--- a/stdlib/source/library/lux/meta/compiler/meta/cache/module.lux
+++ b/stdlib/source/library/lux/meta/compiler/meta/cache/module.lux
@@ -25,7 +25,6 @@
["[0]" file]]]]
["[0]" // (.only)
[//
- [context (.only Context)]
[archive
["[0]" module]]]])
@@ -36,28 +35,34 @@
["Module ID" (%.nat @module)]
["Error" error])))
-(def .public (path fs context @module)
- (All (_ !) (-> (file.System !) Context module.ID file.Path))
- (format (//.path fs context)
- (of fs separator)
- (%.nat @module)))
+(def .public (path fs @module)
+ (All (_ !)
+ (-> (file.System !) module.ID
+ file.Path))
+ (let [/ (of fs separator)]
+ (format //.path
+ / (%.nat @module))))
-(def .public (enabled? fs context @module)
- (All (_ !) (-> (file.System !) Context module.ID (! Bit)))
- (of fs directory? (..path fs context @module)))
+(def .public (enabled? fs @module)
+ (All (_ !)
+ (-> (file.System !) module.ID
+ (! Bit)))
+ (of fs directory? (..path fs @module)))
-(def .public (enable! ! fs context @module)
- (All (_ !) (-> (Monad !) (file.System !) Context module.ID (! (Try Any))))
+(def .public (enable! ! fs @module)
+ (All (_ !)
+ (-> (Monad !) (file.System !) module.ID
+ (! (Try Any))))
(do !
- [.let [path (..path fs context @module)]
+ [.let [path (..path fs @module)]
module_exists? (of fs directory? path)]
(if module_exists?
(in {try.#Success []})
- (with_expansions [<failure> (exception.except ..cannot_enable [(//.path fs context)
+ (with_expansions [<failure> (exception.except ..cannot_enable [//.path
@module
error])]
(do !
- [? (//.enable! ! fs context)]
+ [? (//.enable! ! fs)]
(when ?
{try.#Failure error}
(in <failure>)
@@ -76,24 +81,32 @@
file.Path
"descriptor")
-(def .public (descriptor fs context @module)
- (All (_ !) (-> (file.System !) Context module.ID file.Path))
- (format (..path fs context @module)
- (of fs separator)
- ..file))
+(def .public (descriptor fs @module)
+ (All (_ !)
+ (-> (file.System !) module.ID
+ file.Path))
+ (let [/ (of fs separator)]
+ (format (..path fs @module)
+ / ..file)))
-(def .public (cache! fs context @module content)
- (All (_ !) (-> (file.System !) Context module.ID Binary (! (Try Any))))
- (of fs write (..descriptor fs context @module) content))
+(def .public (cache! fs @module content)
+ (All (_ !)
+ (-> (file.System !) module.ID Binary
+ (! (Try Any))))
+ (of fs write (..descriptor fs @module) content))
-(def .public (cache fs context @module)
- (All (_ !) (-> (file.System !) Context module.ID (! (Try Binary))))
- (of fs read (..descriptor fs context @module)))
+(def .public (cache fs @module)
+ (All (_ !)
+ (-> (file.System !) module.ID
+ (! (Try Binary))))
+ (of fs read (..descriptor fs @module)))
-(def .public (artifacts ! fs context @module)
- (All (_ !) (-> (Monad !) (file.System !) Context module.ID (! (Try (Dictionary Text Binary)))))
+(def .public (artifacts ! fs @module)
+ (All (_ !)
+ (-> (Monad !) (file.System !) module.ID
+ (! (Try (Dictionary Text Binary)))))
(do [! (try.with !)]
- [files (of fs directory_files (..path fs context @module))
+ [files (of fs directory_files (..path fs @module))
pairs (|> files
(list#each (function (_ file)
[(file.name fs file) file]))
diff --git a/stdlib/source/library/lux/meta/compiler/meta/cache/purge.lux b/stdlib/source/library/lux/meta/compiler/meta/cache/purge.lux
index fa3fc4630..769f99958 100644
--- a/stdlib/source/library/lux/meta/compiler/meta/cache/purge.lux
+++ b/stdlib/source/library/lux/meta/compiler/meta/cache/purge.lux
@@ -28,7 +28,6 @@
["[0]" dependency
["[1]" module]]
["/[1]" //
- [context (.only Context)]
["/[1]" // (.only Input)]
["[0]" archive (.only)
[registry (.only Registry)]
@@ -42,10 +41,11 @@
(Dictionary descriptor.Module module.ID))
... TODO: Make the monad parameterizable.
-(def .public (purge! fs context @module)
- (-> (file.System Async) Context module.ID (Async (Try Any)))
+(def .public (purge! fs @module)
+ (-> (file.System Async) module.ID
+ (Async (Try Any)))
(do [! (try.with async.monad)]
- [.let [cache (//module.path fs context @module)]
+ [.let [cache (//module.path fs @module)]
_ (|> cache
(of fs directory_files)
(of ! each (monad.each ! (of fs delete)))
@@ -53,7 +53,8 @@
(of fs delete cache)))
(def .public (valid? expected actual)
- (-> Descriptor Input Bit)
+ (-> Descriptor Input
+ Bit)
(and (text#= (the descriptor.#name expected)
(the ////.#module actual))
(text#= (the descriptor.#file expected)
@@ -62,7 +63,8 @@
(the ////.#hash actual))))
(def initial
- (-> (List Cache) Purge)
+ (-> (List Cache)
+ Purge)
(|>> (list.all (function (_ [valid? module_name @module _])
(if valid?
{.#None}
@@ -70,7 +72,8 @@
(dictionary.of_list text.hash)))
(def .public (purge caches load_order)
- (-> (List Cache) (dependency.Order Any) Purge)
+ (-> (List Cache) (dependency.Order Any)
+ Purge)
(list#mix (function (_ [module_name [@module entry]] purge)
(let [purged? (is (Predicate descriptor.Module)
(dictionary.key? purge))]
diff --git a/stdlib/source/library/lux/meta/compiler/meta/io/archive.lux b/stdlib/source/library/lux/meta/compiler/meta/io/archive.lux
index fd19de547..aff2a0de0 100644
--- a/stdlib/source/library/lux/meta/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/meta/compiler/meta/io/archive.lux
@@ -173,7 +173,7 @@
(Async (Try (archive.Entry .Module)))))
(do (try.with async.monad)
[actual (is (Async (Try (Dictionary Text Binary)))
- (cache/module.artifacts async.monad fs context @module))
+ (cache/module.artifacts async.monad fs @module))
.let [expected (registry.artifacts (the archive.#registry entry))]
[document output] (|> (the [archive.#module module.#document] entry)
(loaded_document (the context.#artifact_extension context) host_environment @module expected actual)
@@ -207,7 +207,7 @@
(with_expansions [<cache> (these module_name @module module registry)]
(do [! (try.with async.monad)]
[data (is (Async (Try Binary))
- (cache/module.cache fs context @module))
+ (cache/module.cache fs @module))
[module registry] (async#in (<binary>.result (..cache_parser customs) data))]
(if (text#= descriptor.runtime module_name)
(in [true <cache>])
@@ -271,7 +271,7 @@
.let [purge (cache/purge.purge pre_loaded_caches load_order)]
_ (|> purge
dictionary.entries
- (monad.each ! (|>> product.right (cache/purge.purge! fs context))))
+ (monad.each ! (|>> product.right (cache/purge.purge! fs))))
loaded_caches (..loaded_caches host_environment fs context purge load_order)]
(async#in
(do [! try.monad]
@@ -288,7 +288,7 @@
(-> (List Custom) Configuration (translation.Host expression declaration) (file.System Async) Context Import (List //.Context)
(Async (Try [Archive .Lux]))))
(do async.monad
- [binary (of fs read (cache/archive.descriptor fs context))]
+ [binary (of fs read (cache/archive.descriptor fs))]
(when binary
{try.#Success binary}
(do (try.with async.monad)
diff --git a/stdlib/source/library/lux/web/css/value.lux b/stdlib/source/library/lux/web/css/value.lux
index 19d80d994..12920e287 100644
--- a/stdlib/source/library/lux/web/css/value.lux
+++ b/stdlib/source/library/lux/web/css/value.lux
@@ -3,7 +3,7 @@
(.require
[library
- [lux (.except Label All Location and static false true all alias)
+ [lux (.except Label All Location and static false true all alias quote)
[control
["[0]" maybe]]
[data
diff --git a/stdlib/source/library/lux/web/html.lux b/stdlib/source/library/lux/web/html.lux
index 2257b97fe..4641d10f3 100644
--- a/stdlib/source/library/lux/web/html.lux
+++ b/stdlib/source/library/lux/web/html.lux
@@ -3,7 +3,7 @@
(.require
[library
- [lux (.except Tag Meta Source comment and template open parameter)
+ [lux (.except Tag Meta Source comment and template open parameter quote)
[control
["[0]" function]
["[0]" maybe (.use "[1]#[0]" functor)]]