124#include "./base/base_uses.f90"
130 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'environment'
151 SUBROUTINE cp2k_init(para_env, output_unit, globenv, input_file_name, wdir)
154 INTEGER :: output_unit
156 CHARACTER(LEN=*) :: input_file_name
157 CHARACTER(LEN=*),
OPTIONAL :: wdir
159 CHARACTER(LEN=10*default_string_length) :: cp_flags
160 INTEGER :: i, ilen, my_output_unit
171 IF (para_env%is_source())
THEN
172 my_output_unit = output_unit
178 default_global_unit_nr=output_unit, &
179 close_global_unit_on_dealloc=.false.)
189 IF (my_output_unit > 0)
THEN
190 WRITE (unit=my_output_unit, fmt=
"(/,T2,A,T31,A50)") &
192 WRITE (unit=my_output_unit, fmt=
"(T2,A,T41,A40)") &
193 "CP2K| source code revision number:", &
196 ilen = len_trim(cp_flags)
197 WRITE (unit=my_output_unit, fmt=
"(T2,A)") &
198 "CP2K| "//cp_flags(1:73)
200 DO i = 0, (ilen - 75)/61
201 WRITE (unit=my_output_unit, fmt=
"(T2,A)") &
202 "CP2K| "//trim(cp_flags(74 + i*61:min(74 + (i + 1)*61, ilen)))
205 WRITE (unit=my_output_unit, fmt=
"(T2,A,T41,A40)") &
206 "CP2K| is freely available from ", &
208 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
209 "CP2K| Program compiled at", &
211 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
212 "CP2K| Program compiled on", &
214 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
215 "CP2K| Program compiled for", &
217 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
218 "CP2K| Data directory path", &
220 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
221 "CP2K| Input file name", &
222 adjustr(trim(input_file_name))
223 FLUSH (my_output_unit)
226#if defined(__FAST_MATH__)
227 CALL cp_warn(__location__, &
228 "During compilation one of the following flags was active:"// &
229 " `-ffast-math` (GCC)"// &
230 " `-hfpN` (Cray, N > 0, default N=2)"// &
231 " This can lead to wrong results and numerical instabilities"// &
232 " and is therefore no longer supported.")
234#if !defined(__FORCE_USE_FAST_MATH)
235#error "-ffast-math (GCC) or -hfpN (N>0, Cray) can lead to wrong results and numerical instabilities and are therefore no longer supported"
240#error "Please do not build CP2K with NDEBUG. There is no performance advantage and asserts will save your neck."
250 SUBROUTINE echo_all_hosts(para_env, output_unit)
252 INTEGER :: output_unit
254 CHARACTER(LEN=default_string_length) :: string
256 INTEGER,
ALLOCATABLE,
DIMENSION(:) :: all_pid
257 INTEGER,
ALLOCATABLE,
DIMENSION(:, :) :: all_host
261 ALLOCATE (all_pid(para_env%num_pe))
263 all_pid(para_env%mepos + 1) =
r_pid
265 CALL para_env%sum(all_pid)
266 ALLOCATE (all_host(30, para_env%num_pe))
269 CALL para_env%sum(all_host)
270 IF (output_unit > 0)
THEN
272 WRITE (unit=output_unit, fmt=
"(T2,A)")
""
273 DO ipe = 1, para_env%num_pe
275 WRITE (unit=output_unit, fmt=
"(T2,A,T63,I8,T71,I10)") &
277 " has created rank and process ", ipe - 1, all_pid(ipe)
279 WRITE (unit=output_unit, fmt=
"(T2,A)")
""
282 DEALLOCATE (all_host)
284 END SUBROUTINE echo_all_hosts
291 SUBROUTINE echo_all_process_host(para_env, output_unit)
293 INTEGER :: output_unit
295 CHARACTER(LEN=default_string_length) :: string, string_sec
296 INTEGER :: ipe, jpe, nr_occu
297 INTEGER,
ALLOCATABLE,
DIMENSION(:) :: all_pid
298 INTEGER,
ALLOCATABLE,
DIMENSION(:, :) :: all_host
300 ALLOCATE (all_host(30, para_env%num_pe))
305 CALL para_env%sum(all_host)
308 IF (output_unit > 0)
THEN
309 ALLOCATE (all_pid(para_env%num_pe))
312 WRITE (unit=output_unit, fmt=
"(T2,A)")
""
313 DO ipe = 1, para_env%num_pe
315 IF (all_pid(ipe) .NE. -1)
THEN
317 DO jpe = 1, para_env%num_pe
319 IF (string .EQ. string_sec)
THEN
320 nr_occu = nr_occu + 1
324 WRITE (unit=output_unit, fmt=
"(T2,A,T63,I8,A)") &
326 " is running ", nr_occu,
" processes"
327 WRITE (unit=output_unit, fmt=
"(T2,A)")
""
334 DEALLOCATE (all_host)
336 END SUBROUTINE echo_all_process_host
357 CHARACTER(LEN=3*default_string_length) :: message
358 CHARACTER(LEN=default_string_length) :: c_val
369 IF (c_val /=
"")
THEN
371 local_filename=trim(c_val)//
"_localLog")
376 IF (index(c_val(:len_trim(c_val)),
" ") > 0)
THEN
377 message =
"Project name <"//trim(c_val)// &
378 "> contains spaces which will be replaced with underscores"
379 cpwarn(trim(message))
380 DO i = 1, len_trim(c_val)
382 IF (c_val(i:i) ==
" ") c_val(i:i) =
"_"
386 IF (c_val /=
"")
THEN
387 CALL cp_logger_set(logger, local_filename=trim(c_val)//
"_localLog")
389 logger%iter_info%project_name = c_val
391 CALL section_vals_val_get(root_section,
"GLOBAL%PRINT_LEVEL", i_val=logger%iter_info%print_level)
394 CALL read_cp2k_section(root_section, para_env, globenv)
400 "GLOBAL%PRINT/BASIC_DATA_TYPES")
406 "GLOBAL%PRINT/PHYSCON")
427 INTEGER,
DIMENSION(:),
POINTER :: seed_vals
428 REAL(kind=
dp),
DIMENSION(3, 2) :: initial_seed
443 "GLOBAL%PRINT/RNG_MATRICES")
448 IF (
SIZE(seed_vals) == 1)
THEN
449 initial_seed(:, :) = real(seed_vals(1), kind=
dp)
450 ELSE IF (
SIZE(seed_vals) == 6)
THEN
451 initial_seed(1:3, 1:2) = reshape(real(seed_vals(:), kind=
dp), (/3, 2/))
453 cpabort(
"Supply exactly 1 or 6 arguments for SEED in &GLOBAL only!")
457 name=
"Global Gaussian random numbers", &
460 extended_precision=.true.)
469 "GLOBAL%PRINT/RNG_CHECK")
474 CALL globenv%gaussian_rng_stream%write(iw, write_all=.true.)
477 "GLOBAL%PRINT/GLOBAL_GAUSSIAN_RNG")
505 SUBROUTINE read_global_section(root_section, para_env, globenv)
511 CHARACTER(LEN=6),
PARAMETER :: start_section_label =
"GLOBAL"
513 CHARACTER(LEN=13) :: omp_stacksize, tracing_string
514 CHARACTER(LEN=6) :: print_level_string
515 CHARACTER(LEN=default_path_length) :: basis_set_file_name, coord_file_name, &
516 mm_potential_file_name, &
518 CHARACTER(LEN=default_string_length) :: env_num, model_name, project_name
519 CHARACTER(LEN=default_string_length), &
520 DIMENSION(:),
POINTER :: trace_routines
521 INTEGER :: cpuid, cpuid_static, i_cholesky, i_dgemm, i_diag, i_fft, i_grid_backend, &
522 iforce_eval, method_name_id, n_rep_val, nforce_eval, num_threads, output_unit, &
523 print_level, trace_max, unit_nr
524 INTEGER(kind=int_8) :: buffers, buffers_avr, buffers_max, buffers_min, cached, cached_avr, &
525 cached_max, cached_min, memfree, memfree_avr, memfree_max, memfree_min, memlikelyfree, &
526 memlikelyfree_avr, memlikelyfree_max, memlikelyfree_min, memtotal, memtotal_avr, &
527 memtotal_max, memtotal_min, slab, slab_avr, slab_max, slab_min, sreclaimable, &
528 sreclaimable_avr, sreclaimable_max, sreclaimable_min
529 INTEGER,
DIMENSION(:),
POINTER :: i_force_eval
530 LOGICAL :: ata, do_echo_all_hosts, efl, explicit, &
531 flag, report_maxloc, trace, &
538 global_section, qmmm_section, &
541 NULLIFY (dft_section, global_section, i_force_eval)
558 IF (unit_nr > 0) globenv%elpa_print = .true.
561 CALL section_vals_val_get(global_section,
"DLAF_CHOLESKY_N_MIN", i_val=globenv%dlaf_cholesky_n_min)
565 CALL section_vals_val_get(global_section,
"FFT_POOL_SCRATCH_LIMIT", i_val=globenv%fft_pool_scratch_limit)
568 CALL section_vals_val_get(global_section,
"FFTW_WISDOM_FILE_NAME", c_val=globenv%fftw_wisdom_file_name)
571 walltime=globenv%cp2k_target_time)
579 NULLIFY (trace_routines)
585 do_echo_all_hosts = do_echo_all_hosts .OR. report_maxloc
591 CALL fm_setup(global_section)
592 CALL fm_diag_rules_setup(global_section)
593 CALL dgemm_setup(global_section)
595 IF (trace .AND. (.NOT. trace_master .OR. para_env%mepos == 0))
THEN
597 IF (logger%para_env%is_source() .OR. .NOT. trace_master) &
599 WRITE (tracing_string,
"(I6.6,A1,I6.6)") para_env%mepos,
":", para_env%num_pe
600 IF (
ASSOCIATED(trace_routines))
THEN
611 globenv%diag_library =
"ScaLAPACK"
613 globenv%diag_library =
"ELPA"
616 globenv%diag_library =
"cuSOLVER"
618 globenv%diag_library =
"DLAF"
621 cpabort(
"Unknown diagonalization library specified")
624 SELECT CASE (i_cholesky)
626 globenv%cholesky_library =
"ScaLAPACK"
629 globenv%cholesky_library =
"DLAF"
634 cpabort(
"Unknown Cholesky decomposition library specified")
639 globenv%default_fft_library =
"FFTSG"
641 globenv%default_fft_library =
"FFTW3"
644 cpabort(
"Unknown FFT library specified")
647 SELECT CASE (i_dgemm)
649 globenv%default_dgemm_library =
"SPLA"
651 globenv%default_dgemm_library =
"BLAS"
653 cpabort(
"Unknown DGEMM library specified")
656 IF (globenv%run_type_id == 0)
THEN
657 SELECT CASE (globenv%prog_name_id)
661 IF (nforce_eval /= 1)
THEN
667 SELECT CASE (method_name_id)
682 cpabort(
"FARMING program supports only NONE as run type")
685 IF (globenv%prog_name_id ==
do_test .AND. globenv%run_type_id /=
none_run) &
686 cpabort(
"TEST program supports only NONE as run type")
688 CALL m_memory_details(memtotal, memfree, buffers, cached, slab, sreclaimable, memlikelyfree)
689 memtotal_avr = memtotal
690 memfree_avr = memfree
691 buffers_avr = buffers
694 sreclaimable_avr = sreclaimable
695 memlikelyfree_avr = memlikelyfree
696 CALL para_env%sum(memtotal_avr); memtotal_avr = memtotal_avr/para_env%num_pe/1024
697 CALL para_env%sum(memfree_avr); memfree_avr = memfree_avr/para_env%num_pe/1024
698 CALL para_env%sum(buffers_avr); buffers_avr = buffers_avr/para_env%num_pe/1024
699 CALL para_env%sum(cached_avr); cached_avr = cached_avr/para_env%num_pe/1024
700 CALL para_env%sum(slab_avr); slab_avr = slab_avr/para_env%num_pe/1024
701 CALL para_env%sum(sreclaimable_avr); sreclaimable_avr = sreclaimable_avr/para_env%num_pe/1024
702 CALL para_env%sum(memlikelyfree_avr); memlikelyfree_avr = memlikelyfree_avr/para_env%num_pe/1024
704 memtotal_min = -memtotal
705 memfree_min = -memfree
706 buffers_min = -buffers
709 sreclaimable_min = -sreclaimable
710 memlikelyfree_min = -memlikelyfree
711 CALL para_env%max(memtotal_min); memtotal_min = -memtotal_min/1024
712 CALL para_env%max(memfree_min); memfree_min = -memfree_min/1024
713 CALL para_env%max(buffers_min); buffers_min = -buffers_min/1024
714 CALL para_env%max(cached_min); cached_min = -cached_min/1024
715 CALL para_env%max(slab_min); slab_min = -slab_min/1024
716 CALL para_env%max(sreclaimable_min); sreclaimable_min = -sreclaimable_min/1024
717 CALL para_env%max(memlikelyfree_min); memlikelyfree_min = -memlikelyfree_min/1024
719 memtotal_max = memtotal
720 memfree_max = memfree
721 buffers_max = buffers
724 sreclaimable_max = sreclaimable
725 memlikelyfree_max = memlikelyfree
726 CALL para_env%max(memtotal_max); memtotal_max = memtotal_max/1024
727 CALL para_env%max(memfree_max); memfree_max = memfree_max/1024
728 CALL para_env%max(buffers_max); buffers_max = buffers_max/1024
729 CALL para_env%max(cached_max); cached_max = cached_max/1024
730 CALL para_env%max(slab_max); slab_max = slab_max/1024
731 CALL para_env%max(sreclaimable_max); sreclaimable_max = sreclaimable_max/1024
732 CALL para_env%max(memlikelyfree_max); memlikelyfree_max = memlikelyfree_max/1024
734 memtotal = memtotal/1024
735 memfree = memfree/1024
736 buffers = buffers/1024
739 sreclaimable = sreclaimable/1024
740 memlikelyfree = memlikelyfree/1024
743 IF (do_echo_all_hosts)
THEN
744 CALL echo_all_hosts(para_env, output_unit)
747 CALL echo_all_process_host(para_env, output_unit)
752 IF (output_unit > 0)
THEN
753 WRITE (unit=output_unit, fmt=*)
754 CALL multiple_fe_list(force_env_sections, root_section, i_force_eval, nforce_eval)
755 DO iforce_eval = 1, nforce_eval
757 i_rep_section=i_force_eval(iforce_eval))
759 i_rep_section=i_force_eval(iforce_eval))
761 c_val=basis_set_file_name)
763 c_val=potential_file_name)
766 c_val=mm_potential_file_name)
769 i_rep_section=i_force_eval(iforce_eval))
771 coord_file_name =
"__STD_INPUT__"
775 IF (n_rep_val == 1)
THEN
777 c_val=coord_file_name)
782 WRITE (unit=output_unit, fmt=
"(T2,A,T41,A)") &
783 start_section_label//
"| Force Environment number", &
784 adjustr(env_num(:40)), &
785 start_section_label//
"| Basis set file name", &
786 adjustr(basis_set_file_name(:40)), &
787 start_section_label//
"| Potential file name", &
788 adjustr(potential_file_name(:40)), &
789 start_section_label//
"| MM Potential file name", &
790 adjustr(mm_potential_file_name(:40)), &
791 start_section_label//
"| Coordinate file name", &
792 adjustr(coord_file_name(:40))
794 DEALLOCATE (i_force_eval)
796 NULLIFY (enum1, enum2, keyword, section)
803 WRITE (unit=output_unit, fmt=
"(T2,A,T41,A40)") &
804 start_section_label//
"| Method name", &
805 adjustr(trim(
enum_i2c(enum1, globenv%prog_name_id))), &
806 start_section_label//
"| Project name", &
807 adjustr(project_name(:40)), &
808 start_section_label//
"| Run type", &
809 adjustr(trim(
enum_i2c(enum2, globenv%run_type_id))), &
810 start_section_label//
"| FFT library", &
811 adjustr(globenv%default_fft_library(:40)), &
812 start_section_label//
"| Diagonalization library", &
813 adjustr(globenv%diag_library(:40)), &
814 start_section_label//
"| Cholesky decomposition library", &
815 adjustr(globenv%cholesky_library(:40)), &
816 start_section_label//
"| DGEMM library", &
817 adjustr(globenv%default_dgemm_library(:40))
819 IF (globenv%diag_library ==
"ELPA")
THEN
820 WRITE (unit=output_unit, fmt=
"(T2,A,T71,I10)") &
821 start_section_label//
"| Minimum number of eigenvectors for ELPA usage", &
822 globenv%elpa_neigvec_min
825 IF (globenv%diag_library ==
"DLAF")
THEN
826 WRITE (unit=output_unit, fmt=
"(T2,A,T71,I10)") &
827 start_section_label//
"| Minimum number of eigenvectors for DLAF usage", &
828 globenv%dlaf_neigvec_min
831 IF (globenv%cholesky_library ==
"DLAF")
THEN
832 WRITE (unit=output_unit, fmt=
"(T2,A,T71,I10)") &
833 start_section_label//
"| Minimum matrix size for Cholesky decomposition with DLAF", &
834 globenv%dlaf_cholesky_n_min
837#if defined(__CHECK_DIAG)
839 IF (globenv%eps_check_diag < 0.0_dp)
THEN
840 WRITE (unit=output_unit, fmt=
"(T2,A,T71,ES10.3)") &
841 start_section_label//
"| Orthonormality check for eigenvectors enabled", &
844 WRITE (unit=output_unit, fmt=
"(T2,A,T71,ES10.3)") &
845 start_section_label//
"| Orthonormality check for eigenvectors enabled", &
846 globenv%eps_check_diag
849 IF (globenv%eps_check_diag < 0.0_dp)
THEN
850 WRITE (unit=output_unit, fmt=
"(T2,A,T73,A)") &
851 start_section_label//
"| Orthonormality check for eigenvectors", &
854 WRITE (unit=output_unit, fmt=
"(T2,A,T71,ES10.3)") &
855 start_section_label//
"| Orthonormality check for eigenvectors enabled", &
856 globenv%eps_check_diag
863 WRITE (unit=output_unit, fmt=
"(T2,A,T72,A)") &
864 start_section_label//
"| Matrix multiplication library",
"ScaLAPACK"
866 WRITE (unit=output_unit, fmt=
"(T2,A,T76,A)") &
867 start_section_label//
"| Matrix multiplication library",
"COSMA"
871 WRITE (unit=output_unit, fmt=
"(T2,A,T80,L1)") &
872 start_section_label//
"| All-to-all communication in single precision", ata
874 WRITE (unit=output_unit, fmt=
"(T2,A,T80,L1)") &
875 start_section_label//
"| FFTs using library dependent lengths", efl
877 SELECT CASE (print_level)
879 print_level_string =
"SILENT"
881 print_level_string =
" LOW"
883 print_level_string =
"MEDIUM"
885 print_level_string =
" HIGH"
887 print_level_string =
" DEBUG"
889 cpabort(
"Unknown print_level")
893 SELECT CASE (i_grid_backend)
895 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
896 start_section_label//
"| Grid backend",
"AUTO"
898 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
899 start_section_label//
"| Grid backend",
"CPU"
901 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
902 start_section_label//
"| Grid backend",
"DGEMM"
904 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
905 start_section_label//
"| Grid backend",
"GPU"
907 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
908 start_section_label//
"| Grid backend",
"HIP"
910 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
911 start_section_label//
"| Grid backend",
"REF"
914 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
915 start_section_label//
"| Global print level", print_level_string
916 WRITE (unit=output_unit, fmt=
"(T2,A,T75,L6)") &
917 start_section_label//
"| MPI I/O enabled", flag
918 WRITE (unit=output_unit, fmt=
"(T2,A,T75,I6)") &
919 start_section_label//
"| Total number of message passing processes", &
921 start_section_label//
"| Number of threads for this process", &
923 start_section_label//
"| This output is from process", para_env%mepos
926 WRITE (unit=output_unit, fmt=
"(T2,A,T68,A13)") &
927 start_section_label//
"| OpenMP stack size per thread (OMP_STACKSIZE)", &
928 adjustr(omp_stacksize)
931 WRITE (unit=output_unit, fmt=
"(T2,A,T68,A13)") &
932 start_section_label//
"| OpenMP issue trace (CP2K_OMP_TRACE)", &
937 WRITE (unit=output_unit, fmt=
"(T2,A,T30,A51)") &
938 start_section_label//
"| CPU model name", adjustr(trim(model_name))
943 IF ((cpuid > 0) .OR. (cpuid_static > 0))
THEN
944 WRITE (unit=output_unit, fmt=
"(T2,A,T75,I6)") &
945 start_section_label//
"| CPUID", cpuid
946 IF (cpuid /= cpuid_static)
THEN
947 WRITE (unit=output_unit, fmt=
"(T2,A,T75,I6)") &
948 start_section_label//
"| Compiled for CPUID", cpuid_static
955 CALL cp_hint(__location__,
"The compiler target flags ("// &
956 trim(
m_cpuid_name(cpuid_static))//
") used to build this binary cannot exploit "// &
957 "all extensions of this CPU model ("//trim(
m_cpuid_name(cpuid))//
"). "// &
958 "Consider compiler target flags as part of FCFLAGS and CFLAGS (ARCH file).")
961 WRITE (unit=output_unit, fmt=
"()")
962 WRITE (unit=output_unit, fmt=
"(T2,A)")
"MEMORY| system memory details [Kb]"
963 WRITE (unit=output_unit, fmt=
"(T2,A23,4A14)")
"MEMORY| ",
"rank 0",
"min",
"max",
"average"
964 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| MemTotal ", memtotal, memtotal_min, memtotal_max, memtotal_avr
965 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| MemFree ", memfree, memfree_min, memfree_max, memfree_avr
966 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| Buffers ", buffers, buffers_min, buffers_max, buffers_avr
967 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| Cached ", cached, cached_min, cached_max, cached_avr
968 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| Slab ", slab, slab_min, slab_max, slab_avr
969 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)") &
970 "MEMORY| SReclaimable ", sreclaimable, sreclaimable_min, sreclaimable_max, &
972 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)") &
973 "MEMORY| MemLikelyFree ", memlikelyfree, memlikelyfree_min, memlikelyfree_max, &
975 WRITE (unit=output_unit, fmt=
'()')
982 END SUBROUTINE read_global_section
993 SUBROUTINE read_cp2k_section(root_section, para_env, globenv)
999 INTEGER :: output_unit
1004 CALL read_global_section(root_section, para_env, globenv)
1009 CALL fft_setup_library(globenv, global_section)
1010 CALL diag_setup_library(globenv)
1015 END SUBROUTINE read_cp2k_section
1026 SUBROUTINE fft_setup_library(globenv, global_section)
1031 CHARACTER(LEN=3*default_string_length) :: message
1032 COMPLEX(KIND=dp),
DIMENSION(4, 4, 4) :: zz
1034 INTEGER,
DIMENSION(3) :: n
1038 zz(:, :, :) = 0.0_dp
1045 IF (globenv%default_fft_library ==
"FFTW3")
THEN
1052 CALL init_fft(fftlib=trim(globenv%default_fft_library), &
1054 fftsg_sizes=.NOT.
section_get_lval(global_section,
"EXTENDED_FFT_LENGTHS"), &
1055 pool_limit=globenv%fft_pool_scratch_limit, &
1056 wisdom_file=globenv%fftw_wisdom_file_name, &
1057 plan_style=globenv%fftw_plan_type)
1063 message =
"FFT library "//trim(globenv%default_fft_library)// &
1064 " is not available. Trying FFT library FFTW3."
1065 cpwarn(trim(message))
1066 globenv%default_fft_library =
"FFTW3"
1067 CALL init_fft(fftlib=trim(globenv%default_fft_library), &
1069 fftsg_sizes=.NOT.
section_get_lval(global_section,
"EXTENDED_FFT_LENGTHS"), &
1070 pool_limit=globenv%fft_pool_scratch_limit, &
1071 wisdom_file=globenv%fftw_wisdom_file_name, &
1072 plan_style=globenv%fftw_plan_type)
1077 message =
"FFT library "//trim(globenv%default_fft_library)// &
1078 " is not available. Trying FFT library FFTSG."
1079 cpwarn(trim(message))
1080 globenv%default_fft_library =
"FFTSG"
1081 CALL init_fft(fftlib=trim(globenv%default_fft_library), &
1083 fftsg_sizes=.NOT.
section_get_lval(global_section,
"EXTENDED_FFT_LENGTHS"), &
1084 pool_limit=globenv%fft_pool_scratch_limit, &
1085 wisdom_file=globenv%fftw_wisdom_file_name, &
1086 plan_style=globenv%fftw_plan_type)
1090 cpabort(
"FFT library FFTSG does not work. No FFT library available.")
1095 END SUBROUTINE fft_setup_library
1103 SUBROUTINE diag_setup_library(globenv)
1106 CHARACTER(LEN=3*default_string_length) :: message
1107 LOGICAL :: fallback_applied
1109 CALL diag_init(diag_lib=trim(globenv%diag_library), &
1110 fallback_applied=fallback_applied, &
1111 elpa_kernel=globenv%k_elpa, &
1112 elpa_neigvec_min_input=globenv%elpa_neigvec_min, &
1113 elpa_qr=globenv%elpa_qr, &
1114 elpa_print=globenv%elpa_print, &
1115 elpa_qr_unsafe=globenv%elpa_qr_unsafe, &
1116 dlaf_neigvec_min_input=globenv%dlaf_neigvec_min, &
1117 eps_check_diag_input=globenv%eps_check_diag)
1119 IF (fallback_applied)
THEN
1120 message =
"Diagonalization library "//trim(globenv%diag_library)// &
1121 " is not available. The ScaLAPACK library is used as fallback."
1122 cpwarn(trim(message))
1125 END SUBROUTINE diag_setup_library
1131 SUBROUTINE fm_setup(glob_section)
1134 INTEGER :: mm_type, ncb, nrb
1148 END SUBROUTINE fm_setup
1154 SUBROUTINE dgemm_setup(glob_section)
1157 INTEGER :: dgemm_type
1163 END SUBROUTINE dgemm_setup
1171 SUBROUTINE fm_diag_rules_setup(glob_section)
1175 LOGICAL :: elpa_force_redistribute, should_print
1187 END SUBROUTINE fm_diag_rules_setup
1199 CHARACTER(LEN=*),
INTENT(in) :: keyword_name
1200 REAL(kind=
dp),
INTENT(out) :: walltime
1202 CHARACTER(LEN=1) :: c1, c2
1203 CHARACTER(LEN=100) :: txt
1204 INTEGER :: hours, ierr, minutes, n,
seconds
1211 ELSE IF (index(txt,
":") == 0)
THEN
1212 READ (txt(1:n), fmt=*, iostat=ierr) walltime
1213 IF (ierr /= 0) cpabort(
'Could not parse WALLTIME: "'//txt(1:n)//
'"')
1215 READ (txt(1:n), fmt=
"(I2,A1,I2,A1,I2)", iostat=ierr) hours, c1, minutes, c2,
seconds
1216 IF (n /= 8 .OR. ierr /= 0 .OR. c1 .NE.
":" .OR. c2 .NE.
":") &
1217 cpabort(
'Could not parse WALLTIME: "'//txt(1:n)//
'"')
1218 walltime = 3600.0_dp*real(hours,
dp) + 60.0_dp*real(minutes,
dp) + real(
seconds,
dp)
1244 CHARACTER(LEN=*),
OPTIONAL :: wdir
1245 LOGICAL,
INTENT(IN),
OPTIONAL :: q_finalize
1247 CHARACTER(LEN=default_path_length) :: cg_filename
1248 INTEGER :: cg_mode, iw, unit_exit
1249 LOGICAL :: delete_it, do_finalize, report_maxloc, &
1251 REAL(kind=
dp) :: r_timings
1258 do_finalize = .true.
1259 IF (
PRESENT(q_finalize)) do_finalize = q_finalize
1263 IF (do_finalize)
THEN
1269 CALL finalize_fft(para_env, globenv%fftw_wisdom_file_name)
1279 "GLOBAL%PROGRAM_RUN_INFO")
1285 WRITE (unit=iw, fmt=
"(/,T2,A)") repeat(
"-", 79)
1286 WRITE (unit=iw, fmt=
"(T2,A,T80,A)")
"-",
"-"
1287 WRITE (unit=iw, fmt=
"(T2,A,T30,A,T80,A)")
"-",
"R E F E R E N C E S",
"-"
1288 WRITE (unit=iw, fmt=
"(T2,A,T80,A)")
"-",
"-"
1289 WRITE (unit=iw, fmt=
"(T2,A)") repeat(
"-", 79)
1290 WRITE (unit=iw, fmt=
"(T2,A)")
""
1291 WRITE (unit=iw, fmt=
"(T2,A)") trim(
cp2k_version)//
", the CP2K developers group ("//trim(
cp2k_year)//
")."
1292 WRITE (unit=iw, fmt=
"(T2,A)")
"CP2K is freely available from "//trim(
cp2k_home)//
" ."
1293 WRITE (unit=iw, fmt=
"(T2,A)")
""
1297 "GLOBAL%REFERENCES")
1299 CALL timestop(globenv%handle)
1304 sort_by_self_time =
section_get_lval(root_section,
"GLOBAL%TIMINGS%SORT_BY_SELF_TIME")
1305 report_maxloc =
section_get_lval(root_section,
"GLOBAL%TIMINGS%REPORT_MAXLOC")
1315 IF (len_trim(cg_filename) == 0) cg_filename = trim(logger%iter_info%project_name)
1317 cg_filename = trim(cg_filename)//
"_"//trim(adjustl(
cp_to_string(para_env%mepos)))
1319 WRITE (unit=iw, fmt=
"(T2,3X,A)")
"Writing callgraph to: "//trim(cg_filename)//
".callgraph"
1320 WRITE (unit=iw, fmt=
"()")
1321 WRITE (unit=iw, fmt=
"(T2,A)")
"-------------------------------------------------------------------------------"
1333 IF (para_env%is_source())
THEN
1339 INQUIRE (file=
"EXIT", exist=delete_it)
1341 CALL open_file(file_name=
"EXIT", unit_number=unit_exit)
1342 CALL close_file(unit_number=unit_exit, file_status=
"DELETE")
1346 INQUIRE (file=trim(logger%iter_info%project_name)//
".EXIT", exist=delete_it)
1348 CALL open_file(file_name=trim(logger%iter_info%project_name)//
".EXIT", unit_number=unit_exit)
1349 CALL close_file(unit_number=unit_exit, file_status=
"DELETE")
1355 WRITE (iw,
"(T2,A,I0)")
"The number of traced issues for OpenMP : ",
m_omp_trace_issues()
1357 WRITE (iw,
"(T2,A,I0)")
"The number of warnings for this run is : ",
warning_counter
1359 WRITE (unit=iw, fmt=
"(T2,A)") repeat(
"-", 79)
1367 IF (iw > 0)
FLUSH (iw)
1370 "GLOBAL%PROGRAM_RUN_INFO")
Target architecture or instruction set extension according to compiler target flags.
Trace OpenMP constructs if ennvironment variable CP2K_OMP_TRACE=1.
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public marek2014
integer, save, public solca2024
integer, save, public frigo2005
some minimal info about CP2K, including its version and license
character(len=default_string_length), public r_host_name
character(len= *), parameter, public cp2k_home
character(len= *), parameter, public compile_host
character(len= *), parameter, public compile_arch
character(len= *), parameter, public compile_revision
character(len= *), parameter, public compile_date
character(len= *), parameter, public cp2k_year
character(len=10 *default_string_length) function, public cp2k_flags()
list all compile time options that influence the capabilities of cp2k. All new flags should be added ...
character(len= *), parameter, public cp2k_version
subroutine, public get_runtime_info()
...
character(len=default_string_length), public r_user_name
Module that contains the routines for error handling.
integer, save, public warning_counter
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.
character(len=default_path_length) function, public get_data_dir()
Returns path of data directory if set, otherwise an empty string.
various cholesky decomposition related routines
integer, parameter, public fm_cholesky_type_dlaf
integer, parameter, public fm_cholesky_type_scalapack
integer, save, public dlaf_cholesky_n_min
integer, save, public cholesky_type
Auxiliary tools to redistribute cp_fm_type matrices before and after diagonalization....
subroutine, public cp_fm_redistribute_init(a, x, should_print, elpa_force_redistribute)
Initializes the parameters that determine how to calculate the optimal number of CPUs for diagonalizi...
used for collecting some of the diagonalization schemes available for cp_fm_type. cp_fm_power also mo...
real(kind=dp), parameter, public eps_check_diag_default
integer, parameter, public fm_diag_type_cusolver
integer, parameter, public fm_diag_type_dlaf
integer, parameter, public fm_diag_type_scalapack
subroutine, public diag_finalize()
Finalize the diagonalization library.
subroutine, public diag_init(diag_lib, fallback_applied, elpa_kernel, elpa_neigvec_min_input, elpa_qr, elpa_print, elpa_qr_unsafe, dlaf_neigvec_min_input, eps_check_diag_input)
Setup the diagonalization library to be used.
integer, parameter, public fm_diag_type_elpa
represent the structure of a full matrix
subroutine, public cp_fm_struct_config(nrow_block, ncol_block, force_block)
allows to modify the default settings for matrix creation
represent a full matrix distributed on many processors
integer function, public cp_fm_get_mm_type()
...
subroutine, public cp_fm_setup(mm_type)
...
various routines to log and control the output. The idea is that decisions about where to log should ...
recursive integer function, public cp_logger_get_default_unit_nr(logger, local, skip_not_ionode)
asks the default unit number of the given logger. try to use cp_logger_get_unit_nr
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
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
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
subroutine, public cp_mpi_io_set(flag)
Sets flag which determines whether or not to use MPI I/O for I/O routines that have been parallized w...
integer, parameter, public debug_print_level
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
integer, parameter, public low_print_level
integer, parameter, public medium_print_level
subroutine, public cp_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, on_file, mpi_io)
should be called after you finish working with a unit obtained with cp_print_key_unit_nr,...
integer, parameter, public high_print_level
integer, parameter, public silent_print_level
Sets up and terminates the global environment variables.
subroutine, public cp2k_finalize(root_section, para_env, globenv, wdir, q_finalize)
Writes final timings and banner for CP2K.
subroutine, public cp2k_read(root_section, para_env, globenv)
read part of cp2k_init
subroutine, public cp2k_get_walltime(section, keyword_name, walltime)
reads the Walltime also in format HH:MM:SS
subroutine, public cp2k_init(para_env, output_unit, globenv, input_file_name, wdir)
Initializes a CP2K run (setting of the global environment variables)
subroutine, public cp2k_setup(root_section, para_env, globenv)
globenv initializations that need the input and error
Interface for the force calculations.
subroutine, public multiple_fe_list(force_env_sections, root_section, i_force_eval, nforce_eval)
returns the order of the multiple force_env
Calculation of the incomplete Gamma function F_n(t) for multi-center integrals over Cartesian Gaussia...
subroutine, public deallocate_md_ftable()
Deallocate the table of F_n(t) values.
Define type storing the global information of a run. Keep the amount of stored data small....
Fortran API for the grid package, which is written in C.
integer, parameter, public grid_backend_auto
integer, parameter, public grid_backend_gpu
integer, parameter, public grid_backend_hip
integer, parameter, public grid_backend_dgemm
integer, parameter, public grid_backend_cpu
integer, parameter, public grid_backend_ref
Defines the basic variable types.
integer, parameter, public int_8
integer, parameter, public dp
integer, parameter, public default_string_length
integer, parameter, public default_path_length
subroutine, public print_kind_info(iw)
Print informations about the used data types.
subroutine, public local_gemm_set_library(dgemm_library)
...
Machine interface based on Fortran 2003 and POSIX.
logical, save, public flush_should_flush
integer function, public m_procrun(pid)
Returns if a process is running on the local machine 1 if yes and 0 if not.
subroutine, public m_memory_details(memtotal, memfree, buffers, cached, slab, sreclaimable, memlikelyfree)
get more detailed memory info, all units are bytes. the only 'useful' option is MemLikelyFree which i...
pure integer function, public m_cpuid()
Target architecture or instruction set extension according to CPU-check at runtime.
pure integer function, public m_cpuid_vlen(cpuid, typesize)
Determine vector-length for a given CPUID.
real(kind=dp) function, public m_energy()
returns the energy used since some time in the past. The precise meaning depends on the infrastructur...
subroutine, public m_cpuinfo(model_name)
reads /proc/cpuinfo if it exists (i.e. Linux) to return relevant info
pure character(len=default_string_length) function, public m_cpuid_name(cpuid)
Determine name of target architecture for a given CPUID.
subroutine, public m_omp_get_stacksize(omp_stacksize)
Retrieve environment variable OMP_STACKSIZE.
Interface to the message passing library MPI.
logical, save, public mp_collect_timings
Defines all routines to deal with the performance of MPI routines.
subroutine, public rm_mp_perf_env()
...
subroutine, public describe_mp_perf_env(scr)
...
subroutine, public add_mp_perf_env(perf_env)
start and stop the performance indicators for every call to start there has to be (exactly) one call ...
Provides Cartesian and spherical orbital pointers and indices.
subroutine, public init_orbital_pointers(maxl)
Initialize or update the orbital pointers.
subroutine, public deallocate_orbital_pointers()
Deallocate the orbital pointers.
Parallel (pseudo)random number generator (RNG) for multiple streams and substreams of random numbers.
subroutine, public check_rng(output_unit, ionode)
...
subroutine, public write_rng_matrices(output_unit)
Write the transformation matrices of the two MRG components (raised to the specified output)
integer, parameter, public gaussian
Definition of physical constants:
real(kind=dp), parameter, public seconds
subroutine, public write_physcon(output_unit)
Write all basic physical constants used by CP2K to a logical output unit.
provides a uniform framework to add references to CP2K cite and output these
subroutine, public collect_citations_from_ranks(para_env)
Checks for each reference if any mpi-rank has marked it for citation.
subroutine, public cite_reference(key)
marks a given reference as cited.
subroutine, public print_cited_references(unit)
printout of all cited references in the journal format sorted by publication year
Utilities for string manipulations.
subroutine, public integer_to_string(inumber, string)
Converts an integer number to a string. The WRITE statement will return an error message,...
subroutine, public string_to_ascii(string, nascii)
Convert a string to sequence of integer numbers.
subroutine, public ascii_to_string(nascii, string)
Convert a sequence of integer numbers (ASCII code) to a string. Blanks are inserted for invalid ASCII...
Timing routines for accounting.
integer, parameter, public cost_type_energy
subroutine, public timings_report_callgraph(filename)
Write accumulated callgraph information as cachegrind-file. http://kcachegrind.sourceforge....
integer, parameter, public cost_type_time
subroutine, public timings_report_print(iw, r_timings, sort_by_self_time, cost_type, report_maxloc, para_env)
Print accumulated information on timers.
Timing routines for accounting.
integer, save, public global_timings_level
subroutine, public timings_setup_tracing(trace_max, unit_nr, trace_str, routine_names)
Set routine tracer.
subroutine, public add_timer_env(timer_env)
adds the given timer_env to the top of the stack
subroutine, public rm_timer_env()
removes the current timer env from the stack
character(len=default_string_length), parameter, public root_cp2k_name
Interface for Voronoi Integration and output of BQB files.
subroutine, public finalize_libvori()
Call libvori's finalize if support is compiled in.
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