[cig-commits] r21856 - in seismo/3D/SPECFEM3D/trunk/src: decompose_mesh generate_databases specfem3D

dkomati1 at geodynamics.org dkomati1 at geodynamics.org
Fri Apr 12 19:17:41 PDT 2013


Author: dkomati1
Date: 2013-04-12 19:17:41 -0700 (Fri, 12 Apr 2013)
New Revision: 21856

Modified:
   seismo/3D/SPECFEM3D/trunk/src/decompose_mesh/decompose_mesh.F90
   seismo/3D/SPECFEM3D/trunk/src/decompose_mesh/part_decompose_mesh.f90
   seismo/3D/SPECFEM3D/trunk/src/generate_databases/create_mass_matrices.f90
   seismo/3D/SPECFEM3D/trunk/src/generate_databases/generate_databases_par.f90
   seismo/3D/SPECFEM3D/trunk/src/generate_databases/memory_eval.f90
   seismo/3D/SPECFEM3D/trunk/src/generate_databases/read_partition_files.f90
   seismo/3D/SPECFEM3D/trunk/src/generate_databases/save_arrays_solver.f90
   seismo/3D/SPECFEM3D/trunk/src/specfem3D/compute_forces_acoustic_noDev.f90
   seismo/3D/SPECFEM3D/trunk/src/specfem3D/compute_forces_viscoelastic_noDev.f90
   seismo/3D/SPECFEM3D/trunk/src/specfem3D/finalize_simulation.f90
   seismo/3D/SPECFEM3D/trunk/src/specfem3D/pml_par.f90
   seismo/3D/SPECFEM3D/trunk/src/specfem3D/prepare_timerun.F90
   seismo/3D/SPECFEM3D/trunk/src/specfem3D/read_mesh_databases.f90
Log:
renamed CPML_mask_ibool() to is_CPML()


Modified: seismo/3D/SPECFEM3D/trunk/src/decompose_mesh/decompose_mesh.F90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/decompose_mesh/decompose_mesh.F90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/decompose_mesh/decompose_mesh.F90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -99,7 +99,7 @@
   integer :: ispec_CPML
   integer :: nspec_cpml
   integer, dimension(:), allocatable :: CPML_to_spec, CPML_regions
-  logical, dimension(:), allocatable :: CPML_mask_ibool
+  logical, dimension(:), allocatable :: is_CPML
 
   ! moho surface (optional)
   integer :: nspec2D_moho
@@ -689,12 +689,12 @@
     if( nspec_cpml > 0 ) print*, '  nspec_cpml = ', nspec_cpml
 
     ! sets mask of C-PML elements for all elements in this partition
-    allocate(CPML_mask_ibool(nspec),stat=ier)
-    if(ier /= 0) stop 'error allocating array CPML_mask_ibool'
-    CPML_mask_ibool(:) = .false.
+    allocate(is_CPML(nspec),stat=ier)
+    if(ier /= 0) stop 'error allocating array is_CPML'
+    is_CPML(:) = .false.
     do ispec_CPML=1,nspec_cpml
        if( (CPML_regions(ispec_CPML)>=1) .and. (CPML_regions(ispec_CPML)<=7) ) then
-          CPML_mask_ibool(CPML_to_spec(ispec_CPML)) = .true.
+          is_CPML(CPML_to_spec(ispec_CPML)) = .true.
        endif
     enddo
 
