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

Subversion Repositories light52

[/] [light52/] [trunk/] [vhdl/] [light52_pkg.vhdl] - Blame information for rev 8

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

Line No. Rev Author Line
1 2 ja_rd
--------------------------------------------------------------------------------
2
-- light52_pkg.vhdl -- Constants and utility functions for light52 core.
3
--------------------------------------------------------------------------------
4
-- Copyright (C) 2012 Jose A. Ruiz
5
--                                                              
6
-- This source file may be used and distributed without         
7
-- restriction provided that this copyright statement is not    
8
-- removed from the file and that any derivative work contains  
9
-- the original copyright notice and the associated disclaimer. 
10
--                                                              
11
-- This source file is free software; you can redistribute it   
12
-- and/or modify it under the terms of the GNU Lesser General   
13
-- Public License as published by the Free Software Foundation; 
14
-- either version 2.1 of the License, or (at your option) any   
15
-- later version.                                               
16
--                                                              
17
-- This source is distributed in the hope that it will be       
18
-- useful, but WITHOUT ANY WARRANTY; without even the implied   
19
-- warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR      
20
-- PURPOSE.  See the GNU Lesser General Public License for more 
21
-- details.                                                     
22
--                                                              
23
-- You should have received a copy of the GNU Lesser General    
24
-- Public License along with this source; if not, download it   
25
-- from http://www.opencores.org/lgpl.shtml
26
--------------------------------------------------------------------------------
27
 
28
library ieee;
29
use ieee.std_logic_1164.all;
30
use ieee.numeric_std.all;
31
 
32
--use work.txt_util.all;
33
 
34
package light52_pkg is
35
 
36
---- SFR addresses -------------------------------------------------------------
37
 
38
subtype t_byte is unsigned(7 downto 0);
39
 
40
-- These include only the CPU SFRs (B,ACC,PSW,DPH,DPL,SP,IE)
41
constant SFR_ADDR_ACC       : t_byte := X"E0";
42
constant SFR_ADDR_PSW       : t_byte := X"D0";
43
constant SFR_ADDR_B         : t_byte := X"F0";
44
constant SFR_ADDR_SP        : t_byte := X"81";
45
constant SFR_ADDR_DPH       : t_byte := X"83";
46
constant SFR_ADDR_DPL       : t_byte := X"82";
47
constant SFR_ADDR_IE        : t_byte := X"A8";
48
 
49
 
50
---- Configuration constants ---------------------------------------------------
51
 
52
---- Magic numbers - not to be changed! ----------------------------------------
53
constant BRAM_SIZE : integer := 512;
54
 
55
---- Basic types ---------------------------------------------------------------
56
 
57
subtype t_address is unsigned(15 downto 0);
58
subtype t_word is unsigned(15 downto 0);
59
subtype t_ebyte is unsigned(8 downto 0);
60
 
61
-- Decoding table; only has 128 16-bit entries, Rn opcodes are not included.
62
type t_ucode_bram is array(0 to BRAM_SIZE-1) of t_byte;
63
 
64
-- Decoding table entry.
65
subtype t_ucode is unsigned(15 downto 0);
66
-- Table of decoding words ('microcode'); one entry per opcode.
67
-- This is NOT the same as the decoding table; entries for Rn opcodes are not
68
-- used in the decoding table.
69
type t_ucode_table is array(0 to 255) of t_ucode;
70
 
71
-- Generic BRAM initialization constant.
72
type t_bram is array(integer range <>) of std_logic_vector(7 downto 0);
73
 
74
-- Object code (i.e. contents of code ROM). Length not related to BRAM size.
75
type t_obj_code is array(natural range <>) of std_logic_vector(7 downto 0);
76
-- Object code used by default if no other is given in the MCU generic.
77
constant default_object_code : t_obj_code(0 to 31) := (
78
    X"01", X"0f", X"00", X"56", X"67", X"78", X"89", X"9a",
79
    X"00", X"00", X"00", X"00", X"00", X"00", X"00", X"00",
80
    X"01", X"00", X"00", X"00", X"00", X"00", X"00", X"00",
81
    X"00", X"00", X"00", X"00", X"00", X"00", X"00", X"00"
82
    );
83
 
