aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data/collection
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/data/collection/dictionary.lux32
-rw-r--r--stdlib/source/lux/data/collection/dictionary/ordered.lux12
-rw-r--r--stdlib/source/lux/data/collection/list.lux14
-rw-r--r--stdlib/source/lux/data/collection/queue.lux6
-rw-r--r--stdlib/source/lux/data/collection/queue/priority.lux10
-rw-r--r--stdlib/source/lux/data/collection/row.lux10
-rw-r--r--stdlib/source/lux/data/collection/set.lux2
-rw-r--r--stdlib/source/lux/data/collection/set/multi.lux2
-rw-r--r--stdlib/source/lux/data/collection/set/ordered.lux4
-rw-r--r--stdlib/source/lux/data/collection/stack.lux4
-rw-r--r--stdlib/source/lux/data/collection/tree.lux4
-rw-r--r--stdlib/source/lux/data/collection/tree/finger.lux2
12 files changed, 51 insertions, 51 deletions
diff --git a/stdlib/source/lux/data/collection/dictionary.lux b/stdlib/source/lux/data/collection/dictionary.lux
index f7a406c45..efb99a8b4 100644
--- a/stdlib/source/lux/data/collection/dictionary.lux
+++ b/stdlib/source/lux/data/collection/dictionary.lux
@@ -218,10 +218,10 @@
## Produces the index of a KV-pair within a #Collisions node.
(def: (collision-index Hash<k> key colls)
(All [k v] (-> (Hash k) k (Collisions k v) (Maybe Index)))
- (:: maybe.monad map product.left
- (array.find+ (function (_ idx [key' val'])
- (:: Hash<k> = key key'))
- colls)))
+ (\ maybe.monad map product.left
+ (array.find+ (function (_ idx [key' val'])
+ (\ Hash<k> = key key'))
+ colls)))
## When #Hierarchy nodes grow too small, they're demoted to #Base
## nodes to save space.
@@ -261,7 +261,7 @@
(#.Some (#.Right [key' val']))
(array.write! hierarchy-idx
- (put' (level-up level) (:: Hash<k> hash key') key' val' Hash<k> empty)
+ (put' (level-up level) (\ Hash<k> hash key') key' val' Hash<k> empty)
h-array)
#.None
@@ -318,12 +318,12 @@
## Otherwise, if it's being used by a KV, I compare the keys.
(#.Some (#.Right key' val'))
- (if (:: Hash<k> = key key')
+ (if (\ Hash<k> = key key')
## If the same key is found, I replace the value.
(#Base bitmap (update! idx (#.Right key val) base))
## Otherwise, I compare the hashes of the keys.
(#Base bitmap (update! idx
- (#.Left (let [hash' (:: Hash<k> hash key')]
+ (#.Left (let [hash' (\ Hash<k> hash key')]
(if (n.= hash hash')
## If the hashes are
## the same, a new
@@ -445,7 +445,7 @@
## If, however, there was a KV-pair instead of a sub-node.
(#.Some (#.Right [key' val']))
## Check if the keys match.
- (if (:: Hash<k> = key key')
+ (if (\ Hash<k> = key key')
## If so, remove the KV-pair and unset the BitPosition.
(#Base (unset-bit-position bit bitmap)
(remove! idx base))
@@ -492,16 +492,16 @@
(get' (level-up level) hash key Hash<k> sub-node)
(#.Some (#.Right [key' val']))
- (if (:: Hash<k> = key key')
+ (if (\ Hash<k> = key key')
(#.Some val')
#.None))
#.None))
## For #Collisions nodes, do a linear scan of all the known KV-pairs.
(#Collisions _hash _colls)
- (:: maybe.monad map product.right
- (array.find (|>> product.left (:: Hash<k> = key))
- _colls))
+ (\ maybe.monad map product.right
+ (array.find (|>> product.left (\ Hash<k> = key))
+ _colls))
))
(def: (size' node)
@@ -562,17 +562,17 @@
(def: #export (put key val dict)
(All [k v] (-> k v (Dictionary k v) (Dictionary k v)))
(let [[Hash<k> node] dict]
- [Hash<k> (put' root-level (:: Hash<k> hash key) key val Hash<k> node)]))
+ [Hash<k> (put' root-level (\ Hash<k> hash key) key val Hash<k> node)]))
(def: #export (remove key dict)
(All [k v] (-> k (Dictionary k v) (Dictionary k v)))
(let [[Hash<k> node] dict]
- [Hash<k> (remove' root-level (:: Hash<k> hash key) key Hash<k> node)]))
+ [Hash<k> (remove' root-level (\ Hash<k> hash key) key Hash<k> node)]))
(def: #export (get key dict)
(All [k v] (-> k (Dictionary k v) (Maybe v)))
(let [[Hash<k> node] dict]
- (get' root-level (:: Hash<k> hash key) key Hash<k> node)))
+ (get' root-level (\ Hash<k> hash key) key Hash<k> node)))
(def: #export (contains? key dict)
(All [k v] (-> k (Dictionary k v) Bit))
@@ -722,4 +722,4 @@
(All [k] (Functor (Dictionary k)))
(def: (map f fa)
- (update@ #root (:: ..functor' map f) fa)))
+ (update@ #root (\ ..functor' map f) fa)))
diff --git a/stdlib/source/lux/data/collection/dictionary/ordered.lux b/stdlib/source/lux/data/collection/dictionary/ordered.lux
index fc02cd5bf..b924a2e5d 100644
--- a/stdlib/source/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/lux/data/collection/dictionary/ordered.lux
@@ -63,11 +63,11 @@
(#.Some node)
(let [node-key (get@ #key node)]
- (cond (:: dict = node-key key)
+ (cond (\ dict = node-key key)
## (_\= node-key key)
(#.Some (get@ #value node))
- (:: dict < node-key key)
+ (\ dict < node-key key)
## (_\< node-key key)
(recur (get@ #left node))
@@ -86,9 +86,9 @@
(#.Some node)
(let [node-key (get@ #key node)]
- (or (:: dict = node-key key)
+ (or (\ dict = node-key key)
## (_\= node-key key)
- (if (:: dict < node-key key)
+ (if (\ dict < node-key key)
## (_\< node-key key)
(recur (get@ #left node))
(recur (get@ #right node)))))))))
@@ -360,7 +360,7 @@
(#.Some (right-balance (get@ #key right)
(get@ #value right)
(get@ #right right>>left)
- (:: maybe.functor map redden (get@ #right right)))))
+ (\ maybe.functor map redden (get@ #right right)))))
_
(error! error-message))
@@ -387,7 +387,7 @@
(get@ #value left>>right)
(#.Some (left-balance (get@ #key left)
(get@ #value left)
- (:: maybe.functor map redden (get@ #left left))
+ (\ maybe.functor map redden (get@ #left left))
(get@ #left left>>right)))
(#.Some (black key value (get@ #right left>>right) ?right)))
diff --git a/stdlib/source/lux/data/collection/list.lux b/stdlib/source/lux/data/collection/list.lux
index d35df1b53..62e8a417d 100644
--- a/stdlib/source/lux/data/collection/list.lux
+++ b/stdlib/source/lux/data/collection/list.lux
@@ -302,7 +302,7 @@
#1
[(#.Cons x xs') (#.Cons y ys')]
- (and (:: Equivalence<a> = x y)
+ (and (\ Equivalence<a> = x y)
(= xs' ys'))
[_ _]
@@ -313,7 +313,7 @@
(All [a] (-> (Hash a) (Hash (List a))))
(def: &equivalence
- (..equivalence (:: super &equivalence)))
+ (..equivalence (\ super &equivalence)))
(def: (hash value)
(case value
@@ -322,7 +322,7 @@
(#.Cons head tail)
($_ n.* 3
- (n.+ (:: super hash head)
+ (n.+ (\ super hash head)
(hash tail)))
)))
@@ -395,7 +395,7 @@
(All [a] (-> (Equivalence a) (List a) a Bit))
(case xs
#.Nil #0
- (#.Cons x' xs') (or (:: eq = x x')
+ (#.Cons x' xs') (or (\ eq = x x')
(member? eq xs' x))))
(template [<name> <output> <side> <doc>]
@@ -571,14 +571,14 @@
(def: #export (concat xss)
(All [a] (-> (List (List a)) (List a)))
- (:: ..monad join xss))
+ (\ ..monad join xss))
(structure: #export (with monad)
(All [M] (-> (Monad M) (Monad (All [a] (M (List a))))))
(def: &functor (functor.compose (get@ #monad.&functor monad) ..functor))
- (def: wrap (|>> (:: ..monad wrap) (:: monad wrap)))
+ (def: wrap (|>> (\ ..monad wrap) (\ monad wrap)))
(def: (join MlMla)
(do {! monad}
@@ -592,7 +592,7 @@
(def: #export (lift monad)
(All [M a] (-> (Monad M) (-> (M a) (M (List a)))))
- (:: monad map (:: ..monad wrap)))
+ (\ monad map (\ ..monad wrap)))
(def: #export (enumeration xs)
{#.doc "Pairs every element in the list with its index, starting at 0."}
diff --git a/stdlib/source/lux/data/collection/queue.lux b/stdlib/source/lux/data/collection/queue.lux
index 69e4f7025..2d8712b82 100644
--- a/stdlib/source/lux/data/collection/queue.lux
+++ b/stdlib/source/lux/data/collection/queue.lux
@@ -79,9 +79,9 @@
(All [a] (-> (Equivalence a) (Equivalence (Queue a))))
(def: (= reference subject)
- (:: (list.equivalence super) =
- (..to-list reference)
- (..to-list subject))))
+ (\ (list.equivalence super) =
+ (..to-list reference)
+ (..to-list subject))))
(structure: #export functor
(Functor Queue)
diff --git a/stdlib/source/lux/data/collection/queue/priority.lux b/stdlib/source/lux/data/collection/queue/priority.lux
index 9c526d0df..4c559e331 100644
--- a/stdlib/source/lux/data/collection/queue/priority.lux
+++ b/stdlib/source/lux/data/collection/queue/priority.lux
@@ -67,7 +67,7 @@
(loop [node tree]
(case (tree.root node)
(0 #0 reference)
- (:: equivalence = reference member)
+ (\ equivalence = reference member)
(0 #1 [left right])
(or (recur left)
@@ -93,24 +93,24 @@
(#.Some right)
(#.Some =left)
- (#.Some (:: ..builder branch =left right)))
+ (#.Some (\ ..builder branch =left right)))
(case (recur right)
#.None
(#.Some left)
(#.Some =right)
- (#.Some (:: ..builder branch left =right)))))))))
+ (#.Some (\ ..builder branch left =right)))))))))
(def: #export (push priority value queue)
(All [a] (-> Priority a (Queue a) (Queue a)))
- (let [addition (:: ..builder leaf priority value)]
+ (let [addition (\ ..builder leaf priority value)]
(:abstraction
(case (:representation queue)
#.None
(#.Some addition)
(#.Some tree)
- (#.Some (:: ..builder branch tree addition))))))
+ (#.Some (\ ..builder branch tree addition))))))
)
(def: #export empty?
diff --git a/stdlib/source/lux/data/collection/row.lux b/stdlib/source/lux/data/collection/row.lux
index ae60e87d5..9bc47be18 100644
--- a/stdlib/source/lux/data/collection/row.lux
+++ b/stdlib/source/lux/data/collection/row.lux
@@ -231,8 +231,8 @@
(exception: incorrect-row-structure)
(exception: #export [a] (index-out-of-bounds {row (Row a)} {index Nat})
- (exception.report ["Size" (:: n.decimal encode (get@ #size row))]
- ["Index" (:: n.decimal encode index)]))
+ (exception.report ["Size" (\ n.decimal encode (get@ #size row))]
+ ["Index" (\ n.decimal encode index)]))
(exception: base-was-not-found)
@@ -363,10 +363,10 @@
(def: (= v1 v2)
(case [v1 v2]
[(#Base b1) (#Base b2)]
- (:: (array.equivalence Equivalence<a>) = b1 b2)
+ (\ (array.equivalence Equivalence<a>) = b1 b2)
[(#Hierarchy h1) (#Hierarchy h2)]
- (:: (array.equivalence (node-equivalence Equivalence<a>)) = h1 h2)
+ (\ (array.equivalence (node-equivalence Equivalence<a>)) = h1 h2)
_
#0)))
@@ -431,7 +431,7 @@
(def: (map f xs)
{#level (get@ #level xs)
#size (get@ #size xs)
- #root (|> xs (get@ #root) (array\map (:: node-functor map f)))
+ #root (|> xs (get@ #root) (array\map (\ node-functor map f)))
#tail (|> xs (get@ #tail) (array\map f))}))
(structure: #export apply
diff --git a/stdlib/source/lux/data/collection/set.lux b/stdlib/source/lux/data/collection/set.lux
index 6dd536739..80cdf89a6 100644
--- a/stdlib/source/lux/data/collection/set.lux
+++ b/stdlib/source/lux/data/collection/set.lux
@@ -71,7 +71,7 @@
(def: &equivalence ..equivalence)
(def: (hash (^@ set [hash _]))
- (list\fold (function (_ elem acc) (n.+ (:: hash hash elem) acc))
+ (list\fold (function (_ elem acc) (n.+ (\ hash hash elem) acc))
0
(..to-list set))))
diff --git a/stdlib/source/lux/data/collection/set/multi.lux b/stdlib/source/lux/data/collection/set/multi.lux
index 46578979d..7e4c0f7fe 100644
--- a/stdlib/source/lux/data/collection/set/multi.lux
+++ b/stdlib/source/lux/data/collection/set/multi.lux
@@ -129,7 +129,7 @@
(def: (hash (^:representation set))
(let [[hash _] set]
(list\fold (function (_ [elem multiplicity] acc)
- (|> elem (:: hash hash) (n.+ multiplicity) (n.+ acc)))
+ (|> elem (\ hash hash) (n.+ multiplicity) (n.+ acc)))
0
(dictionary.entries set)))))
)
diff --git a/stdlib/source/lux/data/collection/set/ordered.lux b/stdlib/source/lux/data/collection/set/ordered.lux
index f215f5430..d350c1e9c 100644
--- a/stdlib/source/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/lux/data/collection/set/ordered.lux
@@ -72,8 +72,8 @@
(All [a] (Equivalence (Set a)))
(def: (= reference sample)
- (:: (list.equivalence (:: (:representation reference) &equivalence))
- = (..to-list reference) (..to-list sample))))
+ (\ (list.equivalence (\ (:representation reference) &equivalence))
+ = (..to-list reference) (..to-list sample))))
)
(def: #export (sub? super sub)
diff --git a/stdlib/source/lux/data/collection/stack.lux b/stdlib/source/lux/data/collection/stack.lux
index e9a7f8bf4..398fa71ba 100644
--- a/stdlib/source/lux/data/collection/stack.lux
+++ b/stdlib/source/lux/data/collection/stack.lux
@@ -52,7 +52,7 @@
(Equivalence (Stack a))))
(def: (= reference subject)
- (:: (//.equivalence super) = (:representation reference) (:representation subject))))
+ (\ (//.equivalence super) = (:representation reference) (:representation subject))))
(structure: #export functor
(Functor Stack)
@@ -60,6 +60,6 @@
(def: (map f value)
(|> value
:representation
- (:: //.functor map f)
+ (\ //.functor map f)
:abstraction)))
)
diff --git a/stdlib/source/lux/data/collection/tree.lux b/stdlib/source/lux/data/collection/tree.lux
index 9519ae0b9..b690e7128 100644
--- a/stdlib/source/lux/data/collection/tree.lux
+++ b/stdlib/source/lux/data/collection/tree.lux
@@ -63,8 +63,8 @@
(All [a] (-> (Equivalence a) (Equivalence (Tree a))))
(def: (= tx ty)
- (and (:: super = (get@ #value tx) (get@ #value ty))
- (:: (list.equivalence (equivalence super)) = (get@ #children tx) (get@ #children ty)))))
+ (and (\ super = (get@ #value tx) (get@ #value ty))
+ (\ (list.equivalence (equivalence super)) = (get@ #children tx) (get@ #children ty)))))
(structure: #export functor
(Functor Tree)
diff --git a/stdlib/source/lux/data/collection/tree/finger.lux b/stdlib/source/lux/data/collection/tree/finger.lux
index e120b068a..c3e20ce08 100644
--- a/stdlib/source/lux/data/collection/tree/finger.lux
+++ b/stdlib/source/lux/data/collection/tree/finger.lux
@@ -43,7 +43,7 @@
(def: (branch left right)
(:abstraction
{#monoid monoid
- #tag (:: monoid compose (..tag left) (..tag right))
+ #tag (\ monoid compose (..tag left) (..tag right))
#root (0 #1 [left right])})))
(def: #export (value tree)