@@ -1084,7 +1084,7 @@
 
        ! writes out C-PML elements indices, CPML-regions and thickness of C-PML layer
        call write_cpml_database(IIN_database, ipart, nspec, nspec_cpml, CPML_to_spec, &
-            CPML_regions, CPML_mask_ibool, glob2loc_elmnts, part)
+            CPML_regions, is_CPML, glob2loc_elmnts, part)
 
        ! gets number of MPI interfaces
        call Write_interfaces_database(IIN_database, tab_interfaces, tab_size_interfaces, ipart, ninterfaces, &
@@ -1142,7 +1142,7 @@
     ! cleanup
     deallocate(CPML_to_spec,stat=ier); if( ier /= 0 ) stop 'error deallocating array CPML_to_spec'
     deallocate(CPML_regions,stat=ier); if( ier /= 0 ) stop 'error deallocating array CPML_regions'
-    deallocate(CPML_mask_ibool,stat=ier); if( ier /= 0 ) stop 'error deallocating array CPML_mask_ibool'
+    deallocate(is_CPML,stat=ier); if( ier /= 0 ) stop 'error deallocating array is_CPML'
 
     print*, 'partitions: '
     print*, '  num = ',nparts

Modified: seismo/3D/SPECFEM3D/trunk/src/decompose_mesh/part_decompose_mesh.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/decompose_mesh/part_decompose_mesh.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/decompose_mesh/part_decompose_mesh.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -978,7 +978,7 @@
   ! pertaining to iproc partition in the corresponding Database
   !--------------------------------------------------
   subroutine write_cpml_database(IIN_database, iproc, nspec, nspec_cpml, CPML_to_spec, &
-                                 CPML_regions, CPML_mask_ibool, glob2loc_elmnts, part)
+                                 CPML_regions, is_CPML, glob2loc_elmnts, part)
 
     integer, intent(in)  :: IIN_database
     integer, intent(in)  :: iproc
@@ -988,7 +988,7 @@
     integer, dimension(nspec_cpml), intent(in) :: CPML_to_spec
     integer, dimension(nspec_cpml), intent(in) :: CPML_regions
 
-    logical, dimension(nspec), intent(in) :: CPML_mask_ibool
+    logical, dimension(nspec), intent(in) :: is_CPML
 
     integer, dimension(:), pointer :: glob2loc_elmnts
 
@@ -1030,7 +1030,7 @@
        ! writes mask of C-PML elements for all elements in this partition
        do i=1,nspec
           if( part(i) == iproc ) then
-             write(IIN_database) CPML_mask_ibool(i)
+             write(IIN_database) is_CPML(i)
           endif
        enddo
     endif

Modified: seismo/3D/SPECFEM3D/trunk/src/generate_databases/create_mass_matrices.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/generate_databases/create_mass_matrices.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/generate_databases/create_mass_matrices.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -425,7 +425,7 @@
 
   subroutine create_mass_matrices_pml(nspec,ibool)
 
-    use generate_databases_par, only: CPML_mask_ibool,CPML_regions,d_store_x,d_store_y,d_store_z, &
+    use generate_databases_par, only: is_CPML,CPML_regions,d_store_x,d_store_y,d_store_z, &
                                       K_store_x,K_store_y,K_store_z,nspec_cpml,CPML_to_spec,DT
 
     use create_regions_mesh_ext_par
@@ -450,7 +450,7 @@
 
     ! loops over physical mesh elements
     do ispec=1,nspec
-       if( .not. CPML_mask_ibool(ispec) .and. ispec_is_elastic(ispec) ) then
+       if( .not. is_CPML(ispec) .and. ispec_is_elastic(ispec) ) then
           do k=1,NGLLZ
              do j=1,NGLLY
                 do i=1,NGLLX
@@ -472,7 +472,7 @@
                 enddo
              enddo
           enddo
-       else if( .not. CPML_mask_ibool(ispec) .and. ispec_is_acoustic(ispec) ) then
+       else if( .not. is_CPML(ispec) .and. ispec_is_acoustic(ispec) ) then
           do k=1,NGLLZ
              do j=1,NGLLY
                 do i=1,NGLLX
@@ -501,7 +501,7 @@
     do ispec_CPML=1,nspec_cpml
        ispec = CPML_to_spec(ispec_CPML)
 
-       if( CPML_mask_ibool(ispec) .and. ispec_is_elastic(ispec) ) then
+       if( is_CPML(ispec) .and. ispec_is_elastic(ispec) ) then
           ! X_surface C-PML
           if( CPML_regions(ispec_CPML) == 1 ) then
              do k=1,NGLLZ
@@ -713,7 +713,7 @@
     do ispec_CPML=1,nspec_cpml
        ispec = CPML_to_spec(ispec_CPML)
 
