Login
7 branches 0 tags
Ben (Win10) Added loop detection to pf 138800e 4 years ago 363 Commits
nujel / stdlib / tests / tests.nuj
[test/add 1073741824 [ash 1 30]]
[test/add -2147483649 [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 [> 5 1]]
[test/add #t [not [< 5 1]]]
[test/add #t [>= 5 5]]
[test/add #t [<= 5 5]]
[test/add #t [== #t #t]]
[test/add #t [not [== #f #t]]]
[test/add #t [== 2 2]]
[test/add 11 [length "Hallo, Welt"]]
[test/add #t [numeric? 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 [neg? -1]]
[test/add #t [neg? -0.01]]
[test/add #t [pos? 0]]
[test/add #t [pos? 0.01]]
[test/add #t [not [neg? 0]]]
[test/add #t [not [pos? -0.01]]]
[test/add #f [pos? "asd"]]
[test/add #f [neg? "asd"]]
[test/add #f [pos? #t]]
[test/add #f [neg? #f]]
[test/add #t [numeric?   1]]
[test/add #t [numeric?  -1]]
[test/add #t [numeric?   0]]
[test/add #t [numeric? 0.1]]
[test/add #t [numeric? [vec 1 2 3]]]
[test/add #f [numeric? #[1 2 3]]]
[test/add #f [numeric? '[1 2 3]]]
[test/add #f [numeric? @[:a 1 :b 2 :c 3]]]
[test/add #t [and [numeric? [vec 1]] [not [numeric? #f]] [not [numeric? "123"]]]]
[test/add #t [and [numeric? 1] [numeric? -1] [numeric? 0] [numeric? 0.1] [numeric? [vec 1]] [not [numeric? #f]] [not [numeric? "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 [not [< 3 2]]]
[test/add #t [zero? 0]]
[test/add #t [> 3.1 2.1]]
[test/add #t [> 3 2]]
[test/add #f [>= 4 "3"]]
[test/add #t [>= 3 3]]
[test/add #t [<= 3 3]]
[test/add #t [not [>= "2" 3]]]
[test/add #t [and [not [< 3 2]] [zero? 0] [> 3.1 2.1] [> 3 2] [not [>= 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 "min"]]]
[test/add 3 [+ 1 [- [length '[1 2 3]] 1]]]
[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 [== "asd" "asd"] [not [== "asd" "bsd"]] [not [== "asd" "asdasd"]]]]
[test/add #nil [list/ref '[1 2] 3]]
[test/add 1  [list/ref '[1 2] 0]]
[test/add 2  [list/ref '[1 2 3 4] 1]]
[test/add #nil [ref '[1 2] 3]]
[test/add 1  [ref '[1 2] 0]]
[test/add 2  [ref '[1 2 3 4] 1]]
[test/add 20 [reduce [make-list 10 2] + 0]]
[test/add #t [nil? #nil]]
[test/add #f [nil? "NotNil"]]
[test/add #t [not [nil? "NotNil"]]]
[test/add #t [vec? [vec 1]]]
[test/add #t [not [vec? "NotVec"]]]
[test/add 11 [def count [let [[a 0]] [λ [b] [set! a [+ a [cond [[numeric? 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 [array/length #[1 2 3 4]]]
[test/add 2 [array/ref #[1 2 3 4] 1]]
[test/add 3 [array/length [array/allocate 3]]]
[test/add #t [arr? #[1 2 3]]]
[test/add #t [arr? [array/allocate 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 [λ [α] [+ 1 α]] '[3]]]]
[test/add 0 [apply +]]
[test/add 0 [def cb '+] [apply cb]]
[test/add 1 [apply [λ [α] [+ 1 α]]]]
[test/add 1 [def cb [λ [α] [+ 1 α]]] [apply cb]]
[test/add 1 [let [[cb [λ [α] [+ 1 α]]]] [apply cb]]]
[test/add 1 [let* [def cb [λ [α] [+ 1 α]]] [apply cb]]]
[test/add 5 [length "12345"]]
[test/add 0 [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 #nil [max]]
[test/add #nil [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 9 25]]
[test/add 25 [max '[1 4 9 25]]]
[test/add 25 [max #[1 4 9 25]]]
[test/add 25 [max 25 4 9 1]]
[test/add 25 [max '[25 4 9 1]]]
[test/add 25 [max #[25 4 9 1]]]
[test/add 1 [min 1 4 9 25]]
[test/add 1 [min '[1 4 9 25]]]
[test/add 1 [min #[1 4 9 25]]]
[test/add 1 [min 25 4 9 1]]
[test/add 1 [min '[25 4 9 1]]]
[test/add 1 [min #[25 4 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 [** 2 8]]]
[test/add 256 [int [pow 2 8]]]
[test/add 256 [int [pow/int 2 8]]]
[test/add 1 [int [pow 1 8]]]
[test/add 1 [int [pow 1.0 8]]]
[test/add 0.5 [pow 2.0 -1.0]]
[test/add 0.25 [pow 2.0 -2.0]]
[test/add 0.125 [pow 2.0 -3.0]]
[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 [set! random/seed 123] [def first-value [random]] [set! random/seed 123] [== first-value [random]]]
[test/add #t [!= [random] [random]]]
[test/add 1 [def a 1] [when-not [== 2 2] [set! a 4]] a]
[test/add 4 [def a 1] [when-not [== 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 4294967295 #b11111111_11111111_11111111_11111111]
[test/add 4294967295 #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/single "[+ 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]" [str/write [abs [vec -1 -2 -3]]]]
[test/add "3.33333" [str/write [+ 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" [str/write [+ [+ 1.1 2.2] [+ 1.1 3] [+ 1 3.2]]]]
[test/add "20.1" [str/write [+ [+ 1.1 3] [+ 1 3.3] [+ 3.3 4.1 4.3]]]]
[test/add "15.54" [str/write [add [add [mul 3.2 3.2] [sub [sub [sub 5.5 1.1] 1] 1.1]] [div 9.9 3.3]]]]
[test/add "0.7" [str/write [% 10 3.1]]]
[test/add "11.7" [str/write [add [add [+ 1.1 2.2] [+ 1.1 3]] [+ 1 3.3]]]]
[test/add "11.75" [str/write [+ [float 10] [int "10"] [float "-8.25"]]]]
[test/add "30.3" [str/write [+ [abs [int "-10"]] [int 8.2] 12.3]]]
[test/add "[vec 12.0 12.0 12.0]" [str/write [+ [vec 1] 1 10]]]
[test/add "[vec 3.0 5.0 6.0]" [str/write [+ [vec 1] [vec 1 2] [vec 1 2 3]]]]
[test/add "[vec 3.0 3.0 3.0]" [str/write [+ 1 [vec 1] 1.0]]]
[test/add "[vec 3.0 3.0 3.0]" [str/write [+ 1.0 [vec 1] "1"]]]
[test/add "[vec -1.0 -1.0 -1.0]" [str/write [- [vec 1] [vec 1.0] [vec "1"]]]]
[test/add "2.7" [str/write [+ [- 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]" [str/write [+ 1 [vec 1] 1.0]]]
[test/add "[vec -1.0 -1.0 -1.0]" [str/write [- 1 [vec 1] 1.0]]]
[test/add "[vec 8.0 8.0 8.0]" [str/write [* [vec 2] "4"]]]
[test/add "[vec 1.0 1.0 1.0]" [str/write [mod [vec 9] 2]]]
[test/add "1.0" [str/write [float [int [+ [vec 1] [vec 0 9 9]]]]]]
[test/add '[] [cons]]
[test/add "[]" [str/write [cons]]]
[test/add '[1] [cons 1]]
[test/add "[1]" [str/write [cons 1]]]
[test/add 1 [car [cons 1 2]]]
[test/add 2 [cdr [cons 1 2]]]
[test/add "[1 . 2]" [str/write [cons 1 2]]]
[test/add "[1 2]" [str/write [cons 1 '[2]]]]
[test/add "[123]" [str/write '[123]]]
[test/add "[1 2 3]" [str/write '[1 2 3]]]
[test/add "[1 2 . 3]" [str/write '[1 2 . 3]]]
[test/add '[1 2 3] [read/single "[1 2 3]"]]
[test/add '[1 2 . 3] [read/single "[1 2 . 3]"]]
[test/add "[1 2 . 3]" [str/write [cons 1 [cons 2 3]]]]
[test/add '[4 3 2 1] [reverse '[1 2 3 4]]]
[test/add "[1 2.0 3 1 2.0 3]" [str/write [append '[1 2.0 3] '[1 2.0 3]]]]
[test/add '[1 4] [filter '[1 2.0 #t 4] int?]]
[test/add "[2.0]" [str/write [filter '[1 2.0 #t 4] float?]]]
[test/add "[2.0]" [str/write [filter '[1 2.0 #t 4] float?]]]
[test/add '[#t]  [filter '[1 2.0 #t 4] bool?]]
[test/add '[1 3 5] [filter '[1 2 3 4 5 6] odd?]]
[test/add 3 [count '[1 2 3 4 5 6] odd?]]
[test/add 3 [count '[1 2 3 4 5 6] even?]]
[test/add 6 [count '[1 2 3 4 5 6] int?]]
[test/add 0 [count '[1 2 3 4 5 6] float?]]
[test/add '[2 4 6] [filter '[1 2 3 4 5 6] even?]]
[test/add '["vier"] [filter '[1 2 3 "vier" 5 6] string?]]
[test/add '[1 2 3 5 6] [filter '[1 2 3 "vier" 5 6] int?]]
[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\"]" [str/write [let [[l '[1.0 #t "a"]]] [append [except-last-pair l] [last-pair l]]]]]
[test/add "[\"asd\" #t #f]" [str/write [member "asd" '[123 456 "asd" #t #f]]]]
[test/add "[[vec 4.0 4.0 4.0] 9 16.0]" [str/write [map [cons [vec 2] '[3 4.0]] [λ [a] [* a a]]]]]
[test/add "11.0" [cat 1 1.0]]
[test/add "[vec 9.0 9.0 9.0]" [str/write [div [vec 99] [float [cat 1 1.0]]]]]
[test/add "#[99 2 3 4]" [str/write [let [[cur-arr #[1 2 3 4]]] [array/set! cur-arr 0 99] cur-arr]]]
[test/add "#[42 42 42 42 42 42]" [str/write [array/fill! [array/allocate 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]]]] [str/write [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 "ASD123" [uppercase "asD123"]]
[test/add "asd123" [lowercase "aSD123"]]
[test/add "Asd123" [capitalize "aSD123"]]
[test/add "[vec 1.0 1.0 1.0]"[str/write  [floor [vec 1.3 1.3 1.3]]]]
[test/add "2.0" [str/write [ceil 1.3]]]
[test/add "[vec 2.0 2.0 2.0]" [str/write [ceil [vec 1.3 1.3 1.3]]]]
[test/add "1.0" [str/write [round 1.3]]]
[test/add "2.0" [str/write [round 1.51]]]
[test/add "3.0" [str/write [sqrt 9]]]
[test/add "[vec 5.0 5.0 5.0]" [str/write [sqrt [vec 25 25 25]]]]
[test/add "256.0" [str/write [pow 2.0 8]]]
[test/add "[vec 4.0 8.0 16.0]" [str/write [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" [str/write :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]] [str/write test]]
[test/add "Eins" [def eins [ω [def say [λ [] "Eins"]]]] [eins [say]]]
[test/add "Zwei" [let* [def eins [ω [defun say [] "Zwei"]]] [def zwei [eins [ω]]] [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]] [str/write [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]" [str/write [map [split "1,2,3" ","] float]]]
[test/add "[\"dies ist\" \"ein\" \"test\"]" [str/write [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 [== 32 #\ ]]
[test/add #t [== #\Backspace 8]]
[test/add #t [== #\Tab [char-at "\t" 0]]]
[test/add #t [and [== #\cr 13] [== #\Return 13]]]
[test/add #t [and [== #\lf 10] [== 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 [== + +]]
[test/add #t [== min min]]
[test/add #t [let [[some-value #f]] [not some-value]]]
[test/add 4 [>> 8 1]]
[test/add 9 [- 10 1]]
[test/add 5 [/ 10 2]]
[test/add 256 [<< 1 8]]
[test/add #t [== :asd :asd]]
[test/add #t [== :bool [type-of #f]]]
[test/add #t [== :int [type-of 123]]]
[test/add #f [== :int [type-of 123.123]]]
[test/add #t [== :float [type-of 123.123]]]
[test/add #t [== :vec [type-of [vec 1]]]]
[test/add #t [== :native-function [type-of +]]]
[test/add #t [== :lambda [type-of test/add*]]]
[test/add #t [== :string [type-of "asd"]]]
[test/add 2 [getf [list :a 1 :b 2 :c 3] :b]]
[test/add "#nil" [str/write [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 [== 4 [+ 2 2]]]
[test/add :int [type-of [+ 2 2]]]
[test/add :float [type-of [+ 2.0 2.1]]]
[test/add :float [type-of [+ 2 2.1]]]
[test/add -1 [do -1]]
[test/add -1 [- 1]]
[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 [zero-neg?    0]]
[test/add #t [zero-neg? -4.0]]
[test/add #f [zero-neg?  0.1]]
[test/add 0.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" [str/write 'do]]
[test/add "[123]" [str/write '[123]]]
[test/add "[123 #t]" [str/write '[123 #t]]]
[test/add "[123 'do]" [str/write '[123 'do]]]
[test/add "[123 \"asd\"]" [str/write '[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 #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 [== #nil #nil]]
[test/add #t [== #t #t]]
[test/add #f [== #t #f]]
[test/add #t [== #f #f]]
[test/add #f [== '[] #f]]
[test/add #f [== #f '[]]]
[test/add #f [== '[] #t]]
[test/add #f [== #t '[]]]
[test/add #t [== '[] '[]]]
[test/add #f [== '[] '[1]]]
[test/add #f [== '[1] '[1]]]
[test/add #t [list-equal? '[1] '[1]]]
[test/add #f [== '[] #nil]]
[test/add 10,000 [let [] [def i 0] [while [< i 10,000] [set! i [+ 1 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 '[λ* #nil [v] "Add 1 to V" [+ 1 v]] [compile '[λ [v] "Add 1 to V" [+ 1 v]]]]
[test/add '[λ* #nil [v] "" [+ 1 v]] [compile '[λ [v] [+ 1 v]]]]
[test/add '[λ* #nil [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 '[2 3 4] [map '[1 2 3] [λ [v] [+ 1 v]]]]
[test/add '[2 4 6] [map '[1 2 3] [λ [v] [* 2 v]]]]
[test/add '["1" "2" "3"] [map '[1 2 3] str/write]]
[test/add "[123 #nil]" [str/write '[123 #nil]]]
[test/add '[123 #nil] '[123 #nil]]
[test/add "@[:asd 123]" [str/write [tree/new :asd 123]]]
[test/add "@[:asd 123]" [str/write @[: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 [+ 1 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 [+ 1 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 [+ 1 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 [== '+ [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 "[]" [str/write '[]]]
[test/add "[]" [str/write '[#nil]]]
[test/add "[#nil #nil]" [str/write '[#nil #nil]]]
[test/add "[and #nil #nil]" [str/write '[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 [== [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" [str/write 0.1]]
[test/add "0.02" [str/write 0.02]]
[test/add "0.003" [str/write 0.003]]
[test/add "0.01234" [str/write 0.01234]]
[test/add "0.1" [str/write [car [read "0.1"]]]]
[test/add "0.1001" [str/write [car [read "0.1001"]]]]
[test/add "0.913" [str/write [car [read "0.913"]]]]
[test/add "0.00012" [str/write [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] [let* [def v 2] `[1 ~v 3]]]
[test/add '[resolve 123] [do [let [[source [cons 123] #nil]] `[resolve ~[car source]]]]]
[test/add '[resolve asd] [do [let [[source [cons 'asd #nil]]] `[resolve ~[car source]]]]]
[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.0 -10.0 5.0]]
[test/add 6 [let* [def sum 0] [for-each '[1 2 3] [λ [a] [set! sum [+ sum a]]]] 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"]]
[test/add #t [[path/ext?! "nuj"] "tests.nuj"]]
[test/add #f [[path/ext?! "nuj"] "tests.nu"]]
[test/add #t [resolves? '+]]
[test/add #t [resolves? 'map]]
[test/add #t [resolves? 'π]]
[test/add #f [resolves? :asd]]
[test/add #f [resolves? 'asdqwe]]
[test/add #t [> [length [symbol-search "abs"]] 0]]
[test/add #t [tree? @[:asd 123]]]
[test/add #f [tree? #[123]]]
[test/add #f [tree? '[:asd 123]]]
[test/add #f [tree? #nil]]
[test/add #f [tree? 123]]
[test/add #f [tree? "asd"]]
[test/add #f [tree? #t]]
[test/add #t [tree? [closure +]]]
[test/add 'source [car [[closure compile] :arguments]]]
[test/add :invalid-literal [try [λ [e] [car e]] [read "#inf"]]]
[test/add 3 [+ '1 '[2]]]
[test/add -1 [- '1 '[2]]]
[test/add -1 [- '1 '[2 3]]]
[test/add :type-error [try [λ [e] [car e]] [+ "1" "2"]]]
[test/add :type-error [try [λ [e] [car e]] [sin 1]]]
[test/add :type-error [try [λ [e] [car e]] [ceil 1]]]
[test/add :type-error [try [λ [e] [car e]] [floor 1]]]
[test/add :type-error [try [λ [e] [car e]] [round 1]]]
[test/add '[1 2 3] `[1 ~@`[2 3]]]
[test/add '[+ 1 2] [compile '[+1 2]]]
[test/add '[1 [2 [3 4]]] `[1 `[2 ~[3 ~[+ 2 2]]]]]
[test/add 2 [cadar '[[1 2 3] 4 5]]]
[test/add #nil [when-not #t 123]]
[test/add 123 [when-not #f 123]]
[test/add '[if #t 123 #nil] [compile '[when #t 123]]]
[test/add '[if #t #nil 123] [compile '[when-not #t 123]]]
[test/add :invalid-let-form [try [λ [err] [car err]] [compile '[let [1] 1]]]]
[test/add :invalid-let-form [try [λ [err] [car err]] [compile '[let [[] 1] 1]]]]
[test/add #t [symbol? 'asd]]
[test/add #t [symbol? :asd]]
[test/add #t [symbol? [gensym]]]
[test/add #t [!= [gensym] [gensym]]]
[test/add #f [symbol? 123]]
[test/add #f [symbol? "asd"]]
[test/add #f [symbol? #[123 'asd]]]
[test/add #f [symbol? @[:a 123]]]
[test/add 1 [if #t 1 2]]
[test/add 2 [if-not :test 1 2]]
[test/add 1 [if-not #f 1 2]]
[test/add 7 [if-let [a 3] [+ a 4] 1]]
[test/add 1 [if-let [a #f] [+ a 4] 1]]
[test/add 7 [when-let [a 3] [+ a 4]]]
[test/add #nil [when-let [a #nil] [+ a 4]]]
[test/add #t [last? '[]]]
[test/add #t [last? '[1]]]
[test/add #f [last? '[1 2]]]
[test/add #t [object? [ω]]]
[test/add #t [object? [current-closure]]]
[test/add #t [native? +]]
[test/add #f [native? min]]
[test/add #f [lambda? +]]
[test/add #t [lambda? min]]
[test/add #t [special-form? if]]
[test/add #f [special-form? when]]
[test/add #nil [def #nil #nil]]
[test/add #nil [def]]
[test/add #nil [set! #nil #nil]]
[test/add #nil [set!]]
[test/add "   1" [string/pad-start "1" 4]]
[test/add "0001" [string/pad-start "1" 4 "0"]]
[test/add "asd1" [string/pad-start "1" 4 "asdasd"]]
[test/add "1   " [string/pad-end "1" 4]]
[test/add "1000" [string/pad-end "1" 4 "0"]]
[test/add "1asd" [string/pad-end "1" 4 "asdasd"]]
[test/add 128 oneTwoThreeTest]
[test/add "[quote . 123]" [str/write [cons 'quote 123]]]
[test/add "[quote . asd]" [str/write [cons 'quote 'asd]]]
[test/add "[quote . asd]" [str/write [cons 'quote 'asd]]]
[test/add 34 [time/seconds 1637755714]]
[test/add  8 [time/minutes 1637755714]]
[test/add 12 [time/hours   1637755714]]
[test/add 59 [time/seconds 1637755739]]
[test/add  0 [time/seconds 1637755740]]
[test/add '[4 5 6] [map '[1 2 3] [+x 3]]]
[test/add 4 [def α 3] [++ α] α]
[test/add 2.0 [cbrt  8]]
[test/add 3.0 [cbrt 27]]
[test/add 2.0 [cbrt 8.0]]
[test/add 3.0 [cbrt 27.0]]
[test/add 2.0 [vec/x [cbrt [vec 8]]]]
[test/add #t [case "1" [[1] #f] [['1] #f] [["1"] #t]]]
[test/add #t [case "asd" [["as"] #f] [["qwe"] #f] [["asd"] #t]]]
[test/add #t [case [+ 1 2] [[3.1] #f] [[3.0] #f] [3 #t]]]
[test/add #t [case [+ 1 2] [[1] #f] [[2 3] #t]]]
[test/add #t [case [+ 1 1] [[1] #f] [[2 3] #t]]]
[test/add #f [case [+ 0 1] [[1] #f] [[2 3] #t]]]
[test/add #nil [case [+ 2 2] [[1] #f] [[2 3] #t]]]
[test/add 123 [case [+ 2 2] [[1] #f] [[2 3] #t] [otherwise 123]]]
[test/add #t [def i 1] [case [++ i] [[9] #f] [[4] #f] [[2] #t]]]
[test/add :too-many-args [try [\ [err] [car err]] [cons 123 234 345]]]
[test/add #t [== λ [resolve [car '[λ asd]]]]]
[test/add #t [pos? [index-of [describe/closure [[defun stackTraceTest [] [current-lambda]]]] "stackTraceTest"]]]
[test/add 2 [case 'asd [['qwe] 1] [['asd] 2] [otherwise 3]]]
[test/add 10 [reduce #[1 2 3 4] add/int 0]]
[test/add "1,2,3,4" [join #[1 2 3 4] ","]]
[test/add 2 [count #[1 2 3 4] even?]]
[test/add 14 [reduce [map #[1 2 3 4] [+x 1]] + 0]]
[test/add 3 [length #[1 2 3]]]
[test/add 2 [def arr #[1 2 3]] [array/length! arr 2] [length arr]]
[test/add 3 [def arr #[1 2 3]] [array/length! arr 2] [reduce arr + 0]]
[test/add "#[2 4]" [str/write [filter #[1 2 3 4] even?]]]
[test/add 5 [count '[4 30 22 23 21 15 7 28 16 25 2 10] [bit-set?! 0]]]
[test/add 7 [count #[4 30 22 23 21 15 7 28 16 25 2 10] [bit-set?! 1]]]
[test/add 7 [count '[4 30 22 23 21 15 7 28 16 25 2 10] [bit-clear?! 0]]]
[test/add 5 [count #[4 30 22 23 21 15 7 28 16 25 2 10] [bit-clear?! 1]]]
[test/add '["123"] [split "123" "\n"]]
[test/add '["" ""] [split "\n" "\n"]]
[test/add '["123" "456"] [split "123\n456" "\n"]]
[test/add '["" "" ""] [split "\n\n" "\n"]]
[test/add '["1" "2" "3"] [split "1\n2\n3" "\n"]]
[test/add '["" "" "" ""] [split "\n\n\n" "\n"]]
[test/add '["1" "2" "3" "4"] [split "1\n2\n3\n4" "\n"]]
[test/add "" [substr "\n" 1 1]]
[test/add "@[:a 1 :b 2]" [str/write [tree/zip '[:a :b] '[1 2]]]]
[test/add "@[:a #nil :b #nil]" [str/write [tree/zip '[:a :b] '[]]]]
[test/add "@[:a 1 :b #nil]" [str/write [tree/zip '[:a :b] '[1]]]]
[test/add "@[]" [str/write [tree/zip '[] '[1 2]]]]
[test/add "123" [str/write [read/single "123;asd"]]]
[test/add '[123] [read "123"]]
[test/add '[123] [read "123;asd"]]
[test/add '[123 234] [read "123;asd\n234"]]
[test/add '[234] [read ";asd\n;qwe\n234;asd"]]
[test/add '[2 1 0] [let [[ret #nil]] [for [i 0 3] [set! ret [cons i ret]]] ret]]
[test/add '[1 2 3] [let [[ret #nil]] [for [i 3 0 -1] [set! ret [cons i ret]]] ret]]
[test/add '[20 10 0] [let [[ret #nil]] [for [i 0 30 10] [set! ret [cons i ret]]] ret]]
[test/add "#[0 0 0]" [str/write [-> [array/allocate 3] [array/fill! 0]]]]
[test/add "#[3 9 0]" [str/write [-> [array/allocate 3] [array/fill! 0] [array/set! 1 9] [array/set! 0 3]]]]
[test/add "@[:a 1 :b 2]" [str/write [-> [tree/new] [tree/set! :a 1] [tree/set! :b 2]]]]
[test/add '[3 2 1] [->> '[1] [cons 2] [cons 3]]]
[test/add '[1] [->> '[1]]]
[test/add 10 [def arr #[1 2 3]] [array/length! arr 4] [array/set! arr 3 4] [reduce arr + 0]]
[test/add 10 [-> #[1 2 3] [array/length! 4] [array/set! 3 4] [reduce add 0]]]
[test/add 10 [sum #[1 2 3 4]]]
[test/add 10 [sum '[1 2 3 4]]]
[test/add 0 [popcount 0]]
[test/add 0 [popcount #nil]]
[test/add 0 [popcount ""]]
[test/add 1 [popcount 1]]
[test/add 1 [popcount 2]]
[test/add 2 [popcount 3]]
[test/add 4 [popcount 15]]
[test/add '[3 2 1] [list/sort '[1 2 3]]]
[test/add '[9 3 1] [list/sort '[1 3 9]]]
[test/add '[9 1] [list/sort '[1 9]]]
[test/add '[9 2 1 1] [list/sort '[1 1 2 9]]]
[test/add '[3.0 2.0 1.0] [list/sort '[3.0 1.0 2.0]]]
[test/add '["z" "m" "a"] [list/sort '["m" "a" "z"]]]
[test/add '["z" "m" "a"] [list/sort '["z" "m" "a"]]]
[test/add '["z" "m" "a"] [list/sort '["a" "z" "m"]]]
[test/add '["m" "a" "Z"] [list/sort '["a" "Z" "m"]]]
[test/add '["zauberer" "mit" "aggressionen"] [list/sort '["aggressionen" "zauberer" "mit"]]]
[test/add #\( [char-at "([{<>}])" 0]]
[test/add #\[ [char-at "([{<>}])" 1]]
[test/add #\{ [char-at "([{<>}])" 2]]
[test/add #\< [char-at "([{<>}])" 3]]
[test/add #\> [char-at "([{<>}])" 4]]
[test/add #\} [char-at "([{<>}])" 5]]
[test/add #\] [char-at "([{<>}])" 6]]
[test/add #\) [char-at "([{<>}])" 7]]
[test/add #t [< 1442693 12049880844]]
[test/add 12051323537 [+ 1442693 12049880844]]
[test/add '[:a 1] [tree/list [tree/dup @[:a 1]]]]
[test/add '[a 1] [tree/list [tree/dup @['a 1]]]]
[test/add "@[:a 1]" [def t @[:a 1]] [-> [tree/dup @[:a 1]] [tree/++ :a]] [str/write t]]
[test/add "@[:a 2]" [def t @[:a 1]] [str/write [-> [tree/dup @[:a 1]] [tree/++ :a]]]]
[test/add #f [> #nil 1.0]]
[test/add #f [> #nil 1]]
[test/add #f [> #nil 0]]
[test/add #f [> #nil -1]]
[test/add #f [> #nil -1.0]]
[test/add #f [< #nil 1.0]]
[test/add #f [< #nil 1]]
[test/add #f [< #nil 0]]
[test/add #f [< #nil -1]]
[test/add #f [< #nil -1.0]]
[test/add #f [== #nil 1]]
[test/add #f [== #nil 0]]
[test/add #f [== #nil -1]]
[test/add '[1 2 3] [nreverse [list 3 2 1]]]
[test/add '[1 2 3 4 5 6 7 8 9] [nreverse [list 9 8 7 6 5 4 3 2 1]]]
[test/add '[1] [nreverse [list 1]]]
[test/add '[2 1] [nreverse [cons 1 [cons 2 #nil]]]]
[test/add #nil [nreverse #nil]]
[test/add :tree [type-of @[]]]
[test/add '[] [tree/list @[]]]
[test/add '[] [tree/keys @[]]]
[test/add '[] [tree/values @[]]]
[test/add '[123] [tree/values @[:asd 123]]]
[test/add '[:asd] [tree/keys @[:asd 123]]]
[test/add '[:asd 123] [tree/list [apply tree/new [tree/list @[:asd 123]]]]]
[test/add :tree [type-of @[:asd 123]]]
[test/add '[:asd 123] [tree/list [tree/dup @[:asd 123]]]]
[test/add '[] [tree/list [tree/dup @[]]]]
[test/add :type-error [try [\ [err] [car err]] [tree/list [tree/dup #nil]]]]
[test/add :type-error [try [\ [err] [car err]] [tree/list [tree/dup 123]]]]
[test/add :type-error [try [\ [err] [car err]] [tree/list [tree/dup '[]]]]]
[test/add "1.1" [str/write 1.1]]
[test/add "1.01" [str/write 1.01]]
[test/add "1.001" [str/write 1.001]]
[test/add "1.0001" [str/write 1.0001]]
[test/add "10.1" [str/write 10.1]]
[test/add "10.01" [str/write 10.01]]
[test/add "10.001" [str/write 10.001]]
[test/add "10.0001" [str/write 10.0001]]
[test/add "100.1" [str/write 100.1]]
[test/add "100.01" [str/write 100.01]]
[test/add "100.001" [str/write 100.001]]
[test/add "100.0001" [str/write 100.0001]]
[test/add "1000.1" [str/write 1000.1]]
[test/add "1000.01" [str/write 1000.01]]
[test/add "1000.001" [str/write 1000.001]]
[test/add "1000.0001" [str/write 1000.0001]]
[test/add "10000.1" [str/write 10000.1]]
[test/add "10000.01" [str/write 10000.01]]
[test/add "10000.001" [str/write 10000.001]]
[test/add "10000.0001" [str/write 10000.0001]]
[test/add "100000.1" [str/write 100000.1]]
[test/add "100000.01" [str/write 100000.01]]
[test/add "40004.40004" [str/write [* 4 10001.10001]]]
[test/add "30003.30003" [str/write [* 3 10001.10001]]]
[test/add "20002.20002" [str/write [* 2 10001.10001]]]
[test/add "50004201.04706" [str/write [+ 50004201 0.04706]]]
[test/add "504201.91003" [str/write [+ 504201 0.91003]]]
[test/add "-900200.01003" [str/write -900200.01003]]
[test/add "-900000.00001" [str/write -900000.00001]]
[test/add "109234.00012" [str/write 109234.00012]]
[test/add "102005" [str/write 102005]]
[test/add "-100295" [str/write -100295]]
[test/add "asd" [string "asd"]]
[test/add "123" [string 123]]
[test/add "#t" [string #t]]
[test/add "" [string #nil]]
[test/add "[1 2 3]" [string '[1 2 3]]]
[test/add "[1 2 3]" [string '[1 2 3]]]
[test/add "@[:a 3]" [string @[:a 3]]]
[test/add "#[#nil]" [str/write [array/set! #[1] 0 #nil]]]
[test/add "#[2]" [str/write [array/set! #[1] 0 2]]]
[test/add "#[#t]" [str/write [array/set! #[1] 0 #t]]]
[test/add "#[#f]" [str/write [array/set! #[1] 0 #f]]]
[test/add '[1] [read "#_[\"asd\"] 1"]]
[test/add '[1] [read "#_[asd] 1"]]
[test/add '[1] [read "#_[asd [123]] 1"]]
[test/add '[1 2] [read "1 #_[asd [123]] 2"]]
[test/add '[1] [read "1 #_[asd [123]]"]]
[test/add "asd" [cat "a" #nil "s" "" "d"]]
[test/add '[1 2 3] [append '[1] '[2] '[3]]]
[test/add '[1 2 . 3] [append '[1] '[2] 3]]
[test/add #t [case 'asd [[asd] #f] [['asd] #t]]]
[test/add #t [case 'asd [[asd] #f] ['asd #t]]]
[test/add #t [case 'quote [['quote] #t] [otherwise #f]]]
[test/add #t [case 'quote ['quote #t] [otherwise #f]]]
[test/add #t [case 'otherwise [['otherwise] #t] [otherwise #f]]]
[test/add #t [case 'otherwise ['otherwise #t] [otherwise #f]]]
[test/add #f [== 0 'asd]]
[test/add #f [== 0 :asd]]
[test/add #f [== 0 "asd"]]
[test/add #f [== 0 #f]]
[test/add #f [== 0 #t]]
[test/add #f [== 0 0.1]]
[test/add #f [== 0 #[0]]]
[test/add #f [== 0 @[:asd 0]]]
[test/add #f [== 0.0 'asd]]
[test/add #f [== 0.0 :asd]]
[test/add #f [== 0.0 "asd"]]
[test/add #f [== 0.0 #f]]
[test/add #f [== 0.0 #t]]
[test/add #f [== 0.0 0.1]]
[test/add #f [== 0.0 #[0]]]
[test/add #f [== 0.0 @[:asd 0]]]
[test/add '[1 2 3] [[\ a a] 1 2 3]]
[test/add 1 [[\ [a . b] a] 1 2 3]]
[test/add '[2 3] [[\ [a . b] b] 1 2 3]]
[test/add '[3] [[\ [a b . c] c] 1 2 3]]
[test/add 2 [[\ [a b . c] b] 1 2 3]]
[test/add 1 [[\ [a b . c] a] 1 2 3]]
[test/add '[] [[\ [a b c . d] d] 1 2 3]]
[test/add 3 [[\ [a b c . d] c] 1 2 3]]
[test/add 2 [[\ [a b c . d] b] 1 2 3]]
[test/add 1 [[\ [a b c . d] a] 1 2 3]]
[test/add 122 [-> @[:asd 123] [tree/-- :asd] [tree/get :asd]]]
[test/add 124 [-> @[:asd 123] [tree/++ :asd] [tree/get :asd]]]
[test/add 10 [def m 5] [for [i 0 m] [++ m] [when [> m 50] [set! i 100]]] m]
[test/add "#[1 2 3 4]" [str/write [array/append #[1 2] #[3 4]]]]
[test/add "#[1 2 3]" [str/write [array/append #[1 2] #[3]]]]
[test/add "#[1 2]" [str/write [array/append #[1 2] #[]]]]
[test/add :type-error [try [\ [e] [car e]] [array/append #[1] '[2]]]]
[test/add :type-error [try [\ [e] [car e]] [array/append '[1] #nil]]]
[test/add :type-error [try [\ [e] [car e]] [array/append #[1]]]]
[test/add :type-error [try [\ [e] [car e]] [array/append '[1]]]]
[test/add :type-error [try [\ [e] [car e]] [array/append]]]
[test/add "#[1 2 3]" [str/write [let [[o #[2 2 3]]] [array/set! o 0 1] [array/set! [array/dup o] 0 3] o]]]
[test/add #t [do [for [i 0 10] [set! i 20] [when [> i 30] [throw [list :error]]]] #t]]
[test/add #f [== #[1] #[1]]]
[test/add #f [== #[1] #[2]]]
[test/add #t [let [[a #[1]]] [== a a]]]
[test/add #f [== @[:a 1] #[:a 1]]]
[test/add #f [== @[:a 1] #[:b 1]]]
[test/add #t [let [[a @[:a 1]]] [== a a]]]
[test/add #t [-> [array/2d/allocate 4 4] [array/2d/set! 1 1 #t] [array/2d/ref 1 1]]]
[test/add #t [-> [array/2d/allocate 3 3] [array/2d/fill! #t] [array/2d/ref 1 1]]]
[test/add "00620062" [string/pad-start [int->string/hex [hash/adler32 "a"]] 8 "0"]]
[test/add "0F9D02BC" [string/pad-start [int->string/hex [hash/adler32 "asdQWE123"]] 8 "0"]]
[test/add "796B110D" [string/pad-start [int->string/hex [hash/adler32 "DiesIstEinTestDerNujelAdler32Implementierung"]] 8 "0"]]
[test/add '[2 3 4] [-> '[1 2 3 4] [delete 1]]]
[test/add "#[2 3 4]" [str/write [-> #[1 2 3 4] [delete 1]]]]
[test/add "#$0" [str/write [int->bytecode-op 0]]]
[test/add "#$9" [str/write [int->bytecode-op 9]]]
[test/add "#$F" [str/write [int->bytecode-op 15]]]
[test/add "#$10" [str/write [int->bytecode-op 16]]]
[test/add "#$FF" [str/write [int->bytecode-op 255]]]
[test/add :invalid-bc-op [try [\ [e] [car e]] [int->bytecode-op -129]]]
[test/add :invalid-bc-op [try [\ [e] [car e]] [int->bytecode-op 256]]]
[test/add "#$0" [str/write #$]]
[test/add "#$9" [str/write #$9]]
[test/add "#$F" [str/write #$F]]
[test/add "#$10" [str/write #$10]]
[test/add "#$FF" [str/write #$FF]]
[test/add :invalid-literal [try [\ [e] [car e]] [read/single "#$1FF"]]]
[test/add #x0 [bytecode-op->int #$0]]
[test/add #x9 [bytecode-op->int #$9]]
[test/add #xF [bytecode-op->int #$F]]
[test/add #x10 [bytecode-op->int #$10]]
[test/add #xFF [bytecode-op->int #$FF]]
[test/add :argument-mismatch [try [\ [e] [car e]] [bytecode-op->int]]]
[test/add :argument-mismatch [try [\ [e] [car e]] [bytecode-op->int 12]]]
[test/add :bytecode-op [type-of #$10]]
[test/add :bytecode-op [type-of [int->bytecode-op 255]]]
[test/add "#[#$0 #$9 #$F #$10 #$FF]" [str/write [arr->bytecode-arr #[#$0 #$9 #$F #$10 #$FF]]]]
[test/add :bytecode-array [type-of [arr->bytecode-arr #[#$0 #$9 #$F #$10 #$FF]]]]
[test/add #$0 [array/ref [bytecode-arr->arr [arr->bytecode-arr #[#$0 #$9 #$F #$10 #$FF]]] 0]]
[test/add 0    [bytecode-eval [arr->bytecode-arr #[#$2 #$0 #$1]]]]
[test/add 127  [bytecode-eval [arr->bytecode-arr #[#$2 #$7F #$1]]]]
[test/add -1   [bytecode-eval [arr->bytecode-arr #[#$2 #$FF #$1]]]]
[test/add -128 [bytecode-eval [arr->bytecode-arr #[#$2 #$80 #$1]]]]
[test/add 1    [bytecode-eval [arr->bytecode-arr #[#$1]] 1 2 3 4]]
[test/add 3    [bytecode-eval [arr->bytecode-arr #[#$3 #$1]] 1 2]]
[test/add 5    [bytecode-eval [assemble [$push/int 3] [$push/int 2] [$add/int] [$ret]]]]
[test/add 3    [bytecode-eval [assemble [$push/int 3] [$ret]]]]
[test/add 0    [bytecode-eval [assemble [$push/int 0] [$ret]]]]
[test/add -3   [bytecode-eval [assemble [$push/int -3] [$ret]]]]
[test/add -128 [bytecode-eval [assemble [$push/int -128] [$nop] [$ret]]]]
[test/add 127  [bytecode-eval [assemble [$push/int 127] [$ret]]]]
[test/add #t   [int? [val->index "asd"]]]
[test/add "asd" [index->val [val->index "asd"]]]
[test/add '[123 asd] [index->val [val->index '[123 asd]]]]
[test/add '[123 asd] [asmrun [$push/lval '[123 asd]] [$ret]]]
[test/add 'test [asmrun [$push/lval 'test] [$ret]]]
[test/add 2 [[asmrun [$push/lval [\ [a] [+ 1 a]]] [$ret]] 1]]
[test/add '[test list] [let [[code [assemble [$push/lval [list 'test 'list]] [$ret]]]]                   [bytecode-eval code]]]
[test/add '[test list] [let [[code [assemble [$push/lval [list 'test 'list]] [$ret]]]] [garbage-collect] [bytecode-eval code]]]
[test/add '[1 2 3] [asmrun [$push/int 1] [$push/int 2] [$push/int 3] [$make-list 3] [$ret]]]
[test/add '[1] [asmrun [$push/int 1][$make-list 1] [$ret]]]
[test/add '[] [asmrun [$make-list 0] [$ret]]]
[test/add 3 [asmrun [$push/lval '[+ 1 2]] [$eval] [$ret]]]
[test/add 5 [asmrun [$push/int 2] [$push/int 3] [$apply 2 add/int] [$ret]]]
[test/add 4 [asmrun [$push/int 2] [$dup] [$apply 2 add/int] [$ret]]]
[test/add 26 [asmrun [$nop] [$push/int 26] [$jmp :asd] [$push/int 99] [:label :asd] [$ret]]]
[test/add 26 [asmrun [$nop] [$push/int 26] [$push/lval #t] [$jt :asd] [$push/int 99] [:label :asd] [$ret]]]
[test/add 99 [asmrun [$nop] [$push/int 26] [$push/lval #f] [$jt :asd] [$push/int 99] [:label :asd] [$ret]]]
[test/add "#[1 2 3]" [str/write [array/push #[1 2 3]]]]
[test/add "#[1 2 3 \"4\"]" [str/write [array/push #[1 2 3] "4"]]]
[test/add "#[1 2 3 4 #f]" [str/write [array/push #[1 2 3] 4 #f]]]
[test/add "#[1 2 3 #nil 5]" [str/write [array/push #[1 2 3] #nil 5]]]
[test/add '[1 2 3 4 5] [flatten #[1 2 3 4 5]]]
[test/add '[1 2 3 4 5] [flatten '[1 2 3 4 5]]]
[test/add '[1 2 3 4 5] [flatten '[[1 2] [3] [[[4] 5]]]]]
[test/add '[1 2 3 4 5] [flatten [list '[1 2] #[3] #['[[4] 5]]]]]
[test/add #t [int? [sym->index 'asd]]]
[test/add 'asd [index->sym [sym->index 'asd]]]
[test/add 5 [[asmrun [$lambda 'test-add '[a b] "Add a and b together" '[+ a b]] [$ret]] 2 3]]
[test/add 13 [byterun '[+ 6 7]]]
;[test/add 15 [byterun '[+ 3 [+ 6 [- 7 1]]]]]
[test/add 6 [byterun '[- 7 1]]]
[test/add 1 [byterun '[if #t 1 2]]]
[test/add 2 [byterun '[if #f 1 2]]]
[test/add 1000 [byterun '[do 1000]]]
[test/add π [byterun '[do π]]]
[test/add π [asmrun [$get 'π] [$ret]]]
[test/add 2 [asmrun [$push/int 1] [$def 'tmp] [$let] [$push/int 2] [$def 'tmp] [$get 'tmp] [$ret]]]
[test/add 1 [asmrun [$push/int 1] [$def 'tmp] [$let] [$push/int 2] [$def 'tmp] [$closure/pop] [$get 'tmp] [$ret]]]
[test/add 3 [[asmrun [$push/int 1] [$def 'tmp] [$let] [$push/int 3] [$def 'tmp] [$lambda two '[] "" '[do tmp]] [$closure/pop] [$ret]]]]
[test/add 128 [eval-compile '[+123 5] [current-closure]]]
[test/add 5 [def a 4] [for [i 0 10] [once [++ a]]] a]
[test/add :asd [try [\ [a] [car a]] [asmrun [$push/lval '[:asd "Test"]] [$throw]]]]
[test/add :asd [car [asmrun [$jmp :start] [:label :handle] [$ret] [:label :start] [$try :handle] [$let] [$push/lval '[:asd "Test"]] [$throw]]]]
[test/add "Test" [cadr [asmrun [$jmp :start] [:label :handle] [$ret] [:label :start] [$try :handle] [$let] [$push/lval '[:asd "Test"]] [$throw]]]]
[test/add '[:asd "Test"] [try [\ [a] :shouldnt-have-caught-that] [asmrun [$jmp :start] [:label :handle] [$ret] [:label :start] [$try :handle] [$let] [$push/lval '[:asd "Test"]] [$throw]]]]
[test/add '[:asd "Test"] [list :asd "Test"]]
[test/add :asd [car [asmrun [$nop] [$nop] [$try :handle] [$let] [$push/lval '[:asd "Test"]] [$throw] [$nop] [$push/lval :error] [:label :handle] [$ret]]]]
[test/add 3 [asmrun [$jmp :start] [:label :ret] [$push/int 3] [$ret] [:label :start] [$push/int 2] [$jmp :ret] [$ret]]]
[test/add 5 [asmrun [$jmp :start] [:label :func] [$push/int 2] [$add/int] [$ret] [:label :start] [$push/int 3] [$call :func] [$ret]]]
[test/add 5 [asmrun [$jmp :start] [:label :func] [$push/int 2] [$add/int] [$ret] [:label :start] [$push/int 3] [$jmp :func]]]
[test/add 10 [let [[t 0]] [for-in [l [list 1 2 3 4]] [+= t l]] t]]
[test/add 1 [let [[t 0]] [for-in [l [list 1]] [+= t l]] t]]
[test/add 0 [let [[t 0]] [for-in [l [list]] [+= t l]] t]]
;[test/add 1000 [byterun '[do [def i 0] [while [< i 100] [set! i [+ 1 i]]] i]]]
;[test/add #t [for [i 5 4]] #t]
;[test/add "\"Polizei\"" [def eins [ω [def say [λ [] "Eins"]]]] [def zwei [eins [ω]]] [zwei [def say [λ [] "Polizei"]]] [zwei [say]]]

[def oneTwoThreeTest [+123 5]]
[defmacro +123 [v]
          `[+ 123 ~v]]

; Having test defined somehow breaks the whole testing system, how come?
; [def test [+99 1]]

; This would interfere with quasiquote as a macro, still have to think about the consequences
;[test/add '[quasiquote [quasiquote [1 2 [unquote [unquote 3]]]]] ```[1 2 ,,,[+ 2 1]]]

; 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]]