OpenCores
URL https://opencores.org/ocsvn/open8_urisc/open8_urisc/trunk

Subversion Repositories open8_urisc

[/] [open8_urisc/] [trunk/] [VHDL/] [o8_cpu.vhd] - Blame information for rev 256

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 185 jshamlet
-- Copyright (c)2006, 2011, 2012, 2013, 2015, 2019, 2020 Jeremy Seth Henry
2 169 jshamlet
-- All rights reserved.
3
--
4
-- Redistribution and use in source and binary forms, with or without
5
-- modification, are permitted provided that the following conditions are met:
6
--     * Redistributions of source code must retain the above copyright
7
--       notice, this list of conditions and the following disclaimer.
8
--     * Redistributions in binary form must reproduce the above copyright
9
--       notice, this list of conditions and the following disclaimer in the
10
--       documentation and/or other materials provided with the distribution,
11
--       where applicable (as part of a user interface, debugging port, etc.)
12
--
13
-- THIS SOFTWARE IS PROVIDED BY JEREMY SETH HENRY ``AS IS'' AND ANY
14
-- EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
15
-- WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
16
-- DISCLAIMED. IN NO EVENT SHALL JEREMY SETH HENRY BE LIABLE FOR ANY
17
-- DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
18
-- (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
19
-- LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND
20
-- ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
21 194 jshamlet
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
22
-- THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
23 169 jshamlet
--
24 181 jshamlet
-- VHDL Units :  o8_cpu
25 169 jshamlet
-- Description:  VHDL model of a RISC 8-bit processor core loosely based on the
26
--            :   V8/ARC uRISC instruction set. Requires Open8_pkg.vhd
27
--            :
28
-- Notes      :  Generic definitions
29
--            :
30
--            :  Program_Start_Addr sets the initial value of the program
31
--            :   counter.
32
--            :
33
--            :  ISR_Start_Addr sets the location of the interrupt service
34
--            :   vector table. There are 8 service vectors, or 16 bytes, which
35
--            :   must be allocated to either ROM or RAM.
36
--            :
37
--            :  Stack_Start_Address sets the initial (reset) value of the
38
--            :   stack pointer. Also used for the RSP instruction if
39
--            :   Allow_Stack_Address_Move is false.
40
--            :
41
--            :  Allow_Stack_Address_Move, when set true, allows the RSP to be
42 181 jshamlet
--            :   programmed via thet RSP instruction. If enabled, the
43
--            :   instruction changes into TSX or TXS based on the flag
44
--            :   specified by Stack_Xfer_Flag. If the flag is '0', RSP will
45
--            :   copy the current stack pointer to R1:R0 (TSX). If the flag
46
--            :   is '1', RSP will copy R1:R0 to the stack pointer (TXS). This
47
--            :   allows the processor to backup and restore stack pointers
48
--            :   in a multi-process environment. Note that no flags are
49
--            :   modified by either form of this instruction.
50 169 jshamlet
--            :
51 181 jshamlet
--            :  Stack_Xfer_Flag instructs the core to use the specified ALU
52
--            :   flag to alter the behavior of the RSP instruction when
53 256 jshamlet
--            :   Allow_Stack_Address_Move is set TRUE, otherwise it's ignored.
54 181 jshamlet
--            :   While technically any of the status bits may be used, the
55
--            :   intent was to use FL_GP[1,2,3,4], as these are not modified
56
--            :   by ordinary ALU operations.
57
--            :
58 169 jshamlet
--            :  The Enable_Auto_Increment generic can be used to modify the
59
--            :   indexed instructions such that specifying an odd register
60
--            :   will use the next lower register pair, post-incrementing the
61
--            :   value in that pair. IOW, specifying STX R1 will instead
62
--            :   result in STX R0++, or R0 = {R1:R0}; {R1:R0} + 1
63
--            :
64
--            :  BRK_Implements_WAI modifies the BRK instruction such that it
65
--            :   triggers the wait for interrupt state, but without triggering
66
--            :   a soft interrupt in lieu of its normal behavior, which is to
67
--            :   insert several dead clock cycles - essentially a long NOP
68
--            :
69
--            :  Enable_NMI overrides the mask bit for interrupt 0, creating a
70
--            :   non-maskable interrupt at the highest priority. To remain
71
--            :   true to the original core, this should be set false.
72
--            :
73 188 jshamlet
--            :  RTI_Ignores_GP_Flags alters the set of flag bits restored
74
--            :   after an interrupt. By default, all of the flag bits are put
75
--            :   back to their original state. If this flag is set true, only
76
--            :   the lower four bits are restored, allowing ISR code to alter
77
--            :   the GP flags persistently.
78
--            :
79 244 jshamlet
--            :  Supervisor_Mode, when set, disables the STP PSR_I instruction
80
--            :   preventing code from setting the I bit. When enabled, only
81
--            :   interrupts can set the I bit, allowing for more robust memory
82
--            :   protection by preventing errant code execution from
83
--            :   inadvertently entering an interrupt state.
84
--            :
85 248 jshamlet
--            :   This setting also sets I bit at startup so that any
86
--            :   initialization code may be run in an ISR context, initially
87
--            :   bypassing memory protection. Init code should clear the I bit
88
--            :   when done;
89 244 jshamlet
--            :
90 255 jshamlet
--            :  Unsigned_Index_Offsets alters the way offsets are added to
91
--            :   [Rn+1:Rn] during LDO/STO instructions. The original, defeault
92
--            :   behavior treats these offsets as signed values, allowing
93
--            :   instructions to offset by -128 to +127 from [Rn+1:Rn].
94
--            :   Setting this generic to TRUE will switch to unsigned offsets,
95
--            :   switching the range to 0 to 255 instead.
96
--            :
97 169 jshamlet
--            :  Default_Interrupt_Mask sets the intial/reset value of the
98
--            :   interrupt mask. To remain true to the original core, which
99
--            :   had no interrupt mask, this should be set to x"FF". Otherwise
100
--            :   it can be initialized to any value. Note that Enable_NMI
101
--            :   will logically force the LSB high.
102 172 jshamlet
--            :
103 169 jshamlet
--            :  Reset_Level determines whether the processor registers reset
104
--            :   on a high or low level from higher logic.
105
--            :
106
--            : Architecture notes
107
--            :  This model deviates from the original ISA in a few important
108
--            :   ways.
109
--            :
110
--            :  First, there is only one set of registers. Interrupt service
111
--            :   routines must explicitely preserve context since the the
112
--            :   hardware doesn't. This was done to decrease size and code
113
--            :   complexity. Older code that assumes this behavior will not
114
--            :   execute correctly on this processor model.
115
--            :
116
--            :  Second, this model adds an additional pipeline stage between
117
--            :   the instruction decoder and the ALU. Unfortunately, this
118
--            :   means that the instruction stream has to be restarted after
119
--            :   any math instruction is executed, implying that any ALU
120
--            :   instruction now has a latency of 2 instead of 0. The
121
--            :   advantage is that the maximum frequency has gone up
122
--            :   significantly, as the ALU code is vastly more efficient.
123
--            :   As an aside, this now means that all math instructions,
124
--            :   including MUL (see below) and UPP have the same instruction
125
--            :   latency.
126
--            :
127
--            :  Third, the original ISA, also a soft core, had two reserved
128
--            :   instructions, USR and USR2. These have been implemented as
129
--            :   DBNZ, and MUL respectively.
130
--            :
131
--            :  DBNZ decrements the specified register and branches if the
132
--            :   result is non-zero. The instruction effectively executes a
133
--            :   DEC Rn instruction prior to branching, so the same flags will
134
--            :   be set.
135
--            :
136
--            :  MUL places the result of R0 * Rn into R1:R0. Instruction
137
--            :   latency is identical to other ALU instructions. Only the Z
138
--            :   flag is set, since there is no defined overflow or "negative
139
--            :   16-bit values"
140
--            :
141
--            :  Fourth, indexed load/store instructions now have an (optional)
142
--            :   ability to post-increment their index registers. If enabled,
143
--            :   using an odd operand for LDO,LDX, STO, STX will cause the
144
--            :   register pair to be incremented after the storage access.
145
--            :
146
--            :  Fifth, the RSP instruction has been (optionally) altered to
147
--            :   allow the stack pointer to be sourced from R1:R0.
148
--            :
149
--            :  Sixth, the BRK instruction can optionally implement a WAI,
150
--            :   which is the same as the INT instruction without the soft
151
--            :   interrupt, as a way to put the processor to "sleep" until the
152
--            :   next external interrupt.
153
--            :
154
--            :  Seventh, the original CPU model had 8 non-maskable interrupts
155
--            :   with priority. This model has the same 8 interrupts, but
156 172 jshamlet
--            :   allows software to mask them (with an additional option to
157 169 jshamlet
--            :   override the highest priority interrupt, making it the NMI.)
158
--            :
159
--            :  Lastly, previous unmapped instructions in the OP_STK opcode
160
--            :   were repurposed to support a new interrupt mask.
161
--            :   SMSK and GMSK transfer the contents of R0 (accumulator)
162
--            :   to/from the interrupt mask register. SMSK is immediate, while
163
--            :   GMSK has the same overhead as a math instruction.
164
--
165
-- Revision History
166
-- Author          Date     Change
167
------------------ -------- ---------------------------------------------------
168
-- Seth Henry      07/19/06 Design Start
169
-- Seth Henry      01/18/11 Fixed BTT instruction to match V8
170
-- Seth Henry      07/22/11 Fixed interrupt transition logic to avoid data
171
--                           corruption issues.
172
-- Seth Henry      07/26/11 Optimized logic in ALU, stack pointer, and data
173
--                           path sections.
174
-- Seth Henry      07/27/11 Optimized logic for timing, merged blocks into
175
--                           single entity.
176
-- Seth Henry      09/20/11 Added BRK_Implements_WAI option, allowing the
177
--                           processor to wait for an interrupt instead of the
178
--                           normal BRK behavior.
179 187 jshamlet
-- Seth Henry      12/20/11 Modified core to allow WAI_Cx state to idle
180 169 jshamlet
--                           the bus entirely (Rd_Enable is low)
181
-- Seth Henry      02/03/12 Replaced complex interrupt controller with simpler,
182
--                           faster logic that simply does priority encoding.
183
-- Seth Henry      08/06/13 Removed HALT functionality
184
-- Seth Henry      10/29/15 Fixed inverted carry logic in CMP and SBC instrs
185 182 jshamlet
-- Seth Henry      12/19/19 Renamed to o8_cpu to fit "theme"
186 181 jshamlet
-- Seth Henry      03/09/20 Modified RSP instruction to work with a CPU flag
187
--                           allowing true backup/restore of the stack pointer
188 182 jshamlet
-- Seth Henry      03/11/20 Split the address logic from the main state machine
189
--                           in order to simplify things and eliminate
190
--                           redundancies. Came across and fixed a problem with
191
--                           the STO instruction when Enable_Auto_Increment is
192
--                           NOT set.
193 185 jshamlet
-- Seth Henry      03/12/20 Rationalized the naming of the CPU flags to match
194
--                           the assembler names. Also fixed an issue where
195
--                           the I bit wasn't being cleared after interrupts.
196
--                          Simplified the program counter logic to only use
197
--                           the offset for increments, redefining the
198
--                           original modes as fixed offset values.
199
--                          Modified the ALU section with a new ALU operation
200
--                           for GMSK. This allowed the .data field to be
201
--                           removed and Operand1 used in its place, which
202
--                           simplified the logic a great deal.
203 187 jshamlet
-- Seth Henry      03/16/20 Added CPU_Halt input back, only now as an input to
204
--                           the instruction decode state, where it acts as a
205
--                           modified form of the BRK instruction that holds
206
--                           state until CPU_Halt is deasserted. This has a
207
--                           much smaller impact on Fmax/complexity than the
208
--                           original clock enable, but imposes a mild impact
209
--                           due to the need to reset the instruction pipeline
210 188 jshamlet
-- Seth Henry      03/17/20 Added generic to control whether RTI full restores
211
--                           the flags, including the general purpose ones, or
212
--                           only the core ALU flags (Z, N, and C). Also
213
--                           brought out copies of the GP flags for external
214
--                           connection.
215 210 jshamlet
-- Seth Henry      04/09/20 Added a compile time setting to block interrupts
216
--                           while the I bit is set to avoid reentering ISRs
217
--                           This may slightly affect timing, as this will
218
--                           potentially block higher priority interrupts
219
--                           until the lower priority ISR returns or clears
220
--                           the I bit.
221
--                          Also added the I bit to the exported flags for
222
--                           use in memory protection schemes.
223 224 jshamlet
-- Seth Henry      04/16/20 Modified to use new Open8 bus record. Also added
224 225 jshamlet
--                           reset and usec_tick logic to drive utility
225
--                           signals. Also added Halt_Ack output.
226 244 jshamlet
-- Seth Henry      05/20/20 Added two new generics to alter the way the I bit
227
--                           is handled. The Supervisor_Mode setting disables
228
--                           STP PSR_I from being executed, preventing it
229
--                           from being set outside of an ISR. The
230
--                           Default_Int_Flag setting allows the I bit to
231
--                           start set so that initialization code can run,
232
--                           but not be hijacked later to corrupt any memory
233
--                           write protection later.
234 245 jshamlet
-- Seth Henry      05/21/20 Supervisor_Mode now protects the interrupt mask
235
--                           and stack pointer as well.
236 248 jshamlet
-- Seth Henry      05/24/20 Removed the Default_Int_Flag, as it is covered by
237
--                           Supervisor_Mode. If Supervisor_Mode isn't set,
238
--                           code can simply use STP to set the bit
239 252 jshamlet
-- Seth Henry      06/09/20 Added ability to use unsigned index offsets for
240 253 jshamlet
--                           LDO/STO. Also pipelined the address calculation
241 252 jshamlet
--                           for indexed instructions, reducing the final
242
--                           address generator to a multiplexor fed only by
243
--                           registers.
244 169 jshamlet
 
245
library ieee;
246
  use ieee.std_logic_1164.all;
247
  use ieee.std_logic_unsigned.all;
248
  use ieee.std_logic_arith.all;
249
  use ieee.std_logic_misc.all;
250
 
251
library work;
252 227 jshamlet
  use work.Open8_pkg.all;
253 169 jshamlet
 
254 183 jshamlet
entity o8_cpu is
255 169 jshamlet
  generic(
256
    Program_Start_Addr       : ADDRESS_TYPE := x"0000"; -- Initial PC location
257
    ISR_Start_Addr           : ADDRESS_TYPE := x"FFF0"; -- Bottom of ISR vec's
258
    Stack_Start_Addr         : ADDRESS_TYPE := x"03FF"; -- Top of Stack
259
    Allow_Stack_Address_Move : boolean      := false;   -- Use Normal v8 RSP
260 188 jshamlet
    Stack_Xfer_Flag          : integer      := PSR_GP4; -- GP4 modifies RSP
261 169 jshamlet
    Enable_Auto_Increment    : boolean      := false;   -- Modify indexed instr
262
    BRK_Implements_WAI       : boolean      := false;   -- BRK -> Wait for Int
263
    Enable_NMI               : boolean      := true;    -- Force INTR0 enabled
264 210 jshamlet
    Sequential_Interrupts    : boolean      := false;   -- Interruptable ISRs
265 224 jshamlet
    RTI_Ignores_GP_Flags     : boolean      := false;   -- RTI sets all flags
266 244 jshamlet
    Supervisor_Mode          : boolean      := false;   -- I bit is restricted
267 252 jshamlet
    Unsigned_Index_Offsets   : boolean      := false;   -- Offsets are signed
268 169 jshamlet
    Default_Interrupt_Mask   : DATA_TYPE    := x"FF";   -- Enable all Ints
269 224 jshamlet
    Clock_Frequency          : real                     -- Clock Frequency
270
);
271 169 jshamlet
  port(
272
    Clock                    : in  std_logic;
273 224 jshamlet
    PLL_Locked               : in  std_logic;
274 169 jshamlet
    --
275 225 jshamlet
    Halt_Req                 : in  std_logic := '0';
276
    Halt_Ack                 : out std_logic;
277
    --
278 223 jshamlet
    Open8_Bus                : out OPEN8_BUS_TYPE;
279 169 jshamlet
    Rd_Data                  : in  DATA_TYPE;
280 223 jshamlet
    Interrupts               : in  INTERRUPT_BUNDLE := x"00"
281
);
282 169 jshamlet
end entity;
283
 
284 183 jshamlet
architecture behave of o8_cpu is
285 169 jshamlet
 
286 224 jshamlet
  signal Reset_q             : std_logic := Reset_Level;
287
  signal Reset               : std_logic := Reset_Level;
288
 
289
  constant USEC_VAL          : integer := integer(Clock_Frequency / 1000000.0);
290
  constant USEC_WDT          : integer := ceil_log2(USEC_VAL - 1);
291
  constant USEC_DLY          : std_logic_vector :=
292
                                conv_std_logic_vector(USEC_VAL - 1, USEC_WDT);
293
  signal uSec_Cntr           : std_logic_vector( USEC_WDT - 1 downto 0 );
294
  signal uSec_Tick           : std_logic;
295
 
296 187 jshamlet
  signal CPU_Next_State      : CPU_STATES := IPF_C0;
297
  signal CPU_State           : CPU_STATES := IPF_C0;
298 169 jshamlet
 
299 225 jshamlet
  signal CPU_Halt_Req        : std_logic := '0';
300
  signal CPU_Halt_Ack        : std_logic := '0';
301 187 jshamlet
 
302 169 jshamlet
  signal Cache_Ctrl          : CACHE_MODES := CACHE_IDLE;
303
 
304
  signal Opcode              : OPCODE_TYPE := (others => '0');
305
  signal SubOp, SubOp_p1     : SUBOP_TYPE  := (others => '0');
306
 
307
  signal Prefetch            : DATA_TYPE   := x"00";
308
  signal Operand1, Operand2  : DATA_TYPE   := x"00";
309
 
310
  signal Instr_Prefetch      : std_logic   := '0';
311
 
312
  signal PC_Ctrl             : PC_CTRL_TYPE;
313
  signal Program_Ctr         : ADDRESS_TYPE := x"0000";
314
 
315 182 jshamlet
  signal ALU_Ctrl            : ALU_CTRL_TYPE;
316
  signal Regfile             : REGFILE_TYPE;
317
  signal Flags               : FLAG_TYPE;
318
  signal Mult                : ADDRESS_TYPE := x"0000";
319
 
320 169 jshamlet
  signal SP_Ctrl             : SP_CTRL_TYPE;
321
  signal Stack_Ptr           : ADDRESS_TYPE := x"0000";
322
 
323
  signal DP_Ctrl             : DATA_CTRL_TYPE;
324
 
325
  signal INT_Ctrl            : INT_CTRL_TYPE;
326
  signal Ack_D, Ack_Q, Ack_Q1: std_logic   := '0';
327
  signal Int_Req, Int_Ack    : std_logic   := '0';
328 245 jshamlet
  signal Set_Mask            : std_logic   := '0';
329 169 jshamlet
  signal Int_Mask            : DATA_TYPE   := x"00";
330
  signal i_Ints              : INTERRUPT_BUNDLE := x"00";
331
  signal Pending             : INTERRUPT_BUNDLE := x"00";
332
  signal Wait_for_FSM        : std_logic := '0';
333 210 jshamlet
  signal Wait_for_ISR        : std_logic := '0';
334 169 jshamlet
 
335 254 jshamlet
  alias  ISR_Addr_Base       is ISR_Start_Addr(15 downto 4);
336
  signal ISR_Addr_Offset     : std_logic_vector(3 downto 0) := x"0";
337
 
338
  constant INT_VECTOR_0      : std_logic_vector(3 downto 0) := x"0";
339
  constant INT_VECTOR_1      : std_logic_vector(3 downto 0) := x"2";
340
  constant INT_VECTOR_2      : std_logic_vector(3 downto 0) := x"4";
341
  constant INT_VECTOR_3      : std_logic_vector(3 downto 0) := x"6";
342
  constant INT_VECTOR_4      : std_logic_vector(3 downto 0) := x"8";
343
  constant INT_VECTOR_5      : std_logic_vector(3 downto 0) := x"A";
344
  constant INT_VECTOR_6      : std_logic_vector(3 downto 0) := x"C";
345
  constant INT_VECTOR_7      : std_logic_vector(3 downto 0) := x"E";
346
 
347 255 jshamlet
  signal IDX_Offset_SX       : std_logic := '0';
348
 
349 252 jshamlet
  signal IDX_Offset          : ADDRESS_TYPE := x"0000";
350
 
351 255 jshamlet
  signal IDX_Sel_l           : std_logic_vector(2 downto 0) := "000";
352
  signal IDX_Sel_h           : std_logic_vector(2 downto 0) := "000";
353
 
354 252 jshamlet
  signal IDX_Reg_l           : integer := 0;
355
  signal IDX_Reg_h           : integer := 0;
356
 
357
  signal IDX_NoOffset_Calc   : ADDRESS_TYPE := x"0000";
358
  signal IDX_Offset_Calc     : ADDRESS_TYPE := x"0000";
359
 
360 169 jshamlet
begin
361
 
362 224 jshamlet
-------------------------------------------------------------------------------
363
-- Reset & uSec Tick
364
-------------------------------------------------------------------------------
365 185 jshamlet
 
366 224 jshamlet
  CPU_Reset_Sync: process( Clock, PLL_Locked )
367
  begin
368
    if( PLL_Locked = '0' )then
369
      Reset_q                <= Reset_Level;
370
      Reset                  <= Reset_Level;
371
    elsif( rising_edge(Clock) )then
372
      Reset_q                <= not Reset_Level;
373
      Reset                  <= Reset_q;
374
    end if;
375
  end process;
376
 
377
  uSec_Tick_proc: process( Clock, Reset )
378
  begin
379
    if( Reset = Reset_Level )then
380
      uSec_Cntr              <= USEC_DLY;
381
      uSec_Tick              <= '0';
382
    elsif( rising_edge( Clock ) )then
383
      uSec_Cntr              <= uSec_Cntr - 1;
384
      if( or_reduce(uSec_Cntr) = '0' )then
385
        uSec_Cntr            <= USEC_DLY;
386
      end if;
387
      uSec_Tick              <= nor_reduce(uSec_Cntr);
388
    end if;
389
  end process;
390
 
391
  Open8_Bus.Clock            <= Clock;
392
  Open8_Bus.Reset            <= Reset;
393
  Open8_Bus.uSec_Tick        <= uSec_Tick;
394
 
395 169 jshamlet
-------------------------------------------------------------------------------
396 182 jshamlet
-- Address bus selection/generation logic
397 169 jshamlet
-------------------------------------------------------------------------------
398
 
399 254 jshamlet
  -- Address selection logic based on current CPU state. This is combinatorial,
400
  --  as adding pipeline registration would add a clock cycle to every instr,
401
  --  without really adding the Fmax to compensate.
402
  Address_Logic: process(CPU_State, Operand1, Operand2, IDX_NoOffset_Calc,
403 255 jshamlet
                         IDX_Offset_Calc, ISR_Addr_Offset, Stack_Ptr,
404
                         Program_Ctr )
405 254 jshamlet
  begin
406
    case( CPU_State )is
407
 
408
      when LDA_C2 | STA_C2 =>
409
        Open8_Bus.Address    <= Operand2 & Operand1;
410
 
411
      when LDX_C1 | STX_C1 =>
412
        Open8_Bus.Address    <= IDX_NoOffset_Calc;
413
 
414
      when LDO_C2 | STO_C2 =>
415
        Open8_Bus.Address    <= IDX_Offset_Calc;
416
 
417
      when ISR_C1 | ISR_C2 =>
418
        Open8_Bus.Address    <= ISR_Addr_Base & ISR_Addr_Offset;
419
 
420 255 jshamlet
      when PSH_C1 | POP_C1 |
421
           ISR_C3 | JSR_C1 | JSR_C2 |
422
           RTS_C1 | RTS_C2 | RTS_C3 =>
423 254 jshamlet
        Open8_Bus.Address    <= Stack_Ptr;
424
 
425
      when others =>
426
        Open8_Bus.Address    <= Program_Ctr;
427
 
428
    end case;
429
  end process;
430
 
431 252 jshamlet
  -- The original model treated the offset to LDO/STO as a signed value
432
  --  allowing access to locations -128 to +127 from [Rn+1:Rn]. This isn't
433
  --  always helpful, so the generic allows the CPU to use unsigned math
434
  --  for the offsets. This makes the range 0 to +255 instead.
435 253 jshamlet
 
436 255 jshamlet
  IDX_Offset_SX <= '0' when Unsigned_Index_Offsets else Operand1(7);
437 252 jshamlet
 
438 255 jshamlet
  IDX_Offset(15 downto 8)    <= (others => IDX_Offset_SX);
439 252 jshamlet
  IDX_Offset(7 downto 0)     <= Operand1;
440
 
441
  -- Enable_Auto_Increment uses the LSB to determine whether or not to
442
  --  do the auto-increment, so we need to lock the LSB for each operand
443
  --  if it is enabled. This forces [ODD:EVEN] pairing.
444
 
445 255 jshamlet
  IDX_Sel_l <= (SubOp(2 downto 1) & '0') when Enable_Auto_Increment else
446
               SubOp;
447 252 jshamlet
 
448 255 jshamlet
  IDX_Sel_h <= (SubOp(2 downto 1) & '1') when Enable_Auto_Increment else
449
               SubOp_p1;
450 252 jshamlet
 
451 255 jshamlet
  IDX_Reg_l <= conv_integer(IDX_Sel_l);
452
  IDX_Reg_h <= conv_integer(IDX_Sel_h);
453
 
454 252 jshamlet
  -- Pipeline registers for the indexed and indexed with offset addresses.
455
  Idx_Addr_Calc_proc: process( Clock, Reset )
456 169 jshamlet
    variable Reg, Reg_1      : integer range 0 to 7 := 0;
457
  begin
458 252 jshamlet
    if( Reset = Reset_Level )then
459
      IDX_NoOffset_Calc      <= x"0000";
460
      IDX_Offset_Calc        <= x"0000";
461
    elsif( rising_edge(Clock))then
462
      IDX_NoOffset_Calc      <= (Regfile(IDX_Reg_h) & Regfile(IDX_Reg_l));
463
      IDX_Offset_Calc        <= (Regfile(IDX_Reg_h) & Regfile(IDX_Reg_l)) +
464
                                IDX_Offset;
465 182 jshamlet
    end if;
466 252 jshamlet
  end process;
467 182 jshamlet
 
468
-------------------------------------------------------------------------------
469
-- Combinatorial portion of CPU finite state machine
470
-- State Logic / Instruction Decoding & Execution
471
-------------------------------------------------------------------------------
472
 
473 187 jshamlet
  State_Logic: process(CPU_State, Flags, Int_Mask, CPU_Halt_Req, Opcode,
474 182 jshamlet
                       SubOp , SubOp_p1, Operand1, Operand2, Int_Req )
475
    variable Reg             : integer range 0 to 7 := 0;
476
  begin
477 169 jshamlet
    CPU_Next_State           <= CPU_State;
478
    Cache_Ctrl               <= CACHE_IDLE;
479
    --
480 185 jshamlet
    PC_Ctrl.Oper             <= PC_INCR;
481
    PC_Ctrl.Offset           <= PC_IDLE;
482 182 jshamlet
    --
483 169 jshamlet
    ALU_Ctrl.Oper            <= ALU_IDLE;
484
    ALU_Ctrl.Reg             <= ACCUM;
485
    --
486
    SP_Ctrl.Oper             <= SP_IDLE;
487
    --
488
    DP_Ctrl.Src              <= DATA_RD_MEM;
489
    DP_Ctrl.Reg              <= ACCUM;
490
    --
491
    INT_Ctrl.Mask_Set        <= '0';
492
    INT_Ctrl.Soft_Ints       <= x"00";
493
    INT_Ctrl.Incr_ISR        <= '0';
494
    Ack_D                    <= '0';
495 225 jshamlet
    --
496 182 jshamlet
    Reg                     := conv_integer(SubOp);
497 225 jshamlet
    --
498
    CPU_Halt_Ack             <= '0';
499 169 jshamlet
 
500
    case CPU_State is
501
-------------------------------------------------------------------------------
502
-- Initial Instruction fetch & decode
503
-------------------------------------------------------------------------------
504 187 jshamlet
      when IPF_C0 =>
505
        CPU_Next_State       <= IPF_C1;
506 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
507 169 jshamlet
 
508 187 jshamlet
      when IPF_C1 =>
509
        CPU_Next_State       <= IPF_C2;
510 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
511 169 jshamlet
 
512 187 jshamlet
      when IPF_C2 =>
513
        CPU_Next_State       <= IDC_C0;
514 169 jshamlet
        Cache_Ctrl           <= CACHE_INSTR;
515 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
516 169 jshamlet
 
517 187 jshamlet
      when IDC_C0 =>
518
        CPU_Next_State       <= IDC_C0;
519 169 jshamlet
        Cache_Ctrl           <= CACHE_INSTR;
520
 
521
        case Opcode is
522
          when OP_PSH =>
523
            CPU_Next_State   <= PSH_C1;
524
            Cache_Ctrl       <= CACHE_PREFETCH;
525 185 jshamlet
            PC_Ctrl.Offset   <= PC_REV1;
526 169 jshamlet
            DP_Ctrl.Src      <= DATA_WR_REG;
527
            DP_Ctrl.Reg      <= SubOp;
528
 
529
          when OP_POP =>
530
            CPU_Next_State   <= POP_C1;
531
            Cache_Ctrl       <= CACHE_PREFETCH;
532 185 jshamlet
            PC_Ctrl.Offset   <= PC_REV2;
533 169 jshamlet
            SP_Ctrl.Oper     <= SP_POP;
534
 
535
          when OP_BR0 | OP_BR1 =>
536
            CPU_Next_State   <= BRN_C1;
537
            Cache_Ctrl       <= CACHE_OPER1;
538 185 jshamlet
            PC_Ctrl.Offset   <= PC_NEXT;
539 169 jshamlet
 
540 185 jshamlet
 
541 169 jshamlet
          when OP_DBNZ =>
542
            CPU_Next_State   <= DBNZ_C1;
543
            Cache_Ctrl       <= CACHE_OPER1;
544 185 jshamlet
            PC_Ctrl.Offset   <= PC_NEXT;
545 169 jshamlet
            ALU_Ctrl.Oper    <= ALU_DEC;
546
            ALU_Ctrl.Reg     <= SubOp;
547
 
548
          when OP_INT =>
549 185 jshamlet
            PC_Ctrl.Offset   <= PC_NEXT;
550 187 jshamlet
            -- Make sure the requested interrupt is actually enabled first.
551
            --  Also, unlike CPU_Halt, the INT instruction is actually being
552
            --  executed, so go ahead and increment the program counter before
553
            --  pausing so the CPU restarts on the next instruction.
554 169 jshamlet
            if( Int_Mask(Reg) = '1' )then
555 187 jshamlet
              CPU_Next_State <= WAI_Cx;
556 169 jshamlet
              INT_Ctrl.Soft_Ints(Reg) <= '1';
557
            end if;
558
 
559
          when OP_STK =>
560
            case SubOp is
561
              when SOP_RSP  =>
562 185 jshamlet
                PC_Ctrl.Offset <= PC_NEXT;
563 181 jshamlet
                if( not Allow_Stack_Address_Move )then
564 187 jshamlet
                  -- The default behavior for this instruction is to simply
565
                  --  repoint the SP to the HDL default
566 185 jshamlet
                  SP_Ctrl.Oper    <= SP_CLR;
567 181 jshamlet
                end if;
568 187 jshamlet
                if( Allow_Stack_Address_Move and
569
                    Flags(Stack_Xfer_Flag) = '1' )then
570
                  -- If RSP is set to allow SP moves, and the specified flag
571
                  --  is true, then signal the stack pointer logic to load
572
                  --  from R1:R0
573 185 jshamlet
                  SP_Ctrl.Oper    <= SP_SET;
574 181 jshamlet
                end if;
575 187 jshamlet
                if( Allow_Stack_Address_Move and
576
                    Flags(Stack_Xfer_Flag) = '0')then
577
                  -- If RSP is set to allow SP moves, and the specified flag
578
                  --  is false, then signal the ALU to copy the stack pointer
579
                  --  to R1:R0
580 185 jshamlet
                  ALU_Ctrl.Oper   <= ALU_RSP;
581 181 jshamlet
                end if;
582 169 jshamlet
 
583
              when SOP_RTS | SOP_RTI =>
584 185 jshamlet
                CPU_Next_State    <= RTS_C1;
585 190 jshamlet
                Cache_Ctrl        <= CACHE_IDLE;
586 185 jshamlet
                SP_Ctrl.Oper      <= SP_POP;
587 169 jshamlet
 
588
              when SOP_BRK  =>
589
                if( BRK_Implements_WAI )then
590 187 jshamlet
                  -- If BRK_Implements_WAI, then jump to the WAI_Cx and
591
                  --  increment the PC similar to an ISR flow.
592
                  CPU_Next_State  <= WAI_Cx;
593 185 jshamlet
                  PC_Ctrl.Offset  <= PC_NEXT;
594 187 jshamlet
                else
595
                -- If Break is implemented normally, back the PC up by
596
                --  2 and return through IPF_C0 in order to execute a 5
597
                --  clock cycle delay
598
                  CPU_Next_State  <= BRK_C1;
599
                  PC_Ctrl.Offset  <= PC_REV2;
600 169 jshamlet
                end if;
601
 
602
              when SOP_JMP  =>
603 185 jshamlet
                CPU_Next_State    <= JMP_C1;
604
                Cache_Ctrl        <= CACHE_OPER1;
605 169 jshamlet
 
606
              when SOP_SMSK =>
607 185 jshamlet
                PC_Ctrl.Offset    <= PC_NEXT;
608 169 jshamlet
                INT_Ctrl.Mask_Set <= '1';
609
 
610
              when SOP_GMSK =>
611 185 jshamlet
                PC_Ctrl.Offset    <= PC_NEXT;
612
                ALU_Ctrl.Oper     <= ALU_GMSK;
613 169 jshamlet
 
614
              when SOP_JSR =>
615
                CPU_Next_State <= JSR_C1;
616 185 jshamlet
                Cache_Ctrl        <= CACHE_OPER1;
617
                DP_Ctrl.Src       <= DATA_WR_PC;
618
                DP_Ctrl.Reg       <= PC_MSB;
619 169 jshamlet
 
620
              when others => null;
621
            end case;
622
 
623
          when OP_MUL =>
624
            CPU_Next_State   <= MUL_C1;
625 181 jshamlet
            -- Multiplication requires a single clock cycle to calculate PRIOR
626
            --  to the ALU writing the result to registers. As a result, this
627
            --  state needs to idle the ALU initially, and back the PC up by 1
628
            -- We can get away with only 1 extra clock by pre-fetching the
629
            --  next instruction, though.
630 169 jshamlet
            Cache_Ctrl       <= CACHE_PREFETCH;
631 185 jshamlet
            PC_Ctrl.Offset   <= PC_REV1;
632 181 jshamlet
            -- Note that both the multiply process AND ALU process need the
633
            --  source register for Rn (R1:R0 = R0 * Rn). Assert ALU_Ctrl.reg
634
            --  now, but hold off on the ALU command until the next state.
635 169 jshamlet
            ALU_Ctrl.Oper    <= ALU_IDLE;
636
            ALU_Ctrl.Reg     <= SubOp;
637
 
638
          when OP_UPP =>
639
            CPU_Next_State   <= UPP_C1;
640
            Cache_Ctrl       <= CACHE_PREFETCH;
641 185 jshamlet
            PC_Ctrl.Offset   <= PC_REV1;
642 169 jshamlet
            ALU_Ctrl.Oper    <= Opcode;
643
            ALU_Ctrl.Reg     <= SubOp;
644
 
645
          when OP_LDA =>
646
            CPU_Next_State   <= LDA_C1;
647
            Cache_Ctrl       <= CACHE_OPER1;
648
 
649
          when OP_LDI =>
650
            CPU_Next_State   <= LDI_C1;
651
            Cache_Ctrl       <= CACHE_OPER1;
652 185 jshamlet
            PC_Ctrl.Offset   <= PC_NEXT;
653 169 jshamlet
 
654
          when OP_LDO =>
655
            CPU_Next_State   <= LDO_C1;
656
            Cache_Ctrl       <= CACHE_OPER1;
657 185 jshamlet
            PC_Ctrl.Offset   <= PC_REV2;
658 169 jshamlet
 
659
          when OP_LDX =>
660
            CPU_Next_State   <= LDX_C1;
661 181 jshamlet
            Cache_Ctrl       <= CACHE_PREFETCH;
662 185 jshamlet
            PC_Ctrl.Offset   <= PC_REV2;
663 169 jshamlet
 
664
          when OP_STA =>
665
            CPU_Next_State   <= STA_C1;
666
            Cache_Ctrl       <= CACHE_OPER1;
667
 
668
          when OP_STO =>
669
            CPU_Next_State   <= STO_C1;
670
            Cache_Ctrl       <= CACHE_OPER1;
671 252 jshamlet
            PC_Ctrl.Offset   <= PC_REV1;
672 169 jshamlet
 
673
          when OP_STX =>
674
            CPU_Next_State   <= STX_C1;
675
            Cache_Ctrl       <= CACHE_PREFETCH;
676 185 jshamlet
            PC_Ctrl.Offset   <= PC_REV2;
677 169 jshamlet
            DP_Ctrl.Src      <= DATA_WR_REG;
678
            DP_Ctrl.Reg      <= ACCUM;
679
 
680 244 jshamlet
          when OP_STP =>
681
            PC_Ctrl.Offset   <= PC_NEXT;
682
            if( Supervisor_Mode )then
683
              if( SubOp /= PSR_I )then
684
                ALU_Ctrl.Oper  <= Opcode;
685
                ALU_Ctrl.Reg   <= SubOp;
686
              end if;
687
            else
688
              ALU_Ctrl.Oper  <= Opcode;
689
              ALU_Ctrl.Reg   <= SubOp;
690
            end if;
691
 
692 169 jshamlet
          when others =>
693 185 jshamlet
            PC_Ctrl.Offset   <= PC_NEXT;
694 169 jshamlet
            ALU_Ctrl.Oper    <= Opcode;
695
            ALU_Ctrl.Reg     <= SubOp;
696
 
697
        end case;
698
 
699 186 jshamlet
        if( Int_Req = '1' )then
700
          CPU_Next_State     <= ISR_C1;
701 187 jshamlet
        end if;
702
 
703
        if( CPU_Halt_Req = '1' )then
704
          CPU_Next_State     <= WAH_Cx;
705
        end if;
706
 
707
        -- If either of these override conditions are true, the decoder needs
708
        --  to undo everything it just setup, since even "single-cycle"
709
        --  instructions will be executed again upon return.
710
        if( Int_Req = '1' or CPU_Halt_Req = '1' )then
711
          -- In either case, we want to skip loading the cache, as the cache
712
          --  will be invalid by the time we get back.
713 186 jshamlet
          Cache_Ctrl         <= CACHE_IDLE;
714 187 jshamlet
          -- Rewind the PC by 3 to put the PC back to the current instruction,
715
          -- compensating for the pipeline registers.
716 186 jshamlet
          PC_Ctrl.Offset     <= PC_REV3;
717
          -- Reset all of the sub-block controls to IDLE, to avoid unintended
718 187 jshamlet
          --  operation due to the current instruction.
719 186 jshamlet
          ALU_Ctrl.Oper      <= ALU_IDLE;
720
          SP_Ctrl.Oper       <= SP_IDLE;
721 187 jshamlet
          -- Interrupt logic outside of the state machine needs this to be set
722
          --  to DATA_RD_MEM, while CPU_Halt considers this a "don't care".
723 186 jshamlet
          DP_Ctrl.Src        <= DATA_RD_MEM;
724 187 jshamlet
          -- If an INT/SMSK instruction was going to be executed, it will get
725
          --  executed again when normal processing resumes, so axe their
726
          --  requests for now.
727
          INT_Ctrl.Mask_Set       <= '0';
728
          INT_Ctrl.Soft_Ints(Reg) <= '0';
729 186 jshamlet
        end if;
730
 
731 169 jshamlet
-------------------------------------------------------------------------------
732
-- Program Control (BR0_C1, BR1_C1, DBNZ_C1, JMP )
733
-------------------------------------------------------------------------------
734
 
735
      when BRN_C1 =>
736 187 jshamlet
        CPU_Next_State       <= IDC_C0;
737 169 jshamlet
        Cache_Ctrl           <= CACHE_INSTR;
738 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
739 169 jshamlet
        if( Flags(Reg) = Opcode(0) )then
740 187 jshamlet
          CPU_Next_State     <= IPF_C0;
741 169 jshamlet
          Cache_Ctrl         <= CACHE_IDLE;
742
          PC_Ctrl.Offset     <= Operand1;
743
        end if;
744
 
745
      when DBNZ_C1 =>
746 187 jshamlet
        CPU_Next_State       <= IDC_C0;
747 169 jshamlet
        Cache_Ctrl           <= CACHE_INSTR;
748 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
749
        if( Flags(PSR_Z) = '0' )then
750 187 jshamlet
          CPU_Next_State     <= IPF_C0;
751 169 jshamlet
          Cache_Ctrl         <= CACHE_IDLE;
752
          PC_Ctrl.Offset     <= Operand1;
753
        end if;
754
 
755
      when JMP_C1 =>
756
        CPU_Next_State       <= JMP_C2;
757
        Cache_Ctrl           <= CACHE_OPER2;
758
 
759
      when JMP_C2 =>
760 187 jshamlet
        CPU_Next_State       <= IPF_C0;
761 169 jshamlet
        PC_Ctrl.Oper         <= PC_LOAD;
762
 
763
-------------------------------------------------------------------------------
764
-- Data Storage - Load from memory (LDA, LDI, LDO, LDX)
765
-------------------------------------------------------------------------------
766
 
767
      when LDA_C1 =>
768
        CPU_Next_State       <= LDA_C2;
769
        Cache_Ctrl           <= CACHE_OPER2;
770
 
771
      when LDA_C2 =>
772
        CPU_Next_State       <= LDA_C3;
773
 
774
      when LDA_C3 =>
775
        CPU_Next_State       <= LDA_C4;
776 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
777 169 jshamlet
 
778
      when LDA_C4 =>
779
        CPU_Next_State       <= LDI_C1;
780
        Cache_Ctrl           <= CACHE_OPER1;
781 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
782 169 jshamlet
 
783
      when LDI_C1 =>
784 187 jshamlet
        CPU_Next_State       <= IDC_C0;
785 169 jshamlet
        Cache_Ctrl           <= CACHE_INSTR;
786 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
787 169 jshamlet
        ALU_Ctrl.Oper        <= ALU_LDI;
788
        ALU_Ctrl.Reg         <= SubOp;
789
 
790
      when LDO_C1 =>
791 252 jshamlet
        CPU_Next_State       <= LDO_C2;
792
 
793
      when LDO_C2 =>
794 181 jshamlet
        CPU_Next_State       <= LDX_C2;
795 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
796 182 jshamlet
        if( Enable_Auto_Increment and SubOp(0) = '1' )then
797
          ALU_Ctrl.Oper      <= ALU_UPP;
798
          ALU_Ctrl.Reg       <= SubOp(2 downto 1) & '0';
799 169 jshamlet
        end if;
800
 
801
      when LDX_C1 =>
802
        CPU_Next_State       <= LDX_C2;
803 182 jshamlet
        if( Enable_Auto_Increment and SubOp(0) = '1' )then
804
          ALU_Ctrl.Oper      <= ALU_UPP;
805
          ALU_Ctrl.Reg       <= SubOp(2 downto 1) & '0';
806 181 jshamlet
        end if;
807 169 jshamlet
 
808
      when LDX_C2 =>
809
        CPU_Next_State       <= LDX_C3;
810 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
811 181 jshamlet
 
812
      when LDX_C3 =>
813
        CPU_Next_State       <= LDX_C4;
814 182 jshamlet
        Cache_Ctrl           <= CACHE_OPER1;
815 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
816 169 jshamlet
 
817 181 jshamlet
      when LDX_C4 =>
818 187 jshamlet
        CPU_Next_State       <= IDC_C0;
819 169 jshamlet
        Cache_Ctrl           <= CACHE_INSTR;
820 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
821 181 jshamlet
        ALU_Ctrl.Oper        <= ALU_LDI;
822 169 jshamlet
        ALU_Ctrl.Reg         <= ACCUM;
823
 
824
-------------------------------------------------------------------------------
825
-- Data Storage - Store to memory (STA, STO, STX)
826
-------------------------------------------------------------------------------
827
      when STA_C1 =>
828
        CPU_Next_State       <= STA_C2;
829
        Cache_Ctrl           <= CACHE_OPER2;
830
        DP_Ctrl.Src          <= DATA_WR_REG;
831
        DP_Ctrl.Reg          <= SubOp;
832
 
833
      when STA_C2 =>
834
        CPU_Next_State       <= STA_C3;
835 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
836 169 jshamlet
 
837
      when STA_C3 =>
838 187 jshamlet
        CPU_Next_State       <= IPF_C2;
839 169 jshamlet
        Cache_Ctrl           <= CACHE_PREFETCH;
840 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
841 169 jshamlet
 
842
      when STO_C1 =>
843 252 jshamlet
        CPU_Next_State       <= STO_C2;
844 169 jshamlet
        Cache_Ctrl           <= CACHE_PREFETCH;
845 252 jshamlet
        DP_Ctrl.Src          <= DATA_WR_REG;
846
        DP_Ctrl.Reg          <= ACCUM;
847
 
848
      when STO_C2 =>
849
        CPU_Next_State       <= IPF_C1;
850 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
851 182 jshamlet
        if( Enable_Auto_Increment and SubOp(0) = '1' )then
852 252 jshamlet
          CPU_Next_State     <= STO_C3;
853 182 jshamlet
          ALU_Ctrl.Oper      <= ALU_UPP;
854
          ALU_Ctrl.Reg       <= SubOp(2 downto 1) & '0';
855 169 jshamlet
        end if;
856
 
857 252 jshamlet
      when STO_C3 =>
858
        CPU_Next_State       <= IPF_C2;
859 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
860 169 jshamlet
        ALU_Ctrl.Oper        <= ALU_UPP2;
861
        ALU_Ctrl.Reg         <= SubOp(2 downto 1) & '1';
862
 
863
      when STX_C1 =>
864 187 jshamlet
        CPU_Next_State       <= IPF_C1;
865 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
866 182 jshamlet
        if( Enable_Auto_Increment and SubOp(0) = '1' )then
867
          CPU_Next_State     <= STX_C2;
868
          ALU_Ctrl.Oper      <= ALU_UPP;
869
          ALU_Ctrl.Reg       <= SubOp(2 downto 1) & '0';
870 169 jshamlet
        end if;
871
 
872
      when STX_C2 =>
873 187 jshamlet
        CPU_Next_State       <= IPF_C2;
874 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
875 169 jshamlet
        ALU_Ctrl.Oper        <= ALU_UPP2;
876
        ALU_Ctrl.Reg         <= SubOp(2 downto 1) & '1';
877
 
878
-------------------------------------------------------------------------------
879
-- Multi-Cycle Math Operations (UPP, MUL)
880
-------------------------------------------------------------------------------
881
 
882
      -- Because we have to backup the pipeline by 1 to refetch the 2nd
883 181 jshamlet
      --  instruction/first operand, we have to return through PF2. Also, we
884
      --  need to tell the ALU to store the results to R1:R0 here. Note that
885
      --  there is no ALU_Ctrl.Reg, as this is implied in the ALU instruction
886 169 jshamlet
      when MUL_C1 =>
887 187 jshamlet
        CPU_Next_State       <= IPF_C2;
888 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
889 169 jshamlet
        ALU_Ctrl.Oper        <= ALU_MUL;
890
 
891
      when UPP_C1 =>
892 187 jshamlet
        CPU_Next_State       <= IPF_C2;
893 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
894 169 jshamlet
        ALU_Ctrl.Oper        <= ALU_UPP2;
895
        ALU_Ctrl.Reg         <= SubOp_p1;
896
 
897
-------------------------------------------------------------------------------
898
-- Basic Stack Manipulation (PSH, POP, RSP)
899
-------------------------------------------------------------------------------
900
      when PSH_C1 =>
901 187 jshamlet
        CPU_Next_State       <= IPF_C1;
902 169 jshamlet
        SP_Ctrl.Oper         <= SP_PUSH;
903
 
904
      when POP_C1 =>
905
        CPU_Next_State       <= POP_C2;
906
 
907
      when POP_C2 =>
908
        CPU_Next_State       <= POP_C3;
909 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
910 169 jshamlet
 
911
      when POP_C3 =>
912
        CPU_Next_State       <= POP_C4;
913
        Cache_Ctrl           <= CACHE_OPER1;
914 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
915 169 jshamlet
 
916
      when POP_C4 =>
917 187 jshamlet
        CPU_Next_State       <= IDC_C0;
918 169 jshamlet
        Cache_Ctrl           <= CACHE_INSTR;
919 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
920 169 jshamlet
        ALU_Ctrl.Oper        <= ALU_POP;
921
        ALU_Ctrl.Reg         <= SubOp;
922 172 jshamlet
 
923 169 jshamlet
-------------------------------------------------------------------------------
924
-- Subroutines & Interrupts (RTS, JSR)
925
-------------------------------------------------------------------------------
926 187 jshamlet
      when WAI_Cx => -- For soft interrupts only, halt the Program_Ctr
927 169 jshamlet
        DP_Ctrl.Src          <= DATA_BUS_IDLE;
928 186 jshamlet
        if( Int_Req = '1' )then
929
          CPU_Next_State     <= ISR_C1;
930 187 jshamlet
          -- Rewind the PC by 3 to put the PC back to would have been the next
931
          --  instruction, compensating for the pipeline registers.
932 186 jshamlet
          PC_Ctrl.Offset     <= PC_REV3;
933
          -- Reset all of the sub-block controls to IDLE, to avoid unintended
934
          --  operation due to the current instruction
935
          DP_Ctrl.Src        <= DATA_RD_MEM;
936
        end if;
937 169 jshamlet
 
938 187 jshamlet
      when WAH_Cx => -- Holds until CPU_Halt_Req is deasserted.
939 225 jshamlet
        CPU_Halt_Ack         <= '1';
940 187 jshamlet
        DP_Ctrl.Src          <= DATA_BUS_IDLE;
941
        if( CPU_Halt_Req = '0' )then
942
          CPU_Next_State     <= IPF_C0;
943
          DP_Ctrl.Src        <= DATA_RD_MEM;
944
        end if;
945
 
946
      when BRK_C1 => -- Debugging (BRK) Performs a 5-clock NOP.
947
        CPU_Next_State       <= IPF_C0;
948
 
949 169 jshamlet
      when ISR_C1 =>
950
        CPU_Next_State       <= ISR_C2;
951
        INT_Ctrl.Incr_ISR    <= '1';
952
 
953
      when ISR_C2 =>
954
        CPU_Next_State       <= ISR_C3;
955
        DP_Ctrl.Src          <= DATA_WR_FLAG;
956
 
957
      when ISR_C3 =>
958
        CPU_Next_State       <= JSR_C1;
959
        Cache_Ctrl           <= CACHE_OPER1;
960 182 jshamlet
        ALU_Ctrl.Oper        <= ALU_STP;
961 185 jshamlet
        ALU_Ctrl.Reg         <= conv_std_logic_vector(PSR_I,3);
962 169 jshamlet
        SP_Ctrl.Oper         <= SP_PUSH;
963
        DP_Ctrl.Src          <= DATA_WR_PC;
964 182 jshamlet
        DP_Ctrl.Reg          <= PC_MSB;
965 169 jshamlet
        Ack_D                <= '1';
966
 
967
      when JSR_C1 =>
968
        CPU_Next_State       <= JSR_C2;
969
        Cache_Ctrl           <= CACHE_OPER2;
970
        SP_Ctrl.Oper         <= SP_PUSH;
971
        DP_Ctrl.Src          <= DATA_WR_PC;
972 182 jshamlet
        DP_Ctrl.Reg          <= PC_LSB;
973 169 jshamlet
 
974
      when JSR_C2 =>
975 187 jshamlet
        CPU_Next_State       <= IPF_C0;
976 169 jshamlet
        PC_Ctrl.Oper         <= PC_LOAD;
977 182 jshamlet
        SP_Ctrl.Oper         <= SP_PUSH;
978 169 jshamlet
 
979
      when RTS_C1 =>
980
        CPU_Next_State       <= RTS_C2;
981
        SP_Ctrl.Oper         <= SP_POP;
982
 
983
      when RTS_C2 =>
984
        CPU_Next_State       <= RTS_C3;
985
        -- if this is an RTI, then we need to POP the flags
986
        if( SubOp = SOP_RTI )then
987
          SP_Ctrl.Oper       <= SP_POP;
988
        end if;
989
 
990
      when RTS_C3 =>
991
        CPU_Next_State       <= RTS_C4;
992
        Cache_Ctrl           <= CACHE_OPER1;
993
 
994
      when RTS_C4 =>
995
        CPU_Next_State       <= RTS_C5;
996
        Cache_Ctrl           <= CACHE_OPER2;
997
 
998
      when RTS_C5 =>
999 187 jshamlet
        CPU_Next_State       <= IPF_C0;
1000 169 jshamlet
        PC_Ctrl.Oper         <= PC_LOAD;
1001 185 jshamlet
        -- if this is an RTI, then we need to clear the I bit
1002 169 jshamlet
        if( SubOp = SOP_RTI )then
1003
          CPU_Next_State     <= RTI_C6;
1004
          Cache_Ctrl         <= CACHE_OPER1;
1005 185 jshamlet
          ALU_Ctrl.Oper      <= ALU_CLP;
1006
          ALU_Ctrl.Reg       <= conv_std_logic_vector(PSR_I,3);
1007 169 jshamlet
        end if;
1008
 
1009
      when RTI_C6 =>
1010 187 jshamlet
        CPU_Next_State       <= IPF_C1;
1011 185 jshamlet
        PC_Ctrl.Offset       <= PC_NEXT;
1012 169 jshamlet
        ALU_Ctrl.Oper        <= ALU_RFLG;
1013
 
1014
      when others =>
1015
        null;
1016
    end case;
1017
 
1018
  end process;
1019
 
1020
-------------------------------------------------------------------------------
1021
-- Registered portion of CPU finite state machine
1022
-------------------------------------------------------------------------------
1023 182 jshamlet
 
1024 169 jshamlet
  CPU_Regs: process( Reset, Clock )
1025
    variable Offset_SX       : ADDRESS_TYPE;
1026 188 jshamlet
    variable i_Ints          : INTERRUPT_BUNDLE := x"00";
1027 169 jshamlet
    variable Index           : integer range 0 to 7         := 0;
1028
    variable Sum             : std_logic_vector(8 downto 0) := "000000000";
1029
    variable Temp            : std_logic_vector(8 downto 0) := "000000000";
1030
  begin
1031
    if( Reset = Reset_Level )then
1032 187 jshamlet
      CPU_State              <= IPF_C0;
1033 169 jshamlet
      Opcode                 <= OP_INC;
1034
      SubOp                  <= ACCUM;
1035
      SubOp_p1               <= ACCUM;
1036
      Operand1               <= x"00";
1037
      Operand2               <= x"00";
1038
      Instr_Prefetch         <= '0';
1039
      Prefetch               <= x"00";
1040
 
1041 187 jshamlet
      CPU_Halt_Req           <= '0';
1042 225 jshamlet
      Halt_Ack               <= '0';
1043 187 jshamlet
 
1044 223 jshamlet
      Open8_Bus.Wr_En        <= '0';
1045
      Open8_Bus.Wr_Data      <= OPEN8_NULLBUS;
1046
      Open8_Bus.Rd_En        <= '1';
1047 169 jshamlet
 
1048
      Program_Ctr            <= Program_Start_Addr;
1049
      Stack_Ptr              <= Stack_Start_Addr;
1050
 
1051
      Ack_Q                  <= '0';
1052
      Ack_Q1                 <= '0';
1053
      Int_Ack                <= '0';
1054
 
1055
      Int_Req                <= '0';
1056
      Pending                <= x"00";
1057
      Wait_for_FSM           <= '0';
1058 210 jshamlet
      Wait_for_ISR           <= '0';
1059 245 jshamlet
      Set_Mask               <= '0';
1060 169 jshamlet
      if( Enable_NMI )then
1061
        Int_Mask             <= Default_Interrupt_Mask(7 downto 1) & '1';
1062
      else
1063
        Int_Mask             <= Default_Interrupt_Mask;
1064
      end if;
1065 254 jshamlet
      ISR_Addr_Offset        <= INT_VECTOR_0;
1066 169 jshamlet
 
1067
      for i in 0 to 7 loop
1068 188 jshamlet
        Regfile(i)           <= x"00";
1069 169 jshamlet
      end loop;
1070
      Flags                  <= x"00";
1071 248 jshamlet
      if( Supervisor_Mode )then
1072 244 jshamlet
        Flags(PSR_I)         <= '1';
1073
      end if;
1074 169 jshamlet
 
1075 224 jshamlet
      Open8_Bus.GP_Flags     <= (others => '0');
1076 188 jshamlet
 
1077 169 jshamlet
    elsif( rising_edge(Clock) )then
1078 187 jshamlet
 
1079 225 jshamlet
      CPU_Halt_Req           <= Halt_Req;
1080
      Halt_Ack               <= CPU_Halt_Ack;
1081 187 jshamlet
 
1082 223 jshamlet
      Open8_Bus.Wr_En        <= '0';
1083
      Open8_Bus.Wr_Data      <= OPEN8_NULLBUS;
1084
      Open8_Bus.Rd_En        <= '0';
1085 169 jshamlet
 
1086
-------------------------------------------------------------------------------
1087
-- Instruction/Operand caching for pipelined memory access
1088
-------------------------------------------------------------------------------
1089
      CPU_State              <= CPU_Next_State;
1090
      case Cache_Ctrl is
1091
        when CACHE_INSTR =>
1092
          Opcode             <= Rd_Data(7 downto 3);
1093
          SubOp              <= Rd_Data(2 downto 0);
1094
          SubOp_p1           <= Rd_Data(2 downto 0) + 1;
1095
          if( Instr_Prefetch = '1' )then
1096
            Opcode           <= Prefetch(7 downto 3);
1097
            SubOp            <= Prefetch(2 downto 0);
1098
            SubOp_p1         <= Prefetch(2 downto 0) + 1;
1099
            Instr_Prefetch   <= '0';
1100
          end if;
1101
 
1102
        when CACHE_OPER1 =>
1103
          Operand1           <= Rd_Data;
1104
 
1105
        when CACHE_OPER2 =>
1106
          Operand2           <= Rd_Data;
1107
 
1108
        when CACHE_PREFETCH =>
1109
          Prefetch           <= Rd_Data;
1110
          Instr_Prefetch     <= '1';
1111
 
1112
        when CACHE_IDLE =>
1113
          null;
1114
      end case;
1115
 
1116
-------------------------------------------------------------------------------
1117
-- Program Counter
1118
-------------------------------------------------------------------------------
1119
      Offset_SX(15 downto 8) := (others => PC_Ctrl.Offset(7));
1120
      Offset_SX(7 downto 0)  := PC_Ctrl.Offset;
1121
 
1122
      case PC_Ctrl.Oper is
1123
        when PC_INCR =>
1124
          Program_Ctr        <= Program_Ctr + Offset_SX - 2;
1125
 
1126
        when PC_LOAD =>
1127 185 jshamlet
          Program_Ctr        <= Operand2 & Operand1;
1128 169 jshamlet
 
1129
        when others =>
1130
          null;
1131
      end case;
1132
 
1133
-------------------------------------------------------------------------------
1134
-- (Write) Data Path
1135
-------------------------------------------------------------------------------
1136
      case DP_Ctrl.Src is
1137
        when DATA_BUS_IDLE =>
1138
          null;
1139
 
1140
        when DATA_RD_MEM =>
1141 223 jshamlet
          Open8_Bus.Rd_En    <= '1';
1142 169 jshamlet
 
1143
        when DATA_WR_REG =>
1144 223 jshamlet
          Open8_Bus.Wr_En    <= '1';
1145
          Open8_Bus.Wr_Data  <= Regfile(conv_integer(DP_Ctrl.Reg));
1146 169 jshamlet
 
1147
        when DATA_WR_FLAG =>
1148 223 jshamlet
          Open8_Bus.Wr_En    <= '1';
1149
          Open8_Bus.Wr_Data  <= Flags;
1150 169 jshamlet
 
1151
        when DATA_WR_PC =>
1152 223 jshamlet
          Open8_Bus.Wr_En    <= '1';
1153
          Open8_Bus.Wr_Data  <= Program_Ctr(15 downto 8);
1154 182 jshamlet
          if( DP_Ctrl.Reg = PC_LSB )then
1155 223 jshamlet
            Open8_Bus.Wr_Data <= Program_Ctr(7 downto 0);
1156 169 jshamlet
          end if;
1157
 
1158
        when others =>
1159
          null;
1160
      end case;
1161
 
1162
-------------------------------------------------------------------------------
1163
-- Stack Pointer
1164
-------------------------------------------------------------------------------
1165
      case SP_Ctrl.Oper is
1166
        when SP_IDLE =>
1167
          null;
1168
 
1169 181 jshamlet
        when SP_CLR =>
1170 169 jshamlet
          Stack_Ptr          <= Stack_Start_Addr;
1171
 
1172 181 jshamlet
        when SP_SET =>
1173 245 jshamlet
          if( Supervisor_Mode )then
1174
            if( Flags(PSR_I) = '1' )then
1175
              Stack_Ptr      <= Regfile(1) & Regfile(0);
1176
            end if;
1177
          else
1178
            Stack_Ptr        <= Regfile(1) & Regfile(0);
1179
          end if;
1180 181 jshamlet
 
1181 169 jshamlet
        when SP_POP  =>
1182
          Stack_Ptr          <= Stack_Ptr + 1;
1183
 
1184
        when SP_PUSH =>
1185
          Stack_Ptr          <= Stack_Ptr - 1;
1186
 
1187
        when others =>
1188
          null;
1189
 
1190
      end case;
1191
 
1192
-------------------------------------------------------------------------------
1193
-- Interrupt Controller
1194
-------------------------------------------------------------------------------
1195 245 jshamlet
 
1196
      -- If Supervisor_Mode is set, restrict the SMSK instruction such that it
1197
      --  requires the I bit to be set.
1198
      if( Supervisor_Mode )then
1199
        Set_Mask             <= INT_Ctrl.Mask_Set and Flags(PSR_I);
1200
      else
1201
        Set_Mask             <= INT_Ctrl.Mask_Set;
1202
      end if;
1203
 
1204 169 jshamlet
      -- The interrupt control mask is always sourced out of R0
1205 245 jshamlet
      if( Set_Mask = '1' )then
1206 169 jshamlet
        if( Enable_NMI )then
1207
          Int_Mask           <= Regfile(conv_integer(ACCUM))(7 downto 1) & '1';
1208
        else
1209
          Int_Mask           <= Regfile(conv_integer(ACCUM));
1210
        end if;
1211
      end if;
1212
 
1213
      -- Combine external and internal interrupts, and mask the OR of the two
1214
      --  with the mask. Record any incoming interrupts to the pending buffer
1215
      i_Ints                 := (Interrupts or INT_Ctrl.Soft_Ints) and
1216
                                Int_Mask;
1217 172 jshamlet
 
1218 169 jshamlet
      Pending                <= i_Ints or Pending;
1219
 
1220 210 jshamlet
      if( Sequential_Interrupts )then
1221
        Wait_for_ISR         <= Flags(PSR_I);
1222
      else
1223
        Wait_for_ISR         <= '0';
1224
      end if;
1225
 
1226
      if( Wait_for_FSM = '0' and Wait_for_ISR = '0' )then
1227 169 jshamlet
        if(    Pending(0) = '1' )then
1228 254 jshamlet
          ISR_Addr_Offset    <= INT_VECTOR_0;
1229 169 jshamlet
          Pending(0)         <= '0';
1230
        elsif( Pending(1) = '1' )then
1231 254 jshamlet
          ISR_Addr_Offset    <= INT_VECTOR_1;
1232 169 jshamlet
          Pending(1)         <= '0';
1233
        elsif( Pending(2) = '1' )then
1234 254 jshamlet
          ISR_Addr_Offset    <= INT_VECTOR_2;
1235 169 jshamlet
          Pending(2)         <= '0';
1236
        elsif( Pending(3) = '1' )then
1237 254 jshamlet
          ISR_Addr_Offset    <= INT_VECTOR_3;
1238 169 jshamlet
          Pending(3)         <= '0';
1239
        elsif( Pending(4) = '1' )then
1240 254 jshamlet
          ISR_Addr_Offset    <= INT_VECTOR_4;
1241 169 jshamlet
          Pending(4)         <= '0';
1242
        elsif( Pending(5) = '1' )then
1243 254 jshamlet
          ISR_Addr_Offset    <= INT_VECTOR_5;
1244 169 jshamlet
          Pending(5)         <= '0';
1245
        elsif( Pending(6) = '1' )then
1246 254 jshamlet
          ISR_Addr_Offset    <= INT_VECTOR_6;
1247 169 jshamlet
          Pending(6)         <= '0';
1248
        elsif( Pending(7) = '1' )then
1249 254 jshamlet
          ISR_Addr_Offset    <= INT_VECTOR_7;
1250 169 jshamlet
          Pending(7)         <= '0';
1251
        end if;
1252 185 jshamlet
        Wait_for_FSM         <= or_reduce(Pending);
1253 169 jshamlet
      end if;
1254
 
1255
      -- Reset the Wait_for_FSM flag on Int_Ack
1256
      Ack_Q                  <= Ack_D;
1257
      Ack_Q1                 <= Ack_Q;
1258
      Int_Ack                <= Ack_Q1;
1259
      if( Int_Ack = '1' )then
1260
        Wait_for_FSM         <= '0';
1261
      end if;
1262
 
1263
      Int_Req                <= Wait_for_FSM and (not Int_Ack);
1264
 
1265
      -- Incr_ISR allows the CPU Core to advance the vector address to pop the
1266
      --  lower half of the address.
1267
      if( INT_Ctrl.Incr_ISR = '1' )then
1268 254 jshamlet
        ISR_Addr_Offset             <= ISR_Addr_Offset + 1;
1269 169 jshamlet
      end if;
1270
 
1271
-------------------------------------------------------------------------------
1272
-- ALU (Arithmetic / Logic Unit)
1273
-------------------------------------------------------------------------------
1274
      Index                  := conv_integer(ALU_Ctrl.Reg);
1275
      Sum                    := (others => '0');
1276
      Temp                   := (others => '0');
1277
 
1278
      case ALU_Ctrl.Oper is
1279
        when ALU_INC => -- Rn = Rn + 1 : Flags N,C,Z
1280
          Sum                := ("0" & x"01") +
1281
                                ("0" & Regfile(Index));
1282 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Sum(7 downto 0));
1283
          Flags(PSR_C)       <= Sum(8);
