[cig-commits] r22987 - in seismo/3D/SPECFEM3D_GLOBE/trunk: . src/auxiliaries

lefebvre at geodynamics.org lefebvre at geodynamics.org
Thu Jan 2 08:00:57 PST 2014


Author: lefebvre
Date: 2014-01-02 08:00:57 -0800 (Thu, 02 Jan 2014)
New Revision: 22987

Added:
   seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/combine_vol_data_adios_impl.f90
Modified:
   seismo/3D/SPECFEM3D_GLOBE/trunk/Makefile.in
   seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/combine_vol_data.F90
   seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/rules.mk
Log:
combine vol data w/ conditional compilation for vtk and/or adios.

Modified: seismo/3D/SPECFEM3D_GLOBE/trunk/Makefile.in
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/Makefile.in	2014-01-02 16:00:49 UTC (rev 22986)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/Makefile.in	2014-01-02 16:00:57 UTC (rev 22987)
@@ -218,6 +218,7 @@
 	@echo "    xcompute_optimized_dumping_undo_att"
 	@echo "    xcombine_vol_data"
 	@echo "    xcombine_vol_data_vtk"
+	@echo "    xcombine_vol_data_adios"
 	@echo "    xcombine_surf_data"
 	@echo "    xcombine_AVS_DX"
 	@echo "    xconvolve_source_timefunction"

Modified: seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/combine_vol_data.F90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/combine_vol_data.F90	2014-01-02 16:00:49 UTC (rev 22986)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/combine_vol_data.F90	2014-01-02 16:00:57 UTC (rev 22987)
@@ -30,6 +30,11 @@
 
   ! combines the database files on several slices.
   ! the local database file needs to have been collected onto the frontend (copy_local_database.pl)
+#ifdef ADIOS_INPUT
+  use mpi
+  use adios_read_mod
+  use combine_vol_data_adios_mod
+#endif
 
   use constants
 
@@ -93,9 +98,30 @@
   real,dimension(:,:),allocatable :: total_dat_xyz
   integer,dimension(:,:),allocatable :: total_dat_con
 #endif
+
+#if ADIOS_INPUT
+  integer :: sizeprocs, ierr, mpier
+  character(len=256) :: var_name, value_file_name, mesh_file_name
+  integer(kind=8) :: value_handle, mesh_handle
+
+#endif
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 
-  ! starts here--------------------------------------------------------------------------------------------------
+  ! starts here---------------------------------------------------------------
+#ifdef ADIOS_INPUT
+  call MPI_Init(ierr)
+  call MPI_Comm_size(MPI_COMM_WORLD, sizeprocs, ierr)
+  print  *, sizeprocs, "procs"
+  if (sizeprocs .ne. 1) then
+    print *, "sequential program. Only mpirun -np 1 ..."
+    call MPI_Abort(MPI_COMM_WORLD, mpier, ierr)  
+  endif
+#endif
+
+  if (NSPEC_CRUST_MANTLE < NSPEC_OUTER_CORE .or. NSPEC_CRUST_MANTLE < NSPEC_INNER_CORE) &
+             stop 'This program needs that NSPEC_CRUST_MANTLE > NSPEC_OUTER_CORE and NSPEC_INNER_CORE'
+
+#ifndef ADIOS_INPUT
   do i = 1, 7
     call get_command_argument(i,arg(i))
     if (i < 7 .and. len_trim(arg(i)) == 0) then
@@ -112,9 +138,6 @@
     endif
   enddo
 
-  if (NSPEC_CRUST_MANTLE < NSPEC_OUTER_CORE .or. NSPEC_CRUST_MANTLE < NSPEC_INNER_CORE) &
-             stop 'This program needs that NSPEC_CRUST_MANTLE > NSPEC_OUTER_CORE and NSPEC_INNER_CORE'
-
   ! get region id
   if (len_trim(arg(7)) == 0) then
     iregion  = 0
@@ -161,6 +184,18 @@
 
   ! resolution
   read(arg(6),*) ires
+#else
+  do i = 1, 7
+    call get_command_argument(i,arg(i))
+  enddo
+  call read_args_adios(arg, MAX_NUM_NODES, node_list, num_node,   &
+                       var_name, value_file_name, mesh_file_name, &
+                       outdir, ires, irs, ire)
+  filename = var_name
+#endif
+print *, irs, ire
+!stop
+
   di = 0
   dj = 0
   dk = 0
@@ -189,6 +224,9 @@
   ! sets up ellipticity splines in order to remove ellipticity from point coordinates
   if( CORRECT_ELLIPTICITY ) call make_ellipticity(nspl,rspl,espl,espl2,ONE_CRUST)
 
