[cig-commits] r15459 - seismo/3D/SPECFEM3D_SESAME/trunk

pieyre at geodynamics.org pieyre at geodynamics.org
Mon Jul 13 07:14:45 PDT 2009


Author: pieyre
Date: 2009-07-13 07:14:44 -0700 (Mon, 13 Jul 2009)
New Revision: 15459

Modified:
   seismo/3D/SPECFEM3D_SESAME/trunk/compute_forces_with_Deville.f90
   seismo/3D/SPECFEM3D_SESAME/trunk/create_regions_mesh.f90
   seismo/3D/SPECFEM3D_SESAME/trunk/generate_databases.f90
   seismo/3D/SPECFEM3D_SESAME/trunk/locate_receivers.f90
   seismo/3D/SPECFEM3D_SESAME/trunk/locate_source.f90
   seismo/3D/SPECFEM3D_SESAME/trunk/specfem3D.f90
Log:
got rid of unused variables

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/compute_forces_with_Deville.f90
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/compute_forces_with_Deville.f90	2009-07-11 00:22:40 UTC (rev 15458)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/compute_forces_with_Deville.f90	2009-07-13 14:14:44 UTC (rev 15459)
@@ -31,7 +31,7 @@
      hdur,hdur_gaussian,t_cmt,dt,stf,t0,sourcearrays, & !pll
      one_minus_sum_beta,factor_common,alphaval,betaval,gammaval,R_xx,R_yy,R_xy,R_xz,R_yz, &
      epsilondev_xx,epsilondev_yy,epsilondev_xy,epsilondev_xz,epsilondev_yz,iflag_attenuation_store, &
-     ABSORBING_CONDITIONS,SAVE_FORWARD,NSTEP,SIMULATION_TYPE, &
+     ABSORBING_CONDITIONS, &
      nspec2D_xmin,nspec2D_xmax,nspec2D_ymin,nspec2D_ymax,NSPEC2D_BOTTOM,NSPEC2DMAX_XMIN_XMAX_ext,NSPEC2DMAX_YMIN_YMAX_ext,&
      ibelm_xmin,ibelm_xmax,ibelm_ymin,ibelm_ymax,ibelm_bottom, &
      nimin,nimax,njmin,njmax,nkmin_xi,nkmin_eta, &
@@ -152,8 +152,7 @@
        epsilondev_xx,epsilondev_yy,epsilondev_xy,epsilondev_xz,epsilondev_yz
   
 ! Stacey conditions
-  logical  :: ABSORBING_CONDITIONS,SAVE_FORWARD
-  integer  :: NSTEP,SIMULATION_TYPE
+  logical  :: ABSORBING_CONDITIONS
   integer  :: nspec2D_xmin,nspec2D_xmax,nspec2D_ymin,nspec2D_ymax,NSPEC2D_BOTTOM
   integer  :: NSPEC2DMAX_XMIN_XMAX_ext,NSPEC2DMAX_YMIN_YMAX_ext
   integer, dimension(nspec2D_xmin) :: ibelm_xmin

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/create_regions_mesh.f90
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/create_regions_mesh.f90	2009-07-11 00:22:40 UTC (rev 15458)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/create_regions_mesh.f90	2009-07-13 14:14:44 UTC (rev 15459)
@@ -146,6 +146,8 @@
   double precision, dimension(:,:,:), allocatable :: shape2D_x,shape2D_y,shape2D_bottom,shape2D_top
   double precision, dimension(:,:,:,:), allocatable :: dershape2D_x,dershape2D_y,dershape2D_bottom,dershape2D_top
 
+  integer  :: ispec2D
+  integer :: iflag, flag_below, flag_above
   integer  :: nspec2D_xmin, nspec2D_xmax, nspec2D_ymin, nspec2D_ymax, NSPEC2D_BOTTOM, NSPEC2D_TOP
   integer  :: NSPEC2DMAX_XMIN_XMAX 
   integer  :: NSPEC2DMAX_YMIN_YMAX
