[cig-commits] r17117 - in seismo/3D/SPECFEM3D/trunk: . EXAMPLES/tomographic_model decompose_mesh_SCOTCH

danielpeter at geodynamics.org danielpeter at geodynamics.org
Tue Aug 24 11:55:03 PDT 2010


Author: danielpeter
Date: 2010-08-24 11:55:03 -0700 (Tue, 24 Aug 2010)
New Revision: 17117

Modified:
   seismo/3D/SPECFEM3D/trunk/EXAMPLES/tomographic_model/Par_file
   seismo/3D/SPECFEM3D/trunk/combine_vol_data.f90
   seismo/3D/SPECFEM3D/trunk/decompose_mesh_SCOTCH/Makefile
   seismo/3D/SPECFEM3D/trunk/decompose_mesh_SCOTCH/decompose_mesh_SCOTCH.f90
   seismo/3D/SPECFEM3D/trunk/flags.guess
   seismo/3D/SPECFEM3D/trunk/model_tomography.f90
   seismo/3D/SPECFEM3D/trunk/program_specfem3D.f90
   seismo/3D/SPECFEM3D/trunk/specfem3D.f90
Log:
adds more flexibility in decompose_mesh_SCOTCH.f90 for unsorted defined/undefined materials in nummaterial_velocity_file; simplifies default ifort flags in flags.guess; minor bug fix in combine_vol_data.f90

Modified: seismo/3D/SPECFEM3D/trunk/EXAMPLES/tomographic_model/Par_file
===================================================================
--- seismo/3D/SPECFEM3D/trunk/EXAMPLES/tomographic_model/Par_file	2010-08-24 16:07:31 UTC (rev 17116)
+++ seismo/3D/SPECFEM3D/trunk/EXAMPLES/tomographic_model/Par_file	2010-08-24 18:55:03 UTC (rev 17117)
@@ -12,7 +12,7 @@
 
 # time step parameters
 NSTEP                           = 1000
-DT                              = 0.05d0
+DT                              = 0.02d0
 
 # parameters describing the model
 OCEANS                          = .false.

Modified: seismo/3D/SPECFEM3D/trunk/combine_vol_data.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/combine_vol_data.f90	2010-08-24 16:07:31 UTC (rev 17116)
+++ seismo/3D/SPECFEM3D/trunk/combine_vol_data.f90	2010-08-24 18:55:03 UTC (rev 17117)
@@ -178,7 +178,7 @@
     ! gets number of elements and global points for this partition
     write(prname_lp,'(a,i6.6,a)') trim(LOCAL_PATH)//'/proc',iproc,'_'
     open(unit=27,file=prname_lp(1:len_trim(prname_lp))//'external_mesh.bin',&
-          status='old',action='read',form='unformatted')
+          status='old',action='read',form='unformatted',iostat=ios)
     read(27) NSPEC_AB
     read(27) NGLOB_AB 
     
@@ -198,25 +198,28 @@
     write(prname,'(a,i6.6,a)') trim(indir)//'proc',iproc,'_'
     local_data_file = trim(prname) // trim(filename) // '.bin'
     open(unit = 28,file = trim(local_data_file),status='old',&
-          action='read', iostat = ios,form ='unformatted')
+          action='read',form ='unformatted',iostat=ios)          
     if (ios /= 0) then
       print *,'Error opening ',trim(local_data_file)
       stop
     endif
-    allocate(data(NGLLX,NGLLY,NGLLZ,NSPEC_AB))    
-    read(28) data
-    close(28)
-    print *, trim(local_data_file)
-
+    
+    allocate(dat(NGLLX,NGLLY,NGLLZ,NSPEC_AB),stat=ios)
+    if( ios /= 0 ) stop 'error allocating dat array'
+    
     ! uses conversion to real values
-    allocate(dat(NGLLX,NGLLY,NGLLZ,NSPEC_AB))
-    if( CUSTOM_REAL == 4 ) then
-      dat = data
+    if( CUSTOM_REAL == 8 ) then
+      allocate(data(NGLLX,NGLLY,NGLLZ,NSPEC_AB),stat=ios)    
+      if( ios /= 0 ) stop 'error allocating data array'
+      read(28) data
+      dat = sngl(data)
+      deallocate(data)
     else
-      dat = sngl(data)
+      read(28) dat  
     endif
+    close(28)
+    print *, trim(local_data_file)
 
-
     ! writes point coordinates and scalar value to mesh file
     if (.not. HIGH_RESOLUTION_MESH) then
       ! writes out element corners only
@@ -234,7 +237,7 @@
     np = np + numpoin
 
     ! cleans up memory allocations
