add libraries
authorLuke Kenneth Casson Leighton <lkcl@lkcl.net>
Wed, 25 Jul 2018 03:58:25 +0000 (04:58 +0100)
committerLuke Kenneth Casson Leighton <lkcl@lkcl.net>
Wed, 25 Jul 2018 03:58:25 +0000 (04:58 +0100)
src/lib/QuadMem.bsv [new file with mode: 0644]
src/lib/Stack.bsv [new file with mode: 0644]
src/lib/TxRx.bsv [new file with mode: 0644]
src/testbench/FlexBus_Slave_to_AXI4_Master_Fabric_Types.bsv [new file with mode: 0644]
src/testbench/Memory_AXI4.bsv [new file with mode: 0644]

diff --git a/src/lib/QuadMem.bsv b/src/lib/QuadMem.bsv
new file mode 100644 (file)
index 0000000..438f559
--- /dev/null
@@ -0,0 +1,58 @@
+/*
+Copyright (c) 2013, IIT Madras
+All rights reserved.
+
+Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met:
+
+*  Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer.
+*  Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution.
+*  Neither the name of IIT Madras  nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 
+---------------------------------------------------------------------------------------------------------------------------------------------------------------------------------
+*/
+package QuadMem;
+       import defined_types::*;
+       import BUtils::*;
+       `include "defined_parameters.bsv"
+
+       interface Ifc_QuadMem;
+               method Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) response_portA;
+               method Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) response_portB;
+               method Action write_portA(Bit#(TMul#(`DCACHE_BLOCK_SIZE,`DCACHE_WORD_SIZE)) we, Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) data);
+               method Action write_portB(Bit#(TMul#(`DCACHE_BLOCK_SIZE,`DCACHE_WORD_SIZE)) we, Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) data);
+       endinterface
+
+       (*synthesize*)
+       module mkQuadMem(Ifc_QuadMem);
+               Reg#(Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE))) data_reg[3] <-mkCReg(3,0);
+
+               method Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) response_portA;
+                       return data_reg[0];
+               endmethod
+               method Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) response_portB;
+                       return data_reg[1];
+               endmethod
+               method Action write_portA(Bit#(TMul#(`DCACHE_BLOCK_SIZE,`DCACHE_WORD_SIZE)) we, Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) data);
+         Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) mask=0;
+         for(Integer i=0;i<32;i=i+1)begin
+            Bit#(8) ex_we=duplicate(we[i]);
+            mask[(i*8)+7:i*8]=ex_we;
+         end
+         Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) x = mask& data;
+         Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) y = ~mask& data_reg[0];
+         data_reg[0]<=x|y;
+      endmethod
+               method Action write_portB(Bit#(TMul#(`DCACHE_BLOCK_SIZE,`DCACHE_WORD_SIZE)) we, Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) data);
+         Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) mask=0;
+         for(Integer i=0;i<32;i=i+1)begin
+            Bit#(8) ex_we=duplicate(we[i]);
+            mask[(i*8)+7:i*8]=ex_we;
+         end
+         Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) x = mask& data;
+         Bit#(TMul#(TMul#(8,`DCACHE_WORD_SIZE),`DCACHE_BLOCK_SIZE)) y = ~mask& data_reg[1];
+         data_reg[1]<=x|y;
+      endmethod
+                       
+       endmodule
+endpackage
diff --git a/src/lib/Stack.bsv b/src/lib/Stack.bsv
new file mode 100644 (file)
index 0000000..876d628
--- /dev/null
@@ -0,0 +1,41 @@
+/*
+Copyright (c) 2013, IIT Madras
+All rights reserved.
+
+Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met:
+
+*  Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer.
+*  Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution.
+*  Neither the name of IIT Madras  nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 
+---------------------------------------------------------------------------------------------------------------------------------------------------------------------------------
+*/
+package Stack;
+       import defined_types::*;
+       import RegFile::*;
+       `include "defined_parameters.bsv"
+       interface Ifc_Stack;
+               method Action push(Bit#(`VADDR) addr);
+               method ActionValue#(Bit#(`VADDR)) top;
+               method Bool empty;
+               method Action flush;
+       endinterface
+
+//     (*synthesize*)
+       module mkStack(Ifc_Stack);
+               Reg#(Bit#(TLog#(`RAS_DEPTH))) top_index[2] <-mkCReg(2,0);
+               RegFile#(Bit#(TLog#(`RAS_DEPTH)),Bit#(`VADDR)) array_reg <-mkRegFileWCF(0,fromInteger(`RAS_DEPTH-1));
+               method ActionValue#(Bit#(`VADDR)) top;
+                       top_index[0]<=top_index[0]-1;
+                       return array_reg.sub(top_index[0]-1);
+               endmethod
+               method Action push(Bit#(`VADDR) addr);
+                       array_reg.upd(top_index[1],addr);
+                       top_index[1]<=top_index[1]+1;
+               endmethod
+               method Bool empty;
+                       return (top_index[0]==0);
+               endmethod
+       endmodule
+endpackage
diff --git a/src/lib/TxRx.bsv b/src/lib/TxRx.bsv
new file mode 100644 (file)
index 0000000..b75a43d
--- /dev/null
@@ -0,0 +1,300 @@
+/*
+Copyright (c) 2013, IIT Madras
+All rights reserved.
+
+Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met:
+
+*  Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer.
+*  Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution.
+*  Neither the name of IIT Madras  nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 
+---------------------------------------------------------------------------------------------------------------------------------------------------------------------------------
+*/
+// Copyright (c) 2013-2017 Bluespec, Inc.  All Rights Reserved
+
+package TxRx;
+
+// ================================================================
+// This package allows a separately synthesized module to have direct
+// access to an external communication channel via FIFOF-like interfaces
+// (methods: notFull, enq, notEmpty, first, deq),
+// without the overhead or latency of an internal FIFOs.
+
+// THE PROBLEM: suppose we want module M1 to send messages to M2
+// Inside M1, we can instantiate a FIFO f1, and enqueue into it,
+// and return g1 = toGet (f1) as part of M1's interface.
+// Inside M2, we can instantiate a FIFO f2, and dequeue from it,
+// and return p2 = toPut (f2) as part of M2's interface.
+// Outside, we connect them with mkConnection(g1,p2).
+// Problem 1: there are 2 ticks of latency in the communication
+// Problem 2: there are at least 2 state elements to hold messages
+// Ideally, we'd like to instantiate a FIFO externally,
+// and pass it as a parameter to M1 and M2
+// so that M1 can enq to it, and M2 can dequeue from it.
+// But then M1 and M2 cannot be separately synthesized.
+
+// This package provides a solution.
+// Terminology: the channel has a tail (enq side) and a head (deq side).
+// Inside M1 (for outgoing data):
+//     Instantiate:    TX #(t) tx <- mkTX;
+//     Use tx.u to send data (methods enq, notFull).
+//     Export tx.e as part of M1's interface.
+// Inside M2 (for incoming data):
+//     Instantiate:    RX #(t) rx <- mkRX;
+//     Use rx.u to receive data (methods first, deq, notEmpty).
+//     Export rx.e as part of M2's interface.
+//
+// Outside, use 'mkChan (buffer_fifof, m1.txe, m2.rxe)' to make an external
+//        communication channel, passing in a module with a FIFOF
+//        interface to instantiate the intermediate buffer.
+//        The buffer could be mkFIFOF, mkPipelineFIFOF, mkSizedFIFOF, ...
+//
+// You can also connect each to a FIFOF:
+//    mkConnection (m1.txe, fifof)
+//    mkConnection (fifof,  m2.rxe)
+
+// ================================================================
+// BSV library imports
+
+import FIFOF       :: *;
+import GetPut      :: *;
+import Connectable :: *;
+
+// ================================================================
+// TX (sender side)
+
+// This interface is used by the sender
+
+interface TXu #(type t);
+   method Bool   notFull;
+   method Action enq (t x);
+endinterface
+
+instance ToPut #(TXu #(t), t);
+   function Put #(t) toPut (TXu #(t) f_in);
+      return interface Put;
+               method Action put (t x);
+                  f_in.enq (x);
+               endmethod
+            endinterface;
+   endfunction
+endinstance
+
+// This interface is exported by the sender
+
+(* always_enabled, always_ready *)
+interface TXe #(type t);
+   method Action notFull (Bool b);
+   method Action enq_rdy (Bool b);
+   method Bool   enq_ena;
+   method t      enq_data;
+endinterface
+
+// ----------------------------------------------------------------
+// Connecting a TXe to an ordinary FIFOF
+
+instance Connectable #(FIFOF #(t), TXe #(t));
+   module mkConnection #(FIFOF #(t) fifo, TXe #(t) txe)
+                       (Empty);
+      (* fire_when_enabled, no_implicit_conditions *)
+      rule connect_notFull;
+        txe.notFull (fifo.notFull);
+      endrule
+
+      (* fire_when_enabled, no_implicit_conditions *)
+      rule connect_rdy;
+        txe.enq_rdy (fifo.notFull);
+      endrule
+
+      rule connect_ena_data (txe.enq_ena);
+        fifo.enq (txe.enq_data);
+      endrule
+   endmodule
+endinstance
+
+instance Connectable #(TXe #(t), FIFOF #(t));
+   module mkConnection #(TXe #(t) txe, FIFOF #(t) fifo)
+                       (Empty);
+      mkConnection (fifo, txe);
+   endmodule
+endinstance
+
+// ----------------------------------------------------------------
+// Transactor from TXu to TXe interface
+
+interface TX #(type t);
+   interface TXu #(t) u;
+   interface TXe #(t) e;
+endinterface
+
+module mkTX (TX #(t))
+   provisos (Bits #(t, tsz));
+
+   Wire #(Bool) w_notFull <- mkBypassWire;
+   Wire #(Bool) w_rdy     <- mkBypassWire;
+   Wire #(Bool) w_ena     <- mkDWire (False);
+   Wire #(t)    w_data    <- mkDWire (?);
+
+   interface TXu u;
+      method Bool notFull;
+        return w_notFull;
+      endmethod
+
+      method Action enq (t x) if (w_rdy);
+        w_ena <= True;
+        w_data <= x;
+      endmethod
+   endinterface
+
+   interface TXe e;
+      method Action notFull (Bool b);
+        w_notFull <= b;
+      endmethod
+
+      method Action enq_rdy (Bool b);
+        w_rdy <= b;
+      endmethod
+
+      method Bool enq_ena;
+        return w_ena;
+      endmethod
+
+      method t enq_data;
+        return w_data;
+      endmethod
+   endinterface
+endmodule: mkTX
+
+// ================================================================
+// RX (receiver side)
+
+// This interface is used by the receiver
+
+interface RXu #(type t);
+   method Bool   notEmpty;
+   method t      first;
+   method Action deq;
+endinterface
+
+instance ToGet #(RXu #(t), t);
+   function Get #(t) toGet (RXu #(t) f_out);
+      return interface Get;
+               method ActionValue #(t) get;
+                  f_out.deq;
+                  return f_out.first;
+               endmethod
+            endinterface;
+   endfunction
+endinstance
+
+// This interface is exported by the receiver
+
+(* always_enabled, always_ready *)
+interface RXe #(type t);
+   method Action notEmpty (Bool b);
+   method Action first_deq_rdy (Bool b);
+   method Action first (t x);
+   method Bool   deq_ena;
+endinterface
+
+// ----------------------------------------------------------------
+// Connecting an ordinary FIFOF to an RXe
+
+instance Connectable #(FIFOF #(t), RXe #(t));
+   module mkConnection #(FIFOF #(t) fifo, RXe #(t) rxe)
+                       (Empty);
+      (* fire_when_enabled, no_implicit_conditions *)
+      rule connect_notEmpty;
+        rxe.notEmpty (fifo.notEmpty);
+      endrule
+
+      (* fire_when_enabled, no_implicit_conditions *)
+      rule connect_rdy;
+        rxe.first_deq_rdy (fifo.notEmpty);
+      endrule
+
+      rule connect_first;
+        let data = (fifo.notEmpty ? fifo.first : ?);
+        rxe.first (data);
+      endrule
+
+      rule connect_ena (rxe.deq_ena);
+        fifo.deq;
+      endrule
+   endmodule
+endinstance
+
+instance Connectable #(RXe #(t), FIFOF #(t));
+   module mkConnection #(RXe #(t) rxe, FIFOF #(t) fifo)
+                       (Empty);
+      mkConnection (fifo, rxe);
+   endmodule
+endinstance
+
+// ----------------------------------------------------------------
+// Transactor from RXe to RXu interface
+
+interface RX #(type t);
+   interface RXu #(t) u;
+   interface RXe #(t) e;
+endinterface
+
+module mkRX (RX #(t))
+   provisos (Bits #(t, tsz));
+
+   Wire #(Bool) w_notEmpty <- mkBypassWire;
+   Wire #(Bool) w_rdy      <- mkBypassWire;
+   Wire #(Bool) w_ena      <- mkDWire (False);
+   Wire #(t)    w_data     <- mkDWire (?);
+
+   interface RXu u;
+      method Bool notEmpty;
+        return w_notEmpty;
+      endmethod
+
+      method t first if (w_rdy);
+        return w_data;
+      endmethod
+
+      method Action deq () if (w_rdy);
+        w_ena <= True;
+      endmethod
+   endinterface
+
+   interface RXe e;
+      method Action notEmpty (Bool b);
+        w_notEmpty <= b;
+      endmethod
+
+      method Action first_deq_rdy (Bool b);
+        w_rdy <= b;
+      endmethod
+
+      method Action first (t x);
+        w_data <= x;
+      endmethod
+
+      method Bool deq_ena;
+        return w_ena;
+      endmethod
+   endinterface
+endmodule: mkRX
+
+// ================================================================
+// Function to connect TXe to RXe, passing in the
+// desired FIFOF constructor for the intermediate buffer
+
+module mkChan #(module #(FIFOF #(t)) mkFIFOF,
+               TXe #(t) txe,
+               RXe #(t) rxe)
+   (Empty);
+
+   let fifof <- mkFIFOF;
+   let empty_txe_to_fifof <- mkConnection (txe,   fifof);
+   let empty_fifof_to_rxe <- mkConnection (fifof, rxe);
+endmodule: mkChan
+
+// ================================================================
+
+endpackage
diff --git a/src/testbench/FlexBus_Slave_to_AXI4_Master_Fabric_Types.bsv b/src/testbench/FlexBus_Slave_to_AXI4_Master_Fabric_Types.bsv
new file mode 100644 (file)
index 0000000..e28b5f7
--- /dev/null
@@ -0,0 +1,399 @@
+
+package FlexBus_Slave_to_AXI4_Master_Fabric_Types;
+
+// ================================================================
+// Exports
+
+export
+
+FlexBus_Slave_to_AXI4_Master_Fabric_IFC (..),
+
+// Transactors from RTL-level interfacecs to FIFO-like interfaces.
+mkFlexBus_Slave_to_AXI4_Master_Fabric;
+
+// ================================================================
+// BSV library imports
+
+import ConfigReg ::*;
+import FIFOF       :: *;
+import SpecialFIFOs::*;
+import Connectable :: *;
+import TriState ::*;
+`include "defined_parameters.bsv"
+
+// ----------------
+// BSV additional libs
+
+import Semi_FIFOF :: *;
+
+import FlexBus_Types :: *; 
+import AXI4_Types   :: *;
+
+function Bit#(wd_addr) address_increment(Bit#(8) arlen, Bit#(3) arsize, Bit#(2) arburst, Bit#(wd_addr) address)
+provisos(
+                Add#(a__, 4, wd_addr),
+                Add#(b__, 3, wd_addr),
+                Add#(c__, 2, wd_addr));
+                // bit_width_size= (2^arsize)*8
+                // arburst = 0(FIXED), 1(INCR) and 2(WRAP)
+                       if(arburst==0) // FIXED
+                             return address;
+                       else if(arburst==1)begin // INCR
+                             return address+ (('b1)<<arsize);
+                       end
+                       else begin // WRAP
+                            let new_addr=address;
+                            case (arlen)
+                                1: new_addr[arsize]=~address[arsize];
+                                3: begin
+                                     if(arsize==0)
+                                           new_addr[1:0]=new_addr[1:0]+1;
+                                     else if(arsize==1)
+                                           new_addr[2:1]=new_addr[2:1]+1;
+                                     else if(arsize==2)
+                                           new_addr[3:2]=new_addr[3:2]+1;
+                                     else if(arsize==3)
+                                           new_addr[4:3]=new_addr[4:3]+1;
+                                   end
+                                7: begin
+                                      if(arsize==0)
+                                           new_addr[2:0]=new_addr[2:0]+1;
+                                      else if(arsize==1)
+                                           new_addr[3:1]=new_addr[3:1]+1;
+                                      else if(arsize==2)
+                                           new_addr[4:2]=new_addr[4:2]+1;
+                                      else if(arsize==3)
+                                           new_addr[5:3]=new_addr[5:3]+1;
+                                   end
+                                15:begin //Bit#(4) x = address[arsize+3:arsize]+1;new_addr[arsize+3:arsize]=x;end
+                                      if(arsize==0)
+                                            new_addr[3:0]=new_addr[3:0]+1;
+                                      else if(arsize==1)
+                                            new_addr[4:1]=new_addr[4:1]+1;
+                                      else if(arsize==2)
+                                            new_addr[5:2]=new_addr[5:2]+1;
+                                      else if(arsize==3)
+                                            new_addr[6:3]=new_addr[6:3]+1;
+                                 end
+                           endcase
+                           return new_addr;
+                    end
+               endfunction
+// ================================================================
+/*
+module mkVerfn_Top (Empty);
+
+       FlexBus_Slave_to_AXI4_Master_Fabric_IFC#(32,32,4) verfn_ifc <- mkFlexBus_Slave_to_AXI4_Master_Fabric;
+
+        AXI4_Slave_to_FlexBus_Master_Xactor_IFC#(32, 32, 4)
+                                                  flexbus_xactor_ifc <- mkAXI4_Slave_to_FlexBus_Master_Xactor;
+
+        mkConnection(flexbus_xactor_ifc.flexbus_side,verfn_ifc.flexbus_side);
+
+endmodule 
+*/
+// ================================================================
+// Master Fabric interface
+
+interface FlexBus_Slave_to_AXI4_Master_Fabric_IFC #(numeric type wd_addr,
+                                       numeric type wd_data,
+                                       numeric type wd_user);
+   method Action reset;
+
+   // FlexBus side
+   interface FlexBus_Slave_IFC flexbus_side;
+
+   // AXI side
+   interface AXI4_Master_IFC #(wd_addr, wd_data, wd_user) axi_side;
+
+endinterface: FlexBus_Slave_to_AXI4_Master_Fabric_IFC
+
+// ----------------------------------------------------------------
+// Master transactor
+
+module mkFlexBus_Slave_to_AXI4_Master_Fabric (FlexBus_Slave_to_AXI4_Master_Fabric_IFC #(wd_addr, wd_data, wd_user))
+provisos(
+                         Add#(a__, 4, wd_addr),
+                         Add#(b__, 3, wd_addr),
+                         Add#(c__, 2, wd_addr),
+             Bits#(Bit#(32), wd_addr),
+             Bits#(Bit#(64), wd_data));
+
+  ConfigReg#(FlexBus_States) flexbus_state_verfn <- mkConfigReg(FlexBus_S1_ADDR);
+
+  Reg#(Bit#(32)) r_AD  <- mkReg(32'h00000000);
+  Reg#(Bit#(1)) r_ALE          <- mkReg(1'b0);
+  Reg#(Bit#(1)) r_R_Wn                 <- mkReg(1'b0);
+  Reg#(Bit#(2)) r_TSIZ                 <- mkReg(2'b00);
+  Reg#(Bit#(6)) r_FBCSn        <- mkReg(6'h00);
+  Reg#(Bit#(4)) r_BE_BWEn      <- mkReg(4'h0);
+  Reg#(Bit#(1)) r_TBSTn        <- mkReg(1'b0);
+  Reg#(Bit#(1)) r_OEn          <- mkReg(1'b0);
+
+  Reg#(Bool)    r1_OEn      <- mkReg(True);
+
+  Reg#(Bit#(32)) r_din         <- mkReg(0);
+  Reg#(Bit#(1)) r_TAn          <- mkReg(1'b0);
+
+  Reg#(Bit#(6)) r_WS_val       <- mkReg(6'h02);
+  Reg#(Bit#(6)) r_WS           <- mkReg(6'h00);
+
+   Bool unguarded = True;
+   Bool guarded   = False;
+
+  Reg#(Maybe#(AXI4_Wr_Addr #(wd_addr, wd_user))) f_wr_addr[3] <-mkCReg(3,tagged Invalid);
+  Reg#(Maybe#(AXI4_Wr_Data #(wd_data)))          f_wr_data[3] <-mkCReg(3,tagged Invalid);
+  Reg#(Maybe#(AXI4_Wr_Resp #(wd_user)))          f_wr_resp[3] <-mkCReg(3,tagged Invalid);
+
+
+   Reg#(Maybe#(AXI4_Rd_Addr #(wd_addr, wd_user)))  f_rd_addr[3] <- mkCReg(3,tagged Invalid);
+   Reg#(Maybe#(AXI4_Rd_Data #(wd_data, wd_user))) f_rd_data[3] <- mkCReg(3, tagged Invalid);
+   Reg#(Maybe#(AXI4_Rd_Addr #(wd_addr, wd_user)))  rd_req_reg[2] <- mkCReg(2,tagged Invalid);
+        Reg#(Bit#(8)) rg_read_burst_cycle <-mkReg(0);
+
+   //  TriState#(Bit#(32)) tri_AD_in <- mkTriState(!r1_OEn,r_din);
+
+        rule rl_OEn;
+            if (r_OEn == 1'b0)
+                r1_OEn <= False;
+            else
+                r1_OEn <= True;
+        endrule
+
+     //   rule rl_read_AD_bus;
+       //     r_AD <= tri_AD_in._read;
+     //   endrule
+
+               rule generate_read_request(rd_req_reg[1] matches tagged Valid .ar &&& f_rd_addr[0] matches tagged Invalid);
+                       `ifdef verbose_debug_ver $display("generate_read_request FIRED");`endif
+                       `ifdef verbose $display($time,"\tAXI4MasterRead: Generating Read Request for Address: %h BurstSize: %d BurstLength: %d BurstMode: :%d",ar.araddr,ar.arsize,ar.arlen,ar.arburst); `endif
+                       f_rd_addr[0]<=tagged Valid ar;
+                       let info=ar;
+                       if(ar.arlen==rg_read_burst_cycle) begin// end of burst
+                               rd_req_reg[1]<= tagged Invalid;
+                               rg_read_burst_cycle<=0;
+                       end
+                       else begin
+                               info.araddr=address_increment(ar.arlen,ar.arsize,ar.arburst,ar.araddr);
+                               rg_read_burst_cycle<=rg_read_burst_cycle+1;
+                               rd_req_reg[1]<=tagged Valid info;
+                       end
+               endrule
+
+   Reg#(Maybe#(AXI4_Wr_Addr #(wd_addr, wd_user)))  wr_req_reg[2] <- mkCReg(2,tagged Invalid);
+   Reg#(Maybe#(AXI4_Wr_Data #(wd_data)))  wr_data_reg[2] <- mkCReg(2,tagged Invalid);
+        Reg#(Bit#(8)) rg_write_burst_cycle <-mkReg(0);
+        rule generate_write_request(wr_req_reg[1] matches tagged Valid .ar &&& wr_data_reg[1] matches tagged Valid .wd &&& f_wr_addr[0] matches tagged Invalid &&& f_wr_data[0] matches tagged Invalid);
+                       `ifdef verbose_debug_ver $display("generate_write_request FIRED"); `endif
+                       `ifdef verbose $display($time,"\tAXI4MasterWrite: Generating Write Request for Address: %h Data: %h BurstSize: %d BurstLength: %d BurstMode: :%d",ar.awaddr,wd.wdata,ar.awsize,ar.awlen,ar.awburst); `endif
+                       f_wr_addr[0]<=tagged Valid ar;
+                       f_wr_data[0]<=tagged Valid wd;
+                       let info=ar;
+                       if(ar.awlen==rg_write_burst_cycle) begin// end of burst
+                               wr_req_reg[1]<= tagged Invalid;
+                               wr_data_reg[1]<= tagged Invalid;
+                               rg_write_burst_cycle<=0;
+                       end
+                       else begin
+                               info.awaddr=address_increment(ar.awlen,ar.awsize,ar.awburst,ar.awaddr);
+                               rg_write_burst_cycle<=rg_write_burst_cycle+1;
+                               wr_req_reg[1]<=tagged Valid info;
+                       end
+               endrule
+
+               rule rl_generate_addr (r_ALE== 1 && flexbus_state_verfn == FlexBus_S1_ADDR );
+                       `ifdef verbose_debug_ver $display("STATE S1 ADDR VERFN fired "); `endif
+                       r_WS <= r_WS_val;
+                       if (r_R_Wn == 1'b1) begin
+                               if(rd_req_reg[0] matches tagged Invalid) begin
+                                       rd_req_reg[0]<=tagged Valid (AXI4_Rd_Addr {araddr : pack({r_AD}),
+                                                                         aruser : 0,
+                                                                         arsize : 3'h2,
+                                                                         arlen  : 8'h00,
+                                                                         arburst: 2'b00,
+                                                                         arid : 0
+                                                                       });
+                               end
+                       end
+                       else begin
+                               if(wr_req_reg[0] matches tagged Invalid) begin
+                                       wr_req_reg[0]<=tagged Valid (AXI4_Wr_Addr {awaddr :pack({r_AD}),
+                                                                         awuser : 0,
+                                                                         awsize : 3'h2,
+                                                                         awlen  : 8'h00,
+                                                                         awburst: 2'b00,
+                                                                         awid : 0
+                                                                       });
+                               end
+                       end
+                       flexbus_state_verfn <= FlexBus_S2_WRITE; 
+               endrule
+               rule rl_state_S2_WRITE (flexbus_state_verfn == FlexBus_S2_WRITE); //Write Phase
+                       `ifdef verbose_debug_ver $display("STATE S2 WRITE VERFN FIRED"); `endif
+                       if (r_R_Wn == 1'b0) begin
+                               if(wr_data_reg[0] matches tagged Invalid) begin
+                                       wr_data_reg[0]<=tagged Valid (AXI4_Wr_Data{wdata: pack({32'h00000000,r_AD[7:0],r_AD[15:8],r_AD[23:16],r_AD[31:24]}),
+                                                                        wstrb  : 8'h0F,
+                                                                        wid    : 0,
+                                                                        wlast  : True
+                                                                       });
+                               end
+                       end
+                       if (r_WS == 0) begin
+                               flexbus_state_verfn <= FlexBus_S3_BURST; 
+                               r_WS <= r_WS_val;
+                       end
+                       else
+                               r_WS <= r_WS -1;
+               endrule
+               rule rl_state_S3_BURST (flexbus_state_verfn == FlexBus_S3_BURST); //Burst Phase
+                       `ifdef verbose_debug_ver $display("STATE S3 BURST VERFN FIRED"); `endif
+                       if (r_R_Wn == 1'b1)  begin
+                               if(f_rd_data[1] matches tagged Valid .ar) begin 
+                                       r_din <= ar.rdata[31:0]; 
+                                       `ifdef verbose_debug_ver $display("r_din = %h %h", r_din, ar.rdata); `endif
+                                       f_rd_data[1]<=tagged Invalid;
+                               end
+                       end
+                       flexbus_state_verfn <= FlexBus_S1_ADDR; 
+               endrule
+
+/*
+   // FIFOF side
+        method Action i_wr_addr(AXI4_Wr_Addr#(wd_addr,wd_user) write_address)if(wr_req_reg[0] matches tagged Invalid);
+               wr_req_reg[0]<=tagged Valid write_address;
+       endmethod
+       method Action i_wr_data(AXI4_Wr_Data#(wd_data) write_data);
+               wr_data_reg[0]<=tagged Valid write_data;
+       endmethod
+        method ActionValue#(AXI4_Wr_Resp#(wd_user)) o_wr_resp if(f_wr_resp[1] matches tagged Valid .aresp);
+               f_wr_resp[1]<=tagged Invalid;
+               return aresp;
+        endmethod
+        method Action i_rd_addr(AXI4_Rd_Addr#(wd_addr,wd_user) read_address)if(rd_req_reg[0] matches tagged Invalid);
+               rd_req_reg[0]<=tagged Valid read_address;
+       endmethod
+        method ActionValue#(AXI4_Rd_Data #(wd_data, wd_user)) o_rd_data if(f_rd_data[1] matches tagged Valid .ar);
+               f_rd_data[1]<=tagged Invalid;
+               return ar;
+        endmethod
+*/
+   // ----------------------------------------------------------------
+   // INTERFACE
+
+   method Action reset;
+      f_wr_addr[2]<=tagged Invalid;
+      f_wr_data[2]<=tagged Invalid;
+      f_wr_resp[2]<=tagged Invalid;
+      f_rd_addr[2]<=tagged Invalid;
+      f_rd_data[2]<=tagged Invalid;
+   endmethod
+
+   // AXI side
+   interface axi_side = interface AXI4_Master_IFC;
+                          // Wr Addr channel
+                          method Bool           m_awvalid = isValid(f_wr_addr[1]);
+                          method Bit #(wd_addr) m_awaddr  = fromMaybe(?,f_wr_addr[1]).awaddr;
+                          method Bit #(wd_user) m_awuser  = fromMaybe(?,f_wr_addr[1]).awuser;
+                                method Bit #(3)                         m_awsize        = fromMaybe(?,f_wr_addr[1]).awsize;
+                                method Bit #(8)                         m_awlen   = fromMaybe(?,f_wr_addr[1]).awlen;
+                                method Bit #(2)                         m_awburst = fromMaybe(?,f_wr_addr[1]).awburst;
+                                method Bit #(4)                         m_awid                 =fromMaybe(?,f_wr_addr[1]).awid;
+                          method Action m_awready (Bool awready);
+                             if (isValid(f_wr_addr[1]) && awready) f_wr_addr[1]<=tagged Invalid;
+                          endmethod
+
+                          // Wr Data channel
+                          method Bool                       m_wvalid = isValid(f_wr_data[1]);
+                          method Bit #(wd_data)             m_wdata  = fromMaybe(?,f_wr_data[1]).wdata;
+                          method Bit #(TDiv #(wd_data, 8))  m_wstrb  = fromMaybe(?,f_wr_data[1]).wstrb;
+                          method Bool                       m_wlast =  fromMaybe(?,f_wr_data[1]).wlast;
+                          method Bit#(4)                                                                                m_wid =                fromMaybe(?,f_wr_data[1]).wid;
+                          method Action m_wready (Bool wready);
+                             if (isValid(f_wr_data[1]) && wready) f_wr_data[1]<=tagged Invalid;
+                          endmethod
+
+                          // Wr Response channel
+                          method Action m_bvalid (Bool bvalid, Bit #(2) bresp, Bit #(wd_user) buser, Bit#(4) bid);
+                             if (bvalid && !isValid(f_wr_resp[0]))
+                                                        f_wr_resp[0]<=tagged Valid (AXI4_Wr_Resp {bresp: unpack (bresp), buser: buser, bid: bid});
+                          endmethod
+
+                          method Bool m_bready;
+                             return !isValid(f_wr_resp[0]);
+                          endmethod
+
+                          // Rd Addr channel
+                          method Bool           m_arvalid = isValid(f_rd_addr[1]);
+                          method Bit #(wd_addr) m_araddr  = fromMaybe(?,f_rd_addr[1]).araddr;
+                          method Bit #(wd_user) m_aruser  = fromMaybe(?,f_rd_addr[1]).aruser;
+                                method Bit #(3)                         m_arsize        = fromMaybe(?,f_rd_addr[1]).arsize;
+                                method Bit #(8)                         m_arlen   = fromMaybe(?,f_rd_addr[1]).arlen;
+                                method Bit #(2)                         m_arburst = fromMaybe(?,f_rd_addr[1]).arburst;
+                                method Bit #(4)                         m_arid                 =fromMaybe(?,f_rd_addr[1]).arid;
+                          method Action m_arready (Bool arready);
+                             if (isValid(f_rd_addr[1]) && arready) 
+                                                       f_rd_addr[1]<=tagged Invalid;
+                          endmethod
+
+                          // Rd Data channel
+                          method Action m_rvalid (Bool           rvalid,
+                                                  Bit #(2)       rresp,
+                                                  Bit #(wd_data) rdata,
+                                                  Bool rlast,
+                                                  Bit #(wd_user) ruser,
+                                                        Bit#(4) rid);
+                             if (rvalid && !isValid(f_rd_data[0]))
+                                f_rd_data[0]<=tagged Valid (AXI4_Rd_Data {rresp: unpack (rresp),
+                                                                  rdata: rdata,
+                                                                        rlast: rlast,
+                                                                  ruser: ruser,
+                                                                        rid: rid});
+                          endmethod
+
+                          method Bool m_rready;
+                             return !isValid(f_rd_data[0]);
+                          endmethod
+
+                       endinterface;
+
+   interface flexbus_side = interface FlexBus_Slave_IFC;
+    //   interface io_AD_slave = tri_AD_in.io;
+       method Action m_AD             (  Bit #(32)   i_AD);                            // in
+               r_AD <= i_AD;
+       endmethod
+    //interface i_not_AD_s = interface Not_AD_s;
+       method Action m_ALE            (  Bit #(1)         i_ALE);                           // in
+               r_ALE <= i_ALE;
+       endmethod
+
+       method Action m_R_Wn           (  Bit #(1)         i_R_Wn);                          // in
+               r_R_Wn <= i_R_Wn;
+       endmethod
+       method Action m_TSIZ           (  Bit #(2)         i_TSIZ);                          // in
+               r_TSIZ <= i_TSIZ;
+       endmethod
+
+       method Action m_FBCSn          (  Bit #(6)         i_FBCSn);                         // in
+               r_FBCSn <= i_FBCSn;
+       endmethod
+       method Action m_BE_BWEn        (  Bit #(4)         i_BE_BWEn);                       // in
+               r_BE_BWEn <= i_BE_BWEn;
+       endmethod
+       method Action m_TBSTn          (  Bit #(1)         i_TBSTn);                         // in
+               r_TBSTn <= i_TBSTn;
+       endmethod
+       method Action m_OEn            (  Bit #(1)         i_OEn);                           // in
+               r_OEn <= i_OEn;
+       endmethod
+
+       method Bit #(32) m_din = r_din;                         //out
+       method Bit #(1) m_TAn = r_TAn;                                  //out
+    //endinterface;
+                           endinterface;
+
+endmodule: mkFlexBus_Slave_to_AXI4_Master_Fabric
+
+// ================================================================
+
+endpackage
diff --git a/src/testbench/Memory_AXI4.bsv b/src/testbench/Memory_AXI4.bsv
new file mode 100644 (file)
index 0000000..a929fff
--- /dev/null
@@ -0,0 +1,147 @@
+/*
+Copyright (c) 2013, IIT Madras
+All rights reserved.
+
+Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met:
+
+*  Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer.
+*  Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution.
+*  Neither the name of IIT Madras  nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 
+---------------------------------------------------------------------------------------------------------------------------------------------------------------------------------
+*/
+
+package Memory_AXI4;
+       /*====== Porject imports ====*/
+       import defined_types::*;
+       `include "defined_parameters.bsv"
+       import Semi_FIFOF        :: *;
+       import AXI4_Types   :: *;
+       import AXI4_Fabric  :: *;
+       import axi_addr_generator::*;
+       /*==== Package imports ======*/
+       import BRAMCore :: *;
+       import DReg::*;
+       import BUtils::*;
+       /*============================*/
+
+       interface Memory_IFC#(numeric type base_address, numeric type mem_size);
+               interface AXI4_Slave_IFC#(`PADDR,`Reg_width,`USERSPACE) axi_slave;
+       endinterface
+       typedef enum{Idle,HandleBurst} Mem_state deriving(Bits,Eq);
+       module mkMemory #(parameter String mem_init_file1 `ifdef RV64 , parameter String mem_init_file2 `endif  ,parameter String module_name) (Memory_IFC#(base_address,mem_size));
+               
+               BRAM_DUAL_PORT_BE#(Bit#(TSub#(mem_size,2)),Bit#(32),4) dmemMSB <- mkBRAMCore2BELoad(valueOf(TExp#(TSub#(mem_size,2))),False,mem_init_file1,False);
+               BRAM_DUAL_PORT_BE#(Bit#(TSub#(mem_size,2)),Bit#(32),4) dmemLSB <- mkBRAMCore2BELoad(valueOf(TExp#(TSub#(mem_size,2))),False,mem_init_file2,False);
+       
+               AXI4_Slave_Xactor_IFC #(`PADDR, `Reg_width, `USERSPACE)  s_xactor <- mkAXI4_Slave_Xactor;
+       
+               Reg#(Mem_state) rd_state <-mkReg(Idle);
+               Reg#(Mem_state) wr_state <-mkReg(Idle);
+               Reg#(Bit#(8)) rg_readburst_counter<-mkReg(0);
+               Reg#(AXI4_Rd_Addr       #(`PADDR,`USERSPACE)) rg_read_packet <-mkReg(?);                                                                                                                   // hold the read packet during bursts
+               Reg#(AXI4_Wr_Addr       #(`PADDR,`USERSPACE)) rg_write_packet<-mkReg(?); // hold the write packer during bursts
+       
+               rule rl_wr_respond(wr_state==Idle);
+             let aw <- pop_o (s_xactor.o_wr_addr);
+             let w  <- pop_o (s_xactor.o_wr_data);
+                       Bit#(TSub#(mem_size,2)) index_address=(aw.awaddr-fromInteger(valueOf(base_address)))[valueOf(mem_size)-1:`byte_offset+1];
+                       dmemLSB.b.put(w.wstrb[3:0],index_address,truncate(w.wdata));
+                       dmemMSB.b.put(w.wstrb[7:4],index_address,truncateLSB(w.wdata));
+                  let b = AXI4_Wr_Resp {bresp: AXI4_OKAY, buser: aw.awuser, bid:aw.awid};
+                       if(aw.awlen!=0) begin
+                               wr_state<=HandleBurst;
+                               let new_address=burst_address_generator(aw.awlen,aw.awsize,aw.awburst,aw.awaddr);
+                               aw.awaddr=new_address;
+                               rg_write_packet<=aw;
+                       end
+                       else
+                       s_xactor.i_wr_resp.enq (b);
+                       `ifdef verbose $display($time,"\t",module_name,":\t Recieved Write Request for Address: %h data: %h strb: %b awlen: %d",aw.awaddr,w.wdata,w.wstrb,aw.awlen);  `endif
+               endrule
+       
+               rule rl_wr_burst_response(wr_state==HandleBurst);
+             let w  <- pop_o (s_xactor.o_wr_data);
+                  let b = AXI4_Wr_Resp {bresp: AXI4_OKAY, buser: rg_write_packet.awuser, bid:rg_write_packet.awid};
+                       if(w.wlast)begin
+                               wr_state<=Idle;
+                               s_xactor.i_wr_resp.enq (b);
+                       end
+                       Bit#(TSub#(mem_size,2)) index_address=(rg_write_packet.awaddr-fromInteger(valueOf(base_address)))[valueOf(mem_size)-1:`byte_offset+1];
+                       dmemLSB.b.put(w.wstrb[3:0],index_address,truncate(w.wdata));
+                       dmemMSB.b.put(w.wstrb[7:4],index_address,truncateLSB(w.wdata));
+                       let new_address=burst_address_generator(rg_write_packet.awlen,rg_write_packet.awsize,rg_write_packet.awburst,rg_write_packet.awaddr);
+                       rg_write_packet.awaddr<=new_address;
+                       `ifdef verbose $display($time,"\t",module_name,":\t BURST Write Request for Address: %h data: %h strb: %b awlen: %d",rg_write_packet.awaddr,w.wdata,w.wstrb,rg_write_packet.awlen);  `endif
+               endrule
+               
+               rule rl_rd_request(rd_state==Idle);
+                       let ar<- pop_o(s_xactor.o_rd_addr);
+                       rg_read_packet<=ar;
+                       Bit#(TSub#(mem_size,2)) index_address=(ar.araddr-fromInteger(valueOf(base_address)))[valueOf(mem_size)-1:`byte_offset+1];
+                       dmemLSB.a.put(0,index_address,?);
+                       dmemMSB.a.put(0,index_address,?);
+                       rd_state<=HandleBurst;
+                       `ifdef verbose $display($time,"\t",module_name,"\t Recieved Read Request for Address: %h Index Address: %h",ar.araddr,index_address);  `endif
+               endrule
+       
+               rule rl_rd_response(rd_state==HandleBurst);
+                  Bit#(`Reg_width) data0 = {dmemMSB.a.read(),dmemLSB.a.read()};
+             AXI4_Rd_Data#(`Reg_width,`USERSPACE) r = AXI4_Rd_Data {rresp: AXI4_OKAY, rdata: data0 ,rlast:rg_readburst_counter==rg_read_packet.arlen, ruser: 0, rid:rg_read_packet.arid};
+                       let transfer_size=rg_read_packet.arsize;
+                       let address=rg_read_packet.araddr;
+                       if(transfer_size==2)begin // 32 bit
+                               if(address[2:0]==0)
+                                       r.rdata=duplicate(data0[31:0]);
+                               else
+                                       r.rdata=duplicate(data0[63:32]);
+                       end
+             else if (transfer_size=='d1)begin // half_word
+                               if(address[2:0] ==0)
+                                       r.rdata = duplicate(data0[15:0]);
+                               else if(address[2:0] ==2)
+                                       r.rdata = duplicate(data0[31:16]);
+                               else if(address[2:0] ==4)
+                                       r.rdata = duplicate(data0[47:32]);
+                               else if(address[2:0] ==6)
+                                       r.rdata = duplicate(data0[63:48]);
+             end
+             else if (transfer_size=='d0) begin// one byte
+                               if(address[2:0] ==0)
+                         r.rdata = duplicate(data0[7:0]);
+                       else if(address[2:0] ==1)
+                         r.rdata = duplicate(data0[15:8]);
+                       else if(address[2:0] ==2)
+                         r.rdata = duplicate(data0[23:16]);
+                       else if(address[2:0] ==3)
+                         r.rdata = duplicate(data0[31:24]);
+                       else if(address[2:0] ==4)
+                                       r.rdata = duplicate(data0[39:32]);
+                       else if(address[2:0] ==5)
+                                       r.rdata = duplicate(data0[47:40]);
+                       else if(address[2:0] ==6)
+                                       r.rdata = duplicate(data0[55:48]);
+                       else if(address[2:0] ==7)
+                                       r.rdata = duplicate(data0[63:56]);
+             end
+             s_xactor.i_rd_data.enq(r);
+                       address=burst_address_generator(rg_read_packet.arlen, rg_read_packet.arsize, rg_read_packet.arburst,rg_read_packet.araddr);
+                       Bit#(TSub#(mem_size,2)) index_address=(address-fromInteger(valueOf(base_address)))[valueOf(mem_size)-1:`byte_offset+1];
+                       if(rg_readburst_counter==rg_read_packet.arlen)begin
+                               rg_readburst_counter<=0;
+                               rd_state<=Idle;
+                       end
+                       else begin
+                               dmemLSB.a.put(0,index_address,?);
+                               dmemMSB.a.put(0,index_address,?);
+                               rg_readburst_counter<=rg_readburst_counter+1;
+                       end
+                       rg_read_packet.araddr<=address;
+                       Bit#(64) new_data=r.rdata;
+                       `ifdef verbose $display($time,"\t",module_name,"\t Responding Read Request with CurrAddr: %h Data: %8h BurstCounter: %d BurstValue: %d NextAddress: %h",rg_read_packet.araddr,new_data,rg_readburst_counter,rg_read_packet.arlen,address);  `endif
+          endrule
+       
+          interface axi_slave= s_xactor.axi_side;
+       endmodule
+endpackage