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