@@ -160,11 +162,6 @@
   integer, dimension(2,NSPEC2DMAX_XMIN_XMAX) :: nkmin_xi
   integer, dimension(2,NSPEC2DMAX_YMIN_YMAX) :: nkmin_eta
 
-  real(kind=CUSTOM_REAL), dimension(:,:), allocatable :: ibedrock
-
-  integer  :: ispec2D
-  integer :: iflag, flag_below, flag_above
-
   ! 2-D jacobians and normals
   real(kind=CUSTOM_REAL), dimension(:,:,:), allocatable :: &
        jacobian2D_xmin,jacobian2D_xmax, &
@@ -204,9 +201,9 @@
 ! ! for Piero Basini's model this is the resolution in meters of the topo file
 !   double precision, parameter :: DEGREES_PER_CELL_TOPO = 250.d0
 
+!real(kind=CUSTOM_REAL), dimension(:,:), allocatable :: ibedrock
 
 
-
 ! **************
 
 ! create the name for the database of the current slide and region

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/generate_databases.f90
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/generate_databases.f90	2009-07-11 00:22:40 UTC (rev 15458)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/generate_databases.f90	2009-07-13 14:14:44 UTC (rev 15459)
@@ -129,17 +129,9 @@
 ! number of spectral elements in each block
   integer nspec,npointot
 
-! meshing parameters
-  double precision, dimension(:), allocatable :: rns
-
 ! auxiliary variables to generate the mesh
-  integer ix,iy,ir
+  integer ix,iy
 
-  double precision xin,etan,rn
-  double precision x_current,y_current,z_top,z_bot
-
-  double precision, dimension(:,:,:), allocatable :: xgrid,ygrid,zgrid
-
 ! parameters needed to store the radii of the grid points
   integer, dimension(:), allocatable :: idoubling
   integer, dimension(:,:,:,:), allocatable :: ibool
@@ -155,16 +147,9 @@
   double precision area_local_top,area_total_top
   double precision volume_local,volume_total
 
-  integer iprocnum,npx,npy
-
-! for loop on all the slices
-  integer iproc_xi,iproc_eta
-  integer, dimension(:,:), allocatable :: addressing
-
 ! use integer array to store topography values
-  integer icornerlat,icornerlong,NX_TOPO,NY_TOPO
-  double precision lat,long,elevation,ORIG_LAT_TOPO,ORIG_LONG_TOPO,DEGREES_PER_CELL_TOPO
-  double precision long_corner,lat_corner,ratio_xi,ratio_eta
+  integer NX_TOPO,NY_TOPO
+  double precision ORIG_LAT_TOPO,ORIG_LONG_TOPO,DEGREES_PER_CELL_TOPO
   character(len=100) topo_file
   integer, dimension(:,:), allocatable :: itopo_bathy
 
@@ -175,9 +160,6 @@
   double precision, external :: wtime
   double precision time_start,tCPU
 
-! addressing for all the slices
-  integer, dimension(:), allocatable :: iproc_xi_slice,iproc_eta_slice
-
 ! parameters read from parameter file
   integer NER_SEDIM,NER_BASEMENT_SEDIM,NER_16_BASEMENT, &
              NER_MOHO_16,NER_BOTTOM_MOHO,NEX_XI,NEX_ETA, &
@@ -185,7 +167,7 @@
   integer NSOURCES
 
   double precision UTM_X_MIN,UTM_X_MAX,UTM_Y_MIN,UTM_Y_MAX
-  double precision Z_DEPTH_BLOCK,Z_BASEMENT_SURFACE,Z_DEPTH_MOHO
+  double precision Z_DEPTH_BLOCK
   double precision DT,LATITUDE_MIN,LATITUDE_MAX,LONGITUDE_MIN,LONGITUDE_MAX,HDUR_MOVIE
   double precision THICKNESS_TAPER_BLOCK_HR,THICKNESS_TAPER_BLOCK_MR,VP_MIN_GOCAD,VP_VS_RATIO_GOCAD_TOP,VP_VS_RATIO_GOCAD_BOTTOM
 
