• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1#! /usr/bin/env perl
2# Copyright 2013-2016 The OpenSSL Project Authors. All Rights Reserved.
3#
4# Licensed under the OpenSSL license (the "License").  You may not use
5# this file except in compliance with the License.  You can obtain a copy
6# in the file LICENSE in the source distribution or at
7# https://www.openssl.org/source/license.html
8
9#
10# ====================================================================
11# Written by Andy Polyakov <appro@openssl.org> for the OpenSSL
12# project. The module is, however, dual licensed under OpenSSL and
13# CRYPTOGAMS licenses depending on where you obtain it. For further
14# details see http://www.openssl.org/~appro/cryptogams/.
15# ====================================================================
16#
17#
18# AES-NI-CTR+GHASH stitch.
19#
20# February 2013
21#
22# OpenSSL GCM implementation is organized in such way that its
23# performance is rather close to the sum of its streamed components,
24# in the context parallelized AES-NI CTR and modulo-scheduled
25# PCLMULQDQ-enabled GHASH. Unfortunately, as no stitch implementation
26# was observed to perform significantly better than the sum of the
27# components on contemporary CPUs, the effort was deemed impossible to
28# justify. This module is based on combination of Intel submissions,
29# [1] and [2], with MOVBE twist suggested by Ilya Albrekht and Max
30# Locktyukhin of Intel Corp. who verified that it reduces shuffles
31# pressure with notable relative improvement, achieving 1.0 cycle per
32# byte processed with 128-bit key on Haswell processor, 0.74 - on
33# Broadwell, 0.63 - on Skylake... [Mentioned results are raw profiled
34# measurements for favourable packet size, one divisible by 96.
35# Applications using the EVP interface will observe a few percent
36# worse performance.]
37#
38# Knights Landing processes 1 byte in 1.25 cycles (measured with EVP).
39#
40# [1] http://rt.openssl.org/Ticket/Display.html?id=2900&user=guest&pass=guest
41# [2] http://www.intel.com/content/dam/www/public/us/en/documents/software-support/enabling-high-performance-gcm.pdf
42
43$flavour = shift;
44$output  = shift;
45if ($flavour =~ /\./) { $output = $flavour; undef $flavour; }
46
47$win64=0; $win64=1 if ($flavour =~ /[nm]asm|mingw64/ || $output =~ /\.asm$/);
48
49$0 =~ m/(.*[\/\\])[^\/\\]+$/; $dir=$1;
50( $xlate="${dir}x86_64-xlate.pl" and -f $xlate ) or
51( $xlate="${dir}../../../perlasm/x86_64-xlate.pl" and -f $xlate) or
52die "can't locate x86_64-xlate.pl";
53
54# |$avx| in ghash-x86_64.pl must be set to at least 1; otherwise tags will
55# be computed incorrectly.
56#
57# In upstream, this is controlled by shelling out to the compiler to check
58# versions, but BoringSSL is intended to be used with pre-generated perlasm
59# output, so this isn't useful anyway.
60#
61# The upstream code uses the condition |$avx>1| even though no AVX2
62# instructions are used, because it assumes MOVBE is supported by the assembler
63# if and only if AVX2 is also supported by the assembler; see
64# https://marc.info/?l=openssl-dev&m=146567589526984&w=2.
65$avx = 2;
66
67open OUT,"| \"$^X\" \"$xlate\" $flavour \"$output\"";
68*STDOUT=*OUT;
69
70# See the comment above regarding why the condition is ($avx>1) when there are
71# no AVX2 instructions being used.
72if ($avx>1) {{{
73
74($inp,$out,$len,$key,$ivp,$Xip)=("%rdi","%rsi","%rdx","%rcx","%r8","%r9");
75
76($Ii,$T1,$T2,$Hkey,
77 $Z0,$Z1,$Z2,$Z3,$Xi) = map("%xmm$_",(0..8));
78
79($inout0,$inout1,$inout2,$inout3,$inout4,$inout5,$rndkey) = map("%xmm$_",(9..15));
80
81($counter,$rounds,$ret,$const,$in0,$end0)=("%ebx","%ebp","%r10","%r11","%r14","%r15");
82
83$code=<<___;
84.text
85
86.type	_aesni_ctr32_ghash_6x,\@abi-omnipotent
87.align	32
88_aesni_ctr32_ghash_6x:
89.cfi_startproc
90	vmovdqu		0x20($const),$T2	# borrow $T2, .Lone_msb
91	sub		\$6,$len
92	vpxor		$Z0,$Z0,$Z0		# $Z0   = 0
93	vmovdqu		0x00-0x80($key),$rndkey
94	vpaddb		$T2,$T1,$inout1
95	vpaddb		$T2,$inout1,$inout2
96	vpaddb		$T2,$inout2,$inout3
97	vpaddb		$T2,$inout3,$inout4
98	vpaddb		$T2,$inout4,$inout5
99	vpxor		$rndkey,$T1,$inout0
100	vmovdqu		$Z0,16+8(%rsp)		# "$Z3" = 0
101	jmp		.Loop6x
102
103.align	32
104.Loop6x:
105	add		\$`6<<24`,$counter
106	jc		.Lhandle_ctr32		# discard $inout[1-5]?
107	vmovdqu		0x00-0x20($Xip),$Hkey	# $Hkey^1
108	  vpaddb	$T2,$inout5,$T1		# next counter value
109	  vpxor		$rndkey,$inout1,$inout1
110	  vpxor		$rndkey,$inout2,$inout2
111
112.Lresume_ctr32:
113	vmovdqu		$T1,($ivp)		# save next counter value
114	vpclmulqdq	\$0x10,$Hkey,$Z3,$Z1
115	  vpxor		$rndkey,$inout3,$inout3
116	  vmovups	0x10-0x80($key),$T2	# borrow $T2 for $rndkey
117	vpclmulqdq	\$0x01,$Hkey,$Z3,$Z2
118
119	# At this point, the current block of 96 (0x60) bytes has already been
120	# loaded into registers. Concurrently with processing it, we want to
121	# load the next 96 bytes of input for the next round. Obviously, we can
122	# only do this if there are at least 96 more bytes of input beyond the
123	# input we're currently processing, or else we'd read past the end of
124	# the input buffer. Here, we set |%r12| to 96 if there are at least 96
125	# bytes of input beyond the 96 bytes we're already processing, and we
126	# set |%r12| to 0 otherwise. In the case where we set |%r12| to 96,
127	# we'll read in the next block so that it is in registers for the next
128	# loop iteration. In the case where we set |%r12| to 0, we'll re-read
129	# the current block and then ignore what we re-read.
130	#
131	# At this point, |$in0| points to the current (already read into
132	# registers) block, and |$end0| points to 2*96 bytes before the end of
133	# the input. Thus, |$in0| > |$end0| means that we do not have the next
134	# 96-byte block to read in, and |$in0| <= |$end0| means we do.
135	xor		%r12,%r12
136	cmp		$in0,$end0
137
138	  vaesenc	$T2,$inout0,$inout0
139	vmovdqu		0x30+8(%rsp),$Ii	# I[4]
140	  vpxor		$rndkey,$inout4,$inout4
141	vpclmulqdq	\$0x00,$Hkey,$Z3,$T1
142	  vaesenc	$T2,$inout1,$inout1
143	  vpxor		$rndkey,$inout5,$inout5
144	setnc		%r12b
145	vpclmulqdq	\$0x11,$Hkey,$Z3,$Z3
146	  vaesenc	$T2,$inout2,$inout2
147	vmovdqu		0x10-0x20($Xip),$Hkey	# $Hkey^2
148	neg		%r12
149	  vaesenc	$T2,$inout3,$inout3
150	 vpxor		$Z1,$Z2,$Z2
151	vpclmulqdq	\$0x00,$Hkey,$Ii,$Z1
152	 vpxor		$Z0,$Xi,$Xi		# modulo-scheduled
153	  vaesenc	$T2,$inout4,$inout4
154	 vpxor		$Z1,$T1,$Z0
155	and		\$0x60,%r12
156	  vmovups	0x20-0x80($key),$rndkey
157	vpclmulqdq	\$0x10,$Hkey,$Ii,$T1
158	  vaesenc	$T2,$inout5,$inout5
159
160	vpclmulqdq	\$0x01,$Hkey,$Ii,$T2
161	lea		($in0,%r12),$in0
162	  vaesenc	$rndkey,$inout0,$inout0
163	 vpxor		16+8(%rsp),$Xi,$Xi	# modulo-scheduled [vpxor $Z3,$Xi,$Xi]
164	vpclmulqdq	\$0x11,$Hkey,$Ii,$Hkey
165	 vmovdqu	0x40+8(%rsp),$Ii	# I[3]
166	  vaesenc	$rndkey,$inout1,$inout1
167	movbe		0x58($in0),%r13
168	  vaesenc	$rndkey,$inout2,$inout2
169	movbe		0x50($in0),%r12
170	  vaesenc	$rndkey,$inout3,$inout3
171	mov		%r13,0x20+8(%rsp)
172	  vaesenc	$rndkey,$inout4,$inout4
173	mov		%r12,0x28+8(%rsp)
174	vmovdqu		0x30-0x20($Xip),$Z1	# borrow $Z1 for $Hkey^3
175	  vaesenc	$rndkey,$inout5,$inout5
176
177	  vmovups	0x30-0x80($key),$rndkey
178	 vpxor		$T1,$Z2,$Z2
179	vpclmulqdq	\$0x00,$Z1,$Ii,$T1
180	  vaesenc	$rndkey,$inout0,$inout0
181	 vpxor		$T2,$Z2,$Z2
182	vpclmulqdq	\$0x10,$Z1,$Ii,$T2
183	  vaesenc	$rndkey,$inout1,$inout1
184	 vpxor		$Hkey,$Z3,$Z3
185	vpclmulqdq	\$0x01,$Z1,$Ii,$Hkey
186	  vaesenc	$rndkey,$inout2,$inout2
187	vpclmulqdq	\$0x11,$Z1,$Ii,$Z1
188	 vmovdqu	0x50+8(%rsp),$Ii	# I[2]
189	  vaesenc	$rndkey,$inout3,$inout3
190	  vaesenc	$rndkey,$inout4,$inout4
191	 vpxor		$T1,$Z0,$Z0
192	vmovdqu		0x40-0x20($Xip),$T1	# borrow $T1 for $Hkey^4
193	  vaesenc	$rndkey,$inout5,$inout5
194
195	  vmovups	0x40-0x80($key),$rndkey
196	 vpxor		$T2,$Z2,$Z2
197	vpclmulqdq	\$0x00,$T1,$Ii,$T2
198	  vaesenc	$rndkey,$inout0,$inout0
199	 vpxor		$Hkey,$Z2,$Z2
200	vpclmulqdq	\$0x10,$T1,$Ii,$Hkey
201	  vaesenc	$rndkey,$inout1,$inout1
202	movbe		0x48($in0),%r13
203	 vpxor		$Z1,$Z3,$Z3
204	vpclmulqdq	\$0x01,$T1,$Ii,$Z1
205	  vaesenc	$rndkey,$inout2,$inout2
206	movbe		0x40($in0),%r12
207	vpclmulqdq	\$0x11,$T1,$Ii,$T1
208	 vmovdqu	0x60+8(%rsp),$Ii	# I[1]
209	  vaesenc	$rndkey,$inout3,$inout3
210	mov		%r13,0x30+8(%rsp)
211	  vaesenc	$rndkey,$inout4,$inout4
212	mov		%r12,0x38+8(%rsp)
213	 vpxor		$T2,$Z0,$Z0
214	vmovdqu		0x60-0x20($Xip),$T2	# borrow $T2 for $Hkey^5
215	  vaesenc	$rndkey,$inout5,$inout5
216
217	  vmovups	0x50-0x80($key),$rndkey
218	 vpxor		$Hkey,$Z2,$Z2
219	vpclmulqdq	\$0x00,$T2,$Ii,$Hkey
220	  vaesenc	$rndkey,$inout0,$inout0
221	 vpxor		$Z1,$Z2,$Z2
222	vpclmulqdq	\$0x10,$T2,$Ii,$Z1
223	  vaesenc	$rndkey,$inout1,$inout1
224	movbe		0x38($in0),%r13
225	 vpxor		$T1,$Z3,$Z3
226	vpclmulqdq	\$0x01,$T2,$Ii,$T1
227	 vpxor		0x70+8(%rsp),$Xi,$Xi	# accumulate I[0]
228	  vaesenc	$rndkey,$inout2,$inout2
229	movbe		0x30($in0),%r12
230	vpclmulqdq	\$0x11,$T2,$Ii,$T2
231	  vaesenc	$rndkey,$inout3,$inout3
232	mov		%r13,0x40+8(%rsp)
233	  vaesenc	$rndkey,$inout4,$inout4
234	mov		%r12,0x48+8(%rsp)
235	 vpxor		$Hkey,$Z0,$Z0
236	 vmovdqu	0x70-0x20($Xip),$Hkey	# $Hkey^6
237	  vaesenc	$rndkey,$inout5,$inout5
238
239	  vmovups	0x60-0x80($key),$rndkey
240	 vpxor		$Z1,$Z2,$Z2
241	vpclmulqdq	\$0x10,$Hkey,$Xi,$Z1
242	  vaesenc	$rndkey,$inout0,$inout0
243	 vpxor		$T1,$Z2,$Z2
244	vpclmulqdq	\$0x01,$Hkey,$Xi,$T1
245	  vaesenc	$rndkey,$inout1,$inout1
246	movbe		0x28($in0),%r13
247	 vpxor		$T2,$Z3,$Z3
248	vpclmulqdq	\$0x00,$Hkey,$Xi,$T2
249	  vaesenc	$rndkey,$inout2,$inout2
250	movbe		0x20($in0),%r12
251	vpclmulqdq	\$0x11,$Hkey,$Xi,$Xi
252	  vaesenc	$rndkey,$inout3,$inout3
253	mov		%r13,0x50+8(%rsp)
254	  vaesenc	$rndkey,$inout4,$inout4
255	mov		%r12,0x58+8(%rsp)
256	vpxor		$Z1,$Z2,$Z2
257	  vaesenc	$rndkey,$inout5,$inout5
258	vpxor		$T1,$Z2,$Z2
259
260	  vmovups	0x70-0x80($key),$rndkey
261	vpslldq		\$8,$Z2,$Z1
262	vpxor		$T2,$Z0,$Z0
263	vmovdqu		0x10($const),$Hkey	# .Lpoly
264
265	  vaesenc	$rndkey,$inout0,$inout0
266	vpxor		$Xi,$Z3,$Z3
267	  vaesenc	$rndkey,$inout1,$inout1
268	vpxor		$Z1,$Z0,$Z0
269	movbe		0x18($in0),%r13
270	  vaesenc	$rndkey,$inout2,$inout2
271	movbe		0x10($in0),%r12
272	vpalignr	\$8,$Z0,$Z0,$Ii		# 1st phase
273	vpclmulqdq	\$0x10,$Hkey,$Z0,$Z0
274	mov		%r13,0x60+8(%rsp)
275	  vaesenc	$rndkey,$inout3,$inout3
276	mov		%r12,0x68+8(%rsp)
277	  vaesenc	$rndkey,$inout4,$inout4
278	  vmovups	0x80-0x80($key),$T1	# borrow $T1 for $rndkey
279	  vaesenc	$rndkey,$inout5,$inout5
280
281	  vaesenc	$T1,$inout0,$inout0
282	  vmovups	0x90-0x80($key),$rndkey
283	  vaesenc	$T1,$inout1,$inout1
284	vpsrldq		\$8,$Z2,$Z2
285	  vaesenc	$T1,$inout2,$inout2
286	vpxor		$Z2,$Z3,$Z3
287	  vaesenc	$T1,$inout3,$inout3
288	vpxor		$Ii,$Z0,$Z0
289	movbe		0x08($in0),%r13
290	  vaesenc	$T1,$inout4,$inout4
291	movbe		0x00($in0),%r12
292	  vaesenc	$T1,$inout5,$inout5
293	  vmovups	0xa0-0x80($key),$T1
294	  cmp		\$11,$rounds
295	  jb		.Lenc_tail		# 128-bit key
296
297	  vaesenc	$rndkey,$inout0,$inout0
298	  vaesenc	$rndkey,$inout1,$inout1
299	  vaesenc	$rndkey,$inout2,$inout2
300	  vaesenc	$rndkey,$inout3,$inout3
301	  vaesenc	$rndkey,$inout4,$inout4
302	  vaesenc	$rndkey,$inout5,$inout5
303
304	  vaesenc	$T1,$inout0,$inout0
305	  vaesenc	$T1,$inout1,$inout1
306	  vaesenc	$T1,$inout2,$inout2
307	  vaesenc	$T1,$inout3,$inout3
308	  vaesenc	$T1,$inout4,$inout4
309	  vmovups	0xb0-0x80($key),$rndkey
310	  vaesenc	$T1,$inout5,$inout5
311	  vmovups	0xc0-0x80($key),$T1
312	  je		.Lenc_tail		# 192-bit key
313
314	  vaesenc	$rndkey,$inout0,$inout0
315	  vaesenc	$rndkey,$inout1,$inout1
316	  vaesenc	$rndkey,$inout2,$inout2
317	  vaesenc	$rndkey,$inout3,$inout3
318	  vaesenc	$rndkey,$inout4,$inout4
319	  vaesenc	$rndkey,$inout5,$inout5
320
321	  vaesenc	$T1,$inout0,$inout0
322	  vaesenc	$T1,$inout1,$inout1
323	  vaesenc	$T1,$inout2,$inout2
324	  vaesenc	$T1,$inout3,$inout3
325	  vaesenc	$T1,$inout4,$inout4
326	  vmovups	0xd0-0x80($key),$rndkey
327	  vaesenc	$T1,$inout5,$inout5
328	  vmovups	0xe0-0x80($key),$T1
329	  jmp		.Lenc_tail		# 256-bit key
330
331.align	32
332.Lhandle_ctr32:
333	vmovdqu		($const),$Ii		# borrow $Ii for .Lbswap_mask
334	  vpshufb	$Ii,$T1,$Z2		# byte-swap counter
335	  vmovdqu	0x30($const),$Z1	# borrow $Z1, .Ltwo_lsb
336	  vpaddd	0x40($const),$Z2,$inout1	# .Lone_lsb
337	  vpaddd	$Z1,$Z2,$inout2
338	vmovdqu		0x00-0x20($Xip),$Hkey	# $Hkey^1
339	  vpaddd	$Z1,$inout1,$inout3
340	  vpshufb	$Ii,$inout1,$inout1
341	  vpaddd	$Z1,$inout2,$inout4
342	  vpshufb	$Ii,$inout2,$inout2
343	  vpxor		$rndkey,$inout1,$inout1
344	  vpaddd	$Z1,$inout3,$inout5
345	  vpshufb	$Ii,$inout3,$inout3
346	  vpxor		$rndkey,$inout2,$inout2
347	  vpaddd	$Z1,$inout4,$T1		# byte-swapped next counter value
348	  vpshufb	$Ii,$inout4,$inout4
349	  vpshufb	$Ii,$inout5,$inout5
350	  vpshufb	$Ii,$T1,$T1		# next counter value
351	jmp		.Lresume_ctr32
352
353.align	32
354.Lenc_tail:
355	  vaesenc	$rndkey,$inout0,$inout0
356	vmovdqu		$Z3,16+8(%rsp)		# postpone vpxor $Z3,$Xi,$Xi
357	vpalignr	\$8,$Z0,$Z0,$Xi		# 2nd phase
358	  vaesenc	$rndkey,$inout1,$inout1
359	vpclmulqdq	\$0x10,$Hkey,$Z0,$Z0
360	  vpxor		0x00($inp),$T1,$T2
361	  vaesenc	$rndkey,$inout2,$inout2
362	  vpxor		0x10($inp),$T1,$Ii
363	  vaesenc	$rndkey,$inout3,$inout3
364	  vpxor		0x20($inp),$T1,$Z1
365	  vaesenc	$rndkey,$inout4,$inout4
366	  vpxor		0x30($inp),$T1,$Z2
367	  vaesenc	$rndkey,$inout5,$inout5
368	  vpxor		0x40($inp),$T1,$Z3
369	  vpxor		0x50($inp),$T1,$Hkey
370	  vmovdqu	($ivp),$T1		# load next counter value
371
372	  vaesenclast	$T2,$inout0,$inout0
373	  vmovdqu	0x20($const),$T2	# borrow $T2, .Lone_msb
374	  vaesenclast	$Ii,$inout1,$inout1
375	 vpaddb		$T2,$T1,$Ii
376	mov		%r13,0x70+8(%rsp)
377	lea		0x60($inp),$inp
378	  vaesenclast	$Z1,$inout2,$inout2
379	 vpaddb		$T2,$Ii,$Z1
380	mov		%r12,0x78+8(%rsp)
381	lea		0x60($out),$out
382	  vmovdqu	0x00-0x80($key),$rndkey
383	  vaesenclast	$Z2,$inout3,$inout3
384	 vpaddb		$T2,$Z1,$Z2
385	  vaesenclast	$Z3, $inout4,$inout4
386	 vpaddb		$T2,$Z2,$Z3
387	  vaesenclast	$Hkey,$inout5,$inout5
388	 vpaddb		$T2,$Z3,$Hkey
389
390	add		\$0x60,$ret
391	sub		\$0x6,$len
392	jc		.L6x_done
393
394	  vmovups	$inout0,-0x60($out)	# save output
395	 vpxor		$rndkey,$T1,$inout0
396	  vmovups	$inout1,-0x50($out)
397	 vmovdqa	$Ii,$inout1		# 0 latency
398	  vmovups	$inout2,-0x40($out)
399	 vmovdqa	$Z1,$inout2		# 0 latency
400	  vmovups	$inout3,-0x30($out)
401	 vmovdqa	$Z2,$inout3		# 0 latency
402	  vmovups	$inout4,-0x20($out)
403	 vmovdqa	$Z3,$inout4		# 0 latency
404	  vmovups	$inout5,-0x10($out)
405	 vmovdqa	$Hkey,$inout5		# 0 latency
406	vmovdqu		0x20+8(%rsp),$Z3	# I[5]
407	jmp		.Loop6x
408
409.L6x_done:
410	vpxor		16+8(%rsp),$Xi,$Xi	# modulo-scheduled
411	vpxor		$Z0,$Xi,$Xi		# modulo-scheduled
412
413	ret
414.cfi_endproc
415.size	_aesni_ctr32_ghash_6x,.-_aesni_ctr32_ghash_6x
416___
417######################################################################
418#
419# size_t aesni_gcm_[en|de]crypt(const void *inp, void *out, size_t len,
420#		const AES_KEY *key, unsigned char iv[16],
421#		struct { u128 Xi,H,Htbl[9]; } *Xip);
422$code.=<<___;
423.globl	aesni_gcm_decrypt
424.type	aesni_gcm_decrypt,\@function,6
425.align	32
426aesni_gcm_decrypt:
427.cfi_startproc
428	xor	$ret,$ret
429
430	# We call |_aesni_ctr32_ghash_6x|, which requires at least 96 (0x60)
431	# bytes of input.
432	cmp	\$0x60,$len			# minimal accepted length
433	jb	.Lgcm_dec_abort
434
435	lea	(%rsp),%rax			# save stack pointer
436.cfi_def_cfa_register	%rax
437	push	%rbx
438.cfi_push	%rbx
439	push	%rbp
440.cfi_push	%rbp
441	push	%r12
442.cfi_push	%r12
443	push	%r13
444.cfi_push	%r13
445	push	%r14
446.cfi_push	%r14
447	push	%r15
448.cfi_push	%r15
449___
450$code.=<<___ if ($win64);
451	lea	-0xa8(%rsp),%rsp
452	movaps	%xmm6,-0xd8(%rax)
453	movaps	%xmm7,-0xc8(%rax)
454	movaps	%xmm8,-0xb8(%rax)
455	movaps	%xmm9,-0xa8(%rax)
456	movaps	%xmm10,-0x98(%rax)
457	movaps	%xmm11,-0x88(%rax)
458	movaps	%xmm12,-0x78(%rax)
459	movaps	%xmm13,-0x68(%rax)
460	movaps	%xmm14,-0x58(%rax)
461	movaps	%xmm15,-0x48(%rax)
462.Lgcm_dec_body:
463___
464$code.=<<___;
465	vzeroupper
466
467	vmovdqu		($ivp),$T1		# input counter value
468	add		\$-128,%rsp
469	mov		12($ivp),$counter
470	lea		.Lbswap_mask(%rip),$const
471	lea		-0x80($key),$in0	# borrow $in0
472	mov		\$0xf80,$end0		# borrow $end0
473	vmovdqu		($Xip),$Xi		# load Xi
474	and		\$-128,%rsp		# ensure stack alignment
475	vmovdqu		($const),$Ii		# borrow $Ii for .Lbswap_mask
476	lea		0x80($key),$key		# size optimization
477	lea		0x20+0x20($Xip),$Xip	# size optimization
478	mov		0xf0-0x80($key),$rounds
479	vpshufb		$Ii,$Xi,$Xi
480
481	and		$end0,$in0
482	and		%rsp,$end0
483	sub		$in0,$end0
484	jc		.Ldec_no_key_aliasing
485	cmp		\$768,$end0
486	jnc		.Ldec_no_key_aliasing
487	sub		$end0,%rsp		# avoid aliasing with key
488.Ldec_no_key_aliasing:
489
490	vmovdqu		0x50($inp),$Z3		# I[5]
491	lea		($inp),$in0
492	vmovdqu		0x40($inp),$Z0
493
494	# |_aesni_ctr32_ghash_6x| requires |$end0| to point to 2*96 (0xc0)
495	# bytes before the end of the input. Note, in particular, that this is
496	# correct even if |$len| is not an even multiple of 96 or 16. XXX: This
497	# seems to require that |$inp| + |$len| >= 2*96 (0xc0); i.e. |$inp| must
498	# not be near the very beginning of the address space when |$len| < 2*96
499	# (0xc0).
500	lea		-0xc0($inp,$len),$end0
501
502	vmovdqu		0x30($inp),$Z1
503	shr		\$4,$len
504	xor		$ret,$ret
505	vmovdqu		0x20($inp),$Z2
506	 vpshufb	$Ii,$Z3,$Z3		# passed to _aesni_ctr32_ghash_6x
507	vmovdqu		0x10($inp),$T2
508	 vpshufb	$Ii,$Z0,$Z0
509	vmovdqu		($inp),$Hkey
510	 vpshufb	$Ii,$Z1,$Z1
511	vmovdqu		$Z0,0x30(%rsp)
512	 vpshufb	$Ii,$Z2,$Z2
513	vmovdqu		$Z1,0x40(%rsp)
514	 vpshufb	$Ii,$T2,$T2
515	vmovdqu		$Z2,0x50(%rsp)
516	 vpshufb	$Ii,$Hkey,$Hkey
517	vmovdqu		$T2,0x60(%rsp)
518	vmovdqu		$Hkey,0x70(%rsp)
519
520	call		_aesni_ctr32_ghash_6x
521
522	vmovups		$inout0,-0x60($out)	# save output
523	vmovups		$inout1,-0x50($out)
524	vmovups		$inout2,-0x40($out)
525	vmovups		$inout3,-0x30($out)
526	vmovups		$inout4,-0x20($out)
527	vmovups		$inout5,-0x10($out)
528
529	vpshufb		($const),$Xi,$Xi	# .Lbswap_mask
530	vmovdqu		$Xi,-0x40($Xip)		# output Xi
531
532	vzeroupper
533___
534$code.=<<___ if ($win64);
535	movaps	-0xd8(%rax),%xmm6
536	movaps	-0xc8(%rax),%xmm7
537	movaps	-0xb8(%rax),%xmm8
538	movaps	-0xa8(%rax),%xmm9
539	movaps	-0x98(%rax),%xmm10
540	movaps	-0x88(%rax),%xmm11
541	movaps	-0x78(%rax),%xmm12
542	movaps	-0x68(%rax),%xmm13
543	movaps	-0x58(%rax),%xmm14
544	movaps	-0x48(%rax),%xmm15
545___
546$code.=<<___;
547	mov	-48(%rax),%r15
548.cfi_restore	%r15
549	mov	-40(%rax),%r14
550.cfi_restore	%r14
551	mov	-32(%rax),%r13
552.cfi_restore	%r13
553	mov	-24(%rax),%r12
554.cfi_restore	%r12
555	mov	-16(%rax),%rbp
556.cfi_restore	%rbp
557	mov	-8(%rax),%rbx
558.cfi_restore	%rbx
559	lea	(%rax),%rsp		# restore %rsp
560.cfi_def_cfa_register	%rsp
561.Lgcm_dec_abort:
562	mov	$ret,%rax		# return value
563	ret
564.cfi_endproc
565.size	aesni_gcm_decrypt,.-aesni_gcm_decrypt
566___
567
568$code.=<<___;
569.type	_aesni_ctr32_6x,\@abi-omnipotent
570.align	32
571_aesni_ctr32_6x:
572.cfi_startproc
573	vmovdqu		0x00-0x80($key),$Z0	# borrow $Z0 for $rndkey
574	vmovdqu		0x20($const),$T2	# borrow $T2, .Lone_msb
575	lea		-1($rounds),%r13
576	vmovups		0x10-0x80($key),$rndkey
577	lea		0x20-0x80($key),%r12
578	vpxor		$Z0,$T1,$inout0
579	add		\$`6<<24`,$counter
580	jc		.Lhandle_ctr32_2
581	vpaddb		$T2,$T1,$inout1
582	vpaddb		$T2,$inout1,$inout2
583	vpxor		$Z0,$inout1,$inout1
584	vpaddb		$T2,$inout2,$inout3
585	vpxor		$Z0,$inout2,$inout2
586	vpaddb		$T2,$inout3,$inout4
587	vpxor		$Z0,$inout3,$inout3
588	vpaddb		$T2,$inout4,$inout5
589	vpxor		$Z0,$inout4,$inout4
590	vpaddb		$T2,$inout5,$T1
591	vpxor		$Z0,$inout5,$inout5
592	jmp		.Loop_ctr32
593
594.align	16
595.Loop_ctr32:
596	vaesenc		$rndkey,$inout0,$inout0
597	vaesenc		$rndkey,$inout1,$inout1
598	vaesenc		$rndkey,$inout2,$inout2
599	vaesenc		$rndkey,$inout3,$inout3
600	vaesenc		$rndkey,$inout4,$inout4
601	vaesenc		$rndkey,$inout5,$inout5
602	vmovups		(%r12),$rndkey
603	lea		0x10(%r12),%r12
604	dec		%r13d
605	jnz		.Loop_ctr32
606
607	vmovdqu		(%r12),$Hkey		# last round key
608	vaesenc		$rndkey,$inout0,$inout0
609	vpxor		0x00($inp),$Hkey,$Z0
610	vaesenc		$rndkey,$inout1,$inout1
611	vpxor		0x10($inp),$Hkey,$Z1
612	vaesenc		$rndkey,$inout2,$inout2
613	vpxor		0x20($inp),$Hkey,$Z2
614	vaesenc		$rndkey,$inout3,$inout3
615	vpxor		0x30($inp),$Hkey,$Xi
616	vaesenc		$rndkey,$inout4,$inout4
617	vpxor		0x40($inp),$Hkey,$T2
618	vaesenc		$rndkey,$inout5,$inout5
619	vpxor		0x50($inp),$Hkey,$Hkey
620	lea		0x60($inp),$inp
621
622	vaesenclast	$Z0,$inout0,$inout0
623	vaesenclast	$Z1,$inout1,$inout1
624	vaesenclast	$Z2,$inout2,$inout2
625	vaesenclast	$Xi,$inout3,$inout3
626	vaesenclast	$T2,$inout4,$inout4
627	vaesenclast	$Hkey,$inout5,$inout5
628	vmovups		$inout0,0x00($out)
629	vmovups		$inout1,0x10($out)
630	vmovups		$inout2,0x20($out)
631	vmovups		$inout3,0x30($out)
632	vmovups		$inout4,0x40($out)
633	vmovups		$inout5,0x50($out)
634	lea		0x60($out),$out
635
636	ret
637.align	32
638.Lhandle_ctr32_2:
639	vpshufb		$Ii,$T1,$Z2		# byte-swap counter
640	vmovdqu		0x30($const),$Z1	# borrow $Z1, .Ltwo_lsb
641	vpaddd		0x40($const),$Z2,$inout1	# .Lone_lsb
642	vpaddd		$Z1,$Z2,$inout2
643	vpaddd		$Z1,$inout1,$inout3
644	vpshufb		$Ii,$inout1,$inout1
645	vpaddd		$Z1,$inout2,$inout4
646	vpshufb		$Ii,$inout2,$inout2
647	vpxor		$Z0,$inout1,$inout1
648	vpaddd		$Z1,$inout3,$inout5
649	vpshufb		$Ii,$inout3,$inout3
650	vpxor		$Z0,$inout2,$inout2
651	vpaddd		$Z1,$inout4,$T1		# byte-swapped next counter value
652	vpshufb		$Ii,$inout4,$inout4
653	vpxor		$Z0,$inout3,$inout3
654	vpshufb		$Ii,$inout5,$inout5
655	vpxor		$Z0,$inout4,$inout4
656	vpshufb		$Ii,$T1,$T1		# next counter value
657	vpxor		$Z0,$inout5,$inout5
658	jmp	.Loop_ctr32
659.cfi_endproc
660.size	_aesni_ctr32_6x,.-_aesni_ctr32_6x
661
662.globl	aesni_gcm_encrypt
663.type	aesni_gcm_encrypt,\@function,6
664.align	32
665aesni_gcm_encrypt:
666.cfi_startproc
667#ifdef BORINGSSL_DISPATCH_TEST
668.extern	BORINGSSL_function_hit
669	movb \$1,BORINGSSL_function_hit+2(%rip)
670#endif
671	xor	$ret,$ret
672
673	# We call |_aesni_ctr32_6x| twice, each call consuming 96 bytes of
674	# input. Then we call |_aesni_ctr32_ghash_6x|, which requires at
675	# least 96 more bytes of input.
676	cmp	\$0x60*3,$len			# minimal accepted length
677	jb	.Lgcm_enc_abort
678
679	lea	(%rsp),%rax			# save stack pointer
680.cfi_def_cfa_register	%rax
681	push	%rbx
682.cfi_push	%rbx
683	push	%rbp
684.cfi_push	%rbp
685	push	%r12
686.cfi_push	%r12
687	push	%r13
688.cfi_push	%r13
689	push	%r14
690.cfi_push	%r14
691	push	%r15
692.cfi_push	%r15
693___
694$code.=<<___ if ($win64);
695	lea	-0xa8(%rsp),%rsp
696	movaps	%xmm6,-0xd8(%rax)
697	movaps	%xmm7,-0xc8(%rax)
698	movaps	%xmm8,-0xb8(%rax)
699	movaps	%xmm9,-0xa8(%rax)
700	movaps	%xmm10,-0x98(%rax)
701	movaps	%xmm11,-0x88(%rax)
702	movaps	%xmm12,-0x78(%rax)
703	movaps	%xmm13,-0x68(%rax)
704	movaps	%xmm14,-0x58(%rax)
705	movaps	%xmm15,-0x48(%rax)
706.Lgcm_enc_body:
707___
708$code.=<<___;
709	vzeroupper
710
711	vmovdqu		($ivp),$T1		# input counter value
712	add		\$-128,%rsp
713	mov		12($ivp),$counter
714	lea		.Lbswap_mask(%rip),$const
715	lea		-0x80($key),$in0	# borrow $in0
716	mov		\$0xf80,$end0		# borrow $end0
717	lea		0x80($key),$key		# size optimization
718	vmovdqu		($const),$Ii		# borrow $Ii for .Lbswap_mask
719	and		\$-128,%rsp		# ensure stack alignment
720	mov		0xf0-0x80($key),$rounds
721
722	and		$end0,$in0
723	and		%rsp,$end0
724	sub		$in0,$end0
725	jc		.Lenc_no_key_aliasing
726	cmp		\$768,$end0
727	jnc		.Lenc_no_key_aliasing
728	sub		$end0,%rsp		# avoid aliasing with key
729.Lenc_no_key_aliasing:
730
731	lea		($out),$in0
732
733	# |_aesni_ctr32_ghash_6x| requires |$end0| to point to 2*96 (0xc0)
734	# bytes before the end of the input. Note, in particular, that this is
735	# correct even if |$len| is not an even multiple of 96 or 16. Unlike in
736	# the decryption case, there's no caveat that |$out| must not be near
737	# the very beginning of the address space, because we know that
738	# |$len| >= 3*96 from the check above, and so we know
739	# |$out| + |$len| >= 2*96 (0xc0).
740	lea		-0xc0($out,$len),$end0
741
742	shr		\$4,$len
743
744	call		_aesni_ctr32_6x
745	vpshufb		$Ii,$inout0,$Xi		# save bswapped output on stack
746	vpshufb		$Ii,$inout1,$T2
747	vmovdqu		$Xi,0x70(%rsp)
748	vpshufb		$Ii,$inout2,$Z0
749	vmovdqu		$T2,0x60(%rsp)
750	vpshufb		$Ii,$inout3,$Z1
751	vmovdqu		$Z0,0x50(%rsp)
752	vpshufb		$Ii,$inout4,$Z2
753	vmovdqu		$Z1,0x40(%rsp)
754	vpshufb		$Ii,$inout5,$Z3		# passed to _aesni_ctr32_ghash_6x
755	vmovdqu		$Z2,0x30(%rsp)
756
757	call		_aesni_ctr32_6x
758
759	vmovdqu		($Xip),$Xi		# load Xi
760	lea		0x20+0x20($Xip),$Xip	# size optimization
761	sub		\$12,$len
762	mov		\$0x60*2,$ret
763	vpshufb		$Ii,$Xi,$Xi
764
765	call		_aesni_ctr32_ghash_6x
766	vmovdqu		0x20(%rsp),$Z3		# I[5]
767	 vmovdqu	($const),$Ii		# borrow $Ii for .Lbswap_mask
768	vmovdqu		0x00-0x20($Xip),$Hkey	# $Hkey^1
769	vpunpckhqdq	$Z3,$Z3,$T1
770	vmovdqu		0x20-0x20($Xip),$rndkey	# borrow $rndkey for $HK
771	 vmovups	$inout0,-0x60($out)	# save output
772	 vpshufb	$Ii,$inout0,$inout0	# but keep bswapped copy
773	vpxor		$Z3,$T1,$T1
774	 vmovups	$inout1,-0x50($out)
775	 vpshufb	$Ii,$inout1,$inout1
776	 vmovups	$inout2,-0x40($out)
777	 vpshufb	$Ii,$inout2,$inout2
778	 vmovups	$inout3,-0x30($out)
779	 vpshufb	$Ii,$inout3,$inout3
780	 vmovups	$inout4,-0x20($out)
781	 vpshufb	$Ii,$inout4,$inout4
782	 vmovups	$inout5,-0x10($out)
783	 vpshufb	$Ii,$inout5,$inout5
784	 vmovdqu	$inout0,0x10(%rsp)	# free $inout0
785___
786{ my ($HK,$T3)=($rndkey,$inout0);
787
788$code.=<<___;
789	 vmovdqu	0x30(%rsp),$Z2		# I[4]
790	 vmovdqu	0x10-0x20($Xip),$Ii	# borrow $Ii for $Hkey^2
791	 vpunpckhqdq	$Z2,$Z2,$T2
792	vpclmulqdq	\$0x00,$Hkey,$Z3,$Z1
793	 vpxor		$Z2,$T2,$T2
794	vpclmulqdq	\$0x11,$Hkey,$Z3,$Z3
795	vpclmulqdq	\$0x00,$HK,$T1,$T1
796
797	 vmovdqu	0x40(%rsp),$T3		# I[3]
798	vpclmulqdq	\$0x00,$Ii,$Z2,$Z0
799	 vmovdqu	0x30-0x20($Xip),$Hkey	# $Hkey^3
800	vpxor		$Z1,$Z0,$Z0
801	 vpunpckhqdq	$T3,$T3,$Z1
802	vpclmulqdq	\$0x11,$Ii,$Z2,$Z2
803	 vpxor		$T3,$Z1,$Z1
804	vpxor		$Z3,$Z2,$Z2
805	vpclmulqdq	\$0x10,$HK,$T2,$T2
806	 vmovdqu	0x50-0x20($Xip),$HK
807	vpxor		$T1,$T2,$T2
808
809	 vmovdqu	0x50(%rsp),$T1		# I[2]
810	vpclmulqdq	\$0x00,$Hkey,$T3,$Z3
811	 vmovdqu	0x40-0x20($Xip),$Ii	# borrow $Ii for $Hkey^4
812	vpxor		$Z0,$Z3,$Z3
813	 vpunpckhqdq	$T1,$T1,$Z0
814	vpclmulqdq	\$0x11,$Hkey,$T3,$T3
815	 vpxor		$T1,$Z0,$Z0
816	vpxor		$Z2,$T3,$T3
817	vpclmulqdq	\$0x00,$HK,$Z1,$Z1
818	vpxor		$T2,$Z1,$Z1
819
820	 vmovdqu	0x60(%rsp),$T2		# I[1]
821	vpclmulqdq	\$0x00,$Ii,$T1,$Z2
822	 vmovdqu	0x60-0x20($Xip),$Hkey	# $Hkey^5
823	vpxor		$Z3,$Z2,$Z2
824	 vpunpckhqdq	$T2,$T2,$Z3
825	vpclmulqdq	\$0x11,$Ii,$T1,$T1
826	 vpxor		$T2,$Z3,$Z3
827	vpxor		$T3,$T1,$T1
828	vpclmulqdq	\$0x10,$HK,$Z0,$Z0
829	 vmovdqu	0x80-0x20($Xip),$HK
830	vpxor		$Z1,$Z0,$Z0
831
832	 vpxor		0x70(%rsp),$Xi,$Xi	# accumulate I[0]
833	vpclmulqdq	\$0x00,$Hkey,$T2,$Z1
834	 vmovdqu	0x70-0x20($Xip),$Ii	# borrow $Ii for $Hkey^6
835	 vpunpckhqdq	$Xi,$Xi,$T3
836	vpxor		$Z2,$Z1,$Z1
837	vpclmulqdq	\$0x11,$Hkey,$T2,$T2
838	 vpxor		$Xi,$T3,$T3
839	vpxor		$T1,$T2,$T2
840	vpclmulqdq	\$0x00,$HK,$Z3,$Z3
841	vpxor		$Z0,$Z3,$Z0
842
843	vpclmulqdq	\$0x00,$Ii,$Xi,$Z2
844	 vmovdqu	0x00-0x20($Xip),$Hkey	# $Hkey^1
845	 vpunpckhqdq	$inout5,$inout5,$T1
846	vpclmulqdq	\$0x11,$Ii,$Xi,$Xi
847	 vpxor		$inout5,$T1,$T1
848	vpxor		$Z1,$Z2,$Z1
849	vpclmulqdq	\$0x10,$HK,$T3,$T3
850	 vmovdqu	0x20-0x20($Xip),$HK
851	vpxor		$T2,$Xi,$Z3
852	vpxor		$Z0,$T3,$Z2
853
854	 vmovdqu	0x10-0x20($Xip),$Ii	# borrow $Ii for $Hkey^2
855	  vpxor		$Z1,$Z3,$T3		# aggregated Karatsuba post-processing
856	vpclmulqdq	\$0x00,$Hkey,$inout5,$Z0
857	  vpxor		$T3,$Z2,$Z2
858	 vpunpckhqdq	$inout4,$inout4,$T2
859	vpclmulqdq	\$0x11,$Hkey,$inout5,$inout5
860	 vpxor		$inout4,$T2,$T2
861	  vpslldq	\$8,$Z2,$T3
862	vpclmulqdq	\$0x00,$HK,$T1,$T1
863	  vpxor		$T3,$Z1,$Xi
864	  vpsrldq	\$8,$Z2,$Z2
865	  vpxor		$Z2,$Z3,$Z3
866
867	vpclmulqdq	\$0x00,$Ii,$inout4,$Z1
868	 vmovdqu	0x30-0x20($Xip),$Hkey	# $Hkey^3
869	vpxor		$Z0,$Z1,$Z1
870	 vpunpckhqdq	$inout3,$inout3,$T3
871	vpclmulqdq	\$0x11,$Ii,$inout4,$inout4
872	 vpxor		$inout3,$T3,$T3
873	vpxor		$inout5,$inout4,$inout4
874	  vpalignr	\$8,$Xi,$Xi,$inout5	# 1st phase
875	vpclmulqdq	\$0x10,$HK,$T2,$T2
876	 vmovdqu	0x50-0x20($Xip),$HK
877	vpxor		$T1,$T2,$T2
878
879	vpclmulqdq	\$0x00,$Hkey,$inout3,$Z0
880	 vmovdqu	0x40-0x20($Xip),$Ii	# borrow $Ii for $Hkey^4
881	vpxor		$Z1,$Z0,$Z0
882	 vpunpckhqdq	$inout2,$inout2,$T1
883	vpclmulqdq	\$0x11,$Hkey,$inout3,$inout3
884	 vpxor		$inout2,$T1,$T1
885	vpxor		$inout4,$inout3,$inout3
886	  vxorps	0x10(%rsp),$Z3,$Z3	# accumulate $inout0
887	vpclmulqdq	\$0x00,$HK,$T3,$T3
888	vpxor		$T2,$T3,$T3
889
890	  vpclmulqdq	\$0x10,0x10($const),$Xi,$Xi
891	  vxorps	$inout5,$Xi,$Xi
892
893	vpclmulqdq	\$0x00,$Ii,$inout2,$Z1
894	 vmovdqu	0x60-0x20($Xip),$Hkey	# $Hkey^5
895	vpxor		$Z0,$Z1,$Z1
896	 vpunpckhqdq	$inout1,$inout1,$T2
897	vpclmulqdq	\$0x11,$Ii,$inout2,$inout2
898	 vpxor		$inout1,$T2,$T2
899	  vpalignr	\$8,$Xi,$Xi,$inout5	# 2nd phase
900	vpxor		$inout3,$inout2,$inout2
901	vpclmulqdq	\$0x10,$HK,$T1,$T1
902	 vmovdqu	0x80-0x20($Xip),$HK
903	vpxor		$T3,$T1,$T1
904
905	  vxorps	$Z3,$inout5,$inout5
906	  vpclmulqdq	\$0x10,0x10($const),$Xi,$Xi
907	  vxorps	$inout5,$Xi,$Xi
908
909	vpclmulqdq	\$0x00,$Hkey,$inout1,$Z0
910	 vmovdqu	0x70-0x20($Xip),$Ii	# borrow $Ii for $Hkey^6
911	vpxor		$Z1,$Z0,$Z0
912	 vpunpckhqdq	$Xi,$Xi,$T3
913	vpclmulqdq	\$0x11,$Hkey,$inout1,$inout1
914	 vpxor		$Xi,$T3,$T3
915	vpxor		$inout2,$inout1,$inout1
916	vpclmulqdq	\$0x00,$HK,$T2,$T2
917	vpxor		$T1,$T2,$T2
918
919	vpclmulqdq	\$0x00,$Ii,$Xi,$Z1
920	vpclmulqdq	\$0x11,$Ii,$Xi,$Z3
921	vpxor		$Z0,$Z1,$Z1
922	vpclmulqdq	\$0x10,$HK,$T3,$Z2
923	vpxor		$inout1,$Z3,$Z3
924	vpxor		$T2,$Z2,$Z2
925
926	vpxor		$Z1,$Z3,$Z0		# aggregated Karatsuba post-processing
927	vpxor		$Z0,$Z2,$Z2
928	vpslldq		\$8,$Z2,$T1
929	vmovdqu		0x10($const),$Hkey	# .Lpoly
930	vpsrldq		\$8,$Z2,$Z2
931	vpxor		$T1,$Z1,$Xi
932	vpxor		$Z2,$Z3,$Z3
933
934	vpalignr	\$8,$Xi,$Xi,$T2		# 1st phase
935	vpclmulqdq	\$0x10,$Hkey,$Xi,$Xi
936	vpxor		$T2,$Xi,$Xi
937
938	vpalignr	\$8,$Xi,$Xi,$T2		# 2nd phase
939	vpclmulqdq	\$0x10,$Hkey,$Xi,$Xi
940	vpxor		$Z3,$T2,$T2
941	vpxor		$T2,$Xi,$Xi
942___
943}
944$code.=<<___;
945	vpshufb		($const),$Xi,$Xi	# .Lbswap_mask
946	vmovdqu		$Xi,-0x40($Xip)		# output Xi
947
948	vzeroupper
949___
950$code.=<<___ if ($win64);
951	movaps	-0xd8(%rax),%xmm6
952	movaps	-0xc8(%rax),%xmm7
953	movaps	-0xb8(%rax),%xmm8
954	movaps	-0xa8(%rax),%xmm9
955	movaps	-0x98(%rax),%xmm10
956	movaps	-0x88(%rax),%xmm11
957	movaps	-0x78(%rax),%xmm12
958	movaps	-0x68(%rax),%xmm13
959	movaps	-0x58(%rax),%xmm14
960	movaps	-0x48(%rax),%xmm15
961___
962$code.=<<___;
963	mov	-48(%rax),%r15
964.cfi_restore	%r15
965	mov	-40(%rax),%r14
966.cfi_restore	%r14
967	mov	-32(%rax),%r13
968.cfi_restore	%r13
969	mov	-24(%rax),%r12
970.cfi_restore	%r12
971	mov	-16(%rax),%rbp
972.cfi_restore	%rbp
973	mov	-8(%rax),%rbx
974.cfi_restore	%rbx
975	lea	(%rax),%rsp		# restore %rsp
976.cfi_def_cfa_register	%rsp
977.Lgcm_enc_abort:
978	mov	$ret,%rax		# return value
979	ret
980.cfi_endproc
981.size	aesni_gcm_encrypt,.-aesni_gcm_encrypt
982___
983
984$code.=<<___;
985.align	64
986.Lbswap_mask:
987	.byte	15,14,13,12,11,10,9,8,7,6,5,4,3,2,1,0
988.Lpoly:
989	.byte	0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0xc2
990.Lone_msb:
991	.byte	0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1
992.Ltwo_lsb:
993	.byte	2,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
994.Lone_lsb:
995	.byte	1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
996.asciz	"AES-NI GCM module for x86_64, CRYPTOGAMS by <appro\@openssl.org>"
997.align	64
998___
999if ($win64) {
1000$rec="%rcx";
1001$frame="%rdx";
1002$context="%r8";
1003$disp="%r9";
1004
1005$code.=<<___
1006.extern	__imp_RtlVirtualUnwind
1007.type	gcm_se_handler,\@abi-omnipotent
1008.align	16
1009gcm_se_handler:
1010	push	%rsi
1011	push	%rdi
1012	push	%rbx
1013	push	%rbp
1014	push	%r12
1015	push	%r13
1016	push	%r14
1017	push	%r15
1018	pushfq
1019	sub	\$64,%rsp
1020
1021	mov	120($context),%rax	# pull context->Rax
1022	mov	248($context),%rbx	# pull context->Rip
1023
1024	mov	8($disp),%rsi		# disp->ImageBase
1025	mov	56($disp),%r11		# disp->HandlerData
1026
1027	mov	0(%r11),%r10d		# HandlerData[0]
1028	lea	(%rsi,%r10),%r10	# prologue label
1029	cmp	%r10,%rbx		# context->Rip<prologue label
1030	jb	.Lcommon_seh_tail
1031
1032	mov	152($context),%rax	# pull context->Rsp
1033
1034	mov	4(%r11),%r10d		# HandlerData[1]
1035	lea	(%rsi,%r10),%r10	# epilogue label
1036	cmp	%r10,%rbx		# context->Rip>=epilogue label
1037	jae	.Lcommon_seh_tail
1038
1039	mov	120($context),%rax	# pull context->Rax
1040
1041	mov	-48(%rax),%r15
1042	mov	-40(%rax),%r14
1043	mov	-32(%rax),%r13
1044	mov	-24(%rax),%r12
1045	mov	-16(%rax),%rbp
1046	mov	-8(%rax),%rbx
1047	mov	%r15,240($context)
1048	mov	%r14,232($context)
1049	mov	%r13,224($context)
1050	mov	%r12,216($context)
1051	mov	%rbp,160($context)
1052	mov	%rbx,144($context)
1053
1054	lea	-0xd8(%rax),%rsi	# %xmm save area
1055	lea	512($context),%rdi	# & context.Xmm6
1056	mov	\$20,%ecx		# 10*sizeof(%xmm0)/sizeof(%rax)
1057	.long	0xa548f3fc		# cld; rep movsq
1058
1059.Lcommon_seh_tail:
1060	mov	8(%rax),%rdi
1061	mov	16(%rax),%rsi
1062	mov	%rax,152($context)	# restore context->Rsp
1063	mov	%rsi,168($context)	# restore context->Rsi
1064	mov	%rdi,176($context)	# restore context->Rdi
1065
1066	mov	40($disp),%rdi		# disp->ContextRecord
1067	mov	$context,%rsi		# context
1068	mov	\$154,%ecx		# sizeof(CONTEXT)
1069	.long	0xa548f3fc		# cld; rep movsq
1070
1071	mov	$disp,%rsi
1072	xor	%rcx,%rcx		# arg1, UNW_FLAG_NHANDLER
1073	mov	8(%rsi),%rdx		# arg2, disp->ImageBase
1074	mov	0(%rsi),%r8		# arg3, disp->ControlPc
1075	mov	16(%rsi),%r9		# arg4, disp->FunctionEntry
1076	mov	40(%rsi),%r10		# disp->ContextRecord
1077	lea	56(%rsi),%r11		# &disp->HandlerData
1078	lea	24(%rsi),%r12		# &disp->EstablisherFrame
1079	mov	%r10,32(%rsp)		# arg5
1080	mov	%r11,40(%rsp)		# arg6
1081	mov	%r12,48(%rsp)		# arg7
1082	mov	%rcx,56(%rsp)		# arg8, (NULL)
1083	call	*__imp_RtlVirtualUnwind(%rip)
1084
1085	mov	\$1,%eax		# ExceptionContinueSearch
1086	add	\$64,%rsp
1087	popfq
1088	pop	%r15
1089	pop	%r14
1090	pop	%r13
1091	pop	%r12
1092	pop	%rbp
1093	pop	%rbx
1094	pop	%rdi
1095	pop	%rsi
1096	ret
1097.size	gcm_se_handler,.-gcm_se_handler
1098
1099.section	.pdata
1100.align	4
1101	.rva	.LSEH_begin_aesni_gcm_decrypt
1102	.rva	.LSEH_end_aesni_gcm_decrypt
1103	.rva	.LSEH_gcm_dec_info
1104
1105	.rva	.LSEH_begin_aesni_gcm_encrypt
1106	.rva	.LSEH_end_aesni_gcm_encrypt
1107	.rva	.LSEH_gcm_enc_info
1108.section	.xdata
1109.align	8
1110.LSEH_gcm_dec_info:
1111	.byte	9,0,0,0
1112	.rva	gcm_se_handler
1113	.rva	.Lgcm_dec_body,.Lgcm_dec_abort
1114.LSEH_gcm_enc_info:
1115	.byte	9,0,0,0
1116	.rva	gcm_se_handler
1117	.rva	.Lgcm_enc_body,.Lgcm_enc_abort
1118___
1119}
1120}}} else {{{
1121$code=<<___;	# assembler is too old
1122.text
1123
1124.globl	aesni_gcm_encrypt
1125.type	aesni_gcm_encrypt,\@abi-omnipotent
1126aesni_gcm_encrypt:
1127	xor	%eax,%eax
1128	ret
1129.size	aesni_gcm_encrypt,.-aesni_gcm_encrypt
1130
1131.globl	aesni_gcm_decrypt
1132.type	aesni_gcm_decrypt,\@abi-omnipotent
1133aesni_gcm_decrypt:
1134	xor	%eax,%eax
1135	ret
1136.size	aesni_gcm_decrypt,.-aesni_gcm_decrypt
1137___
1138}}}
1139
1140$code =~ s/\`([^\`]*)\`/eval($1)/gem;
1141
1142print $code;
1143
1144close STDOUT or die "error closing STDOUT";
1145