[cig-commits] r15668 - in seismo/2D/SPECFEM2D/trunk: . DATA

cmorency at geodynamics.org cmorency at geodynamics.org
Mon Sep 14 15:44:37 PDT 2009


Author: cmorency
Date: 2009-09-14 15:44:36 -0700 (Mon, 14 Sep 2009)
New Revision: 15668

Modified:
   seismo/2D/SPECFEM2D/trunk/DATA/Par_file
   seismo/2D/SPECFEM2D/trunk/README_MANUAL.txt
   seismo/2D/SPECFEM2D/trunk/compute_forces_elastic.f90
   seismo/2D/SPECFEM2D/trunk/meshfem2D.F90
   seismo/2D/SPECFEM2D/trunk/specfem2D.F90
   seismo/2D/SPECFEM2D/trunk/write_seismograms.F90
Log:
Changed the flag for P-SV/SH simulations. It is p_sv = .true. or .false.


Modified: seismo/2D/SPECFEM2D/trunk/DATA/Par_file
===================================================================
--- seismo/2D/SPECFEM2D/trunk/DATA/Par_file	2009-09-14 21:59:09 UTC (rev 15667)
+++ seismo/2D/SPECFEM2D/trunk/DATA/Par_file	2009-09-14 22:44:36 UTC (rev 15668)
@@ -30,7 +30,7 @@
 TURN_VISCATTENUATION_ON         = .false.        # turn viscous attenuation on or off 
 Q0                              =  1             # quality factor for viscous attenuation
 freq0                           =  10            # frequency for viscous attenuation
-body_waves                      = .true.         # set the type of calculation (P-SV or SH/membrane waves)
+p_sv                            = .true.         # set the type of calculation (P-SV or SH/membrane waves)
 
 # absorbing boundaries parameters
 absorbing_conditions            = .true.	 # absorbing boundary active or not

Modified: seismo/2D/SPECFEM2D/trunk/README_MANUAL.txt
===================================================================
--- seismo/2D/SPECFEM2D/trunk/README_MANUAL.txt	2009-09-14 21:59:09 UTC (rev 15667)
+++ seismo/2D/SPECFEM2D/trunk/README_MANUAL.txt	2009-09-14 22:44:36 UTC (rev 15668)
@@ -179,9 +179,9 @@
 How to run P-SV or SH (membrane) waves simulation :
 ---------------------------------------------------
 To run a P-SV waves calculation propagating in the x-z plane, 
-set body_waves = .true. in the Par_file.
+set p_sv = .true. in the Par_file.
 To run a SH (membrane) waves calculation traveling in the x-z plane with a