84
-- Internal state machine states. They are defined here so that they are visible
85
-- to the logging functions in the tb package.
86
type t_cpu_state is (
87
    reset_0,                    --
88
 
89
    -- Fetch & decode -----------------------------------------------
90
    fetch_0,                    -- pc in code_addr
91
    fetch_1,                    -- opcode in code_rd
92
    decode_0,                   -- microcode in BRAM output
93
 
94
    -- States for interrupt handling
95
    irq_1,                      -- SP++, Addr := irq_vector
96
    irq_2,                      -- SP++, RAM[AB]  := low(PC), AB := SP
97
    irq_3,                      -- RAM[AB]  := high(PC), AB := SP
98
    irq_4,                      -- long_jump
99
 
100
    -- States for LJMP
101
    fetch_addr_0,               -- Addr(L) := CODE
102
    fetch_addr_1,               -- Addr(H) := CODE
103
    fetch_addr_0_ajmp,          -- Addr(L) := CODE, Addr(H) := PC(H)|OPCODE
104
    long_jump,                  -- Do actual jump
105
 
106
    -- States for relative jump instructions 
107
    load_rel,                   --
108
    rel_jump,
109
 
110
    -- States for MUL & DIV
111
    alu_mul_0,
112
    alu_div_0,
113
 
114
    -- States for CJNE 
115
    cjne_a_imm_0,               -- T <- #imm
116
    cjne_a_imm_1,               -- byte1_reg <- rel
117
    cjne_a_imm_2,               -- do rel jump
118
 
119
    cjne_ri_imm_0,               -- AB,AR    := <Rx>
120
    cjne_ri_imm_1,               -- AR       := RAM[AB]
121
    cjne_ri_imm_2,               -- AB       := AR   
122
    cjne_ri_imm_3,               -- V        := RAM[AB], T := CODE
123
    cjne_ri_imm_4,               -- byte1_reg <- rel
124
    cjne_ri_imm_5,               -- do rel jump
125
 
126
    cjne_a_dir_0,               -- code_to_ab
127
    cjne_a_dir_1,               -- ram_to_t
128
    cjne_a_dir_2,               -- byte1_reg <- rel
129
    cjne_a_dir_3,               -- do rel jump
130
 
131
    cjne_rn_imm_0,              -- AB,AR    := <Rx>
132
    cjne_rn_imm_1,              -- V        := RAM[AR], T := CODE  
133
    cjne_rn_imm_2,              -- addr0_reg <- code
134
    cjne_rn_imm_3,              -- do rel jump
135
 
136
    -- States for MOVC instructions 
137
    movc_pc_0,
138
    movc_dptr_0,
139
    movc_1,
140
 
141
    -- States for ACALL & LCALL instructions
142
    acall_0,                    -- SP++, Addr(L) := CODE, Addr(H) := PC(H)|OPCODE    
143
    acall_1,                    -- RAM[AB]  := low(PC), AB := SP, SP++
144
    acall_2,                    -- RAM[AB]  := high(PC), AB := SP
145
    -- continues at long_jump
146
 
147
    lcall_0,                    -- Addr(L) := CODE
148
    lcall_1,                    -- SP++, Addr(H) := CODE
149
    lcall_2,                    -- SP++, RAM[AB]  := low(PC), AB := SP
150
    lcall_3,                    -- RAM[AB]  := high(PC), AB := SP
151
    lcall_4,                    -- long_jump
152
 
153
    -- States for JMP @A+DPTR
154
    jmp_adptr_0,                -- long jump with A+DPTR as target
155
 
156
    -- States for RET, RETI
157
    ret_0,                      -- Addr(H)  := RAM[B], SP--, AR,AB := SP
158
    ret_1,                      -- Addr(L)  := RAM[B], SP--, AR,AB := SP
159
    ret_2,                      -- long_jump    
160
    ret_3,
161
 
162
    -- States for DJNZ Rn
163
    djnz_rn_0,
164
 
165
    -- States for DJNZ dir
166
    -- From djnz_dir_1 onwards, they are common to DJNZ Rn; 
167
    -- TODO should rename common states
168
    djnz_dir_0,                 -- addr0_reg <- dir
169
    djnz_dir_1,                 -- T <- [dir]
170
    djnz_dir_2,                 -- [dir] <- alu result, 
171
    djnz_dir_3,                 -- addr0_reg <- code
172
    djnz_dir_4,                 -- do rel jump
173
 
174
    -- States for special instructions line INC DPTR.
175
    special_0,                  -- Do special deed
176
 
177
    -- States for MOV DPTR, #imm16
178
    mov_dptr_0,                 -- T        := CODE
179
    mov_dptr_1,                 -- T        := CODE, DPH := T
180
    mov_dptr_2,                 -- DPL      := T
181
 
182
    -- States for XCH instructions 
183
    xch_dir_0,                  -- AB,AR    := CODE
184
    xch_rn_0,                   -- AB,AR    := <Rx>
185
    xch_rx_0,                   -- AB,AR    := <Rx>
186
    xch_rx_1,                   -- AB,AR    := RAM[AB]
187
    xch_1,                      -- T        := RAM[AB]
188
    xch_2,                      -- RAM[AB]  := ALU (A,0)
189
    xch_3,                      -- A        := ALU (T,0)
190
 
191
    -- States for MOVX A,@Ri and MOVX @Ri,A
192
    movx_a_ri_0,
193
    movx_a_ri_1,
194
    movx_a_ri_2,
195
    movx_a_ri_3,
196
 
197
    movx_ri_a_0,
198
    movx_ri_a_1,
199
    movx_ri_a_2,
200
    movx_ri_a_3,
201
    movx_ri_a_4,
202
 
203
    -- states for MOVX A,@DPTR and MOVX @DPTR,A
204
    movx_dptr_a_0,
205
    movx_a_dptr_0,
206
 
207
    -- States for JBC, JB and JNB: bit-testing relative jumps
208
    jrb_bit_0,                  -- AB,AR    := bit<CODE>
209
    jrb_bit_1,                  -- T        := RAM[AB]
210
    jrb_bit_2,                  -- RAM[AR]  := ALU_BIT
211
    jrb_bit_3,                  -- addr0_reg <- code
212
    jrb_bit_4,                  -- do rel jump
213
 
214
    -- States for BIT instructions (CPL, CLR, SETB)
215
    bit_op_0,                   -- AB,AR    := bit<CODE>
216
    bit_op_1,                   -- T        := RAM[AB]
217
    bit_op_2,                   -- RAM[AR]  := ALU_BIT
218
 
219
    -- States for PUSH and POP 
220
    push_0,                     -- AB       := CODE
221
    push_1,                     -- T        := RAM[AB], SP++
222
    push_2,                     -- RAM[AB]  := ALU, AB := SP
223
 
224
    pop_0,                      -- AB       := SP
225
    pop_1,                      -- T        := RAM[B], SP--, AR,AB := CODE
226
    pop_2,                      -- RAM[AR]  := T
227
 
228
    -- States for DA A
229
    alu_daa_0,                  -- 1st stage of DA operation (low nibble)
230
    alu_daa_1,                  -- 2nd stage of DA operation (high nibble)
231
 
232
 
233
    -- States for XCHD A,@Ri
234
    alu_xchd_0,                 -- AB,AR    := <Rx>
235
    alu_xchd_1,                 -- AR       := RAM[AB]
236
    alu_xchd_2,                 -- AB       := AR
237
    alu_xchd_3,                 -- T        := RAM[AB]
238
    alu_xchd_4,                 -- RAM[AB]  := ALU
239
    alu_xchd_5,                 -- A        := ALU'
240
 
241
    -- States used to fetch operands and store result of ALU class instructions 
242
    alu_rx_to_ab,               -- AB,AR    := <Rx>
243
    alu_ram_to_ar,              -- AR       := RAM[AB]
244
    alu_ar_to_ab,               -- AB       := AR
245
    alu_ram_to_t,               -- T        := RAM[AB]
246
    alu_res_to_a,               -- A        := ALU
247
    alu_ram_to_t_code_to_ab,    -- T        := RAM[AR], AB,AR := CODE 
248
    alu_res_to_ram,             -- RAM[AB]  := ALU
249
    alu_code_to_ab,             -- AB,AR    := CODE
250
    alu_ram_to_t_rx_to_ab,      -- T        := RAM[AR], AB,AR := <Rx> 
251
    alu_ram_to_ar_2,            -- AR       := RAM[AB]    
252
    alu_res_to_ram_ar_to_ab,    -- RAM[AB]  := ALU,     AB := AR
253
    alu_res_to_ram_code_to_ab,  -- RAM[AB]  := ALU,     AB := CODE
254
    alu_code_to_t,              -- T        := CODE
255
    alu_ram_to_v_code_to_t,     -- V        := RAM[AR], T := CODE 
256
    alu_code_to_t_rx_to_ab,     -- T        := CODE,    AB,AR := <Rx>
257
 
258
    -- States used to fetch operands and store result os BIT class instructions
259
    bit_res_to_c,               -- C        := BIT_ALU
260
 
261
    -- Other states -------------------------------------------------
262
 
263
    bug_bad_addressing_mode,    -- Bad field in microcode word
264
    bug_bad_opcode_class,       -- Bad field in microcode word
265
    state_machine_derailed      -- State machine entered invalid state
266
    );
