(no commit message)
[libreriscv.git] / openpower / sv / svp64 / appendix.mdwn
1 # Appendix
2
3 * <https://bugs.libre-soc.org/show_bug.cgi?id=574>
4 * <https://bugs.libre-soc.org/show_bug.cgi?id=558#c47>
5 * <https://bugs.libre-soc.org/show_bug.cgi?id=697>
6
7 This is the appendix to [[sv/svp64]], providing explanations of modes
8 etc. leaving the main svp64 page's primary purpose as outlining the
9 instruction format.
10
11 Table of contents:
12
13 [[!toc]]
14
15 # XER, SO and other global flags
16
17 Vector systems are expected to be high performance. This is achieved
18 through parallelism, which requires that elements in the vector be
19 independent. XER SO and other global "accumulation" flags (CR.OV) cause
20 Read-Write Hazards on single-bit global resources, having a significant
21 detrimental effect.
22
23 Consequently in SV, XER.SO and CR.OV behaviour is disregarded (including
24 in `cmp` instructions). XER is simply neither read nor written.
25 This includes when `scalar identity behaviour` occurs. If precise
26 OpenPOWER v3.0/1 scalar behaviour is desired then OpenPOWER v3.0/1
27 instructions should be used without an SV Prefix.
28
29 An interesting side-effect of this decision is that the OE flag is now
30 free for other uses when SV Prefixing is used.
31
32 Regarding XER.CA: this does not fit either: it was designed for a scalar
33 ISA. Instead, both carry-in and carry-out go into the CR.so bit of a given
34 Vector element. This provides a means to perform large parallel batches
35 of Vectorised carry-capable additions. crweird instructions can be used
36 to transfer the CRs in and out of an integer, where bitmanipulation
37 may be performed to analyse the carry bits (including carry lookahead
38 propagation) before continuing with further parallel additions.
39
40 # v3.0B/v3.1 relevant instructions
41
42 SV is primarily designed for use as an efficient hybrid 3D GPU / VPU /
43 CPU ISA.
44
45 As mentioned above, OE=1 is not applicable in SV, freeing this bit for
46 alternative uses. Additionally, Vectorisation of the VSX SIMD system
47 likewise makes no sense whatsoever. SV *replaces* VSX and provides,
48 at the very minimum, predication (which VSX was designed without).
49 Thus all VSX Major Opcodes - all of them - are "unused" and must raise
50 illegal instruction exceptions in SV Prefix Mode.
51
52 Likewise, `lq` (Load Quad), and Load/Store Multiple make no sense to
53 have because they are not only provided by SV, the SV alternatives may
54 be predicated as well, making them far better suited to use in function
55 calls and context-switching.
56
57 Additionally, some v3.0/1 instructions simply make no sense at all in a
58 Vector context: `rfid` falls into this category,
59 as well as `sc` and `scv`. Here there is simply no point
60 trying to Vectorise them: the standard OpenPOWER v3.0/1 instructions
61 should be called instead.
62
63 Fortuitously this leaves several Major Opcodes free for use by SV
64 to fit alternative future instructions. In a 3D context this means
65 Vector Product, Vector Normalise, [[sv/mv.swizzle]], Texture LD/ST
66 operations, and others critical to an efficient, effective 3D GPU and
67 VPU ISA. With such instructions being included as standard in other
68 commercially-successful GPU ISAs it is likewise critical that a 3D
69 GPU/VPU based on svp64 also have such instructions.
70
71 Note however that svp64 is stand-alone and is in no way
72 critically dependent on the existence or provision of 3D GPU or VPU
73 instructions. These should be considered extensions, and their discussion
74 and specification is out of scope for this document.
75
76 Note, again: this is *only* under svp64 prefixing. Standard v3.0B /
77 v3.1B is *not* altered by svp64 in any way.
78
79 ## Major opcode map (v3.0B)
80
81 This table is taken from v3.0B.
82 Table 9: Primary Opcode Map (opcode bits 0:5)
83
84 | 000 | 001 | 010 | 011 | 100 | 101 | 110 | 111
85 000 | | | tdi | twi | EXT04 | | | mulli | 000
86 001 | subfic | | cmpli | cmpi | addic | addic. | addi | addis | 001
87 010 | bc/l/a | EXT17 | b/l/a | EXT19 | rlwimi| rlwinm | | rlwnm | 010
88 011 | ori | oris | xori | xoris | andi. | andis. | EXT30 | EXT31 | 011
89 100 | lwz | lwzu | lbz | lbzu | stw | stwu | stb | stbu | 100
90 101 | lhz | lhzu | lha | lhau | sth | sthu | lmw | stmw | 101
91 110 | lfs | lfsu | lfd | lfdu | stfs | stfsu | stfd | stfdu | 110
92 111 | lq | EXT57 | EXT58 | EXT59 | EXT60 | EXT61 | EXT62 | EXT63 | 111
93 | 000 | 001 | 010 | 011 | 100 | 101 | 110 | 111
94
95 ## Suitable for svp64-only
96
97 This is the same table containing v3.0B Primary Opcodes except those that
98 make no sense in a Vectorisation Context have been removed. These removed
99 POs can, *in the SV Vector Context only*, be assigned to alternative
100 (Vectorised-only) instructions, including future extensions.
101
102 Note, again, to emphasise: outside of svp64 these opcodes **do not**
103 change. When not prefixed with svp64 these opcodes **specifically**
104 retain their v3.0B / v3.1B OpenPOWER Standard compliant meaning.
105
106 | 000 | 001 | 010 | 011 | 100 | 101 | 110 | 111
107 000 | | | | | | | | mulli | 000
108 001 | subfic | | cmpli | cmpi | addic | addic. | addi | addis | 001
109 010 | | | | EXT19 | rlwimi| rlwinm | | rlwnm | 010
110 011 | ori | oris | xori | xoris | andi. | andis. | EXT30 | EXT31 | 011
111 100 | lwz | lwzu | lbz | lbzu | stw | stwu | stb | stbu | 100
112 101 | lhz | lhzu | lha | lhau | sth | sthu | | | 101
113 110 | lfs | lfsu | lfd | lfdu | stfs | stfsu | stfd | stfdu | 110
114 111 | | | EXT58 | EXT59 | | EXT61 | | EXT63 | 111
115 | 000 | 001 | 010 | 011 | 100 | 101 | 110 | 111
116
117 It is important to note that having a different v3.0B Scalar opcode
118 that is different from an SVP64 one is highly undesirable: the complexity
119 in the decoder is greatly increased.
120
121 # Single Predication
122
123 This is a standard mode normally found in Vector ISAs. every element in every source Vector and in the destination uses the same bit of one single predicate mask.
124
125 In SVSTATE, for Single-predication, implementors MUST increment both srcstep and dststep: unlike Twin-Predication the two must be equal at all times.
126
127 # Twin Predication
128
129 This is a novel concept that allows predication to be applied to a single
130 source and a single dest register. The following types of traditional
131 Vector operations may be encoded with it, *without requiring explicit
132 opcodes to do so*
133
134 * VSPLAT (a single scalar distributed across a vector)
135 * VEXTRACT (like LLVM IR [`extractelement`](https://releases.llvm.org/11.0.0/docs/LangRef.html#extractelement-instruction))
136 * VINSERT (like LLVM IR [`insertelement`](https://releases.llvm.org/11.0.0/docs/LangRef.html#insertelement-instruction))
137 * VCOMPRESS (like LLVM IR [`llvm.masked.compressstore.*`](https://releases.llvm.org/11.0.0/docs/LangRef.html#llvm-masked-compressstore-intrinsics))
138 * VEXPAND (like LLVM IR [`llvm.masked.expandload.*`](https://releases.llvm.org/11.0.0/docs/LangRef.html#llvm-masked-expandload-intrinsics))
139
140 Those patterns (and more) may be applied to:
141
142 * mv (the usual way that V\* ISA operations are created)
143 * exts\* sign-extension
144 * rwlinm and other RS-RA shift operations (**note**: excluding
145 those that take RA as both a src and dest. These are not
146 1-src 1-dest, they are 2-src, 1-dest)
147 * LD and ST (treating AGEN as one source)
148 * FP fclass, fsgn, fneg, fabs, fcvt, frecip, fsqrt etc.
149 * Condition Register ops mfcr, mtcr and other similar
150
151 This is a huge list that creates extremely powerful combinations,
152 particularly given that one of the predicate options is `(1<<r3)`
153
154 Additional unusual capabilities of Twin Predication include a back-to-back
155 version of VCOMPRESS-VEXPAND which is effectively the ability to do
156 sequentially ordered multiple VINSERTs. The source predicate selects a
157 sequentially ordered subset of elements to be inserted; the destination
158 predicate specifies the sequentially ordered recipient locations.
159 This is equivalent to
160 `llvm.masked.compressstore.*`
161 followed by
162 `llvm.masked.expandload.*`
163
164 # Reduce modes
165
166 Reduction in SVP64 is deterministic and somewhat of a misnomer. A normal
167 Vector ISA would have explicit Reduce opcodes with defined characteristics
168 per operation: in SX Aurora there is even an additional scalar argument
169 containing the initial reduction value, and the default is either 0
170 or 1 depending on the specifics of the explicit opcode.
171 SVP64 fundamentally has to
172 utilise *existing* Scalar Power ISA v3.0B operations, which presents some
173 unique challenges.
174
175 The solution turns out to be to simply define reduction as permitting
176 deterministic element-based schedules to be issued using the base Scalar
177 operations, and to rely on the underlying microarchitecture to resolve
178 Register Hazards at the element level. This goes back to
179 the fundamental principle that SV is nothing more than a Sub-Program-Counter
180 sitting between Decode and Issue phases.
181
182 Microarchitectures *may* take opportunities to parallelise the reduction
183 but only if in doing so they preserve Program Order at the Element Level.
184 Opportunities where this is possible include an `OR` operation
185 or a MIN/MAX operation: it may be possible to parallelise the reduction,
186 but for Floating Point it is not permitted due to different results
187 being obtained if the reduction is not executed in strict sequential
188 order.
189
190 In essence it becomes the programmer's responsibility to leverage the
191 pre-determined schedules to desired effect.
192
193 ## Scalar result reduce mode
194
195 Scalar Reduction per se does not exist, instead is implemented in SVP64
196 as a simple and natural relaxation of the usual restriction on the Vector
197 Looping which would terminate if the destination was marked as a Scalar.
198 Scalar Reduction by contrast *keeps issuing Vector Element Operations*
199 even though the destination register is marked as scalar.
200 Thus it is up to the programmer to be aware of this and observe some
201 conventions.
202
203 It is also important to appreciate that there is no
204 actual imposition or restriction on how this mode is utilised: there
205 will therefore be several valuable uses (including Vector Iteration
206 and "Reverse-Gear")
207 and it is up to the programmer to make best use of the capability
208 provided.
209
210 In this mode, which is suited to operations involving carry or overflow,
211 one register must be identified by the programmer as being the "accumulator".
212 Scalar reduction is thus categorised by:
213
214 * One of the sources is a Vector
215 * the destination is a scalar
216 * optionally but most usefully when one source scalar register is
217 also the scalar destination (which may be informally termed
218 the "accumulator")
219 * That the source register type is the same as the destination register
220 type identified as the "accumulator". scalar reduction on `cmp`,
221 `setb` or `isel` makes no sense for example because of the mixture
222 between CRs and GPRs.
223
224 *Note that issuing instructions in Scalar reduce mode such as `setb`
225 are neither `UNDEFINED` nor prohibited, despite them not making much
226 sense at first glance.
227 Scalar reduce is strictly defined behaviour, and the cost in
228 hardware terms of prohibition of seemingly non-sensical operations is too great.
229 Therefore it is permitted and required to be executed successfully.
230 Implementors **MAY** choose to optimise such instructions in instances
231 where their use results in "extraneous execution", i.e. where it is clear
232 that the sequence of operations, comprising multiple overwrites to
233 a scalar destination **without** cumulative, iterative, or reductive
234 behaviour (no "accumulator"), may discard all but the last element
235 operation. Identification
236 of such is trivial to do for `setb` and `cmp`: the source register type is
237 a completely different register file from the destination*
238
239 Typical applications include simple operations such as `ADD r3, r10.v,
240 r3` where, clearly, r3 is being used to accumulate the addition of all
241 elements is the vector starting at r10.
242
243 # add RT, RA,RB but when RT==RA
244 for i in range(VL):
245 iregs[RA] += iregs[RB+i] # RT==RA
246
247 However, *unless* the operation is marked as "mapreduce", SV ordinarily
248 **terminates** at the first scalar operation. Only by marking the
249 operation as "mapreduce" will it continue to issue multiple sub-looped
250 (element) instructions in `Program Order`.
251
252 To perform the loop in reverse order, the ```RG``` (reverse gear) bit must be set. This may be useful in situations where the results may be different
253 (floating-point) if executed in a different order. Given that there is
254 no actual prohibition on Reduce Mode being applied when the destination
255 is a Vector, the "Reverse Gear" bit turns out to be a way to apply Iterative
256 or Cumulative Vector operations in reverse. `sv.add/rg r3.v, r4.v, r4.v`
257 for example will start at the opposite end of the Vector and push
258 a cumulative series of overlapping add operations into the Execution units of
259 the underlying hardware.
260
261 Other examples include shift-mask operations where a Vector of inserts
262 into a single destination register is required, as a way to construct
263 a value quickly from multiple arbitrary bit-ranges and bit-offsets.
264 Using the same register as both the source and destination, with Vectors
265 of different offsets masks and values to be inserted has multiple
266 applications including Video, cryptography and JIT compilation.
267
268 Subtract and Divide are still permitted to be executed in this mode,
269 although from an algorithmic perspective it is strongly discouraged.
270 It would be better to use addition followed by one final subtract,
271 or in the case of divide, to get better accuracy, to perform a multiply
272 cascade followed by a final divide.
273
274 Note that single-operand or three-operand scalar-dest reduce is perfectly
275 well permitted: the programmer may still declare one register, used as
276 both a Vector source and Scalar destination, to be utilised as
277 the "accumulator". In the case of `sv.fmadds` and `sv.maddhw` etc
278 this naturally fits well with the normal expected usage of these
279 operations.
280
281 If an interrupt or exception occurs in the middle of the scalar mapreduce,
282 the scalar destination register **MUST** be updated with the current
283 (intermediate) result, because this is how ```Program Order``` is
284 preserved (Vector Loops are to be considered to be just another way of issuing instructions
285 in Program Order). In this way, after return from interrupt,
286 the scalar mapreduce may continue where it left off. This provides
287 "precise" exception behaviour.
288
289 Note that hardware is perfectly permitted to perform multi-issue
290 parallel optimisation of the scalar reduce operation: it's just that
291 as far as the user is concerned, all exceptions and interrupts **MUST**
292 be precise.
293
294 ## Vector result reduce mode
295
296 Vector Reduce Mode issues a deterministic tree-reduction schedule to the underlying micro-architecture. Like Scalar reduction, the "Scalar Base"
297 (Power ISA v3.0B) operation is leveraged, unmodified, to give the
298 *appearance* and *effect* of Reduction.
299
300 Given that the tree-reduction schedule is deterministic,
301 Interrupts and exceptions
302 can therefore also be precise. The final result will be in the first
303 non-predicate-masked-out destination element, but due again to
304 the deterministic schedule programmers may find uses for the intermediate
305 results.
306
307 When Rc=1 a corresponding Vector of co-resultant CRs is also
308 created. No special action is taken: the result and its CR Field
309 are stored "as usual" exactly as all other SVP64 Rc=1 operations.
310
311 ## Sub-Vector Horizontal Reduction
312
313 Note that when SVM is clear and SUBVL!=1 the sub-elements are
314 *independent*, i.e. they are mapreduced per *sub-element* as a result.
315 illustration with a vec2:
316
317 result.x = op(iregs[RA].x, iregs[RA+1].x)
318 result.y = op(iregs[RA].y, iregs[RA+1].y)
319 for i in range(2, VL):
320 result.x = op(result.x, iregs[RA+i].x)
321 result.y = op(result.y, iregs[RA+i].y)
322
323 Note here that Rc=1 does not make sense when SVM is clear and SUBVL!=1.
324
325 When SVM is set and SUBVL!=1, another variant is enabled: horizontal
326 subvector mode. Example for a vec3:
327
328 for i in range(VL):
329 result = iregs[RA+i].x
330 result = op(result, iregs[RA+i].y)
331 result = op(result, iregs[RA+i].z)
332 iregs[RT+i] = result
333
334 In this mode, when Rc=1 the Vector of CRs is as normal: each result
335 element creates a corresponding CR element (for the final, reduced, result).
336
337 # Fail-on-first
338
339 Data-dependent fail-on-first has two distinct variants: one for LD/ST,
340 the other for arithmetic operations (actually, CR-driven). Note in each
341 case the assumption is that vector elements are required appear to be
342 executed in sequential Program Order, element 0 being the first.
343
344 * LD/ST ffirst treats the first LD/ST in a vector (element 0) as an
345 ordinary one. Exceptions occur "as normal". However for elements 1
346 and above, if an exception would occur, then VL is **truncated** to the
347 previous element.
348 * Data-driven (CR-driven) fail-on-first activates when Rc=1 or other
349 CR-creating operation produces a result (including cmp). Similar to
350 branch, an analysis of the CR is performed and if the test fails, the
351 vector operation terminates and discards all element operations at and
352 above the current one, and VL is truncated to either
353 the *previous* element or the current one, depending on whether
354 VLi (VL "inclusive") is set.
355
356 Thus the new VL comprises a contiguous vector of results,
357 all of which pass the testing criteria (equal to zero, less than zero).
358
359 The CR-based data-driven fail-on-first is new and not found in ARM
360 SVE or RVV. It is extremely useful for reducing instruction count,
361 however requires speculative execution involving modifications of VL
362 to get high performance implementations. An additional mode (RC1=1)
363 effectively turns what would otherwise be an arithmetic operation
364 into a type of `cmp`. The CR is stored (and the CR.eq bit tested
365 against the `inv` field).
366 If the CR.eq bit is equal to `inv` then the Vector is truncated and
367 the loop ends.
368 Note that when RC1=1 the result elements are never stored, only the CRs.
369
370 VLi is only available as an option when `Rc=0` (or for instructions
371 which do not have Rc). When set, the current element is always
372 also included in the count (the new length that VL will be set to).
373 This may be useful in combination with "inv" to truncate the Vector
374 to `exclude` elements that fail a test, or, in the case of implementations
375 of strncpy, to include the terminating zero.
376
377 In CR-based data-driven fail-on-first there is only the option to select
378 and test one bit of each CR (just as with branch BO). For more complex
379 tests this may be insufficient. If that is the case, a vectorised crops
380 (crand, cror) may be used, and ffirst applied to the crop instead of to
381 the arithmetic vector.
382
383 One extremely important aspect of ffirst is:
384
385 * LDST ffirst may never set VL equal to zero. This because on the first
386 element an exception must be raised "as normal".
387 * CR-based data-dependent ffirst on the other hand **can** set VL equal
388 to zero. This is the only means in the entirety of SV that VL may be set
389 to zero (with the exception of via the SV.STATE SPR). When VL is set
390 zero due to the first element failing the CR bit-test, all subsequent
391 vectorised operations are effectively `nops` which is
392 *precisely the desired and intended behaviour*.
393
394 Another aspect is that for ffirst LD/STs, VL may be truncated arbitrarily
395 to a nonzero value for any implementation-specific reason. For example:
396 it is perfectly reasonable for implementations to alter VL when ffirst
397 LD or ST operations are initiated on a nonaligned boundary, such that
398 within a loop the subsequent iteration of that loop begins subsequent
399 ffirst LD/ST operations on an aligned boundary. Likewise, to reduce
400 workloads or balance resources.
401
402 CR-based data-dependent first on the other hand MUST not truncate VL
403 arbitrarily to a length decided by the hardware: VL MUST only be
404 truncated based explicitly on whether a test fails.
405 This because it is a precise test on which algorithms
406 will rely.
407
408 ## Data-dependent fail-first on CR operations (crand etc)
409
410 Operations that actually produce or alter CR Field as a result
411 do not also in turn have an Rc=1 mode. However it makes no
412 sense to try to test the 4 bits of a CR Field for being equal
413 or not equal to zero. Moreover, the result is already in the
414 form that is desired: it is a CR field. Therefore,
415 CR-based operations have their own SVP64 Mode, described
416 in [[sv/cr_ops]]
417
418 There are two primary different types of CR operations:
419
420 * Those which have a 3-bit operand field (referring to a CR Field)
421 * Those which have a 5-bit operand (referring to a bit within the
422 whole 32-bit CR)
423
424 More details can be found in [[sv/cr_ops]].
425
426 # pred-result mode
427
428 This mode merges common CR testing with predication, saving on instruction
429 count. Below is the pseudocode excluding predicate zeroing and elwidth
430 overrides. Note that the paeudocode for [[sv/cr_ops]] is slightly different.
431
432 for i in range(VL):
433 # predication test, skip all masked out elements.
434 if predicate_masked_out(i):
435 continue
436 result = op(iregs[RA+i], iregs[RB+i])
437 CRnew = analyse(result) # calculates eq/lt/gt
438 # Rc=1 always stores the CR
439 if Rc=1 or RC1:
440 crregs[offs+i] = CRnew
441 # now test CR, similar to branch
442 if RC1 or CRnew[BO[0:1]] != BO[2]:
443 continue # test failed: cancel store
444 # result optionally stored but CR always is
445 iregs[RT+i] = result
446
447 The reason for allowing the CR element to be stored is so that
448 post-analysis of the CR Vector may be carried out. For example:
449 Saturation may have occurred (and been prevented from updating, by the
450 test) but it is desirable to know *which* elements fail saturation.
451
452 Note that RC1 Mode basically turns all operations into `cmp`. The
453 calculation is performed but it is only the CR that is written. The
454 element result is *always* discarded, never written (just like `cmp`).
455
456 Note that predication is still respected: predicate zeroing is slightly
457 different: elements that fail the CR test *or* are masked out are zero'd.
458
459 ## pred-result mode on CR ops
460
461 CR operations (mtcr, crand, cror) may be Vectorised,
462 predicated, and also pred-result mode applied to it.
463 Vectorisation applies to 4-bit CR Fields which are treated as
464 elements, not the individual bits of the 32-bit CR.
465 CR ops and how to identify them is described in [[sv/cr_ops]]
466
467 # CR Operations
468
469 CRs are slightly more involved than INT or FP registers due to the
470 possibility for indexing individual bits (crops BA/BB/BT). Again however
471 the access pattern needs to be understandable in relation to v3.0B / v3.1B
472 numbering, with a clear linear relationship and mapping existing when
473 SV is applied.
474
475 ## CR EXTRA mapping table and algorithm
476
477 Numbering relationships for CR fields are already complex due to being
478 in BE format (*the relationship is not clearly explained in the v3.0B
479 or v3.1B specification*). However with some care and consideration
480 the exact same mapping used for INT and FP regfiles may be applied,
481 just to the upper bits, as explained below. The notation
482 `CR{field number}` is used to indicate access to a particular
483 Condition Register Field (as opposed to the notation `CR[bit]`
484 which accesses one bit of the 32 bit Power ISA v3.0B
485 Condition Register)
486
487 In OpenPOWER v3.0/1, BF/BT/BA/BB are all 5 bits. The top 3 bits (0:2)
488 select one of the 8 CRs; the bottom 2 bits (3:4) select one of 4 bits
489 *in* that CR. The numbering was determined (after 4 months of
490 analysis and research) to be as follows:
491
492 CR_index = 7-(BA>>2) # top 3 bits but BE
493 bit_index = 3-(BA & 0b11) # low 2 bits but BE
494 CR_reg = CR{CR_index} # get the CR
495 # finally get the bit from the CR.
496 CR_bit = (CR_reg & (1<<bit_index)) != 0
497
498 When it comes to applying SV, it is the CR\_reg number to which SV EXTRA2/3
499 applies, **not** the CR\_bit portion (bits 3:4):
500
501 if extra3_mode:
502 spec = EXTRA3
503 else:
504 spec = EXTRA2<<1 | 0b0
505 if spec[0]:
506 # vector constructs "BA[0:2] spec[1:2] 00 BA[3:4]"
507 return ((BA >> 2)<<6) | # hi 3 bits shifted up
508 (spec[1:2]<<4) | # to make room for these
509 (BA & 0b11) # CR_bit on the end
510 else:
511 # scalar constructs "00 spec[1:2] BA[0:4]"
512 return (spec[1:2] << 5) | BA
513
514 Thus, for example, to access a given bit for a CR in SV mode, the v3.0B
515 algorithm to determin CR\_reg is modified to as follows:
516
517 CR_index = 7-(BA>>2) # top 3 bits but BE
518 if spec[0]:
519 # vector mode, 0-124 increments of 4
520 CR_index = (CR_index<<4) | (spec[1:2] << 2)
521 else:
522 # scalar mode, 0-32 increments of 1
523 CR_index = (spec[1:2]<<3) | CR_index
524 # same as for v3.0/v3.1 from this point onwards
525 bit_index = 3-(BA & 0b11) # low 2 bits but BE
526 CR_reg = CR{CR_index} # get the CR
527 # finally get the bit from the CR.
528 CR_bit = (CR_reg & (1<<bit_index)) != 0
529
530 Note here that the decoding pattern to determine CR\_bit does not change.
531
532 Note: high-performance implementations may read/write Vectors of CRs in
533 batches of aligned 32-bit chunks (CR0-7, CR7-15). This is to greatly
534 simplify internal design. If instructions are issued where CR Vectors
535 do not start on a 32-bit aligned boundary, performance may be affected.
536
537 ## CR fields as inputs/outputs of vector operations
538
539 CRs (or, the arithmetic operations associated with them)
540 may be marked as Vectorised or Scalar. When Rc=1 in arithmetic operations that have no explicit EXTRA to cover the CR, the CR is Vectorised if the destination is Vectorised. Likewise if the destination is scalar then so is the CR.
541
542 When vectorized, the CR inputs/outputs are sequentially read/written
543 to 4-bit CR fields. Vectorised Integer results, when Rc=1, will begin
544 writing to CR8 (TBD evaluate) and increase sequentially from there.
545 This is so that:
546
547 * implementations may rely on the Vector CRs being aligned to 8. This
548 means that CRs may be read or written in aligned batches of 32 bits
549 (8 CRs per batch), for high performance implementations.
550 * scalar Rc=1 operation (CR0, CR1) and callee-saved CRs (CR2-4) are not
551 overwritten by vector Rc=1 operations except for very large VL
552 * CR-based predication, from CR32, is also not interfered with
553 (except by large VL).
554
555 However when the SV result (destination) is marked as a scalar by the
556 EXTRA field the *standard* v3.0B behaviour applies: the accompanying
557 CR when Rc=1 is written to. This is CR0 for integer operations and CR1
558 for FP operations.
559
560 Note that yes, the CR Fields are genuinely Vectorised. Unlike in SIMD VSX which
561 has a single CR (CR6) for a given SIMD result, SV Vectorised OpenPOWER
562 v3.0B scalar operations produce a **tuple** of element results: the
563 result of the operation as one part of that element *and a corresponding
564 CR element*. Greatly simplified pseudocode:
565
566 for i in range(VL):
567 # calculate the vector result of an add iregs[RT+i] = iregs[RA+i]
568 + iregs[RB+i] # now calculate CR bits CRs{8+i}.eq = iregs[RT+i]
569 == 0 CRs{8+i}.gt = iregs[RT+i] > 0 ... etc
570
571 If a "cumulated" CR based analysis of results is desired (a la VSX CR6)
572 then a followup instruction must be performed, setting "reduce" mode on
573 the Vector of CRs, using cr ops (crand, crnor) to do so. This provides far
574 more flexibility in analysing vectors than standard Vector ISAs. Normal
575 Vector ISAs are typically restricted to "were all results nonzero" and
576 "were some results nonzero". The application of mapreduce to Vectorised
577 cr operations allows far more sophisticated analysis, particularly in
578 conjunction with the new crweird operations see [[sv/cr_int_predication]].
579
580 Note in particular that the use of a separate instruction in this way
581 ensures that high performance multi-issue OoO inplementations do not
582 have the computation of the cumulative analysis CR as a bottleneck and
583 hindrance, regardless of the length of VL.
584
585 Additionally,
586 SVP64 [[sv/branches]] may be used, even when the branch itself is to
587 the following instruction. The combined side-effects of CTR reduction
588 and VL truncation provide several benefits.
589
590 (see [[discussion]]. some alternative schemes are described there)
591
592 ## Rc=1 when SUBVL!=1
593
594 sub-vectors are effectively a form of Packed SIMD (length 2 to 4). Only 1 bit of
595 predicate is allocated per subvector; likewise only one CR is allocated
596 per subvector.
597
598 This leaves a conundrum as to how to apply CR computation per subvector,
599 when normally Rc=1 is exclusively applied to scalar elements. A solution
600 is to perform a bitwise OR or AND of the subvector tests. Given that
601 OE is ignored in SVP64, this field may (when available) be used to select OR or
602 AND behavior.
603
604 ### Table of CR fields
605
606 CR[i] is the notation used by the OpenPower spec to refer to CR field #i,
607 so FP instructions with Rc=1 write to CR[1] aka SVCR1_000.
608
609 CRs are not stored in SPRs: they are registers in their own right.
610 Therefore context-switching the full set of CRs involves a Vectorised
611 mfcr or mtcr, using VL=64, elwidth=8 to do so. This is exactly as how
612 scalar OpenPOWER context-switches CRs: it is just that there are now
613 more of them.
614
615 The 64 SV CRs are arranged similarly to the way the 128 integer registers
616 are arranged. TODO a python program that auto-generates a CSV file
617 which can be included in a table, which is in a new page (so as not to
618 overwhelm this one). [[svp64/cr_names]]
619
620 # Register Profiles
621
622 **NOTE THIS TABLE SHOULD NO LONGER BE HAND EDITED** see
623 <https://bugs.libre-soc.org/show_bug.cgi?id=548> for details.
624
625 Instructions are broken down by Register Profiles as listed in the
626 following auto-generated page: [[opcode_regs_deduped]]. "Non-SV"
627 indicates that the operations with this Register Profile cannot be
628 Vectorised (mtspr, bc, dcbz, twi)
629
630 TODO generate table which will be here [[svp64/reg_profiles]]
631
632 # SV pseudocode illilustration
633
634 ## Single-predicated Instruction
635
636 illustration of normal mode add operation: zeroing not included, elwidth
637 overrides not included. if there is no predicate, it is set to all 1s
638
639 function op_add(rd, rs1, rs2) # add not VADD!
640 int i, id=0, irs1=0, irs2=0; predval = get_pred_val(FALSE, rd);
641 for (i = 0; i < VL; i++)
642 STATE.srcoffs = i # save context if (predval & 1<<i) # predication
643 uses intregs
644 ireg[rd+id] <= ireg[rs1+irs1] + ireg[rs2+irs2]; if (!int_vec[rd
645 ].isvec) break;
646 if (rd.isvec) { id += 1; } if (rs1.isvec) { irs1 += 1; } if
647 (rs2.isvec) { irs2 += 1; } if (id == VL or irs1 == VL or irs2 ==
648 VL) {
649 # end VL hardware loop STATE.srcoffs = 0; # reset return;
650 }
651
652 This has several modes:
653
654 * RT.v = RA.v RB.v * RT.v = RA.v RB.s (and RA.s RB.v) * RT.v = RA.s RB.s *
655 RT.s = RA.v RB.v * RT.s = RA.v RB.s (and RA.s RB.v) * RT.s = RA.s RB.s
656
657 All of these may be predicated. Vector-Vector is straightfoward.
658 When one of source is a Vector and the other a Scalar, it is clear that
659 each element of the Vector source should be added to the Scalar source,
660 each result placed into the Vector (or, if the destination is a scalar,
661 only the first nonpredicated result).
662
663 The one that is not obvious is RT=vector but both RA/RB=scalar.
664 Here this acts as a "splat scalar result", copying the same result into
665 all nonpredicated result elements. If a fixed destination scalar was
666 intended, then an all-Scalar operation should be used.
667
668 See <https://bugs.libre-soc.org/show_bug.cgi?id=552>
669
670 # Assembly Annotation
671
672 Assembly code annotation is required for SV to be able to successfully
673 mark instructions as "prefixed".
674
675 A reasonable (prototype) starting point:
676
677 svp64 [field=value]*
678
679 Fields:
680
681 * ew=8/16/32 - element width
682 * sew=8/16/32 - source element width
683 * vec=2/3/4 - SUBVL
684 * mode=reduce/satu/sats/crpred
685 * pred=1\<\<3/r3/~r3/r10/~r10/r30/~r30/lt/gt/le/ge/eq/ne
686 * spred={reg spec}
687
688 similar to x86 "rex" prefix.
689
690 For actual assembler:
691
692 sv.asmcode/mode.vec{N}.ew=8,sw=16,m={pred},sm={pred} reg.v, src.s
693
694 Qualifiers:
695
696 * m={pred}: predicate mask mode
697 * sm={pred}: source-predicate mask mode (only allowed in Twin-predication)
698 * vec{N}: vec2 OR vec3 OR vec4 - sets SUBVL=2/3/4
699 * ew={N}: ew=8/16/32 - sets elwidth override
700 * sw={N}: sw=8/16/32 - sets source elwidth override
701 * ff={xx}: see fail-first mode
702 * pr={xx}: see predicate-result mode
703 * sat{x}: satu / sats - see saturation mode
704 * mr: see map-reduce mode
705 * mr.svm see map-reduce with sub-vector mode
706 * crm: see map-reduce CR mode
707 * crm.svm see map-reduce CR with sub-vector mode
708 * sz: predication with source-zeroing
709 * dz: predication with dest-zeroing
710
711 For modes:
712
713 * pred-result:
714 - pm=lt/gt/le/ge/eq/ne/so/ns OR
715 - pm=RC1 OR pm=~RC1
716 * fail-first
717 - ff=lt/gt/le/ge/eq/ne/so/ns OR
718 - ff=RC1 OR ff=~RC1
719 * saturation:
720 - sats
721 - satu
722 * map-reduce:
723 - mr OR crm: "normal" map-reduce mode or CR-mode.
724 - mr.svm OR crm.svm: when vec2/3/4 set, sub-vector mapreduce is enabled
725
726 # Proposed Parallel-reduction algorithm
727
728 ```
729 /// reference implementation of proposed SimpleV reduction semantics.
730 ///
731 // reduction operation -- we still use this algorithm even
732 // if the reduction operation isn't associative or
733 // commutative.
734 /// `temp_pred` is a user-visible Vector Condition register
735 ///
736 /// all input arrays have length `vl`
737 def reduce( vl, vec, pred, pred,):
738 step = 1;
739 while step < vl
740 step *= 2;
741 for i in (0..vl).step_by(step)
742 other = i + step / 2;
743 other_pred = other < vl && pred[other];
744 if pred[i] && other_pred
745 vec[i] += vec[other];
746 else if other_pred
747 vec[i] = vec[other];
748 pred[i] |= other_pred;
749
750 def reduce( vl, vec, pred, pred,):
751 j = 0
752 vi = [] # array of lookup indices to skip nonpredicated
753 for i, pbit in enumerate(pred):
754 if pbit:
755 vi[j] = i
756 j += 1
757 step = 2
758 while step <= vl
759 halfstep = step // 2
760 for i in (0..vl).step_by(step)
761 other = vi[i + halfstep]
762 i = vi[i]
763 other_pred = other < vl && pred[other]
764 if pred[i] && other_pred
765 vec[i] += vec[other]
766 pred[i] |= other_pred
767 step *= 2
768
769 ```