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 	$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  ="r13";	$F="r2" if ($SIZE_T==8);# reassigned to exempt TLS pointer
    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 	$LD	$T,`$i*$SZ`($Tbl)
    127 	$ROR	$a0,$e,$Sigma1[0]
    128 	$ROR	$a1,$e,$Sigma1[1]
    129 	and	$t0,$f,$e
    130 	andc	$t1,$g,$e
    131 	add	$T,$T,$h
    132 	xor	$a0,$a0,$a1
    133 	$ROR	$a1,$a1,`$Sigma1[2]-$Sigma1[1]`
    134 	or	$t0,$t0,$t1		; Ch(e,f,g)
    135 	add	$T,$T,@X[$i]
    136 	xor	$a0,$a0,$a1		; Sigma1(e)
    137 	add	$T,$T,$t0
    138 	add	$T,$T,$a0
    139 
    140 	$ROR	$a0,$a,$Sigma0[0]
    141 	$ROR	$a1,$a,$Sigma0[1]
    142 	and	$t0,$a,$b
    143 	and	$t1,$a,$c
    144 	xor	$a0,$a0,$a1
    145 	$ROR	$a1,$a1,`$Sigma0[2]-$Sigma0[1]`
    146 	xor	$t0,$t0,$t1
    147 	and	$t1,$b,$c
    148 	xor	$a0,$a0,$a1		; Sigma0(a)
    149 	add	$d,$d,$T
    150 	xor	$t0,$t0,$t1		; Maj(a,b,c)
    151 	add	$h,$T,$a0
    152 	add	$h,$h,$t0
    153 
    154 ___
    155 }
    156 
    157 sub ROUND_16_xx {
    158 my ($i,$a,$b,$c,$d,$e,$f,$g,$h)=@_;
    159 $i-=16;
    160 $code.=<<___;
    161 	$ROR	$a0,@X[($i+1)%16],$sigma0[0]
    162 	$ROR	$a1,@X[($i+1)%16],$sigma0[1]
    163 	$ROR	$t0,@X[($i+14)%16],$sigma1[0]
    164 	$ROR	$t1,@X[($i+14)%16],$sigma1[1]
    165 	xor	$a0,$a0,$a1
    166 	$SHR	$a1,@X[($i+1)%16],$sigma0[2]
    167 	xor	$t0,$t0,$t1
    168 	$SHR	$t1,@X[($i+14)%16],$sigma1[2]
    169 	add	@X[$i],@X[$i],@X[($i+9)%16]
    170 	xor	$a0,$a0,$a1		; sigma0(X[(i+1)&0x0f])
    171 	xor	$t0,$t0,$t1		; sigma1(X[(i+14)&0x0f])
    172 	add	@X[$i],@X[$i],$a0
    173 	add	@X[$i],@X[$i],$t0
    174 ___
    175 &ROUND_00_15($i,$a,$b,$c,$d,$e,$f,$g,$h);
    176 }
    177 
    178 $code=<<___;
    179 .machine	"any"
    180 .text
    181 
    182 .globl	$func
    183 .align	6
    184 $func:
    185 	$STU	$sp,-$FRAME($sp)
    186 	mflr	r0
    187 	$SHL	$num,$num,`log(16*$SZ)/log(2)`
    188 
    189 	$PUSH	$ctx,`$FRAME-$SIZE_T*22`($sp)
    190 
    191 	$PUSH	$toc,`$FRAME-$SIZE_T*20`($sp)
    192 	$PUSH	r13,`$FRAME-$SIZE_T*19`($sp)
    193 	$PUSH	r14,`$FRAME-$SIZE_T*18`($sp)
    194 	$PUSH	r15,`$FRAME-$SIZE_T*17`($sp)
    195 	$PUSH	r16,`$FRAME-$SIZE_T*16`($sp)
    196 	$PUSH	r17,`$FRAME-$SIZE_T*15`($sp)
    197 	$PUSH	r18,`$FRAME-$SIZE_T*14`($sp)
    198 	$PUSH	r19,`$FRAME-$SIZE_T*13`($sp)
    199 	$PUSH	r20,`$FRAME-$SIZE_T*12`($sp)
    200 	$PUSH	r21,`$FRAME-$SIZE_T*11`($sp)
    201 	$PUSH	r22,`$FRAME-$SIZE_T*10`($sp)
    202 	$PUSH	r23,`$FRAME-$SIZE_T*9`($sp)
    203 	$PUSH	r24,`$FRAME-$SIZE_T*8`($sp)
    204 	$PUSH	r25,`$FRAME-$SIZE_T*7`($sp)
    205 	$PUSH	r26,`$FRAME-$SIZE_T*6`($sp)
    206 	$PUSH	r27,`$FRAME-$SIZE_T*5`($sp)
    207 	$PUSH	r28,`$FRAME-$SIZE_T*4`($sp)
    208 	$PUSH	r29,`$FRAME-$SIZE_T*3`($sp)
    209 	$PUSH	r30,`$FRAME-$SIZE_T*2`($sp)
    210 	$PUSH	r31,`$FRAME-$SIZE_T*1`($sp)
    211 	$PUSH	r0,`$FRAME+$LRSAVE`($sp)
    212 
    213 	$LD	$A,`0*$SZ`($ctx)
    214 	mr	$inp,r4				; incarnate $inp
    215 	$LD	$B,`1*$SZ`($ctx)
    216 	$LD	$C,`2*$SZ`($ctx)
    217 	$LD	$D,`3*$SZ`($ctx)
    218 	$LD	$E,`4*$SZ`($ctx)
    219 	$LD	$F,`5*$SZ`($ctx)
    220 	$LD	$G,`6*$SZ`($ctx)
    221 	$LD	$H,`7*$SZ`($ctx)
    222 
    223 	bl	LPICmeup
    224 LPICedup:
    225 	andi.	r0,$inp,3
    226 	bne	Lunaligned
    227 Laligned:
    228 	add	$num,$inp,$num
    229 	$PUSH	$num,`$FRAME-$SIZE_T*24`($sp)	; end pointer
    230 	$PUSH	$inp,`$FRAME-$SIZE_T*23`($sp)	; inp pointer
    231 	bl	Lsha2_block_private
    232 	b	Ldone
    233 
    234 ; PowerPC specification allows an implementation to be ill-behaved
    235 ; upon unaligned access which crosses page boundary. "Better safe
    236 ; than sorry" principle makes me treat it specially. But I don't
    237 ; look for particular offending word, but rather for the input
    238 ; block which crosses the boundary. Once found that block is aligned
    239 ; and hashed separately...
    240 .align	4
    241 Lunaligned:
    242 	subfic	$t1,$inp,4096
    243 	andi.	$t1,$t1,`4096-16*$SZ`	; distance to closest page boundary
    244 	beq	Lcross_page
    245 	$UCMP	$num,$t1
    246 	ble-	Laligned		; didn't cross the page boundary
    247 	subfc	$num,$t1,$num
    248 	add	$t1,$inp,$t1
    249 	$PUSH	$num,`$FRAME-$SIZE_T*25`($sp)	; save real remaining num
    250 	$PUSH	$t1,`$FRAME-$SIZE_T*24`($sp)	; intermediate end pointer
    251 	$PUSH	$inp,`$FRAME-$SIZE_T*23`($sp)	; inp pointer
    252 	bl	Lsha2_block_private
    253 	; $inp equals to the intermediate end pointer here
    254 	$POP	$num,`$FRAME-$SIZE_T*25`($sp)	; restore real remaining num
    255 Lcross_page:
    256 	li	$t1,`16*$SZ/4`
    257 	mtctr	$t1
    258 	addi	r20,$sp,$LOCALS			; aligned spot below the frame
    259 Lmemcpy:
    260 	lbz	r16,0($inp)
    261 	lbz	r17,1($inp)
    262 	lbz	r18,2($inp)
    263 	lbz	r19,3($inp)
    264 	addi	$inp,$inp,4
    265 	stb	r16,0(r20)
    266 	stb	r17,1(r20)
    267 	stb	r18,2(r20)
    268 	stb	r19,3(r20)
    269 	addi	r20,r20,4
    270 	bdnz	Lmemcpy
    271 
    272 	$PUSH	$inp,`$FRAME-$SIZE_T*26`($sp)	; save real inp
    273 	addi	$t1,$sp,`$LOCALS+16*$SZ`	; fictitious end pointer
    274 	addi	$inp,$sp,$LOCALS		; fictitious inp pointer
    275 	$PUSH	$num,`$FRAME-$SIZE_T*25`($sp)	; save real num
    276 	$PUSH	$t1,`$FRAME-$SIZE_T*24`($sp)	; end pointer
    277 	$PUSH	$inp,`$FRAME-$SIZE_T*23`($sp)	; inp pointer
    278 	bl	Lsha2_block_private
    279 	$POP	$inp,`$FRAME-$SIZE_T*26`($sp)	; restore real inp
    280 	$POP	$num,`$FRAME-$SIZE_T*25`($sp)	; restore real num
    281 	addic.	$num,$num,`-16*$SZ`		; num--
    282 	bne-	Lunaligned
    283 
    284 Ldone:
    285 	$POP	r0,`$FRAME+$LRSAVE`($sp)
    286 	$POP	$toc,`$FRAME-$SIZE_T*20`($sp)
    287 	$POP	r13,`$FRAME-$SIZE_T*19`($sp)
    288 	$POP	r14,`$FRAME-$SIZE_T*18`($sp)
    289 	$POP	r15,`$FRAME-$SIZE_T*17`($sp)
    290 	$POP	r16,`$FRAME-$SIZE_T*16`($sp)
    291 	$POP	r17,`$FRAME-$SIZE_T*15`($sp)
    292 	$POP	r18,`$FRAME-$SIZE_T*14`($sp)
    293 	$POP	r19,`$FRAME-$SIZE_T*13`($sp)
    294 	$POP	r20,`$FRAME-$SIZE_T*12`($sp)
    295 	$POP	r21,`$FRAME-$SIZE_T*11`($sp)
    296 	$POP	r22,`$FRAME-$SIZE_T*10`($sp)
    297 	$POP	r23,`$FRAME-$SIZE_T*9`($sp)
    298 	$POP	r24,`$FRAME-$SIZE_T*8`($sp)
    299 	$POP	r25,`$FRAME-$SIZE_T*7`($sp)
    300 	$POP	r26,`$FRAME-$SIZE_T*6`($sp)
    301 	$POP	r27,`$FRAME-$SIZE_T*5`($sp)
    302 	$POP	r28,`$FRAME-$SIZE_T*4`($sp)
    303 	$POP	r29,`$FRAME-$SIZE_T*3`($sp)
    304 	$POP	r30,`$FRAME-$SIZE_T*2`($sp)
    305 	$POP	r31,`$FRAME-$SIZE_T*1`($sp)
    306 	mtlr	r0
    307 	addi	$sp,$sp,$FRAME
    308 	blr
    309 	.long	0
    310 	.byte	0,12,4,1,0x80,18,3,0
    311 	.long	0
    312 
    313 .align	4
    314 Lsha2_block_private:
    315 ___
    316 for($i=0;$i<16;$i++) {
    317 $code.=<<___ if ($SZ==4);
    318 	lwz	@X[$i],`$i*$SZ`($inp)
    319 ___
    320 # 64-bit loads are split to 2x32-bit ones, as CPU can't handle
    321 # unaligned 64-bit loads, only 32-bit ones...
    322 $code.=<<___ if ($SZ==8);
    323 	lwz	$t0,`$i*$SZ`($inp)
    324 	lwz	@X[$i],`$i*$SZ+4`($inp)
    325 	insrdi	@X[$i],$t0,32,0
    326 ___
    327 	&ROUND_00_15($i,@V);
    328 	unshift(@V,pop(@V));
    329 }
    330 $code.=<<___;
    331 	li	$T,`$rounds/16-1`
    332 	mtctr	$T
    333 .align	4
    334 Lrounds:
    335 	addi	$Tbl,$Tbl,`16*$SZ`
    336 ___
    337 for(;$i<32;$i++) {
    338 	&ROUND_16_xx($i,@V);
    339 	unshift(@V,pop(@V));
    340 }
    341 $code.=<<___;
    342 	bdnz-	Lrounds
    343 
    344 	$POP	$ctx,`$FRAME-$SIZE_T*22`($sp)
    345 	$POP	$inp,`$FRAME-$SIZE_T*23`($sp)	; inp pointer
    346 	$POP	$num,`$FRAME-$SIZE_T*24`($sp)	; end pointer
    347 	subi	$Tbl,$Tbl,`($rounds-16)*$SZ`	; rewind Tbl
    348 
    349 	$LD	r16,`0*$SZ`($ctx)
    350 	$LD	r17,`1*$SZ`($ctx)
    351 	$LD	r18,`2*$SZ`($ctx)
    352 	$LD	r19,`3*$SZ`($ctx)
    353 	$LD	r20,`4*$SZ`($ctx)
    354 	$LD	r21,`5*$SZ`($ctx)
    355 	$LD	r22,`6*$SZ`($ctx)
    356 	addi	$inp,$inp,`16*$SZ`		; advance inp
    357 	$LD	r23,`7*$SZ`($ctx)
    358 	add	$A,$A,r16
    359 	add	$B,$B,r17
    360 	$PUSH	$inp,`$FRAME-$SIZE_T*23`($sp)
    361 	add	$C,$C,r18
    362 	$ST	$A,`0*$SZ`($ctx)
    363 	add	$D,$D,r19
    364 	$ST	$B,`1*$SZ`($ctx)
    365 	add	$E,$E,r20
    366 	$ST	$C,`2*$SZ`($ctx)
    367 	add	$F,$F,r21
    368 	$ST	$D,`3*$SZ`($ctx)
    369 	add	$G,$G,r22
    370 	$ST	$E,`4*$SZ`($ctx)
    371 	add	$H,$H,r23
    372 	$ST	$F,`5*$SZ`($ctx)
    373 	$ST	$G,`6*$SZ`($ctx)
    374 	$UCMP	$inp,$num
    375 	$ST	$H,`7*$SZ`($ctx)
    376 	bne	Lsha2_block_private
    377 	blr
    378 	.long	0
    379 	.byte	0,12,0x14,0,0,0,0,0
    380 ___
    381 
    382 # Ugly hack here, because PPC assembler syntax seem to vary too
    383 # much from platforms to platform...
    384 $code.=<<___;
    385 .align	6
    386 LPICmeup:
    387 	mflr	r0
    388 	bcl	20,31,\$+4
    389 	mflr	$Tbl	; vvvvvv "distance" between . and 1st data entry
    390 	addi	$Tbl,$Tbl,`64-8`
    391 	mtlr	r0
    392 	blr
    393 	.long	0
    394 	.byte	0,12,0x14,0,0,0,0,0
    395 	.space	`64-9*4`
    396 ___
    397 $code.=<<___ if ($SZ==8);
    398 	.long	0x428a2f98,0xd728ae22,0x71374491,0x23ef65cd
    399 	.long	0xb5c0fbcf,0xec4d3b2f,0xe9b5dba5,0x8189dbbc
    400 	.long	0x3956c25b,0xf348b538,0x59f111f1,0xb605d019
    401 	.long	0x923f82a4,0xaf194f9b,0xab1c5ed5,0xda6d8118
    402 	.long	0xd807aa98,0xa3030242,0x12835b01,0x45706fbe
    403 	.long	0x243185be,0x4ee4b28c,0x550c7dc3,0xd5ffb4e2
    404 	.long	0x72be5d74,0xf27b896f,0x80deb1fe,0x3b1696b1
    405 	.long	0x9bdc06a7,0x25c71235,0xc19bf174,0xcf692694
    406 	.long	0xe49b69c1,0x9ef14ad2,0xefbe4786,0x384f25e3
    407 	.long	0x0fc19dc6,0x8b8cd5b5,0x240ca1cc,0x77ac9c65
    408 	.long	0x2de92c6f,0x592b0275,0x4a7484aa,0x6ea6e483
    409 	.long	0x5cb0a9dc,0xbd41fbd4,0x76f988da,0x831153b5
    410 	.long	0x983e5152,0xee66dfab,0xa831c66d,0x2db43210
    411 	.long	0xb00327c8,0x98fb213f,0xbf597fc7,0xbeef0ee4
    412 	.long	0xc6e00bf3,0x3da88fc2,0xd5a79147,0x930aa725
    413 	.long	0x06ca6351,0xe003826f,0x14292967,0x0a0e6e70
    414 	.long	0x27b70a85,0x46d22ffc,0x2e1b2138,0x5c26c926
    415 	.long	0x4d2c6dfc,0x5ac42aed,0x53380d13,0x9d95b3df
    416 	.long	0x650a7354,0x8baf63de,0x766a0abb,0x3c77b2a8
    417 	.long	0x81c2c92e,0x47edaee6,0x92722c85,0x1482353b
    418 	.long	0xa2bfe8a1,0x4cf10364,0xa81a664b,0xbc423001
    419 	.long	0xc24b8b70,0xd0f89791,0xc76c51a3,0x0654be30
    420 	.long	0xd192e819,0xd6ef5218,0xd6990624,0x5565a910
    421 	.long	0xf40e3585,0x5771202a,0x106aa070,0x32bbd1b8
    422 	.long	0x19a4c116,0xb8d2d0c8,0x1e376c08,0x5141ab53
    423 	.long	0x2748774c,0xdf8eeb99,0x34b0bcb5,0xe19b48a8
    424 	.long	0x391c0cb3,0xc5c95a63,0x4ed8aa4a,0xe3418acb
    425 	.long	0x5b9cca4f,0x7763e373,0x682e6ff3,0xd6b2b8a3
    426 	.long	0x748f82ee,0x5defb2fc,0x78a5636f,0x43172f60
    427 	.long	0x84c87814,0xa1f0ab72,0x8cc70208,0x1a6439ec
    428 	.long	0x90befffa,0x23631e28,0xa4506ceb,0xde82bde9
    429 	.long	0xbef9a3f7,0xb2c67915,0xc67178f2,0xe372532b
    430 	.long	0xca273ece,0xea26619c,0xd186b8c7,0x21c0c207
    431 	.long	0xeada7dd6,0xcde0eb1e,0xf57d4f7f,0xee6ed178
    432 	.long	0x06f067aa,0x72176fba,0x0a637dc5,0xa2c898a6
    433 	.long	0x113f9804,0xbef90dae,0x1b710b35,0x131c471b
    434 	.long	0x28db77f5,0x23047d84,0x32caab7b,0x40c72493
    435 	.long	0x3c9ebe0a,0x15c9bebc,0x431d67c4,0x9c100d4c
    436 	.long	0x4cc5d4be,0xcb3e42b6,0x597f299c,0xfc657e2a
    437 	.long	0x5fcb6fab,0x3ad6faec,0x6c44198c,0x4a475817
    438 ___
    439 $code.=<<___ if ($SZ==4);
    440 	.long	0x428a2f98,0x71374491,0xb5c0fbcf,0xe9b5dba5
    441 	.long	0x3956c25b,0x59f111f1,0x923f82a4,0xab1c5ed5
    442 	.long	0xd807aa98,0x12835b01,0x243185be,0x550c7dc3
    443 	.long	0x72be5d74,0x80deb1fe,0x9bdc06a7,0xc19bf174
    444 	.long	0xe49b69c1,0xefbe4786,0x0fc19dc6,0x240ca1cc
    445 	.long	0x2de92c6f,0x4a7484aa,0x5cb0a9dc,0x76f988da
    446 	.long	0x983e5152,0xa831c66d,0xb00327c8,0xbf597fc7
    447 	.long	0xc6e00bf3,0xd5a79147,0x06ca6351,0x14292967
    448 	.long	0x27b70a85,0x2e1b2138,0x4d2c6dfc,0x53380d13
    449 	.long	0x650a7354,0x766a0abb,0x81c2c92e,0x92722c85
    450 	.long	0xa2bfe8a1,0xa81a664b,0xc24b8b70,0xc76c51a3
    451 	.long	0xd192e819,0xd6990624,0xf40e3585,0x106aa070
    452 	.long	0x19a4c116,0x1e376c08,0x2748774c,0x34b0bcb5
    453 	.long	0x391c0cb3,0x4ed8aa4a,0x5b9cca4f,0x682e6ff3
    454 	.long	0x748f82ee,0x78a5636f,0x84c87814,0x8cc70208
    455 	.long	0x90befffa,0xa4506ceb,0xbef9a3f7,0xc67178f2
    456 ___
    457 
    458 $code =~ s/\`([^\`]*)\`/eval $1/gem;
    459 print $code;
    460 close STDOUT;
    461