+#ifdef ADIOS_INPUT
+  call init_adios(value_file_name, mesh_file_name, value_handle, mesh_handle)
+#endif
 
   do ir = irs, ire
     print *, '----------- Region ', ir, '----------------'
@@ -212,10 +250,10 @@
       iproc = node_list(it)
 
       print *, 'Reading slice ', iproc
+#ifndef ADIOS_INPUT
       write(prname_topo,'(a,i6.6,a,i1,a)') trim(in_topo_dir)//'/proc',iproc,'_reg',ir,'_'
       write(prname_file,'(a,i6.6,a,i1,a)') trim(in_file_dir)//'/proc',iproc,'_reg',ir,'_'
 
-
       dimension_file = trim(prname_topo) //'solver_data.bin'
       open(unit = 27,file = trim(dimension_file),status='old',action='read', iostat = ios, form='unformatted')
       if (ios /= 0) then
@@ -226,6 +264,10 @@
       read(27) nspec(it)
       read(27) nglob(it)
       close(27)
+#else
+      call read_scalars_adios_mesh(mesh_handle, iproc, ir, &
+                                   nglob(it), nspec(it))
+#endif
 
       ! check
       if( nspec(it) > NSPEC_CRUST_MANTLE ) stop 'error file nspec too big, please check compilation'
@@ -287,6 +329,7 @@
 
       print *, ' '
       print *, 'Reading slice ', iproc
+#ifndef ADIOS_INPUT
       write(prname_topo,'(a,i6.6,a,i1,a)') trim(in_topo_dir)//'/proc',iproc,'_reg',ir,'_'
       write(prname_file,'(a,i6.6,a,i1,a)') trim(in_file_dir)//'/proc',iproc,'_reg',ir,'_'
 
@@ -305,12 +348,16 @@
         stop 'error reading data'
       endif
       close(27)
+#else
+    call read_values_adios(value_handle, var_name, iproc, ir, nspec(it), data)
+#endif
 
       print *,trim(data_file)
       print *,'  min/max value: ',minval(data(:,:,:,1:nspec(it))),maxval(data(:,:,:,1:nspec(it)))
       print *
 
       ! topology file
+#ifndef ADIOS_INPUT      
       topo_file = trim(prname_topo) // 'solver_data.bin'
       open(unit = 28,file = trim(topo_file),status='old',action='read', iostat = ios, form='unformatted')
       if (ios /= 0) then
@@ -330,10 +377,14 @@
       read(28) ibool(:,:,:,1:nspec(it))
       if (ir==3) read(28) idoubling_inner_core(1:nspec(it)) ! flag that can indicate fictitious elements
       close(28)
+#else
+      call read_coordinates_adios_mesh(mesh_handle, iproc, ir, &
+                                       nglob(it), nspec(it),   &
+                                       xstore, ystore, zstore, ibool)
+#endif
 
       print *, trim(topo_file)
 
-
       !average data on global points
       ibool_count(:) = 0
       ibool_dat(:) = 0.0
@@ -619,6 +670,12 @@
 #endif
   enddo
 
+#ifdef ADIOS_INPUT
+  call clean_adios(value_handle, mesh_handle)
+  call MPI_Finalize(ierr)
+#endif
+
+
   print *, 'Done writing mesh files'
   print *, ' '
 

