Skip to content

Commit

Permalink
Change control reading level based on depth of files.
Browse files Browse the repository at this point in the history
  • Loading branch information
hiromatsui committed Jun 19, 2023
1 parent 6796024 commit 580a15e
Show file tree
Hide file tree
Showing 19 changed files with 135 additions and 154 deletions.
19 changes: 8 additions & 11 deletions src/Fortran_libraries/MHD_src/IO/t_ctl_data_MHD.f90
Expand Up @@ -109,32 +109,29 @@ module t_ctl_data_MHD
!
! ----------------------------------------------------------------------
!
subroutine read_control_4_sph_MHD_noviz(file_name, MHD_ctl)
subroutine read_control_4_sph_MHD_noviz &
& (file_name, MHD_ctl, c_buf)
!
character(len=kchara), intent(in) :: file_name
type(mhd_simulation_control), intent(inout) :: MHD_ctl
type(buffer_for_control), intent(inout) :: c_buf
!
type(buffer_for_control) :: c_buf1
!
!
c_buf1%level = 0
c_buf%level = c_buf%level + 1
open(id_control_file, file = file_name, status='old' )
!
do
call load_one_line_from_control(id_control_file, hd_mhd_ctl, &
& c_buf1)
if(c_buf1%iend .gt. 0) exit
& c_buf)
if(c_buf%iend .gt. 0) exit
!
call read_sph_mhd_ctl_noviz &
& (id_control_file, hd_mhd_ctl, MHD_ctl, c_buf1)
& (id_control_file, hd_mhd_ctl, MHD_ctl, c_buf)
if(MHD_ctl%i_mhd_ctl .gt. 0) exit
end do
close(id_control_file)
!
if(c_buf1%iend .gt. 0) then
MHD_ctl%i_mhd_ctl = c_buf1%iend
return
end if
c_buf%level = c_buf%level - 1
!
end subroutine read_control_4_sph_MHD_noviz
!
Expand Down
21 changes: 9 additions & 12 deletions src/Fortran_libraries/MHD_src/IO/t_ctl_data_sph_MHD_w_psf.f90
Expand Up @@ -12,7 +12,7 @@
!!
!!@verbatim
!! subroutine read_control_4_sph_MHD_w_psf(file_name, MHD_ctl, &
!! & add_SMHD_ctl)
!! & add_SMHD_ctl, c_buf)
!! subroutine read_sph_mhd_ctl_w_psf(id_control, hd_block, &
!! & MHD_ctl, add_SMHD_ctl, c_buf)
!! character(len=kchara), intent(in) :: file_name
Expand Down Expand Up @@ -104,35 +104,32 @@ module t_ctl_data_sph_MHD_w_psf
! ----------------------------------------------------------------------
!
subroutine read_control_4_sph_MHD_w_psf(file_name, MHD_ctl, &
& add_SMHD_ctl)
& add_SMHD_ctl, c_buf)
!
use t_control_data_surfacings
!
character(len=kchara), intent(in) :: file_name
type(mhd_simulation_control), intent(inout) :: MHD_ctl
type(add_psf_sph_mhd_ctl), intent(inout) :: add_SMHD_ctl
!
type(buffer_for_control) :: c_buf1
type(buffer_for_control), intent(inout) :: c_buf
!
!
c_buf1%level = 0
c_buf%level = c_buf%level + 1
open(id_control_file, file = file_name, status='old' )
!
do
call load_one_line_from_control(id_control_file, hd_mhd_ctl, &
& c_buf1)
if(c_buf1%iend .gt. 0) exit
& c_buf)
if(c_buf%iend .gt. 0) exit
!
call read_sph_mhd_ctl_w_psf(id_control_file, hd_mhd_ctl, &
& MHD_ctl, add_SMHD_ctl, c_buf1)
& MHD_ctl, add_SMHD_ctl, c_buf)
if(MHD_ctl%i_mhd_ctl .gt. 0) exit
end do
close(id_control_file)
!
if(c_buf1%iend .gt. 0) then
MHD_ctl%i_mhd_ctl = c_buf1%iend
return
end if
c_buf%level = c_buf%level - 1
if(c_buf%iend .gt. 0) return
!
call section_step_ctls_to_time_ctl(add_SMHD_ctl%surfacing_ctls, &
& MHD_ctl%smctl_ctl%tctl)
Expand Down
2 changes: 1 addition & 1 deletion src/Fortran_libraries/MHD_src/sph_MHD/Makefile.depends
Expand Up @@ -166,7 +166,7 @@ initial_magne_dbench_qvc.o: $(MHD_SPH_DIR)/initial_magne_dbench_qvc.f90 m_precis
$(F90) -c $(F90OPTFLAGS) $<
initial_magne_dynamobench.o: $(MHD_SPH_DIR)/initial_magne_dynamobench.f90 m_precision.o m_constants.o t_phys_address.o t_spheric_rj_data.o
$(F90) -c $(F90OPTFLAGS) $<
input_control_sph_MHD.o: $(MHD_SPH_DIR)/input_control_sph_MHD.f90 m_precision.o m_machine_parameter.o calypso_mpi.o t_const_spherical_grid.o t_MHD_file_parameter.o t_MHD_step_parameter.o t_SPH_MHD_model_data.o t_SPH_mesh_field_data.o t_FEM_mesh_field_data.o t_control_data_dynamo_sects.o t_rms_4_sph_spectr.o t_file_IO_parameter.o t_sph_boundary_input_data.o t_bc_data_list.o t_flex_delta_t_data.o t_work_SPH_MHD.o t_ctl_data_MHD.o t_ctl_data_sph_MHD_w_psf.o bcast_control_sph_MHD.o bcast_ctl_data_surfacings.o bcast_dynamo_sect_control.o t_time_data.o t_node_monitor_IO.o m_error_IDs.o set_control_sph_mhd.o sph_file_IO_select.o set_control_4_SPH_to_FEM.o parallel_load_data_4_sph.o
input_control_sph_MHD.o: $(MHD_SPH_DIR)/input_control_sph_MHD.f90 m_precision.o m_machine_parameter.o calypso_mpi.o t_const_spherical_grid.o t_MHD_file_parameter.o t_MHD_step_parameter.o t_SPH_MHD_model_data.o t_SPH_mesh_field_data.o t_FEM_mesh_field_data.o t_control_data_dynamo_sects.o t_rms_4_sph_spectr.o t_file_IO_parameter.o t_sph_boundary_input_data.o t_bc_data_list.o t_flex_delta_t_data.o t_work_SPH_MHD.o t_ctl_data_MHD.o t_ctl_data_sph_MHD_w_psf.o t_read_control_elements.o bcast_control_sph_MHD.o bcast_ctl_data_surfacings.o bcast_dynamo_sect_control.o t_time_data.o t_node_monitor_IO.o m_error_IDs.o set_control_sph_mhd.o sph_file_IO_select.o set_control_4_SPH_to_FEM.o parallel_load_data_4_sph.o
$(F90) -c $(F90OPTFLAGS) $<
interact_coriolis_rlm.o: $(MHD_SPH_DIR)/interact_coriolis_rlm.f90 m_precision.o m_constants.o m_machine_parameter.o t_gaunt_coriolis_rlm.o cal_gaunt_itgs.o
$(F90) -c $(F90OPTFLAGS) $<
Expand Down
21 changes: 14 additions & 7 deletions src/Fortran_libraries/MHD_src/sph_MHD/input_control_sph_MHD.f90
Expand Up @@ -71,6 +71,7 @@ subroutine load_control_4_sph_MHD_w_psf(file_name, MHD_ctl, &
!
use t_ctl_data_MHD
use t_ctl_data_sph_MHD_w_psf
use t_read_control_elements
use bcast_control_sph_MHD
use bcast_ctl_data_surfacings
use bcast_dynamo_sect_control
Expand All @@ -79,19 +80,22 @@ subroutine load_control_4_sph_MHD_w_psf(file_name, MHD_ctl, &
type(mhd_simulation_control), intent(inout) :: MHD_ctl
type(add_psf_sph_mhd_ctl), intent(inout) :: add_SMHD_ctl
!
type(buffer_for_control) :: c_buf1
!
!
c_buf1%level = 0
if(my_rank .eq. 0) then
call read_control_4_sph_MHD_w_psf(file_name, MHD_ctl, &
& add_SMHD_ctl)
& add_SMHD_ctl, c_buf1)
end if
!
if(c_buf1%iend .gt. 0) then
call calypso_MPI_abort(MHD_ctl%i_mhd_ctl, trim(file_name))
end if
!
call bcast_sph_mhd_control_data(MHD_ctl)
call bcast_surfacing_controls(add_SMHD_ctl%surfacing_ctls)
call s_bcast_dynamo_section_control(add_SMHD_ctl%zm_sects)
!
if(MHD_ctl%i_mhd_ctl .ne. 1) then
call calypso_MPI_abort(MHD_ctl%i_mhd_ctl, trim(file_name))
end if
!
end subroutine load_control_4_sph_MHD_w_psf
!
Expand All @@ -104,15 +108,18 @@ subroutine load_control_4_sph_MHD_noviz(file_name, MHD_ctl)
!
character(len=kchara), intent(in) :: file_name
type(mhd_simulation_control), intent(inout) :: MHD_ctl
!
type(buffer_for_control) :: c_buf1
!
!
c_buf1%level = 0
if(my_rank .eq. 0) then
call read_control_4_sph_MHD_noviz(file_name, MHD_ctl)
call read_control_4_sph_MHD_noviz(file_name, MHD_ctl, c_buf1)
end if
!
call bcast_sph_mhd_control_data(MHD_ctl)
!
if(MHD_ctl%i_mhd_ctl .le. 0) then
if(c_buf1%level .gt. 0) then
call calypso_MPI_abort(MHD_ctl%i_mhd_ctl, trim(file_name))
end if
!
Expand Down
Expand Up @@ -10,7 +10,7 @@
!! subroutine sel_read_ctl_gen_shell_grids &
!! & (id_control, hd_block, file_name, psph_ctl, c_buf)
!! subroutine read_ctl_file_gen_shell_grids(id_control, file_name, &
!! & hd_block, psph_ctl)
!! & hd_block, psph_ctl, c_buf)
!! integer(kind = kint), intent(in) :: id_control
!! character(len=kchara), intent(in) :: hd_block
!! character(len = kchara), intent(inout) :: file_name
Expand Down Expand Up @@ -100,8 +100,7 @@ subroutine sel_read_ctl_gen_shell_grids &
call write_one_ctl_file_message &
& (hd_block, c_buf%level, file_name)
call read_ctl_file_gen_shell_grids(id_control+2, file_name, &
& hd_block, psph_ctl)
c_buf%iend = psph_ctl%iflag_sph_shell
& hd_block, psph_ctl, c_buf)
else if(check_begin_flag(c_buf, hd_block)) then
file_name = 'NO_FILE'
!
Expand All @@ -115,38 +114,33 @@ end subroutine sel_read_ctl_gen_shell_grids
! --------------------------------------------------------------------
!
subroutine read_ctl_file_gen_shell_grids(id_control, file_name, &
& hd_block, psph_ctl)
& hd_block, psph_ctl, c_buf)
!
integer(kind = kint), intent(in) :: id_control
character(len = kchara), intent(in) :: file_name
character(len=kchara), intent(in) :: hd_block
type(parallel_sph_shell_control), intent(inout) :: psph_ctl
!
type(buffer_for_control) :: c_buf1
type(buffer_for_control), intent(inout) :: c_buf
!
!
c_buf1%level = 0
c_buf%level = c_buf%level + 1
open(id_control, file = file_name)
!
do
if(psph_ctl%iflag_sph_shell .gt. 0) exit
call load_one_line_from_control(id_control, hd_block, c_buf1)
if(c_buf1%iend .gt. 0) exit
if(check_end_flag(c_buf1, hd_block)) exit
call load_one_line_from_control(id_control, hd_block, c_buf)
if(c_buf%iend .gt. 0) exit
if(check_end_flag(c_buf, hd_block)) exit
!
call read_parallel_shell_ctl(id_control, hd_block, &
& psph_ctl, c_buf1)
& psph_ctl, c_buf)
call read_parallel_shell_ctl(id_control, hd_sph_shell, &
& psph_ctl, c_buf1)
& psph_ctl, c_buf)
if(psph_ctl%iflag_sph_shell .gt. 0) exit
end do
!
close(id_control)
!
if(c_buf1%iend .gt. 0) then
psph_ctl%iflag_sph_shell = c_buf1%iend
return
end if
c_buf%level = c_buf%level - 1
!
end subroutine read_ctl_file_gen_shell_grids
!
Expand Down
Expand Up @@ -11,7 +11,8 @@
!!@n Modified by H. Matsui on Oct., 2012
!!
!!@verbatim
!! subroutine read_control_4_const_shell(file_name, gen_SPH_ctl)
!! subroutine read_control_4_const_shell(file_name, &
!! & gen_SPH_ctl, c_buf)
!! character(len=kchara), intent(in) :: file_name
!! type(sph_mesh_generation_ctl), intent(inout) :: gen_SPH_ctl
!! subroutine write_control_4_const_shell(file_name, gen_SPH_ctl)
Expand Down Expand Up @@ -69,33 +70,30 @@ module t_ctl_data_const_sph_mesh
!
! ----------------------------------------------------------------------
!
subroutine read_control_4_const_shell(file_name, gen_SPH_ctl)
subroutine read_control_4_const_shell(file_name, &
& gen_SPH_ctl, c_buf)
!
character(len=kchara), intent(in) :: file_name
type(sph_mesh_generation_ctl), intent(inout) :: gen_SPH_ctl
type(buffer_for_control), intent(inout) :: c_buf
!
type(buffer_for_control) :: c_buf1
!
!
c_buf1%level = 0
c_buf%level = c_buf%level + 1
open(control_file_code, file = file_name, status='old')
!
do
call load_one_line_from_control(control_file_code, hd_mhd_ctl, &
& c_buf1)
if(c_buf1%iend .gt. 0) exit
& c_buf)
if(c_buf%iend .gt. 0) exit
!
call read_sph_shell_define_ctl &
& (control_file_code, hd_mhd_ctl, gen_SPH_ctl, c_buf1)
& (control_file_code, hd_mhd_ctl, gen_SPH_ctl, c_buf)
if(gen_SPH_ctl%i_sph_mesh_ctl .gt. 0) exit
end do
!
close(control_file_code)
!
if(c_buf1%iend .gt. 0) then
gen_SPH_ctl%i_sph_mesh_ctl = c_buf1%iend
return
end if
c_buf%level = c_buf%level - 1
!
end subroutine read_control_4_const_shell
!
Expand Down
20 changes: 4 additions & 16 deletions src/Fortran_libraries/SERIAL_src/IO/t_read_control_elements.f90
Expand Up @@ -145,10 +145,7 @@ logical function check_begin_flag(c_buf, label)
!
check_begin_flag = .FALSE.
if(cmp_no_case(first_word(c_buf), hd_begin)) then
if(cmp_no_case(second_word(c_buf), label)) then
check_begin_flag = .TRUE.
c_buf%level = c_buf%level + 1
end if
check_begin_flag = cmp_no_case(second_word(c_buf), label)
end if
!
end function check_begin_flag
Expand Down Expand Up @@ -182,10 +179,7 @@ logical function check_end_flag(c_buf, label)
!
check_end_flag = .FALSE.
if(cmp_no_case(first_word(c_buf), hd_end)) then
if(cmp_no_case(second_word(c_buf), label)) then
check_end_flag = .TRUE.
c_buf%level = c_buf%level - 1
end if
check_end_flag = cmp_no_case(second_word(c_buf), label)
end if
!
end function check_end_flag
Expand All @@ -210,10 +204,7 @@ logical function check_array_flag(c_buf, label)
if(ntmp .eq. 0) return
!
99 continue
if(cmp_no_case(second_word(c_buf), label)) then
check_array_flag = .TRUE.
c_buf%level = c_buf%level + 1
end if
check_array_flag = cmp_no_case(second_word(c_buf), label)
!
end function check_array_flag
!
Expand All @@ -230,10 +221,7 @@ logical function check_end_array_flag(c_buf, label)
check_end_array_flag = .FALSE.
if(cmp_no_case(first_word(c_buf), hd_end)) then
if(cmp_no_case(second_word(c_buf), hd_array)) then
if(cmp_no_case(third_word(c_buf), label)) then
check_end_array_flag = .TRUE.
c_buf%level = c_buf%level - 1
end if
check_end_array_flag = cmp_no_case(third_word(c_buf), label)
end if
end if
!
Expand Down
Expand Up @@ -187,7 +187,7 @@ subroutine s_read_psf_control_data &
if(check_end_flag(c_buf, hd_block)) exit
!
if(check_file_flag(c_buf, hd_surface_define) &
& .or. check_begin_flag(c_buf, hd_block)) then
& .or. check_begin_flag(c_buf, hd_surface_define)) then
call write_multi_ctl_file_message &
& (hd_surface_define, izero, c_buf%level)
call sel_read_ctl_pvr_section_def(id_control, &
Expand Down
Expand Up @@ -78,9 +78,7 @@ subroutine sel_read_ctl_field_on_psf_file(id_control, hd_block, &
call write_one_ctl_file_message &
& (hd_block, c_buf%level, file_name)
call read_ctl_field_on_psf_file((id_control+2), file_name, &
& hd_block, fld_on_psf_c)
if(fld_on_psf_c%i_iso_result .ne. 1) &
& c_buf%iend = fld_on_psf_c%i_iso_result
& hd_block, fld_on_psf_c, c_buf)
else if(check_begin_flag(c_buf, hd_block)) then
file_name = 'NO_FILE'
!
Expand All @@ -94,7 +92,7 @@ end subroutine sel_read_ctl_field_on_psf_file
! --------------------------------------------------------------------
!
subroutine read_ctl_field_on_psf_file(id_control, file_name, &
& hd_block, fld_on_psf_c)
& hd_block, fld_on_psf_c, c_buf)
!
use t_read_control_elements
!
Expand All @@ -103,24 +101,24 @@ subroutine read_ctl_field_on_psf_file(id_control, file_name, &
character(len = kchara), intent(in) :: file_name
character(len=kchara), intent(in) :: hd_block
type(field_on_psf_ctl), intent(inout) :: fld_on_psf_c
type(buffer_for_control), intent(inout) :: c_buf
!
type(buffer_for_control) :: c_buf1
!
!
c_buf1%level = 0
c_buf%level = c_buf%level + 1
write(*,'(a)') trim(file_name)
open(id_control, file=file_name, status='old')
!
do
call load_one_line_from_control(id_control, hd_block, c_buf1)
if(c_buf1%iend .gt. 0) exit
call load_one_line_from_control(id_control, hd_block, c_buf)
if(c_buf%iend .gt. 0) exit
!
call read_fld_on_psf_control(id_control, hd_block, &
& fld_on_psf_c, c_buf1)
& fld_on_psf_c, c_buf)
if(fld_on_psf_c%i_iso_result .gt. 0) exit
end do
close(id_control)
if(c_buf1%iend .gt. 0) fld_on_psf_c%i_iso_result = c_buf1%iend
!
c_buf%level = c_buf%level - 1
!
end subroutine read_ctl_field_on_psf_file
!
Expand Down

0 comments on commit 580a15e

Please sign in to comment.