--------------------------------------------------------------------------------
--
-- Copyright (C) 2014
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- JIVE (Joint Institute for VLBI in Europe) <http://www.jive.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 streaming interface to DDR memory
-- Description:
--   Write or read a block of data to or from DDR memory. The data width is set
--   by the DDR controller data width given by RESIZE_MEM_CTLR_DATA() and eg.
--   256 bits for DDR3 with 64 bit DQ data. The block of data is located from
--   dvr_start_address to dvr_nof_data.
--   The io_ddr_driver takes care that the access is done in a number of bursts.
--   The burst size for both write and read depends on the maximum burst size
--   and the remaining block size.
-- Remarks:
-- . Both this driver and the DDR IP controller use the t_mem_ctlr_miso/mosi
--   interface. The maximum burst size of the controller is defined by 
--   g_tech_ddr.maxburstsize and eg. 64 ctlr data words. The maximum burst size
--   of this driver is as large as the entire ctlr address span. The burst size
--   of driver depends on the block size of the application.


LIBRARY IEEE, tech_ddr_lib, common_lib, dp_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;
USE dp_lib.dp_stream_pkg.ALL;
USE tech_ddr_lib.tech_ddr_pkg.ALL;

ENTITY io_ddr_driver IS 
  GENERIC (
    g_tech_ddr         : t_c_tech_ddr
  );
  PORT ( 
    rst                : IN  STD_LOGIC;
    clk                : IN  STD_LOGIC;

    dvr_miso           : OUT t_mem_ctlr_miso;
    dvr_mosi           : IN  t_mem_ctlr_mosi;
   
    wr_snk_in          : IN  t_dp_sosi;
    wr_snk_out         : OUT t_dp_siso;
    
    rd_src_out         : OUT t_dp_sosi;
    rd_src_in          : IN  t_dp_siso;
    
    ctlr_miso          : IN  t_mem_ctlr_miso;
    ctlr_mosi          : OUT t_mem_ctlr_mosi
   );
END io_ddr_driver;


ARCHITECTURE str OF io_ddr_driver IS

  CONSTANT c_ctlr_address_w     : NATURAL := func_tech_ddr_ctlr_address_w(g_tech_ddr);
 
  TYPE t_state_enum IS (s_init, s_idle, s_wait, s_rd_request, s_wr_request, s_wr_burst);

  SIGNAL state                  : t_state_enum;
  SIGNAL nxt_state              : t_state_enum; 
  SIGNAL prev_state             : t_state_enum; 

  SIGNAL dvr_en                 : STD_LOGIC;
  SIGNAL dvr_wr_not_rd          : STD_LOGIC;       
  SIGNAL dvr_start_address      : STD_LOGIC_VECTOR(c_ctlr_address_w-1 DOWNTO 0);
  SIGNAL dvr_nof_data           : STD_LOGIC_VECTOR(c_ctlr_address_w-1 DOWNTO 0);
  SIGNAL dvr_done               : STD_LOGIC := '0';
  SIGNAL nxt_dvr_done           : STD_LOGIC;

  SIGNAL burst_size             : POSITIVE RANGE 1 TO 2**g_tech_ddr.maxburstsize_w-1 := 1;  -- burst size >= 1
  SIGNAL nxt_burst_size         : POSITIVE;
  SIGNAL burst_wr_cnt           : NATURAL  RANGE 0 TO 2**g_tech_ddr.maxburstsize_w-1 := 0;  -- count down from burst_size to 0
  SIGNAL nxt_burst_wr_cnt       : NATURAL  RANGE 0 TO 2**g_tech_ddr.maxburstsize_w-1;

  SIGNAL cur_address            : STD_LOGIC_VECTOR(c_ctlr_address_w-1 DOWNTO 0) := (OTHERS=>'0');
  SIGNAL nxt_cur_address        : STD_LOGIC_VECTOR(c_ctlr_address_w-1 DOWNTO 0);   
  SIGNAL address_cnt            : STD_LOGIC_VECTOR(c_ctlr_address_w-1 DOWNTO 0) := (OTHERS=>'0');  -- count down nof addresses = nof ctlr data words
  SIGNAL nxt_address_cnt        : STD_LOGIC_VECTOR(c_ctlr_address_w-1 DOWNTO 0);   

