[cig-commits] r20333 - in seismo/2D/SPECFEM2D/trunk/src: meshfem2D specfem2D

dkomati1 at geodynamics.org dkomati1 at geodynamics.org
Thu Jun 7 13:15:22 PDT 2012


Author: dkomati1
Date: 2012-06-07 13:15:21 -0700 (Thu, 07 Jun 2012)
New Revision: 20333

Modified:
   seismo/2D/SPECFEM2D/trunk/src/meshfem2D/meshfem2D.F90
   seismo/2D/SPECFEM2D/trunk/src/specfem2D/createnum_fast.f90
   seismo/2D/SPECFEM2D/trunk/src/specfem2D/createnum_slow.f90
   seismo/2D/SPECFEM2D/trunk/src/specfem2D/initialize_simulation.F90
   seismo/2D/SPECFEM2D/trunk/src/specfem2D/specfem2D.F90
Log:
added calculation and display of the total number of degrees of freedom in the mesh


Modified: seismo/2D/SPECFEM2D/trunk/src/meshfem2D/meshfem2D.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/src/meshfem2D/meshfem2D.F90	2012-06-07 19:44:38 UTC (rev 20332)
+++ seismo/2D/SPECFEM2D/trunk/src/meshfem2D/meshfem2D.F90	2012-06-07 20:15:21 UTC (rev 20333)
@@ -857,19 +857,19 @@
 
   endif
 
-  ! beware of fluid solid edges : coupled elements are transfered to the same partition
+  ! beware of fluid solid edges : coupled elements are transferred to the same partition
   if ( ngnod == 9 ) then
      call acoustic_elastic_repartitioning (elmnts_bis, nb_materials, phi, num_material, nproc)
   else
      call acoustic_elastic_repartitioning (elmnts, nb_materials, phi, num_material, nproc)
   endif
-  ! beware of fluid porous edges : coupled elements are transfered to the same partition
+  ! beware of fluid porous edges : coupled elements are transferred to the same partition
   if ( ngnod == 9 ) then
      call acoustic_poro_repartitioning (elmnts_bis, nb_materials, phi, num_material, nproc)
   else
      call acoustic_poro_repartitioning (elmnts, nb_materials, phi, num_material, nproc)
   endif
-  ! beware of porous solid edges : coupled elements are transfered to the same partition
+  ! beware of porous solid edges : coupled elements are transferred to the same partition
   if ( ngnod == 9 ) then
      call poro_elastic_repartitioning (elmnts_bis, nb_materials, phi, num_material, nproc)
   else

Modified: seismo/2D/SPECFEM2D/trunk/src/specfem2D/createnum_fast.f90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/src/specfem2D/createnum_fast.f90	2012-06-07 19:44:38 UTC (rev 20332)
+++ seismo/2D/SPECFEM2D/trunk/src/specfem2D/createnum_fast.f90	2012-06-07 20:15:21 UTC (rev 20333)
@@ -231,11 +231,11 @@
 ! check the numbering obtained
   if(minval(ibool) /= 1 .or. maxval(ibool) /= nglob) call exit_MPI('Error while generating global numbering')
 
-  if(myrank == 0 .and. ipass == 1) then
-    write(IOUT,*)
-    write(IOUT,*) 'Total number of points of the global mesh: ',nglob
-    write(IOUT,*)
-  endif
+! if(myrank == 0 .and. ipass == 1) then
+!   write(IOUT,*)
+!   write(IOUT,*) 'Total number of points of the global mesh on slice 0: ',nglob
+!   write(IOUT,*)
+! endif
 
   end subroutine createnum_fast
 

Modified: seismo/2D/SPECFEM2D/trunk/src/specfem2D/createnum_slow.f90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/src/specfem2D/createnum_slow.f90	2012-06-07 19:44:38 UTC (rev 20332)
+++ seismo/2D/SPECFEM2D/trunk/src/specfem2D/createnum_slow.f90	2012-06-07 20:15:21 UTC (rev 20333)
@@ -311,14 +311,14 @@
 ! verification de la coherence de la numerotation generee
   if(minval(ibool) /= 1 .or. maxval(ibool) /= nglob) call exit_MPI('Error while generating global numbering')
 
