[cig-commits] r16384 - in seismo/3D/SPECFEM3D_GLOBE: tags/v5.0.0 tags/v5.0.0/USER_MANUAL tags/v5.0.0/USER_MANUAL/figures trunk

dkomati1 at geodynamics.org dkomati1 at geodynamics.org
Thu Mar 4 13:57:20 PST 2010


Author: dkomati1
Date: 2010-03-04 13:57:19 -0800 (Thu, 04 Mar 2010)
New Revision: 16384

Modified:
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/USER_MANUAL/figures/headers_sem_explained.pdf
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/USER_MANUAL/manual_SPECFEM3D_GLOBE.pdf
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/USER_MANUAL/manual_SPECFEM3D_GLOBE.tex
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/constants.h.in
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/create_header_file.f90
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/create_movie_GMT_global.f90
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/initialize_simulation.f90
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/meshfem3D.f90
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/save_header_file.f90
   seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/specfem3D.f90
   seismo/3D/SPECFEM3D_GLOBE/trunk/constants.h.in
   seismo/3D/SPECFEM3D_GLOBE/trunk/create_header_file.f90
   seismo/3D/SPECFEM3D_GLOBE/trunk/initialize_simulation.f90
   seismo/3D/SPECFEM3D_GLOBE/trunk/meshfem3D.f90
   seismo/3D/SPECFEM3D_GLOBE/trunk/save_header_file.f90
   seismo/3D/SPECFEM3D_GLOBE/trunk/specfem3D.f90
Log:
removed code that was specific to GPFS for MareNostrum in Barcelona


Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/USER_MANUAL/figures/headers_sem_explained.pdf
===================================================================
(Binary files differ)

Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/USER_MANUAL/manual_SPECFEM3D_GLOBE.pdf
===================================================================
(Binary files differ)

Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/USER_MANUAL/manual_SPECFEM3D_GLOBE.tex
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/USER_MANUAL/manual_SPECFEM3D_GLOBE.tex	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/USER_MANUAL/manual_SPECFEM3D_GLOBE.tex	2010-03-04 21:57:19 UTC (rev 16384)
@@ -171,9 +171,9 @@
 In the directory in which you want to install the package, type
 
 \begin{lyxcode}
-tar~-zxvf~SPECFEM3D\_GLOBE\_V4.0.3.tar.gz
+tar~-zxvf~SPECFEM3D\_GLOBE\_V5.0.0.tar.gz
 \end{lyxcode}
-The directory \texttt{SPECFEM3D\_GLOBE\_V4.0.3} will then contain
+The directory \texttt{SPECFEM3D\_GLOBE\_V5.0.0} will then contain
 the source code.
 
 To configure the software for your system, run the \texttt{configure}
@@ -271,7 +271,7 @@
 
 Finally, before compiling, make sure that the subdirectories \texttt{obj},
 \texttt{bak} and \texttt{OUTPUT\_FILES} exist within the directory
-with the source code (\texttt{SPECFEM3D\_GLOBE\_V4.0.3}). The \texttt{go\_mesher}
+with the source code (\texttt{SPECFEM3D\_GLOBE\_V5.0.0}). The \texttt{go\_mesher}
 script discussed below automatically takes care of creating the \texttt{OUTPUT\_FILES}
 directory.
 

Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/constants.h.in
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/constants.h.in	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/constants.h.in	2010-03-04 21:57:19 UTC (rev 16384)
@@ -217,11 +217,6 @@
 ! can be useful for benchmarks of a spherical Earth with fictitious sources and stations
   logical, parameter :: ASSUME_PERFECT_SPHERE = .false.
 
-!! DK DK UGLY added this in case we are running on MareNostrum in Barcelona
-!! DK DK UGLY because we then need some calls to the system to use GPFS
-  logical, parameter :: RUN_ON_MARENOSTRUM_BARCELONA = .false.
-
-
 !------------------------------------------------------
 !----------- do not modify anything below -------------
 !------------------------------------------------------

Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/create_header_file.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/create_header_file.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/create_header_file.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -226,9 +226,7 @@
   print *
   print *,'size of static arrays per slice = ',static_memory_size/1073741824.d0,' GB'
   print *
