1// cmd/9l/noop.c, cmd/9l/pass.c, cmd/9l/span.c from Vita Nuova.
2//
3//	Copyright © 1994-1999 Lucent Technologies Inc.  All rights reserved.
4//	Portions Copyright © 1995-1997 C H Forsyth ([email protected])
5//	Portions Copyright © 1997-1999 Vita Nuova Limited
6//	Portions Copyright © 2000-2008 Vita Nuova Holdings Limited (www.vitanuova.com)
7//	Portions Copyright © 2004,2006 Bruce Ellis
8//	Portions Copyright © 2005-2007 C H Forsyth ([email protected])
9//	Revisions Copyright © 2000-2008 Lucent Technologies Inc. and others
10//	Portions Copyright © 2009 The Go Authors. All rights reserved.
11//
12// Permission is hereby granted, free of charge, to any person obtaining a copy
13// of this software and associated documentation files (the "Software"), to deal
14// in the Software without restriction, including without limitation the rights
15// to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
16// copies of the Software, and to permit persons to whom the Software is
17// furnished to do so, subject to the following conditions:
18//
19// The above copyright notice and this permission notice shall be included in
20// all copies or substantial portions of the Software.
21//
22// THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
23// IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
24// FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.  IN NO EVENT SHALL THE
25// AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
26// LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
27// OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
28// THE SOFTWARE.
29
30package ppc64
31
32import (
33	"cmd/internal/obj"
34	"cmd/internal/objabi"
35	"cmd/internal/src"
36	"cmd/internal/sys"
37	"internal/abi"
38	"internal/buildcfg"
39	"log"
40	"math"
41	"math/bits"
42	"strings"
43)
44
45// Test if this value can encoded as a mask for
46// li -1, rx; rlic rx,rx,sh,mb.
47// Masks can also extend from the msb and wrap to
48// the lsb too. That is, the valid masks are 32 bit strings
49// of the form: 0..01..10..0 or 1..10..01..1 or 1...1
50func isPPC64DoublewordRotateMask(v64 int64) bool {
51	// Isolate rightmost 1 (if none 0) and add.
52	v := uint64(v64)
53	vp := (v & -v) + v
54	// Likewise, for the wrapping case.
55	vn := ^v
56	vpn := (vn & -vn) + vn
57	return (v&vp == 0 || vn&vpn == 0) && v != 0
58}
59
60// Encode a doubleword rotate mask into mb (mask begin) and
61// me (mask end, inclusive). Note, POWER ISA labels bits in
62// big endian order.
63func encodePPC64RLDCMask(mask int64) (mb, me int) {
64	// Determine boundaries and then decode them
65	mb = bits.LeadingZeros64(uint64(mask))
66	me = 64 - bits.TrailingZeros64(uint64(mask))
67	mbn := bits.LeadingZeros64(^uint64(mask))
68	men := 64 - bits.TrailingZeros64(^uint64(mask))
69	// Check for a wrapping mask (e.g bits at 0 and 63)
70	if mb == 0 && me == 64 {
71		// swap the inverted values
72		mb, me = men, mbn
73	}
74	// Note, me is inclusive.
75	return mb, me - 1
76}
77
78// Is this a symbol which should never have a TOC prologue generated?
79// These are special functions which should not have a TOC regeneration
80// prologue.
81func isNOTOCfunc(name string) bool {
82	switch {
83	case name == "runtime.duffzero":
84		return true
85	case name == "runtime.duffcopy":
86		return true
87	case strings.HasPrefix(name, "runtime.elf_"):
88		return true
89	default:
90		return false
91	}
92}
93
94// Try converting FMOVD/FMOVS to XXSPLTIDP. If it is converted,
95// return true.
96func convertFMOVtoXXSPLTIDP(p *obj.Prog) bool {
97	if p.From.Type != obj.TYPE_FCONST || buildcfg.GOPPC64 < 10 {
98		return false
99	}
100	v := p.From.Val.(float64)
101	if float64(float32(v)) != v {
102		return false
103	}
104	// Secondly, is this value a normal value?
105	ival := int64(math.Float32bits(float32(v)))
106	isDenorm := ival&0x7F800000 == 0 && ival&0x007FFFFF != 0
107	if !isDenorm {
108		p.As = AXXSPLTIDP
109		p.From.Type = obj.TYPE_CONST
110		p.From.Offset = ival
111		// Convert REG_Fx into equivalent REG_VSx
112		p.To.Reg = REG_VS0 + (p.To.Reg & 31)
113	}
114	return !isDenorm
115}
116
117func progedit(ctxt *obj.Link, p *obj.Prog, newprog obj.ProgAlloc) {
118	p.From.Class = 0
119	p.To.Class = 0
120
121	c := ctxt9{ctxt: ctxt, newprog: newprog}
122
123	// Rewrite BR/BL to symbol as TYPE_BRANCH.
124	switch p.As {
125	case ABR,
126		ABL,
127		obj.ARET,
128		obj.ADUFFZERO,
129		obj.ADUFFCOPY:
130		if p.To.Sym != nil {
131			p.To.Type = obj.TYPE_BRANCH
132		}
133	}
134
135	// Rewrite float constants to values stored in memory.
136	switch p.As {
137	case AFMOVS:
138		if p.From.Type == obj.TYPE_FCONST && !convertFMOVtoXXSPLTIDP(p) {
139			f32 := float32(p.From.Val.(float64))
140			p.From.Type = obj.TYPE_MEM
141			p.From.Sym = ctxt.Float32Sym(f32)
142			p.From.Name = obj.NAME_EXTERN
143			p.From.Offset = 0
144		}
145
146	case AFMOVD:
147		if p.From.Type == obj.TYPE_FCONST {
148			f64 := p.From.Val.(float64)
149			// Constant not needed in memory for float +/- 0
150			if f64 != 0 && !convertFMOVtoXXSPLTIDP(p) {
151				p.From.Type = obj.TYPE_MEM
152				p.From.Sym = ctxt.Float64Sym(f64)
153				p.From.Name = obj.NAME_EXTERN
154				p.From.Offset = 0
155			}
156		}
157
158	case AMOVW, AMOVWZ:
159		// Note, for backwards compatibility, MOVW $const, Rx and MOVWZ $const, Rx are identical.
160		if p.From.Type == obj.TYPE_CONST && p.From.Offset != 0 && p.From.Offset&0xFFFF == 0 {
161			// This is a constant shifted 16 bits to the left, convert it to ADDIS/ORIS $const,...
162			p.As = AADDIS
163			// Use ORIS for large constants which should not be sign extended.
164			if p.From.Offset >= 0x80000000 {
165				p.As = AORIS
166			}
167			p.Reg = REG_R0
168			p.From.Offset >>= 16
169		}
170
171	case AMOVD:
172		// Skip this opcode if it is not a constant load.
173		if p.From.Type != obj.TYPE_CONST || p.From.Name != obj.NAME_NONE || p.From.Reg != 0 {
174			break
175		}
176
177		// 32b constants (signed and unsigned) can be generated via 1 or 2 instructions. They can be assembled directly.
178		isS32 := int64(int32(p.From.Offset)) == p.From.Offset
179		isU32 := uint64(uint32(p.From.Offset)) == uint64(p.From.Offset)
180		// If prefixed instructions are supported, a 34b signed constant can be generated by one pli instruction.
181		isS34 := pfxEnabled && (p.From.Offset<<30)>>30 == p.From.Offset
182
183		// Try converting MOVD $const,Rx into ADDIS/ORIS $s32>>16,R0,Rx
184		switch {
185		case isS32 && p.From.Offset&0xFFFF == 0 && p.From.Offset != 0:
186			p.As = AADDIS
187			p.From.Offset >>= 16
188			p.Reg = REG_R0
189
190		case isU32 && p.From.Offset&0xFFFF == 0 && p.From.Offset != 0:
191			p.As = AORIS
192			p.From.Offset >>= 16
193			p.Reg = REG_R0
194
195		case isS32 || isU32 || isS34:
196			// The assembler can generate this opcode in 1 (on Power10) or 2 opcodes.
197
198		// Otherwise, see if the large constant can be generated with 2 instructions. If not, load it from memory.
199		default:
200			// Is this a shifted 16b constant? If so, rewrite it to avoid a creating and loading a constant.
201			val := p.From.Offset
202			shift := bits.TrailingZeros64(uint64(val))
203			mask := int64(0xFFFF) << shift
204			if val&mask == val || (val>>(shift+16) == -1 && (val>>shift)<<shift == val) {
205				// Rewrite this value into MOVD $const>>shift, Rto; SLD $shift, Rto
206				q := obj.Appendp(p, c.newprog)
207				q.As = ASLD
208				q.From.SetConst(int64(shift))
209				q.To = p.To
210				p.From.Offset >>= shift
211				p = q
212			} else if isPPC64DoublewordRotateMask(val) {
213				// This constant is a mask value, generate MOVD $-1, Rto; RLDIC Rto, ^me, mb, Rto
214				mb, me := encodePPC64RLDCMask(val)
215				q := obj.Appendp(p, c.newprog)
216				q.As = ARLDC
217				q.AddRestSourceConst((^int64(me)) & 0x3F)
218				q.AddRestSourceConst(int64(mb))
219				q.From = p.To
220				q.To = p.To
221				p.From.Offset = -1
222				p = q
223			} else {
224				// Load the constant from memory.
225				p.From.Type = obj.TYPE_MEM
226				p.From.Sym = ctxt.Int64Sym(p.From.Offset)
227				p.From.Name = obj.NAME_EXTERN
228				p.From.Offset = 0
229			}
230		}
231	}
232
233	switch p.As {
234	// Rewrite SUB constants into ADD.
235	case ASUBC:
236		if p.From.Type == obj.TYPE_CONST {
237			p.From.Offset = -p.From.Offset
238			p.As = AADDC
239		}
240
241	case ASUBCCC:
242		if p.From.Type == obj.TYPE_CONST {
243			p.From.Offset = -p.From.Offset
244			p.As = AADDCCC
245		}
246
247	case ASUB:
248		if p.From.Type != obj.TYPE_CONST {
249			break
250		}
251		// Rewrite SUB $const,... into ADD $-const,...
252		p.From.Offset = -p.From.Offset
253		p.As = AADD
254		// This is now an ADD opcode, try simplifying it below.
255		fallthrough
256
257	// Rewrite ADD/OR/XOR/ANDCC $const,... forms into ADDIS/ORIS/XORIS/ANDISCC
258	case AADD:
259		// Don't rewrite if this is not adding a constant value, or is not an int32
260		if p.From.Type != obj.TYPE_CONST || p.From.Offset == 0 || int64(int32(p.From.Offset)) != p.From.Offset {
261			break
262		}
263		if p.From.Offset&0xFFFF == 0 {
264			// The constant can be added using ADDIS
265			p.As = AADDIS
266			p.From.Offset >>= 16
267		} else if buildcfg.GOPPC64 >= 10 {
268			// Let the assembler generate paddi for large constants.
269			break
270		} else if (p.From.Offset < -0x8000 && int64(int32(p.From.Offset)) == p.From.Offset) || (p.From.Offset > 0xFFFF && p.From.Offset < 0x7FFF8000) {
271			// For a constant x, 0xFFFF (UINT16_MAX) < x < 0x7FFF8000 or -0x80000000 (INT32_MIN) <= x < -0x8000 (INT16_MIN)
272			// This is not done for 0x7FFF < x < 0x10000; the assembler will generate a slightly faster instruction sequence.
273			//
274			// The constant x can be rewritten as ADDIS + ADD as follows:
275			//     ADDIS $x>>16 + (x>>15)&1, rX, rY
276			//     ADD   $int64(int16(x)), rY, rY
277			// The range is slightly asymmetric as 0x7FFF8000 and above overflow the sign bit, whereas for
278			// negative values, this would happen with constant values between -1 and -32768 which can
279			// assemble into a single addi.
280			is := p.From.Offset>>16 + (p.From.Offset>>15)&1
281			i := int64(int16(p.From.Offset))
282			p.As = AADDIS
283			p.From.Offset = is
284			q := obj.Appendp(p, c.newprog)
285			q.As = AADD
286			q.From.SetConst(i)
287			q.Reg = p.To.Reg
288			q.To = p.To
289			p = q
290		}
291	case AOR:
292		if p.From.Type == obj.TYPE_CONST && uint64(p.From.Offset)&0xFFFFFFFF0000FFFF == 0 && p.From.Offset != 0 {
293			p.As = AORIS
294			p.From.Offset >>= 16
295		}
296	case AXOR:
297		if p.From.Type == obj.TYPE_CONST && uint64(p.From.Offset)&0xFFFFFFFF0000FFFF == 0 && p.From.Offset != 0 {
298			p.As = AXORIS
299			p.From.Offset >>= 16
300		}
301	case AANDCC:
302		if p.From.Type == obj.TYPE_CONST && uint64(p.From.Offset)&0xFFFFFFFF0000FFFF == 0 && p.From.Offset != 0 {
303			p.As = AANDISCC
304			p.From.Offset >>= 16
305		}
306
307	// To maintain backwards compatibility, we accept some 4 argument usage of
308	// several opcodes which was likely not intended, but did work. These are not
309	// added to optab to avoid the chance this behavior might be used with newer
310	// instructions.
311	//
312	// Rewrite argument ordering like "ADDEX R3, $3, R4, R5" into
313	//                                "ADDEX R3, R4, $3, R5"
314	case AVSHASIGMAW, AVSHASIGMAD, AADDEX, AXXSLDWI, AXXPERMDI:
315		if len(p.RestArgs) == 2 && p.Reg == 0 && p.RestArgs[0].Addr.Type == obj.TYPE_CONST && p.RestArgs[1].Addr.Type == obj.TYPE_REG {
316			p.Reg = p.RestArgs[1].Addr.Reg
317			p.RestArgs = p.RestArgs[:1]
318		}
319	}
320
321	if c.ctxt.Headtype == objabi.Haix {
322		c.rewriteToUseTOC(p)
323	} else if c.ctxt.Flag_dynlink {
324		c.rewriteToUseGot(p)
325	}
326}
327
328// Rewrite p, if necessary, to access a symbol using its TOC anchor.
329// This code is for AIX only.
330func (c *ctxt9) rewriteToUseTOC(p *obj.Prog) {
331	if p.As == obj.ATEXT || p.As == obj.AFUNCDATA || p.As == obj.ACALL || p.As == obj.ARET || p.As == obj.AJMP {
332		return
333	}
334
335	if p.As == obj.ADUFFCOPY || p.As == obj.ADUFFZERO {
336		// ADUFFZERO/ADUFFCOPY is considered as an ABL except in dynamic
337		// link where it should be an indirect call.
338		if !c.ctxt.Flag_dynlink {
339			return
340		}
341		//     ADUFFxxx $offset
342		// becomes
343		//     MOVD runtime.duffxxx@TOC, R12
344		//     ADD $offset, R12
345		//     MOVD R12, LR
346		//     BL (LR)
347		var sym *obj.LSym
348		if p.As == obj.ADUFFZERO {
349			sym = c.ctxt.Lookup("runtime.duffzero")
350		} else {
351			sym = c.ctxt.Lookup("runtime.duffcopy")
352		}
353		// Retrieve or create the TOC anchor.
354		symtoc := c.ctxt.LookupInit("TOC."+sym.Name, func(s *obj.LSym) {
355			s.Type = objabi.SDATA
356			s.Set(obj.AttrDuplicateOK, true)
357			s.Set(obj.AttrStatic, true)
358			c.ctxt.Data = append(c.ctxt.Data, s)
359			s.WriteAddr(c.ctxt, 0, 8, sym, 0)
360		})
361
362		offset := p.To.Offset
363		p.As = AMOVD
364		p.From.Type = obj.TYPE_MEM
365		p.From.Name = obj.NAME_TOCREF
366		p.From.Sym = symtoc
367		p.To.Type = obj.TYPE_REG
368		p.To.Reg = REG_R12
369		p.To.Name = obj.NAME_NONE
370		p.To.Offset = 0
371		p.To.Sym = nil
372		p1 := obj.Appendp(p, c.newprog)
373		p1.As = AADD
374		p1.From.Type = obj.TYPE_CONST
375		p1.From.Offset = offset
376		p1.To.Type = obj.TYPE_REG
377		p1.To.Reg = REG_R12
378		p2 := obj.Appendp(p1, c.newprog)
379		p2.As = AMOVD
380		p2.From.Type = obj.TYPE_REG
381		p2.From.Reg = REG_R12
382		p2.To.Type = obj.TYPE_REG
383		p2.To.Reg = REG_LR
384		p3 := obj.Appendp(p2, c.newprog)
385		p3.As = obj.ACALL
386		p3.To.Type = obj.TYPE_REG
387		p3.To.Reg = REG_LR
388	}
389
390	var source *obj.Addr
391	if p.From.Name == obj.NAME_EXTERN || p.From.Name == obj.NAME_STATIC {
392		if p.From.Type == obj.TYPE_ADDR {
393			if p.As == ADWORD {
394				// ADWORD $sym doesn't need TOC anchor
395				return
396			}
397			if p.As != AMOVD {
398				c.ctxt.Diag("do not know how to handle TYPE_ADDR in %v", p)
399				return
400			}
401			if p.To.Type != obj.TYPE_REG {
402				c.ctxt.Diag("do not know how to handle LEAQ-type insn to non-register in %v", p)
403				return
404			}
405		} else if p.From.Type != obj.TYPE_MEM {
406			c.ctxt.Diag("do not know how to handle %v without TYPE_MEM", p)
407			return
408		}
409		source = &p.From
410
411	} else if p.To.Name == obj.NAME_EXTERN || p.To.Name == obj.NAME_STATIC {
412		if p.To.Type != obj.TYPE_MEM {
413			c.ctxt.Diag("do not know how to handle %v without TYPE_MEM", p)
414			return
415		}
416		if source != nil {
417			c.ctxt.Diag("cannot handle symbols on both sides in %v", p)
418			return
419		}
420		source = &p.To
421	} else {
422		return
423
424	}
425
426	if source.Sym == nil {
427		c.ctxt.Diag("do not know how to handle nil symbol in %v", p)
428		return
429	}
430
431	if source.Sym.Type == objabi.STLSBSS {
432		return
433	}
434
435	// Retrieve or create the TOC anchor.
436	symtoc := c.ctxt.LookupInit("TOC."+source.Sym.Name, func(s *obj.LSym) {
437		s.Type = objabi.SDATA
438		s.Set(obj.AttrDuplicateOK, true)
439		s.Set(obj.AttrStatic, true)
440		c.ctxt.Data = append(c.ctxt.Data, s)
441		s.WriteAddr(c.ctxt, 0, 8, source.Sym, 0)
442	})
443
444	if source.Type == obj.TYPE_ADDR {
445		// MOVD $sym, Rx becomes MOVD symtoc, Rx
446		// MOVD $sym+<off>, Rx becomes MOVD symtoc, Rx; ADD <off>, Rx
447		p.From.Type = obj.TYPE_MEM
448		p.From.Sym = symtoc
449		p.From.Name = obj.NAME_TOCREF
450
451		if p.From.Offset != 0 {
452			q := obj.Appendp(p, c.newprog)
453			q.As = AADD
454			q.From.Type = obj.TYPE_CONST
455			q.From.Offset = p.From.Offset
456			p.From.Offset = 0
457			q.To = p.To
458		}
459		return
460
461	}
462
463	// MOVx sym, Ry becomes MOVD symtoc, REGTMP; MOVx (REGTMP), Ry
464	// MOVx Ry, sym becomes MOVD symtoc, REGTMP; MOVx Ry, (REGTMP)
465	// An addition may be inserted between the two MOVs if there is an offset.
466
467	q := obj.Appendp(p, c.newprog)
468	q.As = AMOVD
469	q.From.Type = obj.TYPE_MEM
470	q.From.Sym = symtoc
471	q.From.Name = obj.NAME_TOCREF
472	q.To.Type = obj.TYPE_REG
473	q.To.Reg = REGTMP
474
475	q = obj.Appendp(q, c.newprog)
476	q.As = p.As
477	q.From = p.From
478	q.To = p.To
479	if p.From.Name != obj.NAME_NONE {
480		q.From.Type = obj.TYPE_MEM
481		q.From.Reg = REGTMP
482		q.From.Name = obj.NAME_NONE
483		q.From.Sym = nil
484	} else if p.To.Name != obj.NAME_NONE {
485		q.To.Type = obj.TYPE_MEM
486		q.To.Reg = REGTMP
487		q.To.Name = obj.NAME_NONE
488		q.To.Sym = nil
489	} else {
490		c.ctxt.Diag("unreachable case in rewriteToUseTOC with %v", p)
491	}
492
493	obj.Nopout(p)
494}
495
496// Rewrite p, if necessary, to access global data via the global offset table.
497func (c *ctxt9) rewriteToUseGot(p *obj.Prog) {
498	if p.As == obj.ADUFFCOPY || p.As == obj.ADUFFZERO {
499		//     ADUFFxxx $offset
500		// becomes
501		//     MOVD runtime.duffxxx@GOT, R12
502		//     ADD $offset, R12
503		//     MOVD R12, LR
504		//     BL (LR)
505		var sym *obj.LSym
506		if p.As == obj.ADUFFZERO {
507			sym = c.ctxt.LookupABI("runtime.duffzero", obj.ABIInternal)
508		} else {
509			sym = c.ctxt.LookupABI("runtime.duffcopy", obj.ABIInternal)
510		}
511		offset := p.To.Offset
512		p.As = AMOVD
513		p.From.Type = obj.TYPE_MEM
514		p.From.Name = obj.NAME_GOTREF
515		p.From.Sym = sym
516		p.To.Type = obj.TYPE_REG
517		p.To.Reg = REG_R12
518		p.To.Name = obj.NAME_NONE
519		p.To.Offset = 0
520		p.To.Sym = nil
521		p1 := obj.Appendp(p, c.newprog)
522		p1.As = AADD
523		p1.From.Type = obj.TYPE_CONST
524		p1.From.Offset = offset
525		p1.To.Type = obj.TYPE_REG
526		p1.To.Reg = REG_R12
527		p2 := obj.Appendp(p1, c.newprog)
528		p2.As = AMOVD
529		p2.From.Type = obj.TYPE_REG
530		p2.From.Reg = REG_R12
531		p2.To.Type = obj.TYPE_REG
532		p2.To.Reg = REG_LR
533		p3 := obj.Appendp(p2, c.newprog)
534		p3.As = obj.ACALL
535		p3.To.Type = obj.TYPE_REG
536		p3.To.Reg = REG_LR
537	}
538
539	// We only care about global data: NAME_EXTERN means a global
540	// symbol in the Go sense, and p.Sym.Local is true for a few
541	// internally defined symbols.
542	if p.From.Type == obj.TYPE_ADDR && p.From.Name == obj.NAME_EXTERN && !p.From.Sym.Local() {
543		// MOVD $sym, Rx becomes MOVD sym@GOT, Rx
544		// MOVD $sym+<off>, Rx becomes MOVD sym@GOT, Rx; ADD <off>, Rx
545		if p.As != AMOVD {
546			c.ctxt.Diag("do not know how to handle TYPE_ADDR in %v with -dynlink", p)
547		}
548		if p.To.Type != obj.TYPE_REG {
549			c.ctxt.Diag("do not know how to handle LEAQ-type insn to non-register in %v with -dynlink", p)
550		}
551		p.From.Type = obj.TYPE_MEM
552		p.From.Name = obj.NAME_GOTREF
553		if p.From.Offset != 0 {
554			q := obj.Appendp(p, c.newprog)
555			q.As = AADD
556			q.From.Type = obj.TYPE_CONST
557			q.From.Offset = p.From.Offset
558			q.To = p.To
559			p.From.Offset = 0
560		}
561	}
562	if p.GetFrom3() != nil && p.GetFrom3().Name == obj.NAME_EXTERN {
563		c.ctxt.Diag("don't know how to handle %v with -dynlink", p)
564	}
565	var source *obj.Addr
566	// MOVx sym, Ry becomes MOVD sym@GOT, REGTMP; MOVx (REGTMP), Ry
567	// MOVx Ry, sym becomes MOVD sym@GOT, REGTMP; MOVx Ry, (REGTMP)
568	// An addition may be inserted between the two MOVs if there is an offset.
569	if p.From.Name == obj.NAME_EXTERN && !p.From.Sym.Local() {
570		if p.To.Name == obj.NAME_EXTERN && !p.To.Sym.Local() {
571			c.ctxt.Diag("cannot handle NAME_EXTERN on both sides in %v with -dynlink", p)
572		}
573		source = &p.From
574	} else if p.To.Name == obj.NAME_EXTERN && !p.To.Sym.Local() {
575		source = &p.To
576	} else {
577		return
578	}
579	if p.As == obj.ATEXT || p.As == obj.AFUNCDATA || p.As == obj.ACALL || p.As == obj.ARET || p.As == obj.AJMP {
580		return
581	}
582	if source.Sym.Type == objabi.STLSBSS {
583		return
584	}
585	if source.Type != obj.TYPE_MEM {
586		c.ctxt.Diag("don't know how to handle %v with -dynlink", p)
587	}
588	p1 := obj.Appendp(p, c.newprog)
589	p2 := obj.Appendp(p1, c.newprog)
590
591	p1.As = AMOVD
592	p1.From.Type = obj.TYPE_MEM
593	p1.From.Sym = source.Sym
594	p1.From.Name = obj.NAME_GOTREF
595	p1.To.Type = obj.TYPE_REG
596	p1.To.Reg = REGTMP
597
598	p2.As = p.As
599	p2.From = p.From
600	p2.To = p.To
601	if p.From.Name == obj.NAME_EXTERN {
602		p2.From.Reg = REGTMP
603		p2.From.Name = obj.NAME_NONE
604		p2.From.Sym = nil
605	} else if p.To.Name == obj.NAME_EXTERN {
606		p2.To.Reg = REGTMP
607		p2.To.Name = obj.NAME_NONE
608		p2.To.Sym = nil
609	} else {
610		return
611	}
612	obj.Nopout(p)
613}
614
615func preprocess(ctxt *obj.Link, cursym *obj.LSym, newprog obj.ProgAlloc) {
616	// TODO(minux): add morestack short-cuts with small fixed frame-size.
617	if cursym.Func().Text == nil || cursym.Func().Text.Link == nil {
618		return
619	}
620
621	c := ctxt9{ctxt: ctxt, cursym: cursym, newprog: newprog}
622
623	p := c.cursym.Func().Text
624	textstksiz := p.To.Offset
625	if textstksiz == -8 {
626		// Compatibility hack.
627		p.From.Sym.Set(obj.AttrNoFrame, true)
628		textstksiz = 0
629	}
630	if textstksiz%8 != 0 {
631		c.ctxt.Diag("frame size %d not a multiple of 8", textstksiz)
632	}
633	if p.From.Sym.NoFrame() {
634		if textstksiz != 0 {
635			c.ctxt.Diag("NOFRAME functions must have a frame size of 0, not %d", textstksiz)
636		}
637	}
638
639	c.cursym.Func().Args = p.To.Val.(int32)
640	c.cursym.Func().Locals = int32(textstksiz)
641
642	/*
643	 * find leaf subroutines
644	 * expand RET
645	 * expand BECOME pseudo
646	 */
647
648	var q *obj.Prog
649	var q1 *obj.Prog
650	for p := c.cursym.Func().Text; p != nil; p = p.Link {
651		switch p.As {
652		/* too hard, just leave alone */
653		case obj.ATEXT:
654			q = p
655
656			p.Mark |= LABEL | LEAF | SYNC
657			if p.Link != nil {
658				p.Link.Mark |= LABEL
659			}
660
661		case ANOR:
662			q = p
663			if p.To.Type == obj.TYPE_REG {
664				if p.To.Reg == REGZERO {
665					p.Mark |= LABEL | SYNC
666				}
667			}
668
669		case ALWAR,
670			ALBAR,
671			ASTBCCC,
672			ASTWCCC,
673			AEIEIO,
674			AICBI,
675			AISYNC,
676			ATLBIE,
677			ATLBIEL,
678			ASLBIA,
679			ASLBIE,
680			ASLBMFEE,
681			ASLBMFEV,
682			ASLBMTE,
683			ADCBF,
684			ADCBI,
685			ADCBST,
686			ADCBT,
687			ADCBTST,
688			ADCBZ,
689			ASYNC,
690			ATLBSYNC,
691			APTESYNC,
692			ALWSYNC,
693			ATW,
694			AWORD,
695			ARFI,
696			ARFCI,
697			ARFID,
698			AHRFID:
699			q = p
700			p.Mark |= LABEL | SYNC
701			continue
702
703		case AMOVW, AMOVWZ, AMOVD:
704			q = p
705			if p.From.Reg >= REG_SPECIAL || p.To.Reg >= REG_SPECIAL {
706				p.Mark |= LABEL | SYNC
707			}
708			continue
709
710		case AFABS,
711			AFABSCC,
712			AFADD,
713			AFADDCC,
714			AFCTIW,
715			AFCTIWCC,
716			AFCTIWZ,
717			AFCTIWZCC,
718			AFDIV,
719			AFDIVCC,
720			AFMADD,
721			AFMADDCC,
722			AFMOVD,
723			AFMOVDU,
724			/* case AFMOVDS: */
725			AFMOVS,
726			AFMOVSU,
727
728			/* case AFMOVSD: */
729			AFMSUB,
730			AFMSUBCC,
731			AFMUL,
732			AFMULCC,
733			AFNABS,
734			AFNABSCC,
735			AFNEG,
736			AFNEGCC,
737			AFNMADD,
738			AFNMADDCC,
739			AFNMSUB,
740			AFNMSUBCC,
741			AFRSP,
742			AFRSPCC,
743			AFSUB,
744			AFSUBCC:
745			q = p
746
747			p.Mark |= FLOAT
748			continue
749
750		case ABL,
751			ABCL,
752			obj.ADUFFZERO,
753			obj.ADUFFCOPY:
754			c.cursym.Func().Text.Mark &^= LEAF
755			fallthrough
756
757		case ABC,
758			ABEQ,
759			ABGE,
760			ABGT,
761			ABLE,
762			ABLT,
763			ABNE,
764			ABR,
765			ABVC,
766			ABVS:
767			p.Mark |= BRANCH
768			q = p
769			q1 = p.To.Target()
770			if q1 != nil {
771				// NOPs are not removed due to #40689.
772
773				if q1.Mark&LEAF == 0 {
774					q1.Mark |= LABEL
775				}
776			} else {
777				p.Mark |= LABEL
778			}
779			q1 = p.Link
780			if q1 != nil {
781				q1.Mark |= LABEL
782			}
783			continue
784
785		case AFCMPO, AFCMPU:
786			q = p
787			p.Mark |= FCMP | FLOAT
788			continue
789
790		case obj.ARET:
791			q = p
792			if p.Link != nil {
793				p.Link.Mark |= LABEL
794			}
795			continue
796
797		case obj.ANOP:
798			// NOPs are not removed due to
799			// #40689
800			continue
801
802		default:
803			q = p
804			continue
805		}
806	}
807
808	autosize := int32(0)
809	var p1 *obj.Prog
810	var p2 *obj.Prog
811	for p := c.cursym.Func().Text; p != nil; p = p.Link {
812		o := p.As
813		switch o {
814		case obj.ATEXT:
815			autosize = int32(textstksiz)
816
817			if p.Mark&LEAF != 0 && autosize == 0 {
818				// A leaf function with no locals has no frame.
819				p.From.Sym.Set(obj.AttrNoFrame, true)
820			}
821
822			if !p.From.Sym.NoFrame() {
823				// If there is a stack frame at all, it includes
824				// space to save the LR.
825				autosize += int32(c.ctxt.Arch.FixedFrameSize)
826			}
827
828			if p.Mark&LEAF != 0 && autosize < abi.StackSmall {
829				// A leaf function with a small stack can be marked
830				// NOSPLIT, avoiding a stack check.
831				p.From.Sym.Set(obj.AttrNoSplit, true)
832			}
833
834			p.To.Offset = int64(autosize)
835
836			q = p
837
838			if NeedTOCpointer(c.ctxt) && !isNOTOCfunc(c.cursym.Name) {
839				// When compiling Go into PIC, without PCrel support, all functions must start
840				// with instructions to load the TOC pointer into r2:
841				//
842				//	addis r2, r12, .TOC.-func@ha
843				//	addi r2, r2, .TOC.-func@l+4
844				//
845				// We could probably skip this prologue in some situations
846				// but it's a bit subtle. However, it is both safe and
847				// necessary to leave the prologue off duffzero and
848				// duffcopy as we rely on being able to jump to a specific
849				// instruction offset for them.
850				//
851				// These are AWORDS because there is no (afaict) way to
852				// generate the addis instruction except as part of the
853				// load of a large constant, and in that case there is no
854				// way to use r12 as the source.
855				//
856				// Note that the same condition is tested in
857				// putelfsym in cmd/link/internal/ld/symtab.go
858				// where we set the st_other field to indicate
859				// the presence of these instructions.
860				q = obj.Appendp(q, c.newprog)
861				q.As = AWORD
862				q.Pos = p.Pos
863				q.From.Type = obj.TYPE_CONST
864				q.From.Offset = 0x3c4c0000
865				q = obj.Appendp(q, c.newprog)
866				q.As = AWORD
867				q.Pos = p.Pos
868				q.From.Type = obj.TYPE_CONST
869				q.From.Offset = 0x38420000
870				rel := obj.Addrel(c.cursym)
871				rel.Off = 0
872				rel.Siz = 8
873				rel.Sym = c.ctxt.Lookup(".TOC.")
874				rel.Type = objabi.R_ADDRPOWER_PCREL
875			}
876
877			if !c.cursym.Func().Text.From.Sym.NoSplit() {
878				q = c.stacksplit(q, autosize) // emit split check
879			}
880
881			if autosize != 0 {
882				var prologueEnd *obj.Prog
883				// Save the link register and update the SP.  MOVDU is used unless
884				// the frame size is too large.  The link register must be saved
885				// even for non-empty leaf functions so that traceback works.
886				if autosize >= -BIG && autosize <= BIG {
887					// Use MOVDU to adjust R1 when saving R31, if autosize is small.
888					q = obj.Appendp(q, c.newprog)
889					q.As = AMOVD
890					q.Pos = p.Pos
891					q.From.Type = obj.TYPE_REG
892					q.From.Reg = REG_LR
893					q.To.Type = obj.TYPE_REG
894					q.To.Reg = REGTMP
895					prologueEnd = q
896
897					q = obj.Appendp(q, c.newprog)
898					q.As = AMOVDU
899					q.Pos = p.Pos
900					q.From.Type = obj.TYPE_REG
901					q.From.Reg = REGTMP
902					q.To.Type = obj.TYPE_MEM
903					q.To.Offset = int64(-autosize)
904					q.To.Reg = REGSP
905					q.Spadj = autosize
906				} else {
907					// Frame size is too large for a MOVDU instruction.
908					// Store link register before decrementing SP, so if a signal comes
909					// during the execution of the function prologue, the traceback
910					// code will not see a half-updated stack frame.
911					// This sequence is not async preemptible, as if we open a frame
912					// at the current SP, it will clobber the saved LR.
913					q = obj.Appendp(q, c.newprog)
914					q.As = AMOVD
915					q.Pos = p.Pos
916					q.From.Type = obj.TYPE_REG
917					q.From.Reg = REG_LR
918					q.To.Type = obj.TYPE_REG
919					q.To.Reg = REG_R29 // REGTMP may be used to synthesize large offset in the next instruction
920
921					q = c.ctxt.StartUnsafePoint(q, c.newprog)
922
923					q = obj.Appendp(q, c.newprog)
924					q.As = AMOVD
925					q.Pos = p.Pos
926					q.From.Type = obj.TYPE_REG
927					q.From.Reg = REG_R29
928					q.To.Type = obj.TYPE_MEM
929					q.To.Offset = int64(-autosize)
930					q.To.Reg = REGSP
931
932					prologueEnd = q
933
934					q = obj.Appendp(q, c.newprog)
935					q.As = AADD
936					q.Pos = p.Pos
937					q.From.Type = obj.TYPE_CONST
938					q.From.Offset = int64(-autosize)
939					q.To.Type = obj.TYPE_REG
940					q.To.Reg = REGSP
941					q.Spadj = +autosize
942
943					q = c.ctxt.EndUnsafePoint(q, c.newprog, -1)
944				}
945				prologueEnd.Pos = prologueEnd.Pos.WithXlogue(src.PosPrologueEnd)
946			} else if c.cursym.Func().Text.Mark&LEAF == 0 {
947				// A very few functions that do not return to their caller
948				// (e.g. gogo) are not identified as leaves but still have
949				// no frame.
950				c.cursym.Func().Text.Mark |= LEAF
951			}
952
953			if c.cursym.Func().Text.Mark&LEAF != 0 {
954				c.cursym.Set(obj.AttrLeaf, true)
955				break
956			}
957
958			if NeedTOCpointer(c.ctxt) {
959				q = obj.Appendp(q, c.newprog)
960				q.As = AMOVD
961				q.Pos = p.Pos
962				q.From.Type = obj.TYPE_REG
963				q.From.Reg = REG_R2
964				q.To.Type = obj.TYPE_MEM
965				q.To.Reg = REGSP
966				q.To.Offset = 24
967			}
968
969			if c.cursym.Func().Text.From.Sym.Wrapper() {
970				// if(g->panic != nil && g->panic->argp == FP) g->panic->argp = bottom-of-frame
971				//
972				//	MOVD g_panic(g), R22
973				//	CMP R22, $0
974				//	BEQ end
975				//	MOVD panic_argp(R22), R23
976				//	ADD $(autosize+8), R1, R24
977				//	CMP R23, R24
978				//	BNE end
979				//	ADD $8, R1, R25
980				//	MOVD R25, panic_argp(R22)
981				// end:
982				//	NOP
983				//
984				// The NOP is needed to give the jumps somewhere to land.
985				// It is a liblink NOP, not a ppc64 NOP: it encodes to 0 instruction bytes.
986
987				q = obj.Appendp(q, c.newprog)
988
989				q.As = AMOVD
990				q.From.Type = obj.TYPE_MEM
991				q.From.Reg = REGG
992				q.From.Offset = 4 * int64(c.ctxt.Arch.PtrSize) // G.panic
993				q.To.Type = obj.TYPE_REG
994				q.To.Reg = REG_R22
995
996				q = obj.Appendp(q, c.newprog)
997				q.As = ACMP
998				q.From.Type = obj.TYPE_REG
999				q.From.Reg = REG_R22
1000				q.To.Type = obj.TYPE_CONST
1001				q.To.Offset = 0
1002
1003				q = obj.Appendp(q, c.newprog)
1004				q.As = ABEQ
1005				q.To.Type = obj.TYPE_BRANCH
1006				p1 = q
1007
1008				q = obj.Appendp(q, c.newprog)
1009				q.As = AMOVD
1010				q.From.Type = obj.TYPE_MEM
1011				q.From.Reg = REG_R22
1012				q.From.Offset = 0 // Panic.argp
1013				q.To.Type = obj.TYPE_REG
1014				q.To.Reg = REG_R23
1015
1016				q = obj.Appendp(q, c.newprog)
1017				q.As = AADD
1018				q.From.Type = obj.TYPE_CONST
1019				q.From.Offset = int64(autosize) + c.ctxt.Arch.FixedFrameSize
1020				q.Reg = REGSP
1021				q.To.Type = obj.TYPE_REG
1022				q.To.Reg = REG_R24
1023
1024				q = obj.Appendp(q, c.newprog)
1025				q.As = ACMP
1026				q.From.Type = obj.TYPE_REG
1027				q.From.Reg = REG_R23
1028				q.To.Type = obj.TYPE_REG
1029				q.To.Reg = REG_R24
1030
1031				q = obj.Appendp(q, c.newprog)
1032				q.As = ABNE
1033				q.To.Type = obj.TYPE_BRANCH
1034				p2 = q
1035
1036				q = obj.Appendp(q, c.newprog)
1037				q.As = AADD
1038				q.From.Type = obj.TYPE_CONST
1039				q.From.Offset = c.ctxt.Arch.FixedFrameSize
1040				q.Reg = REGSP
1041				q.To.Type = obj.TYPE_REG
1042				q.To.Reg = REG_R25
1043
1044				q = obj.Appendp(q, c.newprog)
1045				q.As = AMOVD
1046				q.From.Type = obj.TYPE_REG
1047				q.From.Reg = REG_R25
1048				q.To.Type = obj.TYPE_MEM
1049				q.To.Reg = REG_R22
1050				q.To.Offset = 0 // Panic.argp
1051
1052				q = obj.Appendp(q, c.newprog)
1053
1054				q.As = obj.ANOP
1055				p1.To.SetTarget(q)
1056				p2.To.SetTarget(q)
1057			}
1058
1059		case obj.ARET:
1060			if p.From.Type == obj.TYPE_CONST {
1061				c.ctxt.Diag("using BECOME (%v) is not supported!", p)
1062				break
1063			}
1064
1065			retTarget := p.To.Sym
1066
1067			if c.cursym.Func().Text.Mark&LEAF != 0 {
1068				if autosize == 0 {
1069					p.As = ABR
1070					p.From = obj.Addr{}
1071					if retTarget == nil {
1072						p.To.Type = obj.TYPE_REG
1073						p.To.Reg = REG_LR
1074					} else {
1075						p.To.Type = obj.TYPE_BRANCH
1076						p.To.Sym = retTarget
1077					}
1078					p.Mark |= BRANCH
1079					break
1080				}
1081
1082				p.As = AADD
1083				p.From.Type = obj.TYPE_CONST
1084				p.From.Offset = int64(autosize)
1085				p.To.Type = obj.TYPE_REG
1086				p.To.Reg = REGSP
1087				p.Spadj = -autosize
1088
1089				q = c.newprog()
1090				q.As = ABR
1091				q.Pos = p.Pos
1092				if retTarget == nil {
1093					q.To.Type = obj.TYPE_REG
1094					q.To.Reg = REG_LR
1095				} else {
1096					q.To.Type = obj.TYPE_BRANCH
1097					q.To.Sym = retTarget
1098				}
1099				q.Mark |= BRANCH
1100				q.Spadj = +autosize
1101
1102				q.Link = p.Link
1103				p.Link = q
1104				break
1105			}
1106
1107			p.As = AMOVD
1108			p.From.Type = obj.TYPE_MEM
1109			p.From.Offset = 0
1110			p.From.Reg = REGSP
1111			p.To.Type = obj.TYPE_REG
1112			p.To.Reg = REGTMP
1113
1114			q = c.newprog()
1115			q.As = AMOVD
1116			q.Pos = p.Pos
1117			q.From.Type = obj.TYPE_REG
1118			q.From.Reg = REGTMP
1119			q.To.Type = obj.TYPE_REG
1120			q.To.Reg = REG_LR
1121
1122			q.Link = p.Link
1123			p.Link = q
1124			p = q
1125
1126			if false {
1127				// Debug bad returns
1128				q = c.newprog()
1129
1130				q.As = AMOVD
1131				q.Pos = p.Pos
1132				q.From.Type = obj.TYPE_MEM
1133				q.From.Offset = 0
1134				q.From.Reg = REGTMP
1135				q.To.Type = obj.TYPE_REG
1136				q.To.Reg = REGTMP
1137
1138				q.Link = p.Link
1139				p.Link = q
1140				p = q
1141			}
1142			prev := p
1143			if autosize != 0 {
1144				q = c.newprog()
1145				q.As = AADD
1146				q.Pos = p.Pos
1147				q.From.Type = obj.TYPE_CONST
1148				q.From.Offset = int64(autosize)
1149				q.To.Type = obj.TYPE_REG
1150				q.To.Reg = REGSP
1151				q.Spadj = -autosize
1152
1153				q.Link = p.Link
1154				prev.Link = q
1155				prev = q
1156			}
1157
1158			q1 = c.newprog()
1159			q1.As = ABR
1160			q1.Pos = p.Pos
1161			if retTarget == nil {
1162				q1.To.Type = obj.TYPE_REG
1163				q1.To.Reg = REG_LR
1164			} else {
1165				q1.To.Type = obj.TYPE_BRANCH
1166				q1.To.Sym = retTarget
1167			}
1168			q1.Mark |= BRANCH
1169			q1.Spadj = +autosize
1170
1171			q1.Link = q.Link
1172			prev.Link = q1
1173		case AADD:
1174			if p.To.Type == obj.TYPE_REG && p.To.Reg == REGSP && p.From.Type == obj.TYPE_CONST {
1175				p.Spadj = int32(-p.From.Offset)
1176			}
1177		case AMOVDU:
1178			if p.To.Type == obj.TYPE_MEM && p.To.Reg == REGSP {
1179				p.Spadj = int32(-p.To.Offset)
1180			}
1181			if p.From.Type == obj.TYPE_MEM && p.From.Reg == REGSP {
1182				p.Spadj = int32(-p.From.Offset)
1183			}
1184		case obj.AGETCALLERPC:
1185			if cursym.Leaf() {
1186				/* MOVD LR, Rd */
1187				p.As = AMOVD
1188				p.From.Type = obj.TYPE_REG
1189				p.From.Reg = REG_LR
1190			} else {
1191				/* MOVD (RSP), Rd */
1192				p.As = AMOVD
1193				p.From.Type = obj.TYPE_MEM
1194				p.From.Reg = REGSP
1195			}
1196		}
1197
1198		if p.To.Type == obj.TYPE_REG && p.To.Reg == REGSP && p.Spadj == 0 && p.As != ACMPU {
1199			f := c.cursym.Func()
1200			if f.FuncFlag&abi.FuncFlagSPWrite == 0 {
1201				c.cursym.Func().FuncFlag |= abi.FuncFlagSPWrite
1202				if ctxt.Debugvlog || !ctxt.IsAsm {
1203					ctxt.Logf("auto-SPWRITE: %s %v\n", c.cursym.Name, p)
1204					if !ctxt.IsAsm {
1205						ctxt.Diag("invalid auto-SPWRITE in non-assembly")
1206						ctxt.DiagFlush()
1207						log.Fatalf("bad SPWRITE")
1208					}
1209				}
1210			}
1211		}
1212	}
1213}
1214
1215/*
1216// instruction scheduling
1217
1218	if(debug['Q'] == 0)
1219		return;
1220
1221	curtext = nil;
1222	q = nil;	// p - 1
1223	q1 = firstp;	// top of block
1224	o = 0;		// count of instructions
1225	for(p = firstp; p != nil; p = p1) {
1226		p1 = p->link;
1227		o++;
1228		if(p->mark & NOSCHED){
1229			if(q1 != p){
1230				sched(q1, q);
1231			}
1232			for(; p != nil; p = p->link){
1233				if(!(p->mark & NOSCHED))
1234					break;
1235				q = p;
1236			}
1237			p1 = p;
1238			q1 = p;
1239			o = 0;
1240			continue;
1241		}
1242		if(p->mark & (LABEL|SYNC)) {
1243			if(q1 != p)
1244				sched(q1, q);
1245			q1 = p;
1246			o = 1;
1247		}
1248		if(p->mark & (BRANCH|SYNC)) {
1249			sched(q1, p);
1250			q1 = p1;
1251			o = 0;
1252		}
1253		if(o >= NSCHED) {
1254			sched(q1, p);
1255			q1 = p1;
1256			o = 0;
1257		}
1258		q = p;
1259	}
1260*/
1261func (c *ctxt9) stacksplit(p *obj.Prog, framesize int32) *obj.Prog {
1262	if c.ctxt.Flag_maymorestack != "" {
1263		if c.ctxt.Flag_shared || c.ctxt.Flag_dynlink {
1264			// See the call to morestack for why these are
1265			// complicated to support.
1266			c.ctxt.Diag("maymorestack with -shared or -dynlink is not supported")
1267		}
1268
1269		// Spill arguments. This has to happen before we open
1270		// any more frame space.
1271		p = c.cursym.Func().SpillRegisterArgs(p, c.newprog)
1272
1273		// Save LR and REGCTXT
1274		frameSize := 8 + c.ctxt.Arch.FixedFrameSize
1275
1276		// MOVD LR, REGTMP
1277		p = obj.Appendp(p, c.newprog)
1278		p.As = AMOVD
1279		p.From.Type = obj.TYPE_REG
1280		p.From.Reg = REG_LR
1281		p.To.Type = obj.TYPE_REG
1282		p.To.Reg = REGTMP
1283		// MOVDU REGTMP, -16(SP)
1284		p = obj.Appendp(p, c.newprog)
1285		p.As = AMOVDU
1286		p.From.Type = obj.TYPE_REG
1287		p.From.Reg = REGTMP
1288		p.To.Type = obj.TYPE_MEM
1289		p.To.Offset = -frameSize
1290		p.To.Reg = REGSP
1291		p.Spadj = int32(frameSize)
1292
1293		// MOVD REGCTXT, 8(SP)
1294		p = obj.Appendp(p, c.newprog)
1295		p.As = AMOVD
1296		p.From.Type = obj.TYPE_REG
1297		p.From.Reg = REGCTXT
1298		p.To.Type = obj.TYPE_MEM
1299		p.To.Offset = 8
1300		p.To.Reg = REGSP
1301
1302		// BL maymorestack
1303		p = obj.Appendp(p, c.newprog)
1304		p.As = ABL
1305		p.To.Type = obj.TYPE_BRANCH
1306		// See ../x86/obj6.go
1307		p.To.Sym = c.ctxt.LookupABI(c.ctxt.Flag_maymorestack, c.cursym.ABI())
1308
1309		// Restore LR and REGCTXT
1310
1311		// MOVD 8(SP), REGCTXT
1312		p = obj.Appendp(p, c.newprog)
1313		p.As = AMOVD
1314		p.From.Type = obj.TYPE_MEM
1315		p.From.Offset = 8
1316		p.From.Reg = REGSP
1317		p.To.Type = obj.TYPE_REG
1318		p.To.Reg = REGCTXT
1319
1320		// MOVD 0(SP), REGTMP
1321		p = obj.Appendp(p, c.newprog)
1322		p.As = AMOVD
1323		p.From.Type = obj.TYPE_MEM
1324		p.From.Offset = 0
1325		p.From.Reg = REGSP
1326		p.To.Type = obj.TYPE_REG
1327		p.To.Reg = REGTMP
1328
1329		// MOVD REGTMP, LR
1330		p = obj.Appendp(p, c.newprog)
1331		p.As = AMOVD
1332		p.From.Type = obj.TYPE_REG
1333		p.From.Reg = REGTMP
1334		p.To.Type = obj.TYPE_REG
1335		p.To.Reg = REG_LR
1336
1337		// ADD $16, SP
1338		p = obj.Appendp(p, c.newprog)
1339		p.As = AADD
1340		p.From.Type = obj.TYPE_CONST
1341		p.From.Offset = frameSize
1342		p.To.Type = obj.TYPE_REG
1343		p.To.Reg = REGSP
1344		p.Spadj = -int32(frameSize)
1345
1346		// Unspill arguments.
1347		p = c.cursym.Func().UnspillRegisterArgs(p, c.newprog)
1348	}
1349
1350	// save entry point, but skipping the two instructions setting R2 in shared mode and maymorestack
1351	startPred := p
1352
1353	// MOVD	g_stackguard(g), R22
1354	p = obj.Appendp(p, c.newprog)
1355
1356	p.As = AMOVD
1357	p.From.Type = obj.TYPE_MEM
1358	p.From.Reg = REGG
1359	p.From.Offset = 2 * int64(c.ctxt.Arch.PtrSize) // G.stackguard0
1360	if c.cursym.CFunc() {
1361		p.From.Offset = 3 * int64(c.ctxt.Arch.PtrSize) // G.stackguard1
1362	}
1363	p.To.Type = obj.TYPE_REG
1364	p.To.Reg = REG_R22
1365
1366	// Mark the stack bound check and morestack call async nonpreemptible.
1367	// If we get preempted here, when resumed the preemption request is
1368	// cleared, but we'll still call morestack, which will double the stack
1369	// unnecessarily. See issue #35470.
1370	p = c.ctxt.StartUnsafePoint(p, c.newprog)
1371
1372	var q *obj.Prog
1373	if framesize <= abi.StackSmall {
1374		// small stack: SP < stackguard
1375		//	CMP	stackguard, SP
1376		p = obj.Appendp(p, c.newprog)
1377
1378		p.As = ACMPU
1379		p.From.Type = obj.TYPE_REG
1380		p.From.Reg = REG_R22
1381		p.To.Type = obj.TYPE_REG
1382		p.To.Reg = REGSP
1383	} else {
1384		// large stack: SP-framesize < stackguard-StackSmall
1385		offset := int64(framesize) - abi.StackSmall
1386		if framesize > abi.StackBig {
1387			// Such a large stack we need to protect against underflow.
1388			// The runtime guarantees SP > objabi.StackBig, but
1389			// framesize is large enough that SP-framesize may
1390			// underflow, causing a direct comparison with the
1391			// stack guard to incorrectly succeed. We explicitly
1392			// guard against underflow.
1393			//
1394			//	CMPU	SP, $(framesize-StackSmall)
1395			//	BLT	label-of-call-to-morestack
1396			if offset <= 0xffff {
1397				p = obj.Appendp(p, c.newprog)
1398				p.As = ACMPU
1399				p.From.Type = obj.TYPE_REG
1400				p.From.Reg = REGSP
1401				p.To.Type = obj.TYPE_CONST
1402				p.To.Offset = offset
1403			} else {
1404				// Constant is too big for CMPU.
1405				p = obj.Appendp(p, c.newprog)
1406				p.As = AMOVD
1407				p.From.Type = obj.TYPE_CONST
1408				p.From.Offset = offset
1409				p.To.Type = obj.TYPE_REG
1410				p.To.Reg = REG_R23
1411
1412				p = obj.Appendp(p, c.newprog)
1413				p.As = ACMPU
1414				p.From.Type = obj.TYPE_REG
1415				p.From.Reg = REGSP
1416				p.To.Type = obj.TYPE_REG
1417				p.To.Reg = REG_R23
1418			}
1419
1420			p = obj.Appendp(p, c.newprog)
1421			q = p
1422			p.As = ABLT
1423			p.To.Type = obj.TYPE_BRANCH
1424		}
1425
1426		// Check against the stack guard. We've ensured this won't underflow.
1427		//	ADD  $-(framesize-StackSmall), SP, R4
1428		//	CMPU stackguard, R4
1429		p = obj.Appendp(p, c.newprog)
1430
1431		p.As = AADD
1432		p.From.Type = obj.TYPE_CONST
1433		p.From.Offset = -offset
1434		p.Reg = REGSP
1435		p.To.Type = obj.TYPE_REG
1436		p.To.Reg = REG_R23
1437
1438		p = obj.Appendp(p, c.newprog)
1439		p.As = ACMPU
1440		p.From.Type = obj.TYPE_REG
1441		p.From.Reg = REG_R22
1442		p.To.Type = obj.TYPE_REG
1443		p.To.Reg = REG_R23
1444	}
1445
1446	// q1: BLT	done
1447	p = obj.Appendp(p, c.newprog)
1448	q1 := p
1449
1450	p.As = ABLT
1451	p.To.Type = obj.TYPE_BRANCH
1452
1453	p = obj.Appendp(p, c.newprog)
1454	p.As = obj.ANOP // zero-width place holder
1455
1456	if q != nil {
1457		q.To.SetTarget(p)
1458	}
1459
1460	// Spill the register args that could be clobbered by the
1461	// morestack code.
1462
1463	spill := c.cursym.Func().SpillRegisterArgs(p, c.newprog)
1464
1465	// MOVD LR, R5
1466	p = obj.Appendp(spill, c.newprog)
1467	p.As = AMOVD
1468	p.From.Type = obj.TYPE_REG
1469	p.From.Reg = REG_LR
1470	p.To.Type = obj.TYPE_REG
1471	p.To.Reg = REG_R5
1472
1473	p = c.ctxt.EmitEntryStackMap(c.cursym, p, c.newprog)
1474
1475	var morestacksym *obj.LSym
1476	if c.cursym.CFunc() {
1477		morestacksym = c.ctxt.Lookup("runtime.morestackc")
1478	} else if !c.cursym.Func().Text.From.Sym.NeedCtxt() {
1479		morestacksym = c.ctxt.Lookup("runtime.morestack_noctxt")
1480	} else {
1481		morestacksym = c.ctxt.Lookup("runtime.morestack")
1482	}
1483
1484	if NeedTOCpointer(c.ctxt) {
1485		// In PPC64 PIC code, R2 is used as TOC pointer derived from R12
1486		// which is the address of function entry point when entering
1487		// the function. We need to preserve R2 across call to morestack.
1488		// Fortunately, in shared mode, 8(SP) and 16(SP) are reserved in
1489		// the caller's frame, but not used (0(SP) is caller's saved LR,
1490		// 24(SP) is caller's saved R2). Use 8(SP) to save this function's R2.
1491		// MOVD R2, 8(SP)
1492		p = obj.Appendp(p, c.newprog)
1493		p.As = AMOVD
1494		p.From.Type = obj.TYPE_REG
1495		p.From.Reg = REG_R2
1496		p.To.Type = obj.TYPE_MEM
1497		p.To.Reg = REGSP
1498		p.To.Offset = 8
1499	}
1500
1501	if c.ctxt.Flag_dynlink {
1502		// Avoid calling morestack via a PLT when dynamically linking. The
1503		// PLT stubs generated by the system linker on ppc64le when "std r2,
1504		// 24(r1)" to save the TOC pointer in their callers stack
1505		// frame. Unfortunately (and necessarily) morestack is called before
1506		// the function that calls it sets up its frame and so the PLT ends
1507		// up smashing the saved TOC pointer for its caller's caller.
1508		//
1509		// According to the ABI documentation there is a mechanism to avoid
1510		// the TOC save that the PLT stub does (put a R_PPC64_TOCSAVE
1511		// relocation on the nop after the call to morestack) but at the time
1512		// of writing it is not supported at all by gold and my attempt to
1513		// use it with ld.bfd caused an internal linker error. So this hack
1514		// seems preferable.
1515
1516		// MOVD $runtime.morestack(SB), R12
1517		p = obj.Appendp(p, c.newprog)
1518		p.As = AMOVD
1519		p.From.Type = obj.TYPE_MEM
1520		p.From.Sym = morestacksym
1521		p.From.Name = obj.NAME_GOTREF
1522		p.To.Type = obj.TYPE_REG
1523		p.To.Reg = REG_R12
1524
1525		// MOVD R12, LR
1526		p = obj.Appendp(p, c.newprog)
1527		p.As = AMOVD
1528		p.From.Type = obj.TYPE_REG
1529		p.From.Reg = REG_R12
1530		p.To.Type = obj.TYPE_REG
1531		p.To.Reg = REG_LR
1532
1533		// BL LR
1534		p = obj.Appendp(p, c.newprog)
1535		p.As = obj.ACALL
1536		p.To.Type = obj.TYPE_REG
1537		p.To.Reg = REG_LR
1538	} else {
1539		// BL	runtime.morestack(SB)
1540		p = obj.Appendp(p, c.newprog)
1541
1542		p.As = ABL
1543		p.To.Type = obj.TYPE_BRANCH
1544		p.To.Sym = morestacksym
1545	}
1546
1547	if NeedTOCpointer(c.ctxt) {
1548		// MOVD 8(SP), R2
1549		p = obj.Appendp(p, c.newprog)
1550		p.As = AMOVD
1551		p.From.Type = obj.TYPE_MEM
1552		p.From.Reg = REGSP
1553		p.From.Offset = 8
1554		p.To.Type = obj.TYPE_REG
1555		p.To.Reg = REG_R2
1556	}
1557
1558	// The instructions which unspill regs should be preemptible.
1559	p = c.ctxt.EndUnsafePoint(p, c.newprog, -1)
1560	unspill := c.cursym.Func().UnspillRegisterArgs(p, c.newprog)
1561
1562	// BR	start
1563	p = obj.Appendp(unspill, c.newprog)
1564	p.As = ABR
1565	p.To.Type = obj.TYPE_BRANCH
1566	p.To.SetTarget(startPred.Link)
1567
1568	// placeholder for q1's jump target
1569	p = obj.Appendp(p, c.newprog)
1570
1571	p.As = obj.ANOP // zero-width place holder
1572	q1.To.SetTarget(p)
1573
1574	return p
1575}
1576
1577// MMA accumulator to/from instructions are slightly ambiguous since
1578// the argument represents both source and destination, specified as
1579// an accumulator. It is treated as a unary destination to simplify
1580// the code generation in ppc64map.
1581var unaryDst = map[obj.As]bool{
1582	AXXSETACCZ: true,
1583	AXXMTACC:   true,
1584	AXXMFACC:   true,
1585}
1586
1587var Linkppc64 = obj.LinkArch{
1588	Arch:           sys.ArchPPC64,
1589	Init:           buildop,
1590	Preprocess:     preprocess,
1591	Assemble:       span9,
1592	Progedit:       progedit,
1593	UnaryDst:       unaryDst,
1594	DWARFRegisters: PPC64DWARFRegisters,
1595}
1596
1597var Linkppc64le = obj.LinkArch{
1598	Arch:           sys.ArchPPC64LE,
1599	Init:           buildop,
1600	Preprocess:     preprocess,
1601	Assemble:       span9,
1602	Progedit:       progedit,
1603	UnaryDst:       unaryDst,
1604	DWARFRegisters: PPC64DWARFRegisters,
1605}
1606