RFC ls015 CR Weird operations

Severity: Major

Status: New

Date: 25 Apr 2023

Target: v3.2B

Source: v3.1B

Books and Section affected:

    Book I Fixed-Point Instructions
    Appendix E Power ISA sorted by opcode
    Appendix F Power ISA sorted by version
    Appendix G Power ISA sorted by Compliancy Subset
    Appendix H Power ISA sorted by mnemonic

Summary

    Instructions added: crweird, crweirder, mfcrfm, mfcrweird, mtcrweird, mtcrrweird

Submitter: Luke Leighton (Libre-SOC)

Requester: Libre-SOC

Impact on processor:

    Addition of new GPR-CR-based instructions

Impact on software:

    Requires support for new instructions in assembler, debuggers,
    and related tools.

Keywords:

    CR Fields, predication, GPR

Motivation

Existing Condition Register operations are somewhat anaemic if to be utilised more extensively as Predicate Masks in a True-Scalable Vector ISA. Merging of multiple CR Fields requires several operations that may be achieved with a single "weird" operation, and transfer between CR Fields and GPR is easier and more powerful. This mitigates the need to add dozens of duplicate Logical Operations.

Notes and Observations:

  1. TODO

Changes

Add the following entries to:

  • the Appendices of Book I
  • Book I 3.3.17 Condition Register Instructions
  • Book I 1.6.1 and 1.6.2

\newpage{}

Rationale

Condition Registers are conceptually perfect for use as predicate masks, the only problem being that typical Vector ISAs have quite comprehensive mask-based instructions: set-before-first, popcount and much more. In fact many Vector ISAs can use Vectors as masks, consequently the entire Vector ISA is usually available for use in creating masks (one exception being AVX512 which has a dedicated Mask regfile and opcodes). Duplication of such operations (popcount etc) is not practical for SV given the strategy of leveraging pre-existing Scalar instructions in a minimalist way.

With the scalar OpenPOWER v3.0B ISA having already popcnt, cntlz and others normally seen in Vector Mask operations it makes sense to allow both scalar integers and CR-Vectors to be predicate masks. That in turn means that much more comprehensive interaction between CRs and scalar Integers is required, because with the CR Predication Modes designating CR Fields (not CR bits) as Predicate Elements, fast transfers between CR Fields and the Integer Register File is needed.

The opportunity is therefore taken to also augment CR logical arithmetic as well, using a mask-based paradigm that takes into consideration multiple bits of each CR Field (eq/lt/gt/ov). By contrast v3.0B Scalar CR instructions (crand, crxor) only allow a single bit calculation, and both mtcr and mfcr are CR-orientated rather than CR Field orientated.

Also strangely there is no v3.0 instruction for directly moving CR Fields, only CR bits, so that is corrected here with mcrfm. The opportunity is taken to allow inversion of CR Field bits, when copied.

Basic concept:

  • CR-based instructions that perform simple AND/OR from any four bits of a CR field to create a single bit value (0/1) in an integer register
  • Inverse of the same, taking a single bit value (0/1) from an integer register to selectively target any four bits of a given CR Field
  • CR-to-CR version of the same, allowing multiple bits to be AND/OR/XORed in one hit.
  • Optional Vectorization of the same when SVP64 is implemented

Purpose:

  • To provide a merged version of what is currently a multi-sequence of CR operations (crand, cror, crxor) with mfcr and mtcrf, reducing instruction count.
  • To provide a vectorized version of the same, suitable for advanced predication

Useful side-effects:

  • mtcrweird when RA=0 is a means to set or clear multiple arbitrary CR Field bits simultaneously, using immediates embedded within the instruction.
  • With SVP64 on the weird instructions there is bit-for-bit interaction between GPR predicate masks (r3, r10, r31) and the source or destination GPR, in ways that are not possible with other SVP64 instructions because normal SVP64 is bit-per-element. On these weird instructions the element in effect is a bit.
  • mfcrweird mitigates a need to add conflictd, part of vector ops, as well as allowing more complex comparisons.

\newpage{}

New instructions for CR/INT predication

See:

crrweird

CW2-Form

    |0     |6   |9 |11|12   |16   |19  |22   |26   |31|
    | PO   | RT    |M |fmsk |BFA  |XO  |fmap | XO  |Rc|
  • crrweird RT,BFA,M,fmsk,fmap (Rc=0)
  • crrweird. RT,BFA,M,fmsk,fmap (Rc=1)
    creg <- CR[4*BFA+32:4*BFA+35] 
    n <- (¬fmap ^ creg) & fmsk
    result <- (n != 0) if M else (n == fmsk)
    RT <- [0] * 63 || result
    if Rc then
        CR0 <- analyse(RT)

When used with SVP64 Prefixing this is a normal SVP64 type operation and as such can use Rc=1 and RC1 Data-dependent Mode capability

