[cig-commits] r20960 - in seismo/3D/SPECFEM3D/trunk/src: shared specfem3D

dkomati1 at geodynamics.org dkomati1 at geodynamics.org
Sat Oct 27 08:51:11 PDT 2012


Author: dkomati1
Date: 2012-10-27 08:51:11 -0700 (Sat, 27 Oct 2012)
New Revision: 20960

Modified:
   seismo/3D/SPECFEM3D/trunk/src/shared/prepare_assemble_MPI.f90
   seismo/3D/SPECFEM3D/trunk/src/specfem3D/detect_mesh_surfaces.f90
Log:
removed regolith and asteroid from all variable names


Modified: seismo/3D/SPECFEM3D/trunk/src/shared/prepare_assemble_MPI.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/shared/prepare_assemble_MPI.f90	2012-10-27 15:19:20 UTC (rev 20959)
+++ seismo/3D/SPECFEM3D/trunk/src/shared/prepare_assemble_MPI.f90	2012-10-27 15:51:11 UTC (rev 20960)
@@ -28,11 +28,11 @@
                                    ibool,npoin, &
                                    ninterface, max_interface_size, &
                                    my_nelmnts_neighbours, my_interfaces, &
-                                   ibool_interfaces_asteroid, &
-                                   nibool_interfaces_asteroid,NGNOD )
+                                   ibool_interfaces_ext_mesh, &
+                                   nibool_interfaces_ext_mesh,NGNOD )
 
-! returns: ibool_interfaces_asteroid with the global indices (as defined in ibool)
-!              nibool_interfaces_asteroid with the number of points in ibool_interfaces_asteroid
+! returns: ibool_interfaces_ext_mesh with the global indices (as defined in ibool)
+!              nibool_interfaces_ext_mesh with the number of points in ibool_interfaces_ext_mesh
 !
 ! for all points on the interface defined by ninterface, my_nelmnts_neighbours and my_interfaces
 
@@ -59,31 +59,31 @@
   integer, dimension(ninterface)  :: my_nelmnts_neighbours
   integer, dimension(6,max_interface_size,ninterface)  :: my_interfaces
 
-  integer, dimension(NGLLX*NGLLX*max_interface_size,ninterface) :: ibool_interfaces_asteroid
-  integer, dimension(ninterface)  :: nibool_interfaces_asteroid
+  integer, dimension(NGLLX*NGLLX*max_interface_size,ninterface) :: ibool_interfaces_ext_mesh
+  integer, dimension(ninterface)  :: nibool_interfaces_ext_mesh
 
 ! local parameters
   integer  :: num_interface
   integer  :: ispec_interface
 
-  logical, dimension(:),allocatable  :: mask_ibool_asteroid
+  logical, dimension(:),allocatable  :: mask_ibool_ext_mesh
 
   integer  :: ixmin, ixmax, iymin, iymax, izmin, izmax
   integer, dimension(NGNOD_EIGHT_CORNERS)  :: n
   integer  :: e1, e2, e3, e4
   integer  :: ispec,k,ix,iy,iz,ier,itype,iglob
-  integer  :: npoin_interface_asteroid
+  integer  :: npoin_interface_ext_mesh
 
 ! initializes
-  allocate( mask_ibool_asteroid(npoin), stat=ier); if( ier /= 0) stop 'error allocating array'
+  allocate( mask_ibool_ext_mesh(npoin), stat=ier); if( ier /= 0) stop 'error allocating array'
 
-  ibool_interfaces_asteroid(:,:) = 0
-  nibool_interfaces_asteroid(:) = 0
+  ibool_interfaces_ext_mesh(:,:) = 0
+  nibool_interfaces_ext_mesh(:) = 0
 
 ! loops over MPI interfaces
   do num_interface = 1, ninterface
-    npoin_interface_asteroid = 0
-    mask_ibool_asteroid(:) = .false.
+    npoin_interface_ext_mesh = 0
+    mask_ibool_ext_mesh(:) = .false.
 
     ! loops over number of elements on interface
     do ispec_interface = 1, my_nelmnts_neighbours(num_interface)
@@ -114,12 +114,12 @@
             iglob = ibool(ix,iy,iz,ispec)
 
             ! stores global index of point on interface
-            if(.not. mask_ibool_asteroid(iglob)) then
+            if(.not. mask_ibool_ext_mesh(iglob)) then
               ! masks point as being accounted for
-              mask_ibool_asteroid(iglob) = .true.
+              mask_ibool_ext_mesh(iglob) = .true.
               ! adds point to interface
-              npoin_interface_asteroid = npoin_interface_asteroid + 1
-              ibool_interfaces_asteroid(npoin_interface_asteroid,num_interface) = iglob
+              npoin_interface_ext_mesh = npoin_interface_ext_mesh + 1
+              ibool_interfaces_ext_mesh(npoin_interface_ext_mesh,num_interface) = iglob
             end if
           end do
         end do
@@ -128,11 +128,11 @@
     end do
 
     ! stores total number of (global) points on this MPI interface
-    nibool_interfaces_asteroid(num_interface) = npoin_interface_asteroid
+    nibool_interfaces_ext_mesh(num_interface) = npoin_interface_ext_mesh
 
   end do
 
-  deallocate( mask_ibool_asteroid )
+  deallocate( mask_ibool_ext_mesh )
 
 end subroutine prepare_assemble_MPI
 