-    deallocate(ibool,data,dat,xstore,ystore,zstore)
+    deallocate(ibool,dat,xstore,ystore,zstore)
     
   enddo  ! all slices for points
 
@@ -392,6 +395,11 @@
       nee = nee + NSPEC_AB
 
     endif ! HIGH_RESOLUTION_MESH      
+
+    ! frees arrays
+    if( allocated(mask_ibool) ) deallocate( mask_ibool)
+    if( allocated(ibool) ) deallocate(ibool)
+    
   enddo
     
   end subroutine cvd_count_totals_ext_mesh

Modified: seismo/3D/SPECFEM3D/trunk/decompose_mesh_SCOTCH/Makefile
===================================================================
--- seismo/3D/SPECFEM3D/trunk/decompose_mesh_SCOTCH/Makefile	2010-08-24 16:07:31 UTC (rev 17116)
+++ seismo/3D/SPECFEM3D/trunk/decompose_mesh_SCOTCH/Makefile	2010-08-24 18:55:03 UTC (rev 17117)
@@ -3,7 +3,7 @@
 #############################################################
 ## modify to match your compiler defaults 
 ## (which were used to compile SCOTCH libraries from below as well)
-F90 = ifort # use -g -traceback -check bounds -warn 
+F90 = ifort # -g -traceback -check bounds -warn 
 #F90 = gfortran    # use -Wall
 
 ## modify to match your library paths

Modified: seismo/3D/SPECFEM3D/trunk/decompose_mesh_SCOTCH/decompose_mesh_SCOTCH.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/decompose_mesh_SCOTCH/decompose_mesh_SCOTCH.f90	2010-08-24 16:07:31 UTC (rev 17116)
+++ seismo/3D/SPECFEM3D/trunk/decompose_mesh_SCOTCH/decompose_mesh_SCOTCH.f90	2010-08-24 18:55:03 UTC (rev 17117)
@@ -116,7 +116,8 @@
   !(CUBIT calls this the connectivity, guess in the sense that it connects with the points index in 
   ! the global coordinate file "nodes_coords_file"; it doesn't tell you which point is connected with others)
     open(unit=98, file=localpath_name(1:len_trim(localpath_name))//'/mesh_file', &
-          status='old', form='formatted')
+          status='old', form='formatted',iostat=ierr)
+    if( ierr /= 0 ) stop 'error opening mesh_file'
     read(98,*) nspec
     allocate(elmnts(esize,nspec))
     do ispec = 1, nspec
@@ -157,8 +158,10 @@
 
   ! reads material associations
     open(unit=98, file=localpath_name(1:len_trim(localpath_name))//'/materials_file', &
-          status='old', form='formatted')
+          status='old', form='formatted',iostat=ierr)
+    if( ierr /= 0 ) stop 'error opening materials_file'
     allocate(mat(2,nspec))
+    mat(:,:) = 0
     do ispec = 1, nspec
       ! format: # id_element #flag
       ! note: be aware that elements may not be sorted in materials_file
@@ -188,7 +191,9 @@
     count_def_mat = 0
     count_undef_mat = 0
     open(unit=98, file=localpath_name(1:len_trim(localpath_name))//'/nummaterial_velocity_file',&
-          status='old', form='formatted')
+          status='old', form='formatted',iostat=ierr)
+    if( ierr /= 0 ) stop 'error opening nummaterial_velocity_file'
+          
     ! note: format #material_domain_id #material_id #...      
     read(98,*,iostat=ierr) idummy,num_mat
     print *,'materials:'
@@ -215,21 +220,35 @@
     endif
     allocate(mat_prop(6,count_def_mat))
     allocate(undef_mat_prop(6,count_undef_mat))
+    mat_prop(:,:) = 0.d0
+    undef_mat_prop(:,:) = ''
+    
     ! reads in defined material properties
     open(unit=98, file=localpath_name(1:len_trim(localpath_name))//'/nummaterial_velocity_file', &
-          status='old', form='formatted')
-
-    ! note: entries in nummaterial_velocity_file must be sorted to list all
-    !          defined materials (material_id > 0) first, and afterwards list all
-    !          undefined materials (material_id < 0 )    
+          status='old', form='formatted', iostat=ierr)
+    if( ierr /= 0 ) stop 'error opening nummaterial_velocity_file'
+    
+    ! note: entries in nummaterial_velocity_file can be an unsorted list of all
+    !          defined materials (material_id > 0) and undefined materials (material_id < 0 )    
     do imat=1,count_def_mat
        ! material definitions
        !
        ! format: note that we save the arguments in a slightly different order in mat_prop(:,:)
        !              #(6) material_domain_id #(0) material_id  #(1) rho #(2) vp #(3) vs #(4) Q_flag #(5) anisotropy_flag
        !