@@ -218,18 +200,16 @@
   double precision min_elevation_all,max_elevation_all
 
 ! for tapered basement map
-  integer icorner_x,icorner_y
   integer iz_basement
-  double precision x_corner,y_corner
   double precision z_basement(NX_BASEMENT,NY_BASEMENT)
   character(len=150) BASEMENT_MAP_FILE
 
 ! to filter list of stations
-  integer irec,nrec,nrec_filtered,ios
-  double precision stlat,stlon,stele,stbur
-  character(len=MAX_LENGTH_STATION_NAME) station_name
-  character(len=MAX_LENGTH_NETWORK_NAME) network_name
-  character(len=150) rec_filename,filtered_rec_filename,dummystring
+!   integer nrec,nrec_filtered
+!   double precision stlat,stlon,stele,stbur
+!   character(len=MAX_LENGTH_STATION_NAME) station_name
+!   character(len=MAX_LENGTH_NETWORK_NAME) network_name
+!   character(len=150) rec_filename!,filtered_rec_filename
 
 ! for Databases of external meshes
   character(len=150) prname

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/locate_receivers.f90
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/locate_receivers.f90	2009-07-11 00:22:40 UTC (rev 15458)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/locate_receivers.f90	2009-07-13 14:14:44 UTC (rev 15459)
@@ -31,8 +31,7 @@
                  nrec,islice_selected_rec,ispec_selected_rec, &
                  xi_receiver,eta_receiver,gamma_receiver,station_name,network_name,nu, &
                  NPROC,utm_x_source,utm_y_source, &
-                 TOPOGRAPHY,itopo_bathy,UTM_PROJECTION_ZONE,SUPPRESS_UTM_PROJECTION, &
-                 NX_TOPO,NY_TOPO,ORIG_LAT_TOPO,ORIG_LONG_TOPO,DEGREES_PER_CELL_TOPO, &
+                 TOPOGRAPHY,UTM_PROJECTION_ZONE, &
                  iglob_is_surface_external_mesh,ispec_is_surface_external_mesh &
                  )
 
@@ -40,9 +39,9 @@
 
   include "constants.h"
 
-  integer NPROC,UTM_PROJECTION_ZONE,NX_TOPO,NY_TOPO
+  logical TOPOGRAPHY
 
-  logical TOPOGRAPHY,SUPPRESS_UTM_PROJECTION
+  integer NPROC,UTM_PROJECTION_ZONE
 
   integer nrec,myrank
 
@@ -50,15 +49,9 @@
 
   integer, dimension(NGLLX,NGLLY,NGLLZ,NSPEC_AB) :: ibool
 
-  double precision ORIG_LAT_TOPO,ORIG_LONG_TOPO,DEGREES_PER_CELL_TOPO
-
 ! arrays containing coordinates of the points
   real(kind=CUSTOM_REAL), dimension(NGLOB_AB) :: xstore,ystore,zstore
 
-! use integer array to store topography values
-  integer itopo_bathy(NX_TOPO,NY_TOPO)
-  double precision long_corner,lat_corner,ratio_xi,ratio_eta
-
 ! for surface locating and normal computing with external mesh
   integer :: pt0_ix,pt0_iy,pt0_iz,pt1_ix,pt1_iy,pt1_iz,pt2_ix,pt2_iy,pt2_iz
   real(kind=CUSTOM_REAL), dimension(3) :: u_vector,v_vector,w_vector
@@ -78,7 +71,6 @@
   integer irec
   integer i,j,k,ispec,iglob,imin,imax,jmin,jmax,kmin,kmax
 
