120#include "./base/base_uses.f90"
126 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'environment'
147 SUBROUTINE cp2k_init(para_env, output_unit, globenv, input_file_name, wdir)
150 INTEGER :: output_unit
152 CHARACTER(LEN=*) :: input_file_name
153 CHARACTER(LEN=*),
OPTIONAL :: wdir
155 CHARACTER(LEN=10*default_string_length) :: cp_flags
156 INTEGER :: i, ilen, my_output_unit
167 IF (para_env%is_source())
THEN
168 my_output_unit = output_unit
174 default_global_unit_nr=output_unit, &
175 close_global_unit_on_dealloc=.false.)
185 IF (my_output_unit > 0)
THEN
186 WRITE (unit=my_output_unit, fmt=
"(/,T2,A,T31,A50)") &
188 WRITE (unit=my_output_unit, fmt=
"(T2,A,T41,A40)") &
189 "CP2K| source code revision number:", &
192 ilen = len_trim(cp_flags)
193 WRITE (unit=my_output_unit, fmt=
"(T2,A)") &
194 "CP2K| "//cp_flags(1:73)
196 DO i = 0, (ilen - 75)/61
197 WRITE (unit=my_output_unit, fmt=
"(T2,A)") &
198 "CP2K| "//trim(cp_flags(74 + i*61:min(74 + (i + 1)*61, ilen)))
201 WRITE (unit=my_output_unit, fmt=
"(T2,A,T41,A40)") &
202 "CP2K| is freely available from ", &
204 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
205 "CP2K| Program compiled at", &
207 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
208 "CP2K| Program compiled on", &
210 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
211 "CP2K| Program compiled for", &
213 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
214 "CP2K| Data directory path", &
216 WRITE (unit=my_output_unit, fmt=
"(T2,A,T31,A50)") &
217 "CP2K| Input file name", &
218 adjustr(trim(input_file_name))
219 FLUSH (my_output_unit)
222#if defined(__FAST_MATH__)
223 CALL cp_warn(__location__, &
224 "During compilation one of the following flags was active:"// &
225 " `-ffast-math` (GCC)"// &
226 " `-hfpN` (Cray, N > 0, default N=2)"// &
227 " This can lead to wrong results and numerical instabilities"// &
228 " and is therefore no longer supported.")
230#if !defined(__FORCE_USE_FAST_MATH)
231#error "-ffast-math (GCC) or -hfpN (N>0, Cray) can lead to wrong results and numerical instabilities and are therefore no longer supported"
236#error "Please do not build CP2K with NDEBUG. There is no performance advantage and asserts will save your neck."
246 SUBROUTINE echo_all_hosts(para_env, output_unit)
248 INTEGER :: output_unit
250 CHARACTER(LEN=default_string_length) :: string
252 INTEGER,
ALLOCATABLE,
DIMENSION(:) :: all_pid
253 INTEGER,
ALLOCATABLE,
DIMENSION(:, :) :: all_host
257 ALLOCATE (all_pid(para_env%num_pe))
259 all_pid(para_env%mepos + 1) =
r_pid
261 CALL para_env%sum(all_pid)
262 ALLOCATE (all_host(30, para_env%num_pe))
265 CALL para_env%sum(all_host)
266 IF (output_unit > 0)
THEN
268 WRITE (unit=output_unit, fmt=
"(T2,A)")
""
269 DO ipe = 1, para_env%num_pe
271 WRITE (unit=output_unit, fmt=
"(T2,A,T63,I8,T71,I10)") &
273 " has created rank and process ", ipe - 1, all_pid(ipe)
275 WRITE (unit=output_unit, fmt=
"(T2,A)")
""
278 DEALLOCATE (all_host)
280 END SUBROUTINE echo_all_hosts
287 SUBROUTINE echo_all_process_host(para_env, output_unit)
289 INTEGER :: output_unit
291 CHARACTER(LEN=default_string_length) :: string, string_sec
292 INTEGER :: ipe, jpe, nr_occu
293 INTEGER,
ALLOCATABLE,
DIMENSION(:) :: all_pid
294 INTEGER,
ALLOCATABLE,
DIMENSION(:, :) :: all_host
296 ALLOCATE (all_host(30, para_env%num_pe))
301 CALL para_env%sum(all_host)
304 IF (output_unit > 0)
THEN
305 ALLOCATE (all_pid(para_env%num_pe))
308 WRITE (unit=output_unit, fmt=
"(T2,A)")
""
309 DO ipe = 1, para_env%num_pe
311 IF (all_pid(ipe) .NE. -1)
THEN
313 DO jpe = 1, para_env%num_pe
315 IF (string .EQ. string_sec)
THEN
316 nr_occu = nr_occu + 1
320 WRITE (unit=output_unit, fmt=
"(T2,A,T63,I8,A)") &
322 " is running ", nr_occu,
" processes"
323 WRITE (unit=output_unit, fmt=
"(T2,A)")
""
330 DEALLOCATE (all_host)
332 END SUBROUTINE echo_all_process_host
353 CHARACTER(LEN=3*default_string_length) :: message
354 CHARACTER(LEN=default_string_length) :: c_val
365 IF (c_val /=
"")
THEN
367 local_filename=trim(c_val)//
"_localLog")
372 IF (index(c_val(:len_trim(c_val)),
" ") > 0)
THEN
373 message =
"Project name <"//trim(c_val)// &
374 "> contains spaces which will be replaced with underscores"
375 cpwarn(trim(message))
376 DO i = 1, len_trim(c_val)
378 IF (c_val(i:i) ==
" ") c_val(i:i) =
"_"
382 IF (c_val /=
"")
THEN
383 CALL cp_logger_set(logger, local_filename=trim(c_val)//
"_localLog")
385 logger%iter_info%project_name = c_val
387 CALL section_vals_val_get(root_section,
"GLOBAL%PRINT_LEVEL", i_val=logger%iter_info%print_level)
390 CALL read_cp2k_section(root_section, para_env, globenv)
396 "GLOBAL%PRINT/BASIC_DATA_TYPES")
402 "GLOBAL%PRINT/PHYSCON")
423 INTEGER,
DIMENSION(:),
POINTER :: seed_vals
424 REAL(kind=
dp),
DIMENSION(3, 2) :: initial_seed
439 "GLOBAL%PRINT/RNG_MATRICES")
444 IF (
SIZE(seed_vals) == 1)
THEN
445 initial_seed(:, :) = real(seed_vals(1), kind=
dp)
446 ELSE IF (
SIZE(seed_vals) == 6)
THEN
447 initial_seed(1:3, 1:2) = reshape(real(seed_vals(:), kind=
dp), (/3, 2/))
449 cpabort(
"Supply exactly 1 or 6 arguments for SEED in &GLOBAL only!")
453 name=
"Global Gaussian random numbers", &
456 extended_precision=.true.)
465 "GLOBAL%PRINT/RNG_CHECK")
470 CALL globenv%gaussian_rng_stream%write(iw, write_all=.true.)
473 "GLOBAL%PRINT/GLOBAL_GAUSSIAN_RNG")
501 SUBROUTINE read_global_section(root_section, para_env, globenv)
507 CHARACTER(LEN=6),
PARAMETER :: start_section_label =
"GLOBAL"
509 CHARACTER(LEN=13) :: omp_stacksize, tracing_string
510 CHARACTER(LEN=6) :: print_level_string
511 CHARACTER(LEN=default_path_length) :: basis_set_file_name, coord_file_name, &
512 mm_potential_file_name, &
514 CHARACTER(LEN=default_string_length) :: env_num, model_name, project_name
515 CHARACTER(LEN=default_string_length), &
516 DIMENSION(:),
POINTER :: trace_routines
517 INTEGER :: cpuid, cpuid_static, i_dgemm, i_diag, i_fft, i_grid_backend, iforce_eval, &
518 method_name_id, n_rep_val, nforce_eval, num_threads, output_unit, print_level, trace_max, &
520 INTEGER(kind=int_8) :: buffers, buffers_avr, buffers_max, buffers_min, cached, cached_avr, &
521 cached_max, cached_min, memfree, memfree_avr, memfree_max, memfree_min, memlikelyfree, &
522 memlikelyfree_avr, memlikelyfree_max, memlikelyfree_min, memtotal, memtotal_avr, &
523 memtotal_max, memtotal_min, slab, slab_avr, slab_max, slab_min, sreclaimable, &
524 sreclaimable_avr, sreclaimable_max, sreclaimable_min
525 INTEGER,
DIMENSION(:),
POINTER :: i_force_eval
526 LOGICAL :: ata, do_echo_all_hosts, efl, explicit, &
527 flag, report_maxloc, trace, &
534 global_section, qmmm_section, &
537 NULLIFY (dft_section, global_section, i_force_eval)
553 IF (unit_nr > 0) globenv%elpa_print = .true.
559 CALL section_vals_val_get(global_section,
"FFT_POOL_SCRATCH_LIMIT", i_val=globenv%fft_pool_scratch_limit)
562 CALL section_vals_val_get(global_section,
"FFTW_WISDOM_FILE_NAME", c_val=globenv%fftw_wisdom_file_name)
565 walltime=globenv%cp2k_target_time)
573 NULLIFY (trace_routines)
579 do_echo_all_hosts = do_echo_all_hosts .OR. report_maxloc
585 CALL fm_setup(global_section)
586 CALL fm_diag_rules_setup(global_section)
587 CALL dgemm_setup(global_section)
589 IF (trace .AND. (.NOT. trace_master .OR. para_env%mepos == 0))
THEN
591 IF (logger%para_env%is_source() .OR. .NOT. trace_master) &
593 WRITE (tracing_string,
"(I6.6,A1,I6.6)") para_env%mepos,
":", para_env%num_pe
594 IF (
ASSOCIATED(trace_routines))
THEN
605 globenv%diag_library =
"ScaLAPACK"
607 globenv%diag_library =
"ELPA"
610 globenv%diag_library =
"cuSOLVER"
612 globenv%diag_library =
"DLAF"
615 cpabort(
"Unknown diagonalization library specified")
620 globenv%default_fft_library =
"FFTSG"
622 globenv%default_fft_library =
"FFTW3"
625 cpabort(
"Unknown FFT library specified")
628 SELECT CASE (i_dgemm)
630 globenv%default_dgemm_library =
"SPLA"
632 globenv%default_dgemm_library =
"BLAS"
634 cpabort(
"Unknown DGEMM library specified")
637 IF (globenv%run_type_id == 0)
THEN
638 SELECT CASE (globenv%prog_name_id)
642 IF (nforce_eval /= 1)
THEN
648 SELECT CASE (method_name_id)
663 cpabort(
"FARMING program supports only NONE as run type")
666 IF (globenv%prog_name_id ==
do_test .AND. globenv%run_type_id /=
none_run) &
667 cpabort(
"TEST program supports only NONE as run type")
669 CALL m_memory_details(memtotal, memfree, buffers, cached, slab, sreclaimable, memlikelyfree)
670 memtotal_avr = memtotal
671 memfree_avr = memfree
672 buffers_avr = buffers
675 sreclaimable_avr = sreclaimable
676 memlikelyfree_avr = memlikelyfree
677 CALL para_env%sum(memtotal_avr); memtotal_avr = memtotal_avr/para_env%num_pe/1024
678 CALL para_env%sum(memfree_avr); memfree_avr = memfree_avr/para_env%num_pe/1024
679 CALL para_env%sum(buffers_avr); buffers_avr = buffers_avr/para_env%num_pe/1024
680 CALL para_env%sum(cached_avr); cached_avr = cached_avr/para_env%num_pe/1024
681 CALL para_env%sum(slab_avr); slab_avr = slab_avr/para_env%num_pe/1024
682 CALL para_env%sum(sreclaimable_avr); sreclaimable_avr = sreclaimable_avr/para_env%num_pe/1024
683 CALL para_env%sum(memlikelyfree_avr); memlikelyfree_avr = memlikelyfree_avr/para_env%num_pe/1024
685 memtotal_min = -memtotal
686 memfree_min = -memfree
687 buffers_min = -buffers
690 sreclaimable_min = -sreclaimable
691 memlikelyfree_min = -memlikelyfree
692 CALL para_env%max(memtotal_min); memtotal_min = -memtotal_min/1024
693 CALL para_env%max(memfree_min); memfree_min = -memfree_min/1024
694 CALL para_env%max(buffers_min); buffers_min = -buffers_min/1024
695 CALL para_env%max(cached_min); cached_min = -cached_min/1024
696 CALL para_env%max(slab_min); slab_min = -slab_min/1024
697 CALL para_env%max(sreclaimable_min); sreclaimable_min = -sreclaimable_min/1024
698 CALL para_env%max(memlikelyfree_min); memlikelyfree_min = -memlikelyfree_min/1024
700 memtotal_max = memtotal
701 memfree_max = memfree
702 buffers_max = buffers
705 sreclaimable_max = sreclaimable
706 memlikelyfree_max = memlikelyfree
707 CALL para_env%max(memtotal_max); memtotal_max = memtotal_max/1024
708 CALL para_env%max(memfree_max); memfree_max = memfree_max/1024
709 CALL para_env%max(buffers_max); buffers_max = buffers_max/1024
710 CALL para_env%max(cached_max); cached_max = cached_max/1024
711 CALL para_env%max(slab_max); slab_max = slab_max/1024
712 CALL para_env%max(sreclaimable_max); sreclaimable_max = sreclaimable_max/1024
713 CALL para_env%max(memlikelyfree_max); memlikelyfree_max = memlikelyfree_max/1024
715 memtotal = memtotal/1024
716 memfree = memfree/1024
717 buffers = buffers/1024
720 sreclaimable = sreclaimable/1024
721 memlikelyfree = memlikelyfree/1024
724 IF (do_echo_all_hosts)
THEN
725 CALL echo_all_hosts(para_env, output_unit)
728 CALL echo_all_process_host(para_env, output_unit)
733 IF (output_unit > 0)
THEN
734 WRITE (unit=output_unit, fmt=*)
735 CALL multiple_fe_list(force_env_sections, root_section, i_force_eval, nforce_eval)
736 DO iforce_eval = 1, nforce_eval
738 i_rep_section=i_force_eval(iforce_eval))
740 i_rep_section=i_force_eval(iforce_eval))
742 c_val=basis_set_file_name)
744 c_val=potential_file_name)
747 c_val=mm_potential_file_name)
750 i_rep_section=i_force_eval(iforce_eval))
752 coord_file_name =
"__STD_INPUT__"
756 IF (n_rep_val == 1)
THEN
758 c_val=coord_file_name)
763 WRITE (unit=output_unit, fmt=
"(T2,A,T41,A)") &
764 start_section_label//
"| Force Environment number", &
765 adjustr(env_num(:40)), &
766 start_section_label//
"| Basis set file name", &
767 adjustr(basis_set_file_name(:40)), &
768 start_section_label//
"| Potential file name", &
769 adjustr(potential_file_name(:40)), &
770 start_section_label//
"| MM Potential file name", &
771 adjustr(mm_potential_file_name(:40)), &
772 start_section_label//
"| Coordinate file name", &
773 adjustr(coord_file_name(:40))
775 DEALLOCATE (i_force_eval)
777 NULLIFY (enum1, enum2, keyword, section)
784 WRITE (unit=output_unit, fmt=
"(T2,A,T41,A40)") &
785 start_section_label//
"| Method name", &
786 adjustr(trim(
enum_i2c(enum1, globenv%prog_name_id))), &
787 start_section_label//
"| Project name", &
788 adjustr(project_name(:40)), &
789 start_section_label//
"| Run type", &
790 adjustr(trim(
enum_i2c(enum2, globenv%run_type_id))), &
791 start_section_label//
"| FFT library", &
792 adjustr(globenv%default_fft_library(:40)), &
793 start_section_label//
"| Diagonalization library", &
794 adjustr(globenv%diag_library(:40)), &
795 start_section_label//
"| DGEMM library", &
796 adjustr(globenv%default_dgemm_library(:40))
798 IF (globenv%diag_library ==
"ELPA")
THEN
799 WRITE (unit=output_unit, fmt=
"(T2,A,T71,I10)") &
800 start_section_label//
"| Minimum number of eigenvectors for ELPA usage", &
801 globenv%elpa_neigvec_min
804 IF (globenv%diag_library ==
"DLAF")
THEN
805 WRITE (unit=output_unit, fmt=
"(T2,A,T71,I10)") &
806 start_section_label//
"| Minimum number of eigenvectors for DLAF usage", &
807 globenv%dlaf_neigvec_min
810#if defined(__CHECK_DIAG)
812 IF (globenv%eps_check_diag < 0.0_dp)
THEN
813 WRITE (unit=output_unit, fmt=
"(T2,A,T71,ES10.3)") &
814 start_section_label//
"| Orthonormality check for eigenvectors enabled", &
817 WRITE (unit=output_unit, fmt=
"(T2,A,T71,ES10.3)") &
818 start_section_label//
"| Orthonormality check for eigenvectors enabled", &
819 globenv%eps_check_diag
822 IF (globenv%eps_check_diag < 0.0_dp)
THEN
823 WRITE (unit=output_unit, fmt=
"(T2,A,T73,A)") &
824 start_section_label//
"| Orthonormality check for eigenvectors", &
827 WRITE (unit=output_unit, fmt=
"(T2,A,T71,ES10.3)") &
828 start_section_label//
"| Orthonormality check for eigenvectors enabled", &
829 globenv%eps_check_diag
836 WRITE (unit=output_unit, fmt=
"(T2,A,T72,A)") &
837 start_section_label//
"| Matrix multiplication library",
"ScaLAPACK"
839 WRITE (unit=output_unit, fmt=
"(T2,A,T76,A)") &
840 start_section_label//
"| Matrix multiplication library",
"COSMA"
844 WRITE (unit=output_unit, fmt=
"(T2,A,T80,L1)") &
845 start_section_label//
"| All-to-all communication in single precision", ata
847 WRITE (unit=output_unit, fmt=
"(T2,A,T80,L1)") &
848 start_section_label//
"| FFTs using library dependent lengths", efl
850 SELECT CASE (print_level)
852 print_level_string =
"SILENT"
854 print_level_string =
" LOW"
856 print_level_string =
"MEDIUM"
858 print_level_string =
" HIGH"
860 print_level_string =
" DEBUG"
862 cpabort(
"Unknown print_level")
866 SELECT CASE (i_grid_backend)
868 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
869 start_section_label//
"| Grid backend",
"AUTO"
871 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
872 start_section_label//
"| Grid backend",
"CPU"
874 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
875 start_section_label//
"| Grid backend",
"DGEMM"
877 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
878 start_section_label//
"| Grid backend",
"GPU"
880 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
881 start_section_label//
"| Grid backend",
"HIP"
883 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
884 start_section_label//
"| Grid backend",
"REF"
887 WRITE (unit=output_unit, fmt=
"(T2,A,T75,A6)") &
888 start_section_label//
"| Global print level", print_level_string
889 WRITE (unit=output_unit, fmt=
"(T2,A,T75,L6)") &
890 start_section_label//
"| MPI I/O enabled", flag
891 WRITE (unit=output_unit, fmt=
"(T2,A,T75,I6)") &
892 start_section_label//
"| Total number of message passing processes", &
894 start_section_label//
"| Number of threads for this process", &
896 start_section_label//
"| This output is from process", para_env%mepos
899 WRITE (unit=output_unit, fmt=
"(T2,A,T68,A13)") &
900 start_section_label//
"| OpenMP stack size per thread (OMP_STACKSIZE)", &
901 adjustr(omp_stacksize)
904 WRITE (unit=output_unit, fmt=
"(T2,A,T68,A13)") &
905 start_section_label//
"| OpenMP issue trace (CP2K_OMP_TRACE)", &
910 WRITE (unit=output_unit, fmt=
"(T2,A,T30,A51)") &
911 start_section_label//
"| CPU model name", adjustr(trim(model_name))
916 IF ((cpuid > 0) .OR. (cpuid_static > 0))
THEN
917 WRITE (unit=output_unit, fmt=
"(T2,A,T75,I6)") &
918 start_section_label//
"| CPUID", cpuid
919 IF (cpuid /= cpuid_static)
THEN
920 WRITE (unit=output_unit, fmt=
"(T2,A,T75,I6)") &
921 start_section_label//
"| Compiled for CPUID", cpuid_static
928 CALL cp_hint(__location__,
"The compiler target flags ("// &
929 trim(
m_cpuid_name(cpuid_static))//
") used to build this binary cannot exploit "// &
930 "all extensions of this CPU model ("//trim(
m_cpuid_name(cpuid))//
"). "// &
931 "Consider compiler target flags as part of FCFLAGS and CFLAGS (ARCH file).")
934 WRITE (unit=output_unit, fmt=
"()")
935 WRITE (unit=output_unit, fmt=
"(T2,A)")
"MEMORY| system memory details [Kb]"
936 WRITE (unit=output_unit, fmt=
"(T2,A23,4A14)")
"MEMORY| ",
"rank 0",
"min",
"max",
"average"
937 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| MemTotal ", memtotal, memtotal_min, memtotal_max, memtotal_avr
938 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| MemFree ", memfree, memfree_min, memfree_max, memfree_avr
939 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| Buffers ", buffers, buffers_min, buffers_max, buffers_avr
940 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| Cached ", cached, cached_min, cached_max, cached_avr
941 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)")
"MEMORY| Slab ", slab, slab_min, slab_max, slab_avr
942 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)") &
943 "MEMORY| SReclaimable ", sreclaimable, sreclaimable_min, sreclaimable_max, &
945 WRITE (unit=output_unit, fmt=
"(T2,A23,4I14)") &
946 "MEMORY| MemLikelyFree ", memlikelyfree, memlikelyfree_min, memlikelyfree_max, &
948 WRITE (unit=output_unit, fmt=
'()')
955 END SUBROUTINE read_global_section
966 SUBROUTINE read_cp2k_section(root_section, para_env, globenv)
972 INTEGER :: output_unit
977 CALL read_global_section(root_section, para_env, globenv)
982 CALL fft_setup_library(globenv, global_section)
983 CALL diag_setup_library(globenv)
988 END SUBROUTINE read_cp2k_section
999 SUBROUTINE fft_setup_library(globenv, global_section)
1004 CHARACTER(LEN=3*default_string_length) :: message
1005 COMPLEX(KIND=dp),
DIMENSION(4, 4, 4) :: zz
1007 INTEGER,
DIMENSION(3) :: n
1011 zz(:, :, :) = 0.0_dp
1018 IF (globenv%default_fft_library ==
"FFTW3")
THEN
1025 CALL init_fft(fftlib=trim(globenv%default_fft_library), &
1027 fftsg_sizes=.NOT.
section_get_lval(global_section,
"EXTENDED_FFT_LENGTHS"), &
1028 pool_limit=globenv%fft_pool_scratch_limit, &
1029 wisdom_file=globenv%fftw_wisdom_file_name, &
1030 plan_style=globenv%fftw_plan_type)
1036 message =
"FFT library "//trim(globenv%default_fft_library)// &
1037 " is not available. Trying FFT library FFTW3."
1038 cpwarn(trim(message))
1039 globenv%default_fft_library =
"FFTW3"
1040 CALL init_fft(fftlib=trim(globenv%default_fft_library), &
1042 fftsg_sizes=.NOT.
section_get_lval(global_section,
"EXTENDED_FFT_LENGTHS"), &
1043 pool_limit=globenv%fft_pool_scratch_limit, &
1044 wisdom_file=globenv%fftw_wisdom_file_name, &
1045 plan_style=globenv%fftw_plan_type)
1050 message =
"FFT library "//trim(globenv%default_fft_library)// &
1051 " is not available. Trying FFT library FFTSG."
1052 cpwarn(trim(message))
1053 globenv%default_fft_library =
"FFTSG"
1054 CALL init_fft(fftlib=trim(globenv%default_fft_library), &
1056 fftsg_sizes=.NOT.
section_get_lval(global_section,
"EXTENDED_FFT_LENGTHS"), &
1057 pool_limit=globenv%fft_pool_scratch_limit, &
1058 wisdom_file=globenv%fftw_wisdom_file_name, &
1059 plan_style=globenv%fftw_plan_type)
1063 cpabort(
"FFT library FFTSG does not work. No FFT library available.")
1068 END SUBROUTINE fft_setup_library
1076 SUBROUTINE diag_setup_library(globenv)
1079 CHARACTER(LEN=3*default_string_length) :: message
1080 LOGICAL :: fallback_applied
1082 CALL diag_init(diag_lib=trim(globenv%diag_library), &
1083 fallback_applied=fallback_applied, &
1084 elpa_kernel=globenv%k_elpa, &
1085 elpa_neigvec_min_input=globenv%elpa_neigvec_min, &
1086 elpa_qr=globenv%elpa_qr, &
1087 elpa_print=globenv%elpa_print, &
1088 elpa_qr_unsafe=globenv%elpa_qr_unsafe, &
1089 dlaf_neigvec_min_input=globenv%dlaf_neigvec_min, &
1090 eps_check_diag_input=globenv%eps_check_diag)
1092 IF (fallback_applied)
THEN
1093 message =
"Diagonalization library "//trim(globenv%diag_library)// &
1094 " is not available. The ScaLAPACK library is used as fallback."
1095 cpwarn(trim(message))
1098 END SUBROUTINE diag_setup_library
1104 SUBROUTINE fm_setup(glob_section)
1107 INTEGER :: mm_type, ncb, nrb
1121 END SUBROUTINE fm_setup
1127 SUBROUTINE dgemm_setup(glob_section)
1130 INTEGER :: dgemm_type
1136 END SUBROUTINE dgemm_setup
1144 SUBROUTINE fm_diag_rules_setup(glob_section)
1148 LOGICAL :: elpa_force_redistribute, should_print
1160 END SUBROUTINE fm_diag_rules_setup
1172 CHARACTER(LEN=*),
INTENT(in) :: keyword_name
1173 REAL(kind=
dp),
INTENT(out) :: walltime
1175 CHARACTER(LEN=1) :: c1, c2
1176 CHARACTER(LEN=100) :: txt
1177 INTEGER :: hours, ierr, minutes, n,
seconds
1184 ELSE IF (index(txt,
":") == 0)
THEN
1185 READ (txt(1:n), fmt=*, iostat=ierr) walltime
1186 IF (ierr /= 0) cpabort(
'Could not parse WALLTIME: "'//txt(1:n)//
'"')
1188 READ (txt(1:n), fmt=
"(I2,A1,I2,A1,I2)", iostat=ierr) hours, c1, minutes, c2,
seconds
1189 IF (n /= 8 .OR. ierr /= 0 .OR. c1 .NE.
":" .OR. c2 .NE.
":") &
1190 cpabort(
'Could not parse WALLTIME: "'//txt(1:n)//
'"')
1191 walltime = 3600.0_dp*real(hours,
dp) + 60.0_dp*real(minutes,
dp) + real(
seconds,
dp)
1217 CHARACTER(LEN=*),
OPTIONAL :: wdir
1218 LOGICAL,
INTENT(IN),
OPTIONAL :: q_finalize
1220 CHARACTER(LEN=default_path_length) :: cg_filename
1221 INTEGER :: cg_mode, iw, unit_exit
1222 LOGICAL :: delete_it, do_finalize, report_maxloc, &
1224 REAL(kind=
dp) :: r_timings
1231 do_finalize = .true.
1232 IF (
PRESENT(q_finalize)) do_finalize = q_finalize
1236 IF (do_finalize)
THEN
1242 CALL finalize_fft(para_env, globenv%fftw_wisdom_file_name)
1252 "GLOBAL%PROGRAM_RUN_INFO")
1258 WRITE (unit=iw, fmt=
"(/,T2,A)") repeat(
"-", 79)
1259 WRITE (unit=iw, fmt=
"(T2,A,T80,A)")
"-",
"-"
1260 WRITE (unit=iw, fmt=
"(T2,A,T30,A,T80,A)")
"-",
"R E F E R E N C E S",
"-"
1261 WRITE (unit=iw, fmt=
"(T2,A,T80,A)")
"-",
"-"
1262 WRITE (unit=iw, fmt=
"(T2,A)") repeat(
"-", 79)
1263 WRITE (unit=iw, fmt=
"(T2,A)")
""
1264 WRITE (unit=iw, fmt=
"(T2,A)") trim(
cp2k_version)//
", the CP2K developers group ("//trim(
cp2k_year)//
")."
1265 WRITE (unit=iw, fmt=
"(T2,A)")
"CP2K is freely available from "//trim(
cp2k_home)//
" ."
1266 WRITE (unit=iw, fmt=
"(T2,A)")
""
1270 "GLOBAL%REFERENCES")
1272 CALL timestop(globenv%handle)
1277 sort_by_self_time =
section_get_lval(root_section,
"GLOBAL%TIMINGS%SORT_BY_SELF_TIME")
1278 report_maxloc =
section_get_lval(root_section,
"GLOBAL%TIMINGS%REPORT_MAXLOC")
1288 IF (len_trim(cg_filename) == 0) cg_filename = trim(logger%iter_info%project_name)
1290 cg_filename = trim(cg_filename)//
"_"//trim(adjustl(
cp_to_string(para_env%mepos)))
1292 WRITE (unit=iw, fmt=
"(T2,3X,A)")
"Writing callgraph to: "//trim(cg_filename)//
".callgraph"
1293 WRITE (unit=iw, fmt=
"()")
1294 WRITE (unit=iw, fmt=
"(T2,A)")
"-------------------------------------------------------------------------------"
1306 IF (para_env%is_source())
THEN
1312 INQUIRE (file=
"EXIT", exist=delete_it)
1314 CALL open_file(file_name=
"EXIT", unit_number=unit_exit)
1315 CALL close_file(unit_number=unit_exit, file_status=
"DELETE")
1319 INQUIRE (file=trim(logger%iter_info%project_name)//
".EXIT", exist=delete_it)
1321 CALL open_file(file_name=trim(logger%iter_info%project_name)//
".EXIT", unit_number=unit_exit)
1322 CALL close_file(unit_number=unit_exit, file_status=
"DELETE")
1328 WRITE (iw,
"(T2,A,I0)")
"The number of traced issues for OpenMP : ",
m_omp_trace_issues()
1330 WRITE (iw,
"(T2,A,I0)")
"The number of warnings for this run is : ",
warning_counter
1332 WRITE (unit=iw, fmt=
"(T2,A)") repeat(
"-", 79)
1340 IF (iw > 0)
FLUSH (iw)
1343 "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.
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