Browse Source

+ more avr code

git-svn-id: trunk@10207 -
florian 17 năm trước cách đây
mục cha
commit
0e13d07a31

+ 4 - 0
.gitattributes

@@ -76,6 +76,7 @@ compiler/arm/rarmsup.inc svneol=native#text/plain
 compiler/arm/rgcpu.pas svneol=native#text/plain
 compiler/assemble.pas svneol=native#text/plain
 compiler/avr/aasmcpu.pas svneol=native#text/plain
+compiler/avr/agavrgas.pas svneol=native#text/plain
 compiler/avr/aoptcpu.pas svneol=native#text/plain
 compiler/avr/aoptcpub.pas svneol=native#text/plain
 compiler/avr/aoptcpud.pas svneol=native#text/plain
@@ -87,6 +88,9 @@ compiler/avr/cpunode.pas svneol=native#text/plain
 compiler/avr/cpupara.pas svneol=native#text/plain
 compiler/avr/cpupi.pas svneol=native#text/plain
 compiler/avr/cputarg.pas svneol=native#text/plain
+compiler/avr/itcpugas.pas svneol=native#text/plain
+compiler/avr/raavr.pas svneol=native#text/plain
+compiler/avr/raavrgas.pas svneol=native#text/plain
 compiler/avr/ravrcon.inc svneol=native#text/plain
 compiler/avr/ravrdwa.inc svneol=native#text/plain
 compiler/avr/ravrnor.inc svneol=native#text/plain

+ 180 - 0
compiler/avr/agavrgas.pas

