123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605 |
- {
- Copyright (c) 2003 by Florian Klaempfl
- Contains the assembler object for the ARM
- 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 aasmcpu;
- {$i fpcdefs.inc}
- interface
- uses
- cclasses,globtype,globals,verbose,
- aasmbase,aasmtai,
- symtype,
- cpubase,cpuinfo,cgbase,cgutils;
- const
- { "mov reg,reg" source operand number }
- O_MOV_SOURCE = 1;
- { "mov reg,reg" source operand number }
- O_MOV_DEST = 0;
- maxinfolen = 5;
- IF_NONE = $00000000;
- IF_ARMMASK = $000F0000;
- { if the instruction can change in a second pass }
- IF_PASS2 = longint($80000000);
- type
- tinsentry = record
- opcode : tasmop;
- ops : byte;
- optypes : array[0..2] of longint;
- code : array[0..maxinfolen] of char;
- flags : longint;
- end;
- pinsentry=^tinsentry;
- taicpu = class(tai_cpu_abstract)
- oppostfix : TOpPostfix;
- roundingmode : troundingmode;
- procedure loadshifterop(opidx:longint;const so:tshifterop);
- procedure loadregset(opidx:longint;const s:tcpuregisterset);
- constructor op_none(op : tasmop);
- constructor op_reg(op : tasmop;_op1 : tregister);
- constructor op_const(op : tasmop;_op1 : longint);
- constructor op_reg_reg(op : tasmop;_op1,_op2 : tregister);
- constructor op_reg_ref(op : tasmop;_op1 : tregister;const _op2 : treference);
- constructor op_reg_const(op:tasmop; _op1: tregister; _op2: aint);
- constructor op_ref_regset(op:tasmop; _op1: treference; _op2: tcpuregisterset);
- constructor op_reg_reg_reg(op : tasmop;_op1,_op2,_op3 : tregister);
- constructor op_reg_reg_const(op : tasmop;_op1,_op2 : tregister; _op3: aint);
- constructor op_reg_reg_sym_ofs(op : tasmop;_op1,_op2 : tregister; _op3: tasmsymbol;_op3ofs: longint);
- constructor op_reg_reg_ref(op : tasmop;_op1,_op2 : tregister; const _op3: treference);
- constructor op_reg_reg_shifterop(op : tasmop;_op1,_op2 : tregister;_op3 : tshifterop);
- { SFM/LFM }
- constructor op_reg_const_ref(op : tasmop;_op1 : tregister;_op2 : aint;_op3 : treference);
- { *M*LL }
- constructor op_reg_reg_reg_reg(op : tasmop;_op1,_op2,_op3,_op4 : tregister);
- { this is for Jmp instructions }
- constructor op_cond_sym(op : tasmop;cond:TAsmCond;_op1 : tasmsymbol);
- constructor op_sym(op : tasmop;_op1 : tasmsymbol);
- constructor op_sym_ofs(op : tasmop;_op1 : tasmsymbol;_op1ofs:longint);
- 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);
- function is_same_reg_move(regtype: Tregistertype):boolean; override;
- function spilling_get_operation_type(opnr: longint): topertype;override;
- { assembler }
- public
- { the next will reset all instructions that can change in pass 2 }
- procedure ResetPass1;
- procedure ResetPass2;
- function CheckIfValid:boolean;
- function Pass1(offset:longint):longint;virtual;
- procedure Pass2(objdata:TAsmObjectdata);virtual;
- protected
- procedure ppuloadoper(ppufile:tcompilerppufile;var o:toper);override;
- procedure ppuwriteoper(ppufile:tcompilerppufile;const o:toper);override;
- procedure ppubuildderefimploper(var o:toper);override;
- procedure ppuderefoper(var o:toper);override;
- private
- { next fields are filled in pass1, so pass2 is faster }
- inssize : shortint;
- insoffset : longint;
- LastInsOffset : longint; { need to be public to be reset }
- insentry : PInsEntry;
- function InsEnd:longint;
- procedure create_ot;
- function Matches(p:PInsEntry):longint;
- function calcsize(p:PInsEntry):shortint;
- procedure gencode(objdata:TAsmObjectData);
- function NeedAddrPrefix(opidx:byte):boolean;
- procedure Swapoperands;
- function FindInsentry:boolean;
- end;
- tai_align = class(tai_align_abstract)
- { nothing to add }
- end;
- function spilling_create_load(const ref:treference;r:tregister): tai;
- function spilling_create_store(r:tregister; const ref:treference): tai;
- function setoppostfix(i : taicpu;pf : toppostfix) : taicpu;
- function setroundingmode(i : taicpu;rm : troundingmode) : taicpu;
- function setcondition(i : taicpu;c : tasmcond) : taicpu;
- { inserts pc relative symbols at places where they are reachable }
- procedure insertpcrelativedata(list,listtoinsert : taasmoutput);
- procedure InitAsm;
- procedure DoneAsm;
- implementation
- uses
- cutils,rgobj,itcpugas;
- procedure taicpu.loadshifterop(opidx:longint;const so:tshifterop);
- begin
- allocate_oper(opidx+1);
- with oper[opidx]^ do
- begin
- if typ<>top_shifterop then
- begin
- clearop(opidx);
- new(shifterop);
- end;
- shifterop^:=so;
- typ:=top_shifterop;
- if assigned(add_reg_instruction_hook) then
- add_reg_instruction_hook(self,shifterop^.rs);
- end;
- end;
- procedure taicpu.loadregset(opidx:longint;const s:tcpuregisterset);
- var
- i : byte;
- begin
- allocate_oper(opidx+1);
- with oper[opidx]^ do
- begin
- if typ<>top_regset then
- clearop(opidx);
- new(regset);
- regset^:=s;
- typ:=top_regset;
- for i:=RS_R0 to RS_R15 do
- begin
- if assigned(add_reg_instruction_hook) and (i in regset^) then
- add_reg_instruction_hook(self,newreg(R_INTREGISTER,i,R_SUBWHOLE));
- end;
- end;
- end;
- {*****************************************************************************
- taicpu Constructors
- *****************************************************************************}
- constructor taicpu.op_none(op : tasmop);
- begin
- inherited create(op);
- end;
- constructor taicpu.op_reg(op : tasmop;_op1 : tregister);
- begin
- inherited create(op);
- ops:=1;
- loadreg(0,_op1);
- end;
- constructor taicpu.op_const(op : tasmop;_op1 : longint);
- begin
- inherited create(op);
- ops:=1;
- loadconst(0,aint(_op1));
- end;
- constructor taicpu.op_reg_reg(op : tasmop;_op1,_op2 : tregister);
- begin
- inherited create(op);
- ops:=2;
- loadreg(0,_op1);
- loadreg(1,_op2);
- end;
- constructor taicpu.op_reg_const(op:tasmop; _op1: tregister; _op2: aint);
- begin
- inherited create(op);
- ops:=2;
- loadreg(0,_op1);
- loadconst(1,aint(_op2));
- end;
- constructor taicpu.op_ref_regset(op:tasmop; _op1: treference; _op2: tcpuregisterset);
- begin
- inherited create(op);
- ops:=2;
- loadref(0,_op1);
- loadregset(1,_op2);
- end;
- constructor taicpu.op_reg_ref(op : tasmop;_op1 : tregister;const _op2 : treference);
- begin
- inherited create(op);
- ops:=2;
- loadreg(0,_op1);
- loadref(1,_op2);
- end;
- constructor taicpu.op_reg_reg_reg(op : tasmop;_op1,_op2,_op3 : tregister);
- begin
- inherited create(op);
- ops:=3;
- loadreg(0,_op1);
- loadreg(1,_op2);
- loadreg(2,_op3);
- end;
- constructor taicpu.op_reg_reg_reg_reg(op : tasmop;_op1,_op2,_op3,_op4 : tregister);
- begin
- inherited create(op);
- ops:=4;
- loadreg(0,_op1);
- loadreg(1,_op2);
- loadreg(2,_op3);
- loadreg(3,_op4);
- end;
- constructor taicpu.op_reg_reg_const(op : tasmop;_op1,_op2 : tregister; _op3: aint);
- begin
- inherited create(op);
- ops:=3;
- loadreg(0,_op1);
- loadreg(1,_op2);
- loadconst(2,aint(_op3));
- end;
- constructor taicpu.op_reg_const_ref(op : tasmop;_op1 : tregister;_op2 : aint;_op3 : treference);
- begin
- inherited create(op);
- ops:=3;
- loadreg(0,_op1);
- loadconst(1,_op2);
- loadref(2,_op3);
- end;
- constructor taicpu.op_reg_reg_sym_ofs(op : tasmop;_op1,_op2 : tregister; _op3: tasmsymbol;_op3ofs: longint);
- begin
- inherited create(op);
- ops:=3;
- loadreg(0,_op1);
- loadreg(1,_op2);
- loadsymbol(0,_op3,_op3ofs);
- end;
- constructor taicpu.op_reg_reg_ref(op : tasmop;_op1,_op2 : tregister; const _op3: treference);
- begin
- inherited create(op);
- ops:=3;
- loadreg(0,_op1);
- loadreg(1,_op2);
- loadref(2,_op3);
- end;
- constructor taicpu.op_reg_reg_shifterop(op : tasmop;_op1,_op2 : tregister;_op3 : tshifterop);
- begin
- inherited create(op);
- ops:=3;
- loadreg(0,_op1);
- loadreg(1,_op2);
- loadshifterop(2,_op3);
- end;
- constructor taicpu.op_cond_sym(op : tasmop;cond:TAsmCond;_op1 : tasmsymbol);
- begin
- inherited create(op);
- condition:=cond;
- ops:=1;
- loadsymbol(0,_op1,0);
- end;
- constructor taicpu.op_sym(op : tasmop;_op1 : tasmsymbol);
- begin
- inherited create(op);
- ops:=1;
- loadsymbol(0,_op1,0);
- end;
- constructor taicpu.op_sym_ofs(op : tasmop;_op1 : tasmsymbol;_op1ofs:longint);
- begin
- inherited create(op);
- ops:=1;
- loadsymbol(0,_op1,_op1ofs);
- end;
- constructor taicpu.op_reg_sym_ofs(op : tasmop;_op1 : tregister;_op2:tasmsymbol;_op2ofs : longint);
- begin
- inherited create(op);
- ops:=2;
- loadreg(0,_op1);
- loadsymbol(1,_op2,_op2ofs);
- end;
- constructor taicpu.op_sym_ofs_ref(op : tasmop;_op1 : tasmsymbol;_op1ofs:longint;const _op2 : treference);
- begin
- inherited create(op);
- ops:=2;
- loadsymbol(0,_op1,_op1ofs);
- loadref(1,_op2);
- end;
- { ****************************** newra stuff *************************** }
- function taicpu.is_same_reg_move(regtype: Tregistertype):boolean;
- begin
- { allow the register allocator to remove unnecessary moves }
- result:=(((opcode=A_MOV) and (regtype = R_INTREGISTER)) or
- ((opcode=A_MVF) and (regtype = R_FPUREGISTER))
- ) and
- (condition=C_None) and
- (ops=2) and
- (oper[0]^.typ=top_reg) and
- (oper[1]^.typ=top_reg) and
- (oper[0]^.reg=oper[1]^.reg);
- end;
- function spilling_create_load(const ref:treference;r:tregister): tai;
- begin
- case getregtype(r) of
- R_INTREGISTER :
- result:=taicpu.op_reg_ref(A_LDR,r,ref);
- R_FPUREGISTER :
- { use lfm because we don't know the current internal format
- and avoid exceptions
- }
- result:=taicpu.op_reg_const_ref(A_LFM,r,1,ref);
- else
- internalerror(200401041);
- end;
- end;
- function spilling_create_store(r:tregister; const ref:treference): tai;
- begin
- case getregtype(r) of
- R_INTREGISTER :
- result:=taicpu.op_reg_ref(A_STR,r,ref);
- R_FPUREGISTER :
- { use sfm because we don't know the current internal format
- and avoid exceptions
- }
- result:=taicpu.op_reg_const_ref(A_SFM,r,1,ref);
- else
- internalerror(200401041);
- end;
- end;
- function taicpu.spilling_get_operation_type(opnr: longint): topertype;
- begin
- case opcode of
- A_ADC,A_ADD,A_AND,
- A_EOR,A_CLZ,
- A_LDR,A_LDRB,A_LDRD,A_LDRBT,A_LDRH,A_LDRSB,
- A_LDRSH,A_LDRT,
- A_MOV,A_MVN,A_MLA,A_MUL,
- A_ORR,A_RSB,A_RSC,A_SBC,A_SUB,
- A_SWP,A_SWPB,
- A_LDF,A_FLT,A_FIX,
- A_ADF,A_DVF,A_FDV,A_FML,
- A_RFS,A_RFC,A_RDF,
- A_RMF,A_RPW,A_RSF,A_SUF,A_ABS,A_ACS,A_ASN,A_ATN,A_COS,
- A_EXP,A_LOG,A_LGN,A_MVF,A_MNF,A_FRD,A_MUF,A_POL,A_RND,A_SIN,A_SQT,A_TAN,
- A_LFM:
- if opnr=0 then
- result:=operand_write
- else
- result:=operand_read;
- A_BIC,A_BKPT,A_B,A_BL,A_BLX,A_BX,
- A_CMN,A_CMP,A_TEQ,A_TST,
- A_CMF,A_CMFE,A_WFS,A_CNF:
- result:=operand_read;
- A_SMLAL,A_UMLAL:
- if opnr in [0,1] then
- result:=operand_readwrite
- else
- result:=operand_read;
- A_SMULL,A_UMULL:
- if opnr in [0,1] then
- result:=operand_write
- else
- result:=operand_read;
- A_STR,A_STRB,A_STRBT,A_STRD,
- A_STRH,A_STRT,A_STF,A_SFM:
- { important is what happens with the involved registers }
- if opnr=0 then
- result := operand_read
- else
- { check for pre/post indexed }
- result := operand_read;
- else
- internalerror(200403151);
- end;
- end;
- procedure InitAsm;
- begin
- end;
- procedure DoneAsm;
- begin
- end;
- function setoppostfix(i : taicpu;pf : toppostfix) : taicpu;
- begin
- i.oppostfix:=pf;
- result:=i;
- end;
- function setroundingmode(i : taicpu;rm : troundingmode) : taicpu;
- begin
- i.roundingmode:=rm;
- result:=i;
- end;
- function setcondition(i : taicpu;c : tasmcond) : taicpu;
- begin
- i.condition:=c;
- result:=i;
- end;
- procedure insertpcrelativedata(list,listtoinsert : taasmoutput);
- var
- curpos : longint;
- lastpos : longint;
- curop : longint;
- curtai : tai;
- curdatatai,hp : tai;
- curdata : taasmoutput;
- l : tasmlabel;
- begin
- curdata:=taasmoutput.create;
- lastpos:=-1;
- curpos:=0;
- curtai:=tai(list.first);
- while assigned(curtai) do
- begin
- { instruction? }
- if curtai.typ=ait_instruction then
- begin
- { walk through all operand of the instruction }
- for curop:=0 to taicpu(curtai).ops-1 do
- begin
- { reference? }
- if (taicpu(curtai).oper[curop]^.typ=top_ref) then
- begin
- { pc relative symbol? }
- curdatatai:=tai(taicpu(curtai).oper[curop]^.ref^.symboldata);
- if assigned(curdatatai) then
- begin
- { if yes, insert till next symbol }
- repeat
- hp:=tai(curdatatai.next);
- listtoinsert.remove(curdatatai);
- curdata.concat(curdatatai);
- curdatatai:=hp;
- until (curdatatai=nil) or (curdatatai.typ=ait_label);
- if lastpos=-1 then
- lastpos:=curpos;
- end;
- end;
- end;
- inc(curpos);
- end;
- { split only at real instructions else the test below fails }
- if ((curpos-lastpos)>1016) and (curtai.typ=ait_instruction) and
- (
- { don't split loads of pc to lr and the following move }
- not(
- (taicpu(curtai).opcode=A_MOV) and
- (taicpu(curtai).oper[0]^.typ=top_reg) and
- (taicpu(curtai).oper[0]^.reg=NR_R14) and
- (taicpu(curtai).oper[1]^.typ=top_reg) and
- (taicpu(curtai).oper[1]^.reg=NR_PC)
- )
- ) then
- begin
- lastpos:=curpos;
- hp:=tai(curtai.next);
- objectlibrary.getlabel(l);
- curdata.insert(taicpu.op_sym(A_B,l));
- curdata.concat(tai_label.create(l));
- list.insertlistafter(curtai,curdata);
- curtai:=hp;
- end
- else
- curtai:=tai(curtai.next);
- end;
- list.concatlist(curdata);
- curdata.free;
- end;
- procedure taicpu.ResetPass1;
- begin
- { we need to reset everything here, because the choosen insentry
- can be invalid for a new situation where the previously optimized
- insentry is not correct }
- InsEntry:=nil;
- InsSize:=0;
- LastInsOffset:=-1;
- end;
- procedure taicpu.ResetPass2;
- begin
- { we are here in a second pass, check if the instruction can be optimized }
- if assigned(InsEntry) and
- ((InsEntry^.flags and IF_PASS2)<>0) then
- begin
- InsEntry:=nil;
- InsSize:=0;
- end;
- LastInsOffset:=-1;
- end;
- function taicpu.CheckIfValid:boolean;
- begin
- end;
- function taicpu.Pass1(offset:longint):longint;
- begin
- end;
- procedure taicpu.Pass2(objdata:TAsmObjectdata);
- begin
- end;
- procedure taicpu.ppuloadoper(ppufile:tcompilerppufile;var o:toper);
- begin
- end;
- procedure taicpu.ppuwriteoper(ppufile:tcompilerppufile;const o:toper);
- begin
- end;
- procedure taicpu.ppubuildderefimploper(var o:toper);
- begin
- end;
- procedure taicpu.ppuderefoper(var o:toper);
- begin
- end;
- function taicpu.InsEnd:longint;
- begin
- end;
- procedure taicpu.create_ot;
- begin
- end;
- function taicpu.Matches(p:PInsEntry):longint;
- begin
- end;
- function taicpu.calcsize(p:PInsEntry):shortint;
- begin
- end;
- procedure taicpu.gencode(objdata:TAsmObjectData);
- begin
- end;
- function taicpu.NeedAddrPrefix(opidx:byte):boolean;
- begin
- end;
- procedure taicpu.Swapoperands;
- begin
- end;
- function taicpu.FindInsentry:boolean;
- begin
- end;
- end.
- {$ifdef dummy}
- (*
- static void gencode (long segment, long offset, int bits,
- insn *ins, char *codes, long insn_end)
- {
- int has_S_code; /* S - setflag */
- int has_B_code; /* B - setflag */
- int has_T_code; /* T - setflag */
- int has_W_code; /* ! => W flag */
- int has_F_code; /* ^ => S flag */
- int keep;
- unsigned char c;
- unsigned char bytes[4];
- long data, size;
- static int cc_code[] = /* bit pattern of cc */
- { /* order as enum in */
- 0x0E, 0x03, 0x02, 0x00, /* nasm.h */
- 0x0A, 0x0C, 0x08, 0x0D,
- 0x09, 0x0B, 0x04, 0x01,
- 0x05, 0x07, 0x06,
- };
- (*
- #ifdef DEBUG
- static char *CC[] =
- { /* condition code names */
- "AL", "CC", "CS", "EQ",
- "GE", "GT", "HI", "LE",
- "LS", "LT", "MI", "NE",
- "PL", "VC", "VS", "",
- "S"
- };
- *)
- has_S_code = (ins->condition & C_SSETFLAG);
- has_B_code = (ins->condition & C_BSETFLAG);
- has_T_code = (ins->condition & C_TSETFLAG);
- has_W_code = (ins->condition & C_EXSETFLAG);
- has_F_code = (ins->condition & C_FSETFLAG);
- ins->condition = (ins->condition & 0x0F);
- (*
- if (rt_debug)
- {
- printf ("gencode: instruction: %s%s", insn_names[ins->opcode],
- CC[ins->condition & 0x0F]);
- if (has_S_code)
- printf ("S");
- if (has_B_code)
- printf ("B");
- if (has_T_code)
- printf ("T");
- if (has_W_code)
- printf ("!");
- if (has_F_code)
- printf ("^");
- printf ("\n");
- c = *codes;
- printf (" (%d) decode - '0x%02X'\n", ins->operands, c);
- bytes[0] = 0xB;
- bytes[1] = 0xE;
- bytes[2] = 0xE;
- bytes[3] = 0xF;
- }
- *)
- // First condition code in upper nibble
- if (ins->condition < C_NONE)
- {
- c = cc_code[ins->condition] << 4;
- }
- else
- {
- c = cc_code[C_AL] << 4; // is often ALWAYS but not always
- }
- switch (keep = *codes)
- {
- case 1:
- // B, BL
- ++codes;
- c |= *codes++;
- bytes[0] = c;
- if (ins->oprs[0].segment != segment)
- {
- // fais une relocation
- c = 1;
- data = 0; // Let the linker locate ??
- }
- else
- {
- c = 0;
- data = ins->oprs[0].offset - (offset + 8);
-
- if (data % 4)
- {
- errfunc (ERR_NONFATAL, "offset not aligned on 4 bytes");
- }
- }
-
- if (data >= 0x1000)
- {
- errfunc (ERR_NONFATAL, "too long offset");
- }
- data = data >> 2;
- bytes[1] = (data >> 16) & 0xFF;
- bytes[2] = (data >> 8) & 0xFF;
- bytes[3] = (data ) & 0xFF;
- if (c == 1)
- {
- // out (offset, segment, &bytes[0], OUT_RAWDATA+1, NO_SEG, NO_SEG);
- out (offset, segment, &bytes[0], OUT_REL3ADR+4, ins->oprs[0].segment, NO_SEG);
- }
- else
- {
- out (offset, segment, &bytes[0], OUT_RAWDATA+4, NO_SEG, NO_SEG);
- }
- return;
- case 2:
- // SWI
- ++codes;
- c |= *codes++;
- bytes[0] = c;
- data = ins->oprs[0].offset;
- bytes[1] = (data >> 16) & 0xFF;
- bytes[2] = (data >> 8) & 0xFF;
- bytes[3] = (data) & 0xFF;
- out (offset, segment, &bytes, OUT_RAWDATA+4, NO_SEG, NO_SEG);
- return;
- case 3:
- // BX
- ++codes;
- c |= *codes++;
- bytes[0] = c;
- bytes[1] = *codes++;
- bytes[2] = *codes++;
- bytes[3] = *codes++;
- c = regval (&ins->oprs[0],1);
- if (c == 15) // PC
- {
- errfunc (ERR_WARNING, "'BX' with R15 has undefined behaviour");
- }
- else if (c > 15)
- {
- errfunc (ERR_NONFATAL, "Illegal register specified for 'BX'");
- }
- bytes[3] |= (c & 0x0F);
- out (offset, segment, bytes, OUT_RAWDATA+4, NO_SEG, NO_SEG);
- return;
- case 4: // AND Rd,Rn,Rm
- case 5: // AND Rd,Rn,Rm,<shift>Rs
- case 6: // AND Rd,Rn,Rm,<shift>imm
- case 7: // AND Rd,Rn,<shift>imm
- ++codes;
- #ifdef DEBUG
- if (rt_debug)
- {
- printf (" decode - '0x%02X'\n", keep);
- printf (" code - '0x%02X'\n", (unsigned char) ( *codes));
- }
- #endif
- bytes[0] = c | *codes;
- ++codes;
-
- bytes[1] = *codes;
- if (has_S_code)
- bytes[1] |= 0x10;
- c = regval (&ins->oprs[1],1);
- // Rn in low nibble
- bytes[1] |= c;
- // Rd in high nibble
- bytes[2] = regval (&ins->oprs[0],1) << 4;
- if (keep != 7)
- {
- // Rm in low nibble
- bytes[3] = regval (&ins->oprs[2],1);
- }
- // Shifts if any
- if (keep == 5 || keep == 6)
- {
- // Shift in bytes 2 and 3
- if (keep == 5)
- {
- // Rs
- c = regval (&ins->oprs[3],1);
- bytes[2] |= c;
- c = 0x10; // Set bit 4 in byte[3]
- }
- if (keep == 6)
- {
- c = (ins->oprs[3].offset) & 0x1F;
-
- // #imm
- bytes[2] |= c >> 1;
- if (c & 0x01)
- {
- bytes[3] |= 0x80;
- }
- c = 0; // Clr bit 4 in byte[3]
- }
- // <shift>
- c |= shiftval (&ins->oprs[3]) << 5;
- bytes[3] |= c;
- }
-
- // reg,reg,imm
- if (keep == 7)
- {
- int shimm;
-
- shimm = imm_shift (ins->oprs[2].offset);
- if (shimm == -1)
- {
- errfunc (ERR_NONFATAL, "cannot create that constant");
- }
- bytes[3] = shimm & 0xFF;
- bytes[2] |= (shimm & 0xF00) >> 8;
- }
-
- out (offset, segment, bytes, OUT_RAWDATA+4, NO_SEG, NO_SEG);
- return;
- case 8: // MOV Rd,Rm
- case 9: // MOV Rd,Rm,<shift>Rs
- case 0xA: // MOV Rd,Rm,<shift>imm
- case 0xB: // MOV Rd,<shift>imm
- ++codes;
- #ifdef DEBUG
- if (rt_debug)
- {
- printf (" decode - '0x%02X'\n", keep);
- printf (" code - '0x%02X'\n", (unsigned char) ( *codes));
- }
- #endif
- bytes[0] = c | *codes;
- ++codes;
-
- bytes[1] = *codes;
- if (has_S_code)
- bytes[1] |= 0x10;
- // Rd in high nibble
- bytes[2] = regval (&ins->oprs[0],1) << 4;
- if (keep != 0x0B)
- {
- // Rm in low nibble
- bytes[3] = regval (&ins->oprs[1],1);
- }
- // Shifts if any
- if (keep == 0x09 || keep == 0x0A)
- {
- // Shift in bytes 2 and 3
- if (keep == 0x09)
- {
- // Rs
- c = regval (&ins->oprs[2],1);
- bytes[2] |= c;
- c = 0x10; // Set bit 4 in byte[3]
- }
- if (keep == 0x0A)
- {
- c = (ins->oprs[2].offset) & 0x1F;
-
- // #imm
- bytes[2] |= c >> 1;
- if (c & 0x01)
- {
- bytes[3] |= 0x80;
- }
- c = 0; // Clr bit 4 in byte[3]
- }
- // <shift>
- c |= shiftval (&ins->oprs[2]) << 5;
- bytes[3] |= c;
- }
-
- // reg,imm
- if (keep == 0x0B)
- {
- int shimm;
-
- shimm = imm_shift (ins->oprs[1].offset);
- if (shimm == -1)
- {
- errfunc (ERR_NONFATAL, "cannot create that constant");
- }
- bytes[3] = shimm & 0xFF;
- bytes[2] |= (shimm & 0xF00) >> 8;
- }
-
- out (offset, segment, bytes, OUT_RAWDATA+4, NO_SEG, NO_SEG);
- return;
-
- case 0xC: // CMP Rn,Rm
- case 0xD: // CMP Rn,Rm,<shift>Rs
- case 0xE: // CMP Rn,Rm,<shift>imm
- case 0xF: // CMP Rn,<shift>imm
- ++codes;
- bytes[0] = c | *codes++;
-
- bytes[1] = *codes;
- // Implicit S code
- bytes[1] |= 0x10;
- c = regval (&ins->oprs[0],1);
- // Rn in low nibble
- bytes[1] |= c;
- // No destination
- bytes[2] = 0;
- if (keep != 0x0B)
- {
- // Rm in low nibble
- bytes[3] = regval (&ins->oprs[1],1);
- }
- // Shifts if any
- if (keep == 0x0D || keep == 0x0E)
- {
- // Shift in bytes 2 and 3
- if (keep == 0x0D)
- {
- // Rs
- c = regval (&ins->oprs[2],1);
- bytes[2] |= c;
- c = 0x10; // Set bit 4 in byte[3]
- }
- if (keep == 0x0E)
- {
- c = (ins->oprs[2].offset) & 0x1F;
-
- // #imm
- bytes[2] |= c >> 1;
- if (c & 0x01)
- {
- bytes[3] |= 0x80;
- }
- c = 0; // Clr bit 4 in byte[3]
- }
- // <shift>
- c |= shiftval (&ins->oprs[2]) << 5;
- bytes[3] |= c;
- }
-
- // reg,imm
- if (keep == 0x0F)
- {
- int shimm;
-
- shimm = imm_shift (ins->oprs[1].offset);
- if (shimm == -1)
- {
- errfunc (ERR_NONFATAL, "cannot create that constant");
- }
- bytes[3] = shimm & 0xFF;
- bytes[2] |= (shimm & 0xF00) >> 8;
- }
-
- out (offset, segment, bytes, OUT_RAWDATA+4, NO_SEG, NO_SEG);
- return;
-
- case 0x10: // MRS Rd,<psr>
- ++codes;
- bytes[0] = c | *codes++;
-
- bytes[1] = *codes++;
- // Rd
- c = regval (&ins->oprs[0],1);
- bytes[2] = c << 4;
- bytes[3] = 0;
- c = ins->oprs[1].basereg;
- if (c == R_CPSR || c == R_SPSR)
- {
- if (c == R_SPSR)
- {
- bytes[1] |= 0x40;
- }
- }
- else
- {
- errfunc (ERR_NONFATAL, "CPSR or SPSR expected");
- }
- out (offset, segment, bytes, OUT_RAWDATA+4, NO_SEG, NO_SEG);
- return;
-
- case 0x11: // MSR <psr>,Rm
- case 0x12: // MSR <psrf>,Rm
- case 0x13: // MSR <psrf>,#expression
- ++codes;
- bytes[0] = c | *codes++;
-
- bytes[1] = *codes++;
- bytes[2] = *codes;
- if (keep == 0x11 || keep == 0x12)
- {
- // Rm
- c = regval (&ins->oprs[1],1);
- bytes[3] = c;
- }
- else
- {
- int shimm;
-
- shimm = imm_shift (ins->oprs[1].offset);
- if (shimm == -1)
- {
- errfunc (ERR_NONFATAL, "cannot create that constant");
- }
- bytes[3] = shimm & 0xFF;
- bytes[2] |= (shimm & 0xF00) >> 8;
- }
-
- c = ins->oprs[0].basereg;
- if ( keep == 0x11)
- {
- if ( c == R_CPSR || c == R_SPSR)
- {
- if ( c== R_SPSR)
- {
- bytes[1] |= 0x40;
- }
- }
- else
- {
- errfunc (ERR_NONFATAL, "CPSR or SPSR expected");
- }
- }
- else
- {
- if ( c == R_CPSR_FLG || c == R_SPSR_FLG)
- {
- if ( c== R_SPSR_FLG)
- {
- bytes[1] |= 0x40;
- }
- }
- else
- {
- errfunc (ERR_NONFATAL, "CPSR_flg or SPSR_flg expected");
- }
- }
- break;
- case 0x14: // MUL Rd,Rm,Rs
- case 0x15: // MULA Rd,Rm,Rs,Rn
- ++codes;
-
- bytes[0] = c | *codes++;
-
- bytes[1] = *codes++;
- bytes[3] = *codes;
- // Rd
- bytes[1] |= regval (&ins->oprs[0],1);
- if (has_S_code)
- bytes[1] |= 0x10;
- // Rm
- bytes[3] |= regval (&ins->oprs[1],1);
- // Rs
- bytes[2] = regval (&ins->oprs[2],1);
- if (keep == 0x15)
- {
- bytes[2] |= regval (&ins->oprs[3],1) << 4;
- }
- break;
- case 0x16: // SMLAL RdHi,RdLo,Rm,Rs
- ++codes;
-
- bytes[0] = c | *codes++;
-
- bytes[1] = *codes++;
- bytes[3] = *codes;
- // RdHi
- bytes[1] |= regval (&ins->oprs[1],1);
- if (has_S_code)
- bytes[1] |= 0x10;
- // RdLo
- bytes[2] = regval (&ins->oprs[0],1) << 4;
- // Rm
- bytes[3] |= regval (&ins->oprs[2],1);
- // Rs
- bytes[2] |= regval (&ins->oprs[3],1);
- break;
-
- case 0x17: // LDR Rd, expression
- ++codes;
- bytes[0] = c | *codes++;
- bytes[1] = *codes++;
- // Rd
- bytes[2] = regval (&ins->oprs[0],1) << 4;
- if (has_B_code)
- bytes[1] |= 0x40;
- if (has_T_code)
- {
- errfunc (ERR_NONFATAL, "'T' not allowed in pre-index mode");
- }
- if (has_W_code)
- {
- errfunc (ERR_NONFATAL, "'!' not allowed");
- }
- // Rn - implicit R15
- bytes[1] |= 0xF;
- if (ins->oprs[1].segment != segment)
- {
- errfunc (ERR_NONFATAL, "label not in same segment");
- }
-
- data = ins->oprs[1].offset - (offset + 8);
- if (data < 0)
- {
- data = -data;
- }
- else
- {
- bytes[1] |= 0x80;
- }
- if (data >= 0x1000)
- {
- errfunc (ERR_NONFATAL, "too long offset");
- }
- bytes[2] |= ((data & 0xF00) >> 8);
- bytes[3] = data & 0xFF;
- break;
-
- case 0x18: // LDR Rd, [Rn]
- ++codes;
-
- bytes[0] = c | *codes++;
-
- bytes[1] = *codes++;
- // Rd
- bytes[2] = regval (&ins->oprs[0],1) << 4;
- if (has_B_code)
- bytes[1] |= 0x40;
- if (has_T_code)
- {
- bytes[1] |= 0x20; // write-back
- }
- else
- {
- bytes[0] |= 0x01; // implicit pre-index mode
- }
- if (has_W_code)
- {
- bytes[1] |= 0x20; // write-back
- }
- // Rn
- c = regval (&ins->oprs[1],1);
- bytes[1] |= c;
- if (c == 0x15) // R15
- data = -8;
- else
- data = 0;
- if (data < 0)
- {
- data = -data;
- }
- else
- {
- bytes[1] |= 0x80;
- }
- bytes[2] |= ((data & 0xF00) >> 8);
- bytes[3] = data & 0xFF;
- break;
-
- case 0x19: // LDR Rd, [Rn,#expression]
- case 0x20: // LDR Rd, [Rn,Rm]
- case 0x21: // LDR Rd, [Rn,Rm,shift]
- ++codes;
-
- bytes[0] = c | *codes++;
-
- bytes[1] = *codes++;
- // Rd
- bytes[2] = regval (&ins->oprs[0],1) << 4;
- if (has_B_code)
- bytes[1] |= 0x40;
- // Rn
- c = regval (&ins->oprs[1],1);
- bytes[1] |= c;
- if (ins->oprs[ins->operands-1].bracket) // FIXME: Bracket on last operand -> pre-index <--
- {
- bytes[0] |= 0x01; // pre-index mode
- if (has_W_code)
- {
- bytes[1] |= 0x20;
- }
- if (has_T_code)
- {
- errfunc (ERR_NONFATAL, "'T' not allowed in pre-index mode");
- }
- }
- else
- {
- if (has_T_code) // Forced write-back in post-index mode
- {
- bytes[1] |= 0x20;
- }
- if (has_W_code)
- {
- errfunc (ERR_NONFATAL, "'!' not allowed in post-index mode");
- }
- }
- if (keep == 0x19)
- {
- data = ins->oprs[2].offset;
- if (data < 0)
- {
- data = -data;
- }
- else
- {
- bytes[1] |= 0x80;
- }
- if (data >= 0x1000)
- {
- errfunc (ERR_NONFATAL, "too long offset");
- }
-
- bytes[2] |= ((data & 0xF00) >> 8);
- bytes[3] = data & 0xFF;
- }
- else
- {
- if (ins->oprs[2].minus == 0)
- {
- bytes[1] |= 0x80;
- }
- c = regval (&ins->oprs[2],1);
- bytes[3] = c;
- if (keep == 0x21)
- {
- c = ins->oprs[3].offset;
- if (c > 0x1F)
- {
- errfunc (ERR_NONFATAL, "too large shiftvalue");
- c = c & 0x1F;
- }
-
- bytes[2] |= c >> 1;
- if (c & 0x01)
- {
- bytes[3] |= 0x80;
- }
- bytes[3] |= shiftval (&ins->oprs[3]) << 5;
- }
- }
-
- break;
-
- case 0x22: // LDRH Rd, expression
- ++codes;
-
- bytes[0] = c | 0x01; // Implicit pre-index
- bytes[1] = *codes++;
- // Rd
- bytes[2] = regval (&ins->oprs[0],1) << 4;
-
- // Rn - implicit R15
- bytes[1] |= 0xF;
- if (ins->oprs[1].segment != segment)
- {
- errfunc (ERR_NONFATAL, "label not in same segment");
- }
-
- data = ins->oprs[1].offset - (offset + 8);
- if (data < 0)
- {
- data = -data;
- }
- else
- {
- bytes[1] |= 0x80;
- }
- if (data >= 0x100)
- {
- errfunc (ERR_NONFATAL, "too long offset");
- }
- bytes[3] = *codes++;
- bytes[2] |= ((data & 0xF0) >> 4);
- bytes[3] |= data & 0xF;
- break;
-
- case 0x23: // LDRH Rd, Rn
- ++codes;
-
- bytes[0] = c | 0x01; // Implicit pre-index
-
- bytes[1] = *codes++;
- // Rd
- bytes[2] = regval (&ins->oprs[0],1) << 4;
-
- // Rn
- c = regval (&ins->oprs[1],1);
- bytes[1] |= c;
- if (c == 0x15) // R15
- data = -8;
- else
- data = 0;
-
- if (data < 0)
- {
- data = -data;
- }
- else
- {
- bytes[1] |= 0x80;
- }
- if (data >= 0x100)
- {
- errfunc (ERR_NONFATAL, "too long offset");
- }
- bytes[3] = *codes++;
- bytes[2] |= ((data & 0xF0) >> 4);
- bytes[3] |= data & 0xF;
- break;
-
- case 0x24: // LDRH Rd, Rn, expression
- case 0x25: // LDRH Rd, Rn, Rm
- ++codes;
- bytes[0] = c;
-
- bytes[1] = *codes++;
- // Rd
- bytes[2] = regval (&ins->oprs[0],1) << 4;
- // Rn
- c = regval (&ins->oprs[1],1);
- bytes[1] |= c;
- if (ins->oprs[ins->operands-1].bracket) // FIXME: Bracket on last operand -> pre-index <--
- {
- bytes[0] |= 0x01; // pre-index mode
- if (has_W_code)
- {
- bytes[1] |= 0x20;
- }
- }
- else
- {
- if (has_W_code)
- {
- errfunc (ERR_NONFATAL, "'!' not allowed in post-index mode");
- }
- }
- bytes[3] = *codes++;
- if (keep == 0x24)
- {
- data = ins->oprs[2].offset;
- if (data < 0)
- {
- data = -data;
- }
- else
- {
- bytes[1] |= 0x80;
- }
-
- if (data >= 0x100)
- {
- errfunc (ERR_NONFATAL, "too long offset");
- }
- bytes[2] |= ((data & 0xF0) >> 4);
- bytes[3] |= data & 0xF;
- }
- else
- {
- if (ins->oprs[2].minus == 0)
- {
- bytes[1] |= 0x80;
- }
- c = regval (&ins->oprs[2],1);
- bytes[3] |= c;
- }
- break;
-
- case 0x26: // LDM/STM Rn, {reg-list}
- ++codes;
- bytes[0] = c;
- bytes[0] |= ( *codes >> 4) & 0xF;
- bytes[1] = ( *codes << 4) & 0xF0;
- ++codes;
- if (has_W_code)
- {
- bytes[1] |= 0x20;
- }
- if (has_F_code)
- {
- bytes[1] |= 0x40;
- }
-
- // Rn
- bytes[1] |= regval (&ins->oprs[0],1);
- data = ins->oprs[1].basereg;
- bytes[2] = ((data >> 8) & 0xFF);
- bytes[3] = (data & 0xFF);
-
- break;
-
- case 0x27: // SWP Rd, Rm, [Rn]
- ++codes;
-
- bytes[0] = c;
- bytes[0] |= *codes++;
-
- bytes[1] = regval (&ins->oprs[2],1);
- if (has_B_code)
- {
- bytes[1] |= 0x40;
- }
- bytes[2] = regval (&ins->oprs[0],1) << 4;
- bytes[3] = *codes++;
- bytes[3] |= regval (&ins->oprs[1],1);
- break;
-
- default:
- errfunc (ERR_FATAL, "unknown decoding of instruction");
- bytes[0] = c;
- // And a fix nibble
- ++codes;
- bytes[0] |= *codes++;
- if ( *codes == 0x01) // An I bit
- {
- }
- if ( *codes == 0x02) // An I bit
- {
- }
- ++codes;
- }
- out (offset, segment, bytes, OUT_RAWDATA+4, NO_SEG, NO_SEG);
- }
- *)
- {$endif dummy
- }
|