inserting text into a video stream (from a pre-existing video source)

W

wallge

I would like to superimpose some text into a video stream coming from a
camera into my fpga.
Lets say I would like to print the values of several registers to the
screen as simple ascii text. This text would be superimposed over the
incoming video stream. Does anyone know if there exists a core, or some
free vhdl floating around somewhere to do this kind of thing?
I have seen some cores that do VGA timing generation, then insert pixel
values values from a look up table (but these dont do text from what I
can tell, and must be controlled by a microprocessor).

The problem with these is that they dont really do what I want. Really
what I want is a function that would
convert the value of a register into say, hex or base 10 ascii text,
and then count the number of
rows/columns of video coming in, and insert black or white pixels into
the video stream as appropriate to make those characters appear
(superimposed) on the output video stream.

Anyone have any ideas or thoughts?

thanks.
 
M

MikeJ

There is a project called display test on www.fpgaarcade.com

originally this did exactly what you wanted using a block ram initialised
with ascii bitmaps and a second ram holding the text to be displayed. It had
a bus which could be attached to a state machine or microprocessor. I used
it to display 16 32 bit registers on the screen.

have a look, I can't remember how much code I left in. If you don't find
anything else ping me and I'll try and did up the original. Away in China
for the next 2 weeks however ...

/MikeJ
 
M

Martin Thompson

wallge said:
I would like to superimpose some text into a video stream coming from a
camera into my fpga.
Lets say I would like to print the values of several registers to the
screen as simple ascii text. This text would be superimposed over the
incoming video stream. Does anyone know if there exists a core, or some
free vhdl floating around somewhere to do this kind of thing?
I have seen some cores that do VGA timing generation, then insert pixel
values values from a look up table (but these dont do text from what I
can tell, and must be controlled by a microprocessor).

What format is your incoming video in?

Assuming it's got something like an LVALID and FVALID (and DVALID if
the clk is not the same as the pixel clock), I would use a BRAM as a
character frame buffer, decode the registers and stick the cahracters
into that. Then another BRAM can have an array of bits indexed by
character (make them 8x8 for ease :) that can be used by a process
which keeps track of the location of the pixel and which of the
character locations you are in.

You could have a small state machine run at the end of each frame to
update the character frame buffer with the values you want for next
time around during the vblank. Or double buffer.

Or do you really want to have something which looks like
ENTITY reg_to_screen
(
clk
reset
registervalue (31 downto 0)
xloc, yloc

vsync, hsync
video_out);

which you can then instantiate a number of times and then combine the
video_out signals together? If so, you'll end up duplicating the
character->pixels map unnecesarily.

There's some thoughts for you :)

Cheers,
Martin
 
B

Brad Smallridge

Really
what I want is a function that would
convert the value of a register into say, hex or base 10 ascii text,
and then count the number of
rows/columns of video coming in, and insert black or white pixels into
the video stream as appropriate to make those characters appear
(superimposed) on the output video stream.

Yeah. I might be able to help although I don't know what you are
using. Xilinx? Spartans? Virtex? VHDL? Verilog?

Can we assume that you already have a VGA display that is outputting?
And so can we assume that you have row and column registers in your
design?

Brad Smallridge
AiVision dot com
 
W

wallge

I use VHDL and altera FPGAs.
But the FPGA vendor shouldnt really matter much.
I have VGA video stream coming into the system
at just over 25Mhz at 60FPS at 640 x 480 valid pixels.
Currently I am sending output to a frame grabber via
camera link style output.
It would be nice if there was some code out there that was
video format agnostic - it wouldnt care about the video timing
to be able to insert a white (or black) pixel here and there to form
the letters
of ascii text I am trying to achieve.
 
S

Spehro Pefhany

I would like to superimpose some text into a video stream coming from a
camera into my fpga.
Lets say I would like to print the values of several registers to the
screen as simple ascii text. This text would be superimposed over the
incoming video stream. Does anyone know if there exists a core, or some
free vhdl floating around somewhere to do this kind of thing?
I have seen some cores that do VGA timing generation, then insert pixel
values values from a look up table (but these dont do text from what I
can tell, and must be controlled by a microprocessor).