267
 
268
-- DIV_OVERLAP: how many cycles in the sequential divider overlap other state 
269
-- machine cycles.
270
-- This is the 2 first cycles of the instruction following DIV.
271
constant DIV_OVERLAP        : integer := 1;
272
-- MUL_OVERLAP: same as above, for sequential multiplier.
273
constant MUL_OVERLAP        : integer := 1;
274
 
275
 
276
---- Utility functions ---------------------------------------------------------
277
 
278
-- Computes ceil(log2(A)), e.g. address width of memory block.
279
-- CAN BE USED IN SYNTHESIZABLE CODE as long as called with constant arguments.
280
function log2(A : natural) return natural;
281
 
282
-- Builds a BRAM initialization constant from a constant byte array containing 
283
-- the microcode. The 256 bytes of microcode will be placed at the beginning
284
-- of the BRAM and the rest will be filled with zeros.
285
-- CAN BE USED IN SYNTHESIZABLE CODE to compute a BRAM initialization constant 
286
-- from a constant argument.
287
function ucode_to_bram(uC : t_ucode_table) return t_ucode_bram;
288
 
289
-- Builds BRAM initialization constant from a constant CONSTRAINED byte array
290
-- containing the application object code.
291
-- The object code is placed at the beginning of the BRAM and the rest is
292
-- filled with zeros.
293
-- CAN BE USED IN SYNTHESIZABLE CODE to compute a BRAM initialization constant 
294
-- from a constant argument.
295
function objcode_to_bram(oC : t_obj_code; size : integer) return t_bram;
296
 
