Home | History | Annotate | Download | only in asm
      1 #!/usr/bin/env perl
      2 
      3 # ====================================================================
      4 # Written by Andy Polyakov <appro (at] 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 	$STU="stdu";
     44 	$UCMP="cmpld";
     45 	$SHL="sldi";
     46 	$POP="ld";
     47 	$PUSH="std";
     48 } elsif ($flavour =~ /32/) {
     49 	$SIZE_T=4;
     50 	$STU="stwu";
     51 	$UCMP="cmplw";
     52 	$SHL="slwi";
     53 	$POP="lwz";
     54 	$PUSH="stw";
     55 } else { die "nonsense $flavour"; }
     56 
     57 $0 =~ m/(.*[\/\\])[^\/\\]+$/; $dir=$1;
     58 ( $xlate="${dir}ppc-xlate.pl" and -f $xlate ) or
     59 ( $xlate="${dir}../../perlasm/ppc-xlate.pl" and -f $xlate) or
     60 die "can't locate ppc-xlate.pl";
     61 
     62 open STDOUT,"| $^X $xlate $flavour $output" || die "can't call $xlate: $!";
     63 
     64 if ($output =~ /512/) {
     65 	$func="sha512_block_data_order";
     66 	$SZ=8;
     67 	@Sigma0=(28,34,39);
     68 	@Sigma1=(14,18,41);
     69 	@sigma0=(1,  8, 7);
     70 	@sigma1=(19,61, 6);
     71 	$rounds=80;
     72 	$LD="ld";
     73 	$ST="std";
     74 	$ROR="rotrdi";
     75 	$SHR="srdi";
     76 } else {
     77 	$func="sha256_block_data_order";
     78 	$SZ=4;
     79 	@Sigma0=( 2,13,22);
     80 	@Sigma1=( 6,11,25);
     81 	@sigma0=( 7,18, 3);
     82 	@sigma1=(17,19,10);
     83 	$rounds=64;
     84 	$LD="lwz";
     85 	$ST="stw";
     86 	$ROR="rotrwi";
     87 	$SHR="srwi";
     88 }
     89 
     90 $FRAME=32*$SIZE_T;
     91 
     92 $sp ="r1";
     93 $toc="r2";
     94 $ctx="r3";	# zapped by $a0
     95 $inp="r4";	# zapped by $a1
     96 $num="r5";	# zapped by $t0
     97 
     98 $T  ="r0";
     99 $a0 ="r3";
    100 $a1 ="r4";
    101 $t0 ="r5";
    102 $t1 ="r6";
    103 $Tbl="r7";
    104 
    105 $A  ="r8";
    106 $B  ="r9";
    107 $C  ="r10";
    108 $D  ="r11";
    109 $E  ="r12";
    110 $F  ="r13";	$F="r2" if ($SIZE_T==8);# reassigned to exempt TLS pointer
    111 $G  ="r14";
    112 $H  ="r15";
    113 
    114 @V=($A,$B,$C,$D,$E,$F,$G,$H);
    115 @X=("r16","r17","r18","r19","r20","r21","r22","r23",
    116     "r24","r25","r26","r27","r28","r29","r30","r31");
    117 
    118 $inp="r31";	# reassigned $inp! aliases with @X[15]
    119 
    120 sub ROUND_00_15 {
    121 my ($i,$a,$b,$c,$d,$e,$f,$g,$h)=@_;
    122 $code.=<<___;
    123 	$LD	$T,`$i*$SZ`($Tbl)
    124 	$ROR	$a0,$e,$Sigma1[0]
    125 	$ROR	$a1,$e,$Sigma1[1]
    126 	and	$t0,$f,$e
    127 	andc	$t1,$g,$e
    128 	add	$T,$T,$h
    129 	xor	$a0,$a0,$a1
    130 	$ROR	$a1,$a1,`$Sigma1[2]-$Sigma1[1]`
    131 	or	$t0,$t0,$t1		; Ch(e,f,g)
    132 	add	$T,$T,@X[$i]
    133 	xor	$a0,$a0,$a1		; Sigma1(e)
    134 	add	$T,$T,$t0
    135 	add	$T,$T,$a0
    136 
    137 	$ROR	$a0,$a,$Sigma0[0]
    138 	$ROR	$a1,$a,$Sigma0[1]
    139 	and	$t0,$a,$b
    140 	and	$t1,$a,$c
    141 	xor	$a0,$a0,$a1
    142 	$ROR	$a1,$a1,`$Sigma0[2]-$Sigma0[1]`
    143 	xor	$t0,$t0,$t1
    144 	and	$t1,$b,$c
    145 	xor	$a0,$a0,$a1		; Sigma0(a)
    146 	add	$d,$d,$T
    147 	xor	$t0,$t0,$t1		; Maj(a,b,c)
    148 	add	$h,$T,$a0
    149 	add	$h,$h,$t0
    150 
    151 ___
    152 }
    153 
    154 sub ROUND_16_xx {
    155 my ($i,$a,$b,$c,$d,$e,$f,$g,$h)=@_;
    156 $i-=16;
    157 $code.=<<___;
    158 	$ROR	$a0,@X[($i+1)%16],$sigma0[0]
    159 	$ROR	$a1,@X[($i+1)%16],$sigma0[1]
    160 	$ROR	$t0,@X[($i+14)%16],$sigma1[0]
    161 	$ROR	$t1,@X[($i+14)%16],$sigma1[1]
    162 	xor	$a0,$a0,$a1
    163 	$SHR	$a1,@X[($i+1)%16],$sigma0[2]
    164 	xor	$t0,$t0,$t1
    165 	$SHR	$t1,@X[($i+14)%16],$sigma1[2]
    166 	add	@X[$i],@X[$i],@X[($i+9)%16]
    167 	xor	$a0,$a0,$a1		; sigma0(X[(i+1)&0x0f])
    168 	xor	$t0,$t0,$t1		; sigma1(X[(i+14)&0x0f])
    169 	add	@X[$i],@X[$i],$a0
    170 	add	@X[$i],@X[$i],$t0
    171 ___
    172 &ROUND_00_15($i,$a,$b,$c,$d,$e,$f,$g,$h);
    173 }
    174 
    175 $code=<<___;
    176 .machine	"any"
    177 .text
    178 
    179 .globl	$func
    180 .align	6
    181 $func:
    182 	mflr	r0
    183 	$STU	$sp,`-($FRAME+16*$SZ)`($sp)
    184 	$SHL	$num,$num,`log(16*$SZ)/log(2)`
    185 
    186 	$PUSH	$ctx,`$FRAME-$SIZE_T*22`($sp)
    187 
    188 	$PUSH	r0,`$FRAME-$SIZE_T*21`($sp)
    189 	$PUSH	$toc,`$FRAME-$SIZE_T*20`($sp)
    190 	$PUSH	r13,`$FRAME-$SIZE_T*19`($sp)
    191 	$PUSH	r14,`$FRAME-$SIZE_T*18`($sp)
    192 	$PUSH	r15,`$FRAME-$SIZE_T*17`($sp)
    193 	$PUSH	r16,`$FRAME-$SIZE_T*16`($sp)
    194 	$PUSH	r17,`$FRAME-$SIZE_T*15`($sp)
    195 	$PUSH	r18,`$FRAME-$SIZE_T*14`($sp)
    196 	$PUSH	r19,`$FRAME-$SIZE_T*13`($sp)
    197 	$PUSH	r20,`$FRAME-$SIZE_T*12`($sp)
    198 	$PUSH	r21,`$FRAME-$SIZE_T*11`($sp)
    199 	$PUSH	r22,`$FRAME-$SIZE_T*10`($sp)
    200 	$PUSH	r23,`$FRAME-$SIZE_T*9`($sp)
    201 	$PUSH	r24,`$FRAME-$SIZE_T*8`($sp)
    202 	$PUSH	r25,`$FRAME-$SIZE_T*7`($sp)
    203 	$PUSH	r26,`$FRAME-$SIZE_T*6`($sp)
    204 	$PUSH	r27,`$FRAME-$SIZE_T*5`($sp)
    205 	$PUSH	r28,`$FRAME-$SIZE_T*4`($sp)
    206 	$PUSH	r29,`$FRAME-$SIZE_T*3`($sp)
    207 	$PUSH	r30,`$FRAME-$SIZE_T*2`($sp)
    208 	$PUSH	r31,`$FRAME-$SIZE_T*1`($sp)
    209 
    210 	$LD	$A,`0*$SZ`($ctx)
    211 	mr	$inp,r4				; incarnate $inp
    212 	$LD	$B,`1*$SZ`($ctx)
    213 	$LD	$C,`2*$SZ`($ctx)
    214 	$LD	$D,`3*$SZ`($ctx)
    215 	$LD	$E,`4*$SZ`($ctx)
    216 	$LD	$F,`5*$SZ`($ctx)
    217 	$LD	$G,`6*$SZ`($ctx)
    218 	$LD	$H,`7*$SZ`($ctx)
    219 
    220 	b	LPICmeup
    221 LPICedup:
    222 	andi.	r0,$inp,3
    223 	bne	Lunaligned
    224 Laligned:
    225 	add	$num,$inp,$num
    226 	$PUSH	$num,`$FRAME-$SIZE_T*24`($sp)	; end pointer
    227 	$PUSH	$inp,`$FRAME-$SIZE_T*23`($sp)	; inp pointer
    228 	bl	Lsha2_block_private
    229 Ldone:
    230 	$POP	r0,`$FRAME-$SIZE_T*21`($sp)
    231 	$POP	$toc,`$FRAME-$SIZE_T*20`($sp)
    232 	$POP	r13,`$FRAME-$SIZE_T*19`($sp)
    233 	$POP	r14,`$FRAME-$SIZE_T*18`($sp)
    234 	$POP	r15,`$FRAME-$SIZE_T*17`($sp)
    235 	$POP	r16,`$FRAME-$SIZE_T*16`($sp)
    236 	$POP	r17,`$FRAME-$SIZE_T*15`($sp)
    237 	$POP	r18,`$FRAME-$SIZE_T*14`($sp)
    238 	$POP	r19,`$FRAME-$SIZE_T*13`($sp)
    239 	$POP	r20,`$FRAME-$SIZE_T*12`($sp)
    240 	$POP	r21,`$FRAME-$SIZE_T*11`($sp)
    241 	$POP	r22,`$FRAME-$SIZE_T*10`($sp)
    242 	$POP	r23,`$FRAME-$SIZE_T*9`($sp)
    243 	$POP	r24,`$FRAME-$SIZE_T*8`($sp)
    244 	$POP	r25,`$FRAME-$SIZE_T*7`($sp)
    245 	$POP	r26,`$FRAME-$SIZE_T*6`($sp)
    246 	$POP	r27,`$FRAME-$SIZE_T*5`($sp)
    247 	$POP	r28,`$FRAME-$SIZE_T*4`($sp)
    248 	$POP	r29,`$FRAME-$SIZE_T*3`($sp)
    249 	$POP	r30,`$FRAME-$SIZE_T*2`($sp)
    250 	$POP	r31,`$FRAME-$SIZE_T*1`($sp)
    251 	mtlr	r0
    252 	addi	$sp,$sp,`$FRAME+16*$SZ`
    253 	blr
    254 ___
    255 
    256 # PowerPC specification allows an implementation to be ill-behaved
    257 # upon unaligned access which crosses page boundary. "Better safe
    258 # than sorry" principle makes me treat it specially. But I don't
    259 # look for particular offending word, but rather for the input
    260 # block which crosses the boundary. Once found that block is aligned
    261 # and hashed separately...
    262 $code.=<<___;
    263 .align	4
    264 Lunaligned:
    265 	subfic	$t1,$inp,4096
    266 	andi.	$t1,$t1,`4096-16*$SZ`	; distance to closest page boundary
    267 	beq	Lcross_page
    268 	$UCMP	$num,$t1
    269 	ble-	Laligned		; didn't cross the page boundary
    270 	subfc	$num,$t1,$num
    271 	add	$t1,$inp,$t1
    272 	$PUSH	$num,`$FRAME-$SIZE_T*25`($sp)	; save real remaining num
    273 	$PUSH	$t1,`$FRAME-$SIZE_T*24`($sp)	; intermediate end pointer
    274 	$PUSH	$inp,`$FRAME-$SIZE_T*23`($sp)	; inp pointer
    275 	bl	Lsha2_block_private
    276 	; $inp equals to the intermediate end pointer here
    277 	$POP	$num,`$FRAME-$SIZE_T*25`($sp)	; restore real remaining num
    278 Lcross_page:
    279 	li	$t1,`16*$SZ/4`
    280 	mtctr	$t1
    281 	addi	r20,$sp,$FRAME			; aligned spot below the frame
    282 Lmemcpy:
    283 	lbz	r16,0($inp)
    284 	lbz	r17,1($inp)
    285 	lbz	r18,2($inp)
    286 	lbz	r19,3($inp)
    287 	addi	$inp,$inp,4
    288 	stb	r16,0(r20)
    289 	stb	r17,1(r20)
    290 	stb	r18,2(r20)
    291 	stb	r19,3(r20)
    292 	addi	r20,r20,4
    293 	bdnz	Lmemcpy
    294 
    295 	$PUSH	$inp,`$FRAME-$SIZE_T*26`($sp)	; save real inp
    296 	addi	$t1,$sp,`$FRAME+16*$SZ`		; fictitious end pointer
    297 	addi	$inp,$sp,$FRAME			; fictitious inp pointer
    298 	$PUSH	$num,`$FRAME-$SIZE_T*25`($sp)	; save real num
    299 	$PUSH	$t1,`$FRAME-$SIZE_T*24`($sp)	; end pointer
    300 	$PUSH	$inp,`$FRAME-$SIZE_T*23`($sp)	; inp pointer
    301 	bl	Lsha2_block_private
    302 	$POP	$inp,`$FRAME-$SIZE_T*26`($sp)	; restore real inp
    303 	$POP	$num,`$FRAME-$SIZE_T*25`($sp)	; restore real num
    304 	addic.	$num,$num,`-16*$SZ`		; num--
    305 	bne-	Lunaligned
    306 	b	Ldone
    307 ___
    308 
    309 $code.=<<___;
    310 .align	4
    311 Lsha2_block_private:
    312 ___
    313 for($i=0;$i<16;$i++) {
    314 $code.=<<___ if ($SZ==4);
    315 	lwz	@X[$i],`$i*$SZ`($inp)
    316 ___
    317 # 64-bit loads are split to 2x32-bit ones, as CPU can't handle
    318 # unaligned 64-bit loads, only 32-bit ones...
    319 $code.=<<___ if ($SZ==8);
    320 	lwz	$t0,`$i*$SZ`($inp)
    321 	lwz	@X[$i],`$i*$SZ+4`($inp)
    322 	insrdi	@X[$i],$t0,32,0
    323 ___
    324 	&ROUND_00_15($i,@V);
    325 	unshift(@V,pop(@V));
    326 }
    327 $code.=<<___;
    328 	li	$T,`$rounds/16-1`
    329 	mtctr	$T
    330 .align	4
    331 Lrounds:
    332 	addi	$Tbl,$Tbl,`16*$SZ`
    333 ___
    334 for(;$i<32;$i++) {
    335 	&ROUND_16_xx($i,@V);
    336 	unshift(@V,pop(@V));
    337 }
    338 $code.=<<___;
    339 	bdnz-	Lrounds
    340 
    341 	$POP	$ctx,`$FRAME-$SIZE_T*22`($sp)
    342 	$POP	$inp,`$FRAME-$SIZE_T*23`($sp)	; inp pointer
    343 	$POP	$num,`$FRAME-$SIZE_T*24`($sp)	; end pointer
    344 	subi	$Tbl,$Tbl,`($rounds-16)*$SZ`	; rewind Tbl
    345 
    346 	$LD	r16,`0*$SZ`($ctx)
    347 	$LD	r17,`1*$SZ`($ctx)
    348 	$LD	r18,`2*$SZ`($ctx)
    349 	$LD	r19,`3*$SZ`($ctx)
    350 	$LD	r20,`4*$SZ`($ctx)
    351 	$LD	r21,`5*$SZ`($ctx)
    352 	$LD	r22,`6*$SZ`($ctx)
    353 	addi	$inp,$inp,`16*$SZ`		; advance inp
    354 	$LD	r23,`7*$SZ`($ctx)
    355 	add	$A,$A,r16
    356 	add	$B,$B,r17
    357 	$PUSH	$inp,`$FRAME-$SIZE_T*23`($sp)
    358 	add	$C,$C,r18
    359 	$ST	$A,`0*$SZ`($ctx)
    360 	add	$D,$D,r19
    361 	$ST	$B,`1*$SZ`($ctx)
    362 	add	$E,$E,r20
    363 	$ST	$C,`2*$SZ`($ctx)
    364 	add	$F,$F,r21
    365 	$ST	$D,`3*$SZ`($ctx)
    366 	add	$G,$G,r22
    367 	$ST	$E,`4*$SZ`($ctx)
    368 	add	$H,$H,r23
    369 	$ST	$F,`5*$SZ`($ctx)
    370 	$ST	$G,`6*$SZ`($ctx)
    371 	$UCMP	$inp,$num
    372 	$ST	$H,`7*$SZ`($ctx)
    373 	bne	Lsha2_block_private
    374 	blr
    375 ___
    376 
    377 # Ugly hack here, because PPC assembler syntax seem to vary too
    378 # much from platforms to platform...
    379 $code.=<<___;
    380 .align	6
    381 LPICmeup:
    382 	bl	LPIC
    383 	addi	$Tbl,$Tbl,`64-4`	; "distance" between . and last nop
    384 	b	LPICedup
    385 	nop
    386 	nop
    387 	nop
    388 	nop
    389 	nop
    390 LPIC:	mflr	$Tbl
    391 	blr
    392 	nop
    393 	nop
    394 	nop
    395 	nop
    396 	nop
    397 	nop
    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;
    463