The problem with these is that they dont really do what I want. Really
what I want is a function that would
convert the value of a register into say, hex or base 10 ascii text,
and then count the number of
rows/columns of video coming in, and insert black or white pixels into
the video stream as appropriate to make those characters appear
(superimposed) on the output video stream.

Anyone have any ideas or thoughts?

thanks.

You might get some hints by looking at the data sheet for the STV5730A
OSD chip.


Best regards,
Spehro Pefhany
 
B

Brad Smallridge

Well this is Xilinx specific but
take a look at the three modules below:
overlay,vga_dump_ram

What I remember is that the row and column
registers point to both the dump RAM and
the font ROM at the same time. With the lower
bits going to the font ROM. Your idea of using
8 by 8 fonts is a good one, even if you don't
use all the rows or columns of the font.

These modules create a one bit output that
must be anded into your video stream.

Sorry I wrote these before I was inferring
RAMs and ROMs but I think the Altera switch
should be straight forward.

You also mentioned that you want to spit out
the values of a register which will take some
doing because you will need to mux the nibbles
somehow.

Good Luck,

Brad Smallridge
AiVision


library IEEE;
use IEEE.STD_LOGIC_1164.ALL;

entity overlay is
port(
vga_clk : in std_logic;
vga_reset : in std_logic;
vga_row : in std_logic_vector( 8 downto 0);
vga_col : in std_logic_vector(11 downto 0);
q : out std_logic;
wr_clk : in std_logic;
wr_reset : in std_logic;
wr_en : in std_logic;
wr_stop : in std_logic;
wr_addr : in std_logic_vector(11 downto 0);
wr_data : in std_logic_vector( 7 downto 0) );
end overlay;

architecture behave of overlay is

component vga_dump_ram is
port (
rst : in std_logic;
clk_a : in std_logic;
wr_a : in std_logic;
data_a : in std_logic_vector(7 downto 0);
addr_a : in std_logic_vector(11 downto 0);
clk_b : in std_logic;
addr_b : in std_logic_vector(11 downto 0);
high_b : in std_logic; -- high nibble
dout_b : out std_logic_vector(3 downto 0) );
end component;

signal vga_nibble_addr : std_logic_vector(11 downto 0);
signal vga_nibble_high : std_logic;
signal vga_nibble : std_logic_vector( 3 downto 0);

component vga_font is
port (
clk : in std_logic;
rst : in std_logic;
addr : in std_logic_vector(14 downto 0);
q : out std_logic );
end component;

signal vga_font_addr : std_logic_vector(14 downto 0);
signal vga_font_row_1 : std_logic_vector( 2 downto 0);
signal vga_font_row_2 : std_logic_vector( 2 downto 0);
signal vga_font_col_1 : std_logic_vector( 2 downto 0);
signal vga_font_col_2 : std_logic_vector( 2 downto 0);
signal vga_font_bit : std_logic;
signal vga_font_bit_1 : std_logic;
signal vga_font_bit_2 : std_logic;
signal vga_font_bit_3 : std_logic;
signal vga_font_bit_4 : std_logic;

-- added for wr_stop timing
signal wr_data_1 : std_logic_vector( 7 downto 0);
signal wr_data_2 : std_logic_vector( 7 downto 0);
signal wr_addr_1 : std_logic_vector(11 downto 0);
signal wr_addr_2 : std_logic_vector(11 downto 0);
signal wr_en_1 : std_logic;
signal wr_en_2 : std_logic;

begin

