diff --git a/compiler/arm/aasmcpu.pas b/compiler/arm/aasmcpu.pas index 5b7755f502..5df9467229 100644 --- a/compiler/arm/aasmcpu.pas +++ b/compiler/arm/aasmcpu.pas @@ -37,7 +37,6 @@ uses { "mov reg,reg" source operand number } O_MOV_DEST = 0; - type taicpu = class(taicpu_abstract) constructor op_none(op : tasmop); @@ -60,8 +59,6 @@ uses constructor op_const_reg_const(op : tasmop;_op1 : longint;_op2 : tregister;_op3 : longint); constructor op_reg_reg_reg_reg(op : tasmop;_op1,_op2,_op3,_op4 : tregister); - constructor op_reg_bool_reg_reg(op : tasmop;_op1: tregister;_op2:boolean;_op3,_op4:tregister); - constructor op_reg_bool_reg_const(op : tasmop;_op1: tregister;_op2:boolean;_op3:tregister;_op4: longint); constructor op_reg_reg_reg_const_const(op : tasmop;_op1,_op2,_op3 : tregister;_op4,_op5 : Longint); constructor op_reg_reg_const_const_const(op : tasmop;_op1,_op2 : tregister;_op3,_op4,_op5 : Longint); @@ -77,9 +74,6 @@ uses constructor op_reg_sym_ofs(op : tasmop;_op1 : tregister;_op2:tasmsymbol;_op2ofs : longint); constructor op_sym_ofs_ref(op : tasmop;_op1 : tasmsymbol;_op1ofs:longint;const _op2 : treference); - procedure loadbool(opidx:longint;_b:boolean); - - function is_nop: boolean; override; function is_move:boolean; override; function spill_registers(list:Taasmoutput; @@ -106,20 +100,6 @@ uses cutils,rgobj; taicpu Constructors *****************************************************************************} - procedure taicpu.loadbool(opidx:longint;_b:boolean); - begin - if opidx>=ops then - ops:=opidx+1; - with oper[opidx] do - begin - if typ=top_ref then - dispose(ref); - b:=_b; - typ:=top_bool; - end; - end; - - constructor taicpu.op_none(op : tasmop); begin inherited create(op); @@ -238,6 +218,7 @@ uses cutils,rgobj; loadsymbol(0,_op3,_op3ofs); end; + constructor taicpu.op_reg_reg_ref(op : tasmop;_op1,_op2 : tregister; const _op3: treference); begin inherited create(op); @@ -251,6 +232,7 @@ uses cutils,rgobj; loadref(2,_op3); end; + constructor taicpu.op_const_reg_reg(op : tasmop;_op1 : longint;_op2, _op3 : tregister); begin inherited create(op); @@ -264,6 +246,7 @@ uses cutils,rgobj; loadreg(2,_op3); end; + constructor taicpu.op_const_reg_const(op : tasmop;_op1 : longint;_op2 : tregister;_op3 : longint); begin inherited create(op); @@ -294,36 +277,6 @@ uses cutils,rgobj; loadreg(3,_op4); end; - constructor taicpu.op_reg_bool_reg_reg(op : tasmop;_op1: tregister;_op2:boolean;_op3,_op4:tregister); - begin - inherited create(op); - if (_op1.enum = R_INTREGISTER) and (_op1.number = NR_NO) then - internalerror(2003031227); - if (_op3.enum = R_INTREGISTER) and (_op3.number = NR_NO) then - internalerror(2003031228); - if (_op4.enum = R_INTREGISTER) and (_op4.number = NR_NO) then - internalerror(2003031229); - ops:=4; - loadreg(0,_op1); - loadbool(1,_op2); - loadreg(2,_op3); - loadreg(3,_op4); - end; - - constructor taicpu.op_reg_bool_reg_const(op : tasmop;_op1: tregister;_op2:boolean;_op3:tregister;_op4: longint); - begin - inherited create(op); - if (_op1.enum = R_INTREGISTER) and (_op1.number = NR_NO) then - internalerror(2003031230); - if (_op3.enum = R_INTREGISTER) and (_op3.number = NR_NO) then - internalerror(2003031231); - ops:=4; - loadreg(0,_op1); - loadbool(0,_op2); - loadreg(0,_op3); - loadconst(0,cardinal(_op4)); - end; - constructor taicpu.op_reg_reg_reg_const_const(op : tasmop;_op1,_op2,_op3 : tregister;_op4,_op5 : Longint); begin @@ -420,7 +373,7 @@ uses cutils,rgobj; function taicpu.is_move:boolean; begin - is_move := opcode = A_MR; + is_move := opcode = A_MOV; end; @@ -430,7 +383,7 @@ uses cutils,rgobj; r:Tsupregset; var unusedregsint:Tsupregset; const spilltemplist:Tspill_temp_list): boolean; - +{$ifdef dummy} function get_insert_pos(p:Tai;huntfor1,huntfor2,huntfor3:Tsuperregister):Tai; var back:Tsupregset; @@ -748,7 +701,10 @@ uses cutils,rgobj; end; end; end; - +{$else dummy} + begin + end; +{$endif dummy} procedure InitAsm; @@ -763,6 +719,9 @@ uses cutils,rgobj; end. { $Log$ - Revision 1.1 2003-08-16 13:23:01 florian + Revision 1.2 2003-08-20 15:50:12 florian + * more arm stuff + + Revision 1.1 2003/08/16 13:23:01 florian * several arm related stuff fixed } diff --git a/compiler/arm/agarmgas.pas b/compiler/arm/agarmgas.pas index 647488a037..49b0d07a44 100644 --- a/compiler/arm/agarmgas.pas +++ b/compiler/arm/agarmgas.pas @@ -40,6 +40,13 @@ unit agarmgas; procedure WriteInstruction(hp : tai);override; end; + var + gas_reg2str : reg2strtable; + + function gas_regnum_search(const s:string):Tnewregister; + function gas_regname(const r:Tnewregister):string; + + implementation uses @@ -250,11 +257,25 @@ unit agarmgas; AsmWriteLn(s); end; + function gas_regnum_search(const s:string):Tnewregister; + begin + end; + + + function gas_regname(const r:Tnewregister):string; + begin + end; + + begin RegisterAssembler(as_arm_gas_info,TARMGNUAssembler); + gas_reg2str:=std_reg2str; end. { $Log$ - Revision 1.1 2003-08-16 13:23:01 florian + Revision 1.2 2003-08-20 15:50:12 florian + * more arm stuff + + Revision 1.1 2003/08/16 13:23:01 florian * several arm related stuff fixed } diff --git a/compiler/arm/cgcpu.pas b/compiler/arm/cgcpu.pas index f7e3e22262..e5f330fd18 100644 --- a/compiler/arm/cgcpu.pas +++ b/compiler/arm/cgcpu.pas @@ -33,7 +33,7 @@ unit cgcpu; cgbase,cgobj, aasmbase,aasmcpu,aasmtai, cpubase,cpuinfo,node,cg64f32,cginfo; - ; + type tcgarm = class(tcg) @@ -124,7 +124,7 @@ unit cgcpu; { creates the correct branch instruction for a given combination } { of asmcondflags and destination addressing mode } procedure a_jmp(list: taasmoutput; op: tasmop; - c: tasmcondflag; crval: longint; l: tasmlabel); + c: tasmcond; l: tasmlabel); end; @@ -150,12 +150,362 @@ unit cgcpu; implementation + + uses + globtype,globals,verbose,systems,cutils,symconst,symdef,symsym,rgobj,tgobj,cpupi; + + + procedure tcgarm.a_param_const(list : taasmoutput;size : tcgsize;a : aword;const locpara : tparalocation); + var + ref: treference; + begin + case locpara.loc of + LOC_REGISTER,LOC_CREGISTER: + a_load_const_reg(list,size,a,locpara.register); + LOC_REFERENCE: + begin + reference_reset(ref); + ref.base:=locpara.reference.index; + ref.offset:=locpara.reference.offset; + a_load_const_ref(list,size,a,ref); + end; + else + internalerror(2002081101); + end; + if locpara.sp_fixup<>0 then + internalerror(2002081102); + end; + + + procedure tcgarm.a_param_ref(list : taasmoutput;size : tcgsize;const r : treference;const locpara : tparalocation); + var + ref: treference; + tmpreg: tregister; + begin + case locpara.loc of + LOC_REGISTER,LOC_CREGISTER: + a_load_ref_reg(list,size,size,r,locpara.register); + LOC_REFERENCE: + begin + reference_reset(ref); + ref.base:=locpara.reference.index; + ref.offset:=locpara.reference.offset; + tmpreg := rg.getregisterint(list,size); + a_load_ref_reg(list,size,size,r,tmpreg); + a_load_reg_ref(list,size,size,tmpreg,ref); + rg.ungetregisterint(list,tmpreg); + end; + LOC_FPUREGISTER,LOC_CFPUREGISTER: + case size of + OS_F32, OS_F64: + a_loadfpu_ref_reg(list,size,r,locpara.register); + else + internalerror(2002072801); + end; + else + internalerror(2002081103); + end; + if locpara.sp_fixup<>0 then + internalerror(2002081104); + end; + + + procedure tcgarm.a_paramaddr_ref(list : taasmoutput;const r : treference;const locpara : tparalocation); + var + ref: treference; + tmpreg: tregister; + begin + case locpara.loc of + LOC_REGISTER,LOC_CREGISTER: + a_loadaddr_ref_reg(list,r,locpara.register); + LOC_REFERENCE: + begin + reference_reset(ref); + ref.base := locpara.reference.index; + ref.offset := locpara.reference.offset; + tmpreg := rg.getregisterint(list,OS_ADDR); + a_loadaddr_ref_reg(list,r,tmpreg); + a_load_reg_ref(list,OS_ADDR,OS_ADDR,tmpreg,ref); + rg.ungetregisterint(list,tmpreg); + end; + else + internalerror(2002080701); + end; + end; + + + procedure tcgarm.a_call_name(list : taasmoutput;const s : string); + begin + list.concat(taicpu.op_sym(A_BL,objectlibrary.newasmsymbol(s))); + if not(pi_do_call in current_procinfo.flags) then + internalerror(2003060703); + end; + + + procedure tcgarm.a_call_reg(list : taasmoutput;reg: tregister); + var + r : tregister; + begin + r.enum:=R_INTREGISTER; + r.number:=NR_PC; + list.concat(taicpu.op_reg_reg(A_MOV,r,reg)); + if not(pi_do_call in current_procinfo.flags) then + internalerror(2003060704); + end; + + + procedure tcgarm.a_call_ref(list : taasmoutput;const ref : treference); + var + r : tregister; + begin + r.enum:=R_INTREGISTER; + r.number:=NR_PC; + a_load_ref_reg(list,OS_ADDR,OS_ADDR,ref,r); + if not(pi_do_call in current_procinfo.flags) then + internalerror(2003060705); + end; + + + procedure tcgarm.a_op_const_reg(list : taasmoutput; Op: TOpCG; size: TCGSize; a: AWord; reg: TRegister); + begin + end; + + + procedure tcgarm.a_op_reg_reg(list : taasmoutput; Op: TOpCG; size: TCGSize; src, dst: TRegister); + begin + end; + + + procedure tcgarm.a_op_const_reg_reg(list: taasmoutput; op: TOpCg; + size: tcgsize; a: aword; src, dst: tregister); + begin + end; + + + procedure tcgarm.a_op_reg_reg_reg(list: taasmoutput; op: TOpCg; + size: tcgsize; src1, src2, dst: tregister); + begin + end; + + + function rotl(d : dword;b : byte) : dword; + begin + result=(d shr (32-b)) or (d shl b); + end; + + + function is_shifter_const(d : dword;var imm_shift : byte) : boolean; + var + i : longint; + begin + for i:=0 to 15 do + begin + if (d and not(rotl($ff,i)))=0 then + begin + imm_shift:=i; + result:=true; + exit; + end; + end; + result:=false; + end; + + + procedure a_load_const_reg(list : taasmoutput; size: tcgsize; a : aword;reg : tregister);override; + var + imm_shift : byte; + l : tasmlabel; + hr : treference; + begin + if not(size in [OS_8,OS_S8,OS_16,OS_S16,OS_32,OS_S32]) then + internalerror(2002090902); + if is_shifter_const(a,imm_shift) then + list.concat(taicpu.op_reg_const(A_MOV,reg,a)) + else if is_shifter_const(not(a),imm_shift) then + list.concat(taicpu.op_reg_const(A_MVN,reg,not(a))) + else + begin + objectlibrary.getdatalabel(l); + aktlocaldata.concat(Tai_const_symbol.Create(l)); + aktlocaldata.concat(Tai_const.Create_32bit(a)); + reference_reset(hr); + hr.symbol:=l; + list.concat(taicpu.op_reg_ref(A_LDR,reg,hr)); + end; + end; + + + procedure tcgarm.a_load_reg_ref(list : taasmoutput; fromsize, tosize: tcgsize; reg : tregister;const ref : treference); + begin + end; + + + procedure tcgarm.a_load_ref_reg(list : taasmoutput; fromsize, tosize : tcgsize;const Ref : treference;reg : tregister); + begin + end; + + + procedure tcgarm.a_load_reg_reg(list : taasmoutput; fromsize, tosize : tcgsize;reg1,reg2 : tregister); + begin + end; + + + procedure tcgarm.a_loadfpu_reg_reg(list: taasmoutput; size: tcgsize; reg1, reg2: tregister); + begin + end; + + + procedure tcgarm.a_loadfpu_ref_reg(list: taasmoutput; size: tcgsize; const ref: treference; reg: tregister); + begin + end; + + + procedure tcgarm.a_loadfpu_reg_ref(list: taasmoutput; size: tcgsize; reg: tregister; const ref: treference); + begin + end; + + + { comparison operations } + procedure tcgarm.a_cmp_const_reg_label(list : taasmoutput;size : tcgsize;cmp_op : topcmp;a : aword;reg : tregister; + l : tasmlabel); + begin + end; + + + procedure tcgarm.a_cmp_reg_reg_label(list : taasmoutput;size : tcgsize;cmp_op : topcmp;reg1,reg2 : tregister;l : tasmlabel); + begin + end; + + + procedure tcgarm.a_jmp_always(list : taasmoutput;l: tasmlabel); + begin + end; + + + procedure tcgarm.a_jmp_flags(list : taasmoutput;const f : TResFlags;l: tasmlabel); + begin + end; + + + procedure tcgarm.g_flags2reg(list: taasmoutput; size: TCgSize; const f: TResFlags; reg: TRegister); + begin + end; + + + procedure tcgarm.g_copyvaluepara_openarray(list : taasmoutput;const ref, lenref:treference;elesize:integer); + begin + end; + + + procedure tcgarm.g_stackframe_entry(list : taasmoutput;localsize : longint); + begin + end; + + + procedure tcgarm.g_return_from_proc(list : taasmoutput;parasize : aword); + begin + end; + + + procedure tcgarm.g_restore_frame_pointer(list : taasmoutput); + begin + end; + + + procedure tcgarm.a_loadaddr_ref_reg(list : taasmoutput;const ref : treference;r : tregister); + begin + end; + + + procedure tcgarm.g_concatcopy(list : taasmoutput;const source,dest : treference;len : aword; delsource,loadref : boolean); + begin + end; + + + procedure tcgarm.g_overflowcheck(list: taasmoutput; const l: tlocation; def: tdef); + begin + end; + + + procedure tcgarm.g_save_standard_registers(list : taasmoutput; usedinproc : Tsupregset); + begin + end; + + + procedure tcgarm.g_restore_standard_registers(list : taasmoutput; usedinproc : Tsupregset); + begin + end; + + + procedure tcgarm.g_save_all_registers(list : taasmoutput); + begin + end; + + + procedure tcgarm.g_restore_all_registers(list : taasmoutput;accused,acchiused:boolean); + begin + end; + + + procedure tcgarm.a_jmp_cond(list : taasmoutput;cond : TOpCmp;l: tasmlabel); + begin + end; + + + procedure tcgarm.g_stackframe_entry_sysv(list : taasmoutput;localsize : longint); + begin + end; + + + procedure tcgarm.g_return_from_proc_sysv(list : taasmoutput;parasize : aword); + begin + end; + + + procedure tcgarm.g_stackframe_entry_aix(list : taasmoutput;localsize : longint); + begin + end; + + + procedure tcgarm.g_return_from_proc_aix(list : taasmoutput;parasize : aword); + begin + end; + + + procedure tcgarm.g_stackframe_entry_mac(list : taasmoutput;localsize : longint); + begin + end; + + + procedure tcgarm.g_return_from_proc_mac(list : taasmoutput;parasize : aword); + begin + end; + + + { contains the common code of a_load_reg_ref and a_load_ref_reg } + procedure tcgarm.a_load_store(list:taasmoutput;op: tasmop;reg:tregister; + ref: treference); + begin + end; + + + { creates the correct branch instruction for a given combination } + { of asmcondflags and destination addressing mode } + procedure tcgarm.a_jmp(list: taasmoutput; op: tasmop; + c: tasmcond; l: tasmlabel); + begin + end; + + begin cg := tcgarm.create; cg64 :=tcg64farm.create; end. { $Log$ - Revision 1.1 2003-07-21 16:35:30 florian + Revision 1.2 2003-08-20 15:50:12 florian + * more arm stuff + + Revision 1.1 2003/07/21 16:35:30 florian * very basic stuff for the arm } diff --git a/compiler/arm/cpubase.pas b/compiler/arm/cpubase.pas index c017a928e0..f7039c5bb3 100644 --- a/compiler/arm/cpubase.pas +++ b/compiler/arm/cpubase.pas @@ -113,6 +113,7 @@ uses NR_R9 = $0A00; NR_R10 = $0B00; NR_R11 = $0C00; NR_R12 = $0D00; NR_R13 = $0E00; NR_R14 = $0F00; NR_R15 = $1000; + NR_PC = NR_R15; { Super registers: } RS_NONE=$00; @@ -128,6 +129,7 @@ uses { registers which may be destroyed by calls } VOLATILE_INTREGISTERS = [RS_R0..RS_R3]; + VOLATILE_FPUREGISTERS = [R_F0..R_F3]; { Number of first and last imaginary register. } first_imreg = $21; @@ -386,6 +388,7 @@ uses { c_countusableregsxxx = amount of registers in the usableregsxxx set } maxintregs = 15; + maxintscratchregs = 2; intregs = [R_R0..R_R14]; usableregsint = [RS_R4..RS_R10]; c_countusableregsint = 7; @@ -628,7 +631,10 @@ implementation end. { $Log$ - Revision 1.3 2003-08-16 13:23:01 florian + Revision 1.4 2003-08-20 15:50:13 florian + * more arm stuff + + Revision 1.3 2003/08/16 13:23:01 florian * several arm related stuff fixed Revision 1.2 2003/07/26 00:55:57 florian diff --git a/compiler/arm/cpupi.pas b/compiler/arm/cpupi.pas new file mode 100644 index 0000000000..afece847a1 --- /dev/null +++ b/compiler/arm/cpupi.pas @@ -0,0 +1,132 @@ +{ + $Id$ + Copyright (c) 2002 by Florian Klaempfl + + This unit contains the CPU specific part of tprocinfo + + This program is free software; you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation; either version 2 of the License, or + (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program; if not, write to the Free Software + Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. + + **************************************************************************** +} + +{ This unit contains the CPU specific part of tprocinfo. } +unit cpupi; + +{$i fpcdefs.inc} + + interface + + uses + cutils, + cgbase,cpuinfo,psub; + + type + tarmprocinfo = class(tcgprocinfo) + { max. of space need for parameters, currently used by the PowerPC port only } + maxpushedparasize : aword; + constructor create(aparent:tprocinfo);override; + procedure handle_body_start;override; + procedure after_pass1;override; + procedure allocate_push_parasize(size: longint);override; + function calc_stackframe_size:longint;override; + end; + + + implementation + + uses + globtype,globals,systems, + cpubase, + aasmtai, + tgobj, + symconst,symsym,paramgr; + + constructor tarmprocinfo.create(aparent:tprocinfo); + + begin + inherited create(aparent); + maxpushedparasize:=0; + end; + + + procedure tarmprocinfo.handle_body_start; + var + ofs : aword; + begin + if not(po_assembler in procdef.procoptions) then + begin + {!!!!!!!! + case target_info.abi of + abi_powerpc_aix: + ofs:=align(maxpushedparasize+LinkageAreaSizeAIX,16); + abi_powerpc_sysv: + ofs:=align(maxpushedparasize+LinkageAreaSizeSYSV,16); + end; + } + inc(procdef.parast.address_fixup,ofs); + procdef.localst.address_fixup:=procdef.parast.address_fixup+procdef.parast.datasize; + end; + inherited handle_body_start; + end; + + + procedure tarmprocinfo.after_pass1; + begin + if not(po_assembler in procdef.procoptions) then + begin + if cs_asm_source in aktglobalswitches then + aktproccode.insert(Tai_comment.Create(strpnew('Parameter copies start at: r1+'+tostr(procdef.parast.address_fixup)))); + + if cs_asm_source in aktglobalswitches then + aktproccode.insert(Tai_comment.Create(strpnew('Locals start at: r1+'+tostr(procdef.localst.address_fixup)))); + + firsttemp_offset:=align(procdef.localst.address_fixup+procdef.localst.datasize,16); + if cs_asm_source in aktglobalswitches then + aktproccode.insert(Tai_comment.Create(strpnew('Temp. space start: r1+'+tostr(firsttemp_offset)))); + + //!!!! tg.setfirsttemp(firsttemp_offset); + tg.firsttemp:=firsttemp_offset; + tg.lasttemp:=firsttemp_offset; + inherited after_pass1; + end; + end; + + + procedure tarmprocinfo.allocate_push_parasize(size:longint); + begin + if size>maxpushedparasize then + maxpushedparasize:=size; + end; + + + function tarmprocinfo.calc_stackframe_size:longint; + begin + { more or less copied from cgcpu.pas/g_stackframe_entry } + if not (po_assembler in procdef.procoptions) then + result := align(align((31-13+1)*4+(31-14+1)*8,16)+tg.lasttemp,16) + else + result := align(tg.lasttemp,16); + end; + + +begin + cprocinfo:=tarmprocinfo; +end. +{ + $Log$ + Revision 1.1 2003-08-20 15:50:13 florian + * more arm stuff +} + diff --git a/compiler/arm/cpuswtch.pas b/compiler/arm/cpuswtch.pas new file mode 100644 index 0000000000..82fb4ebbb6 --- /dev/null +++ b/compiler/arm/cpuswtch.pas @@ -0,0 +1,124 @@ +{ + $Id$ + Copyright (c) 1998-2002 by Florian Klaempfl, Pierre Muller + + interprets the commandline options which are arm specific + + This program is free software; you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation; either version 2 of the License, or + (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program; if not, write to the Free Software + Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. + + **************************************************************************** +} +unit cpuswtch; + +{$i fpcdefs.inc} + +interface + +uses + options; + +type + toptionarm=class(toption) + procedure interpret_proc_specific_options(const opt:string);override; + end; + +implementation + +uses + cutils,globtype,systems,globals; + +procedure toptionarm.interpret_proc_specific_options(const opt:string); +var + more: string; + j: longint; +begin + More:=Upper(copy(opt,3,length(opt)-2)); + case opt[2] of + 'O' : Begin + j := 3; + While (j <= Length(Opt)) Do + Begin + case opt[j] of + '-' : + begin + initglobalswitches:=initglobalswitches-[cs_optimize,cs_fastoptimize,cs_slowoptimize,cs_littlesize, + cs_regvars,cs_uncertainopts]; + FillChar(ParaAlignment,sizeof(ParaAlignment),0); + end; + 'a' : + begin + UpdateAlignmentStr(Copy(Opt,j+1,255),ParaAlignment); + j:=length(Opt); + end; + 'g' : initglobalswitches:=initglobalswitches+[cs_littlesize]; + 'G' : initglobalswitches:=initglobalswitches-[cs_littlesize]; + 'r' : + begin + initglobalswitches:=initglobalswitches+[cs_regvars]; + Simplify_ppu:=false; + end; + 'u' : initglobalswitches:=initglobalswitches+[cs_uncertainopts]; + '1' : initglobalswitches:=initglobalswitches-[cs_fastoptimize,cs_slowoptimize]+[cs_optimize]; + '2' : initglobalswitches:=initglobalswitches-[cs_slowoptimize]+[cs_optimize,cs_fastoptimize]; + '3' : initglobalswitches:=initglobalswitches+[cs_optimize,cs_fastoptimize,cs_slowoptimize]; +{$ifdef dummy} + 'p' : + Begin + If j < Length(Opt) Then + Begin + Case opt[j+1] Of + '1': initoptprocessor := Class386; + '2': initoptprocessor := ClassP5; + '3': initoptprocessor := ClassP6 + Else IllegalPara(Opt) + End; + Inc(j); + End + Else IllegalPara(opt) + End; +{$endif dummy} + else IllegalPara(opt); + End; + Inc(j) + end; + end; +{$ifdef dummy} + 'R' : begin + if More='GAS' then + initasmmode:=asmmode_ppc_gas + else + if More='MOTOROLA' then + initasmmode:=asmmode_ppc_motorola + else + if More='DIRECT' then + initasmmode:=asmmode_direct + else + IllegalPara(opt); + end; +{$endif dummy} + else + IllegalPara(opt); + end; +end; + + +initialization + coption:=toptionarm; +end. +{ + $Log$ + Revision 1.1 2003-08-20 15:50:13 florian + * more arm stuff +}