Also as noted below, element-width override bits normally used on the source is instead used to allow multiple results to be packed sequentially into the destination. Destination elwidth overrides still apply.

Special registers altered:

    CR0        (Rc=1)

mfcrrweird

CW2-Form

    |0     |6   |9 |11|12   |16   |19  |22   |26   |31|
    | PO   | RT    |M |fmsk |BFA  |XO  |fmap | XO  |Rc|
  • mfcrrweird RT,BFA,fmsk,fmap (Rc=0)
  • mfcrrweird. RT,BFA,fmsk,fmap (Rc=1)
    creg = CR[4*BFA+32:4*BFA+35]
    result = (¬fmap ^ creg) & fmsk
    RT = [0] * 60 || result
    If Rc:
        CR0 = analyse(RT)

When used with SVP64 Prefixing this is a normal SVP64 type operation and as such can use Rc=1 and RC1 Data-dependent Mode capability.

Also as noted below, element-width override bits normally used on the source is instead used to allow multiple results to be packed into the destination. Destination elwidth overrides still apply

mtcrrweird

CW-Form

    |0     |6   |9 |11|12   |16   |19  |22   |26   |31|
    | PO   | RA    |M |fmsk |BF   |XO  |fmap | XO     |
    | PO   | BT    |M |fmsk |BF   |XO  |fmap | XO     |
    | PO   | BF |  |M |fmsk |BF   |XO  |fmap | XO     |
  • mtcrrweird BF,RA,M,fmsk,fmap
    a = (RA|0)
    creg = a[60:63]
    result = (¬fmap ^ creg) & fmsk
    if M:
        result |= CR[4*BF+32:4*BF+35]  & ~fmsk
    CR[4*BF+32:4*BF+35]  = result

When used with SVP64 Prefixing this is a normal SVP64 type operation and as such can use RC1 Data-dependent Mode capability

Hardware Architectural Note: when M=1 this instruction is a Read-Modify-Write on the BF CR Field. When M=0 it is a more normal Write.

Special Registers Altered:

    CR Field BF

mtcrweird

CW-Form

    |0     |6   |9 |11|12   |16   |19  |22   |26   |31|
    | PO   | RA    |M |fmsk |BF   |XO  |fmap | XO     |
    | PO   | BT    |M |fmsk |BF   |XO  |fmap | XO     |
    | PO   | BF |  |M |fmsk |BF   |XO  |fmap | XO     |
  • mtcrweird BF,RA,M,fmsk,fmap
    reg = (RA|0)
    creg = reg[63] || reg[63] || reg[63] || reg[63]
    result = (¬fmap ^ creg) & fmsk
    if M:
        result |= CR[4*BF+32:4*BF+35] & ~fmsk
    CR[4*BF+32:4*BF+35]  = result

Note that when M=1 this operation is a Read-Modify-Write on the CR Field BF. Masked-out bits of the 4-bit CR Field BF will not be changed when M=1. Correspondingly when M=0 this operation is an overwrite: no read of BF is required because the masked-out bits of the BF CR Field are set to zero.

When used with SVP64 Prefixing this is a cr ops SVP64 type operation that has 3-bit Data-dependent and 3-bit Predicate-result capability (BF is 3 bits)

Special Registers Altered:

    CR Field BF

mcrfm - Move CR Field, masked.

CW-Form

    |0     |6   |9 |11|12   |16   |19  |22   |26   |31|
    | PO   | BF |  |M |fmsk |BF   |XO  |fmap | XO     |
  • mcrfm: BF,BFA,M,fmsk,fmap
    result = fmsk & CR[4*BFA+32:4*BFA+35] 
    if M:
        result |= CR[4*BF+32:4*BF+35]  & ~fmsk
    result ^= fmap
    CR[4*BF+32:4*BF+35]  = result

This instruction copies, sets, or inverts parts of a CR Field into another CR Field. mcrf copies only one bit of the CR from any arbitrary bit to any other arbitrary bit, whereas mcrfm copies an entire 4-bit CR Field (or masked parts thereof). Unlike mcrf the bits of the CR Field may not change position: the EQ bit from the source may only go into the EQ bit of the destination (optionally inverted, set, or cleared).

When M=1 this operation is a Read-Modify-Write on the CR Field BF. Masked-out bits of the 4-bit CR Field BF will not be changed when M=1. Correspondingly when M=0 this operation is an overwrite: no read of BF is required because the masked-out bits of the BF CR Field are set to zero.

When used with SVP64 Prefixing this is a cr ops SVP64 type operation that has 3-bit Data-dependent and 3-bit Predicate-result capability (BF is 3 bits)

Programmer's note: fmap being XORed onto the result provides considerable flexibility. individual bits of BFA may be copied inverted to BF by ensuring that fmsk and fmap have the same bit set. Also, individual bits in BF may be set to 1 by ensuring that the required bit of fmsk is set to zero and the same bit in fmap is set to 1