@@ -0,0 +1,180 @@
+{
+    Copyright (c) 2003 by Florian Klaempfl
+
+    This unit implements an asm for the ARM
+
+    This program is free software; you can redistribute it and/or modify
+    it under the terms of the GNU General Public License as published by
+    the Free Software Foundation; either version 2 of the License, or
+    (at your option) any later version.
+
+    This program is distributed in the hope that it will be useful,
+    but WITHOUT ANY WARRANTY; without even the implied warranty of
+    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+    GNU General Public License for more details.
+
+    You should have received a copy of the GNU General Public License
+    along with this program; if not, write to the Free Software
+    Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
+
+ ****************************************************************************
+}
+{ This unit implements the GNU Assembler writer for the ARM
+}
+
+unit agavrgas;
+
+{$i fpcdefs.inc}
+
+  interface
+
+    uses
+       aasmtai,aasmdata,
+       aggas,
+       cpubase;
+
+    type
+      TAVRGNUAssembler=class(TGNUassembler)
+        constructor create(smart: boolean); override;
+      end;
+
+     TAVRInstrWriter=class(TCPUInstrWriter)
+        procedure WriteInstruction(hp : tai);override;
+     end;
+
+
+    const
+      gas_shiftmode2str : array[tshiftmode] of string[3] = (
+        '','lsl','lsr','asr','ror','rrx');
+
+  implementation
+
+    uses
+       cutils,globals,verbose,
+       systems,
+       assemble,
+       aasmcpu,
+       itcpugas,
+       cgbase,cgutils;
+
+{****************************************************************************}
+{                         GNU Arm Assembler writer                           }
+{****************************************************************************}
+
+    constructor TAVRGNUAssembler.create(smart: boolean);
+      begin
+        inherited create(smart);
+        InstrWriter := TAVRInstrWriter.create(self);
+      end;
+
+
+{****************************************************************************}
+{                  Helper routines for Instruction Writer                    }
+{****************************************************************************}
+
+    function getreferencestring(var ref : treference) : string;
+      var
+        s : string;
+      begin
+         with ref do
+          begin
+{$ifdef extdebug}
+            // if base=NR_NO then
+            //   internalerror(200308292);
+
+            // if ((index<>NR_NO) or (shiftmode<>SM_None)) and ((offset<>0) or (symbol<>nil)) then
+            //   internalerror(200308293);
+{$endif extdebug}
+
+            if assigned(symbol) then
+              begin
+                if (base<>NR_NO) and not(is_pc(base)) then
+                  internalerror(200309011);
+                s:=symbol.name;
+                if offset<0 then
+                  s:=s+tostr(offset)
+                else if offset>0 then
+                  s:=s+'+'+tostr(offset);
+              end
+            else
+              begin
+                s:=gas_regname(base);
+              end;
+
+          end;
+        getreferencestring:=s;
+      end;
+
+
+    const
+      shiftmode2str: array[tshiftmode] of string[3] = ('','lsl','lsr','asr','ror','rrx');
+
+    function getopstr(const o:toper) : string;
+      var
+        hs : string;
+        first : boolean;
+        r : tsuperregister;
+      begin
+        case o.typ of
+          top_reg:
+            getopstr:=gas_regname(o.reg);
+          top_const:
+            getopstr:='#'+tostr(longint(o.val));
+          top_ref:
+            if o.ref^.refaddr=addr_full then
+              begin
+                hs:=o.ref^.symbol.name;
+                if o.ref^.offset>0 then
+                 hs:=hs+'+'+tostr(o.ref^.offset)
+                else
+                 if o.ref^.offset<0 then
+                  hs:=hs+tostr(o.ref^.offset);
+                getopstr:=hs;
+              end
+            else
+              getopstr:=getreferencestring(o.ref^);
+          else
+            internalerror(2002070604);
+        end;
+      end;
+
+
+    Procedure TAVRInstrWriter.WriteInstruction(hp : tai);
+    var op: TAsmOp;
+        s: string;
+        i: byte;
+        sep: string[3];
+    begin
+      op:=taicpu(hp).opcode;
+      s:=#9+gas_op2str[op]+cond2str[taicpu(hp).condition];
+      if taicpu(hp).ops<>0 then
+        begin
+          sep:=#9;
+          for i:=0 to taicpu(hp).ops-1 do
+            begin
+              s:=s+sep+getopstr(taicpu(hp).oper[i]^);
+              sep:=',';
+            end;
+        end;
+      owner.AsmWriteLn(s);
+    end;
+
+
+    const
+       as_arm_gas_info : tasminfo =
+          (
+            id     : as_gas;
+
+            idtxt  : 'AS';
+            asmbin : 'as';
+            asmcmd : '-o $OBJ $ASM';
+            supported_target : system_any;
+            flags : [af_allowdirect,af_needar,af_smartlink_sections];
+            labelprefix : '.L';
+            comment : '# ';
+          );
+
+
+begin
+  RegisterAssembler(as_arm_gas_info,TAVRGNUAssembler);
+end.

+ 1 - 0
compiler/avr/cpubase.pas

@@ -324,6 +324,7 @@ unit cpubase;
       }
       std_param_align = 4;
 
+      saved_mm_registers : array[0..0] of tsuperregister = (RS_INVALID);
 
 {*****************************************************************************
                                   Helpers

+ 2 - 4
compiler/avr/cputarg.pas

@@ -44,17 +44,15 @@ implementation
 **************************************}
 
     {$ifndef NOAGARMGAS}
-      ,agarmgas
+      ,agavrgas
     {$endif}
 
-      ,ogcoff
-
 {**************************************
         Assembler Readers
 **************************************}
 
   {$ifndef NoRaarmgas}