1284 209 jshamlet
          Flags(PSR_N)       <= Sum(7);
1285 169 jshamlet
          Regfile(Index)     <= Sum(7 downto 0);
1286
 
1287
        when ALU_UPP => -- Rn = Rn + 1
1288
          Sum                := ("0" & x"01") +
1289
                                ("0" & Regfile(Index));
1290 185 jshamlet
          Flags(PSR_C)       <= Sum(8);
1291 169 jshamlet
          Regfile(Index)     <= Sum(7 downto 0);
1292
 
1293
        when ALU_UPP2 => -- Rn = Rn + C
1294
          Sum                := ("0" & x"00") +
1295
                                ("0" & Regfile(Index)) +
1296 185 jshamlet
                                Flags(PSR_C);
1297
          Flags(PSR_C)       <= Sum(8);
1298 169 jshamlet
          Regfile(Index)     <= Sum(7 downto 0);
1299
 
1300
        when ALU_ADC => -- R0 = R0 + Rn + C : Flags N,C,Z
1301
          Sum                := ("0" & Regfile(0)) +
1302
                                ("0" & Regfile(Index)) +
1303 185 jshamlet
                                Flags(PSR_C);
1304
          Flags(PSR_Z)       <= nor_reduce(Sum(7 downto 0));
1305
          Flags(PSR_C)       <= Sum(8);