Modified: seismo/3D/SPECFEM3D/trunk/src/specfem3D/detect_mesh_surfaces.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/src/specfem3D/detect_mesh_surfaces.f90	2012-10-27 15:19:20 UTC (rev 20959)
+++ seismo/3D/SPECFEM3D/trunk/src/specfem3D/detect_mesh_surfaces.f90	2012-10-27 15:51:11 UTC (rev 20960)
@@ -119,120 +119,5 @@
     call write_PNM_GIF_initialize()
   endif
 
-
-!!!! NL NL REGOLITH : runs at cines for asteroid simulations. Elements in contact with surface are part of the regolith layer.
-!!$  allocate(ispec_is_regolith(NSPEC_AB))
-!!$  ispec_is_regolith(:) = .false.
-!!$  do ispec = 1, NSPEC_AB
-!!$    do k = 1, NGLLZ
-!!$      do j = 1, NGLLY
-!!$        do i = 1, NGLLX
-!!$          iglob = ibool(i,j,k,ispec)
-!!$          if (iglob_is_surface_external_mesh(iglob)) then
-!!$            ispec_is_regolith(ispec) = .true.
-!!$          endif
-!!$        enddo
-!!$      enddo
-!!$    enddo
-!!$  enddo
-!!$
-!!$  do ispec = 1, NSPEC_AB
-!!$    if (ispec_is_regolith(ispec)) then
-!!$      do k = 1, NGLLZ
-!!$        do j = 1, NGLLY
-!!$          do i = 1, NGLLX
-!!$             kappastore(i,j,k,ispec) = materials_ext_mesh(1,2)* &
-!!$                  (materials_ext_mesh(2,2)*materials_ext_mesh(2,2) - &
-!!$                  4.d0*materials_ext_mesh(3,2)*materials_ext_mesh(3,2)/3.d0)
-!!$             mustore(i,j,k,ispec) = materials_ext_mesh(1,2)*materials_ext_mesh(3,2)*&
-!!$                  materials_ext_mesh(3,2)
-!!$
-!!$          enddo
-!!$        enddo
-!!$      enddo
-!!$    endif
-!!$  enddo
-!!$
-!!$
-!!$  call zwgljd(xigll,wxgll,NGLLX,GAUSSALPHA,GAUSSBETA)
-!!$  call zwgljd(yigll,wygll,NGLLY,GAUSSALPHA,GAUSSBETA)
-!!$  call zwgljd(zigll,wzgll,NGLLZ,GAUSSALPHA,GAUSSBETA)
-!!$
-!!$  rmass(:) = 0._CUSTOM_REAL
-!!$
-!!$  do ispec=1,NSPEC_AB
-!!$  do k=1,NGLLZ
-!!$    do j=1,NGLLY
-!!$      do i=1,NGLLX
-!!$        weight=wxgll(i)*wygll(j)*wzgll(k)
-!!$        iglob=ibool(i,j,k,ispec)
-!!$
-!!$        jacobianl=jacobian(i,j,k,ispec)
-!!$
-!!$! distinguish between single and double precision for reals
-!!$        if (.not. ispec_is_regolith(ispec)) then
-!!$        if(CUSTOM_REAL == SIZE_REAL) then
-!!$          rmass(iglob) = rmass(iglob) + &
-!!$               sngl(dble(materials_ext_mesh(1,1)) * dble(jacobianl) * weight)
-!!$        else
-!!$          rmass(iglob) = rmass(iglob) + materials_ext_mesh(1,1) * jacobianl * weight
-!!$        endif
-!!$        else
-!!$        if(CUSTOM_REAL == SIZE_REAL) then
-!!$          rmass(iglob) = rmass(iglob) + &
-!!$               sngl(dble(materials_ext_mesh(1,2)) * dble(jacobianl) * weight)
-!!$        else
-!!$          rmass(iglob) = rmass(iglob) + materials_ext_mesh(1,2) * jacobianl * weight
-!!$        endif
-!!$        endif
-!!$
-!!$      enddo
-!!$    enddo
-!!$  enddo
-!!$  enddo
-
-
-!!!! NL NL REGOLITH
-
-!!!!!!!!!! DK DK   endif
-
   end subroutine detect_mesh_surfaces
 
-
-!!!! NL NL REGOLITH
-!!$  double precision function materials_ext_mesh(i,j)
-!!$
-!!$    implicit none
-!!$
-!!$    integer :: i,j
-!!$
-!!$    select case (j)
-!!$      case (1)
-!!$        select case (i)
-!!$          case (1)
-!!$            materials_ext_mesh = 2700.d0
-!!$          case (2)
-!!$            materials_ext_mesh = 3000.d0
-!!$          case (3)
-!!$            materials_ext_mesh = 1732.051d0
-!!$          case default
-!!$            call stop_all()
-!!$          end select
-!!$      case (2)
-!!$        select case (i)
-!!$          case (1)
-!!$            materials_ext_mesh = 2000.d0
-!!$          case (2)
-!!$            materials_ext_mesh = 900.d0
-!!$          case (3)
-!!$            materials_ext_mesh = 500.d0
-!!$          case default
-!!$            call stop_all()
-!!$          end select
-!!$      case default
-!!$        call stop_all()
-!!$    end select
-!!$
-!!$  end function materials_ext_mesh
-!!!! NL NL REGOLITH
-



More information about the CIG-COMMITS mailing list