HierarchyFilesModulesSignalsTasksFunctionsHelp
Prev12345678
//output flush_ic_d_raw;
output fpu_mem_e;
output iu_iflush_e;
output [1:0] size_e;

// FORWARD DECLARATIONS

	wire [8:0] d_hop3 = d_opcode[10:2];
//	wire [8:0] w_hop3 = w_opcode[10:2];
//	wire ngot_data;
//	REGWIRE got_data;



/*
 * warthog to Data status signals
 *   let 'em know what kind of memop is in E and W
 */

	wire ld_op_d_op = valid_decode & ~TRAP & ~reset & (
		  d_hop3==`LDSB | d_hop3==`LDUB | d_hop3==`LDSH | d_hop3==`LDUH
		| d_hop3==`LD
		| d_hop3==`LDSBA | d_hop3==`LDUBA
		| d_hop3==`LDSHA | d_hop3==`LDUHA
		| d_hop3==`LDA
		| d_hop3==`LDD | d_hop3==`LDDA
		| d_hop3==`LDF | d_hop3==`LDDF
		| d_hop3==`LDFSR
		| d_hop3==`SWAP | d_hop3==`SWAPA
		| d_hop3==`LDSTB |d_hop3==`LDSTBA)
		;

	wire ld_op_d = ld_op_d_op;

	wire ld_op_e_op;
	Mflipflop_1 ld_op_e_op_reg_1(ld_op_e_op,ld_op_d_op,ss_clock,hold) ;

	wire ld_op_e = ld_op_e_op & ~reset & ~fold_annul; // & ~TRAP
	wire ld_op_e_mmu = ld_op_e;

	wire sgnd_ld_d = valid_decode & ~TRAP & ~reset & (
		  d_hop3==`LDSB | d_hop3==`LDSH
		| d_hop3==`LDSBA | d_hop3==`LDSHA)
		;

	wire sgnd_ld_e_op;
	Mflipflop_1 sgnd_ld_e_op_reg_1(sgnd_ld_e_op,sgnd_ld_d,ss_clock,hold) ;

	wire sgnd_ld_e = ~reset & ~fold_annul & sgnd_ld_e_op; 	//~TRAP

	wire st_op_d_op = valid_decode & ~TRAP & ~reset & (
		  d_hop3==`STB | d_hop3==`STBA
		| d_hop3==`STH | d_hop3==`STHA
		| d_hop3==`ST | d_hop3==`STA
		| d_hop3==`STD | d_hop3==`STDA
		| d_hop3==`STDFQ
		| d_hop3==`STF | d_hop3==`STDF
		| d_hop3==`STFSR
		| d_hop3==`SWAP | d_hop3==`SWAPA
		| d_hop3==`LDSTB |d_hop3==`LDSTBA)
		;

	wire st_op_d = st_op_d_op;

	wire st_op_e_op;
	Mflipflop_1 st_op_e_op_reg_1(st_op_e_op,st_op_d_op,ss_clock,hold) ;

	wire st_op_e = st_op_e_op & ~reset & ~fold_annul; // & ~TRAP
	wire st_op_e_mmu = st_op_e;

	wire fpu_mem_d_op = valid_decode & ~TRAP & ~reset & (
		  d_hop3==`LDF | d_hop3==`LDDF
		| d_hop3==`LDFSR
		| d_hop3==`STDFQ
		| d_hop3==`STF | d_hop3==`STDF
		| d_hop3==`STFSR)
		;

	wire fpu_mem_e_op;
	Mflipflop_1 fpu_mem_e_op_reg_1(fpu_mem_e_op,fpu_mem_d_op,ss_clock,hold) ;

	wire fpu_mem_e = fpu_mem_e_op & ~reset & ~fold_annul; // & ~TRAP

	wire iu_iflush_d = d_hop3==`IFLUSH & valid_decode & ~TRAP & ~reset;

	wire iu_iflush_e_op;
	Mflipflop_1 iu_iflush_e_op_reg_1(iu_iflush_e_op,iu_iflush_d,ss_clock,hold) ;

	wire iu_iflush_e = iu_iflush_e_op & ~reset & ~fold_annul; // & ~TRAP

/*
	// do the similar thing for iu_flush_ic_d - used to come from
	// D$ controller, but to save the boundary crossing, put it
	// in IU.

	wire sta_icflush_d =
		  st_op_d_op & nalternate_e
		& ~d_asi[5] & d_asi[4]
		;

	wire flush_ic_d_raw = iu_iflush_d | sta_icflush_d;

	REGWIRE flush_ic_e_op;
	REG(flush_ic_e_op_reg,1,flush_ic_e_op,flush_ic_d_raw,ss_clock,hold)

	wire flush_ic_e = flush_ic_e_op & ~reset & ~fold_annul;
 */

// iu_size indicates to the memory what size the memop is referencing
//		00	byte
//		01	half word
//		10	word
//		11	double word

	wire [1:0] size_e;
	wire [1:0] size_d;

//    all double and word sized memops have iu_size[1] = 1
	assign size_d[1] = valid_decode & ~reset & (
		  d_hop3==`LD
		| d_hop3==`LDA
		| d_hop3==`LDD | d_hop3==`LDDA
		| d_hop3==`LDF | d_hop3==`LDDF
		| d_hop3==`LDFSR
		| d_hop3==`ST | d_hop3==`STA
		| d_hop3==`STD | d_hop3==`STDA
		| d_hop3==`STDFQ
		| d_hop3==`STF | d_hop3==`STDF
		| d_hop3==`STFSR
		| d_hop3==`SWAP | d_hop3==`SWAPA
		| d_opcode==`HSTD0 | d_opcode==`HSTDA0
		| d_opcode==`HSWAP | d_opcode==`HSWAPA)
		;

