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/abstract/apply.lux15
-rw-r--r--stdlib/source/library/lux/abstract/enum.lux12
-rw-r--r--stdlib/source/library/lux/control/exception.lux8
-rw-r--r--stdlib/source/library/lux/control/function/memo.lux6
-rw-r--r--stdlib/source/library/lux/control/function/mixin.lux6
-rw-r--r--stdlib/source/library/lux/control/io.lux8
-rw-r--r--stdlib/source/library/lux/control/lazy.lux2
-rw-r--r--stdlib/source/library/lux/control/parser/text.lux12
-rw-r--r--stdlib/source/library/lux/data/collection/array.lux13
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary.lux72
-rw-r--r--stdlib/source/library/lux/data/collection/row.lux29
-rw-r--r--stdlib/source/library/lux/data/color.lux8
-rw-r--r--stdlib/source/library/lux/data/format/tar.lux17
-rw-r--r--stdlib/source/library/lux/data/text.lux38
-rw-r--r--stdlib/source/library/lux/data/text/regex.lux7
-rw-r--r--stdlib/source/library/lux/debug.lux2
-rw-r--r--stdlib/source/library/lux/documentation.lux21
-rw-r--r--stdlib/source/library/lux/ffi.js.lux13
-rw-r--r--stdlib/source/library/lux/ffi.jvm.lux13
-rw-r--r--stdlib/source/library/lux/ffi.lua.lux23
-rw-r--r--stdlib/source/library/lux/ffi.php.lux13
-rw-r--r--stdlib/source/library/lux/ffi.py.lux13
-rw-r--r--stdlib/source/library/lux/ffi.rb.lux13
-rw-r--r--stdlib/source/library/lux/ffi.scm.lux13
-rw-r--r--stdlib/source/library/lux/math.lux8
-rw-r--r--stdlib/source/library/lux/math/number/complex.lux10
-rw-r--r--stdlib/source/library/lux/math/number/rev.lux58
-rw-r--r--stdlib/source/library/lux/meta.lux49
-rw-r--r--stdlib/source/library/lux/target/js.lux10
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/unsigned.lux12
-rw-r--r--stdlib/source/library/lux/target/lua.lux2
-rw-r--r--stdlib/source/library/lux/test.lux4
-rw-r--r--stdlib/source/library/lux/time/date.lux20
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux13
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux40
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux93
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux15
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux51
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux42
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux5
-rw-r--r--stdlib/source/library/lux/type.lux53
-rw-r--r--stdlib/source/library/lux/type/check.lux18
-rw-r--r--stdlib/source/library/lux/type/quotient.lux16
-rw-r--r--stdlib/source/library/lux/type/refinement.lux16
-rw-r--r--stdlib/source/library/lux/type/resource.lux44
-rw-r--r--stdlib/source/library/lux/type/unit.lux19
-rw-r--r--stdlib/source/library/lux/type/variance.lux3
-rw-r--r--stdlib/source/library/lux/world/console.lux6
-rw-r--r--stdlib/source/library/lux/world/file.lux22
-rw-r--r--stdlib/source/library/lux/world/file/watch.lux9
-rw-r--r--stdlib/source/library/lux/world/input/keyboard.lux2
-rw-r--r--stdlib/source/library/lux/world/net.lux3
-rw-r--r--stdlib/source/library/lux/world/net/http/client.lux10
-rw-r--r--stdlib/source/library/lux/world/net/http/route.lux2
-rw-r--r--stdlib/source/library/lux/world/net/http/status.lux23
-rw-r--r--stdlib/source/library/lux/world/net/uri.lux2
-rw-r--r--stdlib/source/library/lux/world/output/video/resolution.lux29
-rw-r--r--stdlib/source/library/lux/world/program.lux3
-rw-r--r--stdlib/source/library/lux/world/shell.lux9
67 files changed, 471 insertions, 659 deletions
diff --git a/stdlib/source/library/lux/abstract/apply.lux b/stdlib/source/library/lux/abstract/apply.lux
index 7ca651988..1831db134 100644
--- a/stdlib/source/library/lux/abstract/apply.lux
+++ b/stdlib/source/library/lux/abstract/apply.lux
@@ -1,6 +1,7 @@
(.module:
[library
- [lux #*]]
+ [lux #*
+ ["@" target]]]
[//
[monad (#+ Monad)]
["." functor (#+ Functor)]])
@@ -24,10 +25,14 @@
(def: (on fgx fgf)
... TODO: Switch from this version to the one below (in comments) ASAP.
- (let [fgf' (\ f_apply on
- fgf
- (\ f_monad in (function (_ gf gx) (\ g_apply on gx gf))))]
- (\ f_apply on fgx fgf'))
+ (for {@.old (let [fgf' (\ f_apply on
+ fgf
+ (\ f_monad in (function (_ gf gx) (\ g_apply on gx gf))))]
+ (:expected (\ f_apply on (:expected fgx) (:expected fgf'))))}
+ (let [fgf' (\ f_apply on
+ fgf
+ (\ f_monad in (function (_ gf gx) (\ g_apply on gx gf))))]
+ (\ f_apply on fgx fgf')))
... (let [applyF (\ f_apply on)
... applyG (\ g_apply on)]
... ($_ applyF
diff --git a/stdlib/source/library/lux/abstract/enum.lux b/stdlib/source/library/lux/abstract/enum.lux
index bb82c2936..5a43d91cd 100644
--- a/stdlib/source/library/lux/abstract/enum.lux
+++ b/stdlib/source/library/lux/abstract/enum.lux
@@ -11,14 +11,14 @@
(def: .public (range enum from to)
(All [a] (-> (Enum a) a a (List a)))
- (let [(^open "/\.") enum]
+ (let [(^open ".") enum]
(loop [end to
output #.End]
- (cond (/\< end from)
- (recur (/\pred end) (#.Item end output))
+ (cond (< end from)
+ (recur (pred end) (#.Item end output))
- (/\< from end)
- (recur (/\succ end) (#.Item end output))
+ (< from end)
+ (recur (succ end) (#.Item end output))
- ... (/\= end from)
+ ... (= end from)
(#.Item end output)))))
diff --git a/stdlib/source/library/lux/control/exception.lux b/stdlib/source/library/lux/control/exception.lux
index cf00522fa..bdca98684 100644
--- a/stdlib/source/library/lux/control/exception.lux
+++ b/stdlib/source/library/lux/control/exception.lux
@@ -47,7 +47,7 @@
(let [reference (value@ #label exception)]
(if (text.starts_with? reference error)
(#//.Success (|> error
- (text.clip' (text.size reference))
+ (text.clip_since (text.size reference))
maybe.trusted
then))
(#//.Failure error)))))
@@ -138,9 +138,9 @@
tail))))
(syntax: .public (report [entries (<>.many (<code>.tuple (<>.and <code>.any <code>.any)))])
- (in (list (` ((~! report') (list (~+ (|> entries
- (list\each (function (_ [header message])
- (` [(~ header) (~ message)])))))))))))
+ (in (list (` ((~! ..report') (list (~+ (|> entries
+ (list\each (function (_ [header message])
+ (` [(~ header) (~ message)])))))))))))
(def: .public (listing format entries)
(All [a]
diff --git a/stdlib/source/library/lux/control/function/memo.lux b/stdlib/source/library/lux/control/function/memo.lux
index 4d89e9778..6245dea04 100644
--- a/stdlib/source/library/lux/control/function/memo.lux
+++ b/stdlib/source/library/lux/control/function/memo.lux
@@ -39,20 +39,20 @@
(All [i o]
(:let [Memory (Dictionary i o)]
(-> (Memo i o) (-> [Memory i] [Memory o]))))
- (let [memo (//.mixin (//.with ..memoization (//.of_recursive memo)))]
+ (let [memo (//.fixed (//.mixed ..memoization (//.of_recursive memo)))]
(function (_ [memory input])
(|> input memo (state.result memory)))))
(def: .public (closed hash memo)
(All [i o]
(-> (Hash i) (Memo i o) (-> i o)))
- (let [memo (//.mixin (//.with ..memoization (//.of_recursive memo)))
+ (let [memo (//.fixed (//.mixed ..memoization (//.of_recursive memo)))
empty (dictionary.empty hash)]
(|>> memo (state.result empty) product.right)))
(def: .public (none hash memo)
(All [i o]
(-> (Hash i) (Memo i o) (-> i o)))
- (let [memo (//.mixin (//.of_recursive memo))
+ (let [memo (//.fixed (//.of_recursive memo))
empty (dictionary.empty hash)]
(|>> memo (state.result empty) product.right)))
diff --git a/stdlib/source/library/lux/control/function/mixin.lux b/stdlib/source/library/lux/control/function/mixin.lux
index 4f5013f77..68d2e4bf0 100644
--- a/stdlib/source/library/lux/control/function/mixin.lux
+++ b/stdlib/source/library/lux/control/function/mixin.lux
@@ -12,7 +12,7 @@
(type: .public (Mixin i o)
(-> (-> i o) (-> i o) (-> i o)))
-(def: .public (mixin f)
+(def: .public (fixed f)
(All [i o] (-> (Mixin i o) (-> i o)))
(function (mix input)
((f mix mix) input)))
@@ -22,7 +22,7 @@
(function (_ delegate recur)
delegate))
-(def: .public (with parent child)
+(def: .public (mixed parent child)
(All [i o] (-> (Mixin i o) (Mixin i o) (Mixin i o)))
(function (_ delegate recur)
(parent (child delegate recur) recur)))
@@ -31,7 +31,7 @@
(All [i o] (Monoid (Mixin i o)))
(def: identity ..nothing)
- (def: composite ..with))
+ (def: composite ..mixed))
(def: .public (advice when then)
(All [i o] (-> (Predicate i) (Mixin i o) (Mixin i o)))
diff --git a/stdlib/source/library/lux/control/io.lux b/stdlib/source/library/lux/control/io.lux
index 4f051e604..b418d435f 100644
--- a/stdlib/source/library/lux/control/io.lux
+++ b/stdlib/source/library/lux/control/io.lux
@@ -39,13 +39,13 @@
(def: .public run!
(All [a] (-> (IO a) a))
- (|>> run!'))
+ (|>> ..run!'))
(implementation: .public functor
(Functor IO)
(def: (each f)
- (|>> run!' f !io)))
+ (|>> ..run!' f !io)))
(implementation: .public apply
(Apply IO)
@@ -53,7 +53,7 @@
(def: &functor ..functor)
(def: (on fa ff)
- (!io ((run!' ff) (run!' fa)))))
+ (!io ((..run!' ff) (..run!' fa)))))
(implementation: .public monad
(Monad IO)
@@ -64,5 +64,5 @@
(|>> !io))
(def: conjoint
- (|>> run!' run!' !io)))
+ (|>> ..run!' ..run!' !io)))
)
diff --git a/stdlib/source/library/lux/control/lazy.lux b/stdlib/source/library/lux/control/lazy.lux
index e12de5bb9..c3a351c71 100644
--- a/stdlib/source/library/lux/control/lazy.lux
+++ b/stdlib/source/library/lux/control/lazy.lux
@@ -42,7 +42,7 @@
(syntax: .public (lazy [expression <code>.any])
(with_identifiers [g!_]
- (in (list (` ((~! lazy') (function ((~ g!_) (~ g!_)) (~ expression))))))))
+ (in (list (` ((~! ..lazy') (function ((~ g!_) (~ g!_)) (~ expression))))))))
(implementation: .public (equivalence (^open "\."))
(All [a] (-> (Equivalence a) (Equivalence (Lazy a))))
diff --git a/stdlib/source/library/lux/control/parser/text.lux b/stdlib/source/library/lux/control/parser/text.lux
index 24a2f9e3c..2dda427e6 100644
--- a/stdlib/source/library/lux/control/parser/text.lux
+++ b/stdlib/source/library/lux/control/parser/text.lux
@@ -35,20 +35,20 @@
{#basis Offset
#distance Offset}))
-(def: (remaining' offset tape)
+(def: (left_over offset tape)
(-> Offset Text Text)
- (|> tape (/.split_at offset) maybe.trusted product.right))
+ (|> tape (/.clip_since offset) maybe.trusted))
(exception: .public (unconsumed_input {offset Offset} {tape Text})
(exception.report
["Offset" (n\encoded offset)]
["Input size" (n\encoded (/.size tape))]
- ["Remaining input" (remaining' offset tape)]))
+ ["Remaining input" (..left_over offset tape)]))
(exception: .public (expected_to_fail {offset Offset} {tape Text})
(exception.report
["Offset" (n\encoded offset)]
- ["Input" (remaining' offset tape)]))
+ ["Input" (..left_over offset tape)]))
(exception: .public cannot_parse)
(exception: .public cannot_slice)
@@ -125,7 +125,7 @@
(def: .public (this reference)
(-> Text (Parser Any))
(function (_ [offset tape])
- (case (/.index' offset reference tape)
+ (case (/.index_since offset reference tape)
(#.Some where)
(if (n.= offset where)
(#try.Success [[("lux i64 +" (/.size reference) offset) tape]
@@ -155,7 +155,7 @@
(def: .public remaining
(Parser Text)
(function (_ (^@ input [offset tape]))
- (#try.Success [input (remaining' offset tape)])))
+ (#try.Success [input (..left_over offset tape)])))
(def: .public (range bottom top)
(-> Nat Nat (Parser Text))
diff --git a/stdlib/source/library/lux/data/collection/array.lux b/stdlib/source/library/lux/data/collection/array.lux
index 3ae79571c..1549bae80 100644
--- a/stdlib/source/library/lux/data/collection/array.lux
+++ b/stdlib/source/library/lux/data/collection/array.lux
@@ -275,7 +275,7 @@
Nat
(-- 0))
-(def: .public (list array)
+(def: (list|-default array)
(All [a] (-> (Array a) (List a)))
(loop [idx (-- (size array))
output #.End]
@@ -292,7 +292,7 @@
#.None
output)))))
-(def: .public (list' default array)
+(def: (list|+default default array)
(All [a] (-> a (Array a) (List a)))
(loop [idx (-- (size array))
output #.End]
@@ -305,6 +305,15 @@
(#.Item (maybe.else default (read! idx array))
output)))))
+(def: .public (list default array)
+ (All [a] (-> (Maybe a) (Array a) (List a)))
+ (case default
+ (#.Some default)
+ (list|+default default array)
+
+ #.None
+ (list|-default array)))
+
(implementation: .public (equivalence (^open ",\."))
(All [a] (-> (Equivalence a) (Equivalence (Array a))))
diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux
index e06983307..0828d54e2 100644
--- a/stdlib/source/library/lux/data/collection/dictionary.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary.lux
@@ -145,9 +145,11 @@
(|> array array.clone (array.write! idx value)))
... Creates a clone of the array, with an empty position at index.
-(def: (array\lacks' idx array)
+(def: (array\clear idx array)
(All [a] (-> Index (Array a) (Array a)))
- (|> array array.clone (array.delete! idx)))
+ (|> array
+ array.clone
+ (array.delete! idx)))
... Shrinks a copy of the array by removing the space at index.
(def: (array\lacks idx array)
@@ -284,7 +286,7 @@
... All empty nodes look the same (a #Base node with clean bitmap is
... used).
... So, this test is introduced to detect them.
-(def: (empty?' node)
+(def: (node\empty? node)
(All [k v] (-> (Node k v) Bit))
(`` (case node
(#Base (~~ (static ..clean_bitmap)) _)
@@ -355,18 +357,18 @@
... However, if the Bit_Position has not been used yet, check
... whether this #Base node is ready for a promotion.
(let [base_count (bitmap_size bitmap)]
- (if (n.>= ..promotion_threshold base_count)
- ... If so, promote it to a #Hierarchy node, and add the new
+ (if (n.< ..promotion_threshold base_count)
+ ... If so, resize the #Base node to accommodate the
+ ... new KV-pair.
+ (#Base (with_bit_position bit bitmap)
+ (array\has (base_index bit bitmap) (#.Right [key val]) base))
+ ... Otherwise, promote it to a #Hierarchy node, and add the new
... KV-pair as a singleton node to it.
(#Hierarchy (++ base_count)
(|> base
(promotion node\has key_hash level bitmap)
(array.write! (level_index level hash)
- (node\has (level_up level) hash key val key_hash empty_node))))
- ... Otherwise, just resize the #Base node to accommodate the
- ... new KV-pair.
- (#Base (with_bit_position bit bitmap)
- (array\has (base_index bit bitmap) (#.Right [key val]) base))))))
+ (node\has (level_up level) hash key val key_hash empty_node))))))))
... For #Collisions nodes, compare the hashes.
(#Collisions _hash _colls)
@@ -390,7 +392,7 @@
(node\has level hash key val key_hash)))
))
-(def: (lacks' level hash key key_hash node)
+(def: (node\lacks level hash key key_hash node)
(All [k v] (-> Level Hash_Code k (Hash k) (Node k v) (Node k v)))
(case node
... For #Hierarchy nodes, find out if there's a valid sub-node for
@@ -404,19 +406,19 @@
... But if there is, try to remove the key from the sub-node.
(#.Some sub_node)
- (let [sub_node' (lacks' (level_up level) hash key key_hash sub_node)]
+ (let [sub_node' (node\lacks (level_up level) hash key key_hash sub_node)]
... Then check if a removal was actually done.
(if (same? sub_node sub_node')
... If not, then there's nothing to change here either.
node
... But if the sub_removal yielded an empty sub_node...
- (if (empty?' sub_node')
+ (if (node\empty? sub_node')
... Check if it's due time for a demotion.
- (if (n.<= demotion_threshold h_size)
- ... If so, perform it.
- (#Base (demotion idx [h_size h_array]))
- ... Otherwise, just clear the space.
- (#Hierarchy (-- h_size) (array\lacks' idx h_array)))
+ (if (n.> demotion_threshold h_size)
+ ... If so, just clear the space.
+ (#Hierarchy (-- h_size) (array\clear idx h_array))
+ ... Otherwise, perform it.
+ (#Base (demotion idx [h_size h_array])))
... But if the sub_removal yielded a non_empty node, then
... just update the hiearchy branch.
(#Hierarchy h_size (array\revised idx sub_node' h_array)))))))
@@ -430,13 +432,13 @@
... If set, check if it's a sub_node, and remove the KV
... from it.
(#.Some (#.Left sub_node))
- (let [sub_node' (lacks' (level_up level) hash key key_hash sub_node)]
+ (let [sub_node' (node\lacks (level_up level) hash key key_hash sub_node)]
... Verify that it was removed.
(if (same? sub_node sub_node')
... If not, there's also nothing to change here.
node
... But if it came out empty...
- (if (empty?' sub_node')
+ (if (node\empty? sub_node')
...# ... figure out whether that's the only position left.
(if (only_bit_position? bit bitmap)
... If so, removing it leaves this node empty too.
@@ -482,14 +484,14 @@
(#Collisions _hash (array\lacks idx _colls))))
))
-(def: (value' level hash key key_hash node)
+(def: (node\value level hash key key_hash node)
(All [k v] (-> Level Hash_Code k (Hash k) (Node k v) (Maybe v)))
(case node
... For #Hierarchy nodes, just look-up the key on its children.
(#Hierarchy _size hierarchy)
(case (array.read! (level_index level hash) hierarchy)
#.None #.None
- (#.Some sub_node) (value' (level_up level) hash key key_hash sub_node))
+ (#.Some sub_node) (node\value (level_up level) hash key key_hash sub_node))
... For #Base nodes, check the leaves, and recursively check the branches.
(#Base bitmap base)
@@ -497,7 +499,7 @@
(if (with_bit_position? bit bitmap)
(case (array.read! (base_index bit bitmap) base)
(#.Some (#.Left sub_node))
- (value' (level_up level) hash key key_hash sub_node)
+ (node\value (level_up level) hash key key_hash sub_node)
(#.Some (#.Right [key' val']))
(if (\ key_hash = key key')
@@ -515,16 +517,16 @@
_colls))
))
-(def: (size' node)
+(def: (node\size node)
(All [k v] (-> (Node k v) Nat))
(case node
(#Hierarchy _size hierarchy)
- (array\mix n.+ 0 (array\each size' hierarchy))
+ (array\mix n.+ 0 (array\each node\size hierarchy))
(#Base _ base)
(array\mix n.+ 0 (array\each (function (_ sub_node')
(case sub_node'
- (#.Left sub_node) (size' sub_node)
+ (#.Left sub_node) (node\size sub_node)
(#.Right _) 1))
base))
@@ -532,11 +534,11 @@
(array.size colls)
))
-(def: (entries' node)
+(def: (node\entries node)
(All [k v] (-> (Node k v) (List [k v])))
(case node
(#Hierarchy _size hierarchy)
- (array\mix (function (_ sub_node tail) (list\composite (entries' sub_node) tail))
+ (array\mix (function (_ sub_node tail) (list\composite (node\entries sub_node) tail))
#.End
hierarchy)
@@ -544,7 +546,7 @@
(array\mix (function (_ branch tail)
(case branch
(#.Left sub_node)
- (list\composite (entries' sub_node) tail)
+ (list\composite (node\entries sub_node) tail)
(#.Right [key' val'])
(#.Item [key' val'] tail)))
@@ -578,12 +580,12 @@
(def: .public (lacks key dict)
(All [k v] (-> k (Dictionary k v) (Dictionary k v)))
(let [[key_hash node] dict]
- [key_hash (lacks' root_level (\ key_hash hash key) key key_hash node)]))
+ [key_hash (node\lacks root_level (\ key_hash hash key) key key_hash node)]))
(def: .public (value key dict)
(All [k v] (-> k (Dictionary k v) (Maybe v)))
(let [[key_hash node] dict]
- (value' root_level (\ key_hash hash key) key key_hash node)))
+ (node\value root_level (\ key_hash hash key) key key_hash node)))
(def: .public (key? dict key)
(All [k v] (-> (Dictionary k v) k Bit))
@@ -617,7 +619,7 @@
(def: .public size
(All [k v] (-> (Dictionary k v) Nat))
- (|>> product.right ..size'))
+ (|>> product.right ..node\size))
(def: .public empty?
(All [k v] (-> (Dictionary k v) Bit))
@@ -625,7 +627,7 @@
(def: .public entries
(All [k v] (-> (Dictionary k v) (List [k v])))
- (|>> product.right ..entries'))
+ (|>> product.right ..node\entries))
(def: .public (of_list key_hash kvs)
(All [k v] (-> (Hash k) (List [k v]) (Dictionary k v)))
@@ -700,7 +702,7 @@
#0))
(..entries reference)))))
-(implementation: functor'
+(implementation: node_functor
(All [k] (Functor (Node k)))
(def: (each f fa)
@@ -727,4 +729,4 @@
(All [k] (Functor (Dictionary k)))
(def: (each f fa)
- (revised@ #root (\ ..functor' each f) fa)))
+ (revised@ #root (\ ..node_functor each f) fa)))
diff --git a/stdlib/source/library/lux/data/collection/row.lux b/stdlib/source/library/lux/data/collection/row.lux
index 6cba59b62..30a2323c4 100644
--- a/stdlib/source/library/lux/data/collection/row.lux
+++ b/stdlib/source/library/lux/data/collection/row.lux
@@ -132,13 +132,13 @@
(array.copy! tail_size 0 tail 0)
(array.write! tail_size val))))
-(def: (has' level idx val hierarchy)
+(def: (hierarchy\has level idx val hierarchy)
(All [a] (-> Level Index a (Hierarchy a) (Hierarchy a)))
(let [sub_idx (branch_idx (i64.right_shifted level idx))]
(case (array.read! sub_idx hierarchy)
(#.Some (#Hierarchy sub_node))
(|> (array.clone hierarchy)
- (array.write! sub_idx (#Hierarchy (has' (level_down level) idx val sub_node))))
+ (array.write! sub_idx (#Hierarchy (hierarchy\has (level_down level) idx val sub_node))))
(^multi (#.Some (#Base base))
(n.= 0 (level_down level)))
@@ -175,17 +175,18 @@
#.Some)
)))
-(def: (list' node)
+(def: (node\list node)
(All [a] (-> (Node a) (List a)))
(case node
(#Base base)
- (array.list base)
+ (array.list #.None base)
(#Hierarchy hierarchy)
(|> hierarchy
- array.list
+ (array.list #.None)
list.reversed
- (list\mix (function (_ sub acc) (list\composite (list' sub) acc))
+ (list\mix (function (_ sub acc)
+ (list\composite (node\list sub) acc))
#.End))))
(type: .public (Row a)
@@ -254,8 +255,7 @@
(def: (base_for idx row)
(All [a] (-> Index (Row a) (Try (Base a))))
(if (within_bounds? row idx)
- (if (n.>= (tail_off (value@ #size row)) idx)
- (#try.Success (value@ #tail row))
+ (if (n.< (tail_off (value@ #size row)) idx)
(loop [level (value@ #level row)
hierarchy (value@ #root row)]
(case [(n.> branching_exponent level)
@@ -270,7 +270,8 @@
(exception.except ..base_was_not_found [])
_
- (exception.except ..incorrect_row_structure []))))
+ (exception.except ..incorrect_row_structure [])))
+ (#try.Success (value@ #tail row)))
(exception.except ..index_out_of_bounds [row idx])))
(def: .public (item idx row)
@@ -288,13 +289,13 @@
(All [a] (-> Nat a (Row a) (Try (Row a))))
(let [row_size (value@ #size row)]
(if (within_bounds? row idx)
- (#try.Success (if (n.>= (tail_off row_size) idx)
+ (#try.Success (if (n.< (tail_off row_size) idx)
+ (revised@ #root (hierarchy\has (value@ #level row) idx val)
+ row)
(revised@ #tail (for {@.old
(: (-> (Base (:parameter 0)) (Base (:parameter 0)))
(|>> array.clone (array.write! (branch_idx idx) val)))}
(|>> array.clone (array.write! (branch_idx idx) val)))
- row)
- (revised@ #root (has' (value@ #level row) idx val)
row)))
(exception.except ..index_out_of_bounds [row idx]))))
@@ -348,8 +349,8 @@
(def: .public (list row)
(All [a] (-> (Row a) (List a)))
- (list\composite (list' (#Hierarchy (value@ #root row)))
- (list' (#Base (value@ #tail row)))))
+ (list\composite (node\list (#Hierarchy (value@ #root row)))
+ (node\list (#Base (value@ #tail row)))))
(def: .public of_list
(All [a] (-> (List a) (Row a)))
diff --git a/stdlib/source/library/lux/data/color.lux b/stdlib/source/library/lux/data/color.lux
index 3cf8fa6d5..f688297f2 100644
--- a/stdlib/source/library/lux/data/color.lux
+++ b/stdlib/source/library/lux/data/color.lux
@@ -115,16 +115,16 @@
#green (n.max lG rG)
#blue (n.max lB rB)}))))
- (def: (complement' value)
+ (def: (opposite_intensity value)
(-> Nat Nat)
(|> ..top (n.- value)))
(def: .public (complement color)
(-> Color Color)
(let [[red green blue] (:representation color)]
- (:abstraction {#red (complement' red)
- #green (complement' green)
- #blue (complement' blue)})))
+ (:abstraction {#red (opposite_intensity red)
+ #green (opposite_intensity green)
+ #blue (opposite_intensity blue)})))
(implementation: .public subtraction
(Monoid Color)
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index 745acf38d..6aeaa6539 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -261,9 +261,12 @@
(def: .public (<in> value)
(-> <representation> (Try <type>))
(if (..ascii? value)
- (if (|> value (\ utf8.codec encoded) binary.size (n.<= <size>))
- (#try.Success (:abstraction value))
- (exception.except <exception> [value]))
+ (if (|> value
+ (\ utf8.codec encoded)
+ binary.size
+ (n.> <size>))
+ (exception.except <exception> [value])
+ (#try.Success (:abstraction value)))
(exception.except ..not_ascii [value])))
(def: .public <out>
@@ -519,11 +522,11 @@
(Parser Mode)
(do {! <>.monad}
[value (\ ! each ..from_small ..small_parser)]
- (if (n.<= (:representation ..maximum_mode)
- value)
- (in (:abstraction value))
+ (if (n.> (:representation ..maximum_mode)
+ value)
(<>.lifted
- (exception.except ..invalid_mode [value]))))))
+ (exception.except ..invalid_mode [value]))
+ (in (:abstraction value))))))
)
(def: maximum_content_size
diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux
index daf951a7d..31e42bfa5 100644
--- a/stdlib/source/library/lux/data/text.lux
+++ b/stdlib/source/library/lux/data/text.lux
@@ -56,30 +56,26 @@
(#.Some ("lux text char" index input))
#.None))
-(def: .public (index' from pattern input)
+(def: .public (index_since offset pattern input)
(-> Nat Text Text (Maybe Nat))
- ("lux text index" from pattern input))
+ ("lux text index" offset pattern input))
(def: .public (index pattern input)
(-> Text Text (Maybe Nat))
- (index' 0 pattern input))
+ (index_since 0 pattern input))
-(def: (last_index' from part text)
- (-> Nat Text Text (Maybe Nat))
- (loop [from from
+(def: .public (last_index part text)
+ (-> Text Text (Maybe Nat))
+ (loop [offset 0
output (: (Maybe Nat)
#.None)]
- (let [output' ("lux text index" from part text)]
+ (let [output' ("lux text index" offset part text)]
(case output'
#.None
output
- (#.Some from')
- (recur (++ from') output')))))
-
-(def: .public (last_index part text)
- (-> Text Text (Maybe Nat))
- (last_index' 0 part text))
+ (#.Some offset')
+ (recur (++ offset') output')))))
(def: .public (starts_with? prefix x)
(-> Text Text Bit)
@@ -136,20 +132,20 @@
(def: .public (clip offset size input)
(-> Nat Nat Text (Maybe Text))
- (if (|> size (n.+ offset) (n.<= ("lux text size" input)))
- (#.Some ("lux text clip" offset size input))
- #.None))
+ (if (|> size (n.+ offset) (n.> ("lux text size" input)))
+ #.None
+ (#.Some ("lux text clip" offset size input))))
-(def: .public (clip' offset input)
+(def: .public (clip_since offset input)
(-> Nat Text (Maybe Text))
(let [size ("lux text size" input)]
- (if (n.<= size offset)
- (#.Some ("lux text clip" offset (n.- offset size) input))
- #.None)))
+ (if (n.> size offset)
+ #.None
+ (#.Some ("lux text clip" offset (n.- offset size) input)))))
(def: .public (split_at at x)
(-> Nat Text (Maybe [Text Text]))
- (case [(..clip 0 at x) (..clip' at x)]
+ (case [(..clip 0 at x) (..clip_since at x)]
[(#.Some pre) (#.Some post)]
(#.Some [pre post])
diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux
index 77d4e94e1..fcfb718ab 100644
--- a/stdlib/source/library/lux/data/text/regex.lux
+++ b/stdlib/source/library/lux/data/text/regex.lux
@@ -116,9 +116,10 @@
(def: re_user_class^
(Parser Code)
(do <>.monad
- [_ (in [])
- init re_user_class^'
- rest (<>.some (<>.after (<text>.this "&&") (<text>.enclosed ["[" "]"] re_user_class^')))]
+ [init ..re_user_class^'
+ rest (<>.some (<>.after (<text>.this "&&")
+ (<text>.enclosed ["[" "]"]
+ ..re_user_class^')))]
(in (list\mix (function (_ refinement base)
(` ((~! refine^) (~ refinement) (~ base))))
init
diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux
index 96ccfe30e..c08076bcf 100644
--- a/stdlib/source/library/lux/debug.lux
+++ b/stdlib/source/library/lux/debug.lux
@@ -135,7 +135,7 @@
(~~ (as_is)))]
(`` (|>> (:as (array.Array Any))
<adaption>
- array.list
+ (array.list #.None)
(list\each inspection)
(text.interposed " ")
(text.enclosed ["[" "]"])))))
diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux
index 35cebc0f4..05610b52f 100644
--- a/stdlib/source/library/lux/documentation.lux
+++ b/stdlib/source/library/lux/documentation.lux
@@ -301,13 +301,6 @@
(|>> (text.all_split_by ..expected_separator)
(set.of_list text.hash)))
-(def: (module' name description expected definitions)
- (-> Text Text Text (List Definition) Module)
- {#module name
- #description description
- #expected (..expected expected)
- #definitions definitions})
-
(syntax: .public (module [[name _] ..qualified_identifier
description <code>.any
definitions (<code>.tuple (<>.some <code>.any))
@@ -315,13 +308,13 @@
(do meta.monad
[expected (meta.exports name)]
(in (list (` (: (List Module)
- (list& ((~! ..module')
- (~ (code.text name))
- (~ description)
- (~ (code.text (|> expected
- (list\each product.left)
- ..expected_format)))
- ((~! list.together) (list (~+ definitions))))
+ (list& {#..module (~ (code.text name))
+ #..description (~ description)
+ #..expected ((~! ..expected)
+ (~ (code.text (|> expected
+ (list\each product.left)
+ ..expected_format))))
+ #..definitions ((~! list.together) (list (~+ definitions)))}
($_ (\ (~! list.monoid) (~' composite))
(: (List Module)
(\ (~! list.monoid) (~' identity)))
diff --git a/stdlib/source/library/lux/ffi.js.lux b/stdlib/source/library/lux/ffi.js.lux
index 38a207259..6d1867dfc 100644
--- a/stdlib/source/library/lux/ffi.js.lux
+++ b/stdlib/source/library/lux/ffi.js.lux
@@ -81,12 +81,13 @@
..nullable)))
(type: Common_Method
- {#name Text
- #alias (Maybe Text)
- #inputs (List Nullable)
- #io? Bit
- #try? Bit
- #output Nullable})
+ (Record
+ {#name Text
+ #alias (Maybe Text)
+ #inputs (List Nullable)
+ #io? Bit
+ #try? Bit
+ #output Nullable}))
(type: Static_Method Common_Method)
(type: Virtual_Method Common_Method)
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux
index d57bde2b1..f7b94e8df 100644
--- a/stdlib/source/library/lux/ffi.jvm.lux
+++ b/stdlib/source/library/lux/ffi.jvm.lux
@@ -715,17 +715,12 @@
(<code>.form (<>.and <code>.local_identifier
annotation_parameters^))))
-(def: annotations^'
- (Parser (List Annotation))
- (do <>.monad
- [_ (<code>.this! (' #ann))]
- (<code>.tuple (<>.some ..annotation^))))
-
(def: annotations^
(Parser (List Annotation))
- (do <>.monad
- [anns?? (<>.maybe ..annotations^')]
- (in (maybe.else (list) anns??))))
+ (<| (<>.else (list))
+ (do <>.monad
+ [_ (<code>.this! (' #ann))]
+ (<code>.tuple (<>.some ..annotation^)))))
(def: (throws_decl^ type_vars)
(-> (List (Type Var)) (Parser (List (Type Class))))
diff --git a/stdlib/source/library/lux/ffi.lua.lux b/stdlib/source/library/lux/ffi.lua.lux
index 3d14b554f..d8bcfdb42 100644
--- a/stdlib/source/library/lux/ffi.lua.lux
+++ b/stdlib/source/library/lux/ffi.lua.lux
@@ -80,12 +80,13 @@
..nilable)))
(type: Common_Method
- {#name Text
- #alias (Maybe Text)
- #inputs (List Nilable)
- #io? Bit
- #try? Bit
- #output Nilable})
+ (Record
+ {#name Text
+ #alias (Maybe Text)
+ #inputs (List Nilable)
+ #io? Bit
+ #try? Bit
+ #output Nilable}))
(type: Static_Method Common_Method)
(type: Virtual_Method Common_Method)
@@ -315,8 +316,8 @@
(: ..Function
(closure [left right]
(do_something (:as Foo left) (:as Bar right)))))}
- (.:as ..Function
- (`` ("lua function"
- (~~ (template.amount <inputs>))
- (.function (_ [<inputs>])
- <output>)))))
+ [(.:as ..Function
+ (`` ("lua function"
+ (~~ (template.amount <inputs>))
+ (.function (_ [<inputs>])
+ <output>))))])
diff --git a/stdlib/source/library/lux/ffi.php.lux b/stdlib/source/library/lux/ffi.php.lux
index 82208f783..c06124708 100644
--- a/stdlib/source/library/lux/ffi.php.lux
+++ b/stdlib/source/library/lux/ffi.php.lux
@@ -86,12 +86,13 @@
..nullable)))
(type: Common_Method
- {#name Text
- #alias (Maybe Alias)
- #inputs (List Nullable)
- #io? Bit
- #try? Bit
- #output Nullable})
+ (Record
+ {#name Text
+ #alias (Maybe Alias)
+ #inputs (List Nullable)
+ #io? Bit
+ #try? Bit
+ #output Nullable}))
(type: Static_Method Common_Method)
(type: Virtual_Method Common_Method)
diff --git a/stdlib/source/library/lux/ffi.py.lux b/stdlib/source/library/lux/ffi.py.lux
index 3dbd3cc5a..bf455fc2e 100644
--- a/stdlib/source/library/lux/ffi.py.lux
+++ b/stdlib/source/library/lux/ffi.py.lux
@@ -81,12 +81,13 @@
..noneable)))
(type: Common_Method
- {#name Text
- #alias (Maybe Text)
- #inputs (List Noneable)
- #io? Bit
- #try? Bit
- #output Noneable})
+ (Record
+ {#name Text
+ #alias (Maybe Text)
+ #inputs (List Noneable)
+ #io? Bit
+ #try? Bit
+ #output Noneable}))
(type: Static_Method Common_Method)
(type: Virtual_Method Common_Method)
diff --git a/stdlib/source/library/lux/ffi.rb.lux b/stdlib/source/library/lux/ffi.rb.lux
index 2ba821582..060b3dfea 100644
--- a/stdlib/source/library/lux/ffi.rb.lux
+++ b/stdlib/source/library/lux/ffi.rb.lux
@@ -88,12 +88,13 @@
..nilable)))
(type: Common_Method
- {#name Text
- #alias (Maybe Alias)
- #inputs (List Nilable)
- #io? Bit
- #try? Bit
- #output Nilable})
+ (Record
+ {#name Text
+ #alias (Maybe Alias)
+ #inputs (List Nilable)
+ #io? Bit
+ #try? Bit
+ #output Nilable}))
(type: Static_Method Common_Method)
(type: Virtual_Method Common_Method)
diff --git a/stdlib/source/library/lux/ffi.scm.lux b/stdlib/source/library/lux/ffi.scm.lux
index 675aadcd1..f8f75f21e 100644
--- a/stdlib/source/library/lux/ffi.scm.lux
+++ b/stdlib/source/library/lux/ffi.scm.lux
@@ -86,12 +86,13 @@
..nilable)))
(type: Common_Method
- {#name Text
- #alias (Maybe Alias)
- #inputs (List Nilable)
- #io? Bit
- #try? Bit
- #output Nilable})
+ (Record
+ {#name Text
+ #alias (Maybe Alias)
+ #inputs (List Nilable)
+ #io? Bit
+ #try? Bit
+ #output Nilable}))
(def: common_method
(Parser Common_Method)
diff --git a/stdlib/source/library/lux/math.lux b/stdlib/source/library/lux/math.lux
index a0a31472d..c5fc005c6 100644
--- a/stdlib/source/library/lux/math.lux
+++ b/stdlib/source/library/lux/math.lux
@@ -318,7 +318,7 @@
... ("lux f64 =" +0.0 y)
("lux f64 /" +0.0 +0.0))))
-(def: .public (log' base it)
+(def: .public (log_by base it)
(-> Frac Frac Frac)
("lux f64 /"
(..log base)
@@ -328,9 +328,9 @@
(-> Nat Nat)
(loop [acc 1
it it]
- (if (n.<= 1 it)
- acc
- (recur (n.* it acc) (-- it)))))
+ (if (n.> 1 it)
+ (recur (n.* it acc) (-- it))
+ acc)))
(def: .public (hypotenuse catA catB)
(-> Frac Frac Frac)
diff --git a/stdlib/source/library/lux/math/number/complex.lux b/stdlib/source/library/lux/math/number/complex.lux
index b3418da98..6687bd043 100644
--- a/stdlib/source/library/lux/math/number/complex.lux
+++ b/stdlib/source/library/lux/math/number/complex.lux
@@ -230,13 +230,13 @@
(-> Complex Complex)
(let [(^slots [#real #imaginary]) input
t (|> input ..abs (f.+ (f.abs real)) (f./ +2.0) (math.pow +0.5))]
- (if (f.>= +0.0 real)
- {#real t
- #imaginary (f./ (f.* +2.0 t)
- imaginary)}
+ (if (f.< +0.0 real)
{#real (f./ (f.* +2.0 t)
(f.abs imaginary))
- #imaginary (f.* t (..with_sign imaginary +1.0))})))
+ #imaginary (f.* t (..with_sign imaginary +1.0))}
+ {#real t
+ #imaginary (f./ (f.* +2.0 t)
+ imaginary)})))
(def: (root/2-1z input)
(-> Complex Complex)
diff --git a/stdlib/source/library/lux/math/number/rev.lux b/stdlib/source/library/lux/math/number/rev.lux
index a65025c0b..5af0bf3ff 100644
--- a/stdlib/source/library/lux/math/number/rev.lux
+++ b/stdlib/source/library/lux/math/number/rev.lux
@@ -297,31 +297,34 @@
(loop [idx idx
carry 0
output output]
- (if (//int.>= +0 (.int idx))
+ (if (//int.< +0 (.int idx))
+ output
(let [raw (|> (..digit idx output)
(//nat.* 5)
(//nat.+ carry))]
(recur (-- idx)
(//nat./ 10 raw)
- (digits\put! idx (//nat.% 10 raw) output)))
- output)))
+ (digits\put! idx (//nat.% 10 raw) output))))))
(def: (power_digits power)
(-> Nat Digits)
(loop [times power
output (|> (..digits [])
(digits\put! power 1))]
- (if (//int.>= +0 (.int times))
+ (if (//int.< +0 (.int times))
+ output
(recur (-- times)
- (digits\times_5! power output))
- output)))
+ (digits\times_5! power output)))))
(def: (format digits)
(-> Digits Text)
(loop [idx (-- //i64.width)
all_zeroes? true
output ""]
- (if (//int.>= +0 (.int idx))
+ (if (//int.< +0 (.int idx))
+ (if all_zeroes?
+ "0"
+ output)
(let [digit (..digit idx digits)]
(if (and (//nat.= 0 digit)
all_zeroes?)
@@ -330,30 +333,28 @@
false
("lux text concat"
(\ //nat.decimal encoded digit)
- output))))
- (if all_zeroes?
- "0"
- output))))
+ output)))))))
(def: (digits\+! param subject)
(-> Digits Digits Digits)
(loop [idx (-- //i64.width)
carry 0
output (..digits [])]
- (if (//int.>= +0 (.int idx))
+ (if (//int.< +0 (.int idx))
+ output
(let [raw ($_ //nat.+
carry
(..digit idx param)
(..digit idx subject))]
(recur (-- idx)
(//nat./ 10 raw)
- (digits\put! idx (//nat.% 10 raw) output)))
- output)))
+ (digits\put! idx (//nat.% 10 raw) output))))))
(def: (text_digits input)
(-> Text (Maybe Digits))
(let [length ("lux text size" input)]
- (if (//nat.<= //i64.width length)
+ (if (//nat.> //i64.width length)
+ #.None
(loop [idx 0
output (..digits [])]
(if (//nat.< length idx)
@@ -364,8 +365,7 @@
(#.Some digit)
(recur (++ idx)
(digits\put! idx digit output)))
- (#.Some output)))
- #.None)))
+ (#.Some output))))))
(def: (digits\< param subject)
(-> Digits Digits Bit)
@@ -380,23 +380,23 @@
(def: (digits\-!' idx param subject)
(-> Nat Nat Digits Digits)
(let [sd (..digit idx subject)]
- (if (//nat.>= param sd)
- (digits\put! idx (//nat.- param sd) subject)
+ (if (//nat.< param sd)
(let [diff (|> sd
(//nat.+ 10)
(//nat.- param))]
(|> subject
(digits\put! idx diff)
- (digits\-!' (-- idx) 1))))))
+ (digits\-!' (-- idx) 1)))
+ (digits\put! idx (//nat.- param sd) subject))))
(def: (digits\-! param subject)
(-> Digits Digits Digits)
(loop [idx (-- //i64.width)
output subject]
- (if (//int.>= +0 (.int idx))
+ (if (//int.< +0 (.int idx))
+ output
(recur (-- idx)
- (digits\-!' idx (..digit idx param) output))
- output)))
+ (digits\-!' idx (..digit idx param) output)))))
(implementation: .public decimal
(Codec Text Rev)
@@ -410,16 +410,15 @@
(let [last_idx (-- //i64.width)]
(loop [idx last_idx
digits (..digits [])]
- (if (//int.>= +0 (.int idx))
+ (if (//int.< +0 (.int idx))
+ ("lux text concat" "." (..format digits))
(if (//i64.one? idx input)
(let [digits' (digits\+! (power_digits (//nat.- idx last_idx))
digits)]
(recur (-- idx)
digits'))
(recur (-- idx)
- digits))
- ("lux text concat" "." (..format digits))
- )))))
+ digits)))))))
(def: (decoded input)
(let [dotted? (case ("lux text index" 0 "." input)
@@ -428,8 +427,9 @@
_
false)
- within_limits? (//nat.<= (++ //i64.width)
- ("lux text size" input))]
+ within_limits? (|> input
+ "lux text size"
+ (//nat.<= (++ //i64.width)))]
(if (and dotted? within_limits?)
(case (|> input ..decimals ..text_digits)
(#.Some digits)
diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux
index 103796a2e..c51425fcc 100644
--- a/stdlib/source/library/lux/meta.lux
+++ b/stdlib/source/library/lux/meta.lux
@@ -160,37 +160,36 @@
_
(\ ..monad in name)))
-(def: (macro' modules this_module module name)
- (-> (List [Text Module]) Text Text Text
- (Maybe Macro))
- (do maybe.monad
- [$module (plist.value module modules)
- definition (: (Maybe Global)
- (|> (: Module $module)
- (value@ #.definitions)
- (plist.value name)))]
- (case definition
- (#.Alias [r_module r_name])
- (macro' modules this_module r_module r_name)
-
- (#.Definition [exported? def_type def_anns def_value])
- (if (macro_type? def_type)
- (#.Some (:as Macro def_value))
- #.None))))
-
(def: .public (macro full_name)
(-> Name (Meta (Maybe Macro)))
(do ..monad
[[module name] (..normal full_name)]
(: (Meta (Maybe Macro))
(function (_ lux)
- (let [macro (case (..current_module_name lux)
- (#try.Failure error)
- #.None
-
- (#try.Success [_ this_module])
- (macro' (value@ #.modules lux) this_module module name))]
- (#try.Success [lux macro]))))))
+ (#try.Success [lux
+ (case (..current_module_name lux)
+ (#try.Failure error)
+ #.None
+
+ (#try.Success [_ this_module])
+ (let [modules (value@ #.modules lux)]
+ (loop [module module
+ name name]
+ (do maybe.monad
+ [$module (plist.value module modules)
+ definition (: (Maybe Global)
+ (|> $module
+ (: Module)
+ (value@ #.definitions)
+ (plist.value name)))]
+ (case definition
+ (#.Alias [r_module r_name])
+ (recur r_module r_name)
+
+ (#.Definition [exported? def_type def_anns def_value])
+ (if (macro_type? def_type)
+ (#.Some (:as Macro def_value))
+ #.None))))))])))))
(def: .public seed
(Meta Nat)
diff --git a/stdlib/source/library/lux/target/js.lux b/stdlib/source/library/lux/target/js.lux
index 7a1f5b3bc..a2b83491d 100644
--- a/stdlib/source/library/lux/target/js.lux
+++ b/stdlib/source/library/lux/target/js.lux
@@ -307,10 +307,6 @@
(-> Var Expression Statement)
(:abstraction (format "var " (:representation name) " = " (:representation value) ..statement_suffix)))
- (def: .public (set' name value)
- (-> Location Expression Expression)
- (:abstraction (..expression (format (:representation name) " = " (:representation value)))))
-
(def: .public (set name value)
(-> Location Expression Statement)
(:abstraction (format (:representation name) " = " (:representation value) ..statement_suffix)))
@@ -323,13 +319,9 @@
(-> Expression Statement)
(:abstraction (format "return " (:representation value) ..statement_suffix)))
- (def: .public (delete' value)
- (-> Location Expression)
- (:abstraction (format "delete " (:representation value))))
-
(def: .public (delete value)
(-> Location Statement)
- (:abstraction (format (:representation (delete' value)) ..statement_suffix)))
+ (:abstraction (format "delete " (:representation value) ..statement_suffix)))
(def: .public (if test then! else!)
(-> Expression Statement Statement Statement)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux
index 7e56004c3..1fe22ef1a 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode.lux
@@ -700,9 +700,9 @@
[jump (\ ! each //signed.value
(/address.jump @from @to))]
(let [big? (n.> (//unsigned.value //unsigned.maximum/2)
- (.nat (i.* (if (i.>= +0 jump)
- +1
- -1)
+ (.nat (i.* (if (i.< +0 jump)
+ -1
+ +1)
jump)))]
(if big?
(\ ! each (|>> #.Left) (//signed.s4 jump))
diff --git a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
index 8a889a1ad..c294201b6 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux
@@ -74,9 +74,9 @@
(def: .public (<constructor> value)
(-> Nat (Try <name>))
- (if (n.<= (:representation <maximum>) value)
- (#try.Success (:abstraction value))
- (exception.except ..value_exceeds_the_maximum [(name_of <name>) value <maximum>])))
+ (if (n.> (:representation <maximum>) value)
+ (exception.except ..value_exceeds_the_maximum [(name_of <name>) value <maximum>])
+ (#try.Success (:abstraction value))))
(def: .public (<+> parameter subject)
(-> <name> <name> (Try <name>))
@@ -88,9 +88,9 @@
(-> <name> <name> (Try <name>))
(let [parameter' (:representation parameter)
subject' (:representation subject)]
- (if (n.<= subject' parameter')
- (#try.Success (:abstraction (n.- parameter' subject')))
- (exception.except ..subtraction_cannot_yield_negative_value [(name_of <name>) parameter subject]))))
+ (if (n.> subject' parameter')
+ (exception.except ..subtraction_cannot_yield_negative_value [(name_of <name>) parameter subject])
+ (#try.Success (:abstraction (n.- parameter' subject'))))))
(def: .public (<max> left right)
(-> <name> <name> <name>)
diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux
index 7a057f870..b307e8a79 100644
--- a/stdlib/source/library/lux/target/lua.lux
+++ b/stdlib/source/library/lux/target/lua.lux
@@ -159,7 +159,7 @@
(text.enclosed ["{" "}"])
:abstraction))
- (def: .public (nth idx array)
+ (def: .public (item idx array)
(-> Expression Expression Access)
(:abstraction (format (:representation array) "[" (:representation idx) "]")))
diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux
index afe40ea8b..b5275fa01 100644
--- a/stdlib/source/library/lux/test.lux
+++ b/stdlib/source/library/lux/test.lux
@@ -212,9 +212,9 @@
%.frac
(text.replaced/1 "+" ""))]
(|> raw
- (text.clip 0 (if (f.>= +10.0 done_percent)
- 5 ... XX.XX
+ (text.clip 0 (if (f.< +10.0 done_percent)
4 ... X.XX
+ 5 ... XX.XX
))
(maybe.else raw)
(text.suffix "%"))))))]
diff --git a/stdlib/source/library/lux/time/date.lux b/stdlib/source/library/lux/time/date.lux
index 7009c54eb..559638614 100644
--- a/stdlib/source/library/lux/time/date.lux
+++ b/stdlib/source/library/lux/time/date.lux
@@ -44,10 +44,10 @@
(//month.leap_year_days month)
(//month.days month)))
-(def: (day_is_within_limits? year month day)
+(def: (invalid_day? year month day)
(-> Year Month Nat Bit)
- (and (n.>= ..minimum_day day)
- (n.<= (..month_days year month) day)))
+ (or (n.< ..minimum_day day)
+ (n.> (..month_days year month) day)))
(exception: .public (invalid_day {year Year} {month Month} {day Nat})
(exception.report
@@ -77,13 +77,13 @@
(def: .public (date year month day_of_month)
(-> Year Month Nat (Try Date))
- (if (..day_is_within_limits? year month day_of_month)
+ (if (..invalid_day? year month day_of_month)
+ (exception.except ..invalid_day [year month day_of_month])
(#try.Success
(:abstraction
{#year year
#month month
- #day day_of_month}))
- (exception.except ..invalid_day [year month day_of_month])))
+ #day day_of_month}))))
(def: .public epoch
Date
@@ -163,10 +163,10 @@
(Parser Nat)
(do <>.monad
[value ..section_parser]
- (if (and (n.>= <minimum> value)
- (n.<= <maximum> value))
- (in value)
- (<>.lifted (exception.except <exception> [value])))))]
+ (if (or (n.< <minimum> value)
+ (n.> <maximum> value))
+ (<>.lifted (exception.except <exception> [value]))
+ (in value))))]
[1 12 month_parser invalid_month]
)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
index d5b6529f0..5532c5977 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
@@ -84,7 +84,7 @@
(#.Var id)
(do ///.monad
[?caseT' (//type.with_env
- (check.read' id))]
+ (check.peek id))]
(.case ?caseT'
(#.Some caseT')
(recur envs caseT')
@@ -110,7 +110,7 @@
(do ///.monad
[funcT' (//type.with_env
(do check.monad
- [?funct' (check.read' funcT_id)]
+ [?funct' (check.peek funcT_id)]
(.case ?funct'
(#.Some funct')
(in funct')
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
index 31ed0f394..36c5f193f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
@@ -48,12 +48,13 @@
... way, while the other tags cover more specific cases for bits
... and variants.
(type: .public #rec Coverage
- #Partial
- (#Bit Bit)
- (#Variant (Maybe Nat) (Dictionary Nat Coverage))
- (#Seq Coverage Coverage)
- (#Alt Coverage Coverage)
- #Exhaustive)
+ (.Variant
+ #Partial
+ (#Bit Bit)
+ (#Variant (Maybe Nat) (Dictionary Nat Coverage))
+ (#Seq Coverage Coverage)
+ (#Alt Coverage Coverage)
+ #Exhaustive))
(def: .public (exhaustive? coverage)
(-> Coverage Bit)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux
index 931e27eeb..a499b5df4 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux
@@ -71,7 +71,7 @@
(#.Var id)
(do !
[?expectedT' (//type.with_env
- (check.read' id))]
+ (check.peek id))]
(case ?expectedT'
(#.Some expectedT')
(recur expectedT')
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux
index 36ddce2e2..366a92cad 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux
@@ -167,7 +167,7 @@
(#.Var infer_id)
(do ///.monad
[?inferT' (//type.with_env
- (check.read' infer_id))]
+ (check.peek infer_id))]
(case ?inferT'
(#.Some inferT')
(general archive analyse inferT' args)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
index 76781c92a..f44670a38 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
@@ -119,7 +119,7 @@
(#.Var id)
(do !
[?expectedT' (//type.with_env
- (check.read' id))]
+ (check.peek id))]
(case ?expectedT'
(#.Some expectedT')
(//type.with_type expectedT'
@@ -145,7 +145,7 @@
(#.Var funT_id)
(do !
[?funT' (//type.with_env
- (check.read' funT_id))]
+ (check.peek funT_id))]
(case ?funT'
(#.Some funT')
(//type.with_type (#.Apply inputT funT')
@@ -209,7 +209,7 @@
(#.Var id)
(do !
[?expectedT' (//type.with_env
- (check.read' id))]
+ (check.peek id))]
(case ?expectedT'
(#.Some expectedT')
(//type.with_type expectedT'
@@ -239,7 +239,7 @@
(#.Var funT_id)
(do !
[?funT' (//type.with_env
- (check.read' funT_id))]
+ (check.peek funT_id))]
(case ?funT'
(#.Some funT')
(//type.with_type (#.Apply inputT funT')
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 b1b57e1ff..ef87ca48a 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
@@ -189,17 +189,19 @@
)
(type: Member
- {#class External
- #member Text})
+ (Record
+ {#class External
+ #member Text}))
(def: member
(Parser Member)
($_ <>.and <code>.text <code>.text))
(type: Method_Signature
- {#method .Type
- #deprecated? Bit
- #exceptions (List .Type)})
+ (Record
+ {#method .Type
+ #deprecated? Bit
+ #exceptions (List .Type)}))
(template [<name>]
[(exception: .public (<name> {type .Type})
@@ -1079,11 +1081,12 @@
objectA)))))]))
(type: Method_Style
- #Static
- #Abstract
- #Virtual
- #Special
- #Interface)
+ (Variant
+ #Static
+ #Abstract
+ #Virtual
+ #Special
+ #Interface))
(def: (check_method aliasing class method_name method_style inputsJT method)
(-> Aliasing (java/lang/Class java/lang/Object) Text Method_Style (List (Type Value)) java/lang/reflect/Method (Operation Bit))
@@ -1246,8 +1249,9 @@
exceptionsT]))))
(type: Evaluation
- (#Pass Method_Signature)
- (#Hint Method_Signature))
+ (Variant
+ (#Pass Method_Signature)
+ (#Hint Method_Signature)))
(template [<name> <tag>]
[(def: <name>
@@ -1597,10 +1601,11 @@
)
(type: .public Visibility
- #Public
- #Private
- #Protected
- #Default)
+ (Variant
+ #Public
+ #Private
+ #Protected
+ #Default))
(type: .public Finality Bit)
(type: .public Strictness Bit)
@@ -2022,7 +2027,8 @@
))))))
(type: .public (Method_Definition a)
- (#Overriden_Method (Overriden_Method a)))
+ (Variant
+ (#Overriden_Method (Overriden_Method a))))
(def: .public parameter_types
(-> (List (Type Var)) (Check (List [(Type Var) .Type])))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
index 11605c1d5..0c812936b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
@@ -19,7 +19,7 @@
[number
["f" frac]]]
["@" target
- ["_" lua (#+ Expression)]]]]
+ ["_" lua (#+ Expression Statement)]]]]
["." //// #_
["/" bundle]
["/#" // #_
@@ -28,12 +28,18 @@
[extension (#+ Nullary Unary Binary Trinary
nullary unary binary trinary)]
["//" lua #_
- ["#." runtime (#+ Operation Phase Handler Bundle Generator)]]]
+ ["#." runtime (#+ Operation Phase Phase! Handler Bundle Generator)]
+ ["#." primitive]
+ ["#." structure]
+ ["#." reference]
+ ["#." case]
+ ["#." loop]
+ ["#." function]]]
[//
- [synthesis (#+ %synthesis)]
+ ["." synthesis (#+ %synthesis)]
["." generation]
[///
- ["#" phase]]]]])
+ ["#" phase ("#\." monad)]]]]])
(def: .public (custom [parser handler])
(All [s]
@@ -49,7 +55,51 @@
(/////.except extension.invalid_syntax [extension_name %synthesis input]))))
(template: (!unary function)
- (|>> list _.apply/* (|> (_.var function))))
+ [(|>> list _.apply/* (|> (_.var function)))])
+
+(def: .public (statement expression archive synthesis)
+ Phase!
+ (case synthesis
+ ... TODO: Get rid of this ASAP
+ (#synthesis.Extension "lux syntax char case!" parameters)
+ (do /////.monad
+ [body (expression archive synthesis)]
+ (in (:as Statement body)))
+
+ (^template [<tag>]
+ [(^ (<tag> value))
+ (/////\each _.return (expression archive synthesis))])
+ ([synthesis.bit]
+ [synthesis.i64]
+ [synthesis.f64]
+ [synthesis.text]
+ [synthesis.variant]
+ [synthesis.tuple]
+ [#synthesis.Reference]
+ [synthesis.branch/get]
+ [synthesis.function/apply]
+ [#synthesis.Extension])
+
+ (^ (synthesis.branch/case case))
+ (//case.case! statement expression archive case)
+
+ (^ (synthesis.branch/let let))
+ (//case.let! statement expression archive let)
+
+ (^ (synthesis.branch/if if))
+ (//case.if! statement expression archive if)
+
+ (^ (synthesis.loop/scope scope))
+ (do /////.monad
+ [[inits scope!] (//loop.scope! statement expression archive false scope)]
+ (in scope!))
+
+ (^ (synthesis.loop/recur updates))
+ (//loop.recur! statement expression archive updates)
+
+ (^ (synthesis.function/abstraction abstraction))
+ (/////\each _.return (//function.function statement expression archive abstraction))
+ ))
... TODO: Get rid of this ASAP
(def: lux::syntax_char_case!
@@ -62,12 +112,12 @@
(function (_ extension_name phase archive [input else conditionals])
(do {! /////.monad}
[inputG (phase archive input)
- elseG (phase archive else)
+ else! (..statement phase archive else)
@input (\ ! each _.var (generation.identifier "input"))
- conditionalsG (: (Operation (List [Expression Expression]))
+ conditionals! (: (Operation (List [Expression Statement]))
(monad.each ! (function (_ [chars branch])
(do !
- [branchG (phase archive branch)]
+ [branch! (..statement phase archive branch)]
(in [(|> chars
(list\each (|>> .int _.int (_.= @input)))
(list\mix (function (_ clause total)
@@ -75,14 +125,23 @@
clause
(_.or clause total)))
_.nil))
- branchG])))
+ branch!])))
conditionals))
- .let [closure (_.closure (list @input)
- (list\mix (function (_ [test then] else)
- (_.if test (_.return then) else))
- (_.return elseG)
- conditionalsG))]]
- (in (_.apply/1 closure inputG))))]))
+ ... .let [closure (_.closure (list @input)
+ ... (list\mix (function (_ [test then] else)
+ ... (_.if test (_.return then) else))
+ ... (_.return elseG)
+ ... conditionalsG))]
+ ]
+ ... (in (_.apply/1 closure inputG))
+ (in (<| (:as Expression)
+ (: Statement)
+ ($_ _.then
+ (_.set (list @input) inputG)
+ (list\mix (function (_ [test then!] else!)
+ (_.if test then! else!))
+ else!
+ conditionals!))))))]))
(def: lux_procs
Bundle
@@ -98,8 +157,8 @@
(/.install "and" (binary (product.uncurried _.bit_and)))
(/.install "or" (binary (product.uncurried _.bit_or)))
(/.install "xor" (binary (product.uncurried _.bit_xor)))
- (/.install "left-shift" (binary (product.uncurried //runtime.i64//left_shift)))
- (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shift)))
+ (/.install "left-shift" (binary (product.uncurried //runtime.i64//left_shifted)))
+ (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shifted)))
(/.install "=" (binary (product.uncurried _.=)))
(/.install "+" (binary (product.uncurried _.+)))
(/.install "-" (binary (product.uncurried _.-)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
index 78e4d7a4a..16ac4b882 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
@@ -140,13 +140,14 @@
... _ (generation.save! (product.right artifact_id) #.None closure)
]
... (in (_.apply/* @closure dependencies))
- (in (:as (Expression Any)
- ($_ _.then
- (_.set (list @input) inputG)
- (list\mix (function (_ [test then!] else!)
- (_.if test then! else!))
- else!
- conditionals!))))))]))
+ (in (<| (:as (Expression Any))
+ (: (Statement Any))
+ ($_ _.then
+ (_.set (list @input) inputG)
+ (list\mix (function (_ [test then!] else!)
+ (_.if test then! else!))
+ else!
+ conditionals!))))))]))
(def: lux_procs
Bundle
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
index 6579de615..b76af26be 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
@@ -601,12 +601,12 @@
(_.apply/1 (_.var "Math.log"))
(_./ (_.var "Math.LN2"))
(_.apply/1 (_.var "Math.ceil"))))
- (_.define delta (_.? (_.<= (_.i32 +48) log2)
- (_.i32 +1)
+ (_.define delta (_.? (_.> (_.i32 +48) log2)
(_.apply/2 (_.var "Math.pow")
(_.i32 +2)
(_.- (_.i32 +48)
- log2))))
+ log2))
+ (_.i32 +1)))
(_.define approximate_result approximate_result')
(_.define approximate_remainder approx_remainder)
(_.while (_.or (negative? approximate_remainder)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux
index 59dc82f3c..05fa66ca8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux
@@ -8,7 +8,7 @@
[target
["_" lua]]]]
["." / #_
- [runtime (#+ Phase Phase!)]
+ [runtime (#+ Phase)]
["#." primitive]
["#." structure]
["#." reference]
@@ -18,7 +18,10 @@
["/#" // #_
["#." reference]
["/#" // #_
- ["#." extension]
+ ["#." extension
+ [generation
+ [lua
+ ["#/." common]]]]
["/#" // #_
[analysis (#+)]
["." synthesis]
@@ -27,44 +30,6 @@
[reference (#+)
[variable (#+)]]]]]]])
-(def: (statement expression archive synthesis)
- Phase!
- (case synthesis
- (^template [<tag>]
- [(^ (<tag> value))
- (//////phase\each _.return (expression archive synthesis))])
- ([synthesis.bit]
- [synthesis.i64]
- [synthesis.f64]
- [synthesis.text]
- [synthesis.variant]
- [synthesis.tuple]
- [#synthesis.Reference]
- [synthesis.branch/get]
- [synthesis.function/apply]
- [#synthesis.Extension])
-
- (^ (synthesis.branch/case case))
- (/case.case! statement expression archive case)
-
- (^ (synthesis.branch/let let))
- (/case.let! statement expression archive let)
-
- (^ (synthesis.branch/if if))
- (/case.if! statement expression archive if)
-
- (^ (synthesis.loop/scope scope))
- (do //////phase.monad
- [[inits scope!] (/loop.scope! statement expression archive false scope)]
- (in scope!))
-
- (^ (synthesis.loop/recur updates))
- (/loop.recur! statement expression archive updates)
-
- (^ (synthesis.function/abstraction abstraction))
- (//////phase\each _.return (/function.function statement expression archive abstraction))
- ))
-
(exception: .public cannot_recur_as_an_expression)
(def: (expression archive synthesis)
@@ -88,7 +53,7 @@
(//reference.reference /reference.system archive value)
(^ (synthesis.branch/case case))
- (/case.case ..statement expression archive case)
+ (/case.case ///extension/common.statement expression archive case)
(^ (synthesis.branch/let let))
(/case.let expression archive let)
@@ -100,13 +65,13 @@
(/case.get expression archive get)
(^ (synthesis.loop/scope scope))
- (/loop.scope ..statement expression archive scope)
+ (/loop.scope ///extension/common.statement expression archive scope)
(^ (synthesis.loop/recur updates))
(//////phase.except ..cannot_recur_as_an_expression [])
(^ (synthesis.function/abstraction abstraction))
- (/function.function ..statement expression archive abstraction)
+ (/function.function ///extension/common.statement expression archive abstraction)
(^ (synthesis.function/apply application))
(/function.apply expression archive application)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
index 0d96c3150..f88bc1d3a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux (#- function)
+ [lux (#- Tuple Variant function)
[abstract
["." monad (#+ do)]]
[control
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux
index 59d70ae69..ebb503f26 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux #*
+ [lux (#- Tuple Variant)
[abstract
["." monad (#+ do)]]
[target
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
index 5d91dbde7..26c962945 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
@@ -180,10 +180,10 @@
(runtime: (i64::unsigned_low input)
(with_vars [low]
($_ _.then
- (_.set! low (|> input (_.item (_.string ..i64_low_field))))
- (_.if (|> low (_.>= (_.int +0)))
- low
- (|> low (_.+ f2^32))))))
+ (_.set! low (_.item (_.string ..i64_low_field) input))
+ (_.if (_.< (_.int +0) low)
+ (_.+ f2^32 low)
+ low))))
(runtime: (i64::float input)
(let [high (|> input
@@ -423,9 +423,10 @@
(i64::new high low))])
(let [low (|> (i64_high input)
(i64::arithmetic_right_shifted_32 (|> shift (_.- (_.int +32)))))
- high (_.if (|> (i64_high input) (_.>= (_.int +0)))
- (_.int +0)
- (_.int -1))]
+ high (_.if (_.< (_.int +0)
+ (i64_high input))
+ (_.int -1)
+ (_.int +0))]
(i64::new high low)))))
(runtime: (i64::/ param subject)
@@ -485,10 +486,10 @@
(_.var "floor"))
calc_approximate_result (i64::of_float approximate)
calc_approximate_remainder (|> approximate_result (i64::* param))
- delta (_.if (|> (_.float +48.0) (_.<= log2))
- (_.float +1.0)
+ delta (_.if (_.> log2 (_.float +48.0))
(_.** (|> log2 (_.- (_.float +48.0)))
- (_.float +2.0)))]
+ (_.float +2.0))
+ (_.float +1.0))]
($_ _.then
(_.set! approximate (_.apply (list (_.float +1.0) calc_rough_estimate)
(_.var "max")))
@@ -722,15 +723,6 @@
(-> Expression Expression)
(|>> (_.+ (_.int +1))))
-(template [<name> <top_cmp>]
- [(def: (<name> top value)
- (-> Expression Expression Expression)
- (|> (|> value (_.>= (_.int +0)))
- (_.and (|> value (<top_cmp> top)))))]
-
- [within? _.<]
- )
-
(def: (text_clip start end text)
(-> Expression Expression Expression Expression)
(_.apply (list text start end)
@@ -745,7 +737,7 @@
($_ _.then
(_.set! startF (i64::float start))
(_.set! subjectL (text_length subject))
- (_.if (|> startF (within? subjectL))
+ (_.if (_.< subjectL startF)
($_ _.then
(_.set! idx (|> (_.apply_kw (list param (_.if (|> startF (_.= (_.int +0)))
subject
@@ -765,7 +757,7 @@
($_ _.then
(_.set! length (_.length text))
(_.set! to (_.+ additional minimum))
- (_.if (within? length to)
+ (_.if (_.< length to)
(..some (text_clip (++ minimum) (++ to) text))
..none))))
@@ -775,7 +767,7 @@
(_.var "utf8ToInt")))
(runtime: (text::char text idx)
- (_.if (|> idx (within? (_.length text)))
+ (_.if (_.< (_.length text) idx)
($_ _.then
(_.set! idx (++ idx))
(..some (i64::of_float (char_at idx text))))
@@ -791,9 +783,9 @@
(def: (check_index_out_of_bounds array idx body)
(-> Expression Expression Expression Expression)
- (_.if (|> idx (_.<= (_.length array)))
- body
- (_.stop (_.string "Array index out of bounds!"))))
+ (_.if (_.> (_.length array) idx)
+ (_.stop (_.string "Array index out of bounds!"))
+ body))
(runtime: (array::new size)
(with_vars [output]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
index 75e27d5bf..b6544e285 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
@@ -317,8 +317,9 @@
"Invalid expression for pattern-matching.")
(type: .public Storage
- {#bindings (Set Register)
- #dependencies (Set Variable)})
+ (Record
+ {#bindings (Set Register)
+ #dependencies (Set Variable)}))
(def: empty
Storage
diff --git a/stdlib/source/library/lux/type.lux b/stdlib/source/library/lux/type.lux
index fb2baf861..60aebf7e9 100644
--- a/stdlib/source/library/lux/type.lux
+++ b/stdlib/source/library/lux/type.lux
@@ -1,5 +1,4 @@
(.module:
- {#.doc "Basic functionality for working with types."}
[library
[lux (#- function :as)
["@" target]
@@ -30,7 +29,6 @@
(template [<name> <tag>]
[(def: .public (<name> type)
- {#.doc (example "The number of parameters, and the body, of a quantified type.")}
(-> Type [Nat Type])
(loop [num_args 0
type type]
@@ -46,7 +44,6 @@
)
(def: .public (flat_function type)
- {#.doc (example "The input, and the output of a function type.")}
(-> Type [(List Type) Type])
(case type
(#.Function in out')
@@ -57,7 +54,6 @@
[(list) type]))
(def: .public (flat_application type)
- {#.doc (example "The quantified type, and its parameters, for a type-application.")}
(-> Type [Type (List Type)])
(case type
(#.Apply arg func')
@@ -69,7 +65,6 @@
(template [<name> <tag>]
[(def: .public (<name> type)
- {#.doc (example "The members of a composite type.")}
(-> Type (List Type))
(case type
(<tag> left right)
@@ -83,7 +78,6 @@
)
(def: .public (format type)
- {#.doc (example "A (readable) textual representable of a type.")}
(-> Type Text)
(case type
(#.Primitive name params)
@@ -227,7 +221,6 @@
))))
(def: .public (applied params func)
- {#.doc (example "To the extend possible, applies a quantified type to the given parameters.")}
(-> (List Type) Type (Maybe Type))
(case params
#.End
@@ -252,8 +245,6 @@
#.None)))
(def: .public (code type)
- {#.doc (example "A representation of a type as code."
- "The code is such that evaluating it would yield the type value.")}
(-> Type Code)
(case type
(#.Primitive name params)
@@ -282,7 +273,6 @@
))
(def: .public (de_aliased type)
- {#.doc (example "A (potentially named) type that does not have its name shadowed by other names.")}
(-> Type Type)
(case type
(#.Named _ (#.Named name type'))
@@ -292,7 +282,6 @@
type))
(def: .public (anonymous type)
- {#.doc (example "A type without any names covering it.")}
(-> Type Type)
(case type
(#.Named name type')
@@ -303,7 +292,6 @@
(template [<name> <base> <ctor>]
[(def: .public (<name> types)
- {#.doc (example "A composite type, constituted by the given member types.")}
(-> (List Type) Type)
(case types
#.End
@@ -320,7 +308,6 @@
)
(def: .public (function inputs output)
- {#.doc (example "A function type, with the given inputs and output.")}
(-> (List Type) Type Type)
(case inputs
#.End
@@ -330,7 +317,6 @@
(#.Function input (function inputs' output))))
(def: .public (application params quant)
- {#.doc (example "An un-evaluated type application, with the given quantified type, and parameters.")}
(-> (List Type) Type Type)
(case params
#.End
@@ -341,7 +327,6 @@
(template [<name> <tag>]
[(def: .public (<name> size body)
- {#.doc (example "A quantified type, with the given number of parameters, and body.")}
(-> Nat Type Type)
(case size
0 body
@@ -352,7 +337,6 @@
)
(def: .public (quantified? type)
- {#.doc (example "Only yields #1 for universally or existentially quantified types.")}
(-> Type Bit)
(case type
(#.Named [module name] _type)
@@ -370,7 +354,6 @@
#0))
(def: .public (array depth element_type)
- {#.doc (example "An array type, with the given level of nesting/depth, and the given element type.")}
(-> Nat Type Type)
(case depth
0 element_type
@@ -380,7 +363,6 @@
(#.Primitive array.type_name))))
(def: .public (flat_array type)
- {#.doc (example "The level of nesting/depth and element type for an array type.")}
(-> Type [Nat Type])
(case type
(^multi (^ (#.Primitive name (list element_type)))
@@ -392,7 +374,6 @@
[0 type]))
(def: .public array?
- {#.doc (example "Is a type an array type?")}
(-> Type Bit)
(|>> ..flat_array
product.left
@@ -408,12 +389,6 @@
(syntax: .public (:log! [input (<>.or (<>.and <code>.identifier
(<>.maybe (<>.after (<code>.identifier! ..secret_marker) <code>.any)))
<code>.any)])
- {#.doc (example "Logs to the console/terminal the type of an expression."
- (:log! (: Foo (foo expression)))
- "=>"
- "Expression: (foo expression)"
- " Type: Foo"
- (foo expression))}
(case input
(#.Left [valueN valueC])
(do meta.monad
@@ -445,15 +420,6 @@
input <code>.any
output <code>.any
value (<>.maybe <code>.any)])
- {#.doc (example "Casts a value to a specific type."
- "The specified type can depend on type variables of the original type of the value."
- (: (Bar Bit Nat Text)
- (:as [a b c]
- (Foo a [b c])
- (Bar a b c)
- (: (Foo Bit [Nat Text])
- (foo expression))))
- "NOTE: Careless use of type-casts is an easy way to introduce bugs. USE WITH CAUTION.")}
(let [casterC (` (: (All [(~+ (list\each code.local_identifier type_vars))]
(-> (~ input) (~ output)))
(|>> :expected)))]
@@ -477,15 +443,6 @@
(syntax: .public (:sharing [type_vars ..type_parameters
exemplar ..typed
computation ..typed])
- {#.doc (example "Allows specifing the type of an expression as sharing type-variables with the type of another expression."
- (: (Bar Bit Nat Text)
- (:sharing [a b c]
- (Foo a [b c])
- (: (Foo Bit [Nat Text])
- (foo expression))
-
- (Bar a b c)
- (bar expression))))}
(macro.with_identifiers [g!_]
(let [shareC (` (: (All [(~+ (list\each code.local_identifier type_vars))]
(-> (~ (value@ #type exemplar))
@@ -497,16 +454,6 @@
(syntax: .public (:by_example [type_vars ..type_parameters
exemplar ..typed
extraction <code>.any])
- {#.doc (example "Constructs a type that shares type-variables with an expression of some other type."
- (: Type
- (:by_example [a b c]
- (Foo a [b c])
- (: (Foo Bit [Nat Text])
- (foo expression))
-
- (Bar a b c)))
- "=>"
- (.type (Bar Bit Nat Text)))}
(in (list (` (:of ((~! :sharing)
[(~+ (list\each code.local_identifier type_vars))]
diff --git a/stdlib/source/library/lux/type/check.lux b/stdlib/source/library/lux/type/check.lux
index 2d57a12d7..aaac468d1 100644
--- a/stdlib/source/library/lux/type/check.lux
+++ b/stdlib/source/library/lux/type/check.lux
@@ -204,13 +204,13 @@
(exception.except ..unknown_type_var id))))]
[bound? Bit false true]
- [read' (Maybe Type) #.None (#.Some bound)]
+ [peek (Maybe Type) #.None (#.Some bound)]
)
(def: .public (read id)
(-> Var (Check Type))
(do ..monad
- [?type (read' id)]
+ [?type (peek id)]
(case ?type
(#.Some type)
(in type)
@@ -270,7 +270,7 @@
(case funcT
(#.Var func_id)
(do ..monad
- [?funcT' (read' func_id)]
+ [?funcT' (peek func_id)]
(case ?funcT'
(#.Some funcT')
(on argT funcT')
@@ -369,7 +369,7 @@
_ (monad.each ! (re_bind type) (set.list ring))]
then)
(do ..monad
- [?bound (read' id)]
+ [?bound (peek id)]
(else (maybe.else (#.Var id) ?bound)))))
... TODO: "link/2" can be optimized...
@@ -546,11 +546,12 @@
(def: (with exception parameter check)
(All [e a] (-> (Exception e) e (Check a) (Check a)))
- (|>> check (exception.with exception parameter)))
+ (|>> check
+ (exception.with exception parameter)))
... TODO: "check'" can be optimized...
+... Type-check to ensure that the 'expected' type subsumes the 'actual' type.
(def: (check' assumptions expected actual)
- {#.doc "Type-check to ensure that the 'expected' type subsumes the 'actual' type."}
(Checker Type)
(if (for {@.php false} ... TODO: Remove this once JPHP is gone.
(same? expected actual))
@@ -664,7 +665,8 @@
(def: .public (subsumes? expected actual)
(-> Type Type Bit)
- (case (..result ..fresh_context (..check' (list) expected actual))
+ (case (..result ..fresh_context
+ (..check expected actual))
(#try.Failure _)
false
@@ -697,7 +699,7 @@
(#.Var id)
(do ..monad
- [?actualT (read' id)]
+ [?actualT (peek id)]
(case ?actualT
(#.Some actualT)
(clean actualT)
diff --git a/stdlib/source/library/lux/type/quotient.lux b/stdlib/source/library/lux/type/quotient.lux
index be7663444..42da7c4d7 100644
--- a/stdlib/source/library/lux/type/quotient.lux
+++ b/stdlib/source/library/lux/type/quotient.lux
@@ -12,7 +12,7 @@
abstract]]])
(abstract: .public (Class t c %)
- {#.doc (example "The class knows how to classify/label values that are meant to be equivalent to one another.")}
+ {}
(-> t c)
@@ -23,9 +23,7 @@
(|>> :abstraction))
(abstract: .public (Quotient t c %)
- {#.doc (example "A quotient value has been labeled with a class."
- "All equivalent values will belong to the same class."
- "This means all equivalent values possess the same label.")}
+ {}
(Record
{#value t
@@ -50,16 +48,6 @@
)
(syntax: .public (type [class <code>.any])
- {#.doc (example "The Quotient type associated with a Class type."
- (def: even
- (class even?))
-
- (def: Even
- Type
- (type even))
-
- (: Even
- (quotient even 123)))}
(with_identifiers [g!t g!c g!%]
(in (list (` ((~! type.:by_example)
[(~ g!t) (~ g!c) (~ g!%)]
diff --git a/stdlib/source/library/lux/type/refinement.lux b/stdlib/source/library/lux/type/refinement.lux
index 2ab800d2c..03d064acc 100644
--- a/stdlib/source/library/lux/type/refinement.lux
+++ b/stdlib/source/library/lux/type/refinement.lux
@@ -12,14 +12,13 @@
abstract]]])
(abstract: .public (Refined t %)
- {#.doc "A refined version of another type, using a predicate to select valid instances."}
+ {}
(Record
{#value t
#predicate (Predicate t)})
(type: .public (Refiner t %)
- {#.doc (example "A selection mechanism for refined instances of a type.")}
(-> t (Maybe (Refined t %))))
(def: .public (refiner predicate)
@@ -42,8 +41,6 @@
)
(def: .public (lifted transform)
- {#.doc (example "Yields a function that can work on refined values."
- "Respects the constraints of the refinement.")}
(All [t %]
(-> (-> t t)
(-> (Refined t %) (Maybe (Refined t %)))))
@@ -72,7 +69,6 @@
(only refiner tail))))
(def: .public (partition refiner values)
- {#.doc (example "Separates refined values from the un-refined ones.")}
(All [t %]
(-> (Refiner t %) (List t) [(List (Refined t %)) (List t)]))
(case values
@@ -91,16 +87,6 @@
(#.Item head no)]))))
(syntax: .public (type [refiner <code>.any])
- {#.doc (example "The Refined type associated with a Refiner type."
- (def: even
- (refiner even?))
-
- (def: Even
- Type
- (type even))
-
- (: (Maybe Even)
- (even 123)))}
(macro.with_identifiers [g!t g!%]
(in (list (` ((~! type.:by_example) [(~ g!t) (~ g!%)]
(..Refiner (~ g!t) (~ g!%))
diff --git a/stdlib/source/library/lux/type/resource.lux b/stdlib/source/library/lux/type/resource.lux
index 796bf4e4d..b07f56303 100644
--- a/stdlib/source/library/lux/type/resource.lux
+++ b/stdlib/source/library/lux/type/resource.lux
@@ -26,25 +26,17 @@
abstract]]])
(type: .public (Procedure monad input output value)
- {#.doc (example "A computation that takes a sequence of resource access rights as inputs and yields a different sequence as outputs."
- "A procedure yields a result value."
- "A procedure can make use of monadic effects.")}
(-> input (monad [output value])))
(type: .public (Linear monad value)
- {#.doc (example "A procedure that is constant with regards to resource access rights."
- "This means no additional resources will be available after the computation is over."
- "This also means no previously available resources will have been consumed.")}
(All [keys]
(Procedure monad keys keys value)))
(type: .public (Affine monad permissions value)
- {#.doc (example "A procedure which expands the number of available resources.")}
(All [keys]
(Procedure monad keys [permissions keys] value)))
(type: .public (Relevant monad permissions value)
- {#.doc (example "A procedure which reduces the number of available resources.")}
(All [keys]
(Procedure monad [permissions keys] keys value)))
@@ -74,17 +66,11 @@
[output procedure]
(in [keys output]))))
-(abstract: .public Ordered
- {#.doc (example "The mode of keys which CANNOT be swapped, and for whom order of release/consumption matters.")}
- Any)
-
-(abstract: .public Commutative
- {#.doc (example "The mode of keys which CAN be swapped, and for whom order of release/consumption DOES NOT matters.")}
- Any)
+(abstract: .public Ordered {} Any)
+(abstract: .public Commutative {} Any)
(abstract: .public (Key mode key)
- {#.doc (example "The access right for a resource."
- "Without the key for a resource existing somewhere among the available ambient rights, one cannot use a resource.")}
+ {}
Any
@@ -98,14 +84,12 @@
))
(abstract: .public (Res key value)
- {#.doc (example "A resource locked by a key."
- "The 'key' represents the right to access/consume a resource.")}
+ {}
value
(template [<name> <mode> <key>]
[(def: .public (<name> monad value)
- {#.doc (example "Makes a value into a resource and adds the key/access-right to it to the ambient keyring for future use.")}
(All [! v] (Ex [k] (-> (Monad !) v (Affine ! (Key <mode> k) (Res k v)))))
(function (_ keys)
(\ monad in [[(<key> []) keys] (:abstraction value)])))]
@@ -115,7 +99,6 @@
)
(def: .public (read monad resource)
- {#.doc (example "Access the value of a resource, so long as its key is available.")}
(All [! v k m]
(-> (Monad !) (Res k v) (Relevant ! (Key m k) v)))
(function (_ [key keys])
@@ -148,16 +131,6 @@
(\ monad in [context []])))
(syntax: .public (exchange [swaps ..indices])
- {#.doc (example "A function that can exchange the keys for resource, so long as they are commutative."
- "This keys will be placed at the front of the keyring in the order they are specified."
- "The specific keys must be specified based of their index into the current keyring."
- (do (..monad !)
- [res|left (commutative ! pre)
- res|right (commutative ! post)
- _ ((exchange [1 0]) !)
- left (read ! res|left)
- right (read ! res|right)]
- (in (format left right))))}
(macro.with_identifiers [g!_ g!context g!!]
(case swaps
#.End
@@ -197,15 +170,6 @@
(template [<name> <from> <to>]
[(syntax: .public (<name> [amount ..amount])
- {#.doc (example "Group/un-group keys in the keyring into/out-of tuples."
- (do (..monad !)
- [res|left (commutative ! pre)
- res|right (commutative ! post)
- _ ((group 2) !)
- _ ((un_group 2) !)
- right (read ! res|right)
- left (read ! res|left)]
- (in (format left right))))}
(macro.with_identifiers [g!_ g!context g!!]
(do {! meta.monad}
[g!keys (|> (macro.identifier "keys")
diff --git a/stdlib/source/library/lux/type/unit.lux b/stdlib/source/library/lux/type/unit.lux
index e18af25b0..c4f1e5e58 100644
--- a/stdlib/source/library/lux/type/unit.lux
+++ b/stdlib/source/library/lux/type/unit.lux
@@ -28,7 +28,7 @@
abstract]]])
(abstract: .public (Qty unit)
- {#.doc (example "A quantity with an associated unit of measurement.")}
+ {}
Int
@@ -62,14 +62,12 @@
)
(interface: .public (Unit a)
- {#.doc (example "A unit of measurement, to qualify numbers with.")}
(: (-> Int (Qty a))
in)
(: (-> (Qty a) Int)
out))
(interface: .public (Scale s)
- {#.doc (example "A scale of magnitude.")}
(: (All [u] (-> (Qty u) (Qty (s u))))
scale)
(: (All [u] (-> (Qty (s u)) (Qty u)))
@@ -78,7 +76,6 @@
ratio))
(type: .public Pure
- {#.doc (example "A pure, unit-less quantity.")}
(Qty Any))
(def: .public pure
@@ -95,10 +92,6 @@
<code>.local_identifier
<code>.local_identifier
(<>.else |annotations|.empty |annotations|.parser)))])
- {#.doc (example "Define a unit of measurement."
- "Both the name of the type, and the name of the Unit implementation must be specified."
- (unit: .public Feet feet
- {#.doc (example "Optional annotations.")}))}
(do meta.monad
[@ meta.current_module_name
.let [g!type (code.local_identifier type_name)]]
@@ -131,10 +124,6 @@
<code>.local_identifier
..scale
(<>.else |annotations|.empty |annotations|.parser)))])
- {#.doc (example "Define a scale of magnitude."
- (scale: .public Bajillion bajillion
- [1 1,234,567,890]
- {#.doc (example "Optional annotations.")}))}
(do meta.monad
[.let [(^slots [#ratio.numerator #ratio.denominator]) ratio]
@ meta.current_module_name
@@ -176,8 +165,7 @@
(template [<type> <from> <to>]
[(`` (scale: .public <type>
(~~ (implementation_name <type>))
- [<from> <to>]
- {#.doc (example (~~ (template.text ["'" <type> "' scale from " <from> " to " <to> "."])))}))]
+ [<from> <to>]))]
[Kilo 1 1,000]
[Mega 1 1,000,000]
@@ -190,8 +178,7 @@
(template [<type>]
[(`` (unit: .public <type>
- (~~ (implementation_name <type>))
- {#.doc (example (~~ (template.text ["'" <type> "' unit of meaurement."])))}))]
+ (~~ (implementation_name <type>))))]
[Gram]
[Meter]
diff --git a/stdlib/source/library/lux/type/variance.lux b/stdlib/source/library/lux/type/variance.lux
index 8502ec6fa..2a7d65267 100644
--- a/stdlib/source/library/lux/type/variance.lux
+++ b/stdlib/source/library/lux/type/variance.lux
@@ -3,13 +3,10 @@
[lux #*]])
(type: .public (Co t)
- {#.doc (example "A constraint for covariant types.")}
(-> Any t))
(type: .public (Contra t)
- {#.doc (example "A constraint for contravariant types.")}
(-> t Any))
(type: .public (In t)
- {#.doc (example "A constraint for invariant types.")}
(-> t t))
diff --git a/stdlib/source/library/lux/world/console.lux b/stdlib/source/library/lux/world/console.lux
index 4f52cacb1..02d4ee299 100644
--- a/stdlib/source/library/lux/world/console.lux
+++ b/stdlib/source/library/lux/world/console.lux
@@ -17,8 +17,6 @@
["%" format (#+ format)]]]]])
(interface: .public (Console !)
- {#.doc (example "An interface to console/terminal I/O.")}
-
(: (-> [] (! (Try Char)))
read)
(: (-> [] (! (Try Text)))
@@ -101,14 +99,10 @@
(as_is)))
(def: .public (write_line message console)
- {#.doc (example "Writes the message on the console and appends a new-line/line-feed at the end.")}
(All [!] (-> Text (Console !) (! (Try Any))))
(\ console write (format message text.new_line)))
(interface: .public (Mock s)
- {#.doc (example "A mock/simulation of a console."
- "Useful for testing.")}
-
(: (-> s (Try [s Char]))
on_read)
(: (-> s (Try [s Text]))
diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux
index 08bffdb97..d9676e54e 100644
--- a/stdlib/source/library/lux/world/file.lux
+++ b/stdlib/source/library/lux/world/file.lux
@@ -36,12 +36,9 @@
["." duration]]]])
(type: .public Path
- {#.doc (example "A path to a file or a directory in a file-system.")}
Text)
(`` (interface: .public (System !)
- {#.doc (example "An interface to a file-system.")}
-
(: Text
separator)
@@ -93,14 +90,12 @@
(in [parent child])))))
(def: .public (parent fs path)
- {#.doc (example "If a path represents a nested file/directory, extracts its parent directory.")}
(All [!] (-> (System !) Path (Maybe Path)))
(|> path
(..un_rooted fs)
(maybe\each product.left)))
(def: .public (name fs path)
- {#.doc (example "The un-nested name of a file/directory.")}
(All [!] (-> (System !) Path Text))
(|> path
(..un_rooted fs)
@@ -142,7 +137,6 @@
)))
(def: .public (rooted fs parent child)
- {#.doc (example "A nested path for a file/directory, given a root/parent path and a file/directory name within it.")}
(All [!] (-> (System !) Path Text Path))
(format parent (\ fs separator) child))
@@ -236,7 +230,7 @@
(case ?children
(#.Some children)
(|> children
- array.list
+ (array.list #.None)
(monad.only ! (|>> <method>))
(\ ! each (monad.each ! (|>> java/io/File::getAbsolutePath)))
(\ ! conjoint))
@@ -455,7 +449,7 @@
subs (with_async write! (Try (Array ffi.String))
(Fs::readdir [path (..value_callback write!)] node_fs))]
(|> subs
- array.list
+ (array.list #.None)
(list\each (|>> (format path ..js_separator)))
(monad.each ! (function (_ sub)
(\ ! each (|>> (<method> []) [sub])
@@ -602,7 +596,7 @@
(let [! (try.with io.monad)]
(|> path
os::listdir
- (\ ! each (|>> array.list
+ (\ ! each (|>> (array.list #.None)
(list\each (|>> (format path ..python_separator)))
(monad.each ! (function (_ sub)
(\ ! each (|>> [sub]) (<method> [sub]))))
@@ -729,7 +723,7 @@
[self (RubyDir::open [path])
children (RubyDir::children [] self)
output (loop [input (|> children
- array.list
+ (array.list #.None)
(list\each (|>> (format path ..ruby_separator))))
output (: (List ..Path)
(list))]
@@ -922,7 +916,7 @@
... (do {! (try.with io.monad)}
... [children (..scandir [path])]
... (loop [input (|> children
- ... array.list
+ ... (array.list #.None)
... (list.only (function (_ child)
... (not (or (text\= "." child)
... (text\= ".." child))))))
@@ -991,7 +985,6 @@
(as_is)))
(def: .public (exists? monad fs path)
- {#.doc (example "Checks if either a file or a directory exists at the given path.")}
(All [!] (-> (Monad !) (System !) Path (! Bit)))
(do monad
[verdict (\ fs file? path)]
@@ -1178,8 +1171,6 @@
(recur sub_directory tail)))))))
(def: .public (mock separator)
- {#.doc (example "A purely in-memory simulation of a file-system."
- "Useful for testing.")}
(-> Text (System Async))
(let [store (stm.var ..empty_mock)]
(`` (implementation
@@ -1328,8 +1319,6 @@
(\ fs make_directory path))))
(def: .public (make_directories monad fs path)
- {#.doc (example "Creates the directory specified by the given path."
- "Also, creates every super-directory necessary to make the given path valid.")}
(All [!] (-> (Monad !) (System !) Path (! (Try Any))))
(let [rooted? (text.starts_with? (\ fs separator) path)
segments (text.all_split_by (\ fs separator) path)]
@@ -1362,7 +1351,6 @@
(in (#try.Failure error)))))))))
(def: .public (make_file monad fs content path)
- {#.doc (example "Creates a new file with the given content if-and-only-if the file does not already exist.")}
(All [!] (-> (Monad !) (System !) Binary Path (! (Try Any))))
(do monad
[? (\ fs file? path)]
diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux
index 35dfb894d..581beba6d 100644
--- a/stdlib/source/library/lux/world/file/watch.lux
+++ b/stdlib/source/library/lux/world/file/watch.lux
@@ -33,7 +33,7 @@
["." //])
(abstract: .public Concern
- {#.doc (example "A particular concern to watch-out for.")}
+ {}
(Record
{#creation Bit
@@ -84,8 +84,6 @@
)
(interface: .public (Watcher !)
- {#.doc (example "Machinery for watching a file-system for changes to files and directories.")}
-
(: (-> Concern //.Path (! (Try Any)))
start)
(: (-> //.Path (! (Try Concern)))
@@ -188,8 +186,6 @@
deletions]])))
(def: .public (polling fs)
- {#.doc (example "A simple watcher that works for any file-system."
- "Polls files and directories to detect changes.")}
(-> (//.System Async) (Watcher Async))
(let [tracker (: (Var Directory_Tracker)
(stm.var (dictionary.empty text.hash)))]
@@ -262,8 +258,6 @@
)))
(def: .public (mock separator)
- {#.doc (example "A fake/emulated watcher."
- "Must be given a path separator for the file-system.")}
(-> Text [(//.System Async) (Watcher Async)])
(let [fs (//.mock separator)]
[fs
@@ -415,7 +409,6 @@
))
(def: .public default
- {#.doc (example "The default watcher for the default file-system.")}
(IO (Try (Watcher Async)))
(do (try.with io.monad)
[watcher (java/nio/file/FileSystem::newWatchService
diff --git a/stdlib/source/library/lux/world/input/keyboard.lux b/stdlib/source/library/lux/world/input/keyboard.lux
index e33e8c4a7..b22f9b792 100644
--- a/stdlib/source/library/lux/world/input/keyboard.lux
+++ b/stdlib/source/library/lux/world/input/keyboard.lux
@@ -3,7 +3,6 @@
[lux #*]])
(type: .public Key
- {#.doc (example "A key from a keyboard, identify by a numeric ID.")}
Nat)
(template [<code> <name>]
@@ -99,7 +98,6 @@
)
(type: .public Press
- {#.doc (example "A key-press for a key.")}
(Record
{#pressed? Bit
#input Key}))
diff --git a/stdlib/source/library/lux/world/net.lux b/stdlib/source/library/lux/world/net.lux
index fae3c1f78..606202f9b 100644
--- a/stdlib/source/library/lux/world/net.lux
+++ b/stdlib/source/library/lux/world/net.lux
@@ -3,15 +3,12 @@
[lux (#- Location)]])
(type: .public Address
- {#.doc (example "A TCP/IP address.")}
Text)
(type: .public Port
- {#.doc (example "A TCP/IP port.")}
Nat)
(type: .public URL
- {#.doc (example "A Uniform Resource Locator.")}
Text)
(type: .public Location
diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux
index eaf97a16e..4790ab3c5 100644
--- a/stdlib/source/library/lux/world/net/http/client.lux
+++ b/stdlib/source/library/lux/world/net/http/client.lux
@@ -31,24 +31,16 @@
[// (#+ URL)]])
(interface: .public (Client !)
- {#.doc (example "A HTTP client capable of issuing requests to a HTTP server.")}
-
(: (-> //.Method URL //.Headers (Maybe Binary)
(! (Try (//.Response !))))
request))
-(syntax: (method_name [[_ name] <code>.tag])
- (in (list (code.text (text.upper_cased name)))))
-
(syntax: (method_function [[_ name] <code>.tag])
(in (list (code.local_identifier (text.lower_cased name)))))
(template [<method>]
- [(with_expansions [<name> (method_function <method>)
- <method_name> (method_name <method>)
- <documentation> (template.text ["A " <method_name> " request."])]
+ [(with_expansions [<name> (method_function <method>)]
(def: .public (<name> url headers data client)
- {#.doc (example <documentation>)}
(All [!]
(-> URL //.Headers (Maybe Binary) (Client !)
(! (Try (//.Response !)))))
diff --git a/stdlib/source/library/lux/world/net/http/route.lux b/stdlib/source/library/lux/world/net/http/route.lux
index 9689e3414..c3bcd9be6 100644
--- a/stdlib/source/library/lux/world/net/http/route.lux
+++ b/stdlib/source/library/lux/world/net/http/route.lux
@@ -58,7 +58,7 @@
(server [identification
protocol
(revised@ #//.uri
- (|>> (text.clip' (text.size path)) maybe.trusted)
+ (|>> (text.clip_since (text.size path)) maybe.trusted)
resource)
message])
(async.resolved //response.not_found))))
diff --git a/stdlib/source/library/lux/world/net/http/status.lux b/stdlib/source/library/lux/world/net/http/status.lux
index b0111e660..e7810c7fa 100644
--- a/stdlib/source/library/lux/world/net/http/status.lux
+++ b/stdlib/source/library/lux/world/net/http/status.lux
@@ -1,28 +1,13 @@
(.module:
[library
- [lux #*
- [control
- [parser
- ["<.>" code]]]
- [data
- ["." text]]
- [macro
- [syntax (#+ syntax:)]
- ["." code]
- ["." template]]]]
+ [lux #*]]
[// (#+ Status)])
-(syntax: (status_description [name <code>.local_identifier])
- (in (list (code.text (text.replaced "_" " " name)))))
-
... https://en.wikipedia.org/wiki/List_of_HTTP_status_codes
(template [<status> <name>]
- [(with_expansions [<description> (status_description <name>)
- <documentation> (template.text [<status> ": " <description>])]
- (def: .public <name>
- {#.doc <documentation>}
- Status
- <status>))]
+ [(def: .public <name>
+ Status
+ <status>)]
... 1xx Informational response
[100 continue]
diff --git a/stdlib/source/library/lux/world/net/uri.lux b/stdlib/source/library/lux/world/net/uri.lux
index 84df2b716..b25d6c40e 100644
--- a/stdlib/source/library/lux/world/net/uri.lux
+++ b/stdlib/source/library/lux/world/net/uri.lux
@@ -4,9 +4,7 @@
... https://en.wikipedia.org/wiki/Uniform_Resource_Identifier
(type: .public URI
- {#.doc (example "A Uniform Resource Identifier.")}
Text)
(def: .public separator
- {#.doc (example "A separator for the pieces of a URI.")}
"/")
diff --git a/stdlib/source/library/lux/world/output/video/resolution.lux b/stdlib/source/library/lux/world/output/video/resolution.lux
index 973cdac9b..8bf8a1bd7 100644
--- a/stdlib/source/library/lux/world/output/video/resolution.lux
+++ b/stdlib/source/library/lux/world/output/video/resolution.lux
@@ -4,22 +4,13 @@
[abstract
[equivalence (#+ Equivalence)]
[hash (#+ Hash)]]
- [control
- [parser
- ["<.>" code]]]
[data
- ["." product]
- ["." text]]
- [macro
- [syntax (#+ syntax:)]
- ["." code]
- ["." template]]
+ ["." product]]
[math
[number
["." nat]]]]])
(type: .public Resolution
- {#.doc (example "A screen resolution.")}
(Record
{#width Nat
#height Nat}))
@@ -32,22 +23,12 @@
(Equivalence Resolution)
(\ ..hash &equivalence))
-(syntax: (description [name <code>.local_identifier])
- (in (list (|> name
- (text.replaced "/" " ")
- (text.replaced "_" " ")
- text.upper_cased
- code.text))))
-
... https://en.wikipedia.org/wiki/Display_resolution#Common_display_resolutions
(template [<name> <width> <height>]
- [(with_expansions [<description> (..description <name>)
- <documentation> (template.text [<description> " resolution: " <width> "x" <height> "."])]
- (def: .public <name>
- {#.doc <documentation>}
- Resolution
- {#width <width>
- #height <height>}))]
+ [(def: .public <name>
+ Resolution
+ {#width <width>
+ #height <height>})]
[svga 800 600]
[wsvga 1024 600]
diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux
index 6262649aa..00aa1553d 100644
--- a/stdlib/source/library/lux/world/program.lux
+++ b/stdlib/source/library/lux/world/program.lux
@@ -40,8 +40,6 @@
["Name" (%.text name)]))
(interface: .public (Program !)
- {#.doc (example "Access to ambient program data and the capacity to exit the program.")}
-
(: (-> Any (! (List Text)))
available_variables)
(: (-> Text (! (Try Text)))
@@ -54,7 +52,6 @@
exit))
(def: .public (environment monad program)
- {#.doc (example "Assembles the environment variables available to the program.")}
(All [!] (-> (Monad !) (Program !) (! Environment)))
(do {! monad}
[variables (\ program available_variables [])
diff --git a/stdlib/source/library/lux/world/shell.lux b/stdlib/source/library/lux/world/shell.lux
index 209c161bd..470ac4cd2 100644
--- a/stdlib/source/library/lux/world/shell.lux
+++ b/stdlib/source/library/lux/world/shell.lux
@@ -34,7 +34,6 @@
[file (#+ Path)]])
(type: .public Exit
- {#.doc (example "A program exit code.")}
Int)
(template [<code> <name>]
@@ -47,8 +46,6 @@
)
(interface: .public (Process !)
- {#.doc (example "The means for communicating with a program/process being executed by the operating system.")}
-
(: (-> [] (! (Try Text)))
read)
(: (-> [] (! (Try Text)))
@@ -76,16 +73,12 @@
)))))
(type: .public Command
- {#.doc (example "A command that can be executed by the operating system.")}
Text)
(type: .public Argument
- {#.doc (example "A parameter for a command.")}
Text)
(interface: .public (Shell !)
- {#.doc (example "The means for issuing commands to the operating system.")}
-
(: (-> [Environment Path Command (List Argument)] (! (Try (Process !))))
execute))
@@ -315,8 +308,6 @@
(as_is)))
(interface: .public (Mock s)
- {#.doc (example "A simulated process.")}
-
(: (-> s (Try [s Text]))
on_read)
(: (-> s (Try [s Text]))