Special Registers Altered:

    CR Field BF

crweirder

    |0     |6   |9 |11|12   |16   |19  |22   |26   |31|
    | PO   | BT    |M |fmsk |BF   |XO  |fmap | XO     |
  • crweirder: BT,BFA,fmsk,fmap
    creg = CR[4*BFA+32:4*BFA+35]
    n = (¬fmap ^ creg) & fmsk
    result = (n != 0) if M else (n == fmsk)
    CR[32+BT] = result

Special Registers Altered:

    CR[BT+32]

When used with SVP64 Prefixing this is a cr ops SVP64 type operation that has 5-bit Data-dependent capability (BT is 5 bits)

Hardware Architectural Note: this instruction is always a Read-Modify-Write on the CR Field containing BT.

Example Pseudo-ops:

    mtcri BF, fmap    mtcrweird BF, r0, 0, 0b1111,~fmap
    mtcrset BF, fmsk  mtcrweird BF, r0, 1, fmsk,0b0000
    mtcrclr BF, fmsk  mtcrweird BF, r0, 1, fmsk,0b1111

\newpage{}

Vectorized versions involving GPRs

The name "weird" refers to a minor violation of SV rules when it comes to deriving the Vectorized versions of these instructions.

Normally the progression of the SV for-loop would move on to the next register. Instead however in the scalar case these instructions remain in the same register and insert or transfer between bits of the scalar integer source or destination. The reason is that when using CR Fields as predicate masks and there is a need to transfer into a GPR, again for use as a predicate mask, the CR Field bits need to be efficiently packed into that one GPR (r3, r10 or r31).

Further useful violation of the normal SV Elwidth override rules allows for packing (or unpacking) of multiple CR test results into (or out of) an Integer Element. Note that the CR (source operand) elwidth field is utilised to determine the bit- packing size (1/2/4/8 with remaining bits within the Integer element set to zero) whilst the INT (dest operand) elwidth field still sets the Integer element size as usual (8/16/32/default)