//    all double and half word sized memops have iu_size[0] = 1
	assign size_d[0] = valid_decode & ~reset & (
		  d_hop3==`LDD | d_hop3==`LDDA
		| d_hop3==`LDDF
		| d_hop3==`STD | d_hop3==`STDA
		| d_hop3==`STDFQ
		| d_hop3==`STDF
		| d_hop3==`LDSH | d_hop3==`LDUH
		| d_hop3==`LDSHA | d_hop3==`LDUHA
		| d_hop3==`STH | d_hop3==`STHA
		| d_opcode==`HSTD0 | d_opcode==`HSTDA0)
		;

	Mflipflop_2 size_e_reg_2(size_e,size_d,ss_clock,hold) ;

/*
 * Puma Data Cache interface logic
 */

// Quick theory:  the data cache miss will be detected with the
// memop in R.  dmhold will be asserted at this time, which will
// hold Puma.  if the miss was caused by a ld op, then the data
// that missed will be returned along with the d_data_avail signal.
// Puma uses the d_data_avail to register the data.  Puma may
// continue with the pipeline normally during dmhold on the next
// clock cycle.  Puma may continue this way during dmhold until a
// memop reaches the w-stage or the d cache finishes its fill.
// Puma will hold until the dmhold is finished, if a memop is
// encountered in W.
//
// However, on LDST or SWAP, Puma may not continue after it
// receives the d_data_avail signal - this allows the store
// part of the instruction to complete correctly.
//
// Puma will put out the data address in D_MAR during the entire
// dmhold except for the last cycle of dmhold, indicatedby
// last_dmhold.  If Puma is being held, D_CAR will be put out
// on the address bus - otherwise the ALU output will go out
// (address generation).
//
// Since the data address is latched in a free-running register inside
// the cache RAM, we must adjust for pipeline holds in this mux select. 
// We do this by selecting the W-stage DCAR back around to this E-stage
// address output whenever there is a non-DMHOLD hold.


// Controls for Data cache CAR, CAR incrementer, and MAR
/*
 * not for warthog?
//	use temporarily - should be just dc_sustain_dmhold
	wire temp_dmhold = dc_sustain_dmhold | mm_start_dmhold;

	wire dcar_case1_part1 =
		(  w_hop3==SWAP | w_hop3==SWAPA
			| w_hop3==LDSTB |w_hop3==LDSTBA
			| w_hop3==STB | w_hop3==STBA
			| w_hop3==STH | w_hop3==STHA
			| w_hop3==ST | w_hop3==STA
			| w_hop3==STD | w_hop3==STDA
			| w_hop3==STDFQ
			| w_hop3==STF | w_hop3==STDF
			| w_hop3==STFSR  )
		;

	wire dcar_case1 = dcar_case1_part1 & ~temp_dmhold & ~hold;

	wire dcar_case2 = ~temp_dmhold & hold;

	wire dcar_case34_part1 = 
		 last_dmhold & (ngot_data | got_data)
		| (ngot_data | got_data) &
			( w_opcode==HLDD | w_opcode==HLDDA
			| w_opcode==HLDDF )
		;

	wire dcar_case34 = temp_dmhold & hold & dcar_case34_part1;

	wire sel_DC_dcar =
		dcar_case1 | dcar_case2 | dcar_case34 | dc_shold;

//     this version is used for byte mark selection only
	wire sel_DC_dcar_bm =
		dcar_case2 | dcar_case34 | dc_shold;

 // split these two up for speed
	wire sel_DC_dcar =
		~temp_dmhold & ~hold &
		(  w_hop3==SWAP | w_hop3==SWAPA
			| w_hop3==LDSTB |w_hop3==LDSTBA
			| w_hop3==STB | w_hop3==STBA
			| w_hop3==STH | w_hop3==STHA
			| w_hop3==ST | w_hop3==STA
			| w_hop3==STD | w_hop3==STDA
			| w_hop3==STDFQ
			| w_hop3==STF | w_hop3==STDF
			| w_hop3==STFSR  )
		| ~temp_dmhold & hold
		| temp_dmhold & hold & last_dmhold & (ngot_data | got_data)
		| temp_dmhold & hold & (ngot_data | got_data) &
			( w_opcode==HLDD | w_opcode==HLDDA
			| w_opcode==HLDDF )
		| dc_shold
		;

//     this version is used for byte mark selection only
	wire sel_DC_dcar_bm =
		  ~temp_dmhold & hold
		| temp_dmhold & hold & last_dmhold & (ngot_data | got_data)
		| temp_dmhold & hold & (ngot_data | got_data) &
			( w_opcode==HLDD | w_opcode==HLDDA
			| w_opcode==HLDDF )
		| dc_shold
		;

	wire sel_DC_dcar_inc_short =
			~ss_scan_mode &
			(  e_opcode==HLDD | e_opcode==HLDDA)
		;
//			| e_opcode==HLDDF
//			| e_opcode==HSTD1 | e_opcode==HSTDA1
//			| e_opcode==HSTDF1
//			| e_opcode==HSTDFQ1  )

	wire sel_DC_dcar_inc =
		  sel_DC_dcar_inc_short
//		& ~temp_dmhold & ~hold
		;
 *
 */

/*
 * also not for warthog?
	wire sel_DC_dmar =
		  temp_dmhold & ~ss_scan_mode &
			~(
				((ngot_data | got_data) &
				( w_opcode==HLDD | w_opcode==HLDDA
				| w_opcode==HLDDF ))
			|
				(last_dmhold & (ngot_data | got_data))
			 )
		;

	wire sel_DC_dmar_l = ~sel_DC_dmar;

	wire sel_DC_dmar_l = ~sel_DC_dmar;
	wire sel_DC_alu =
		 ~sel_DC_dcar & ~sel_DC_dcar_inc;


// these are used to select bits [3:2] for D$ address.  dc_sel_fillp
// comes from the D$

	wire sel_DClow_dmar = sel_DC_dmar & ~dc_sel_fillp & ~ss_scan_mode;
	wire sel_DClow_plain = ~sel_DClow_dmar & ~dc_sel_fillp;
 */


/*
 * not needed for warthog
// for byte marks
	wire sel_norm_bytemarks =
		  ~sel_DC_dmar & ~sel_DC_dcar_bm
		;
 */

/*
 * not needed for warthog
// got_data state machine - got_data should usually be 0.
// during a dmhold, when d_data_avail = 1, then in the next cycle
// got_data should be 1.  It should then hold this value
// until dmhold goes away.

	wire dmh_and_dda =
		  dc_sustain_dmhold
		& d_data_avail;

	wire gotd_muxsel =
		  dc_sustain_dmhold
		& got_data;

	CMUX2(gotd_mux,1,ngot_data,dmh_and_dda,got_data,gotd_muxsel)

//    free running register
	REG(gotd_reg,1,got_data,ngot_data,ss_clock,1'b0)
 */

/*
 * not needed for warthog
 * Fix for D$ and MMU - override hold on DOUT register when
 * receive dc_dout_done
	wire hold_dout_reg = hold & ~dc_dout_done;
 */

// -------------

/*
 * Remove BUSOP from SUNERGY - do direct decodes instead
 * Following are the direct decodes.
 */

// Generate byte marks for cache.  alu_out_lsb5[4:0] has low 5 order
// bits of d cache address (in E-cycle).  Need [1:0].

//	REGWIRE [1:0] w_alu_out_lsb2;
//	REG(alu_out_lsb2_reg,2, w_alu_out_lsb2, alu_out_lsb2, ss_clock, hold)

//	wire [0:3] byte_marks;

	wire [3:0] byte_bytemark = 4'b1000 >> alu_out_lsb2[1:0];
	wire [3:0] half_bytemark = 4'b1100 >> {alu_out_lsb2[1], 1'b0};
	wire [3:0] word_bytemark = 4'b1111;

	wire sel_byte_d =
		  d_hop3==`STB | d_hop3==`STBA
		| d_opcode==`HLDSTB | d_opcode==`HLDSTBA
		;

	wire sel_byte;
	Mflipflop_1 sel_byte_reg_1(sel_byte,sel_byte_d,ss_clock,hold) ;

	wire sel_half_d =
		  d_hop3==`STH | d_hop3==`STHA
		;
	wire sel_half;
	Mflipflop_1 sel_half_reg_1(sel_half,sel_half_d,ss_clock,hold) ;

	wire sel_word = ~sel_byte & ~sel_half;

	wire [3:0] almost_bytemark;
    // Expanded macro begin.
    // cmux3dnm(almost_bytemark_mux, 4, almost_bytemark,  		byte_bytemark,  sel_byte,  		half_bytemark,  sel_half,  		word_bytemark,  sel_word)
    function [4:1] almost_bytemark_mux ;
        input [4:1] in0_fn ;
        input s0_fn ;
        input [4:1] in1_fn ;
        input s1_fn ;
        input [4:1] in2_fn ;
        input s2_fn ;
        reg [4:1] out_fn ;
        begin
            case ({ sel_word,  sel_half,  sel_byte}) /* synopsys parallel_case */
                3'b001:         out_fn = in0_fn;
                3'b010: out_fn = in1_fn;
                3'b100:         out_fn = in2_fn;
                default:        out_fn = 65'hx;
            endcase
            almost_bytemark_mux = out_fn ;
        end
    endfunction
    assign almost_bytemark = almost_bytemark_mux( 		byte_bytemark,  sel_byte,  		half_bytemark,  sel_half,  		word_bytemark,  sel_word) ;
    // Expanded macro end.


	wire byte_mark0_e = almost_bytemark[3];
	wire byte_mark1_e = almost_bytemark[2];
	wire byte_mark2_e = almost_bytemark[1];
	wire byte_mark3_e = almost_bytemark[0];


//	assign byte_marks = almost_bytemark;

/*
 * OLD
	wire [0:3] byte_marks =
	    (e_hop3==LDSTB | e_hop3==LDSTBA | e_opcode==HLDSTB | e_opcode==HLDSTBA)	? (4'b1000 >> alu_out_lsb2[1:0]) : (
	    (e_hop3==STB | e_hop3==STBA)	? (4'b1000 >> alu_out_lsb2[1:0]) : (
	    (e_opcode==HSTB | e_opcode==HSTBA)	? (4'b1000 >> w_alu_out_lsb2[1:0]) : (
	    (e_hop3==STH | e_hop3==STHA)	? (4'b1100 >> {alu_out_lsb2[1], 1'b0}) : (
	    (e_opcode==HSTH | e_opcode==HSTHA)	? (4'b1100 >> {w_alu_out_lsb2[1], 1'b0}) : (
	    4'b1111 ))))) ;

not quite as old

	wire [0:3] byte_marks =
	    (e_opcode==HLDSTB | e_opcode==HLDSTBA)	? (4'b1000 >> w_alu_out_lsb2[1:0]) : (
	    (e_opcode==HSTB | e_opcode==HSTBA)	? (4'b1000 >> w_alu_out_lsb2[1:0]) : (
	    (e_opcode==HSTH | e_opcode==HSTHA)	? (4'b1100 >> {w_alu_out_lsb2[1], 1'b0}) : (
	    4'b1111 ))) ;

 *
 */
endmodule

[Up: Mdecode special_reg_control]
module Mspecial_reg_control(
	TRAP,
        ss_clock,
	d_opcode,
	dopc_hidiv0_op,
	dopc_himulcc2,
	dopc_hidivcc3,
        d_trap,
        e_hop3,
        et,
	fold_annul,
	help_ctr_0,
	help_ctr_1,
        hold,
	hnop_into_ex,
	htrap_into_ex,
	nERROR,
	ns,
        psm,
        reset,
	ss_scan_mode,
        sm,
	sv_rest_recirc,
        trap_cyc1,
        valid_decode,
	valid_decode_nilock,
        w_hop3,
        alternate_e,
        clret_sets,
        cwp_dec,
        cwp_hold,
        cwp_inc,
	cwp_recirc,
	wcwpm1,
	cwpp1,
	cwpm1,
	wcwp,
	cwp,
        e_jmpcallm,
        e_rdpsrm,
        e_rdtbrm,
        e_rdwimm,
        e_rdym,
	sel_pcspec_l,
        ecwp_next,
        hld_pilefec,
        hld_tba,
        hld_tt,
	n_hld_tt_scan,
        hld_wim,
        hold_cc,
        hold_ets,
        hold_ps,
        load_cc,
	nalternate_e,
        normal_asi0,
        rdtpcm,
        restore_cc,
        s_into_ps,
	setcc,
        setet_ps2s,
        w_wrpsr,
        write_cc,
        write_etps,
	e_rdpsr_op,
	e_rdtbr_op,
	e_rdwim_op,
	e_rdy_op,
	e_rdy_op_forilock,
	use_ps
);

input TRAP;
input ss_clock;
input dopc_hidiv0_op;
input dopc_himulcc2;
input dopc_hidivcc3;
input d_trap;
input [8:0] e_hop3;
input [10:0] d_opcode;
input et;
input fold_annul;
input help_ctr_0;
input help_ctr_1;
input hold;
input hnop_into_ex;
input htrap_into_ex;
input nERROR;
input ns;
input psm;
input reset;
input ss_scan_mode;
input sm;
input sv_rest_recirc;
input trap_cyc1;
input valid_decode;
input valid_decode_nilock;
input [8:0] w_hop3;

output alternate_e;
output clret_sets;
output cwp_dec;
output cwp_hold;
output cwp_inc;
output cwp_recirc;
output [2:0] wcwpm1;
output [2:0] cwpp1;
output [2:0] cwpm1;
input [2:0] wcwp;
input [2:0] cwp;
output e_jmpcallm;
output e_rdpsrm;
output e_rdtbrm;
output e_rdwimm;
output e_rdym;
output sel_pcspec_l;
output ecwp_next;
output hld_pilefec;
output hld_tba;
output hld_tt;
output n_hld_tt_scan;
output hld_wim;
output hold_cc;
output hold_ets;
output hold_ps;
output load_cc;
output nalternate_e;
output normal_asi0;
output rdtpcm;
output restore_cc;
output s_into_ps;
output setcc;
output setet_ps2s;
output w_wrpsr;
output write_cc;
output write_etps;
output e_rdpsr_op;
output e_rdtbr_op;
output e_rdwim_op;
output e_rdy_op;
output e_rdy_op_forilock;
output use_ps;

	wire w_wrwim;
	wire use_ps;
	wire use_ps_g;

	wire [8:0] d_hop3 = d_opcode[10:2];
	wire [2:0] e_hop = e_hop3[8:6];

	// SPECIAL MUX CONTROL

	wire rdtpc = TRAP | trap_cyc1;

	wire rdtpcm;
	Mflipflop_1 rdtpc_m_1( rdtpcm, rdtpc, ss_clock, hold) ;

	wire d_rdpsr_op = d_hop3==`RDPSR & valid_decode & ~TRAP;

	wire e_rdpsr_op;
	Mflipflop_1 e_rdpsr_op_reg_1(e_rdpsr_op,d_rdpsr_op,ss_clock,hold) ;

	wire e_rdpsr = e_rdpsr_op & ~TRAP;

	wire e_rdpsrm;
	Mflipflop_1 e_rdpsr_m_1( e_rdpsrm, e_rdpsr, ss_clock, hold) ;

	wire d_rdwim_op = d_hop3==`RDWIM & valid_decode & ~TRAP;

	wire e_rdwim_op;
	Mflipflop_1 e_rdwim_op_reg_1(e_rdwim_op,d_rdwim_op,ss_clock,hold) ;

	wire e_rdwim = e_rdwim_op & ~TRAP;

	wire e_rdwimm;
	Mflipflop_1 e_rdwim_m_1( e_rdwimm, e_rdwim, ss_clock, hold) ;

	wire e_rdy_op =
		  e_hop3==`RDY
		| dopc_hidiv0_op & (help_ctr_1 | help_ctr_0)
			& valid_decode_nilock
		;

	wire d_rdy_op_forilock = d_hop3==`RDY & valid_decode & ~TRAP;

	wire e_rdy_op_forilock;
	Mflipflop_1 e_rdy_op_forilock_reg_1(e_rdy_op_forilock,d_rdy_op_forilock, 		ss_clock,hold) ;


	wire e_rdy = e_rdy_op & ~TRAP;

	wire e_rdym;
	Mflipflop_1 e_rdy_m_1( e_rdym, e_rdy, ss_clock, hold) ;

	wire d_rdtbr_op = d_hop3==`RDTBR & valid_decode & ~TRAP;
	wire e_rdtbr_op;
	Mflipflop_1 e_rdtbr_op_reg_1(e_rdtbr_op,d_rdtbr_op,ss_clock,hold) ;

	wire e_rdtbr = e_rdtbr_op & ~TRAP;

	wire e_rdtbrm;
	Mflipflop_1 e_rdtbr_m_1( e_rdtbrm, e_rdtbr, ss_clock, hold) ;

	wire e_jmpcall_op = e_hop3==`JMP | e_hop==`CALL;

	wire e_jmpcall = e_jmpcall_op & ~TRAP;

	wire e_jmpcallm;
	Mflipflop_1 e_jmpcall_m_1( e_jmpcallm, e_jmpcall, ss_clock, hold) ;

	wire nsel_pcspec_l = ~(rdtpc | e_jmpcall | e_rdpsr | e_rdwim |
                e_rdy | e_rdtbr);

	wire sel_pcspec_l;
	Mflipflop_1 sel_pcspec_l_reg_1(sel_pcspec_l,nsel_pcspec_l,ss_clock,hold) ;

	// CWP CONTROL

	wire w_hop3wrpsr = w_hop3==`WRPSR;

	wire w_wrpsr = w_hop3wrpsr & ~TRAP;

/*
 * Because the MMU wants to see the G cycle version of the
 * iu_sup_inst signal, we must do some tricks.  The problem is
 * that if a wrpsr changes the S bit, it must be reflected in
 * the instruction fetch of the 4th instruction after the wrpsr.
 * Unfortunately, with the wrpsr in W (1 cycle before the write),
 * we are generating the address and iu_sup_inst_g for that instruction.
 * Therefore, we must generate iu_sup_inst_g with the S bit
 * that is about to be written (ns).
 *
 * Also, because the MMU drops the iu_sup_inst_g it had when a
 * imiss was detected, we must recirculate that value for the
 * mmu - that's why we have the pipeline register and mux.
	wire iu_sup_inst_gen_p1 =
		// synopsys translate_off
			(use_ps_g===1'bx) ? 'bx :
		// synopsys translate_on
		  (use_ps_g ? psm : sm);
	wire iu_sup_inst_gen = iu_sup_inst_gen_p1
				| w_wrpsr & ~reset & ns;

	wire iu_sup_inst_g = iu_sup_inst_gen;

 * MMU doesn't use iu_sup_inst_g anymore
*/

	wire d_save_op = d_hop3==`SAVE;

	wire d_save = valid_decode & d_save_op;

	wire d_restore_op = d_hop3==`RESTORE;

	wire d_restore = valid_decode & d_restore_op;

	wire d_rett_op = d_hop3==`RETT;

	wire d_rett = valid_decode & d_rett_op;

	wire cwp_inc = (d_restore | d_rett) & ~w_wrpsr & ~TRAP;

	wire cwp_dec = d_save & ~w_wrpsr & ~TRAP;

	wire cwp_hold = ~TRAP & ~d_save & ~d_restore & ~d_rett & ~w_wrpsr;

	wire ecwp_next = ~TRAP & ~w_wrpsr;

	wire cwp_recirc = sv_rest_recirc;

	wire [2:0] wcwpm1;
	wire [2:0] cwpp1;
	wire [2:0] cwpm1;

/*
 * for tsunami's 7 register windows
	assign cwpp1 =
		// synopsys translate_off
			((cwp==3'b110 || cwp==3'b111)===1'bx) ? 'bx :
		// synopsys translate_on
		(cwp==3'b110 || cwp==3'b111) ? 3'b000 : cwp + 3'b001;

	assign cwpm1 =
		// synopsys translate_off
			((cwp==3'b000)===1'bx) ? 'bx :
		// synopsys translate_on
		cwp==3'b000 ? 3'b110 : cwp - 3'b001;
	assign wcwpm1 =
		// synopsys translate_off
			((wcwp == 3'b000)===1'bx) ? 'bx :
		// synopsys translate_on
		wcwp == 3'b000 ? 3'b110 : wcwp - 3'b001;

// Decimal way
//	assign cwpp1 = (cwp==6 || cwp==7) ? 0 : cwp + 1;
//	assign cwpm1 = cwp == 0 ? 6 : cwp - 1;
//	assign wcwpm1 = wcwp == 0 ? 6 : wcwp - 1;

 */

	assign cwpp1 = cwp + 3'b001;
	assign cwpm1 = cwp - 3'b001;
	assign wcwpm1 = wcwp - 3'b001;

	// PSR CONTROL

	wire w_rett_op = w_hop3==`RETT;

	wire w_rett = w_rett_op & ~TRAP;

	wire clret_sets = TRAP | reset;

	wire setet_ps2s = w_rett & ~reset;

	wire write_etps = w_wrpsr & ~reset;

	wire hold_ets = ~TRAP & ~w_rett & ~w_wrpsr & ~reset;

	wire hld_pilefec = ~w_wrpsr;	// ss_clock hold for PIL, EF, and EC


	// PSR PS BIT CONTROL

	wire s_into_ps = TRAP & ~reset & ~nERROR;

	wire hold_ps = ~TRAP & ~w_wrpsr & ~reset
			| nERROR | reset;


	// CC CONTROL

	wire nsetcc_op = 
		  (d_hop3[8:5]==`ALU & d_hop3[4]
			& ~(
				  d_hop3==`UMULCC | d_hop3==`SMULCC
				| d_hop3==`UDIVCC | d_hop3==`SDIVCC
			   )
		  )
		| d_hop3==`TADDCC | d_hop3==`TADDCCTV
		| d_hop3==`TSUBCC | d_hop3==`TSUBCCTV
		| d_hop3==`MULSCC
		| dopc_himulcc2 | dopc_hidivcc3
		;

	wire nsetcc = valid_decode & ~TRAP & nsetcc_op;
	
	wire setcc_e;	// valid in E of setcc (was just setcc)
	Mflipflop_1 setcc_ff_1(setcc_e, nsetcc, ss_clock, hold) ;

	wire setcc = setcc_e & ~fold_annul;

	wire e_setcc = setcc & ~TRAP;

	wire w_setcc;		// valid in W of setcc
	Mflipflop_1 wsetcc_reg_1(w_setcc, e_setcc, ss_clock, hold) ;

	wire restore_cc = TRAP & w_setcc & ~ss_scan_mode;

	wire load_cc = setcc & ~TRAP & ~ss_scan_mode;	// valid in E of setcc

	wire write_cc = w_wrpsr & ~setcc & ~TRAP & ~ss_scan_mode;

	wire hold_cc = ~restore_cc & ~load_cc & ~write_cc;



	// WIM WRITE CONTROL

	wire w_hop3wrwim = w_hop3==`WRWIM;

	assign w_wrwim = w_hop3wrwim & ~TRAP;

	wire hld_wim = ~w_wrwim;



	// TBR WRITE CONTROL

	wire w_hop3wrtbr = w_hop3==`WRTBR;

	wire hld_tba = ~(w_hop3wrtbr & ~TRAP);

	wire hld_tt = ~TRAP
			| (~w_rett_op & ~et);

	wire n_hld_tt_scan = ~hld_tt;

	// ASI CONTROL

/* Notes:
 * This stuff to detect RETT at the DIN in Suntan is motivated by
 * a potential problem with the jmp/rett combination.  When
 * returning from a trap, the ASI are supervisor.  The jmp
 * back to the user code should have user ASI.  The fetch
 * of the RETT should have supervisor ASI.

	// detect RETT at output of DIN master register
	// NOTE that 8'b01_000110 is the RETT opcode inverted

	wire d_rett_din =
		  in_dec_hi[31:30]==2'b10
		& in_dec_mid[24:19]==6'b111001
		;
 */

	// must use PS instead of S to generate ASI's during
	// D, E, and W cycles of RETT

	wire rett_in_w = w_hop3==`RETT;

	assign use_ps = e_hop3==`RETT | rett_in_w;

/*
 * for tsunami
	assign use_ps = 
		    ((w_hop3==JMP & d_hop3==RETT & valid_decode_nilock
		      & ~d_trap)
			| e_hop3==RETT
			| rett_in_w);
 */

	assign use_ps_g =
		~TRAP &
		   ((d_hop3==`RETT & valid_decode_nilock & ~d_trap)
		      | e_hop3==`RETT | rett_in_w
		   )
		;
	
	// get ASI's from opcode pipeline due to an alternate space load
	// or store

//	wire alternate_e =
//		e_hop3[8:4]==MEMA | e_hop3[8:4]==HMEMA;
// as per MMU request, don't assert during helps.
//  they changed their minds - they want asi's for hldda

	wire nalternate_e =
		~hnop_into_ex & ~htrap_into_ex
		& (d_hop3[8:4]==`MEMA | d_opcode==`HLDDA)
		;

	wire alternate_e;
	Mflipflop_1 alternate_e_reg_1(alternate_e,nalternate_e,ss_clock,hold) ;

// these used to have ~TRAP and ~reset in them
//	wire alternate_e = alternate_e_op;

	// the usual ASI's (non alternate)

	wire normal_asi0 = (~use_ps & sm) | (use_ps & sm & psm);

endmodule



[Up: Miuchip decode]
module Mdecode (
		hld_dirreg, hld_dirreg_rf,
		cwpm_, ecwpm_,
		TRAP, trapcode, resultMSB, result_lo,
		high_2_1, idiv_shiftin_low, alu_s1m_0,
		byte_mark0_e, byte_mark1_e, byte_mark2_e, byte_mark3_e,
		sadr_tbr, sadr_jmprett,
		sadr_zero,
		hld_dpc, hld_dum_dpc,
		alus1_b1m, alus1_b2m, alus1_b3m, alus1_datam,
		alus1_rfm_b3m,
		alus1_setm,
		alus2_b1m, alus2_b2m, alus2_b3m, alus2_datam,
		byp_res3, byp_wr3, byp_rf3,
		a2top_default, rs2_passit,
		alu_s2_reg_hold,
		alu_s2m_5_0, src2m_lo,
		rs1_pass, spc_mux_default,
		rs1_clear, rs1_double, nrs1_negate, nrs1_negate_l,
		sel_srl2_mult, rs2_clear, nsel_w_mult,
		nsel_w_mult_l_b, nsel_w_mult_l_not_b,
		sel_sll1_divalu, sel_sll1_divalu_l,
		msign_bit, src1m_msb, dsign_bit2, 
		rf2_imm_data_msb, dsign_bit1,
		hold_Wreg,
		eopc_hidiv3,
		use_hi_y, use_hi_alu, use_hi_rs1_default,
		use_hi_rs2, use_low_rs1, use_hi_rs2_default, not_rs2_rs1_default,
		alus1_b2_shift, sel_rs1_shiftin,
		alu_ADD, alu_AND, alu_XNOR,
		shift_left, arith_shift,
		ym,
		alu_cc_next, 
		ccN_noninv,
		ccZ_noninv,
		ccm,
		ne_mulsm, next_e_not_negmul, hld_y, 
		wr_y, wr_mulscc, n_ymsb,
		carry_in, pass_hi_rs1,
		det_divovf,
		tagged_ovf, alu_sub,
		alu_s1s_lsb2,
		rs_from_alu, rs_from_else, rs_from_sh,
		force_neg, force_pos,
		e_rdpsrm, e_rdwimm, e_rdym, e_rdtbrm, e_jmpcallm, sel_pcspec_l, rdtpcm,
		w_wrpsr,
		hold_cc, load_cc, write_cc, restore_cc,
		clret_sets, setet_ps2s, write_etps, hold_ets,
		s_into_ps, hold_ps, hld_pilefec,
		cwp_inc, wcwpm1, cwpp1, cwpm1, wcwp, cwp, cwp_dec,
		cwp_hold, ecwp_next,
		cwp_recirc,
		hld_wim, wimm,
		hld_tba, hld_tt, n_hld_tt_scan,
        	wr_lddatam_l,
		word_store_d, half_store_d, byte_store_d,
		s, ns, psm, et, ef, pil,
		alu_out_lsb5,
		mm_dacc_exc_w,
		mm_dacc_err_w,
		mm_dacc_mmu_miss_w,
		mm_dacc_wp_w,
		iu_mm_iacc_wp_exc_d,
		start_itag_inv,
		q3_iae, q3_ptc, q2_iae, q2_ptc, q1_iae, q1_ptc,
		stop_fetch, did_fetch,
		this_s, sup_ex_trap,
		FEXC,
		iwait_f, dwait_w_for_flush,
		ld_op_e, ld_op_e_mmu, ld_op_d, sgnd_ld_e,
		st_op_e, st_op_e_mmu, st_op_d,
		fpu_mem_e, size_e,
		hld_car_mar, hld_lgens,
		rf_we_w,
		error_mode,
		ER_SDOUT,
		pfcc, pfccv,
		ss_clock, hold, hold_noic, hold_ic, // extend_tag_miss,
		enbl_br_fold,
		w_hhn_2,
		lta_hold, reset,
		iu_iflush_e,
		valid_decode,
		select_FP_DOUT, sel_ldstb_1, select_IU_DOUT,
		IU_in_trap, IU_in_trap4fpu, IU_in_trap4dc,
		FXACK,
		ss_reset, IRL, iu_asi_e,
		sel_lta_fpc, sel_idpc_fpc, sel_post_reset,
		sel_p_fpc, sel_alt_tag, sel_i1pfpc_fpc, sel_i2dpc_fpc,
		fetch_ic_even, fetch_ic_odd, fetch_TOQ,
		fetch_alt, fetch_SIQ, ncant_unload,
		hold_alt, fold_annul,
		sel_shift1, sel_shift2, sel_shift3,
		sel_fold1, sel_fold2, sel_even1, sel_odd1, hold_q1,
		sel_even2, sel_odd2, hold_q2,
		sel_even3, sel_odd3, hold_q3,
		hold_q4,
		hld_backup, take_icdata, sel_old_aa, hld_dir2,
		sel_last_gen, recirc2_default,
		sel_inc_ll_gen, sel_inc_dpc, sel_inc_alttag,
		sel_gpc, sel_recirc, sel_recirc_inc,
		sel_lgen_iva,
		sel_gpc_ic, sel_recirc_ic, sel_recirc_inc_ic,
		sadr_zero_ic,
		force_ifill, flush_ic_e, force_dva, sel_lgen_ica,
		fwd_wpc, use_tpc, fwd_tpcm4,
		toq_entry_bits, nq1_entry_hi, iexc_for_br, niexc1_hi,
		iexc_for_int_hi,
		fpc_low, nlta_low, ndpc_low, nalttag_low,
		ic_force_ifill_g, mm_istat_avail, i_dva_req,
		iu_event,
		nbrs1_decm, brs3_d, nr_rdp,
		in_dec_lo22, d_imm_l,
		iu_sfs_sup,
		iu_sfs_perr, iu_sfs_xerr, iu_sfs_mmiss,
		iu_sfs_iae, iu_sfs_sbe, iu_sfs_sto,
		iu_sfs_prtct, iu_sfs_priv, iu_sfs_lvl,
		w_op, w_op3_5, w_op3_3, w_op3_2, w_op3_0,
		inst_for_int,
		ndec_inst_traps, ncwpm_l,
		ss_scan_mode, Mdecode_scan_in, Mdecode_scan_out
	);


// OPCODES FROM IR PIPE

/* don't need cuz Mir is in Mdecode now
input [1:0] d_op;		// OP in decode
input [5:0] d_op3;		// OP3 in decode
input [1:0] e_op;		// OP in execute
input [5:0] e_op3;		// OP3 in execute
input [1:0] w_op;		// OP in write
input [5:0] w_op3;		// OP3 in write

input d_imm;			// Immediate bit from decode
input d_anl;			// decode annul bit
input [3:0] d_cond;		// conf field in decode
input [5:4] d_asi;
 */
Next12345678
HierarchyFilesModulesSignalsTasksFunctionsHelp

This page: Created:Thu Aug 19 11:57:32 1999
From: ../../../sparc_v8/ssparc/iu/Mdecode/rtl/decode.v

Verilog converted to html by v2html 5.0 (written by Costas Calamvokis).Help