]> gitweb.factorcode.org Git - factor.git/blob - basis/math/vectors/simd/simd-tests.factor
use reject instead of [ ... not ] filter.
[factor.git] / basis / math / vectors / simd / simd-tests.factor
1 USING: accessors arrays classes compiler.test compiler.tree.debugger
2 effects fry io kernel kernel.private math math.functions
3 math.private math.vectors math.vectors.simd math.ranges
4 math.vectors.simd.private prettyprint random sequences system
5 tools.test vocabs assocs compiler.cfg.debugger words
6 locals combinators cpu.architecture namespaces byte-arrays alien
7 specialized-arrays classes.struct eval classes.algebra sets
8 quotations math.constants compiler.units splitting math.matrices
9 math.vectors.simd.cords alien.data ;
10 FROM: math.vectors.simd.intrinsics => alien-vector set-alien-vector ;
11 QUALIFIED-WITH: alien.c-types c
12 SPECIALIZED-ARRAY: c:float
13 IN: math.vectors.simd.tests
14
15 ! Test type propagation
16 [ V{ float } ] [ [ { float-4 } declare norm-sq ] final-classes ] unit-test
17
18 [ V{ float } ] [ [ { float-4 } declare norm ] final-classes ] unit-test
19
20 [ V{ float-4 } ] [ [ { float-4 } declare normalize ] final-classes ] unit-test
21
22 [ V{ float-4 } ] [ [ { float-4 float-4 } declare v+ ] final-classes ] unit-test
23
24 [ V{ float } ] [ [ { float-4 } declare second ] final-classes ] unit-test
25
26 [ V{ int-4 } ] [ [ { int-4 int-4 } declare v+ ] final-classes ] unit-test
27
28 [ t ] [ [ { int-4 } declare second ] final-classes first integer class<= ] unit-test
29
30 [ V{ longlong-2 } ] [ [ { longlong-2 longlong-2 } declare v+ ] final-classes ] unit-test
31
32 [ V{ integer } ] [ [ { longlong-2 } declare second ] final-classes ] unit-test
33
34 ! Test puns; only on x86
35 cpu x86? [
36     [ double-2{ 4 1024 } ] [
37         float-4{ 0 1 0 2 }
38         [ { float-4 } declare dup v+ underlying>> double-2 boa dup v+ ] compile-call
39     ] unit-test
40 ] when
41
42 ! Fuzz testing
43 CONSTANT: simd-classes
44     {
45         char-16
46         uchar-16
47         short-8
48         ushort-8
49         int-4
50         uint-4
51         longlong-2
52         ulonglong-2
53         float-4
54         double-2
55     }
56
57 SYMBOLS: -> +vector+ +any-vector+ +scalar+ +boolean+ +nonnegative+ +literal+ ;
58
59 CONSTANT: vector-words
60     H{
61         { [v-] { +vector+ +vector+ -> +vector+ } }
62         { distance { +vector+ +vector+ -> +nonnegative+ } }
63         { n*v { +scalar+ +vector+ -> +vector+ } }
64         { n+v { +scalar+ +vector+ -> +vector+ } }
65         { n-v { +scalar+ +vector+ -> +vector+ } }
66         { n/v { +scalar+ +vector+ -> +vector+ } }
67         { norm { +vector+ -> +nonnegative+ } }
68         { norm-sq { +vector+ -> +nonnegative+ } }
69         { normalize { +vector+ -> +vector+ } }
70         { v* { +vector+ +vector+ -> +vector+ } }
71         { vs* { +vector+ +vector+ -> +vector+ } }
72         { v*n { +vector+ +scalar+ -> +vector+ } }
73         { v*high { +vector+ +vector+ -> +vector+ } }
74         { v*hs+ { +vector+ +vector+ -> +vector+ } }
75         { v+ { +vector+ +vector+ -> +vector+ } }
76         { vs+ { +vector+ +vector+ -> +vector+ } }
77         { v+- { +vector+ +vector+ -> +vector+ } }
78         { v+n { +vector+ +scalar+ -> +vector+ } }
79         { v- { +vector+ +vector+ -> +vector+ } }
80         { vneg { +vector+ -> +vector+ } }
81         { vs- { +vector+ +vector+ -> +vector+ } }
82         { v-n { +vector+ +scalar+ -> +vector+ } }
83         { v. { +vector+ +vector+ -> +scalar+ } }
84         { vsad { +vector+ +vector+ -> +scalar+ } }
85         { v/ { +vector+ +vector+ -> +vector+ } }
86         { v/n { +vector+ +scalar+ -> +vector+ } }
87         { vceiling { +vector+ -> +vector+ } }
88         { vfloor { +vector+ -> +vector+ } }
89         { vmax { +vector+ +vector+ -> +vector+ } }
90         { vmin { +vector+ +vector+ -> +vector+ } }
91         { vavg { +vector+ +vector+ -> +vector+ } }
92         { vneg { +vector+ -> +vector+ } }
93         { vtruncate { +vector+ -> +vector+ } }
94         { sum { +vector+ -> +scalar+ } }
95         { vcount { +vector+ -> +scalar+ } }
96         { vabs { +vector+ -> +vector+ } }
97         { vsqrt { +vector+ -> +vector+ } }
98         { vbitand { +vector+ +vector+ -> +vector+ } }
99         { vbitandn { +vector+ +vector+ -> +vector+ } }
100         { vbitor { +vector+ +vector+ -> +vector+ } }
101         { vbitxor { +vector+ +vector+ -> +vector+ } }
102         { vbitnot { +vector+ -> +vector+ } }
103         { vand { +vector+ +vector+ -> +vector+ } }
104         { vandn { +vector+ +vector+ -> +vector+ } }
105         { vor { +vector+ +vector+ -> +vector+ } }
106         { vxor { +vector+ +vector+ -> +vector+ } }
107         { vnot { +vector+ -> +vector+ } }
108         { vlshift { +vector+ +scalar+ -> +vector+ } }
109         { vrshift { +vector+ +scalar+ -> +vector+ } }
110         { (vmerge-head) { +vector+ +vector+ -> +vector+ } }
111         { (vmerge-tail) { +vector+ +vector+ -> +vector+ } }
112         { v<= { +vector+ +vector+ -> +vector+ } }
113         { v< { +vector+ +vector+ -> +vector+ } }
114         { v= { +vector+ +vector+ -> +vector+ } }
115         { v> { +vector+ +vector+ -> +vector+ } }
116         { v>= { +vector+ +vector+ -> +vector+ } }
117         { vunordered? { +vector+ +vector+ -> +vector+ } }
118     }
119
120 : vector-word-inputs ( schema -- seq ) { -> } split first ;
121
122 : with-ctors ( -- seq )
123     simd-classes [ [ name>> "-with" append ] [ vocabulary>> ] bi lookup-word ] map ;
124
125 : boa-ctors ( -- seq )
126     simd-classes [ [ name>> "-boa" append ] [ vocabulary>> ] bi lookup-word ] map ;
127
128 TUPLE: simd-test-failure
129     input
130     input-quot
131     unoptimized-result
132     optimized-result
133     nonintrinsic-result ;
134
135 :: check-optimizer (
136     seq
137     test-quot: ( input -- input-quot: ( -- ..v ) code-quot: ( ..v -- result ) )
138     eq-quot: ( resulta resultb -- ? )
139     --
140     failures
141 )
142     #! Use test-quot to generate a bunch of test cases from the
143     #! given inputs. Run each test case optimized and
144     #! unoptimized. Compare results with eq-quot.
145     #!
146     #! seq: sequence of inputs
147     #! test-quot: ( input -- input-quot: ( -- ..v ) code-quot: ( ..v -- result ) )
148     #! eq-quot: ( result1 result2 -- ? )
149     seq [| input |
150         input test-quot call :> ( input-quot code-quot )
151         input-quot [ class-of ] { } map-as :> input-classes
152         input-classes code-quot '[ _ declare @ ] :> code-quot'
153
154         "print-mr" get [ code-quot' regs. ] when
155         "print-checks" get [ input-quot . code-quot' . ] when
156
157         input-quot code-quot' [ [ call ] dip call ]
158         call( i c -- result ) :> unoptimized-result
159         input-quot code-quot' [ [ call ] dip compile-call ]
160         call( i c -- result ) :> optimized-result
161         input-quot code-quot' [
162             t "always-inline-simd-intrinsics" [
163                 "print-inline-mr" get [ code-quot' regs. ] when
164                 [ call ] dip compile-call
165             ] with-variable
166         ] call( i c -- result ) :> nonintrinsic-result
167
168         unoptimized-result optimized-result eq-quot call
169         optimized-result nonintrinsic-result eq-quot call
170         and
171         [ f ] [
172             input input-quot unoptimized-result optimized-result nonintrinsic-result
173             simd-test-failure boa
174         ] if
175     ] map sift
176     dup empty? [ dup ... ] unless ! Print full errors
177     ; inline
178
179 "== Checking -new constructors" print
180
181 [ { } ] [
182     simd-classes [ [ [ ] ] dip '[ _ new ] ] [ = ] check-optimizer
183 ] unit-test
184
185 [ { } ] [
186     simd-classes [ '[ _ new ] compile-call [ zero? ] all? ] reject
187 ] unit-test
188
189 "== Checking -with constructors" print
190
191 [ { } ] [
192     with-ctors [
193         [ 1000 random '[ _ ] ] dip '[ _ execute ]
194     ] [ = ] check-optimizer
195 ] unit-test
196
197 [ 0xffffffff ] [ 0xffffffff uint-4-with first ] unit-test
198
199 [ 0xffffffff ] [ 0xffffffff [ uint-4-with ] compile-call first ] unit-test
200
201 [ 0xffffffff ] [ [ 0xffffffff uint-4-with ] compile-call first ] unit-test
202
203 "== Checking -boa constructors" print
204
205 [ { } ] [
206     boa-ctors [
207         [ stack-effect in>> length [ 1000 random ] [ ] replicate-as ] keep
208         '[ _ execute ]
209     ] [ = ] check-optimizer
210 ] unit-test
211
212 [ 0xffffffff ] [ 0xffffffff 2 3 4 [ uint-4-boa ] compile-call first ] unit-test
213
214 "== Checking vector operations" print
215
216 : random-int-vector ( class -- vec )
217     new [ drop 1000 random ] map ;
218
219 : random-float-vector ( class -- vec )
220     new [
221         drop
222         1000 random
223         10 swap <array> 0/0. suffix random
224     ] map ;
225
226 : random-vector ( class elt-class -- vec )
227     float =
228     [ random-float-vector ]
229     [ random-int-vector ] if ;
230
231 :: check-vector-op ( word inputs class elt-class -- inputs quot )
232     inputs [
233         {
234             { +vector+ [ class elt-class random-vector ] }
235             { +scalar+ [ 1000 random elt-class float = [ >float ] when ] }
236         } case
237     ] [ ] map-as
238     word '[ _ execute ] ;
239
240 : remove-float-words ( alist -- alist' )
241     { distance vsqrt n/v v/n v/ normalize } unique assoc-diff ;
242
243 : remove-integer-words ( alist -- alist' )
244     { vlshift vrshift v*high v*hs+ } unique assoc-diff ;
245
246 : boolean-ops ( -- words )
247     { vand vandn vor vxor vnot vcount } ;
248
249 : remove-boolean-words ( alist -- alist' )
250     boolean-ops unique assoc-diff ;
251
252 : ops-to-check ( elt-class -- alist )
253     [ vector-words >alist ] dip
254     float = [ remove-integer-words ] [ remove-float-words ] if
255     remove-boolean-words ;
256
257 : check-vector-ops ( class elt-class compare-quot -- failures )
258     [
259         [ nip ops-to-check ] 2keep
260         '[ first2 vector-word-inputs _ _ check-vector-op ]
261     ] dip check-optimizer ; inline
262
263 : (approx=) ( x y -- ? )
264     {
265         { [ 2dup [ fp-nan? ] both? ] [ 2drop t ] }
266         { [ 2dup [ fp-nan? ] either? ] [ 2drop f ] }
267         { [ 2dup [ fp-infinity? ] either? ] [ fp-bitwise= ] }
268         { [ 2dup [ float? ] both? ] [ -1.e8 ~ ] }
269         [ = ]
270     } cond ;
271
272 : approx= ( x y -- ? )
273     2dup [ sequence? ] both?
274     [ [ (approx=) ] 2all? ] [ (approx=) ] if ;
275
276 : exact= ( x y -- ? )
277     {
278         { [ 2dup [ float? ] both? ] [ fp-bitwise= ] }
279         { [ 2dup [ sequence? ] both? ] [ [ fp-bitwise= ] 2all? ] }
280         [ = ]
281     } cond ;
282
283 : simd-classes&reps ( -- alist )
284     simd-classes [
285         {
286             { [ dup name>> "float" head? ] [ float [ approx= ] ] }
287             { [ dup name>> "double" head? ] [ float [ exact= ] ] }
288             [ fixnum [ = ] ]
289         } cond 3array
290     ] map ;
291
292 simd-classes&reps [
293     [ [ { } ] ] dip first3 '[ _ _ _ check-vector-ops ] unit-test
294 ] each
295
296 "== Checking boolean operations" print
297
298 : random-boolean-vector ( class -- vec )
299     new [ drop 2 random zero? ] map ;
300
301 :: check-boolean-op ( word inputs class elt-class -- inputs quot )
302     inputs [
303         {
304             { +vector+ [ class random-boolean-vector ] }
305             { +scalar+ [ 1000 random elt-class float = [ >float ] when ] }
306         } case
307     ] [ ] map-as
308     word '[ _ execute ] ;
309
310 : check-boolean-ops ( class elt-class compare-quot -- seq )
311     [
312         [ boolean-ops [ dup vector-words at ] { } map>assoc ] 2dip
313         '[ first2 vector-word-inputs _ _ check-boolean-op ]
314     ] dip check-optimizer ; inline
315
316 simd-classes&reps [
317     [ [ { } ] ] dip first3 '[ _ _ _ check-boolean-ops ] unit-test
318 ] each
319
320 "== Checking vector blend" print
321
322 [ char-16{ 0 1 22 33 4 5 6 77 8 99 110 121 12 143 14 15 } ]
323 [
324     char-16{ t  t  f  f  t  t  t  f  t  f   f   f   t   f   t   t }
325     char-16{ 0  1  2  3  4  5  6  7  8  9  10  11  12  13  14  15 }
326     char-16{ 0 11 22 33 44 55 66 77 88 99 110 121 132 143 154 165 } v?
327 ] unit-test
328
329 [ char-16{ 0 1 22 33 4 5 6 77 8 99 110 121 12 143 14 15 } ]
330 [
331     char-16{ t  t  f  f  t  t  t  f  t  f   f   f   t   f   t   t }
332     char-16{ 0  1  2  3  4  5  6  7  8  9  10  11  12  13  14  15 }
333     char-16{ 0 11 22 33 44 55 66 77 88 99 110 121 132 143 154 165 }
334     [ { char-16 char-16 char-16 } declare v? ] compile-call
335 ] unit-test
336
337 [ int-4{ 1 22 33 4 } ]
338 [ int-4{ t f f t } int-4{ 1 2 3 4 } int-4{ 11 22 33 44 } v? ] unit-test
339
340 [ int-4{ 1 22 33 4 } ]
341 [
342     int-4{ t f f t } int-4{ 1 2 3 4 } int-4{ 11 22 33 44 }
343     [ { int-4 int-4 int-4 } declare v? ] compile-call
344 ] unit-test
345
346 [ float-4{ 1.0 22.0 33.0 4.0 } ]
347 [ float-4{ t f f t } float-4{ 1.0 2.0 3.0 4.0 } float-4{ 11.0 22.0 33.0 44.0 } v? ] unit-test
348
349 [ float-4{ 1.0 22.0 33.0 4.0 } ]
350 [
351     float-4{ t f f t } float-4{ 1.0 2.0 3.0 4.0 } float-4{ 11.0 22.0 33.0 44.0 }
352     [ { float-4 float-4 float-4 } declare v? ] compile-call
353 ] unit-test
354
355 "== Checking shifts and permutations" print
356
357 [ char-16{ 0 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 } ]
358 [ char-16{ 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 } 1 hlshift ] unit-test
359
360 [ char-16{ 0 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 } ]
361 [ char-16{ 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 } [ { char-16 } declare 1 hlshift ] compile-call ] unit-test
362
363 [ char-16{ 0 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 } ]
364 [ char-16{ 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 } [ { char-16 } declare 1 >bignum hlshift ] compile-call ] unit-test
365
366 [ char-16{ 0 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 } ]
367 [ char-16{ 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 } 1 [ { char-16 fixnum } declare hlshift ] compile-call ] unit-test
368
369 [ char-16{ 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 0 } ]
370 [ char-16{ 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 } 1 hrshift ] unit-test
371
372 [ char-16{ 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 0 } ]
373 [ char-16{ 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 } [ { char-16 } declare 1 hrshift ] compile-call ] unit-test
374
375 [ char-16{ 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 0 } ]
376 [ char-16{ 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 } [ { char-16 } declare 1 >bignum hrshift ] compile-call ] unit-test
377
378 [ char-16{ 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 0 } ]
379 [ char-16{ 1 2 4 8 1 2 4 8 1 2 4 8 1 2 4 8 } 1 [ { char-16 fixnum } declare hrshift ] compile-call ] unit-test
380
381 [ int-4{ 4 8 12 16 } ]
382 [ int-4{ 1 2 3 4 } 2 vlshift ] unit-test
383
384 [ int-4{ 4 8 12 16 } ]
385 [ int-4{ 1 2 3 4 } 2 [ { int-4 fixnum } declare vlshift ] compile-call ] unit-test
386
387 [ int-4{ 4 8 12 16 } ]
388 [ int-4{ 1 2 3 4 } 2 >bignum [ { int-4 bignum } declare vlshift ] compile-call ] unit-test
389
390 ! Invalid inputs should not cause the compiler to throw errors
391 [ ] [
392     [ [ { int-4 } declare t hrshift ] ( a -- b ) define-temp drop ] with-compilation-unit
393 ] unit-test
394
395 [ ] [
396     [ [ { int-4 } declare { 3 2 1 } vshuffle ] ( a -- b ) define-temp drop ] with-compilation-unit
397 ] unit-test
398
399 ! Shuffles
400 : shuffles-for ( n -- shuffles )
401     {
402         { 2 [
403             {
404                 { 0 1 }
405                 { 1 1 }
406                 { 1 0 }
407                 { 0 0 }
408             }
409         ] }
410         { 4 [
411             {
412                 { 1 2 3 0 }
413                 { 0 1 2 3 }
414                 { 1 1 2 2 }
415                 { 0 0 1 1 }
416                 { 2 2 3 3 }
417                 { 0 1 0 1 }
418                 { 2 3 2 3 }
419                 { 0 0 2 2 }
420                 { 1 1 3 3 }
421                 { 0 1 0 1 }
422                 { 2 2 3 3 }
423             }
424         ] }
425         { 8 [
426             4 shuffles-for
427             4 shuffles-for
428             [ [ 4 + ] map ] map
429             [ append ] 2map
430         ] }
431         [ dup '[ _ random ] replicate 1array ]
432     } case ;
433
434 : 2shuffles-for ( n -- shuffles )
435     {
436         { 2 [
437             {
438                 { 0 1 }
439                 { 0 3 }
440                 { 2 3 }
441                 { 2 0 }
442             }
443         ] }
444         { 4 [
445             {
446                 { 0 1 2 3 }
447                 { 4 1 2 3 }
448                 { 0 5 2 3 }
449                 { 0 1 6 3 }
450                 { 0 1 2 7 }
451                 { 4 5 2 3 }
452                 { 0 1 6 7 }
453                 { 4 5 6 7 }
454                 { 0 5 2 7 }
455             }
456         ] }
457         { 8 [
458             4 2shuffles-for
459             4 2shuffles-for
460             [ [ 8 + ] map ] map
461             [ append ] 2map
462         ] }
463         [ dup 2 * '[ _ random ] replicate 1array ]
464     } case ;
465
466 simd-classes [
467     [ [ { } ] ] dip
468     [ new length shuffles-for ] keep
469     '[
470         _ [ [ _ new [ length iota ] keep like 1quotation ] dip '[ _ vshuffle ] ]
471         [ = ] check-optimizer
472     ] unit-test
473 ] each
474
475 simd-classes [
476     [ [ { } ] ] dip
477     [ new length 2shuffles-for ] keep
478     '[
479         _ [ [
480             _ new
481             [ [ length iota ] keep like ]
482             [ [ length dup dup + [a,b) ] keep like ] bi [ ] 2sequence
483         ] dip '[ _ vshuffle2-elements ] ]
484         [ = ] check-optimizer
485     ] unit-test
486 ] each
487
488 "== Checking variable shuffles" print
489
490 : random-shift-vector ( class -- vec )
491     new [ drop 16 random ] map ;
492
493 :: test-shift-vector ( class -- ? )
494     [
495         class random-int-vector :> src
496         char-16 random-shift-vector :> perm
497         { class char-16 } :> decl
498     
499         src perm vshuffle
500         src perm [ decl declare vshuffle ] compile-call
501         =
502     ] call( -- ? ) ;
503
504 { char-16 uchar-16 short-8 ushort-8 int-4 uint-4 longlong-2 ulonglong-2 }
505 [ 10 swap '[ [ t ] [ _ test-shift-vector ] unit-test ] times ] each
506
507 "== Checking vector tests" print
508
509 :: test-vector-tests-bool ( vector declaration -- none? any? all? )
510     [
511         vector
512         [ [ declaration declare vnone? ] compile-call ]
513         [ [ declaration declare vany?  ] compile-call ]
514         [ [ declaration declare vall?  ] compile-call ] tri
515     ] call( -- none? any? all? ) ;
516
517 : yes ( -- x ) t ;
518 : no ( -- x ) f ;
519
520 :: test-vector-tests-branch ( vector declaration -- none? any? all? )
521     [
522         vector
523         [ [ declaration declare vnone? [ yes ] [ no ] if ] compile-call ]
524         [ [ declaration declare vany?  [ yes ] [ no ] if ] compile-call ]
525         [ [ declaration declare vall?  [ yes ] [ no ] if ] compile-call ] tri
526     ] call( -- none? any? all? ) ;
527
528 TUPLE: inconsistent-vector-test bool branch ;
529
530 : ?inconsistent ( bool branch -- ?/inconsistent )
531     2dup = [ drop ] [ inconsistent-vector-test boa ] if ;
532
533 :: test-vector-tests ( vector decl -- none? any? all? )
534     [
535         vector decl test-vector-tests-bool :> ( bool-none bool-any bool-all )
536         vector decl test-vector-tests-branch :> ( branch-none branch-any branch-all )
537         
538         bool-none branch-none ?inconsistent
539         bool-any  branch-any  ?inconsistent
540         bool-all  branch-all  ?inconsistent
541     ] call( -- none? any? all? ) ;
542
543 [ f t t ]
544 [ float-4{ t t t t } { float-4 } test-vector-tests ] unit-test
545 [ f t f ]
546 [ float-4{ f t t t } { float-4 } test-vector-tests ] unit-test
547 [ t f f ]
548 [ float-4{ f f f f } { float-4 } test-vector-tests ] unit-test
549
550 [ f t t ]
551 [ double-2{ t t } { double-2 } test-vector-tests ] unit-test
552 [ f t f ]
553 [ double-2{ f t } { double-2 } test-vector-tests ] unit-test
554 [ t f f ]
555 [ double-2{ f f } { double-2 } test-vector-tests ] unit-test
556
557 [ f t t ]
558 [ int-4{ t t t t } { int-4 } test-vector-tests ] unit-test
559 [ f t f ]
560 [ int-4{ f t t t } { int-4 } test-vector-tests ] unit-test
561 [ t f f ]
562 [ int-4{ f f f f } { int-4 } test-vector-tests ] unit-test
563
564 "== Checking element access" print
565
566 ! Test element access -- it should box bignums for int-4 on x86
567 : test-accesses ( seq -- failures )
568     [ length iota dup [ >bignum ] map append ] keep
569     '[ [ _ 1quotation ] dip '[ _ swap nth ] ] [ = ] check-optimizer ; inline
570
571 [ { } ] [ float-4{ 1.0 2.0 3.0 4.0 } test-accesses ] unit-test
572 [ { } ] [ int-4{ 0x7fffffff 3 4 -8 } test-accesses ] unit-test
573 [ { } ] [ uint-4{ 0xffffffff 2 3 4 } test-accesses ] unit-test
574
575 [ 0x7fffffff ] [ int-4{ 0x7fffffff 3 4 -8 } first ] unit-test
576 [ -8 ] [ int-4{ 0x7fffffff 3 4 -8 } last ] unit-test
577 [ 0xffffffff ] [ uint-4{ 0xffffffff 2 3 4 } first ] unit-test
578
579 [ { } ] [ double-2{ 1.0 2.0 } test-accesses ] unit-test
580 [ { } ] [ longlong-2{ 1 2 } test-accesses ] unit-test
581 [ { } ] [ ulonglong-2{ 1 2 } test-accesses ] unit-test
582
583 "== Checking broadcast" print
584 : test-broadcast ( seq -- failures )
585     [ length iota >array ] keep
586     '[ [ _ 1quotation ] dip '[ _ vbroadcast ] ] [ = ] check-optimizer ;
587
588 [ { } ] [ float-4{ 1.0 2.0 3.0 4.0 } test-broadcast ] unit-test
589 [ { } ] [ int-4{ 0x7fffffff 3 4 -8 } test-broadcast ] unit-test
590 [ { } ] [ uint-4{ 0xffffffff 2 3 4 } test-broadcast ] unit-test
591
592 [ { } ] [ double-2{ 1.0 2.0 } test-broadcast ] unit-test
593 [ { } ] [ longlong-2{ 1 2 } test-broadcast ] unit-test
594 [ { } ] [ ulonglong-2{ 1 2 } test-broadcast ] unit-test
595
596 ! Make sure we use the fallback in the correct situations
597 [ int-4{ 3 3 3 3 } ] [ int-4{ 12 34 3 17 } 2 [ { int-4 fixnum } declare vbroadcast ] compile-call ] unit-test
598
599 "== Checking alien operations" print
600
601 [ float-4{ 1 2 3 4 } ] [
602     [
603         float-4{ 1 2 3 4 }
604         underlying>> 0 float-4-rep alien-vector
605     ] compile-call float-4 boa
606 ] unit-test
607
608 [ B{ 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 } ] [
609     16 [ 1 ] B{ } replicate-as 16 <byte-array>
610     [
611         0 [
612             { byte-array c-ptr fixnum } declare
613             float-4-rep set-alien-vector
614         ] compile-call
615     ] keep
616 ] unit-test
617
618 [ float-array{ 1 2 3 4 } ] [
619     [
620         float-array{ 1 2 3 4 } underlying>>
621         float-array{ 4 3 2 1 } clone
622         [ underlying>> 0 float-4-rep set-alien-vector ] keep
623     ] compile-call
624 ] unit-test
625
626 STRUCT: simd-struct
627 { x float-4 }
628 { y longlong-2 }
629 { z double-2 }
630 { w int-4 } ;
631
632 [ t ] [ [ simd-struct <struct> ] compile-call >c-ptr [ 0 = ] all? ] unit-test
633
634 [
635     float-4{ 1 2 3 4 }
636     longlong-2{ 2 1 }
637     double-2{ 4 3 }
638     int-4{ 1 2 3 4 }
639 ] [
640     simd-struct <struct>
641     float-4{ 1 2 3 4 } >>x
642     longlong-2{ 2 1 } >>y
643     double-2{ 4 3 } >>z
644     int-4{ 1 2 3 4 } >>w
645     { [ x>> ] [ y>> ] [ z>> ] [ w>> ] } cleave
646 ] unit-test
647
648 [
649     float-4{ 1 2 3 4 }
650     longlong-2{ 2 1 }
651     double-2{ 4 3 }
652     int-4{ 1 2 3 4 }
653 ] [
654     [
655         simd-struct <struct>
656         float-4{ 1 2 3 4 } >>x
657         longlong-2{ 2 1 } >>y
658         double-2{ 4 3 } >>z
659         int-4{ 1 2 3 4 } >>w
660         { [ x>> ] [ y>> ] [ z>> ] [ w>> ] } cleave
661     ] compile-call
662 ] unit-test
663
664 "== Misc tests" print
665
666 [ ] [ char-16 new 1array stack. ] unit-test
667
668 ! Test some sequence protocol stuff
669 [ t ] [ 4 double-4{ 1 2 3 4 } new-sequence double-4? ] unit-test
670 [ double-4{ 2 3 4 5 } ] [ double-4{ 1 2 3 4 } [ 1 + ] map ] unit-test
671
672 ! Test cross product
673 [ float-4{ 0.0 0.0 1.0 0.0 } ] [ float-4{ 1.0 0.0 0.0 0.0 } float-4{ 0.0 1.0 0.0 0.0 } cross ] unit-test
674 [ float-4{ 0.0 0.0 1.0 0.0 } ] [ float-4{ 1.0 0.0 0.0 0.0 } float-4{ 0.0 1.0 0.0 0.0 } [ { float-4 float-4 } declare cross ] compile-call ] unit-test
675 [ float-4{ 0.0 -1.0 0.0 0.0 } ] [ float-4{ 1.0 0.0 0.0 0.0 } float-4{ 0.0 0.0 1.0 0.0 } cross ] unit-test
676 [ float-4{ 0.0 -1.0 0.0 0.0 } ] [ float-4{ 1.0 0.0 0.0 0.0 } float-4{ 0.0 0.0 1.0 0.0 } [ { float-4 float-4 } declare cross ] compile-call ] unit-test
677
678 [ double-4{ 0.0 0.0 1.0 0.0 } ] [ double-4{ 1.0 0.0 0.0 0.0 } double-4{ 0.0 1.0 0.0 0.0 } cross ] unit-test
679 [ double-4{ 0.0 0.0 1.0 0.0 } ] [ double-4{ 1.0 0.0 0.0 0.0 } double-4{ 0.0 1.0 0.0 0.0 } [ { double-4 double-4 } declare cross ] compile-call ] unit-test
680 [ double-4{ 0.0 -1.0 0.0 0.0 } ] [ double-4{ 1.0 0.0 0.0 0.0 } double-4{ 0.0 0.0 1.0 0.0 } cross ] unit-test
681 [ double-4{ 0.0 -1.0 0.0 0.0 } ] [ double-4{ 1.0 0.0 0.0 0.0 } double-4{ 0.0 0.0 1.0 0.0 } [ { double-4 double-4 } declare cross ] compile-call ] unit-test
682
683 ! CSSA bug
684 [ 4000000 ] [
685     int-4{ 1000 1000 1000 1000 }
686     [ { int-4 } declare dup [ * ] [ + ] 2map-reduce ] compile-call
687 ] unit-test
688
689 ! Coalescing was too aggressive
690 :: broken ( axis theta -- a b c )
691    axis { float-4 } declare drop
692    theta { float } declare drop
693
694    theta cos float-4-with :> cc
695    theta sin float-4-with :> ss
696    
697    axis cc v+ :> diagonal
698
699    diagonal cc ss ; inline
700
701 [ t ] [
702     float-4{ 1.0 0.0 1.0 0.0 } pi [ broken 3array ]
703     [ compile-call ] [ call ] 3bi =
704 ] unit-test
705
706 ! Spilling SIMD values -- this basically just tests that the
707 ! stack was aligned properly by the runtime
708
709 : simd-spill-test-1 ( a b c -- v )
710     { float-4 float-4 float } declare 
711     [ v+ ] dip sin v*n ;
712
713 [ float-4{ 0 0 0 0 } ]
714 [ float-4{ 1 2 3 4 } float-4{ 4 5 6 7 } 0.0 simd-spill-test-1 ] unit-test
715
716 : simd-spill-test-2 ( a b d c -- v )
717     { float float-4 float-4 float } declare 
718     [ [ 3.0 + ] 2dip v+ ] dip sin v*n n*v ;
719
720 [ float-4{ 0 0 0 0 } ]
721 [ 5.0 float-4{ 1 2 3 4 } float-4{ 4 5 6 7 } 0.0 simd-spill-test-2 ] unit-test
722
723 : callback-1 ( -- c )
724     c:int { c:int c:int c:int c:int c:int } cdecl [ + + + + ] alien-callback ;
725
726 : indirect-1 ( x x x x x c -- y )
727     c:int { c:int c:int c:int c:int c:int } cdecl alien-indirect ; inline
728
729 : simd-spill-test-3 ( a b d c -- v )
730     { float float-4 float-4 float } declare
731     [ [ 3.0 + ] 2dip v+ ] dip sin v*n n*v
732     10 5 100 50 500 callback-1 indirect-1 665 assert= ;
733
734 [ float-4{ 0 0 0 0 } ]
735 [ 5.0 float-4{ 1 2 3 4 } float-4{ 4 5 6 7 } 0.0 simd-spill-test-3 ] unit-test
736
737 ! Stack allocation of SIMD values -- make sure that everything is
738 ! aligned right
739
740 : simd-stack-test ( -- b c )
741     { c:int float-4 } [
742         [ 123 swap 0 c:int c:set-alien-value ]
743         [ float-4{ 1 2 3 4 } swap 0 float-4 c:set-alien-value ] bi*
744     ] with-out-parameters ;
745
746 [ 123 float-4{ 1 2 3 4 } ] [ simd-stack-test ] unit-test
747
748 ! Stack allocation + spilling
749
750 : (simd-stack-spill-test) ( -- n ) 17 ;
751
752 : simd-stack-spill-test ( x -- b c )
753     { c:int } [
754         123 swap 0 c:int c:set-alien-value
755         >float (simd-stack-spill-test) float-4-with swap cos v*n
756     ] with-out-parameters ;
757
758 [ ] [
759     1.047197551196598 simd-stack-spill-test
760     [ float-4{ 8.5 8.5 8.5 8.5 } approx= t assert= ]
761     [ 123 assert= ]
762     bi*
763 ] unit-test