1306
          Flags(PSR_N)       <= Sum(7);
1307 169 jshamlet
          Regfile(0)         <= Sum(7 downto 0);
1308
 
1309
        when ALU_TX0 => -- R0 = Rn : Flags N,Z
1310
          Temp               := "0" & Regfile(Index);
1311 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Temp(7 downto 0));
1312
          Flags(PSR_N)       <= Temp(7);
1313 169 jshamlet
          Regfile(0)         <= Temp(7 downto 0);
1314
 
1315
        when ALU_OR  => -- R0 = R0 | Rn : Flags N,Z
1316
          Temp(7 downto 0)   := Regfile(0) or Regfile(Index);
1317 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Temp(7 downto 0));
1318
          Flags(PSR_N)       <= Temp(7);
1319 169 jshamlet
          Regfile(0)         <= Temp(7 downto 0);
1320
 
1321
        when ALU_AND => -- R0 = R0 & Rn : Flags N,Z
1322
          Temp(7 downto 0)   := Regfile(0) and Regfile(Index);
1323 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Temp(7 downto 0));
1324
          Flags(PSR_N)       <= Temp(7);
1325 169 jshamlet
          Regfile(0)         <= Temp(7 downto 0);
1326
 
1327
        when ALU_XOR => -- R0 = R0 ^ Rn : Flags N,Z
