aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/data/collection/set
diff options
context:
space:
mode:
authorEduardo Julian2022-04-08 05:42:36 -0400
committerEduardo Julian2022-04-08 05:42:36 -0400
commit0d909187d5b9effcd08f533d50af7d29c0d6bfd8 (patch)
treec50f12c5e47e3db90c3a701b54ee9953da942210 /stdlib/source/test/lux/data/collection/set
parente5e4c2aff562e5c01fefb808d1d68a40f29c9cc5 (diff)
De-sigil-ification: $
Diffstat (limited to 'stdlib/source/test/lux/data/collection/set')
-rw-r--r--stdlib/source/test/lux/data/collection/set/multi.lux334
-rw-r--r--stdlib/source/test/lux/data/collection/set/ordered.lux236
2 files changed, 285 insertions, 285 deletions
diff --git a/stdlib/source/test/lux/data/collection/set/multi.lux b/stdlib/source/test/lux/data/collection/set/multi.lux
index 755efb685..9ace968fb 100644
--- a/stdlib/source/test/lux/data/collection/set/multi.lux
+++ b/stdlib/source/test/lux/data/collection/set/multi.lux
@@ -40,15 +40,15 @@
Test
(do [! random.monad]
[diversity (# ! each (n.% 10) random.nat)]
- ($_ _.and
- (_.for [/.equivalence]
- ($equivalence.spec /.equivalence (..random diversity n.hash ..count random.nat)))
- (_.for [/.hash]
- (|> random.nat
- (# random.monad each (function (_ single)
- (/.has 1 single (/.empty n.hash))))
- ($hash.spec /.hash)))
- )))
+ (all _.and
+ (_.for [/.equivalence]
+ ($equivalence.spec /.equivalence (..random diversity n.hash ..count random.nat)))
+ (_.for [/.hash]
+ (|> random.nat
+ (# random.monad each (function (_ single)
+ (/.has 1 single (/.empty n.hash))))
+ ($hash.spec /.hash)))
+ )))
(def: composition
Test
@@ -56,57 +56,57 @@
[diversity (# ! each (n.% 10) random.nat)
sample (..random diversity n.hash ..count random.nat)
another (..random diversity n.hash ..count random.nat)]
- (`` ($_ _.and
- (~~ (template [<name> <composition>]
- [(_.cover [<name>]
- (let [|sample| (/.support sample)
- |another| (/.support another)
- sample_only (set.difference |another| |sample|)
- another_only (set.difference |sample| |another|)
- common (set.intersection |sample| |another|)
- composed (<name> sample another)
+ (`` (all _.and
+ (~~ (template [<name> <composition>]
+ [(_.cover [<name>]
+ (let [|sample| (/.support sample)
+ |another| (/.support another)
+ sample_only (set.difference |another| |sample|)
+ another_only (set.difference |sample| |another|)
+ common (set.intersection |sample| |another|)
+ composed (<name> sample another)
- no_left_changes! (list.every? (function (_ member)
- (n.= (/.multiplicity sample member)
- (/.multiplicity composed member)))
- (set.list sample_only))
- no_right_changes! (list.every? (function (_ member)
- (n.= (/.multiplicity another member)
+ no_left_changes! (list.every? (function (_ member)
+ (n.= (/.multiplicity sample member)
(/.multiplicity composed member)))
- (set.list another_only))
- common_changes! (list.every? (function (_ member)
- (n.= (<composition> (/.multiplicity sample member)
- (/.multiplicity another member))
- (/.multiplicity composed member)))
- (set.list common))]
- (and no_left_changes!
- no_right_changes!
- common_changes!)))]
+ (set.list sample_only))
+ no_right_changes! (list.every? (function (_ member)
+ (n.= (/.multiplicity another member)
+ (/.multiplicity composed member)))
+ (set.list another_only))
+ common_changes! (list.every? (function (_ member)
+ (n.= (<composition> (/.multiplicity sample member)
+ (/.multiplicity another member))
+ (/.multiplicity composed member)))
+ (set.list common))]
+ (and no_left_changes!
+ no_right_changes!
+ common_changes!)))]
- [/.sum n.+]
- [/.union n.max]
- ))
- (_.cover [/.intersection]
- (let [|sample| (/.support sample)
- |another| (/.support another)
- sample_only (set.difference |another| |sample|)
- another_only (set.difference |sample| |another|)
- common (set.intersection |sample| |another|)
- composed (/.intersection sample another)
+ [/.sum n.+]
+ [/.union n.max]
+ ))
+ (_.cover [/.intersection]
+ (let [|sample| (/.support sample)
+ |another| (/.support another)
+ sample_only (set.difference |another| |sample|)
+ another_only (set.difference |sample| |another|)
+ common (set.intersection |sample| |another|)
+ composed (/.intersection sample another)
- left_removals! (list.every? (|>> (/.member? composed) not)
- (set.list sample_only))
- right_removals! (list.every? (|>> (/.member? composed) not)
- (set.list another_only))
- common_changes! (list.every? (function (_ member)
- (n.= (n.min (/.multiplicity sample member)
- (/.multiplicity another member))
- (/.multiplicity composed member)))
- (set.list common))]
- (and left_removals!
- right_removals!
- common_changes!)))
- ))))
+ left_removals! (list.every? (|>> (/.member? composed) not)
+ (set.list sample_only))
+ right_removals! (list.every? (|>> (/.member? composed) not)
+ (set.list another_only))
+ common_changes! (list.every? (function (_ member)
+ (n.= (n.min (/.multiplicity sample member)
+ (/.multiplicity another member))
+ (/.multiplicity composed member)))
+ (set.list common))]
+ (and left_removals!
+ right_removals!
+ common_changes!)))
+ ))))
(def: .public test
Test
@@ -120,121 +120,121 @@
addition_count ..count
partial_removal_count (# ! each (n.% addition_count) random.nat)
another (..random diversity n.hash ..count random.nat)]
- ($_ _.and
- (_.cover [/.list /.of_list]
- (|> sample
- /.list
- (/.of_list n.hash)
- (# /.equivalence = sample)))
- (_.cover [/.size]
- (n.= (list.size (/.list sample))
- (/.size sample)))
- (_.cover [/.empty?]
- (bit#= (/.empty? sample)
- (n.= 0 (/.size sample))))
- (_.cover [/.empty]
- (/.empty? (/.empty n.hash)))
- (_.cover [/.support]
- (list.every? (set.member? (/.support sample))
- (/.list sample)))
- (_.cover [/.member?]
- (let [non_member_is_not_identified!
- (not (/.member? sample non_member))
+ (all _.and
+ (_.cover [/.list /.of_list]
+ (|> sample
+ /.list
+ (/.of_list n.hash)
+ (# /.equivalence = sample)))
+ (_.cover [/.size]
+ (n.= (list.size (/.list sample))
+ (/.size sample)))
+ (_.cover [/.empty?]
+ (bit#= (/.empty? sample)
+ (n.= 0 (/.size sample))))
+ (_.cover [/.empty]
+ (/.empty? (/.empty n.hash)))
+ (_.cover [/.support]
+ (list.every? (set.member? (/.support sample))
+ (/.list sample)))
+ (_.cover [/.member?]
+ (let [non_member_is_not_identified!
+ (not (/.member? sample non_member))
- all_members_are_identified!
- (list.every? (/.member? sample)
- (/.list sample))]
- (and non_member_is_not_identified!
- all_members_are_identified!)))
- (_.cover [/.multiplicity]
- (let [non_members_have_0_multiplicity!
- (n.= 0 (/.multiplicity sample non_member))
+ all_members_are_identified!
+ (list.every? (/.member? sample)
+ (/.list sample))]
+ (and non_member_is_not_identified!
+ all_members_are_identified!)))
+ (_.cover [/.multiplicity]
+ (let [non_members_have_0_multiplicity!
+ (n.= 0 (/.multiplicity sample non_member))
- every_member_has_positive_multiplicity!
- (list.every? (|>> (/.multiplicity sample) (n.> 0))
- (/.list sample))]
- (and non_members_have_0_multiplicity!
- every_member_has_positive_multiplicity!)))
- (_.cover [/.has]
- (let [null_scenario!
- (|> sample
- (/.has 0 non_member)
- (# /.equivalence = sample))
+ every_member_has_positive_multiplicity!
+ (list.every? (|>> (/.multiplicity sample) (n.> 0))
+ (/.list sample))]
+ (and non_members_have_0_multiplicity!
+ every_member_has_positive_multiplicity!)))
+ (_.cover [/.has]
+ (let [null_scenario!
+ (|> sample
+ (/.has 0 non_member)
+ (# /.equivalence = sample))
- normal_scenario!
- (let [sample+ (/.has addition_count non_member sample)]
- (and (not (/.member? sample non_member))
- (/.member? sample+ non_member)
- (n.= addition_count (/.multiplicity sample+ non_member))))]
- (and null_scenario!
- normal_scenario!)))
- (_.cover [/.lacks]
- (let [null_scenario!
- (# /.equivalence =
- (|> sample
- (/.has addition_count non_member))
- (|> sample
- (/.has addition_count non_member)
- (/.lacks 0 non_member)))
+ normal_scenario!
+ (let [sample+ (/.has addition_count non_member sample)]
+ (and (not (/.member? sample non_member))
+ (/.member? sample+ non_member)
+ (n.= addition_count (/.multiplicity sample+ non_member))))]
+ (and null_scenario!
+ normal_scenario!)))
+ (_.cover [/.lacks]
+ (let [null_scenario!
+ (# /.equivalence =
+ (|> sample
+ (/.has addition_count non_member))
+ (|> sample
+ (/.has addition_count non_member)
+ (/.lacks 0 non_member)))
- partial_scenario!
- (let [sample* (|> sample
- (/.has addition_count non_member)
- (/.lacks partial_removal_count non_member))]
- (and (/.member? sample* non_member)
- (n.= (n.- partial_removal_count
- addition_count)
- (/.multiplicity sample* non_member))))
-
- total_scenario!
- (|> sample
- (/.has addition_count non_member)
- (/.lacks addition_count non_member)
- (# /.equivalence = sample))]
- (and null_scenario!
partial_scenario!
- total_scenario!)))
- (_.cover [/.of_set]
- (let [unary (|> sample /.support /.of_set)]
- (list.every? (|>> (/.multiplicity unary) (n.= 1))
- (/.list unary))))
- (_.cover [/.sub?]
- (let [unary (|> sample /.support /.of_set)]
- (and (/.sub? sample unary)
- (or (not (/.sub? unary sample))
- (# /.equivalence = sample unary)))))
- (_.cover [/.super?]
- (let [unary (|> sample /.support /.of_set)]
- (and (/.super? unary sample)
- (or (not (/.super? sample unary))
- (# /.equivalence = sample unary)))))
- (_.cover [/.difference]
- (let [|sample| (/.support sample)
- |another| (/.support another)
- sample_only (set.difference |another| |sample|)
- another_only (set.difference |sample| |another|)
- common (set.intersection |sample| |another|)
- composed (/.difference sample another)
+ (let [sample* (|> sample
+ (/.has addition_count non_member)
+ (/.lacks partial_removal_count non_member))]
+ (and (/.member? sample* non_member)
+ (n.= (n.- partial_removal_count
+ addition_count)
+ (/.multiplicity sample* non_member))))
+
+ total_scenario!
+ (|> sample
+ (/.has addition_count non_member)
+ (/.lacks addition_count non_member)
+ (# /.equivalence = sample))]
+ (and null_scenario!
+ partial_scenario!
+ total_scenario!)))
+ (_.cover [/.of_set]
+ (let [unary (|> sample /.support /.of_set)]
+ (list.every? (|>> (/.multiplicity unary) (n.= 1))
+ (/.list unary))))
+ (_.cover [/.sub?]
+ (let [unary (|> sample /.support /.of_set)]
+ (and (/.sub? sample unary)
+ (or (not (/.sub? unary sample))
+ (# /.equivalence = sample unary)))))
+ (_.cover [/.super?]
+ (let [unary (|> sample /.support /.of_set)]
+ (and (/.super? unary sample)
+ (or (not (/.super? sample unary))
+ (# /.equivalence = sample unary)))))
+ (_.cover [/.difference]
+ (let [|sample| (/.support sample)
+ |another| (/.support another)
+ sample_only (set.difference |another| |sample|)
+ another_only (set.difference |sample| |another|)
+ common (set.intersection |sample| |another|)
+ composed (/.difference sample another)
- ommissions! (list.every? (|>> (/.member? composed) not)
- (set.list sample_only))
- intact! (list.every? (function (_ member)
- (n.= (/.multiplicity another member)
- (/.multiplicity composed member)))
- (set.list another_only))
- subtractions! (list.every? (function (_ member)
- (let [sample_multiplicity (/.multiplicity sample member)
- another_multiplicity (/.multiplicity another member)]
- (n.= (if (n.> another_multiplicity sample_multiplicity)
- 0
- (n.- sample_multiplicity
- another_multiplicity))
- (/.multiplicity composed member))))
- (set.list common))]
- (and ommissions!
- intact!
- subtractions!)))
+ ommissions! (list.every? (|>> (/.member? composed) not)
+ (set.list sample_only))
+ intact! (list.every? (function (_ member)
+ (n.= (/.multiplicity another member)
+ (/.multiplicity composed member)))
+ (set.list another_only))
+ subtractions! (list.every? (function (_ member)
+ (let [sample_multiplicity (/.multiplicity sample member)
+ another_multiplicity (/.multiplicity another member)]
+ (n.= (if (n.> another_multiplicity sample_multiplicity)
+ 0
+ (n.- sample_multiplicity
+ another_multiplicity))
+ (/.multiplicity composed member))))
+ (set.list common))]
+ (and ommissions!
+ intact!
+ subtractions!)))
- ..signature
- ..composition
- ))))
+ ..signature
+ ..composition
+ ))))
diff --git a/stdlib/source/test/lux/data/collection/set/ordered.lux b/stdlib/source/test/lux/data/collection/set/ordered.lux
index b4b97a984..67f7bb483 100644
--- a/stdlib/source/test/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/test/lux/data/collection/set/ordered.lux
@@ -52,126 +52,126 @@
setL (/.of_list n.order listL)
setR (/.of_list n.order listR)
empty (/.empty n.order)]]
- (`` ($_ _.and
- (_.for [/.equivalence]
- ($equivalence.spec /.equivalence (..random sizeL n.order random.nat)))
-
- (_.cover [/.size]
- (n.= sizeL (/.size setL)))
- (_.cover [/.empty?]
- (bit#= (n.= 0 (/.size setL))
- (/.empty? setL)))
- (_.cover [/.empty]
- (/.empty? (/.empty n.order)))
- (_.cover [/.list]
- (# (list.equivalence n.equivalence) =
- (/.list (/.of_list n.order listL))
- (list.sorted (# n.order <) listL)))
- (_.cover [/.of_list]
- (|> setL
- /.list (/.of_list n.order)
- (/#= setL)))
- (~~ (template [<coverage> <comparison>]
- [(_.cover [<coverage>]
- (case (<coverage> setL)
- {.#Some value}
- (|> setL /.list (list.every? (<comparison> value)))
-
- {.#None}
- (/.empty? setL)))]
-
- [/.min n.>=]
- [/.max n.<=]
- ))
- (_.cover [/.member?]
- (let [members_are_identified!
- (list.every? (/.member? setL) (/.list setL))
-
- non_members_are_not_identified!
- (not (/.member? setL non_memberL))]
- (and members_are_identified!
- non_members_are_not_identified!)))
- (_.cover [/.has]
- (let [setL+ (/.has non_memberL setL)]
- (and (not (/.member? setL non_memberL))
- (/.member? setL+ non_memberL)
- (n.= (++ (/.size setL))
- (/.size setL+)))))
- (_.cover [/.lacks]
- (|> setL
- (/.has non_memberL)
- (/.lacks non_memberL)
- (# /.equivalence = setL)))
- (_.cover [/.sub?]
- (let [self!
- (/.sub? setL setL)
-
- empty!
- (/.sub? setL empty)]
- (and self!
- empty!)))
- (_.cover [/.super?]
- (let [self!
- (/.super? setL setL)
-
- empty!
- (/.super? empty setL)
-
- symmetry!
- (bit#= (/.super? setL setR)
- (/.sub? setR setL))]
- (and self!
+ (`` (all _.and
+ (_.for [/.equivalence]
+ ($equivalence.spec /.equivalence (..random sizeL n.order random.nat)))
+
+ (_.cover [/.size]
+ (n.= sizeL (/.size setL)))
+ (_.cover [/.empty?]
+ (bit#= (n.= 0 (/.size setL))
+ (/.empty? setL)))
+ (_.cover [/.empty]
+ (/.empty? (/.empty n.order)))
+ (_.cover [/.list]
+ (# (list.equivalence n.equivalence) =
+ (/.list (/.of_list n.order listL))
+ (list.sorted (# n.order <) listL)))
+ (_.cover [/.of_list]
+ (|> setL
+ /.list (/.of_list n.order)
+ (/#= setL)))
+ (~~ (template [<coverage> <comparison>]
+ [(_.cover [<coverage>]
+ (case (<coverage> setL)
+ {.#Some value}
+ (|> setL /.list (list.every? (<comparison> value)))
+
+ {.#None}
+ (/.empty? setL)))]
+
+ [/.min n.>=]
+ [/.max n.<=]
+ ))
+ (_.cover [/.member?]
+ (let [members_are_identified!
+ (list.every? (/.member? setL) (/.list setL))
+
+ non_members_are_not_identified!
+ (not (/.member? setL non_memberL))]
+ (and members_are_identified!
+ non_members_are_not_identified!)))
+ (_.cover [/.has]
+ (let [setL+ (/.has non_memberL setL)]
+ (and (not (/.member? setL non_memberL))
+ (/.member? setL+ non_memberL)
+ (n.= (++ (/.size setL))
+ (/.size setL+)))))
+ (_.cover [/.lacks]
+ (|> setL
+ (/.has non_memberL)
+ (/.lacks non_memberL)
+ (# /.equivalence = setL)))
+ (_.cover [/.sub?]
+ (let [self!
+ (/.sub? setL setL)
+
+ empty!
+ (/.sub? setL empty)]
+ (and self!
+ empty!)))
+ (_.cover [/.super?]
+ (let [self!
+ (/.super? setL setL)
+
empty!
- symmetry!)))
- (~~ (template [<coverage> <relation> <empty?>]
- [(_.cover [<coverage>]
- (let [self!
- (# /.equivalence =
- setL
- (<coverage> setL setL))
-
- super!
- (and (<relation> (<coverage> setL setR) setL)
- (<relation> (<coverage> setL setR) setR))
-
- empty!
- (# /.equivalence =
- (if <empty?> empty setL)
- (<coverage> setL empty))
-
- idempotence!
- (# /.equivalence =
- (<coverage> setL (<coverage> setL setR))
- (<coverage> setR (<coverage> setL setR)))]
- (and self!
+ (/.super? empty setL)
+
+ symmetry!
+ (bit#= (/.super? setL setR)
+ (/.sub? setR setL))]
+ (and self!
+ empty!
+ symmetry!)))
+ (~~ (template [<coverage> <relation> <empty?>]
+ [(_.cover [<coverage>]
+ (let [self!
+ (# /.equivalence =
+ setL
+ (<coverage> setL setL))
+
super!
+ (and (<relation> (<coverage> setL setR) setL)
+ (<relation> (<coverage> setL setR) setR))
+
empty!
- idempotence!)))]
-
- [/.union /.sub? false]
- [/.intersection /.super? true]
- ))
- (_.cover [/.difference]
- (let [self!
- (|> setL
- (/.difference setL)
- (# /.equivalence = empty))
-
- empty!
- (|> setL
- (/.difference empty)
- (# /.equivalence = setL))
-
- difference!
- (not (list.any? (/.member? (/.difference setL setR))
- (/.list setL)))
-
- idempotence!
- (# /.equivalence =
- (/.difference setL setR)
- (/.difference setL (/.difference setL setR)))]
- (and self!
+ (# /.equivalence =
+ (if <empty?> empty setL)
+ (<coverage> setL empty))
+
+ idempotence!
+ (# /.equivalence =
+ (<coverage> setL (<coverage> setL setR))
+ (<coverage> setR (<coverage> setL setR)))]
+ (and self!
+ super!
+ empty!
+ idempotence!)))]
+
+ [/.union /.sub? false]
+ [/.intersection /.super? true]
+ ))
+ (_.cover [/.difference]
+ (let [self!
+ (|> setL
+ (/.difference setL)
+ (# /.equivalence = empty))
+
empty!
+ (|> setL
+ (/.difference empty)
+ (# /.equivalence = setL))
+
difference!
- idempotence!)))
- )))))
+ (not (list.any? (/.member? (/.difference setL setR))
+ (/.list setL)))
+
+ idempotence!
+ (# /.equivalence =
+ (/.difference setL setR)
+ (/.difference setL (/.difference setL setR)))]
+ (and self!
+ empty!
+ difference!
+ idempotence!)))
+ )))))