]> rtime.felk.cvut.cz Git - fpga/zynq/canbench-sw.git/blob - system/ip/axi_pwm_coprocessor_1.0/hdl/axi_pwm_coprocessor_v1_0_M00_AXI.vhd
AXI PWM Coprocessor: PWM generation logic roughly implemented.
[fpga/zynq/canbench-sw.git] / system / ip / axi_pwm_coprocessor_1.0 / hdl / axi_pwm_coprocessor_v1_0_M00_AXI.vhd
1 library ieee;
2 use ieee.std_logic_1164.all;
3 use ieee.numeric_std.all;
4
5 entity axi_pwm_coprocessor_v1_0_M00_AXI is
6         generic (
7                 -- Users to add parameters here
8
9                 -- User parameters ends
10                 -- Do not modify the parameters beyond this line
11
12                 -- The master will start generating data from the C_M_START_DATA_VALUE value
13                 C_M_START_DATA_VALUE    : std_logic_vector      := x"AA000000";
14                 -- The master requires a target slave base address.
15     -- The master will initiate read and write transactions on the slave with base address specified here as a parameter.
16                 C_M_TARGET_SLAVE_BASE_ADDR      : std_logic_vector      := x"40000000";
17                 -- Width of M_AXI address bus.
18     -- The master generates the read and write addresses of width specified as C_M_AXI_ADDR_WIDTH.
19                 C_M_AXI_ADDR_WIDTH      : integer       := 32;
20                 -- Width of M_AXI data bus.
21     -- The master issues write data and accept read data where the width of the data bus is C_M_AXI_DATA_WIDTH
22                 C_M_AXI_DATA_WIDTH      : integer       := 32;
23                 -- Transaction number is the number of write
24     -- and read transactions the master will perform as a part of this example memory test.
25                 C_M_TRANSACTIONS_NUM    : integer       := 1
26         );
27         port (
28                 -- Users to add ports here
29                 pwm_state_i : in std_logic_vector(1 downto 0);
30                 pwm_enabled_i : in std_logic;
31
32                 pwm_wr_addr : in std_logic_vector(C_M_AXI_DATA_WIDTH-1 downto 0);
33                 pwm_wr0 : in std_logic_vector(C_M_AXI_DATA_WIDTH-1 downto 0);
34                 pwm_wr1 : in std_logic_vector(C_M_AXI_DATA_WIDTH-1 downto 0);
35                 pwm_wr2 : in std_logic_vector(C_M_AXI_DATA_WIDTH-1 downto 0);
36                 -- User ports ends
37                 -- Do not modify the ports beyond this line
38
39                 -- Initiate AXI transactions
40                 -- INIT_AXI_TXN : in std_logic;
41                 -- Asserts when ERROR is detected
42                 ERROR   : out std_logic;
43                 -- Asserts when AXI transactions is complete
44                 TXN_DONE        : out std_logic;
45                 -- AXI clock signal
46                 M_AXI_ACLK      : in std_logic;
47                 -- AXI active low reset signal
48                 M_AXI_ARESETN   : in std_logic;
49                 -- Master Interface Write Address Channel ports. Write address (issued by master)
50                 M_AXI_AWADDR    : out std_logic_vector(C_M_AXI_ADDR_WIDTH-1 downto 0);
51                 -- Write channel Protection type.
52     -- This signal indicates the privilege and security level of the transaction,
53     -- and whether the transaction is a data access or an instruction access.
54                 M_AXI_AWPROT    : out std_logic_vector(2 downto 0);
55                 -- Write address valid.
56     -- This signal indicates that the master signaling valid write address and control information.
57                 M_AXI_AWVALID   : out std_logic;
58                 -- Write address ready.
59     -- This signal indicates that the slave is ready to accept an address and associated control signals.
60                 M_AXI_AWREADY   : in std_logic;
61                 -- Master Interface Write Data Channel ports. Write data (issued by master)
62                 M_AXI_WDATA     : out std_logic_vector(C_M_AXI_DATA_WIDTH-1 downto 0);
63                 -- Write strobes.
64     -- This signal indicates which byte lanes hold valid data.
65     -- There is one write strobe bit for each eight bits of the write data bus.
66                 M_AXI_WSTRB     : out std_logic_vector(C_M_AXI_DATA_WIDTH/8-1 downto 0);
67                 -- Write valid. This signal indicates that valid write data and strobes are available.
68                 M_AXI_WVALID    : out std_logic;
69                 -- Write ready. This signal indicates that the slave can accept the write data.
70                 M_AXI_WREADY    : in std_logic;
71                 -- Master Interface Write Response Channel ports.
72     -- This signal indicates the status of the write transaction.
73                 M_AXI_BRESP     : in std_logic_vector(1 downto 0);
74                 -- Write response valid.
75     -- This signal indicates that the channel is signaling a valid write response
76                 M_AXI_BVALID    : in std_logic;
77                 -- Response ready. This signal indicates that the master can accept a write response.
78                 M_AXI_BREADY    : out std_logic;
79                 -- Master Interface Read Address Channel ports. Read address (issued by master)
80                 M_AXI_ARADDR    : out std_logic_vector(C_M_AXI_ADDR_WIDTH-1 downto 0);
81                 -- Protection type.
82     -- This signal indicates the privilege and security level of the transaction,
83     -- and whether the transaction is a data access or an instruction access.
84                 M_AXI_ARPROT    : out std_logic_vector(2 downto 0);
85                 -- Read address valid.
86     -- This signal indicates that the channel is signaling valid read address and control information.
87                 M_AXI_ARVALID   : out std_logic;
88                 -- Read address ready.
89     -- This signal indicates that the slave is ready to accept an address and associated control signals.
90                 M_AXI_ARREADY   : in std_logic;
91                 -- Master Interface Read Data Channel ports. Read data (issued by slave)
92                 M_AXI_RDATA     : in std_logic_vector(C_M_AXI_DATA_WIDTH-1 downto 0);
93                 -- Read response. This signal indicates the status of the read transfer.
94                 M_AXI_RRESP     : in std_logic_vector(1 downto 0);
95                 -- Read valid. This signal indicates that the channel is signaling the required read data.
96                 M_AXI_RVALID    : in std_logic;
97                 -- Read ready. This signal indicates that the master can accept the read data and response information.
98                 M_AXI_RREADY    : out std_logic
99         );
100 end axi_pwm_coprocessor_v1_0_M00_AXI;
101
102 architecture implementation of axi_pwm_coprocessor_v1_0_M00_AXI is
103
104         -- function called clogb2 that returns an integer which has the
105         -- value of the ceiling of the log base 2
106         function clogb2 (bit_depth : integer) return integer is
107                 variable depth  : integer := bit_depth;
108                 variable count  : integer := 1;
109          begin
110                  for clogb2 in 1 to bit_depth loop  -- Works for up to 32 bit integers
111               if (bit_depth <= 2) then
112                 count := 1;
113               else
114                 if(depth <= 1) then
115                        count := count;
116                      else
117                        depth := depth / 2;
118                   count := count + 1;
119                      end if;
120                    end if;
121            end loop;
122            return(count);
123          end;
124
125         -- Example user application signals
126
127         -- TRANS_NUM_BITS is the width of the index counter for
128         -- number of write or read transaction..
129          constant  TRANS_NUM_BITS  : integer := clogb2(C_M_TRANSACTIONS_NUM-1);
130
131         -- Example State machine to initialize counter, initialize write transactions,
132          -- initialize read transactions and comparison of read data with the
133          -- written data words.
134          type state is ( IDLE, -- This state initiates AXI4Lite transaction
135                                                                 -- after the state machine changes state to INIT_WRITE
136                                                                 -- when there is 0 to 1 transition on INIT_AXI_TXN
137                                         INIT_WRITE,   -- This state initializes write transaction,
138                                                                 -- once writes are done, the state machine
139                                                                 -- changes state to INIT_READ
140                                         INIT_READ,    -- This state initializes read transaction
141                                                                 -- once reads are done, the state machine
142                                                                 -- changes state to INIT_COMPARE
143                                         INIT_COMPARE);-- This state issues the status of comparison
144                                                                 -- of the written data with the read data
145
146          signal mst_exec_state  : state ;
147
148         -- AXI4LITE signals
149         --write address valid
150         signal axi_awvalid      : std_logic;
151         --write data valid
152         signal axi_wvalid       : std_logic;
153         --read address valid
154         signal axi_arvalid      : std_logic;
155         --read data acceptance
156         signal axi_rready       : std_logic;
157         --write response acceptance
158         signal axi_bready       : std_logic;
159         --write address
160         signal axi_awaddr       : std_logic_vector(C_M_AXI_ADDR_WIDTH-1 downto 0);
161         --write data
162         signal axi_wdata        : std_logic_vector(C_M_AXI_DATA_WIDTH-1 downto 0);
163         --read addresss
164         signal axi_araddr       : std_logic_vector(C_M_AXI_ADDR_WIDTH-1 downto 0);
165         --Asserts when there is a write response error
166         signal write_resp_error : std_logic;
167         --Asserts when there is a read response error
168         signal read_resp_error  : std_logic;
169         --A pulse to initiate a write transaction
170         signal start_single_write       : std_logic;
171         --A pulse to initiate a read transaction
172         signal start_single_read        : std_logic;
173         --Asserts when a single beat write transaction is issued and remains asserted till the completion of write trasaction.
174         signal write_issued     : std_logic;
175         --Asserts when a single beat read transaction is issued and remains asserted till the completion of read trasaction.
176         signal read_issued      : std_logic;
177         --flag that marks the completion of write trasactions. The number of write transaction is user selected by the parameter C_M_TRANSACTIONS_NUM.
178         signal writes_done      : std_logic;
179         --flag that marks the completion of read trasactions. The number of read transaction is user selected by the parameter C_M_TRANSACTIONS_NUM
180         signal reads_done       : std_logic;
181         --The error register is asserted when any of the write response error, read response error or the data mismatch flags are asserted.
182         signal error_reg        : std_logic;
183         --index counter to track the number of write transaction issued
184         signal write_index      : std_logic_vector(TRANS_NUM_BITS downto 0);
185         --index counter to track the number of read transaction issued
186         signal read_index       : std_logic_vector(TRANS_NUM_BITS downto 0);
187         --Expected read data used to compare with the read data.
188         signal expected_rdata   : std_logic_vector(C_M_AXI_DATA_WIDTH-1 downto 0);
189         --Flag marks the completion of comparison of the read data with the expected read data
190         signal compare_done     : std_logic;
191         --This flag is asserted when there is a mismatch of the read data with the expected read data.
192         signal read_mismatch    : std_logic;
193         --Flag is asserted when the write index reaches the last write transction number
194         signal last_write       : std_logic;
195         --Flag is asserted when the read index reaches the last read transction number
196         signal last_read        : std_logic;
197         signal init_txn_ff      : std_logic;
198         signal init_txn_ff2     : std_logic;
199         signal init_txn_edge    : std_logic;
200         signal init_txn_pulse   : std_logic;
201
202         signal INIT_AXI_TXN     : std_logic := '0';
203
204         signal pwm_state_prev : std_logic_vector(1 downto 0) := "00";
205         signal pwm_state_inpr : std_logic_vector(1 downto 0) := "00";
206
207 begin
208         -- I/O Connections assignments
209
210         --Adding the offset address to the base addr of the slave
211         -- M_AXI_AWADDR <= std_logic_vector (unsigned(C_M_TARGET_SLAVE_BASE_ADDR) + unsigned(axi_awaddr));
212         M_AXI_AWADDR    <= pwm_wr_addr;
213         --AXI 4 write data
214         M_AXI_WDATA     <= pwm_wr1 when (pwm_state_inpr = "01")
215                   else pwm_wr2 when (pwm_state_inpr = "01")
216                   else pwm_wr0;
217
218         M_AXI_AWPROT    <= "000";
219         M_AXI_AWVALID   <= axi_awvalid;
220         --Write Data(W)
221         M_AXI_WVALID    <= axi_wvalid;
222         --Set all byte strobes in this example
223         M_AXI_WSTRB     <= "1111";
224         --Write Response (B)
225         M_AXI_BREADY    <= axi_bready;
226         --Read Address (AR)
227         M_AXI_ARADDR    <= std_logic_vector(unsigned(C_M_TARGET_SLAVE_BASE_ADDR) + unsigned(axi_araddr));
228         M_AXI_ARVALID   <= axi_arvalid;
229         M_AXI_ARPROT    <= "001";
230         --Read and Read Response (R)
231         M_AXI_RREADY    <= axi_rready;
232         --Example design I/O
233         TXN_DONE        <= compare_done;
234         init_txn_pulse  <= ( not init_txn_ff2)  and  init_txn_ff;
235
236         process(M_AXI_ACLK)
237         begin
238           if (rising_edge (M_AXI_ACLK)) then
239               -- Initiates AXI transaction delay
240             if (M_AXI_ARESETN = '0' ) or (pwm_enabled_i = '0') then
241               INIT_AXI_TXN <= '0';
242             else
243               pwm_state_inpr <= pwm_state_inpr;
244               if (pwm_state_prev = pwm_state_i) or (mst_exec_state /= IDLE) then
245                 INIT_AXI_TXN <= '0';
246               else
247                 INIT_AXI_TXN <= '1';
248                 pwm_state_inpr <= pwm_state_inpr;
249               end if;
250             end if;
251           end if;
252         end process;
253
254         --Generate a pulse to initiate AXI transaction.
255         process(M_AXI_ACLK)
256         begin
257           if (rising_edge (M_AXI_ACLK)) then
258               -- Initiates AXI transaction delay
259             if (M_AXI_ARESETN = '0' ) then
260               init_txn_ff <= '0';
261                 init_txn_ff2 <= '0';
262             else
263               init_txn_ff <= INIT_AXI_TXN;
264                 init_txn_ff2 <= init_txn_ff;
265             end if;
266           end if;
267         end process;
268
269
270         ----------------------
271         --Write Address Channel
272         ----------------------
273
274         -- The purpose of the write address channel is to request the address and
275         -- command information for the entire transaction.  It is a single beat
276         -- of information.
277
278         -- Note for this example the axi_awvalid/axi_wvalid are asserted at the same
279         -- time, and then each is deasserted independent from each other.
280         -- This is a lower-performance, but simplier control scheme.
281
282         -- AXI VALID signals must be held active until accepted by the partner.
283
284         -- A data transfer is accepted by the slave when a master has
285         -- VALID data and the slave acknoledges it is also READY. While the master
286         -- is allowed to generated multiple, back-to-back requests by not
287         -- deasserting VALID, this design will add rest cycle for
288         -- simplicity.
289
290         -- Since only one outstanding transaction is issued by the user design,
291         -- there will not be a collision between a new request and an accepted
292         -- request on the same clock cycle.
293
294           process(M_AXI_ACLK)
295           begin
296             if (rising_edge (M_AXI_ACLK)) then
297               --Only VALID signals must be deasserted during reset per AXI spec
298               --Consider inverting then registering active-low reset for higher fmax
299               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
300                 axi_awvalid <= '0';
301               else
302                 --Signal a new address/data command is available by user logic
303                 if (start_single_write = '1') then
304                   axi_awvalid <= '1';
305                 elsif (M_AXI_AWREADY = '1' and axi_awvalid = '1') then
306                   --Address accepted by interconnect/slave (issue of M_AXI_AWREADY by slave)
307                   axi_awvalid <= '0';
308                 end if;
309               end if;
310             end if;
311           end process;
312
313           -- start_single_write triggers a new write
314           -- transaction. write_index is a counter to
315           -- keep track with number of write transaction
316           -- issued/initiated
317           process(M_AXI_ACLK)
318           begin
319             if (rising_edge (M_AXI_ACLK)) then
320               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
321                 write_index <= (others => '0');
322               elsif (start_single_write = '1') then
323                 -- Signals a new write address/ write data is
324                 -- available by user logic
325                 write_index <= std_logic_vector (unsigned(write_index) + 1);
326               end if;
327             end if;
328           end process;
329
330
331         ----------------------
332         --Write Data Channel
333         ----------------------
334
335         --The write data channel is for transfering the actual data.
336         --The data generation is speific to the example design, and
337         --so only the WVALID/WREADY handshake is shown here
338
339            process(M_AXI_ACLK)
340            begin
341              if (rising_edge (M_AXI_ACLK)) then
342                if (M_AXI_ARESETN = '0' or init_txn_pulse = '1' ) then
343                  axi_wvalid <= '0';
344                  pwm_state_prev <= "00";
345                else
346                  if (start_single_write = '1') then
347                    --Signal a new address/data command is available by user logic
348                    axi_wvalid <= '1';
349                  elsif (M_AXI_WREADY = '1' and axi_wvalid = '1') then
350                    --Data accepted by interconnect/slave (issue of M_AXI_WREADY by slave)
351                    axi_wvalid <= '0';
352                  end if;
353                end if;
354              end if;
355            end process;
356
357
358         ------------------------------
359         --Write Response (B) Channel
360         ------------------------------
361
362         --The write response channel provides feedback that the write has committed
363         --to memory. BREADY will occur after both the data and the write address
364         --has arrived and been accepted by the slave, and can guarantee that no
365         --other accesses launched afterwards will be able to be reordered before it.
366
367         --The BRESP bit [1] is used indicate any errors from the interconnect or
368         --slave for the entire write burst. This example will capture the error.
369
370         --While not necessary per spec, it is advisable to reset READY signals in
371         --case of differing reset latencies between master/slave.
372
373           process(M_AXI_ACLK)
374           begin
375             if (rising_edge (M_AXI_ACLK)) then
376               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
377                 axi_bready <= '0';
378               else
379                 if (M_AXI_BVALID = '1' and axi_bready = '0') then
380                   -- accept/acknowledge bresp with axi_bready by the master
381                   -- when M_AXI_BVALID is asserted by slave
382                    axi_bready <= '1';
383                 elsif (axi_bready = '1') then
384                   -- deassert after one clock cycle
385                   axi_bready <= '0';
386                 end if;
387               end if;
388             end if;
389           end process;
390         --Flag write errors
391           write_resp_error <= (axi_bready and M_AXI_BVALID and M_AXI_BRESP(1));
392
393
394         ------------------------------
395         --Read Address Channel
396         ------------------------------
397
398         --start_single_read triggers a new read transaction. read_index is a counter to
399         --keep track with number of read transaction issued/initiated
400
401           process(M_AXI_ACLK)
402           begin
403             if (rising_edge (M_AXI_ACLK)) then
404               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
405                 read_index <= (others => '0');
406               else
407                 if (start_single_read = '1') then
408                   -- Signals a new read address is
409                   -- available by user logic
410                   read_index <= std_logic_vector (unsigned(read_index) + 1);
411                 end if;
412               end if;
413             end if;
414           end process;
415
416           -- A new axi_arvalid is asserted when there is a valid read address
417           -- available by the master. start_single_read triggers a new read
418           -- transaction
419           process(M_AXI_ACLK)
420           begin
421             if (rising_edge (M_AXI_ACLK)) then
422               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
423                 axi_arvalid <= '0';
424               else
425                 if (start_single_read = '1') then
426                   --Signal a new read address command is available by user logic
427                   axi_arvalid <= '1';
428                 elsif (M_AXI_ARREADY = '1' and axi_arvalid = '1') then
429                 --RAddress accepted by interconnect/slave (issue of M_AXI_ARREADY by slave)
430                   axi_arvalid <= '0';
431                 end if;
432               end if;
433             end if;
434           end process;
435
436
437         ----------------------------------
438         --Read Data (and Response) Channel
439         ----------------------------------
440
441         --The Read Data channel returns the results of the read request
442         --The master will accept the read data by asserting axi_rready
443         --when there is a valid read data available.
444         --While not necessary per spec, it is advisable to reset READY signals in
445         --case of differing reset latencies between master/slave.
446
447           process(M_AXI_ACLK)
448           begin
449             if (rising_edge (M_AXI_ACLK)) then
450               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
451                 axi_rready <= '1';
452               else
453                 if (M_AXI_RVALID = '1' and axi_rready = '0') then
454                  -- accept/acknowledge rdata/rresp with axi_rready by the master
455                  -- when M_AXI_RVALID is asserted by slave
456                   axi_rready <= '1';
457                 elsif (axi_rready = '1') then
458                   -- deassert after one clock cycle
459                   axi_rready <= '0';
460                 end if;
461               end if;
462             end if;
463           end process;
464
465         --Flag write errors
466           read_resp_error <= (axi_rready and M_AXI_RVALID and M_AXI_RRESP(1));
467
468
469         ----------------------------------
470         --User Logic
471         ----------------------------------
472
473         --Address/Data Stimulus
474
475         --Address/data pairs for this example. The read and write values should
476         --match.
477         --Modify these as desired for different address patterns.
478
479         --  Write Addresses
480             process(M_AXI_ACLK)
481               begin
482                 if (rising_edge (M_AXI_ACLK)) then
483                   if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
484                     axi_awaddr <= (others => '0');
485                   elsif (M_AXI_AWREADY = '1' and axi_awvalid = '1') then
486                     -- Signals a new write address/ write data is
487                     -- available by user logic
488                     axi_awaddr <= std_logic_vector (unsigned(axi_awaddr) + 4);
489                   end if;
490                 end if;
491               end process;
492
493         -- Read Addresses
494             process(M_AXI_ACLK)
495                   begin
496                     if (rising_edge (M_AXI_ACLK)) then
497                       if (M_AXI_ARESETN = '0' or init_txn_pulse = '1' ) then
498                         axi_araddr <= (others => '0');
499                       elsif (M_AXI_ARREADY = '1' and axi_arvalid = '1') then
500                         -- Signals a new write address/ write data is
501                         -- available by user logic
502                         axi_araddr <= std_logic_vector (unsigned(axi_araddr) + 4);
503                       end if;
504                     end if;
505                   end process;
506
507         -- Write data
508             process(M_AXI_ACLK)
509                   begin
510                     if (rising_edge (M_AXI_ACLK)) then
511                       if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
512                         axi_wdata <= C_M_START_DATA_VALUE;
513                       elsif (M_AXI_WREADY = '1' and axi_wvalid = '1') then
514                         -- Signals a new write address/ write data is
515                         -- available by user logic
516                         axi_wdata <= std_logic_vector (unsigned(C_M_START_DATA_VALUE) + unsigned(write_index));
517                       end if;
518                     end if;
519                   end process;
520
521
522         -- Expected read data
523             process(M_AXI_ACLK)
524             begin
525               if (rising_edge (M_AXI_ACLK)) then
526                 if (M_AXI_ARESETN = '0' or init_txn_pulse = '1' ) then
527                   expected_rdata <= C_M_START_DATA_VALUE;
528                 elsif (M_AXI_RVALID = '1' and axi_rready = '1') then
529                   -- Signals a new write address/ write data is
530                   -- available by user logic
531                   expected_rdata <= std_logic_vector (unsigned(C_M_START_DATA_VALUE) + unsigned(read_index));
532                 end if;
533               end if;
534             end process;
535           --implement master command interface state machine
536           MASTER_EXECUTION_PROC:process(M_AXI_ACLK)
537           begin
538             if (rising_edge (M_AXI_ACLK)) then
539               if (M_AXI_ARESETN = '0' ) then
540                 -- reset condition
541                 -- All the signals are ed default values under reset condition
542                 mst_exec_state  <= IDLE;
543                 start_single_write <= '0';
544                 write_issued   <= '0';
545                 start_single_read  <= '0';
546                 read_issued  <= '0';
547                 compare_done   <= '0';
548                 ERROR <= '0';
549             pwm_state_prev <= "00";
550               else
551             pwm_state_prev <= pwm_state_prev;
552                 -- state transition
553                 case (mst_exec_state) is
554
555                   when IDLE =>
556                     -- This state is responsible to initiate
557                     -- AXI transaction when init_txn_pulse is asserted
558                     if ( init_txn_pulse = '1') then
559                       mst_exec_state  <= INIT_WRITE;
560                       ERROR <= '0';
561                       compare_done <= '0';
562                     else
563                       mst_exec_state  <= IDLE;
564                     end if;
565
566                   when INIT_WRITE =>
567                     -- This state is responsible to issue start_single_write pulse to
568                     -- initiate a write transaction. Write transactions will be
569                     -- issued until last_write signal is asserted.
570                     -- write controller
571                     if (writes_done = '1') then
572                       -- mst_exec_state <= INIT_READ;
573                       mst_exec_state <= IDLE;
574                       pwm_state_prev <= pwm_state_inpr;
575                     else
576                       mst_exec_state  <= INIT_WRITE;
577
578                       if (axi_awvalid = '0' and axi_wvalid = '0' and M_AXI_BVALID = '0' and
579                         last_write = '0' and start_single_write = '0' and write_issued = '0') then
580                         start_single_write <= '1';
581                         write_issued  <= '1';
582                       elsif (axi_bready = '1') then
583                         write_issued   <= '0';
584                       else
585                         start_single_write <= '0'; --Negate to generate a pulse
586                       end if;
587                     end if;
588
589                   when INIT_READ =>
590                     -- This state is responsible to issue start_single_read pulse to
591                     -- initiate a read transaction. Read transactions will be
592                     -- issued until last_read signal is asserted.
593                     -- read controller
594                     if (reads_done = '1') then
595                       mst_exec_state <= INIT_COMPARE;
596                     else
597                       mst_exec_state  <= INIT_READ;
598
599                       if (axi_arvalid = '0' and M_AXI_RVALID = '0' and last_read = '0' and
600                         start_single_read = '0' and read_issued = '0') then
601                         start_single_read <= '1';
602                         read_issued   <= '1';
603                       elsif (axi_rready = '1') then
604                         read_issued   <= '0';
605                       else
606                         start_single_read <= '0'; --Negate to generate a pulse
607                       end if;
608                     end if;
609
610                   when INIT_COMPARE =>
611                     -- This state is responsible to issue the state of comparison
612                     -- of written data with the read data. If no error flags are set,
613                     -- compare_done signal will be asseted to indicate success.
614                     ERROR <= error_reg;
615                     mst_exec_state <= IDLE;
616                     compare_done <= '1';
617
618                   when others  =>
619                       mst_exec_state  <= IDLE;
620                 end case  ;
621               end if;
622             end if;
623           end process;
624
625         --Terminal write count
626           process(M_AXI_ACLK)
627           begin
628             if (rising_edge (M_AXI_ACLK)) then
629               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
630                 -- reset condition
631                 last_write <= '0';
632               else
633                 --The last write should be associated with a write address ready response
634                 if (write_index = STD_LOGIC_VECTOR(TO_UNSIGNED(C_M_TRANSACTIONS_NUM, TRANS_NUM_BITS+1)) and M_AXI_AWREADY = '1') then
635                   last_write  <= '1';
636                 end if;
637               end if;
638             end if;
639           end process;
640
641         --/*
642         -- Check for last write completion.
643         --
644         -- This logic is to qualify the last write count with the final write
645         -- response. This demonstrates how to confirm that a write has been
646         -- committed.
647         -- */
648           process(M_AXI_ACLK)
649           begin
650             if (rising_edge (M_AXI_ACLK)) then
651               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
652                 -- reset condition
653                 writes_done <= '0';
654               else
655                 if (last_write = '1' and M_AXI_BVALID = '1' and axi_bready = '1') then
656                   --The writes_done should be associated with a bready response
657                   writes_done <= '1';
658                 end if;
659               end if;
660             end if;
661           end process;
662
663         --------------
664         --Read example
665         --------------
666
667         --Terminal Read Count
668
669           process(M_AXI_ACLK)
670           begin
671             if (rising_edge (M_AXI_ACLK)) then
672               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
673                 last_read <= '0';
674               else
675                 if (read_index = STD_LOGIC_VECTOR(TO_UNSIGNED(C_M_TRANSACTIONS_NUM, TRANS_NUM_BITS+1)) and (M_AXI_ARREADY = '1') ) then
676                   --The last read should be associated with a read address ready response
677                   last_read <= '1';
678                 end if;
679               end if;
680             end if;
681           end process;
682
683
684         --/*
685         -- Check for last read completion.
686         --
687         -- This logic is to qualify the last read count with the final read
688         -- response/data.
689         -- */
690           process(M_AXI_ACLK)
691           begin
692             if (rising_edge (M_AXI_ACLK)) then
693               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
694                 reads_done <= '0';
695               else
696                 if (last_read = '1' and M_AXI_RVALID = '1' and axi_rready = '1') then
697                   --The reads_done should be associated with a read ready response
698                   reads_done <= '1';
699                 end if;
700               end if;
701             end if;
702           end process;
703
704
705         ------------------------------/
706         --Example design error register
707         ------------------------------/
708
709         --Data Comparison
710           process(M_AXI_ACLK)
711           begin
712             if (rising_edge (M_AXI_ACLK)) then
713               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
714                 read_mismatch <= '0';
715               else
716                 if ((M_AXI_RVALID = '1' and axi_rready = '1') and  M_AXI_RDATA /= expected_rdata) then
717                   --The read data when available (on axi_rready) is compared with the expected data
718                   read_mismatch <= '1';
719                 end if;
720               end if;
721             end if;
722           end process;
723
724         -- Register and hold any data mismatches, or read/write interface errors
725           process(M_AXI_ACLK)
726           begin
727             if (rising_edge (M_AXI_ACLK)) then
728               if (M_AXI_ARESETN = '0' or init_txn_pulse = '1') then
729                 error_reg <= '0';
730               else
731                 if (read_mismatch = '1' or write_resp_error = '1' or read_resp_error = '1') then
732                   --Capture any error types
733                   error_reg <= '1';
734                 end if;
735               end if;
736             end if;
737           end process;
738
739         -- Add user logic here
740
741         -- User logic ends
742
743 end implementation;