From 24ba990800665299b551e66d1bc3d89c96ff6c55 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Wed, 7 Oct 2020 20:53:30 -0400 Subject: Re-named "Cursor" type to "Location". --- stdlib/source/test/aedifex/parser.lux | 4 +- stdlib/source/test/lux/control/parser/binary.lux | 14 +-- stdlib/source/test/lux/data/lazy.lux | 50 ++++++----- stdlib/source/test/lux/data/maybe.lux | 99 ++++++++++++---------- stdlib/source/test/lux/macro/code.lux | 6 +- stdlib/source/test/lux/meta.lux | 30 +++---- .../test/lux/tool/compiler/language/lux/syntax.lux | 12 +-- 7 files changed, 112 insertions(+), 103 deletions(-) (limited to 'stdlib/source/test') diff --git a/stdlib/source/test/aedifex/parser.lux b/stdlib/source/test/aedifex/parser.lux index 497533fbf..97895a201 100644 --- a/stdlib/source/test/aedifex/parser.lux +++ b/stdlib/source/test/aedifex/parser.lux @@ -205,7 +205,9 @@ (def: #export test Test (<| (_.covering /._) - (_.with-cover [/.project] + (_.covering //format._) + (_.with-cover [/.project + //format.Format //format.profile //format.project] ($_ _.and ..single-profile ..multiple-profiles diff --git a/stdlib/source/test/lux/control/parser/binary.lux b/stdlib/source/test/lux/control/parser/binary.lux index 8bc24976e..11875d19f 100644 --- a/stdlib/source/test/lux/control/parser/binary.lux +++ b/stdlib/source/test/lux/control/parser/binary.lux @@ -69,8 +69,8 @@ (Random Name) (random.and ..random-text ..random-text)) -(structure: cursor-equivalence - (Equivalence Cursor) +(structure: location-equivalence + (Equivalence Location) (def: (= [expected-module expected-line expected-column] [sample-module sample-line sample-column]) @@ -78,8 +78,8 @@ (n.= expected-line sample-line) (n.= expected-column sample-column)))) -(def: random-cursor - (Random Cursor) +(def: random-location + (Random Location) ($_ random.and ..random-text random.nat @@ -93,8 +93,8 @@ [size (:: @ map (n.% 2) random.nat)] (random.list size recur))] ($_ random.and - ..random-cursor - (: (Random (Code' (Ann Cursor))) + ..random-location + (: (Random (Code' (Ann Location))) ($_ random.or random.bit random.nat @@ -240,7 +240,7 @@ (!expect (^multi (#try.Success actual) (:: = expected actual))))))] - [/.cursor format.cursor random-cursor cursor-equivalence] + [/.location format.location random-location location-equivalence] [/.code format.code random-code code.equivalence] [/.type format.type random-type type.equivalence] )) diff --git a/stdlib/source/test/lux/data/lazy.lux b/stdlib/source/test/lux/data/lazy.lux index b31953a9f..440aa0316 100644 --- a/stdlib/source/test/lux/data/lazy.lux +++ b/stdlib/source/test/lux/data/lazy.lux @@ -10,11 +10,10 @@ ["$." monad] ["$." equivalence]]}] [data - ["%" text/format (#+ format)] [number ["n" nat]]] [math - ["r" random (#+ Random)]]] + ["." random (#+ Random)]]] {1 ["." / (#+ Lazy)]}) @@ -29,28 +28,35 @@ (def: #export lazy (All [a] (-> (Random a) (Random (Lazy a)))) - (:: r.functor map (|>> /.freeze))) + (:: random.functor map (|>> /.freeze))) (def: #export test Test - (<| (_.context (%.name (name-of /.Lazy))) - (do r.monad - [left r.nat - right r.nat - #let [lazy (/.freeze (n.* left right)) - expected (n.* left right)]] - ($_ _.and - ($equivalence.spec (/.equivalence n.equivalence) (..lazy r.nat)) - ($functor.spec ..injection ..comparison /.functor) - ($apply.spec ..injection ..comparison /.apply) - ($monad.spec ..injection ..comparison /.monad) + (<| (_.covering /._) + (do random.monad + [left random.nat + right random.nat + #let [expected (n.* left right)]] + (_.with-cover [/.Lazy] + ($_ _.and + (_.with-cover [/.equivalence] + ($equivalence.spec (/.equivalence n.equivalence) (..lazy random.nat))) + (_.with-cover [/.functor] + ($functor.spec ..injection ..comparison /.functor)) + (_.with-cover [/.apply] + ($apply.spec ..injection ..comparison /.apply)) + (_.with-cover [/.monad] + ($monad.spec ..injection ..comparison /.monad)) - (_.test "Freezing does not alter the expected value." - (n.= expected - (/.thaw lazy))) - (_.test "Lazy values only evaluate once." - (and (not (is? expected - (/.thaw lazy))) - (is? (/.thaw lazy) + (_.cover [/.freeze] + (let [lazy (/.freeze (n.* left right))] + (n.= expected (/.thaw lazy)))) - )))) + + (_.cover [/.thaw] + (let [lazy (/.freeze (n.* left right))] + (and (not (is? expected + (/.thaw lazy))) + (is? (/.thaw lazy) + (/.thaw lazy))))) + ))))) diff --git a/stdlib/source/test/lux/data/maybe.lux b/stdlib/source/test/lux/data/maybe.lux index a10e0154e..24114f6c0 100644 --- a/stdlib/source/test/lux/data/maybe.lux +++ b/stdlib/source/test/lux/data/maybe.lux @@ -6,6 +6,7 @@ {[0 #spec] [/ ["$." equivalence] + ["$." monoid] ["$." functor] ["$." apply] ["$." monad]]}] @@ -13,58 +14,64 @@ ["." io ("#@." monad)] pipe] [data - ["." text - ["%" format (#+ format)]] + ["." text] [number - ["n" nat]]] + ["n" nat]] + [collection + ["." list]]] [math - ["r" random (#+ Random)]]] + ["." random (#+ Random)]]] {1 ["." / ("#@." monoid monad)]}) -(def: #export maybe - (All [a] (-> (Random a) (Random (Maybe a)))) - (:: r.functor map (|>> #.Some))) - (def: #export test Test - (<| (_.context (%.name (name-of .Maybe))) - ($_ _.and - ($equivalence.spec (/.equivalence n.equivalence) (..maybe r.nat)) - ($functor.spec /@wrap /.equivalence /.functor) - ($apply.spec /@wrap /.equivalence /.apply) - ($monad.spec /@wrap /.equivalence /.monad) - - (do r.monad - [left r.nat - right r.nat - #let [expected (n.+ left right)]] - (let [lift (/.lift io.monad)] - (_.test "Can add maybe functionality to any monad." - (|> (io.run (do (/.with io.monad) - [a (lift (io@wrap left)) - b (wrap right)] - (wrap (n.+ a b)))) - (case> (#.Some actual) - (n.= expected actual) + (<| (_.covering /._) + (_.with-cover [.Maybe] + ($_ _.and + (_.with-cover [/.equivalence] + ($equivalence.spec (/.equivalence n.equivalence) (random.maybe random.nat))) + (_.with-cover [/.monoid] + ($monoid.spec (/.equivalence n.equivalence) /.monoid (random.maybe random.nat))) + (_.with-cover [/.functor] + ($functor.spec /@wrap /.equivalence /.functor)) + (_.with-cover [/.apply] + ($apply.spec /@wrap /.equivalence /.apply)) + (_.with-cover [/.monad] + ($monad.spec /@wrap /.equivalence /.monad)) + + (do random.monad + [left random.nat + right random.nat + #let [expected (n.+ left right)]] + (let [lift (/.lift io.monad)] + (_.cover [/.with /.lift] + (|> (io.run (do (/.with io.monad) + [a (lift (io@wrap left)) + b (wrap right)] + (wrap (n.+ a b)))) + (case> (#.Some actual) + (n.= expected actual) - _ - false))))) - (let [(^open "/@.") (/.equivalence text.equivalence) - (^open "/@.") /.monoid] - (_.test "Monoid respects Maybe." - (and (/@= #.None /@identity) - (/@= (#.Some "yolo") (/@compose (#.Some "yolo") (#.Some "lol"))) - (/@= (#.Some "yolo") (/@compose (#.Some "yolo") #.None)) - (/@= (#.Some "lol") (/@compose #.None (#.Some "lol"))) - (/@= #.None (: (Maybe Text) (/@compose #.None #.None)))))) - (do r.monad - [default r.nat - value r.nat] - (_.test "Can have defaults for Maybe values." - (and (is? default (/.default default - #.None)) + _ + false))))) + (do random.monad + [default random.nat + value random.nat] + (_.cover [/.default] + (and (is? default (/.default default + #.None)) - (is? value (/.default default - (#.Some value)))))) - ))) + (is? value (/.default default + (#.Some value)))))) + (do random.monad + [value random.nat] + (_.cover [/.assume] + (is? value (/.assume (#.Some value))))) + (do random.monad + [value random.nat] + (_.cover [/.to-list] + (:: (list.equivalence n.equivalence) = + (list value) + (/.to-list (#.Some value))))) + )))) diff --git a/stdlib/source/test/lux/macro/code.lux b/stdlib/source/test/lux/macro/code.lux index 0cdbc9610..eec419644 100644 --- a/stdlib/source/test/lux/macro/code.lux +++ b/stdlib/source/test/lux/macro/code.lux @@ -69,7 +69,7 @@ syntax.no-aliases (text.size source-code)) start (: Source - [.dummy-cursor 0 source-code])] + [.dummy-location 0 source-code])] (case (parse start) (#.Left [end error]) (#try.Failure error) @@ -132,7 +132,7 @@ (#try.Failure error) false) (:: /.equivalence = - [.dummy-cursor ( expected)] + [.dummy-location ( expected)] ( expected)))))] [/.bit random.bit #.Bit] @@ -159,7 +159,7 @@ (#try.Failure error) false) (:: /.equivalence = - [.dummy-cursor ( ["" expected])] + [.dummy-location ( ["" expected])] ( expected))) ))] diff --git a/stdlib/source/test/lux/meta.lux b/stdlib/source/test/lux/meta.lux index ec400d5e3..1f5e2c5fa 100644 --- a/stdlib/source/test/lux/meta.lux +++ b/stdlib/source/test/lux/meta.lux @@ -46,8 +46,8 @@ #let [expected-lux {#.info {#.target target #.version version #.mode #.Build} - #.source [..dummy-cursor 0 source-code] - #.cursor ..dummy-cursor + #.source [.dummy-location 0 source-code] + #.location .dummy-location #.current-module (#.Some expected-current-module) #.modules (list) #.scopes (list) @@ -93,8 +93,8 @@ #let [expected-lux {#.info {#.target target #.version version #.mode #.Build} - #.source [..dummy-cursor 0 source-code] - #.cursor ..dummy-cursor + #.source [.dummy-location 0 source-code] + #.location .dummy-location #.current-module (#.Some expected-current-module) #.modules (list) #.scopes (list) @@ -167,8 +167,8 @@ #let [expected-lux {#.info {#.target target #.version version #.mode #.Build} - #.source [..dummy-cursor 0 source-code] - #.cursor ..dummy-cursor + #.source [.dummy-location 0 source-code] + #.location .dummy-location #.current-module (#.Some expected-current-module) #.modules (list) #.scopes (list) @@ -199,8 +199,8 @@ (is? expected-short actual-short))))))) ))) -(def: random-cursor - (Random Cursor) +(def: random-location + (Random Location) ($_ random.and (random.ascii/upper-alpha 1) random.nat @@ -241,12 +241,12 @@ dummy-module (random.filter (|>> (text@= expected-current-module) not) (random.ascii/upper-alpha 1)) expected-gensym (random.ascii/upper-alpha 1) - expected-cursor ..random-cursor + expected-location ..random-location #let [expected-lux {#.info {#.target target #.version version #.mode #.Build} - #.source [.dummy-cursor 0 source-code] - #.cursor expected-cursor + #.source [.dummy-location 0 source-code] + #.location expected-location #.current-module (#.Some expected-current-module) #.modules (list) #.scopes (list) @@ -285,11 +285,11 @@ (!expect (^multi (#try.Success actual-gensym) (and (text.contains? expected-gensym actual-gensym) (text.contains? (%.nat expected-seed) actual-gensym)))))) - (_.cover [/.cursor] - (|> /.cursor + (_.cover [/.location] + (|> /.location (/.run expected-lux) - (!expect (^multi (#try.Success actual-cursor) - (is? expected-cursor actual-cursor))))) + (!expect (^multi (#try.Success actual-location) + (is? expected-location actual-location))))) (_.cover [/.expected-type] (|> /.expected-type (/.run expected-lux) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux index 103dc069e..c6ac62bc5 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux @@ -22,12 +22,6 @@ {1 ["." /]}) -(def: default-cursor - Cursor - {#.module "" - #.line 0 - #.column 0}) - (def: name-part^ (Random Text) (do {@ r.monad} @@ -83,7 +77,7 @@ (_.test "Can parse Lux code." (case (let [source-code (%.code sample)] (/.parse "" (dictionary.new text.hash) (text.size source-code) - [default-cursor 0 source-code])) + [.dummy-location 0 source-code])) (#.Left error) false @@ -95,7 +89,7 @@ (let [source-code (format (%.code sample) " " (%.code other)) source-code//size (text.size source-code)] (case (/.parse "" (dictionary.new text.hash) source-code//size - [default-cursor 0 source-code]) + [.dummy-location 0 source-code]) (#.Left error) false @@ -133,7 +127,7 @@ (case (let [source-code (format comment (%.code sample)) source-code//size (text.size source-code)] (/.parse "" (dictionary.new text.hash) source-code//size - [default-cursor 0 source-code])) + [.dummy-location 0 source-code])) (#.Left error) false -- cgit v1.2.3