1328
          Temp(7 downto 0)   := Regfile(0) xor Regfile(Index);
1329 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Temp(7 downto 0));
1330
          Flags(PSR_N)       <= Temp(7);
1331 169 jshamlet
          Regfile(0)         <= Temp(7 downto 0);
1332
 
1333
        when ALU_ROL => -- Rn = Rn<<1,C : Flags N,C,Z
1334 185 jshamlet
          Temp               := Regfile(Index) & Flags(PSR_C);
1335
          Flags(PSR_Z)       <= nor_reduce(Temp(7 downto 0));
1336
          Flags(PSR_C)       <= Temp(8);
1337
          Flags(PSR_N)       <= Temp(7);
1338 169 jshamlet
          Regfile(Index)     <= Temp(7 downto 0);
1339
 
1340
        when ALU_ROR => -- Rn = C,Rn>>1 : Flags N,C,Z
1341 185 jshamlet
          Temp               := Regfile(Index)(0) & Flags(PSR_C) &
1342 169 jshamlet
                                Regfile(Index)(7 downto 1);
1343 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Temp(7 downto 0));
1344
          Flags(PSR_C)       <= Temp(8);
1345
          Flags(PSR_N)       <= Temp(7);
1346 169 jshamlet
          Regfile(Index)     <= Temp(7 downto 0);
