xref: /aosp_15_r20/external/google-breakpad/src/common/linux/breakpad_getcontext.S (revision 9712c20fc9bbfbac4935993a2ca0b3958c5adad2)
1// Copyright 2012 Google LLC
2//
3// Redistribution and use in source and binary forms, with or without
4// modification, are permitted provided that the following conditions are
5// met:
6//
7//     * Redistributions of source code must retain the above copyright
8// notice, this list of conditions and the following disclaimer.
9//     * Redistributions in binary form must reproduce the above
10// copyright notice, this list of conditions and the following disclaimer
11// in the documentation and/or other materials provided with the
12// distribution.
13//     * Neither the name of Google LLC nor the names of its
14// contributors may be used to endorse or promote products derived from
15// this software without specific prior written permission.
16//
17// THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
18// "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
19// LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
20// A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
21// OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
22// SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
23// LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
24// DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
25// THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
26// (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
27// OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
28
29// A minimalistic implementation of getcontext() to be used by
30// Google Breakpad when getcontext() is not available in libc.
31
32#include "common/linux/ucontext_constants.h"
33
34/* int getcontext (ucontext_t* ucp) */
35
36#if defined(__arm__)
37
38  .text
39  .global breakpad_getcontext
40  .hidden breakpad_getcontext
41  .type breakpad_getcontext, #function
42  .align 0
43  .fnstart
44breakpad_getcontext:
45
46  /* First, save r4-r11 */
47  add   r1, r0, #(MCONTEXT_GREGS_OFFSET + 4*4)
48  stm   r1, {r4-r11}
49
50  /* r12 is a scratch register, don't save it */
51
52  /* Save sp and lr explicitly. */
53  /* - sp can't be stored with stmia in Thumb-2 */
54  /* - STM instructions that store sp and pc are deprecated in ARM */
55  str   sp, [r0, #(MCONTEXT_GREGS_OFFSET + 13*4)]
56  str   lr, [r0, #(MCONTEXT_GREGS_OFFSET + 14*4)]
57
58  /* Save the caller's address in 'pc' */
59  str   lr, [r0, #(MCONTEXT_GREGS_OFFSET + 15*4)]
60
61  /* Save ucontext_t* pointer across next call */
62  mov   r4, r0
63
64  /* Call sigprocmask(SIG_BLOCK, NULL, &(ucontext->uc_sigmask)) */
65  mov   r0, #0  /* SIG_BLOCK */
66  mov   r1, #0  /* NULL */
67  add   r2, r4, #UCONTEXT_SIGMASK_OFFSET
68  bl    sigprocmask(PLT)
69
70  /* Intentionally do not save the FPU state here. This is because on
71   * Linux/ARM, one should instead use ptrace(PTRACE_GETFPREGS) or
72   * ptrace(PTRACE_GETVFPREGS) to get it.
73   *
74   * Note that a real implementation of getcontext() would need to save
75   * this here to allow setcontext()/swapcontext() to work correctly.
76   */
77
78  /* Restore the values of r4 and lr */
79  mov   r0, r4
80  ldr   lr, [r0, #(MCONTEXT_GREGS_OFFSET + 14*4)]
81  ldr   r4, [r0, #(MCONTEXT_GREGS_OFFSET +  4*4)]
82
83  /* Return 0 */
84  mov   r0, #0
85  bx    lr
86
87  .fnend
88  .size breakpad_getcontext, . - breakpad_getcontext
89
90#elif defined(__aarch64__)
91
92#if defined(__ARM_FEATURE_PAC_DEFAULT) && __ARM_FEATURE_PAC_DEFAULT
93    // ENABLE_PAUTH must be defined to 1 since this value will be used in
94    // bitwise-shift later!
95    #define ENABLE_PAUTH 1
96
97    #if ((__ARM_FEATURE_PAC_DEFAULT&((1<<0)|(1<<1)))==0)
98        #error Pointer authentication defines no valid key!
99    #endif
100#else
101    #define ENABLE_PAUTH 0
102#endif
103
104#if defined(__ARM_FEATURE_BTI_DEFAULT) && (__ARM_FEATURE_BTI_DEFAULT==1)
105    // ENABLE_BTI must be defined to 1 since this value will be used in
106    // bitwise-shift later!
107    #define ENABLE_BTI 1
108#else
109    #define ENABLE_BTI 0
110#endif
111
112
113// Although Pointer Authentication and Branch Target Instructions are technically
114// seperate features they work together, i.e. the paciasp and pacibsp instructions
115// serve as BTI landing pads.
116// Therefore PA-instructions are enabled when PA _or_ BTI is enabled!
117#if ENABLE_PAUTH || ENABLE_BTI
118    // See section "Pointer Authentication" of
119    // https://developer.arm.com/documentation/101028/0012/5--Feature-test-macros
120    // for details how to interpret __ARM_FEATURE_PAC_DEFAULT
121    #if (__ARM_FEATURE_PAC_DEFAULT & (1<<0))
122        #define PAUTH_SIGN_SP paciasp
123        #define PAUTH_AUTH_SP autiasp
124    #else
125        #define PAUTH_SIGN_SP pacibsp
126        #define PAUTH_AUTH_SP autibsp
127    #endif
128#else
129    #define PAUTH_SIGN_SP
130    #define PAUTH_AUTH_SP
131#endif
132
133#define  _NSIG                       64
134#define  __NR_rt_sigprocmask         135
135
136  .text
137  .global breakpad_getcontext
138  .hidden breakpad_getcontext
139  .type breakpad_getcontext, #function
140  .align 4
141  .cfi_startproc
142breakpad_getcontext:
143
144  PAUTH_SIGN_SP
145
146  /* The saved context will return to the getcontext() call point
147     with a return value of 0 */
148  str     xzr,      [x0, MCONTEXT_GREGS_OFFSET +  0 * REGISTER_SIZE]
149
150  stp     x18, x19, [x0, MCONTEXT_GREGS_OFFSET + 18 * REGISTER_SIZE]
151  stp     x20, x21, [x0, MCONTEXT_GREGS_OFFSET + 20 * REGISTER_SIZE]
152  stp     x22, x23, [x0, MCONTEXT_GREGS_OFFSET + 22 * REGISTER_SIZE]
153  stp     x24, x25, [x0, MCONTEXT_GREGS_OFFSET + 24 * REGISTER_SIZE]
154  stp     x26, x27, [x0, MCONTEXT_GREGS_OFFSET + 26 * REGISTER_SIZE]
155  stp     x28, x29, [x0, MCONTEXT_GREGS_OFFSET + 28 * REGISTER_SIZE]
156  str     x30,      [x0, MCONTEXT_GREGS_OFFSET + 30 * REGISTER_SIZE]
157
158  /* Place LR into the saved PC, this will ensure that when
159     switching to this saved context with setcontext() control
160     will pass back to the caller of getcontext(), we have
161     already arranged to return the appropriate return value in x0
162     above.  */
163  str     x30, [x0, MCONTEXT_PC_OFFSET]
164
165  /* Save the current SP */
166  mov     x2, sp
167  str     x2, [x0, MCONTEXT_SP_OFFSET]
168
169  /* Initialize the pstate.  */
170  str     xzr, [x0, MCONTEXT_PSTATE_OFFSET]
171
172  /* Figure out where to place the first context extension
173     block.  */
174  add     x2, x0, #MCONTEXT_EXTENSION_OFFSET
175
176  /* Write the context extension fpsimd header.  */
177  mov     w3, #(FPSIMD_MAGIC & 0xffff)
178  movk    w3, #(FPSIMD_MAGIC >> 16), lsl #16
179  str     w3, [x2, #FPSIMD_CONTEXT_MAGIC_OFFSET]
180  mov     w3, #FPSIMD_CONTEXT_SIZE
181  str     w3, [x2, #FPSIMD_CONTEXT_SIZE_OFFSET]
182
183  /* Fill in the FP SIMD context.  */
184  add     x3, x2, #(FPSIMD_CONTEXT_VREGS_OFFSET + 8 * SIMD_REGISTER_SIZE)
185  stp     d8,  d9, [x3], #(2 * SIMD_REGISTER_SIZE)
186  stp     d10, d11, [x3], #(2 * SIMD_REGISTER_SIZE)
187  stp     d12, d13, [x3], #(2 * SIMD_REGISTER_SIZE)
188  stp     d14, d15, [x3], #(2 * SIMD_REGISTER_SIZE)
189
190  add     x3, x2, FPSIMD_CONTEXT_FPSR_OFFSET
191
192  mrs     x4, fpsr
193  str     w4, [x3]
194
195  mrs     x4, fpcr
196  str     w4, [x3, FPSIMD_CONTEXT_FPCR_OFFSET - FPSIMD_CONTEXT_FPSR_OFFSET]
197
198  /* Write the termination context extension header.  */
199  add     x2, x2, #FPSIMD_CONTEXT_SIZE
200
201  str     xzr, [x2, #FPSIMD_CONTEXT_MAGIC_OFFSET]
202  str     xzr, [x2, #FPSIMD_CONTEXT_SIZE_OFFSET]
203
204  /* Grab the signal mask */
205  /* rt_sigprocmask (SIG_BLOCK, NULL, &ucp->uc_sigmask, _NSIG8) */
206  add     x2, x0, #UCONTEXT_SIGMASK_OFFSET
207  mov     x0, #0  /* SIG_BLOCK */
208  mov     x1, #0  /* NULL */
209  mov     x3, #(_NSIG / 8)
210  mov     x8, #__NR_rt_sigprocmask
211  svc     0
212
213  /* Return x0 for success */
214  mov     x0, 0
215
216  PAUTH_AUTH_SP
217
218  ret
219
220  .cfi_endproc
221  .size breakpad_getcontext, . - breakpad_getcontext
222
223#elif defined(__i386__)
224
225  .text
226  .global breakpad_getcontext
227  .hidden breakpad_getcontext
228  .align 4
229  .type breakpad_getcontext, @function
230
231breakpad_getcontext:
232
233  movl 4(%esp), %eax   /* eax = uc */
234
235  /* Save register values */
236  movl %ecx, MCONTEXT_ECX_OFFSET(%eax)
237  movl %edx, MCONTEXT_EDX_OFFSET(%eax)
238  movl %ebx, MCONTEXT_EBX_OFFSET(%eax)
239  movl %edi, MCONTEXT_EDI_OFFSET(%eax)
240  movl %esi, MCONTEXT_ESI_OFFSET(%eax)
241  movl %ebp, MCONTEXT_EBP_OFFSET(%eax)
242
243  movl (%esp), %edx   /* return address */
244  lea  4(%esp), %ecx  /* exclude return address from stack */
245  mov  %edx, MCONTEXT_EIP_OFFSET(%eax)
246  mov  %ecx, MCONTEXT_ESP_OFFSET(%eax)
247
248  xorl %ecx, %ecx
249  movw %fs, %cx
250  mov  %ecx, MCONTEXT_FS_OFFSET(%eax)
251
252  movl $0, MCONTEXT_EAX_OFFSET(%eax)
253
254  /* Save floating point state to fpregstate, then update
255   * the fpregs pointer to point to it */
256  leal UCONTEXT_FPREGS_MEM_OFFSET(%eax), %ecx
257  fnstenv (%ecx)
258  fldenv  (%ecx)
259  mov %ecx, UCONTEXT_FPREGS_OFFSET(%eax)
260
261  /* Save signal mask: sigprocmask(SIGBLOCK, NULL, &uc->uc_sigmask) */
262  leal UCONTEXT_SIGMASK_OFFSET(%eax), %edx
263  xorl %ecx, %ecx
264  push %edx   /* &uc->uc_sigmask */
265  push %ecx   /* NULL */
266  push %ecx   /* SIGBLOCK == 0 on i386 */
267  call sigprocmask@PLT
268  addl $12, %esp
269
270  movl $0, %eax
271  ret
272
273  .size breakpad_getcontext, . - breakpad_getcontext
274
275#elif defined(__mips__)
276
277// This implementation is inspired by implementation of getcontext in glibc.
278#include <asm-mips/asm.h>
279#include <asm-mips/regdef.h>
280#if _MIPS_SIM == _ABIO32
281#include <asm-mips/fpregdef.h>
282#endif
283
284// from asm-mips/asm.h
285#if _MIPS_SIM == _ABIO32
286#define ALSZ 7
287#define ALMASK ~7
288#define SZREG 4
289#else // _MIPS_SIM != _ABIO32
290#define ALSZ 15
291#define ALMASK ~15
292#define SZREG 8
293#endif
294
295#include <asm/unistd.h> // for __NR_rt_sigprocmask
296
297#define _NSIG8 128 / 8
298#define SIG_BLOCK 1
299
300
301  .text
302LOCALS_NUM = 1 // save gp on stack
303FRAME_SIZE = ((LOCALS_NUM * SZREG) + ALSZ) & ALMASK
304
305GP_FRAME_OFFSET = FRAME_SIZE - (1 * SZREG)
306MCONTEXT_REG_SIZE = 8
307
308#if _MIPS_SIM == _ABIO32
309
310NESTED (breakpad_getcontext, FRAME_SIZE, ra)
311  .mask	0x00000000, 0
312  .fmask 0x00000000, 0
313
314  .set noreorder
315  .cpload t9
316  .set reorder
317
318  move a2, sp
319#define _SP a2
320
321  addiu sp, -FRAME_SIZE
322  .cprestore GP_FRAME_OFFSET
323
324  sw s0, (16 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
325  sw s1, (17 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
326  sw s2, (18 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
327  sw s3, (19 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
328  sw s4, (20 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
329  sw s5, (21 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
330  sw s6, (22 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
331  sw s7, (23 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
332  sw _SP, (29 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
333  sw fp, (30 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
334  sw ra, (31 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
335  sw ra, MCONTEXT_PC_OFFSET(a0)
336
337#ifdef __mips_hard_float
338  s.d fs0, (20 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
339  s.d fs1, (22 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
340  s.d fs2, (24 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
341  s.d fs3, (26 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
342  s.d fs4, (28 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
343  s.d fs5, (30 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
344
345  cfc1 v1, fcr31
346  sw v1, MCONTEXT_FPC_CSR(a0)
347#endif  // __mips_hard_float
348
349  /* rt_sigprocmask (SIG_BLOCK, NULL, &ucp->uc_sigmask, _NSIG8) */
350  li a3, _NSIG8
351  addu a2, a0, UCONTEXT_SIGMASK_OFFSET
352  move a1, zero
353  li a0, SIG_BLOCK
354  li v0, __NR_rt_sigprocmask
355  syscall
356
357  addiu sp, FRAME_SIZE
358  jr ra
359
360END (breakpad_getcontext)
361#else
362
363#ifndef NESTED
364/*
365 * NESTED - declare nested routine entry point
366 */
367#define NESTED(symbol, framesize, rpc)  \
368    .globl  symbol;                     \
369    .align  2;                          \
370    .type symbol,@function;             \
371    .ent  symbol,0;                     \
372symbol:   .frame  sp, framesize, rpc;
373#endif
374
375/*
376 * END - mark end of function
377 */
378#ifndef END
379# define END(function)                  \
380    .end  function;                     \
381    .size function,.-function
382#endif
383
384/* int getcontext (ucontext_t* ucp) */
385
386NESTED (breakpad_getcontext, FRAME_SIZE, ra)
387  .mask   0x10000000, 0
388  .fmask  0x00000000, 0
389
390  move  a2, sp
391#define _SP a2
392  move  a3, gp
393#define _GP a3
394
395  daddiu sp, -FRAME_SIZE
396  .cpsetup $25, GP_FRAME_OFFSET, breakpad_getcontext
397
398  /* Store a magic flag.  */
399  li  v1, 1
400  sd v1, (0 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)  /* zero */
401
402  sd s0, (16 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
403  sd s1, (17 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
404  sd s2, (18 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
405  sd s3, (19 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
406  sd s4, (20 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
407  sd s5, (21 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
408  sd s6, (22 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
409  sd s7, (23 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
410  sd _GP, (28 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
411  sd _SP, (29 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
412  sd s8, (30 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
413  sd ra, (31 * MCONTEXT_REG_SIZE + MCONTEXT_GREGS_OFFSET)(a0)
414  sd ra, MCONTEXT_PC_OFFSET(a0)
415
416#ifdef __mips_hard_float
417  s.d $f24, (24 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
418  s.d $f25, (25 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
419  s.d $f26, (26 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
420  s.d $f27, (27 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
421  s.d $f28, (28 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
422  s.d $f29, (29 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
423  s.d $f30, (30 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
424  s.d $f31, (31 * MCONTEXT_REG_SIZE + MCONTEXT_FPREGS_OFFSET)(a0)
425
426  cfc1  v1, $31
427  sw  v1, MCONTEXT_FPC_CSR(a0)
428#endif /* __mips_hard_float */
429
430/* rt_sigprocmask (SIG_BLOCK, NULL, &ucp->uc_sigmask, _NSIG8) */
431  li  a3, _NSIG8
432  daddu a2, a0, UCONTEXT_SIGMASK_OFFSET
433  move  a1, zero
434  li  a0, SIG_BLOCK
435
436  li  v0, __NR_rt_sigprocmask
437  syscall
438
439  .cpreturn
440  daddiu sp, FRAME_SIZE
441  move  v0, zero
442  jr  ra
443
444END (breakpad_getcontext)
445#endif // _MIPS_SIM == _ABIO32
446
447#elif defined(__x86_64__)
448/* The x64 implementation of breakpad_getcontext was derived in part
449   from the implementation of libunwind which requires the following
450   notice. */
451/* libunwind - a platform-independent unwind library
452   Copyright (C) 2008 Google, Inc
453	Contributed by Paul Pluzhnikov <[email protected]>
454   Copyright (C) 2010 Konstantin Belousov <[email protected]>
455
456This file is part of libunwind.
457
458Permission is hereby granted, free of charge, to any person obtaining
459a copy of this software and associated documentation files (the
460"Software"), to deal in the Software without restriction, including
461without limitation the rights to use, copy, modify, merge, publish,
462distribute, sublicense, and/or sell copies of the Software, and to
463permit persons to whom the Software is furnished to do so, subject to
464the following conditions:
465
466The above copyright notice and this permission notice shall be
467included in all copies or substantial portions of the Software.
468
469THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
470EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
471MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
472NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE
473LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION
474OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION
475WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.  */
476
477  .text
478  .global breakpad_getcontext
479  .hidden breakpad_getcontext
480  .align 4
481  .type breakpad_getcontext, @function
482
483breakpad_getcontext:
484  .cfi_startproc
485
486  /* Callee saved: RBX, RBP, R12-R15  */
487  movq %r12, MCONTEXT_GREGS_R12(%rdi)
488  movq %r13, MCONTEXT_GREGS_R13(%rdi)
489  movq %r14, MCONTEXT_GREGS_R14(%rdi)
490  movq %r15, MCONTEXT_GREGS_R15(%rdi)
491  movq %rbp, MCONTEXT_GREGS_RBP(%rdi)
492  movq %rbx, MCONTEXT_GREGS_RBX(%rdi)
493
494  /* Save argument registers (not strictly needed, but setcontext
495     restores them, so don't restore garbage).  */
496  movq %r8,  MCONTEXT_GREGS_R8(%rdi)
497  movq %r9,  MCONTEXT_GREGS_R9(%rdi)
498  movq %rdi, MCONTEXT_GREGS_RDI(%rdi)
499  movq %rsi, MCONTEXT_GREGS_RSI(%rdi)
500  movq %rdx, MCONTEXT_GREGS_RDX(%rdi)
501  movq %rax, MCONTEXT_GREGS_RAX(%rdi)
502  movq %rcx, MCONTEXT_GREGS_RCX(%rdi)
503
504  /* Save fp state (not needed, except for setcontext not
505     restoring garbage).  */
506  leaq MCONTEXT_FPREGS_MEM(%rdi),%r8
507  movq %r8, MCONTEXT_FPREGS_PTR(%rdi)
508  fnstenv (%r8)
509  stmxcsr FPREGS_OFFSET_MXCSR(%r8)
510
511  leaq 8(%rsp), %rax /* exclude this call.  */
512  movq %rax, MCONTEXT_GREGS_RSP(%rdi)
513
514  movq 0(%rsp), %rax
515  movq %rax, MCONTEXT_GREGS_RIP(%rdi)
516
517  /* Save signal mask: sigprocmask(SIGBLOCK, NULL, &uc->uc_sigmask) */
518  leaq UCONTEXT_SIGMASK_OFFSET(%rdi), %rdx  // arg3
519  xorq %rsi, %rsi  // arg2 NULL
520  xorq %rdi, %rdi  // arg1 SIGBLOCK == 0
521  call sigprocmask@PLT
522
523  /* Always return 0 for success, even if sigprocmask failed. */
524  xorl %eax, %eax
525  ret
526  .cfi_endproc
527  .size breakpad_getcontext, . - breakpad_getcontext
528
529#elif defined(__riscv)
530
531# define SIG_BLOCK                     0
532# define _NSIG8                        8
533# define __NR_rt_sigprocmask         135
534
535  .text
536  .globl breakpad_getcontext
537  .type breakpad_getcontext, @function
538  .align 0
539  .cfi_startproc
540breakpad_getcontext:
541  REG_S ra,  MCONTEXT_GREGS_PC(a0)
542  REG_S ra,  MCONTEXT_GREGS_RA(a0)
543  REG_S sp,  MCONTEXT_GREGS_SP(a0)
544  REG_S gp,  MCONTEXT_GREGS_SP(a0)
545  REG_S tp,  MCONTEXT_GREGS_TP(a0)
546  REG_S t0,  MCONTEXT_GREGS_T0(a0)
547  REG_S t1,  MCONTEXT_GREGS_T1(a0)
548  REG_S t2,  MCONTEXT_GREGS_T2(a0)
549  REG_S s0,  MCONTEXT_GREGS_S0(a0)
550  REG_S s1,  MCONTEXT_GREGS_S1(a0)
551  REG_S a0,  MCONTEXT_GREGS_A0(a0)
552  REG_S a1,  MCONTEXT_GREGS_A1(a0)
553  REG_S a2,  MCONTEXT_GREGS_A2(a0)
554  REG_S a3,  MCONTEXT_GREGS_A3(a0)
555  REG_S a4,  MCONTEXT_GREGS_A4(a0)
556  REG_S a5,  MCONTEXT_GREGS_A5(a0)
557  REG_S a6,  MCONTEXT_GREGS_A6(a0)
558  REG_S a7,  MCONTEXT_GREGS_A7(a0)
559  REG_S s2,  MCONTEXT_GREGS_S2(a0)
560  REG_S s3,  MCONTEXT_GREGS_S3(a0)
561  REG_S s4,  MCONTEXT_GREGS_S4(a0)
562  REG_S s5,  MCONTEXT_GREGS_S5(a0)
563  REG_S s6,  MCONTEXT_GREGS_S6(a0)
564  REG_S s7,  MCONTEXT_GREGS_S7(a0)
565  REG_S s8,  MCONTEXT_GREGS_S8(a0)
566  REG_S s9,  MCONTEXT_GREGS_S9(a0)
567  REG_S s10, MCONTEXT_GREGS_S10(a0)
568  REG_S s11, MCONTEXT_GREGS_S11(a0)
569  REG_S t3,  MCONTEXT_GREGS_T3(a0)
570  REG_S t4,  MCONTEXT_GREGS_T4(a0)
571  REG_S t5,  MCONTEXT_GREGS_T5(a0)
572  REG_S t6 , MCONTEXT_GREGS_T6(a0)
573# ifndef __riscv_float_abi_soft
574  frsr a1
575
576  FREG_S ft0,  MCONTEXT_FPREGS_FT0(a0)
577  FREG_S ft1,  MCONTEXT_FPREGS_FT1(a0)
578  FREG_S ft2,  MCONTEXT_FPREGS_FT2(a0)
579  FREG_S ft3,  MCONTEXT_FPREGS_FT3(a0)
580  FREG_S ft4,  MCONTEXT_FPREGS_FT4(a0)
581  FREG_S ft5,  MCONTEXT_FPREGS_FT5(a0)
582  FREG_S ft6,  MCONTEXT_FPREGS_FT6(a0)
583  FREG_S ft7,  MCONTEXT_FPREGS_FT7(a0)
584  FREG_S fs0,  MCONTEXT_FPREGS_FS0(a0)
585  FREG_S fs1,  MCONTEXT_FPREGS_FS1(a0)
586  FREG_S fa0,  MCONTEXT_FPREGS_FA0(a0)
587  FREG_S fa1,  MCONTEXT_FPREGS_FA1(a0)
588  FREG_S fa2,  MCONTEXT_FPREGS_FA2(a0)
589  FREG_S fa3,  MCONTEXT_FPREGS_FA3(a0)
590  FREG_S fa4,  MCONTEXT_FPREGS_FA4(a0)
591  FREG_S fa5,  MCONTEXT_FPREGS_FA5(a0)
592  FREG_S fa6,  MCONTEXT_FPREGS_FA6(a0)
593  FREG_S fa7,  MCONTEXT_FPREGS_FA7(a0)
594  FREG_S fs2,  MCONTEXT_FPREGS_FS2(a0)
595  FREG_S fs3,  MCONTEXT_FPREGS_FS3(a0)
596  FREG_S fs4,  MCONTEXT_FPREGS_FS4(a0)
597  FREG_S fs5,  MCONTEXT_FPREGS_FS5(a0)
598  FREG_S fs6,  MCONTEXT_FPREGS_FS6(a0)
599  FREG_S fs7,  MCONTEXT_FPREGS_FS7(a0)
600  FREG_S fs8,  MCONTEXT_FPREGS_FS8(a0)
601  FREG_S fs9,  MCONTEXT_FPREGS_FS9(a0)
602  FREG_S fs10, MCONTEXT_FPREGS_FS10(a0)
603  FREG_S fs11, MCONTEXT_FPREGS_FS11(a0)
604  FREG_S ft8,  MCONTEXT_FPREGS_FT8(a0)
605  FREG_S ft9,  MCONTEXT_FPREGS_FT9(a0)
606  FREG_S ft10, MCONTEXT_FPREGS_FT10(a0)
607  FREG_S ft11, MCONTEXT_FPREGS_FT11(a0)
608
609  sw a1, MCONTEXT_FPC_CSR(a0)
610# endif // __riscv_float_abi_soft
611  mv a1, zero
612  add a2, a0, UCONTEXT_SIGMASK_OFFSET
613  li a3, _NSIG8
614  mv a0, zero
615  li a7, __NR_rt_sigprocmask
616  ecall
617  mv a0, zero
618  ret
619
620  .cfi_endproc
621  .size breakpad_getcontext, . - breakpad_getcontext
622
623#else
624# error "This file has not been ported for your CPU!"
625#endif
626
627#if defined(__aarch64__)
628// ENABLE_PAUTH and ENABLE_BTI would be enabled at the definition
629//  of AArch64 specific breakpad_getcontext function
630#if ENABLE_PAUTH || ENABLE_BTI
631// for further information on the .note.gnu.property section see
632// https://github.com/ARM-software/abi-aa/blob/main/aaelf64/aaelf64.rst#program-property
633.pushsection .note.gnu.property, "a";
634    .balign 8
635    .long 4
636    .long 0x10
637    .long 0x5
638    .asciz "GNU"
639    .long 0xc0000000 /* GNU_PROPERTY_AARCH64_FEATURE_1_AND */
640    .long 4
641    .long ((ENABLE_PAUTH)<<1) | ((ENABLE_BTI)<<0) /* PAuth and BTI */
642    .long 0
643.popsection
644#endif
645#endif
646