Added: seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/combine_vol_data_adios_impl.f90
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/combine_vol_data_adios_impl.f90	                        (rev 0)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/combine_vol_data_adios_impl.f90	2014-01-02 16:00:57 UTC (rev 22987)
@@ -0,0 +1,232 @@
+
+module combine_vol_data_adios_mod
+  use mpi
+  use adios_read_mod
+  implicit none
+contains
+
+!=============================================================================
+!> Print help message. 
+subroutine print_usage_adios()
+  print *, 'Usage: '
+  print *, '   xcombine_data slice_list varname var_file mesh_file ' // &
+           'output_dir high/low-resolution region'
+  print *
+  print *, '* possible varnames are '
+  print *, '   rho, rho, kappastore, mustore, alpha_kernel, etc'
+  print *
+  print *, '   that are stored in the local directory as ' // &
+           'real(kind=CUSTOM_REAL) varname(NGLLX,NGLLY,NGLLZ,NSPEC)  '
+  print *, '   in var_file.bp'
+  print *
+  print *, '* mesh_files are used to link variable to the topology'
+  print *, '* output_dir indicates where var_name.vtk will be written'
+  print *, '* give 0 for low resolution and 1 for high resolution'
+  print *
+
+  stop ' Reenter command line options'
+end subroutine print_usage_adios
+
+!=============================================================================
+!> Interpret command line arguments
+subroutine read_args_adios(arg, MAX_NUM_NODES, node_list, num_node,   &
+                           var_name, value_file_name, mesh_file_name, &
+                           outdir, ires, irs, ire)
+  implicit none
+  ! Arguments
+  character(len=*), intent(in) :: arg(:)
+  integer, intent(in) :: MAX_NUM_NODES
+  integer, intent(out) :: node_list(:)
+  integer, intent(out) :: num_node, ires, irs, ire
+  character(len=*), intent(out) :: var_name, value_file_name, mesh_file_name, &
+                                   outdir
+  ! Variables
+  character(len=256) :: sline
+  integer :: ios, njunk, iregion
+
+  if ((command_argument_count() == 6) &
+     .or. (command_argument_count() == 7)) then
+    num_node = 0
+    open(unit = 20, file = trim(arg(1)), status = 'unknown',iostat = ios)
+    if (ios /= 0) then
+      print *,'Error opening slice file ',trim(arg(1))
+      stop
+    endif
+    do while ( 1 == 1)
+      read(20,'(a)',iostat=ios) sline
+      if (ios /= 0) exit
+      read(sline,*,iostat=ios) njunk
+      if (ios /= 0) exit
+      num_node = num_node + 1
+      if( num_node > MAX_NUM_NODES ) &
+          stop 'error number of slices exceeds MAX_NUM_NODES...'
+      node_list(num_node) = njunk
+    enddo
+    close(20)
+    var_name = arg(2)
+    value_file_name = arg(3)
+    mesh_file_name = arg(4)
+    outdir = arg(5)
+    read(arg(6),*) ires
+  else
+    call print_usage_adios()
+  endif
+
+  iregion = 0
+  if (command_argument_count() == 7) then 
+    read(arg(7),*) iregion
+  endif
+  if (iregion > 3 .or. iregion < 0) stop 'Iregion = 0,1,2,3'
+  if (iregion == 0) then
+    irs = 1
+    ire = 3
+  else
+    irs = iregion
+    ire = irs
+  endif
+
+end subroutine read_args_adios
+
+
+!=============================================================================
+!> Open ADIOS value and mesh files, read mode 
+subroutine init_adios(value_file_name, mesh_file_name, &
+                      value_handle, mesh_handle)
+  implicit none
+  ! Parameters 
+  character(len=*), intent(in) :: value_file_name, mesh_file_name
+  integer(kind=8), intent(out) :: value_handle, mesh_handle
+  ! Variables
+  integer :: ier
+
+  call adios_read_init_method(ADIOS_READ_METHOD_BP, MPI_COMM_WORLD, &
+                              "verbose=1", ier)
+  call adios_read_open_file(mesh_handle, trim(mesh_file_name), 0, &
+                            MPI_COMM_WORLD, ier)
+  call adios_read_open_file(value_handle, trim(value_file_name), 0, &
+                            MPI_COMM_WORLD, ier)
+end subroutine init_adios
+
+
+!=============================================================================
+!> Open ADIOS value and mesh files, read mode 
+subroutine clean_adios(value_handle, mesh_handle)
+  implicit none
+  ! Parameters 
+  integer(kind=8), intent(in) :: value_handle, mesh_handle
+  ! Variables
+  integer :: ier
+
+  call adios_read_close(mesh_handle,ier)
+  call adios_read_close(value_handle,ier)
+  call adios_read_finalize_method(ADIOS_READ_METHOD_BP, ier)
+end subroutine clean_adios
+
+
+!=============================================================================
+subroutine read_scalars_adios_mesh(mesh_handle, iproc, ir, nglob, nspec)
+  implicit none
+  ! Parameters
+  integer(kind=8), intent(in) :: mesh_handle
+  integer, intent(in) :: iproc, ir
+  integer, intent(out) :: nglob, nspec
+  ! Variables
+  integer(kind=8) :: sel
+  character(len=256) :: reg_name
+  integer :: ier
+
+  write(reg_name, '(a,i1)') trim("reg"), ir
+
+  call adios_selection_writeblock(sel, iproc)
+  call adios_schedule_read(mesh_handle, sel, trim(reg_name) // "/nglob", &
+                           0, 1, nglob, ier)
+  call adios_schedule_read(mesh_handle, sel, trim(reg_name) // "/nspec", &
+                           0, 1, nspec, ier)
+  call adios_perform_reads(mesh_handle, ier) 
+end subroutine read_scalars_adios_mesh
+
+
+!=============================================================================
+subroutine read_coordinates_adios_mesh(mesh_handle, iproc, ir, nglob, nspec, & 
+                                       xstore, ystore, zstore, ibool)
+  implicit none
+  include 'constants.h'
+  ! Parameters
+  integer(kind=8), intent(in) :: mesh_handle
+  integer, intent(in) :: iproc, ir, nglob, nspec 
+  real(kind=CUSTOM_REAL),dimension(:), intent(inout) :: xstore, ystore, zstore
+  integer, dimension(:,:,:,:), intent(inout) :: ibool
+  ! Variables
+  character(len=256) :: reg_name
+  integer(kind=8), dimension(1) :: start, count_ad
+  integer(kind=8) :: sel_coord, sel_ibool, sel_scalar
+  integer :: offset_coord, offset_ibool, ier
+
+  write(reg_name, '(a,i1, a)') trim("reg"), ir, "/"
+
+  call adios_selection_writeblock(sel_scalar, iproc)
+  call adios_schedule_read(mesh_handle, sel_scalar,          &
+                           trim(reg_name) // "ibool/offset", &
+                           0, 1, offset_ibool, ier)
+  call adios_schedule_read(mesh_handle, sel_scalar,             &
+                           trim(reg_name) // "x_global/offset", &
+                           0, 1, offset_coord, ier)
+  call adios_perform_reads(mesh_handle, ier) 
+
+  start(1) = offset_ibool
+  count_ad(1) = NGLLX * NGLLY * NGLLZ * nspec
+  call adios_selection_boundingbox (sel_ibool , 1, start, count_ad)
+  call adios_schedule_read(mesh_handle, sel_ibool, &
+                           trim(reg_name) // "ibool/array", 0, 1, &
+                           ibool, ier)
+
+  start(1) = offset_coord 
+  count_ad(1) = nglob
+  call adios_selection_boundingbox (sel_coord , 1, start, count_ad)
+  call adios_schedule_read(mesh_handle, sel_coord, &
+                           trim(reg_name) // "x_global/array", 0, 1, &
+                           xstore, ier)
+  call adios_schedule_read(mesh_handle, sel_coord, &
+                           trim(reg_name) // "y_global/array", 0, 1, &
+                           ystore, ier)
+  call adios_schedule_read(mesh_handle, sel_coord, &
+                           trim(reg_name) // "z_global/array", 0, 1, &
+                           zstore, ier)
+  call adios_perform_reads(mesh_handle, ier) 
+end subroutine read_coordinates_adios_mesh
+
+
+!=============================================================================
+subroutine read_values_adios(value_handle, var_name, iproc, ir, &
+                             nspec, data)
+  implicit none
+  include 'constants.h'
+  ! Parameters
+  integer(kind=8), intent(in) :: value_handle 
+  character(len=*), intent(in) :: var_name
+  integer, intent(in) :: iproc, ir, nspec
+  real(kind=CUSTOM_REAL), dimension(:,:,:,:), intent(inout) :: data
+  ! Variables
+  character(len=256) :: reg_name
+  integer(kind=8), dimension(1) :: start, count_ad
+  integer(kind=8) :: sel
+  integer :: offset, ier
+
+  write(reg_name, '(a,i1, a)') trim("reg"), ir, "/"
+
+  call adios_selection_writeblock(sel, iproc)
+  call adios_schedule_read(value_handle, sel,                             &
+                           trim(reg_name) // trim(var_name) // "/offset", &
+                           0, 1, offset, ier)
+  call adios_perform_reads(value_handle, ier) 
+
+  start(1) = offset
+  count_ad(1) = NGLLX * NGLLY * NGLLZ * nspec
+  call adios_selection_boundingbox (sel , 1, start, count_ad)
+  call adios_schedule_read(value_handle, sel, &
+                           trim(reg_name) // trim(var_name) // "/array", 0, 1,&
+                           data, ier)
+  call adios_perform_reads(value_handle, ier) 
+end subroutine read_values_adios
+
+end module combine_vol_data_adios_mod

