aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data/collection
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/data/collection')
-rw-r--r--stdlib/source/lux/data/collection/array.lux20
-rw-r--r--stdlib/source/lux/data/collection/bits.lux6
-rw-r--r--stdlib/source/lux/data/collection/dictionary.lux70
-rw-r--r--stdlib/source/lux/data/collection/dictionary/ordered.lux28
-rw-r--r--stdlib/source/lux/data/collection/list.lux12
-rw-r--r--stdlib/source/lux/data/collection/set.lux125
-rw-r--r--stdlib/source/lux/data/collection/set/ordered.lux14
-rw-r--r--stdlib/source/lux/data/collection/stack.lux23
-rw-r--r--stdlib/source/lux/data/collection/tree/rose.lux4
9 files changed, 171 insertions, 131 deletions
diff --git a/stdlib/source/lux/data/collection/array.lux b/stdlib/source/lux/data/collection/array.lux
index 8677ceb62..d135b06d9 100644
--- a/stdlib/source/lux/data/collection/array.lux
+++ b/stdlib/source/lux/data/collection/array.lux
@@ -10,7 +10,7 @@
["." product]
["." maybe]
[collection
- ["." list ("#;." fold)]]]
+ ["." list ("#@." fold)]]]
[tool
[compiler
["." host]]]])
@@ -89,7 +89,7 @@
(Array a)))
(if (n/= 0 length)
dest-array
- (list;fold (function (_ offset target)
+ (list@fold (function (_ offset target)
(case (read (n/+ offset src-start) src-array)
#.None
target
@@ -102,7 +102,7 @@
(def: #export (occupied array)
{#.doc "Finds out how many cells in an array are occupied."}
(All [a] (-> (Array a) Nat))
- (list;fold (function (_ idx count)
+ (list@fold (function (_ idx count)
(case (read idx array)
#.None
count
@@ -120,7 +120,7 @@
(def: #export (filter! p xs)
(All [a]
(-> (-> a Bit) (Array a) (Array a)))
- (list;fold (function (_ idx xs')
+ (list@fold (function (_ idx xs')
(case (read idx xs)
#.None
xs'
@@ -168,7 +168,7 @@
(def: #export (clone xs)
(All [a] (-> (Array a) (Array a)))
(let [arr-size (size xs)]
- (list;fold (function (_ idx ys)
+ (list@fold (function (_ idx ys)
(case (read idx xs)
#.None
ys
@@ -180,7 +180,7 @@
(def: #export (from-list xs)
(All [a] (-> (List a) (Array a)))
- (product.right (list;fold (function (_ x [idx arr])
+ (product.right (list@fold (function (_ x [idx arr])
[(inc idx) (write idx x arr)])
[0 (new (list.size xs))]
xs)))
@@ -211,20 +211,20 @@
(#.Cons (maybe.default default (read idx array))
output)))))
-(structure: #export (equivalence Equivalence<a>)
+(structure: #export (equivalence (^open ",@."))
(All [a] (-> (Equivalence a) (Equivalence (Array a))))
(def: (= xs ys)
(let [sxs (size xs)
sxy (size ys)]
(and (n/= sxy sxs)
- (list;fold (function (_ idx prev)
+ (list@fold (function (_ idx prev)
(and prev
(case [(read idx xs) (read idx ys)]
[#.None #.None]
#1
[(#.Some x) (#.Some y)]
- (:: Equivalence<a> = x y)
+ (,@= x y)
_
#0)))
@@ -246,7 +246,7 @@
(let [arr-size (size ma)]
(if (n/= 0 arr-size)
(new arr-size)
- (list;fold (function (_ idx mb)
+ (list@fold (function (_ idx mb)
(case (read idx ma)
#.None
mb
diff --git a/stdlib/source/lux/data/collection/bits.lux b/stdlib/source/lux/data/collection/bits.lux
index 975605fdc..93158c54c 100644
--- a/stdlib/source/lux/data/collection/bits.lux
+++ b/stdlib/source/lux/data/collection/bits.lux
@@ -10,7 +10,7 @@
[text
format]
[collection
- ["." array (#+ Array) ("#;." fold)]]]])
+ ["." array (#+ Array) ("#@." fold)]]]])
(type: #export Chunk I64)
@@ -27,7 +27,7 @@
(def: #export (size bits)
(-> Bits Nat)
- (array;fold (function (_ chunk total)
+ (array@fold (function (_ chunk total)
(|> chunk i64.count (n/+ total)))
0
bits))
@@ -64,7 +64,7 @@
(let [idx|output (dec size|output)]
(if (n/> 0 size|output)
(case (|> (..chunk idx|output input)
- (cond> [(new> (n/= chunk-index idx|output))]
+ (cond> [(new> (n/= chunk-index idx|output) [])]
[(<op> bit-index)]
## else
diff --git a/stdlib/source/lux/data/collection/dictionary.lux b/stdlib/source/lux/data/collection/dictionary.lux
index a1f16311d..9a9663228 100644
--- a/stdlib/source/lux/data/collection/dictionary.lux
+++ b/stdlib/source/lux/data/collection/dictionary.lux
@@ -1,23 +1,23 @@
(.module:
[lux #*
[control
- hash
- [equivalence (#+ Equivalence)]]
+ [hash (#+ Hash)]
+ [equivalence (#+ Equivalence)]
+ [functor (#+ Functor)]]
[data
["." maybe]
["." product]
["." number
["." i64]]
[collection
- ["." list ("#;." fold functor monoid)]
- ["." array (#+ Array) ("#;." functor fold)]]]
+ ["." list ("#@." fold functor monoid)]
+ ["." array (#+ Array) ("#@." functor fold)]]]
])
## This implementation of Hash Array Mapped Trie (HAMT) is based on
## Clojure's PersistentHashMap implementation.
## That one is further based on Phil Bagwell's Hash Array Mapped Trie.
-## [Utils]
## Bitmaps are used to figure out which branches on a #Base node are
## populated. The number of bits that are 1s in a bitmap signal the
## size of the #Base node.
@@ -219,7 +219,7 @@
## nodes to save space.
(def: (demote-hierarchy except-idx [h-size h-array])
(All [k v] (-> Index (Hierarchy k v) [BitMap (Base k v)]))
- (product.right (list;fold (function (_ idx [insertion-idx node])
+ (product.right (list@fold (function (_ idx [insertion-idx node])
(let [[bitmap base] node]
(case (array.read idx h-array)
#.None [insertion-idx node]
@@ -243,7 +243,7 @@
(Hash k) Level
BitMap (Base k v)
(Array (Node k v))))
- (product.right (list;fold (function (_ hierarchy-idx (^@ default [base-idx h-array]))
+ (product.right (list@fold (function (_ hierarchy-idx (^@ default [base-idx h-array]))
(if (bit-position-is-set? (->bit-position hierarchy-idx)
bitmap)
[(inc base-idx)
@@ -500,10 +500,10 @@
(All [k v] (-> (Node k v) Nat))
(case node
(#Hierarchy _size hierarchy)
- (array;fold n/+ 0 (array;map size' hierarchy))
+ (array@fold n/+ 0 (array@map size' hierarchy))
(#Base _ base)
- (array;fold n/+ 0 (array;map (function (_ sub-node')
+ (array@fold n/+ 0 (array@map (function (_ sub-node')
(case sub-node'
(#.Left sub-node) (size' sub-node)
(#.Right _) 1))
@@ -517,15 +517,15 @@
(All [k v] (-> (Node k v) (List [k v])))
(case node
(#Hierarchy _size hierarchy)
- (array;fold (function (_ sub-node tail) (list;compose (entries' sub-node) tail))
+ (array@fold (function (_ sub-node tail) (list@compose (entries' sub-node) tail))
#.Nil
hierarchy)
(#Base bitmap base)
- (array;fold (function (_ branch tail)
+ (array@fold (function (_ branch tail)
(case branch
(#.Left sub-node)
- (list;compose (entries' sub-node) tail)
+ (list@compose (entries' sub-node) tail)
(#.Right [key' val'])
(#.Cons [key' val'] tail)))
@@ -533,11 +533,10 @@
base)
(#Collisions hash colls)
- (array;fold (function (_ [key' val'] tail) (#.Cons [key' val'] tail))
+ (array@fold (function (_ [key' val'] tail) (#.Cons [key' val'] tail))
#.Nil
colls)))
-## [Exports]
(type: #export (Dictionary k v)
{#.doc "A dictionary implemented as a Hash-Array Mapped Trie (HAMT)."}
{#hash (Hash k)
@@ -609,7 +608,7 @@
(def: #export (from-list Hash<k> kvs)
(All [k v] (-> (Hash k) (List [k v]) (Dictionary k v)))
- (list;fold (function (_ [k v] dict)
+ (list@fold (function (_ [k v] dict)
(put k v dict))
(new Hash<k>)
kvs))
@@ -617,7 +616,7 @@
(do-template [<name> <elem-type> <side>]
[(def: #export (<name> dict)
(All [k v] (-> (Dictionary k v) (List <elem-type>)))
- (|> dict entries (list;map <side>)))]
+ (|> dict entries (list@map <side>)))]
[keys k product.left]
[values v product.right]
@@ -627,7 +626,7 @@
{#.doc (doc "Merges 2 dictionaries."
"If any collisions with keys occur, the values of dict2 will overwrite those of dict1.")}
(All [k v] (-> (Dictionary k v) (Dictionary k v) (Dictionary k v)))
- (list;fold (function (_ [key val] dict) (put key val dict))
+ (list@fold (function (_ [key val] dict) (put key val dict))
dict1
(entries dict2)))
@@ -635,7 +634,7 @@
{#.doc (doc "Merges 2 dictionaries."
"If any collisions with keys occur, a new value will be computed by applying 'f' to the values of dict2 and dict1.")}
(All [k v] (-> (-> v v v) (Dictionary k v) (Dictionary k v) (Dictionary k v)))
- (list;fold (function (_ [key val2] dict)
+ (list@fold (function (_ [key val2] dict)
(case (get key dict)
#.None
(put key val2 dict)
@@ -660,23 +659,50 @@
{#.doc "Creates a sub-set of the given dict, with only the specified keys."}
(All [k v] (-> (List k) (Dictionary k v) (Dictionary k v)))
(let [[Hash<k> _] dict]
- (list;fold (function (_ key new-dict)
+ (list@fold (function (_ key new-dict)
(case (get key dict)
#.None new-dict
(#.Some val) (put key val new-dict)))
(new Hash<k>)
keys)))
-## [Structures]
-(structure: #export (equivalence Equivalence<v>) (All [k v] (-> (Equivalence v) (Equivalence (Dictionary k v))))
+(structure: #export (equivalence (^open ",@."))
+ (All [k v] (-> (Equivalence v) (Equivalence (Dictionary k v))))
+
(def: (= test subject)
(and (n/= (size test)
(size subject))
(list.every? (function (_ k)
(case [(get k test) (get k subject)]
[(#.Some tk) (#.Some sk)]
- (:: Equivalence<v> = tk sk)
+ (,@= tk sk)
_
#0))
(keys test)))))
+
+(structure: #export functor
+ (All [k] (Functor (Dictionary k)))
+ (def: (map f fa)
+ (update@ #root
+ (function (recur node)
+ (case node
+ (#Hierarchy size hierarchy)
+ (#Hierarchy size (array@map recur hierarchy))
+
+ (#Base bitmap base)
+ (#Base bitmap (array@map (function (_ either)
+ (case either
+ (#.Left node)
+ (#.Left (recur node))
+
+ (#.Right [k v])
+ (#.Right [k (f v)])))
+ base))
+
+ (#Collisions hash collisions)
+ (#Collisions hash (array@map (function (_ [k v])
+ [k (f v)])
+ collisions))))
+ fa)
+ ))
diff --git a/stdlib/source/lux/data/collection/dictionary/ordered.lux b/stdlib/source/lux/data/collection/dictionary/ordered.lux
index 8b384ca4c..e2d0f21fd 100644
--- a/stdlib/source/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/lux/data/collection/dictionary/ordered.lux
@@ -15,7 +15,9 @@
(def: error-message Text "Invariant violation")
-(type: Color #Red #Black)
+(type: Color
+ #Red
+ #Black)
(type: (Node k v)
{#color Color
@@ -38,19 +40,19 @@
)
(type: #export (Dictionary k v)
- {#order (Order k)
+ {#&order (Order k)
#root (Maybe (Node k v))})
-(def: #export (new Order<k>)
+(def: #export (new order)
(All [k v] (-> (Order k) (Dictionary k v)))
- {#order Order<k>
+ {#&order order
#root #.None})
## TODO: Doing inneficient access of Order functions due to compiler bug.
## TODO: Must improve it as soon as bug is fixed.
(def: #export (get key dict)
(All [k v] (-> k (Dictionary k v) (Maybe v)))
- (let [## (^open "T/.") (get@ #order dict)
+ (let [## (^open "T/.") (get@ #&order dict)
]
(loop [node (get@ #root dict)]
(case node
@@ -73,7 +75,7 @@
(def: #export (contains? key dict)
(All [k v] (-> k (Dictionary k v) Bit))
- (let [## (^open "T/.") (get@ #order dict)
+ (let [## (^open "T/.") (get@ #&order dict)
]
(loop [node (get@ #root dict)]
(case node
@@ -246,7 +248,7 @@
(def: #export (put key value dict)
(All [k v] (-> k v (Dictionary k v) (Dictionary k v)))
- (let [(^open "T/.") (get@ #order dict)
+ (let [(^open "T/.") (get@ #&order dict)
root' (loop [?root (get@ #root dict)]
(case ?root
#.None
@@ -469,7 +471,7 @@
(def: #export (remove key dict)
(All [k v] (-> k (Dictionary k v) (Dictionary k v)))
- (let [(^open "T/.") (get@ #order dict)
+ (let [(^open "T/.") (get@ #&order dict)
[?root found?] (loop [?root (get@ #root dict)]
(case ?root
#.None
@@ -554,9 +556,11 @@
[values v (get@ #value node')]
)
-(structure: #export (equivalence Equivalence<v>) (All [k v] (-> (Equivalence v) (Equivalence (Dictionary k v))))
+(structure: #export (equivalence (^open ",@."))
+ (All [k v] (-> (Equivalence v) (Equivalence (Dictionary k v))))
+
(def: (= reference sample)
- (let [Equivalence<k> (:: sample eq)]
+ (let [(^open "/@.") (get@ #&order reference)]
(loop [entriesR (entries reference)
entriesS (entries sample)]
(case [entriesR entriesS]
@@ -564,8 +568,8 @@
#1
[(#.Cons [keyR valueR] entriesR') (#.Cons [keyS valueS] entriesS')]
- (and (:: Equivalence<k> = keyR keyS)
- (:: Equivalence<v> = valueR valueS)
+ (and (/@= keyR keyS)
+ (,@= valueR valueS)
(recur entriesR' entriesS'))
_
diff --git a/stdlib/source/lux/data/collection/list.lux b/stdlib/source/lux/data/collection/list.lux
index 46d47e398..46042d1d7 100644
--- a/stdlib/source/lux/data/collection/list.lux
+++ b/stdlib/source/lux/data/collection/list.lux
@@ -391,7 +391,7 @@
(-> Text Code)
[["" 0 0] (#.Identifier "" name)])
-(def: (nat;encode value)
+(def: (nat@encode value)
(-> Nat Text)
(loop [input value
output ""]
@@ -423,7 +423,7 @@
(if (n/> 0 num-lists)
(let [(^open ".") ..functor
indices (..indices num-lists)
- type-vars (: (List Code) (map (|>> nat;encode identifier$) indices))
+ type-vars (: (List Code) (map (|>> nat@encode identifier$) indices))
zip-type (` (All [(~+ type-vars)]
(-> (~+ (map (: (-> Code Code) (function (_ var) (` (List (~ var)))))
type-vars))
@@ -431,7 +431,7 @@
vars+lists (|> indices
(map inc)
(map (function (_ idx)
- (let [base (nat;encode idx)]
+ (let [base (nat@encode idx)]
[(identifier$ base)
(identifier$ ("lux text concat" base "'"))]))))
pattern (` [(~+ (map (function (_ [v vs]) (` (#.Cons (~ v) (~ vs))))
@@ -469,7 +469,7 @@
indices (..indices num-lists)
g!return-type (identifier$ "0return-type0")
g!func (identifier$ "0func0")
- type-vars (: (List Code) (map (|>> nat;encode identifier$) indices))
+ type-vars (: (List Code) (map (|>> nat@encode identifier$) indices))
zip-type (` (All [(~+ type-vars) (~ g!return-type)]
(-> (-> (~+ type-vars) (~ g!return-type))
(~+ (map (: (-> Code Code) (function (_ var) (` (List (~ var)))))
@@ -478,7 +478,7 @@
vars+lists (|> indices
(map inc)
(map (function (_ idx)
- (let [base (nat;encode idx)]
+ (let [base (nat@encode idx)]
[(identifier$ base)
(identifier$ ("lux text concat" base "'"))]))))
pattern (` [(~+ (map (function (_ [v vs]) (` (#.Cons (~ v) (~ vs))))
@@ -540,7 +540,7 @@
(All [a] (-> (List (List a)) (List a)))
(:: ..monad join xss))
-(structure: #export (with-list monad)
+(structure: #export (with monad)
(All [M] (-> (Monad M) (Monad (All [a] (M (List a))))))
(def: &functor (functor.compose (get@ #monad.&functor monad) ..functor))
diff --git a/stdlib/source/lux/data/collection/set.lux b/stdlib/source/lux/data/collection/set.lux
index 0a195f4eb..5ab374b84 100644
--- a/stdlib/source/lux/data/collection/set.lux
+++ b/stdlib/source/lux/data/collection/set.lux
@@ -2,71 +2,72 @@
[lux #*
[control
[equivalence (#+ Equivalence)]
- ["." hash (#+ Hash)]
- [predicate (#+ Predicate)]]
+ [predicate (#+ Predicate)]
+ [monoid (#+ Monoid)]
+ ["." hash (#+ Hash)]]
[data
[collection
- ["dict" dictionary (#+ Dictionary)]
- ["." list ("#;." fold)]]]
- [type
- abstract]])
+ ["//" dictionary (#+ Dictionary)]
+ ["." list ("#@." fold)]]]])
-(abstract: #export (Set a)
- {}
+(type: #export (Set a)
+ (Dictionary a Any))
+
+(def: #export new
+ (All [a] (-> (Hash a) (Set a)))
+ //.new)
+
+(def: #export size
+ (All [a] (-> (Set a) Nat))
+ //.size)
+
+(def: #export (add elem set)
+ (All [a] (-> a (Set a) (Set a)))
+ (|> set (//.put elem [])))
+
+(def: #export remove
+ (All [a] (-> a (Set a) (Set a)))
+ //.remove)
+
+(def: #export (member? set elem)
+ (All [a] (-> (Set a) a Bit))
+ (//.contains? elem set))
+
+(def: #export to-list
+ (All [a] (-> (Set a) (List a)))
+ //.keys)
+
+(def: #export union
+ (All [a] (-> (Set a) (Set a) (Set a)))
+ //.merge)
+
+(def: #export (difference sub base)
+ (All [a] (-> (Set a) (Set a) (Set a)))
+ (list@fold ..remove base (..to-list sub)))
+
+(def: #export (intersection filter base)
+ (All [a] (-> (Set a) (Set a) (Set a)))
+ (//.select (//.keys filter)
+ base))
+
+(structure: #export equivalence (All [a] (Equivalence (Set a)))
+ (def: (= (^@ reference [hash _]) sample)
+ (:: (list.equivalence (get@ #hash.&equivalence hash)) =
+ (..to-list reference) (..to-list sample))))
+
+(structure: #export hash (All [a] (Hash (Set a)))
+ (def: &equivalence ..equivalence)
- (Dictionary a a)
-
- (def: #export new
- (All [a] (-> (Hash a) (Set a)))
- (|>> dict.new :abstraction))
-
- (def: #export size
- (All [a] (-> (Set a) Nat))
- (|>> :representation dict.size))
-
- (def: #export (add elem set)
- (All [a] (-> a (Set a) (Set a)))
- (|> set :representation (dict.put elem elem) :abstraction))
-
- (def: #export (remove elem set)
- (All [a] (-> a (Set a) (Set a)))
- (|> set :representation (dict.remove elem) :abstraction))
-
- (def: #export (member? set elem)
- (All [a] (-> (Set a) a Bit))
- (|> set :representation (dict.contains? elem)))
-
- (def: #export to-list
- (All [a] (-> (Set a) (List a)))
- (|>> :representation dict.keys))
-
- (def: #export (union xs yx)
- (All [a] (-> (Set a) (Set a) (Set a)))
- (:abstraction (dict.merge (:representation xs) (:representation yx))))
-
- (def: #export (difference sub base)
- (All [a] (-> (Set a) (Set a) (Set a)))
- (list;fold ..remove base (..to-list sub)))
-
- (def: #export (intersection filter base)
- (All [a] (-> (Set a) (Set a) (Set a)))
- (:abstraction (dict.select (dict.keys (:representation filter))
- (:representation base))))
-
- (structure: #export equivalence (All [a] (Equivalence (Set a)))
- (def: (= reference sample)
- (let [[hash _] (:representation reference)]
- (:: (list.equivalence (get@ #hash.&equivalence hash)) =
- (..to-list reference) (..to-list sample)))))
-
- (structure: #export hash (All [a] (Hash (Set a)))
- (def: &equivalence ..equivalence)
-
- (def: (hash set)
- (let [[hash _] (:representation set)]
- (list;fold (function (_ elem acc) (n/+ (:: hash hash elem) acc))
- 0
- (..to-list set)))))
+ (def: (hash (^@ set [hash _]))
+ (list@fold (function (_ elem acc) (n/+ (:: hash hash elem) acc))
+ 0
+ (..to-list set))))
+
+(structure: #export (monoid hash)
+ (All [a] (-> (Hash a) (Monoid (Set a))))
+
+ (def: identity (..new hash))
+ (def: compose ..union)
)
(def: #export empty?
@@ -75,7 +76,7 @@
(def: #export (from-list hash elements)
(All [a] (-> (Hash a) (List a) (Set a)))
- (list;fold ..add (..new hash) elements))
+ (list@fold ..add (..new hash) elements))
(def: #export (sub? super sub)
(All [a] (-> (Set a) (Set a) Bit))
diff --git a/stdlib/source/lux/data/collection/set/ordered.lux b/stdlib/source/lux/data/collection/set/ordered.lux
index 32702ed7f..1be73506b 100644
--- a/stdlib/source/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/lux/data/collection/set/ordered.lux
@@ -5,7 +5,7 @@
[order (#+ Order)]]
[data
[collection
- ["." list ("#;." fold)]
+ ["." list ("#@." fold)]
[dictionary
["/" ordered]]]]
[type
@@ -54,29 +54,29 @@
(All [a] (-> (Set a) (List a)))
(|>> :representation /.keys))
- (def: #export (from-list Order<a> list)
+ (def: #export (from-list &order list)
(All [a] (-> (Order a) (List a) (Set a)))
- (list;fold add (new Order<a>) list))
+ (list@fold add (..new &order) list))
(def: #export (union left right)
(All [a] (-> (Set a) (Set a) (Set a)))
- (list;fold ..add right (..to-list left)))
+ (list@fold ..add right (..to-list left)))
(def: #export (intersection left right)
(All [a] (-> (Set a) (Set a) (Set a)))
(|> (..to-list right)
(list.filter (..member? left))
- (..from-list (get@ #/.order (:representation right)))))
+ (..from-list (get@ #/.&order (:representation right)))))
(def: #export (difference param subject)
(All [a] (-> (Set a) (Set a) (Set a)))
(|> (..to-list subject)
(list.filter (|>> (..member? param) not))
- (..from-list (get@ #/.order (:representation subject)))))
+ (..from-list (get@ #/.&order (:representation subject)))))
(structure: #export equivalence (All [a] (Equivalence (Set a)))
(def: (= reference sample)
- (:: (list.equivalence (:: (:representation sample) eq))
+ (:: (list.equivalence (:: (:representation reference) &equivalence))
= (..to-list reference) (..to-list sample))))
)
diff --git a/stdlib/source/lux/data/collection/stack.lux b/stdlib/source/lux/data/collection/stack.lux
index 2f822ecb1..d3a937cb4 100644
--- a/stdlib/source/lux/data/collection/stack.lux
+++ b/stdlib/source/lux/data/collection/stack.lux
@@ -1,8 +1,11 @@
(.module:
[lux #*
+ [control
+ [equivalence (#+ Equivalence)]
+ [functor (#+ Functor)]]
[data
[collection
- ["." list]]]])
+ ["//" list]]]])
(type: #export (Stack a)
(List a))
@@ -11,13 +14,13 @@
Stack
(list))
-(def: #export (size stack)
+(def: #export size
(All [a] (-> (Stack a) Nat))
- (list.size stack))
+ //.size)
-(def: #export (empty? stack)
+(def: #export empty?
(All [a] (-> (Stack a) Bit))
- (list.empty? stack))
+ //.empty?)
(def: #export (peek stack)
(All [a] (-> (Stack a) (Maybe a)))
@@ -40,3 +43,13 @@
(def: #export (push value stack)
(All [a] (-> a (Stack a) (Stack a)))
(#.Cons value stack))
+
+(def: #export equivalence
+ (All [a]
+ (-> (Equivalence a)
+ (Equivalence (Stack a))))
+ //.equivalence)
+
+(def: #export functor
+ (Functor Stack)
+ //.functor)
diff --git a/stdlib/source/lux/data/collection/tree/rose.lux b/stdlib/source/lux/data/collection/tree/rose.lux
index 7043c2afd..209b6af40 100644
--- a/stdlib/source/lux/data/collection/tree/rose.lux
+++ b/stdlib/source/lux/data/collection/tree/rose.lux
@@ -13,12 +13,10 @@
["." code]
["s" syntax (#+ syntax: Syntax)]]])
-## [Types]
(type: #export (Tree a)
{#value a
#children (List (Tree a))})
-## [Values]
(def: #export (flatten tree)
(All [a] (-> (Tree a) (List a)))
(#.Cons (get@ #value tree)
@@ -34,7 +32,6 @@
{#value value
#children children})
-## [Syntax]
(type: #rec Tree-Code
[Code (List Tree-Code)])
@@ -56,7 +53,6 @@
(` {#value (~ value)
#children (list (~+ (list;map recur children)))})))))))
-## [Structs]
(structure: #export (equivalence Equivalence<a>) (All [a] (-> (Equivalence a) (Equivalence (Tree a))))
(def: (= tx ty)
(and (:: Equivalence<a> = (get@ #value tx) (get@ #value ty))