-       read(98,*) idomain_id,num_mat,rho,vp,vs,q_flag,aniso_flag
+       !read(98,*) idomain_id,num_mat,rho,vp,vs,q_flag,aniso_flag
+       ! reads lines unti it reaches a defined material
+       num_mat = -1
+       do while( num_mat < 0 .and. ierr == 0)
+         read(98,'(A256)',iostat=ierr) line
+         read(line,*) idomain_id,num_mat
+       enddo
+       if( ierr /= 0 ) stop 'error reading in defined materials in nummaterial_velocity_file'
+       
+       ! reads in defined material properties
+       read(line,*) idomain_id,num_mat,rho,vp,vs,q_flag,aniso_flag
 
+       ! checks material_id bounds     
        if(num_mat < 1 .or. num_mat > count_def_mat)  stop "ERROR : Invalid nummaterial_velocity_file file."    
        
        !read(98,*) num_mat, mat_prop(1,num_mat),mat_prop(2,num_mat),&
@@ -246,7 +265,9 @@
           stop 'wrong attenuation flag in mesh: too large, not supported yet - check with constants.h'
        endif
     end do
+    
     ! reads in undefined material properties
+    rewind(98,iostat=ierr) ! back to the beginning of the file
     do imat=1,count_undef_mat
        !  undefined materials: have to be listed in decreasing order of material_id (start with -1, -2, etc...)
        !  format: 
@@ -256,15 +277,21 @@
        !   - for tomography models 
        !    #material_domain_id #material_id (<0) #type_name (="tomography") #block_name 
        !        example:     2  -1 tomography elastic tomography_model.xyz 1
-       read(98,'(A256)') line
-
+       ! reads lines unti it reaches a defined material
+       num_mat = 1
+       do while( num_mat >= 0 .and. ierr == 0 )
+         read(98,'(A256)',iostat=ierr) line
+         read(line,*) idomain_id,num_mat
+       enddo
+       if( ierr /= 0 ) stop 'error reading in undefined materials in nummaterial_velocity_file'
+        
        ! checks if interface or tomography definition 
        read(line,*) undef_mat_prop(6,imat),undef_mat_prop(1,imat),undef_mat_prop(2,imat)
        if( trim(undef_mat_prop(2,imat)) == 'interface' ) then
          ! line will have 5 arguments, e.g.: 2  -1 interface 1 2 
          read(line,*) undef_mat_prop(6,imat),undef_mat_prop(1,imat),undef_mat_prop(2,imat),&
                      undef_mat_prop(3,imat),undef_mat_prop(4,imat)
-         undef_mat_prop(5,imat) = "1" ! dummy value
+         undef_mat_prop(5,imat) = "0" ! dummy value
        else if( trim(undef_mat_prop(2,imat)) == 'tomography' ) then 
          ! line will have 6 arguments, e.g.: 2  -1 tomography elastic tomography_model.xyz 1
          read(line,*) undef_mat_prop(6,imat),undef_mat_prop(1,imat),undef_mat_prop(2,imat),&
@@ -307,7 +334,7 @@
           ! must point to an undefined material
           if( -num_mat > count_undef_mat) stop "ERROR: invalid flag_up in interface definition in nummaterial_velocity_file"
          endif
-       endif                                                                           
+       endif   
     end do
     close(98)
 

Modified: seismo/3D/SPECFEM3D/trunk/flags.guess
===================================================================
--- seismo/3D/SPECFEM3D/trunk/flags.guess	2010-08-24 16:07:31 UTC (rev 17116)
+++ seismo/3D/SPECFEM3D/trunk/flags.guess	2010-08-24 18:55:03 UTC (rev 17117)
@@ -26,20 +26,22 @@
         # Intel ifort Fortran90
         #
         if test x"$FLAGS_CHECK" = x; then
-            #FLAGS_CHECK="-O3 -vec-report0 -e95 -std95 -implicitnone -warn truncated_source -warn argument_checking -warn unused -warn declarations -warn alignments -warn ignore_loc -warn usage -check nobounds -align sequence -assume byterecl -fpe0 -ftz -traceback -ftrapuv" # -mcmodel=medium
-
+            FLAGS_CHECK="-O3 -assume byterecl -check nobounds -traceback -ftrapuv" 
+            
+            # for debugging:
             # ifort v 10.1 with these flags shows best performance