-  if(myrank == 0 .and. ipass == 1) then
-    write(IOUT,*) 'Total number of points of the global mesh: ',nglob,' distributed as follows:'
-    write(IOUT,*)
-    write(IOUT,*) 'Number of interior points: ',nglob-npedge-npcorn
-    write(IOUT,*) 'Number of edge points (without corners): ',npedge
-    write(IOUT,*) 'Number of corner points: ',npcorn
-    write(IOUT,*)
-  endif
+! if(myrank == 0 .and. ipass == 1) then
+!   write(IOUT,*) 'Total number of points of the global mesh on slice 0: ',nglob,' distributed as follows:'
+!   write(IOUT,*)
+!   write(IOUT,*) 'Number of interior points: ',nglob-npedge-npcorn
+!   write(IOUT,*) 'Number of edge points (without corners): ',npedge
+!   write(IOUT,*) 'Number of corner points: ',npcorn
+!   write(IOUT,*)
+! endif
 
   end subroutine createnum_slow
 

Modified: seismo/2D/SPECFEM2D/trunk/src/specfem2D/initialize_simulation.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/src/specfem2D/initialize_simulation.F90	2012-06-07 19:44:38 UTC (rev 20332)
+++ seismo/2D/SPECFEM2D/trunk/src/specfem2D/initialize_simulation.F90	2012-06-07 20:15:21 UTC (rev 20333)
@@ -114,7 +114,7 @@
 
   subroutine initialize_simulation_domains(any_acoustic,any_elastic,any_poroelastic, &
                                 anisotropic,elastic,poroelastic,porosity,anisotropy,kmato,numat, &
-                                nspec,nspec_allocate,p_sv,ATTENUATION_VISCOELASTIC_SOLID)
+                                nspec,nspec_allocate,p_sv,ATTENUATION_VISCOELASTIC_SOLID,count_nspec_acoustic)
 
   implicit none
   include "constants.h"
@@ -125,7 +125,7 @@
   logical, dimension(nspec) :: elastic
   logical, dimension(nspec) :: poroelastic
 
-  integer :: numat
+  integer :: numat,count_nspec_acoustic
   double precision, dimension(numat) :: porosity
   double precision, dimension(6,numat) :: anisotropy
   integer, dimension(nspec) :: kmato
@@ -146,6 +146,7 @@
   poroelastic(:) = .false.
 
   ! loops over all elements
+  count_nspec_acoustic = 0
   do ispec = 1,nspec
 
     if( nint(porosity(kmato(ispec))) == 1 ) then
@@ -153,6 +154,7 @@
       elastic(ispec) = .false.
       poroelastic(ispec) = .false.
       any_acoustic = .true.
+      count_nspec_acoustic = count_nspec_acoustic + 1
     elseif( porosity(kmato(ispec)) < TINYVAL) then
       ! elastic domain
       elastic(ispec) = .true.
@@ -168,7 +170,7 @@
       any_poroelastic = .true.
     endif
 
-  enddo !do ispec = 1,nspec
+  enddo ! of do ispec = 1,nspec
 
 
   if(.not. p_sv .and. .not. any_elastic) then

Modified: seismo/2D/SPECFEM2D/trunk/src/specfem2D/specfem2D.F90
===================================================================
--- seismo/2D/SPECFEM2D/trunk/src/specfem2D/specfem2D.F90	2012-06-07 19:44:38 UTC (rev 20332)
+++ seismo/2D/SPECFEM2D/trunk/src/specfem2D/specfem2D.F90	2012-06-07 20:15:21 UTC (rev 20333)
@@ -952,6 +952,10 @@
 ! for rk44
   double precision :: weight_rk
 