-       if( CPML_mask_ibool(ispec) .and. ispec_is_acoustic(ispec) ) then
+       if( is_CPML(ispec) .and. ispec_is_acoustic(ispec) ) then
           ! X_surface C-PML
           if( CPML_regions(ispec_CPML) == 1 ) then
              do k=1,NGLLZ

Modified: seismo/3D/SPECFEM3D/trunk/src/generate_databases/generate_databases_par.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/generate_databases/generate_databases_par.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/generate_databases/generate_databases_par.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -136,7 +136,7 @@
   integer, dimension(:), allocatable :: CPML_regions
 
   ! mask of C-PML elements for the global mesh
-  logical, dimension(:), allocatable :: CPML_mask_ibool
+  logical, dimension(:), allocatable :: is_CPML
 
   ! thickness of C-PML layers in each direction
   real(kind=CUSTOM_REAL) :: CPML_width_x,CPML_width_y,CPML_width_z

Modified: seismo/3D/SPECFEM3D/trunk/src/generate_databases/memory_eval.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/generate_databases/memory_eval.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/generate_databases/memory_eval.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -91,7 +91,7 @@
      ! spec_to_CPML
      memory_size = memory_size + NSPEC_AB*dble(SIZE_INTEGER)
 
-     ! CPML_mask_ibool
+     ! is_CPML
      memory_size = memory_size + NSPEC_AB*dble(SIZE_LOGICAL)
 
      ! d_store_x,d_store_y,d_store_z,d_store_x,d_store_y,d_store_z,alpha_store

Modified: seismo/3D/SPECFEM3D/trunk/src/generate_databases/read_partition_files.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/generate_databases/read_partition_files.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/generate_databases/read_partition_files.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -249,11 +249,11 @@
      enddo
 
      ! reads mask of C-PML elements for all elements in this partition
-     allocate(CPML_mask_ibool(NSPEC_AB),stat=ier)
-     if(ier /= 0) stop 'error allocating array CPML_mask_ibool'
+     allocate(is_CPML(NSPEC_AB),stat=ier)
+     if(ier /= 0) stop 'error allocating array is_CPML'
 
      do i=1,NSPEC_AB
-        read(IIN) CPML_mask_ibool(i)
+        read(IIN) is_CPML(i)
      enddo
   endif
 

Modified: seismo/3D/SPECFEM3D/trunk/src/generate_databases/save_arrays_solver.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/generate_databases/save_arrays_solver.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/generate_databases/save_arrays_solver.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -33,7 +33,7 @@
                     SAVE_MESH_FILES,ANISOTROPY)
 
   use generate_databases_par, only: nspec_cpml,CPML_width_x,CPML_width_y,CPML_width_z,CPML_to_spec,&
-                                    CPML_regions,CPML_mask_ibool,nspec_cpml_tot, &
+                                    CPML_regions,is_CPML,nspec_cpml_tot, &
                                     d_store_x,d_store_y,d_store_z,k_store_x,k_store_y,k_store_z,alpha_store, &
                                     nspec2D_xmin,nspec2D_xmax,nspec2D_ymin,nspec2D_ymax,NSPEC2D_BOTTOM,NSPEC2D_TOP, &
                                     ibelm_xmin,ibelm_xmax,ibelm_ymin,ibelm_ymax,ibelm_bottom,ibelm_top,PML_CONDITIONS
@@ -138,7 +138,7 @@
   if( nspec_cpml > 0 ) then
      write(IOUT) CPML_regions
      write(IOUT) CPML_to_spec
-     write(IOUT) CPML_mask_ibool
+     write(IOUT) is_CPML
      write(IOUT) d_store_x
      write(IOUT) d_store_y
      write(IOUT) d_store_z
@@ -316,7 +316,7 @@
   if( nspec_cpml_tot > 0 ) then
      deallocate(CPML_to_spec,stat=ier); if( ier /= 0 ) stop 'error deallocating array CPML_to_spec'
      deallocate(CPML_regions,stat=ier); if( ier /= 0 ) stop 'error deallocating array CPML_regions'