-  integer icornerlong,icornerlat
   double precision utm_x_source,utm_y_source
   double precision dist
   double precision xi,eta,gamma,dx,dy,dz,dxi,deta,dgamma

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/locate_source.f90
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/locate_source.f90	2009-07-11 00:22:40 UTC (rev 15458)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/locate_source.f90	2009-07-13 14:14:44 UTC (rev 15459)
@@ -33,10 +33,8 @@
                  NSTEP,DT,hdur,Mxx,Myy,Mzz,Mxy,Mxz,Myz, &
                  islice_selected_source,ispec_selected_source, &
                  xi_source,eta_source,gamma_source, &
-                 LATITUDE_MIN,LATITUDE_MAX,LONGITUDE_MIN,LONGITUDE_MAX,Z_DEPTH_BLOCK, &
-                 TOPOGRAPHY,itopo_bathy,UTM_PROJECTION_ZONE, &
-                 PRINT_SOURCE_TIME_FUNCTION,SUPPRESS_UTM_PROJECTION, &
-                 NX_TOPO,NY_TOPO,ORIG_LAT_TOPO,ORIG_LONG_TOPO,DEGREES_PER_CELL_TOPO, &
+                 TOPOGRAPHY,UTM_PROJECTION_ZONE, &
+                 PRINT_SOURCE_TIME_FUNCTION, &
                  nu_source,iglob_is_surface_external_mesh,ispec_is_surface_external_mesh &
                  )
 
@@ -45,19 +43,14 @@
   include "constants.h"
 
   integer NPROC,UTM_PROJECTION_ZONE
-  integer NSTEP,NSPEC_AB,NGLOB_AB,NSOURCES,NX_TOPO,NY_TOPO
+  integer NSTEP,NSPEC_AB,NGLOB_AB,NSOURCES
 
-  logical TOPOGRAPHY,PRINT_SOURCE_TIME_FUNCTION,SUPPRESS_UTM_PROJECTION
+  logical TOPOGRAPHY,PRINT_SOURCE_TIME_FUNCTION
 
-  double precision DT,LATITUDE_MIN,LATITUDE_MAX,LONGITUDE_MIN,LONGITUDE_MAX,Z_DEPTH_BLOCK
-  double precision ORIG_LAT_TOPO,ORIG_LONG_TOPO,DEGREES_PER_CELL_TOPO
+  double precision DT
 
   integer, dimension(NGLLX,NGLLY,NGLLZ,NSPEC_AB) :: ibool
 
-! use integer array to store topography values
-  integer itopo_bathy(NX_TOPO,NY_TOPO)
-  double precision long_corner,lat_corner,ratio_xi,ratio_eta
-
   integer myrank
 
 ! arrays containing coordinates of the points
@@ -122,7 +115,6 @@
   double precision, dimension(NSOURCES) :: xi_source,eta_source,gamma_source
   double precision, dimension(3,3,NSOURCES) :: nu_source
 
-  integer icornerlong,icornerlat
   double precision, dimension(NSOURCES) :: lat,long,depth,elevation
   double precision moment_tensor(6,NSOURCES)
 

Modified: seismo/3D/SPECFEM3D_SESAME/trunk/specfem3D.f90
===================================================================
--- seismo/3D/SPECFEM3D_SESAME/trunk/specfem3D.f90	2009-07-11 00:22:40 UTC (rev 15458)
+++ seismo/3D/SPECFEM3D_SESAME/trunk/specfem3D.f90	2009-07-13 14:14:44 UTC (rev 15459)
@@ -1215,10 +1215,8 @@
           NSTEP,DT,hdur,Mxx,Myy,Mzz,Mxy,Mxz,Myz, &
           islice_selected_source,ispec_selected_source, &
           xi_source,eta_source,gamma_source, &
-          LATITUDE_MIN,LATITUDE_MAX,LONGITUDE_MIN,LONGITUDE_MAX,Z_DEPTH_BLOCK, &
-          TOPOGRAPHY,itopo_bathy,UTM_PROJECTION_ZONE, &
-          PRINT_SOURCE_TIME_FUNCTION,SUPPRESS_UTM_PROJECTION, &
-          NX_TOPO,NY_TOPO,ORIG_LAT_TOPO,ORIG_LONG_TOPO,DEGREES_PER_CELL_TOPO, &
+          TOPOGRAPHY,UTM_PROJECTION_ZONE, &
+          PRINT_SOURCE_TIME_FUNCTION, &
           nu_source,iglob_is_surface_external_mesh,ispec_is_surface_external_mesh)
 
   if(minval(t_cmt) /= 0.) call exit_MPI(myrank,'one t_cmt must be zero, others must be positive')