-- This process adds two clock delays to the
-- address font look-up-table and compensates
-- for the character nibble look-up-table delay
vga_font_addr_process: process(vga_clk)
begin
if(vga_clk'event and vga_clk='1') then
vga_font_row_1 <= vga_row(2 downto 0);
vga_font_col_1 <= vga_col(2 downto 0);
vga_font_row_2 <= vga_font_row_1;
vga_font_col_2 <= vga_font_col_1;
vga_font_addr <= "00000" & vga_nibble & vga_font_row_2 & vga_font_col_2;
end if;
end process;

vga_font_inst: vga_font
port map(
clk => vga_clk,
rst => vga_reset,
addr => vga_font_addr, -- in 15 bit
q => vga_font_bit ); -- out 1 bit

vga_font_bit_delay_process: process(vga_clk)
begin
if(vga_clk'event and vga_clk='1') then
vga_font_bit_1 <= vga_font_bit;
vga_font_bit_2 <= vga_font_bit_1;
vga_font_bit_3 <= vga_font_bit_2;
vga_font_bit_4 <= vga_font_bit_3;
end if;
end process;
q <= vga_font_bit_4;
vga_nibble_addr <= vga_row(8 downto 3) & vga_col(9 downto 4);
vga_nibble_high <= not vga_col(3);

vga_nibble_inst:vga_dump_ram
port map(
rst => wr_reset, -- in 1
clk_a => wr_clk, -- in 1
wr_a => wr_en_2, -- in 1
data_a => wr_data_2, -- in 8
addr_a => wr_addr_2, -- in 12
clk_b => vga_clk, -- in 1
addr_b => vga_nibble_addr, -- in 12
high_b => vga_nibble_high, -- in 1
dout_b => vga_nibble ); -- out 4

-- This process added for wr_stop pushbutton
-- or a signal like 1Hz.
-- Wr_stop kills the wr_en signal
-- after a full line has been written.
wr_stop_timing_process: process (vga_clk)
begin
if(vga_clk'event and vga_clk='1') then
wr_data_1 <= wr_data;
wr_addr_1 <= wr_addr;
wr_en_1 <= wr_en;
wr_data_2 <= wr_data_1;
wr_addr_2 <= wr_addr_1;
if(wr_stop='1') then
if( wr_en_1='1' and wr_en='0' ) then -- on falling edge
wr_en_2 <= '0'; -- kill
end if;
else
wr_en_2 <= wr_en_1;
end if;
end if;
end process;

end behave;


-- Store 8 bit data
-- Read 4 bit nibbles
-- Brad Smallridge
-- Ai Vision
-- Xilinx ISE 7.1.04i
-- ModelSimXE III 6.0d

library IEEE;
use IEEE.STD_LOGIC_1164.ALL;

library UNISIM;
use UNISIM.VComponents.all;

entity vga_dump_ram is
port (
rst : in std_logic;
clk_a : in std_logic;
wr_a : in std_logic;
data_a : in std_logic_vector(7 downto 0);
addr_a : in std_logic_vector(11 downto 0);
clk_b : in std_logic;
addr_b : in std_logic_vector(11 downto 0);
high_b : in std_logic; -- high nibble
dout_b : out std_logic_vector(3 downto 0) );
end vga_dump_ram;

-- Addr_b and high_b will probably tied to a 13 bit counter
-- with high_b connected to the lowest bit of that counter.
-- If you want the highest nibble to output first,
-- as you might in a screen dump,
-- you want to invert this lowest bit.

architecture behavioral of vga_dump_ram is

signal addra : std_logic_vector(14 downto 0);
signal addrb : std_logic_vector(14 downto 0);
signal dob : std_logic_vector(31 downto 0);
signal dia : std_logic_vector(31 downto 0);
signal wea : std_logic_vector(3 downto 0);

begin

-- Offset the address by n bits,
-- 1
-- 2 '0'
-- 4 "00"
-- 9 "000"
-- 18 "0000"
-- 36 "00000"
addra <= addr_a & "000";
addrb <= addr_b & high_b & "00"; -- outputs the high nibble
first
dia(7 downto 0) <= data_a;
dia(31 downto 8) <= (others=>'1');
wea(3) <= wr_a;
wea(2) <= wr_a;
wea(1) <= wr_a;
wea(0) <= wr_a;

RAMB16_1 : RAMB16
generic map (
DOA_REG => 0, -- output registers on the A port (0 or 1)
DOB_REG => 1, -- output registers on the B port (0 or 1)
INIT_A => X"000000000", -- Initial values on A output port
INIT_B => X"000000000", -- Initial values on B output port
INVERT_CLK_DOA_REG => FALSE, -- Invert clock on A port output registers
INVERT_CLK_DOB_REG => FALSE, -- Invert clock on B port output registers
RAM_EXTENSION_A => "NONE", -- "UPPER", "LOWER" or "NONE" when cascaded
RAM_EXTENSION_B => "NONE", -- "UPPER", "LOWER" or "NONE" when cascaded
READ_WIDTH_A => 9, -- Valid values are 1,2,4,9,18 or 36
READ_WIDTH_B => 4, -- Valid values are 1,2,4,9,18 or 36
SIM_COLLISION_CHECK => "ALL", -- "ALL", "WARNING_ONLY", "GENERATE_X_ONLY"
or "NONE"
SRVAL_A => X"000000000", -- Port A ouput value upon SSR assertion
SRVAL_B => X"000000000", -- Port B ouput value upon SSR assertion
WRITE_MODE_A => "READ_FIRST", -- WRITE_FIRST, READ_FIRST or NO_CHANGE
WRITE_MODE_B => "READ_FIRST", -- WRITE_FIRST, READ_FIRST or NO_CHANGE
WRITE_WIDTH_A => 9, -- Valid values are 1,2,4,9,18 or 36
WRITE_WIDTH_B => 9) -- Valid values are 1,2,4,9,18 or 36

port map (
CASCADEOUTA => open, -- 1-bit cascade output
CASCADEOUTB => open, -- 1-bit cascade output
DOA => open, -- 32-bit A port Data Output
DOB => dob, -- 32-bit B port Data Output
DOPA => open, -- 4-bit A port Parity Output
DOPB => open, -- 4-bit B port Parity Output
ADDRA => addra, -- 15-bit A port Address Input
ADDRB => addrb, -- 15-bit B port Address Input
CASCADEINA => '0', -- 1-bit cascade A input
CASCADEINB => '0', -- 1-bit cascade B input
CLKA => clk_a, -- Port A Clock
CLKB => clk_b, -- Port B Clock
DIA => dia, -- 32-bit A port Data Input
DIB => (others=>'1'), -- 32-bit B port Data Input
DIPA => (others=>'1'), -- 4-bit A port parity Input
DIPB => (others=>'1'), -- 4-bit B port parity Input
ENA => '1', -- 1-bit A port Enable Input
ENB => '1', -- 1-bit B port Enable Input
REGCEA => '1', -- 1-bit A port register enable input
REGCEB => '1', -- 1-bit B port register enable input
SSRA => '0', -- 1-bit A port Synchronous Set/Reset Input
SSRB => '0', -- 1-bit B port Synchronous Set/Reset Input
WEA => wea, -- 4-bit A port Write Enable Input
WEB => (others=>'0') ); -- 4-bit B port Write Enable Input

dout_b <= dob(3 downto 0);

end behavioral;

library IEEE;
use IEEE.STD_LOGIC_1164.ALL;

library UNISIM;
use UNISIM.VComponents.all;

entity vga_font is
port (
clk : in std_logic;
rst : in std_logic;
addr : in std_logic_vector(14 downto 0);
q : out std_logic );
end vga_font;

architecture behavioral of vga_font is

type init_array_type is array(natural range <>) of bit_vector(7 downto 0);
constant vga_font_data : init_array_type :=(

"00000000",
"00111000",
"01111100",
"11000110",
"11000110",
"11000110",
"01111100",
"00111000",

"00000000",
"00011000",
"00111000",
"00011000",
"00011000",
"00011000",
"00011000",
"00111100",

"00000000",
"01111000",
"11001100",
"00011000",
"00110000",
"01100000",
"11000000",
"11111110",

"00000000",
"01111100",
"00000110",
"00000110",
"00011100",
"00000110",
"00000110",
"01111100",

"00000000",
"11001100",
"11001100",
"11001100",
"01111110",
"00001100",
"00001100",
"00001100",

"00000000",
"11111110",
"11000000",
"11000000",
"01111000",
"00011100",
"00001110",
"11111100",

"00000000",
"00001100",
"00011000",
"00110000",
"01111100",
"11000110",
"01100110",
"00111000",

"00000000",
"11111110",
"00000110",
"00001100",
"00011000",
"00110000",
"01100000",
"11000000",

"00000000",
"00111000",
"11000110",
"11000110",
"01111100",
"11000110",
"11000110",
"00111000",

"00000000",
"00111000",
"11000110",
"11000110",
"00111100",
"00011000",
"00110000",
"01100000",

"00000000",
"00111000",
"01101100",
"01101100",
"01111100",
"11000110",
"11000110",
"11000110",

"00000000",
"11111100",
"11000110",
"11000110",
"11111100",
"11000110",
"11000110",
"11111100",

"00000000",
"00111100",
"11000110",
"11000000",
"11000000",
"11000000",
"11000110",
"00111100",

"00000000",
"11111000",
"11001100",
"11000110",
"11000110",
"11000110",
"11001100",
"11111000",

"00000000",
"11111110",
"11000000",
"11000000",
"11110000",
"11000000",
"11000000",
"11111110",

"00000000",
"11111110",
"11000000",
"11000000",
"11111000",
"11000000",
"11000000",
"11000000",

X"00",X"FF"
);

function stuff_it
(
init_array : init_array_type;
init_xx : integer
) return bit_vector is
variable result : bit_vector(255 downto 0);
variable i : integer ;
variable j : integer ;
variable temp : bit_vector(7 downto 0);
begin
result :=
X"0000000000000000000000000000000000000000000000000000000000000000";
i := 0 ;
j := 32*init_xx ;
while( (j < init_array'length) and (i<256) )
loop
-- result( (i+7) downto (i) ) := init_array(j) ;
temp := init_array(j);
-- mirror bit vector
result(i+7) := temp(0);
result(i+6) := temp(1);
result(i+5) := temp(2);
result(i+4) := temp(3);
result(i+3) := temp(4);
result(i+2) := temp(5);
result(i+1) := temp(6);
result(i) := temp(7);
i := i + 8 ;
j := j + 1 ;
end loop;
return result;
end function stuff_it;

signal dob : std_logic_vector(31 downto 0);

begin

RAMB16_1 : RAMB16
generic map (
DOA_REG => 0, -- Optional output registers on the A port (0 or 1)
DOB_REG => 1, -- Optional output registers on the B port (0 or 1)
INIT_A => X"000000000", -- Initial values on A output port
INIT_B => X"000000000", -- Initial values on B output port
INVERT_CLK_DOA_REG => FALSE, -- Invert clock on A port output registers
(TRUE or FALSE)
INVERT_CLK_DOB_REG => FALSE, -- Invert clock on B port output registers
(TRUE or FALSE)
RAM_EXTENSION_A => "NONE", -- "UPPER", "LOWER" or "NONE" when cascaded
RAM_EXTENSION_B => "NONE", -- "UPPER", "LOWER" or "NONE" when cascaded
READ_WIDTH_A => 9, -- Valid values are 1,2,4,9,18 or 36
READ_WIDTH_B => 1, -- Valid values are 1,2,4,9,18 or 36
SIM_COLLISION_CHECK => "ALL", -- "ALL", "WARNING_ONLY", "GENERATE_X_ONLY"
or "NONE"
SRVAL_A => X"000000000", -- Port A ouput value upon SSR assertion
SRVAL_B => X"000000000", -- Port B ouput value upon SSR assertion
WRITE_MODE_A => "READ_FIRST", -- WRITE_FIRST, READ_FIRST or NO_CHANGE
WRITE_MODE_B => "READ_FIRST", -- WRITE_FIRST, READ_FIRST or NO_CHANGE
WRITE_WIDTH_A => 9, -- Valid values are 1,2,4,9,18 or 36
WRITE_WIDTH_B => 9, -- Valid values are 1,2,4,9,18 or 36

INIT_00 => stuff_it(vga_font_data,16#00#),
INIT_01 => stuff_it(vga_font_data,16#01#),
INIT_02 => stuff_it(vga_font_data,16#02#),
INIT_03 => stuff_it(vga_font_data,16#03#),
INIT_04 => stuff_it(vga_font_data,16#04#),
INIT_05 => stuff_it(vga_font_data,16#05#),
INIT_06 => stuff_it(vga_font_data,16#06#),
INIT_07 => stuff_it(vga_font_data,16#07#),
INIT_08 => stuff_it(vga_font_data,16#08#),
INIT_09 => stuff_it(vga_font_data,16#09#),
INIT_0A => stuff_it(vga_font_data,16#0A#),
INIT_0B => stuff_it(vga_font_data,16#0B#),
INIT_0C => stuff_it(vga_font_data,16#0C#),
INIT_0D => stuff_it(vga_font_data,16#0D#),
INIT_0E => stuff_it(vga_font_data,16#0E#),
INIT_0F => stuff_it(vga_font_data,16#0F#),

INIT_10 => stuff_it(vga_font_data,16#10#),
INIT_11 => stuff_it(vga_font_data,16#11#),
INIT_12 => stuff_it(vga_font_data,16#12#),
INIT_13 => stuff_it(vga_font_data,16#13#),
INIT_14 => stuff_it(vga_font_data,16#14#),
INIT_15 => stuff_it(vga_font_data,16#15#),
INIT_16 => stuff_it(vga_font_data,16#16#),
INIT_17 => stuff_it(vga_font_data,16#17#),
INIT_18 => stuff_it(vga_font_data,16#18#),
INIT_19 => stuff_it(vga_font_data,16#19#),
INIT_1A => stuff_it(vga_font_data,16#1A#),
INIT_1B => stuff_it(vga_font_data,16#1B#),
INIT_1C => stuff_it(vga_font_data,16#1C#),
INIT_1D => stuff_it(vga_font_data,16#1D#),
INIT_1E => stuff_it(vga_font_data,16#1E#),
INIT_1F => stuff_it(vga_font_data,16#1F#),

INIT_20 => stuff_it(vga_font_data,16#20#),
INIT_21 => stuff_it(vga_font_data,16#21#),
INIT_22 => stuff_it(vga_font_data,16#22#),
INIT_23 => stuff_it(vga_font_data,16#23#),
INIT_24 => stuff_it(vga_font_data,16#24#),
INIT_25 => stuff_it(vga_font_data,16#25#),
INIT_26 => stuff_it(vga_font_data,16#26#),
INIT_27 => stuff_it(vga_font_data,16#27#),
INIT_28 => stuff_it(vga_font_data,16#28#),
INIT_29 => stuff_it(vga_font_data,16#29#),
INIT_2A => stuff_it(vga_font_data,16#2A#),
INIT_2B => stuff_it(vga_font_data,16#2B#),
INIT_2C => stuff_it(vga_font_data,16#2C#),
INIT_2D => stuff_it(vga_font_data,16#2D#),
INIT_2E => stuff_it(vga_font_data,16#2E#),
INIT_2F => stuff_it(vga_font_data,16#2F#),

INIT_30 => stuff_it(vga_font_data,16#30#),
INIT_31 => stuff_it(vga_font_data,16#31#),
INIT_32 => stuff_it(vga_font_data,16#32#),
INIT_33 => stuff_it(vga_font_data,16#33#),
INIT_34 => stuff_it(vga_font_data,16#34#),
INIT_35 => stuff_it(vga_font_data,16#35#),
INIT_36 => stuff_it(vga_font_data,16#36#),
INIT_37 => stuff_it(vga_font_data,16#37#),
INIT_38 => stuff_it(vga_font_data,16#38#),
INIT_39 => stuff_it(vga_font_data,16#39#),
INIT_3A => stuff_it(vga_font_data,16#3A#),
INIT_3B => stuff_it(vga_font_data,16#3B#),
INIT_3C => stuff_it(vga_font_data,16#3C#),
INIT_3D => stuff_it(vga_font_data,16#3D#),
INIT_3E => stuff_it(vga_font_data,16#3E#),
INIT_3F => stuff_it(vga_font_data,16#3F#),

INITP_00 =>
X"0000000000000000000000000000000000000000000000000000000000000000",
INITP_01 =>
X"0000000000000000000000000000000000000000000000000000000000000000",
INITP_02 =>
X"0000000000000000000000000000000000000000000000000000000000000000",
INITP_03 =>
X"0000000000000000000000000000000000000000000000000000000000000000",
INITP_04 =>
X"0000000000000000000000000000000000000000000000000000000000000000",
INITP_05 =>
X"0000000000000000000000000000000000000000000000000000000000000000",
INITP_06 =>
X"0000000000000000000000000000000000000000000000000000000000000000",
INITP_07 =>
X"0000000000000000000000000000000000000000000000000000000000000000")

port map (
CASCADEOUTA => open, -- 1-bit cascade output
CASCADEOUTB => open, -- 1-bit cascade output
DOA => open, -- 32-bit A port Data Output
DOB => dob, -- 32-bit B port Data Output
DOPA => open, -- 4-bit A port Parity Output
DOPB => open, -- 4-bit B port Parity Output
ADDRA => (others=>'1'), -- 15-bit A port Address Input
ADDRB => addr, -- 15-bit B port Address Input
CASCADEINA => '0', -- 1-bit cascade A input
CASCADEINB => '0', -- 1-bit cascade B input
CLKA => '0', -- Port A Clock
CLKB => clk, -- Port B Clock
DIA => (others=>'1'), -- 32-bit A port Data Input
DIB => (others=>'1'), -- 32-bit B port Data Input
DIPA => (others=>'1'), -- 4-bit A port parity Input
DIPB => (others=>'1'), -- 4-bit B port parity Input
ENA => '0', -- 1-bit A port Enable Input
ENB => '1', -- 1-bit B port Enable Input
REGCEA => '0', -- 1-bit A port register enable input
REGCEB => '1', -- 1-bit B port register enable input
SSRA => '0', -- 1-bit A port Synchronous Set/Reset
Input
SSRB => '0', -- 1-bit B port Synchronous Set/Reset
Input
WEA => (others=>'0'), -- 4-bit A port Write Enable Input
WEB => (others=>'0') ); -- 4-bit B port Write Enable Input

q <= dob(0);

end behavioral;
 
J

-jg

wallge said:
I use VHDL and altera FPGAs.
But the FPGA vendor shouldnt really matter much.
I have VGA video stream coming into the system
at just over 25Mhz at 60FPS at 640 x 480 valid pixels.
Currently I am sending output to a frame grabber via
camera link style output.
It would be nice if there was some code out there that was
video format agnostic - it wouldnt care about the video timing
to be able to insert a white (or black) pixel here and there to form
the letters
of ascii text I am trying to achieve.

You wont be able to be video-format-agnostic for a number of
reasons :

To properly CHAR insert you need to phase-lock to the incomming Line
Sync
(often called GenLock) - if you do not do this, the chars jitter about
as you
have two clock domains.

You also need to Sync to Frame, and count lines, to decide when to
start the CHAR insert-stream.

Some of the better designs insert CHARs with a drop-shadow, so they are

readable over a wider range of backgrounds.

Teletext chipsets, and OnScreenDisplay chips, as others have
mentioned,
are a good design referance for the sync-side of things
-jg.
 
W

wallge

You wont be able to be video-format-agnostic for a number of
reasons :

To properly CHAR insert you need to phase-lock to the incomming Line
Sync
(often called GenLock) - if you do not do this, the chars jitter about
as you
have two clock domains.

No, in my design all the video processing is done in a processing clock
domain
that is bridged to the input video clock domain by asynchronous FIFOs.
What you are describing should not be a problem in my system.
Each pixel carries three flags: frame start, line start, and valid
data.
Video timing counters increment as appropriate when each of these flags
is observed in
a given video processing block.
You also need to Sync to Frame, and count lines, to decide when to
start the CHAR insert-stream.

I realize that lines need to be counted, and position in the current
frame kept track of,
and thus you need to know the number of valid/blank pixels and lines
and count them while
the system is online.
But these parameters could be set as generics or package constants or
even passed in
to registers at run time (if we wanted the char-gen scheme to be
resolution and timing agnostic).

This is the kind of block I am looking for. But it looks as if no-one
knows of something like this floating around on the web.
 

Ask a Question

Want to reply to this thread or ask your own question?

You'll need to choose a username for the site, which only take a couple of moments. After that, you can post your question and our members will help you out.

Ask a Question

Members online

Forum statistics

Threads
473,731
Messages
2,569,432
Members
44,835
Latest member
KetoRushACVBuy

Latest Threads

Top