-       ,raarmgas
+       ,raavrgas
   {$endif NoRaarmgas}
 
 {**************************************

+ 101 - 0
compiler/avr/itcpugas.pas

@@ -0,0 +1,101 @@
+{
+    Copyright (c) 1998-2002 by Florian Klaempfl
+
+    This unit contains the ARM 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
+    { Standard opcode string table (for each tasmop enumeration). The
+      opcode strings should conform to the names as defined by the
+      processor manufacturer.
+    }
+    gas_op2str : op2strtable = ('',
+        'add','adc','adiw','sub','subi','sbc','sbci','sbiw','and','andi',
+        'or','ori','eor','com','neg','sbr','cbr','inc','dec','tst','clr',
+        'ser','mul','muls','fmul','fmuls','fmulsu','rjmp','ijmp',
+        'eijmp','jmp','rcall','icall','eicall','call','ret','reti','cpse',
+        'cp','cpc','cpi','sb','br','mov','movw','ldi','lds','ld','ldd',
+        'sts','st','std','lpm','elpm','spm','in','out','push','pop',
+        'lsl','lsr','rol','ror','asr','swap','bset','bclr','sbi','cbi',
+        'bst','bld','s','c','brak','nop','sleep','wdr');
+
+    function gas_regnum_search(const s:string):Tregister;
+    function gas_regname(r:Tregister):string;
+
+
+implementation
+
+    uses
+      cutils,verbose;
+
+    const
+      gas_regname_table : array[tregisterindex] of string[7] = (
+        {$i ravrstd.inc}
+      );
+
+      gas_regname_index : array[tregisterindex] of tregisterindex = (
+        {$i ravrsri.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.

+ 52 - 0
compiler/avr/raavr.pas

@@ -0,0 +1,52 @@
+{
+    Copyright (c) 1998-2003 by Carl Eric Codere and Peter Vreman
+
+    Handles the common arm 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 raavr;
+
+{$i fpcdefs.inc}
+
+  interface
+
+    uses
+      cpubase,
+      aasmtai,aasmdata,
+      rautils;
+
+    type
+      TAVROperand=class(TOperand)
+      end;
+
+      TAVRInstruction=class(TInstruction)
+        function ConcatInstruction(p:TAsmList) : tai;override;
+      end;
+
+  implementation
+
+    uses
+      aasmcpu;
+
+    function TAVRInstruction.ConcatInstruction(p:TAsmList) : tai;
+      begin
+        result:=inherited ConcatInstruction(p);
+      end;
+
+
+end.

+ 748 - 0
compiler/avr/raavrgas.pas

@@ -0,0 +1,748 @@
+{
+    Copyright (c) 1998-2008 by Carl Eric Codere and Peter Vreman
+
+    Does the parsing for the ARM 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 raavrgas;
+
+{$i fpcdefs.inc}
+
+  Interface
+
+    uses
+      raatt,raavr,
+      cpubase;
+
+    type
+      tavrattreader = class(tattreader)
+        function is_asmopcode(const s: string):boolean;override;
+        function is_register(const s:string):boolean;override;
+        procedure handleopcode;override;
+        procedure BuildReference(oper : tavroperand);
+        procedure BuildOperand(oper : tavroperand);
+        function TryBuildShifterOp(oper : tavroperand) : boolean;
+        procedure BuildOpCode(instr : tavrinstruction);
+        procedure ReadSym(oper : tavroperand);
+        procedure ConvertCalljmp(instr : tavrinstruction);
+      end;
+
+
+  Implementation
+
+    uses
+      { helpers }
+      cutils,
+      { global }
+      globtype,globals,verbose,
+      systems,
+      { aasm }
+      cpuinfo,aasmbase,aasmtai,aasmdata,aasmcpu,
+      { symtable }
+      symconst,symbase,symtype,symsym,symtable,
+      { parser }
+      scanner,
+      procinfo,
+      itcpugas,
+      rabase,rautils,
+      cgbase,cgobj
+      ;
+
+
+    function tavrattreader.is_register(const s:string):boolean;
+      type
+        treg2str = record
+          name : string[2];
+          reg : tregister;
+        end;
+{
+      const
+        extraregs : array[0..19] of treg2str = (
+          (name: 'X'; reg : NR_Z),
+          (name: 'Y'; reg : NR_R1),
+          (name: 'Z'; reg : NR_R2),
+        );
+}
+      var
+        i : longint;
+
+      begin
+        result:=inherited is_register(s);
+        { reg found?
+          possible aliases are always 2 char
+        }
+        if result or (length(s)<>2) 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;
+
+
+    procedure tavrattreader.ReadSym(oper : tavroperand);
+      var
+         tempstr, mangledname : string;
+         typesize,l,k : longint;
+      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 tavrattreader.BuildReference(oper : tavroperand);
+
+      procedure Consume_RBracket;
+        begin
+          if actasmtoken<>AS_RBRACKET then
+           Begin
+             Message(asmr_e_invalid_reference_syntax);
+             RecoverConsume(true);
+           end
+          else
+           begin
+             Consume(AS_RBRACKET);
+             if not (actasmtoken in [AS_COMMA,AS_SEPARATOR,AS_END]) then
+              Begin
+                Message(asmr_e_invalid_reference_syntax);
+                RecoverConsume(true);
+              end;
+           end;
+        end;
+
+
+      procedure read_index;
+        begin
+          Consume(AS_COMMA);
+          if actasmtoken=AS_REGISTER then
+            Begin
+              oper.opr.ref.index:=actasmregister;
+              Consume(AS_REGISTER);
+            end
+          else if actasmtoken=AS_HASH then
+            begin
+              Consume(AS_HASH);
+              inc(oper.opr.ref.offset,BuildConstExpression(false,true));
+            end;
+        end;
+
+
+      begin
+        Consume(AS_LBRACKET);
+        if actasmtoken=AS_REGISTER then
+          begin
+            oper.opr.ref.base:=actasmregister;
+            Consume(AS_REGISTER);
+            { can either be a register or a right parenthesis }
+            { (reg)        }
+            if actasmtoken=AS_RBRACKET then
+             Begin
+               Consume_RBracket;
+               oper.opr.ref.addressmode:=AM_POSTINDEXED;
+               if actasmtoken=AS_COMMA then
+                 read_index;
+               exit;
+             end;
+            if actasmtoken=AS_COMMA then
+              begin
+                read_index;
+                Consume_RBracket;
+              end;
+            if actasmtoken=AS_NOT then
+              begin
+                consume(AS_NOT);
+                oper.opr.ref.addressmode:=AM_PREINDEXED;
+              end;
+          end {end case }
+        else
+          Begin
+            Message(asmr_e_invalid_reference_syntax);
+            RecoverConsume(false);
+          end;
+      end;
+
+
+    Procedure tavrattreader.BuildOperand(oper : tavroperand);
+      var
+        expr : string;
+        typesize,l : longint;
+
+
+        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   : longint;
+          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
+                     (tabstractnormalvarsym(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 :
+                inc(oper.opr.val,l);
+              OPR_REFERENCE :
+                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.RefAsmSymbol(mangledname);
+                  end
+                else
+                  inc(oper.opr.val,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;
+
+
+      var
+        tempreg : tregister;
+        ireg : tsuperregister;
+        hl : tasmlabel;
+        ofs : longint;
+        registerset : tcpuregisterset;
+      Begin
+        expr:='';
+        case actasmtoken of
+          AS_LBRACKET: { Memory reference or constant expression }
+            Begin
+              oper.InitRef;
+              BuildReference(oper);
+            end;
+
+          AS_HASH: { Constant expression  }
+            Begin
+              Consume(AS_HASH);
+              BuildConstantOperand(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
+              { 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 not(oper.SetupVar(expr,false)) then
+                        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;
+
+          { Register, a variable reference or a constant reference  }
+          AS_REGISTER:
+            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 if (actasmtoken=AS_NOT) and (actopcode in [A_LDM,A_STM]) then
+                begin
+                  consume(AS_NOT);
+                  oper.opr.typ:=OPR_REFERENCE;
+                  oper.opr.ref.addressmode:=AM_PREINDEXED;
+                  oper.opr.ref.index:=tempreg;
+                end
+              else
+                Message(asmr_e_syn_operand);
+            end;
+
+          { Registerset }
+          AS_LSBRACKET:
+            begin
+              consume(AS_LSBRACKET);
+              registerset:=[];
+              while true do
+                begin
+                  if actasmtoken=AS_REGISTER then
+                    begin
+                      include(registerset,getsupreg(actasmregister));
+                      tempreg:=actasmregister;
+                      consume(AS_REGISTER);
+                      if actasmtoken=AS_MINUS then
+                        begin
+                          consume(AS_MINUS);
+                          for ireg:=getsupreg(tempreg) to getsupreg(actasmregister) do
+                            include(registerset,ireg);
+                          consume(AS_REGISTER);
+                        end;
+                    end
+                  else
+                    consume(AS_REGISTER);
+                  if actasmtoken=AS_COMMA then
+                    consume(AS_COMMA)
+                  else
+                    break;
+                end;
+              consume(AS_RSBRACKET);
+              oper.opr.typ:=OPR_REGSET;
+              oper.opr.regset:=registerset;
+            end;
+          AS_END,
+          AS_SEPARATOR,
+          AS_COMMA: ;
+        else
+          Begin
+            Message(asmr_e_syn_operand);
+            Consume(actasmtoken);
+          end;
+        end; { end case }
+      end;
+
+
+{*****************************************************************************
+                                tavrattreader
+*****************************************************************************}
+
+    procedure tavrattreader.BuildOpCode(instr : tavrinstruction);
+      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;
+            oppostfix:=actoppostfix;
+          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 ((instr.opcode=A_MOV) and (operandnum=2)) or
+                  ((operandnum=3) and not(instr.opcode in [A_UMLAL,A_UMULL,A_SMLAL,A_SMULL,A_MLA])) then
+                  begin
+                    Consume(AS_COMMA);
+                    if not(TryBuildShifterOp(instr.Operands[operandnum+1] as tavroperand)) then
+                      Message(asmr_e_illegal_shifterop_syntax);
+                    Inc(operandnum);
+                  end
+                else
+                  begin
+                    if operandnum>Max_Operands then
+                      Message(asmr_e_too_many_operands)
+                    else
+                      Inc(operandnum);
+                    Consume(AS_COMMA);
+                  end;
+              end;
+            AS_SEPARATOR,
+            AS_END : { End of asm operands for this opcode  }
+              begin
+                break;
+              end;
+          else
+            BuildOperand(instr.Operands[operandnum] as tavroperand);
+          end; { end case }
+        until false;
+        instr.Ops:=operandnum;
+      end;
+
+
+    function tavrattreader.is_asmopcode(const s: string):boolean;
+
+      const
+        { sorted by length so longer postfixes will match first }
+        postfix2strsorted : array[1..19] of string[2] = (
+          'EP','SB','BT','SH',
+          'IA','IB','DA','DB','FD','FA','ED','EA',
+          'B','D','E','P','T','H','S');
+
+        postfixsorted : array[1..19] of TOpPostfix = (
+          PF_EP,PF_SB,PF_BT,PF_SH,
+          PF_IA,PF_IB,PF_DA,PF_DB,PF_FD,PF_FA,PF_ED,PF_EA,
+          PF_B,PF_D,PF_E,PF_P,PF_T,PF_H,PF_S);
+
+      var
+        len,
+        j,
+        sufidx : longint;
+        hs : string;
+        maxlen : longint;
+        icond : tasmcond;
+      Begin
+        { making s a value parameter would break other assembler readers }
+        hs:=s;
+        is_asmopcode:=false;
+
+        { clear op code }
+        actopcode:=A_None;
+
+        actcondition:=C_None;
+
+        { first, handle B else BLS is read wrong }
+        if ((hs[1]='B') and (length(hs)=3)) then
+          begin
+            for icond:=low(tasmcond) to high(tasmcond) do
+              begin
+                if copy(hs,2,3)=uppercond2str[icond] then
+                  begin
+                    actopcode:=A_B;
+                    actasmtoken:=AS_OPCODE;
+                    actcondition:=icond;
+                    is_asmopcode:=true;
+                    exit;
+                  end;
+              end;
+          end;
+        maxlen:=max(length(hs),5);
+        actopcode:=A_NONE;
+        for j:=maxlen downto 1 do
+          begin
+            actopcode:=tasmop(PtrInt(iasmops.Find(copy(hs,1,j))));
+            if actopcode<>A_NONE then
+              begin
+                actasmtoken:=AS_OPCODE;
+                { strip op code }
+                delete(hs,1,j);
+                break;
+              end;
+          end;
+        if actopcode=A_NONE then
+          exit;
+        { search for condition, conditions are always 2 chars }
+        if length(hs)>1 then
+          begin
+            for icond:=low(tasmcond) to high(tasmcond) do
+              begin
+                if copy(hs,1,2)=uppercond2str[icond] then
+                  begin
+                    actcondition:=icond;
+                    { strip condition }
+                    delete(hs,1,2);
+                    break;
+                  end;
+              end;
+          end;
+        { check for postfix }
+        if length(hs)>0 then
+          begin
+            for j:=low(postfixsorted) to high(postfixsorted) do
+              begin
+                if copy(hs,1,length(postfix2strsorted[j]))=postfix2strsorted[j] then
+                  begin
+                    actoppostfix:=postfixsorted[j];
+                    { strip postfix }
+                    delete(hs,1,length(postfix2strsorted[j]));
+                    break;
+                  end;
+              end;
+          end;
+        { if we stripped all postfixes, it's a valid opcode }
+        is_asmopcode:=length(hs)=0;
+      end;
+
+
+    procedure tavrattreader.ConvertCalljmp(instr : tavrinstruction);
+      var
+        newopr : toprrec;
+      begin
+        if instr.Operands[1].opr.typ=OPR_REFERENCE then
+          begin
+            newopr.typ:=OPR_SYMBOL;
+            newopr.symbol:=instr.Operands[1].opr.ref.symbol;
+            newopr.symofs:=instr.Operands[1].opr.ref.offset;
+            if (instr.Operands[1].opr.ref.base<>NR_NO) or
+              (instr.Operands[1].opr.ref.index<>NR_NO) then
+              Message(asmr_e_syn_operand);
+            instr.Operands[1].opr:=newopr;
+          end;
+      end;
+
+
+    procedure tavrattreader.handleopcode;
+      var
+        instr : tavrinstruction;
+      begin
+        instr:=tavrinstruction.Create(tavroperand);
+        BuildOpcode(instr);
+        if is_calljmp(instr.opcode) then
+          ConvertCalljmp(instr);
+        {
+        instr.AddReferenceSizes;
+        instr.SetInstructionOpsize;
+        instr.CheckOperandSizes;
+        }
+        instr.ConcatInstruction(curlist);
+        instr.Free;
+        actoppostfix:=PF_None;
+      end;
+
+
+{*****************************************************************************
+                                     Initialize
+*****************************************************************************}
+
+const
+  asmmode_avr_att_info : tasmmodeinfo =
+          (
+            id    : asmmode_avr_gas;
+            idtxt : 'GAS';
+            casmreader : tavrattreader;
+          );
+
+  asmmode_avr_standard_info : tasmmodeinfo =
+          (
+            id    : asmmode_standard;
+            idtxt : 'STANDARD';
+            casmreader : tavrattreader;
+          );
+
+initialization
+  RegisterAsmMode(asmmode_avr_att_info);
+  RegisterAsmMode(asmmode_avr_standard_info);
+end.

+ 3 - 0
compiler/cgutils.pas

@@ -51,6 +51,9 @@ unit cgutils;
          addressmode : taddressmode;
          shiftmode   : tshiftmode;
 {$endif arm}
+{$ifdef avr}
+         addressmode : taddressmode;
+{$endif avr}
 {$ifdef m68k}
          { indexed increment and decrement mode }
          { (An)+ and -(An)                      }

+ 2 - 1
compiler/psystem.pas

@@ -419,7 +419,8 @@ implementation
 {$ifdef cpu16bit}
         uinttype:=u16inttype;
         sinttype:=s16inttype;
-        ptrinttype:=u16inttype;
+        ptruinttype:=u16inttype;
+        ptrsinttype:=s16inttype;
 {$endif cpu16bit}
         set_current_module(oldcurrentmodule);
       end;