297
end package light52_pkg;
298
 
299
 
300
--------------------------------------------------------------------------------
301
 
302
package body light52_pkg is
303
 
304
function log2(A : natural) return natural is
305
begin
306
    for I in 1 to 30 loop -- Works for up to 32 bit integers
307
        if(2**I >= A) then
308
            return(I);
309
        end if;
310
    end loop;
311
    return(30);
312
end function log2;
313
 
314
function ucode_to_bram(uC : t_ucode_table) return t_ucode_bram is
315
variable br : t_ucode_bram;
316
variable opcode, index: integer;
317
begin
318
    -- Copy uCode to start of BRAM...
319
    index := 0;
320
    for row in 0 to 7 loop
321
        for col in 0 to 15 loop
322
            opcode := col * 16 + row;
323
            --print(str(opcode, 16));
324
            --if uc(opcode) /= x"0000" then
325
            --    print(str(index,16)& " --> "& hstr(std_logic_vector(uc(opcode))));
326
            --end if;
327
            br(index*2 + 0) := uC(opcode)(15 downto 8);
328
            br(index*2 + 1) := uC(opcode)( 7 downto 0);
329
            index := index + 1;
330
        end loop;
331
    end loop;
332
 
333
    -- ... and fill the rest with zeros
334
    if BRAM_SIZE > 256 then
335
        br(256 to BRAM_SIZE-1) := (others => x"00");
336
    end if;
337
 
338
    return br;
339
end function ucode_to_bram;
340
 
341
function objcode_to_bram(oC : t_obj_code; size : integer) return t_bram is
342
variable br : t_bram(integer range 0 to size-1);
343
variable obj_size : integer;
344
begin
345
 
346
    -- If the object code table is longer than the array size, kill synthesis.
347
    assert oC'length <= size
348
    report "Object code does not fit in XCODE ROM."
349
    severity failure;
350
 
351
    obj_size := oC'length;
352
 
353
    -- Copy object code to start of BRAM...
354
    for i in 0 to obj_size-1 loop
355
        br(i) := oC(i);
356
    end loop;
357
 
358
    -- ... and fill the rest with zeros
359
    br(obj_size to size-1) := (others => x"00");
360
 
361
    return br;
362
end function objcode_to_bram;
363
 
364
end package body;
365
 

powered by: WebSVN 2.1.0

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