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

Subversion Repositories astron_requantizer

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /
    from Rev 1 to Rev 2
    Reverse comparison

Rev 1 → Rev 2

/astron_requantizer/trunk/common_requantize.vhd
0,0 → 1,140
-------------------------------------------------------------------------------
--
-- Copyright (C) 2009
-- 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_pkg_lib;
USE IEEE.std_logic_1164.ALL;
USE IEEE.numeric_std.ALL;
USE common_pkg_lib.common_pkg.ALL;
 
-- Purpose: Requantize the input data to the output data width by removing
-- LSbits and/or MSbits
-- Description:
--
-- . in_dat --> remove LSbits --> rem_dat --> remove MSbits --> shift left by c_gain_w --> out_dat
--
-- . Remove LSBits by means of ROUND or TRUNCATE
-- . Remove LSBits when c_lsb_w>0
--
-- . Remove MSBits by means of CLIP or WRAP
-- . Remove MSbits when g_in_dat_w-c_lsb_w > g_out_dat_w:
-- in_dat <---------------------g_in_dat_w--------------------->
-- rem_dat <---------------------c_rem_dat_w-------><--c_lsb_w-->
-- res_dat <-------------g_out_dat_w-------><--c_lsb_w-->
--
-- . Extend MSbits when g_in_dat_w-c_lsb_w <= g_out_dat_w::
-- in_dat <-------------g_in_dat_w--------------------->
-- rem_dat <-------------c_rem_dat_w-------><--c_lsb_w-->
-- res_dat <---------------------g_out_dat_w-------><--c_lsb_w-->
--
-- . Shift left res_dat before resizing to out_dat'LENGTH, which is useful to keep the res_dat in the MSbits when out_dat'LENGTH > g_out_dat_w
-- gain_dat <-------g_out_dat_w-------><--c_gain_w-->
--
-- Remarks:
-- . It is not necessary to define g_msb_w, because the number of MSbits that
-- need to be removed (or extended) follows from the other widths.
 
ENTITY common_requantize IS
GENERIC (
g_representation : STRING := "SIGNED"; -- SIGNED (round +-0.5 away from zero to +- infinity) or UNSIGNED rounding (round 0.5 up to + inifinity)
g_lsb_w : INTEGER := 4; -- when > 0, number of LSbits to remove from in_dat
-- when < 0, number of LSBits to insert as a gain before resize to out_dat'LENGTH
-- when 0 then no effect
g_lsb_round : BOOLEAN := TRUE; -- when true ROUND else TRUNCATE the input LSbits
g_lsb_round_clip : BOOLEAN := FALSE; -- when true round clip to +max to avoid wrapping to output -min (signed) or 0 (unsigned) due to rounding
g_msb_clip : BOOLEAN := TRUE; -- when true CLIP else WRAP the input MSbits
g_msb_clip_symmetric : BOOLEAN := FALSE; -- when TRUE clip signed symmetric to +c_smax and -c_smax, else to +c_smax and c_smin_symm
-- for wrapping when g_msb_clip=FALSE the g_msb_clip_symmetric is ignored, so signed wrapping is done asymmetric
g_gain_w : NATURAL := 0; -- do not use, must be 0, use negative g_lsb_w instead
g_pipeline_remove_lsb : NATURAL := 0; -- >= 0
g_pipeline_remove_msb : NATURAL := 0; -- >= 0, use g_pipeline_remove_lsb=0 and g_pipeline_remove_msb=0 for combinatorial output
g_in_dat_w : NATURAL := 36; -- input data width
g_out_dat_w : NATURAL := 18 -- output data width
);
PORT (
clk : IN STD_LOGIC;
clken : IN STD_LOGIC := '1';
in_dat : IN STD_LOGIC_VECTOR; -- unconstrained slv to also support widths other than g_in_dat_w by only using [g_in_dat_w-1:0] from the in_dat slv
out_dat : OUT STD_LOGIC_VECTOR; -- unconstrained slv to also support widths other then g_out_dat_w by resizing the result [g_out_dat_w-1:0] to the out_dat slv
out_ovr : OUT STD_LOGIC -- out_ovr is '1' when the removal of MSbits causes clipping or wrapping
);
END;
 
 
ARCHITECTURE str OF common_requantize IS
 