-  print *,'   (should be below and typically equal to 80% of 1.5 GB = 1.2 GB on pangu'
-  print *,'    at Caltech, and below and typically equal to 85% of 2 GB = 1.7 GB'
-  print *,'    on Marenostrum in Barcelona)'
+  print *,'   (should be below and typically equal to 80% or 90% of the memory installed per core)'
   print *,'   (if significantly more, the job will not run by lack of memory)'
   print *,'   (if significantly less, you waste a significant amount of memory)'
   print *

Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/create_movie_GMT_global.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/create_movie_GMT_global.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/create_movie_GMT_global.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -44,6 +44,18 @@
 
   include "constants.h"
 
+!---------------------
+! USER PARAMETER
+
+  ! to avoid flickering in movies, the displacement field will get normalized with an 
+  ! averaged maximum value over the past few, available snapshots
+  logical,parameter :: USE_AVERAGED_MAXIMUM = .false.
+  
+  ! minimum number of frames to average maxima
+  integer,parameter :: AVERAGE_MINIMUM = 2
+  
+!---------------------
+
   integer i,j,it
   integer it1,it2
   integer ispec
@@ -55,7 +67,12 @@
   real(kind=CUSTOM_REAL) normal_x,normal_y,normal_z
   real(kind=CUSTOM_REAL) thetahat_x,thetahat_y,thetahat_z
   real(kind=CUSTOM_REAL) phihat_x,phihat_y
-  double precision min_field_current,max_field_current,max_absol
+  
+  ! to average maxima over past few steps
+  double precision min_field_current,max_field_current,max_absol,max_average
+  double precision,dimension(:),allocatable :: max_history
+  integer :: nmax_history,imax
+
   real disp,lat,long
   integer nframes,iframe,USE_COMPONENT
 
@@ -187,6 +204,7 @@
   print *,'Allocating arrays for reading data of size ',ilocnum*NPROCTOT,'=',6*ilocnum*NPROCTOT*CUSTOM_REAL/1000000,'MB'
   print *
 
+  ! allocates movie arrays
   allocate(store_val_x(ilocnum,0:NPROCTOT-1),stat=ierror)
   if(ierror /= 0) stop 'error while allocating store_val_x'
 
@@ -217,27 +235,31 @@
   allocate(displn(NGLLX,NGLLY),stat=ierror)
   if(ierror /= 0) stop 'error while allocating displn'
 
-
-
   print *,'movie frames have been saved every ',NTSTEP_BETWEEN_FRAMES,' time steps'
   print *
 
+  ! user input
+  print *,'--------'
   print *,'enter first time step of movie (e.g. 1)'
   read(5,*) it1
 
-  print *,'enter last time step of movie (e.g. ',NSTEP,')'
+  print *,'enter last time step of movie (e.g. ',NSTEP,'or -1 for all)'
   read(5,*) it2
-
+  
   print *,'enter component (e.g. 1=Z, 2=N, 3=E)'
   read(5,*) USE_COMPONENT
 
   print *,'enter output ascii (F) or binary (T)'
   read(5,*) OUTPUT_BINARY
+  print *,'--------'
 
+  ! checks options
+  if( it2 == -1 ) it2 = NSTEP
+
   print *
   print *,'looping from ',it1,' to ',it2,' every ',NTSTEP_BETWEEN_FRAMES,' time steps'
 
-! count number of movie frames
+  ! counts number of movie frames
   nframes = 0
   do it = it1,it2
     if(mod(it,NTSTEP_BETWEEN_FRAMES) == 0) nframes = nframes + 1
@@ -246,7 +268,7 @@
   print *,'total number of frames will be ',nframes
   if(nframes == 0) stop 'null number of frames'
 
-! maximum theoretical number of points at the surface
+  ! maximum theoretical number of points at the surface
   if(MOVIE_COARSE) then
     npointot = NCHUNKS * NEX_XI * NEX_ETA
   else
@@ -275,6 +297,23 @@
   if(ierror /= 0) stop 'error while allocating field_display'
 
 
+  ! initializes maxima history
+  if( USE_AVERAGED_MAXIMUM ) then
+    ! determines length of history
+    nmax_history = AVERAGE_MINIMUM + int( HDUR_MOVIE / (DT*NTSTEP_BETWEEN_FRAMES) * 1.5 )
+    
+    ! allocates history array
+    allocate(max_history(nmax_history))
+    max_history(:) = 0.0d0
+
+    print *
+    print *,'Movie half-duration: ',HDUR_MOVIE,'(s)'
+    print *,'Frame step size    : ',DT*NTSTEP_BETWEEN_FRAMES,'(s)'
+    print *,'Normalization by averaged maxima over ',nmax_history,'snapshots'
+    print *
+  endif
+  print *,'--------'
+
 !--- ****** read data saved by solver ******
 
 ! --------------------------------------