+! to count the number of degrees of freedom
+  integer :: count_nspec_acoustic,count_nspec_acoustic_total,nspec_total,nglob_total,nb_acoustic_DOFs,nb_elastic_DOFs
+  double precision :: ratio_1DOF,ratio_2DOFs
+
 !***********************************************************************
 !
 !             i n i t i a l i z a t i o n    p h a s e
@@ -1246,7 +1250,7 @@
 !-------------------------------------------------------------------------------
   call initialize_simulation_domains(any_acoustic,any_elastic,any_poroelastic, &
                                 anisotropic,elastic,poroelastic,porosity,anisotropy,kmato,numat, &
-                                nspec,nspec_allocate,p_sv,ATTENUATION_VISCOELASTIC_SOLID)
+                                nspec,nspec_allocate,p_sv,ATTENUATION_VISCOELASTIC_SOLID,count_nspec_acoustic)
 
   ! allocate memory variables for attenuation
   if(ipass == 1) then
@@ -1645,6 +1649,50 @@
     call createnum_slow(knods,ibool,nglob,nspec,ngnod,myrank,ipass)
   endif
 
+#ifdef USE_MPI
+  call MPI_REDUCE(count_nspec_acoustic, count_nspec_acoustic_total, 1, MPI_INTEGER, MPI_SUM, 0, MPI_COMM_WORLD, ier)
+  call MPI_REDUCE(nspec, nspec_total, 1, MPI_INTEGER, MPI_SUM, 0, MPI_COMM_WORLD, ier)
+  call MPI_REDUCE(nglob, nglob_total, 1, MPI_INTEGER, MPI_SUM, 0, MPI_COMM_WORLD, ier)
+#else
+  count_nspec_acoustic_total = count_nspec_acoustic
+  nspec_total = nspec
+  nglob_total = nglob
+#endif
+  if (myrank == 0 .and. ipass == 1) then
+    write(IOUT,*)
+    write(IOUT,*) 'Total number of elastic/visco/poro elements: ',nspec_total - count_nspec_acoustic_total
+    write(IOUT,*) 'Total number of acoustic elements: ',count_nspec_acoustic_total
+    write(IOUT,*)
+#ifdef USE_MPI
+    write(IOUT,*) 'Approximate total number of grid points in the mesh'
+    write(IOUT,*) '(with a few duplicates coming from MPI buffers): ',nglob_total
+#else
+    write(IOUT,*) 'Exact total number of grid points in the mesh: ',nglob_total
+#endif
+
+! percentage of elements with 2 degrees of freedom per point
+    ratio_2DOFs = (nspec_total - count_nspec_acoustic_total) / dble(nspec_total)
+    ratio_1DOF  = count_nspec_acoustic_total / dble(nspec_total)
+    nb_acoustic_DOFs = nint(nglob_total*ratio_1DOF)
+! elastic elements have two degrees of freedom per point
+    nb_elastic_DOFs  = nint(nglob_total*ratio_2DOFs*2)
+
+    if(p_sv) then
+      write(IOUT,*)
+      write(IOUT,*) 'Approximate number of acoustic degrees of freedom in the mesh: ',nb_acoustic_DOFs
+      write(IOUT,*) 'Approximate number of elastic degrees of freedom in the mesh: ',nb_elastic_DOFs
+      write(IOUT,*) '  (there are 2 degrees of freedom per point for elastic elements)'
+      write(IOUT,*)
+      write(IOUT,*) 'Approximate total number of degrees of freedom in the mesh'
+      write(IOUT,*) '(sum of the two values above): ',nb_acoustic_DOFs + nb_elastic_DOFs
+      write(IOUT,*)
+      write(IOUT,*) ' (for simplicity viscoelastic or poroelastic elements, if any,'
+      write(IOUT,*) '  are counted as elastic in the above three estimates;'
+      write(IOUT,*) '  in reality they have more degrees of freedom)'
+      write(IOUT,*)
+    endif
+  endif
+
 ! create a new indirect addressing array to reduce cache misses in memory access in the solver
   if(ipass == 2) then
 



More information about the CIG-COMMITS mailing list