BEGIN

  -- Map original dvr interface signals to t_mem_ctlr_mosi/miso
  dvr_miso.done     <= dvr_done;             -- Requested wr or rd sequence is done
  dvr_en            <= dvr_mosi.burstbegin;
  dvr_wr_not_rd     <= dvr_mosi.wr;          -- No need to use dvr_mosi.rd
  dvr_start_address <= dvr_mosi.address(c_ctlr_address_w-1 DOWNTO 0);
  dvr_nof_data      <= dvr_mosi.burstsize(c_ctlr_address_w-1 DOWNTO 0);

  p_clk : PROCESS(rst, clk)
  BEGIN
    IF rst='1' THEN
      state          <= s_init;
      prev_state     <= s_init;
    ELSIF rising_edge(clk) THEN
      state          <= nxt_state;
      prev_state     <= state;
      burst_wr_cnt   <= nxt_burst_wr_cnt;
      dvr_done       <= nxt_dvr_done;
      cur_address    <= nxt_cur_address;
      address_cnt    <= nxt_address_cnt;
      burst_size     <= nxt_burst_size;
    END IF;
  END PROCESS;

  p_burst_size : PROCESS (address_cnt)
  BEGIN 
    -- Access burst size is at least 1 and if more then set to the smallest of g_tech_ddr.maxburstsize and address_cnt
    nxt_burst_size <= 1;
    IF UNSIGNED(address_cnt) > 0 THEN
      nxt_burst_size <= g_tech_ddr.maxburstsize;
      IF UNSIGNED(address_cnt) < g_tech_ddr.maxburstsize THEN
        nxt_burst_size <= TO_UINT(address_cnt);
      END IF;
    END IF;
  END PROCESS;
  
  rd_src_out.valid <= ctlr_miso.rdval;
  rd_src_out.data <= RESIZE_DP_DATA(ctlr_miso.rddata);
  
  p_state : PROCESS(prev_state, state,
                    dvr_en, dvr_wr_not_rd, dvr_start_address, dvr_nof_data,
                    ctlr_miso, wr_snk_in, rd_src_in, 
                    burst_size, burst_wr_cnt, cur_address, address_cnt)
  BEGIN  
    nxt_state              <= state;
    
    ctlr_mosi.address      <= RESIZE_MEM_CTLR_ADDRESS(cur_address);
    ctlr_mosi.wrdata       <= RESIZE_MEM_CTLR_DATA(wr_snk_in.data);
    ctlr_mosi.wr           <= '0';
    ctlr_mosi.rd           <= '0';
    ctlr_mosi.burstbegin   <= '0'; 
    ctlr_mosi.burstsize    <= (OTHERS => '0');
    
    wr_snk_out.ready       <= '0';
    nxt_dvr_done           <= '0';
    nxt_cur_address        <= cur_address;
    nxt_address_cnt        <= address_cnt;
    nxt_burst_wr_cnt       <= burst_wr_cnt;

    CASE state IS
     
      WHEN s_wr_burst => -- Performs the burst portion (word 2+)        
        IF ctlr_miso.waitrequest_n = '1' THEN
          IF wr_snk_in.valid = '1' THEN         -- it is allowed that valid is not always active during a burst
            wr_snk_out.ready <= '1';            -- wr side uses latency of 0, so wr_snk_out.ready<='1' acknowledges a successful write request.
            ctlr_mosi.wr     <= '1';
            nxt_burst_wr_cnt <= burst_wr_cnt-1;
            IF burst_wr_cnt = 1 THEN            -- check for the last cycle of this burst sequence
              nxt_state <= s_wr_request;        -- initiate a new wr burst or goto idle via the wr_request state
            END IF;
          END IF;
        END IF;            

      WHEN s_wr_request =>  -- Performs 1 write access and goes into s_wr_burst when requested write words >1       
        IF UNSIGNED(address_cnt) = 0 THEN -- end address reached
          nxt_dvr_done  <= '1';              
          nxt_state     <= s_idle;          
        ELSIF ctlr_miso.waitrequest_n = '1' THEN 
          IF wr_snk_in.valid = '1' THEN
            -- Always perform 1st write here             
            wr_snk_out.ready     <= '1';
            ctlr_mosi.wr         <= '1';
            ctlr_mosi.burstbegin <= '1';                                -- assert burstbegin,
            ctlr_mosi.burstsize  <= TO_MEM_CTLR_BURSTSIZE(burst_size);  -- burstsize >= 1
            nxt_cur_address      <= INCR_UVEC(cur_address, burst_size);
            nxt_address_cnt      <= INCR_UVEC(address_cnt, -burst_size);
            nxt_burst_wr_cnt     <= burst_size-1;
            -- Return for next wr request or perform any remaining writes in this burst
            nxt_state <= s_wait; 
            IF burst_size > 1 THEN
              nxt_state <= s_wr_burst;  -- first burst wr cycle is done here, the rest are done in s_wr_burst
            END IF;
          END IF;
        END IF;        

      WHEN s_rd_request =>  -- Posts a read request for a burst (1...g_tech_ddr.maxburstsize)      
        IF UNSIGNED(address_cnt) = 0 THEN -- end address reached
          nxt_dvr_done  <= '1';              
          nxt_state     <= s_idle;
        ELSE 
          IF rd_src_in.ready = '1' THEN  -- the external FIFO uses almost full level assert its snk_out.ready and can then still accept the maximum rd burst of words
            IF ctlr_miso.waitrequest_n = '1' THEN    
              ctlr_mosi.rd         <= '1';                   
              ctlr_mosi.burstbegin <= '1';                                -- assert burstbegin,
              ctlr_mosi.burstsize  <= TO_MEM_CTLR_BURSTSIZE(burst_size);  -- burstsize >= 1
              nxt_cur_address      <= INCR_UVEC(cur_address, burst_size);  
              nxt_address_cnt      <= INCR_UVEC(address_cnt, -burst_size);
              -- Return for next rd request
              nxt_state <= s_wait;
            END IF;           
          END IF;
        END IF; 

      -- In this state address_cnt is valid and in the next state burst_size (that depends on address_cnt) will be valid.
      -- Therefore this wait state is inserted between any requests.
      WHEN s_wait =>
        IF prev_state = s_wr_request THEN nxt_state <= s_wr_request; END IF;  -- between wr-wr burst requests
        IF prev_state = s_rd_request THEN nxt_state <= s_rd_request; END IF;  -- between rd-rd burst requests
        IF prev_state = s_idle THEN                                           -- between wr and rd accesses
          IF dvr_wr_not_rd = '1' THEN
            nxt_state <= s_wr_request;
          ELSE
            nxt_state <= s_rd_request;
          END IF;
        END IF;
         
      WHEN s_idle =>
        nxt_cur_address  <= dvr_start_address; 
        nxt_address_cnt  <= dvr_nof_data;
        nxt_burst_wr_cnt <= 0;
        nxt_dvr_done <= '1';    -- assert dvr_done after s_init or keep it asserted after a finished access
        IF dvr_en = '1' THEN  
          nxt_dvr_done <= '0';
          nxt_state    <= s_wait;
        END IF;
     
      WHEN OTHERS => -- s_init
        nxt_dvr_done <= '0';
        IF ctlr_miso.done = '1' THEN
          nxt_state <= s_idle;  -- and assert dvr_done when in s_idle to indicate ctlr_miso.done
        END IF;
      
    END CASE;
  END PROCESS;

END str;