Login
7 branches 0 tags
Ben (X13/Arch) Completely rewrote the bootstrap procedure 08d4954 4 years ago 158 Commits
nujel / stdlib / tests.nuj
[test-add 1073741824 [ash 1 30]]
[test-add 2147483647 [lognot [ash 1 31]]]
[test-add 1 1]
[test-add 3 [+ 1 2]]
[test-add -1 [+ 1 -2]]
[test-add 3 [- 4 1]]
[test-add 5 [- 4 -1]]
[test-add 8 [* 4 2]]
[test-add 16 [* 4 4]]
[test-add 2 [/ 4 2]]
[test-add 2 [do 2]]
[test-add 4 [/ 8 2]]
[test-add 1 [% 5 2]]
[test-add 0 [% 4 2]]
[test-add 3.1 [+ 1 2.1]]
[test-add 2.1 [* 1 2.1]]
[test-add 3 [int [vec/x [+ [vec 1.1 1.2 1.3] [vec 2 2 2]]]]]
[test-add 39 [+ 42 [- 3]]]
[test-add 24 [* 4 [- [+ 1 [+ 1 1]] [- 3 3 3]]]]
[test-add 3 [div 9 3]]
[test-add 3 [let [[vier -4]] [+ [% 9 4] [/ -9 vier]]]]
[test-add 69 [+ [* 2 [/ 32 8] [- 16 8]] 5]]
[test-add 3 [def eins 1] [def zwei 2] [+ eins zwei]]
[test-add -3 [def eins 1] [def zwei 2] [def drei [+ eins zwei]] [set! eins [- drei drei drei]]]
[test-add 128 [def zahl 1_2_8] zahl]
[test-add 10 [let [[a 10]] a]]
[test-add 20 [def b 20] [let [[a b]] a]]
[test-add 10 [def b 20] [let [[a b]] [set! a 10] a]]
[test-add 20 [def b 20] [let [[a b]] [set! a 10] b]]
[test-add 42 [let [[a 12] [b 30]] [+ a b]]]
[test-add 16 [def square [λ [a] [* a a]]] [square 4]]
[test-add 0 [- -1 -1]]
[test-add #t [or #f [and [> 5 1] [not [< 5 1]] [>= 5 5] [<= 5 5]]]]
[test-add #t [and [= #t #t] [= #f #f] [not [= #f #t]] [= 2 2]]]
[test-add 11 [length "Hallo, Welt"]]
[test-add #t [number? 0.1]]
[test-add #t [bool #t]]
[test-add #f [bool #nil]]
[test-add #f [bool #f]]
[test-add #t [bool 0]]
[test-add #t [bool 1]]
[test-add #t [bool 0.1]]
[test-add #t [bool ""]]
[test-add #t [bool "a"]]
[test-add 14 [def abs [λ [a] [if [neg? a] [- 0 a] a]]] [+ [abs -7] [abs 7]]]
[test-add #t [and [or #f #t] [and #t #t]]]
[test-add #t [and [neg? -1] [neg? -0.01] [pos? 0] [pos? 0.01] [not [neg? 0]] [not [pos? -0.01]] [not [neg? #f]]]]
[test-add #t [and [number? 1] [number? -1] [number? 0] [number? 0.1]]]
[test-add #t [and [number? [vec 1]] [not [number? #f]] [not [number? "123"]]]]
[test-add #t [and [number? 1] [number? -1] [number? 0] [number? 0.1] [number? [vec 1]] [not [number? #f]] [not [number? "123"]]]]
[test-add 12340 [- [int [cat 12 "3" "45 Test"]] 5]]
[test-add 12340 [let [[a [cat 12 "3" 45]]] [- [int a] [length a]]]]
[test-add 123 [int [cat "123" "abc" 456]]]
[test-add 28 [+ [int 10] [int 10.23] [int "8"]]]
[test-add #t [and [not [< 3 2]] [zero? 0] [> 3.1 2.1] [> 3 2] [>= 4 "3"] [>= 3 3] [<= 3 3] [not [>= "2" 3]]]]
[test-add 1 [int [float [+ [vec 1] [vec 0 9 9]]]]]
[test-add 0 [- #nil]]
[test-add #t [and [pair? [cons 1 '[2]]] [not [pair? 1]]]]
[test-add 1 [car [cons 1 '[2]]]]
[test-add 2 [+ [cadr '[1 2]] [cadr #nil] [cadr '[1]]]]
[test-add #t [string? [describe "++"]]]
[test-add 3 [++ [-- [length '[1 2 3]]]]]
[test-add #t [and [for-all? '[1 2 3] int?] [not [for-all? '[1 2 3.0] int?]]]]
[test-add #t [and [there-exists? '[1.0 2 3.0] int?] [not [there-exists? '[1.0 2.0 3.0] int?]]]]
[test-add #t [and [eq? "asd" "asd"] [not [eq? "asd" "bsd"]] [not [eq? "asd" "asdasd"]]]]
[test-add 23 [+ [reduce + [make-list 10 2] 0] [list-ref '[1 2 3 4] 1] [list-ref '[1 2] 0] [list-ref '[1 2] 3]]]
[test-add #t [and [nil? #nil] [not [nil? "NotNil"] [inf? #inf] [not [inf? "NotInf"] [vec? [vec 1]] [not [inf? "NotVec"]]]]]]
[test-add 11 [def count [let [[a 0]] [λ [b] [set! a [+ a [cond [[number? b] b] [#t 1]]]]]]] [count 10] [count]]
[test-add 4 [let [[a 10]] [when [when #t [set! a [+ 2 "2"]] #f] [set! a -1]] a]]
[test-add 6 [eval '[+ 1 2 3]]]
[test-add 4 [arr-length #[1 2 3 4]]]
[test-add 2 [arr-ref #[1 2 3 4] 1]]
[test-add 3 [arr-length [arr-new 3]]]
[test-add #t [arr? #[1 2 3]]]
[test-add #t [arr? [arr-new 3]]]
[test-add #f [arr? '[1 2 3]]]
[test-add #f [arr? @[:a 1 :b 2 :c 3]]]
[test-add 10 [+ [apply + '[1 2 3]] [apply ++ '[3]]]]
[test-add 0 [apply +]]
[test-add 0 [def cb '+] [apply cb]]
[test-add 1 [apply ++]]
[test-add 1 [def cb '++] [apply cb]]
[test-add 1 [let [[cb '++]] [apply cb]]]
[test-add 1 [let* [def cb '++] [apply cb]]]
[test-add 5 [length "12345"]]
[test-add #f [or 0 0]]
[test-add 2  [and 1 2]]
[test-add #t [bool [and 1 1]]]
[test-add #t [bool 1]]
[test-add 6 [[λ [a] [+ a 4]] 2]]
[test-add 2 [def test 1] [def test 2] test]
[test-add 0 [max]]
[test-add 0 [min]]
[test-add 1 [max 1]]
[test-add 4 [min 4]]
[test-add 4 [min 4 9]]
[test-add 9 [max 4 9]]
[test-add 25 [max 1 4.0 9 25]]
[test-add 25 [max 25 4.0 9 1]]
[test-add 1 [min 1 4.0 9 25]]
[test-add 1 [min 25 4.0 9 1]]
[test-add #t [even? 2]]
[test-add #f [even? 9]]
[test-add #t [odd? 7]]
[test-add #f [odd? 4]]
[test-add 256 [int [pow 2 8]]]
[test-add 3 [def ein-test-arr #[1 2 3]] [ein-test-arr 2]]
[test-add 3 [def ein-test-arr #[1 2 3]] [ein-test-arr 2 9] [ein-test-arr 2]]
[test-add 123 [def i-assaultmegablaster 123] i-assaultmegablaster]
[test-add #t [int? [random]]]
[test-add #t [random/seed! 123] [def first-value [random]] [random/seed! 123] [eq? first-value [random]]]
[test-add #t [random/seed! 123] [!= [random] [random]]]
[test-add 1 [def a 1] [unless [= 2 2] [set! a 4]] a]
[test-add 4 [def a 1] [unless [= 2 3] [set! a 4]] a]
[test-add 4 [def a 1] [when   [= 2 2] [set! a 4]] a]
[test-add 1 [def a 1] [when   [= 2 3] [set! a 4]] a]
[test-add 3 [def ein-test-arr #[1 2 3]] [ein-test-arr 2.2]]
[test-add 123 #d123]
[test-add 6 #b0110]
[test-add 10 #b1010]
[test-add 15 #b11_11]
[test-add 7 #b01,11]
[test-add 192 #b1100_0000]
[test-add 255 #xFF]
[test-add 255 #xFf]
[test-add 160 #xa0]
[test-add 31 #x1_F]
[test-add 30 #x1,E]
[test-add 50 #x32]
[test-add 256 #x100]
[test-add 0 #o]
[test-add 7 #o7]
[test-add 10 #o12]
[test-add 26 #o32]
[test-add -1 #b11111111_11111111_11111111_11111111]
[test-add -1 #xFFFFFFFF]
[test-add 2 [- [+ 1 #b10] 1]]
[test-add 8 [- [+ 1 #o10] 1]]
[test-add 16 [- [+ 1 #x10] 1]]
[test-add 32 [+ #x10#x10]]
[test-add 16 [+ #x10#f]]
[test-add 32 [+ #x10"16"]]
[test-add 32 [+ #x10[+ 0#x10]]]
[test-add 0 [logand #xf0 #x0F]]
[test-add 255 [logior #xf0 #x0F]]
[test-add 255 [logior #xfF #xFF]]
[test-add 255 [logxor #xf0 #x0F]]
[test-add 240 [logxor #xff #x0F]]
[test-add -1 [lognot 0]]
[test-add 0 [lognot -1]]
[test-add 16 [ash 1 4]]
[test-add 65536 [ash 1 16]]
[test-add -1 [ash -1 -1]]
[test-add -16 [lognand #b1111 #b1111]]
[test-add 6 [eval [read "[+ 1 2 3]"]]]
[test-add '[3] [let [[test-string "3"]] [read test-string] [read test-string]]]
[test-add "[vec 1.0 2.0 3.0]" [abs [vec -1 -2 -3]]]
[test-add "3.33333" [+ 1.11111 2.22222]]
[test-add "\"H#Hallo\"" [let [[a "Hallo, Welt#"]] [cat [substr a 0 1] [substr a -1] [substr a 0 -7]]]]
[test-add "\"Test\"" [def a "Test"] a]
[test-add "11.6" [+ [+ 1.1 2.2] [+ 1.1 3] [+ 1 3.2]]]
[test-add "20.1" [+ [+ 1.1 3] [+ 1 3.3] [+ 3.3 4.1 4.3]]]
[test-add "15.54" [add [mul 3.2 3.2] [sub 5.5 1.1 1 1.1] [div 9.9 3.3]]]
[test-add "0.7" [% 10 3.1]]
[test-add #t [eq? #inf #inf]]
[test-add "11.7" [add [+ 1.1 2.2] [+ 1.1 3] [+ 1 3.3]]]
[test-add "11.75" [+ [float 10] [int "10"] [float "-8.25"]]]
[test-add "30.3" [+ [abs "-10"] [int 8.2] 12.3]]
[test-add "[vec 12.0 12.0 12.0]" [+ [vec 1] 1 10]]
[test-add "[vec 3.0 5.0 6.0]" [+ [vec 1] [vec 1 2] [vec 1 2 3]]]
[test-add "[vec 3.0 3.0 3.0]" [+ 1 [vec 1] 1.0]]
[test-add "[vec 3.0 3.0 3.0]" [+ 1.0 [vec 1] "1"]]
[test-add "[vec -1.0 -1.0 -1.0]" [- [vec 1] [vec 1.0] [vec "1"]]]
[test-add "2.7" [+ [- 1 -1.0] [- 5 1.1 1] [- 1 1.1 1] [- 1 1.1 [int "1"]]]]
[test-add "[vec 3.0 3.0 3.0]" [+ 1 [vec 1] 1.0]]
[test-add "[vec -1.0 -1.0 -1.0]" [- 1 [vec 1] 1.0]]
[test-add "[vec 8.0 8.0 8.0]" [* [vec 2] "4"]]
[test-add "[vec 1.0 1.0 1.0]" [mod [vec 9] 2]]
[test-add "1.0" [float [int [+ [vec 1] [vec 0 9 9]]]]]
[test-add '[] [cons]]
[test-add "[]" [cons]]
[test-add '[1] [cons 1]]
[test-add "[1]" [cons 1]]
[test-add 1 [car [cons 1 2]]]
[test-add 2 [cdr [cons 1 2]]]
[test-add "[1 . 2]" [cons 1 2]]
[test-add "[1 2]" [cons 1 '[2]]]
[test-add "[4 3 2 1]" [reverse '[1 2 3 4]]]
[test-add "[1 2.0 3 1 2.0 3]" [append '[1 2.0 3] '[1 2.0 3]]]
[test-add "[1 4]" [filter int?   '[1 2.0 #t 4]]]
[test-add "[2.0]" [filter float? '[1 2.0 #t 4]]]
[test-add "[2.0]" [filter float? '[1 2.0 #t 4]]]
[test-add "[#t]"  [filter bool?  '[1 2.0 #t 4]]]
[test-add "[2 3]" [sublist '[1 2 3 4 5 6] 1 3]]
[test-add "[1 2 3]" [list-head '[1 2 3 4 5 6] 3]]
[test-add "[4 5 6]" [list-tail [list 1 2 3 4 5 6] 3]]
[test-add "[3]" [last-pair [list 1 2 3]]]
[test-add "[1 2]" [except-last-pair '[1 2 3]]]
[test-add "[1.0 #t \"a\"]" [let [[l '[1.0 #t "a"]]] [append [except-last-pair l] [last-pair l]]]]
[test-add "[\"asd\" #t #f]" [member "asd" '[123 456 "asd" #t #f]]]
[test-add "[[vec 4.0 4.0 4.0] 9 16.0]" [map [λ [a] [* a a]] [cons [vec 2] '[3 4.0]]]]
[test-add "\"11.0\"" [cat 1 1.0]]
[test-add "[vec 9.0 9.0 9.0]" [div [vec 99] [cat 1 1.0]]]
[test-add "#[99 12 3 4]" [let [[cur-arr #[1 2 3 4]]] [arr-set! cur-arr 0 99 12] cur-arr]]
[test-add "#[42 42 42 42 42 42]" [arr-fill! [arr-new 6] 42]]
[test-add "#nil" [apply #nil]]
[test-add "[vec 1.0 3.0 9.0]" [def vs [λ [a] [vec [vec/z a] [vec/y a] [vec/x a]]]] [vs [vec 9 3.0 "1"]]]
[test-add "3" [def fib [λ [a] [cond [[zero? a] 0] [[= a 1] 1] [#t [+ [fib [- a 1]] [fib [- a 2]]]]]]] [fib 4]]
[test-add "21" [def fib [λ [a] [cond [[zero? a] 0] [[= a 1] 1] [#t [+ [fib [- a 1]] [fib [- a 2]]]]]]] [fib 8]]
[test-add "102334155" [def fib-iter [λ [a b count] [cond [[= count 0] b] [#t [fib-iter [+ a b] a [- count 1]]]]]] [def fib [λ [n] [fib-iter 1 0 n]]] [fib 40]]
[test-add 87654321 [let [[ret ""]] [[λ [a] [cond [[zero? a] [int ret]] [#t [set! ret [cat ret a]] [[cl-lambda 1] [-- a]]]]] 8]]]
[test-add "\"ASD123\"" [uppercase "asD123"]]
[test-add "\"asd123\"" [lowercase "aSD123"]]
[test-add "\"Asd123\"" [capitalize "aSD123"]]
[test-add "[vec 1.0 1.0 1.0]" [floor [vec 1.3 1.3 1.3]]]
[test-add "2.0" [ceil 1.3]]
[test-add "[vec 2.0 2.0 2.0]" [ceil [vec 1.3 1.3 1.3]]]
[test-add "1.0" [round 1.3]]
[test-add "2.0" [round 1.51]]
[test-add "3.0" [sqrt 9]]
[test-add "[vec 5.0 5.0 5.0]" [sqrt [vec 25 25 25]]]
[test-add "256.0" [pow 2.0 8]]
[test-add "[vec 4.0 8.0 16.0]" [pow 2.0 [vec 2.0 3.0 4.0]]]
[test-add "\"123\"" [string 123]]
[test-add "\"#t\"" [string #t]]
[test-add "#nil" testerle]
[test-add ":testerle" :testerle]
[test-add :testerle :testerle]
[test-add '[:asd qwerty] [:asd qwerty]]
[test-add :asd [do [def :asd #t] :asd]]
[test-add "[1 . 2]" [def test [cons 1 2]] test]
[test-add "\"Eins\"" [def eins [ω [def say [λ [] "Eins"]]]] [eins [say]]]
[test-add "\"Zwei\"" [def eins [ω [def say [λ [] "Zwei"]]]] [def zwei [eins [ω]]] [zwei [say]]]
[test-add "\"Polizei\"" [def eins [ω [def say [λ [] "Eins"]]]] [def zwei [eins [ω]]] [zwei [def say [λ [] "Polizei"]]] [zwei [say]]]
[test-add "\"asd\"" ["a" "s" "d"]]
[test-add "\"a\"" ["a"]]
[test-add "#nil" [def testerle #[1 2 3]] [testerle 4]]
[test-add "#nil" [def testerle #[1 2 3]] [testerle 40000]]
[test-add "#[1 2 3]" [def testerle #[1 2 3]] [testerle]]
[test-add "#nil" [def testerle #[1 2 3]] [testerle #t]]
[test-add "#nil" [def testerle #[1 2 3]] [testerle [vec 1 2 3]]]
[test-add "\"Trim Test\"" [trim "   Trim Test    \n"]]
[test-add "\"1,asd,3.0,#f\"" [join '[1 "asd" 3.0 #f] ","]]
[test-add "[1.0 2.0 3.0]" [map float [split "1,2,3" ","]]]
[test-add "[\"dies ist\" \"ein\" \"test\"]" [split "dies ist/ein/test" "/"]]
[test-add 1 [index-of "1,2,3" ","]]
[test-add #x123 [car [read [join [cons "#x" [split "123" ""]]]]]]
[test-add 7 [char-at "\a" 0]]
[test-add 5 [char-at [from-char-code 5 10 20] 0]]
[test-add 2600 [int [from-char-code [char-at "2" 0] #\6 48 48]]]
[test-add #t [eq? 32 #\ ]]
[test-add #t [eq? #\Backspace 8]]
[test-add #t [eq? #\Tab [char-at "\t" 0]]]
[test-add #t [and [eq? #\cr 13] [eq? #\Return 13]]]
[test-add #t [and [eq? #\lf 10] [eq? 10 #\Linefeed]]]
[test-add #x07 [char-at "\a" 0]]
[test-add #x08 [char-at "\b" 0]]
[test-add #x1B [char-at "\e" 0]]
[test-add #x0c [char-at "\f" 0]]
[test-add #\lf [char-at "\n" 0]]
[test-add #\cr [char-at "\r" 0]]
[test-add #x09 [char-at "\t" 0]]
[test-add #x0B [char-at "\v" 0]]
[test-add #x27 [char-at "\'" 0]]
[test-add #x22 [char-at "\"" 0]]
[test-add #t [> [symbol-count] 200]] ; Probably not gonna shrink over time
[test-add #t [equal? + add]]
[test-add #t [eq? min min]]
[test-add #t [let [[some-value #f]] [not some-value]]]
[test-add 4 [>> 8 1]]
[test-add 15 [1 + 2 * [3 + 4]]]
[test-add 9 [10 - 1]]
[test-add 5 [10 / 2]]
[test-add 256 [1 << 8]]
[test-add #t [eq? :asd :asd]]
[test-add #t [eq? :bool [type-of #f]]]
[test-add #t [eq? :int [type-of 123]]]
[test-add #f [eq? :int [type-of 123.123]]]
[test-add #t [eq? :float [type-of 123.123]]]
[test-add #t [eq? :vec [type-of [vec 1]]]]
[test-add #t [eq? :native-function [type-of +]]]
[test-add #t [eq? :lambda [type-of test-add]]]
[test-add #t [eq? :string [type-of "asd"]]]
[test-add 2 [getf [list :a 1 :b 2 :c 3] :b]]
[test-add "#nil" [getf [list :a 1 :b 2 :c 3] :d]]
[test-add "\"\\n\"" "\n"]
[test-add "\"\\n\"" [br]]
[test-add "\"\\n\\n\\n\"" [br 3]]
[test-add :dies-ist-ein-test-ob-lange-symbole-funktionieren :dies-ist-ein-test-ob-lange-symbole-funktionieren]
[test-add #t [eq? [+ 2 2] [2 + 2]]]
[test-add #t [eq? 4 [2 + 2]]]
[test-add #t [eq? 4 [+ 2 2]]]
[test-add :int [type-of [+ 2 2]]]
[test-add :int [type-of [2 + 2]]]
[test-add :float [type-of [+ 2.0 2.1]]]
[test-add :float [type-of [2.0 + 2.1]]]
[test-add :float [type-of [+ 2 2.1]]]
[test-add :float [type-of [2 + 2.1]]]
[test-add -1 [-1]]
[test-add -1 [- 1]]
[test-add -1 [let [[a 1]] [- a]]]
[test-add -1 [let [[a 1]] [-a]]]
[test-add -1 [let [[a 1]] -a]]
[test-add  0 [wrap-value 0 0 2]]
[test-add  1 [wrap-value 1 0 2]]
[test-add  0 [wrap-value 2 0 2]]
[test-add  1 [wrap-value 3 0 2]]
[test-add  0 [wrap-value 4 0 2]]
[test-add #t [zn? 0]]
[test-add #t [zn? -4.0]]
[test-add #f [zn? 0.1]]
[test-add  0 [let [[tmp [vec 0 0 0]]] [+ tmp [vec 1 1 1]] [vec/y tmp]]]
[test-add  0 [let [[tmp 0]] [+ tmp 1] tmp]]
[test-add #t [list-equal? '[] '[]]]
[test-add #f [list-equal? '[] '[1]]]
[test-add #f [list-equal? '[1] '[]]]
[test-add #t [list-equal? '[1 "asd"] '[1 "asd"]]]
[test-add #f [list-equal? '[1 "asd"] '[1 "as"]]]
[test-add #f [list-equal? '[1 :asd] '[1 :as]]]
[test-add #t [list-equal? '[1 :asd] '[1 :asd]]]
[test-add #t [list-equal? '[1 asd] '[1 asd]]]
[test-add #t [list-equal? '[1 #f] '[1 #f]]]
[test-add #f [list-equal? '[1 #t] '[1 #f]]]
[test-add #t [list-equal? '[1 2 3] '[1 2 3]]]
[test-add #f [list-equal? '[1 2 3] '[1 2 4]]]
[test-add #f [list-equal? '[1 2 3] '[1 2]]]
[test-add #f [list-equal? '[1 2 3] '[1 2 [3 4]]]]
[test-add #t [list-equal? '[1 2 [3 4]] '[1 2 [3 4]]]]
[test-add #t [list-equal? '[1 2 [3 4]] '[1 2 [3 4]]]]
[test-add "do" 'do]
[test-add "[123]" '[123]]
[test-add "[123 #t]" '[123 #t]]
[test-add "[123 'do]" '[123 'do]]
[test-add "[123 \"asd\"]" '[123 "asd"]]
[test-add 2 [wrap-value 2 2 4]]
[test-add 3 [wrap-value 3 2 4]]
[test-add 2 [wrap-value 4 2 4]]
[test-add 3 [wrap-value 5 2 4]]
[test-add #t [1 < 10]]
[test-add #f [1 > 10]]
[test-add #t [1 <> 10]]
[test-add #f [1 <> 1]]
[test-add #t [1 != 10]]
[test-add #f [1 != 1]]
[test-add #f [1 = 10]]
[test-add #t [1 = 1]]
[test-add #t [1 >= 1]]
[test-add #t [1 <= 1]]
[test-add #t [1 <= 4]]
[test-add #t [4 >= 1]]
[test-add #f [and #nil #nil]]
[test-add #t [eq? #nil #nil]]
[test-add #t [eq? #t #t]]
[test-add #f [eq? #t #f]]
[test-add #t [eq? #f #f]]
[test-add #f [eq? '[] #f]]
[test-add #f [eq? #f '[]]]
[test-add #f [eq? '[] #t]]
[test-add #f [eq? #t '[]]]
[test-add #t [eq? '[] '[]]]
[test-add #f [eq? '[] '[1]]]
[test-add #f [eq? '[1] '[1]]]
[test-add #t [list-equal? '[1] '[1]]]
[test-add #f [eq? '[] #nil]]
[test-add #t [eq? λ [resolve [car '[λ asd]]]]]
[test-add 10,000 [let [] [def i 0] [while [< i 10,000] [set! i [++ i]]]]]
[test-add '[1 :a "q"] '[1 :a "q"]]
[test-add 4 [compile '[do "Test" 4]]]
[test-add '[do [display "Test"] 4] [compile '[do [display "Test"] 4]]]
[test-add '[do [display "Test"] 4] [compile '[do [display "Test"] 9 4]]]
[test-add '[λ* [v] "Add 1 to V" [+ 1 v]] [compile '[λ [v] "Add 1 to V" [+ 1 v]]]]
[test-add '[λ* [v] "" [+ 1 v]] [compile '[λ [v] [+ 1 v]]]]
[test-add '[λ* [v] "" [do [display v] [+ 1 v]]] [compile '[λ [v] [display v] [+ 1 v]]]]
[test-add '[1 2] [except-last-pair '[1 2 3]]]
[test-add '[3] [last-pair '[1 2 3]]]
[test-add '[1 3 5] [filter odd?  '[1 2 3 4 5 6]]]
[test-add '[2 4 6] [filter even? '[1 2 3 4 5 6]]]
[test-add '["vier"] [filter string? '[1 2 3 "vier" 5 6]]]
[test-add '[1 2 3 5 6] [filter int? '[1 2 3 "vier" 5 6]]]
[test-add '[2 3 4] [map [λ [v] [+ 1 v]] '[1 2 3]]]
[test-add '[2 4 6] [map [λ [v] [* 2 v]] '[1 2 3]]]
[test-add '["1" "2" "3"] [map str/write '[1 2 3]]]
[test-add "[123 #nil]" '[123 #nil]]
[test-add '[123 #nil] '[123 #nil]]
[test-add "@[:asd 123]" [tree/new :asd 123]]
[test-add "@[:asd 123]" @[:asd 123]]
[test-add #f [tree/has? @[:a 123] :b]]
[test-add #t [tree/has? @[:a 123] :a]]
[test-add 123 [tree/get @[:a 123] :a]]
[test-add 123 [tree/get @[:b 2 :a 123] :a]]
[test-add 9 [tree/get [tree/set! @[:b 2 :a 123] :a 9] :a]]
[test-add 2 [tree/get @[:b 2 :a 123] :b]]
[test-add #t [let* [def keys [tree/keys @[:b 2 :a 123]]] [or [list-equal? keys '[:b :a]] [list-equal? keys '[:a :b]]]]]
[test-add #t [let* [def vals [tree/values @[:b 2 :a 123]]] [or [list-equal? vals '[2 123]] [list-equal? vals '[123 2]]]]]
[test-add 2 [length [tree/keys @[:b 2 :a 123]]]]
[test-add 2 [length [tree/values @[:b 2 :a 123]]]]
[test-add 3 [length [tree/keys @[:b 2 :a 123 :c 7]]]]
[test-add '[:asd 123]   [car [read "{:asd 123}"]]]
[test-add '[123 [:asd]] [car [read "[123[:asd]]"]]]
[test-add '[123 [:asd]] [car [read "{123{:asd}}"]]]
[test-add '[123 [:asd]] [car [read "(123(:asd))"]]]
[test-add '[123 [:asd]] [car [read "(123{:asd})"]]]
[test-add '[:asd [123]] [car [read "(:asd[123])"]]]
[test-add #x123 [car '[#x123[#o234]]]]
[test-add '[#o234] [cadr '[#x123[#o234]]]]
[test-add #o234 [cadr '[#x123#o234]]]
[test-add #b101 [car '[#b101"asd"]]]
[test-add "\"asd\"" [cadr '[#b101"asd"]]]
[test-add #t [pair? [symbol-table]]]
[test-add #t [> [length [symbol-table]] 200]]
[test-add :one [car '[:one :two :three]]]
[test-add :two [cadr '[:one :two :three]]]
[test-add :three [caddr '[:one :two :three]]]
[test-add '[:two :three] [cdr '[:one :two :three]]]
[test-add '[:three] [cddr '[:one :two :three]]]
[test-add 'two [cadr '[:one two :three]]]
[test-add :value [car [memory-info]]]
[test-add #t [int? [cadr [memory-info]]]]
[test-add 102334155 [let* [def i 1] [def a 0] [def b 1] [while [< i 40] [let [[new [+ a b]]] [set! a b] [set! b new] [set! i [++ i] new]]] b]]
[test-add 832040 [let* [def i 1] [def a 0] [def b 1] [while [< i 30] [let [[new [+ a b]]] [set! a b] [set! b new] [set! i [++ i] new]]] b]]
[test-add 17711 [let* [def i 1] [def a 0] [def b 1] [while [< i 22] [let [[new [+ a b]]] [set! a b] [set! b new] [set! i [++ i] new]]] b]]
[test-add 6765  [let* [def fib-slow [λ [v] [if [< v 2] v [+ [fib-slow [- v 2]] [fib-slow [- v 1]]]]]] [fib-slow 20]]]
[test-add 10946 [let* [def fib-slow [λ [v] [if [< v 2] v [+ [fib-slow [- v 1]] [fib-slow [- v 2]]]]]] [fib-slow 21]]]
[test-add 4 [[λ [v] [+ v 2]] 2]]
[test-add 4 [[λ [λ] [+ λ 2]] 2]]
[test-add 4 [[λ [+ *] [- + *]] 6 2]]
[test-add 246 [let* [def - 123] [+ - -]]]
[test-add 'v [car '[v]]]
[test-add '+ [car '[+]]]
[test-add #t [eq? '+ [str->sym "+"]]]
[test-add 3 [[eval* [str->sym "+"]] 1 2]]
[test-add '-- [car '[--]]]
[test-add '- [car '[-]]]
[test-add -1 [let* [def + -] [+ 1 2]]]
[test-add #t [procedure? [let* [def t -] t]]]
[test-add #nil [when #f 1]]
[test-add 1 [when #t 1]]
[test-add "[]" '[]]
[test-add "[]" '[#nil]]
[test-add "[#nil #nil]" '[#nil #nil]]
[test-add "[and #nil #nil]" '[and #nil #nil]]
[test-add '[1 . 2] [cons 1 2]]
[test-add '[1 . 2] '[1 . 2]]
[test-add 1 [car '[1 . 2]]]
[test-add 2 [cdr '[1 . 2]]]
[test-add 1 [#[1 2 3] 0]]
[test-add 2 [@[:asd 1 :bsd 2] :bsd]]
[test-add 0 [+ #nil]]
[test-add 0 [- #nil]]
[test-add 0 [* #nil]]
[test-add 0 [/ #nil]]
[test-add :unresolved-procedure [try [λ [err] [if [eq? [caddr err] 'asdqwe] [car err] #nil]] [asdqwe qweasdzxc]]]
[test-add #t [try [λ [error] [string? [cadr error]]} [/ 3 0]]]
[test-add :success [try [λ [error] error] [throw :success] :failure]]
[test-add 123 [try [λ [error] error] [throw 123] 0]]
[test-add #t [try [λ [error] error] [throw #t] #f]]
[test-add "\"asd\"" [try [λ [error] error] [throw "asd"] #nil]]
[test-add :test-exception [try [λ [error] [car error]] [throw [list :test-exception "Testing the exception system"]] #nil]]
[test-add #t [try [λ [error] [string? [cadr error]]] [throw [list :test-exception "Testing the exception system"]] #nil]]
[test-add :division-by-zero [try [λ [err] [car err]] [try [λ [err] [/ 3 0] err] [throw :test-exception]]]]
[test-add :test [[λ [e] [car e]] [cons :test "Test"]]]
[test-add 10 #d10]
[test-add 10.1 #d10.1]
[test-add -10.1 #d-10.1]
[test-add -31 #x-1F]
[test-add -15 #o-17]
[test-add -3 #b-11]
[test-add :invalid-literal [try [λ [err] [car err]] [read "#b1111-0000"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "#x1-F"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "#o12378"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "#d1F"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "#qwe"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "\"\\z\""]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "123kg"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "123.123m"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "123.123.123"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "#xF.F"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "#o7.7"]]]
[test-add :invalid-literal [try [λ [err] [car err]] [read "#b1.1"]]]
[test-add :division-by-zero [try [λ [error] [car error]] [/ 3 0]]]
[test-add :division-by-zero [try [λ [error] [car error]] [try [λ [error] [/ 3 0] error] [throw :test-exception]]]]
[test-add :float-inf [try [λ [err] [car err]] [/  1.0 0.0]]]
[test-add :float-nan [try [λ [err] [car err]] [/  0.0 0.0]]]
[test-add :float-inf [try [λ [err] [car err]] [/ -1.0 0.0]]]
[test-add "\"0\""    [int->string 0]]
[test-add "\"123\""  [int->string 123]]
[test-add "\"999\""  [int->string/decimal 999]]
[test-add "\"0\""    [int->string/binary 0]]
[test-add "\"1100\"" [int->string/binary 12]]
[test-add "\"1010\"" [int->string/binary 10]]
[test-add "\"1001\"" [int->string/binary 9]]
[test-add "\"100000000\"" [int->string/binary 256]]
[test-add "\"0\""    [int->string/octal 0]]
[test-add "\"17\""   [int->string/octal 15]]
[test-add "\"36\""   [int->string/octal 30]]
[test-add "\"400\""  [int->string/octal 256]]
[test-add "\"1000\"" [int->string/hex 4096]]
[test-add "\"100\""  [int->string/hex 256]]
[test-add "\"FF\""   [int->string/hex 255]]
[test-add "\"1F\""   [int->string/hex 31]]
[test-add "\"0\""    [int->string/hex 0]]
[test-add "0.1"                     0.1]
[test-add "0.02"                   0.02]
[test-add "0.003"                 0.003]
[test-add "0.01234"             0.01234]
[test-add "0.1"         [car [read "0.1"]]]
[test-add "0.1001"   [car [read "0.1001"]]]
[test-add "0.913"     [car [read "0.913"]]]
[test-add "0.00012" [car [read "0.00012"]]]
[test-add 1 `1]
[test-add '[1] `[1]]
[test-add '[1 2] `[1 2]]
[test-add '[1 "asd"] `[1 "asd"]]
[test-add '[1 :asd] `[1 :asd]]
[test-add '[@[:asd 123]] `[@[:asd 123]]]
[test-add '[#[1 2 3]] `[#[1 2 3]]]
[test-add '[1.0001] `[1.0001]]
[test-add '[:asd] `[:asd]]
[test-add '[1 2 3] `[1 ,[1 + 1] 3]]
[test-add '[1 2 3 4] `[1 ,[1 + 1] ,@[read "3 4"]]]
[test-add '[1 2 3] `[1 ,@`[2 3]]]
[test-add '[1 [quasiquote [2 [unquote [3 4]]]]] `[1 `[2 ,[3 ,[+ 2 2]]]]]
[test-add '[quasiquote [quasiquote [1 2 [unquote [unquote 3]]]]] ```[1 2 ,,,[+ 2 1]]]
[test-add '[1 2 3] [let* [def v 2] `[1 ,v 3]]]
[test-add '[+ 1 2] [compile '[+1 2]]]
[test-add #t [macro? [μ [] #f]]]
[test-add #t [macro? +1]]
[test-add #f [macro? min]]
[test-add #f [macro? 123]]
[test-add 4 [let* [defun double [α] [* α 2]] [double 2]]]
[test-add #t [in-range? 3 1 5]]
[test-add #f [in-range? -3 1 5]]
[test-add #f [in-range? 9 1 5]]
[test-add #t [in-range? -3 -10 5]]
[test-add #t [in-range? -3 -10.0 5]]
[test-add #t [in-range? -3 -10.0 5.0]]
[test-add #t [in-range? -3.0 -10.0 5.0]]
[test-add 6 [let* [def sum 0] [for-each [λ [a] [set! sum [+ sum a]]] '[1 2 3]] sum]]
[test-add "\"nuj\"" [path/extension "test.nuj"]]
[test-add "\"nuj\"" [path/extension "Another/test.nuj"]]
[test-add "\"NUJ\"" [uppercase [path/extension "Another/test.nuj"]]]
[test-add "\"no\"" [path/extension "asd/test.nuj.no"]]
[test-add "\"asd/test.nuj\"" [path/without-extension "asd/test.nuj.no"]]

; Still have to ponder whether [undefine!] should exist
;[test-add #f [undefine! testerle]]
;[test-add "#nil" [def testerle 123] [undefine! testerle] testerle]

; Has to wait until the new constant system is in place
;[test-add 3.14159 [set! π 3] π]

; Has to wait until infix operators can be λs
;[test-add 64 [512 >> 3]]