sha512-ppc.pl mutli-thread safety fix.
[openssl.git] / crypto / sha / asm / sha512-ppc.pl
1 #!/usr/bin/env perl
2
3 # ====================================================================
4 # Written by Andy Polyakov <appro@fy.chalmers.se> for the OpenSSL
5 # project. The module is, however, dual licensed under OpenSSL and
6 # CRYPTOGAMS licenses depending on where you obtain it. For further
7 # details see http://www.openssl.org/~appro/cryptogams/.
8 # ====================================================================
9
10 # I let hardware handle unaligned input, except on page boundaries
11 # (see below for details). Otherwise straightforward implementation
12 # with X vector in register bank. The module is big-endian [which is
13 # not big deal as there're no little-endian targets left around].
14
15 #                       sha256          |       sha512
16 #                       -m64    -m32    |       -m64    -m32
17 # --------------------------------------+-----------------------
18 # PPC970,gcc-4.0.0      +50%    +38%    |       +40%    +410%(*)
19 #
20 # (*)   64-bit code in 32-bit application context, which actually is
21 #       on TODO list. It should be noted that for safe deployment in
22 #       32-bit *mutli-threaded* context asyncronous signals should be
23 #       blocked upon entry to SHA512 block routine. This is because
24 #       32-bit signaling procedure invalidates upper halves of GPRs.
25 #       Context switch procedure preserves them, but not signaling:-(
26
27 # Second version is true multi-thread safe. Trouble with the original
28 # version was that it was using thread local storage pointer register.
29 # Well, it scrupulously preserved it, but the problem would arise the
30 # moment asynchronous signal was delivered and signal handler would
31 # dereference the TLS pointer. While it's never the case in openssl
32 # application or test suite, we have to respect this scenario and not
33 # use TLS pointer register. Alternative would be to require caller to
34 # block signals prior calling this routine. For the record, in 32-bit
35 # context R2 serves as TLS pointer, while in 64-bit context - R13.
36
37 $output=shift;
38
39 if ($output =~ /64/) {
40         $SIZE_T=8;
41         $STU="stdu";
42         $UCMP="cmpld";
43         $SHL="sldi";
44         $POP="ld";
45         $PUSH="std";
46 } elsif ($output =~ /32/) {
47         $SIZE_T=4;
48         $STU="stwu";
49         $UCMP="cmplw";
50         $SHL="slwi";
51         $POP="lwz";
52         $PUSH="stw";
53 } else { die "nonsense $output"; }
54
55 ( defined shift || open STDOUT,"| $^X ../perlasm/ppc-xlate.pl $output" ) ||
56         die "can't call ../perlasm/ppc-xlate.pl: $!";
57
58 if ($output =~ /512/) {
59         $func="sha512_block_data_order";
60         $SZ=8;
61         @Sigma0=(28,34,39);
62         @Sigma1=(14,18,41);
63         @sigma0=(1,  8, 7);
64         @sigma1=(19,61, 6);
65         $rounds=80;
66         $LD="ld";
67         $ST="std";
68         $ROR="rotrdi";
69         $SHR="srdi";
70 } else {
71         $func="sha256_block_data_order";
72         $SZ=4;
73         @Sigma0=( 2,13,22);
74         @Sigma1=( 6,11,25);
75         @sigma0=( 7,18, 3);
76         @sigma1=(17,19,10);
77         $rounds=64;
78         $LD="lwz";
79         $ST="stw";
80         $ROR="rotrwi";
81         $SHR="srwi";
82 }
83
84 $FRAME=32*$SIZE_T;
85
86 $sp ="r1";
87 $toc="r2";
88 $ctx="r3";      # zapped by $a0
89 $inp="r4";      # zapped by $a1
90 $num="r5";      # zapped by $t0
91
92 $T  ="r0";
93 $a0 ="r3";
94 $a1 ="r4";
95 $t0 ="r5";
96 $t1 ="r6";
97 $Tbl="r7";
98
99 $A  ="r8";
100 $B  ="r9";
101 $C  ="r10";
102 $D  ="r11";
103 $E  ="r12";
104 $F  ="r13";     $F="r2" if ($SIZE_T==8);# reassigned to exempt TLS pointer
105 $G  ="r14";
106 $H  ="r15";
107
108 @V=($A,$B,$C,$D,$E,$F,$G,$H);
109 @X=("r16","r17","r18","r19","r20","r21","r22","r23",
110     "r24","r25","r26","r27","r28","r29","r30","r31");
111
112 $inp="r31";     # reassigned $inp! aliases with @X[15]
113
114 sub ROUND_00_15 {
115 my ($i,$a,$b,$c,$d,$e,$f,$g,$h)=@_;
116 $code.=<<___;
117         $LD     $T,`$i*$SZ`($Tbl)
118         $ROR    $a0,$e,$Sigma1[0]
119         $ROR    $a1,$e,$Sigma1[1]
120         and     $t0,$f,$e
121         andc    $t1,$g,$e
122         add     $T,$T,$h
123         xor     $a0,$a0,$a1
124         $ROR    $a1,$a1,`$Sigma1[2]-$Sigma1[1]`
125         or      $t0,$t0,$t1             ; Ch(e,f,g)
126         add     $T,$T,@X[$i]
127         xor     $a0,$a0,$a1             ; Sigma1(e)
128         add     $T,$T,$t0
129         add     $T,$T,$a0
130
131         $ROR    $a0,$a,$Sigma0[0]
132         $ROR    $a1,$a,$Sigma0[1]
133         and     $t0,$a,$b
134         and     $t1,$a,$c
135         xor     $a0,$a0,$a1
136         $ROR    $a1,$a1,`$Sigma0[2]-$Sigma0[1]`
137         xor     $t0,$t0,$t1
138         and     $t1,$b,$c
139         xor     $a0,$a0,$a1             ; Sigma0(a)
140         add     $d,$d,$T
141         xor     $t0,$t0,$t1             ; Maj(a,b,c)
142         add     $h,$T,$a0
143         add     $h,$h,$t0
144
145 ___
146 }
147
148 sub ROUND_16_xx {
149 my ($i,$a,$b,$c,$d,$e,$f,$g,$h)=@_;
150 $i-=16;
151 $code.=<<___;
152         $ROR    $a0,@X[($i+1)%16],$sigma0[0]
153         $ROR    $a1,@X[($i+1)%16],$sigma0[1]
154         $ROR    $t0,@X[($i+14)%16],$sigma1[0]
155         $ROR    $t1,@X[($i+14)%16],$sigma1[1]
156         xor     $a0,$a0,$a1
157         $SHR    $a1,@X[($i+1)%16],$sigma0[2]
158         xor     $t0,$t0,$t1
159         $SHR    $t1,@X[($i+14)%16],$sigma1[2]
160         add     @X[$i],@X[$i],@X[($i+9)%16]
161         xor     $a0,$a0,$a1             ; sigma0(X[(i+1)&0x0f])
162         xor     $t0,$t0,$t1             ; sigma1(X[(i+14)&0x0f])
163         add     @X[$i],@X[$i],$a0
164         add     @X[$i],@X[$i],$t0
165 ___
166 &ROUND_00_15($i,$a,$b,$c,$d,$e,$f,$g,$h);
167 }
168
169 $code=<<___;
170 .text
171
172 .globl  $func
173 .align  6
174 $func:
175         mflr    r0
176         $STU    $sp,`-($FRAME+16*$SZ)`($sp)
177         $SHL    $num,$num,`log(16*$SZ)/log(2)`
178
179         $PUSH   $ctx,`$FRAME-$SIZE_T*22`($sp)
180
181         $PUSH   r0,`$FRAME-$SIZE_T*21`($sp)
182         $PUSH   $toc,`$FRAME-$SIZE_T*20`($sp)
183         $PUSH   r13,`$FRAME-$SIZE_T*19`($sp)
184         $PUSH   r14,`$FRAME-$SIZE_T*18`($sp)
185         $PUSH   r15,`$FRAME-$SIZE_T*17`($sp)
186         $PUSH   r16,`$FRAME-$SIZE_T*16`($sp)
187         $PUSH   r17,`$FRAME-$SIZE_T*15`($sp)
188         $PUSH   r18,`$FRAME-$SIZE_T*14`($sp)
189         $PUSH   r19,`$FRAME-$SIZE_T*13`($sp)
190         $PUSH   r20,`$FRAME-$SIZE_T*12`($sp)
191         $PUSH   r21,`$FRAME-$SIZE_T*11`($sp)
192         $PUSH   r22,`$FRAME-$SIZE_T*10`($sp)
193         $PUSH   r23,`$FRAME-$SIZE_T*9`($sp)
194         $PUSH   r24,`$FRAME-$SIZE_T*8`($sp)
195         $PUSH   r25,`$FRAME-$SIZE_T*7`($sp)
196         $PUSH   r26,`$FRAME-$SIZE_T*6`($sp)
197         $PUSH   r27,`$FRAME-$SIZE_T*5`($sp)
198         $PUSH   r28,`$FRAME-$SIZE_T*4`($sp)
199         $PUSH   r29,`$FRAME-$SIZE_T*3`($sp)
200         $PUSH   r30,`$FRAME-$SIZE_T*2`($sp)
201         $PUSH   r31,`$FRAME-$SIZE_T*1`($sp)
202
203         $LD     $A,`0*$SZ`($ctx)
204         mr      $inp,r4                         ; incarnate $inp
205         $LD     $B,`1*$SZ`($ctx)
206         $LD     $C,`2*$SZ`($ctx)
207         $LD     $D,`3*$SZ`($ctx)
208         $LD     $E,`4*$SZ`($ctx)
209         $LD     $F,`5*$SZ`($ctx)
210         $LD     $G,`6*$SZ`($ctx)
211         $LD     $H,`7*$SZ`($ctx)
212
213         b       LPICmeup
214 LPICedup:
215         andi.   r0,$inp,3
216         bne     Lunaligned
217 Laligned:
218         add     $num,$inp,$num
219         $PUSH   $num,`$FRAME-$SIZE_T*24`($sp)   ; end pointer
220         $PUSH   $inp,`$FRAME-$SIZE_T*23`($sp)   ; inp pointer
221         bl      Lsha2_block_private
222 Ldone:
223         $POP    r0,`$FRAME-$SIZE_T*21`($sp)
224         $POP    $toc,`$FRAME-$SIZE_T*20`($sp)
225         $POP    r13,`$FRAME-$SIZE_T*19`($sp)
226         $POP    r14,`$FRAME-$SIZE_T*18`($sp)
227         $POP    r15,`$FRAME-$SIZE_T*17`($sp)
228         $POP    r16,`$FRAME-$SIZE_T*16`($sp)
229         $POP    r17,`$FRAME-$SIZE_T*15`($sp)
230         $POP    r18,`$FRAME-$SIZE_T*14`($sp)
231         $POP    r19,`$FRAME-$SIZE_T*13`($sp)
232         $POP    r20,`$FRAME-$SIZE_T*12`($sp)
233         $POP    r21,`$FRAME-$SIZE_T*11`($sp)
234         $POP    r22,`$FRAME-$SIZE_T*10`($sp)
235         $POP    r23,`$FRAME-$SIZE_T*9`($sp)
236         $POP    r24,`$FRAME-$SIZE_T*8`($sp)
237         $POP    r25,`$FRAME-$SIZE_T*7`($sp)
238         $POP    r26,`$FRAME-$SIZE_T*6`($sp)
239         $POP    r27,`$FRAME-$SIZE_T*5`($sp)
240         $POP    r28,`$FRAME-$SIZE_T*4`($sp)
241         $POP    r29,`$FRAME-$SIZE_T*3`($sp)
242         $POP    r30,`$FRAME-$SIZE_T*2`($sp)
243         $POP    r31,`$FRAME-$SIZE_T*1`($sp)
244         mtlr    r0
245         addi    $sp,$sp,`$FRAME+16*$SZ`
246         blr
247 ___
248
249 # PowerPC specification allows an implementation to be ill-behaved
250 # upon unaligned access which crosses page boundary. "Better safe
251 # than sorry" principle makes me treat it specially. But I don't
252 # look for particular offending word, but rather for the input
253 # block which crosses the boundary. Once found that block is aligned
254 # and hashed separately...
255 $code.=<<___;
256 .align  4
257 Lunaligned:
258         subfic  $t1,$inp,4096
259         andi.   $t1,$t1,`4096-16*$SZ`   ; distance to closest page boundary
260         beq     Lcross_page
261         $UCMP   $num,$t1
262         ble-    Laligned                ; didn't cross the page boundary
263         subfc   $num,$t1,$num
264         add     $t1,$inp,$t1
265         $PUSH   $num,`$FRAME-$SIZE_T*25`($sp)   ; save real remaining num
266         $PUSH   $t1,`$FRAME-$SIZE_T*24`($sp)    ; intermediate end pointer
267         $PUSH   $inp,`$FRAME-$SIZE_T*23`($sp)   ; inp pointer
268         bl      Lsha2_block_private
269         ; $inp equals to the intermediate end pointer here
270         $POP    $num,`$FRAME-$SIZE_T*25`($sp)   ; restore real remaining num
271 Lcross_page:
272         li      $t1,`16*$SZ/4`
273         mtctr   $t1
274         addi    r20,$sp,$FRAME                  ; aligned spot below the frame
275 Lmemcpy:
276         lbz     r16,0($inp)
277         lbz     r17,1($inp)
278         lbz     r18,2($inp)
279         lbz     r19,3($inp)
280         addi    $inp,$inp,4
281         stb     r16,0(r20)
282         stb     r17,1(r20)
283         stb     r18,2(r20)
284         stb     r19,3(r20)
285         addi    r20,r20,4
286         bdnz    Lmemcpy
287
288         $PUSH   $inp,`$FRAME-$SIZE_T*26`($sp)   ; save real inp
289         addi    $t1,$sp,`$FRAME+16*$SZ`         ; fictitious end pointer
290         addi    $inp,$sp,$FRAME                 ; fictitious inp pointer
291         $PUSH   $num,`$FRAME-$SIZE_T*25`($sp)   ; save real num
292         $PUSH   $t1,`$FRAME-$SIZE_T*24`($sp)    ; end pointer
293         $PUSH   $inp,`$FRAME-$SIZE_T*23`($sp)   ; inp pointer
294         bl      Lsha2_block_private
295         $POP    $inp,`$FRAME-$SIZE_T*26`($sp)   ; restore real inp
296         $POP    $num,`$FRAME-$SIZE_T*25`($sp)   ; restore real num
297         addic.  $num,$num,`-16*$SZ`             ; num--
298         bne-    Lunaligned
299         b       Ldone
300 ___
301
302 $code.=<<___;
303 .align  4
304 Lsha2_block_private:
305 ___
306 for($i=0;$i<16;$i++) {
307 $code.=<<___ if ($SZ==4);
308         lwz     @X[$i],`$i*$SZ`($inp)
309 ___
310 # 64-bit loads are split to 2x32-bit ones, as CPU can't handle
311 # unaligned 64-bit loads, only 32-bit ones...
312 $code.=<<___ if ($SZ==8);
313         lwz     $t0,`$i*$SZ`($inp)
314         lwz     @X[$i],`$i*$SZ+4`($inp)
315         insrdi  @X[$i],$t0,32,0
316 ___
317         &ROUND_00_15($i,@V);
318         unshift(@V,pop(@V));
319 }
320 $code.=<<___;
321         li      $T,`$rounds/16-1`
322         mtctr   $T
323 .align  4
324 Lrounds:
325         addi    $Tbl,$Tbl,`16*$SZ`
326 ___
327 for(;$i<32;$i++) {
328         &ROUND_16_xx($i,@V);
329         unshift(@V,pop(@V));
330 }
331 $code.=<<___;
332         bdnz-   Lrounds
333
334         $POP    $ctx,`$FRAME-$SIZE_T*22`($sp)
335         $POP    $inp,`$FRAME-$SIZE_T*23`($sp)   ; inp pointer
336         $POP    $num,`$FRAME-$SIZE_T*24`($sp)   ; end pointer
337         subi    $Tbl,$Tbl,`($rounds-16)*$SZ`    ; rewind Tbl
338
339         $LD     r16,`0*$SZ`($ctx)
340         $LD     r17,`1*$SZ`($ctx)
341         $LD     r18,`2*$SZ`($ctx)
342         $LD     r19,`3*$SZ`($ctx)
343         $LD     r20,`4*$SZ`($ctx)
344         $LD     r21,`5*$SZ`($ctx)
345         $LD     r22,`6*$SZ`($ctx)
346         addi    $inp,$inp,`16*$SZ`              ; advance inp
347         $LD     r23,`7*$SZ`($ctx)
348         add     $A,$A,r16
349         add     $B,$B,r17
350         $PUSH   $inp,`$FRAME-$SIZE_T*23`($sp)
351         add     $C,$C,r18
352         $ST     $A,`0*$SZ`($ctx)
353         add     $D,$D,r19
354         $ST     $B,`1*$SZ`($ctx)
355         add     $E,$E,r20
356         $ST     $C,`2*$SZ`($ctx)
357         add     $F,$F,r21
358         $ST     $D,`3*$SZ`($ctx)
359         add     $G,$G,r22
360         $ST     $E,`4*$SZ`($ctx)
361         add     $H,$H,r23
362         $ST     $F,`5*$SZ`($ctx)
363         $ST     $G,`6*$SZ`($ctx)
364         $UCMP   $inp,$num
365         $ST     $H,`7*$SZ`($ctx)
366         bne     Lsha2_block_private
367         blr
368 ___
369
370 # Ugly hack here, because PPC assembler syntax seem to vary too
371 # much from platforms to platform...
372 $code.=<<___;
373 .align  6
374 LPICmeup:
375         bl      LPIC
376         addi    $Tbl,$Tbl,`64-4`        ; "distance" between . and last nop
377         b       LPICedup
378         nop
379         nop
380         nop
381         nop
382         nop
383 LPIC:   mflr    $Tbl
384         blr
385         nop
386         nop
387         nop
388         nop
389         nop
390         nop
391 ___
392 $code.=<<___ if ($SZ==8);
393         .long   0x428a2f98,0xd728ae22,0x71374491,0x23ef65cd
394         .long   0xb5c0fbcf,0xec4d3b2f,0xe9b5dba5,0x8189dbbc
395         .long   0x3956c25b,0xf348b538,0x59f111f1,0xb605d019
396         .long   0x923f82a4,0xaf194f9b,0xab1c5ed5,0xda6d8118
397         .long   0xd807aa98,0xa3030242,0x12835b01,0x45706fbe
398         .long   0x243185be,0x4ee4b28c,0x550c7dc3,0xd5ffb4e2
399         .long   0x72be5d74,0xf27b896f,0x80deb1fe,0x3b1696b1
400         .long   0x9bdc06a7,0x25c71235,0xc19bf174,0xcf692694
401         .long   0xe49b69c1,0x9ef14ad2,0xefbe4786,0x384f25e3
402         .long   0x0fc19dc6,0x8b8cd5b5,0x240ca1cc,0x77ac9c65
403         .long   0x2de92c6f,0x592b0275,0x4a7484aa,0x6ea6e483
404         .long   0x5cb0a9dc,0xbd41fbd4,0x76f988da,0x831153b5
405         .long   0x983e5152,0xee66dfab,0xa831c66d,0x2db43210
406         .long   0xb00327c8,0x98fb213f,0xbf597fc7,0xbeef0ee4
407         .long   0xc6e00bf3,0x3da88fc2,0xd5a79147,0x930aa725
408         .long   0x06ca6351,0xe003826f,0x14292967,0x0a0e6e70
409         .long   0x27b70a85,0x46d22ffc,0x2e1b2138,0x5c26c926
410         .long   0x4d2c6dfc,0x5ac42aed,0x53380d13,0x9d95b3df
411         .long   0x650a7354,0x8baf63de,0x766a0abb,0x3c77b2a8
412         .long   0x81c2c92e,0x47edaee6,0x92722c85,0x1482353b
413         .long   0xa2bfe8a1,0x4cf10364,0xa81a664b,0xbc423001
414         .long   0xc24b8b70,0xd0f89791,0xc76c51a3,0x0654be30
415         .long   0xd192e819,0xd6ef5218,0xd6990624,0x5565a910
416         .long   0xf40e3585,0x5771202a,0x106aa070,0x32bbd1b8
417         .long   0x19a4c116,0xb8d2d0c8,0x1e376c08,0x5141ab53
418         .long   0x2748774c,0xdf8eeb99,0x34b0bcb5,0xe19b48a8
419         .long   0x391c0cb3,0xc5c95a63,0x4ed8aa4a,0xe3418acb
420         .long   0x5b9cca4f,0x7763e373,0x682e6ff3,0xd6b2b8a3
421         .long   0x748f82ee,0x5defb2fc,0x78a5636f,0x43172f60
422         .long   0x84c87814,0xa1f0ab72,0x8cc70208,0x1a6439ec
423         .long   0x90befffa,0x23631e28,0xa4506ceb,0xde82bde9
424         .long   0xbef9a3f7,0xb2c67915,0xc67178f2,0xe372532b
425         .long   0xca273ece,0xea26619c,0xd186b8c7,0x21c0c207
426         .long   0xeada7dd6,0xcde0eb1e,0xf57d4f7f,0xee6ed178
427         .long   0x06f067aa,0x72176fba,0x0a637dc5,0xa2c898a6
428         .long   0x113f9804,0xbef90dae,0x1b710b35,0x131c471b
429         .long   0x28db77f5,0x23047d84,0x32caab7b,0x40c72493
430         .long   0x3c9ebe0a,0x15c9bebc,0x431d67c4,0x9c100d4c
431         .long   0x4cc5d4be,0xcb3e42b6,0x597f299c,0xfc657e2a
432         .long   0x5fcb6fab,0x3ad6faec,0x6c44198c,0x4a475817
433 ___
434 $code.=<<___ if ($SZ==4);
435         .long   0x428a2f98,0x71374491,0xb5c0fbcf,0xe9b5dba5
436         .long   0x3956c25b,0x59f111f1,0x923f82a4,0xab1c5ed5
437         .long   0xd807aa98,0x12835b01,0x243185be,0x550c7dc3
438         .long   0x72be5d74,0x80deb1fe,0x9bdc06a7,0xc19bf174
439         .long   0xe49b69c1,0xefbe4786,0x0fc19dc6,0x240ca1cc
440         .long   0x2de92c6f,0x4a7484aa,0x5cb0a9dc,0x76f988da
441         .long   0x983e5152,0xa831c66d,0xb00327c8,0xbf597fc7
442         .long   0xc6e00bf3,0xd5a79147,0x06ca6351,0x14292967
443         .long   0x27b70a85,0x2e1b2138,0x4d2c6dfc,0x53380d13
444         .long   0x650a7354,0x766a0abb,0x81c2c92e,0x92722c85
445         .long   0xa2bfe8a1,0xa81a664b,0xc24b8b70,0xc76c51a3
446         .long   0xd192e819,0xd6990624,0xf40e3585,0x106aa070
447         .long   0x19a4c116,0x1e376c08,0x2748774c,0x34b0bcb5
448         .long   0x391c0cb3,0x4ed8aa4a,0x5b9cca4f,0x682e6ff3
449         .long   0x748f82ee,0x78a5636f,0x84c87814,0x8cc70208
450         .long   0x90befffa,0xa4506ceb,0xbef9a3f7,0xc67178f2
451 ___
452
453 $code =~ s/\`([^\`]*)\`/eval $1/gem;
454 print $code;
455 close STDOUT;