-     deallocate(CPML_mask_ibool,stat=ier); if( ier /= 0 ) stop 'error deallocating array CPML_mask_ibool'
+     deallocate(is_CPML,stat=ier); if( ier /= 0 ) stop 'error deallocating array is_CPML'
   endif
 
   if( PML_CONDITIONS ) then

Modified: seismo/3D/SPECFEM3D/trunk/src/specfem3D/compute_forces_acoustic_noDev.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/specfem3D/compute_forces_acoustic_noDev.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/specfem3D/compute_forces_acoustic_noDev.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -135,8 +135,8 @@
 
           if (PML_CONDITIONS) then
              ! do not merge this second line with the first using an ".and." statement
-             ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-             if(CPML_mask_ibool(ispec)) then
+             ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+             if(is_CPML(ispec)) then
                 temp1l_new = temp1l
                 temp2l_new = temp2l
                 temp3l_new = temp3l
@@ -181,8 +181,8 @@
           ! stores derivatives of ux, uy and uz with respect to x, y and z
           if (PML_CONDITIONS) then
              ! do not merge this second line with the first using an ".and." statement
-             ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-             if(CPML_mask_ibool(ispec)) then
+             ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+             if(is_CPML(ispec)) then
                 ispec_CPML = spec_to_CPML(ispec)
 
                 PML_dpotential_dxl(i,j,k,ispec_CPML) = dpotentialdxl
@@ -216,8 +216,8 @@
 
     if (PML_CONDITIONS) then
        ! do not merge this second line with the first using an ".and." statement
-       ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-       if(CPML_mask_ibool(ispec)) then
+       ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+       if(is_CPML(ispec)) then
           ! sets C-PML elastic memory variables to compute stress sigma and form dot product with test vector
           call pml_compute_memory_variables(ispec,ispec_CPML,deltat,tempx1,tempy1,tempz1,tempx2,tempy2,tempz2, &
                tempx3,tempy3,tempz3,NSPEC_AB,xix,xiy,xiz,etax,etay,etaz,gammax,gammay,gammaz,jacobian)
@@ -253,8 +253,8 @@
           ! updates potential_dot_dot_acoustic with contribution from each C-PML element
           if (PML_CONDITIONS) then
              ! do not merge this second line with the first using an ".and." statement
-             ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-             if(CPML_mask_ibool(ispec)) then
+             ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+             if(is_CPML(ispec)) then
                 potential_dot_dot_acoustic(iglob) = potential_dot_dot_acoustic(iglob) - &
                      potential_dot_dot_acoustic_CPML(i,j,k,ispec_CPML)
              endif

Modified: seismo/3D/SPECFEM3D/trunk/src/specfem3D/compute_forces_viscoelastic_noDev.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/specfem3D/compute_forces_viscoelastic_noDev.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/specfem3D/compute_forces_viscoelastic_noDev.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -256,8 +256,8 @@
            enddo
         else if(PML_CONDITIONS) then
            ! do not merge this second line with the first using an ".and." statement
-           ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-           if(CPML_mask_ibool(ispec)) then
+           ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+           if(is_CPML(ispec)) then
               do k=1,NGLLZ
                  do j=1,NGLLY
                     do i=1,NGLLX
@@ -342,8 +342,8 @@
 
           else if(PML_CONDITIONS) then
              ! do not merge this second line with the first using an ".and." statement
-             ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-             if(CPML_mask_ibool(ispec)) then
+             ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+             if(is_CPML(ispec)) then
                 tempx1_att(i,j,k) = tempx1(i,j,k)
                 tempx2_att(i,j,k) = tempx2(i,j,k)
                 tempx3_att(i,j,k) = tempx3(i,j,k)
@@ -406,8 +406,8 @@
               ! stores derivatives of ux, uy and uz with respect to x, y and z
               if (PML_CONDITIONS) then
                  ! do not merge this second line with the first using an ".and." statement
-                 ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-                 if(CPML_mask_ibool(ispec)) then
+                 ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+                 if(is_CPML(ispec)) then
                     ispec_CPML = spec_to_CPML(ispec)
 
                     PML_dux_dxl(i,j,k,ispec_CPML) = duxdxl