Modified: seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/rules.mk
===================================================================
--- seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/rules.mk	2014-01-02 16:00:49 UTC (rev 22986)
+++ seismo/3D/SPECFEM3D_GLOBE/trunk/src/auxiliaries/rules.mk	2014-01-02 16:00:57 UTC (rev 22987)
@@ -33,6 +33,8 @@
 	$E/xcombine_paraview_strain_data \
 	$E/xcombine_vol_data \
 	$E/xcombine_vol_data_vtk \
+	$E/xcombine_vol_data_adios \
+	$E/xcombine_vol_data_vtk_adios \
 	$E/xcombine_surf_data \
 	$E/xcreate_movie_AVS_DX \
 	$E/xcreate_movie_GMT_global \
@@ -94,6 +96,12 @@
 ${E}/xcombine_vol_data: $(auxiliaries_SHARED_OBJECTS) $O/combine_vol_data.auxsolver.o $O/write_c_binary.cc.o $O/combine_vol_data_shared.aux.o
 	${FCCOMPILE_CHECK} -o ${E}/xcombine_vol_data $(auxiliaries_SHARED_OBJECTS) $O/combine_vol_data.auxsolver.o $O/write_c_binary.cc.o $O/combine_vol_data_shared.aux.o
 
+${E}/xcombine_vol_data_adios: $(auxiliaries_SHARED_OBJECTS) $O/combine_vol_data_adios_impl.auxmpi.o $O/combine_vol_data.auxadios.o $O/write_c_binary.cc.o $O/combine_vol_data_shared.aux.o
+	${MPIFCCOMPILE_CHECK} -o ${E}/xcombine_vol_data_adios $(auxiliaries_SHARED_OBJECTS) $O/combine_vol_data_adios_impl.auxmpi.o $O/combine_vol_data.auxadios.o $O/write_c_binary.cc.o $O/combine_vol_data_shared.aux.o $(MPILIBS)
+
+${E}/xcombine_vol_data_vtk_adios: $(auxiliaries_SHARED_OBJECTS) $O/combine_vol_data_adios_impl.auxmpi.o $O/combine_vol_data.auxadios_vtk.o $O/write_c_binary.cc.o $O/combine_vol_data_shared.aux.o
+	${MPIFCCOMPILE_CHECK} -o ${E}/xcombine_vol_data_vtk_adios $(auxiliaries_SHARED_OBJECTS) $O/combine_vol_data_adios_impl.auxmpi.o $O/combine_vol_data.auxadios_vtk.o $O/write_c_binary.cc.o $O/combine_vol_data_shared.aux.o $(MPILIBS)
+
 ${E}/xcombine_vol_data_vtk: $(auxiliaries_SHARED_OBJECTS) $O/combine_vol_data.auxsolver_vtk.o $O/write_c_binary.cc.o $O/combine_vol_data_shared.aux.o
 	${FCCOMPILE_CHECK} -o ${E}/xcombine_vol_data_vtk $(auxiliaries_SHARED_OBJECTS) $O/combine_vol_data.auxsolver_vtk.o $O/write_c_binary.cc.o $O/combine_vol_data_shared.aux.o
 
