IFND POWERPC_POWERPC_I POWERPC_POWERPC_I SET 1 ** ** $VER: PowerPC.i 15.0 (13.3.99) ** ** Hardware and communication related structures and macros ** for the powerpc.library ** IFND POWERPC_PPCMACROS_I include powerpc/ppcmacros.i ENDC IFND EXEC_TYPES_I include exec/types.i ENDC IFND UTILITY_TAGITEM_I include utility/tagitem.i ENDC IFND POWERPCLIB_V7 ;only for V8+ **** tagitem values for GetHALInfo (V14+) ENUM TAG_USER+$103000 EITEM HINFO_ALEXC_HIGH ;High word of emulated ;alignment exceptions EITEM HINFO_ALEXC_LOW ;Low word of ... **** tagitem values for SetScheduling (V14+) ENUM TAG_USER+$104000 EITEM SCHED_REACTION ;reaction of low activity tasks **** tagitem values for GetInfo ENUM TAG_USER+$102000 EITEM PPCINFO_CPU ;CPU type (see below) EITEM PPCINFO_PVR ;PVR value EITEM PPCINFO_ICACHE ;Instruction cache state EITEM PPCINFO_DCACHE ;Data cache state EITEM PPCINFO_PAGETABLE ;Page table location EITEM PPCINFO_TABLESIZE ;Page table size EITEM PPCINFO_BUSCLOCK ;PPC bus clock EITEM PPCINFO_CPUCLOCK ;PPC CPU clock EITEM PPCINFO_CPULOAD ;Total CPU usage *100 [%] EITEM PPCINFO_SYSTEMLOAD ;Total system load *100 [%] **** PPCINFO_ICACHE / PPCINFO_DCACHE BITDEF CACHE,ON_UNLOCKED,0 ;cache is on and unlocked BITDEF CACHE,ON_LOCKED,1 ;cache is on and locked BITDEF CACHE,OFF_UNLOCKED,2 ;cache is off and unlocked BITDEF CACHE,OFF_LOCKED,3 ;cache is off and locked **** Cache flags (required by SetCache/SetCache68K) CACHE_DCACHEOFF = 1 CACHE_DCACHEON = 2 CACHE_DCACHELOCK = 3 CACHE_DCACHEUNLOCK = 4 CACHE_DCACHEFLUSH = 5 CACHE_ICACHEOFF = 6 CACHE_ICACHEON = 7 CACHE_ICACHELOCK = 8 CACHE_ICACHEUNLOCK = 9 CACHE_ICACHEINV = 10 CACHE_DCACHEINV = 11 **** Hardware flags (required by SetHardware) HW_TRACEON = 1 ;enable singlestep mode HW_TRACEOFF = 2 ;disable singlestep mode HW_BRANCHTRACEON = 3 ;enable branch trace mode HW_BRANCHTRACEOFF = 4 ;disable branch trace mode HW_FPEXCON = 5 ;enable FP exceptions HW_FPEXCOFF = 6 ;disable FP exceptions HW_SETIBREAK = 7 ;set instruction breakpoint HW_CLEARIBREAK = 8 ;clear instruction breakpoint HW_SETDBREAK = 9 ;set data breakpoint (604[E] only) HW_CLEARDBREAK = 10 ;clear data breakpoint (604[E] only) **** return values of SetHardware HW_AVAILABLE = -1 ;feature available HW_NOTAVAILABLE = 0 ;feature not available **** return values of GetPPCState BITDEF PPCSTATE,POWERSAVE,0 ;PPC is in power save mode BITDEF PPCSTATE,APPACTIVE,1 ;PPC application tasks are active BITDEF PPCSTATE,APPRUNNING,2 ;PPC application task is running **** FP flags (required by ModifyFPExc) BITDEF FP,EN_OVERFLOW,0 ;enable overflow exception BITDEF FP,EN_UNDERFLOW,1 ;enable underflow exception BITDEF FP,EN_ZERODIVIDE,2 ;enable zerodivide exception BITDEF FP,EN_INEXACT,3 ;enable inexact op. exception BITDEF FP,EN_INVALID,4 ;enable invalid op. exception BITDEF FP,DIS_OVERFLOW,5 ;disable overflow exception BITDEF FP,DIS_UNDERFLOW,6 ;disable underflow exception BITDEF FP,DIS_ZERODIVIDE,7 ;disable zerodivide exception BITDEF FP,DIS_INEXACT,8 ;disable inexact op. exception BITDEF FP,DIS_INVALID,9 ;disable invalid op. exception FPF_ENABLEALL = $0000001f ;enable all FP exceptions FPF_DISABLEALL = $000003e0 ;disable all FP exceptions **** tags passed to SetExcHandler (exception handler attributes) ENUM TAG_USER+$101000 EITEM EXCATTR_CODE ;-> exception code (required) EITEM EXCATTR_DATA ;exception data EITEM EXCATTR_TASK ;task if task dependant exc. ;0 for current task EITEM EXCATTR_EXCID ;exception ID EITEM EXCATTR_FLAGS ;see below EITEM EXCATTR_NAME ;identification name EITEM EXCATTR_PRI ;handler priority **** EXCATTR_FLAGS (either EXC_GLOBAL or EXC_LOCAL, resp. * EXC_SMALLCONTEXT or EXC_LARGECONTEXT must be * specified) BITDEF EXC,GLOBAL,0 ;global handler BITDEF EXC,LOCAL,1 ;task dependant handler BITDEF EXC,SMALLCONTEXT,2 ;small context structure BITDEF EXC,LARGECONTEXT,3 ;large context structure BITDEF EXC,ACTIVE,4 ;private **** EXCATTR_EXCID (Exception ID) BITDEF EXC,MCHECK,2 ;machine check exception BITDEF EXC,DACCESS,3 ;data access exception BITDEF EXC,IACCESS,4 ;instruction access exception BITDEF EXC,INTERRUPT,5 ;external interrupt (V15+) BITDEF EXC,ALIGN,6 ;alignment exception BITDEF EXC,PROGRAM,7 ;program exception BITDEF EXC,FPUN,8 ;FP unavailable exception BITDEF EXC,TRACE,13 ;trace exception BITDEF EXC,PERFMON,15 ;performance monitor exception BITDEF EXC,IABR,19 ;IA breakpoint exception **** Large exception context structure (if EXCATTR_LARGECONTEXT was set) STRUCTURE EXCCONTEXT,0 ULONG EC_EXCID ;exception ID (see above) ULONG EC_SRR0 ;process' program counter ULONG EC_SRR1 ;process' context ULONG EC_DAR ;DAR register ULONG EC_DSISR ;DSISR register ULONG EC_CR ;condition register ULONG EC_CTR ;count register ULONG EC_LR ;link register ULONG EC_XER ;integer exception register ULONG EC_FPSCR ;FP status register STRUCT EC_GPR,32*4 ;r0 - r31 STRUCT EC_FPR,32*8 ;f0 - f31 LABEL EC_SIZE ;don't depend on this size **** Symbolic offsets into the register arrays __r0 = 0*4 __r1 = 1*4 __r2 = 2*4 __r3 = 3*4 __r4 = 4*4 __r5 = 5*4 __r6 = 6*4 __r7 = 7*4 __r8 = 8*4 __r9 = 9*4 __r10 = 10*4 __r11 = 11*4 __r12 = 12*4 __r13 = 13*4 __r14 = 14*4 __r15 = 15*4 __r16 = 16*4 __r17 = 17*4 __r18 = 18*4 __r19 = 19*4 __r20 = 20*4 __r21 = 21*4 __r22 = 22*4 __r23 = 23*4 __r24 = 24*4 __r25 = 25*4 __r26 = 26*4 __r27 = 27*4 __r28 = 28*4 __r29 = 29*4 __r30 = 30*4 __r31 = 31*4 __f0 = 0*8 __f1 = 1*8 __f2 = 2*8 __f3 = 3*8 __f4 = 4*8 __f5 = 5*8 __f6 = 6*8 __f7 = 7*8 __f8 = 8*8 __f9 = 9*8 __f10 = 10*8 __f11 = 11*8 __f12 = 12*8 __f13 = 13*8 __f14 = 14*8 __f15 = 15*8 __f16 = 16*8 __f17 = 17*8 __f18 = 18*8 __f19 = 19*8 __f20 = 20*8 __f21 = 21*8 __f22 = 22*8 __f23 = 23*8 __f24 = 24*8 __f25 = 25*8 __f26 = 26*8 __f27 = 27*8 __f28 = 28*8 __f29 = 29*8 __f30 = 30*8 __f31 = 31*8 **** Small exception context structure (if EXCATTR_SMALLCONTEXT was set) STRUCTURE XCONTEXT,0 ULONG XCO_EXCID ;exception ID (see above) ULONG XCO_R3 ;r3 LABEL XCO_SIZE ;don't depend on this size **** Possible return values for exception handlers EXCRETURN_NORMAL = 0 ;allow the next exc handlers to complete EXCRETURN_ABORT = 1 ;exception is immediately leaved, all ;other exception handlers are ignored ENDC ;POWERPCLIB_V7 **** PPCINFO_CPU (returned by GetCPU and GetInfo) BITDEF CPU,603,4 BITDEF CPU,603E,8 BITDEF CPU,604,12 BITDEF CPU,604E,16 BITDEF CPU,620,20 BITDEF CPU,G3,21 BITDEF CPU,G4,22 BITDEF CPU,G5,23 **** PowerPC Structure transferred to RunPPC, WaitforPPC, **** Run68K and WaitFor68K STRUCTURE PP,0 APTR PP_CODE ;Ptr to PPC code ULONG PP_OFFSET ;Offset to PP_CODE ULONG PP_FLAGS ;flags (see below) APTR PP_STACKPTR ;stack pointer ULONG PP_STACKSIZE ;stack size STRUCT PP_REGS,15*4 ;15 registers (d0-a6) STRUCT PP_FREGS,8*8 ;8 registers (fp0-fp7) LABEL PP_SIZE **** PP_FLAGS BITDEF PP,ASYNC,0 ;call PPC/68K in asynchrone mode BITDEF PP,LINEAR,1 ;pass r3-r10/f1-f8 (V15+) BITDEF PP,THROW,2 ;throw exception before entering function **** status returned by RunPPC, WaitForPPC, Run68K and WaitFor68K PPERR_SUCCESS = 0 ;success PPERR_ASYNCERR = 1 ;synchron call after asynchron call PPERR_WAITERR = 2 ;WaitFor[PPC/68K] after synchron call **** 68K-Assembler macro to open the powerpc.library * * Usage: OPENPOWERPC [Version] * * note: The macro POWERDATA (see below) must be defined * The base of the exec.library must be defined under the name * _SysBase OPENPOWERPC macro movem.l d0/d1/a0/a1/a6,-(sp) IFC "","\1" moveq #0,d0 ELSEIF move.l #\1,d0 ENDC lea powerpcname,a1 move.l _SysBase,a6 jsr -552(a6) move.l d0,_PowerPCBase movem.l (sp)+,d0/d1/a0/a1/a6 endm **** 68K-Assembler macro to close the powerpc.library * * Usage: CLOSEPOWERPC * * note: The macro POWERDATA (see below) must be defined * The base of the exec.library must be defined under the name * _SysBase CLOSEPOWERPC macro movem.l d0/d1/a0/a1/a6,-(sp) move.l _SysBase,a6 move.l _PowerPCBase,d0 beq.b .noclose\@ move.l d0,a1 jsr -414(a6) .noclose\@ movem.l (sp)+,d0/d1/a0/a1/a6 endm **** 68K-Assembler macro to run a PPC function * * Usage: RUNPOWERPC_XL Function,[Offset,[Flags,[StackSize,[FPU]]]] * * note: a4 MUST point to the small data section (resp. * must have the value _LinkerDB) RUNPOWERPC_XL macro lea -(PP_SIZE-PP_REGS-15*4)(sp),sp movem.l d0-a6,-(sp) lea -PP_REGS(sp),a0 move.l a0,sp IFC "FPU","\5" lea PP_FREGS(a0),a1 fmove.d fp0,(a1)+ fmove.d fp1,(a1)+ fmove.d fp2,(a1)+ fmove.d fp3,(a1)+ fmove.d fp4,(a1)+ fmove.d fp5,(a1)+ fmove.d fp6,(a1)+ fmove.d fp7,(a1)+ ENDC IFNC "","\2" move.l \1,a1 move.l _LVO\2+2(a1),PP_CODE(a0) move.l a1,PP_REGS+0*4(a0) ELSEIF XREF @_\1 move.l @_\1,a1 ; lea \1,a1 move.l a1,PP_CODE(a0) ENDC clr.l PP_OFFSET(a0) IFC "","\3" clr.l PP_FLAGS(a0) ELSEIF move.l #\3,PP_FLAGS(a0) ENDC IFC "","\4" clr.l PP_STACKPTR(a0) clr.l PP_STACKSIZE(a0) ELSEIF move.l sp,PP_STACKPTR(a0) add.l #PP_SIZE,PP_STACKPTR(a0) move.l #\4,PP_STACKSIZE(a0) ENDC move.l _PowerPCBase,a6 jsr -30(a6) ;RunPPC IFC "FPU","\5" lea PP_FREGS(sp),a0 fmove.d (a0)+,fp0 fmove.d (a0)+,fp1 fmove.d (a0)+,fp2 fmove.d (a0)+,fp3 fmove.d (a0)+,fp4 fmove.d (a0)+,fp5 fmove.d (a0)+,fp6 fmove.d (a0)+,fp7 ENDC lea PP_REGS(sp),sp movem.l (sp),d0-a6 lea (PP_SIZE-PP_REGS)(sp),sp endm **** 68K-Assembler macro to run a PPC function (quick version) * * Usage: RUNPOWERPC Function,[Offset[Flags,[,FPU]]] * * note: a4 MUST point to the small data section (resp. * must have the value _LinkerDB) * * this macro does only transfer d0/d1/a0/a1 (and fp0/fp1 with * FPU-Option). No stack is transferred. The only return parameter * is d0 (fp0/fp1 with FPU-Option). d1/a0/a1 are trashed. RUNPOWERPC macro lea -PP_SIZE(sp),sp move.l d0,PP_REGS(sp) move.l d1,PP_REGS+1*4(sp) move.l a0,PP_REGS+8*4(sp) move.l a1,PP_REGS+9*4(sp) move.l a4,PP_REGS+12*4(sp) move.l sp,a0 IFC "FPU","\5" fmove.d fp0,PP_FREGS(a0) fmove.d fp1,PP_FREGS+1*8(a0) ENDC IFNC "","\2" move.l \1,a1 move.l _LVO\2+2(a1),PP_CODE(a0) move.l a1,PP_REGS+0*4(a0) ELSEIF XREF @_\1 move.l @_\1,a1 ; lea \1,a1 move.l a1,PP_CODE(a0) ENDC clr.l PP_OFFSET(a0) IFC "","\3" clr.l PP_FLAGS(a0) ELSEIF move.l #\3,PP_FLAGS(a0) ENDC clr.l PP_STACKPTR(a0) clr.l PP_STACKSIZE(a0) move.l _PowerPCBase,a6 jsr -30(a6) ;RunPPC IFC "FPU","\5" fmove.d PP_FREGS(sp),fp0 fmove.d PP_FREGS+1*8(sp),fp1 ENDC move.l PP_REGS(sp),d0 lea PP_SIZE(sp),sp endm **** 68K-Assembler macro to wait for an asynchron PPC process * * Usage: WAITFORPPC_XL [FPU] * WAITFORPPC_XL macro lea -PP_SIZE(sp),sp move.l sp,a0 move.l _PowerPCBase,a6 jsr -36(a6) ;WaitForPPC cmp.l #PPERR_SUCCESS,d0 beq.b .success\@ lea PP_SIZE(sp),sp bra.b .exit\@ .success\@ IFC "FPU","\1" lea PP_FREGS(sp),a0 fmove.d (a0)+,fp0 fmove.d (a0)+,fp1 fmove.d (a0)+,fp2 fmove.d (a0)+,fp3 fmove.d (a0)+,fp4 fmove.d (a0)+,fp5 fmove.d (a0)+,fp6 fmove.d (a0)+,fp7 ENDC lea PP_REGS(sp),sp movem.l (sp),d0-a6 lea (PP_SIZE-PP_REGS)(sp),sp .exit\@ endm **** 68K-Assembler macro to wait for an asynchron PPC process * (quick version) * * Usage: WAITFORPPC [FPU] * * The only return parameter is d0 (fp0/fp1 with FPU-Option). * d1/a0/a1 are trashed. WAITFORPPC macro lea -PP_SIZE(sp),sp move.l sp,a0 move.l _PowerPCBase,a6 jsr -36(a6) ;WaitForPPC cmp.l #PPERR_SUCCESS,d0 bne.b .exit\@ IFC "FPU","\1" fmove.d PP_FREGS(sp),fp0 fmove.d PP_FREGS+1*8(sp),fp1 ENDC move.l PP_REGS(sp),d0 .exit\@ lea PP_SIZE(sp),sp endm **** 68K-Assembler macro to define some variables required by * some other macros (see above) * * Usage: POWERDATA POWERDATA macro _PowerPCBase dc.l 0 powerpcname dc.b "powerpc.library",0 cnop 0,4 endm **** PPC-Assembler macro to run a 68K function * * Usage: RUN68K_XL Function,[Offset,[Flags,[StackSize,[FPU]]]] * * note: the local stackpointer must be properly initialized * this macro needs currently 148 bytes of local stack space * The base of the powerpc.library must be defined under the name * _PowerPCBase * * r7-r10 are trashed RUN68K_XL MACRO push _a6 subi local,local,PP_SIZE stw _d0,PP_REGS(local) stw _d1,PP_REGS+1*4(local) stw _d2,PP_REGS+2*4(local) stw _d3,PP_REGS+3*4(local) stw _d4,PP_REGS+4*4(local) stw _d5,PP_REGS+5*4(local) stw _d6,PP_REGS+6*4(local) stw _d7,PP_REGS+7*4(local) stw _a0,PP_REGS+8*4(local) stw _a1,PP_REGS+9*4(local) stw _a2,PP_REGS+10*4(local) stw _a3,PP_REGS+11*4(local) stw _a4,PP_REGS+12*4(local) stw _a5,PP_REGS+13*4(local) IFC "FPU","\5" stfd _fp0,PP_FREGS(local) stfd _fp1,PP_FREGS+1*8(local) stfd _fp2,PP_FREGS+2*8(local) stfd _fp3,PP_FREGS+3*8(local) stfd _fp4,PP_FREGS+4*8(local) stfd _fp5,PP_FREGS+5*8(local) stfd _fp6,PP_FREGS+6*8(local) stfd _fp7,PP_FREGS+7*8(local) ENDC IFNC "","\2" lw _d0,\1 stw _d0,PP_CODE(local) stw _d0,PP_REGS+14*4(local) li _d0,_LVO\2 ELSEIF stw _a6,PP_REGS+14*4(local) lw _d0,.routine\@ stw _d0,PP_CODE(local) li _d0,0 ENDC stw _d0,PP_OFFSET(local) IFC "","\3" li _d0,0 ELSEIF liw _d0,\3 ENDC stw _d0,PP_FLAGS(local) IFC "","\4" li _d0,0 stw _d0,PP_STACKPTR(local) ELSEIF stw stack,PP_STACKPTR(local) liw _d0,\4 ENDC stw _d0,PP_STACKSIZE(local) mr r4,local lw r3,_PowerPCBase lwz r0,-300+2(r3) ;Run68K mtlr r0 blrl IFC "FPU","\5" lfd _fp0,PP_FREGS(local) lfd _fp1,PP_FREGS+1*8(local) lfd _fp2,PP_FREGS+2*8(local) lfd _fp3,PP_FREGS+3*8(local) lfd _fp4,PP_FREGS+4*8(local) lfd _fp5,PP_FREGS+5*8(local) lfd _fp6,PP_FREGS+6*8(local) lfd _fp7,PP_FREGS+7*8(local) ENDC lwz _d0,PP_REGS(local) lwz _d1,PP_REGS+1*4(local) lwz _d2,PP_REGS+2*4(local) lwz _d3,PP_REGS+3*4(local) lwz _d4,PP_REGS+4*4(local) lwz _d5,PP_REGS+5*4(local) lwz _d6,PP_REGS+6*4(local) lwz _d7,PP_REGS+7*4(local) lwz _a0,PP_REGS+8*4(local) lwz _a1,PP_REGS+9*4(local) lwz _a2,PP_REGS+10*4(local) lwz _a3,PP_REGS+11*4(local) lwz _a4,PP_REGS+12*4(local) lwz _a5,PP_REGS+13*4(local) lwz _a6,PP_REGS+14*4(local) addi local,local,PP_SIZE pop _a6 IFC "","\2" save section "Run68K",data .routine\@ dc.l \1 restore ENDC ENDM **** PPC-Assembler macro to run a 68K function (quick version) * * Usage: RUN68K Function,[Offset,[Flags,[,FPU]]] * * note: the local stackpointer must be properly initialized * this macro needs currently 148 bytes of local stack space * The base of the powerpc.library must be defined under the name * _PowerPCBase * * this macro does only transfer _d0/_d1/_a0/_a1 (and _fp0/_fp1 with * FPU-Option). No stack is transferred. The only return parameter * is _d0 (_fp0/_fp1 with FPU-Option). r4-r10 are trashed. RUN68K MACRO push _a6 subi local,local,PP_SIZE stw _d0,PP_REGS(local) stw _d1,PP_REGS+1*4(local) stw _a0,PP_REGS+8*4(local) stw _a1,PP_REGS+9*4(local) stw _a4,PP_REGS+12*4(local) IFC "FPU","\5" stfd _fp0,PP_FREGS(local) stfd _fp1,PP_FREGS+1*8(local) ENDC IFNC "","\2" lw _d0,\1 stw _d0,PP_CODE(local) stw _d0,PP_REGS+14*4(local) li _d0,_LVO\2 ELSEIF lw _d0,.routine\@ stw _d0,PP_CODE(local) li _d0,0 ENDC stw _d0,PP_OFFSET(local) IFC "","\3" li _d0,0 ELSEIF liw _d0,\3 ENDC stw _d0,PP_FLAGS(local) li _d0,0 stw _d0,PP_STACKPTR(local) stw _d0,PP_STACKSIZE(local) mr r4,local lw r3,_PowerPCBase lwz r0,-300+2(r3) ;Run68K mtlr r0 blrl IFC "FPU","\5" lfd _fp0,PP_FREGS(local) lfd _fp1,PP_FREGS+1*8(local) ENDC lwz _d0,PP_REGS(local) addi local,local,PP_SIZE pop _a6 IFC "","\2" save section "Run68K",data .routine\@ dc.l \1 restore ENDC ENDM **** PPC-Assembler macro to wait for an asynchron 68K process * * Usage: WAITFOR68K_XL [FPU] * * r7-r10 are trashed * Important: If an AMIGA-OS library function was called using * RUN68K or RUN68K_XL then r31 contains the library base! WAITFOR68K_XL macro subi local,local,PP_SIZE mr r4,local lw r3,_PowerPCBase lwz r0,-306+2(r3) ;WaitFor68K mtlr r0 blrl liw r0,PPERR_SUCCESS cmpw r3,r0 bne .exit\@ IFC "FPU","\1" lfd _fp0,PP_FREGS(local) lfd _fp1,PP_FREGS+1*8(local) lfd _fp2,PP_FREGS+2*8(local) lfd _fp3,PP_FREGS+3*8(local) lfd _fp4,PP_FREGS+4*8(local) lfd _fp5,PP_FREGS+5*8(local) lfd _fp6,PP_FREGS+6*8(local) lfd _fp7,PP_FREGS+7*8(local) ENDC lwz _d0,PP_REGS(local) lwz _d1,PP_REGS+1*4(local) lwz _d2,PP_REGS+2*4(local) lwz _d3,PP_REGS+3*4(local) lwz _d4,PP_REGS+4*4(local) lwz _d5,PP_REGS+5*4(local) lwz _d6,PP_REGS+6*4(local) lwz _d7,PP_REGS+7*4(local) lwz _a0,PP_REGS+8*4(local) lwz _a1,PP_REGS+9*4(local) lwz _a2,PP_REGS+10*4(local) lwz _a3,PP_REGS+11*4(local) lwz _a4,PP_REGS+12*4(local) lwz _a5,PP_REGS+13*4(local) lwz _a6,PP_REGS+14*4(local) .exit\@ addi local,local,PP_SIZE endm **** PPC-Assembler macro to wait for an asynchron 68K process * (quick version) * * Usage: WAITFOR68K [FPU] * * The only return parameter is _d0 (_fp0/_fp1 with FPU-Option). * r4-r10 are trashed. WAITFOR68K macro subi local,local,PP_SIZE mr r4,local lw r3,_PowerPCBase lwz r0,-306+2(r3) ;WaitFor68K mtlr r0 blrl liw r0,PPERR_SUCCESS cmpw r3,r0 bne .exit\@ IFC "FPU","\1" lfd _fp0,PP_FREGS(local) lfd _fp1,PP_FREGS+1*8(local) ENDC lwz _d0,PP_REGS(local) .exit\@ addi local,local,PP_SIZE endm ENDC ;POWERPC_I