sv.crrweird: RT, BB, fmsk, fmap

    for i in range(VL):
        if BB.isvec: # Vector CR Field source?
            creg = CR{BB+i}
        else:
            creg = CR{BB}
        n = (¬fmap ^ creg) & fmsk
        result = (n != 0) if M else (n == fmsk)
        if RT.isvec:
            # TODO: RT.elwidth override to be also added here
            # note, yes, really, the CR's elwidth field determines
            # the bit-packing into the INT!
            if BB.elwidth == 0b00:
                # pack 1 result into 64-bit registers
                iregs[RT+i][0..62] = 0
                iregs[RT+i][63] = result # sets LSB to result
            if BB.elwidth == 0b01:
                # pack 2 results sequentially into INT registers
                iregs[RT+i//2][0..61] = 0
                iregs[RT+i//2][63-(i%2)] = result
            if BB.elwidth == 0b10:
                # pack 4 results sequentially into INT registers
                iregs[RT+i//4][0..59] = 0
                iregs[RT+i//4][63-(i%4)] = result
            if BB.elwidth == 0b11:
                # pack 8 results sequentially into INT registers
                iregs[RT+i//8][0..55] = 0
                iregs[RT+i//8][63-(i%8)] = result
        else:
            # scalar RT destination: exceeding VL=64 is UNDEFINED
            iregs[RT][63-i] = result # results also in scalar INT
            # only mapreduce mode (/mr) allows continuation here
            if not SVRM.mapreduce: break

Note that:

  • in the scalar case the CR-Vector assessment is stored bit-wise starting at the LSB of the destination scalar INT
  • in the INT-vector case the results are packed into LSBs of the INT Elements, the packing arrangement depending on both elwidth override settings.

mfcrrweird: RT, BFA, fmsk.fmap

Unlike crrweird the results are 4-bit wide, so the packing will begin to spill over to other destination elements. 8 results per destination at 4-bits each still fits into destination elwidth at 32-bit, but for 16-bit and 8-bit obviously this does not fit, and must split across to the next element

When for example destination elwidth is 16-bit (0b10) the following packing occurs:

  • SVRM bits 6:7 equal to 0b00 - one 4-bit result element packed into the first 4-bits of the 16-bit destination element (in the first 4 LSBs)
  • SVRM bits 6:7 equal to 0b01 - two 4-bit result elements packed into the first 8-bits of the 16-bit destination element (in the first 8 LSBs)
  • SVRM bits 6:7 equal to 0b10 - four 4-bit result elements packed into each 16-bit destination element
  • SVRM bits 6:7 equal to 0b11 - eight 4-bit result elements, the first four of which are packed into the first 16-bit destination element, the second four of which are packed into the second 16-bit destination element.

Pseudocode example: note that dest elwidth overrides affect the packing of results. BB.elwidth in effect requests how many 4-bit result elements would like to be packed, but RT.elwidth determines the limit. Any parts of the destination elements not containing results are set to zero.

    for i in range(VL):
        if BB.isvec:
            creg = CR{BB+i}
        else:
            creg = CR{BB}
        result = (¬fmap ^ creg) & fmsk # 4-bit result
        if RT.isvec:
            # RT.elwidth override can affect the packing
            bwid = {0b00:64, 0b01:8, 0b10:16, 0b11:32}[RT.elwidth]
            t4, t8 = min(4, bwid//2), min(8, bwid//2)
            # yes, really, the CR's elwidth field determines
            # the bit-packing into the INT!
            if BB.elwidth == 0b00:
                # pack 1 result into 64-bit registers
                idx, boff = i, 0
            if BB.elwidth == 0b01:
                # pack 2 results sequentially into INT registers
                idx, boff = i//2, i%2
            if BB.elwidth == 0b10:
                # pack 4 results sequentially into INT registers
                idx, boff = i//t4, i%t4
            if BB.elwidth == 0b11:
                # pack 8 results sequentially into INT registers
                idx, boff = i//t8, i%t8
        else:
            # scalar RT destination: exceeding VL=16 is UNDEFINED
            idx, boff = 0, i
        # store 4-bit result in Vector starting from RT
        iregs[RT+idx][60-boff*4:63-boff*4] = result
        if not RT.isvec:
            # only mapreduce mode (/mr) allows continuation here
            if not SVRM.mapreduce: break

Predication Examples

Take the following example:

    r10 = 0b00010
    sv.mtcrweird/dm=r10/dz cr8.v, 0, 0b0011.0000

Here, RA is zero, so the source input is zero. The destination is CR Field 8, and the destination predicate mask indicates to target the first two elements. Destination predicate zeroing is enabled, and the destination predicate is only set in the 2nd bit. fmsk is 0b0011, fmap is all zeros.

Let us first consider what should go into element 0 (CR Field 8):

  • The destination predicate bit is zero, and zeroing is enabled.
  • Therefore, what is in the source is irrelevant: the result must be zero.
  • Therefore all four bits of CR Field 8 are therefore set to zero.

Now the second element, CR Field 9 (CR9):

  • Bit 2 of the destination predicate, r10, is 1. Therefore the computation of the result is relevant.
  • RA is zero therefore bit 2 is zero. fmsk is 0b0011 and fmap is 0b0000
  • When calculating n0 thru n3 we get n0=1, n1=2, n2=0, n3=0
  • Therefore, CR9 is set (using LSB0 ordering) to 0b0011, i.e. to fmsk.

It should be clear that this instruction uses bits of the integer predicate to decide whether to set CR Fields to (fmsk & ~fmap) or to zero. Thus, in effect, it is the integer predicate that has been copied into the CR Fields.

By using twin predication, zeroing, and inversion (sm=~r3, dm=r10) for example, it becomes possible to combine two Integers together in order to set bits in CR Fields. Likewise there are dozens of ways that CR Predicates can be used, on the same sv.mtcrweird instruction.


\newpage{}

Instruction Formats

Add the following entries to Book I 1.6.1 Word Instruction Formats:

CW-FORM

    |0     |6   |9 |11|12   |16   |19  |22   |26   |31|
    | PO   | RA    |M |fmsk |BF   |XO  |fmap | XO     |
    | PO   | BT    |M |fmsk |BF   |XO  |fmap | XO     |
    | PO   | BF |  |M |fmsk |BF   |XO  |fmap | XO     |

CW2-FORM

    |0     |6   |9 |11|12   |16   |19  |22   |26   |31|
    | PO   | RT    |M |fmsk |BFA  |XO  |fmap | XO  |Rc|

Add the following new fields to Book I 1.6.2 Word Instruction Fields:

    fmap (22:25)
        Field used to specify the CR Field set/clear map for CR Weird
        instructions.
        Formats: CW, CW2

    fmsk (12:15)
        Field used to specify the CR Field mask for CR Weird instructions.
        Formats: CW, CW2

Add CW and CW2 to the Formats: list for all of RT, RA, BF, BFA and Rc.

Add CW to the Formats: list for XO (25:30).

Add CW2 to the Formats: list for XO (25:31).


\newpage{}

Appendices

Appendix E Power ISA sorted by opcode
Appendix F Power ISA sorted by version
Appendix G Power ISA sorted by Compliancy Subset
Appendix H Power ISA sorted by mnemonic
Form Book Page Version Mnemonic Description
CW2 I # 3.2B crrweird
CW2 I # 3.2B mfcrweird
CW I # 3.2B mtcrrweird
CW I # 3.2B mtcrweird
CW I # 3.2B crweirder
CW I # 3.2B mcrfm