dlx/dlx-behaviour.vhdl

    1 --------------------------------------------------------------------------
    2 --
    3 --  Copyright (C) 1993, Peter J. Ashenden
    4 --  Mail:       Dept. Computer Science
    5 --              University of Adelaide, SA 5005, Australia
    6 --  e-mail:     petera@cs.adelaide.edu.au
    7 --
    8 --  This program is free software; you can redistribute it and/or modify
    9 --  it under the terms of the GNU General Public License as published by
   10 --  the Free Software Foundation; either version 1, or (at your option)
   11 --  any later version.
   12 --
   13 --  This program is distributed in the hope that it will be useful,
   14 --  but WITHOUT ANY WARRANTY; without even the implied warranty of
   15 --  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16 --  GNU General Public License for more details.
   17 --
   18 --  You should have received a copy of the GNU General Public License
   19 --  along with this program; if not, write to the Free Software
   20 --  Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
   21 --
   22 --------------------------------------------------------------------------
   23 --
   24 --  $RCSfile: dlx-behaviour.vhdl,v $  $Revision: 1.1 $  $Date: 2000/05/08 14:36:47 $
   25 --
   26 --------------------------------------------------------------------------
   27 --
   28 --  Behavioural architecture for DLX processor
   29 --
   30 
   31 
   32 use work.dlx_instr.all,
   33     work.bv_arithmetic.all,
   34     std.textio.all;
   35 
   36 
   37 architecture behaviour of dlx is
   38 
   39 begin -- behaviour
   40 
   41   interpreter: process
   42 
   43     type reg_array is array (reg_index) of dlx_word;
   44 
   45     variable reg : reg_array;
   46     variable fp_reg : reg_array;
   47 
   48     variable PC : dlx_word;
   49     variable user_mode : boolean;
   50     variable overflow, div_by_zero : boolean;
   51 
   52     constant PC_incr : dlx_word := X"0000_0004";
   53 
   54     variable IR : dlx_word;
   55     alias IR_opcode : dlx_opcode is IR(0 to 5);
   56     alias IR_sp_func : dlx_sp_func is IR(26 to 31);
   57     alias IR_fp_func : dlx_fp_func is IR(27 to 31);
   58     alias IR_rs1 : dlx_reg_addr is IR(6 to 10);
   59     alias IR_rs2 : dlx_reg_addr is IR(11 to 15);
   60     alias IR_Itype_rd : dlx_reg_addr is IR(11 to 15);
   61     alias IR_Rtype_rd : dlx_reg_addr is IR(16 to 20);
   62     alias IR_immed16 : dlx_immed16 is IR(16 to 31);
   63     alias IR_immed26 : dlx_immed26 is IR(6 to 31);
   64 
   65     variable IR_opcode_num : dlx_opcode_num;
   66     variable IR_sp_func_num : dlx_sp_func_num;
   67     variable IR_fp_func_num : dlx_fp_func_num;
   68     variable rs1, rs2, Itype_rd, Rtype_rd : reg_index;
   69     variable mem_addr : dlx_address;
   70     variable mem_data : dlx_word;
   71 
   72     subtype ls_2_addr_bits is bit_vector(1 downto 0);
   73 
   74     variable L : line;
   75 
   76 
   77     procedure write (address : in dlx_address;
   78                      data_width : in mem_width;
   79                      data : in dlx_word;
   80                      signal phi1, phi2 : in bit;    -- 2-phase non-overlapping clks
   81                      signal reset : in bit;         -- synchronous reset input
   82                      signal a : out dlx_address;    -- address bus output
   83                      signal d : inout dlx_word_bus; -- bidirectional data bus
   84                      signal width : out mem_width;  -- byte/halfword/word
   85                      signal write_enable : out bit; -- selects read/write cycle
   86                      signal mem_enable : out bit;   -- starts memory cycle
   87                      signal ifetch : out bit;       -- indicates instruction fetch
   88                      signal ready : in bit;         -- status from memory system
   89                      Tpd_clk_out : in time          -- clock to output delay
   90                     ) is
   91 
   92     begin
   93       wait until phi1 = '1';
   94       if reset = '1' then
   95         return;
   96       end if;
   97       a <= address after Tpd_clk_out;
   98       width <= data_width after Tpd_clk_out;
   99       d <= data after Tpd_clk_out;
  100       write_enable <= '1' after Tpd_clk_out;
  101       mem_enable <= '1' after Tpd_clk_out;
  102       ifetch <= '0' after Tpd_clk_out;
  103       loop
  104         wait until phi2 = '0';
  105         exit when ready = '1' or reset = '1';
  106       end loop;
  107       d <= null after Tpd_clk_out;
  108       write_enable <= '0' after Tpd_clk_out;
  109       mem_enable <= '0' after Tpd_clk_out;
  110     end write;
  111 
  112 
  113     procedure bus_read (address : in dlx_address;
  114                     data_width : in mem_width;
  115                     instr_fetch : in boolean;
  116                     data : out dlx_word;
  117                     signal phi1, phi2 : in bit;    -- 2-phase non-overlapping clks
  118                     signal reset : in bit;         -- synchronous reset input
  119                     signal a : out dlx_address;    -- address bus output
  120                     signal d : inout dlx_word_bus; -- bidirectional data bus
  121                     signal width : out mem_width;  -- byte/halfword/word
  122                     signal write_enable : out bit; -- selects read/write cycle
  123                     signal mem_enable : out bit;   -- starts memory cycle
  124                     signal ifetch : out bit;       -- indicates instruction eftch
  125                     signal ready : in bit;         -- status from memory system
  126                     Tpd_clk_out : in time          -- clock to output delay
  127                    ) is
  128 
  129     begin
  130       wait until phi1 = '1';
  131       if reset = '1' then
  132         return;
  133       end if;
  134       a <= address after Tpd_clk_out;
  135       width <= data_width after Tpd_clk_out;
  136       mem_enable <= '1' after Tpd_clk_out;
  137       ifetch <= bit'val(boolean'pos(instr_fetch)) after Tpd_clk_out;
  138       loop
  139         wait until phi2 = '0';
  140         exit when ready = '1' or reset = '1';
  141       end loop;
  142       data := d;
  143       mem_enable <= '0' after Tpd_clk_out;
  144     end bus_read;
  145 
  146 
  147   begin -- interpreter
  148     --
  149     -- reset the processor
  150     --
  151     d <= null;
  152     halt <= '0';
  153     write_enable <= '0';
  154     mem_enable <= '0';
  155     reg(0) := X"0000_0000";
  156     PC := X"0000_0000";
  157     user_mode := false;
  158     --
  159     -- fetch-decode-execute loop
  160     --
  161     loop
  162       --
  163       -- fetch next instruction
  164       --
  165       if debug then
  166         write(L, tag);
  167         write(L, string'(": fetching instruction..."));
  168         writeline(output, L);
  169       end if;
  170       --
  171       bus_read(PC, width_word, true, IR,
  172          phi1, phi2, reset, a, d, width, write_enable, mem_enable, ifetch, ready,
  173          Tpd_clk_out);
  174       exit when reset = '1';
  175       --
  176       -- increment the PC to point to the following instruction
  177       --
  178       if debug then
  179         write(L, tag);
  180         write(L, string'(": incrementing PC..."));
  181         writeline(output, L);
  182       end if;
  183       --
  184       bv_add(PC, PC_incr, PC, overflow);
  185       --
  186       -- decode the instruction
  187       --
  188       if debug then
  189         write(L, tag);
  190         write(L, string'(": decoding instruction..."));
  191         writeline(output, L);
  192       end if;
  193       --
  194       IR_opcode_num := bv_to_natural(IR_opcode);
  195       IR_sp_func_num := bv_to_natural(IR_sp_func);
  196       IR_fp_func_num := bv_to_natural(IR_fp_func);
  197       rs1 := bv_to_natural(IR_rs1);
  198       rs2 := bv_to_natural(IR_rs2);
  199       Itype_rd := bv_to_natural(IR_Itype_rd);
  200       Rtype_rd := bv_to_natural(IR_Rtype_rd);
  201       --
  202       -- exectute
  203       --
  204       if debug then
  205         write(L, tag);
  206         write(L, string'(": executing instruction..."));
  207         writeline(output, L);
  208       end if;
  209       --
  210       case IR_opcode is
  211         when op_special =>
  212           case IR_sp_func is
  213             WHEN sp_func_nop =>
  214               null;
  215             when sp_func_sll =>
  216               reg(Rtype_rd) := bv_sll(reg(rs1), bv_to_natural(reg(rs2)(27 to 31)));
  217             when sp_func_srl =>
  218               reg(Rtype_rd) := bv_srl(reg(rs1), bv_to_natural(reg(rs2)(27 to 31)));
  219             when sp_func_sra =>
  220               reg(Rtype_rd) := bv_sra(reg(rs1), bv_to_natural(reg(rs2)(27 to 31)));
  221             when sp_func_sequ =>
  222               if reg(rs1) = reg(rs2) then
  223                 reg(Rtype_rd) := X"0000_0001";
  224               else
  225                 reg(Rtype_rd) := X"0000_0000";
  226               end if;
  227             when sp_func_sneu =>
  228               if reg(rs1) /= reg(rs2) then
  229                 reg(Rtype_rd) := X"0000_0001";
  230               else
  231                 reg(Rtype_rd) := X"0000_0000";
  232               end if;
  233             when sp_func_sltu =>
  234               if reg(rs1) < reg(rs2) then
  235                 reg(Rtype_rd) := X"0000_0001";
  236               else
  237                 reg(Rtype_rd) := X"0000_0000";
  238               end if;
  239             when sp_func_sgtu =>
  240               if reg(rs1) > reg(rs2) then
  241                 reg(Rtype_rd) := X"0000_0001";
  242               else
  243                 reg(Rtype_rd) := X"0000_0000";
  244               end if;
  245             when sp_func_sleu =>
  246               if reg(rs1) <= reg(rs2) then
  247                 reg(Rtype_rd) := X"0000_0001";
  248               else
  249                 reg(Rtype_rd) := X"0000_0000";
  250               end if;
  251             when sp_func_sgeu =>
  252               if reg(rs1) >= reg(rs2) then
  253                 reg(Rtype_rd) := X"0000_0001";
  254               else
  255                 reg(Rtype_rd) := X"0000_0000";
  256               end if;
  257             when sp_func_add =>
  258               bv_add(reg(rs1), reg(rs2), reg(Rtype_rd), overflow);
  259             when sp_func_addu =>
  260               bv_addu(reg(rs1), reg(rs2), reg(Rtype_rd), overflow);
  261             when sp_func_sub =>
  262               bv_sub(reg(rs1), reg(rs2), reg(Rtype_rd), overflow);
  263             when sp_func_subu =>
  264               bv_subu(reg(rs1), reg(rs2), reg(Rtype_rd), overflow);
  265             when sp_func_and =>
  266               reg(Rtype_rd) := reg(rs1) and reg(rs2);
  267             when sp_func_or =>
  268               reg(Rtype_rd) := reg(rs1) or reg(rs2);
  269             when sp_func_xor =>
  270               reg(Rtype_rd) := reg(rs1) xor reg(rs2);
  271             when sp_func_seq =>
  272               if reg(rs1) = reg(rs2) then
  273                 reg(Rtype_rd) := X"0000_0001";
  274               else
  275                 reg(Rtype_rd) := X"0000_0000";
  276               end if;
  277             when sp_func_sne =>
  278               if reg(rs1) /= reg(rs2) then
  279                 reg(Rtype_rd) := X"0000_0001";
  280               else
  281                 reg(Rtype_rd) := X"0000_0000";
  282               end if;
  283             when sp_func_slt =>
  284                if bv_lt(reg(rs1), reg(rs2)) then
  285                 reg(Rtype_rd) := X"0000_0001";
  286               else
  287                 reg(Rtype_rd) := X"0000_0000";
  288               end if;
  289             when sp_func_sgt =>
  290               if bv_gt(reg(rs1), reg(rs2)) then
  291                 reg(Rtype_rd) := X"0000_0001";
  292               else
  293                 reg(Rtype_rd) := X"0000_0000";
  294               end if;
  295             when sp_func_sle =>
  296               if bv_le(reg(rs1), reg(rs2)) then
  297                 reg(Rtype_rd) := X"0000_0001";
  298               else
  299                 reg(Rtype_rd) := X"0000_0000";
  300               end if;
  301             when sp_func_sge =>
  302               if bv_ge(reg(rs1), reg(rs2)) then
  303                 reg(Rtype_rd) := X"0000_0001";
  304               else
  305                 reg(Rtype_rd) := X"0000_0000";
  306               end if;
  307             when sp_func_movi2s =>
  308               assert false
  309                 report "MOVI2S instruction not implemented" severity warning;
  310             when sp_func_movs2i =>
  311               assert false
  312                 report "MOVS2I instruction not implemented" severity warning;
  313             when sp_func_movf =>
  314               assert false
  315                 report "MOVF instruction not implemented" severity warning;
  316             when sp_func_movd =>
  317               assert false
  318                 report "MOVD instruction not implemented" severity warning;
  319             when sp_func_movfp2i =>
  320               reg(Rtype_rd) := fp_reg(rs1);
  321             when sp_func_movi2fp =>
  322               fp_reg(Rtype_rd) := reg(rs1);
  323             when others =>
  324               assert false
  325                 report "undefined special instruction function" severity error;
  326           end case;
  327         when op_fparith =>
  328           case IR_fp_func is
  329             when fp_func_mult =>
  330               bv_mult(fp_reg(rs1), fp_reg(rs2), fp_reg(Rtype_rd), overflow);
  331             when fp_func_multu =>
  332               bv_multu(fp_reg(rs1), fp_reg(rs2), fp_reg(Rtype_rd), overflow);
  333             when fp_func_div =>
  334               bv_div(fp_reg(rs1), fp_reg(rs2), fp_reg(Rtype_rd), div_by_zero, overflow);
  335             when fp_func_divu =>
  336               bv_divu(fp_reg(rs1), fp_reg(rs2), fp_reg(Rtype_rd), div_by_zero);
  337             when fp_func_addf | fp_func_subf | fp_func_multf | fp_func_divf |
  338               fp_func_addd | fp_func_subd | fp_func_multd | fp_func_divd |
  339               fp_func_cvtf2d | fp_func_cvtf2i | fp_func_cvtd2f |
  340               fp_func_cvtd2i | fp_func_cvti2f | fp_func_cvti2d |
  341               fp_func_eqf | fp_func_nef | fp_func_ltf | fp_func_gtf |
  342               fp_func_lef | fp_func_gef | fp_func_eqd | fp_func_ned |
  343               fp_func_ltd | fp_func_gtd | fp_func_led | fp_func_ged =>
  344               assert false
  345                 report "floating point instructions not implemented" severity warning;
  346             when others =>
  347               assert false
  348                 report "undefined floating point instruction function" severity error;
  349           end case;
  350         when op_j  =>
  351           bv_add(PC, bv_sext(IR_immed26, 32), PC, overflow);
  352         when op_jal =>
  353           reg(link_reg) := PC;
  354           bv_add(PC, bv_sext(IR_immed26, 32), PC, overflow);
  355         when op_beqz =>
  356           if reg(rs1) = X"0000_0000" then
  357             bv_add(PC, bv_sext(IR_immed16, 32), PC, overflow);
  358           end if;
  359         when op_bnez =>
  360           if reg(rs1) /= X"0000_0000" then
  361             bv_add(PC, bv_sext(IR_immed16, 32), PC, overflow);
  362           end if;
  363         when op_bfpt =>
  364           assert false
  365             report "BFPT instruction not implemented" severity warning;
  366         when op_bfpf =>
  367           assert false
  368             report "BFPF instruction not implemented" severity warning;
  369         when op_addi =>
  370           bv_add(reg(rs1), bv_sext(IR_immed16, 32), reg(Itype_rd), overflow);
  371         when op_addui =>
  372           bv_addu(reg(rs1), bv_zext(IR_immed16, 32), reg(Itype_rd), overflow);
  373         when op_subi =>
  374           bv_sub(reg(rs1), bv_sext(IR_immed16, 32), reg(Itype_rd), overflow);
  375         when op_subui =>
  376           bv_subu(reg(rs1), bv_zext(IR_immed16, 32), reg(Itype_rd), overflow);
  377         when op_slli =>
  378           reg(Itype_rd) := bv_sll(reg(rs1), bv_to_natural(IR_immed16(11 to 15)));
  379         when op_srli =>
  380           reg(Itype_rd) := bv_srl(reg(rs1), bv_to_natural(IR_immed16(11 to 15)));
  381         when op_srai =>
  382           reg(Itype_rd) := bv_sra(reg(rs1), bv_to_natural(IR_immed16(11 to 15)));
  383         when op_andi =>
  384           reg(Itype_rd) := reg(rs1) and bv_zext(IR_immed16, 32);
  385         when op_ori =>
  386           reg(Itype_rd) := reg(rs1) or bv_zext(IR_immed16, 32);
  387         when op_xori =>
  388           reg(Itype_rd) := reg(rs1) xor bv_zext(IR_immed16, 32);
  389         when op_lhi =>
  390           reg(Itype_rd) := IR_immed16 & X"0000";
  391         when op_rfe =>
  392           assert false
  393             report "RFE instruction not implemented" severity warning;
  394         when op_trap =>
  395           assert false
  396             report "TRAP instruction encountered, execution halted"
  397             severity note;
  398           halt <= '1' after Tpd_clk_out;
  399           wait until reset = '1';
  400           exit;
  401         when op_jr =>
  402           PC := reg(rs1);
  403         when op_jalr =>
  404           reg(link_reg) := PC;
  405           PC := reg(rs1);
  406         when op_seqi =>
  407           if reg(rs1) = bv_sext(IR_immed16, 32) then
  408             reg(Itype_rd) := X"0000_0001";
  409           else
  410             reg(Itype_rd) := X"0000_0000";
  411           end if;
  412         when op_snei =>
  413           if reg(rs1) /= bv_sext(IR_immed16, 32) then
  414             reg(Itype_rd) := X"0000_0001";
  415           else
  416             reg(Itype_rd) := X"0000_0000";
  417           end if;
  418         when op_slti =>
  419           if bv_lt(reg(rs1), bv_sext(IR_immed16, 32)) then
  420             reg(Itype_rd) := X"0000_0001";
  421           else
  422             reg(Itype_rd) := X"0000_0000";
  423           end if;
  424         when op_sgti =>
  425           if bv_gt(reg(rs1), bv_sext(IR_immed16, 32)) then
  426             reg(Itype_rd) := X"0000_0001";
  427           else
  428             reg(Itype_rd) := X"0000_0000";
  429           end if;
  430         when op_slei =>
  431           if bv_le(reg(rs1), bv_sext(IR_immed16, 32)) then
  432             reg(Itype_rd) := X"0000_0001";
  433           else
  434             reg(Itype_rd) := X"0000_0000";
  435           end if;
  436         when op_sgei =>
  437           if bv_ge(reg(rs1), bv_sext(IR_immed16, 32)) then
  438             reg(Itype_rd) := X"0000_0001";
  439           else
  440             reg(Itype_rd) := X"0000_0000";
  441           end if;
  442         when op_lb =>
  443           bv_add(reg(rs1), bv_sext(IR_immed16, 32), mem_addr, overflow);
  444           bus_read(mem_addr, width_byte, false, mem_data,
  445             phi1, phi2, reset, a, d, width, write_enable, mem_enable, ifetch, ready,
  446             Tpd_clk_out);
  447           exit when reset = '1';
  448           case ls_2_addr_bits'(mem_addr(1 downto 0)) is
  449             when B"00" =>
  450               reg(Itype_rd) := bv_sext(mem_data(0 to 7), 32);
  451             when B"01" =>
  452               reg(Itype_rd) := bv_sext(mem_data(8 to 15), 32);
  453             when B"10" =>
  454               reg(Itype_rd) := bv_sext(mem_data(16 to 23), 32);
  455             when B"11" =>
  456               reg(Itype_rd) := bv_sext(mem_data(24 to 31), 32);
  457           end case;
  458         when op_lh =>
  459           bv_add(reg(rs1), bv_sext(IR_immed16, 32), mem_addr, overflow);
  460           bus_read(mem_addr, width_halfword, false, mem_data,
  461             phi1, phi2, reset, a, d, width, write_enable, mem_enable, ifetch, ready,
  462             Tpd_clk_out);
  463           exit when reset = '1';
  464           if mem_addr(1) = '0' then
  465             reg(Itype_rd) := bv_sext(mem_data(0 to 15), 32);
  466           else
  467             reg(Itype_rd) := bv_sext(mem_data(16 to 31), 32);
  468           end if;
  469         when op_lw =>
  470           bv_add(reg(rs1), bv_sext(IR_immed16, 32), mem_addr, overflow);
  471           bus_read(mem_addr, width_word, false, mem_data,
  472             phi1, phi2, reset, a, d, width, write_enable, mem_enable, ifetch, ready,
  473             Tpd_clk_out);
  474           exit when reset = '1';
  475           reg(Itype_rd) := mem_data;
  476         when op_lbu =>
  477           bv_add(reg(rs1), bv_sext(IR_immed16, 32), mem_addr, overflow);
  478           bus_read(mem_addr, width_byte, false, mem_data,
  479             phi1, phi2, reset, a, d, width, write_enable, mem_enable, ifetch, ready,
  480             Tpd_clk_out);
  481           exit when reset = '1';
  482           case ls_2_addr_bits'(mem_addr(1 downto 0)) is
  483             when B"00" =>
  484               reg(Itype_rd) := bv_zext(mem_data(0 to 7), 32);
  485             when B"01" =>
  486               reg(Itype_rd) := bv_zext(mem_data(8 to 15), 32);
  487             when B"10" =>
  488               reg(Itype_rd) := bv_zext(mem_data(16 to 23), 32);
  489             when B"11" =>
  490               reg(Itype_rd) := bv_zext(mem_data(24 to 31), 32);
  491           end case;
  492         when op_lhu =>
  493           bv_add(reg(rs1), bv_sext(IR_immed16, 32), mem_addr, overflow);
  494           bus_read(mem_addr, width_halfword, false, mem_data,
  495             phi1, phi2, reset, a, d, width, write_enable, mem_enable, ifetch, ready,
  496             Tpd_clk_out);
  497           exit when reset = '1';
  498           if mem_addr(1) = '0' then
  499             reg(Itype_rd) := bv_zext(mem_data(0 to 15), 32);
  500           else
  501             reg(Itype_rd) := bv_zext(mem_data(16 to 31), 32);
  502           end if;
  503         when op_lf =>
  504           assert false
  505             report "LF instruction not implemented" severity warning;
  506         when op_ld =>
  507           assert false
  508             report "LD instruction not implemented" severity warning;
  509         when op_sb =>
  510           bv_add(reg(rs1), bv_sext(IR_immed16, 32), mem_addr, overflow);
  511           mem_data := X"0000_0000";
  512           case ls_2_addr_bits'(mem_addr(1 downto 0)) is
  513             when B"00" =>
  514               mem_data(0 to 7) := reg(Itype_rd)(0 to 7);
  515             when B"01" =>
  516               mem_data(8 to 15) := reg(Itype_rd)(0 to 7);
  517             when B"10" =>
  518               mem_data(16 to 23) := reg(Itype_rd)(0 to 7);
  519             when B"11" =>
  520               mem_data(24 to 31) := reg(Itype_rd)(0 to 7);
  521           end case;
  522           write(mem_addr, width_halfword, mem_data,
  523             phi1, phi2, reset, a, d, width, write_enable, mem_enable, ifetch, ready,
  524             Tpd_clk_out);
  525           exit when reset = '1';
  526         when op_sh =>
  527           bv_add(reg(rs1), bv_sext(IR_immed16, 32), mem_addr, overflow);
  528           mem_data := X"0000_0000";
  529           if mem_addr(1) = '0' then
  530             mem_data(0 to 15) := reg(Itype_rd)(0 to 15);
  531           else
  532             mem_data(16 to 31) := reg(Itype_rd)(0 to 15);
  533           end if;
  534           write(mem_addr, width_halfword, mem_data,
  535             phi1, phi2, reset, a, d, width, write_enable, mem_enable, ifetch, ready,
  536             Tpd_clk_out);
  537           exit when reset = '1';
  538         when op_sw =>
  539           bv_add(reg(rs1), bv_sext(IR_immed16, 32), mem_addr, overflow);
  540           mem_data := reg(Itype_rd);
  541           write(mem_addr, width_word, mem_data,
  542             phi1, phi2, reset, a, d, width, write_enable, mem_enable, ifetch, ready,
  543             Tpd_clk_out);
  544           exit when reset = '1';
  545         when op_sf =>
  546           assert false
  547             report "SF instruction not implemented" severity warning;
  548         when op_sd =>
  549           assert false
  550             report "SD instruction not implemented" severity warning;
  551         when op_sequi =>
  552           if reg(rs1) = bv_zext(IR_immed16, 32) then
  553             reg(Itype_rd) := X"0000_0001";
  554           else
  555             reg(Itype_rd) := X"0000_0000";
  556           end if;
  557         when op_sneui =>
  558           if reg(rs1) /= bv_zext(IR_immed16, 32) then
  559             reg(Itype_rd) := X"0000_0001";
  560           else
  561             reg(Itype_rd) := X"0000_0000";
  562           end if;
  563         when op_sltui =>
  564           if reg(rs1) < bv_zext(IR_immed16, 32) then
  565             reg(Itype_rd) := X"0000_0001";
  566           else
  567             reg(Itype_rd) := X"0000_0000";
  568           end if;
  569         when op_sgtui =>
  570           if reg(rs1) > bv_zext(IR_immed16, 32) then
  571             reg(Itype_rd) := X"0000_0001";
  572           else
  573             reg(Itype_rd) := X"0000_0000";
  574           end if;
  575         when op_sleui =>
  576           if reg(rs1) <= bv_zext(IR_immed16, 32) then
  577             reg(Itype_rd) := X"0000_0001";
  578           else
  579             reg(Itype_rd) := X"0000_0000";
  580           end if;
  581         when op_sgeui =>
  582           if reg(rs1) >= bv_zext(IR_immed16, 32) then
  583             reg(Itype_rd) := X"0000_0001";
  584           else
  585             reg(Itype_rd) := X"0000_0000";
  586           end if;
  587         when others =>
  588           assert false
  589             report "undefined instruction" severity error;
  590       end case;
  591       --
  592       -- fix up R0 in case it was overwritten
  593       --
  594       reg(0) := X"0000_0000";
  595       --
  596       if debug then
  597         write(L, tag);
  598         write(L, string'(": end of execution"));
  599         writeline(output, L);
  600       end if;
  601       --
  602     end loop;
  603     --
  604     -- loop is only exited when reset active: wait until it goes inactive
  605     --
  606     assert reset = '1'
  607       report "reset code reached with reset = '0'" severity error;
  608     wait until phi2 = '0' and reset = '0';
  609     --
  610     -- process interpreter now starts again from beginning
  611     --
  612   end process interpreter;
  613 
  614 end behaviour;
  615 

This page was generated using GHDL 0.14 (20040829) [Sokcho edition], a program written by Tristan Gingold