1347
 
1348
        when ALU_DEC => -- Rn = Rn - 1 : Flags N,C,Z
1349
          Sum                := ("0" & Regfile(Index)) +
1350
                                ("0" & x"FF");
1351 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Sum(7 downto 0));
1352
          Flags(PSR_C)       <= Sum(8);
1353
          Flags(PSR_N)       <= Sum(7);
1354 169 jshamlet
          Regfile(Index)     <= Sum(7 downto 0);
1355
 
1356
        when ALU_SBC => -- Rn = R0 - Rn - C : Flags N,C,Z
1357
          Sum                := ("0" & Regfile(0)) +
1358
                                ("1" & (not Regfile(Index))) +
1359 185 jshamlet
                                Flags(PSR_C);
1360
          Flags(PSR_Z)       <= nor_reduce(Sum(7 downto 0));
1361
          Flags(PSR_C)       <= Sum(8);
1362
          Flags(PSR_N)       <= Sum(7);
1363 169 jshamlet
          Regfile(0)         <= Sum(7 downto 0);
1364
 
1365
        when ALU_ADD => -- R0 = R0 + Rn : Flags N,C,Z
1366
          Sum                := ("0" & Regfile(0)) +
1367
                                ("0" & Regfile(Index));
1368 185 jshamlet
          Flags(PSR_C)       <= Sum(8);
