summaryrefslogtreecommitdiff
path: root/compiler/riscv64
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/riscv64')
-rw-r--r--compiler/riscv64/aoptcpu.pas387
-rw-r--r--compiler/riscv64/aoptcpub.pas116
-rw-r--r--compiler/riscv64/aoptcpuc.pas40
-rw-r--r--compiler/riscv64/aoptcpud.pas40
-rw-r--r--compiler/riscv64/cgcpu.pas642
-rw-r--r--compiler/riscv64/cpubase.pas462
-rw-r--r--compiler/riscv64/cpuinfo.pas139
-rw-r--r--compiler/riscv64/cpunode.pas55
-rw-r--r--compiler/riscv64/cpupara.pas545
-rw-r--r--compiler/riscv64/cpupi.pas116
-rw-r--r--compiler/riscv64/cputarg.pas85
-rw-r--r--compiler/riscv64/hlcgcpu.pas78
-rw-r--r--compiler/riscv64/itcpugas.pas157
-rw-r--r--compiler/riscv64/nrv64add.pas98
-rw-r--r--compiler/riscv64/nrv64cal.pas56
-rw-r--r--compiler/riscv64/nrv64cnv.pas124
-rw-r--r--compiler/riscv64/nrv64ld.pas57
-rw-r--r--compiler/riscv64/nrv64mat.pas163
-rw-r--r--compiler/riscv64/rarv.pas50
-rw-r--r--compiler/riscv64/rarv64gas.pas840
-rw-r--r--compiler/riscv64/rrv32con.inc67
-rw-r--r--compiler/riscv64/rrv32dwa.inc67
-rw-r--r--compiler/riscv64/rrv32nor.inc2
-rw-r--r--compiler/riscv64/rrv32num.inc67
-rw-r--r--compiler/riscv64/rrv32rni.inc67
-rw-r--r--compiler/riscv64/rrv32sri.inc67
-rw-r--r--compiler/riscv64/rrv32sta.inc67
-rw-r--r--compiler/riscv64/rrv32std.inc67
-rw-r--r--compiler/riscv64/rrv32sup.inc67
-rw-r--r--compiler/riscv64/rv32reg.dat77
-rw-r--r--compiler/riscv64/symcpu.pas220
31 files changed, 5085 insertions, 0 deletions
diff --git a/compiler/riscv64/aoptcpu.pas b/compiler/riscv64/aoptcpu.pas
new file mode 100644
index 0000000000..7e2ed6cf1a
--- /dev/null
+++ b/compiler/riscv64/aoptcpu.pas
@@ -0,0 +1,387 @@
+{
+ Copyright (c) 1998-2002 by Jonas Maebe, member of the Free Pascal
+ Development Team
+
+ This unit implements the RiscV64 optimizer object
+
+ 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 aoptcpu;
+
+interface
+
+{$I fpcdefs.inc}
+
+{$define DEBUG_AOPTCPU}
+
+uses
+ cpubase,
+ globals, globtype,
+ cgbase,
+ aoptobj, aoptcpub, aopt,
+ aasmtai, aasmcpu;
+
+type
+
+ TCpuAsmOptimizer = class(TAsmOptimizer)
+ function InstructionLoadsFromReg(const reg: TRegister; const hp: tai): boolean; override;
+ function RegLoadedWithNewValue(reg: tregister; hp: tai): boolean; override;
+ Function GetNextInstructionUsingReg(Current: tai; Out Next: tai; reg: TRegister): Boolean;
+ { outputs a debug message into the assembler file }
+ procedure DebugMsg(const s: string; p: tai);
+
+ function PeepHoleOptPass1Cpu(var p: tai): boolean; override;
+ end;
+
+implementation
+
+ uses
+ cutils;
+
+ function MatchInstruction(const instr: tai; const op: TAsmOps; const AConditions: TAsmConds = []): boolean;
+ begin
+ result :=
+ (instr.typ = ait_instruction) and
+ (taicpu(instr).opcode in op) and
+ ((AConditions=[]) or (taicpu(instr).condition in AConditions));
+ end;
+
+
+ function MatchInstruction(const instr: tai; const op: TAsmOp; const AConditions: TAsmConds = []): boolean;
+ begin
+ result :=
+ (instr.typ = ait_instruction) and
+ (taicpu(instr).opcode = op) and
+ ((AConditions=[]) or (taicpu(instr).condition in AConditions));
+ end;
+
+
+ function MatchOperand(const oper1: TOper; const oper2: TOper): boolean; inline;
+ begin
+ result := oper1.typ = oper2.typ;
+
+ if result then
+ case oper1.typ of
+ top_const:
+ Result:=oper1.val = oper2.val;
+ top_reg:
+ Result:=oper1.reg = oper2.reg;
+ {top_ref:
+ Result:=RefsEqual(oper1.ref^, oper2.ref^);}
+ else Result:=false;
+ end
+ end;
+
+
+ function MatchOperand(const oper: TOper; const reg: TRegister): boolean; inline;
+ begin
+ result := (oper.typ = top_reg) and (oper.reg = reg);
+ end;
+
+
+{$ifdef DEBUG_AOPTCPU}
+ procedure TCpuAsmOptimizer.DebugMsg(const s: string;p : tai);
+ begin
+ asml.insertbefore(tai_comment.Create(strpnew(s)), p);
+ end;
+{$else DEBUG_AOPTCPU}
+ procedure TCpuAsmOptimizer.DebugMsg(const s: string;p : tai);inline;
+ begin
+ end;
+{$endif DEBUG_AOPTCPU}
+
+
+ function TCpuAsmOptimizer.InstructionLoadsFromReg(const reg: TRegister; const hp: tai): boolean;
+ var
+ p: taicpu;
+ i: longint;
+ begin
+ result:=false;
+ if not (assigned(hp) and (hp.typ=ait_instruction)) then
+ exit;
+ p:=taicpu(hp);
+
+ i:=0;
+ while(i<p.ops) do
+ begin
+ case p.oper[I]^.typ of
+ top_reg:
+ result:=(p.oper[I]^.reg=reg) and (p.spilling_get_operation_type(i)<>operand_write);
+ top_ref:
+ result:=
+ (p.oper[I]^.ref^.base=reg);
+ end;
+ if result then exit; {Bailout if we found something}
+ Inc(I);
+ end;
+ end;
+
+
+ function TCpuAsmOptimizer.RegLoadedWithNewValue(reg: tregister; hp: tai): boolean;
+ begin
+ result:=
+ (hp.typ=ait_instruction) and
+ (taicpu(hp).ops>1) and
+ (taicpu(hp).oper[0]^.typ=top_reg) and
+ (taicpu(hp).oper[0]^.reg=reg) and
+ (taicpu(hp).spilling_get_operation_type(0)<>operand_read);
+ end;
+
+
+ function TCpuAsmOptimizer.GetNextInstructionUsingReg(Current: tai; out Next: tai; reg: TRegister): Boolean;
+ begin
+ Next:=Current;
+ repeat
+ Result:=GetNextInstruction(Next,Next);
+ until not (Result) or
+ not(cs_opt_level3 in current_settings.optimizerswitches) or
+ (Next.typ<>ait_instruction) or
+ RegInInstruction(reg,Next) or
+ is_calljmp(taicpu(Next).opcode);
+ end;
+
+
+ function TCpuAsmOptimizer.PeepHoleOptPass1Cpu(var p: tai): boolean;
+
+ procedure RemoveInstr(var orig: tai; moveback: boolean = true);
+ var
+ n: tai;
+ begin
+ if moveback and (not GetLastInstruction(orig,n)) then
+ GetNextInstruction(orig,n);
+
+ AsmL.Remove(orig);
+ orig.Free;
+
+ orig:=n;
+ end;
+
+ var
+ hp1: tai;
+ begin
+ result:=false;
+ case p.typ of
+ ait_instruction:
+ begin
+ case taicpu(p).opcode of
+ A_ADDI:
+ begin
+ {
+ Changes
+ addi x, y, #
+ addi/addiw z, x, #
+ dealloc x
+ To
+ addi z, y, #+#
+ }
+ if (taicpu(p).ops=3) and
+ (taicpu(p).oper[2]^.typ=top_const) and
+ GetNextInstructionUsingReg(p, hp1, taicpu(p).oper[0]^.reg) and
+ MatchInstruction(hp1,[A_ADDI,A_ADDIW]) and
+ (taicpu(hp1).ops=3) and
+ MatchOperand(taicpu(p).oper[0]^,taicpu(hp1).oper[1]^) and
+ (taicpu(p).oper[2]^.typ=top_const) and
+ is_imm12(taicpu(p).oper[2]^.val+taicpu(hp1).oper[2]^.val) and
+ (not RegModifiedBetween(taicpu(p).oper[1]^.reg, p,hp1)) and
+ RegEndOfLife(taicpu(p).oper[0]^.reg, taicpu(hp1)) then
+ begin
+ taicpu(hp1).loadreg(1,taicpu(p).oper[1]^.reg);
+ taicpu(hp1).loadconst(2, taicpu(p).oper[2]^.val+taicpu(hp1).oper[2]^.val);
+
+ DebugMsg('Peephole AddiAddi2Addi performed', hp1);
+
+ RemoveInstr(p);
+
+ result:=true;
+ end
+ {
+ Changes
+ addi x, x, (ref)
+ ld/sd y, 0(x)
+ dealloc x
+ To
+ ld/sd y, 0(ref)(x)
+ }
+ else if (taicpu(p).ops=3) and
+ (taicpu(p).oper[2]^.typ=top_ref) and
+ MatchOperand(taicpu(p).oper[0]^,taicpu(p).oper[1]^) and
+ GetNextInstructionUsingReg(p, hp1, taicpu(p).oper[0]^.reg) and
+ MatchInstruction(hp1, [A_LB,A_LBU,A_LH,A_LHU,A_LW,A_LWU,A_LD,
+ A_SB,A_SH,A_SW,A_SD]) and
+ (taicpu(hp1).ops=2) and
+ (taicpu(hp1).oper[1]^.typ=top_ref) and
+ (taicpu(hp1).oper[1]^.ref^.base=taicpu(p).oper[0]^.reg) and
+ (taicpu(hp1).oper[1]^.ref^.offset=0) and
+ (not RegModifiedBetween(taicpu(p).oper[1]^.reg, p,hp1)) and
+ RegEndOfLife(taicpu(p).oper[0]^.reg, taicpu(hp1)) then
+ begin
+ taicpu(hp1).loadref(1,taicpu(p).oper[2]^.ref^);
+ taicpu(hp1).oper[1]^.ref^.base:=taicpu(p).oper[1]^.reg;
+
+ DebugMsg('Peephole AddiMem2Mem performed', hp1);
+
+ RemoveInstr(p);
+
+ result:=true;
+ end;
+ end;
+ A_SUB:
+ begin
+ {
+ Turn
+ sub x,y,z
+ bgeu X0,x,...
+ dealloc x
+ Into
+ bne y,x,...
+ }
+ if (taicpu(p).ops=3) and
+ GetNextInstructionUsingReg(p, hp1, taicpu(p).oper[0]^.reg) and
+ MatchInstruction(hp1,A_Bxx,[C_GEU,C_EQ]) and
+ (taicpu(hp1).ops=3) and
+ MatchOperand(taicpu(hp1).oper[0]^,NR_X0) and
+ MatchOperand(taicpu(hp1).oper[1]^,taicpu(p).oper[0]^) and
+ (not RegModifiedBetween(taicpu(p).oper[1]^.reg, p,hp1)) and
+ (not RegModifiedBetween(taicpu(p).oper[2]^.reg, p,hp1)) and
+ RegEndOfLife(taicpu(p).oper[0]^.reg, taicpu(hp1)) then
+ begin
+ taicpu(hp1).loadreg(0,taicpu(p).oper[1]^.reg);
+ taicpu(hp1).loadreg(1,taicpu(p).oper[2]^.reg);
+ taicpu(hp1).condition:=C_EQ;
+
+ DebugMsg('Peephole SubBxx2Beq performed', hp1);
+
+ RemoveInstr(p);
+
+ result:=true;
+ end;
+ end;
+ A_SLTU:
+ begin
+ {
+ Turn
+ sltu x,X0,y
+ beq/bne x, X0, ...
+ dealloc x
+ Into
+ bltu/geu X0, y, ...
+ }
+ if (taicpu(p).ops=3) and
+ MatchOperand(taicpu(p).oper[1]^,NR_X0) and
+ GetNextInstructionUsingReg(p, hp1, taicpu(p).oper[0]^.reg) and
+ MatchInstruction(hp1,A_Bxx,[C_NE,C_EQ]) and
+ (taicpu(hp1).ops=3) and
+ MatchOperand(taicpu(hp1).oper[0]^,taicpu(p).oper[0]^) and
+ MatchOperand(taicpu(hp1).oper[1]^,NR_X0) and
+ (not RegModifiedBetween(taicpu(p).oper[2]^.reg, p,hp1)) and
+ RegEndOfLife(taicpu(p).oper[0]^.reg, taicpu(hp1)) then
+ begin
+ taicpu(hp1).loadreg(0,NR_X0);
+ taicpu(hp1).loadreg(1,taicpu(p).oper[2]^.reg);
+
+ if taicpu(hp1).condition=C_NE then
+ taicpu(hp1).condition:=C_LTU
+ else
+ taicpu(hp1).condition:=C_GEU;
+
+ DebugMsg('Peephole SltuB2B performed', hp1);
+
+ RemoveInstr(p);
+
+ result:=true;
+ end;
+ end;
+ A_SLTIU:
+ begin
+ {
+ Turn
+ sltiu x,y,1
+ beq/ne x,x0,...
+ dealloc x
+ Into
+ bne y,x0,...
+ }
+ if (taicpu(p).ops=3) and
+ (taicpu(p).oper[2]^.typ=top_const) and
+ (taicpu(p).oper[2]^.val=1) and
+ GetNextInstructionUsingReg(p, hp1, taicpu(p).oper[0]^.reg) and
+ MatchInstruction(hp1,A_Bxx,[C_NE,C_EQ]) and
+ (taicpu(hp1).ops=3) and
+ MatchOperand(taicpu(hp1).oper[0]^,taicpu(p).oper[0]^) and
+ MatchOperand(taicpu(hp1).oper[1]^,NR_X0) and
+ (not RegModifiedBetween(taicpu(p).oper[1]^.reg, p,hp1)) and
+ RegEndOfLife(taicpu(p).oper[0]^.reg, taicpu(hp1)) then
+ begin
+ taicpu(hp1).loadreg(0,taicpu(p).oper[1]^.reg);
+ taicpu(hp1).condition:=inverse_cond(taicpu(hp1).condition);
+
+ DebugMsg('Peephole Sltiu0B2B performed', hp1);
+
+ RemoveInstr(p);
+
+ result:=true;
+ end;
+ end;
+ A_SLTI:
+ begin
+ {
+ Turn
+ slti x,y,0
+ beq/ne x,x0,...
+ dealloc x
+ Into
+ bge/lt y,x0,...
+ }
+ if (taicpu(p).ops=3) and
+ (taicpu(p).oper[2]^.typ=top_const) and
+ (taicpu(p).oper[2]^.val=0) and
+ GetNextInstructionUsingReg(p, hp1, taicpu(p).oper[0]^.reg) and
+ (hp1.typ=ait_instruction) and
+ (taicpu(hp1).opcode=A_Bxx) and
+ (taicpu(hp1).ops=3) and
+ (taicpu(hp1).oper[0]^.typ=top_reg) and
+ (taicpu(hp1).oper[0]^.reg=taicpu(p).oper[0]^.reg) and
+ (taicpu(hp1).oper[1]^.typ=top_reg) and
+ (taicpu(hp1).oper[1]^.reg=NR_X0) and
+ (taicpu(hp1).condition in [C_NE,C_EQ]) and
+ (not RegModifiedBetween(taicpu(p).oper[1]^.reg, p,hp1)) and
+ RegEndOfLife(taicpu(p).oper[0]^.reg, taicpu(hp1)) then
+ begin
+ taicpu(hp1).loadreg(0,taicpu(p).oper[1]^.reg);
+ taicpu(hp1).loadreg(1,NR_X0);
+
+ if taicpu(hp1).condition=C_NE then
+ taicpu(hp1).condition:=C_LT
+ else
+ taicpu(hp1).condition:=C_GE;
+
+ DebugMsg('Peephole Slti0B2B performed', hp1);
+
+ RemoveInstr(p);
+
+ result:=true;
+ end;
+ end;
+ end;
+ end;
+ end;
+ end;
+
+begin
+ casmoptimizer := TCpuAsmOptimizer;
+end.
diff --git a/compiler/riscv64/aoptcpub.pas b/compiler/riscv64/aoptcpub.pas
new file mode 100644
index 0000000000..da6587c061
--- /dev/null
+++ b/compiler/riscv64/aoptcpub.pas
@@ -0,0 +1,116 @@
+{
+ Copyright (c) 1998-2002 by Jonas Maebe, member of the Free Pascal
+ Development Team
+
+ This unit contains several types and constants necessary for the
+ optimizer to work on the RiscV64 architecture
+
+ 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 aoptcpub; { Assembler OPTimizer CPU specific Base }
+
+{$I fpcdefs.inc}
+
+{ enable the following define if memory references can have a scaled index }
+{ define RefsHaveScale}
+
+{ enable the following define if memory references can have a segment }
+{ override }
+{ define RefsHaveSegment}
+
+interface
+
+uses
+ aasmcpu, AOptBase, cpubase;
+
+type
+
+ { type of a normal instruction }
+ TInstr = Taicpu;
+ PInstr = ^TInstr;
+
+ { ************************************************************************* }
+ { **************************** TCondRegs ********************************** }
+ { ************************************************************************* }
+ { Info about the conditional registers }
+ TCondRegs = object
+ constructor Init;
+ destructor Done;
+ end;
+
+ { ************************************************************************* }
+ { **************************** TAoptBaseCpu ******************************* }
+ { ************************************************************************* }
+
+ TAoptBaseCpu = class(TAoptBase)
+ end;
+
+ { ************************************************************************* }
+ { ******************************* Constants ******************************* }
+ { ************************************************************************* }
+const
+
+ { the maximum number of things (registers, memory, ...) a single instruction }
+ { changes }
+
+ MaxCh = 3;
+
+ { the maximum number of operands an instruction has }
+
+ MaxOps = 5;
+
+ {Oper index of operand that contains the source (reference) with a load }
+ {instruction }
+
+ LoadSrc = 1;
+
+ {Oper index of operand that contains the destination (register) with a load }
+ {instruction }
+
+ LoadDst = 0;
+
+ {Oper index of operand that contains the source (register) with a store }
+ {instruction }
+
+ StoreSrc = 0;
+
+ {Oper index of operand that contains the destination (reference) with a load }
+ {instruction }
+
+ StoreDst = 1;
+
+ aopt_uncondjmp = A_JAL;
+ aopt_condjmp = A_Bxx;
+
+implementation
+
+{ ************************************************************************* }
+{ **************************** TCondRegs ********************************** }
+{ ************************************************************************* }
+
+constructor TCondRegs.init;
+begin
+end;
+
+destructor TCondRegs.Done;
+{$IFDEF inl}inline;
+{$ENDIF inl}
+begin
+end;
+
+end.
+
diff --git a/compiler/riscv64/aoptcpuc.pas b/compiler/riscv64/aoptcpuc.pas
new file mode 100644
index 0000000000..e002fedb21
--- /dev/null
+++ b/compiler/riscv64/aoptcpuc.pas
@@ -0,0 +1,40 @@
+{
+ Copyright (c) 1998-2002 by Jonas Maebe, member of the Free Pascal
+ Development Team
+
+ This unit contains the processor specific implementation of the
+ assembler optimizer common subexpression elimination object.
+
+ 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 aoptcpuc;
+
+interface
+
+{$I fpcdefs.inc}
+
+uses
+ AOptCs;
+
+type
+ TRegInfoCpu = object(TRegInfo)
+ end;
+
+implementation
+
+end.
+
diff --git a/compiler/riscv64/aoptcpud.pas b/compiler/riscv64/aoptcpud.pas
new file mode 100644
index 0000000000..5e6e7fc308
--- /dev/null
+++ b/compiler/riscv64/aoptcpud.pas
@@ -0,0 +1,40 @@
+{
+ Copyright (c) 1998-2002 by Jonas Maebe, member of the Free Pascal
+ Development Team
+
+ This unit contains the processor specific implementation of the
+ assembler optimizer data flow analyzer.
+
+ 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 aoptcpud;
+
+{$I fpcdefs.inc}
+
+interface
+
+uses
+ AOptDA;
+
+type
+ TAOptDFACpu = class(TAOptDFA)
+ end;
+
+implementation
+
+end.
+
diff --git a/compiler/riscv64/cgcpu.pas b/compiler/riscv64/cgcpu.pas
new file mode 100644
index 0000000000..554107ab91
--- /dev/null
+++ b/compiler/riscv64/cgcpu.pas
@@ -0,0 +1,642 @@
+{
+ Copyright (c) 1998-2002 by Florian Klaempfl
+
+ This unit implements the code generator for the RiscV64
+
+ 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 cgcpu;
+
+{$I fpcdefs.inc}
+
+ interface
+
+ uses
+ globtype, symtype, symdef, symsym,
+ cgbase, cgobj,cgrv,
+ aasmbase, aasmcpu, aasmtai,aasmdata,
+ cpubase, cpuinfo, cgutils, rgcpu,
+ parabase;
+
+ type
+ tcgrv64 = class(tcgrv)
+ procedure init_register_allocators; override;
+ procedure done_register_allocators; override;
+
+ { move instructions }
+ procedure a_load_reg_reg(list: TAsmList; fromsize, tosize: tcgsize; reg1, reg2: tregister); override;
+ procedure a_load_const_reg(list: TAsmList; size: tcgsize; a: tcgint; register: tregister); override;
+
+ procedure a_op_const_reg_reg_checkoverflow(list: TAsmList; op: TOpCg; size: tcgsize; a: tcgint; src, dst: tregister; setflags: boolean; var ovloc: tlocation); override;
+ procedure a_op_reg_reg_reg_checkoverflow(list: TAsmList; op: TOpCg; size: tcgsize; src1, src2, dst: tregister; setflags: boolean; var ovloc: tlocation); override;
+
+ procedure g_overflowcheck(list: TAsmList; const Loc: tlocation; def: tdef); override;
+
+ procedure g_proc_entry(list: TAsmList; localsize: longint; nostackframe: boolean); override;
+ procedure g_proc_exit(list: TAsmList; parasize: longint; nostackframe: boolean); override;
+
+ procedure g_concatcopy_move(list: tasmlist; const Source, dest: treference; len: tcgint);
+ procedure g_concatcopy(list: TAsmList; const source, dest: treference; len: aint); override;
+ end;
+
+ procedure create_codegen;
+
+implementation
+
+ uses
+ sysutils, cclasses,
+ globals, verbose, systems, cutils,
+ symconst, fmodule, symtable,
+ rgobj, tgobj, cpupi, procinfo, paramgr, cpupara;
+
+
+ procedure tcgrv64.init_register_allocators;
+ begin
+ inherited init_register_allocators;
+ rg[R_INTREGISTER]:=trgintcpu.create(R_INTREGISTER,R_SUBWHOLE,
+ [RS_X10,RS_X11,RS_X12,RS_X13,RS_X14,RS_X15,RS_X16,RS_X17,
+ RS_X31,RS_X30,RS_X29,RS_X28,
+ RS_X5,RS_X6,RS_X7,
+ RS_X9,RS_X27,RS_X26,RS_X25,RS_X24,RS_X23,RS_X22,
+ RS_X21,RS_X20,RS_X19,RS_X18],first_int_imreg,[]);
+ rg[R_FPUREGISTER]:=trgcpu.create(R_FPUREGISTER,R_SUBNONE,
+ [RS_F10,RS_F11,RS_F12,RS_F13,RS_F14,RS_F15,RS_F16,RS_F17,
+ RS_F0,RS_F1,RS_F2,RS_F3,RS_F4,RS_F5,RS_F6,RS_F7,
+ RS_F28,RS_F29,RS_F30,RS_F31,
+ RS_F8,RS_F9,
+ RS_F27,
+ RS_F26,RS_F25,RS_F24,RS_F23,RS_F22,RS_F21,RS_F20,RS_F19,RS_F18],first_fpu_imreg,[]);
+ end;
+
+
+ procedure tcgrv64.done_register_allocators;
+ begin
+ rg[R_INTREGISTER].free;
+ rg[R_FPUREGISTER].free;
+ inherited done_register_allocators;
+ end;
+
+
+ procedure tcgrv64.a_load_reg_reg(list: TAsmList; fromsize, tosize: tcgsize; reg1, reg2: tregister);
+ var
+ ai: taicpu;
+ begin
+ list.concat(tai_comment.Create(strpnew('Move '+tcgsize2str(fromsize)+'->'+tcgsize2str(tosize))));
+
+ if (tcgsize2unsigned[tosize]=OS_64) and (fromsize=OS_S32) then
+ list.Concat(taicpu.op_reg_reg_const(A_ADDIW,reg2,reg1,0))
+ else if (tosize=OS_S32) and (tcgsize2unsigned[fromsize]=OS_64) then
+ list.Concat(taicpu.op_reg_reg_const(A_ADDIW,reg2,reg1,0))
+ else if (tcgsize2unsigned[tosize]=OS_64) and (fromsize=OS_8) then
+ list.Concat(taicpu.op_reg_reg_const(A_ANDI,reg2,reg1,$FF))
+ else if (tcgsize2size[fromsize] > tcgsize2size[tosize]) or
+ ((tcgsize2size[fromsize] = tcgsize2size[tosize]) and (fromsize <> tosize)) or
+ { do we need to mask out the sign when loading from smaller signed to larger unsigned type? }
+ ((tcgsize2unsigned[fromsize]<>fromsize) and ((tcgsize2unsigned[tosize]=tosize)) and
+ (tcgsize2size[fromsize] < tcgsize2size[tosize]) and (tcgsize2size[tosize] <> sizeof(pint)) ) then
+ begin
+ if tcgsize2size[fromsize]<tcgsize2size[tosize] then
+ begin
+ list.Concat(taicpu.op_reg_reg_const(A_SLLI,reg2,reg1,8*(8-tcgsize2size[fromsize])));
+
+ if tcgsize2unsigned[fromsize]<>fromsize then
+ list.Concat(taicpu.op_reg_reg_const(A_SRAI,reg2,reg2,8*(tcgsize2size[tosize]-tcgsize2size[fromsize])))
+ else
+ list.Concat(taicpu.op_reg_reg_const(A_SRLI,reg2,reg2,8*(tcgsize2size[tosize]-tcgsize2size[fromsize])));
+ end
+ else if tcgsize2unsigned[tosize]<>OS_64 then
+ list.Concat(taicpu.op_reg_reg_const(A_SLLI,reg2,reg1,8*(8-tcgsize2size[tosize])))
+ else
+ a_load_reg_reg(list,tosize,tosize,reg1,reg2);
+
+ if tcgsize2unsigned[tosize]=tosize then
+ list.Concat(taicpu.op_reg_reg_const(A_SRLI,reg2,reg2,8*(8-tcgsize2size[tosize])))
+ else
+ list.Concat(taicpu.op_reg_reg_const(A_SRAI,reg2,reg2,8*(8-tcgsize2size[tosize])));
+ end
+ else
+ begin
+ ai:=taicpu.op_reg_reg_const(A_ADDI,reg2,reg1,0);
+ list.concat(ai);
+ rg[R_INTREGISTER].add_move_instruction(ai);
+ end;
+ end;
+
+ procedure tcgrv64.a_load_const_reg(list: TAsmList; size: tcgsize; a: tcgint; register: tregister);
+ var
+ l: TAsmLabel;
+ hr: treference;
+ begin
+ if a=0 then
+ a_load_reg_reg(list,size,size,NR_X0,register)
+ else
+ begin
+ if is_imm12(a) then
+ list.concat(taicpu.op_reg_reg_const(A_ADDI,register,NR_X0,a))
+ else if is_lui_imm(a) then
+ list.concat(taicpu.op_reg_const(A_LUI,register,(a shr 12) and $FFFFF))
+ else if (int64(longint(a))=a) then
+ begin
+ if (a and $800)<>0 then
+ list.concat(taicpu.op_reg_const(A_LUI,register,((a shr 12)+1) and $FFFFF))
+ else
+ list.concat(taicpu.op_reg_const(A_LUI,register,(a shr 12) and $FFFFF));
+
+ list.concat(taicpu.op_reg_reg_const(A_ADDIW,register,register,SarSmallint(a shl 4,4)));
+ end
+ else
+ begin
+ reference_reset(hr,8,[]);
+
+ current_asmdata.getjumplabel(l);
+ current_procinfo.aktlocaldata.Concat(cai_align.Create(8));
+ cg.a_label(current_procinfo.aktlocaldata,l);
+ hr.symboldata:=current_procinfo.aktlocaldata.last;
+ current_procinfo.aktlocaldata.concat(tai_const.Create_64bit(a));
+
+ hr.symbol:=l;
+ hr.refaddr:=addr_pcrel_hi20;
+
+ current_asmdata.getjumplabel(l);
+ a_label(list,l);
+
+ list.concat(taicpu.op_reg_ref(A_AUIPC,register,hr));
+
+ reference_reset_symbol(hr,l,0,0,[]);
+ hr.refaddr:=addr_pcrel_lo12;
+ hr.base:=register;
+ list.concat(taicpu.op_reg_ref(A_LD,register,hr));
+ end;
+ end;
+ end;
+
+
+ procedure tcgrv64.a_op_const_reg_reg_checkoverflow(list: TAsmList; op: TOpCg; size: tcgsize; a: tcgint; src, dst: tregister; setflags: boolean; var ovloc: tlocation);
+ var
+ signed: Boolean;
+ l: TAsmLabel;
+ tmpreg: tregister;
+ ai: taicpu;
+ begin
+ if setflags then
+ begin
+ tmpreg:=getintregister(list,size);
+ a_load_const_reg(list,size,a,tmpreg);
+ a_op_reg_reg_reg_checkoverflow(list,op,size,tmpreg,src,dst,setflags,ovloc);
+ end
+ else
+ a_op_const_reg_reg(list,op,size,a,src,dst);
+ end;
+
+
+ procedure tcgrv64.a_op_reg_reg_reg_checkoverflow(list: TAsmList; op: TOpCg; size: tcgsize; src1, src2, dst: tregister; setflags: boolean; var ovloc: tlocation);
+ var
+ signed: Boolean;
+ l: TAsmLabel;
+ tmpreg, tmpreg0: tregister;
+ ai: taicpu;
+ begin
+ signed:=tcgsize2unsigned[size]<>size;
+
+ if setflags then
+ case op of
+ OP_ADD:
+ begin
+ current_asmdata.getjumplabel(l);
+
+ list.Concat(taicpu.op_reg_reg_reg(A_ADD,dst,src2,src1));
+
+ if signed then
+ begin
+ {
+ t0=src1<0
+ t1=result<src2
+ overflow if t0<>t1
+ }
+ tmpreg0:=getintregister(list,OS_INT);
+ tmpreg:=getintregister(list,OS_INT);
+ list.Concat(taicpu.op_reg_reg_reg(A_SLT,tmpreg0,src1,NR_X0));
+ list.Concat(taicpu.op_reg_reg_reg(A_SLT,tmpreg,dst,src2));
+
+ ai:=taicpu.op_reg_reg_sym_ofs(A_Bxx,tmpreg,tmpreg0,l,0);
+ ai.condition:=C_EQ;
+ list.concat(ai);
+ end
+ else
+ begin
+ {
+ jump if sum>=x
+ }
+ if size in [OS_S32,OS_32] then
+ begin
+ tmpreg:=getintregister(list,OS_INT);
+ a_load_reg_reg(list,size,OS_64,dst,tmpreg);
+ dst:=tmpreg;
+ end;
+
+ ai:=taicpu.op_reg_reg_sym_ofs(A_Bxx,dst,src2,l,0);
+ ai.condition:=C_GEU;
+ list.concat(ai);
+ end;
+
+ a_call_name(list,'FPC_OVERFLOW',false);
+ a_label(list,l);
+ end;
+ OP_SUB:
+ begin
+ current_asmdata.getjumplabel(l);
+
+ list.Concat(taicpu.op_reg_reg_reg(A_SUB,dst,src2,src1));
+
+ if signed then
+ begin
+ tmpreg0:=getintregister(list,OS_INT);
+ tmpreg:=getintregister(list,OS_INT);
+ list.Concat(taicpu.op_reg_reg_reg(A_SLT,tmpreg0,NR_X0,src1));
+ list.Concat(taicpu.op_reg_reg_reg(A_SLT,tmpreg,dst,src2));
+
+ ai:=taicpu.op_reg_reg_sym_ofs(A_Bxx,tmpreg,tmpreg0,l,0);
+ ai.condition:=C_EQ;
+ list.concat(ai);
+ end
+ else
+ begin
+ { no overflow if result<=src2 }
+ if size in [OS_S32,OS_32] then
+ begin
+ tmpreg:=getintregister(list,OS_INT);
+ a_load_reg_reg(list,size,OS_64,dst,tmpreg);
+ dst:=tmpreg;
+ end;
+
+ ai:=taicpu.op_reg_reg_sym_ofs(A_Bxx,src2,dst,l,0);
+ ai.condition:=C_GEU;
+ list.concat(ai);
+ end;
+
+ a_call_name(list,'FPC_OVERFLOW',false);
+ a_label(list,l);
+ end;
+ OP_IMUL:
+ begin
+ { No overflow if upper result is same as sign of result }
+ current_asmdata.getjumplabel(l);
+
+ tmpreg:=getintregister(list,OS_INT);
+ tmpreg0:=getintregister(list,OS_INT);
+ list.Concat(taicpu.op_reg_reg_reg(A_MUL,dst,src1,src2));
+ list.Concat(taicpu.op_reg_reg_reg(A_MULH,tmpreg,src1,src2));
+
+ list.concat(taicpu.op_reg_reg_const(A_SRAI,tmpreg0,dst,63));
+
+ a_cmp_reg_reg_label(list,OS_INT,OC_EQ,tmpreg,tmpreg0,l);
+
+ a_call_name(list,'FPC_OVERFLOW',false);
+ a_label(list,l);
+ end;
+ OP_MUL:
+ begin
+ { No overflow if upper result is 0 }
+ current_asmdata.getjumplabel(l);
+
+ tmpreg:=getintregister(list,OS_INT);
+ list.Concat(taicpu.op_reg_reg_reg(A_MUL,dst,src1,src2));
+ list.Concat(taicpu.op_reg_reg_reg(A_MULHU,tmpreg,src1,src2));
+
+ a_cmp_reg_reg_label(list,OS_INT,OC_EQ,tmpreg,NR_X0,l);
+
+ a_call_name(list,'FPC_OVERFLOW',false);
+ a_label(list,l);
+ end;
+ OP_IDIV:
+ begin
+ { Only overflow if dst is all 1's }
+ current_asmdata.getjumplabel(l);
+
+ tmpreg:=getintregister(list,OS_INT);
+ list.Concat(taicpu.op_reg_reg_reg(A_DIV,dst,src1,src2));
+ list.Concat(taicpu.op_reg_reg_const(A_ADDI,tmpreg,dst,1));
+
+ a_cmp_reg_reg_label(list,OS_INT,OC_NE,tmpreg,NR_X0,l);
+
+ a_call_name(list,'FPC_OVERFLOW',false);
+ a_label(list,l);
+ end;
+ end
+ else
+ a_op_reg_reg_reg(list,op,size,src1,src2,dst);
+ end;
+
+
+ procedure tcgrv64.g_overflowcheck(list: TAsmList; const Loc: tlocation; def: tdef);
+ begin
+ end;
+
+
+ procedure tcgrv64.g_proc_entry(list: TAsmList; localsize: longint; nostackframe: boolean);
+ var
+ regs, fregs: tcpuregisterset;
+ r: TSuperRegister;
+ href: treference;
+ stackcount, stackAdjust: longint;
+ begin
+ if not(nostackframe) then
+ begin
+ a_reg_alloc(list,NR_STACK_POINTER_REG);
+ if current_procinfo.framepointer<>NR_STACK_POINTER_REG then
+ a_reg_alloc(list,NR_FRAME_POINTER_REG);
+
+ reference_reset_base(href,NR_STACK_POINTER_REG,-8,ctempposinvalid,0,[]);
+
+ { Int registers }
+ regs:=rg[R_INTREGISTER].used_in_proc-paramanager.get_volatile_registers_int(pocall_stdcall);
+
+ if current_procinfo.framepointer<>NR_STACK_POINTER_REG then
+ regs:=regs+[RS_FRAME_POINTER_REG,RS_RETURN_ADDRESS_REG];
+
+ if (pi_do_call in current_procinfo.flags) then
+ regs:=regs+[RS_RETURN_ADDRESS_REG];
+
+ stackcount:=0;
+ for r:=RS_X0 to RS_X31 do
+ if r in regs then
+ inc(stackcount,8);
+
+ { Float registers }
+ fregs:=rg[R_FPUREGISTER].used_in_proc-paramanager.get_volatile_registers_fpu(pocall_stdcall);
+ for r:=RS_F0 to RS_F31 do
+ if r in fregs then
+ inc(stackcount,8);
+
+ inc(localsize,stackcount);
+ if not is_imm12(-(localsize-stackcount)) then
+ begin
+ if not (RS_RETURN_ADDRESS_REG in regs) then
+ begin
+ include(regs,RS_RETURN_ADDRESS_REG);
+ inc(localsize,8);
+ inc(stackcount,8);
+ end;
+ end;
+
+ stackAdjust:=0;
+ if (CPURV_HAS_COMPACT in cpu_capabilities[current_settings.cputype]) and
+ (stackcount>0) then
+ begin
+ list.concat(taicpu.op_reg_reg_const(A_ADDI,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,-stackcount));
+ inc(href.offset,stackcount);
+ stackAdjust:=stackcount;
+ dec(localsize,stackcount);
+ end;
+
+ for r:=RS_X0 to RS_X31 do
+ if r in regs then
+ begin
+ list.concat(taicpu.op_reg_ref(A_SD,newreg(R_INTREGISTER,r,R_SUBWHOLE),href));
+ dec(href.offset,8);
+ end;
+
+ { Float registers }
+ for r:=RS_F0 to RS_F31 do
+ if r in fregs then
+ begin
+ list.concat(taicpu.op_reg_ref(A_FSD,newreg(R_FPUREGISTER,r,R_SUBWHOLE),href));
+ dec(href.offset,8);
+ end;
+
+ if current_procinfo.framepointer<>NR_STACK_POINTER_REG then
+ list.concat(taicpu.op_reg_reg_const(A_ADDI,NR_FRAME_POINTER_REG,NR_STACK_POINTER_REG,stackAdjust));
+
+ if localsize>0 then
+ begin
+ localsize:=align(localsize,8);
+
+ if is_imm12(-localsize) then
+ list.concat(taicpu.op_reg_reg_const(A_ADDI,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,-localsize))
+ else
+ begin
+ a_load_const_reg(list,OS_INT,localsize,NR_RETURN_ADDRESS_REG);
+ list.concat(taicpu.op_reg_reg_reg(A_SUB,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,NR_RETURN_ADDRESS_REG));
+ end;
+ end;
+ end;
+ end;
+
+
+ procedure tcgrv64.g_proc_exit(list: TAsmList; parasize: longint; nostackframe: boolean);
+ var
+ r: tsuperregister;
+ regs, fregs: tcpuregisterset;
+ localsize: longint;
+ href: treference;
+ begin
+ if not(nostackframe) then
+ begin
+ regs:=rg[R_INTREGISTER].used_in_proc-paramanager.get_volatile_registers_int(pocall_stdcall);
+
+ if current_procinfo.framepointer<>NR_STACK_POINTER_REG then
+ regs:=regs+[RS_FRAME_POINTER_REG,RS_RETURN_ADDRESS_REG];
+
+ if (pi_do_call in current_procinfo.flags) then
+ regs:=regs+[RS_RETURN_ADDRESS_REG];
+
+ reference_reset_base(href,NR_STACK_POINTER_REG,-8,ctempposinvalid,0,[]);
+ for r:=RS_X31 downto RS_X0 do
+ if r in regs then
+ dec(href.offset,8);
+
+ { Float registers }
+ fregs:=rg[R_FPUREGISTER].used_in_proc-paramanager.get_volatile_registers_fpu(pocall_stdcall);
+ for r:=RS_F0 to RS_F31 do
+ if r in fregs then
+ dec(href.offset,8);
+
+ localsize:=current_procinfo.calc_stackframe_size+(-href.offset-8);
+ if current_procinfo.framepointer<>NR_STACK_POINTER_REG then
+ list.concat(taicpu.op_reg_reg_const(A_ADDI,NR_STACK_POINTER_REG,NR_FRAME_POINTER_REG,0))
+ else if localsize>0 then
+ begin
+ localsize:=align(localsize,8);
+
+ if is_imm12(localsize) then
+ list.concat(taicpu.op_reg_reg_const(A_ADDI,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,localsize))
+ else
+ begin
+ if not (RS_RETURN_ADDRESS_REG in regs) then
+ begin
+ include(regs,RS_RETURN_ADDRESS_REG);
+ dec(href.offset,8);
+ inc(localsize,8);
+ end;
+
+ a_load_const_reg(list,OS_INT,localsize,NR_RETURN_ADDRESS_REG);
+ list.concat(taicpu.op_reg_reg_reg(A_ADD,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,NR_RETURN_ADDRESS_REG));
+ end;
+ end;
+
+ { Float registers }
+ for r:=RS_F31 downto RS_F0 do
+ if r in fregs then
+ begin
+ inc(href.offset,8);
+ list.concat(taicpu.op_reg_ref(A_FLD,newreg(R_FPUREGISTER,r,R_SUBWHOLE),href));
+ end;
+
+ for r:=RS_X31 downto RS_X0 do
+ if r in regs then
+ begin
+ inc(href.offset,8);
+ list.concat(taicpu.op_reg_ref(A_LD,newreg(R_INTREGISTER,r,R_SUBWHOLE),href));
+ end;
+ end;
+
+ list.concat(taicpu.op_reg_reg(A_JALR,NR_X0,NR_RETURN_ADDRESS_REG));
+ end;
+
+
+ procedure tcgrv64.g_concatcopy_move(list: tasmlist; const Source, dest: treference; len: tcgint);
+ var
+ paraloc1, paraloc2, paraloc3: TCGPara;
+ pd: tprocdef;
+ begin
+ pd:=search_system_proc('MOVE');
+ paraloc1.init;
+ paraloc2.init;
+ paraloc3.init;
+ paramanager.getintparaloc(list, pd, 1, paraloc1);
+ paramanager.getintparaloc(list, pd, 2, paraloc2);
+ paramanager.getintparaloc(list, pd, 3, paraloc3);
+ a_load_const_cgpara(list, OS_SINT, len, paraloc3);
+ a_loadaddr_ref_cgpara(list, dest, paraloc2);
+ a_loadaddr_ref_cgpara(list, Source, paraloc1);
+ paramanager.freecgpara(list, paraloc3);
+ paramanager.freecgpara(list, paraloc2);
+ paramanager.freecgpara(list, paraloc1);
+ alloccpuregisters(list, R_INTREGISTER, paramanager.get_volatile_registers_int(pocall_default));
+ alloccpuregisters(list, R_FPUREGISTER, paramanager.get_volatile_registers_fpu(pocall_default));
+ a_call_name(list, 'FPC_MOVE', false);
+ dealloccpuregisters(list, R_FPUREGISTER, paramanager.get_volatile_registers_fpu(pocall_default));
+ dealloccpuregisters(list, R_INTREGISTER, paramanager.get_volatile_registers_int(pocall_default));
+ paraloc3.done;
+ paraloc2.done;
+ paraloc1.done;
+ end;
+
+ procedure tcgrv64.g_concatcopy(list: TAsmList; const source, dest: treference; len: aint);
+ var
+ tmpreg1, hreg, countreg: TRegister;
+ src, dst, src2, dst2: TReference;
+ lab: tasmlabel;
+ Count, count2: aint;
+ begin
+ src2:=source;
+ fixref(list,src2);
+
+ dst2:=dest;
+ fixref(list,dst2);
+
+ if len > high(longint) then
+ internalerror(2002072704);
+ { A call (to FPC_MOVE) requires the outgoing parameter area to be properly
+ allocated on stack. This can only be done before tmipsprocinfo.set_first_temp_offset,
+ i.e. before secondpass. Other internal procedures request correct stack frame
+ by setting pi_do_call during firstpass, but for this particular one it is impossible.
+ Therefore, if the current procedure is a leaf one, we have to leave it that way. }
+
+ { anybody wants to determine a good value here :)? }
+ if (len > 100) and
+ assigned(current_procinfo) and
+ (pi_do_call in current_procinfo.flags) then
+ g_concatcopy_move(list, src2, dst2, len)
+ else
+ begin
+ Count := len div 8;
+ reference_reset(src,sizeof(aint),[]);
+ { load the address of src2 into src.base }
+ src.base := GetAddressRegister(list);
+ a_loadaddr_ref_reg(list, src2, src.base);
+
+ reference_reset(dst,sizeof(aint),[]);
+ { load the address of dst2 into dst.base }
+ dst.base := GetAddressRegister(list);
+ a_loadaddr_ref_reg(list, dst2, dst.base);
+
+ { generate a loop }
+ if Count > 4 then
+ begin
+ countreg := GetIntRegister(list, OS_INT);
+ tmpreg1 := GetIntRegister(list, OS_INT);
+ a_load_const_reg(list, OS_INT, Count, countreg);
+ current_asmdata.getjumplabel(lab);
+ a_label(list, lab);
+ list.concat(taicpu.op_reg_ref(A_LD, tmpreg1, src));
+ list.concat(taicpu.op_reg_ref(A_SD, tmpreg1, dst));
+ list.concat(taicpu.op_reg_reg_const(A_ADDI, src.base, src.base, 8));
+ list.concat(taicpu.op_reg_reg_const(A_ADDI, dst.base, dst.base, 8));
+ list.concat(taicpu.op_reg_reg_const(A_ADDI, countreg, countreg, -1));
+ a_cmp_reg_reg_label(list,OS_INT,OC_GT,NR_X0,countreg,lab);
+ len := len mod 8;
+ end;
+ { unrolled loop }
+ Count := len div 8;
+ if Count > 0 then
+ begin
+ tmpreg1 := GetIntRegister(list, OS_INT);
+ count2 := 1;
+ while count2 <= Count do
+ begin
+ list.concat(taicpu.op_reg_ref(A_LD, tmpreg1, src));
+ list.concat(taicpu.op_reg_ref(A_SD, tmpreg1, dst));
+ Inc(src.offset, 8);
+ Inc(dst.offset, 8);
+ Inc(count2);
+ end;
+ len := len mod 8;
+ end;
+ if (len and 4) <> 0 then
+ begin
+ hreg := GetIntRegister(list, OS_INT);
+ a_load_ref_reg(list, OS_32, OS_32, src, hreg);
+ a_load_reg_ref(list, OS_32, OS_32, hreg, dst);
+ Inc(src.offset, 4);
+ Inc(dst.offset, 4);
+ end;
+ { copy the leftovers }
+ if (len and 2) <> 0 then
+ begin
+ hreg := GetIntRegister(list, OS_INT);
+ a_load_ref_reg(list, OS_16, OS_16, src, hreg);
+ a_load_reg_ref(list, OS_16, OS_16, hreg, dst);
+ Inc(src.offset, 2);
+ Inc(dst.offset, 2);
+ end;
+ if (len and 1) <> 0 then
+ begin
+ hreg := GetIntRegister(list, OS_INT);
+ a_load_ref_reg(list, OS_8, OS_8, src, hreg);
+ a_load_reg_ref(list, OS_8, OS_8, hreg, dst);
+ end;
+ end;
+ end;
+
+procedure create_codegen;
+begin
+ cg := tcgrv64.create;
+ cg128:=tcg128.create;
+end;
+
+end.
diff --git a/compiler/riscv64/cpubase.pas b/compiler/riscv64/cpubase.pas
new file mode 100644
index 0000000000..89ce7d292a
--- /dev/null
+++ b/compiler/riscv64/cpubase.pas
@@ -0,0 +1,462 @@
+{
+ Copyright (c) 1998-2002 by Florian Klaempfl
+
+ Contains the base types for the RiscV64
+
+ 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 base types for the RiscV64
+}
+unit cpubase;
+
+{$I fpcdefs.inc}
+
+interface
+
+uses
+ strings, globtype,
+ cutils, cclasses, aasmbase, cpuinfo, cgbase;
+
+{*****************************************************************************
+ Assembler Opcodes
+*****************************************************************************}
+
+type
+ TAsmOp=(A_None,
+ { Pseudo instructions }
+ A_NOP,
+ { normal opcodes }
+ A_LUI,A_AUIPC,A_JAL,A_JALR,
+ A_Bxx,A_LB,A_LH,A_LW,A_LBU,A_LHU,
+ A_SB,A_SH,A_SW,
+ A_ADDI,A_SLTI,A_SLTIU,
+ A_XORI,A_ORI,A_ANDI,
+ A_SLLI,A_SRLI,A_SRAI,
+ A_ADD,A_SUB,A_SLL,A_SLT,A_SLTU,
+ A_XOR,A_SRL,A_SRA,A_OR,A_AND,
+ A_FENCE,A_FENCE_I,
+ A_ECALL,A_EBREAK,
+ A_CSRRW,A_CSRRS,A_CSRRC,A_CSRRWI,A_CSRRSI,A_CSRRCI,
+ { 64-bit }
+ A_ADDIW,A_SLLIW,A_SRLIW,A_SRAIW,
+ A_ADDW,A_SLLW,A_SRLW,A_SUBW,A_SRAW,
+ A_LD,A_SD,A_LWU,
+
+ { M-extension }
+ A_MUL,A_MULH,A_MULHSU,A_MULHU,
+ A_DIV,A_DIVU,A_REM,A_REMU,
+ { 64-bit }
+ A_MULW,
+ A_DIVW,A_DIVUW,A_REMW,A_REMUW,
+
+ { A-extension }
+ A_LR_W,A_SC_W,A_AMOSWAP_W,A_AMOADD_W,A_AMOXOR_W,A_AMOAND_W,
+ A_AMOOR_W,A_AMOMIN_W,A_AMOMAX_W,A_AMOMINU_W,A_AMOMAXU_W,
+ { 64-bit }
+ A_LR_D,A_SC_D,A_AMOSWAP_D,A_AMOADD_D,A_AMOXOR_D,A_AMOAND_D,
+ A_AMOOR_D,A_AMOMIN_D,A_AMOMAX_D,A_AMOMINU_D,A_AMOMAXU_D,
+
+ { F-extension }
+ A_FLW,A_FSW,
+ A_FMADD_S,A_FMSUB_S,A_FNMSUB_S,A_FNMADD_S,
+ A_FADD_S,A_FSUB_S,A_FMUL_S,A_FDIV_S,
+ A_FSQRT_S,A_FSGNJ_S,A_FSGNJN_S,A_FSGNJX_S,
+ A_FMIN_S,A_FMAX_S,
+ A_FMV_X_S,A_FEQ_S,A_FLT_S,A_FLE_S,A_FCLASS_S,
+ A_FCVT_W_S,A_FCVT_WU_S,A_FCVT_S_W,A_FCVT_S_WU,
+ A_FMV_S_X,
+ A_FRCSR,A_FRRM,A_FRFLAGS,A_FSCSR,A_FSRM,
+ A_FSFLAGS,A_FSRMI,A_FSFLAGSI,
+ { 64-bit }
+ A_FCVT_L_S,A_FCVT_LU_S,
+ A_FCVT_S_L,A_FCVT_S_LU,
+
+ { D-extension }
+ A_FLD,A_FSD,
+ A_FMADD_D,A_FMSUB_D,A_FNMSUB_D,A_FNMADD_D,
+ A_FADD_D,A_FSUB_D,A_FMUL_D,A_FDIV_D,
+ A_FSQRT_D,A_FSGNJ_D,A_FSGNJN_D,A_FSGNJX_D,
+ A_FMIN_D,A_FMAX_D,
+ A_FEQ_D,A_FLT_D,A_FLE_D,A_FCLASS_D,
+ A_FCVT_D_S,A_FCVT_S_D,
+ A_FCVT_W_D,A_FCVT_WU_D,A_FCVT_D_W,A_FCVT_D_WU,
+ { 64-bit }
+ A_FCVT_L_D,A_FCVT_LU_D,A_FMV_X_D,
+ A_FCVT_D_L,A_FCVT_D_LU,A_FMV_D_X,
+
+ { Machine mode }
+ A_MRET,A_HRET,A_SRET,A_URET,
+ A_WFI,
+
+ { Supervisor }
+ A_SFENCE_VM
+ );
+
+ TAsmOps = set of TAsmOp;
+
+ {# This should define the array of instructions as string }
+ op2strtable = array[tasmop] of string[8];
+
+const
+ {# First value of opcode enumeration }
+ firstop = low(tasmop);
+ {# Last value of opcode enumeration }
+ lastop = high(tasmop);
+
+ {*****************************************************************************
+ Registers
+ *****************************************************************************}
+
+type
+ { Number of registers used for indexing in tables }
+ tregisterindex=0..{$i rrv32nor.inc}-1;
+ totherregisterset = set of tregisterindex;
+
+ const
+ maxvarregs = 32-6; { 32 int registers - r0 - stackpointer - r2 - 3 scratch registers }
+ maxfpuvarregs = 28; { 32 fpuregisters - some scratch registers (minimally 2) }
+ { Available Superregisters }
+ {$i rrv32sup.inc}
+
+ { No Subregisters }
+ R_SUBWHOLE=R_SUBNONE;
+
+ { Available Registers }
+ {$i rrv32con.inc}
+
+ { Integer Super registers first and last }
+ first_int_imreg = $20;
+
+ { Float Super register first and last }
+ first_fpu_imreg = $20;
+
+ { MM Super register first and last }
+ first_mm_imreg = $20;
+
+{ TODO: Calculate bsstart}
+ regnumber_count_bsstart = 64;
+
+ regnumber_table : array[tregisterindex] of tregister = (
+ {$i rrv32num.inc}
+ );
+
+ regstabs_table : array[tregisterindex] of shortint = (
+ {$i rrv32sta.inc}
+ );
+
+ regdwarf_table : array[tregisterindex] of shortint = (
+ {$i rrv32dwa.inc}
+ );
+
+{*****************************************************************************
+ Operands
+*****************************************************************************}
+ type
+ TMemoryOrderingFlag = (moRl, moAq);
+ TMemoryOrdering = set of TMemoryOrderingFlag;
+
+ TFenceFlag = (ffI, ffO, ffR, ffW);
+ TFenceFlags = set of TFenceFlag;
+
+ TRoundingMode = (RM_Default,
+ RM_RNE,
+ RM_RTZ,
+ RM_RDN,
+ RM_RUP,
+ RM_RMM);
+
+ const
+ roundingmode2str : array[TRoundingMode] of string[3] = ('',
+ 'rne','rtz','rdn','rup','rmm');
+
+{*****************************************************************************
+ Conditions
+*****************************************************************************}
+
+ type
+ TAsmCond = (C_None { unconditional jumps },
+ C_LT,C_LTU,C_GE,C_GEU,C_NE,C_EQ);
+
+ TAsmConds = set of TAsmCond;
+
+ const
+ cond2str: Array[TAsmCond] of string[4] = ({cf_none}'',
+ { conditions when not using ctr decrement etc}
+ 'lt','ltu','ge','geu','ne','eq');
+
+ uppercond2str: Array[TAsmCond] of string[4] = ({cf_none}'',
+ { conditions when not using ctr decrement etc}
+ 'LT','LTU','GE','GEU','NE','EQ');
+
+ {*****************************************************************************
+ Flags
+ *****************************************************************************}
+
+type
+ TResFlagsEnum = (F_EQ,F_NE,F_LT,F_LTU,F_GE,F_GEU);
+
+{*****************************************************************************
+ Reference
+*****************************************************************************}
+
+ {*****************************************************************************
+ Operand Sizes
+ *****************************************************************************}
+
+ {*****************************************************************************
+ Constants
+ *****************************************************************************}
+
+const
+ max_operands = 5;
+
+ {*****************************************************************************
+ Default generic sizes
+ *****************************************************************************}
+
+ {# Defines the default address size for a processor, }
+ OS_ADDR = OS_64;
+ {# the natural int size for a processor,
+ has to match osuinttype/ossinttype as initialized in psystem }
+ OS_INT = OS_64;
+ OS_SINT = OS_S64;
+ {# the maximum float size for a processor, }
+ OS_FLOAT = OS_F64;
+ {# the size of a vector register for a processor }
+ OS_VECTOR = OS_M128;
+
+ {*****************************************************************************
+ GDB Information
+ *****************************************************************************}
+
+ stab_regindex: array[tregisterindex] of shortint = (
+{$I rrv32sta.inc}
+ );
+
+ {*****************************************************************************
+ Generic Register names
+ *****************************************************************************}
+
+ {# Stack pointer register }
+ NR_STACK_POINTER_REG = NR_X2;
+ RS_STACK_POINTER_REG = RS_X2;
+ {# Frame pointer register }
+ NR_FRAME_POINTER_REG = NR_X8;
+ RS_FRAME_POINTER_REG = RS_X8;
+
+ NR_PIC_OFFSET_REG = NR_X3;
+ { Return address of a function }
+ NR_RETURN_ADDRESS_REG = NR_X1;
+ RS_RETURN_ADDRESS_REG = RS_X1;
+ { Results are returned in this register (32-bit values) }
+ NR_FUNCTION_RETURN_REG = NR_X10;
+ RS_FUNCTION_RETURN_REG = RS_X10;
+ { Low part of 64bit return value }
+ NR_FUNCTION_RETURN64_LOW_REG = NR_X10;
+ RS_FUNCTION_RETURN64_LOW_REG = RS_X10;
+ { High part of 64bit return value }
+ NR_FUNCTION_RETURN64_HIGH_REG = NR_X11;
+ RS_FUNCTION_RETURN64_HIGH_REG = RS_X11;
+ { The value returned from a function is available in this register }
+ NR_FUNCTION_RESULT_REG = NR_FUNCTION_RETURN_REG;
+ RS_FUNCTION_RESULT_REG = RS_FUNCTION_RETURN_REG;
+ { The lowh part of 64bit value returned from a function }
+ NR_FUNCTION_RESULT64_LOW_REG = NR_FUNCTION_RETURN64_LOW_REG;
+ RS_FUNCTION_RESULT64_LOW_REG = RS_FUNCTION_RETURN64_LOW_REG;
+ { The high part of 64bit value returned from a function }
+ NR_FUNCTION_RESULT64_HIGH_REG = NR_FUNCTION_RETURN64_HIGH_REG;
+ RS_FUNCTION_RESULT64_HIGH_REG = RS_FUNCTION_RETURN64_HIGH_REG;
+
+ NR_FPU_RESULT_REG = NR_F10;
+ NR_MM_RESULT_REG = NR_NO;
+
+ NR_DEFAULTFLAGS = NR_NO;
+ RS_DEFAULTFLAGS = RS_NO;
+
+ {*****************************************************************************
+ GCC /ABI linking information
+ *****************************************************************************}
+
+ {# Registers which must be saved when calling a routine declared as
+ cppdecl, cdecl, stdcall, safecall, palmossyscall. The registers
+ saved should be the ones as defined in the target ABI and / or GCC.
+
+ This value can be deduced from CALLED_USED_REGISTERS array in the
+ GCC source.
+ }
+ saved_standard_registers: array[0..12] of tsuperregister = (
+ RS_X2,
+ RS_X8,RS_X9,
+ RS_X18,RS_X19,
+ RS_X20,RS_X21,RS_X22,RS_X23,RS_X24,RS_X25,RS_X26,RS_X27
+ );
+
+ { this is only for the generic code which is not used for this architecture }
+ saved_address_registers : array[0..0] of tsuperregister = (RS_INVALID);
+ saved_mm_registers : array[0..0] of tsuperregister = (RS_INVALID);
+
+ {# Required parameter alignment when calling a routine declared as
+ stdcall and cdecl. The alignment value should be the one defined
+ by GCC or the target ABI.
+
+ The value of this constant is equal to the constant
+ PARM_BOUNDARY / BITS_PER_UNIT in the GCC source.
+ }
+ std_param_align = 8; { for 32-bit version only }
+
+
+{*****************************************************************************
+ CPU Dependent Constants
+*****************************************************************************}
+
+ maxfpuregs = 8;
+
+ {*****************************************************************************
+ Helpers
+ *****************************************************************************}
+
+ function is_imm12(value: aint): boolean;
+ function is_lui_imm(value: aint): boolean;
+
+ function is_calljmp(o:tasmop):boolean;
+
+ function cgsize2subreg(regtype: tregistertype; s:Tcgsize):Tsubregister;
+ { Returns the tcgsize corresponding with the size of reg.}
+ function reg_cgsize(const reg: tregister) : tcgsize;
+
+ function findreg_by_number(r:Tregister):tregisterindex;
+ function std_regnum_search(const s:string):Tregister;
+ function std_regname(r:Tregister):string;
+
+ function inverse_cond(const c: TAsmCond): Tasmcond; {$ifdef USEINLINE}inline;{$endif USEINLINE}
+ function dwarf_reg(r:tregister):shortint;
+
+ function conditions_equal(const c1,c2: TAsmCond): boolean;
+
+implementation
+
+ uses
+ rgbase,verbose;
+
+ const
+ std_regname_table : TRegNameTable = (
+ {$i rrv32std.inc}
+ );
+
+ regnumber_index : array[tregisterindex] of tregisterindex = (
+ {$i rrv32rni.inc}
+ );
+
+ std_regname_index : array[tregisterindex] of tregisterindex = (
+ {$i rrv32sri.inc}
+ );
+
+
+{*****************************************************************************
+ Helpers
+*****************************************************************************}
+
+ function is_imm12(value: aint): boolean;
+ begin
+ result:=(value >= -2048) and (value <= 2047);
+ end;
+
+
+ function is_lui_imm(value: aint): boolean;
+ begin
+ result:=SarInt64((value and $FFFFF000) shl 32, 32) = value;
+ end;
+
+
+ function is_calljmp(o:tasmop):boolean;
+ begin
+ is_calljmp:=false;
+ case o of
+ A_JAL,A_JALR,A_Bxx:
+ is_calljmp:=true;
+ end;
+ end;
+
+
+ function inverse_cond(const c: TAsmCond): Tasmcond; {$ifdef USEINLINE}inline;{$endif USEINLINE}
+ const
+ inv_condflags:array[TAsmCond] of TAsmCond=(C_None,
+ C_GE,C_GEU,C_LT,C_LTU,C_EQ,C_NE);
+ begin
+ result := inv_condflags[c];
+ end;
+
+
+ function reg_cgsize(const reg: tregister): tcgsize;
+ begin
+ case getregtype(reg) of
+ R_INTREGISTER :
+ result:=OS_64;
+ R_MMREGISTER:
+ result:=OS_M128;
+ R_FPUREGISTER:
+ result:=OS_F64;
+ else
+ internalerror(200303181);
+ end;
+ end;
+
+
+ function cgsize2subreg(regtype: tregistertype; s:Tcgsize):Tsubregister;
+ begin
+ cgsize2subreg:=R_SUBWHOLE;
+ end;
+
+
+ function findreg_by_number(r:Tregister):tregisterindex;
+ begin
+ result:=rgBase.findreg_by_number_table(r,regnumber_index);
+ end;
+
+
+ function std_regnum_search(const s:string):Tregister;
+ begin
+ result:=regnumber_table[findreg_by_name_table(s,std_regname_table,std_regname_index)];
+ end;
+
+
+ function std_regname(r:Tregister):string;
+ var
+ p : tregisterindex;
+ begin
+ p:=findreg_by_number_table(r,regnumber_index);
+ if p<>0 then
+ result:=std_regname_table[p]
+ else
+ result:=generic_regname(r);
+ end;
+
+
+ function dwarf_reg(r:tregister):shortint;
+ begin
+ result:=regdwarf_table[findreg_by_number(r)];
+ if result=-1 then
+ internalerror(200603251);
+ end;
+
+ function conditions_equal(const c1, c2: TAsmCond): boolean;
+ begin
+ result:=c1=c2;
+ end;
+
+end.
+
diff --git a/compiler/riscv64/cpuinfo.pas b/compiler/riscv64/cpuinfo.pas
new file mode 100644
index 0000000000..91879a0b48
--- /dev/null
+++ b/compiler/riscv64/cpuinfo.pas
@@ -0,0 +1,139 @@
+{
+ Copyright (c) 1998-2002 by the Free Pascal development team
+
+ Basic Processor information for the Risc-V64
+
+ See the file COPYING.FPC, included in this distribution,
+ for details about the copyright.
+
+ 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.
+
+ **********************************************************************}
+
+unit CPUInfo;
+
+interface
+
+uses
+ globtype;
+
+type
+ bestreal = double;
+{$if FPC_FULLVERSION>20700}
+ bestrealrec = TDoubleRec;
+{$endif FPC_FULLVERSION>20700}
+ ts32real = single;
+ ts64real = double;
+ ts80real = extended;
+ ts128real = extended;
+ ts64comp = comp;
+
+ pbestreal = ^bestreal;
+
+ { possible supported processors for this target }
+ tcputype = (cpu_none,
+ cpu_rv64imafdc,
+ cpu_rv64imafd,
+ cpu_rv64ima,
+ cpu_rv64im,
+ cpu_rv64i
+ );
+
+ tfputype =
+ (fpu_none,
+ fpu_libgcc,
+ fpu_soft,
+ fpu_fd
+ );
+
+ tcontrollertype =
+ (ct_none
+ );
+
+ tcontrollerdatatype = record
+ controllertypestr, controllerunitstr: string[20];
+ cputype: tcputype; fputype: tfputype;
+ flashbase, flashsize, srambase, sramsize, eeprombase, eepromsize, bootbase, bootsize: dword;
+ end;
+
+
+Const
+ { Is there support for dealing with multiple microcontrollers available }
+ { for this platform? }
+ ControllerSupport = false;
+
+ { We know that there are fields after sramsize
+ but we don't care about this warning }
+ {$PUSH}
+ {$WARN 3177 OFF}
+ embedded_controllers : array [tcontrollertype] of tcontrollerdatatype =
+ (
+ (controllertypestr:''; controllerunitstr:''; cputype:cpu_none; fputype:fpu_none; flashbase:0; flashsize:0; srambase:0; sramsize:0));
+ {$POP}
+
+ { calling conventions supported by the code generator }
+ supported_calling_conventions: tproccalloptions = [
+ pocall_internproc,
+ pocall_stdcall,
+ { the difference to stdcall is only the name mangling }
+ pocall_cdecl,
+ { the difference to stdcall is only the name mangling }
+ pocall_cppdecl,
+ { the difference with stdcall is that all const record
+ parameters are passed by reference }
+ pocall_mwpascal
+ ];
+
+ cputypestr: array[tcputype] of string[10] = ('',
+ 'RV64IMAFDC',
+ 'RV64IMAFD',
+ 'RV64IMA',
+ 'RV64IM',
+ 'RV64I'
+ );
+
+ fputypestr: array[tfputype] of string[8] = ('',
+ 'LIBGCC',
+ 'SOFT',
+ 'FD'
+ );
+
+ { Supported optimizations, only used for information }
+ supported_optimizerswitches = genericlevel1optimizerswitches+
+ genericlevel2optimizerswitches+
+ genericlevel3optimizerswitches-
+ { no need to write info about those }
+ [cs_opt_level1,cs_opt_level2,cs_opt_level3]+
+ [cs_opt_regvar,cs_opt_loopunroll,cs_opt_nodecse,
+ cs_opt_tailrecursion,cs_opt_reorder_fields,cs_opt_fastmath,
+ cs_opt_stackframe];
+
+ level1optimizerswitches = genericlevel1optimizerswitches;
+ level2optimizerswitches = genericlevel2optimizerswitches + level1optimizerswitches +
+ [cs_opt_regvar,cs_opt_stackframe,cs_opt_nodecse,cs_opt_tailrecursion];
+ level3optimizerswitches = genericlevel3optimizerswitches + level2optimizerswitches + [{,cs_opt_loopunroll}];
+ level4optimizerswitches = genericlevel4optimizerswitches + level3optimizerswitches + [cs_opt_stackframe];
+
+ type
+ tcpuflags =
+ (CPURV_HAS_MUL,
+ CPURV_HAS_ATOMIC,
+ CPURV_HAS_COMPACT
+ );
+
+ const
+ cpu_capabilities : array[tcputype] of set of tcpuflags =
+ ( { cpu_none } [],
+ { cpu_rv64imafdc } [CPURV_HAS_MUL,CPURV_HAS_ATOMIC,CPURV_HAS_COMPACT],
+ { cpu_rv64imafd } [CPURV_HAS_MUL,CPURV_HAS_ATOMIC],
+ { cpu_rv64ima } [CPURV_HAS_MUL,CPURV_HAS_ATOMIC],
+ { cpu_rv64im } [CPURV_HAS_MUL],
+ { cpu_rv64i } []
+ );
+
+implementation
+
+end.
+
diff --git a/compiler/riscv64/cpunode.pas b/compiler/riscv64/cpunode.pas
new file mode 100644
index 0000000000..e619c41a42
--- /dev/null
+++ b/compiler/riscv64/cpunode.pas
@@ -0,0 +1,55 @@
+{
+ Copyright (c) 2000-2002 by Florian Klaempfl
+
+ Includes the RiscV64 code generator
+
+ 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 cpunode;
+
+{$I fpcdefs.inc}
+
+interface
+
+implementation
+
+uses
+ { generic nodes }
+ ncgbas, ncgld, ncgflw, ncgcnv, ncgmem, ncgcon, ncgcal, ncgset, ncginl, ncgopt,
+ ncgobjc,
+ { symtable }
+ symcpu,
+ aasmdef,
+ { to be able to only parts of the generic code,
+ the processor specific nodes must be included
+ after the generic one (FK)
+ }
+{$ifndef llvm}
+ nrv64add,
+ nrv64cal,
+ nrvset,
+ nrvinl,
+ nrv64mat,
+ nrv64cnv,
+ nrv64ld
+{$else not llvm}
+ llvmnode
+{$endif not llvm}
+ ;
+
+end.
+
diff --git a/compiler/riscv64/cpupara.pas b/compiler/riscv64/cpupara.pas
new file mode 100644
index 0000000000..67602ed122
--- /dev/null
+++ b/compiler/riscv64/cpupara.pas
@@ -0,0 +1,545 @@
+{
+ Copyright (c) 2002 by Florian Klaempfl
+
+ RiscV64 specific calling conventions
+
+ 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 cpupara;
+
+{$I fpcdefs.inc}
+
+ interface
+
+ uses
+ globtype,
+ aasmtai,aasmdata,
+ cpubase,
+ symconst, symtype, symdef, symsym,
+ paramgr, parabase, cgbase, cgutils;
+
+ type
+ tcpuparamanager = class(tparamanager)
+ function get_volatile_registers_int(calloption: tproccalloption): tcpuregisterset; override;
+ function get_volatile_registers_fpu(calloption: tproccalloption): tcpuregisterset; override;
+ function push_addr_param(varspez: tvarspez; def: tdef; calloption: tproccalloption): boolean; override;
+ function ret_in_param(def: tdef; pd: tabstractprocdef): boolean; override;
+
+ procedure getintparaloc(list: TAsmList; pd : tabstractprocdef; nr: longint; var cgpara: tcgpara); override;
+ function create_paraloc_info(p: tabstractprocdef; side: tcallercallee): longint; override;
+ function create_varargs_paraloc_info(p: tabstractprocdef; varargspara: tvarargsparalist): longint; override;
+ function get_funcretloc(p : tabstractprocdef; side: tcallercallee; forcetempdef: tdef): tcgpara;override;
+
+ private
+ procedure init_values(var curintreg, curfloatreg, curmmreg: tsuperregister; var cur_stack_offset: aword);
+ function create_paraloc_info_intern(p: tabstractprocdef; side: tcallercallee; paras: tparalist; var curintreg, curfloatreg, curmmreg: tsuperregister; var cur_stack_offset: aword; isVararg : boolean): longint;
+ function parseparaloc(p: tparavarsym; const s: string): boolean; override;
+ procedure create_paraloc_for_def(var para: TCGPara; varspez: tvarspez; paradef: tdef; var nextfloatreg, nextintreg: tsuperregister; var stack_offset: aword; const isVararg, forceintmem: boolean; const side: tcallercallee; const p: tabstractprocdef);
+ end;
+
+implementation
+
+ uses
+ verbose, systems,
+ globals, cpuinfo,
+ defutil,symtable,symcpu,
+ procinfo, cpupi;
+
+ function tcpuparamanager.get_volatile_registers_int(calloption: tproccalloption): tcpuregisterset;
+ begin
+ result:=[RS_X0..RS_X31]-[RS_X2,RS_X8..RS_X9,RS_X18..RS_X27];
+ end;
+
+ function tcpuparamanager.get_volatile_registers_fpu(calloption: tproccalloption): tcpuregisterset;
+ begin
+ result:=[RS_F0..RS_F31]-[RS_F8..RS_F9,RS_F18..RS_F27];
+ end;
+
+ procedure tcpuparamanager.getintparaloc(list: TAsmList; pd : tabstractprocdef; nr: longint; var cgpara: tcgpara);
+ var
+ paraloc: pcgparalocation;
+ psym: tparavarsym;
+ pdef: tdef;
+ begin
+ psym:=tparavarsym(pd.paras[nr-1]);
+ pdef:=psym.vardef;
+ if push_addr_param(psym.varspez,pdef,pd.proccalloption) then
+ pdef:=cpointerdef.getreusable_no_free(pdef);
+ cgpara.reset;
+ cgpara.size := def_cgsize(pdef);
+ cgpara.intsize := tcgsize2size[cgpara.size];
+ cgpara.alignment := get_para_align(pd.proccalloption);
+ cgpara.def:=pdef;
+ paraloc := cgpara.add_location;
+ with paraloc^ do begin
+ size := def_cgsize(pdef);
+ def := pdef;
+ if (nr <= 8) then begin
+ if (nr = 0) then
+ internalerror(200309271);
+ loc := LOC_REGISTER;
+ register := newreg(R_INTREGISTER, RS_X10 + nr-1, R_SUBWHOLE);
+ end else begin
+ loc := LOC_REFERENCE;
+ paraloc^.reference.index := NR_STACK_POINTER_REG;
+ reference.offset := sizeof(aint) * (nr - 9);
+ end;
+ end;
+ end;
+
+ function getparaloc(p: tdef): tcgloc;
+ begin
+ { Later, the LOC_REFERENCE is in most cases changed into LOC_REGISTER
+ if push_addr_param for the def is true
+ }
+ case p.typ of
+ orddef:
+ result := LOC_REGISTER;
+ floatdef:
+ if (cs_fp_emulation in current_settings.moduleswitches) or
+ (current_settings.fputype in [fpu_soft]) then
+ result := LOC_REGISTER
+ else
+ result := LOC_FPUREGISTER;
+ enumdef:
+ result := LOC_REGISTER;
+ pointerdef:
+ result := LOC_REGISTER;
+ formaldef:
+ result := LOC_REGISTER;
+ classrefdef:
+ result := LOC_REGISTER;
+ procvardef,
+ recorddef:
+ result := LOC_REGISTER;
+ objectdef:
+ if is_object(p) then
+ result := LOC_REFERENCE
+ else
+ result := LOC_REGISTER;
+ stringdef:
+ if is_shortstring(p) or is_longstring(p) then
+ result := LOC_REFERENCE
+ else
+ result := LOC_REGISTER;
+ filedef:
+ result := LOC_REGISTER;
+ arraydef:
+ if is_dynamic_array(p) then
+ getparaloc:=LOC_REGISTER
+ else
+ result := LOC_REFERENCE;
+ setdef:
+ if is_smallset(p) then
+ result := LOC_REGISTER
+ else
+ result := LOC_REFERENCE;
+ variantdef:
+ result := LOC_REFERENCE;
+ { avoid problems with errornous definitions }
+ errordef:
+ result := LOC_REGISTER;
+ else
+ internalerror(2002071001);
+ end;
+ end;
+
+ function tcpuparamanager.push_addr_param(varspez: tvarspez; def: tdef; calloption: tproccalloption): boolean;
+ begin
+ result := false;
+ { var,out,constref always require address }
+ if varspez in [vs_var, vs_out, vs_constref] then
+ begin
+ result := true;
+ exit;
+ end;
+ case def.typ of
+ variantdef,
+ formaldef:
+ result := true;
+ procvardef,
+ recorddef:
+ result := (def.size > 16);
+ arraydef:
+ result := (tarraydef(def).highrange >= tarraydef(def).lowrange) or
+ is_open_array(def) or
+ is_array_of_const(def) or
+ is_array_constructor(def);
+ objectdef:
+ result := is_object(def);
+ setdef:
+ result := not is_smallset(def);
+ stringdef:
+ result := tstringdef(def).stringtype in [st_shortstring, st_longstring];
+ end;
+ end;
+
+ function tcpuparamanager.ret_in_param(def: tdef; pd: tabstractprocdef): boolean;
+ var
+ tmpdef: tdef;
+ begin
+ if handle_common_ret_in_param(def,pd,result) then
+ exit;
+
+ { general rule: passed in registers -> returned in registers }
+ result:=push_addr_param(vs_value,def,pd.proccalloption);
+ end;
+
+ procedure tcpuparamanager.init_values(var curintreg, curfloatreg, curmmreg: tsuperregister; var cur_stack_offset: aword);
+ begin
+ { register parameter save area begins at 48(r2) }
+ cur_stack_offset := 0;
+ curintreg := RS_X10;
+ curfloatreg := RS_F10;
+ curmmreg := RS_NO;
+ end;
+
+ function tcpuparamanager.get_funcretloc(p : tabstractprocdef; side: tcallercallee; forcetempdef: tdef): tcgpara;
+ var
+ paraloc: pcgparalocation;
+ retcgsize: tcgsize;
+ nextfloatreg, nextintreg, nextmmreg: tsuperregister;
+ stack_offset: aword;
+ begin
+ if set_common_funcretloc_info(p,forcetempdef,retcgsize,result) then
+ exit;
+
+ { in this case, it must be returned in registers as if it were passed
+ as the first parameter }
+ init_values(nextintreg,nextfloatreg,nextmmreg,stack_offset);
+ create_paraloc_for_def(result,vs_value,result.def,nextfloatreg,nextintreg,stack_offset,false,false,side,p);
+ { sanity check (LOC_VOID for empty records) }
+ if not assigned(result.location) or
+ not(result.location^.loc in [LOC_REGISTER,LOC_FPUREGISTER,LOC_VOID]) then
+ internalerror(2014113001);
+ end;
+
+ function tcpuparamanager.create_paraloc_info(p: tabstractprocdef; side: tcallercallee): longint;
+ var
+ cur_stack_offset: aword;
+ curintreg, curfloatreg, curmmreg : tsuperregister;
+ begin
+ init_values(curintreg, curfloatreg, curmmreg, cur_stack_offset);
+
+ result := create_paraloc_info_intern(p, side, p.paras, curintreg, curfloatreg, curmmreg, cur_stack_offset, false);
+
+ create_funcretloc_info(p, side);
+ end;
+
+ function tcpuparamanager.create_paraloc_info_intern(p: tabstractprocdef; side: tcallercallee; paras: tparalist; var curintreg, curfloatreg, curmmreg: tsuperregister; var cur_stack_offset: aword; isVararg : boolean): longint;
+ var
+ nextintreg, nextfloatreg, nextmmreg : tsuperregister;
+ i: integer;
+ hp: tparavarsym;
+ paraloc: pcgparalocation;
+ delphi_nestedfp: boolean;
+
+ begin
+{$IFDEF extdebug}
+ if po_explicitparaloc in p.procoptions then
+ internalerror(200411141);
+{$ENDIF extdebug}
+
+ result := 0;
+ nextintreg := curintreg;
+ nextfloatreg := curfloatreg;
+ nextmmreg := curmmreg;
+
+ for i := 0 to paras.count - 1 do begin
+ hp := tparavarsym(paras[i]);
+
+ if (vo_has_explicit_paraloc in hp.varoptions) then begin
+ internalerror(200412153);
+ end;
+
+ { currently only support C-style array of const }
+ if (p.proccalloption in [pocall_cdecl, pocall_cppdecl]) and
+ is_array_of_const(hp.vardef) then begin
+ paraloc := hp.paraloc[side].add_location;
+ { hack: the paraloc must be valid, but is not actually used }
+ paraloc^.loc := LOC_REGISTER;
+ paraloc^.register := NR_X0;
+ paraloc^.size := OS_ADDR;
+ paraloc^.def := voidpointertype;
+ break;
+ end;
+ delphi_nestedfp:=(vo_is_parentfp in hp.varoptions) and (po_delphi_nested_cc in p.procoptions);
+ create_paraloc_for_def(hp.paraloc[side], hp.varspez, hp.vardef,
+ nextfloatreg, nextintreg, cur_stack_offset, isVararg, delphi_nestedfp, side, p);
+ end;
+
+ curintreg := nextintreg;
+ curfloatreg := nextfloatreg;
+ curmmreg := nextmmreg;
+ result := cur_stack_offset;
+ end;
+
+ procedure tcpuparamanager.create_paraloc_for_def(var para: TCGPara; varspez: tvarspez; paradef: tdef; var nextfloatreg, nextintreg: tsuperregister; var stack_offset: aword; const isVararg, forceintmem: boolean; const side: tcallercallee; const p: tabstractprocdef);
+ var
+ paracgsize: tcgsize;
+ loc: tcgloc;
+ paraloc: pcgparalocation;
+ { def to use for all paralocs if <> nil }
+ alllocdef,
+ { def to use for the current paraloc }
+ locdef,
+ tmpdef: tdef;
+ paralen: aint;
+ firstparaloc,
+ paraaligned: boolean;
+ begin
+ alllocdef:=nil;
+ locdef:=nil;
+ para.reset;
+ { have we ensured that the next parameter location will be aligned to the
+ next 8 byte boundary? }
+ paraaligned:=false;
+ if push_addr_param(varspez, paradef, p.proccalloption) then begin
+ paradef := cpointerdef.getreusable_no_free(paradef);
+ loc := LOC_REGISTER;
+ paracgsize := OS_ADDR;
+ paralen := tcgsize2size[OS_ADDR];
+ end else begin
+ if not is_special_array(paradef) then
+ paralen := paradef.size
+ else
+ paralen := tcgsize2size[def_cgsize(paradef)];
+
+ if (paradef.typ=recorddef) and
+ tabstractrecordsymtable(tabstractrecorddef(paradef).symtable).has_single_field(tmpdef) and
+ (tmpdef.typ=floatdef) then
+ begin
+ paradef:=tmpdef;
+ loc:=getparaloc(paradef);
+ paracgsize:=def_cgsize(paradef)
+ end
+ else if (((paradef.typ=arraydef) and not
+ is_special_array(paradef)) or
+ (paradef.typ=recorddef)) then
+ begin
+ { general fallback rule: pass aggregate types in integer registers
+ without special adjustments (incl. Darwin h) }
+ loc:=LOC_REGISTER;
+ paracgsize:=int_cgsize(paralen);
+ end
+ else
+ begin
+ loc:=getparaloc(paradef);
+ paracgsize:=def_cgsize(paradef);
+ { for things like formaldef }
+ if (paracgsize=OS_NO) then
+ begin
+ paracgsize:=OS_ADDR;
+ paralen:=tcgsize2size[OS_ADDR];
+ end;
+ end
+ end;
+
+ { patch FPU values into integer registers if we are processing varargs }
+ if (isVararg) and (paradef.typ = floatdef) then begin
+ loc := LOC_REGISTER;
+ if paracgsize = OS_F64 then
+ paracgsize := OS_64
+ else
+ paracgsize := OS_32;
+ end;
+
+
+ para.alignment := std_param_align;
+ para.size := paracgsize;
+ para.intsize := paralen;
+ para.def := paradef;
+ if (paralen = 0) then
+ if (paradef.typ = recorddef) then begin
+ paraloc := para.add_location;
+ paraloc^.loc := LOC_VOID;
+ end else
+ internalerror(2005011310);
+ if not assigned(alllocdef) then
+ locdef:=paradef
+ else
+ begin
+ locdef:=alllocdef;
+ paracgsize:=def_cgsize(locdef);
+ end;
+ firstparaloc:=true;
+
+ // Parameters passed in 2 registers are passed in a register starting with an even number.
+ if isVararg and
+ (paralen > 8) and
+ (loc = LOC_REGISTER) and
+ (nextintreg <= RS_X17) and
+ odd(nextintreg) then
+ inc(nextintreg);
+
+ { can become < 0 for e.g. 3-byte records }
+ while (paralen > 0) do begin
+ paraloc := para.add_location;
+ { In case of po_delphi_nested_cc, the parent frame pointer
+ is always passed on the stack. }
+ if (loc = LOC_REGISTER) and
+ (nextintreg <= RS_X17) and
+ not forceintmem then begin
+ paraloc^.loc := loc;
+
+ { make sure we don't lose whether or not the type is signed }
+ if (paracgsize <> OS_NO) and
+ (paradef.typ <> orddef) and
+ not assigned(alllocdef) then
+ begin
+ paracgsize := int_cgsize(paralen);
+ locdef:=get_paraloc_def(paradef, paralen, firstparaloc);
+ end;
+
+ if (paracgsize in [OS_NO, OS_128, OS_S128]) then
+ begin
+ if (paralen>4) then
+ begin
+ paraloc^.size := OS_INT;
+ paraloc^.def := osuinttype;
+ end
+ else
+ begin
+ { for 3-byte records aligned in the lower bits of register }
+ paraloc^.size := OS_32;
+ paraloc^.def := u32inttype;
+ end;
+ end
+ else
+ begin
+ paraloc^.size := paracgsize;
+ paraloc^.def := locdef;
+ end;
+
+ paraloc^.register := newreg(R_INTREGISTER, nextintreg, R_SUBNONE);
+ inc(nextintreg);
+ dec(paralen, tcgsize2size[paraloc^.size]);
+ end else if (loc = LOC_FPUREGISTER) and
+ (nextfloatreg <= RS_F17) then begin
+ paraloc^.loc := loc;
+ paraloc^.size := paracgsize;
+ paraloc^.def := locdef;
+ paraloc^.register := newreg(R_FPUREGISTER, nextfloatreg, R_SUBWHOLE);
+ { the RiscV ABI says that the GPR index is increased for every parameter, no matter
+ which type it is stored in
+
+ not really, https://github.com/riscv/riscv-elf-psabi-doc/blob/master/riscv-elf.md#hardware-floating-point-calling-convention says
+ otherwise, gcc doesn't do it either }
+ inc(nextfloatreg);
+ dec(paralen, tcgsize2size[paraloc^.size]);
+ end else if (loc = LOC_MMREGISTER) then begin
+ { no mm registers }
+ internalerror(2018072601);
+ end else begin
+ { either LOC_REFERENCE, or one of the above which must be passed on the
+ stack because of insufficient registers }
+ paraloc^.loc := LOC_REFERENCE;
+ case loc of
+ LOC_FPUREGISTER:
+ begin
+ paraloc^.size:=int_float_cgsize(paralen);
+ case paraloc^.size of
+ OS_F32: paraloc^.def:=s32floattype;
+ OS_F64: paraloc^.def:=s64floattype;
+ else
+ internalerror(2013060122);
+ end;
+ end;
+ LOC_REGISTER,
+ LOC_REFERENCE:
+ begin
+ paraloc^.size:=int_cgsize(paralen);
+ paraloc^.def:=get_paraloc_def(paradef, paralen, firstparaloc);
+ end;
+ else
+ internalerror(2006011101);
+ end;
+ if (side = callerside) then
+ paraloc^.reference.index := NR_STACK_POINTER_REG
+ else begin
+ { during procedure entry, NR_OLD_STACK_POINTER_REG contains the old stack pointer }
+ paraloc^.reference.index := NR_FRAME_POINTER_REG;
+ { create_paraloc_info_intern might be also called when being outside of
+ code generation so current_procinfo might be not set }
+ if assigned(current_procinfo) then
+ trv64procinfo(current_procinfo).needs_frame_pointer := true;
+ end;
+ paraloc^.reference.offset := stack_offset;
+
+ { align temp contents to next register size }
+ if not paraaligned then
+ inc(stack_offset, align(paralen, 8))
+ else
+ inc(stack_offset, paralen);
+ paralen := 0;
+ end;
+ firstparaloc:=false;
+ end;
+ end;
+
+function tcpuparamanager.create_varargs_paraloc_info(p: tabstractprocdef;
+ varargspara: tvarargsparalist): longint;
+var
+ cur_stack_offset: aword;
+ parasize, l: longint;
+ curintreg, firstfloatreg, curfloatreg, curmmreg: tsuperregister;
+ i: integer;
+ hp: tparavarsym;
+ paraloc: pcgparalocation;
+begin
+ init_values(curintreg, curfloatreg, curmmreg, cur_stack_offset);
+ firstfloatreg := curfloatreg;
+
+ result := create_paraloc_info_intern(p, callerside, p.paras, curintreg,
+ curfloatreg, curmmreg, cur_stack_offset, false);
+ if (p.proccalloption in [pocall_cdecl, pocall_cppdecl, pocall_mwpascal]) then begin
+ { just continue loading the parameters in the registers }
+ result := create_paraloc_info_intern(p, callerside, varargspara, curintreg,
+ curfloatreg, curmmreg, cur_stack_offset, true);
+ { varargs routines have to reserve at least 64 bytes for the RiscV ABI }
+ if (result < 64) then
+ result := 64;
+ end else begin
+ parasize := cur_stack_offset;
+ for i := 0 to varargspara.count - 1 do begin
+ hp := tparavarsym(varargspara[i]);
+ hp.paraloc[callerside].alignment := 8;
+ paraloc := hp.paraloc[callerside].add_location;
+ paraloc^.loc := LOC_REFERENCE;
+ paraloc^.size := def_cgsize(hp.vardef);
+ paraloc^.def := hp.vardef;
+ paraloc^.reference.index := NR_STACK_POINTER_REG;
+ l := push_size(hp.varspez, hp.vardef, p.proccalloption);
+ paraloc^.reference.offset := parasize;
+ parasize := parasize + l;
+ end;
+ result := parasize;
+ end;
+ if curfloatreg <> firstfloatreg then
+ include(varargspara.varargsinfo, va_uses_float_reg);
+end;
+
+function tcpuparamanager.parseparaloc(p: tparavarsym; const s: string): boolean;
+begin
+ internalerror(200404182);
+ result := true;
+end;
+
+
+begin
+ paramanager := tcpuparamanager.create;
+end.
+
diff --git a/compiler/riscv64/cpupi.pas b/compiler/riscv64/cpupi.pas
new file mode 100644
index 0000000000..a0b3c129fb
--- /dev/null
+++ b/compiler/riscv64/cpupi.pas
@@ -0,0 +1,116 @@
+{
+ 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,aasmdata,
+ globtype, cgutils, cgbase,
+ procinfo, cpuinfo, psub;
+
+ type
+ trv64procinfo = class(tcgprocinfo)
+ stackframesize,
+ floatregstart : aint;
+ stackpaddingreg: TSuperRegister;
+
+ needs_frame_pointer: boolean;
+
+ constructor create(aparent: tprocinfo); override;
+ procedure set_first_temp_offset; override;
+ function calc_stackframe_size: longint; override;
+ end;
+
+implementation
+
+ uses
+ globals, systems,
+ cpubase,
+ aasmtai,
+ tgobj,cgobj,
+ symconst, symsym, paramgr, symutil, symtable,
+ verbose,
+ aasmcpu;
+
+
+ constructor trv64procinfo.create(aparent: tprocinfo);
+ begin
+ inherited create(aparent);
+ maxpushedparasize := 0;
+ end;
+
+
+ procedure trv64procinfo.set_first_temp_offset;
+ begin
+ if (po_nostackframe in procdef.procoptions) then
+ begin
+ { maxpushedparasize sghould be zero,
+ if not we will get an error later. }
+ tg.setfirsttemp(maxpushedparasize);
+ exit;
+ end;
+
+ if tg.direction = -1 then
+ tg.setfirsttemp(-(1+12)*8)
+ else
+ tg.setfirsttemp(maxpushedparasize);
+ end;
+
+
+ function trv64procinfo.calc_stackframe_size: longint;
+ var
+ firstfloatreg,lastfloatreg,
+ r : byte;
+ floatsavesize : aword;
+ regs: tcpuregisterset;
+ begin
+ maxpushedparasize:=align(maxpushedparasize,max(current_settings.alignment.localalignmin,8));
+ floatsavesize:=0;
+ case current_settings.fputype of
+ fpu_fd:
+ begin
+ floatsavesize:=0;
+ regs:=cg.rg[R_FPUREGISTER].used_in_proc-paramanager.get_volatile_registers_fpu(pocall_stdcall);
+ for r:=RS_F0 to RS_F31 do
+ if r in regs then
+ inc(floatsavesize,8);
+ end;
+ end;
+ floatsavesize:=system.align(floatsavesize,max(current_settings.alignment.localalignmin,8));
+ result:=Align(tg.direction*tg.lasttemp,max(current_settings.alignment.localalignmin,8))+maxpushedparasize+aint(floatsavesize);
+
+ if tg.direction=1 then
+ floatregstart:=result-aint(floatsavesize)
+ else
+ floatregstart:=-result+maxpushedparasize;
+ end;
+
+
+begin
+ cprocinfo := trv64procinfo;
+end.
+
diff --git a/compiler/riscv64/cputarg.pas b/compiler/riscv64/cputarg.pas
new file mode 100644
index 0000000000..6986b1f2b6
--- /dev/null
+++ b/compiler/riscv64/cputarg.pas
@@ -0,0 +1,85 @@
+{
+ Copyright (c) 2001-2002 by Peter Vreman
+
+ Includes the RiscV64 dependent target units
+
+ 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 cputarg;
+
+{$i fpcdefs.inc}
+
+interface
+
+
+implementation
+
+ uses
+ systems { prevent a syntax error when nothing is included }
+
+{**************************************
+ Targets
+**************************************}
+
+ {$ifndef NOTARGETLINUX}
+ ,t_linux
+ {$endif}
+ {$ifndef NOTARGETEMBEDDED}
+ ,t_embed
+ {$endif}
+
+{**************************************
+ Assemblers
+**************************************}
+
+ {$ifndef NOAGRVGAS}
+ ,agrvgas
+ {$endif}
+
+{**************************************
+ Assembler Readers
+**************************************}
+
+ {$ifndef NoRaRVGas}
+ ,rarv64gas
+ {$endif NoRaRVGas}
+
+{**************************************
+ Debuginfo
+**************************************}
+
+ {$ifndef NoDbgStabs}
+ ,dbgstabs
+ {$endif NoDbgStabs}
+ {$ifndef NoDbgStabx}
+ ,dbgstabx
+ {$endif NoDbgStabx}
+ {$ifndef NoDbgDwarf}
+ ,dbgdwarf
+ {$endif NoDbgDwarf}
+
+
+{**************************************
+ Optimizer
+**************************************}
+
+ {$ifndef NOOPT}
+ , aoptcpu
+ {$endif NOOPT}
+ ;
+
+end.
diff --git a/compiler/riscv64/hlcgcpu.pas b/compiler/riscv64/hlcgcpu.pas
new file mode 100644
index 0000000000..3c0f4968f7
--- /dev/null
+++ b/compiler/riscv64/hlcgcpu.pas
@@ -0,0 +1,78 @@
+{
+ Copyright (c) 1998-2010 by Florian Klaempfl and Jonas Maebe
+ Member of the Free Pascal development team
+
+ This unit contains high-level code generator support for riscv64
+
+ 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 hlcgcpu;
+
+{$i fpcdefs.inc}
+
+interface
+
+uses
+ globtype,
+ aasmdata,
+ symtype,
+ cgbase,cgutils,hlcgobj,hlcgrv;
+
+type
+ thlcgcpu = class(thlcgriscv)
+ procedure a_load_const_subsetreg(list: TAsmlist; tosubsetsize: tdef; a: tcgint; const sreg: tsubsetregister); override;
+ end;
+
+ procedure create_hlcodegen;
+
+implementation
+
+ uses
+ cpubase,aasmcpu,
+ defutil,
+ cgobj,cgcpu;
+
+ { thlcgcpu }
+
+
+ procedure thlcgcpu.a_load_const_subsetreg(list: TAsmlist; tosubsetsize: tdef; a: tcgint; const sreg: tsubsetregister);
+ var
+ tmpreg : TRegister;
+ begin
+{$ifdef extdebug}
+ list.concat(tai_comment.create(strpnew('a_load_const_subsetreg subsetregsize = ' + cgsize2string(sreg.subsetregsize) + ' subsetsize = ' + cgsize2string(def_cgsize(subsetsize)) + ' startbit = ' + intToStr(sreg.startbit) + ' a = ' + intToStr(a))));
+{$endif}
+ { loading the constant into the lowest bits of a temp register and then inserting is
+ better than loading some usually large constants and do some masking and shifting on riscv64 }
+ tmpreg:=getintregister(list,tosubsetsize);
+ a_load_const_reg(list,tosubsetsize,a,tmpreg);
+ a_load_reg_subsetreg(list,tosubsetsize,tosubsetsize,tmpreg,sreg);
+ end;
+
+
+ procedure create_hlcodegen;
+ begin
+ hlcg:=thlcgcpu.create;
+ create_codegen;
+ end;
+
+
+
+begin
+ chlcgobj:=thlcgcpu;
+end.
diff --git a/compiler/riscv64/itcpugas.pas b/compiler/riscv64/itcpugas.pas
new file mode 100644
index 0000000000..4fabace6e8
--- /dev/null
+++ b/compiler/riscv64/itcpugas.pas
@@ -0,0 +1,157 @@
+{
+ Copyright (c) 1998-2002 by Florian Klaempfl
+
+ This unit contains the RiscV64 GAS instruction tables
+
+ 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 itcpugas;
+
+{$I fpcdefs.inc}
+
+ interface
+
+ uses
+ cpubase, cgbase;
+
+ const
+ gas_op2str: array[tasmop] of string[14] = ('<none>',
+ 'nop',
+ 'lui','auipc','jal','jalr',
+ 'b','lb','lh','lw','lbu','lhu',
+ 'sb','sh','sw',
+ 'addi','slti','sltiu',
+ 'xori','ori','andi',
+ 'slli','srli','srai',
+ 'add','sub','sll','slt','sltu',
+ 'xor','srl','sra','or','and',
+ 'fence','fence.i',
+ 'ecall','ebreak',
+ 'csrrw','csrrs','csrrc','csrrwi','csrrsi','csrrci',
+ { 64-bit }
+ 'addiw','slliw','srliw','sraiw',
+ 'addw','sllw','srlw','subw','sraw',
+ 'ld','sd','lwu',
+
+ { m-extension }
+ 'mul','mulh','mulhsu','mulhu',
+ 'div','divu','rem','remu',
+ { 64-bit }
+ 'mulw',
+ 'divw','divuw','remw','remuw',
+
+ { a-extension }
+ 'lr.w','sc.w','amoswap.w','amoadd.w','amoxor.w','amoand.w',
+ 'amoor.w','amomin.w','amomax.w','amominu.w','amomaxu.w',
+ { 64-bit }
+ 'lr.d','sc.d','amoswap.d','amoadd.d','amoxor.d','amoand.d',
+ 'amoor.d','amomin.d','amomax.d','amominu.d','amomaxu.d',
+
+ { f-extension }
+ 'flw','fsw',
+ 'fmadd.s','fmsub.s','fnmsub.s','fnmadd.s',
+ 'fadd.s','fsub.s','fmul.s','fdiv.s',
+ 'fsqrt.s','fsgnj.s','fsgnjn.s','fsgnjx.s',
+ 'fmin.s','fmax.s',
+ 'fmv.x.s','feq.s','flt.s','fle.s','fclass.s',
+ 'fcvt.w.s','fcvt.wu.s','fcvt.s.w','fcvt.s.wu',
+ 'fmv.s.x',
+ 'frcsr','frrm','frflags','fscsr','fsrm',
+ 'fsflags','fsrmi','fsflagsi',
+ { 64-bit }
+ 'fcvt.l.s','fcvt.lu.s',
+ 'fcvt.s.l','fcvt.s.lu',
+
+ { d-extension }
+ 'fld','fsd',
+ 'fmadd.d','fmsub.d','fnmsub.d','fnmadd.d',
+ 'fadd.d','fsub.d','fmul.d','fdiv.d',
+ 'fsqrt.d','fsgnj.d','fsgnjn.d','fsgnjx.d',
+ 'fmin.d','fmax.d',
+ 'feq.d','flt.d','fle.d','fclass.d',
+ 'fcvt.d.s','fcvt.s.d',
+ 'fcvt.w.d','fcvt.wu.d','fcvt.d.w','fcvt.d.wu',
+ { 64-bit }
+ 'fcvt.l.d','fcvt.lu.d','fmv.x.d',
+ 'fcvt.d.l','fcvt.d.lu','fmv.d.x',
+
+ { Machine mode }
+ 'mret','hret','sret','uret',
+ 'wfi',
+
+ { Supervisor mode }
+ 'sfence.vm'
+ );
+
+ function gas_regnum_search(const s: string): Tregister;
+ function gas_regname(r: Tregister): string;
+
+ implementation
+
+ uses
+ globtype,globals,aasmbase,
+ cutils,verbose, systems,
+ rgbase;
+
+ const
+ gas_regname_table : TRegNameTable = (
+ {$i rrv32std.inc}
+ );
+
+ gas_regname_index : array[tregisterindex] of tregisterindex = (
+ {$i rrv32sri.inc}
+ );
+
+
+ function findreg_by_gasname(const s:string):tregisterindex;
+ var
+ i,p : tregisterindex;
+ begin
+ {Binary search.}
+ p:=0;
+ i:=regnumber_count_bsstart;
+ repeat
+ if (p+i<=high(tregisterindex)) and (gas_regname_table[gas_regname_index[p+i]]<=s) then
+ p:=p+i;
+ i:=i shr 1;
+ until i=0;
+ if gas_regname_table[gas_regname_index[p]]=s then
+ findreg_by_gasname:=gas_regname_index[p]
+ else
+ findreg_by_gasname:=0;
+ end;
+
+
+ function gas_regnum_search(const s:string):Tregister;
+ begin
+ result:=regnumber_table[findreg_by_gasname(s)];
+ end;
+
+
+ function gas_regname(r:Tregister):string;
+ var
+ p : tregisterindex;
+ begin
+ p:=findreg_by_number(r);
+ if p<>0 then
+ result:=gas_regname_table[p]
+ else
+ result:=generic_regname(r);
+ end;
+
+end.
+
diff --git a/compiler/riscv64/nrv64add.pas b/compiler/riscv64/nrv64add.pas
new file mode 100644
index 0000000000..37356772ff
--- /dev/null
+++ b/compiler/riscv64/nrv64add.pas
@@ -0,0 +1,98 @@
+{
+ Copyright (c) 2000-2002 by Florian Klaempfl and Jonas Maebe
+
+ Code generation for add nodes on the Risc-V64
+
+ 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 nrv64add;
+
+{$I fpcdefs.inc}
+
+ interface
+
+ uses
+ node, ncgadd, aasmbase, nrvadd, cpubase;
+
+ type
+ trv64addnode = class(trvaddnode)
+ protected
+ function pass_1: tnode; override;
+
+ procedure second_add64bit; override;
+
+ function use_generic_mul32to64: boolean; override;
+ end;
+
+ implementation
+
+ uses
+ systems,
+ cutils,verbose,
+ paramgr,procinfo,
+ aasmtai,aasmdata,aasmcpu,defutil,
+ cgbase,cgcpu,cgutils,
+ globals,
+ pass_1,
+ CPUInfo,cpupara,
+ ncon,nset,nadd,
+ symconst,
+ hlcgobj, ncgutil,cgobj;
+
+ function trv64addnode.pass_1: tnode;
+ begin
+ if (nodetype=muln) and
+ (left.resultdef.typ=orddef) and (left.resultdef.typ=orddef) and
+ (CPURV_HAS_MUL in cpu_capabilities[current_settings.cputype]) then
+ begin
+ result:=nil;
+
+ firstpass(left);
+ firstpass(right);
+
+ expectloc:=LOC_REGISTER;
+ end
+ else if (nodetype=muln) and
+ (not (CPURV_HAS_MUL in cpu_capabilities[current_settings.cputype])) and
+ (is_64bit(left.resultdef) or
+ is_64bit(right.resultdef)) then
+ begin
+ result:=first_add64bitint;
+ end
+ else
+ Result:=inherited pass_1;
+
+ if expectloc=LOC_FLAGS then
+ expectloc:=LOC_REGISTER;
+ end;
+
+
+ procedure trv64addnode.second_add64bit;
+ begin
+ second_addordinal;
+ end;
+
+
+ function trv64addnode.use_generic_mul32to64: boolean;
+ begin
+ result:=false;
+ end;
+
+begin
+ caddnode := trv64addnode;
+end.
+
diff --git a/compiler/riscv64/nrv64cal.pas b/compiler/riscv64/nrv64cal.pas
new file mode 100644
index 0000000000..7781434673
--- /dev/null
+++ b/compiler/riscv64/nrv64cal.pas
@@ -0,0 +1,56 @@
+{
+ Copyright (c) 2002 by Florian Klaempfl
+
+ Implements the RiscV64 specific part of call nodes
+
+ 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 nrv64cal;
+
+{$I fpcdefs.inc}
+
+interface
+
+uses
+ aasmdata, cgbase,
+ symdef, node, ncal, ncgcal;
+
+type
+
+ trv64callparanode = class(tcgcallparanode)
+ end;
+
+ trv64ccallnode = class(tcgcallnode)
+ end;
+
+implementation
+
+uses
+ globtype, systems,
+ cutils, verbose, globals,
+ symconst, symbase, symsym, symtable, defutil, paramgr, parabase,
+ pass_2,
+ cpuinfo, cpubase, aasmbase, aasmtai, aasmcpu,
+ nmem, nld, ncnv,
+ ncgutil, cgutils, cgobj, tgobj, rgobj, rgcpu,
+ cgcpu, cpupi, procinfo;
+
+begin
+ ccallparanode:=trv64callparanode;
+ ccallnode := trv64ccallnode;
+end.
+
diff --git a/compiler/riscv64/nrv64cnv.pas b/compiler/riscv64/nrv64cnv.pas
new file mode 100644
index 0000000000..65c3714b36
--- /dev/null
+++ b/compiler/riscv64/nrv64cnv.pas
@@ -0,0 +1,124 @@
+{
+ Copyright (c) 1998-2002 by Florian Klaempfl
+
+ Generate RiscV64 assembler for type converting nodes
+
+ 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 nrv64cnv;
+
+{$I fpcdefs.inc}
+
+ interface
+
+ uses
+ node, ncnv, ncgcnv, nrvcnv;
+
+ type
+ trv64typeconvnode = class(trvtypeconvnode)
+ protected
+ { procedure second_int_to_int;override; }
+ { procedure second_string_to_string;override; }
+ { procedure second_cstring_to_pchar;override; }
+ { procedure second_string_to_chararray;override; }
+ { procedure second_array_to_pointer;override; }
+ function first_int_to_real: tnode; override;
+ { procedure second_pointer_to_array;override; }
+ { procedure second_chararray_to_string;override; }
+ { procedure second_char_to_string;override; }
+ procedure second_int_to_real; override;
+ { procedure second_real_to_real; override;}
+ { procedure second_cord_to_pointer;override; }
+ { procedure second_proc_to_procvar;override; }
+ { procedure second_bool_to_int;override; }
+ { procedure second_int_to_bool; override; }
+ { procedure second_load_smallset;override; }
+ { procedure second_ansistring_to_pchar;override; }
+ { procedure second_pchar_to_string;override; }
+ { procedure second_class_to_intf;override; }
+ { procedure second_char_to_char;override; }
+ end;
+
+ implementation
+
+ uses
+ verbose, globtype, globals, systems,
+ symconst, symdef, aasmbase, aasmtai,aasmdata,
+ defutil, symcpu,
+ cgbase, cgutils, pass_1, pass_2,
+ ncon, ncal,procinfo,
+ ncgutil,
+ cpubase, aasmcpu,
+ rgobj, tgobj, cgobj, hlcgobj;
+
+ {*****************************************************************************
+ FirstTypeConv
+ *****************************************************************************}
+
+ function trv64typeconvnode.first_int_to_real: tnode;
+ begin
+ if (cs_fp_emulation in current_settings.moduleswitches) then
+ result:=inherited first_int_to_real
+ { converting a 64bit integer to a float requires a helper }
+ else
+ begin
+ if (is_currency(left.resultdef)) then begin
+ // hack to avoid double division by 10000, as it's
+ // already done by typecheckpass.resultdef_int_to_real
+ left.resultdef := s64inttype;
+ end else begin
+ // everything that is less than 64 bits is converted to a 64 bit signed
+ // integer - because the int_to_real conversion is faster for 64 bit
+ // signed ints compared to 64 bit unsigned ints.
+ if (not (torddef(left.resultdef).ordtype in [s64bit, u64bit, scurrency])) then begin
+ inserttypeconv(left, s64inttype);
+ end;
+ end;
+ firstpass(left);
+ result := nil;
+ expectloc := LOC_FPUREGISTER;
+ end;
+ end;
+
+ {*****************************************************************************
+ SecondTypeConv
+ *****************************************************************************}
+
+ procedure trv64typeconvnode.second_int_to_real;
+ const
+ ops: array[boolean,boolean,s32real..s64real] of TAsmOp = (
+ ((A_FCVT_S_WU,A_FCVT_D_WU),
+ (A_FCVT_S_W,A_FCVT_D_W)),
+ ((A_FCVT_S_LU,A_FCVT_D_LU),
+ (A_FCVT_S_L,A_FCVT_D_L)));
+ var
+ restype: tfloattype;
+ begin
+ location_reset(location, LOC_FPUREGISTER, def_cgsize(resultdef));
+
+ restype:=tfloatdef(resultdef).floattype;
+
+ location.Register := cg.getfpuregister(current_asmdata.CurrAsmList, tfloat2tcgsize[restype]);
+ if not(left.location.loc in [LOC_REGISTER,LOC_CREGISTER]) then
+ hlcg.location_force_reg(current_asmdata.CurrAsmList, left.location, left.resultdef, left.resultdef, true);
+ current_asmdata.CurrAsmList.concat(taicpu.op_reg_reg(ops[is_64bit(left.resultdef),is_signed(left.resultdef),restype], location.register, left.location.register));
+ end;
+
+begin
+ ctypeconvnode := trv64typeconvnode;
+end.
+
diff --git a/compiler/riscv64/nrv64ld.pas b/compiler/riscv64/nrv64ld.pas
new file mode 100644
index 0000000000..c2a6963a5b
--- /dev/null
+++ b/compiler/riscv64/nrv64ld.pas
@@ -0,0 +1,57 @@
+{
+ Copyright (c) 1998-2002 by Florian Klaempfl
+
+ Generate riscv64 assembler for nodes that handle loads and assignments
+
+ 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 nrv64ld;
+
+{$I fpcdefs.inc}
+
+interface
+
+uses
+ node, ncgld;
+
+type
+ trv64loadnode = class(tcgloadnode)
+ procedure pass_generate_code override;
+ end;
+
+implementation
+
+uses
+ verbose,
+ systems,
+ cpubase,
+ cgutils, cgobj,
+ aasmbase, aasmtai,aasmdata,
+ symconst, symsym,
+ procinfo,
+ nld;
+
+procedure trv64loadnode.pass_generate_code;
+begin
+ inherited pass_generate_code;
+end;
+
+
+begin
+ cloadnode := trv64loadnode;
+end.
+
diff --git a/compiler/riscv64/nrv64mat.pas b/compiler/riscv64/nrv64mat.pas
new file mode 100644
index 0000000000..abcdfdb124
--- /dev/null
+++ b/compiler/riscv64/nrv64mat.pas
@@ -0,0 +1,163 @@
+{
+ Copyright (c) 1998-2002 by Florian Klaempfl
+
+ Generate RiscV64 assembler for math nodes
+
+ 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 nrv64mat;
+
+{$I fpcdefs.inc}
+
+ interface
+
+ uses
+ node,nmat, ncgmat,
+ cgbase;
+
+ type
+ trv64moddivnode = class(tcgmoddivnode)
+ function use_moddiv64bitint_helper: boolean; override;
+ procedure emit_div_reg_reg(signed: boolean; denum, num: tregister); override;
+ procedure emit_mod_reg_reg(signed: boolean; denum, num: tregister); override;
+ function first_moddiv64bitint: tnode; override;
+ end;
+
+ trv64shlshrnode = class(tcgshlshrnode)
+ end;
+
+ trv64unaryminusnode = class(tcgunaryminusnode)
+ end;
+
+ trv64notnode = class(tcgnotnode)
+ procedure second_boolean; override;
+ end;
+
+implementation
+
+ uses
+ nadd,ninl,ncal,ncnv,
+ globtype,systems,constexp,
+ cutils,verbose,globals,
+ cpuinfo,
+ symconst,symdef,
+ aasmbase,aasmcpu,aasmtai,aasmdata,
+ defutil,
+ cgutils,cgobj,hlcgobj,
+ pass_1,pass_2,htypechk,
+ ncon,procinfo,
+ cpubase,
+ ncgutil,cgcpu;
+
+ procedure trv64notnode.second_boolean;
+ var
+ tlabel, flabel: tasmlabel;
+ begin
+ if not handle_locjump then
+ begin
+ secondpass(left);
+ case left.location.loc of
+ LOC_FLAGS :
+ begin
+ Internalerror(2016060601);
+ //location_copy(location,left.location);
+ //inverse_flags(location.resflags);
+ end;
+ LOC_REGISTER, LOC_CREGISTER,
+ LOC_REFERENCE, LOC_CREFERENCE,
+ LOC_SUBSETREG, LOC_CSUBSETREG,
+ LOC_SUBSETREF, LOC_CSUBSETREF:
+ begin
+ hlcg.location_force_reg(current_asmdata.CurrAsmList,left.location,left.resultdef,left.resultdef,false);
+
+ location_reset(location,LOC_REGISTER,OS_INT);
+ location.register:=hlcg.getintregister(current_asmdata.CurrAsmList,s64inttype);
+
+ current_asmdata.CurrAsmList.Concat(taicpu.op_reg_reg_const(A_SLTIU,location.register,left.location.register,1));
+ end;
+ else
+ internalerror(2003042401);
+ end;
+ end;
+ end;
+
+
+ function trv64moddivnode.use_moddiv64bitint_helper: boolean;
+ begin
+ Result:=true;
+ end;
+
+
+ procedure trv64moddivnode.emit_div_reg_reg(signed: boolean; denum, num: tregister);
+ var
+ op: TAsmOp;
+ begin
+ if signed then
+ op:=A_DIV
+ else
+ op:=A_DIVU;
+
+ current_asmdata.CurrAsmList.Concat(taicpu.op_reg_reg_reg(op,num,num,denum));
+ end;
+
+
+ procedure trv64moddivnode.emit_mod_reg_reg(signed: boolean; denum, num: tregister);
+ var
+ op: TAsmOp;
+ begin
+ if signed then
+ op:=A_REM
+ else
+ op:=A_REMU;
+
+ current_asmdata.CurrAsmList.Concat(taicpu.op_reg_reg_reg(op,num,num,denum));
+ end;
+
+
+ function trv64moddivnode.first_moddiv64bitint: tnode;
+ var
+ power: longint;
+ begin
+ {We can handle all cases of constant division}
+ if not(cs_check_overflow in current_settings.localswitches) and
+ (right.nodetype=ordconstn) and
+ (nodetype=divn) and
+ ((CPURV_HAS_MUL in cpu_capabilities[current_settings.cputype]) and
+ (ispowerof2(tordconstnode(right).value,power) or
+ (tordconstnode(right).value=1) or
+ (tordconstnode(right).value=int64(-1))
+ )
+ ) then
+ result:=nil
+ else if (CPURV_HAS_MUL in cpu_capabilities[current_settings.cputype]) and
+ (nodetype in [divn,modn]) then
+ result:=nil
+ else
+ result:=inherited;
+
+ { we may not change the result type here }
+ if assigned(result) and (torddef(result.resultdef).ordtype<>torddef(resultdef).ordtype) then
+ inserttypeconv(result,resultdef);
+ end;
+
+begin
+ cmoddivnode := trv64moddivnode;
+ cshlshrnode := trv64shlshrnode;
+ cunaryminusnode := trv64unaryminusnode;
+ cnotnode := trv64notnode;
+end.
+
diff --git a/compiler/riscv64/rarv.pas b/compiler/riscv64/rarv.pas
new file mode 100644
index 0000000000..b02c55abab
--- /dev/null
+++ b/compiler/riscv64/rarv.pas
@@ -0,0 +1,50 @@
+{
+ Copyright (c) 1998-2003 by Carl Eric Codere and Peter Vreman
+
+ Handles the common riscv assembler reader routines
+
+ 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 rarv;
+
+{$I fpcdefs.inc}
+
+interface
+
+uses
+ aasmbase, aasmtai,aasmdata, aasmcpu,
+ cpubase, rautils, cclasses;
+
+type
+ TRVOperand = class(TOperand)
+ end;
+
+ TRVInstruction = class(TInstruction)
+ ordering: TMemoryOrdering;
+ function ConcatInstruction(p: TAsmList): tai; override;
+ end;
+
+implementation
+
+ function TRVInstruction.ConcatInstruction(p: TAsmList): tai;
+ begin
+ Result:=inherited ConcatInstruction(p);
+ (result as taicpu).memoryordering:=ordering;
+ end;
+
+end.
+
diff --git a/compiler/riscv64/rarv64gas.pas b/compiler/riscv64/rarv64gas.pas
new file mode 100644
index 0000000000..2c727846d8
--- /dev/null
+++ b/compiler/riscv64/rarv64gas.pas
@@ -0,0 +1,840 @@
+{
+ Copyright (c) 2016 by Jeppe Johansen
+
+ Does the parsing for the RiscV64 GNU AS styled inline assembler.
+
+ 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 rarv64gas;
+
+{$I fpcdefs.inc}
+
+ interface
+
+ uses
+ raatt, rarv,
+ cpubase;
+
+ type
+ trv64attreader = class(tattreader)
+ actmemoryordering: TMemoryOrdering;
+ function is_register(const s: string): boolean; override;
+ function is_asmopcode(const s: string):boolean;override;
+ procedure handleopcode;override;
+ procedure BuildReference(oper : trvoperand);
+ procedure BuildOperand(oper : trvoperand);
+ procedure BuildOpCode(instr : trvinstruction);
+ procedure ReadAt(oper : trvoperand);
+ procedure ReadSym(oper : trvoperand);
+ end;
+
+ implementation
+
+ uses
+ { helpers }
+ cutils,
+ { global }
+ globtype,globals,verbose,
+ systems,
+ { aasm }
+ aasmbase,aasmtai,aasmdata,aasmcpu,
+ { symtable }
+ symconst,symsym,symdef,
+ { parser }
+ procinfo,
+ rabase,rautils,
+ cgbase,cgobj,cgrv
+ ;
+
+ procedure trv64attreader.ReadSym(oper : trvoperand);
+ var
+ tempstr, mangledname : string;
+ typesize,l,k : aint;
+ begin
+ tempstr:=actasmpattern;
+ Consume(AS_ID);
+ { typecasting? }
+ if (actasmtoken=AS_LPAREN) and
+ SearchType(tempstr,typesize) then
+ begin
+ oper.hastype:=true;
+ Consume(AS_LPAREN);
+ BuildOperand(oper);
+ Consume(AS_RPAREN);
+ if oper.opr.typ in [OPR_REFERENCE,OPR_LOCAL] then
+ oper.SetSize(typesize,true);
+ end
+ else
+ if not oper.SetupVar(tempstr,false) then
+ Message1(sym_e_unknown_id,tempstr);
+ { record.field ? }
+ if actasmtoken=AS_DOT then
+ begin
+ BuildRecordOffsetSize(tempstr,l,k,mangledname,false);
+ if (mangledname<>'') then
+ Message(asmr_e_invalid_reference_syntax);
+ inc(oper.opr.ref.offset,l);
+ end;
+ end;
+
+
+ procedure trv64attreader.ReadAt(oper : trvoperand);
+ begin
+ { check for ...@ }
+ if actasmtoken=AS_AT then
+ begin
+ if (oper.opr.ref.symbol=nil) and
+ (oper.opr.ref.offset = 0) then
+ Message(asmr_e_invalid_reference_syntax);
+ Consume(AS_AT);
+ if actasmtoken=AS_ID then
+ begin
+ {if upper(actasmpattern)='L' then
+ oper.opr.ref.refaddr:=addr_low
+ else if upper(actasmpattern)='HI' then
+ oper.opr.ref.refaddr:=addr_high
+ else if upper(actasmpattern)='HA' then
+ oper.opr.ref.refaddr:=addr_higha
+ else}
+ Message(asmr_e_invalid_reference_syntax);
+ Consume(AS_ID);
+ end
+ else
+ Message(asmr_e_invalid_reference_syntax);
+ end;
+ end;
+
+
+ procedure trv64attreader.BuildReference(oper: trvoperand);
+
+ procedure Consume_RParen;
+ begin
+ if actasmtoken <> AS_RPAREN then
+ Begin
+ Message(asmr_e_invalid_reference_syntax);
+ RecoverConsume(true);
+ end
+ else
+ begin
+ Consume(AS_RPAREN);
+ if not (actasmtoken in [AS_COMMA,AS_SEPARATOR,AS_END]) then
+ Begin
+ Message(asmr_e_invalid_reference_syntax);
+ RecoverConsume(true);
+ end;
+ end;
+ end;
+
+ var
+ l : aint;
+ relsym: string;
+ asmsymtyp: tasmsymtype;
+ isflags: tindsymflags;
+
+ begin
+ Consume(AS_LPAREN);
+ Case actasmtoken of
+ AS_INTNUM,
+ AS_MINUS,
+ AS_PLUS:
+ Begin
+ { offset(offset) is invalid }
+ If oper.opr.Ref.Offset <> 0 Then
+ Begin
+ Message(asmr_e_invalid_reference_syntax);
+ RecoverConsume(true);
+ End
+ Else
+ Begin
+ oper.opr.Ref.Offset:=BuildConstExpression(false,true);
+ Consume(AS_RPAREN);
+ if actasmtoken=AS_AT then
+ ReadAt(oper);
+ end;
+ exit;
+ End;
+ AS_REGISTER: { (reg ... }
+ Begin
+ if ((oper.opr.typ=OPR_REFERENCE) and (oper.opr.ref.base<>NR_NO)) or
+ ((oper.opr.typ=OPR_LOCAL) and (oper.opr.localsym.localloc.loc<>LOC_REGISTER)) then
+ message(asmr_e_cannot_index_relative_var);
+ oper.opr.ref.base:=actasmregister;
+ Consume(AS_REGISTER);
+ Consume_RParen;
+ end; {end case }
+ AS_ID:
+ Begin
+ ReadSym(oper);
+ case actasmtoken of
+ AS_PLUS:
+ begin
+ { add a constant expression? }
+ l:=BuildConstExpression(true,true);
+ case oper.opr.typ of
+ OPR_CONSTANT :
+ inc(oper.opr.val,l);
+ OPR_LOCAL :
+ inc(oper.opr.localsymofs,l);
+ OPR_REFERENCE :
+ inc(oper.opr.ref.offset,l);
+ else
+ internalerror(200309202);
+ end;
+ end;
+ AS_MINUS:
+ begin
+ Consume(AS_MINUS);
+ BuildConstSymbolExpression(false,true,false,l,relsym,asmsymtyp);
+ if (relsym<>'') then
+ begin
+ if (oper.opr.typ = OPR_REFERENCE) then
+ oper.opr.ref.relsymbol:=current_asmdata.RefAsmSymbol(relsym,AT_DATA)
+ else
+ begin
+ Message(asmr_e_invalid_reference_syntax);
+ RecoverConsume(false);
+ end
+ end
+ else
+ begin
+ case oper.opr.typ of
+ OPR_CONSTANT :
+ dec(oper.opr.val,l);
+ OPR_LOCAL :
+ dec(oper.opr.localsymofs,l);
+ OPR_REFERENCE :
+ dec(oper.opr.ref.offset,l);
+ else
+ internalerror(2007092601);
+ end;
+ end;
+ end;
+ end;
+ Consume(AS_RPAREN);
+ if actasmtoken=AS_AT then
+ ReadAt(oper);
+ End;
+ AS_COMMA: { (, ... can either be scaling, or index }
+ Begin
+ Consume(AS_COMMA);
+ { Index }
+ if (actasmtoken=AS_REGISTER) then
+ Begin
+ oper.opr.ref.index:=actasmregister;
+ Consume(AS_REGISTER);
+ { check for scaling ... }
+ Consume_RParen;
+ end
+ else
+ begin
+ Message(asmr_e_invalid_reference_syntax);
+ RecoverConsume(false);
+ end;
+ end;
+ else
+ Begin
+ Message(asmr_e_invalid_reference_syntax);
+ RecoverConsume(false);
+ end;
+ end;
+ end;
+
+
+ procedure trv64attreader.BuildOperand(oper: trvoperand);
+ var
+ expr : string;
+ typesize,l : aint;
+
+
+ procedure AddLabelOperand(hl:tasmlabel);
+ begin
+ if not(actasmtoken in [AS_PLUS,AS_MINUS,AS_LPAREN]) and
+ is_calljmp(actopcode) then
+ begin
+ oper.opr.typ:=OPR_SYMBOL;
+ oper.opr.symbol:=hl;
+ end
+ else
+ begin
+ oper.InitRef;
+ oper.opr.ref.symbol:=hl;
+ end;
+ end;
+
+
+ procedure MaybeRecordOffset;
+ var
+ mangledname: string;
+ hasdot : boolean;
+ l,
+ toffset,
+ tsize : aint;
+ begin
+ if not(actasmtoken in [AS_DOT,AS_PLUS,AS_MINUS]) then
+ exit;
+ l:=0;
+ hasdot:=(actasmtoken=AS_DOT);
+ if hasdot then
+ begin
+ if expr<>'' then
+ begin
+ BuildRecordOffsetSize(expr,toffset,tsize,mangledname,false);
+ if (oper.opr.typ<>OPR_CONSTANT) and
+ (mangledname<>'') then
+ Message(asmr_e_wrong_sym_type);
+ inc(l,toffset);
+ oper.SetSize(tsize,true);
+ end;
+ end;
+ if actasmtoken in [AS_PLUS,AS_MINUS] then
+ inc(l,BuildConstExpression(true,false));
+ case oper.opr.typ of
+ OPR_LOCAL :
+ begin
+ { don't allow direct access to fields of parameters, because that
+ will generate buggy code. Allow it only for explicit typecasting }
+ if hasdot and
+ (not oper.hastype) and
+ (tabstractvarsym(oper.opr.localsym).owner.symtabletype=parasymtable) and
+ (current_procinfo.procdef.proccalloption<>pocall_register) then
+ Message(asmr_e_cannot_access_field_directly_for_parameters);
+ inc(oper.opr.localsymofs,l)
+ end;
+ OPR_CONSTANT :
+ if (mangledname<>'') then
+ begin
+ if (oper.opr.val<>0) then
+ Message(asmr_e_wrong_sym_type);
+ oper.opr.typ:=OPR_SYMBOL;
+ oper.opr.symbol:=current_asmdata.DefineAsmSymbol(mangledname,AB_EXTERNAL,AT_FUNCTION,voidcodepointertype);
+ end
+ else
+ inc(oper.opr.val,l);
+ OPR_REFERENCE :
+ inc(oper.opr.ref.offset,l);
+ OPR_SYMBOL:
+ Message(asmr_e_invalid_symbol_ref);
+ else
+ internalerror(200309221);
+ end;
+ end;
+
+
+ function MaybeBuildReference:boolean;
+ { Try to create a reference, if not a reference is found then false
+ is returned }
+ begin
+ MaybeBuildReference:=true;
+ case actasmtoken of
+ AS_INTNUM,
+ AS_MINUS,
+ AS_PLUS:
+ Begin
+ oper.opr.ref.offset:=BuildConstExpression(True,False);
+ if actasmtoken<>AS_LPAREN then
+ Message(asmr_e_invalid_reference_syntax)
+ else
+ BuildReference(oper);
+ end;
+ AS_LPAREN:
+ BuildReference(oper);
+ AS_ID: { only a variable is allowed ... }
+ Begin
+ ReadSym(oper);
+ case actasmtoken of
+ AS_END,
+ AS_SEPARATOR,
+ AS_COMMA: ;
+ AS_LPAREN:
+ BuildReference(oper);
+ else
+ Begin
+ Message(asmr_e_invalid_reference_syntax);
+ Consume(actasmtoken);
+ end;
+ end; {end case }
+ end;
+ else
+ MaybeBuildReference:=false;
+ end; { end case }
+ end;
+
+
+ function is_fenceflag(hs : string): boolean;
+ var
+ i: longint;
+ flags: TFenceFlags;
+ begin
+ is_fenceflag := false;
+
+ flags:=[];
+ hs:=lower(hs);
+
+ if (actopcode in [A_FENCE]) and (length(hs) >= 1) then
+ begin
+ for i:=1 to length(hs) do
+ begin
+ case hs[i] of
+ 'i':
+ Include(flags,ffi);
+ 'o':
+ Include(flags,ffo);
+ 'r':
+ Include(flags,ffr);
+ 'w':
+ Include(flags,ffw);
+ else
+ exit;
+ end;
+ end;
+ oper.opr.typ := OPR_FENCEFLAGS;
+ oper.opr.fenceflags := flags;
+ exit(true);
+ end;
+ end;
+
+
+ var
+ tempreg : tregister;
+ hl : tasmlabel;
+ ofs : aint;
+ refaddr: trefaddr;
+ Begin
+ expr:='';
+
+ refaddr:=addr_full;
+ if actasmtoken=AS_MOD then
+ begin
+ consume(AS_MOD);
+
+ if actasmtoken<>AS_ID then
+ begin
+ Message(asmr_e_invalid_reference_syntax);
+ RecoverConsume(false);
+ end
+ else
+ begin
+ if lower(actasmpattern)='pcrel_hi' then
+ refaddr:=addr_pcrel_hi20
+ else if lower(actasmpattern)='pcrel_lo' then
+ refaddr:=addr_pcrel_lo12
+ else if lower(actasmpattern)='hi' then
+ refaddr:=addr_hi20
+ else if lower(actasmpattern)='lo' then
+ refaddr:=addr_lo12
+ else
+ begin
+ Message(asmr_e_invalid_reference_syntax);
+ RecoverConsume(false);
+ end;
+
+ consume(AS_ID);
+ consume(AS_LPAREN);
+ end;
+ end;
+
+ case actasmtoken of
+ AS_LPAREN: { Memory reference or constant expression }
+ Begin
+ oper.InitRef;
+ BuildReference(oper);
+ end;
+
+ AS_INTNUM,
+ AS_MINUS,
+ AS_PLUS:
+ Begin
+ { Constant memory offset }
+ { This must absolutely be followed by ( }
+ oper.InitRef;
+ oper.opr.ref.offset:=BuildConstExpression(True,False);
+ if actasmtoken<>AS_LPAREN then
+ begin
+ ofs:=oper.opr.ref.offset;
+ BuildConstantOperand(oper);
+ inc(oper.opr.val,ofs);
+ end
+ else
+ BuildReference(oper);
+ end;
+
+ AS_ID: { A constant expression, or a Variable ref. }
+ Begin
+ if is_fenceflag(actasmpattern) then
+ begin
+ consume(AS_ID);
+ end
+ else
+ { Local Label ? }
+ if is_locallabel(actasmpattern) then
+ begin
+ CreateLocalLabel(actasmpattern,hl,false);
+ Consume(AS_ID);
+ AddLabelOperand(hl);
+ end
+ else
+ { Check for label }
+ if SearchLabel(actasmpattern,hl,false) then
+ begin
+ Consume(AS_ID);
+ AddLabelOperand(hl);
+ end
+ else
+ { probably a variable or normal expression }
+ { or a procedure (such as in CALL ID) }
+ Begin
+ { is it a constant ? }
+ if SearchIConstant(actasmpattern,l) then
+ Begin
+ if not (oper.opr.typ in [OPR_NONE,OPR_CONSTANT]) then
+ Message(asmr_e_invalid_operand_type);
+ BuildConstantOperand(oper);
+ end
+ else
+ begin
+ expr:=actasmpattern;
+ Consume(AS_ID);
+ { typecasting? }
+ if (actasmtoken=AS_LPAREN) and
+ SearchType(expr,typesize) then
+ begin
+ oper.hastype:=true;
+ Consume(AS_LPAREN);
+ BuildOperand(oper);
+ Consume(AS_RPAREN);
+ if oper.opr.typ in [OPR_REFERENCE,OPR_LOCAL] then
+ oper.SetSize(typesize,true);
+ end
+ else
+ begin
+ if oper.SetupVar(expr,false) then
+ ReadAt(oper)
+ else
+ Begin
+ { look for special symbols ... }
+ if expr= '__HIGH' then
+ begin
+ consume(AS_LPAREN);
+ if not oper.setupvar('high'+actasmpattern,false) then
+ Message1(sym_e_unknown_id,'high'+actasmpattern);
+ consume(AS_ID);
+ consume(AS_RPAREN);
+ end
+ else
+ if expr = '__RESULT' then
+ oper.SetUpResult
+ else
+ if expr = '__SELF' then
+ oper.SetupSelf
+ else
+ if expr = '__OLDEBP' then
+ oper.SetupOldEBP
+ else
+ Message1(sym_e_unknown_id,expr);
+ end;
+ end;
+ end;
+ if actasmtoken=AS_DOT then
+ MaybeRecordOffset;
+ { add a constant expression? }
+ if (actasmtoken=AS_PLUS) then
+ begin
+ l:=BuildConstExpression(true,false);
+ case oper.opr.typ of
+ OPR_CONSTANT :
+ inc(oper.opr.val,l);
+ OPR_LOCAL :
+ inc(oper.opr.localsymofs,l);
+ OPR_REFERENCE :
+ inc(oper.opr.ref.offset,l);
+ else
+ internalerror(200309202);
+ end;
+ end
+ end;
+ { Do we have a indexing reference, then parse it also }
+ if actasmtoken=AS_LPAREN then
+ BuildReference(oper);
+ end;
+
+ AS_REGISTER: { Register, a variable reference or a constant reference }
+ Begin
+ { save the type of register used. }
+ tempreg:=actasmregister;
+ Consume(AS_REGISTER);
+ if (actasmtoken in [AS_END,AS_SEPARATOR,AS_COMMA]) then
+ begin
+ if not (oper.opr.typ in [OPR_NONE,OPR_REGISTER]) then
+ Message(asmr_e_invalid_operand_type);
+ oper.opr.typ:=OPR_REGISTER;
+ oper.opr.reg:=tempreg;
+ end
+ else
+ Message(asmr_e_syn_operand);
+ end;
+ AS_END,
+ AS_SEPARATOR,
+ AS_COMMA: ;
+ else
+ Begin
+ Message(asmr_e_syn_operand);
+ Consume(actasmtoken);
+ end;
+ end; { end case }
+
+ if refaddr<>addr_full then
+ begin
+ if oper.opr.typ<>OPR_REFERENCE then
+ oper.InitRef;
+
+ oper.opr.ref.refaddr:=refaddr;
+ Consume(AS_RPAREN);
+ end;
+ end;
+
+
+{*****************************************************************************
+ trv64attreader
+*****************************************************************************}
+
+ procedure trv64attreader.BuildOpCode(instr : trvinstruction);
+ var
+ operandnum : longint;
+ Begin
+ { opcode }
+ if (actasmtoken<>AS_OPCODE) then
+ Begin
+ Message(asmr_e_invalid_or_missing_opcode);
+ RecoverConsume(true);
+ exit;
+ end;
+ { Fill the instr object with the current state }
+ with instr do
+ begin
+ Opcode:=ActOpcode;
+ condition:=ActCondition;
+ ordering:=actmemoryordering;
+ end;
+
+ { We are reading operands, so opcode will be an AS_ID }
+ operandnum:=1;
+ Consume(AS_OPCODE);
+ { Zero operand opcode ? }
+ if actasmtoken in [AS_SEPARATOR,AS_END] then
+ begin
+ operandnum:=0;
+ exit;
+ end;
+ { Read the operands }
+ repeat
+ case actasmtoken of
+ AS_COMMA: { Operand delimiter }
+ Begin
+ if operandnum>Max_Operands then
+ Message(asmr_e_too_many_operands)
+ else
+ begin
+ { condition operands doesn't set the operand but write to the
+ condition field of the instruction
+ }
+ if instr.Operands[operandnum].opr.typ<>OPR_NONE then
+ Inc(operandnum);
+ end;
+ Consume(AS_COMMA);
+ end;
+ AS_SEPARATOR,
+ AS_END : { End of asm operands for this opcode }
+ begin
+ break;
+ end;
+ else
+ BuildOperand(instr.Operands[operandnum] as trvoperand);
+ end; { end case }
+ until false;
+ if (operandnum=1) and (instr.Operands[operandnum].opr.typ=OPR_NONE) then
+ dec(operandnum);
+ instr.Ops:=operandnum;
+ end;
+
+ function trv64attreader.is_register(const s: string): boolean;
+ type
+ treg2str = record
+ name : string[3];
+ reg : tregister;
+ end;
+
+ const
+ extraregs : array[0..31] of treg2str = (
+ (name: 'A0'; reg : NR_X10),
+ (name: 'A1'; reg : NR_X11),
+ (name: 'A2'; reg : NR_X12),
+ (name: 'A3'; reg : NR_X13),
+ (name: 'A4'; reg : NR_X14),
+ (name: 'A5'; reg : NR_X15),
+ (name: 'A6'; reg : NR_X16),
+ (name: 'A7'; reg : NR_X17),
+ (name: 'RA'; reg : NR_X1),
+ (name: 'SP'; reg : NR_X2),
+ (name: 'GP'; reg : NR_X3),
+ (name: 'TP'; reg : NR_X4),
+ (name: 'T0'; reg : NR_X5),
+ (name: 'T1'; reg : NR_X6),
+ (name: 'T2'; reg : NR_X7),
+ (name: 'S0'; reg : NR_X8),
+ (name: 'FP'; reg : NR_X8),
+ (name: 'S1'; reg : NR_X9),
+ (name: 'S2'; reg : NR_X18),
+ (name: 'S3'; reg : NR_X19),
+ (name: 'S4'; reg : NR_X20),
+ (name: 'S5'; reg : NR_X21),
+ (name: 'S6'; reg : NR_X22),
+ (name: 'S7'; reg : NR_X23),
+ (name: 'S8'; reg : NR_X24),
+ (name: 'S9'; reg : NR_X25),
+ (name: 'S10';reg : NR_X26),
+ (name: 'S11';reg : NR_X27),
+ (name: 'T3'; reg : NR_X28),
+ (name: 'T4'; reg : NR_X29),
+ (name: 'T5'; reg : NR_X30),
+ (name: 'T6'; reg : NR_X31)
+ );
+
+ var
+ i : longint;
+
+ begin
+ result:=inherited is_register(s);
+ { reg found?
+ possible aliases are always 2 char
+ }
+ if result or (not (length(s) in [2,3])) then
+ exit;
+ for i:=low(extraregs) to high(extraregs) do
+ begin
+ if s=extraregs[i].name then
+ begin
+ actasmregister:=extraregs[i].reg;
+ result:=true;
+ actasmtoken:=AS_REGISTER;
+ exit;
+ end;
+ end;
+ end;
+
+
+ function trv64attreader.is_asmopcode(const s: string):boolean;
+ var
+ cond : tasmcond;
+ hs, postfix : string;
+ l: longint;
+ Begin
+ { making s a value parameter would break other assembler readers }
+ hs:=s;
+ is_asmopcode:=false;
+
+ { clear op code }
+ actopcode:=A_None;
+ { clear condition }
+ fillchar(actcondition,sizeof(actcondition),0);
+
+ { check for direction hint }
+ actopcode := tasmop(ptruint(iasmops.find(hs)));
+ if actopcode <> A_NONE then
+ begin
+ actasmtoken:=AS_OPCODE;
+ is_asmopcode:=true;
+ exit;
+ end;
+ { not found, check branch instructions }
+ if hs[1]='B' then
+ begin
+ { we can search here without an extra table which is sorted by string length
+ because we take the whole remaining string without the leading B }
+ actopcode := A_Bxx;
+ for cond:=low(TAsmCond) to high(TAsmCond) do
+ if copy(hs,2,length(s)-1)=uppercond2str[cond] then
+ begin
+ actcondition:=cond;
+ actasmtoken:=AS_OPCODE;
+ is_asmopcode:=true;
+ exit;
+ end;
+ end;
+
+ { check atomic instructions }
+ if (pos('AMO',hs)=1) or
+ (pos('LR', hs)=1) or
+ (pos('SC', hs)=1) then
+ begin
+ l := length(hs)-1;
+ while l>1 do
+ begin
+ actopcode := tasmop(ptruint(iasmops.find(copy(hs,1,l))));
+ if actopcode <> A_None then
+ begin
+ postfix := copy(hs,l+1,length(hs)-l);
+
+ if postfix='.AQRL' then actmemoryordering:=[moAq,moRl]
+ else if postfix='.RL' then actmemoryordering:=[moRl]
+ else if postfix='.AQ' then actmemoryordering:=[moAq]
+ else
+ exit;
+
+ actasmtoken:=AS_OPCODE;
+ is_asmopcode:=true;
+ exit;
+ end;
+ dec(l);
+ end;
+ end;
+ end;
+
+
+ procedure trv64attreader.handleopcode;
+ var
+ instr : trvinstruction;
+ begin
+ instr:=trvinstruction.Create(trvoperand);
+ BuildOpcode(instr);
+ instr.condition := actcondition;
+ {
+ instr.AddReferenceSizes;
+ instr.SetInstructionOpsize;
+ instr.CheckOperandSizes;
+ }
+ instr.ConcatInstruction(curlist);
+ instr.Free;
+ actmemoryordering:=[];
+ end;
+
+
+{*****************************************************************************
+ Initialize
+*****************************************************************************}
+
+ const
+ asmmode_rv64_standard_info : tasmmodeinfo =
+ (
+ id : asmmode_standard;
+ idtxt : 'STANDARD';
+ casmreader : trv64attreader;
+ );
+
+initialization
+ RegisterAsmMode(asmmode_rv64_standard_info);
+end.
+
diff --git a/compiler/riscv64/rrv32con.inc b/compiler/riscv64/rrv32con.inc
new file mode 100644
index 0000000000..94c5f42533
--- /dev/null
+++ b/compiler/riscv64/rrv32con.inc
@@ -0,0 +1,67 @@
+{ don't edit, this file is generated from rv32reg.dat }
+NR_NO = tregister($00000000);
+NR_X0 = tregister($01000000);
+NR_X1 = tregister($01000001);
+NR_X2 = tregister($01000002);
+NR_X3 = tregister($01000003);
+NR_X4 = tregister($01000004);
+NR_X5 = tregister($01000005);
+NR_X6 = tregister($01000006);
+NR_X7 = tregister($01000007);
+NR_X8 = tregister($01000008);
+NR_X9 = tregister($01000009);
+NR_X10 = tregister($0100000a);
+NR_X11 = tregister($0100000b);
+NR_X12 = tregister($0100000c);
+NR_X13 = tregister($0100000d);
+NR_X14 = tregister($0100000e);
+NR_X15 = tregister($0100000f);
+NR_X16 = tregister($01000010);
+NR_X17 = tregister($01000011);
+NR_X18 = tregister($01000012);
+NR_X19 = tregister($01000013);
+NR_X20 = tregister($01000014);
+NR_X21 = tregister($01000015);
+NR_X22 = tregister($01000016);
+NR_X23 = tregister($01000017);
+NR_X24 = tregister($01000018);
+NR_X25 = tregister($01000019);
+NR_X26 = tregister($0100001a);
+NR_X27 = tregister($0100001b);
+NR_X28 = tregister($0100001c);
+NR_X29 = tregister($0100001d);
+NR_X30 = tregister($0100001e);
+NR_X31 = tregister($0100001f);
+NR_F0 = tregister($02000000);
+NR_F1 = tregister($02000001);
+NR_F2 = tregister($02000002);
+NR_F3 = tregister($02000003);
+NR_F4 = tregister($02000004);
+NR_F5 = tregister($02000005);
+NR_F6 = tregister($02000006);
+NR_F7 = tregister($02000007);
+NR_F8 = tregister($02000008);
+NR_F9 = tregister($02000009);
+NR_F10 = tregister($0200000a);
+NR_F11 = tregister($0200000b);
+NR_F12 = tregister($0200000c);
+NR_F13 = tregister($0200000d);
+NR_F14 = tregister($0200000e);
+NR_F15 = tregister($0200000f);
+NR_F16 = tregister($02000010);
+NR_F17 = tregister($02000011);
+NR_F18 = tregister($02000012);
+NR_F19 = tregister($02000013);
+NR_F20 = tregister($02000014);
+NR_F21 = tregister($02000015);
+NR_F22 = tregister($02000016);
+NR_F23 = tregister($02000017);
+NR_F24 = tregister($02000018);
+NR_F25 = tregister($02000019);
+NR_F26 = tregister($0200001a);
+NR_F27 = tregister($0200001b);
+NR_F28 = tregister($0200001c);
+NR_F29 = tregister($0200001d);
+NR_F30 = tregister($0200001e);
+NR_F31 = tregister($0200001f);
+NR_FCSR = tregister($05000001);
diff --git a/compiler/riscv64/rrv32dwa.inc b/compiler/riscv64/rrv32dwa.inc
new file mode 100644
index 0000000000..6755ebb4c5
--- /dev/null
+++ b/compiler/riscv64/rrv32dwa.inc
@@ -0,0 +1,67 @@
+{ don't edit, this file is generated from rv32reg.dat }
+-1,
+0,
+1,
+2,
+3,
+4,
+5,
+6,
+7,
+8,
+9,
+10,
+11,
+12,
+13,
+14,
+15,
+16,
+17,
+18,
+19,
+20,
+21,
+22,
+23,
+24,
+25,
+26,
+27,
+28,
+29,
+30,
+31,
+0,
+1,
+2,
+3,
+4,
+5,
+6,
+7,
+8,
+9,
+10,
+11,
+12,
+13,
+14,
+15,
+16,
+17,
+18,
+19,
+20,
+21,
+22,
+23,
+24,
+25,
+26,
+27,
+28,
+29,
+30,
+31,
+0
diff --git a/compiler/riscv64/rrv32nor.inc b/compiler/riscv64/rrv32nor.inc
new file mode 100644
index 0000000000..a3c3b517a4
--- /dev/null
+++ b/compiler/riscv64/rrv32nor.inc
@@ -0,0 +1,2 @@
+{ don't edit, this file is generated from rv32reg.dat }
+66
diff --git a/compiler/riscv64/rrv32num.inc b/compiler/riscv64/rrv32num.inc
new file mode 100644
index 0000000000..f9553bf4fb
--- /dev/null
+++ b/compiler/riscv64/rrv32num.inc
@@ -0,0 +1,67 @@
+{ don't edit, this file is generated from rv32reg.dat }
+tregister($00000000),
+tregister($01000000),
+tregister($01000001),
+tregister($01000002),
+tregister($01000003),
+tregister($01000004),
+tregister($01000005),
+tregister($01000006),
+tregister($01000007),
+tregister($01000008),
+tregister($01000009),
+tregister($0100000a),
+tregister($0100000b),
+tregister($0100000c),
+tregister($0100000d),
+tregister($0100000e),
+tregister($0100000f),
+tregister($01000010),
+tregister($01000011),
+tregister($01000012),
+tregister($01000013),
+tregister($01000014),
+tregister($01000015),
+tregister($01000016),
+tregister($01000017),
+tregister($01000018),
+tregister($01000019),
+tregister($0100001a),
+tregister($0100001b),
+tregister($0100001c),
+tregister($0100001d),
+tregister($0100001e),
+tregister($0100001f),
+tregister($02000000),
+tregister($02000001),
+tregister($02000002),
+tregister($02000003),
+tregister($02000004),
+tregister($02000005),
+tregister($02000006),
+tregister($02000007),
+tregister($02000008),
+tregister($02000009),
+tregister($0200000a),
+tregister($0200000b),
+tregister($0200000c),
+tregister($0200000d),
+tregister($0200000e),
+tregister($0200000f),
+tregister($02000010),
+tregister($02000011),
+tregister($02000012),
+tregister($02000013),
+tregister($02000014),
+tregister($02000015),
+tregister($02000016),
+tregister($02000017),
+tregister($02000018),
+tregister($02000019),
+tregister($0200001a),
+tregister($0200001b),
+tregister($0200001c),
+tregister($0200001d),
+tregister($0200001e),
+tregister($0200001f),
+tregister($05000001)
diff --git a/compiler/riscv64/rrv32rni.inc b/compiler/riscv64/rrv32rni.inc
new file mode 100644
index 0000000000..de9f6b796b
--- /dev/null
+++ b/compiler/riscv64/rrv32rni.inc
@@ -0,0 +1,67 @@
+{ don't edit, this file is generated from rv32reg.dat }
+0,
+1,
+2,
+3,
+4,
+5,
+6,
+7,
+8,
+9,
+10,
+11,
+12,
+13,
+14,
+15,
+16,
+17,
+18,
+19,
+20,
+21,
+22,
+23,
+24,
+25,
+26,
+27,
+28,
+29,
+30,
+31,
+32,
+33,
+34,
+35,
+36,
+37,
+38,
+39,
+40,
+41,
+42,
+43,
+44,
+45,
+46,
+47,
+48,
+49,
+50,
+51,
+52,
+53,
+54,
+55,
+56,
+57,
+58,
+59,
+60,
+61,
+62,
+63,
+64,
+65
diff --git a/compiler/riscv64/rrv32sri.inc b/compiler/riscv64/rrv32sri.inc
new file mode 100644
index 0000000000..a39dc1faa3
--- /dev/null
+++ b/compiler/riscv64/rrv32sri.inc
@@ -0,0 +1,67 @@
+{ don't edit, this file is generated from rv32reg.dat }
+0,
+33,
+34,
+43,
+44,
+45,
+46,
+47,
+48,
+49,
+50,
+51,
+52,
+35,
+53,
+54,
+55,
+56,
+57,
+58,
+59,
+60,
+61,
+62,
+36,
+63,
+64,
+37,
+38,
+39,
+40,
+41,
+42,
+65,
+1,
+2,
+11,
+12,
+13,
+14,
+15,
+16,
+17,
+18,
+19,
+20,
+3,
+21,
+22,
+23,
+24,
+25,
+26,
+27,
+28,
+29,
+30,
+4,
+31,
+32,
+5,
+6,
+7,
+8,
+9,
+10
diff --git a/compiler/riscv64/rrv32sta.inc b/compiler/riscv64/rrv32sta.inc
new file mode 100644
index 0000000000..6755ebb4c5
--- /dev/null
+++ b/compiler/riscv64/rrv32sta.inc
@@ -0,0 +1,67 @@
+{ don't edit, this file is generated from rv32reg.dat }
+-1,
+0,
+1,
+2,
+3,
+4,
+5,
+6,
+7,
+8,
+9,
+10,
+11,
+12,
+13,
+14,
+15,
+16,
+17,
+18,
+19,
+20,
+21,
+22,
+23,
+24,
+25,
+26,
+27,
+28,
+29,
+30,
+31,
+0,
+1,
+2,
+3,
+4,
+5,
+6,
+7,
+8,
+9,
+10,
+11,
+12,
+13,
+14,
+15,
+16,
+17,
+18,
+19,
+20,
+21,
+22,
+23,
+24,
+25,
+26,
+27,
+28,
+29,
+30,
+31,
+0
diff --git a/compiler/riscv64/rrv32std.inc b/compiler/riscv64/rrv32std.inc
new file mode 100644
index 0000000000..468a711616
--- /dev/null
+++ b/compiler/riscv64/rrv32std.inc
@@ -0,0 +1,67 @@
+{ don't edit, this file is generated from rv32reg.dat }
+'INVALID',
+'x0',
+'x1',
+'x2',
+'x3',
+'x4',
+'x5',
+'x6',
+'x7',
+'x8',
+'x9',
+'x10',
+'x11',
+'x12',
+'x13',
+'x14',
+'x15',
+'x16',
+'x17',
+'x18',
+'x19',
+'x20',
+'x21',
+'x22',
+'x23',
+'x24',
+'x25',
+'x26',
+'x27',
+'x28',
+'x29',
+'x30',
+'x31',
+'f0',
+'f1',
+'f2',
+'f3',
+'f4',
+'f5',
+'f6',
+'f7',
+'f8',
+'f9',
+'f10',
+'f11',
+'f12',
+'f13',
+'f14',
+'f15',
+'f16',
+'f17',
+'f18',
+'f19',
+'f20',
+'f21',
+'f22',
+'f23',
+'f24',
+'f25',
+'f26',
+'f27',
+'f28',
+'f29',
+'f30',
+'f31',
+'fcsr'
diff --git a/compiler/riscv64/rrv32sup.inc b/compiler/riscv64/rrv32sup.inc
new file mode 100644
index 0000000000..cb12862e9d
--- /dev/null
+++ b/compiler/riscv64/rrv32sup.inc
@@ -0,0 +1,67 @@
+{ don't edit, this file is generated from rv32reg.dat }
+RS_NO = $00;
+RS_X0 = $00;
+RS_X1 = $01;
+RS_X2 = $02;
+RS_X3 = $03;
+RS_X4 = $04;
+RS_X5 = $05;
+RS_X6 = $06;
+RS_X7 = $07;
+RS_X8 = $08;
+RS_X9 = $09;
+RS_X10 = $0a;
+RS_X11 = $0b;
+RS_X12 = $0c;
+RS_X13 = $0d;
+RS_X14 = $0e;
+RS_X15 = $0f;
+RS_X16 = $10;
+RS_X17 = $11;
+RS_X18 = $12;
+RS_X19 = $13;
+RS_X20 = $14;
+RS_X21 = $15;
+RS_X22 = $16;
+RS_X23 = $17;
+RS_X24 = $18;
+RS_X25 = $19;
+RS_X26 = $1a;
+RS_X27 = $1b;
+RS_X28 = $1c;
+RS_X29 = $1d;
+RS_X30 = $1e;
+RS_X31 = $1f;
+RS_F0 = $00;
+RS_F1 = $01;
+RS_F2 = $02;
+RS_F3 = $03;
+RS_F4 = $04;
+RS_F5 = $05;
+RS_F6 = $06;
+RS_F7 = $07;
+RS_F8 = $08;
+RS_F9 = $09;
+RS_F10 = $0a;
+RS_F11 = $0b;
+RS_F12 = $0c;
+RS_F13 = $0d;
+RS_F14 = $0e;
+RS_F15 = $0f;
+RS_F16 = $10;
+RS_F17 = $11;
+RS_F18 = $12;
+RS_F19 = $13;
+RS_F20 = $14;
+RS_F21 = $15;
+RS_F22 = $16;
+RS_F23 = $17;
+RS_F24 = $18;
+RS_F25 = $19;
+RS_F26 = $1a;
+RS_F27 = $1b;
+RS_F28 = $1c;
+RS_F29 = $1d;
+RS_F30 = $1e;
+RS_F31 = $1f;
+RS_FCSR = $01;
diff --git a/compiler/riscv64/rv32reg.dat b/compiler/riscv64/rv32reg.dat
new file mode 100644
index 0000000000..0be9f17f99
--- /dev/null
+++ b/compiler/riscv64/rv32reg.dat
@@ -0,0 +1,77 @@
+;
+; RiscV registers
+;
+; layout
+; <name>,<type>,<subtype>,<value>,<stdname>,<stab idx>,<dwarf idx>
+;
+NO,$00,$00,$00,INVALID,-1,-1
+; Integer registers
+X0,$01,$00,$00,x0,0,0
+X1,$01,$00,$01,x1,1,1
+X2,$01,$00,$02,x2,2,2
+X3,$01,$00,$03,x3,3,3
+X4,$01,$00,$04,x4,4,4
+X5,$01,$00,$05,x5,5,5
+X6,$01,$00,$06,x6,6,6
+X7,$01,$00,$07,x7,7,7
+X8,$01,$00,$08,x8,8,8
+X9,$01,$00,$09,x9,9,9
+X10,$01,$00,$0a,x10,10,10
+X11,$01,$00,$0b,x11,11,11
+X12,$01,$00,$0c,x12,12,12
+X13,$01,$00,$0d,x13,13,13
+X14,$01,$00,$0e,x14,14,14
+X15,$01,$00,$0f,x15,15,15
+X16,$01,$00,$10,x16,16,16
+X17,$01,$00,$11,x17,17,17
+X18,$01,$00,$12,x18,18,18
+X19,$01,$00,$13,x19,19,19
+X20,$01,$00,$14,x20,20,20
+X21,$01,$00,$15,x21,21,21
+X22,$01,$00,$16,x22,22,22
+X23,$01,$00,$17,x23,23,23
+X24,$01,$00,$18,x24,24,24
+X25,$01,$00,$19,x25,25,25
+X26,$01,$00,$1a,x26,26,26
+X27,$01,$00,$1b,x27,27,27
+X28,$01,$00,$1c,x28,28,28
+X29,$01,$00,$1d,x29,29,29
+X30,$01,$00,$1e,x30,30,30
+X31,$01,$00,$1f,x31,31,31
+
+; Float registers
+F0,$02,$00,$00,f0,0,0
+F1,$02,$00,$01,f1,1,1
+F2,$02,$00,$02,f2,2,2
+F3,$02,$00,$03,f3,3,3
+F4,$02,$00,$04,f4,4,4
+F5,$02,$00,$05,f5,5,5
+F6,$02,$00,$06,f6,6,6
+F7,$02,$00,$07,f7,7,7
+F8,$02,$00,$08,f8,8,8
+F9,$02,$00,$09,f9,9,9
+F10,$02,$00,$0a,f10,10,10
+F11,$02,$00,$0b,f11,11,11
+F12,$02,$00,$0c,f12,12,12
+F13,$02,$00,$0d,f13,13,13
+F14,$02,$00,$0e,f14,14,14
+F15,$02,$00,$0f,f15,15,15
+F16,$02,$00,$10,f16,16,16
+F17,$02,$00,$11,f17,17,17
+F18,$02,$00,$12,f18,18,18
+F19,$02,$00,$13,f19,19,19
+F20,$02,$00,$14,f20,20,20
+F21,$02,$00,$15,f21,21,21
+F22,$02,$00,$16,f22,22,22
+F23,$02,$00,$17,f23,23,23
+F24,$02,$00,$18,f24,24,24
+F25,$02,$00,$19,f25,25,25
+F26,$02,$00,$1a,f26,26,26
+F27,$02,$00,$1b,f27,27,27
+F28,$02,$00,$1c,f28,28,28
+F29,$02,$00,$1d,f29,29,29
+F30,$02,$00,$1e,f30,30,30
+F31,$02,$00,$1f,f31,31,31
+
+; Special registers
+FCSR,$05,$00,$01,fcsr,0,0
diff --git a/compiler/riscv64/symcpu.pas b/compiler/riscv64/symcpu.pas
new file mode 100644
index 0000000000..e1b5f3b08e
--- /dev/null
+++ b/compiler/riscv64/symcpu.pas
@@ -0,0 +1,220 @@
+{
+ Copyright (c) 2014 by Florian Klaempfl
+
+ Symbol table overrides for RiscV64
+
+ 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 symcpu;
+
+{$i fpcdefs.inc}
+
+interface
+
+uses
+ symtype,symdef,symsym;
+
+type
+ { defs }
+ tcpufiledef = class(tfiledef)
+ end;
+ tcpufiledefclass = class of tcpufiledef;
+
+ tcpuvariantdef = class(tvariantdef)
+ end;
+ tcpuvariantdefclass = class of tcpuvariantdef;
+
+ tcpuformaldef = class(tformaldef)
+ end;
+ tcpuformaldefclass = class of tcpuformaldef;
+
+ tcpuforwarddef = class(tforwarddef)
+ end;
+ tcpuforwarddefclass = class of tcpuforwarddef;
+
+ tcpuundefineddef = class(tundefineddef)
+ end;
+ tcpuundefineddefclass = class of tcpuundefineddef;
+
+ tcpuerrordef = class(terrordef)
+ end;
+ tcpuerrordefclass = class of tcpuerrordef;
+
+ tcpupointerdef = class(tpointerdef)
+ end;
+ tcpupointerdefclass = class of tcpupointerdef;
+
+ tcpurecorddef = class(trecorddef)
+ end;
+ tcpurecorddefclass = class of tcpurecorddef;
+
+ tcpuimplementedinterface = class(timplementedinterface)
+ end;
+ tcpuimplementedinterfaceclass = class of tcpuimplementedinterface;
+
+ tcpuobjectdef = class(tobjectdef)
+ end;
+ tcpuobjectdefclass = class of tcpuobjectdef;
+
+ tcpuclassrefdef = class(tclassrefdef)
+ end;
+ tcpuclassrefdefclass = class of tcpuclassrefdef;
+
+ tcpuarraydef = class(tarraydef)
+ end;
+ tcpuarraydefclass = class of tcpuarraydef;
+
+ tcpuorddef = class(torddef)
+ end;
+ tcpuorddefclass = class of tcpuorddef;
+
+ tcpufloatdef = class(tfloatdef)
+ end;
+ tcpufloatdefclass = class of tcpufloatdef;
+
+ tcpuprocvardef = class(tprocvardef)
+ end;
+ tcpuprocvardefclass = class of tcpuprocvardef;
+
+ tcpuprocdef = class(tprocdef)
+ end;
+ tcpuprocdefclass = class of tcpuprocdef;
+
+ tcpustringdef = class(tstringdef)
+ end;
+ tcpustringdefclass = class of tcpustringdef;
+
+ tcpuenumdef = class(tenumdef)
+ end;
+ tcpuenumdefclass = class of tcpuenumdef;
+
+ tcpusetdef = class(tsetdef)
+ end;
+ tcpusetdefclass = class of tcpusetdef;
+
+ { syms }
+ tcpulabelsym = class(tlabelsym)
+ end;
+ tcpulabelsymclass = class of tcpulabelsym;
+
+ tcpuunitsym = class(tunitsym)
+ end;
+ tcpuunitsymclass = class of tcpuunitsym;
+
+ tcpuprogramparasym = class(tprogramparasym)
+ end;
+ tcpuprogramparasymclass = class(tprogramparasym);
+
+ tcpunamespacesym = class(tnamespacesym)
+ end;
+ tcpunamespacesymclass = class of tcpunamespacesym;
+
+ tcpuprocsym = class(tprocsym)
+ end;
+ tcpuprocsymclass = class of tcpuprocsym;
+
+ tcputypesym = class(ttypesym)
+ end;
+ tcpuypesymclass = class of tcputypesym;
+
+ tcpufieldvarsym = class(tfieldvarsym)
+ end;
+ tcpufieldvarsymclass = class of tcpufieldvarsym;
+
+ tcpulocalvarsym = class(tlocalvarsym)
+ end;
+ tcpulocalvarsymclass = class of tcpulocalvarsym;
+
+ tcpuparavarsym = class(tparavarsym)
+ end;
+ tcpuparavarsymclass = class of tcpuparavarsym;
+
+ tcpustaticvarsym = class(tstaticvarsym)
+ end;
+ tcpustaticvarsymclass = class of tcpustaticvarsym;
+
+ tcpuabsolutevarsym = class(tabsolutevarsym)
+ end;
+ tcpuabsolutevarsymclass = class of tcpuabsolutevarsym;
+
+ tcpupropertysym = class(tpropertysym)
+ end;
+ tcpupropertysymclass = class of tcpupropertysym;
+
+ tcpuconstsym = class(tconstsym)
+ end;
+ tcpuconstsymclass = class of tcpuconstsym;
+
+ tcpuenumsym = class(tenumsym)
+ end;
+ tcpuenumsymclass = class of tcpuenumsym;
+
+ tcpusyssym = class(tsyssym)
+ end;
+ tcpusyssymclass = class of tcpusyssym;
+
+
+const
+ pbestrealtype : ^tdef = @s64floattype;
+
+
+implementation
+
+ uses
+ symconst, defutil, defcmp;
+
+
+begin
+ { used tdef classes }
+ cfiledef:=tcpufiledef;
+ cvariantdef:=tcpuvariantdef;
+ cformaldef:=tcpuformaldef;
+ cforwarddef:=tcpuforwarddef;
+ cundefineddef:=tcpuundefineddef;
+ cerrordef:=tcpuerrordef;
+ cpointerdef:=tcpupointerdef;
+ crecorddef:=tcpurecorddef;
+ cimplementedinterface:=tcpuimplementedinterface;
+ cobjectdef:=tcpuobjectdef;
+ cclassrefdef:=tcpuclassrefdef;
+ carraydef:=tcpuarraydef;
+ corddef:=tcpuorddef;
+ cfloatdef:=tcpufloatdef;
+ cprocvardef:=tcpuprocvardef;
+ cprocdef:=tcpuprocdef;
+ cstringdef:=tcpustringdef;
+ cenumdef:=tcpuenumdef;
+ csetdef:=tcpusetdef;
+
+ { used tsym classes }
+ clabelsym:=tcpulabelsym;
+ cunitsym:=tcpuunitsym;
+ cprogramparasym:=tcpuprogramparasym;
+ cnamespacesym:=tcpunamespacesym;
+ cprocsym:=tcpuprocsym;
+ ctypesym:=tcputypesym;
+ cfieldvarsym:=tcpufieldvarsym;
+ clocalvarsym:=tcpulocalvarsym;
+ cparavarsym:=tcpuparavarsym;
+ cstaticvarsym:=tcpustaticvarsym;
+ cabsolutevarsym:=tcpuabsolutevarsym;
+ cpropertysym:=tcpupropertysym;
+ cconstsym:=tcpuconstsym;
+ cenumsym:=tcpuenumsym;
+ csyssym:=tcpusyssym;
+end.
+