@@ -128,8 +136,17 @@
 $O/%.auxsolver.o: $S/%.f90 ${OUTPUT}/values_from_mesher.h $O/shared_par.shared_module.o
 	${FCCOMPILE_CHECK} ${FCFLAGS_f90} -c -o $@ $<
 
+$O/%.auxmpi.o: $S/%.f90 ${OUTPUT}/values_from_mesher.h $O/shared_par.shared_module.o
+	${MPIFCCOMPILE_CHECK} ${FCFLAGS_f90} -c -o $@ $<
+
 $O/%.auxsolver.o: $S/%.F90 ${OUTPUT}/values_from_mesher.h $O/shared_par.shared_module.o
 	${FCCOMPILE_CHECK} ${FCFLAGS_f90} -c -o $@ $<
 
 $O/%.auxsolver_vtk.o: $S/%.F90 ${OUTPUT}/values_from_mesher.h $O/shared_par.shared_module.o
 	${FCCOMPILE_CHECK} ${FCFLAGS_f90} -c -o $@ $< -DUSE_VTK_INSTEAD_OF_MESH
+
+$O/%.auxadios.o: $S/%.F90 ${OUTPUT}/values_from_mesher.h $O/shared_par.shared_module.o
+	${MPIFCCOMPILE_CHECK} ${FCFLAGS_f90} -c -o $@ $< -DADIOS_INPUT
+
+$O/%.auxadios_vtk.o: $S/%.F90 ${OUTPUT}/values_from_mesher.h $O/shared_par.shared_module.o
+	${MPIFCCOMPILE_CHECK} ${FCFLAGS_f90} -c -o $@ $< -DADIOS_INPUT -DUSE_VTK_INSTEAD_OF_MESH



More information about the CIG-COMMITS mailing list