[cig-commits] r12459 - seismo/2D/SPECFEM2D/trunk

nlegoff at geodynamics.org nlegoff at geodynamics.org
Mon Jul 21 12:49:33 PDT 2008


Author: nlegoff
Date: 2008-07-21 12:49:32 -0700 (Mon, 21 Jul 2008)
New Revision: 12459

Modified:
   seismo/2D/SPECFEM2D/trunk/assemble_MPI.F90
   seismo/2D/SPECFEM2D/trunk/specfem2D.F90
Log:
a few changes on the communication scheme
 - communications are no longer overlapped, as the merging of the computation on inner and outer elements will make it irrelevant.
 - persistent communications were replaced by isend and irecv, as the trace tool MPITrace does not yet instrument those calls.
 - the send and merge phases were merged, as it should be possible to come up with a better communication scheme (maybe execute them in a certain order) and easier to implement it if those two phases are merged in one subroutine.


Modified: seismo/2D/SPECFEM2D/trunk/assemble_MPI.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/assemble_MPI.F90	2008-07-21 19:27:45 UTC (rev 12458)
+++ seismo/2D/SPECFEM2D/trunk/assemble_MPI.F90	2008-07-21 19:49:32 UTC (rev 12459)
@@ -295,115 +295,7 @@
 
 #ifdef USE_MPI
 
-
 !-----------------------------------------------