@@ -1290,8 +1288,7 @@
             nrec,islice_selected_rec,ispec_selected_rec, &
             xi_receiver,eta_receiver,gamma_receiver,station_name,network_name,nu, &
             NPROC,utm_x_source(1),utm_y_source(1), &
-            TOPOGRAPHY,itopo_bathy,UTM_PROJECTION_ZONE,SUPPRESS_UTM_PROJECTION, &
-            NX_TOPO,NY_TOPO,ORIG_LAT_TOPO,ORIG_LONG_TOPO,DEGREES_PER_CELL_TOPO, &
+            TOPOGRAPHY,UTM_PROJECTION_ZONE, &
             iglob_is_surface_external_mesh,ispec_is_surface_external_mesh &
 )
 
@@ -1952,8 +1949,7 @@
          NSOURCES,myrank,it,islice_selected_source,ispec_selected_source,xi_source,eta_source,gamma_source,nu_source, &
          hdur,hdur_gaussian,t_cmt,dt,stf,t0,sourcearrays, & 
          one_minus_sum_beta,factor_common,alphaval,betaval,gammaval,R_xx,R_yy,R_xy,R_xz,R_yz, &
-         epsilondev_xx,epsilondev_yy,epsilondev_xy,epsilondev_xz,epsilondev_yz,iflag_attenuation_store, &
-         ABSORBING_CONDITIONS,SAVE_FORWARD,NSTEP,SIMULATION_TYPE, &
+         epsilondev_xx,epsilondev_yy,epsilondev_xy,epsilondev_xz,epsilondev_yz,iflag_attenuation_store,ABSORBING_CONDITIONS, &
          nspec2D_xmin,nspec2D_xmax,nspec2D_ymin,nspec2D_ymax,NSPEC2D_BOTTOM,NSPEC2DMAX_XMIN_XMAX_ext,NSPEC2DMAX_YMIN_YMAX_ext, &
          ibelm_xmin,ibelm_xmax,ibelm_ymin,ibelm_ymax,ibelm_bottom, &
          nimin,nimax,njmin,njmax,nkmin_xi,nkmin_eta, &
@@ -1979,8 +1975,7 @@
          NSOURCES,myrank,it,islice_selected_source,ispec_selected_source,xi_source,eta_source,gamma_source,nu_source, &
          hdur,hdur_gaussian,t_cmt,dt,stf,t0,sourcearrays, & 
          one_minus_sum_beta,factor_common,alphaval,betaval,gammaval,R_xx,R_yy,R_xy,R_xz,R_yz, &
-         epsilondev_xx,epsilondev_yy,epsilondev_xy,epsilondev_xz,epsilondev_yz,iflag_attenuation_store, &
-         ABSORBING_CONDITIONS,SAVE_FORWARD,NSTEP,SIMULATION_TYPE, &
+         epsilondev_xx,epsilondev_yy,epsilondev_xy,epsilondev_xz,epsilondev_yz,iflag_attenuation_store,ABSORBING_CONDITIONS, &
          nspec2D_xmin,nspec2D_xmax,nspec2D_ymin,nspec2D_ymax,NSPEC2D_BOTTOM,NSPEC2DMAX_XMIN_XMAX_ext,NSPEC2DMAX_YMIN_YMAX_ext, &
          ibelm_xmin,ibelm_xmax,ibelm_ymin,ibelm_ymax,ibelm_bottom, &
          nimin,nimax,njmin,njmax,nkmin_xi,nkmin_eta, &



More information about the CIG-COMMITS mailing list