1369 169 jshamlet
          Regfile(0)         <= Sum(7 downto 0);
1370 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Sum(7 downto 0));
1371
          Flags(PSR_N)       <= Sum(7);
1372 169 jshamlet
 
1373
        when ALU_STP => -- Sets bit(n) in the Flags register
1374
          Flags(Index)       <= '1';
1375
 
1376
        when ALU_BTT => -- Z = !R0(N), N = R0(7)
1377 185 jshamlet
          Flags(PSR_Z)       <= not Regfile(0)(Index);
1378
          Flags(PSR_N)       <= Regfile(0)(7);
1379 169 jshamlet
 
1380
        when ALU_CLP => -- Clears bit(n) in the Flags register
1381
          Flags(Index)       <= '0';
1382
 
1383
        when ALU_T0X => -- Rn = R0 : Flags N,Z
1384
          Temp               := "0" & Regfile(0);
1385 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Temp(7 downto 0));
1386
          Flags(PSR_N)       <= Temp(7);
1387 169 jshamlet
          Regfile(Index)     <= Temp(7 downto 0);
1388
 
1389
        when ALU_CMP => -- Sets Flags on R0 - Rn : Flags N,C,Z
1390
          Sum                := ("0" & Regfile(0)) +
1391
                                ("1" & (not Regfile(Index))) +
