aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data/collection/list.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/data/collection/list.lux58
1 files changed, 29 insertions, 29 deletions
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index 4b0071ddd..450bfea3a 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -382,10 +382,10 @@
(if (< x x')
[{.#Item x' pre} post]
[pre {.#Item x' post}]))
- (`` [(: (~~ (:of xs))
- (list))
- (: (~~ (:of xs))
- (list))])
+ (`` [(is (~~ (type_of xs))
+ (list))
+ (is (~~ (type_of xs))
+ (list))])
xs')]
($_ composite (sorted < pre) (list x) (sorted < post)))))
@@ -460,9 +460,9 @@
(if (n.> 0 num_lists)
(let [(open "[0]") ..functor
indices (..indices num_lists)
- type_vars (: (List Code) (each (|>> nat#encoded symbol$) indices))
+ type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices))
zipped_type (` (.All ((~ (symbol$ "0_")) (~+ type_vars))
- (-> (~+ (each (: (-> Code Code) (function (_ var) (` (List (~ var)))))
+ (-> (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var)))))
type_vars))
(List [(~+ type_vars)]))))
vars+lists (|> indices
@@ -476,15 +476,15 @@
g!step (symbol$ "0step0")
g!blank (symbol$ "0,0")
list_vars (each product.right vars+lists)
- code (` (: (~ zipped_type)
- (function ((~ g!step) (~+ list_vars))
- (case [(~+ list_vars)]
- (~ pattern)
- {.#Item [(~+ (each product.left vars+lists))]
- ((~ g!step) (~+ list_vars))}
-
- (~ g!blank)
- {.#End}))))]
+ code (` (is (~ zipped_type)
+ (function ((~ g!step) (~+ list_vars))
+ (case [(~+ list_vars)]
+ (~ pattern)
+ {.#Item [(~+ (each product.left vars+lists))]
+ ((~ g!step) (~+ list_vars))}
+
+ (~ g!blank)
+ {.#End}))))]
{.#Right [state (list code)]})
{.#Left "Cannot zipped 0 lists."})
@@ -502,10 +502,10 @@
indices (..indices num_lists)
g!return_type (symbol$ "0return_type0")
g!func (symbol$ "0func0")
- type_vars (: (List Code) (each (|>> nat#encoded symbol$) indices))
+ type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices))
zipped_type (` (All ((~ (symbol$ "0_")) (~+ type_vars) (~ g!return_type))
(-> (-> (~+ type_vars) (~ g!return_type))
- (~+ (each (: (-> Code Code) (function (_ var) (` (List (~ var)))))
+ (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var)))))
type_vars))
(List (~ g!return_type)))))
vars+lists (|> indices
@@ -519,15 +519,15 @@
g!step (symbol$ "0step0")
g!blank (symbol$ "0,0")
list_vars (each product.right vars+lists)
- code (` (: (~ zipped_type)
- (function ((~ g!step) (~ g!func) (~+ list_vars))
- (case [(~+ list_vars)]
- (~ pattern)
- {.#Item ((~ g!func) (~+ (each product.left vars+lists)))
- ((~ g!step) (~ g!func) (~+ list_vars))}
-
- (~ g!blank)
- {.#End}))))]
+ code (` (is (~ zipped_type)
+ (function ((~ g!step) (~ g!func) (~+ list_vars))
+ (case [(~+ list_vars)]
+ (~ pattern)
+ {.#Item ((~ g!func) (~+ (each product.left vars+lists)))
+ ((~ g!step) (~ g!func) (~+ list_vars))}
+
+ (~ g!blank)
+ {.#End}))))]
{.#Right [state (list code)]})
{.#Left "Cannot zipped_with 0 lists."})
@@ -585,9 +585,9 @@
(do [! monad]
[lMla MlMla
... TODO: Remove this version ASAP and use one below.
- lla (for @.old (: {.#Apply (type (List (List (:parameter 1))))
- (:parameter 0)}
- (monad.all ! lMla))
+ lla (for @.old (is {.#Apply (type (List (List (parameter 1))))
+ (parameter 0)}
+ (monad.all ! lMla))
(monad.all ! lMla))]
(in (..together lla)))))