Skip to content
Snippets Groups Projects
Commit 14386f52 authored by Kenneth Hiemstra's avatar Kenneth Hiemstra
Browse files

PMBUS additions

parent ede9fb89
No related branches found
No related tags found
No related merge requests found
...@@ -16,10 +16,14 @@ synth_files = ...@@ -16,10 +16,14 @@ synth_files =
# src/vhdl/unb2_board_clk200mm_pll.vhd # src/vhdl/unb2_board_clk200mm_pll.vhd
src/vhdl/unb2_board_wdi_extend.vhd src/vhdl/unb2_board_wdi_extend.vhd
src/vhdl/unb2_board_node_ctrl.vhd src/vhdl/unb2_board_node_ctrl.vhd
src/vhdl/unb2_board_pmbus_ctrl.vhd
src/vhdl/unb2_board_sens_ctrl.vhd src/vhdl/unb2_board_sens_ctrl.vhd
src/vhdl/unb2_board_pmbus.vhd
src/vhdl/unb2_board_sens.vhd src/vhdl/unb2_board_sens.vhd
src/vhdl/unb2_board_pmbus_reg.vhd
src/vhdl/unb2_board_sens_reg.vhd src/vhdl/unb2_board_sens_reg.vhd
src/vhdl/unb2_fpga_sens_reg.vhd src/vhdl/unb2_fpga_sens_reg.vhd
src/vhdl/mms_unb2_board_pmbus.vhd
src/vhdl/mms_unb2_board_sens.vhd src/vhdl/mms_unb2_board_sens.vhd
src/vhdl/mms_unb2_fpga_sens.vhd src/vhdl/mms_unb2_fpga_sens.vhd
src/vhdl/unb2_board_wdi_reg.vhd src/vhdl/unb2_board_wdi_reg.vhd
......
-------------------------------------------------------------------------------
--
-- Copyright (C) 2012-2015
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
-- Purpose : MMS for unb2_board_pmbus
-- Description: See unb2_board_pmbus.vhd
LIBRARY IEEE, common_lib;
USE IEEE.STD_LOGIC_1164.ALL;
USE IEEE.NUMERIC_STD.ALL;
USE common_lib.common_pkg.ALL;
USE common_lib.common_mem_pkg.ALL;
ENTITY mms_unb2_board_pmbus IS
GENERIC (
g_sim : BOOLEAN := FALSE;
--g_clk_freq : NATURAL := 8*10**6; -- (to be checked) this (re)calculation lets the I2C bus run at ~300kHz @ mm_clk=50MHz
g_clk_freq : NATURAL := 100*10**6; -- clk frequency in Hz
g_temp_high : NATURAL := 85
);
PORT (
-- Clocks and reset
mm_rst : IN STD_LOGIC; -- reset synchronous with mm_clk
mm_clk : IN STD_LOGIC; -- memory-mapped bus clock
mm_start : IN STD_LOGIC;
-- Memory-mapped clock domain
reg_mosi : IN t_mem_mosi := c_mem_mosi_rst; -- actual ranges defined by c_mm_reg
reg_miso : OUT t_mem_miso; -- actual ranges defined by c_mm_reg
-- i2c bus
scl : INOUT STD_LOGIC := '0';
sda : INOUT STD_LOGIC := '0';
-- Temperature alarm output
temp_alarm : OUT STD_LOGIC
);
END mms_unb2_board_pmbus;
ARCHITECTURE str OF mms_unb2_board_pmbus IS
CONSTANT c_sens_nof_result : NATURAL := 4; -- Should match nof read bytes via I2C in the unb2_board_pmbus_ctrl SEQUENCE list
CONSTANT c_temp_high_w : NATURAL := 7; -- Allow user to use only 7 (no sign, only positive) of 8 bits to set set max temp
SIGNAL sens_err : STD_LOGIC;
SIGNAL sens_data : t_slv_16_arr(0 TO c_sens_nof_result-1);
SIGNAL temp_high : STD_LOGIC_VECTOR(c_temp_high_w-1 DOWNTO 0);
BEGIN
u_unb2_board_pmbus_reg : ENTITY work.unb2_board_pmbus_reg
GENERIC MAP (
g_sens_nof_result => c_sens_nof_result,
g_temp_high => g_temp_high
)
PORT MAP (
-- Clocks and reset
mm_rst => mm_rst,
mm_clk => mm_clk,
-- Memory Mapped Slave in mm_clk domain
sla_in => reg_mosi,
sla_out => reg_miso,
-- MM registers
sens_err => sens_err,
sens_data => sens_data,
-- Max temp threshold
temp_high => temp_high
);
u_unb2_board_pmbus : ENTITY work.unb2_board_pmbus
GENERIC MAP (
g_sim => g_sim,
g_clk_freq => g_clk_freq,
g_temp_high => g_temp_high,
g_sens_nof_result => c_sens_nof_result
)
PORT MAP (
clk => mm_clk,
rst => mm_rst,
start => mm_start,
-- i2c bus
scl => scl,
sda => sda,
-- read results
sens_evt => OPEN,
sens_err => sens_err,
sens_data => sens_data
);
-- Temperature: 7 bits (1 bit per degree) plus sign. A faulty readout (never pulled down = all ones)
-- would produce -1 degrees so does not trigger a temperature alarm.
-- temp_high is 7 bits, preceded by a '0' to allow only positive temps to be set.
temp_alarm <= '1' WHEN (SIGNED(sens_data(0)) > SIGNED('0' & temp_high)) ELSE '0';
END str;
...@@ -162,10 +162,10 @@ PACKAGE unb2_board_peripherals_pkg IS ...@@ -162,10 +162,10 @@ PACKAGE unb2_board_peripherals_pkg IS
reg_fpga_voltage_sens_adr_w : NATURAL; -- = 4 reg_fpga_voltage_sens_adr_w : NATURAL; -- = 4
-- pi_unb_pmbus -- pi_unb_pmbus
reg_unb_pmbus_adr_w : NATURAL; -- = 3 reg_unb_pmbus_adr_w : NATURAL; -- = 5
END RECORD; END RECORD;
CONSTANT c_unb2_board_peripherals_mm_reg_default : t_c_unb2_board_peripherals_mm_reg := (TRUE, 10, 4, 10, 5, 10, 1, 1, 3, 1, 1, 1, 1, 1, 3, 3, 3, 16, 4, 6, 2, 2, 1, 4, 3, 6, 13, 12, 2, 32, 8, 2, 8, 10, 16, 1024, 14, 5, 3, 11, 2, 3, 5, 16, 11, 3, 1, 3, 4, 3); CONSTANT c_unb2_board_peripherals_mm_reg_default : t_c_unb2_board_peripherals_mm_reg := (TRUE, 10, 4, 10, 5, 10, 1, 1, 3, 1, 1, 1, 1, 1, 3, 3, 3, 16, 4, 6, 2, 2, 1, 4, 3, 6, 13, 12, 2, 32, 8, 2, 8, 10, 16, 1024, 14, 5, 3, 11, 2, 3, 5, 16, 11, 3, 1, 3, 4, 5);
END unb2_board_peripherals_pkg; END unb2_board_peripherals_pkg;
......
-------------------------------------------------------------------------------
--
-- Copyright (C) 2012-2014
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
LIBRARY IEEE, common_lib, i2c_lib;
USE IEEE.std_logic_1164.ALL;
USE common_lib.common_pkg.ALL;
USE i2c_lib.i2c_pkg.ALL;
ENTITY unb2_board_pmbus is
GENERIC (
g_sim : BOOLEAN := FALSE;
g_clk_freq : NATURAL := 100*10**6; -- clk frequency in Hz
g_temp_high : NATURAL := 85;
g_sens_nof_result : NATURAL := 4 -- Should match nof read bytes via I2C in the unb2_board_pmbus_ctrl SEQUENCE list
);
PORT (
rst : IN STD_LOGIC;
clk : IN STD_LOGIC;
start : IN STD_LOGIC;
-- i2c bus
scl : INOUT STD_LOGIC;
sda : INOUT STD_LOGIC;
-- read results
sens_evt : OUT STD_LOGIC;
sens_err : OUT STD_LOGIC;
sens_data : OUT t_slv_16_arr(0 TO g_sens_nof_result-1)
);
END ENTITY;
ARCHITECTURE str OF unb2_board_pmbus IS
-- I2C clock rate settings
CONSTANT c_sens_clk_cnt : NATURAL := sel_a_b(g_sim, 1, func_i2c_calculate_clk_cnt(g_clk_freq/10**6)); -- define I2C clock rate
CONSTANT c_sens_comma_w : NATURAL := 0; -- 2**c_i2c_comma_w * system clock period comma time after I2C start and after each octet
-- 0 = no comma time
CONSTANT c_sens_phy : t_c_i2c_phy := (c_sens_clk_cnt, c_sens_comma_w);
SIGNAL smbus_in_dat : STD_LOGIC_VECTOR(c_byte_w-1 DOWNTO 0);
SIGNAL smbus_in_val : STD_LOGIC;
SIGNAL smbus_out_dat : STD_LOGIC_VECTOR(c_byte_w-1 DOWNTO 0);
SIGNAL smbus_out_val : STD_LOGIC;
SIGNAL smbus_out_err : STD_LOGIC;
SIGNAL smbus_out_ack : STD_LOGIC;
SIGNAL smbus_out_end : STD_LOGIC;
BEGIN
u_unb2_board_pmbus_ctrl : ENTITY work.unb2_board_pmbus_ctrl
GENERIC MAP (
g_sim => g_sim,
g_nof_result => g_sens_nof_result,
g_temp_high => g_temp_high
)
PORT MAP (
clk => clk,
rst => rst,
start => start,
in_dat => smbus_out_dat,
in_val => smbus_out_val,
in_err => smbus_out_err,
in_ack => smbus_out_ack,
in_end => smbus_out_end,
out_dat => smbus_in_dat,
out_val => smbus_in_val,
result_val => sens_evt,
result_err => sens_err,
result_dat => sens_data
);
u_i2c_smbus : ENTITY i2c_lib.i2c_smbus
GENERIC MAP (
g_i2c_phy => c_sens_phy
)
PORT MAP (
gs_sim => g_sim,
clk => clk,
rst => rst,
in_dat => smbus_in_dat,
in_req => smbus_in_val,
out_dat => smbus_out_dat,
out_val => smbus_out_val,
out_err => smbus_out_err,
out_ack => smbus_out_ack,
st_end => smbus_out_end,
scl => scl,
sda => sda
);
END ARCHITECTURE;
-------------------------------------------------------------------------------
--
-- Copyright (C) 2012-2014
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
LIBRARY IEEE, common_lib, i2c_lib;
USE IEEE.std_logic_1164.ALL;
USE i2c_lib.i2c_smbus_pkg.ALL;
USE i2c_lib.i2c_dev_max1617_pkg.ALL;
USE i2c_lib.i2c_dev_ltc4260_pkg.ALL;
USE common_lib.common_pkg.ALL;
ENTITY unb2_board_pmbus_ctrl IS
GENERIC (
g_sim : BOOLEAN := FALSE;
g_nof_result : NATURAL := 4;
g_temp_high : NATURAL := 85
);
PORT (
rst : IN STD_LOGIC;
clk : IN STD_LOGIC;
start : IN STD_LOGIC; -- pulse to start the I2C sequence to read out the sensors
out_dat : OUT STD_LOGIC_VECTOR(c_byte_w-1 DOWNTO 0);
out_val : OUT STD_LOGIC;
in_dat : IN STD_LOGIC_VECTOR(c_byte_w-1 DOWNTO 0);
in_val : IN STD_LOGIC;
in_err : IN STD_LOGIC;
in_ack : IN STD_LOGIC;
in_end : IN STD_LOGIC;
result_val : OUT STD_LOGIC;
result_err : OUT STD_LOGIC;
result_dat : OUT t_slv_16_arr(0 TO g_nof_result-1)
);
END ENTITY;
ARCHITECTURE rtl OF unb2_board_pmbus_ctrl IS
-- I2C slave addresses for the PMBUS, power module readouts
CONSTANT LOC_POWER_CORE : NATURAL := 16#01#;
CONSTANT LOC_POWER_ERAM : NATURAL := 16#0D#;
CONSTANT LOC_POWER_TR_R : NATURAL := 16#0E#;
CONSTANT LOC_POWER_TR_T : NATURAL := 16#0F#;
CONSTANT LOC_POWER_BAT : NATURAL := 16#10#;
CONSTANT LOC_POWER_IO : NATURAL := 16#11#;
-- Each slave has these registers:
CONSTANT LP_VOUT_MODE : NATURAL := 16#20#;
CONSTANT LP_VOUT : NATURAL := 16#8B#;
CONSTANT LP_IOUT : NATURAL := 16#8C#;
CONSTANT LP_TEMP : NATURAL := 16#8D#;
TYPE t_SEQUENCE IS ARRAY (NATURAL RANGE <>) OF NATURAL;
-- The I2C bit rate is c_i2c_bit_rate = 50 [kbps], so 20 us period. Hence 20 us wait time for SDA is enough
-- Assume clk <= 200 MHz, so 5 ns period. Hence timeout of 4000 is enough.
CONSTANT c_timeout_sda : NATURAL := sel_a_b(g_sim, 0, 16); -- wait 16 * 256 = 4096 clk periods
CONSTANT c_SEQ : t_SEQUENCE := (
-- SMBUS_READ_BYTE , LOC_POWER_CORE, LP_VOUT_MODE,
-- SMBUS_READ_WORD , LOC_POWER_CORE, LP_VOUT,
-- SMBUS_READ_WORD , LOC_POWER_CORE, LP_IOUT,
-- SMBUS_READ_WORD , LOC_POWER_CORE, LP_TEMP,
--SMBUS_READ_BYTE , LOC_POWER_ERAM, LP_VOUT_MODE,
-- SMBUS_READ_WORD , LOC_POWER_ERAM, LP_VOUT,
-- SMBUS_READ_WORD , LOC_POWER_ERAM, LP_IOUT,
-- SMBUS_READ_WORD , LOC_POWER_ERAM, LP_TEMP,
--
SMBUS_READ_BYTE , LOC_POWER_TR_R, LP_VOUT_MODE,
SMBUS_READ_WORD , LOC_POWER_TR_R, LP_VOUT,
SMBUS_READ_WORD , LOC_POWER_TR_R, LP_IOUT,
SMBUS_READ_WORD , LOC_POWER_TR_R, LP_TEMP,
--
-- --SMBUS_READ_BYTE , LOC_POWER_TR_T, LP_VOUT_MODE,
-- SMBUS_READ_WORD , LOC_POWER_TR_T, LP_VOUT,
-- SMBUS_READ_WORD , LOC_POWER_TR_T, LP_IOUT,
-- SMBUS_READ_WORD , LOC_POWER_TR_T, LP_TEMP,
--
-- --SMBUS_READ_BYTE , LOC_POWER_BAT, LP_VOUT_MODE,
-- SMBUS_READ_WORD , LOC_POWER_BAT, LP_VOUT,
-- SMBUS_READ_WORD , LOC_POWER_BAT, LP_IOUT,
-- SMBUS_READ_WORD , LOC_POWER_BAT, LP_TEMP,
--
-- --SMBUS_READ_BYTE , LOC_POWER_IO, LP_VOUT_MODE,
-- SMBUS_READ_WORD , LOC_POWER_IO, LP_VOUT,
-- SMBUS_READ_WORD , LOC_POWER_IO, LP_IOUT,
-- SMBUS_READ_WORD , LOC_POWER_IO, LP_TEMP,
SMBUS_C_SAMPLE_SDA, 0, c_timeout_sda, 0, 0,
SMBUS_C_END,
SMBUS_C_NOP
); -- = (7 24 1) (7 77 1) (7 68 4) (7 68 5) (20, timeout[0:3]) (19)
CONSTANT c_seq_len : NATURAL := c_SEQ'LENGTH-1; -- upto SMBUS_C_END, the SMBUS_C_NOP is dummy to allow sufficient seq_cnt range
-- The protocol list c_SEQ yields a list of g_nof_result=14 result bytes:
-- . expected SMBUS_READ_BYTE -> rdbyte, ok=0
-- . expected SMBUS_WRITE_BYTE -> ok=0
-- . expected SMBUS_C_END -> ok=0
-- ==> so expected result_dat[0:4] = [rdbyte, rdbyte, rdbyte, rdbyte, rdbyte]
SIGNAL start_reg : STD_LOGIC;
SIGNAL seq_cnt : NATURAL RANGE 0 TO c_seq_len := c_seq_len;
SIGNAL nxt_seq_cnt : NATURAL;
SIGNAL rx_cnt : NATURAL RANGE 0 TO g_nof_result;
SIGNAL nxt_rx_cnt : NATURAL;
SIGNAL rx_val : STD_LOGIC;
SIGNAL nxt_rx_val : STD_LOGIC;
SIGNAL rx_err : STD_LOGIC;
SIGNAL nxt_rx_err : STD_LOGIC;
SIGNAL rx_dat : t_slv_16_arr(result_dat'RANGE);
SIGNAL nxt_rx_dat : t_slv_16_arr(result_dat'RANGE);
SIGNAL nxt_result_val : STD_LOGIC;
SIGNAL nxt_result_err : STD_LOGIC;
SIGNAL i_result_dat : t_slv_16_arr(result_dat'RANGE);
SIGNAL nxt_result_dat : t_slv_16_arr(result_dat'RANGE);
BEGIN
result_dat <= i_result_dat;
regs: PROCESS(rst, clk)
BEGIN
IF rst='1' THEN
start_reg <= '0';
seq_cnt <= c_seq_len;
rx_cnt <= 0;
rx_val <= '0';
rx_err <= '0';
rx_dat <= (OTHERS=>(OTHERS=>'0'));
result_val <= '0';
result_err <= '0';
i_result_dat <= (OTHERS=>(OTHERS=>'0'));
ELSIF rising_edge(clk) THEN
start_reg <= start;
seq_cnt <= nxt_seq_cnt;
rx_cnt <= nxt_rx_cnt;
rx_val <= nxt_rx_val;
rx_err <= nxt_rx_err;
rx_dat <= nxt_rx_dat;
result_val <= nxt_result_val;
result_err <= nxt_result_err;
i_result_dat <= nxt_result_dat;
END IF;
END PROCESS;
-- Issue the protocol list
p_seq_cnt : PROCESS(seq_cnt, start_reg, in_ack)
BEGIN
nxt_seq_cnt <= seq_cnt;
IF start_reg = '1' THEN
nxt_seq_cnt <= 0;
ELSIF seq_cnt<c_seq_len AND in_ack='1' THEN
nxt_seq_cnt <= seq_cnt + 1;
END IF;
END PROCESS;
out_dat <= STD_LOGIC_VECTOR(TO_UVEC(c_SEQ(seq_cnt), c_byte_w));
out_val <= '1' WHEN seq_cnt<c_seq_len ELSE '0';
-- Fill the rx_dat byte array
p_rx_dat : PROCESS(start_reg, rx_err, in_err, rx_dat, rx_cnt, in_dat, in_val)
BEGIN
nxt_rx_err <= rx_err;
IF start_reg = '1' THEN
nxt_rx_err <= '0';
ELSIF in_err='1' THEN
nxt_rx_err <= '1';
END IF;
nxt_rx_dat <= rx_dat;
nxt_rx_cnt <= rx_cnt;
IF start_reg = '1' THEN
nxt_rx_dat <= (OTHERS=>(OTHERS=>'0'));
nxt_rx_cnt <= 0;
ELSIF in_val='1' THEN
nxt_rx_dat(rx_cnt) <= in_dat;
nxt_rx_cnt <= rx_cnt + 1;
END IF;
END PROCESS;
nxt_rx_val <= in_end;
-- Capture the complete rx_dat byte array
nxt_result_val <= rx_val;
nxt_result_err <= rx_err;
nxt_result_dat <= rx_dat WHEN rx_val='1' ELSE i_result_dat;
END rtl;
-------------------------------------------------------------------------------
--
-- Copyright (C) 2012-2014
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
-- Purpose: Provide MM slave register for unb2_board_sens
-- Description:
--
-- 31 24 23 16 15 8 7 0 wi
-- |-----------------|-----------------|-----------------|-----------------|
-- | xxx fpga_temp = sens_data[0][7:0]| 0
-- |-----------------------------------------------------------------------|
-- | xxx eth_temp = sens_data[1][7:0]| 1
-- |-----------------------------------------------------------------------|
-- | xxx hot_swap_v_sense = sens_data[2][7:0]| 2
-- |-----------------------------------------------------------------------|
-- | xxx hot_swap_v_source = sens_data[3][7:0]| 3
-- |-----------------------------------------------------------------------|
-- | xxx sens_err[0]| 4
-- |-----------------------------------------------------------------------|
-- | xxx temp_high[6:0]| 5
-- |-----------------------------------------------------------------------|
--
-- * The fpga_temp and eth_temp are in degrees (two's complement)
-- * The hot swap voltages depend on:
-- . From i2c_dev_ltc4260_pkg:
-- LTC4260_V_UNIT_SENSE = 0.0003 -- 0.3 mV over Rs for current sense
-- LTC4260_V_UNIT_SOURCE = 0.4 -- 400 mV supply voltage (e.g +48 V)
-- LTC4260_V_UNIT_ADIN = 0.01 -- 10 mV ADC
--
-- . From UniBoard unb_sensors.h:
-- SENS_HOT_SWAP_R_SENSE = 0.005 -- R sense on UniBoard is 5 mOhm (~= 10 mOhm // 10 mOhm)
-- SENS_HOT_SWAP_I_UNIT_SENSE = LTC4260_V_UNIT_SENSE / SENS_HOT_SWAP_R_SENSE
-- SENS_HOT_SWAP_V_UNIT_SOURCE = LTC4260_V_UNIT_SOURCE
--
-- ==>
-- Via all nodes:
-- 0 = FPGA temperature = TInt8(fpga_temp)
-- Only via node2:
-- 1 = UniBoard ETH PHY temperature = TInt8(eth_temp)
-- 2 = UniBoard hot swap supply current = hot_swap_v_sense * SENS_HOT_SWAP_I_UNIT_SENSE
-- 3 = UniBoard hot swap supply voltage = hot_swap_v_source * SENS_HOT_SWAP_V_UNIT_SOURCE
-- 4 = I2C error status for node2 sensors access only, 0 = ok
--
LIBRARY IEEE, common_lib;
USE IEEE.STD_LOGIC_1164.ALL;
USE IEEE.NUMERIC_STD.ALL;
USE common_lib.common_pkg.ALL;
USE common_lib.common_mem_pkg.ALL;
ENTITY unb2_board_pmbus_reg IS
GENERIC (
g_sens_nof_result : NATURAL := 4;
g_temp_high : NATURAL := 85
);
PORT (
-- Clocks and reset
mm_rst : IN STD_LOGIC; -- reset synchronous with mm_clk
mm_clk : IN STD_LOGIC; -- memory-mapped bus clock
-- Memory Mapped Slave in mm_clk domain
sla_in : IN t_mem_mosi; -- actual ranges defined by c_mm_reg
sla_out : OUT t_mem_miso; -- actual ranges defined by c_mm_reg
-- MM registers
sens_err : IN STD_LOGIC := '0';
sens_data : IN t_slv_16_arr(0 TO g_sens_nof_result-1);
-- Max temp output
temp_high : OUT STD_LOGIC_VECTOR(6 DOWNTO 0)
);
END unb2_board_pmbus_reg;
ARCHITECTURE rtl OF unb2_board_pmbus_reg IS
-- Define the actual size of the MM slave register
CONSTANT c_mm_nof_dat : NATURAL := g_sens_nof_result+1+1; -- +1 to fit user set temp_high one additional address
-- +1 to fit sens_err in the last address
CONSTANT c_mm_reg : t_c_mem := (latency => 1,
adr_w => ceil_log2(c_mm_nof_dat),
dat_w => c_word_w, -- Use MM bus data width = c_word_w = 32 for all MM registers
nof_dat => c_mm_nof_dat,
init_sl => '0');
SIGNAL i_temp_high : STD_LOGIC_VECTOR(6 DOWNTO 0);
BEGIN
temp_high <= i_temp_high;
------------------------------------------------------------------------------
-- MM register access in the mm_clk domain
-- . Hardcode the shared MM slave register directly in RTL instead of using
-- the common_reg_r_w instance. Directly using RTL is easier when the large
-- MM register has multiple different fields and with different read and
-- write options per field in one MM register.
------------------------------------------------------------------------------
p_mm_reg : PROCESS (mm_rst, mm_clk)
VARIABLE vA : NATURAL := 0;
BEGIN
IF mm_rst = '1' THEN
-- Read access
sla_out <= c_mem_miso_rst;
-- Write access, register values
i_temp_high <= TO_UVEC(g_temp_high, 7);
ELSIF rising_edge(mm_clk) THEN
vA := TO_UINT(sla_in.address(c_mm_reg.adr_w-1 DOWNTO 0));
-- Read access defaults
sla_out.rdval <= '0';
-- Write access: set register value
IF sla_in.wr = '1' THEN
IF vA = g_sens_nof_result+1 THEN
-- Only change temp_high if user writes a max. 7-bit value. This prevents accidentally
-- setting a negative temp as temp_high, e.g. 128 which becomes -128.
IF UNSIGNED(sla_in.wrdata(c_word_w-1 DOWNTO 7)) = 0 THEN
i_temp_high <= sla_in.wrdata(6 DOWNTO 0);
END IF;
END IF;
-- Read access: get register value
ELSIF sla_in.rd = '1' THEN
sla_out <= c_mem_miso_rst; -- set unused rddata bits to '0' when read
sla_out.rdval <= '1'; -- c_mm_reg.latency = 1
-- no need to capture sens_data, it is not critical if the sens_data happens to be read just before and after an I2C access occurred
IF vA < g_sens_nof_result THEN
sla_out.rddata <= RESIZE_MEM_DATA(sens_data(vA)(c_halfword_w-1 DOWNTO 0));
ELSIF vA = g_sens_nof_result THEN
sla_out.rddata(0) <= sens_err; -- only valid for node2
ELSE
sla_out.rddata(6 DOWNTO 0) <= i_temp_high;
END IF;
-- else unused addresses read zero
END IF;
END IF;
END PROCESS;
END rtl;
...@@ -54,15 +54,12 @@ END ENTITY; ...@@ -54,15 +54,12 @@ END ENTITY;
ARCHITECTURE rtl OF unb2_board_sens_ctrl IS ARCHITECTURE rtl OF unb2_board_sens_ctrl IS
-- I2C slave addresses of the devices on the I2C bus on UniBoard -- I2C slave addresses of the devices on the I2C bus on UniBoard
CONSTANT FPGA_MAX1617_ADR : NATURAL := MAX1617_ADR_LOW_LOW; -- FPGA temperature sensor, slave address is "0011000" CONSTANT ETH_MAX1617_ADR : NATURAL := 16#29#; -- ETH temperature sensor
CONSTANT ETH_MAX1617_ADR : NATURAL := MAX1617_ADR_MID_LOW; -- ETH temperature sensor, slave address is "0101001" CONSTANT FPGA_TMP451_ADR : NATURAL := 16#4C#; -- FPGA temperature sensor
CONSTANT HOTSWAP_LTC4260_ADR : NATURAL := LTC4260_ADR_LOW_LOW_LOW; -- Hot swap controller, slave address is "1000100";
-- Experimental constants for the PMBUS, power module readouts (to be checked FIXME) -- Experimental constants for the PMBUS, power module readouts (to be checked FIXME)
CONSTANT LOC_POWER_TR_R : NATURAL := 16#1C#; -- 0x0E CONSTANT LOC_POWER_TR_R : NATURAL := 16#0E#;
CONSTANT LOC_POWER_TR_R1 : NATURAL := 16#0E#;
CONSTANT LOC_POWER_TR_R2 : NATURAL := 16#0F#; -- 0x0E
CONSTANT LP_VOUT_MODE : NATURAL := 16#20#; CONSTANT LP_VOUT_MODE : NATURAL := 16#20#;
CONSTANT LP_VOUT : NATURAL := 16#8B#; CONSTANT LP_VOUT : NATURAL := 16#8B#;
CONSTANT LP_IOUT : NATURAL := 16#8C#; CONSTANT LP_IOUT : NATURAL := 16#8C#;
...@@ -76,12 +73,15 @@ ARCHITECTURE rtl OF unb2_board_sens_ctrl IS ...@@ -76,12 +73,15 @@ ARCHITECTURE rtl OF unb2_board_sens_ctrl IS
CONSTANT c_timeout_sda : NATURAL := sel_a_b(g_sim, 0, 16); -- wait 16 * 256 = 4096 clk periods CONSTANT c_timeout_sda : NATURAL := sel_a_b(g_sim, 0, 16); -- wait 16 * 256 = 4096 clk periods
CONSTANT c_SEQ : t_SEQUENCE := ( CONSTANT c_SEQ : t_SEQUENCE := (
SMBUS_READ_BYTE , LOC_POWER_TR_R, LP_TEMP,--LP_VOUT_MODE, --SMBUS_READ_BYTE , LOC_POWER_TR_R, LP_VOUT_MODE,
SMBUS_READ_BYTE , LOC_POWER_TR_R1, LP_TEMP,--LP_VOUT, -- SMBUS_READ_WORD --SMBUS_READ_WORD , LOC_POWER_TR_R, LP_VOUT,
SMBUS_READ_BYTE , LOC_POWER_TR_R2, LP_TEMP,--LP_IOUT, -- SMBUS_READ_WORD --SMBUS_READ_WORD , LOC_POWER_TR_R, LP_IOUT,
SMBUS_READ_BYTE , LOC_POWER_TR_R1, LP_VOUT_MODE, -- SMBUS_READ_WORD --SMBUS_READ_WORD , LOC_POWER_TR_R, LP_TEMP,
--SMBUS_READ_BYTE , FPGA_MAX1617_ADR, MAX1617_CMD_READ_REMOTE_TEMP, SMBUS_READ_BYTE , ETH_MAX1617_ADR, MAX1617_CMD_READ_REMOTE_TEMP,
SMBUS_READ_BYTE , ETH_MAX1617_ADR, MAX1617_CMD_READ_REMOTE_TEMP,
SMBUS_READ_BYTE , ETH_MAX1617_ADR, MAX1617_CMD_READ_REMOTE_TEMP,
SMBUS_READ_BYTE , ETH_MAX1617_ADR, MAX1617_CMD_READ_REMOTE_TEMP,
--SMBUS_READ_BYTE , ETH_MAX1617_ADR, MAX1617_CMD_READ_REMOTE_TEMP, --SMBUS_READ_BYTE , ETH_MAX1617_ADR, MAX1617_CMD_READ_REMOTE_TEMP,
--SMBUS_READ_BYTE , HOTSWAP_LTC4260_ADR, LTC4260_CMD_SENSE, --SMBUS_READ_BYTE , HOTSWAP_LTC4260_ADR, LTC4260_CMD_SENSE,
--SMBUS_READ_BYTE , HOTSWAP_LTC4260_ADR, LTC4260_CMD_SOURCE, --SMBUS_READ_BYTE , HOTSWAP_LTC4260_ADR, LTC4260_CMD_SOURCE,
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment