1 /* STACK.C      (c) Copyright Roger Bowler, 1999-2009                */
2 /*              ESA/390 Linkage Stack Operations                     */
3 
4 /* Interpretive Execution - (c) Copyright Jan Jaeger, 1999-2009      */
5 /* z/Architecture support - (c) Copyright Jan Jaeger, 1999-2009      */
6 
7 /*-------------------------------------------------------------------*/
8 /* This module implements the linkage stack functions of ESA/390     */
9 /* described in SA22-7201-04 ESA/390 Principles of Operation.        */
10 /* The numbers in square brackets refer to sections in the manual.   */
11 /*-------------------------------------------------------------------*/
12 
13 /*-------------------------------------------------------------------*/
14 /* Fix CR15 corruption in form_stack_entry                Jan Jaeger */
15 /* Fix nullification in form_stack_entry                  Jan Jaeger */
16 /* Fix nullification in unstack_registers                 Jan Jaeger */
17 /* Modifications for Interpretive Execution (SIE)         Jan Jaeger */
18 /* ESAME low-address protection                   v208d Roger Bowler */
19 /* ESAME linkage stack operations                 v208e Roger Bowler */
20 /* TRAP support added                                     Jan Jaeger */
21 /* Correction to stack types in ESAME mode                Jan Jaeger */
22 /* ASN-and-LX-reuse facility                  June 2004 Roger Bowler */
23 /*-------------------------------------------------------------------*/
24 
25 
26 #include "hstdinc.h"
27 
28 // #define  STACK_DEBUG
29 
30 #if !defined(_HENGINE_DLL_)
31 #define _HENGINE_DLL_
32 #endif
33 
34 #if !defined(_STACK_C_)
35 #define _STACK_C_
36 #endif
37 
38 #include "hercules.h"
39 
40 #include "opcode.h"
41 
42 #include "inline.h"
43 
44 /*-------------------------------------------------------------------*/
45 /* Linkage stack macro definitions                                   */
46 /*-------------------------------------------------------------------*/
47 #undef  CR15_LSEA
48 #undef  LSEA_WRAP
49 #undef  LSSE_SIZE
50 #undef  LSSE_REGSIZE
51 #undef  FETCH_BSEA
52 #undef  STORE_BSEA
53 #undef  LSHE_BSEA
54 #undef  LSHE_RESV
55 #undef  LSHE_BVALID
56 #undef  FETCH_FSHA
57 #undef  LSTE_FSHA
58 #undef  LSTE_RESV
59 #undef  LSTE_FVALID
60 
61 #if defined(FEATURE_ESAME)
62 
63   #define CR15_LSEA     CR15_LSEA_900   /* Bit mask for ESAME linkage
64                                            stack entry addr in CR15  */
65   #define LSEA_WRAP(_lsea)              /* No address wrap for ESAME */
66   #define LSSE_SIZE     296             /* Size of an ESAME linkage
67                                            stack state entry         */
68   #define LSSE_REGSIZE  8               /* Size of a general register
69                                            in ESAME state entry      */
70 
71   /* ESAME linkage stack header entry */
72   /* LSHE words 1 and 2 contain the backward stack entry address */
73   #define FETCH_BSEA(_bsea,_lshe)       FETCH_DW(_bsea,_lshe)
74   #define STORE_BSEA(_lshe,_bsea)       STORE_DW(_lshe,_bsea)
75   #define LSHE_BSEA     0xFFFFFFFFFFFFFFF8ULL  /* Backward address   */
76   #define LSHE_RESV     0x06            /* Reserved bits - must be 0 */
77   #define LSHE_BVALID   0x01            /* Backward address is valid */
78   /* LSHE words 2 and 3 contain a linkage stack entry descriptor */
79 
80   /* ESAME linkage stack trailer entry */
81   /* LSTE words 1 and 2 contain the forward section header address */
82   #define FETCH_FSHA(_fsha,_lste)       FETCH_DW(_fsha,_lste)
83   #define LSTE_FSHA     0xFFFFFFFFFFFFFFF8ULL  /* Forward address    */
84   #define LSTE_RESV     0x06            /* Reserved bits - must be 0 */
85   #define LSTE_FVALID   0x01            /* Forward address is valid  */
86   /* LSTE words 2 and 3 contain a linkage stack entry descriptor */
87 
88 #else /*!defined(FEATURE_ESAME)*/
89 
90   #define CR15_LSEA     CR15_LSEA_390   /* Bit mask for ESA/390 linkage
91                                            stack entry addr in CR15  */
92   #define LSEA_WRAP(_lsea) \
93                 _lsea &= 0x7FFFFFFF     /* Wrap linkage stack address*/
94   #define LSSE_SIZE     168             /* Size of an ESA/390 linkage
95                                            stack state entry         */
96   #define LSSE_REGSIZE  4               /* Size of a general register
97                                            in ESA/390 state entry    */
98 
99   /* ESA/390 linkage stack header entry */
100   /* LSHE word 0 is reserved for control program use */
101   /* LSHE word 1 contains the backward stack entry address */
102   #define FETCH_BSEA(_bsea,_lshe)       FETCH_FW(_bsea,(_lshe)+4)
103   #define STORE_BSEA(_lshe,_bsea)       STORE_FW((_lshe)+4,_bsea)
104   #define LSHE_BVALID   0x80000000      /* Backward address is valid */
105   #define LSHE_BSEA     0x7FFFFFF8      /* Backward stack entry addr */
106   #define LSHE_RESV     0x00000007      /* Reserved bits - must be 0 */
107   /* LSHE words 2 and 3 contain a linkage stack entry descriptor */
108 
109   /* ESA/390 linkage stack trailer entry */
110   /* LSTE word 0 is reserved for control program use */
111   /* LSTE word 1 contains the forward section header address */
112   #define FETCH_FSHA(_fsha,_lste)       FETCH_FW(_fsha,(_lste)+4)
113   #define LSTE_FVALID   0x80000000      /* Forward address is valid  */
114   #define LSTE_FSHA     0x7FFFFFF8      /* Forward section hdr addr  */
115   #define LSTE_RESV     0x00000007      /* Reserved bits - must be 0 */
116   /* LSTE words 2 and 3 contain a linkage stack entry descriptor */
117 
118 #endif /*!defined(FEATURE_ESAME)*/
119 
120 
121 #if defined(FEATURE_LINKAGE_STACK)
122 
ARCH_DEP(abs_stack_addr)123 static inline RADR ARCH_DEP(abs_stack_addr) (VADR vaddr, REGS *regs, int acctype)
124 {
125     return MADDR(vaddr, USE_HOME_SPACE, regs, acctype, 0) - regs->mainstor;
126 }
127 
128 
ARCH_DEP(abs_trap_addr)129 static inline RADR ARCH_DEP(abs_trap_addr) (VADR vaddr, REGS *regs, int acctype)
130 {
131     return MADDR(vaddr, USE_HOME_SPACE, regs, acctype, regs->psw.pkey) - regs->mainstor;
132 }
133 
134 /*-------------------------------------------------------------------*/
135 /* Subroutine called by the TRAP2 and TRAP4 instructions             */
136 /*                                                                   */
137 /* Input:                                                            */
138 /*      trap4   0=TRAP2 instruction, 1=TRAP4 instruction             */
139 /*      regs    Pointer to the CPU register context                  */
140 /*      operand Effective address if TRAP4                           */
141 /*-------------------------------------------------------------------*/
ARCH_DEP(trap_x)142 void ARCH_DEP(trap_x) (int trap_is_trap4, REGS *regs, U32 trap_operand)
143 {
144 RADR ducto;
145 U32  duct11;
146 U32  tcba;
147 RADR atcba;
148 #if defined(FEATURE_ESAME)
149 U32  tcba0;
150 #endif /*defined(FEATURE_ESAME)*/
151 U32  tsao;
152 RADR tsaa1,
153      tsaa2;
154 VADR lastbyte;
155 U32  trap_ia;
156 U32  trap_flags;
157 QWORD trap_psw;
158 int  i;
159 
160     if(SIE_STATB(regs, MX, XC))
161         ARCH_DEP(program_interrupt)(regs, PGM_SPECIAL_OPERATION_EXCEPTION);
162 
163     if (   REAL_MODE(&regs->psw)
164       || !(PRIMARY_SPACE_MODE(&regs->psw)
165       ||   ACCESS_REGISTER_MODE(&regs->psw)) )
166         ARCH_DEP(program_interrupt) (regs, PGM_SPECIAL_OPERATION_EXCEPTION);
167 
168     /* Obtain the DUCT origin from control register 2 */
169     ducto = regs->CR(2) & CR2_DUCTO;
170 
171     /* Program check if DUCT origin address is invalid */
172     if (ducto > regs->mainlim)
173         ARCH_DEP(program_interrupt) (regs, PGM_ADDRESSING_EXCEPTION);
174 
175     /* Fetch DUCT bytes 44-47 */
176     duct11 = ARCH_DEP(fetch_fullword_absolute) (ducto + 44, regs);
177 
178     if(!(duct11 & DUCT11_TE))
179         ARCH_DEP(program_interrupt) (regs, PGM_SPECIAL_OPERATION_EXCEPTION);
180 
181     /* Isolate the Trap Control Block Address */
182     tcba = duct11 & DUCT11_TCBA;
183 
184 #if defined(FEATURE_ESAME)
185     /* Fetch word 0 of the TCB */
186     atcba = ARCH_DEP(abs_trap_addr) (tcba, regs, ACCTYPE_READ);
187     FETCH_FW(tcba0, regs->mainstor + atcba);
188 #endif /*defined(FEATURE_ESAME)*/
189 
190     /* Advance to offset +12 */
191     tcba += 12;
192     atcba = ARCH_DEP(abs_trap_addr) (tcba, regs, ACCTYPE_READ);
193 
194     /* Fetch word 3 of the TCB */
195     FETCH_FW(tsao, regs->mainstor + atcba);
196     tsao &= 0x7FFFFFF8;
197 
198     /* Advance to offset +20 */
199     tcba += 8; atcba += 8;
200     if((atcba & PAGEFRAME_BYTEMASK) < 8)
201         atcba = ARCH_DEP(abs_trap_addr) (tcba, regs, ACCTYPE_READ);
202 
203     /* Fetch word 5 of the TCB */
204     FETCH_FW(trap_ia, regs->mainstor + atcba);
205     trap_ia &= 0x7FFFFFFF;
206 
207     /* Calculate last byte stored */
208     lastbyte = tsao + 95
209 #if defined(FEATURE_ESAME)
210                          + ((tcba0 & TCB0_R) ? 64 : 0)
211 #endif /*defined(FEATURE_ESAME)*/
212                                                        ;
213 
214     /* Use abs_trap_addr as it conforms to trap save area access */
215     tsaa1 = tsaa2 = ARCH_DEP(abs_trap_addr) (tsao, regs, ACCTYPE_WRITE);
216     if((tsaa1 & PAGEFRAME_PAGEMASK) != (lastbyte & PAGEFRAME_PAGEMASK))
217     {
218         tsao = lastbyte & PAGEFRAME_PAGEMASK;
219         tsaa2 = ARCH_DEP(abs_trap_addr) (tsao, regs, ACCTYPE_WRITE);
220     }
221     STORAGE_KEY(tsaa1, regs) |= STORKEY_CHANGE;
222     if (tsaa1 != tsaa2)
223         STORAGE_KEY(tsaa2, regs) |= STORKEY_CHANGE;
224 
225 
226 #if defined(FEATURE_ESAME)
227     /* Special operation exception if P == 0 and EA == 1 */
228     if(!(tcba0 & TCB0_P) && regs->psw.amode64)
229         ARCH_DEP(program_interrupt) (regs, PGM_SPECIAL_OPERATION_EXCEPTION);
230 #endif /*defined(FEATURE_ESAME)*/
231 
232   #ifdef FEATURE_TRACING
233     if (regs->CR(12) & CR12_BRTRACE)
234         regs->CR(12) = ARCH_DEP(trace_br) (1, trap_ia, regs);
235   #endif /*FEATURE_TRACING*/
236 
237     PER_SB(regs, trap_ia);
238 
239     trap_flags = REAL_ILC(regs) << 16;
240 
241     if(regs->execflag)
242         trap_flags |= TRAP0_EXECUTE;
243 
244     if(trap_is_trap4)
245         trap_flags |= TRAP0_TRAP4;
246 
247     /* Trap flags at offset +0 */
248     STORE_FW(regs->mainstor + tsaa1, trap_flags);
249     /* Reserved zero's stored at offset +4 */
250     STORE_FW(regs->mainstor + tsaa1 + 4, 0);
251 
252     tsaa1 += 8;
253     if((tsaa1 & PAGEFRAME_BYTEMASK) == 0)
254         tsaa1 = tsaa2;
255 
256     /* Bits 33-63 of Second-Op address of TRAP4 at offset +8 */
257     STORE_FW(regs->mainstor + tsaa1, trap_operand);
258     /* Access register 15 at offset +12 */
259     STORE_FW(regs->mainstor + tsaa1 + 4, regs->AR(15));
260 
261     tsaa1 += 8;
262     if((tsaa1 & PAGEFRAME_BYTEMASK) == 0)
263         tsaa1 = tsaa2;
264 
265 #if defined(FEATURE_ESAME)
266     /* If the P bit is one then store the PSW in esame format */
267     if(tcba0 & TCB0_P)
268         ARCH_DEP(store_psw) (regs, trap_psw);
269     else
270 #endif /*defined(FEATURE_ESAME)*/
271     {
272         s390_store_psw(regs, trap_psw);
273 #if defined(FEATURE_ESAME)
274         /* Set the notesame mode bit for a esa/390 psw */
275         trap_psw[1] |= 0x08;
276 #endif /*defined(FEATURE_ESAME)*/
277     }
278 
279     /* bits 0-63 of PSW at offset +16 */
280     memcpy(regs->mainstor + tsaa1, trap_psw, 8);
281     tsaa1 += 8;
282     if((tsaa1 & PAGEFRAME_BYTEMASK) == 0)
283     {
284         tsaa1 = tsaa2;
285     }
286 
287 #if defined(FEATURE_ESAME)
288     /* If the P bit is one then store the PSW in esame format */
289     /* bits 64-127 of PSW at offset +24 */
290     if(tcba0 & TCB0_P)
291     {
292         memcpy(regs->mainstor + tsaa1, trap_psw + 8, 8);
293     }
294     else
295     {
296 #endif /*defined(FEATURE_ESAME)*/
297         memset(regs->mainstor + tsaa1, 0, 8);
298 #if defined(FEATURE_ESAME)
299     }
300 #endif /*defined(FEATURE_ESAME)*/
301     tsaa1 += 8;
302     if((tsaa1 & PAGEFRAME_BYTEMASK) == 0)
303         tsaa1 = tsaa2;
304 
305 #if defined(FEATURE_ESAME)
306     /* General registers at offset +32 */
307     if(tcba0 & TCB0_R)
308         for(i = 0; i < 16; i++)
309         {
310             STORE_DW(regs->mainstor + tsaa1, regs->GR_G(i));
311             tsaa1 += 8;
312             if((tsaa1 & PAGEFRAME_BYTEMASK) == 0)
313                 tsaa1 = tsaa2;
314         }
315     else
316 #endif /*defined(FEATURE_ESAME)*/
317         for(i = 0; i < 16; i++)
318         {
319             STORE_FW(regs->mainstor + tsaa1, regs->GR_L(i));
320             tsaa1 += 4;
321             if((tsaa1 & PAGEFRAME_BYTEMASK) == 0)
322                 tsaa1 = tsaa2;
323         }
324 
325     /* Load the Trap Control Block Address in gr15 */
326 #if defined(FEATURE_ESAME)
327     if(regs->psw.amode64)
328         regs->GR(15) = duct11 & DUCT11_TCBA & 0x00000000FFFFFFFF;
329     else
330 #endif /*defined(FEATURE_ESAME)*/
331         regs->GR_L(15) = duct11 & DUCT11_TCBA;
332 
333     /* Ensure psw.IA is set */
334     SET_PSW_IA(regs);
335 
336     /* Set the Breaking Event Address Register */
337     SET_BEAR_REG(regs, regs->ip -
338       (trap_is_trap4 ? 4 : regs->execflag ? regs->exrl ? 6 : 4 : 2));
339     regs->psw.amode = 1;
340     regs->psw.AMASK = AMASK31;
341     UPD_PSW_IA(regs, trap_ia);
342     /* set PSW to primary space */
343     regs->psw.asc = 0;
344     SET_AEA_MODE(regs);
345 }
346 
347 
348 /*-------------------------------------------------------------------*/
349 /* Form a new entry on the linkage stack                             */
350 /*                                                                   */
351 /* Input:                                                            */
352 /*      etype   Linkage stack entry type (LSED_UET_PC/BAKR)          */
353 /*      retna   Return amode and instruction address to be stored    */
354 /*              in the saved PSW in the new stack entry              */
355 /*      calla   Called amode and instruction address (for BAKR)      */
356 /*      csi     32-bit called-space identification (for PC)          */
357 /*      pcnum   Called PC number (for PC)                            */
358 /*      regs    Pointer to the CPU register context                  */
359 /*                                                                   */
360 /*      This function performs the stacking process for the          */
361 /*      Branch and Stack (BAKR) and Program Call (PC) instructions.  */
362 /*                                                                   */
363 /*      For ESAME, bit 63 of retna/calla indicate a 64-bit address,  */
364 /*      otherwise bit 32 indicates a 31-bit address.                 */
365 /*      For ESA/390, bit 0 of retna/calla indicate a 31-bit address. */
366 /*                                                                   */
367 /*      For ESAME, bit 0 of pcnum indicates resulting 64-bit mode.   */
368 /*                                                                   */
369 /*      In the event of any stack error, this function generates     */
370 /*      a program check and does not return.                         */
371 /*-------------------------------------------------------------------*/
ARCH_DEP(form_stack_entry)372 void ARCH_DEP(form_stack_entry) (BYTE etype, VADR retna, VADR calla,
373                                 U32 csi, U32 pcnum, REGS *regs)
374 {
375 QWORD   currpsw;                        /* Current PSW               */
376 VADR    lsea;                           /* Linkage stack entry addr  */
377 VADR    lseaold;                        /* Linkage stack old addr    */
378 RADR    abs, abs2 = 0;                  /* Absolute addr new entry   */
379 RADR    absold;                         /* Absolute addr old entry   */
380 LSED    lsed;                           /* Linkage stack entry desc. */
381 LSED    lsed2;                          /* New entry descriptor      */
382 U16     rfs;                            /* Remaining free space      */
383 VADR    fsha;                           /* Forward section hdr addr  */
384 VADR    bsea = 0;                       /* Backward stack entry addr */
385 RADR    absea = 0;                      /* Absolute address of bsea  */
386 int     i;                              /* Array subscript           */
387 
388     /* [5.12.3.1] Locate space for a new linkage stack entry */
389 
390     /* Obtain the virtual address of the current entry from CR15 */
391     lsea = regs->CR(15) & CR15_LSEA;
392 
393     /* Fetch the entry descriptor of the current entry */
394     absold = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
395     memcpy (&lsed, regs->mainstor+absold, sizeof(LSED));
396     lseaold = lsea;
397 
398 #ifdef STACK_DEBUG
399     logmsg (_("stack: Current stack entry at " F_VADR "\n"), lsea);
400     logmsg (_("stack: et=%2.2X si=%2.2X rfs=%2.2X%2.2X nes=%2.2X%2.2X\n"),
401             lsed.uet, lsed.si, lsed.rfs[0],
402             lsed.rfs[1], lsed.nes[0], lsed.nes[1]);
403 #endif /*STACK_DEBUG*/
404 
405     /* Check whether the current linkage stack section has enough
406        remaining free space to contain the new stack entry */
407     FETCH_HW(rfs,lsed.rfs);
408     if (rfs < LSSE_SIZE)
409     {
410         /* Program check if remaining free space not a multiple of 8 */
411         if ((rfs & 0x07) != 0)
412             ARCH_DEP(program_interrupt) (regs, PGM_STACK_SPECIFICATION_EXCEPTION);
413 
414         /* Not enough space, so fetch the forward section header addr
415            from the trailer entry of current linkage stack section */
416         lsea += sizeof(LSED) + rfs;
417         LSEA_WRAP(lsea);
418         abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
419         FETCH_FSHA(fsha, regs->mainstor + abs);
420 
421 #ifdef STACK_DEBUG
422         logmsg (_("stack: Forward section header addr " F_VADR "\n"), fsha);
423 #endif /*STACK_DEBUG*/
424 
425         /* Stack full exception if forward address is not valid */
426         if ((fsha & LSTE_FVALID) == 0)
427             ARCH_DEP(program_interrupt) (regs, PGM_STACK_FULL_EXCEPTION);
428 
429         /* Extract the forward section header address, which points to
430            the entry descriptor (words 2-3) of next section's header */
431         fsha &= LSTE_FSHA;
432 
433         /* Fetch the entry descriptor of the next section's header */
434         absold = ARCH_DEP(abs_stack_addr) (fsha, regs, ACCTYPE_READ);
435         memcpy (&lsed, regs->mainstor+absold, sizeof(LSED));
436         lseaold = fsha;
437 
438 #ifdef STACK_DEBUG
439         logmsg (_("stack: et=%2.2X si=%2.2X rfs=%2.2X%2.2X "
440                 "nes=%2.2X%2.2X\n"),
441                 lsed.uet, lsed.si, lsed.rfs[0],
442                 lsed.rfs[1], lsed.nes[0], lsed.nes[1]);
443 #endif /*STACK_DEBUG*/
444 
445         /* Program check if the next linkage stack section does not
446            have enough free space to contain the new stack entry */
447         FETCH_HW(rfs,lsed.rfs);
448         if (rfs < LSSE_SIZE)
449             ARCH_DEP(program_interrupt) (regs, PGM_STACK_SPECIFICATION_EXCEPTION);
450 
451         /* Calculate the virtual address of the new section's header
452            entry, which is 8 bytes before the entry descriptor */
453         lsea = fsha - 8;
454         LSEA_WRAP(lsea);
455 
456         /* Form the backward stack entry address */
457         bsea = LSHE_BVALID | (regs->CR(15) & CR15_LSEA);
458         absea = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_WRITE);
459 
460         /* Use the virtual address of the entry descriptor of the
461            new section's header entry as the current entry address */
462         lsea = fsha;
463 
464     } /* end if(rfs<LSSE_SIZE) */
465 
466     /* [5.12.3.2] Form the new stack entry */
467 
468     /* Calculate the virtual address of the new stack entry */
469     lsea += sizeof(LSED);
470     LSEA_WRAP(lsea);
471 
472     /* Obtain absolute address of the new stack entry */
473     abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_WRITE);
474 
475     /* If new stack entry will cross a page boundary, obtain the
476        absolute address of the second page of the stack entry */
477     if(((lsea + (LSSE_SIZE - 1)) & PAGEFRAME_PAGEMASK)
478                                 != (lsea & PAGEFRAME_PAGEMASK))
479         abs2 = ARCH_DEP(abs_stack_addr)
480                         ((lsea + (LSSE_SIZE - 1)) & PAGEFRAME_PAGEMASK,
481                         regs, ACCTYPE_WRITE);
482 
483 #ifdef STACK_DEBUG
484     logmsg (_("stack: New stack entry at " F_VADR "\n"), lsea);
485 #endif /*STACK_DEBUG*/
486 
487     /* If a new section then place updated backward stack
488        entry address in the new section's header entry */
489     if(bsea)
490         STORE_BSEA(regs->mainstor + absea, bsea);
491 
492     /* Store general registers 0-15 in bytes 0-63 (ESA/390)
493        or bytes 0-127 (ESAME) of the new state entry */
494     for (i = 0; i < 16; i++)
495     {
496 #if defined(FEATURE_ESAME)
497         /* Store the 64-bit general register in the stack entry */
498         STORE_DW(regs->mainstor + abs, regs->GR_G(i));
499 
500       #ifdef STACK_DEBUG
501         logmsg (_("stack: GPR%d=" F_GREG " stored at V:" F_VADR
502                 " A:" F_RADR "\n"), i, regs->GR_G(i), lsea, abs);
503       #endif /*STACK_DEBUG*/
504 #else /*!defined(FEATURE_ESAME)*/
505         /* Store the 32-bit general register in the stack entry */
506         STORE_FW(regs->mainstor + abs, regs->GR_L(i));
507 
508       #ifdef STACK_DEBUG
509         logmsg (_("stack: GPR%d=" F_GREG " stored at V:" F_VADR
510                 " A:" F_RADR "\n"), i, regs->GR_L(i), lsea, abs);
511       #endif /*STACK_DEBUG*/
512 #endif /*!defined(FEATURE_ESAME)*/
513 
514         /* Update the virtual and absolute addresses */
515         lsea += LSSE_REGSIZE;
516         LSEA_WRAP(lsea);
517         abs += LSSE_REGSIZE;
518 
519         /* Recalculate absolute address if page boundary crossed */
520         if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
521             abs = abs2;
522 
523     } /* end for(i) */
524 
525 #if !defined(FEATURE_ESAME)
526     /* For ESA/390, store access registers 0-15 in bytes 64-127 */
527     for (i = 0; i < 16; i++)
528     {
529         /* Store the access register in the stack entry */
530         STORE_FW(regs->mainstor + abs, regs->AR(i));
531 
532       #ifdef STACK_DEBUG
533         logmsg (_("stack: AR%d=" F_AREG " stored at V:" F_VADR
534                 " A:" F_RADR "\n"), i, regs->AR(i), lsea, abs);
535       #endif /*STACK_DEBUG*/
536 
537         /* Update the virtual and absolute addresses */
538         lsea += 4;
539         LSEA_WRAP(lsea);
540         abs += 4;
541 
542         /* Recalculate absolute address if page boundary crossed */
543         if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
544             abs = abs2;
545 
546     } /* end for(i) */
547 #endif /*!defined(FEATURE_ESAME)*/
548 
549     /* Store the PKM, SASN, EAX, and PASN in bytes 128-135 */
550     STORE_FW(regs->mainstor + abs, regs->CR_L(3));
551     STORE_HW(regs->mainstor + abs + 4, regs->CR_LHH(8));
552     STORE_HW(regs->mainstor + abs + 6, regs->CR_LHL(4));
553 
554   #ifdef STACK_DEBUG
555     logmsg (_("stack: PKM=%2.2X%2.2X SASN=%2.2X%2.2X "
556             "EAX=%2.2X%2.2X PASN=%2.2X%2.2X \n"
557             "stored at V:" F_VADR " A:" F_RADR "\n"),
558             regs->mainstor[abs], regs->mainstor[abs+1],
559             regs->mainstor[abs+2], regs->mainstor[abs+3],
560             regs->mainstor[abs+4], regs->mainstor[abs+5],
561             regs->mainstor[abs+6], regs->mainstor[abs+7],
562             lsea, abs);
563   #endif /*STACK_DEBUG*/
564 
565     /* Update virtual and absolute addresses to point to byte 136 */
566     lsea += 8;
567     LSEA_WRAP(lsea);
568     abs += 8;
569 
570     /* Recalculate absolute address if page boundary crossed */
571     if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
572         abs = abs2;
573 
574     /* Store bits 0-63 of the current PSW in bytes 136-143 */
575     ARCH_DEP(store_psw) (regs, currpsw);
576     memcpy (regs->mainstor + abs, currpsw, 8);
577 
578 #if defined(FEATURE_ESAME)
579     /* For ESAME, use the addressing mode bits from the return
580        address to set bits 31 and 32 of bytes 136-143 */
581     if (retna & 0x01)
582     {
583         /* For a 64-bit return address, set bits 31 and 32 */
584         regs->mainstor[abs+3] |= 0x01;
585         regs->mainstor[abs+4] |= 0x80;
586         retna &= 0xFFFFFFFFFFFFFFFEULL;
587     }
588     else if (retna & 0x80000000)
589     {
590         /* For a 31-bit return address, clear bit 31 and set bit 32 */
591         regs->mainstor[abs+3] &= 0xFE;
592         regs->mainstor[abs+4] |= 0x80;
593         retna &= 0x7FFFFFFF;
594     }
595     else
596     {
597         /* For a 24-bit return address, clear bits 31 and 32 */
598         regs->mainstor[abs+3] &= 0xFE;
599         regs->mainstor[abs+4] &= 0x7F;
600         retna &= 0x00FFFFFF;
601     }
602 #else /*!defined(FEATURE_ESAME)*/
603     /* For ESA/390, replace bytes 140-143 by the return address,
604        with the high-order bit indicating the addressing mode */
605     STORE_FW(regs->mainstor + abs + 4, retna);
606 #endif /*!defined(FEATURE_ESAME)*/
607 
608   #ifdef STACK_DEBUG
609     logmsg (_("stack: PSW=%2.2X%2.2X%2.2X%2.2X %2.2X%2.2X%2.2X%2.2X "
610             "stored at V:" F_VADR " A:" F_RADR "\n"),
611             regs->mainstor[abs], regs->mainstor[abs+1],
612             regs->mainstor[abs+2], regs->mainstor[abs+3],
613             regs->mainstor[abs+4], regs->mainstor[abs+5],
614             regs->mainstor[abs+6], regs->mainstor[abs+7],
615             lsea, abs);
616   #endif /*STACK_DEBUG*/
617 
618     /* Update virtual and absolute addresses to point to byte 144 */
619     lsea += 8;
620     LSEA_WRAP(lsea);
621     abs += 8;
622 
623     /* Recalculate absolute address if page boundary crossed */
624     if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
625         abs = abs2;
626 
627     /* Store bytes 144-151 according to PC or BAKR */
628     if (etype == LSED_UET_PC)
629     {
630       #if defined(FEATURE_CALLED_SPACE_IDENTIFICATION)
631         /* Store the called-space identification in bytes 144-147 */
632         STORE_FW(regs->mainstor + abs, csi);
633       #endif /*defined(FEATURE_CALLED_SPACE_IDENTIFICATION)*/
634 
635         /* Store the PC number in bytes 148-151 */
636         STORE_FW(regs->mainstor + abs + 4, pcnum);
637     }
638     else
639     {
640       #if defined(FEATURE_ESAME)
641         /* Store the called address and amode in bytes 144-151 */
642         STORE_DW(regs->mainstor + abs, calla);
643       #else /*!defined(FEATURE_ESAME)*/
644         /* Store the called address and amode in bytes 148-151 */
645         STORE_FW(regs->mainstor + abs + 4, calla);
646       #endif /*!defined(FEATURE_ESAME)*/
647     }
648 
649     /* Update virtual and absolute addresses to point to byte 152 */
650     lsea += 8;
651     LSEA_WRAP(lsea);
652     abs += 8;
653 
654     /* Recalculate absolute address if page boundary crossed */
655     if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
656         abs = abs2;
657 
658     /* Store zeroes in bytes 152-159 */
659     memset (regs->mainstor+abs, 0, 8);
660 
661     /* Update virtual and absolute addresses to point to byte 160 */
662     lsea += 8;
663     LSEA_WRAP(lsea);
664     abs += 8;
665 
666     /* Recalculate absolute address if page boundary crossed */
667     if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
668         abs = abs2;
669 
670 #if defined(FEATURE_ESAME)
671     /* For ESAME, store zeroes in bytes 160-167 */
672     memset (regs->mainstor+abs, 0, 8);
673 
674     /* Update virtual and absolute addresses to point to byte 168 */
675     lsea += 8;
676     LSEA_WRAP(lsea);
677     abs += 8;
678 
679     /* Recalculate absolute address if page boundary crossed */
680     if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
681         abs = abs2;
682 
683     /* For ESAME, store the return address in bytes 168-175 */
684     STORE_DW (regs->mainstor + abs, retna);
685 
686   #ifdef STACK_DEBUG
687     logmsg (_("stack: PSW2=%2.2X%2.2X%2.2X%2.2X %2.2X%2.2X%2.2X%2.2X "
688             "stored at V:" F_VADR " A:" F_RADR "\n"),
689             regs->mainstor[abs], regs->mainstor[abs+1],
690             regs->mainstor[abs+2], regs->mainstor[abs+3],
691             regs->mainstor[abs+4], regs->mainstor[abs+5],
692             regs->mainstor[abs+6], regs->mainstor[abs+7],
693             lsea, abs);
694   #endif /*STACK_DEBUG*/
695 
696     /* Update virtual and absolute addresses to point to byte 176 */
697     lsea += 8;
698     LSEA_WRAP(lsea);
699     abs += 8;
700 
701     /* Recalculate absolute address if page boundary crossed */
702     if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
703         abs = abs2;
704 
705     /* If ASN-and-LX-reuse is installed and active, store
706        the SASTEIN (CR3 bits 0-31) in bytes 176-179, and
707        store the PASTEIN (CR4 bits 0-31) in bytes 180-183 */
708     if (ASN_AND_LX_REUSE_ENABLED(regs))
709     {
710         STORE_FW(regs->mainstor + abs, regs->CR_H(3));
711         STORE_FW(regs->mainstor + abs + 4, regs->CR_H(4));
712 
713       #ifdef STACK_DEBUG
714         logmsg (_("stack: SASTEIN=%2.2X%2.2X%2.2X%2.2X "
715                 "PASTEIN=%2.2X%2.2X%2.2X%2.2X \n"
716                 "stored at V:" F_VADR " A:" F_RADR "\n"),
717                 regs->mainstor[abs], regs->mainstor[abs+1],
718                 regs->mainstor[abs+2], regs->mainstor[abs+3],
719                 regs->mainstor[abs+4], regs->mainstor[abs+5],
720                 regs->mainstor[abs+6], regs->mainstor[abs+7],
721                 lsea, abs);
722       #endif /*STACK_DEBUG*/
723 
724     } /* end if(ASN_AND_LX_REUSE_ENABLED) */
725 
726     /* Skip bytes 176-223 of the new stack entry */
727     lsea += 48;
728     LSEA_WRAP(lsea);
729     abs += 48;
730 
731     /* Recalculate absolute address if page boundary crossed */
732     if ((lsea & PAGEFRAME_BYTEMASK) < 48)
733         abs = abs2 | (lsea & PAGEFRAME_BYTEMASK);
734 
735     /* For ESAME, store access registers 0-15 in bytes 224-287 */
736     for (i = 0; i < 16; i++)
737     {
738         /* Store the access register in the stack entry */
739         STORE_FW(regs->mainstor + abs, regs->AR(i));
740 
741       #ifdef STACK_DEBUG
742         logmsg (_("stack: AR%d=" F_AREG " stored at V:" F_VADR
743                 " A:" F_RADR "\n"), i, regs->AR(i), lsea, abs);
744       #endif /*STACK_DEBUG*/
745 
746         /* Update the virtual and absolute addresses */
747         lsea += 4;
748         LSEA_WRAP(lsea);
749         abs += 4;
750 
751         /* Recalculate absolute address if page boundary crossed */
752         if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
753             abs = abs2;
754 
755     } /* end for(i) */
756 #endif /*defined(FEATURE_ESAME)*/
757 
758     /* Build the new linkage stack entry descriptor */
759     memset (&lsed2, 0, sizeof(LSED));
760     lsed2.uet = etype & LSED_UET_ET;
761     lsed2.si = lsed.si;
762     rfs -= LSSE_SIZE;
763     STORE_HW(lsed2.rfs,rfs);
764 
765     /* Store the linkage stack entry descriptor in the last eight
766        bytes of the new state entry (bytes 160-167 for ESA/390,
767        or bytes 288-295 for ESAME) */
768     memcpy (regs->mainstor+abs, &lsed2, sizeof(LSED));
769 
770 #ifdef STACK_DEBUG
771     logmsg (_("stack: New stack entry at " F_VADR "\n"), lsea);
772     logmsg (_("stack: et=%2.2X si=%2.2X rfs=%2.2X%2.2X nes=%2.2X%2.2X\n"),
773             lsed2.uet, lsed2.si, lsed2.rfs[0],
774             lsed2.rfs[1], lsed2.nes[0], lsed2.nes[1]);
775 #endif /*STACK_DEBUG*/
776 
777     /* [5.12.3.3] Update the current entry */
778     STORE_HW(lsed.nes, LSSE_SIZE);
779     absold = ARCH_DEP(abs_stack_addr) (lseaold, regs, ACCTYPE_WRITE);
780     memcpy (regs->mainstor+absold, &lsed, sizeof(LSED));
781 
782 #ifdef STACK_DEBUG
783     logmsg (_("stack: Previous stack entry updated at A:" F_RADR "\n"),
784             absold);
785     logmsg (_("stack: et=%2.2X si=%2.2X rfs=%2.2X%2.2X nes=%2.2X%2.2X\n"),
786             lsed.uet, lsed.si, lsed.rfs[0],
787             lsed.rfs[1], lsed.nes[0], lsed.nes[1]);
788 #endif /*STACK_DEBUG*/
789 
790     /* [5.12.3.4] Update control register 15 */
791     regs->CR(15) = lsea & CR15_LSEA;
792 
793 #ifdef STACK_DEBUG
794     logmsg (_("stack: CR15=" F_CREG "\n"), regs->CR(15));
795 #endif /*STACK_DEBUG*/
796 
797 } /* end function ARCH_DEP(form_stack_entry) */
798 
799 /*-------------------------------------------------------------------*/
800 /* Locate the current linkage stack entry                            */
801 /*                                                                   */
802 /* Input:                                                            */
803 /*      prinst  1=PR instruction, 0=EREG/EREGG/ESTA/MSTA instruction */
804 /*      lsedptr Pointer to an LSED structure                         */
805 /*      regs    Pointer to the CPU register context                  */
806 /* Output:                                                           */
807 /*      The entry descriptor for the current state entry in the      */
808 /*      linkage stack is copied into the LSED structure.             */
809 /*      The home virtual address of the entry descriptor is          */
810 /*      returned as the function return value.                       */
811 /*                                                                   */
812 /*      This function performs the first part of the unstacking      */
813 /*      process for the Program Return (PR), Extract Stacked         */
814 /*      Registers (EREG/EREGG), Extract Stacked State (ESTA),        */
815 /*      and Modify Stacked State (MSTA) instructions.                */
816 /*                                                                   */
817 /*      In the event of any stack error, this function generates     */
818 /*      a program check and does not return.                         */
819 /*-------------------------------------------------------------------*/
ARCH_DEP(locate_stack_entry)820 VADR ARCH_DEP(locate_stack_entry) (int prinst, LSED *lsedptr,
821                                     REGS *regs)
822 {
823 VADR    lsea;                           /* Linkage stack entry addr  */
824 RADR    abs;                            /* Absolute address          */
825 VADR    bsea;                           /* Backward stack entry addr */
826 
827     /* [5.12.4] Special operation exception if ASF is not enabled,
828        or if DAT is off, or if in secondary-space mode */
829     if (!ASF_ENABLED(regs)
830         || REAL_MODE(&regs->psw)
831         || SECONDARY_SPACE_MODE(&regs->psw))
832         ARCH_DEP(program_interrupt) (regs, PGM_SPECIAL_OPERATION_EXCEPTION);
833 
834     /* Special operation exception if home space mode PR instruction */
835     if (prinst && HOME_SPACE_MODE(&regs->psw))
836         ARCH_DEP(program_interrupt) (regs, PGM_SPECIAL_OPERATION_EXCEPTION);
837 
838     /* [5.12.4.1] Locate current entry and process header entry */
839 
840     /* Obtain the virtual address of the current entry from CR15 */
841     lsea = regs->CR(15) & CR15_LSEA;
842 
843     /* Fetch the entry descriptor of the current entry */
844     abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
845     memcpy (lsedptr, regs->mainstor+abs, sizeof(LSED));
846 
847 #ifdef STACK_DEBUG
848     logmsg (_("stack: Stack entry located at " F_VADR "\n"), lsea);
849     logmsg (_("stack: et=%2.2X si=%2.2X rfs=%2.2X%2.2X nes=%2.2X%2.2X\n"),
850             lsedptr->uet, lsedptr->si, lsedptr->rfs[0],
851             lsedptr->rfs[1], lsedptr->nes[0], lsedptr->nes[1]);
852 #endif /*STACK_DEBUG*/
853 
854     /* Check for a header entry */
855     if ((lsedptr->uet & LSED_UET_ET) == LSED_UET_HDR)
856     {
857         /* For PR instruction only, generate stack operation exception
858            if the unstack suppression bit in the header entry is set */
859         if (prinst && (lsedptr->uet & LSED_UET_U))
860             ARCH_DEP(program_interrupt) (regs, PGM_STACK_OPERATION_EXCEPTION);
861 
862         /* Calculate the virtual address of the header entry,
863            which is 8 bytes before the entry descriptor */
864         lsea -= 8;
865         LSEA_WRAP(lsea);
866 
867         /* Fetch the backward stack entry address from the header */
868         abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
869         FETCH_BSEA(bsea,regs->mainstor + abs);
870 
871 #ifdef STACK_DEBUG
872         logmsg (_("stack: Stack entry located at " F_VADR "\n"), bsea);
873 #endif /*STACK_DEBUG*/
874 
875         /* Stack empty exception if backward address is not valid */
876         if ((bsea & LSHE_BVALID) == 0)
877             ARCH_DEP(program_interrupt) (regs, PGM_STACK_EMPTY_EXCEPTION);
878 
879         /* Extract the virtual address of the entry descriptor
880            of the last entry in the previous section */
881         lsea = bsea & LSHE_BSEA;
882 
883         /* Fetch the entry descriptor of the designated entry */
884         abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
885         memcpy (lsedptr, regs->mainstor+abs, sizeof(LSED));
886 
887 #ifdef STACK_DEBUG
888         logmsg (_("stack: et=%2.2X si=%2.2X rfs=%2.2X%2.2X "
889                 "nes=%2.2X%2.2X\n"),
890                 lsedptr->uet, lsedptr->si, lsedptr->rfs[0],
891                 lsedptr->rfs[1], lsedptr->nes[0], lsedptr->nes[1]);
892 #endif /*STACK_DEBUG*/
893 
894         /* Stack specification exception if this is also a header */
895         if ((lsedptr->uet & LSED_UET_ET) == LSED_UET_HDR)
896             ARCH_DEP(program_interrupt) (regs, PGM_STACK_SPECIFICATION_EXCEPTION);
897 
898     } /* end if(LSED_UET_HDR) */
899 
900     /* [5.12.4.2] Check for a state entry */
901 
902     /* Stack type exception if this is not a state entry */
903     if ((lsedptr->uet & LSED_UET_ET) != LSED_UET_BAKR
904         && (lsedptr->uet & LSED_UET_ET) != LSED_UET_PC)
905         ARCH_DEP(program_interrupt) (regs, PGM_STACK_TYPE_EXCEPTION);
906 
907     /* [5.12.4.3] For PR instruction only, stack operation exception
908        if the unstack suppression bit in the state entry is set */
909     if (prinst && (lsedptr->uet & LSED_UET_U))
910         ARCH_DEP(program_interrupt) (regs, PGM_STACK_OPERATION_EXCEPTION);
911 
912     /* Return the virtual address of the entry descriptor */
913     return lsea;
914 
915 } /* end function ARCH_DEP(locate_stack_entry) */
916 
917 /*-------------------------------------------------------------------*/
918 /* Stack modify                                                      */
919 /*                                                                   */
920 /* Input:                                                            */
921 /*      lsea    Virtual address of linkage stack entry descriptor    */
922 /*      m1      Left 32 bits to be stored in state entry             */
923 /*      m2      Right 32 bits to be stored in state entry            */
924 /*      regs    Pointer to the CPU register context                  */
925 /*                                                                   */
926 /*      This function places eight bytes of information into the     */
927 /*      modifiable area of a state entry in the linkage stack.  It   */
928 /*      is called by the Modify Stacked State (MSTA) instruction     */
929 /*      after it has located the current state entry.                */
930 /*                                                                   */
931 /*      If a translation exception occurs when accessing the stack   */
932 /*      entry, then a program check will be generated by the         */
933 /*      abs_stack_addr subroutine, and the function will not return. */
934 /*-------------------------------------------------------------------*/
ARCH_DEP(stack_modify)935 void ARCH_DEP(stack_modify) (VADR lsea, U32 m1, U32 m2, REGS *regs)
936 {
937 RADR    abs;                            /* Absolute address          */
938 
939     /* Point back to byte 152 of the state entry */
940     lsea -= LSSE_SIZE - sizeof(LSED);
941     lsea += 152;
942     LSEA_WRAP(lsea);
943 
944     /* Store the modify values into the state entry */
945     abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_WRITE);
946     STORE_FW(regs->mainstor + abs, m1);
947     STORE_FW(regs->mainstor + abs + 4, m2);
948 
949 } /* end function ARCH_DEP(stack_modify) */
950 
951 /*-------------------------------------------------------------------*/
952 /* Stack extract                                                     */
953 /*                                                                   */
954 /* Input:                                                            */
955 /*      lsea    Virtual address of linkage stack entry descriptor    */
956 /*      r1      The number of an even-odd pair of registers          */
957 /*      code    A code indicating which bytes are to be extracted:   */
958 /*              0 = Bytes 128-135 (PKN/SASN/EAX/PASN)                */
959 /*              1 = ESA/390: Bytes 136-143 (PSW)                     */
960 /*                  ESAME: Bytes 136-139, 140.0, 168-175.33-63       */
961 /*                         (ESA/390-format PSW)                      */
962 /*              2 = Bytes 144-151 (Branch address or PC number)      */
963 /*              3 = Bytes 152-159 (Modifiable area)                  */
964 /*              4 = Bytes 136-143 and 168-175 (ESAME-format PSW)     */
965 /*              5 = Bytes 176-183 (SASTEIN,PASTEIN)                  */
966 /*      regs    Pointer to the CPU register context                  */
967 /*                                                                   */
968 /*      This function extracts 64 or 128 bits of information from    */
969 /*      the status area of a state entry in the linkage stack.  It   */
970 /*      is called by the Extract Stacked State (ESTA) instruction    */
971 /*      after it has located the current state entry.                */
972 /*                                                                   */
973 /*      For codes 0 through 3, the rightmost 32 bits of the R1 and   */
974 /*      R1+1 registers are updated (the leftmost 32 bits remain      */
975 /*      unchanged for ESAME).  For code 4, which is valid only for   */
976 /*      ESAME, all 64 bits of the R1 and R1+1 registers are loaded.  */
977 /*      For code 5 (valid only if the ASN-and-LX-reuse facility is   */
978 /*      installed), the leftmost 32 bits of the R1 and R1+1 regs     */
979 /*      are updated, and the rightmost 32 bits remain unchanged.     */
980 /*                                                                   */
981 /*      If a translation exception occurs when accessing the stack   */
982 /*      entry, then a program check will be generated by the         */
983 /*      abs_stack_addr subroutine, and the function will not return. */
984 /*-------------------------------------------------------------------*/
ARCH_DEP(stack_extract)985 void ARCH_DEP(stack_extract) (VADR lsea, int r1, int code, REGS *regs)
986 {
987 RADR    abs;                            /* Absolute address          */
988 
989     /* Point back to byte 128 of the state entry */
990     lsea -= LSSE_SIZE - sizeof(LSED);
991     lsea += 128;
992 
993   #if defined(FEATURE_ESAME)
994     /* For codes 1 and 4, extract bytes 136-143 and 168-175 */
995     if (code == 1 || code == 4)
996     {
997         U64 psw1, psw2;
998 
999         /* Point to byte 136 of the state entry */
1000         lsea += 8;
1001         LSEA_WRAP(lsea);
1002 
1003         /* Load bits 0-63 of ESAME PSW from bytes 136-143 */
1004         abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
1005         FETCH_DW(psw1, regs->mainstor + abs);
1006 
1007         /* Point to byte 168 of the state entry */
1008         lsea += 32;
1009         abs += 32;
1010 
1011         /* Recalculate absolute address if page boundary crossed */
1012         if ((lsea & PAGEFRAME_BYTEMASK) < 32)
1013             abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
1014 
1015         /* Load bits 64-127 of ESAME PSW from bytes 168-175 */
1016         FETCH_DW(psw2, regs->mainstor + abs);
1017 
1018         /* For code 4, return ESAME PSW in general register pair */
1019         if (code == 4)
1020         {
1021             regs->GR_G(r1) = psw1;
1022             regs->GR_G(r1+1) = psw2;
1023             return;
1024         }
1025 
1026         /* For code 1, convert ESAME PSW to ESA/390 format */
1027         regs->GR_L(r1) = (psw1 >> 32) | 0x00080000;
1028         regs->GR_L(r1+1) = (psw1 & 0x80000000)
1029                             | (psw2 & 0x7FFFFFFF);
1030 
1031         /* Set low-order bit of R1+1 if IA exceeds 31-bit address */
1032         if (psw2 > 0x7FFFFFFF)
1033             regs->GR_L(r1+1) |= 0x01;
1034 
1035         return;
1036 
1037     } /* if(code==1||code==4) */
1038   #endif /*defined(FEATURE_ESAME)*/
1039 
1040   #if defined(FEATURE_ASN_AND_LX_REUSE)
1041     /* For code 5, extract bytes 176-183 */
1042     if (code == 5)
1043     {
1044         /* Point to byte 176 of the state entry */
1045         lsea += 48;
1046         LSEA_WRAP(lsea);
1047 
1048         /* Load the SASTEIN, PASTEIN from bytes 176-179, 180-183*/
1049         abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
1050         FETCH_FW(regs->GR_H(r1), regs->mainstor + abs);
1051         FETCH_FW(regs->GR_H(r1+1), regs->mainstor + abs + 4);
1052 
1053         return;
1054 
1055     } /* if(code==5) */
1056   #endif /*defined(FEATURE_ASN_AND_LX_REUSE)*/
1057 
1058     /* For codes 0,2,3 in ESAME, and codes 0,1,2,3 in ESA/390 */
1059     /* Point to byte 128, 136, 144, or 152 depending on the code */
1060     lsea += code * 8;
1061     LSEA_WRAP(lsea);
1062 
1063     /* Load the general register pair from the state entry */
1064     abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
1065     FETCH_FW(regs->GR_L(r1), regs->mainstor + abs);
1066     FETCH_FW(regs->GR_L(r1+1), regs->mainstor + abs + 4);
1067 
1068 } /* end function ARCH_DEP(stack_extract) */
1069 
1070 /*-------------------------------------------------------------------*/
1071 /* Unstack registers                                                 */
1072 /*                                                                   */
1073 /* Input:                                                            */
1074 /*      gtype   0=EREG instruction, 1=EREGG or PR instruction        */
1075 /*      lsea    Virtual address of linkage stack entry descriptor    */
1076 /*      r1      The number of the first register to be loaded        */
1077 /*      r2      The number of the last register to be loaded         */
1078 /*      regs    Pointer to the CPU register context                  */
1079 /*                                                                   */
1080 /*      This function loads a range of general registers and         */
1081 /*      access registers from the specified linkage stack entry.     */
1082 /*      It is called by the Extract Stacked Registers (EREG/EREGG)   */
1083 /*      and Program Return (PR) instructions after they have located */
1084 /*      the current state entry in the linkage stack.                */
1085 /*                                                                   */
1086 /*      If a translation exception occurs when accessing the stack   */
1087 /*      entry, then a program check will be generated by the         */
1088 /*      abs_stack_addr subroutine, and the function will not return. */
1089 /*      Since the stack entry can only span at most two pages, and   */
1090 /*      the caller will have already successfully accessed the       */
1091 /*      entry descriptor which is at the end of the stack entry,     */
1092 /*      the only place a translation exception can occur is when     */
1093 /*      attempting to load the first register, in which case the     */
1094 /*      operation is nullified with all registers unchanged.         */
1095 /*-------------------------------------------------------------------*/
ARCH_DEP(unstack_registers)1096 void ARCH_DEP(unstack_registers) (int gtype, VADR lsea,
1097                                 int r1, int r2, REGS *regs)
1098 {
1099 RADR    abs, abs2 = 0;                  /* Absolute address          */
1100 VADR    firstbyte,                      /* First byte to be fetched  */
1101         lastbyte;                       /* Last byte to be fetched   */
1102 int     i;                              /* Array subscript           */
1103 
1104     UNREFERENCED(gtype);
1105 
1106     /* Point back to byte 0 of the state entry */
1107     lsea -= LSSE_SIZE - sizeof(LSED);
1108     LSEA_WRAP(lsea);
1109 
1110     /* Determine first and last byte to fetch from the state entry */
1111     firstbyte = lsea + ((r1 > r2) ? 0 : r1) * LSSE_REGSIZE;
1112     lastbyte = lsea + (LSSE_SIZE - 69) + (((r1 > r2) ? 15 : r2) * 4);
1113 
1114     lsea = firstbyte;
1115 
1116     /* Obtain absolute address of the state entry */
1117     abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
1118 
1119     /* If the state entry crosses a page boundary, obtain the
1120        absolute address of the second page of the stack entry */
1121     if( (firstbyte & PAGEFRAME_PAGEMASK)
1122                                 != (lastbyte & PAGEFRAME_PAGEMASK))
1123         abs2 = ARCH_DEP(abs_stack_addr)
1124                  (lastbyte & PAGEFRAME_PAGEMASK, regs, ACCTYPE_READ);
1125 
1126   #ifdef STACK_DEBUG
1127     logmsg (_("stack: Unstacking registers %d-%d from " F_VADR "\n"),
1128             r1, r2, lsea);
1129   #endif /*STACK_DEBUG*/
1130 
1131     /* Load general registers from bytes 0-63 (for ESA/390), or
1132        bytes 0-127 (for ESAME) of the state entry */
1133     for (i = ((r1 > r2) ? 0 : r1); i <= 15; i++)
1134     {
1135         /* Load the general register from the stack entry */
1136         if ((r1 <= r2 && i >= r1 && i <= r2)
1137             || (r1 > r2 && (i >= r1 || i <= r2)))
1138         {
1139     #if defined(FEATURE_ESAME)
1140             if (gtype)
1141             {
1142                 /* For ESAME PR and EREGG instructions,
1143                    load all 64 bits of the register */
1144                 FETCH_DW(regs->GR_G(i), regs->mainstor + abs);
1145             } else {
1146                 /* For ESAME EREG instruction, load bits 32-63 of
1147                    the register, and leave bits 0-31 unchanged */
1148                 FETCH_FW(regs->GR_L(i), regs->mainstor + abs + 4);
1149             }
1150 
1151           #ifdef STACK_DEBUG
1152             logmsg (_("stack: GPR%d=" F_GREG " loaded from V:" F_VADR
1153                     " A:" F_RADR "\n"), i, regs->GR(i), lsea, abs);
1154           #endif /*STACK_DEBUG*/
1155     #else /*!defined(FEATURE_ESAME)*/
1156             /* For ESA/390, load a 32-bit general register */
1157             FETCH_FW(regs->GR_L(i), regs->mainstor + abs);
1158 
1159           #ifdef STACK_DEBUG
1160             logmsg (_("stack: GPR%d=" F_GREG " loaded from V:" F_VADR
1161                     " A:" F_RADR "\n"), i, regs->GR(i), lsea, abs);
1162           #endif /*STACK_DEBUG*/
1163     #endif /*!defined(FEATURE_ESAME)*/
1164         }
1165 
1166         /* Update the virtual and absolute addresses */
1167         lsea += LSSE_REGSIZE;
1168         LSEA_WRAP(lsea);
1169         abs += LSSE_REGSIZE;
1170 
1171         /* Recalculate absolute address if page boundary crossed */
1172         if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
1173             abs = abs2;
1174 
1175     } /* end for(i) */
1176 
1177 #if defined(FEATURE_ESAME)
1178     /* For ESAME, skip the next 96 bytes of the state entry */
1179     lsea += 96; abs += 96;
1180 
1181     /* Recalculate absolute address if page boundary crossed */
1182     if ((lsea & PAGEFRAME_BYTEMASK) < 96)
1183         abs = abs2 | (lsea & PAGEFRAME_BYTEMASK);
1184 #endif /*defined(FEATURE_ESAME)*/
1185 
1186     /* Load access registers from bytes 64-127 (for ESA/390), or
1187        bytes 224-280 (for ESAME) of the state entry */
1188     for (i = 0; i <= ((r1 > r2) ? 15 : r2); i++)
1189     {
1190         /* Load the access register from the stack entry */
1191         if ((r1 <= r2 && i >= r1 && i <= r2)
1192             || (r1 > r2 && (i >= r1 || i <= r2)))
1193         {
1194             FETCH_FW(regs->AR(i),regs->mainstor + abs);
1195             SET_AEA_AR(regs, i);
1196 
1197           #ifdef STACK_DEBUG
1198             logmsg (_("stack: AR%d=" F_AREG " loaded from V:" F_VADR
1199                     " A:" F_RADR "\n"), i, regs->AR(i), lsea, abs);
1200           #endif /*STACK_DEBUG*/
1201         }
1202 
1203         /* Update the virtual and absolute addresses */
1204         lsea += 4;
1205         LSEA_WRAP(lsea);
1206         abs += 4;
1207 
1208         /* Recalculate absolute address if page boundary crossed */
1209         if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
1210             abs = abs2;
1211 
1212     } /* end for(i) */
1213 
1214 } /* end function ARCH_DEP(unstack_registers) */
1215 
1216 /*-------------------------------------------------------------------*/
1217 /* Program return unstack                                            */
1218 /*                                                                   */
1219 /* Input:                                                            */
1220 /*      regs    Pointer to a copy of the CPU register context        */
1221 /* Output:                                                           */
1222 /*      lsedap  The absolute address of the entry descriptor of      */
1223 /*              the new current entry on the linkage stack.          */
1224 /*      rc      Return code from load_psw, checked later for PIC 06  */
1225 /* Return value:                                                     */
1226 /*      The type of entry unstacked: LSED_UET_BAKR or LSED_UET_PC    */
1227 /*                                                                   */
1228 /*      This function performs the restoring and updating parts      */
1229 /*      of the unstacking process for the Program Return (PR)        */
1230 /*      instruction.  If a program exception occurs during the PR    */
1231 /*      instruction (either during or after the unstack), then the   */
1232 /*      effects of the instruction must be nullified or suppressed.  */
1233 /*      This is achieved by updating a copy of the CPU register      */
1234 /*      context instead of the actual register context.              */
1235 /*      The current register context is replaced by the copy         */
1236 /*      only on successful completion of the PR instruction.         */
1237 /*                                                                   */
1238 /*      In the event of any stack error, this function generates     */
1239 /*      a program check and does not return.                         */
1240 /*-------------------------------------------------------------------*/
ARCH_DEP(program_return_unstack)1241 int ARCH_DEP(program_return_unstack) (REGS *regs, RADR *lsedap, int *rc)
1242 {
1243 QWORD   newpsw;                         /* New PSW                   */
1244 LSED    lsed;                           /* Linkage stack entry desc. */
1245 VADR    lsea;                           /* Linkage stack entry addr  */
1246 RADR    abs;                            /* Absolute address          */
1247 int     permode;                        /* 1=PER mode is set in PSW  */
1248 U16     pkm;                            /* PSW key mask              */
1249 U16     sasn;                           /* Secondary ASN             */
1250 U16     eax;                            /* Extended AX               */
1251 U16     pasn;                           /* Primary ASN               */
1252 VADR    lsep;                           /* Virtual addr of entry desc.
1253                                            of previous stack entry   */
1254 
1255     /* Find the virtual address of the entry descriptor
1256        of the current state entry in the linkage stack */
1257     lsea = ARCH_DEP(locate_stack_entry) (1, &lsed, regs);
1258 
1259     /* [5.12.4.3] Restore information from stack entry */
1260 
1261     /* Load registers 2-14 from the stack entry */
1262     ARCH_DEP(unstack_registers) (1, lsea, 2, 14, regs);
1263 
1264     /* Point back to the entry descriptor of previous stack entry */
1265     lsep = lsea - LSSE_SIZE;
1266     LSEA_WRAP(lsep);
1267 
1268     /* Point back to byte 128 of the current state entry */
1269     lsea -= LSSE_SIZE - sizeof(LSED);
1270     lsea += 128;
1271     LSEA_WRAP(lsea);
1272 
1273     /* Translate virtual address to absolute address */
1274     abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
1275 
1276     /* For a call state entry, replace the PKM, SASN, EAX, and PASN */
1277     if ((lsed.uet & LSED_UET_ET) == LSED_UET_PC)
1278     {
1279         /* Fetch the PKM from bytes 128-129 of the stack entry */
1280         FETCH_HW(pkm,regs->mainstor + abs);
1281 
1282         /* Fetch the SASN from bytes 130-131 of the stack entry */
1283         FETCH_HW(sasn,regs->mainstor + abs + 2);
1284 
1285         /* Fetch the EAX from bytes 132-133 of the stack entry */
1286         FETCH_HW(eax,regs->mainstor + abs + 4);
1287 
1288         /* Fetch the PASN from bytes 134-135 of the stack entry */
1289         FETCH_HW(pasn,regs->mainstor + abs + 6);
1290 
1291       #ifdef STACK_DEBUG
1292         logmsg (_("stack: PKM=%2.2X%2.2X SASN=%2.2X%2.2X "
1293                 "EAX=%2.2X%2.2X PASN=%2.2X%2.2X \n"
1294                 "loaded from V:" F_VADR " A:" F_RADR "\n"),
1295                 regs->mainstor[abs], regs->mainstor[abs+1],
1296                 regs->mainstor[abs+2], regs->mainstor[abs+3],
1297                 regs->mainstor[abs+4], regs->mainstor[abs+5],
1298                 regs->mainstor[abs+6], regs->mainstor[abs+7],
1299                 lsea, abs);
1300       #endif /*STACK_DEBUG*/
1301 
1302         /* Load PKM into CR3 bits 0-15 (32-47) */
1303         regs->CR_LHH(3) = pkm;
1304 
1305         /* Load SASN into CR3 bits 16-31 (48-63) */
1306         regs->CR_LHL(3) = sasn;
1307 
1308         /* Load EAX into CR8 bits 0-15 (32-47) */
1309         regs->CR_LHH(8) = eax;
1310 
1311         /* Load PASN into CR4 bits 16-31 (48-63) */
1312         regs->CR_LHL(4) = pasn;
1313 
1314     } /* end if(LSED_UET_PC) */
1315 
1316     /* Update virtual and absolute addresses to point to byte 136 */
1317     lsea += 8;
1318     LSEA_WRAP(lsea);
1319     abs += 8;
1320 
1321     /* Recalculate absolute address if page boundary crossed */
1322     if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
1323         abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
1324 
1325     /* Save the PER mode bit from the current PSW */
1326     permode = (regs->psw.sysmask & PSW_PERMODE) ? 1 : 0;
1327 
1328   #ifdef STACK_DEBUG
1329     logmsg (_("stack: PSW=%2.2X%2.2X%2.2X%2.2X %2.2X%2.2X%2.2X%2.2X "
1330             "loaded from V:" F_VADR " A:" F_RADR "\n"),
1331             regs->mainstor[abs], regs->mainstor[abs+1],
1332             regs->mainstor[abs+2], regs->mainstor[abs+3],
1333             regs->mainstor[abs+4], regs->mainstor[abs+5],
1334             regs->mainstor[abs+6], regs->mainstor[abs+7],
1335             lsea, abs);
1336   #endif /*STACK_DEBUG*/
1337 
1338     /* Copy PSW bits 0-63 from bytes 136-143 of the stack entry */
1339     memcpy (newpsw, regs->mainstor + abs, 8);
1340 
1341 #if defined(FEATURE_ESAME)
1342     /* For ESAME, advance to byte 168 of the stack entry */
1343     lsea += 32;
1344     LSEA_WRAP(lsea);
1345     abs += 32;
1346 
1347     /* Recalculate absolute address if page boundary crossed */
1348     if ((lsea & PAGEFRAME_BYTEMASK) < 32)
1349         abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
1350 
1351     /* Copy ESAME PSW bits 64-127 from bytes 168-175 */
1352     memcpy (newpsw + 8, regs->mainstor + abs, 8);
1353 
1354     /* Update virtual and absolute addresses to point to byte 176 */
1355     lsea += 8;
1356     LSEA_WRAP(lsea);
1357     abs += 8;
1358 
1359     /* Recalculate absolute address if page boundary crossed */
1360     if ((lsea & PAGEFRAME_BYTEMASK) == 0x000)
1361         abs = ARCH_DEP(abs_stack_addr) (lsea, regs, ACCTYPE_READ);
1362 
1363     /* For a call state entry only, if ASN-and-LX-reuse is installed and
1364        active, load the SASTEIN (high word of CR3) from bytes 176-179,
1365        and load the PASTEIN (high word of CR4) from bytes 180-183 */
1366     if ((lsed.uet & LSED_UET_ET) == LSED_UET_PC
1367         && ASN_AND_LX_REUSE_ENABLED(regs))
1368     {
1369         FETCH_FW(regs->CR_H(3), regs->mainstor + abs);
1370         FETCH_FW(regs->CR_H(4), regs->mainstor + abs + 4);
1371 
1372       #ifdef STACK_DEBUG
1373         logmsg (_("stack: SASTEIN=%2.2X%2.2X%2.2X%2.2X "
1374                 "PASTEIN=%2.2X%2.2X%2.2X%2.2X \n"
1375                 "loaded from V:" F_VADR " A:" F_RADR "\n"),
1376                 regs->mainstor[abs], regs->mainstor[abs+1],
1377                 regs->mainstor[abs+2], regs->mainstor[abs+3],
1378                 regs->mainstor[abs+4], regs->mainstor[abs+5],
1379                 regs->mainstor[abs+6], regs->mainstor[abs+7],
1380                 lsea, abs);
1381       #endif /*STACK_DEBUG*/
1382 
1383     } /* end if(LSED_UET_PC && ASN_AND_LX_REUSE_ENABLED) */
1384 
1385 #endif /*defined(FEATURE_ESAME)*/
1386 
1387     /* [5.12.4.4] Pass back the absolute address of the entry
1388        descriptor of the preceding linkage stack entry.  The
1389        next entry size field of this entry will be cleared on
1390        successful completion of the PR instruction */
1391     *lsedap = ARCH_DEP(abs_stack_addr) (lsep, regs, ACCTYPE_WRITE);
1392 
1393     /* [5.12.4.5] Update CR15 to point to the previous entry */
1394     regs->CR(15) = lsep & CR15_LSEA;
1395 
1396     /* Load new PSW using the bytes extracted from the stack entry */
1397     /* The rc will be checked by calling routine for PIC 06        */
1398     *rc = ARCH_DEP(load_psw) (regs, newpsw);
1399 
1400     /* Restore the PER mode bit from the current PSW */
1401     if (permode)
1402         regs->psw.sysmask |= PSW_PERMODE;
1403     else
1404         regs->psw.sysmask &= ~PSW_PERMODE;
1405 
1406     /* restore PER masks which could have been wiped out by load_psw */
1407     SET_IC_MASK(regs);
1408 
1409 #ifdef STACK_DEBUG
1410     logmsg (_("stack: CR15=" F_CREG "\n"), regs->CR(15));
1411 #endif /*STACK_DEBUG*/
1412 
1413     /* Return the entry type of the unstacked state entry */
1414     return (lsed.uet & LSED_UET_ET);
1415 
1416 } /* end function ARCH_DEP(program_return_unstack) */
1417 
1418 
1419 #endif /*defined(FEATURE_LINKAGE_STACK)*/
1420 
1421 
1422 #if !defined(_GEN_ARCH)
1423 
1424 #if defined(_ARCHMODE2)
1425  #define  _GEN_ARCH _ARCHMODE2
1426  #include "stack.c"
1427 #endif
1428 
1429 #if defined(_ARCHMODE3)
1430  #undef   _GEN_ARCH
1431  #define  _GEN_ARCH _ARCHMODE3
1432  #include "stack.c"
1433 #endif
1434 
1435 #endif /*!defined(_GEN_ARCH)*/
1436