-! Creation of persistent communication requests (send and recv) for acoustic elements.
-! Should be disposed of if using Paraver (with MPItrace), since it does not instrument persistent
-! communications yet.
-!-----------------------------------------------
-subroutine create_MPI_req_SEND_RECV_ac( &
-     ninterface, ninterface_acoustic, &
-     nibool_interfaces_acoustic, &
-     my_neighbours, &
-     max_ibool_interfaces_size_ac, &
-     buffer_send_faces_vector_ac, &
-     buffer_recv_faces_vector_ac, &
-     tab_requests_send_recv_acoustic, &
-     inum_interfaces_acoustic &
-     )
-
-  implicit none
-
-  include 'constants.h'
-  include 'mpif.h'
-  include 'precision_mpi.h'
-
-  integer, intent(in)  :: ninterface, ninterface_acoustic
-  integer, dimension(ninterface), intent(in)  :: inum_interfaces_acoustic
-  integer, intent(in)  :: max_ibool_interfaces_size_ac
-  real(kind=CUSTOM_REAL), dimension(max_ibool_interfaces_size_ac,ninterface_acoustic), intent(in)  :: &
-       buffer_send_faces_vector_ac
-  real(kind=CUSTOM_REAL), dimension(max_ibool_interfaces_size_ac,ninterface_acoustic), intent(in)  :: &
-       buffer_recv_faces_vector_ac
-  integer, dimension(ninterface_acoustic*2), intent(inout)  :: tab_requests_send_recv_acoustic
-  integer, dimension(ninterface), intent(in)  :: nibool_interfaces_acoustic
-  integer, dimension(ninterface), intent(in) :: my_neighbours
-
-  integer  :: inum_interface,num_interface
-  integer  :: ier
-
-  do inum_interface = 1, ninterface_acoustic
-
-     num_interface = inum_interfaces_acoustic(inum_interface)
-
-        call MPI_Send_init ( buffer_send_faces_vector_ac(1,inum_interface), &
-             nibool_interfaces_acoustic(num_interface), CUSTOM_MPI_TYPE, &
-             my_neighbours(num_interface), 12, MPI_COMM_WORLD, &
-             tab_requests_send_recv_acoustic(inum_interface), ier)
-        call MPI_Recv_init ( buffer_recv_faces_vector_ac(1,inum_interface), &
-             nibool_interfaces_acoustic(num_interface), CUSTOM_MPI_TYPE, &
-             my_neighbours(num_interface), 12, MPI_COMM_WORLD, &
-             tab_requests_send_recv_acoustic(ninterface_acoustic+inum_interface), ier)
-  end do
-
-end subroutine create_MPI_req_SEND_RECV_ac
-
-
-!-----------------------------------------------
-! Creation of persistent communication requests (send and recv) for elastic elements.
-! Should be disposed of if using Paraver (with MPItrace), since it does not instrument persistent
-! communications yet.
-!-----------------------------------------------
-subroutine create_MPI_req_SEND_RECV_el( &
-     ninterface, ninterface_elastic, &
-     nibool_interfaces_elastic, &
-     my_neighbours, &
-     max_ibool_interfaces_size_el, &
-     buffer_send_faces_vector_el, &
-     buffer_recv_faces_vector_el, &
-     tab_requests_send_recv_elastic, &
-     inum_interfaces_elastic &
-     )
-
-  implicit none
-
-  include 'constants.h'
-  include 'mpif.h'
-  include 'precision_mpi.h'
-
-
-  integer, intent(in)  :: ninterface, ninterface_elastic
-  integer, dimension(ninterface), intent(in)  :: inum_interfaces_elastic
-  integer, intent(in)  :: max_ibool_interfaces_size_el
-  real(kind=CUSTOM_REAL), dimension(max_ibool_interfaces_size_el,ninterface_elastic), intent(in)  :: &
-       buffer_send_faces_vector_el
-  real(kind=CUSTOM_REAL), dimension(max_ibool_interfaces_size_el,ninterface_elastic), intent(in)  :: &
-       buffer_recv_faces_vector_el
-  integer, dimension(ninterface_elastic*2), intent(inout)  :: tab_requests_send_recv_elastic
-  integer, dimension(ninterface), intent(in)  :: nibool_interfaces_elastic
-  integer, dimension(ninterface), intent(in) :: my_neighbours
-
-  integer  :: inum_interface,num_interface
-  integer  :: ier
-
-  do inum_interface = 1, ninterface_elastic
-
-     num_interface = inum_interfaces_elastic(inum_interface)
-
-        call MPI_Send_init ( buffer_send_faces_vector_el(1,inum_interface), &
-             NDIM*nibool_interfaces_elastic(num_interface), CUSTOM_MPI_TYPE, &
-             my_neighbours(num_interface), 13, MPI_COMM_WORLD, &
-             tab_requests_send_recv_elastic(inum_interface), ier)
-        call MPI_Recv_init ( buffer_recv_faces_vector_el(1,inum_interface), &
-             NDIM*nibool_interfaces_elastic(num_interface), CUSTOM_MPI_TYPE, &
-             my_neighbours(num_interface), 13, MPI_COMM_WORLD, &
-             tab_requests_send_recv_elastic(ninterface_elastic+inum_interface), ier)
-  end do
-
-end subroutine create_MPI_req_SEND_RECV_el
-
-
-!-----------------------------------------------
 ! Assembling the mass matrix.
 !-----------------------------------------------
 subroutine assemble_MPI_scalar(array_val1, array_val2,npoin, &
@@ -487,25 +379,34 @@
 
 !-----------------------------------------------
 ! Assembling potential_dot_dot for acoustic elements :
-! the buffers are filled, and the send and recv are started here.
-! We use MPI_Start (MPI_Startall is not used, since it causes problems in OpenMPI prior to v1.2).
+! the buffers are filled, the Isend and Irecv are started here, then
+! contributions are added.
+! The previous version included communication overlap using persistent
+! communication, but the merging of the outer and inner elements rendered
+! overlap no longer possible, while persistent communications were removed
+! because trace tool MPITrace does not yet instrument those.
+! Particular care should be taken concerning possible optimisations of the
+! communication scheme.
 !-----------------------------------------------
-subroutine assemble_MPI_vector_ac_start(array_val1,npoin, &
+subroutine assemble_MPI_vector_ac(array_val1,npoin, &
      ninterface, ninterface_acoustic, &
      inum_interfaces_acoustic, &
      max_interface_size, max_ibool_interfaces_size_ac,&
      ibool_interfaces_acoustic, nibool_interfaces_acoustic, &
      tab_requests_send_recv_acoustic, &
-     buffer_send_faces_vector_ac &
+     buffer_send_faces_vector_ac, &
+     buffer_recv_faces_vector_ac, &
+     my_neighbours &
      )
 
   implicit none
 
   include 'constants.h'
   include 'mpif.h'
+  include 'precision_mpi.h'
 
   ! array to assemble
-  real(kind=CUSTOM_REAL), dimension(npoin), intent(in) :: array_val1
+  real(kind=CUSTOM_REAL), dimension(npoin), intent(inout) :: array_val1
 
   integer, intent(in)  :: npoin
   integer, intent(in)  :: ninterface, ninterface_acoustic
@@ -517,9 +418,13 @@
   integer, dimension(ninterface_acoustic*2), intent(inout)  :: tab_requests_send_recv_acoustic
   real(kind=CUSTOM_REAL), dimension(max_ibool_interfaces_size_ac,ninterface_acoustic), intent(inout)  :: &
        buffer_send_faces_vector_ac
+  real(kind=CUSTOM_REAL), dimension(max_ibool_interfaces_size_ac,ninterface_acoustic), intent(inout)  :: &
+       buffer_recv_faces_vector_ac
+  integer, dimension(ninterface), intent(in) :: my_neighbours
 
   integer  :: ipoin, num_interface, inum_interface
   integer  :: ier
+  integer, dimension(MPI_STATUS_SIZE)  :: status_acoustic
 
   integer  :: i
 
@@ -536,39 +441,82 @@
 
   end do
 
-  do inum_interface = 1, ninterface_acoustic*2
-     call MPI_START(tab_requests_send_recv_acoustic(inum_interface), ier)
-     if ( ier /= MPI_SUCCESS ) then
-        call exit_mpi('MPI_start unsuccessful in assemble_MPI_vector_start')
-     end if
+  do inum_interface = 1, ninterface_acoustic
+
+    num_interface = inum_interfaces_acoustic(inum_interface)
+
+    call MPI_Isend ( buffer_send_faces_vector_ac(1,inum_interface), &
+             nibool_interfaces_acoustic(num_interface), CUSTOM_MPI_TYPE, &
+             my_neighbours(num_interface), 12, MPI_COMM_WORLD, &
+             tab_requests_send_recv_acoustic(inum_interface), ier)
+
+    if ( ier /= MPI_SUCCESS ) then
+      call exit_mpi('MPI_Isend unsuccessful in assemble_MPI_vector_start')
+    end if
+
+    call MPI_Irecv ( buffer_recv_faces_vector_ac(1,inum_interface), &
+             nibool_interfaces_acoustic(num_interface), CUSTOM_MPI_TYPE, &
+             my_neighbours(num_interface), 12, MPI_COMM_WORLD, &
+             tab_requests_send_recv_acoustic(ninterface_acoustic+inum_interface), ier)
+
+    if ( ier /= MPI_SUCCESS ) then
+      call exit_mpi('MPI_Irecv unsuccessful in assemble_MPI_vector')
+    end if
+
   end do
 
-!call MPI_Startall ( ninterface*2, tab_requests_send_recv(1), ier )
+  do inum_interface = 1, ninterface_acoustic*2
+  
+    call MPI_Wait (tab_requests_send_recv_acoustic(inum_interface), status_acoustic, ier)
 
-end subroutine assemble_MPI_vector_ac_start
+  enddo
 
+  do inum_interface = 1, ninterface_acoustic
 
+     num_interface = inum_interfaces_acoustic(inum_interface)
+
+     ipoin = 0
+     do i = 1, nibool_interfaces_acoustic(num_interface)
+        ipoin = ipoin + 1
+        array_val1(ibool_interfaces_acoustic(i,num_interface)) = array_val1(ibool_interfaces_acoustic(i,num_interface)) + &
+             buffer_recv_faces_vector_ac(ipoin,inum_interface)
+     end do
+
+  end do
+
+end subroutine assemble_MPI_vector_ac
+
+
 !-----------------------------------------------
 ! Assembling accel_elastic for elastic elements :
-! the buffers are filled, and the send and recv are started here.
-! We use MPI_Start (MPI_Startall is not used, since it causes problems in OpenMPI prior to v1.2).
+! the buffers are filled, the Isend and Irecv are started here, then
+! contributions are added.
+! The previous version included communication overlap using persistent
+! communication, but the merging of the outer and inner elements rendered
+! overlap no longer possible, while persistent communications were removed
+! because trace tool MPITrace does not yet instrument those.
+! Particular care should be taken concerning possible optimisations of the
+! communication scheme.
 !-----------------------------------------------
-subroutine assemble_MPI_vector_el_start(array_val2,npoin, &
+subroutine assemble_MPI_vector_el(array_val2,npoin, &
      ninterface, ninterface_elastic, &
      inum_interfaces_elastic, &
      max_interface_size, max_ibool_interfaces_size_el,&
      ibool_interfaces_elastic, nibool_interfaces_elastic, &
      tab_requests_send_recv_elastic, &
-     buffer_send_faces_vector_el &
+     buffer_send_faces_vector_el, &
+     buffer_recv_faces_vector_el, &
+     my_neighbours &
      )
 
   implicit none
 
   include 'constants.h'
   include 'mpif.h'
+  include 'precision_mpi.h'
 
   ! array to assemble
-  real(kind=CUSTOM_REAL), dimension(NDIM,npoin), intent(in) :: array_val2
+  real(kind=CUSTOM_REAL), dimension(NDIM,npoin), intent(inout) :: array_val2
 
   integer, intent(in)  :: npoin
   integer, intent(in)  :: ninterface, ninterface_elastic
@@ -580,10 +528,13 @@
   integer, dimension(ninterface_elastic*2), intent(inout)  :: tab_requests_send_recv_elastic
   real(CUSTOM_REAL), dimension(max_ibool_interfaces_size_el,ninterface_elastic), intent(inout)  :: &
        buffer_send_faces_vector_el
+  real(CUSTOM_REAL), dimension(max_ibool_interfaces_size_el,ninterface_elastic), intent(inout)  :: &
+       buffer_recv_faces_vector_el
+ integer, dimension(ninterface), intent(in) :: my_neighbours
 
-
   integer  :: ipoin, num_interface, inum_interface
   integer  :: ier
+  integer, dimension(MPI_STATUS_SIZE)  :: status_elastic
 
   integer  :: i
 
@@ -601,122 +552,36 @@
 
   end do
 
-  do inum_interface = 1, ninterface_elastic*2
-     call MPI_START(tab_requests_send_recv_elastic(inum_interface), ier)
-     if ( ier /= MPI_SUCCESS ) then
-        call exit_mpi('MPI_start unsuccessful in assemble_MPI_vector_start')
-     end if
-  end do
+  do inum_interface = 1, ninterface_elastic
 
-!call MPI_Startall ( ninterface*2, tab_requests_send_recv(1), ier )
+    num_interface = inum_interfaces_elastic(inum_interface)
 
-end subroutine assemble_MPI_vector_el_start
+    call MPI_Isend ( buffer_send_faces_vector_el(1,inum_interface), &
+             NDIM*nibool_interfaces_elastic(num_interface), CUSTOM_MPI_TYPE, &
+             my_neighbours(num_interface), 12, MPI_COMM_WORLD, &
+             tab_requests_send_recv_elastic(inum_interface), ier)
 
+    if ( ier /= MPI_SUCCESS ) then
+      call exit_mpi('MPI_Isend unsuccessful in assemble_MPI_vector_el')
+    end if
 
-!-----------------------------------------------
-! Assembling potential_dot_dot for acoustic elements :
-! We wait for the completion of the communications, and add the contributions received
-! for the points on the interfaces.
-!-----------------------------------------------
-subroutine assemble_MPI_vector_ac_wait(array_val1,npoin, &
-     ninterface, ninterface_acoustic, &
-     inum_interfaces_acoustic, &
-     max_interface_size, max_ibool_interfaces_size_ac,&
-     ibool_interfaces_acoustic, nibool_interfaces_acoustic, &
-     tab_requests_send_recv_acoustic, &
-     buffer_recv_faces_vector_ac &
-     )
+    call MPI_Irecv ( buffer_recv_faces_vector_el(1,inum_interface), &
+             NDIM*nibool_interfaces_elastic(num_interface), CUSTOM_MPI_TYPE, &
+             my_neighbours(num_interface), 12, MPI_COMM_WORLD, &
+             tab_requests_send_recv_elastic(ninterface_elastic+inum_interface), ier)
 
-  implicit none
-
-  include 'constants.h'
-  include 'mpif.h'
-
-  ! array to assemble
-  real(kind=CUSTOM_REAL), dimension(npoin), intent(inout) :: array_val1
-
-  integer, intent(in)  :: npoin
-  integer, intent(in)  :: ninterface, ninterface_acoustic
-  integer, dimension(ninterface), intent(in)  :: inum_interfaces_acoustic
-  integer, intent(in)  :: max_interface_size
-  integer, intent(in)  :: max_ibool_interfaces_size_ac
-  integer, dimension(NGLLX*max_interface_size,ninterface), intent(in)  :: ibool_interfaces_acoustic
-  integer, dimension(ninterface), intent(in)  :: nibool_interfaces_acoustic
-  integer, dimension(ninterface_acoustic*2), intent(inout)  :: tab_requests_send_recv_acoustic
-  real(kind=CUSTOM_REAL), dimension(max_ibool_interfaces_size_ac,ninterface_acoustic), intent(inout)  :: &
-       buffer_recv_faces_vector_ac
-
-  integer  :: ipoin, num_interface, inum_interface
-  integer  :: ier
-  integer, dimension(MPI_STATUS_SIZE,ninterface_acoustic*2)  :: tab_statuses_acoustic
-
-  integer  :: i
-
-  call MPI_Waitall ( ninterface_acoustic*2, tab_requests_send_recv_acoustic(1), tab_statuses_acoustic(1,1), ier )
-  if ( ier /= MPI_SUCCESS ) then
-     call exit_mpi('MPI_WAITALL unsuccessful in assemble_MPI_vector_wait')
-  end if
-
-  do inum_interface = 1, ninterface_acoustic
-
-     num_interface = inum_interfaces_acoustic(inum_interface)
-
-     ipoin = 0
-     do i = 1, nibool_interfaces_acoustic(num_interface)
-        ipoin = ipoin + 1
-        array_val1(ibool_interfaces_acoustic(i,num_interface)) = array_val1(ibool_interfaces_acoustic(i,num_interface)) + &
-             buffer_recv_faces_vector_ac(ipoin,inum_interface)
-     end do
-
+    if ( ier /= MPI_SUCCESS ) then
+      call exit_mpi('MPI_Irecv unsuccessful in assemble_MPI_vector_el')
+    end if
+    
   end do
 
-end subroutine assemble_MPI_vector_ac_wait
+  do inum_interface = 1, ninterface_elastic*2
+  
+    call MPI_Wait (tab_requests_send_recv_elastic(inum_interface), status_elastic, ier)
 
-
-!-----------------------------------------------
-! Assembling accel_elastic for elastic elements :
-! We wait for the completion of the communications, and add the contributions received
-! for the points on the interfaces.
-!-----------------------------------------------
-subroutine assemble_MPI_vector_el_wait(array_val2,npoin, &
-     ninterface, ninterface_elastic, &
-     inum_interfaces_elastic, &
-     max_interface_size, max_ibool_interfaces_size_el,&
-     ibool_interfaces_elastic, nibool_interfaces_elastic, &
-     tab_requests_send_recv_elastic, &
-     buffer_recv_faces_vector_el &
-     )
-
-  implicit none
-
-  include 'constants.h'
-  include 'mpif.h'
-
-  ! array to assemble
-  real(kind=CUSTOM_REAL), dimension(NDIM,npoin), intent(inout) :: array_val2
-
-  integer, intent(in)  :: npoin
-  integer, intent(in)  :: ninterface, ninterface_elastic
-  integer, dimension(ninterface), intent(in)  :: inum_interfaces_elastic
-  integer, intent(in)  :: max_interface_size
-  integer, intent(in)  :: max_ibool_interfaces_size_el
-  integer, dimension(NGLLX*max_interface_size,ninterface), intent(in)  :: ibool_interfaces_elastic
-  integer, dimension(ninterface), intent(in)  :: nibool_interfaces_elastic
-  integer, dimension(ninterface_elastic*2), intent(inout)  :: tab_requests_send_recv_elastic
-  real(kind=CUSTOM_REAL), dimension(max_ibool_interfaces_size_el,ninterface_elastic), intent(inout)  :: &
-       buffer_recv_faces_vector_el
-
-  integer  :: ipoin, num_interface, inum_interface
-  integer  :: ier
-  integer, dimension(MPI_STATUS_SIZE,ninterface_elastic*2)  :: tab_statuses_elastic
-
-  integer  :: i
-
-  call MPI_Waitall ( ninterface_elastic*2, tab_requests_send_recv_elastic(1), tab_statuses_elastic(1,1), ier )
-  if ( ier /= MPI_SUCCESS ) then
-     call exit_mpi('MPI_WAITALL unsuccessful in assemble_MPI_vector_wait')
-  end if
-
+  enddo
+  
   do inum_interface = 1, ninterface_elastic
 
      num_interface = inum_interfaces_elastic(inum_interface)
@@ -730,7 +595,7 @@
 
   end do
 
-end subroutine assemble_MPI_vector_el_wait
+end subroutine assemble_MPI_vector_el
 
 #endif
 

Modified: seismo/2D/SPECFEM2D/trunk/specfem2D.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/specfem2D.F90	2008-07-21 19:27:45 UTC (rev 12458)
+++ seismo/2D/SPECFEM2D/trunk/specfem2D.F90	2008-07-21 19:49:32 UTC (rev 12459)
@@ -1287,20 +1287,6 @@
     allocate(buffer_recv_faces_vector_el(max_ibool_interfaces_size_el,ninterface_elastic))
   endif
 
-! creating mpi non-blocking persistent communications for acoustic elements
-  call create_MPI_req_SEND_RECV_ac(ninterface, ninterface_acoustic, &
-     nibool_interfaces_acoustic,my_neighbours, &
-     max_ibool_interfaces_size_ac, &
-     buffer_send_faces_vector_ac,buffer_recv_faces_vector_ac, &
-     tab_requests_send_recv_acoustic,inum_interfaces_acoustic)
-
-! creating mpi non-blocking persistent communications for elastic elements
-  call create_MPI_req_SEND_RECV_el(ninterface, ninterface_elastic, &
-     nibool_interfaces_elastic,my_neighbours, &
-     max_ibool_interfaces_size_el, &
-     buffer_send_faces_vector_el,buffer_recv_faces_vector_el, &
-     tab_requests_send_recv_elastic,inum_interfaces_elastic)
-
 ! assembling the mass matrix
   call assemble_MPI_scalar(rmass_inverse_acoustic, rmass_inverse_elastic,npoin, &
      ninterface, max_interface_size, max_ibool_interfaces_size_ac, max_ibool_interfaces_size_el, &
@@ -2450,17 +2436,6 @@
 
    endif
 
-! assembling potential_dot_dot for acoustic elements (send)
-#ifdef USE_MPI
-  if ( nproc > 1 .and. any_acoustic .and. ninterface_acoustic > 0) then
-    call assemble_MPI_vector_ac_start(potential_dot_dot_acoustic,npoin, &
-           ninterface, ninterface_acoustic,inum_interfaces_acoustic, &
-           max_interface_size, max_ibool_interfaces_size_ac,&
-           ibool_interfaces_acoustic, nibool_interfaces_acoustic, &
-           tab_requests_send_recv_acoustic,buffer_send_faces_vector_ac)
-  endif
-#endif
-
 ! second call, computation on inner elements
   if(any_acoustic) then
     call compute_forces_acoustic(npoin,nspec,nelemabs,numat, &
@@ -2474,17 +2449,19 @@
                nspec_outer, .false.)
    endif
 
-! assembling potential_dot_dot for acoustic elements (receive)
+! assembling potential_dot_dot for acoustic elements
 #ifdef USE_MPI
   if ( nproc > 1 .and. any_acoustic .and. ninterface_acoustic > 0) then
-    call assemble_MPI_vector_ac_wait(potential_dot_dot_acoustic,npoin, &
+    call assemble_MPI_vector_ac(potential_dot_dot_acoustic,npoin, &
            ninterface, ninterface_acoustic,inum_interfaces_acoustic, &
            max_interface_size, max_ibool_interfaces_size_ac,&
            ibool_interfaces_acoustic, nibool_interfaces_acoustic, &
-           tab_requests_send_recv_acoustic,buffer_recv_faces_vector_ac)
+           tab_requests_send_recv_acoustic,buffer_send_faces_vector_ac, &
+           buffer_recv_faces_vector_ac, my_neighbours)
   endif
 #endif
 
+
 ! ************************************************************************************
 ! ************* multiply by the inverse of the mass matrix and update velocity
 ! ************************************************************************************
@@ -2604,17 +2581,6 @@
 
     endif
 
-! assembling accel_elastic for elastic elements (send)
-#ifdef USE_MPI
-  if (nproc > 1 .and. any_elastic .and. ninterface_elastic > 0) then
-    call assemble_MPI_vector_el_start(accel_elastic,npoin, &
-      ninterface, ninterface_elastic,inum_interfaces_elastic, &
-      max_interface_size, max_ibool_interfaces_size_el,&
-      ibool_interfaces_elastic, nibool_interfaces_elastic, &
-      tab_requests_send_recv_elastic,buffer_send_faces_vector_el)
-  endif
-#endif
-
 ! second call, computation on inner elements and update
   if(any_elastic) &
     call compute_forces_elastic(npoin,nspec,nelemabs,numat, &
@@ -2632,18 +2598,19 @@
                t0x_left(1,it),t0z_left(1,it),t0x_right(1,it),t0z_right(1,it),t0x_bot(1,it),t0z_bot(1,it), &
                count_left,count_right,count_bot,over_critical_angle)
 
-
-! assembling accel_elastic for elastic elements (receive)
+! assembling accel_elastic for elastic elements
 #ifdef USE_MPI
   if (nproc > 1 .and. any_elastic .and. ninterface_elastic > 0) then
-    call assemble_MPI_vector_el_wait(accel_elastic,npoin, &
+    call assemble_MPI_vector_el(accel_elastic,npoin, &
       ninterface, ninterface_elastic,inum_interfaces_elastic, &
       max_interface_size, max_ibool_interfaces_size_el,&
       ibool_interfaces_elastic, nibool_interfaces_elastic, &
-      tab_requests_send_recv_elastic,buffer_recv_faces_vector_el)
+      tab_requests_send_recv_elastic,buffer_send_faces_vector_el, &
+      buffer_recv_faces_vector_el, my_neighbours)
   endif
 #endif
 
+
 ! ************************************************************************************
 ! ************* multiply by the inverse of the mass matrix and update velocity
 ! ************************************************************************************



More information about the cig-commits mailing list