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

Subversion Repositories light52

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

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

powered by: WebSVN 2.1.0

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