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