1392
                                '1';
1393 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Sum(7 downto 0));
1394
          Flags(PSR_C)       <= Sum(8);
1395
          Flags(PSR_N)       <= Sum(7);
1396 169 jshamlet
 
1397
        when ALU_MUL => -- Stage 1 of 2 {R1:R0} = R0 * Rn : Flags Z
1398
          Regfile(0)         <= Mult(7 downto 0);
1399
          Regfile(1)         <= Mult(15 downto 8);
1400 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Mult);
1401 169 jshamlet
 
1402
        when ALU_LDI => -- Rn <= Data : Flags N,Z
1403 185 jshamlet
          Flags(PSR_Z)       <= nor_reduce(Operand1);
1404
          Flags(PSR_N)       <= Operand1(7);
1405
          Regfile(Index)     <= Operand1;
1406 169 jshamlet
 
1407
        when ALU_POP => -- Rn <= Data
1408 185 jshamlet
          Regfile(Index)     <= Operand1;
1409 169 jshamlet
 
1410
        when ALU_RFLG =>
1411 188 jshamlet
          Flags(3 downto 0)  <= Operand1(3 downto 0);
1412
          if( not RTI_Ignores_GP_Flags )then
1413
            Flags(7 downto 4)<= Operand1(7 downto 4);
1414
          end if;
