1 {
2     Copyright (c) 2006 by Florian Klaempfl
3 
4     Contains the base types for the AVR
5 
6     This program is free software; you can redistribute it and/or modify
7     it under the terms of the GNU General Public License as published by
8     the Free Software Foundation; either version 2 of the License, or
9     (at your option) any later version.
10 
11     This program is distributed in the hope that it will be useful,
12     but WITHOUT ANY WARRANTY; without even the implied warranty of
13     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14     GNU General Public License for more details.
15 
16     You should have received a copy of the GNU General Public License
17     along with this program; if not, write to the Free Software
18     Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
19 
20  ****************************************************************************
21 }
22 {# Base unit for processor information. This unit contains
23    enumerations of registers, opcodes, sizes, and other
24    such things which are processor specific.
25 }
26 unit cpubase;
27 
28 {$i fpcdefs.inc}
29 
30   interface
31 
32     uses
33       cutils,cclasses,
34       globtype,globals,
35       cpuinfo,
36       aasmbase,
37       cgbase
38       ;
39 
40 
41 {*****************************************************************************
42                                 Assembler Opcodes
43 *****************************************************************************}
44 
45     type
46       TAsmOp=(A_None,
47         A_ADD,A_ADC,A_ADIW,A_SUB,A_SUBI,A_SBC,A_SBCI,A_SBRC,A_SBRS,A_SBIW,A_AND,A_ANDI,
48         A_OR,A_ORI,A_EOR,A_COM,A_NEG,A_SBR,A_CBR,A_INC,A_DEC,A_TST,
49         A_MUL,A_MULS,A_MULSU,A_FMUL,A_FMULS,A_FMULSU,A_RJMP,A_IJMP,
50         A_EIJMP,A_JMP,A_RCALL,A_ICALL,R_EICALL,A_CALL,A_RET,A_RETI,A_CPSE,
51         A_CP,A_CPC,A_CPI,A_SBIC,A_SBIS,A_BRxx,A_MOV,A_MOVW,A_LDI,A_LDS,A_LD,A_LDD,
52         A_STS,A_ST,A_STD,A_LPM,A_ELPM,A_SPM,A_IN,A_OUT,A_PUSH,A_POP,
53         A_LSL,A_LSR,A_ROL,A_ROR,A_ASR,A_SWAP,A_BSET,A_BCLR,A_SBI,A_CBI,
54         A_SEC,A_SEH,A_SEI,A_SEN,A_SER,A_SES,A_SET,A_SEV,A_SEZ,
55         A_CLC,A_CLH,A_CLI,A_CLN,A_CLR,A_CLS,A_CLT,A_CLV,A_CLZ,
56         A_BST,A_BLD,A_BREAK,A_NOP,A_SLEEP,A_WDR,A_XCH);
57 
58 
59       { This should define the array of instructions as string }
60       op2strtable=array[tasmop] of string[11];
61 
62     const
63       { First value of opcode enumeration }
64       firstop = low(tasmop);
65       { Last value of opcode enumeration  }
66       lastop  = high(tasmop);
67 
68       { call/reg instructions (A_RCALL,A_ICALL,A_CALL,A_RET,A_RETI) are not considered as jmp instructions for the usage cases of
69         this set }
70       jmp_instructions = [A_BRxx,A_SBIC,A_SBIS,A_JMP,A_EIJMP,A_RJMP,A_CPSE,A_IJMP];
71       call_jmp_instructions = [A_ICALL,A_RCALL,A_CALL,A_RET,A_RETI]+jmp_instructions;
72 
73 {*****************************************************************************
74                                   Registers
75 *****************************************************************************}
76 
77     type
78       { Number of registers used for indexing in tables }
79       tregisterindex=0..{$i ravrnor.inc}-1;
80 
81     const
82       { Available Superregisters }
83       {$i ravrsup.inc}
84 
85       { No Subregisters }
86       R_SUBWHOLE = R_SUBNONE;
87 
88       { Available Registers }
89       {$i ravrcon.inc}
90 
91       NR_XLO = NR_R26;
92       NR_XHI = NR_R27;
93       NR_YLO = NR_R28;
94       NR_YHI = NR_R29;
95       NR_ZLO = NR_R30;
96       NR_ZHI = NR_R31;
97 
98       NIO_SREG = $3f;
99       NIO_SP_LO = $3d;
100       NIO_SP_HI = $3e;
101 
102       { Integer Super registers first and last }
103       first_int_supreg = RS_R0;
104       first_int_imreg = $20;
105 
106       { Float Super register first and last }
107       first_fpu_supreg    = RS_INVALID;
108       first_fpu_imreg     = 0;
109 
110       { MM Super register first and last }
111       first_mm_supreg    = RS_INVALID;
112       first_mm_imreg     = 0;
113 
114       regnumber_count_bsstart = 32;
115 
116       regnumber_table : array[tregisterindex] of tregister = (
117         {$i ravrnum.inc}
118       );
119 
120       regstabs_table : array[tregisterindex] of shortint = (
121         {$i ravrsta.inc}
122       );
123 
124       regdwarf_table : array[tregisterindex] of shortint = (
125         {$i ravrdwa.inc}
126       );
127       { registers which may be destroyed by calls }
128       VOLATILE_INTREGISTERS = [RS_R0,RS_R1,RS_R18..RS_R27,RS_R30,RS_R31];
129       VOLATILE_FPUREGISTERS = [];
130 
131     type
132       totherregisterset = set of tregisterindex;
133 
134 {*****************************************************************************
135                                 Conditions
136 *****************************************************************************}
137 
138     type
139       TAsmCond=(C_None,
140         C_CC,C_CS,C_EQ,C_GE,C_HC,C_HS,C_ID,C_IE,C_LO,C_LT,
141         C_MI,C_NE,C_PL,C_SH,C_TC,C_TS,C_VC,C_VS
142       );
143 
144     const
145       cond2str : array[TAsmCond] of string[2]=('',
146         'cc','cs','eq','ge','hc','hs','id','ie','lo','lt',
147         'mi','ne','pl','sh','tc','ts','vc','vs'
148       );
149 
150       uppercond2str : array[TAsmCond] of string[2]=('',
151         'CC','CS','EQ','GE','HC','HS','ID','IE','LO','LT',
152         'MI','NE','PL','SH','TC','TS','VC','VS'
153       );
154 
155 {*****************************************************************************
156                                    Flags
157 *****************************************************************************}
158 
159     type
160       TResFlags = (F_NotPossible,F_CC,F_CS,F_EQ,F_GE,F_LO,F_LT,
161         F_NE,F_SH,F_VC,F_VS,F_PL,F_MI);
162 
163 {*****************************************************************************
164                                 Operands
165 *****************************************************************************}
166 
167       taddressmode = (AM_UNCHANGED,AM_POSTINCREMENT,AM_PREDRECEMENT);
168 
169 {*****************************************************************************
170                                  Constants
171 *****************************************************************************}
172 
173     const
174       max_operands = 4;
175 
176       maxintregs = 15;
177       maxfpuregs = 0;
178       maxaddrregs = 0;
179 
180 {*****************************************************************************
181                                 Operand Sizes
182 *****************************************************************************}
183 
184     type
185       topsize = (S_NO,
186         S_B,S_W,S_L,S_BW,S_BL,S_WL,
187         S_IS,S_IL,S_IQ,
188         S_FS,S_FL,S_FX,S_D,S_Q,S_FV,S_FXX
189       );
190 
191 {*****************************************************************************
192                                  Constants
193 *****************************************************************************}
194 
195     const
196       firstsaveintreg = RS_R4;
197       lastsaveintreg  = RS_R10;
198       firstsavefpureg = RS_INVALID;
199       lastsavefpureg  = RS_INVALID;
200       firstsavemmreg  = RS_INVALID;
201       lastsavemmreg   = RS_INVALID;
202 
203       maxvarregs = 7;
204       varregs : Array [1..maxvarregs] of tsuperregister =
205                 (RS_R4,RS_R5,RS_R6,RS_R7,RS_R8,RS_R9,RS_R10);
206 
207       maxfpuvarregs = 1;
208       fpuvarregs : Array [1..maxfpuvarregs] of tsuperregister =
209                 (RS_INVALID);
210 
211 {*****************************************************************************
212                           Default generic sizes
213 *****************************************************************************}
214 
215       { Defines the default address size for a processor, }
216       OS_ADDR = OS_16;
217       { the natural int size for a processor,
218         has to match osuinttype/ossinttype as initialized in psystem,
219         initially, this was OS_16/OS_S16 on avr, but experience has
220         proven that it is better to make it 8 Bit thus having the same
221         size as a register.
222       }
223       OS_INT = OS_8;
224       OS_SINT = OS_S8;
225       { the maximum float size for a processor,           }
226       OS_FLOAT = OS_F64;
227       { the size of a vector register for a processor     }
228       OS_VECTOR = OS_M32;
229 
230 {*****************************************************************************
231                           Generic Register names
232 *****************************************************************************}
233 
234       { Stack pointer register }
235       NR_STACK_POINTER_REG = NR_R13;
236       RS_STACK_POINTER_REG = RS_R13;
237       { Frame pointer register }
238       RS_FRAME_POINTER_REG = RS_R28;
239       NR_FRAME_POINTER_REG = NR_R28;
240       { Register for addressing absolute data in a position independant way,
241         such as in PIC code. The exact meaning is ABI specific. For
242         further information look at GCC source : PIC_OFFSET_TABLE_REGNUM
243       }
244       NR_PIC_OFFSET_REG = NR_R9;
245       { Results are returned in this register (32-bit values) }
246       NR_FUNCTION_RETURN_REG = NR_R24;
247       RS_FUNCTION_RETURN_REG = RS_R24;
248       { Low part of 64bit return value }
249       NR_FUNCTION_RETURN64_LOW_REG = NR_R22;
250       RS_FUNCTION_RETURN64_LOW_REG = RS_R22;
251       { High part of 64bit return value }
252       NR_FUNCTION_RETURN64_HIGH_REG = NR_R1;
253       RS_FUNCTION_RETURN64_HIGH_REG = RS_R1;
254       { The value returned from a function is available in this register }
255       NR_FUNCTION_RESULT_REG = NR_FUNCTION_RETURN_REG;
256       RS_FUNCTION_RESULT_REG = RS_FUNCTION_RETURN_REG;
257       { The lowh part of 64bit value returned from a function }
258       NR_FUNCTION_RESULT64_LOW_REG = NR_FUNCTION_RETURN64_LOW_REG;
259       RS_FUNCTION_RESULT64_LOW_REG = RS_FUNCTION_RETURN64_LOW_REG;
260       { The high part of 64bit value returned from a function }
261       NR_FUNCTION_RESULT64_HIGH_REG = NR_FUNCTION_RETURN64_HIGH_REG;
262       RS_FUNCTION_RESULT64_HIGH_REG = RS_FUNCTION_RETURN64_HIGH_REG;
263 
264       NR_FPU_RESULT_REG = NR_NO;
265 
266       NR_MM_RESULT_REG  = NR_NO;
267 
268       NR_RETURN_ADDRESS_REG = NR_FUNCTION_RETURN_REG;
269 
270       { Offset where the parent framepointer is pushed }
271       PARENT_FRAMEPOINTER_OFFSET = 0;
272 
273       NR_DEFAULTFLAGS = NR_SREG;
274       RS_DEFAULTFLAGS = RS_SREG;
275 
276 {*****************************************************************************
277                        GCC /ABI linking information
278 *****************************************************************************}
279 
280     const
281       { Required parameter alignment when calling a routine declared as
282         stdcall and cdecl. The alignment value should be the one defined
283         by GCC or the target ABI.
284 
285         The value of this constant is equal to the constant
286         PARM_BOUNDARY / BITS_PER_UNIT in the GCC source.
287       }
288       std_param_align = 4;
289 
290 {*****************************************************************************
291                                   Helpers
292 *****************************************************************************}
293 
294     { Returns the tcgsize corresponding with the size of reg.}
reg_cgsizenull295     function reg_cgsize(const reg: tregister) : tcgsize;
cgsize2subregnull296     function cgsize2subreg(regtype: tregistertype; s:Tcgsize):Tsubregister;
297     procedure inverse_flags(var f: TResFlags);
flags_to_condnull298     function flags_to_cond(const f: TResFlags) : TAsmCond;
findreg_by_numbernull299     function findreg_by_number(r:Tregister):tregisterindex;
std_regnum_searchnull300     function std_regnum_search(const s:string):Tregister;
std_regnamenull301     function std_regname(r:Tregister):string;
302 
inverse_condnull303     function inverse_cond(const c: TAsmCond): TAsmCond; {$ifdef USEINLINE}inline;{$endif USEINLINE}
conditions_equalnull304     function conditions_equal(const c1, c2: TAsmCond): boolean; {$ifdef USEINLINE}inline;{$endif USEINLINE}
305 
dwarf_regnull306     function dwarf_reg(r:tregister):byte;
dwarf_reg_no_errornull307     function dwarf_reg_no_error(r:tregister):shortint;
308 
is_calljmpnull309     function is_calljmp(o:tasmop):boolean;{$ifdef USEINLINE}inline;{$endif USEINLINE}
310 
311   implementation
312 
313     uses
314       rgBase,verbose;
315 
316 
317     const
318       std_regname_table : TRegNameTable = (
319         {$i ravrstd.inc}
320       );
321 
322       regnumber_index : array[tregisterindex] of tregisterindex = (
323         {$i ravrrni.inc}
324       );
325 
326       std_regname_index : array[tregisterindex] of tregisterindex = (
327         {$i ravrsri.inc}
328       );
329 
330 
cgsize2subregnull331     function cgsize2subreg(regtype: tregistertype; s:Tcgsize):Tsubregister;
332       begin
333         cgsize2subreg:=R_SUBWHOLE;
334       end;
335 
336 
reg_cgsizenull337     function reg_cgsize(const reg: tregister): tcgsize;
338       begin
339         case getregtype(reg) of
340           R_INTREGISTER :
341             reg_cgsize:=OS_8;
342           R_ADDRESSREGISTER :
343             reg_cgsize:=OS_16;
344           else
345             internalerror(2011021905);
346           end;
347         end;
348 
349 
350     procedure inverse_flags(var f: TResFlags);
351       const
352         inv_flags: array[TResFlags] of TResFlags =
353           (F_NotPossible,F_CS,F_CC,F_NE,F_LT,F_SH,F_GE,
354            F_NE,F_LO,F_VS,F_VC,F_MI,F_PL);
355       begin
356         f:=inv_flags[f];
357       end;
358 
359 
flags_to_condnull360     function flags_to_cond(const f: TResFlags) : TAsmCond;
361       const
362         flag_2_cond: array[F_CC..F_MI] of TAsmCond =
363           (C_CC,C_CS,C_EQ,C_GE,C_LO,C_LT,
364            C_NE,C_SH,C_VC,C_VS,C_PL,C_MI);
365       begin
366         if f=F_NotPossible then
367           internalerror(2011022101);
368         if f>high(flag_2_cond) then
369           internalerror(200112301);
370         result:=flag_2_cond[f];
371       end;
372 
373 
findreg_by_numbernull374     function findreg_by_number(r:Tregister):tregisterindex;
375       begin
376         result:=rgBase.findreg_by_number_table(r,regnumber_index);
377       end;
378 
379 
std_regnum_searchnull380     function std_regnum_search(const s:string):Tregister;
381       begin
382         result:=regnumber_table[findreg_by_name_table(s,std_regname_table,std_regname_index)];
383       end;
384 
385 
std_regnamenull386     function std_regname(r:Tregister):string;
387       var
388         p : tregisterindex;
389       begin
390         p:=findreg_by_number_table(r,regnumber_index);
391         if p<>0 then
392           result:=std_regname_table[p]
393         else
394           result:=generic_regname(r);
395       end;
396 
397 
inverse_condnull398     function inverse_cond(const c: TAsmCond): TAsmCond; {$ifdef USEINLINE}inline;{$endif USEINLINE}
399       const
400         inverse: array[TAsmCond] of TAsmCond=(C_None,
401           C_CS,C_CC,C_NE,C_LT,C_HS,C_HC,C_IE,C_ID,C_SH,C_GE,
402           C_PL,C_EQ,C_MI,C_LO,C_TS,C_TC,C_VS,C_VC);
403       begin
404         result := inverse[c];
405       end;
406 
407 
conditions_equalnull408     function conditions_equal(const c1, c2: TAsmCond): boolean; {$ifdef USEINLINE}inline;{$endif USEINLINE}
409       begin
410         result := c1 = c2;
411       end;
412 
413 
rotlnull414     function rotl(d : dword;b : byte) : dword;
415       begin
416          result:=(d shr (32-b)) or (d shl b);
417       end;
418 
419 
dwarf_regnull420     function dwarf_reg(r:tregister):byte;
421       var
422         reg : shortint;
423       begin
424         reg:=regdwarf_table[findreg_by_number(r)];
425         if reg=-1 then
426           internalerror(200603251);
427         result:=reg;
428       end;
429 
dwarf_reg_no_errornull430     function dwarf_reg_no_error(r:tregister):shortint;
431       begin
432         result:=regdwarf_table[findreg_by_number(r)];
433       end;
434 
is_calljmpnull435     function is_calljmp(o:tasmop):boolean;{$ifdef USEINLINE}inline;{$endif USEINLINE}
436       begin
437         is_calljmp:= o in call_jmp_instructions;
438       end;
439 
440 
441 end.
442