From 6fd22846f21b8b70b7867e989109d14a366c0a3e Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sat, 14 Aug 2021 03:09:58 -0400 Subject: Moved documentation-generation machinery to its own module. --- stdlib/source/test/aedifex/command/version.lux | 2 +- stdlib/source/test/lux.lux | 2 + stdlib/source/test/lux/abstract/comonad/cofree.lux | 4 +- .../source/test/lux/control/concurrency/actor.lux | 2 +- stdlib/source/test/lux/control/concurrency/stm.lux | 40 +++++----- stdlib/source/test/lux/control/parser.lux | 8 +- stdlib/source/test/lux/control/parser/text.lux | 6 +- stdlib/source/test/lux/control/parser/type.lux | 8 +- stdlib/source/test/lux/control/region.lux | 30 +++---- stdlib/source/test/lux/control/thread.lux | 16 ++-- stdlib/source/test/lux/data/binary.lux | 8 +- stdlib/source/test/lux/data/collection/array.lux | 20 ++--- .../source/test/lux/data/collection/dictionary.lux | 16 ++-- stdlib/source/test/lux/data/collection/list.lux | 22 ++--- stdlib/source/test/lux/data/collection/queue.lux | 14 ++-- .../test/lux/data/collection/queue/priority.lux | 30 +++---- .../source/test/lux/data/collection/sequence.lux | 36 ++++----- stdlib/source/test/lux/data/collection/stack.lux | 16 ++-- stdlib/source/test/lux/data/text.lux | 4 +- stdlib/source/test/lux/documentation.lux | 93 ++++++++++++++++++++++ stdlib/source/test/lux/meta.lux | 4 +- .../compiler/language/lux/phase/analysis/case.lux | 12 +-- .../language/lux/phase/analysis/function.lux | 24 +++--- .../language/lux/phase/analysis/structure.lux | 16 ++-- stdlib/source/test/lux/world/console.lux | 2 +- 25 files changed, 265 insertions(+), 170 deletions(-) create mode 100644 stdlib/source/test/lux/documentation.lux (limited to 'stdlib/source/test') diff --git a/stdlib/source/test/aedifex/command/version.lux b/stdlib/source/test/aedifex/command/version.lux index 2bdf72078..c1ab3814e 100644 --- a/stdlib/source/test/aedifex/command/version.lux +++ b/stdlib/source/test/aedifex/command/version.lux @@ -38,7 +38,7 @@ (try.of_maybe (do maybe.monad [head (text.char 0 state) - [_ tail] (text.split 1 state)] + [_ tail] (text.split_at 1 state)] (in [[open? tail] head]))) (exception.except ..console_is_closed! []))) (def: (on_read_line [open? state]) diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index cf45f0ca5..b2c6790ee 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -49,6 +49,7 @@ ["#." control] ["#." data] ["#." debug] + ["#." documentation] ["#." locale] ["#." macro ["#/." code]] @@ -85,6 +86,7 @@ /control.test /data.test /debug.test + /documentation.test /locale.test /macro.test /math.test diff --git a/stdlib/source/test/lux/abstract/comonad/cofree.lux b/stdlib/source/test/lux/abstract/comonad/cofree.lux index 541977fc5..916d1953b 100644 --- a/stdlib/source/test/lux/abstract/comonad/cofree.lux +++ b/stdlib/source/test/lux/abstract/comonad/cofree.lux @@ -34,8 +34,8 @@ (Comparison (/.CoFree Sequence)) (function (_ == left right) (\ (list.equivalence ==) = - (sequence.take 100 (..interpret left)) - (sequence.take 100 (..interpret right))))) + (sequence.first 100 (..interpret left)) + (sequence.first 100 (..interpret right))))) (def: .public test Test diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux index c6b381829..627b294ad 100644 --- a/stdlib/source/test/lux/control/concurrency/actor.lux +++ b/stdlib/source/test/lux/control/concurrency/actor.lux @@ -203,7 +203,7 @@ [num_events (\ ! map (|>> (n.% 10) inc) random.nat) events (random.list num_events random.nat) num_observations (\ ! map (n.% num_events) random.nat) - .let [expected (list.take num_observations events) + .let [expected (list.first num_observations events) sink (: (Atom (Row Nat)) (atom.atom row.empty))]] (in (do async.monad diff --git a/stdlib/source/test/lux/control/concurrency/stm.lux b/stdlib/source/test/lux/control/concurrency/stm.lux index 5ac592494..dbe98177f 100644 --- a/stdlib/source/test/lux/control/concurrency/stm.lux +++ b/stdlib/source/test/lux/control/concurrency/stm.lux @@ -51,52 +51,52 @@ ($monad.spec ..injection ..comparison /.monad)) (in (do async.monad - [actual (/.commit (\ /.monad in expected))] - (_.cover' [/.commit] + [actual (/.commit! (\ /.monad in expected))] + (_.cover' [/.commit!] (n.= expected actual)))) (in (do async.monad - [actual (/.commit (/.read (/.var expected)))] + [actual (/.commit! (/.read (/.var expected)))] (_.cover' [/.Var /.var /.read] (n.= expected actual)))) (in (do async.monad [actual (let [box (/.var dummy)] - (/.commit (do /.monad - [_ (/.write expected box)] - (/.read box)))) + (/.commit! (do /.monad + [_ (/.write expected box)] + (/.read box)))) verdict (let [box (/.var dummy)] - (/.commit (do /.monad - [_ (/.write expected box) - actual (/.read box)] - (in (n.= expected actual)))))] + (/.commit! (do /.monad + [_ (/.write expected box) + actual (/.read box)] + (in (n.= expected actual)))))] (_.cover' [/.write] (and (n.= expected actual) verdict)))) (in (do async.monad [.let [box (/.var dummy)] - output (/.commit (do /.monad - [_ (/.update (n.+ expected) box)] - (/.read box)))] + output (/.commit! (do /.monad + [_ (/.update (n.+ expected) box)] + (/.read box)))] (_.cover' [/.update] (n.= (n.+ expected dummy) output)))) (in (do async.monad [.let [box (/.var dummy) - [follower sink] (io.run! (/.follow box))] - _ (/.commit (/.write expected box)) - _ (/.commit (/.update (n.* 2) box)) + [follower sink] (io.run! (/.follow! box))] + _ (/.commit! (/.write expected box)) + _ (/.commit! (/.update (n.* 2) box)) _ (async.future (\ sink close)) - _ (/.commit (/.update (n.* 3) box)) + _ (/.commit! (/.update (n.* 3) box)) changes (frp.list follower)] - (_.cover' [/.follow] + (_.cover' [/.follow!] (\ (list.equivalence n.equivalence) = (list expected (n.* 2 expected)) changes)))) (in (let [var (/.var 0)] (do {! async.monad} [_ (|> (list.repeated iterations_per_process []) - (list\map (function (_ _) (/.commit (/.update inc var)))) + (list\map (function (_ _) (/.commit! (/.update inc var)))) (monad.seq !)) - cummulative (/.commit (/.read var))] + cummulative (/.commit! (/.read var))] (_.cover' [/.STM] (n.= iterations_per_process cummulative))))) diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux index d6fa54ee1..bb81f4383 100644 --- a/stdlib/source/test/lux/control/parser.lux +++ b/stdlib/source/test/lux/control/parser.lux @@ -192,7 +192,7 @@ (/.result (/.exactly times .nat)) (match actual (\ (list.equivalence n.equivalence) = - (list.take times expected+) + (list.first times expected+) actual))) (|> (list\map code.nat expected+) (/.result (/.exactly (inc variadic) .nat)) @@ -212,7 +212,7 @@ (/.result (/.at_most times .nat)) (match actual (\ (list.equivalence n.equivalence) = - (list.take times expected+) + (list.first times expected+) actual))) (|> (list\map code.nat expected+) (/.result (/.at_most (inc variadic) .nat)) @@ -227,11 +227,11 @@ (\ (list.equivalence n.equivalence) = expected+ actual))) - (|> (list\map code.nat (list.take times expected+)) + (|> (list\map code.nat (list.first times expected+)) (/.result (/.between times (n.- times variadic) .nat)) (match actual (\ (list.equivalence n.equivalence) = - (list.take times expected+) + (list.first times expected+) actual))))) (_.cover [/.separated_by] (|> (list.interposed (code.text separator) (list\map code.nat expected+)) diff --git a/stdlib/source/test/lux/control/parser/text.lux b/stdlib/source/test/lux/control/parser/text.lux index a7bbfda92..35c509e00 100644 --- a/stdlib/source/test/lux/control/parser/text.lux +++ b/stdlib/source/test/lux/control/parser/text.lux @@ -333,10 +333,10 @@ (..should_fail "" /.any!)))) (do {! random.monad} [expected (random.unicode 1)] - (_.cover [/.peek /.cannot_parse] - (and (..should_pass expected (<>.before /.any /.peek)) + (_.cover [/.next /.cannot_parse] + (and (..should_pass expected (<>.before /.any /.next)) (|> "" - (/.result (<>.before /.any /.peek)) + (/.result (<>.before /.any /.next)) (!expect (^multi (#try.Failure error) (exception.match? /.cannot_parse error))))))) (do {! random.monad} diff --git a/stdlib/source/test/lux/control/parser/type.lux b/stdlib/source/test/lux/control/parser/type.lux index b348c1da2..373d549e9 100644 --- a/stdlib/source/test/lux/control/parser/type.lux +++ b/stdlib/source/test/lux/control/parser/type.lux @@ -198,15 +198,15 @@ (type\= expected actual)))))) (do {! random.monad} [expected ..primitive] - (_.cover [/.peek /.unconsumed_input] + (_.cover [/.next /.unconsumed_input] (and (|> (/.result (do //.monad - [actual /.peek + [actual /.next _ /.any] (in actual)) expected) (!expect (^multi (#try.Success actual) (type\= expected actual)))) - (|> (/.result /.peek expected) + (|> (/.result /.next expected) (!expect (^multi (#try.Failure error) (exception.match? /.unconsumed_input error))))))) (do {! random.monad} @@ -221,7 +221,7 @@ (exception.match? /.empty_input error))))] [/.any] - [/.peek] + [/.next] )))))) (do {! random.monad} [expected ..primitive] diff --git a/stdlib/source/test/lux/control/region.lux b/stdlib/source/test/lux/control/region.lux index ceda7b3a9..4f135a57d 100644 --- a/stdlib/source/test/lux/control/region.lux +++ b/stdlib/source/test/lux/control/region.lux @@ -103,14 +103,14 @@ .let [//@ ! count_clean_up (function (_ value) (do ! - [_ (thread.update inc clean_up_counter)] + [_ (thread.update! inc clean_up_counter)] (in (#try.Success []))))] outcome (/.run! ! (do {! (/.monad !)} - [_ (monad.map ! (/.acquire //@ count_clean_up) + [_ (monad.map ! (/.acquire! //@ count_clean_up) (enum.range n.enum 1 expected_clean_ups))] (in []))) - actual_clean_ups (thread.read clean_up_counter)] + actual_clean_ups (thread.read! clean_up_counter)] (in (and (..success? outcome) (n.= expected_clean_ups actual_clean_ups)))))) @@ -121,15 +121,15 @@ .let [//@ ! count_clean_up (function (_ value) (do ! - [_ (thread.update inc clean_up_counter)] + [_ (thread.update! inc clean_up_counter)] (in (#try.Success []))))] outcome (/.run! ! (do {! (/.monad !)} - [_ (monad.map ! (/.acquire //@ count_clean_up) + [_ (monad.map ! (/.acquire! //@ count_clean_up) (enum.range n.enum 1 expected_clean_ups)) _ (/.failure //@ (exception.error ..oops []))] (in []))) - actual_clean_ups (thread.read clean_up_counter)] + actual_clean_ups (thread.read! clean_up_counter)] (in (and (..throws? ..oops outcome) (n.= expected_clean_ups actual_clean_ups)))))) @@ -140,34 +140,34 @@ .let [//@ ! count_clean_up (function (_ value) (do ! - [_ (thread.update inc clean_up_counter)] + [_ (thread.update! inc clean_up_counter)] (in (#try.Success []))))] outcome (/.run! ! (do {! (/.monad !)} - [_ (monad.map ! (/.acquire //@ count_clean_up) + [_ (monad.map ! (/.acquire! //@ count_clean_up) (enum.range n.enum 1 expected_clean_ups)) _ (/.except //@ ..oops [])] (in []))) - actual_clean_ups (thread.read clean_up_counter)] + actual_clean_ups (thread.read! clean_up_counter)] (in (and (..throws? ..oops outcome) (n.= expected_clean_ups actual_clean_ups)))))) - (_.cover [/.acquire /.clean_up_error] + (_.cover [/.acquire! /.clean_up_error] (thread.result (do {! thread.monad} [clean_up_counter (thread.box 0) .let [//@ ! count_clean_up (function (_ value) (do ! - [_ (thread.update inc clean_up_counter)] + [_ (thread.update! inc clean_up_counter)] (in (: (Try Any) (exception.except ..oops [])))))] outcome (/.run! ! (do {! (/.monad !)} - [_ (monad.map ! (/.acquire //@ count_clean_up) + [_ (monad.map ! (/.acquire! //@ count_clean_up) (enum.range n.enum 1 expected_clean_ups))] (in []))) - actual_clean_ups (thread.read clean_up_counter)] + actual_clean_ups (thread.read! clean_up_counter)] (in (and (or (n.= 0 expected_clean_ups) (..throws? /.clean_up_error outcome)) (n.= expected_clean_ups @@ -179,9 +179,9 @@ .let [//@ !] outcome (/.run! ! (do (/.monad !) - [_ (/.lift //@ (thread.write expected_clean_ups clean_up_counter))] + [_ (/.lift //@ (thread.write! expected_clean_ups clean_up_counter))] (in []))) - actual_clean_ups (thread.read clean_up_counter)] + actual_clean_ups (thread.read! clean_up_counter)] (in (and (..success? outcome) (n.= expected_clean_ups actual_clean_ups)))))) diff --git a/stdlib/source/test/lux/control/thread.lux b/stdlib/source/test/lux/control/thread.lux index 4f71c7203..2f93f2349 100644 --- a/stdlib/source/test/lux/control/thread.lux +++ b/stdlib/source/test/lux/control/thread.lux @@ -57,26 +57,26 @@ (_.for [/.Box /.box] ($_ _.and - (_.cover [/.read] + (_.cover [/.read!] (n.= sample (/.result (: (All [!] (Thread ! Nat)) (do /.monad [box (/.box sample)] - (/.read box)))))) + (/.read! box)))))) - (_.cover [/.write] + (_.cover [/.write!] (n.= factor (/.result (: (All [!] (Thread ! Nat)) (do /.monad [box (/.box sample) - _ (/.write factor box)] - (/.read box)))))) + _ (/.write! factor box)] + (/.read! box)))))) - (_.cover [/.update] + (_.cover [/.update!] (n.= (n.* factor sample) (/.result (: (All [!] (Thread ! Nat)) (do /.monad [box (/.box sample) - old (/.update (n.* factor) box)] - (/.read box)))))))) + old (/.update! (n.* factor) box)] + (/.read! box)))))))) )))) diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux index d45cc6554..aab56834f 100644 --- a/stdlib/source/test/lux/data/binary.lux +++ b/stdlib/source/test/lux/data/binary.lux @@ -134,16 +134,16 @@ (case offset 0 (not verdict) _ verdict)))) - (_.cover [/.drop] - (and (\ /.equivalence = sample (/.drop 0 sample)) - (\ /.equivalence = (/.empty 0) (/.drop size sample)) + (_.cover [/.after] + (and (\ /.equivalence = sample (/.after 0 sample)) + (\ /.equivalence = (/.empty 0) (/.after size sample)) (case (list.reversed (..as_list sample)) #.End false (#.Item head tail) (n.= (list.fold n.+ 0 tail) - (/.fold n.+ 0 (/.drop 1 sample)))))) + (/.fold n.+ 0 (/.after 1 sample)))))) (_.cover [/.copy] (and (case (/.copy size 0 sample 0 (/.empty size)) (#try.Success output) diff --git a/stdlib/source/test/lux/data/collection/array.lux b/stdlib/source/test/lux/data/collection/array.lux index c7433632e..c1e1471f8 100644 --- a/stdlib/source/test/lux/data/collection/array.lux +++ b/stdlib/source/test/lux/data/collection/array.lux @@ -66,7 +66,7 @@ (n.even? member)) the_array)] [(#.Some expected) (#.Some [idx actual])] - (case (/.read idx the_array) + (case (/.read! idx the_array) (#.Some again) (and (n.= expected actual) (n.= actual again)) @@ -114,12 +114,12 @@ _ false)) - (_.cover [/.read /.write!] + (_.cover [/.read! /.write!] (let [the_array (|> (/.empty 2) (: (Array Nat)) (/.write! 0 expected))] - (case [(/.read 0 the_array) - (/.read 1 the_array)] + (case [(/.read! 0 the_array) + (/.read! 1 the_array)] [(#.Some actual) #.None] (n.= expected actual) @@ -129,8 +129,8 @@ (let [the_array (|> (/.empty 1) (: (Array Nat)) (/.write! 0 expected))] - (case [(/.read 0 the_array) - (/.read 0 (/.delete! 0 the_array))] + (case [(/.read! 0 the_array) + (/.read! 0 (/.delete! 0 the_array))] [(#.Some actual) #.None] (n.= expected actual) @@ -148,7 +148,7 @@ (: (Array Nat)) (/.write! 0 base) (/.update! 0 (n.+ shift)))] - (case (/.read 0 the_array) + (case (/.read! 0 the_array) (#.Some actual) (n.= expected actual) @@ -160,8 +160,8 @@ (/.write! 0 base) (/.upsert! 0 dummy (n.+ shift)) (/.upsert! 1 base (n.+ shift)))] - (case [(/.read 0 the_array) - (/.read 1 the_array)] + (case [(/.read! 0 the_array) + (/.read! 1 the_array)] [(#.Some actual/0) (#.Some actual/1)] (and (n.= expected actual/0) (n.= expected actual/1)) @@ -195,7 +195,7 @@ (/.empty size))] (exec (/.copy! amount 0 the_array 0 copy) (\ (list.equivalence n.equivalence) = - (list.take amount (/.list the_array)) + (list.first amount (/.list the_array)) (/.list copy)))))) (_.cover [/.clone] (let [clone (/.clone the_array)] diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index 7114a2eed..82e421d28 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -161,9 +161,9 @@ (#.Some v) (n.= test_val v) _ true))) - (_.cover [/.try_put /.key_already_exists] + (_.cover [/.has' /.key_already_exists] (let [can_put_new_keys! - (case (/.try_put non_key test_val dict) + (case (/.has' non_key test_val dict) (#try.Success dict) (case (/.value non_key dict) (#.Some v) (n.= test_val v) @@ -175,7 +175,7 @@ cannot_put_old_keys! (or (n.= 0 size) (let [first_key (|> dict /.keys list.head maybe.assume)] - (case (/.try_put first_key test_val dict) + (case (/.has' first_key test_val dict) (#try.Success _) false @@ -206,9 +206,9 @@ _ false))) - (_.cover [/.upsert] + (_.cover [/.revised'] (let [can_upsert_new_key! - (case (/.value non_key (/.upsert non_key test_val inc dict)) + (case (/.value non_key (/.revised' non_key test_val inc dict)) (#.Some inserted) (n.= (inc test_val) inserted) @@ -221,7 +221,7 @@ true (#.Some [known_key known_value]) - (case (/.value known_key (/.upsert known_key test_val inc dict)) + (case (/.value known_key (/.revised' known_key test_val inc dict)) (#.Some updated) (n.= (inc known_value) updated) @@ -237,10 +237,10 @@ /.size (n.= 1))) - (_.cover [/.re_bind] + (_.cover [/.re_bound] (or (n.= 0 size) (let [first_key (|> dict /.keys list.head maybe.assume) - rebound (/.re_bind first_key non_key dict)] + rebound (/.re_bound first_key non_key dict)] (and (n.= (/.size dict) (/.size rebound)) (/.key? rebound non_key) (not (/.key? rebound first_key)) diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index 7fb1e8704..ce86a80c7 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -202,18 +202,18 @@ positives) (/\= (/.only (bit.complement n.even?) sample) negatives)))) - (_.cover [/.split] - (let [[left right] (/.split idx sample)] + (_.cover [/.split_at] + (let [[left right] (/.split_at idx sample)] (/\= sample (/\compose left right)))) (_.cover [/.split_when] (let [[left right] (/.split_when n.even? sample)] (/\= sample (/\compose left right)))) - (_.cover [/.take /.drop] + (_.cover [/.first /.after] (/\= sample - (/\compose (/.take idx sample) - (/.drop idx sample)))) + (/\compose (/.first idx sample) + (/.after idx sample)))) (_.cover [/.while /.until] (/\= sample (/\compose (/.while n.even? sample) @@ -292,9 +292,9 @@ (n.min (/.size sample/0) (/.size sample/1))) can_extract_values! - (and (/\= (/.take zipped::size sample/0) + (and (/\= (/.first zipped::size sample/0) (/\map product.left zipped)) - (/\= (/.take zipped::size sample/1) + (/\= (/.first zipped::size sample/1) (/\map product.right zipped)))] (and size_of_smaller_list! can_extract_values!))) @@ -310,11 +310,11 @@ (/.size sample/2))) can_extract_values! - (and (/\= (/.take zipped::size sample/0) + (and (/\= (/.first zipped::size sample/0) (/\map product.left zipped)) - (/\= (/.take zipped::size sample/1) + (/\= (/.first zipped::size sample/1) (/\map (|>> product.right product.left) zipped)) - (/\= (/.take zipped::size sample/2) + (/\= (/.first zipped::size sample/2) (/\map (|>> product.right product.right) zipped)))] (and size_of_smaller_list! can_extract_values!))) @@ -424,7 +424,7 @@ 0))))) (_.cover [/.folds] (/\= (/\map (function (_ index) - (\ /.fold fold n.+ 0 (/.take index sample))) + (\ /.fold fold n.+ 0 (/.first index sample))) (/.indices (inc (/.size sample)))) (/.folds n.+ 0 sample))) (do random.monad diff --git a/stdlib/source/test/lux/data/collection/queue.lux b/stdlib/source/test/lux/data/collection/queue.lux index 33ec7d9ba..5fcec5102 100644 --- a/stdlib/source/test/lux/data/collection/queue.lux +++ b/stdlib/source/test/lux/data/collection/queue.lux @@ -58,8 +58,8 @@ /.empty))] (and empty_is_empty! all_empty_queues_look_the_same!))) - (_.cover [/.peek] - (case [members (/.peek sample)] + (_.cover [/.front] + (case [members (/.front sample)] [(#.Item head tail) (#.Some first)] (n.= head first) @@ -77,8 +77,8 @@ (not (/.member? n.equivalence sample non_member))] (and every_member_is_identified! non_member_is_not_identified!))) - (_.cover [/.push] - (let [pushed (/.push non_member sample) + (_.cover [/.end] + (let [pushed (/.end non_member sample) size_increases! (n.= (inc (/.size sample)) (/.size pushed)) @@ -93,10 +93,10 @@ (and size_increases! new_member_is_identified! has_expected_order!))) - (_.cover [/.pop] + (_.cover [/.next] (case members (#.Item target expected) - (let [popped (/.pop sample) + (let [popped (/.next sample) size_decreases! (n.= (dec (/.size sample)) @@ -115,5 +115,5 @@ #.End (and (/.empty? sample) - (/.empty? (/.pop sample))))) + (/.empty? (/.next sample))))) )))) diff --git a/stdlib/source/test/lux/data/collection/queue/priority.lux b/stdlib/source/test/lux/data/collection/queue/priority.lux index 20579c5b6..4faaaf488 100644 --- a/stdlib/source/test/lux/data/collection/queue/priority.lux +++ b/stdlib/source/test/lux/data/collection/queue/priority.lux @@ -22,7 +22,7 @@ (monad.fold ! (function (_ head tail) (do ! [priority random.nat] - (in (/.push priority head tail)))) + (in (/.end priority head tail)))) /.empty inputs))) @@ -47,28 +47,28 @@ (/.empty? sample))) (_.cover [/.empty] (/.empty? /.empty)) - (_.cover [/.peek] - (case (/.peek sample) + (_.cover [/.front] + (case (/.front sample) (#.Some first) (n.> 0 (/.size sample)) #.None (/.empty? sample))) (_.cover [/.member?] - (case (/.peek sample) + (case (/.front sample) (#.Some first) (/.member? n.equivalence sample first) #.None (/.empty? sample))) - (_.cover [/.push] - (let [sample+ (/.push non_member_priority non_member sample)] + (_.cover [/.end] + (let [sample+ (/.end non_member_priority non_member sample)] (and (not (/.member? n.equivalence sample non_member)) (n.= (inc (/.size sample)) (/.size sample+)) (/.member? n.equivalence sample+ non_member)))) - (_.cover [/.pop] - (let [sample- (/.pop sample)] + (_.cover [/.next] + (let [sample- (/.next sample)] (or (and (/.empty? sample) (/.empty? sample-)) (n.= (dec (/.size sample)) @@ -77,17 +77,17 @@ ($_ _.and (_.cover [/.max] (|> /.empty - (/.push /.min min_member) - (/.push /.max max_member) - /.peek + (/.end /.min min_member) + (/.end /.max max_member) + /.front (maybe\map (n.= max_member)) (maybe.else false))) (_.cover [/.min] (|> /.empty - (/.push /.max max_member) - (/.push /.min min_member) - /.pop - /.peek + (/.end /.max max_member) + (/.end /.min min_member) + /.next + /.front (maybe\map (n.= min_member)) (maybe.else false))) )) diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux index 9a2c78afb..19183f1b1 100644 --- a/stdlib/source/test/lux/data/collection/sequence.lux +++ b/stdlib/source/test/lux/data/collection/sequence.lux @@ -26,8 +26,8 @@ (def: (= reference subject) (\ (list.equivalence super) = - (/.take 100 reference) - (/.take 100 subject)))) + (/.first 100 reference) + (/.first 100 subject)))) (def: .public test Test @@ -53,18 +53,18 @@ (_.cover [/.repeated] (n.= repeated (/.item index (/.repeated repeated)))) - (_.cover [/.take] + (_.cover [/.first] (list\= (enum.range n.enum offset (dec (n.+ size offset))) - (/.take size (/.iterations inc offset)))) - (_.cover [/.drop] + (/.first size (/.iterations inc offset)))) + (_.cover [/.after] (list\= (enum.range n.enum offset (dec (n.+ size offset))) - (/.take size (/.drop offset (/.iterations inc 0))))) - (_.cover [/.split] - (let [[drops takes] (/.split size (/.iterations inc 0))] + (/.first size (/.after offset (/.iterations inc 0))))) + (_.cover [/.split_at] + (let [[drops takes] (/.split_at size (/.iterations inc 0))] (and (list\= (enum.range n.enum 0 (dec size)) drops) (list\= (enum.range n.enum size (dec (n.* 2 size))) - (/.take size takes))))) + (/.first size takes))))) (_.cover [/.while] (list\= (enum.range n.enum 0 (dec size)) (/.while (n.< size) (/.iterations inc 0)))) @@ -83,10 +83,10 @@ (/.head (/.iterations inc offset)))) (_.cover [/.tail] (list\= (enum.range n.enum (inc offset) (n.+ size offset)) - (/.take size (/.tail (/.iterations inc offset))))) + (/.first size (/.tail (/.iterations inc offset))))) (_.cover [/.only] (list\= (list\map (n.* 2) (enum.range n.enum 0 (dec size))) - (/.take size (/.only n.even? (/.iterations inc 0))))) + (/.first size (/.only n.even? (/.iterations inc 0))))) (_.cover [/.partition] (let [[evens odds] (/.partition n.even? (/.iterations inc 0))] (and (n.= (n.* 2 offset) @@ -96,16 +96,16 @@ (_.cover [/.unfold] (let [(^open "/\.") /.functor (^open "list\.") (list.equivalence text.equivalence)] - (list\= (/.take size - (/\map %.nat (/.iterations inc offset))) - (/.take size - (/.unfold (function (_ n) [(inc n) (%.nat n)]) - offset))))) + (list\= (/.first size + (/\map %.nat (/.iterations inc offset))) + (/.first size + (/.unfold (function (_ n) [(inc n) (%.nat n)]) + offset))))) (_.cover [/.cycle] (let [cycle (list& cycle_start cycle_next)] (list\= (list.joined (list.repeated size cycle)) - (/.take (n.* size (list.size cycle)) - (/.cycle [cycle_start cycle_next]))))) + (/.first (n.* size (list.size cycle)) + (/.cycle [cycle_start cycle_next]))))) (_.cover [/.^sequence&] (let [(/.^sequence& first second third next) (/.iterations inc offset)] (and (n.= offset first) diff --git a/stdlib/source/test/lux/data/collection/stack.lux b/stdlib/source/test/lux/data/collection/stack.lux index 591308f56..79355156f 100644 --- a/stdlib/source/test/lux/data/collection/stack.lux +++ b/stdlib/source/test/lux/data/collection/stack.lux @@ -20,7 +20,7 @@ (def: (injection value) (Injection /.Stack) - (/.push value /.empty)) + (/.top value /.empty)) (def: .public test Test @@ -43,24 +43,24 @@ (/.empty? sample))) (_.cover [/.empty] (/.empty? /.empty)) - (_.cover [/.peek] - (case (/.peek sample) + (_.cover [/.value] + (case (/.value sample) #.None (/.empty? sample) (#.Some _) (not (/.empty? sample)))) - (_.cover [/.pop] - (case (/.pop sample) + (_.cover [/.next] + (case (/.next sample) #.None (/.empty? sample) (#.Some [top remaining]) (\ (/.equivalence n.equivalence) = sample - (/.push top remaining)))) - (_.cover [/.push] - (case (/.pop (/.push expected_top sample)) + (/.top top remaining)))) + (_.cover [/.top] + (case (/.next (/.top expected_top sample)) (#.Some [actual_top actual_sample]) (and (same? expected_top actual_top) (same? sample actual_sample)) diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index f95757333..1efa4ebfe 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -288,8 +288,8 @@ .let [sample (/.joined (list sampleL sampleR)) (^open "/\.") /.equivalence]] ($_ _.and - (_.cover [/.split] - (|> (/.split sizeL sample) + (_.cover [/.split_at] + (|> (/.split_at sizeL sample) (case> (#.Right [_l _r]) (and (/\= sampleL _l) (/\= sampleR _r) diff --git a/stdlib/source/test/lux/documentation.lux b/stdlib/source/test/lux/documentation.lux new file mode 100644 index 000000000..b8a34a752 --- /dev/null +++ b/stdlib/source/test/lux/documentation.lux @@ -0,0 +1,93 @@ +(.module: + [library + [lux #* + ["_" test (#+ Test)] + [control + ["." try] + ["." exception] + [parser + ["<.>" code]]] + [data + ["." text ("#\." equivalence)] + [format + ["md" markdown]]] + ["." macro + [syntax (#+ syntax:)] + ["." template] + ["." code]]]] + [\\library + ["." /]]) + +(syntax: (macro_error [macro .any]) + (function (_ compiler) + (case ((macro.expansion macro) compiler) + (#try.Failure error) + (#try.Success [compiler (list (code.text error))]) + + (#try.Success _) + (#try.Failure "OOPS!")))) + +(template.with_locals [g!default + g!description] + (as_is (def: g!default + Nat + 123) + + (`` (/.documentation: /.documentation: + (~~ (template.text [g!description])))) + + (def: .public test + Test + (<| (_.covering /._) + ($_ _.and + (_.for [/.Definition] + ($_ _.and + (_.cover [/.default] + (let [definition (`` (/.default (~~ (template.identifier [.._] [g!default]))))] + (and (|> definition + (get@ #/.definition) + (text\= (template.text [g!default]))) + (|> definition + (get@ #/.documentation) + md.markdown + (text\= "") + not)))) + (_.cover [/.documentation:] + (and (|> ..documentation: + (get@ #/.definition) + (text\= (template.text [/.documentation:]))) + (|> ..documentation: + (get@ #/.documentation) + md.markdown + (text.contains? (template.text [g!description])) + not))) + )) + (_.for [/.Module] + ($_ _.and + (_.cover [/.module /.documentation] + (let [sub (/.module /._ + [] + []) + super (/.module .._ + [..documentation:] + [sub])] + (and (text.contains? (/.documentation sub) + (/.documentation super)) + (text.contains? (md.markdown (get@ #/.documentation ..documentation:)) + (/.documentation super))))) + )) + (_.cover [/.unqualified_identifier] + (`` (and (~~ (template [] + [(<| (text.contains? (get@ #exception.label /.unqualified_identifier)) + macro_error + )] + + [(/.default g!default)] + [(/.documentation: g!default + (~~ (template.text [g!description])))] + [(/.module g!default + [..documentation:] + [sub])] + ))))) + )))) + ) diff --git a/stdlib/source/test/lux/meta.lux b/stdlib/source/test/lux/meta.lux index b8e3e1c76..1403d6ee8 100644 --- a/stdlib/source/test/lux/meta.lux +++ b/stdlib/source/test/lux/meta.lux @@ -653,8 +653,8 @@ all_tags (|> random_tag (random.set name.hash 10) (\ ! map set.list)) - .let [tags_0 (list.take 5 all_tags) - tags_1 (list.drop 5 all_tags) + .let [tags_0 (list.first 5 all_tags) + tags_1 (list.after 5 all_tags) type_0 (#.Primitive name_0 (list)) type_1 (#.Primitive name_1 (list)) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux index 3f975a006..f694d0629 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -179,8 +179,8 @@ (_.test "Can analyse exhaustive pattern-matching." (|> (analyse_pm exhaustive_branchesC) _structure.check_succeeds)) - (let [non_exhaustive_branchesC (list.take (dec (list.size exhaustive_branchesC)) - exhaustive_branchesC)] + (let [non_exhaustive_branchesC (list.first (dec (list.size exhaustive_branchesC)) + exhaustive_branchesC)] (_.test "Will reject non-exhaustive pattern-matching." (|> (analyse_pm non_exhaustive_branchesC) _structure.check_fails))) @@ -189,9 +189,9 @@ redundancy_idx (|> r.nat (\ ! map (n.% (list.size redundant_patterns)))) .let [redundant_branchesC (<| (list!map (branch outputC)) list.joined - (list (list.take redundancy_idx redundant_patterns) + (list (list.first redundancy_idx redundant_patterns) (list (maybe.assume (list.item redundancy_idx redundant_patterns))) - (list.drop redundancy_idx redundant_patterns)))]] + (list.after redundancy_idx redundant_patterns)))]] (_.test "Will reject redundant pattern-matching." (|> (analyse_pm redundant_branchesC) _structure.check_fails))) @@ -199,10 +199,10 @@ [[heterogeneousT heterogeneousC] (r.only (|>> product.left (check.subsumes? outputT) not) _primitive.primitive) heterogeneous_idx (|> r.nat (\ ! map (n.% (list.size exhaustive_patterns)))) - .let [heterogeneous_branchesC (list.joined (list (list.take heterogeneous_idx exhaustive_branchesC) + .let [heterogeneous_branchesC (list.joined (list (list.first heterogeneous_idx exhaustive_branchesC) (list (let [[_pattern _body] (maybe.assume (list.item heterogeneous_idx exhaustive_branchesC))] [_pattern heterogeneousC])) - (list.drop (inc heterogeneous_idx) exhaustive_branchesC)))]] + (list.after (inc heterogeneous_idx) exhaustive_branchesC)))]] (_.test "Will reject pattern-matching if the bodies of the branches do not all have the same type." (|> (analyse_pm heterogeneous_branchesC) _structure.check_fails))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux index 3213443a6..b0027b15d 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -61,21 +61,21 @@ ($_ _.and (_.test "Can analyse function." (and (|> (//type.with_type (All [a] (-> a outputT)) - (/.function _primitive.phase func_name arg_name archive.empty outputC)) + (/.function _primitive.phase func_name arg_name archive.empty outputC)) _structure.check_succeeds) (|> (//type.with_type (All [a] (-> a a)) - (/.function _primitive.phase func_name arg_name archive.empty g!arg)) + (/.function _primitive.phase func_name arg_name archive.empty g!arg)) _structure.check_succeeds))) (_.test "Generic functions can always be specialized." (and (|> (//type.with_type (-> inputT outputT) - (/.function _primitive.phase func_name arg_name archive.empty outputC)) + (/.function _primitive.phase func_name arg_name archive.empty outputC)) _structure.check_succeeds) (|> (//type.with_type (-> inputT inputT) - (/.function _primitive.phase func_name arg_name archive.empty g!arg)) + (/.function _primitive.phase func_name arg_name archive.empty g!arg)) _structure.check_succeeds))) (_.test "The function's name is bound to the function's type." (|> (//type.with_type (Rec self (-> inputT self)) - (/.function _primitive.phase func_name arg_name archive.empty (code.local_identifier func_name))) + (/.function _primitive.phase func_name arg_name archive.empty (code.local_identifier func_name))) _structure.check_succeeds)) )))) @@ -89,15 +89,15 @@ inputsC (list\map product.right inputsTC)] [outputT outputC] _primitive.primitive .let [funcT (type.function inputsT outputT) - partialT (type.function (list.drop partial_args inputsT) outputT) + partialT (type.function (list.after partial_args inputsT) outputT) varT (#.Parameter 1) polyT (<| (type.univ_q 1) - (type.function (list.joined (list (list.take var_idx inputsT) + (type.function (list.joined (list (list.first var_idx inputsT) (list varT) - (list.drop (inc var_idx) inputsT)))) + (list.after (inc var_idx) inputsT)))) varT) poly_inputT (maybe.assume (list.item var_idx inputsT)) - partial_poly_inputsT (list.drop (inc var_idx) inputsT) + partial_poly_inputsT (list.after (inc var_idx) inputsT) partial_polyT1 (<| (type.function partial_poly_inputsT) poly_inputT) partial_polyT2 (<| (type.univ_q 1) @@ -110,16 +110,16 @@ (|> (/.apply _primitive.phase inputsC funcT dummy_function archive.empty (' [])) (check_apply outputT full_args))) (_.test "Can partially apply functions." - (|> (/.apply _primitive.phase (list.take partial_args inputsC) funcT dummy_function archive.empty (' [])) + (|> (/.apply _primitive.phase (list.first partial_args inputsC) funcT dummy_function archive.empty (' [])) (check_apply partialT partial_args))) (_.test "Can apply polymorphic functions." (|> (/.apply _primitive.phase inputsC polyT dummy_function archive.empty (' [])) (check_apply poly_inputT full_args))) (_.test "Polymorphic partial application propagates found type-vars." - (|> (/.apply _primitive.phase (list.take (inc var_idx) inputsC) polyT dummy_function archive.empty (' [])) + (|> (/.apply _primitive.phase (list.first (inc var_idx) inputsC) polyT dummy_function archive.empty (' [])) (check_apply partial_polyT1 (inc var_idx)))) (_.test "Polymorphic partial application preserves quantification for type-vars." - (|> (/.apply _primitive.phase (list.take var_idx inputsC) polyT dummy_function archive.empty (' [])) + (|> (/.apply _primitive.phase (list.first var_idx inputsC) polyT dummy_function archive.empty (' [])) (check_apply partial_polyT2 var_idx))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/structure.lux index 9aa837e50..bc4890efe 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -126,9 +126,9 @@ .let [variantT (type.variant (list\map product.left primitives)) [valueT valueC] (maybe.assume (list.item choice primitives)) +size (inc size) - +primitives (list.joined (list (list.take choice primitives) + +primitives (list.joined (list (list.first choice primitives) (list [(#.Parameter 1) +valueC]) - (list.drop choice primitives))) + (list.after choice primitives))) [+valueT +valueC] (maybe.assume (list.item +choice +primitives)) +variantT (type.variant (list\map product.left +primitives))]] (<| (_.context (%.name (name_of /.sum))) @@ -176,9 +176,9 @@ [_ +valueC] _primitive.primitive .let [tupleT (type.tuple (list\map product.left primitives)) [singletonT singletonC] (|> primitives (list.item choice) maybe.assume) - +primitives (list.joined (list (list.take choice primitives) + +primitives (list.joined (list (list.first choice primitives) (list [(#.Parameter 1) +valueC]) - (list.drop choice primitives))) + (list.after choice primitives))) +tupleT (type.tuple (list\map product.left +primitives))]] (<| (_.context (%.name (name_of /.product))) ($_ _.and @@ -243,9 +243,9 @@ [choiceT choiceC] (maybe.assume (list.item choice primitives)) [other_choiceT other_choiceC] (maybe.assume (list.item other_choice primitives)) monoT (type.variant primitivesT) - polyT (|> (type.variant (list.joined (list (list.take choice primitivesT) + polyT (|> (type.variant (list.joined (list (list.first choice primitivesT) (list varT) - (list.drop (inc choice) primitivesT)))) + (list.after (inc choice) primitivesT)))) (type.univ_q 1)) choice_tag (maybe.assume (list.item choice tags)) other_choice_tag (maybe.assume (list.item other_choice tags))]] @@ -288,9 +288,9 @@ primitivesC (list\map product.right primitives) monoT (#.Named [module_name type_name] (type.tuple primitivesT)) recordC (list.zipped/2 tagsC primitivesC) - polyT (|> (type.tuple (list.joined (list (list.take choice primitivesT) + polyT (|> (type.tuple (list.joined (list (list.first choice primitivesT) (list varT) - (list.drop (inc choice) primitivesT)))) + (list.after (inc choice) primitivesT)))) (type.univ_q 1) (#.Named [module_name type_name]))]] (<| (_.context (%.name (name_of /.record))) diff --git a/stdlib/source/test/lux/world/console.lux b/stdlib/source/test/lux/world/console.lux index 1198e56bb..5a8c28ad7 100644 --- a/stdlib/source/test/lux/world/console.lux +++ b/stdlib/source/test/lux/world/console.lux @@ -26,7 +26,7 @@ (def: (on_read [dead? content]) (do try.monad [char (try.of_maybe (text.char 0 content)) - [_ content] (try.of_maybe (text.split 1 content))] + [_ content] (try.of_maybe (text.split_at 1 content))] (if dead? (exception.except ..dead []) (in [[dead? content] char])))) -- cgit v1.2.3