-- Use c_lsb_w > 0 to remove LSBits and support c_lsb < 0 to shift in zero value LSbits as a gain
CONSTANT c_lsb_w : NATURAL := sel_a_b(g_lsb_w > 0, g_lsb_w, 0);
CONSTANT c_gain_w : NATURAL := sel_a_b(g_lsb_w < 0, -g_lsb_w, 0);
CONSTANT c_rem_dat_w : NATURAL := g_in_dat_w-c_lsb_w;
SIGNAL rem_dat : STD_LOGIC_VECTOR(c_rem_dat_w-1 DOWNTO 0); -- remaining in_dat after removing the c_lsb_w number of LSBits
SIGNAL res_dat : STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0); -- resulting out_dat after removing the g_msb_w number of MSBits
SIGNAL gain_dat : STD_LOGIC_VECTOR(g_out_dat_w+c_gain_w-1 DOWNTO 0) := (OTHERS=>'0'); -- fill extra LSBits with '0' instead of extending MSbits
BEGIN
 
ASSERT g_gain_w=0 REPORT "common_requantize: must use g_gain_w = 0, because gain is now supported via negative g_lsb_w." SEVERITY FAILURE;
 
-- Remove LSBits using ROUND or TRUNCATE
u_remove_lsb : ENTITY work.common_round
GENERIC MAP (
g_representation => g_representation,
g_round => g_lsb_round,
g_round_clip => g_lsb_round_clip,
g_pipeline_input => 0,
g_pipeline_output => g_pipeline_remove_lsb,
g_in_dat_w => g_in_dat_w,
g_out_dat_w => c_rem_dat_w
)
PORT MAP (
clk => clk,
clken => clken,
in_dat => in_dat(g_in_dat_w-1 DOWNTO 0),
out_dat => rem_dat
);
-- Remove MSBits using CLIP or WRAP
u_remove_msb : ENTITY work.common_resize
GENERIC MAP (
g_representation => g_representation,
g_pipeline_input => 0,
g_pipeline_output => g_pipeline_remove_msb,
g_clip => g_msb_clip,
g_clip_symmetric => g_msb_clip_symmetric,
g_in_dat_w => c_rem_dat_w,
g_out_dat_w => g_out_dat_w
)
PORT MAP (
clk => clk,
clken => clken,
in_dat => rem_dat,
out_dat => res_dat,
out_ovr => out_ovr
);
-- Output gain
gain_dat(g_out_dat_w+c_gain_w-1 DOWNTO c_gain_w) <= res_dat;
out_dat <= RESIZE_SVEC(gain_dat, out_dat'LENGTH) WHEN g_representation="SIGNED" ELSE RESIZE_UVEC(gain_dat, out_dat'LENGTH);
END str;
astron_requantizer/trunk/common_requantize.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_requantizer/trunk/common_resize.vhd =================================================================== --- astron_requantizer/trunk/common_resize.vhd (nonexistent) +++ astron_requantizer/trunk/common_resize.vhd (revision 2) @@ -0,0 +1,138 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2009 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY ieee, common_pkg_lib, common_components_lib; +USE ieee.std_logic_1164.ALL; +USE ieee.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; + +ENTITY common_resize IS + GENERIC ( + g_representation : STRING := "SIGNED"; -- SIGNED or UNSIGNED resizing + g_clip : BOOLEAN := FALSE; -- when TRUE clip input if it is outside the output range, else wrap + g_clip_symmetric : BOOLEAN := FALSE; -- when TRUE clip signed symmetric to +c_smax and -c_smax, else to +c_smax and c_smin_symm + -- for wrapping when g_clip=FALSE the g_clip_symmetric is ignored, so signed wrapping is done asymmetric + g_pipeline_input : NATURAL := 0; -- >= 0 + g_pipeline_output : NATURAL := 1; -- >= 0 + g_in_dat_w : INTEGER := 36; + g_out_dat_w : INTEGER := 18 + ); + PORT ( + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + in_dat : IN STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + out_dat : OUT STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0); + out_ovr : OUT STD_LOGIC + ); +END; + + +ARCHITECTURE rtl OF common_resize IS + + -- Clipping is only necessary when g_out_dat_w "SIGNED", + g_pipeline => g_pipeline_input, + g_in_dat_w => g_in_dat_w, + g_out_dat_w => g_in_dat_w + ) + PORT MAP ( + clk => clk, + clken => clken, + in_dat => in_dat, + out_dat => reg_dat + ); + + no_clip : IF c_clip=FALSE GENERATE + -- Note that g_pipeline_input=0 AND g_clip=FALSE is equivalent to using RESIZE_SVEC or RESIZE_UVEC directly. + gen_s : IF g_representation="SIGNED" GENERATE + -- If g_out_dat_w>g_in_dat_w then IEEE resize extends the sign bit, + -- else IEEE resize preserves the sign bit and keeps the low part. + wrap <= '1' WHEN SIGNED(reg_dat)>c_smax OR SIGNED(reg_dat)< c_smin_most ELSE '0'; + res_dat <= RESIZE_SVEC(reg_dat, g_out_dat_w); + res_ovr <= wrap; + END GENERATE; + + gen_u : IF g_representation="UNSIGNED" GENERATE + -- If g_out_dat_w>g_in_dat_w then IEEE resize sign extends with '0', + -- else IEEE resize keeps the low part. + wrap <= '1' WHEN UNSIGNED(reg_dat)>c_umax ELSE '0'; + res_dat <= RESIZE_UVEC(reg_dat, g_out_dat_w); + res_ovr <= wrap; + END GENERATE; + END GENERATE; + + gen_clip : IF c_clip=TRUE GENERATE + gen_s_clip : IF g_representation="SIGNED" GENERATE + clip <= '1' WHEN SIGNED(reg_dat)>c_smax OR SIGNED(reg_dat)< c_smin ELSE '0'; + sign <= reg_dat(reg_dat'HIGH); + res_dat <= reg_dat(out_dat'RANGE) WHEN clip='0' ELSE STD_LOGIC_VECTOR( c_smax) WHEN sign='0' ELSE STD_LOGIC_VECTOR(c_smin); + res_ovr <= clip; + END GENERATE; + + gen_u_clip : IF g_representation="UNSIGNED" GENERATE + clip <= '1' WHEN UNSIGNED(reg_dat)>c_umax ELSE '0'; + res_dat <= reg_dat(out_dat'RANGE) WHEN clip='0' ELSE STD_LOGIC_VECTOR(c_umax); + res_ovr <= clip; + END GENERATE; + END GENERATE; + + res_vec <= res_ovr & res_dat; + + u_output_pipe : ENTITY common_components_lib.common_pipeline -- pipeline output + GENERIC MAP ( + g_representation => "SIGNED", + g_pipeline => g_pipeline_output, + g_in_dat_w => g_out_dat_w+1, + g_out_dat_w => g_out_dat_w+1 + ) + PORT MAP ( + clk => clk, + clken => clken, + in_dat => res_vec, + out_dat => out_vec + ); + + out_ovr <= out_vec(g_out_dat_w); + out_dat <= out_vec(g_out_dat_w-1 DOWNTO 0); + +END rtl;
astron_requantizer/trunk/common_resize.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_requantizer/trunk/common_round.vhd =================================================================== --- astron_requantizer/trunk/common_round.vhd (nonexistent) +++ astron_requantizer/trunk/common_round.vhd (revision 2) @@ -0,0 +1,117 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2009 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY ieee, common_pkg_lib, common_components_lib; +USE ieee.std_logic_1164.ALL; +USE ieee.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; + +ENTITY common_round IS + + -- + -- ISE XST results for rounding 36b --> 18b: + -- int clip --> slices FFs LUTs + -- 1) signed TRUE 63 54 80 -- increases with input widths > 18b + -- 2) signed FALSE 59 54 73 -- increases with input widths > 18b + -- 3) unsigned TRUE 34 37 43 -- same for all input widths > 18b + -- 4) unsigned FALSE 21 37 19 -- same for all input widths > 18b + -- + -- If the input comes from a product and is rounded to the input width then g_round_clip can safely be FALSE, because e.g. for unsigned + -- 4b*4b=8b->4b the maximum product is 15*15=225 <= 255-8, so wrapping will never occur. + -- + + GENERIC ( + g_representation : STRING := "SIGNED"; -- SIGNED (round +-0.5 away from zero to +- infinity) or UNSIGNED rounding (round 0.5 up to + inifinity) + g_round : BOOLEAN := TRUE; -- when TRUE round the input, else truncate the input + g_round_clip : BOOLEAN := FALSE; -- when TRUE clip rounded input >= +max to avoid wrapping to output -min (signed) or 0 (unsigned) + g_pipeline_input : NATURAL := 0; -- >= 0 + g_pipeline_output : NATURAL := 1; -- >= 0, use g_pipeline_input=0 and g_pipeline_output=0 for combinatorial output + g_in_dat_w : NATURAL := 36; + g_out_dat_w : NATURAL := 18 + ); + PORT ( + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + in_dat : IN STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + out_dat : OUT STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0) + ); +END; + + +ARCHITECTURE rtl OF common_round IS + + CONSTANT c_remove_w : INTEGER := g_in_dat_w-g_out_dat_w; + + SIGNAL reg_dat : STD_LOGIC_VECTOR(in_dat'RANGE); + SIGNAL res_dat : STD_LOGIC_VECTOR(out_dat'RANGE); + +BEGIN + + u_input_pipe : ENTITY common_components_lib.common_pipeline + GENERIC MAP ( + g_representation => g_representation, + g_pipeline => g_pipeline_input, + g_in_dat_w => g_in_dat_w, + g_out_dat_w => g_in_dat_w + ) + PORT MAP ( + clk => clk, + clken => clken, + in_dat => in_dat, + out_dat => reg_dat + ); + + -- Increase to out_dat width + no_s : IF c_remove_w<=0 AND g_representation="SIGNED" GENERATE + res_dat <= RESIZE_SVEC(reg_dat, g_out_dat_w); + END GENERATE; + no_u : IF c_remove_w<=0 AND g_representation="UNSIGNED" GENERATE + res_dat <= RESIZE_UVEC(reg_dat, g_out_dat_w); + END GENERATE; + + -- Decrease to out_dat width by c_remove_w number of LSbits + -- . rounding + gen_s : IF c_remove_w>0 AND g_round=TRUE AND g_representation="SIGNED" GENERATE + res_dat <= s_round(reg_dat, c_remove_w, g_round_clip); + END GENERATE; + gen_u : IF c_remove_w>0 AND g_round=TRUE AND g_representation="UNSIGNED" GENERATE + res_dat <= u_round(reg_dat, c_remove_w, g_round_clip); + END GENERATE; + -- . truncating + gen_t : IF c_remove_w>0 AND g_round=FALSE GENERATE + res_dat <= truncate(reg_dat, c_remove_w); + END GENERATE; + + u_output_pipe : ENTITY common_components_lib.common_pipeline + GENERIC MAP ( + g_representation => g_representation, + g_pipeline => g_pipeline_output, + g_in_dat_w => g_out_dat_w, + g_out_dat_w => g_out_dat_w + ) + PORT MAP ( + clk => clk, + clken => clken, + in_dat => res_dat, + out_dat => out_dat + ); + +END rtl;
astron_requantizer/trunk/common_round.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_requantizer/trunk/dp_requantize.vhd =================================================================== --- astron_requantizer/trunk/dp_requantize.vhd (nonexistent) +++ astron_requantizer/trunk/dp_requantize.vhd (revision 2) @@ -0,0 +1,186 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- JIVE (Joint Institute for VLBI in Europe) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib, dp_pkg_lib, common_requantize_lib, dp_pipeline_lib; +USE IEEE.std_logic_1164.all; +USE dp_pkg_lib.dp_stream_pkg.ALL; +--USE common_lib.all; +USE common_pkg_lib.common_pkg.ALL; + +-- Purpose: Requantize the data in the re, im or data field of the sosi record. +-- Description: +-- See common_requantize.vhd +-- Remarks: +-- . It does not take into account the ready signal from the siso record. + +ENTITY dp_requantize IS + GENERIC ( + g_complex : BOOLEAN := TRUE; -- when true, the re and im field are processed, when false, the data field is processed + g_representation : STRING := "SIGNED"; -- SIGNED (round +-0.5 away from zero to +- infinity) or UNSIGNED rounding (round 0.5 up to + inifinity) + g_lsb_w : INTEGER := 4; -- when > 0, number of LSbits to remove from in_dat + -- when < 0, number of LSBits to insert as a gain before resize to out_dat'LENGTH + -- when 0 then no effect + g_lsb_round : BOOLEAN := TRUE; -- when true ROUND else TRUNCATE the input LSbits + g_lsb_round_clip : BOOLEAN := FALSE; -- when true round clip to +max to avoid wrapping to output -min (signed) or 0 (unsigned) due to rounding + g_msb_clip : BOOLEAN := TRUE; -- when true CLIP else WRAP the input MSbits + g_msb_clip_symmetric : BOOLEAN := FALSE; -- when TRUE clip signed symmetric to +c_smax and -c_smax, else to +c_smax and c_smin_symm + -- for wrapping when g_msb_clip=FALSE the g_msb_clip_symmetric is ignored, so signed wrapping is done asymmetric + g_gain_w : NATURAL := 0; -- do not use, must be 0, use negative g_lsb_w instead + g_pipeline_remove_lsb : NATURAL := 0; -- >= 0 + g_pipeline_remove_msb : NATURAL := 0; -- >= 0, use g_pipeline_remove_lsb=0 and g_pipeline_remove_msb=0 for combinatorial output + g_in_dat_w : NATURAL := 36; -- input data width + g_out_dat_w : NATURAL := 18 -- output data width + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + -- ST sink + snk_in : IN t_dp_sosi; + -- ST source + src_out : OUT t_dp_sosi; + -- + out_ovr : OUT std_logic -- out_ovr is '1' when the removal of MSbits causes clipping or wrapping + ); +END dp_requantize; + + +ARCHITECTURE str OF dp_requantize IS + + CONSTANT c_pipeline : NATURAL := g_pipeline_remove_lsb + g_pipeline_remove_msb; + + SIGNAL snk_in_piped : t_dp_sosi; + + SIGNAL quantized_data : STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0); + SIGNAL quantized_re : STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0); + SIGNAL quantized_im : STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0); + SIGNAL out_ovr_re : STD_LOGIC; + SIGNAL out_ovr_im : STD_LOGIC; + +BEGIN + + ASSERT g_gain_w=0 REPORT "dp_requantize: must use g_gain_w = 0, because gain is now supported via negative g_lsb_w." SEVERITY FAILURE; + + --------------------------------------------------------------- + -- Requantize the sosi data field + --------------------------------------------------------------- + gen_requantize_data : IF g_complex=FALSE GENERATE + u_requantize_data : ENTITY common_requantize_lib.common_requantize + GENERIC MAP ( + g_representation => g_representation, + g_lsb_w => g_lsb_w, + g_lsb_round => g_lsb_round, + g_lsb_round_clip => g_lsb_round_clip, + g_msb_clip => g_msb_clip, + g_msb_clip_symmetric => g_msb_clip_symmetric, + g_pipeline_remove_lsb => g_pipeline_remove_lsb, + g_pipeline_remove_msb => g_pipeline_remove_msb, + g_in_dat_w => g_in_dat_w, + g_out_dat_w => g_out_dat_w + ) + PORT MAP ( + clk => clk, + in_dat => snk_in.data, + out_dat => quantized_data, + out_ovr => out_ovr + ); + END GENERATE; + + --------------------------------------------------------------- + -- Requantize the sosi complex fields + --------------------------------------------------------------- + gen_requantize_complex : IF g_complex=TRUE GENERATE + u_requantize_re: ENTITY common_requantize_lib.common_requantize + GENERIC MAP ( + g_representation => g_representation, + g_lsb_w => g_lsb_w, + g_lsb_round => g_lsb_round, + g_lsb_round_clip => g_lsb_round_clip, + g_msb_clip => g_msb_clip, + g_msb_clip_symmetric => g_msb_clip_symmetric, + g_pipeline_remove_lsb => g_pipeline_remove_lsb, + g_pipeline_remove_msb => g_pipeline_remove_msb, + g_in_dat_w => g_in_dat_w, + g_out_dat_w => g_out_dat_w + ) + PORT MAP ( + clk => clk, + in_dat => snk_in.re, + out_dat => quantized_re, + out_ovr => out_ovr_re + ); + + u_requantize_im: ENTITY common_requantize_lib.common_requantize + GENERIC MAP ( + g_representation => g_representation, + g_lsb_w => g_lsb_w, + g_lsb_round => g_lsb_round, + g_lsb_round_clip => g_lsb_round_clip, + g_msb_clip => g_msb_clip, + g_msb_clip_symmetric => g_msb_clip_symmetric, + g_pipeline_remove_lsb => g_pipeline_remove_lsb, + g_pipeline_remove_msb => g_pipeline_remove_msb, + g_in_dat_w => g_in_dat_w, + g_out_dat_w => g_out_dat_w + ) + PORT MAP ( + clk => clk, + in_dat => snk_in.im, + out_dat => quantized_im, + out_ovr => out_ovr_im + ); + + out_ovr <= out_ovr_re OR out_ovr_im; + END GENERATE; + + + -------------------------------------------------------------- + -- Pipeline to align the other sosi fields + -------------------------------------------------------------- + u_dp_pipeline : ENTITY dp_pipeline_lib.dp_pipeline + GENERIC MAP ( + g_pipeline => c_pipeline -- 0 for wires, > 0 for registers, + ) + PORT MAP ( + rst => rst, + clk => clk, + -- ST sink + snk_in => snk_in, + -- ST source + src_out => snk_in_piped + ); + + PROCESS(snk_in_piped, quantized_data, quantized_re, quantized_im) + BEGIN + src_out <= snk_in_piped; + IF g_complex=FALSE THEN + IF g_representation="UNSIGNED" THEN + src_out.data <= RESIZE_DP_DATA( quantized_data); + ELSE + src_out.data <= RESIZE_DP_SDATA(quantized_data); + END IF; + ELSE + src_out.re <= RESIZE_DP_DSP_DATA(quantized_re); + src_out.im <= RESIZE_DP_DSP_DATA(quantized_im); + END IF; + END PROCESS; + +END str;
astron_requantizer/trunk/dp_requantize.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_requantizer/trunk/hdllib.cfg =================================================================== --- astron_requantizer/trunk/hdllib.cfg (nonexistent) +++ astron_requantizer/trunk/hdllib.cfg (revision 2) @@ -0,0 +1,23 @@ +hdl_lib_name = dp_requantize +hdl_library_clause_name = dp_requantize_lib +hdl_lib_uses_synth = common_pkg common_components dp_pkg dp_pipeline common_requantize +hdl_lib_uses_sim = +hdl_lib_technology = + +synth_files = + common_round.vhd + common_resize.vhd + common_requantize.vhd + + dp_requantize.vhd + +test_bench_files = + + +regression_test_vhdl = + + +[modelsim_project_file] + + +[quartus_project_file]
astron_requantizer/trunk/hdllib.cfg Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property

powered by: WebSVN 2.1.0

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