-y-component of motion, set body_waves = .false.
+y-component of motion, set p_sv = .false.
 
 This feature is only implemented for elastic materials and sensitivity kernels
 can be calculated (see Tape, Liu & Tromp, GJI 2006 for details on membrane

Modified: seismo/2D/SPECFEM2D/trunk/compute_forces_elastic.f90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/compute_forces_elastic.f90	2009-09-14 21:59:09 UTC (rev 15667)
+++ seismo/2D/SPECFEM2D/trunk/compute_forces_elastic.f90	2009-09-14 22:44:36 UTC (rev 15668)
@@ -42,7 +42,7 @@
 !
 !========================================================================
 
-  subroutine compute_forces_elastic(body_waves,npoin,nspec,myrank,nelemabs,numat, &
+  subroutine compute_forces_elastic(p_sv,npoin,nspec,myrank,nelemabs,numat, &
        ispec_selected_source,ispec_selected_rec,is_proc_source,which_proc_receiver, &
        source_type,it,NSTEP,anyabs,assign_external_model, &
        initialfield,TURN_ATTENUATION_ON,TURN_ANISOTROPY_ON,angleforce,deltatcube, &
@@ -66,7 +66,7 @@
 
   include "constants.h"
 
-  logical :: body_waves
+  logical :: p_sv
   integer :: NSOURCE, i_source
   integer :: npoin,nspec,myrank,nelemabs,numat,it,NSTEP
   integer, dimension(NSOURCE) :: ispec_selected_source,is_proc_source,source_type
@@ -360,7 +360,7 @@
 ! Pre-kernels calculation
    if(isolver == 2) then
           iglob = ibool(i,j,ispec)
-      if(body_waves)then !P-SV waves
+      if(p_sv)then !P-SV waves
             dsxx =  dux_dxl
             dsxz = HALF * (duz_dxl + dux_dzl)
             dszz =  duz_dzl
@@ -523,14 +523,14 @@
             accel_elastic(3,iglob) = accel_elastic(3,iglob) - (tz + traction_z_t0)*weight
 
             if(save_forward .and. isolver ==1) then
-             if(body_waves)then !P-SV waves
+             if(p_sv)then !P-SV waves
               b_absorb_elastic_left(1,j,ib_xmin(ispecabs),it) = tx*weight
               b_absorb_elastic_left(3,j,ib_xmin(ispecabs),it) = tz*weight
              else !SH (membrane) waves
               b_absorb_elastic_left(2,j,ib_xmin(ispecabs),it) = ty*weight
              endif
             elseif(isolver == 2) then
-             if(body_waves)then !P-SV waves
+             if(p_sv)then !P-SV waves
               b_accel_elastic(1,iglob) = b_accel_elastic(1,iglob) - b_absorb_elastic_left(1,j,ib_xmin(ispecabs),NSTEP-it+1)
               b_accel_elastic(3,iglob) = b_accel_elastic(3,iglob) - b_absorb_elastic_left(3,j,ib_xmin(ispecabs),NSTEP-it+1)
              else !SH (membrane) waves
@@ -611,14 +611,14 @@
             accel_elastic(3,iglob) = accel_elastic(3,iglob) - (tz - traction_z_t0)*weight
 
             if(save_forward .and. isolver ==1) then
-             if(body_waves)then !P-SV waves
+             if(p_sv)then !P-SV waves
               b_absorb_elastic_right(1,j,ib_xmax(ispecabs),it) = tx*weight
               b_absorb_elastic_right(3,j,ib_xmax(ispecabs),it) = tz*weight
              else! SH (membrane) waves
               b_absorb_elastic_right(2,j,ib_xmax(ispecabs),it) = ty*weight
              endif
             elseif(isolver == 2) then
-             if(body_waves)then !P-SV waves
+             if(p_sv)then !P-SV waves
               b_accel_elastic(1,iglob) = b_accel_elastic(1,iglob) - b_absorb_elastic_right(1,j,ib_xmax(ispecabs),NSTEP-it+1)
               b_accel_elastic(3,iglob) = b_accel_elastic(3,iglob) - b_absorb_elastic_right(3,j,ib_xmax(ispecabs),NSTEP-it+1)
              else! SH (membrane) waves
@@ -705,14 +705,14 @@
             accel_elastic(3,iglob) = accel_elastic(3,iglob) - (tz + traction_z_t0)*weight
 
             if(save_forward .and. isolver ==1) then
-             if(body_waves)then !P-SV waves
+             if(p_sv)then !P-SV waves
               b_absorb_elastic_bottom(1,i,ib_zmin(ispecabs),it) = tx*weight
               b_absorb_elastic_bottom(3,i,ib_zmin(ispecabs),it) = tz*weight
              else!SH (membrane) waves
               b_absorb_elastic_bottom(2,i,ib_zmin(ispecabs),it) = ty*weight
              endif
             elseif(isolver == 2) then
-             if(body_waves)then !P-SV waves
+             if(p_sv)then !P-SV waves
               b_accel_elastic(1,iglob) = b_accel_elastic(1,iglob) - b_absorb_elastic_bottom(1,i,ib_zmin(ispecabs),NSTEP-it+1)
               b_accel_elastic(3,iglob) = b_accel_elastic(3,iglob) - b_absorb_elastic_bottom(3,i,ib_zmin(ispecabs),NSTEP-it+1)
              else!SH (membrane) waves
@@ -791,14 +791,14 @@
             accel_elastic(3,iglob) = accel_elastic(3,iglob) - (tz - traction_z_t0)*weight
 
             if(save_forward .and. isolver ==1) then
-             if(body_waves)then !P-SV waves
+             if(p_sv)then !P-SV waves
               b_absorb_elastic_top(1,i,ib_zmax(ispecabs),it) = tx*weight
               b_absorb_elastic_top(3,i,ib_zmax(ispecabs),it) = tz*weight
              else!SH (membrane) waves
               b_absorb_elastic_top(2,i,ib_zmax(ispecabs),it) = ty*weight
              endif
             elseif(isolver == 2) then
-             if(body_waves)then !P-SV waves
+             if(p_sv)then !P-SV waves
               b_accel_elastic(1,iglob) = b_accel_elastic(1,iglob) - b_absorb_elastic_top(1,i,ib_zmax(ispecabs),NSTEP-it+1)
               b_accel_elastic(3,iglob) = b_accel_elastic(3,iglob) - b_absorb_elastic_top(3,i,ib_zmax(ispecabs),NSTEP-it+1)
              else!SH (membrane) waves
@@ -826,7 +826,7 @@
 ! moment tensor
         if(source_type(i_source) == 2) then
 
-       if(.not.body_waves)  call exit_MPI('cannot have moment tensor source in SH (membrane) waves calculation')  
+       if(.not.p_sv)  call exit_MPI('cannot have moment tensor source in SH (membrane) waves calculation')  
 
        if(isolver == 1) then  ! forward wavefield
 ! add source array
@@ -868,7 +868,7 @@
       do j=1,NGLLZ
         do i=1,NGLLX
           iglob = ibool(i,j,ispec_selected_rec(irec))
-         if(body_waves)then !P-SH waves
+         if(p_sv)then !P-SH waves
           accel_elastic(1,iglob) = accel_elastic(1,iglob) + adj_sourcearrays(irec_local,NSTEP-it+1,1,i,j)
           accel_elastic(3,iglob) = accel_elastic(3,iglob) + adj_sourcearrays(irec_local,NSTEP-it+1,3,i,j)
          else !SH (membrane) waves

Modified: seismo/2D/SPECFEM2D/trunk/meshfem2D.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/meshfem2D.F90	2009-09-14 21:59:09 UTC (rev 15667)
+++ seismo/2D/SPECFEM2D/trunk/meshfem2D.F90	2009-09-14 22:44:36 UTC (rev 15668)
@@ -279,7 +279,7 @@
 
   double precision :: Q0,freq0
 
-  logical :: body_waves
+  logical :: p_sv 
 
   logical, dimension(:), allocatable :: enreg_surf
 
@@ -470,7 +470,7 @@
   call read_value_double_precision(IIN,IGNORE_JUNK,freq0)
 
 ! determine if body or surface (membrane) waves calculation
-  call read_value_logical(IIN,IGNORE_JUNK,body_waves)
+  call read_value_logical(IIN,IGNORE_JUNK,p_sv)
 
   if ( read_external_mesh ) then
      call read_mesh(mesh_file, nelmnts, elmnts, nnodes, num_start)
@@ -1449,8 +1449,8 @@
      write(15,*) 'TURN_VISCATTENUATION_ON Q0 freq0'
      write(15,*) TURN_VISCATTENUATION_ON,Q0,freq0
 
-     write(15,*) 'body_waves'
-     write(15,*) body_waves
+     write(15,*) 'p_sv'
+     write(15,*) p_sv
 
      write(15,*) 'nt deltat isolver'
      write(15,*) nt,deltat,isolver

Modified: seismo/2D/SPECFEM2D/trunk/specfem2D.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/specfem2D.F90	2009-09-14 21:59:09 UTC (rev 15667)
+++ seismo/2D/SPECFEM2D/trunk/specfem2D.F90	2009-09-14 22:44:36 UTC (rev 15668)
@@ -232,8 +232,8 @@
   double precision, dimension(:,:), allocatable :: coorg
   double precision, dimension(:), allocatable :: coorgread
 
-! for body or surface (membrane) waves calculation
-  logical :: body_waves
+! for P-SV or SH (membrane) waves calculation
+  logical :: p_sv
 
 ! receiver information
   integer :: nrec,ios
@@ -756,7 +756,7 @@
   read(IIN,*) TURN_VISCATTENUATION_ON,Q0,freq0
 
   read(IIN,"(a80)") datlin
-  read(IIN,*) body_waves
+  read(IIN,*) p_sv
 
 !---- check parameters read
   if (myrank == 0 .and. ipass == 1) then
@@ -1024,13 +1024,13 @@
   enddo !do ispec = 1,nspec
 
 
-  if(.not. body_waves .and. .not. any_elastic) then
+  if(.not. p_sv .and. .not. any_elastic) then
   print*, '*************** WARNING ***************'
   print*, 'Surface (membrane) waves calculation needs an elastic medium'
   print*, '*************** WARNING ***************'
   stop
   endif
-  if(body_waves .and. (TURN_ATTENUATION_ON .or. TURN_ANISOTROPY_ON)) then
+  if(p_sv .and. (TURN_ATTENUATION_ON .or. TURN_ANISOTROPY_ON)) then
   print*, '*************** WARNING ***************'
   print*, 'Attenuation and anisotropy are not implemented for surface (membrane) waves calculation'
   print*, '*************** WARNING ***************'
@@ -3019,7 +3019,7 @@
       if(nspec_xmin >0) then
       do ispec = 1,nspec_xmin
 
-     if(body_waves)then!P-SV waves
+     if(p_sv)then!P-SV waves
        do id =1,2
          do i=1,NGLLZ
      read(35) b_absorb_elastic_left(id,i,ispec,it)
@@ -3042,7 +3042,7 @@
       if(nspec_xmax >0) then
       do ispec = 1,nspec_xmax
 
-     if(body_waves)then!P-SV waves
+     if(p_sv)then!P-SV waves
        do id =1,2
          do i=1,NGLLZ
      read(36) b_absorb_elastic_right(id,i,ispec,it)
@@ -3065,7 +3065,7 @@
       if(nspec_zmin >0) then
       do ispec = 1,nspec_zmin
 
-     if(body_waves)then!P-SV waves
+     if(p_sv)then!P-SV waves
        do id =1,2
          do i=1,NGLLX
      read(37) b_absorb_elastic_bottom(id,i,ispec,it)
@@ -3088,7 +3088,7 @@
       if(nspec_zmax >0) then
       do ispec = 1,nspec_zmax
 
-     if(body_waves)then!P-SV waves
+     if(p_sv)then!P-SV waves
        do id =1,2
          do i=1,NGLLX
      read(38) b_absorb_elastic_top(id,i,ispec,it)
@@ -3228,7 +3228,7 @@
    if(any_elastic) then
     write(outputname,'(a,i6.6,a)') 'lastframe_elastic',myrank,'.bin'
     open(unit=55,file='OUTPUT_FILES/'//outputname,status='old',action='read',form='unformatted')
-      if(body_waves)then !P-SV waves
+      if(p_sv)then !P-SV waves
        do j=1,npoin
       read(55) (b_displ_elastic(i,j), i=1,NDIM), &
                   (b_veloc_elastic(i,j), i=1,NDIM), &
@@ -5127,7 +5127,7 @@
 ! *********************************************************
 
  if(any_elastic) then
-    call compute_forces_elastic(body_waves,npoin,nspec,myrank,nelemabs,numat, &
+    call compute_forces_elastic(p_sv,npoin,nspec,myrank,nelemabs,numat, &
                ispec_selected_source,ispec_selected_rec,is_proc_source,which_proc_receiver, &
                source_type,it,NSTEP,anyabs,assign_external_model, &
                initialfield,TURN_ATTENUATION_ON,TURN_ANISOTROPY_ON,angleforce,deltatcube, &
@@ -5151,7 +5151,7 @@
       if(nspec_xmin >0) then
       do ispec = 1,nspec_xmin
       
-      if(body_waves)then!P-SV waves
+      if(p_sv)then!P-SV waves
          do i=1,NGLLZ
      write(35) b_absorb_elastic_left(1,i,ispec,it)
          enddo
@@ -5172,7 +5172,7 @@
       do ispec = 1,nspec_xmax
 
 
-      if(body_waves)then!P-SV waves
+      if(p_sv)then!P-SV waves
          do i=1,NGLLZ
      write(36) b_absorb_elastic_right(1,i,ispec,it)
          enddo
@@ -5192,7 +5192,7 @@
       if(nspec_zmin >0) then
       do ispec = 1,nspec_zmin
 
-      if(body_waves)then!P-SV waves
+      if(p_sv)then!P-SV waves
          do i=1,NGLLX
      write(37) b_absorb_elastic_bottom(1,i,ispec,it)
          enddo
@@ -5212,7 +5212,7 @@
       if(nspec_zmax >0) then
       do ispec = 1,nspec_zmax
 
-      if(body_waves)then!P-SV waves
+      if(p_sv)then!P-SV waves
          do i=1,NGLLX
      write(38) b_absorb_elastic_top(1,i,ispec,it)
          enddo
@@ -5637,7 +5637,7 @@
         if(source_type(i_source) == 1) then
        if(isolver == 1) then  ! forward wavefield
 
-          if(body_waves) then ! P-SV calculation
+          if(p_sv) then ! P-SV calculation
           accel_elastic(1,iglob_source(i_source)) = accel_elastic(1,iglob_source(i_source)) &
                             - sin(angleforce(i_source))*source_time_function(i_source,it)
           accel_elastic(3,iglob_source(i_source)) = accel_elastic(3,iglob_source(i_source)) &
@@ -5649,7 +5649,7 @@
 
        else                   ! backward wavefield
 
-          if(body_waves) then ! P-SV calculation
+          if(p_sv) then ! P-SV calculation
       b_accel_elastic(1,iglob_source(i_source)) = b_accel_elastic(1,iglob_source(i_source)) &
                             - sin(angleforce(i_source))*source_time_function(i_source,NSTEP-it+1)
       b_accel_elastic(3,iglob_source(i_source)) = b_accel_elastic(3,iglob_source(i_source)) &
@@ -6595,7 +6595,7 @@
 
 ! rotate seismogram components if needed, except if recording pressure, which is a scalar
     if(seismotype /= 4 .and. seismotype /= 6) then
-      if(body_waves) then
+      if(p_sv) then
       sisux(seismo_current,irecloc) =   cosrot_irec(irecloc)*valux + sinrot_irec(irecloc)*valuz
       sisuz(seismo_current,irecloc) = - sinrot_irec(irecloc)*valux + cosrot_irec(irecloc)*valuz
       else
@@ -6920,7 +6920,7 @@
 
   if (myrank == 0) write(IOUT,*) 'Writing PostScript file'
 
-  if(imagetype == 1 .and. body_waves) then
+  if(imagetype == 1 .and. p_sv) then
 
     if (myrank == 0) write(IOUT,*) 'drawing displacement vector as small arrows...'
 
@@ -6956,7 +6956,7 @@
           d1_coorg_send_ps_vector_field,d1_coorg_recv_ps_vector_field,d2_coorg_send_ps_vector_field,d2_coorg_recv_ps_vector_field, &
           coorg_send_ps_vector_field,coorg_recv_ps_vector_field)
 
-  else if(imagetype == 2 .and. body_waves) then
+  else if(imagetype == 2 .and. p_sv) then
 
     if (myrank == 0) write(IOUT,*) 'drawing velocity vector as small arrows...'
 
@@ -6992,7 +6992,7 @@
           d1_coorg_send_ps_vector_field,d1_coorg_recv_ps_vector_field,d2_coorg_send_ps_vector_field,d2_coorg_recv_ps_vector_field, &
           coorg_send_ps_vector_field,coorg_recv_ps_vector_field)
 
-  else if(imagetype == 3 .and. body_waves) then
+  else if(imagetype == 3 .and. p_sv) then
 
     if (myrank == 0) write(IOUT,*) 'drawing acceleration vector as small arrows...'
 
@@ -7028,7 +7028,7 @@
           d1_coorg_send_ps_vector_field,d1_coorg_recv_ps_vector_field,d2_coorg_send_ps_vector_field,d2_coorg_recv_ps_vector_field, &
           coorg_send_ps_vector_field,coorg_recv_ps_vector_field)
 
-  else if(imagetype == 4 .or. .not. body_waves) then
+  else if(imagetype == 4 .or. .not. p_sv) then
 
     if (myrank == 0) write(IOUT,*) 'cannot draw scalar pressure field or y-component field as a vector plot, skipping...'
 
@@ -7036,7 +7036,7 @@
     call exit_MPI('wrong type for snapshots')
   endif
 
-  if (myrank == 0 .and. imagetype /= 4 .and. body_waves) write(IOUT,*) 'PostScript file written'
+  if (myrank == 0 .and. imagetype /= 4 .and. p_sv) write(IOUT,*) 'PostScript file written'
 
   endif
 
@@ -7071,7 +7071,7 @@
           elastic,poroelastic,vector_field_display, &
           xix,xiz,gammax,gammaz,ibool,hprime_xx,hprime_zz,nspec,npoin,numat,kmato,density,rhoext,assign_external_model)
 
-  else if(imagetype == 4 .and. body_waves) then
+  else if(imagetype == 4 .and. p_sv) then
 
     if (myrank == 0) write(IOUT,*) 'drawing image of pressure field...'
 
@@ -7081,7 +7081,7 @@
          numat,kmato,density,porosity,tortuosity,poroelastcoef,vpext,vsext,rhoext,e1,e11, &
          TURN_ATTENUATION_ON,TURN_ANISOTROPY_ON,Mu_nu1,Mu_nu2,N_SLS)
 
-  else if(imagetype == 4 .and. .not. body_waves) then
+  else if(imagetype == 4 .and. .not. p_sv) then
     call exit_MPI('cannot draw pressure field for SH (membrane) waves')
   else
     call exit_MPI('wrong type for snapshots')
@@ -7092,7 +7092,7 @@
   do k = 1, nb_pixel_loc
      j = ceiling(real(num_pixel_loc(k)) / real(NX_IMAGE_color))
      i = num_pixel_loc(k) - (j-1)*NX_IMAGE_color
-    if(body_waves) then !P-SH waves, plot vertical component or pressure
+    if(p_sv) then !P-SH waves, plot vertical component or pressure
      image_color_data(i,j) = vector_field_display(3,iglob_image_color(i,j))
     else !SH (membrane) waves, plot y-component
      image_color_data(i,j) = vector_field_display(2,iglob_image_color(i,j))
@@ -7119,7 +7119,7 @@
         do k = 1, nb_pixel_loc
            j = ceiling(real(num_pixel_loc(k)) / real(NX_IMAGE_color))
            i = num_pixel_loc(k) - (j-1)*NX_IMAGE_color
-    if(body_waves) then !P-SH waves, plot vertical component or pressure
+    if(p_sv) then !P-SH waves, plot vertical component or pressure
            data_pixel_send(k) = vector_field_display(3,iglob_image_color(i,j))
     else !SH (membrane) waves, plot y-component
            data_pixel_send(k) = vector_field_display(2,iglob_image_color(i,j))
@@ -7144,7 +7144,7 @@
 ! suppress seismograms if we generate traces of the run for analysis with "ParaVer", because time consuming
   if(.not. GENERATE_PARAVER_TRACES) call write_seismograms(sisux,sisuz,siscurl,station_name,network_name,NSTEP, &
         nrecloc,which_proc_receiver,nrec,myrank,deltat,seismotype,st_xval,t0(1), &
-        NTSTEP_BETWEEN_OUTPUT_SEISMO,seismo_offset,seismo_current,body_waves)
+        NTSTEP_BETWEEN_OUTPUT_SEISMO,seismo_offset,seismo_current,p_sv)
 
   seismo_offset = seismo_offset + seismo_current
   seismo_current = 0