@@ -294,7 +333,7 @@
 
         print *
         print *,'reading snapshot time step ',it,' out of ',NSTEP,' file ',outputname
-        print *
+        !print *
 
         read(IOUT) store_val_x
         read(IOUT) store_val_y
@@ -303,7 +342,7 @@
         read(IOUT) store_val_uy
         read(IOUT) store_val_uz
         close(IOUT)
-        print *, 'finished reading ',outputname
+        !print *, 'finished reading ',outputname
         ! clear number of elements kept
         ispec = 0
 
@@ -380,9 +419,9 @@
                       ieoff = (ielm+(i-1)+(j-1)*(NGLLX-1))+1
                     endif
 
-! Daniel: for movie_coarse e.g. x(i,j) is defined at x(1,1), x(1,NGLLY), x(NGLLX,1) and x(NGLLX,NGLLY)
-!         be aware that for the cubed sphere, the mapping changes for different chunks,
-!         i.e. e.g. x(1,1) and x(5,5) flip left and right sides of the elements in geographical coordinates
+! for movie_coarse e.g. x(i,j) is defined at x(1,1), x(1,NGLLY), x(NGLLX,1) and x(NGLLX,NGLLY)
+! be aware that for the cubed sphere, the mapping changes for different chunks,
+! i.e. e.g. x(1,1) and x(5,5) flip left and right sides of the elements in geographical coordinates
                     if(MOVIE_COARSE) then
                       if(NCHUNKS == 6) then
                         ! chunks mapped such that element corners increase in long/lat
@@ -448,17 +487,52 @@
         print *
         print *,'minimum amplitude in current snapshot = ',min_field_current
         print *,'maximum amplitude in current snapshot = ',max_field_current
-        print *
 
-        ! make sure range is always symmetric and center is in zero
-        ! this assumption works only for fields that can be negative
-        ! would not work for norm of vector for instance
-        ! (we would lose half of the color palette if no negative values)
-        max_absol = max(abs(min_field_current),abs(max_field_current))
-        min_field_current = - max_absol
-        max_field_current = + max_absol
+        ! takes average over last few snapshots available and uses it
+        ! to normalize field values
+        if( USE_AVERAGED_MAXIMUM ) then
+        
+          ! make sure range is always symmetric and center is in zero
+          ! this assumption works only for fields that can be negative
+          ! would not work for norm of vector for instance
+          ! (we would lose half of the color palette if no negative values)
+          max_absol = max(abs(min_field_current),abs(max_field_current))
+        
+          ! index between 1 and nmax_history
+          imax = mod(iframe-1,nmax_history) + 1        
+        
+          ! stores last few maxima
+          max_history( imax ) = max_absol
+        
+          ! average over history 
+          max_average = sum( max_history )
+          if( iframe < nmax_history ) then
+            ! history not filled yet, only average over available entries
+            max_average = max_average / iframe
+          else
+            ! average over all history entries
+            max_average = max_average / nmax_history        
+          endif
 
+          print *,'maximum amplitude over averaged last snapshots = ',max_average
 
+          ! thresholds positive & negative maximum values
+          if( max_field_current > max_average ) then
+            where( field_display(:) > max_average ) field_display = max_average          
+          endif
+          if( min_field_current < - max_average ) then          
+            where( field_display(:) < - max_average ) field_display = -max_average
+          endif
+          
+          ! scales field values up to maximum when too small
+          if( max_absol < max_average .and. max_absol > TINYVAL) &
+            field_display = field_display * max_average / max_absol 
+                     
+          ! normalizes field values
+          if( max_average > TINYVAL ) field_display = field_display / max_average
+          
+        endif
+
         print *
         print *,'initial number of points (with multiples) was ',npointot
         print *,'final number of points is                     ',ieoff
@@ -466,27 +540,27 @@
         !--- ****** create GMT file ******
 
         ! create file name and open file
-      if(OUTPUT_BINARY) then
-        if(USE_COMPONENT == 1) then
+        if(OUTPUT_BINARY) then
+          if(USE_COMPONENT == 1) then
            write(outputname,"('bin_movie_',i6.6,'.d')") it
-        elseif(USE_COMPONENT == 2) then
+          elseif(USE_COMPONENT == 2) then
            write(outputname,"('bin_movie_',i6.6,'.N')") it
