From f7097aee6854d255849c61b1f29fc62988a790da Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Thu, 1 Dec 2016 23:40:02 -0400 Subject: - Bug fixes, refactorings and minor expansions. - Added tests for lux/data/error/exception. - Update tests for lux/data/format/json. --- stdlib/test/test/lux/data/error/exception.lux | 50 ++++ stdlib/test/test/lux/data/format/json.lux | 402 +++++++------------------- stdlib/test/test/lux/data/struct/vector.lux | 19 +- stdlib/test/tests.lux | 4 +- 4 files changed, 166 insertions(+), 309 deletions(-) create mode 100644 stdlib/test/test/lux/data/error/exception.lux (limited to 'stdlib/test') diff --git a/stdlib/test/test/lux/data/error/exception.lux b/stdlib/test/test/lux/data/error/exception.lux new file mode 100644 index 000000000..16d09a626 --- /dev/null +++ b/stdlib/test/test/lux/data/error/exception.lux @@ -0,0 +1,50 @@ +## Copyright (c) Eduardo Julian. All rights reserved. +## This Source Code Form is subject to the terms of the Mozilla Public License, v. 2.0. +## If a copy of the MPL was not distributed with this file, +## You can obtain one at http://mozilla.org/MPL/2.0/. + +(;module: + lux + (lux (codata [io]) + (control monad) + (data (error ["&" exception #+ exception:]) + [text] + [number]) + (codata function) + (math ["R" random]) + pipe) + lux/test) + +(exception: Some-Exception) + +(exception: Another-Exception) + +(exception: Unknown-Exception) + +(test: "Exceptions" + [should-throw? R;bool + which? R;bool + should-catch? R;bool + default-val R;nat + some-val R;nat + another-val R;nat + otherwise-val R;nat + #let [this-ex (if should-catch? + (if which? + Some-Exception + Another-Exception) + Unknown-Exception) + this-val (if should-throw? + (if should-catch? + (if which? + some-val + another-val) + otherwise-val) + default-val)]] + (assert "Catch and otherwhise handlers can properly handle the flow of exception-handling." + (=+ this-val (|> (if should-throw? + (&;return default-val) + (&;throw this-ex "Uh-oh...")) + (&;catch Some-Exception (lambda [ex] some-val)) + (&;catch Another-Exception (lambda [ex] another-val)) + (&;otherwise (lambda [ex] otherwise-val)))))) diff --git a/stdlib/test/test/lux/data/format/json.lux b/stdlib/test/test/lux/data/format/json.lux index 78b0b1a76..d7c622bd5 100644 --- a/stdlib/test/test/lux/data/format/json.lux +++ b/stdlib/test/test/lux/data/format/json.lux @@ -6,309 +6,121 @@ (;module: lux (lux (codata [io]) - (control monad) + (control monad + codec + eq) (data [text "Text/" Monoid] text/format error - (format [json #* "JSON/" Eq Codec]) + [bool] + [char] + [maybe] + [number] + (format ["&" json]) (struct [vector #+ vector] - [dict])) + [dict] + [list])) [compiler #+ with-gensyms] + [macro] (macro [ast] [syntax #+ syntax:] [poly #+ derived:]) - [pipe] + (math ["R" random]) + pipe test) ) -## [Utils] -(syntax: (reads-to-itself expr) - (with-gensyms [g!json g!parsed g!message] - (wrap (list (` (: (Test Unit) - (let [(~ g!json) (~ expr)] - (case (|> (~ g!json) JSON/encode JSON/decode) - (#;Left (~ g!message)) - (fail (~ g!message)) - - (#;Right (~ g!parsed)) - (if (JSON/= (~ g!json) (~ g!parsed)) - (~ (' (:: Monad wrap []))) - (fail (format "Expression does not parse to itself: " (~ (ast;text (ast;ast-to-text expr))) - "\n\nWhich is: " (|> (~ g!json) JSON/encode) - "\n\nInstead, it parsed to: " (JSON/encode (~ g!parsed)))) - )))) - ))))) - -## [Tests] -## (derived: (Codec ;Bool)) -## (derived: (Codec ;Int)) -## (derived: (Codec ;Real)) -## (derived: (Codec ;Char)) -## (derived: (Codec ;Text)) - -## (type: Int-List (List Int)) -## (derived: (Codec ;;Int-List)) - -## (type: Int-Maybe (Maybe Int)) -## (derived: (Codec ;;Int-Maybe)) - -## (type: Triple [Bool Int Text]) -## (derived: (Codec ;;Triple)) - -## (type: User -## {#alive? Bool -## #age Int -## #name Text}) -## (derived: (Codec ;;User)) - -## (type: Options -## (#One Bool) -## (#Two Int) -## (#Three Text)) -## (derived: (Codec ;;Options)) - -## (test: "Auto-generated codecs" -## (let% [ (do-template [ ] -## [(match -## (|> -## (:: encode) -## JSON/encode)) -## (match+ -## (should-pass (|> (JSON/decode ) -## (pipe;%> Error/Monad -## [(:: decode)]))))] - -## [true "true" Codec] -## [123 "123.0" Codec] -## [123.45 "123.45" Codec] -## [#"a" "\"a\"" Codec] -## ["yolo" "\"yolo\"" Codec] - -## [(#;Cons 1 (#;Cons 2 (#;Cons 3 #;Nil))) "[1.0,2.0,3.0]" Codec] -## [#;Nil "[]" Codec] -## [(#;Some 1) "1.0" Codec] -## [#;None "null" Codec] -## [[false 456 "lol"] "[false,456.0,\"lol\"]" Codec] -## [{#alive? true #age 25 #name "Eduardo Julian"} -## "{\"alive?\":true,\"age\":25.0,\"name\":\"Eduardo Julian\"}" -## Codec] -## [(#One true) "[\"One\",true]" Codec] -## [(#Two 123) "[\"Two\",123.0]" Codec] -## [(#Three "yolo") "[\"Three\",\"yolo\"]" Codec] -## )] -## (test-all -## ))) - -(test: "Basics" - (test-all (match #json;Null - null) - - (match (#json;Boolean true) - (gen-boolean true)) - - (match (#json;Boolean false) - (gen-boolean false)) - - (match (#json;Number 123.45) - (gen-number 123.45)) - - (match (#json;String "YOLO") - (gen-string "YOLO")) - - ## (match (^ (#json;Array (list (#json;Boolean true) (#json;Number 123.45) (#json;String "YOLO")))) - ## (json [(gen-boolean true) (gen-number 123.45) (gen-string "YOLO")])) - - ## (match (^ (#json;Object (list ["yolo" (#json;Boolean true)] - ## ["lol" (#json;Number 123.45)]))) - ## (json {"yolo" (gen-boolean true) - ## "lol" (gen-number 123.45)})) - - (match (#;Some (#json;Boolean true)) - (get "yolo" (json {"yolo" true - "lol" 123.45}))) - - (match (#;Left _) - (get "yolo" (json {}))) - - ## (match (^ (#;Some (#json;Object (list ["lol" (#json;Number 123.45)] - ## ["yolo" (#json;Boolean true)])))) - ## (|> (json {"yolo" (gen-boolean true)}) - ## (set "lol" (gen-number 123.45)))) - - (match (#;Right true) - (get-boolean "value" (json {"value" true}))) - - (match (#;Right 123.45) - (get-number "value" (json {"value" 123.45}))) - - (match (#;Right "YOLO") - (get-string "value" (json {"value" "YOLO"}))) - - ## (match (^ (#;Right (list (#json;Boolean true) (#json;Number 123.45) (#json;String "YOLO")))) - ## (get-array "value" (json {"value" (json [(gen-boolean true) - ## (gen-number 123.45) - ## (gen-string "YOLO")])}))) - - ## (match (^ (#;Right (list ["yolo" (#json;Boolean true)] - ## ["lol" (#json;Number 123.45)]))) - ## (get-object "value" (json {"value" (json {"yolo" (gen-boolean true) - ## "lol" (gen-number 123.45)})}))) - - (match (#;Left _) - (get-array "value" (json {}))) - - (match (#;Left _) - (get-array "value" (gen-boolean true))) - )) - -(test: "Encoding" - (test-all (match "null" - (JSON/encode (json #null))) - - (match "123.0" - (JSON/encode (json 123))) - - (match "123.46" - (JSON/encode (json 123.46))) - - (match "true" - (JSON/encode (json true))) - - (match "false" - (JSON/encode (json false))) - - (match "\"YOLO\"" - (JSON/encode (json "YOLO"))) - - (match "[null,123.46,true,\"YOLO\",[\"nyan\",\"cat\"]]" - (JSON/encode (json [#null 123.46 true "YOLO" ["nyan" "cat"]]))) - - (match "{\"foo\":\"bar\",\"baz\":null,\"quux\":[\"nyan\",{\"cat\":\"meme\"}]}" - (JSON/encode (json {"foo" "bar" - "baz" #null - "quux" ["nyan" {"cat" "meme"}]}))) - )) - -(test: "Decoding" - (test-all (reads-to-itself (json #null)) - (reads-to-itself (json 123)) - (reads-to-itself (json 123.46)) - (reads-to-itself (json true)) - (reads-to-itself (json false)) - (reads-to-itself (json "\tY\"OLO\n")) - (reads-to-itself (json [#null 123.46 true "YOLO" ["nyan" "cat"]])) - (reads-to-itself (json {"foo" "bar" - "baz" #null - "quux" ["nyan" {"cat" "meme"}]})) - )) - -(test: "Parser" - (test-all (should-pass (run unit - (json #null))) - (should-fail (run unit - (json 123))) - - (match+ 123.45 - (should-pass (run real - (json 123.45)))) - (should-fail (run real - (json #null))) - - (match+ 123 - (should-pass (run int - (json 123)))) - (should-fail (run int - (json #null))) - - (match+ true - (should-pass (run bool - (json true)))) - (should-fail (run bool - (json 123))) - - (match+ "YOLO" - (should-pass (run text - (json "YOLO")))) - (should-fail (run text - (json 123))) - - (match+ (^ (list "YOLO" "LOL" "MEME")) - (should-pass (run (array text) - (json ["YOLO" "LOL" "MEME"])))) - (should-fail (run (array text) - (json 123))) - - (match+ "LOL" - (should-pass (run (at +1 text) - (json ["YOLO" "LOL" "MEME"])))) - (should-fail (run (array text) - (json 123))) - - (match+ "MEME" - (should-pass (run (field "baz" text) - (json {"foo" "YOLO" - "bar" "LOL" - "baz" "MEME"})))) - (should-fail (run (field "baz" text) - (json 123))) - - (match+ (#json;Number 123.0) - (should-pass (run any - (json 123)))) - - (match+ ["YOLO" "MEME"] - (should-pass (run (seq (field "foo" text) - (field "baz" text)) - (json {"foo" "YOLO" - "bar" "LOL" - "baz" "MEME"})))) - (should-fail (run (seq (field "foo" text) - (field "baz" text)) - (json {"foo" "YOLO" - "bar" "LOL"}))) - - (match+ (#;Left "YOLO") - (should-pass (run (alt (field "foo" text) - (field "baz" text)) - (json {"foo" "YOLO" - "bar" "LOL" - "baz" "MEME"})))) - (match+ (#;Right "MEME") - (should-pass (run (alt (field "fool" text) - (field "baz" text)) - (json {"foo" "YOLO" - "bar" "LOL" - "baz" "MEME"})))) - (should-fail (run (alt (field "fool" text) - (field "baz" text)) - (json {"foo" "YOLO" - "bar" "LOL"}))) - - (match+ "YOLO" - (should-pass (run (either (field "foo" text) - (field "baz" text)) - (json {"foo" "YOLO" - "bar" "LOL" - "baz" "MEME"})))) - (match+ "MEME" - (should-pass (run (either (field "fool" text) - (field "baz" text)) - (json {"foo" "YOLO" - "bar" "LOL" - "baz" "MEME"})))) - (should-fail (run (either (field "fool" text) - (field "baz" text)) - (json {"foo" "YOLO" - "bar" "LOL"}))) - - (match+ (#;Some "YOLO") - (should-pass (run (opt (field "foo" text)) - (json {"foo" "YOLO" - "bar" "LOL" - "baz" "MEME"})))) - (match+ #;None - (should-pass (run (opt (field "fool" text)) - (json {"foo" "YOLO" - "bar" "LOL" - "baz" "MEME"})))) - )) +(def: gen-json + (R;Random &;JSON) + (R;rec (lambda [gen-json] + (do R;Monad + [size (:: @ map (%+ +2) R;nat)] + ($_ R;alt + (:: @ wrap []) + R;bool + R;real + (R;text size) + (R;vector size gen-json) + (R;dict text;Hash size (R;text size) gen-json) + ))))) + +(test: "JSON" + [sample gen-json + #let [(^open "&/") &;Eq + (^open "&/") &;Codec]] + ($_ seq + (assert "Every JSON is equal to itself." + (&/= sample sample)) + + (assert "Can encode/decode JSON." + (|> sample &/encode &/decode + (case> (#;Right result) + (&/= sample result) + + (#;Left _) + false))) + )) + +(type: Variant + (#Case0 Bool) + (#Case1 Int) + (#Case2 Real)) + +(type: Record + {#unit Unit + #bool Bool + #int Int + #real Real + #char Char + #text Text + #maybe (Maybe Int) + #list (List Int) + #variant Variant + #tuple [Int Real Char]}) + +(def: gen-record + (R;Random Record) + (do R;Monad + [size (:: @ map (%+ +2) R;nat)] + ($_ R;seq + (:: @ wrap []) + R;bool + R;int + R;real + R;char + (R;text size) + (R;maybe R;int) + (R;list size R;int) + ($_ R;alt R;bool R;int R;real) + ($_ R;seq R;int R;real R;char) + ))) + +(derived: (&;Codec Record)) + +(struct: _ (Eq Record) + (def: (= recL recR) + (and (:: bool;Eq = (get@ #bool recL) (get@ #bool recR)) + (;= (get@ #int recL) (get@ #int recR)) + (=. (get@ #real recL) (get@ #real recR)) + (:: char;Eq = (get@ #char recL) (get@ #char recR)) + (:: text;Eq = (get@ #text recL) (get@ #text recR)) + (:: (maybe;Eq number;Eq) = (get@ #maybe recL) (get@ #maybe recR)) + (:: (list;Eq number;Eq) = (get@ #list recL) (get@ #list recR)) + (let [[tL0 tL1 tL2] (get@ #tuple recL) + [tR0 tR1 tR2] (get@ #tuple recR)] + (and (;= tL0 tR0) + (=. tL1 tR1) + (:: char;Eq = tL2 tR2))) + ))) + +(test: "Polytypism" + [sample gen-record + #let [(^open "&/") Eq + (^open "&/") Codec]] + (assert "Can encode/decode arbitrary types." + (|> sample &/encode &/decode + (case> (#;Right result) + (&/= sample result) + + (#;Left _) + false)))) diff --git a/stdlib/test/test/lux/data/struct/vector.lux b/stdlib/test/test/lux/data/struct/vector.lux index 2ccfa2fc1..c3f3a706e 100644 --- a/stdlib/test/test/lux/data/struct/vector.lux +++ b/stdlib/test/test/lux/data/struct/vector.lux @@ -35,10 +35,8 @@ (=+ size (&;size sample)))) (assert "Can add and remove elements to vectors." - (and (=+ (inc+ size) - (&;size (&;add non-member sample))) - (=+ (dec+ size) - (&;size (&;pop sample))))) + (and (=+ (inc+ size) (&;size (&;add non-member sample))) + (=+ (dec+ size) (&;size (&;pop sample))))) (assert "Can put and get elements into vectors." (|> sample @@ -49,16 +47,12 @@ (assert "Can update elements of vectors." (|> sample - (&;put idx non-member) - (&;update idx inc+) - (&;at idx) - (default (undefined)) + (&;put idx non-member) (&;update idx inc+) + (&;at idx) (default (undefined)) (=+ (inc+ non-member)))) (assert "Can safely transform to/from lists." - (|> sample - &;to-list &;from-list - (&/= sample))) + (|> sample &;to-list &;from-list (&/= sample))) (assert "Can identify members of a vector." (and (not (&;member? number;Eq sample non-member)) @@ -76,8 +70,7 @@ (assert "Applicative allows you to create singleton vectors, and apply vectors of functions to vectors of values." (and (&/= (&;vector non-member) (&/wrap non-member)) - (&/= (&/map inc+ sample) - (&/apply (&/wrap inc+) sample)))) + (&/= (&/map inc+ sample) (&/apply (&/wrap inc+) sample)))) (assert "Vector concatenation is a monad." (&/= (&/append sample other-sample) diff --git a/stdlib/test/tests.lux b/stdlib/test/tests.lux index 7b760c0f1..94148e1d7 100644 --- a/stdlib/test/tests.lux +++ b/stdlib/test/tests.lux @@ -23,7 +23,8 @@ [product] [sum] [text] - [text/format] + (error [exception]) + (format [json]) (struct [array] [dict] [list] @@ -34,6 +35,7 @@ [vector] [zipper] ) + (text [format]) ) ## (codata ["_;" io] ## [env] -- cgit v1.2.3