1415 169 jshamlet
 
1416 185 jshamlet
        when ALU_RSP =>
1417 181 jshamlet
          Regfile(0)         <= Stack_Ptr(7 downto 0);
1418
          Regfile(1)         <= Stack_Ptr(15 downto 8);
1419
 
1420 185 jshamlet
        when ALU_GMSK =>
1421
          Flags(PSR_Z)       <= nor_reduce(Int_Mask);
1422
          Regfile(0)         <= Int_Mask;
1423
 
1424 169 jshamlet
        when others =>
1425
          null;
1426
      end case;
1427
 
1428 224 jshamlet
      Open8_Bus.GP_Flags     <= Flags(7 downto 3);
1429 188 jshamlet
 
1430 169 jshamlet
    end if;
1431
  end process;
1432
 
1433 182 jshamlet
-------------------------------------------------------------------------------
1434
-- Multiplier Logic
1435
--
1436
-- We need to infer a hardware multipler, so we create a special clocked
1437
--  process with no reset or clock enable
1438
-------------------------------------------------------------------------------
1439
 
1440
  Multiplier_proc: process( Clock )
1441
  begin
1442
    if( rising_edge(Clock) )then
1443
      Mult                   <= Regfile(0) *
1444 186 jshamlet
                                Regfile(conv_integer(ALU_Ctrl.Reg));
1445
    end if;
1446
  end process;
1447
 
1448
end architecture;

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.