-            FLAGS_CHECK="-O2 -ftz -xT -fpe0 -ftz -traceback -ftrapuv -vec-report0 -std95 -implicitnone -check nobounds  -assume byterecl  -static-intel -warn truncated_source -warn argument_checking -warn unused -warn declarations -warn alignments -warn ignore_loc -warn usage "
+            #FLAGS_CHECK="-O2 -ftz -xT -fpe0 -ftz -traceback -ftrapuv -vec-report0 -std95 -implicitnone -check nobounds  -assume byterecl  -static-intel -warn truncated_source -warn argument_checking -warn unused -warn declarations -warn alignments -warn ignore_loc -warn usage "
             #FLAGS_CHECK="-O2 -xT -static-intel -r8 -mcmodel=large -implicitnone -warn truncated_source -warn argument_checking -warn unused -warn declarations -check nobounds -align sequence -assume byterecl -ftrapuv -fpe0 -ftz -traceback"
         fi
         if test x"$FLAGS_NO_CHECK" = x; then
         # standard options (leave option -ftz, which is *critical* for performance)
         # add -Winline to get information about routines that are inlined
         # add -vec-report3 to get information about loops that are vectorized or not
-            #FLAGS_NO_CHECK="-O3 -xP -vec-report0 -e95 -std95 -implicitnone -warn truncated_source -warn argument_checking -warn unused -warn declarations -warn alignments -warn ignore_loc -warn usage -check nobounds -align sequence -assume byterecl -fpe3 -ftz" # -mcmodel=medium
+            FLAGS_NO_CHECK="-O3 -assume byterecl "
 
+            # for debugging:
             # ifort v 10.1 with these flags shows best performance
-            FLAGS_NO_CHECK="-O2 -ftz -xT -fpe3 -ftz -vec-report0 -std95 -implicitnone -check nobounds  -assume byterecl  -static-intel -warn truncated_source -warn argument_checking -warn unused -warn declarations -warn alignments -warn ignore_loc -warn usage "
+            #FLAGS_NO_CHECK="-O2 -ftz -xT -fpe3 -ftz -vec-report0 -std95 -implicitnone -check nobounds  -assume byterecl  -static-intel -warn truncated_source -warn argument_checking -warn unused -warn declarations -warn alignments -warn ignore_loc -warn usage "
             #FLAGS_NO_CHECK="-O2 -xT -static-intel -r8 -mcmodel=large -implicitnone -warn truncated_source -warn argument_checking -warn unused -warn declarations -check nobounds -align sequence -assume byterecl -ftrapuv -fpe0 -ftz -traceback"
         fi
         ;;

Modified: seismo/3D/SPECFEM3D/trunk/model_tomography.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/model_tomography.f90	2010-08-24 16:07:31 UTC (rev 17116)
+++ seismo/3D/SPECFEM3D/trunk/model_tomography.f90	2010-08-24 18:55:03 UTC (rev 17117)
@@ -142,14 +142,12 @@
     vs_tomography(irecord) = vs_tomo
     rho_tomography(irecord) = rho_tomo
     z_tomography(irecord) = z_tomo
-  enddo 
-  
+  enddo   
   close(27)   
 
+  ! user output
   if( myrank == 0 ) then
-    write(IMAIN,*) 
-    write(IMAIN,*) 'tomography model: ',trim(TOMO_FILENAME)
-    write(IMAIN,*) 
+    write(IMAIN,*) '     tomography model: ',trim(TOMO_FILENAME)
   endif
                                                                 
   end subroutine read_model_tomography

Modified: seismo/3D/SPECFEM3D/trunk/program_specfem3D.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/program_specfem3D.f90	2010-08-24 16:07:31 UTC (rev 17116)
+++ seismo/3D/SPECFEM3D/trunk/program_specfem3D.f90	2010-08-24 18:55:03 UTC (rev 17117)
@@ -29,7 +29,7 @@
   call init()
 
 ! run the main program
-  call specfem3D
+  call specfem3D()
 
 ! mpi finish
   call finalize()

Modified: seismo/3D/SPECFEM3D/trunk/specfem3D.f90
===================================================================
--- seismo/3D/SPECFEM3D/trunk/specfem3D.f90	2010-08-24 16:07:31 UTC (rev 17116)
+++ seismo/3D/SPECFEM3D/trunk/specfem3D.f90	2010-08-24 18:55:03 UTC (rev 17117)
@@ -25,7 +25,7 @@
 !
 ! United States and French Government Sponsorship Acknowledged.
 
-  subroutine specfem3D
+  subroutine specfem3D()
 
   use specfem_par
   



More information about the CIG-COMMITS mailing list