-        elseif(USE_COMPONENT == 3) then
+          elseif(USE_COMPONENT == 3) then
            write(outputname,"('bin_movie_',i6.6,'.E')") it
-        endif
-        open(unit=11,file='OUTPUT_FILES/'//trim(outputname),status='unknown',form='unformatted')
-        if(iframe == 1) open(unit=12,file='OUTPUT_FILES/bin_movie.xy',status='unknown',form='unformatted')
-       else
-        if(USE_COMPONENT == 1) then
+          endif
+          open(unit=11,file='OUTPUT_FILES/'//trim(outputname),status='unknown',form='unformatted')
+          if(iframe == 1) open(unit=12,file='OUTPUT_FILES/bin_movie.xy',status='unknown',form='unformatted')
+        else
+          if(USE_COMPONENT == 1) then
            write(outputname,"('ascii_movie_',i6.6,'.d')") it
-        elseif(USE_COMPONENT == 2) then
+          elseif(USE_COMPONENT == 2) then
            write(outputname,"('ascii_movie_',i6.6,'.N')") it
-        elseif(USE_COMPONENT == 3) then
+          elseif(USE_COMPONENT == 3) then
            write(outputname,"('ascii_movie_',i6.6,'.E')") it
+          endif
+          open(unit=11,file='OUTPUT_FILES/'//trim(outputname),status='unknown')
+          if(iframe == 1) open(unit=12,file='OUTPUT_FILES/ascii_movie.xy',status='unknown')
         endif
-        open(unit=11,file='OUTPUT_FILES/'//trim(outputname),status='unknown')
-        if(iframe == 1) open(unit=12,file='OUTPUT_FILES/ascii_movie.xy',status='unknown')
-       endif
         ! clear number of elements kept
         ispec = 0
 
@@ -494,41 +568,53 @@
         print *,'Writing output',outputname
         do iproc = 0,NPROCTOT-1
 
-           ! reset point number
-           ipoin = 0
+          ! reset point number
+          ipoin = 0
 
-           do ispecloc = 1,NEX_PER_PROC_XI*NEX_PER_PROC_ETA
-              ispec = ispec + 1
-              if(MOVIE_COARSE) then
-                ielm = ispec - 1
-              else
-                ielm = (NGLLX-1)*(NGLLY-1)*(ispec-1)
-              endif
-                do j = 1,NGLLY-NIT
-                 do i = 1,NGLLX-NIT
-                    if(MOVIE_COARSE) then
-                     ieoff = ielm + 1
-                    else
-                     ieoff = (ielm+(i-1)+(j-1)*(NGLLX-1))+1
-                    endif
-                    xcoord = sngl(xp(ieoff))
-                    ycoord = sngl(yp(ieoff))
-                    zcoord = sngl(zp(ieoff))
-                    call xyz_2_rthetaphi(xcoord,ycoord,zcoord,rval,thetaval,phival)
-                    lat = sngl((PI/2.0-thetaval)*180.0/PI)
-                    long = sngl(phival*180.0/PI)
-                    disp = sngl(field_display(ieoff))
-                   if(long > 180.0) long = long-360.0
-                    if(OUTPUT_BINARY) then
-                     write(11) disp
-                    if(iframe == 1) write(12) long,lat
-                    else
-                     write(11,*) disp
-                     if(iframe == 1) write(12,*) long,lat
-                    endif
-                 enddo !i
-              enddo !j
-           enddo !ispecloc
+          do ispecloc = 1,NEX_PER_PROC_XI*NEX_PER_PROC_ETA
+            ispec = ispec + 1
+            if(MOVIE_COARSE) then
+              ielm = ispec - 1
+            else
+              ielm = (NGLLX-1)*(NGLLY-1)*(ispec-1)
+            endif
+            
+            do j = 1,NGLLY-NIT
+              do i = 1,NGLLX-NIT
+                if(MOVIE_COARSE) then
+                  ieoff = ielm + 1
+                else
+                  ieoff = (ielm+(i-1)+(j-1)*(NGLLX-1))+1
+                endif
+                
+                ! point position
+                if(iframe == 1) then
+                  xcoord = sngl(xp(ieoff))
+                  ycoord = sngl(yp(ieoff))
+                  zcoord = sngl(zp(ieoff))
+                
+                  ! location latitude/longitude
+                  call xyz_2_rthetaphi(xcoord,ycoord,zcoord,rval,thetaval,phival)
+                  lat = sngl((PI/2.0-thetaval)*180.0/PI)
+                  long = sngl(phival*180.0/PI)
+                  if(long > 180.0) long = long-360.0
+                endif
+                
+                ! displacement
+                disp = sngl(field_display(ieoff))
+                
+                ! writes displacement and latitude/longitude to corresponding files
+                if(OUTPUT_BINARY) then
+                  write(11) disp
+                  if(iframe == 1) write(12) long,lat
+                else
+                  write(11,*) disp
+                  if(iframe == 1) write(12,*) long,lat
+                endif
+                
+              enddo !i
+            enddo !j
+          enddo !ispecloc
         enddo !iproc
         close(11)
         if(iframe == 1) close(12)

Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/initialize_simulation.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/initialize_simulation.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/initialize_simulation.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -148,11 +148,8 @@
     ATTENUATION,ATTENUATION_3D,ROTATION,ELLIPTICITY,GRAVITY,CASE_3D,ISOTROPIC_3D_MANTLE, &
     HETEROGEN_3D_MANTLE,CRUSTAL,INFLATE_CENTRAL_CUBE
   character(len=150) :: MODEL,dummystring
-  ! if running on MareNostrum in Barcelona
-  character(len=400) :: system_command
   integer, external :: err_occurred
 
-
   ! sizeprocs returns number of processes started (should be equal to NPROCTOT).
   ! myrank is the rank of each process, between 0 and sizeprocs-1.
   ! as usual in MPI, process 0 is in charge of coordinating everything
@@ -237,22 +234,6 @@
                 ISOTROPIC_3D_MANTLE,ANISOTROPIC_3D_MANTLE,HETEROGEN_3D_MANTLE, &
                 ATTENUATION,ATTENUATION_3D,ANISOTROPIC_INNER_CORE)
 
-  ! if running on MareNostrum in Barcelona
-  if(RUN_ON_MARENOSTRUM_BARCELONA) then
-
-    ! check that we combine the seismograms in one large file to avoid GPFS overloading
-    if(.not. SAVE_ALL_SEISMOS_IN_ONE_FILE) &
-      call exit_MPI(myrank,'should use SAVE_ALL_SEISMOS_IN_ONE_FILE for GPFS in Barcelona')
-
-    ! use the local scratch disk to save all the files, ignore the path that is given in the Par_file
-    LOCAL_PATH = '/scratch/komatits_new'
-
-    ! add processor name to local /scratch/komatits_new path
-    write(system_command,"('_proc',i4.4)") myrank
-    LOCAL_PATH = trim(LOCAL_PATH) // trim(system_command)
-
-  endif
-
   ! get the base pathname for output files
   call get_value_string(OUTPUT_FILES, 'OUTPUT_FILES', 'OUTPUT_FILES')
 

Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/meshfem3D.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/meshfem3D.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/meshfem3D.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -351,11 +351,6 @@
                NGLOB2DMAX_XMIN_XMAX,NGLOB2DMAX_YMIN_YMAX, &
                NGLOB
 
-! DK DK UGLY if running on MareNostrum in Barcelona
-  integer :: sender, receiver, dummy1, dummy2
-  integer msg_status(MPI_STATUS_SIZE)
-  character(len=400) system_command
-
 ! computed in read_compute_parameters
   integer, dimension(MAX_NUMBER_OF_MESH_LAYERS) :: ner,ratio_sampling_array
   integer, dimension(MAX_NUMBER_OF_MESH_LAYERS) :: doubling_index
@@ -564,45 +559,6 @@
   ANGULAR_WIDTH_ETA_RAD = ANGULAR_WIDTH_ETA_IN_DEGREES * PI / 180.d0
   if(NCHUNKS /= 6) call euler_angles(rotation_matrix,CENTER_LONGITUDE_IN_DEGREES,CENTER_LATITUDE_IN_DEGREES,GAMMA_ROTATION_AZIMUTH)
 
-
-! DK DK UGLY if running on MareNostrum in Barcelona
-  if(RUN_ON_MARENOSTRUM_BARCELONA) then
-
-    ! check that we combine the seismograms in one large file to avoid GPFS overloading
-    if(.not. SAVE_ALL_SEISMOS_IN_ONE_FILE) call exit_MPI(myrank,'should use SAVE_ALL_SEISMOS_IN_ONE_FILE for GPFS in Barcelona')
-
-    ! clean the local scratch space using a cascade (serial removal, one process after the other)
-    if(myrank == 0) then
-
-      receiver = myrank + 1
-      call system('rm -f -r /scratch/komatits_new* > /dev/null')
-      call MPI_SEND(dummy1,1,MPI_INTEGER,receiver,itag,MPI_COMM_WORLD,ier)
-
-    else
-
-      sender = myrank - 1
-      receiver = myrank + 1
-      call MPI_RECV(dummy2,1,MPI_INTEGER,sender,itag,MPI_COMM_WORLD,msg_status,ier)
-      call system('rm -f -r /scratch/komatits_new* > /dev/null')
-      if(myrank < sizeprocs - 1) call MPI_SEND(dummy1,1,MPI_INTEGER,receiver,itag,MPI_COMM_WORLD,ier)
-
-    endif
-
-    call MPI_BARRIER(MPI_COMM_WORLD,ier)
-
-    ! use the local scratch disk to save all the files, ignore the path that is given in the Par_file
-    LOCAL_PATH = '/scratch/komatits_new'
-
-    ! add processor name to local /scratch/komatits_new path
-    write(system_command,"('_proc',i4.4)") myrank
-    LOCAL_PATH = trim(LOCAL_PATH) // trim(system_command)
-
-    ! create a local directory to store all the local files
-    write(system_command,"('mkdir /scratch/komatits_new_proc',i4.4)") myrank
-    call system(system_command)
-
-  endif
-
   ! dynamic allocation of mesh arrays
   allocate(addressing(NCHUNKS,0:NPROC_XI-1,0:NPROC_ETA-1))
   allocate(ichunk_slice(0:NPROCTOT-1))

Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/save_header_file.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/save_header_file.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/save_header_file.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -256,9 +256,7 @@
   write(IOUT,*) '!'
   write(IOUT,*) '! size of static arrays per slice = ',static_memory_size/1073741824.d0,' GB'
   write(IOUT,*) '!'
-  write(IOUT,*) '!   (should be below and typically equal to 80% of 1.5 GB = 1.2 GB on pangu'
-  write(IOUT,*) '!    at Caltech, and below and typically equal to 85% of 2 GB = 1.7 GB'
-  write(IOUT,*) '!    on Marenostrum in Barcelona)'
+  write(IOUT,*) '!   (should be below and typically equal to 80% or 90% of the memory installed per core)'
   write(IOUT,*) '!   (if significantly more, the job will not run by lack of memory)'
   write(IOUT,*) '!   (if significantly less, you waste a significant amount of memory)'
   write(IOUT,*) '!'

Modified: seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/specfem3D.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/specfem3D.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/tags/v5.0.0/specfem3D.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -752,10 +752,6 @@
 
   integer i,ier
 
-  ! if running on MareNostrum in Barcelona
-  character(len=400) system_command
-
-
 ! ************** PROGRAM STARTS HERE **************
 !
 !-------------------------------------------------------------------------------------------------
@@ -3156,19 +3152,6 @@
                                 nu_source,moment_der,sloc_der,number_receiver_global)
   endif
 
-
-  ! if running on MareNostrum in Barcelona
-  if(RUN_ON_MARENOSTRUM_BARCELONA) then
-
-  ! synchronize all the processes to make sure everybody has finished
-    call MPI_BARRIER(MPI_COMM_WORLD,ier)
-
-  ! suppress the local directory to leave space for future runs with a different rank number
-    write(system_command,"('rm -r -f /scratch/komatits_new_proc',i4.4)") myrank
-    call system(system_command)
-
-  endif
-
   ! close the main output file
   if(myrank == 0) then
     write(IMAIN,*)
@@ -3183,15 +3166,12 @@
   ! stop all the MPI processes, and exit
   call MPI_FINALIZE(ier)
 
-
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
-!
 
-
   end program xspecfem3D
 

Modified: seismo/3D/SPECFEM3D_GLOBE/trunk/constants.h.in
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/constants.h.in	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/constants.h.in	2010-03-04 21:57:19 UTC (rev 16384)
@@ -217,11 +217,6 @@
 ! can be useful for benchmarks of a spherical Earth with fictitious sources and stations
   logical, parameter :: ASSUME_PERFECT_SPHERE = .false.
 
-!! DK DK UGLY added this in case we are running on MareNostrum in Barcelona
-!! DK DK UGLY because we then need some calls to the system to use GPFS
-  logical, parameter :: RUN_ON_MARENOSTRUM_BARCELONA = .false.
-
-
 !------------------------------------------------------
 !----------- do not modify anything below -------------
 !------------------------------------------------------

Modified: seismo/3D/SPECFEM3D_GLOBE/trunk/create_header_file.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/create_header_file.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/create_header_file.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -226,9 +226,7 @@
   print *
   print *,'size of static arrays per slice = ',static_memory_size/1073741824.d0,' GB'
   print *
-  print *,'   (should be below and typically equal to 80% of 1.5 GB = 1.2 GB on pangu'
-  print *,'    at Caltech, and below and typically equal to 85% of 2 GB = 1.7 GB'
-  print *,'    on Marenostrum in Barcelona)'
+  print *,'   (should be below and typically equal to 80% or 90% of the memory installed per core)'
   print *,'   (if significantly more, the job will not run by lack of memory)'
   print *,'   (if significantly less, you waste a significant amount of memory)'
   print *

Modified: seismo/3D/SPECFEM3D_GLOBE/trunk/initialize_simulation.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/initialize_simulation.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/initialize_simulation.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -148,11 +148,8 @@
     ATTENUATION,ATTENUATION_3D,ROTATION,ELLIPTICITY,GRAVITY,CASE_3D,ISOTROPIC_3D_MANTLE, &
     HETEROGEN_3D_MANTLE,CRUSTAL,INFLATE_CENTRAL_CUBE
   character(len=150) :: MODEL,dummystring
-  ! if running on MareNostrum in Barcelona
-  character(len=400) :: system_command
   integer, external :: err_occurred
 
-
   ! sizeprocs returns number of processes started (should be equal to NPROCTOT).
   ! myrank is the rank of each process, between 0 and sizeprocs-1.
   ! as usual in MPI, process 0 is in charge of coordinating everything
@@ -237,22 +234,6 @@
                 ISOTROPIC_3D_MANTLE,ANISOTROPIC_3D_MANTLE,HETEROGEN_3D_MANTLE, &
                 ATTENUATION,ATTENUATION_3D,ANISOTROPIC_INNER_CORE)
 
-  ! if running on MareNostrum in Barcelona
-  if(RUN_ON_MARENOSTRUM_BARCELONA) then
-
-    ! check that we combine the seismograms in one large file to avoid GPFS overloading
-    if(.not. SAVE_ALL_SEISMOS_IN_ONE_FILE) &
-      call exit_MPI(myrank,'should use SAVE_ALL_SEISMOS_IN_ONE_FILE for GPFS in Barcelona')
-
-    ! use the local scratch disk to save all the files, ignore the path that is given in the Par_file
-    LOCAL_PATH = '/scratch/komatits_new'
-
-    ! add processor name to local /scratch/komatits_new path
-    write(system_command,"('_proc',i4.4)") myrank
-    LOCAL_PATH = trim(LOCAL_PATH) // trim(system_command)
-
-  endif
-
   ! get the base pathname for output files
   call get_value_string(OUTPUT_FILES, 'OUTPUT_FILES', 'OUTPUT_FILES')
 

Modified: seismo/3D/SPECFEM3D_GLOBE/trunk/meshfem3D.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/meshfem3D.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/meshfem3D.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -351,11 +351,6 @@
                NGLOB2DMAX_XMIN_XMAX,NGLOB2DMAX_YMIN_YMAX, &
                NGLOB
 
-! DK DK UGLY if running on MareNostrum in Barcelona
-  integer :: sender, receiver, dummy1, dummy2
-  integer msg_status(MPI_STATUS_SIZE)
-  character(len=400) system_command
-
 ! computed in read_compute_parameters
   integer, dimension(MAX_NUMBER_OF_MESH_LAYERS) :: ner,ratio_sampling_array
   integer, dimension(MAX_NUMBER_OF_MESH_LAYERS) :: doubling_index
@@ -564,45 +559,6 @@
   ANGULAR_WIDTH_ETA_RAD = ANGULAR_WIDTH_ETA_IN_DEGREES * PI / 180.d0
   if(NCHUNKS /= 6) call euler_angles(rotation_matrix,CENTER_LONGITUDE_IN_DEGREES,CENTER_LATITUDE_IN_DEGREES,GAMMA_ROTATION_AZIMUTH)
 
-
-! DK DK UGLY if running on MareNostrum in Barcelona
-  if(RUN_ON_MARENOSTRUM_BARCELONA) then
-
-    ! check that we combine the seismograms in one large file to avoid GPFS overloading
-    if(.not. SAVE_ALL_SEISMOS_IN_ONE_FILE) call exit_MPI(myrank,'should use SAVE_ALL_SEISMOS_IN_ONE_FILE for GPFS in Barcelona')
-
-    ! clean the local scratch space using a cascade (serial removal, one process after the other)
-    if(myrank == 0) then
-
-      receiver = myrank + 1
-      call system('rm -f -r /scratch/komatits_new* > /dev/null')
-      call MPI_SEND(dummy1,1,MPI_INTEGER,receiver,itag,MPI_COMM_WORLD,ier)
-
-    else
-
-      sender = myrank - 1
-      receiver = myrank + 1
-      call MPI_RECV(dummy2,1,MPI_INTEGER,sender,itag,MPI_COMM_WORLD,msg_status,ier)
-      call system('rm -f -r /scratch/komatits_new* > /dev/null')
-      if(myrank < sizeprocs - 1) call MPI_SEND(dummy1,1,MPI_INTEGER,receiver,itag,MPI_COMM_WORLD,ier)
-
-    endif
-
-    call MPI_BARRIER(MPI_COMM_WORLD,ier)
-
-    ! use the local scratch disk to save all the files, ignore the path that is given in the Par_file
-    LOCAL_PATH = '/scratch/komatits_new'
-
-    ! add processor name to local /scratch/komatits_new path
-    write(system_command,"('_proc',i4.4)") myrank
-    LOCAL_PATH = trim(LOCAL_PATH) // trim(system_command)
-
-    ! create a local directory to store all the local files
-    write(system_command,"('mkdir /scratch/komatits_new_proc',i4.4)") myrank
-    call system(system_command)
-
-  endif
-
   ! dynamic allocation of mesh arrays
   allocate(addressing(NCHUNKS,0:NPROC_XI-1,0:NPROC_ETA-1))
   allocate(ichunk_slice(0:NPROCTOT-1))

Modified: seismo/3D/SPECFEM3D_GLOBE/trunk/save_header_file.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/save_header_file.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/save_header_file.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -256,9 +256,7 @@
   write(IOUT,*) '!'
   write(IOUT,*) '! size of static arrays per slice = ',static_memory_size/1073741824.d0,' GB'
   write(IOUT,*) '!'
-  write(IOUT,*) '!   (should be below and typically equal to 80% of 1.5 GB = 1.2 GB on pangu'
-  write(IOUT,*) '!    at Caltech, and below and typically equal to 85% of 2 GB = 1.7 GB'
-  write(IOUT,*) '!    on Marenostrum in Barcelona)'
+  write(IOUT,*) '!   (should be below and typically equal to 80% or 90% of the memory installed per core)'
   write(IOUT,*) '!   (if significantly more, the job will not run by lack of memory)'
   write(IOUT,*) '!   (if significantly less, you waste a significant amount of memory)'
   write(IOUT,*) '!'

Modified: seismo/3D/SPECFEM3D_GLOBE/trunk/specfem3D.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/specfem3D.f90	2010-03-04 21:17:11 UTC (rev 16383)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/specfem3D.f90	2010-03-04 21:57:19 UTC (rev 16384)
@@ -752,10 +752,6 @@
 
   integer i,ier
 
-  ! if running on MareNostrum in Barcelona
-  character(len=400) system_command
-
-
 ! ************** PROGRAM STARTS HERE **************
 !
 !-------------------------------------------------------------------------------------------------
@@ -3156,19 +3152,6 @@
                                 nu_source,moment_der,sloc_der,number_receiver_global)
   endif
 
-
-  ! if running on MareNostrum in Barcelona
-  if(RUN_ON_MARENOSTRUM_BARCELONA) then
-
-  ! synchronize all the processes to make sure everybody has finished
-    call MPI_BARRIER(MPI_COMM_WORLD,ier)
-
-  ! suppress the local directory to leave space for future runs with a different rank number
-    write(system_command,"('rm -r -f /scratch/komatits_new_proc',i4.4)") myrank
-    call system(system_command)
-
-  endif
-
   ! close the main output file
   if(myrank == 0) then
     write(IMAIN,*)
@@ -3183,15 +3166,12 @@
   ! stop all the MPI processes, and exit
   call MPI_FINALIZE(ier)
 
-
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
 !-------------------------------------------------------------------------------------------------
-!
 
-
   end program xspecfem3D
 



More information about the CIG-COMMITS mailing list