@@ -488,8 +488,8 @@
 
               else if(PML_CONDITIONS) then
                     ! do not merge this second line with the first using an ".and." statement
-                    ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-                    if(CPML_mask_ibool(ispec)) then
+                    ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+                    if(is_CPML(ispec)) then
                        PML_dux_dxl_new(i,j,k,ispec_CPML) = &
                             xixl*tempx1_att(i,j,k) + etaxl*tempx2_att(i,j,k) + gammaxl*tempx3_att(i,j,k)
                        PML_dux_dyl_new(i,j,k,ispec_CPML) = &
@@ -682,8 +682,8 @@
 !! DK DK shouldn't there be at least a "if (is_CPML(ispec))" test as well here, or something like that?
               if (PML_CONDITIONS) then
                  ! do not merge this second line with the first using an ".and." statement
-                 ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-                 if(.not.CPML_mask_ibool(ispec)) then
+                 ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+                 if(.not.is_CPML(ispec)) then
                     ! define symmetric components of sigma
                     sigma_yx = sigma_xy
                     sigma_zx = sigma_xz
@@ -727,8 +727,8 @@
 
     if (PML_CONDITIONS) then
        ! do not merge this second line with the first using an ".and." statement
-       ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-       if(CPML_mask_ibool(ispec)) then
+       ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+       if(is_CPML(ispec)) then
           ! sets C-PML elastic memory variables to compute stress sigma and form dot product with test vector
           call pml_compute_memory_variables(ispec,ispec_CPML,deltat,tempx1,tempy1,tempz1,tempx2,tempy2,tempz2, &
                tempx3,tempy3,tempz3,NSPEC_AB,xix,xiy,xiz,etax,etay,etaz,gammax,gammay,gammaz,jacobian)
@@ -790,8 +790,8 @@
           ! updates acceleration with contribution from each C-PML element
           if (PML_CONDITIONS) then
              ! do not merge this second line with the first using an ".and." statement
-             ! because array CPML_mask_ibool() is unallocated when PML_CONDITIONS is false
-             if(CPML_mask_ibool(ispec)) then
+             ! because array is_CPML() is unallocated when PML_CONDITIONS is false
+             if(is_CPML(ispec)) then
                 accel(1,iglob) = accel(1,iglob) - accel_elastic_CPML(1,i,j,k,ispec_CPML)
                 accel(2,iglob) = accel(2,iglob) - accel_elastic_CPML(2,i,j,k,ispec_CPML)
                 accel(3,iglob) = accel(3,iglob) - accel_elastic_CPML(3,i,j,k,ispec_CPML)
@@ -881,7 +881,7 @@
      do ispec2D=1,nspec2D_xmin
         ispec = ibelm_xmin(ispec2D)
 
-        if(CPML_mask_ibool(ispec) .and. ispec_is_elastic(ispec)) then
+        if(is_CPML(ispec) .and. ispec_is_elastic(ispec)) then
            i = 1
 
            do k=1,NGLLZ
@@ -908,7 +908,7 @@
      do ispec2D=1,nspec2D_xmax
         ispec = ibelm_xmax(ispec2D)
 
-        if(CPML_mask_ibool(ispec) .and. ispec_is_elastic(ispec)) then
+        if(is_CPML(ispec) .and. ispec_is_elastic(ispec)) then
            i = NGLLX
 
            do k=1,NGLLZ
@@ -935,7 +935,7 @@
      do ispec2D=1,nspec2D_ymin
         ispec = ibelm_ymin(ispec2D)
 
-        if(CPML_mask_ibool(ispec) .and. ispec_is_elastic(ispec)) then
+        if(is_CPML(ispec) .and. ispec_is_elastic(ispec)) then
            j = 1
 
            do k=1,NGLLZ
@@ -962,7 +962,7 @@
      do ispec2D=1,nspec2D_ymax
         ispec = ibelm_ymax(ispec2D)
 
-        if(CPML_mask_ibool(ispec) .and. ispec_is_elastic(ispec)) then
+        if(is_CPML(ispec) .and. ispec_is_elastic(ispec)) then
            j = NGLLY
 
            do k=1,NGLLZ
