77#include "../base/base_uses.f90"
83 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'tmc_setup'
97 SUBROUTINE do_tmc(input_declaration, root_section, para_env, globenv)
103 CHARACTER(LEN=*),
PARAMETER :: routinen =
'do_tmc'
105 INTEGER :: bcast_output_unit, handle, i, ierr, &
107 LOGICAL :: init_rng, success
108 REAL(kind=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: init_rng_seed
116 CALL timeset(routinen, handle)
120 NULLIFY (logger, logger_sub, tmc_env, tmc_ana_env_list)
125 IF (output_unit > 0)
THEN
132 WRITE (unit=output_unit, fmt=
"(/,T2,A)") repeat(
"-", 79)
133 WRITE (unit=output_unit, fmt=
"(/,T2,A)")
"The TMC output files are:"
134 WRITE (unit=output_unit, fmt=
"(/,T2,A)") &
136 WRITE (unit=output_unit, fmt=
"(/,T2,A)") &
138 WRITE (unit=output_unit, fmt=
"(/,T2,A)") &
140 WRITE (unit=output_unit, fmt=
"(/,T2,A)") repeat(
"-", 79)
142 bcast_output_unit = output_unit
143 CALL para_env%bcast(bcast_output_unit)
147 CALL tmc_preread_input(root_section, tmc_env)
148 CALL tmc_redistributing_cores(tmc_env%tmc_comp_set, para_env, &
149 ana_on_the_fly=tmc_env%tmc_comp_set%ana_on_the_fly, &
154 IF (tmc_env%tmc_comp_set%group_nr .EQ. 0)
THEN
156 ELSE IF (tmc_env%tmc_comp_set%group_nr .NE. 0)
THEN
160 CALL tmc_read_input(root_section, tmc_env)
165 IF (tmc_env%tmc_comp_set%group_nr .EQ. 0)
THEN
166 IF (tmc_env%m_env%rnd_init .GT. 0)
THEN
168 ALLOCATE (init_rng_seed(3, 2))
169 init_rng_seed(:, :) = &
170 reshape((/tmc_env%m_env%rnd_init*42.0_dp, &
171 tmc_env%m_env%rnd_init*54.0_dp, &
172 tmc_env%m_env%rnd_init*63.0_dp, &
173 tmc_env%m_env%rnd_init*98.0_dp, &
174 tmc_env%m_env%rnd_init*10.0_dp, &
175 tmc_env%m_env%rnd_init*2.0_dp/), &
178 name=
"TMC_deterministic_rng_stream", &
179 seed=init_rng_seed(:, :), &
181 DEALLOCATE (init_rng_seed)
186 name=
"TMC_rng_stream", &
192 IF (tmc_env%tmc_comp_set%group_nr .EQ. 0)
THEN
194 CALL cp_logger_create(logger_sub, para_env=tmc_env%tmc_comp_set%para_env_m_only, &
206 file_action=
"WRITE", file_position=
"APPEND", &
207 unit_number=tmc_env%m_env%io_unit)
211 CALL tmc_print_params(tmc_env)
213 tmc_params=tmc_env%params)
216 IF (bcast_output_unit .NE. tmc_env%m_env%io_unit)
THEN
217 CALL close_file(unit_number=tmc_env%m_env%io_unit)
224 ELSE IF (tmc_env%tmc_comp_set%group_nr .GT. 0)
THEN
227 CALL cp_logger_create(logger_sub, para_env=tmc_env%tmc_comp_set%para_env_sub_group, &
229 CALL cp_logger_set(logger_sub, local_filename=
"tmc_localLog")
234 IF (tmc_env%tmc_comp_set%group_nr .LE. tmc_env%tmc_comp_set%group_ener_nr)
THEN
236 input_declaration=input_declaration, &
237 input_path=tmc_env%params%energy_inp_file, &
238 mpi_comm=tmc_env%tmc_comp_set%para_env_sub_group, &
240 ivalue=tmc_env%tmc_comp_set%group_nr)), &
243 cpabort(
"creating force env result in error "//
cp_to_string(ierr))
246 IF (tmc_env%params%NMC_inp_file .NE.
"" .AND. &
247 (tmc_env%tmc_comp_set%group_cc_nr .EQ. 0 .OR. &
248 tmc_env%tmc_comp_set%group_nr .GT. tmc_env%tmc_comp_set%group_ener_nr))
THEN
250 input_declaration=input_declaration, &
251 input_path=tmc_env%params%NMC_inp_file, &
252 mpi_comm=tmc_env%tmc_comp_set%para_env_sub_group, &
254 ivalue=tmc_env%tmc_comp_set%group_nr)), &
257 cpabort(
"creating approx force env result in error "//
cp_to_string(ierr))
261 IF (tmc_env%w_env%env_id_ener .GT. 0) &
263 IF (tmc_env%w_env%env_id_approx .GT. 0) &
270 ELSE IF (
ASSOCIATED(tmc_env%tmc_comp_set%para_env_m_ana))
THEN
274 CALL cp_logger_create(logger_sub, para_env=tmc_env%tmc_comp_set%para_env_m_ana, &
277 CALL cp_logger_set(logger_sub, local_filename=
"tmc_ana_localLog")
286 file_action=
"WRITE", file_position=
"APPEND", &
287 unit_number=output_unit)
291 ALLOCATE (tmc_ana_env_list(tmc_env%params%nr_temp))
293 DO i = 1, tmc_env%params%nr_temp
295 tmc_ana_env_list(i)%temp%io_unit = output_unit
297 CALL do_tmc_worker(tmc_env=tmc_env, ana_list=tmc_ana_env_list)
298 DO i = 1, tmc_env%params%nr_temp
299 IF (
ASSOCIATED(tmc_ana_env_list(i)%temp%last_elem)) &
303 DEALLOCATE (tmc_ana_env_list)
304 IF (bcast_output_unit .NE. output_unit)
THEN
305 CALL close_file(unit_number=tmc_env%m_env%io_unit)
313 DEALLOCATE (tmc_env%rng_stream)
319 IF (tmc_env%tmc_comp_set%group_nr .EQ. 0)
THEN
321 ELSE IF (tmc_env%tmc_comp_set%group_nr .NE. 0)
THEN
326 IF (tmc_env%params%print_test_output)
THEN
327 WRITE (output_unit, *)
"TMC|NOTenoughProcessorsX= -999"
328 WRITE (output_unit, *)
"TMC|NOTcalculatedTotal energy: -999"
335 CALL timestop(handle)
352 CHARACTER(LEN=*),
PARAMETER :: routinen =
'do_analyze_files'
354 INTEGER :: dir_ind, handle, nr_dim, output_unit, &
361 NULLIFY (ana_list, tmc_env, elem, logger)
364 CALL timeset(routinen, handle)
369 ALLOCATE (tmc_env%tmc_comp_set%para_env_m_ana)
370 CALL tmc_env%tmc_comp_set%para_env_m_ana%from_split(para_env, para_env%mepos, 0)
371 IF (para_env%num_pe .NE. 1)
THEN
372 cpwarn(
"just one out of "//
cp_to_string(para_env%num_pe)//
"cores is used ")
375 IF (para_env%mepos .EQ. 0)
THEN
379 cpassert(output_unit .GT. 0)
384 CALL tmc_read_ana_files_input(input_declaration=input_declaration, &
385 input=root_section, ana_list=ana_list, &
386 elem=elem, tmc_env=tmc_env)
387 nr_dim =
SIZE(elem%pos)
390 cpassert(
SIZE(ana_list) .GT. 0)
393 IF (tmc_env%params%print_test_output)
THEN
394 WRITE (output_unit, *)
"TMC|ANAtestOutputInitX= -999"
398 DO temp = 1,
SIZE(ana_list)
400 ana_list(temp)%temp%io_unit = output_unit
401 CALL analysis_init(ana_env=ana_list(temp)%temp, nr_dim=nr_dim)
403 IF (ana_list(temp)%temp%costum_dip_file_name .NE. &
405 tmc_env%params%print_dipole = .true.
407 IF (.NOT.
ASSOCIATED(elem)) &
409 next_el=elem, nr_dim=nr_dim)
412 IF (.NOT.
ASSOCIATED(elem) .AND. .NOT.
ASSOCIATED(ana_list(temp)%temp%last_elem)) &
413 cpabort(
"uncorrect initialization of the initial configuration")
415 DO dir_ind = 1,
SIZE(ana_list(temp)%temp%dirs)
416 WRITE (output_unit, fmt=
'(T2,A,"| ",A,T41,A40)')
"TMC_ANA", &
417 "read directory", trim(ana_list(temp)%temp%dirs(dir_ind))
419 start_id=ana_list(temp)%temp%from_elem, &
420 end_id=ana_list(temp)%temp%to_elem, &
422 ana_env=ana_list(temp)%temp, &
423 tmc_params=tmc_env%params)
426 IF (dir_ind .LT.
SIZE(ana_list(temp)%temp%dirs) .AND. &
427 ASSOCIATED(ana_list(temp)%temp%last_elem)) &
429 IF (
ASSOCIATED(ana_list(temp)%temp%last_elem)) &
430 ana_list(temp)%temp%conf_offset = ana_list(temp)%temp%conf_offset &
431 + ana_list(temp)%temp%last_elem%nr
437 IF (
ASSOCIATED(ana_list(temp)%temp%last_elem)) &
439 IF (
ASSOCIATED(ana_list(temp)%temp%last_elem)) &
441 IF (
ASSOCIATED(elem)) &
444 IF (
ASSOCIATED(ana_list(temp)%temp%last_elem)) &
450 DEALLOCATE (ana_list)
455 CALL timestop(handle)
467 SUBROUTINE tmc_read_ana_files_input(input_declaration, input, ana_list, elem, tmc_env)
474 CHARACTER(len=default_string_length), &
475 DIMENSION(:),
POINTER :: directories
476 INTEGER :: env_id, ierr, nr_temp, t_act
478 REAL(kind=
dp) :: tmax, tmin
479 REAL(kind=
dp),
DIMENSION(:),
POINTER :: inp_temp, temps
482 NULLIFY (tmc_section, inp_temp, temps)
483 cpassert(
ASSOCIATED(input))
484 cpassert(.NOT.
ASSOCIATED(ana_list))
485 cpassert(.NOT.
ASSOCIATED(elem))
486 cpassert(
ASSOCIATED(tmc_env))
490 CALL section_vals_val_get(tmc_section,
"PRINT_TEST_OUTPUT", l_val=tmc_env%params%print_test_output)
497 c_val=tmc_env%params%energy_inp_file)
502 IF ((nr_temp .GT. 1) .AND. (
SIZE(inp_temp) .NE. 2)) &
503 cpabort(
"specify each temperature, skip keyword NR_TEMPERATURE")
504 IF (nr_temp .EQ. 1)
THEN
505 nr_temp =
SIZE(inp_temp)
506 ALLOCATE (temps(nr_temp))
507 temps(:) = inp_temp(:)
511 ALLOCATE (temps(nr_temp))
513 DO t_act = 2,
SIZE(temps)
514 temps(t_act) = temps(t_act - 1) + (tmax - tmin)/(
SIZE(temps) - 1.0_dp)
516 IF (any(temps .LT. 0.0_dp)) &
517 CALL cp_abort(__location__,
"The temperatures are negative. Should be specified using "// &
518 "TEMPERATURE {T_min} {T_max} and NR_TEMPERATURE {#temperatures}")
526 input_declaration=input_declaration, &
527 input_path=tmc_env%params%energy_inp_file, &
528 mpi_comm=tmc_env%tmc_comp_set%para_env_m_ana, &
529 output_path=
"tmc_ana.out", ierr=ierr)
533 cell=tmc_env%params%cell)
536 ALLOCATE (ana_list(
SIZE(temps)))
537 DO t_act = 1,
SIZE(temps)
538 ana_list(t_act)%temp => null()
540 ana_list(t_act)%temp%temperature = temps(t_act)
541 ALLOCATE (ana_list(t_act)%temp%dirs(
SIZE(directories)))
542 ana_list(t_act)%temp%dirs(:) = directories(:)
543 ana_list(t_act)%temp%cell => tmc_env%params%cell
544 ana_list(t_act)%temp%atoms => tmc_env%params%atoms
545 ana_list(t_act)%temp%print_test_output = tmc_env%params%print_test_output
548 c_val=ana_list(t_act)%temp%costum_pos_file_name)
550 c_val=ana_list(t_act)%temp%costum_dip_file_name)
552 c_val=ana_list(t_act)%temp%costum_cell_file_name)
557 END SUBROUTINE tmc_read_ana_files_input
565 SUBROUTINE tmc_preread_input(input, tmc_env)
569 CHARACTER(LEN=default_path_length) :: c_tmp
571 LOGICAL :: explicit_key, flag
572 REAL(kind=
dp) :: tmax, tmin
573 REAL(kind=
dp),
DIMENSION(:),
POINTER :: inp_temp
576 NULLIFY (tmc_section, inp_temp)
578 cpassert(
ASSOCIATED(input))
580 tmc_env%tmc_comp_set%ana_on_the_fly = 0
584 tmc_env%tmc_comp_set%ana_on_the_fly = 1
591 CALL section_vals_val_get(tmc_section,
"PRINT_TEST_OUTPUT", l_val=tmc_env%params%print_test_output)
593 cpassert(
ASSOCIATED(tmc_env%tmc_comp_set))
595 CALL section_vals_val_get(tmc_section,
"GROUP_ENERGY_SIZE", i_val=tmc_env%tmc_comp_set%group_ener_size)
596 CALL section_vals_val_get(tmc_section,
"GROUP_ENERGY_NR", i_val=tmc_env%tmc_comp_set%group_ener_nr)
597 CALL section_vals_val_get(tmc_section,
"GROUP_CC_SIZE", i_val=tmc_env%tmc_comp_set%group_cc_size)
599 IF (tmc_env%tmc_comp_set%ana_on_the_fly .GT. 0) &
600 tmc_env%tmc_comp_set%ana_on_the_fly = itmp
601 IF (tmc_env%tmc_comp_set%ana_on_the_fly .GT. 1) &
602 CALL cp_abort(__location__, &
603 "analysing on the fly is up to now not supported for multiple cores. "// &
604 "Restart file witing for this case and temperature "// &
605 "distribution has to be solved.!.")
606 CALL section_vals_val_get(tmc_section,
"RESULT_LIST_IN_MEMORY", l_val=tmc_env%params%USE_REDUCED_TREE)
608 tmc_env%params%USE_REDUCED_TREE = .NOT. tmc_env%params%USE_REDUCED_TREE
612 CALL section_vals_val_get(tmc_section,
"NMC_MOVES%NMC_FILE_NAME", c_val=tmc_env%params%NMC_inp_file)
615 cpabort(
"no or a valid NMC input file has to be specified ")
616 ELSE IF (tmc_env%params%NMC_inp_file .EQ.
"")
THEN
618 IF (tmc_env%tmc_comp_set%group_cc_size .GT. 0) &
619 CALL cp_warn(__location__, &
620 "The configurational groups are deactivated, "// &
621 "because no approximated energy input is specified.")
622 tmc_env%tmc_comp_set%group_cc_size = 0
625 INQUIRE (file=trim(tmc_env%params%NMC_inp_file), exist=flag, iostat=itmp)
626 IF (.NOT. flag .OR. itmp .NE. 0) &
627 cpabort(
"a valid NMC input file has to be specified")
631 IF (tmc_env%params%nr_temp .GT. 1 .AND.
SIZE(inp_temp) .NE. 2) &
632 cpabort(
"specify each temperature, skip keyword NR_TEMPERATURE")
633 IF (tmc_env%params%nr_temp .EQ. 1)
THEN
634 tmc_env%params%nr_temp =
SIZE(inp_temp)
635 ALLOCATE (tmc_env%params%Temp(tmc_env%params%nr_temp))
636 tmc_env%params%Temp(:) = inp_temp(:)
640 ALLOCATE (tmc_env%params%Temp(tmc_env%params%nr_temp))
641 tmc_env%params%Temp(1) = tmin
642 DO itmp = 2,
SIZE(tmc_env%params%Temp)
643 tmc_env%params%Temp(itmp) = tmc_env%params%Temp(itmp - 1) + (tmax - tmin)/(
SIZE(tmc_env%params%Temp) - 1.0_dp)
645 IF (any(tmc_env%params%Temp .LT. 0.0_dp)) &
646 CALL cp_abort(__location__,
"The temperatures are negative. Should be specified using "// &
647 "TEMPERATURE {T_min} {T_max} and NR_TEMPERATURE {#temperatures}")
651 IF (explicit_key)
THEN
653 SELECT CASE (trim(c_tmp))
659 CALL cp_warn(__location__, &
660 'unknown TMC task type "'//trim(c_tmp)//
'" specified. '// &
666 END SUBROUTINE tmc_preread_input
674 SUBROUTINE tmc_read_input(input, tmc_env)
679 LOGICAL :: explicit, flag
680 REAL(kind=
dp) :: r_tmp
681 REAL(kind=
dp),
DIMENSION(:),
POINTER :: r_arr_tmp
684 NULLIFY (tmc_section)
686 cpassert(
ASSOCIATED(input))
693 IF (tmc_env%tmc_comp_set%group_nr == 0)
THEN
694 cpassert(
ASSOCIATED(tmc_env%m_env))
697 walltime=tmc_env%m_env%walltime)
705 INQUIRE (file=tmc_env%m_env%restart_in_file_name, exist=flag)
706 IF (.NOT. flag) tmc_env%m_env%restart_in_file_name =
""
710 IF (tmc_env%m_env%restart_out_step .EQ. -9)
THEN
712 tmc_env%m_env%restart_out_step = huge(tmc_env%m_env%restart_out_step)
714 IF (tmc_env%m_env%restart_out_step .LT. 0) &
715 CALL cp_abort(__location__, &
716 "Please specify a valid value for the frequency "// &
717 "to write restart files (RESTART_OUT #). "// &
718 "# > 0 to define the amount of Markov chain elements in between, "// &
719 "or 0 to deactivate the restart file writing. "// &
720 "Lonely keyword writes restart file only at the end of the run.")
722 CALL section_vals_val_get(tmc_section,
"INFO_OUT_STEP_SIZE", i_val=tmc_env%m_env%info_out_step_size)
724 CALL section_vals_val_get(tmc_section,
"ALL_CONF_FILE_NAME", c_val=tmc_env%params%all_conf_file_name)
725 IF (tmc_env%params%dot_file_name .NE.
"") tmc_env%params%DRAW_TREE = .true.
728 ELSE IF (tmc_env%tmc_comp_set%group_nr .NE. 0)
THEN
729 cpassert(
ASSOCIATED(tmc_env%w_env))
735 CALL section_vals_val_get(tmc_section,
"ENERGY_FILE_NAME", c_val=tmc_env%params%energy_inp_file)
737 IF (tmc_env%params%energy_inp_file .EQ.
"") &
738 cpabort(
"a valid exact energy input file has to be specified ")
740 INQUIRE (file=trim(tmc_env%params%energy_inp_file), exist=flag, iostat=itmp)
741 IF (.NOT. flag .OR. itmp .NE. 0) &
742 CALL cp_abort(__location__,
"a valid exact energy input file has to be specified, "// &
743 trim(tmc_env%params%energy_inp_file)//
" does not exist.")
749 tmc_env%params%pressure = tmc_env%params%pressure/au2bar
750 CALL section_vals_val_get(tmc_section,
"MOVE_CENTER_OF_MASS", l_val=tmc_env%params%mv_cen_of_mass)
753 IF (
SIZE(r_arr_tmp) .GT. 1)
THEN
754 IF (
SIZE(r_arr_tmp) .NE. tmc_env%params%dim_per_elem) &
755 cpabort(
"The entered sub box sizes does not fit in number of dimensions.")
756 IF (any(r_arr_tmp .LE. 0.0_dp)) &
757 cpabort(
"The entered sub box lengths should be greater than 0.")
758 DO itmp = 1,
SIZE(tmc_env%params%sub_box_size)
759 tmc_env%params%sub_box_size(itmp) = r_arr_tmp(itmp)/au2a
761 ELSE IF (r_arr_tmp(1) .GT. 0.0_dp)
THEN
762 r_tmp = r_arr_tmp(1)/au2a
763 tmc_env%params%sub_box_size(:) = r_tmp
768 tmc_section=tmc_section)
770 CALL section_vals_val_get(tmc_section,
"ESIMATE_ACC_PROB", l_val=tmc_env%params%esimate_acc_prob)
771 CALL section_vals_val_get(tmc_section,
"SPECULATIVE_CANCELING", l_val=tmc_env%params%SPECULATIVE_CANCELING)
772 CALL section_vals_val_get(tmc_section,
"USE_SCF_ENERGY_INFO", l_val=tmc_env%params%use_scf_energy_info)
774 CALL section_vals_val_get(tmc_section,
"PRINT_ONLY_ACC", l_val=tmc_env%params%print_only_diff_conf)
787 END SUBROUTINE tmc_read_input
797 SUBROUTINE tmc_redistributing_cores(tmc_comp_set, para_env, ana_on_the_fly, &
801 INTEGER :: ana_on_the_fly
804 INTEGER :: cc_group, cc_group_rank, master_ana_group, master_ana_rank, &
805 master_first_e_worker_g, master_first_e_worker_r, master_worker_group, &
806 master_worker_rank, my_mpi_undefined, total_used
807 LOGICAL :: flag, master
809 cpassert(
ASSOCIATED(tmc_comp_set))
810 cpassert(
ASSOCIATED(para_env))
814 tmc_comp_set%group_nr = -1
815 my_mpi_undefined = para_env%num_pe + 10000
816 master_worker_group = my_mpi_undefined
817 master_worker_rank = -1
818 cc_group = my_mpi_undefined
820 master_first_e_worker_g = my_mpi_undefined
821 master_first_e_worker_r = -1
822 master_ana_group = my_mpi_undefined
829 IF (para_env%num_pe .LE. 1)
THEN
830 cpwarn(
"TMC need at least 2 cores (one for master, one for worker)")
834 IF (tmc_comp_set%group_ener_size*tmc_comp_set%group_ener_nr .GT. (para_env%num_pe - 1))
THEN
835 cpwarn(
"The selected energy group size is too huge. ")
838 tmc_comp_set%group_ener_nr = int((para_env%num_pe - 1)/ &
839 REAL(tmc_comp_set%group_ener_size, kind=
dp))
840 IF (tmc_comp_set%group_ener_nr .LT. 1)
THEN
841 cpwarn(
"The selected energy group size is too huge. ")
843 IF (flag) success = .false.
847 tmc_comp_set%group_cc_nr = 0
848 IF (tmc_comp_set%group_cc_size .GT. 0)
THEN
849 tmc_comp_set%group_cc_nr = int((para_env%num_pe - 1 - tmc_comp_set%ana_on_the_fly &
850 - tmc_comp_set%group_ener_size*tmc_comp_set%group_ener_nr)/ &
851 REAL(tmc_comp_set%group_cc_size, kind=
dp))
853 IF (tmc_comp_set%group_cc_nr .LT. 1) &
854 CALL cp_warn(__location__, &
855 "There are not enougth cores left for creating groups for configurational change.")
856 IF (flag) success = .false.
859 total_used = tmc_comp_set%group_ener_size*tmc_comp_set%group_ener_nr + &
860 tmc_comp_set%group_cc_size*tmc_comp_set%group_cc_nr + &
861 tmc_comp_set%ana_on_the_fly
862 IF (para_env%num_pe - 1 .GT. total_used)
THEN
863 cpwarn(
" mpi ranks are unused, but can be used for analysis.")
867 IF (para_env%mepos == para_env%num_pe - 1)
THEN
869 master_worker_group = para_env%num_pe + 3
870 master_worker_rank = 0
871 master_first_e_worker_g = para_env%num_pe + 3
872 master_first_e_worker_r = 0
873 tmc_comp_set%group_nr = 0
874 master_ana_group = para_env%num_pe + 4
878 IF (para_env%mepos .LT. tmc_comp_set%group_ener_size*tmc_comp_set%group_ener_nr)
THEN
879 tmc_comp_set%group_nr = int(para_env%mepos/tmc_comp_set%group_ener_size) + 1
881 IF (
modulo(para_env%mepos, tmc_comp_set%group_ener_size) .EQ. 0)
THEN
882 master_worker_group = para_env%num_pe + 3
883 master_worker_rank = tmc_comp_set%group_nr
884 IF (master_worker_rank .EQ. 1)
THEN
885 master_first_e_worker_g = para_env%num_pe + 3
886 master_first_e_worker_r = 1
889 cc_group = tmc_comp_set%group_nr
890 cc_group_rank = para_env%mepos - &
891 (tmc_comp_set%group_nr - 1)*tmc_comp_set%group_ener_size
894 ELSE IF (para_env%mepos .LT. (tmc_comp_set%group_ener_size*tmc_comp_set%group_ener_nr + &
895 tmc_comp_set%group_cc_size*tmc_comp_set%group_cc_nr))
THEN
896 cc_group_rank = para_env%mepos - tmc_comp_set%group_ener_size*tmc_comp_set%group_ener_nr
897 tmc_comp_set%group_nr = tmc_comp_set%group_ener_nr + 1 + int(cc_group_rank/tmc_comp_set%group_cc_size)
898 cc_group = tmc_comp_set%group_nr
900 IF (
modulo(cc_group_rank, tmc_comp_set%group_cc_size) .EQ. 0)
THEN
901 master_worker_group = para_env%num_pe + 3
902 master_worker_rank = tmc_comp_set%group_nr
905 cc_group_rank =
modulo(cc_group_rank, tmc_comp_set%group_cc_size)
909 IF (para_env%mepos .EQ. para_env%num_pe - 2)
THEN
910 tmc_comp_set%group_nr = para_env%mepos - (para_env%num_pe - 1)
911 cpassert(tmc_comp_set%group_nr .LT. 0)
912 IF (para_env%mepos .GE. para_env%num_pe - 1 - ana_on_the_fly)
THEN
913 master_ana_group = para_env%num_pe + 4
914 master_ana_rank = -tmc_comp_set%group_nr
923 ALLOCATE (tmc_comp_set%para_env_sub_group)
924 CALL tmc_comp_set%para_env_sub_group%from_split(para_env, cc_group, cc_group_rank)
926 IF (cc_group_rank < 0)
THEN
927 CALL tmc_comp_set%para_env_sub_group%free()
928 DEALLOCATE (tmc_comp_set%para_env_sub_group)
932 ALLOCATE (tmc_comp_set%para_env_m_w)
933 CALL tmc_comp_set%para_env_m_w%from_split(para_env, master_worker_group, master_worker_rank)
935 IF (master_worker_rank < 0)
THEN
936 CALL tmc_comp_set%para_env_m_w%free()
937 DEALLOCATE (tmc_comp_set%para_env_m_w)
941 ALLOCATE (tmc_comp_set%para_env_m_first_w)
942 CALL tmc_comp_set%para_env_m_first_w%from_split(para_env, master_first_e_worker_g, master_first_e_worker_r)
944 IF (master_first_e_worker_r < 0)
THEN
945 CALL tmc_comp_set%para_env_m_first_w%free()
946 DEALLOCATE (tmc_comp_set%para_env_m_first_w)
950 ALLOCATE (tmc_comp_set%para_env_m_ana)
951 CALL tmc_comp_set%para_env_m_ana%from_split(para_env, master_ana_group, master_ana_rank)
952 IF (master_ana_rank < 0)
THEN
953 CALL tmc_comp_set%para_env_m_ana%free()
954 DEALLOCATE (tmc_comp_set%para_env_m_ana)
958 master_ana_group = my_mpi_undefined
964 ALLOCATE (tmc_comp_set%para_env_m_only)
965 CALL tmc_comp_set%para_env_m_only%from_split(para_env, master_ana_group, master_ana_rank)
966 IF (master_ana_rank < 0)
THEN
967 CALL tmc_comp_set%para_env_m_only%free()
968 DEALLOCATE (tmc_comp_set%para_env_m_only)
972 END SUBROUTINE tmc_redistributing_cores
979 SUBROUTINE tmc_print_params(tmc_env)
982 CHARACTER(LEN=*),
PARAMETER :: fmt_my =
'(T2,A,"| ",A,T41,A40)', plabel =
"TMC"
984 CHARACTER(LEN=80) :: c_tmp, fmt_tmp
987 cpassert(
ASSOCIATED(tmc_env))
988 cpassert(
ASSOCIATED(tmc_env%tmc_comp_set))
990 IF (tmc_env%tmc_comp_set%group_nr == 0)
THEN
991 file_nr = tmc_env%m_env%io_unit
992 cpassert(
ASSOCIATED(tmc_env%tmc_comp_set%para_env_m_w))
993 cpassert(
ASSOCIATED(tmc_env%m_env))
998 WRITE (unit=file_nr, fmt=
"(/,T2,A)") repeat(
"-", 79)
999 WRITE (unit=file_nr, fmt=
"(T2,A,T80,A)")
"-",
"-"
1000 WRITE (unit=file_nr, fmt=
"(T2,A,T35,A,T80,A)")
"-",
"TMC setting",
"-"
1001 WRITE (unit=file_nr, fmt=
"(T2,A,T80,A)")
"-",
"-"
1002 WRITE (unit=file_nr, fmt=
"(T2,A)") repeat(
"-", 79)
1004 WRITE (unit=file_nr, fmt=
"(T2,A,T35,A,T80,A)")
"-",
"distribution of cores",
"-"
1005 WRITE (file_nr, fmt=fmt_my) plabel,
"number of all working groups ", &
1006 cp_to_string(tmc_env%tmc_comp_set%para_env_m_w%num_pe - 1)
1007 WRITE (file_nr, fmt=fmt_my) plabel,
"number of groups (ener|cc)", &
1008 cp_to_string(tmc_env%tmc_comp_set%group_ener_nr)//
" | "// &
1010 WRITE (file_nr, fmt=fmt_my) plabel,
"cores per group (ener|cc) ", &
1011 cp_to_string(tmc_env%tmc_comp_set%group_ener_size)//
" | "// &
1013 IF (
ASSOCIATED(tmc_env%tmc_comp_set%para_env_m_ana)) &
1014 WRITE (file_nr, fmt=fmt_my) plabel,
"Analysis groups ", &
1015 cp_to_string(tmc_env%tmc_comp_set%para_env_m_ana%num_pe - 1)
1016 IF (
SIZE(tmc_env%params%Temp(:)) .LE. 7)
THEN
1017 WRITE (fmt_tmp, *)
'(T2,A,"| ",A,T25,A56)'
1019 WRITE (c_tmp, fmt=
"(1000F8.2)") tmc_env%params%Temp(:)
1020 WRITE (file_nr, fmt=fmt_tmp) plabel,
"Temperature(s) [K]", trim(c_tmp)
1022 WRITE (file_nr, fmt=
'(A,1000F8.2)')
" "//plabel//
"| Temperature(s) [K]", &
1023 tmc_env%params%Temp(:)
1025 WRITE (file_nr, fmt=fmt_my) plabel,
"# of Monte Carlo Chain elements: ", &
1027 WRITE (file_nr, fmt=fmt_my) plabel,
"exact potential input file:", &
1028 trim(tmc_env%params%energy_inp_file)
1029 IF (tmc_env%params%NMC_inp_file .NE.
"") &
1030 WRITE (file_nr, fmt=fmt_my) plabel,
"approximate potential input file:", &
1031 trim(tmc_env%params%NMC_inp_file)
1032 IF (any(tmc_env%params%sub_box_size .GT. 0.0_dp))
THEN
1033 WRITE (fmt_tmp, *)
'(T2,A,"| ",A,T25,A56)'
1035 WRITE (c_tmp, fmt=
"(1000F8.2)") tmc_env%params%sub_box_size(:)*au2a
1036 WRITE (file_nr, fmt=fmt_tmp) plabel,
"Sub box size [A]", trim(c_tmp)
1038 IF (tmc_env%params%pressure .GT. 0.0_dp) &
1039 WRITE (file_nr, fmt=fmt_my) plabel,
"Pressure [bar]: ", &
1041 WRITE (file_nr, fmt=fmt_my) plabel,
"Numbers of atoms/molecules moved "
1042 WRITE (file_nr, fmt=fmt_my) plabel,
" within one conf. change", &
1044 WRITE (unit=file_nr, fmt=
"(/,T2,A)") repeat(
"-", 79)
1047 END SUBROUTINE tmc_print_params
static GRID_HOST_DEVICE int modulo(int a, int m)
Equivalent of Fortran's MODULO, which always return a positive number. https://gcc....
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public schonherr2014
Utility routines to open and close files. Tracking of preconnections.
subroutine, public open_file(file_name, file_status, file_form, file_action, file_position, file_pad, unit_number, debug, skip_get_unit_number, file_access)
Opens the requested file using a free unit number.
subroutine, public close_file(unit_number, file_status, keep_preconnection)
Close an open file given by its logical unit number. Optionally, keep the file and unit preconnected.
various routines to log and control the output. The idea is that decisions about where to log should ...
subroutine, public cp_logger_set(logger, local_filename, global_filename)
sets various attributes of the given logger
subroutine, public cp_rm_default_logger()
the cousin of cp_add_default_logger, decrements the stack, so that the default logger is what it has ...
subroutine, public cp_logger_release(logger)
releases this logger
integer function, public cp_logger_get_default_io_unit(logger)
returns the unit nr for the ionode (-1 on all other processors) skips as well checks if the procs cal...
subroutine, public cp_logger_create(logger, para_env, print_level, default_global_unit_nr, default_local_unit_nr, global_filename, local_filename, close_global_unit_on_dealloc, iter_info, close_local_unit_on_dealloc, suffix, template_logger)
initializes a logger
subroutine, public cp_add_default_logger(logger)
adds a default logger. MUST be called before logging occours
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
Sets up and terminates the global environment variables.
subroutine, public cp2k_get_walltime(section, keyword_name, walltime)
reads the Walltime also in format HH:MM:SS
interface to use cp2k as library
recursive subroutine, public destroy_force_env(env_id, ierr, q_finalize)
deallocates the force_env with the given id
recursive subroutine, public create_force_env(new_env_id, input_declaration, input_path, output_path, mpi_comm, output_unit, owns_out_unit, input, ierr, work_dir, initial_variables)
creates a new force environment using the given input, and writing the output to the given output uni...
Define type storing the global information of a run. Keep the amount of stored data small....
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_string_length
integer, parameter, public default_path_length
Machine interface based on Fortran 2003 and POSIX.
integer, parameter, public default_output_unit
subroutine, public m_flush(lunit)
flushes units if the &GLOBAL flag is set accordingly
Interface to the message passing library MPI.
Parallel (pseudo)random number generator (RNG) for multiple streams and substreams of random numbers.
integer, parameter, public uniform
Definition of physical constants:
real(kind=dp), parameter, public angstrom
real(kind=dp), parameter, public bar
module provides variables for the TMC analysis tool
subroutine, public tmc_ana_env_release(tmc_ana)
releases the structure environment for TMC analysis
module analyses element of the TMC tree element structure e.g. density, radial distribution function,...
subroutine, public analysis_restart_read(ana_env, elem)
read analysis restart file
subroutine, public finalize_tmc_analysis(ana_env)
call all the necessarry analysis printing routines
subroutine, public tmc_read_ana_input(tmc_ana_section, tmc_ana)
creates a new para environment for tmc analysis
subroutine, public analyze_file_configurations(start_id, end_id, dir_ind, ana_env, tmc_params)
read the files and analyze the configurations
subroutine, public analysis_init(ana_env, nr_dim)
initialize all the necessarry analysis structures
subroutine, public analysis_restart_print(ana_env)
print analysis restart file
writing and printing the files, trajectory (pos, cell, dipoles) as well as restart files
character(len=default_path_length) function, public expand_file_name_int(file_name, ivalue)
placing an integer at the end of a file name (before the file extension)
module contains the master routine handling the tree creation, communication with workers and task di...
subroutine, public do_tmc_master(tmc_env, globenv)
global master handling tree creation and communication/work distribution with workers
acceptance ratio handling of the different Monte Carlo Moves types For each move type and each temper...
subroutine, public read_init_move_types(tmc_params, tmc_section)
initialization of the different moves, with sizes and probabilities
subroutine, public finalize_mv_types(tmc_params)
deallocating the module variables
subroutine, public print_move_types(init, file_io, tmc_params)
routine pronts out the probabilities and sized for each type and temperature the output is divided in...
Tree Monte Carlo entry point, set up, CPU redistribution and input reading.
subroutine, public do_analyze_files(input_declaration, root_section, para_env)
analyze TMC trajectory files
subroutine, public do_tmc(input_declaration, root_section, para_env, globenv)
tmc_entry point
tree nodes creation, searching, deallocation, references etc.
character(len= *), parameter, public tmc_nmc_worker_out_file_name
character(len= *), parameter, public tmc_master_out_file_name
character(len= *), parameter, public tmc_default_unspecified_name
character(len= *), parameter, public tmc_ana_out_file_name
integer, parameter, public task_type_mc
character(len= *), parameter, public tmc_default_restart_in_file_name
character(len= *), parameter, public tmc_default_restart_out_file_name
character(len= *), parameter, public tmc_energy_worker_out_file_name
integer, parameter, public task_type_ideal_gas
tree nodes creation, deallocation, references etc.
subroutine, public deallocate_sub_tree_node(tree_elem)
deallocates an elements of the subtree element structure
subroutine, public allocate_new_sub_tree_node(tmc_params, next_el, nr_dim)
allocates an elements of the subtree element structure
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
subroutine, public tmc_env_release(tmc_env)
releases the structure environment for TMC
subroutine, public tmc_worker_env_create(tmc_env)
creates a new structure environment for TMC master
subroutine, public tmc_master_env_create(tmc_env)
creates a new structure environment for TMC master
subroutine, public tmc_master_env_release(tmc_env)
releases the structure environment for TMC master
subroutine, public tmc_worker_env_release(tmc_env)
releases the structure environment for TMC master
subroutine, public tmc_env_create(tmc_env)
creates a new structure environment for TMC
module contains the worker routine handling the communication and the calculation / creation of the c...
subroutine, public do_tmc_worker(tmc_env, ana_list)
worker get tasks form master and fulfill them
subroutine, public get_initial_conf(tmc_params, init_conf, env_id)
get the initial confuguration (pos,...)
subroutine, public get_atom_kinds_and_cell(env_id, atoms, cell)
get the pointer to the atoms, for easy handling
type of a logger, at the moment it contains just a print level starting at which level it should be l...
contains the initially parsed file and the initial parallel environment
stores all the informations relevant to an mpi environment