@@ -7218,7 +7218,7 @@
   endif
     write(outputname,'(a,i6.6,a)') 'lastframe_elastic',myrank,'.bin'
     open(unit=55,file='OUTPUT_FILES/'//outputname,status='unknown',form='unformatted')
-      if(body_waves)then !P-SV waves
+      if(p_sv)then !P-SV waves
        do j=1,npoin
       write(55) displ_elastic(1,j), displ_elastic(3,j), &
                   veloc_elastic(1,j), veloc_elastic(3,j), &

Modified: seismo/2D/SPECFEM2D/trunk/write_seismograms.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/write_seismograms.F90	2009-09-14 21:59:09 UTC (rev 15667)
+++ seismo/2D/SPECFEM2D/trunk/write_seismograms.F90	2009-09-14 22:44:36 UTC (rev 15668)
@@ -46,7 +46,7 @@
 
   subroutine write_seismograms(sisux,sisuz,siscurl,station_name,network_name, &
       NSTEP,nrecloc,which_proc_receiver,nrec,myrank,deltat,seismotype,st_xval,t0, &
-      NTSTEP_BETWEEN_OUTPUT_SEISMO,seismo_offset,seismo_current,body_waves &
+      NTSTEP_BETWEEN_OUTPUT_SEISMO,seismo_offset,seismo_current,p_sv &
       )
 
   implicit none
@@ -60,7 +60,7 @@
   integer :: NTSTEP_BETWEEN_OUTPUT_SEISMO,seismo_offset,seismo_current
   double precision :: t0,deltat
 
-  logical :: body_waves
+  logical :: p_sv
 
   integer, intent(in) :: nrecloc,myrank
   integer, dimension(nrec),intent(in) :: which_proc_receiver
@@ -113,7 +113,7 @@
 
 
 ! only one seismogram if pressures or SH (membrane) waves
-  if(seismotype == 4 .or. seismotype == 6 .or. .not. body_waves) then
+  if(seismotype == 4 .or. seismotype == 6 .or. .not. p_sv) then
      number_of_components = 1
   else if(seismotype == 5) then
      number_of_components = NDIM+1
@@ -158,7 +158,7 @@
 ! write the new files
      if(seismotype == 4 .or. seismotype == 6) then
         open(unit=12,file='OUTPUT_FILES/pressure_file_single.bin',status='unknown',access='direct',recl=4)
-     elseif(.not.body_waves) then
+     elseif(.not.p_sv) then
         open(unit=12,file='OUTPUT_FILES/Uy_file_single.bin',status='unknown',access='direct',recl=4)
      else
         open(unit=12,file='OUTPUT_FILES/Ux_file_single.bin',status='unknown',access='direct',recl=4)
@@ -166,14 +166,14 @@
 
      if(seismotype == 4 .or. seismotype == 6) then
         open(unit=13,file='OUTPUT_FILES/pressure_file_double.bin',status='unknown',access='direct',recl=8)
-     elseif(.not.body_waves) then
+     elseif(.not.p_sv) then
         open(unit=13,file='OUTPUT_FILES/Uz_file_double.bin',status='unknown',access='direct',recl=8)
      else
         open(unit=13,file='OUTPUT_FILES/Ux_file_double.bin',status='unknown',access='direct',recl=8)
      endif
 
 ! no Z component seismogram if pressure
-     if(seismotype /= 4 .and. seismotype /= 6 .and. body_waves) then
+     if(seismotype /= 4 .and. seismotype /= 6 .and. p_sv) then
         open(unit=14,file='OUTPUT_FILES/Uz_file_single.bin',status='unknown',access='direct',recl=4)
         open(unit=15,file='OUTPUT_FILES/Uz_file_double.bin',status='unknown',access='direct',recl=8)
 
@@ -239,7 +239,7 @@
            ! in case of pressure, use different abbreviation
            if(seismotype == 4 .or. seismotype == 6) chn = 'PRE'
            ! in case of SH (membrane) waves, use different abbreviation
-           if(.not.body_waves) chn = 'BHY'
+           if(.not.p_sv) chn = 'BHY'
 
            ! create the name of the seismogram file for each slice
            ! file name includes the name of the station, the network and the component
@@ -285,7 +285,7 @@
         do isample = 1, seismo_current
            write(12,rec=(irec-1)*NSTEP+seismo_offset+isample) sngl(buffer_binary(isample,1))
            write(13,rec=(irec-1)*NSTEP+seismo_offset+isample) buffer_binary(isample,1)
-        if ( seismotype /= 4 .and. seismotype /= 6 .and. body_waves) then
+        if ( seismotype /= 4 .and. seismotype /= 6 .and. p_sv) then
            write(14,rec=(irec-1)*NSTEP+seismo_offset+isample) sngl(buffer_binary(isample,2))
            write(15,rec=(irec-1)*NSTEP+seismo_offset+isample) buffer_binary(isample,2)
         end if
@@ -316,7 +316,7 @@
 
   close(12)
   close(13)
-  if ( seismotype /= 4 .and. seismotype /= 6 .and. body_waves) then
+  if ( seismotype /= 4 .and. seismotype /= 6 .and. p_sv) then
      close(14)
      close(15)
   end if



More information about the CIG-COMMITS mailing list