@@ -989,7 +989,7 @@
      do ispec2D=1,NSPEC2D_BOTTOM
         ispec = ibelm_bottom(ispec2D)
 
-        if(CPML_mask_ibool(ispec) .and. ispec_is_elastic(ispec)) then
+        if(is_CPML(ispec) .and. ispec_is_elastic(ispec)) then
            k = 1
 
            do j=1,NGLLY
@@ -1017,7 +1017,7 @@
        do ispec2D=1,NSPEC2D_BOTTOM
           ispec = ibelm_top(ispec2D)
 
-          if(CPML_mask_ibool(ispec) .and. ispec_is_elastic(ispec)) then
+          if(is_CPML(ispec) .and. ispec_is_elastic(ispec)) then
              k = NGLLZ
 
              do j=1,NGLLY

Modified: seismo/3D/SPECFEM3D/trunk/src/specfem3D/finalize_simulation.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/specfem3D/finalize_simulation.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/specfem3D/finalize_simulation.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -174,7 +174,7 @@
      ! deallocates C_PML arrays
      deallocate(CPML_regions)
      deallocate(CPML_to_spec)
-     deallocate(CPML_mask_ibool)
+     deallocate(is_CPML)
      deallocate(d_store_x)
      deallocate(d_store_y)
      deallocate(d_store_z)

Modified: seismo/3D/SPECFEM3D/trunk/src/specfem3D/pml_par.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/specfem3D/pml_par.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/specfem3D/pml_par.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -50,7 +50,7 @@
   integer, dimension(:), allocatable :: CPML_type
 
   ! mask of C-PML elements for the global mesh
-  logical, dimension(:), allocatable :: CPML_mask_ibool
+  logical, dimension(:), allocatable :: is_CPML
 
   ! thickness of C-PML layers
 !ZN  real(CUSTOM_REAL) :: CPML_width,CPML_width_x,CPML_width_y,CPML_width_z

Modified: seismo/3D/SPECFEM3D/trunk/src/specfem3D/prepare_timerun.F90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/specfem3D/prepare_timerun.F90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/specfem3D/prepare_timerun.F90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -733,7 +733,7 @@
     ! defines C-PML spectral elements local indexing
     ispec_CPML = 0
     do ispec=1,NSPEC_AB
-       if( CPML_mask_ibool(ispec) ) then
+       if( is_CPML(ispec) ) then
           ispec_CPML = ispec_CPML + 1
           spec_to_CPML(ispec) = ispec_CPML
        endif

Modified: seismo/3D/SPECFEM3D/trunk/src/specfem3D/read_mesh_databases.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/specfem3D/read_mesh_databases.f90	2013-04-13 02:16:07 UTC (rev 21855)
+++ seismo/3D/SPECFEM3D/trunk/src/specfem3D/read_mesh_databases.f90	2013-04-13 02:17:41 UTC (rev 21856)
@@ -342,8 +342,8 @@
      if(ier /= 0) stop 'error allocating array CPML_regions'
      allocate(CPML_to_spec(NSPEC_CPML),stat=ier)
      if(ier /= 0) stop 'error allocating array CPML_to_spec'
-     allocate(CPML_mask_ibool(NSPEC_AB),stat=ier)
-     if(ier /= 0) stop 'error allocating array CPML_mask_ibool'
+     allocate(is_CPML(NSPEC_AB),stat=ier)
+     if(ier /= 0) stop 'error allocating array is_CPML'
      allocate(d_store_x(NGLLX,NGLLY,NGLLZ,NSPEC_CPML),stat=ier)
      if(ier /= 0) stop 'error allocating array d_store_x'
      allocate(d_store_y(NGLLX,NGLLY,NGLLZ,NSPEC_CPML),stat=ier)
@@ -361,7 +361,7 @@
 
      read(27) CPML_regions
      read(27) CPML_to_spec
-     read(27) CPML_mask_ibool
+     read(27) is_CPML
      read(27) d_store_x
      read(27) d_store_y
      read(27) d_store_z



More information about the CIG-COMMITS mailing list