(git:374b731)
Loading...
Searching...
No Matches
environment.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief Sets up and terminates the global environment variables
10!> \par History
11!> - Merged with Quickstep MODULE start_program_run (17.01.2002,MK)
12!> - Compile information added (16.01.2002,MK)
13!> - Merged with MODULE cp2k_input, some rearrangements (30.10.2002,MK)
14!> - Update seed input (24.10.2016,MK)
15!> \author JGH,MK
16! **************************************************************************************************
18 USE bibliography, ONLY: frigo2005,&
19 marek2014,&
20 cite_reference
21 USE cp2k_info, ONLY: &
25 USE cp_files, ONLY: close_file,&
33 diag_init,&
39 USE cp_log_handling, ONLY: &
51 USE fft_tools, ONLY: fft3d,&
57 USE grid_api, ONLY: grid_backend_auto,&
63 USE header, ONLY: cp2k_footer,&
65 USE input_constants, ONLY: &
74 USE input_section_types, ONLY: &
78 USE kinds, ONLY: default_path_length,&
80 dp,&
81 int_8,&
84 USE machine, ONLY: &
89 USE mp_perf_env, ONLY: add_mp_perf_env,&
96 USE parallel_rng_types, ONLY: gaussian,&
97 check_rng,&
100 USE physcon, ONLY: write_physcon
107 USE timings, ONLY: add_timer_env,&
117
118!$ USE OMP_LIB, ONLY: omp_get_max_threads, omp_get_thread_num, omp_get_num_threads
119#include "./base/base_uses.f90"
120
121 IMPLICIT NONE
122
123 PRIVATE
124
125 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'environment'
126
127 ! Public subroutines
128
130
131CONTAINS
132
133! **************************************************************************************************
134!> \brief Initializes a CP2K run (setting of the global environment variables)
135!> \param para_env ...
136!> \param output_unit ...
137!> \param globenv ...
138!> \param input_file_name ...
139!> \param wdir ...
140!> \par History
141!> JGH (28.11.2001) : default for pp_library_path
142!> - print keys added (17.01.2002, MK)
143!> - merged with cp2k_input (30.10.2002,MK)
144!> \author JGH,MK
145! **************************************************************************************************
146 SUBROUTINE cp2k_init(para_env, output_unit, globenv, input_file_name, wdir)
147
148 TYPE(mp_para_env_type), POINTER :: para_env
149 INTEGER :: output_unit
150 TYPE(global_environment_type), POINTER :: globenv
151 CHARACTER(LEN=*) :: input_file_name
152 CHARACTER(LEN=*), OPTIONAL :: wdir
153
154 CHARACTER(LEN=10*default_string_length) :: cp_flags
155 INTEGER :: i, ilen, my_output_unit
156 TYPE(cp_logger_type), POINTER :: logger
157
158 ! create a timer_env
159
160 CALL add_timer_env()
161
162 ! Message passing performance
163 CALL add_mp_perf_env()
164
165 ! Init the default logger
166 IF (para_env%is_source()) THEN
167 my_output_unit = output_unit
168 ELSE
169 my_output_unit = -1
170 END IF
171 NULLIFY (logger)
172 CALL cp_logger_create(logger, para_env=para_env, &
173 default_global_unit_nr=output_unit, &
174 close_global_unit_on_dealloc=.false.)
175 CALL cp_add_default_logger(logger)
176 CALL cp_logger_release(logger)
177
178 ! Initialize timing
179 CALL timeset(root_cp2k_name, globenv%handle)
180
181 ! Print header
182 CALL cp2k_header(my_output_unit, wdir)
183
184 IF (my_output_unit > 0) THEN
185 WRITE (unit=my_output_unit, fmt="(/,T2,A,T31,A50)") &
186 "CP2K| version string: ", adjustr(trim(cp2k_version))
187 WRITE (unit=my_output_unit, fmt="(T2,A,T41,A40)") &
188 "CP2K| source code revision number:", &
189 adjustr(compile_revision)
190 cp_flags = cp2k_flags()
191 ilen = len_trim(cp_flags)
192 WRITE (unit=my_output_unit, fmt="(T2,A)") &
193 "CP2K| "//cp_flags(1:73)
194 IF (ilen > 73) THEN
195 DO i = 0, (ilen - 75)/61
196 WRITE (unit=my_output_unit, fmt="(T2,A)") &
197 "CP2K| "//trim(cp_flags(74 + i*61:min(74 + (i + 1)*61, ilen)))
198 END DO
199 END IF
200 WRITE (unit=my_output_unit, fmt="(T2,A,T41,A40)") &
201 "CP2K| is freely available from ", &
202 adjustr(trim(cp2k_home))
203 WRITE (unit=my_output_unit, fmt="(T2,A,T31,A50)") &
204 "CP2K| Program compiled at", &
205 adjustr(compile_date(1:min(50, len(compile_date))))
206 WRITE (unit=my_output_unit, fmt="(T2,A,T31,A50)") &
207 "CP2K| Program compiled on", &
208 adjustr(compile_host(1:min(50, len(compile_host))))
209 WRITE (unit=my_output_unit, fmt="(T2,A,T31,A50)") &
210 "CP2K| Program compiled for", &
211 adjustr(compile_arch(1:min(50, len(compile_arch))))
212 WRITE (unit=my_output_unit, fmt="(T2,A,T31,A50)") &
213 "CP2K| Data directory path", &
214 adjustr(trim(get_data_dir()))
215 WRITE (unit=my_output_unit, fmt="(T2,A,T31,A50)") &
216 "CP2K| Input file name", &
217 adjustr(trim(input_file_name))
218 FLUSH (my_output_unit) ! ignore &GLOBAL / FLUSH_SHOULD_FLUSH
219 END IF
220
221#if defined(__FAST_MATH__)
222 CALL cp_warn(__location__, &
223 "During compilation one of the following flags was active:"// &
224 " `-ffast-math` (GCC)"// &
225 " `-hfpN` (Cray, N > 0, default N=2)"// &
226 " This can lead to wrong results and numerical instabilities"// &
227 " and is therefore no longer supported.")
228
229#if !defined(__FORCE_USE_FAST_MATH)
230#error "-ffast-math (GCC) or -hfpN (N>0, Cray) can lead to wrong results and numerical instabilities and are therefore no longer supported"
231#endif
232#endif
233
234#if defined(NDEBUG)
235#error "Please do not build CP2K with NDEBUG. There is no performance advantage and asserts will save your neck."
236#endif
237
238 END SUBROUTINE cp2k_init
239
240! **************************************************************************************************
241!> \brief echoes the list of host names and pids
242!> \param para_env ...
243!> \param output_unit ...
244! **************************************************************************************************
245 SUBROUTINE echo_all_hosts(para_env, output_unit)
246 TYPE(mp_para_env_type), POINTER :: para_env
247 INTEGER :: output_unit
248
249 CHARACTER(LEN=default_string_length) :: string
250 INTEGER :: ipe
251 INTEGER, ALLOCATABLE, DIMENSION(:) :: all_pid
252 INTEGER, ALLOCATABLE, DIMENSION(:, :) :: all_host
253
254 ! Print a list of all started processes
255
256 ALLOCATE (all_pid(para_env%num_pe))
257 all_pid(:) = 0
258 all_pid(para_env%mepos + 1) = r_pid
259
260 CALL para_env%sum(all_pid)
261 ALLOCATE (all_host(30, para_env%num_pe))
262 all_host(:, :) = 0
263 CALL string_to_ascii(r_host_name, all_host(:, para_env%mepos + 1))
264 CALL para_env%sum(all_host)
265 IF (output_unit > 0) THEN
266
267 WRITE (unit=output_unit, fmt="(T2,A)") ""
268 DO ipe = 1, para_env%num_pe
269 CALL ascii_to_string(all_host(:, ipe), string)
270 WRITE (unit=output_unit, fmt="(T2,A,T63,I8,T71,I10)") &
271 trim(r_user_name)//"@"//trim(string)// &
272 " has created rank and process ", ipe - 1, all_pid(ipe)
273 END DO
274 WRITE (unit=output_unit, fmt="(T2,A)") ""
275 END IF
276 DEALLOCATE (all_pid)
277 DEALLOCATE (all_host)
278
279 END SUBROUTINE echo_all_hosts
280
281! **************************************************************************************************
282!> \brief echoes the list the number of process per host
283!> \param para_env ...
284!> \param output_unit ...
285! **************************************************************************************************
286 SUBROUTINE echo_all_process_host(para_env, output_unit)
287 TYPE(mp_para_env_type), POINTER :: para_env
288 INTEGER :: output_unit
289
290 CHARACTER(LEN=default_string_length) :: string, string_sec
291 INTEGER :: ipe, jpe, nr_occu
292 INTEGER, ALLOCATABLE, DIMENSION(:) :: all_pid
293 INTEGER, ALLOCATABLE, DIMENSION(:, :) :: all_host
294
295 ALLOCATE (all_host(30, para_env%num_pe))
296 all_host(:, :) = 0
297
298 IF (m_procrun(r_pid) .EQ. 1) THEN
299 CALL string_to_ascii(r_host_name, all_host(:, para_env%mepos + 1))
300 CALL para_env%sum(all_host)
301 END IF
302
303 IF (output_unit > 0) THEN
304 ALLOCATE (all_pid(para_env%num_pe))
305 all_pid(:) = 0
306
307 WRITE (unit=output_unit, fmt="(T2,A)") ""
308 DO ipe = 1, para_env%num_pe
309 nr_occu = 0
310 IF (all_pid(ipe) .NE. -1) THEN
311 CALL ascii_to_string(all_host(:, ipe), string)
312 DO jpe = 1, para_env%num_pe
313 CALL ascii_to_string(all_host(:, jpe), string_sec)
314 IF (string .EQ. string_sec) THEN
315 nr_occu = nr_occu + 1
316 all_pid(jpe) = -1
317 END IF
318 END DO
319 WRITE (unit=output_unit, fmt="(T2,A,T63,I8,A)") &
320 trim(r_user_name)//"@"//trim(string)// &
321 " is running ", nr_occu, " processes"
322 WRITE (unit=output_unit, fmt="(T2,A)") ""
323 END IF
324 END DO
325 DEALLOCATE (all_pid)
326
327 END IF
328
329 DEALLOCATE (all_host)
330
331 END SUBROUTINE echo_all_process_host
332
333! **************************************************************************************************
334!> \brief read part of cp2k_init
335!> \param root_section ...
336!> \param para_env ...
337!> \param globenv the globenv
338!> \author fawzi
339!> \note
340!> The following routines need to be synchronized wrt. adding/removing
341!> of the default environments (logging, performance,error):
342!> environment:cp2k_init, environment:cp2k_finalize,
343!> f77_interface:f_env_add_defaults, f77_interface:f_env_rm_defaults,
344!> f77_interface:create_force_env, f77_interface:destroy_force_env
345! **************************************************************************************************
346 SUBROUTINE cp2k_read(root_section, para_env, globenv)
347
348 TYPE(section_vals_type), POINTER :: root_section
349 TYPE(mp_para_env_type), POINTER :: para_env
350 TYPE(global_environment_type), POINTER :: globenv
351
352 CHARACTER(LEN=3*default_string_length) :: message
353 CHARACTER(len=default_string_length) :: c_val
354 INTEGER :: i, iw
355 TYPE(cp_logger_type), POINTER :: logger
356
357 ! Read the input/output section
358
359 logger => cp_get_default_logger()
360
361 ! try to use better names for the local log if it is not too late
362 CALL section_vals_val_get(root_section, "GLOBAL%OUTPUT_FILE_NAME", &
363 c_val=c_val)
364 IF (c_val /= "") THEN
365 CALL cp_logger_set(logger, &
366 local_filename=trim(c_val)//"_localLog")
367 END IF
368
369 ! Process project name
370 CALL section_vals_val_get(root_section, "GLOBAL%PROJECT", c_val=c_val)
371 IF (index(c_val(:len_trim(c_val)), " ") > 0) THEN
372 message = "Project name <"//trim(c_val)// &
373 "> contains spaces which will be replaced with underscores"
374 cpwarn(trim(message))
375 DO i = 1, len_trim(c_val)
376 ! Replace space with underscore
377 IF (c_val(i:i) == " ") c_val(i:i) = "_"
378 END DO
379 CALL section_vals_val_set(root_section, "GLOBAL%PROJECT", c_val=trim(c_val))
380 END IF
381 IF (c_val /= "") THEN
382 CALL cp_logger_set(logger, local_filename=trim(c_val)//"_localLog")
383 END IF
384 logger%iter_info%project_name = c_val
385
386 CALL section_vals_val_get(root_section, "GLOBAL%PRINT_LEVEL", i_val=logger%iter_info%print_level)
387
388 ! Read the CP2K section
389 CALL read_cp2k_section(root_section, para_env, globenv)
390
391 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%PRINT/BASIC_DATA_TYPES", &
392 extension=".Log")
393 IF (iw > 0) CALL print_kind_info(iw)
394 CALL cp_print_key_finished_output(iw, logger, root_section, &
395 "GLOBAL%PRINT/BASIC_DATA_TYPES")
396
397 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%PRINT/PHYSCON", &
398 extension=".Log")
399 IF (iw > 0) CALL write_physcon(iw)
400 CALL cp_print_key_finished_output(iw, logger, root_section, &
401 "GLOBAL%PRINT/PHYSCON")
402
403 END SUBROUTINE cp2k_read
404
405! **************************************************************************************************
406!> \brief globenv initializations that need the input and error
407!> \param root_section ...
408!> \param para_env ...
409!> \param globenv the global environment to initialize
410!> \author fawzi
411!> \note
412!> if possible do the initializations here as the environment
413!> (error,...) is setup, instead of cp2k_init
414! **************************************************************************************************
415 SUBROUTINE cp2k_setup(root_section, para_env, globenv)
416
417 TYPE(section_vals_type), POINTER :: root_section
418 TYPE(mp_para_env_type), POINTER :: para_env
419 TYPE(global_environment_type), POINTER :: globenv
420
421 INTEGER :: iw, maxl
422 INTEGER, DIMENSION(:), POINTER :: seed_vals
423 REAL(kind=dp), DIMENSION(3, 2) :: initial_seed
424 TYPE(cp_logger_type), POINTER :: logger
425
426 NULLIFY (logger)
427 logger => cp_get_default_logger()
428
429 ! Initialize the parallel random number generator
430
431 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%PRINT/RNG_MATRICES", &
432 extension=".Log")
433 IF (iw > 0) THEN
434 CALL write_rng_matrices(iw)
435 END IF
436
437 CALL cp_print_key_finished_output(iw, logger, root_section, &
438 "GLOBAL%PRINT/RNG_MATRICES")
439
440 ! Initialize a global normally Gaussian distributed (pseudo)random number stream
441
442 CALL section_vals_val_get(root_section, "GLOBAL%SEED", i_vals=seed_vals)
443 IF (SIZE(seed_vals) == 1) THEN
444 initial_seed(:, :) = real(seed_vals(1), kind=dp)
445 ELSE IF (SIZE(seed_vals) == 6) THEN
446 initial_seed(1:3, 1:2) = reshape(real(seed_vals(:), kind=dp), (/3, 2/))
447 ELSE
448 cpabort("Supply exactly 1 or 6 arguments for SEED in &GLOBAL only!")
449 END IF
450
451 globenv%gaussian_rng_stream = rng_stream_type( &
452 name="Global Gaussian random numbers", &
453 distribution_type=gaussian, &
454 seed=initial_seed, &
455 extended_precision=.true.)
456
457 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%PRINT/RNG_CHECK", &
458 extension=".Log")
459 IF (iw > 0) THEN
460 CALL check_rng(iw, para_env%is_source())
461 END IF
462
463 CALL cp_print_key_finished_output(iw, logger, root_section, &
464 "GLOBAL%PRINT/RNG_CHECK")
465
466 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%PRINT/GLOBAL_GAUSSIAN_RNG", &
467 extension=".Log")
468 IF (iw > 0) &
469 CALL globenv%gaussian_rng_stream%write(iw, write_all=.true.)
470
471 CALL cp_print_key_finished_output(iw, logger, root_section, &
472 "GLOBAL%PRINT/GLOBAL_GAUSSIAN_RNG")
473
474 CALL section_vals_val_get(root_section, "GLOBAL%PRINT%SPHERICAL_HARMONICS", i_val=maxl)
475 IF (maxl >= 0) THEN
476 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%PRINT", &
477 extension=".Log")
478 CALL init_orbital_pointers(maxl)
479 CALL init_spherical_harmonics(maxl, iw)
482 CALL cp_print_key_finished_output(iw, logger, root_section, &
483 "GLOBAL%PRINT")
484 END IF
485
486 END SUBROUTINE cp2k_setup
487
488! **************************************************************************************************
489!> \brief read the global section of new input
490!> \param root_section ...
491!> \param para_env ...
492!> \param globenv ...
493!> \par History
494!> 06-2005 [created]
495!> \author MI
496!> \note
497!> Should not be required anymore once everything is converted
498!> to get information directly from the input structure
499! **************************************************************************************************
500 SUBROUTINE read_global_section(root_section, para_env, globenv)
501
502 TYPE(section_vals_type), POINTER :: root_section
503 TYPE(mp_para_env_type), POINTER :: para_env
504 TYPE(global_environment_type), POINTER :: globenv
505
506 CHARACTER(LEN=6), PARAMETER :: start_section_label = "GLOBAL"
507
508 CHARACTER(len=13) :: omp_stacksize, tracing_string
509 CHARACTER(len=6) :: print_level_string
510 CHARACTER(len=default_path_length) :: basis_set_file_name, coord_file_name, &
511 mm_potential_file_name, &
512 potential_file_name
513 CHARACTER(LEN=default_string_length) :: env_num, model_name, project_name
514 CHARACTER(LEN=default_string_length), &
515 DIMENSION(:), POINTER :: trace_routines
516 INTEGER :: cpuid, cpuid_static, i_dgemm, i_diag, i_fft, i_grid_backend, iforce_eval, &
517 method_name_id, n_rep_val, nforce_eval, num_threads, output_unit, print_level, trace_max, &
518 unit_nr
519 INTEGER(kind=int_8) :: buffers, buffers_avr, buffers_max, buffers_min, cached, cached_avr, &
520 cached_max, cached_min, memfree, memfree_avr, memfree_max, memfree_min, memlikelyfree, &
521 memlikelyfree_avr, memlikelyfree_max, memlikelyfree_min, memtotal, memtotal_avr, &
522 memtotal_max, memtotal_min, slab, slab_avr, slab_max, slab_min, sreclaimable, &
523 sreclaimable_avr, sreclaimable_max, sreclaimable_min
524 INTEGER, DIMENSION(:), POINTER :: i_force_eval
525 LOGICAL :: ata, do_echo_all_hosts, efl, explicit, &
526 flag, report_maxloc, trace, &
527 trace_master
528 TYPE(cp_logger_type), POINTER :: logger
529 TYPE(enumeration_type), POINTER :: enum1, enum2
530 TYPE(keyword_type), POINTER :: keyword
531 TYPE(section_type), POINTER :: section
532 TYPE(section_vals_type), POINTER :: dft_section, force_env_sections, &
533 global_section, qmmm_section, &
534 subsys_section
535
536 NULLIFY (dft_section, global_section, i_force_eval)
537
538 logger => cp_get_default_logger()
539 global_section => section_vals_get_subs_vals(root_section, "GLOBAL")
540 CALL section_vals_val_get(global_section, "BLACS_GRID", i_val=globenv%blacs_grid_layout)
541 CALL section_vals_val_get(global_section, "BLACS_REPEATABLE", l_val=globenv%blacs_repeatable)
542 CALL section_vals_val_get(global_section, "PREFERRED_DIAG_LIBRARY", i_val=i_diag)
543 CALL section_vals_val_get(global_section, "PREFERRED_DGEMM_LIBRARY", i_val=i_dgemm)
544 CALL section_vals_val_get(global_section, "EPS_CHECK_DIAG", r_val=globenv%eps_check_diag)
545 CALL section_vals_val_get(global_section, "ENABLE_MPI_IO", l_val=flag)
546 CALL cp_mpi_io_set(flag)
547 CALL section_vals_val_get(global_section, "ELPA_KERNEL", i_val=globenv%k_elpa)
548 CALL section_vals_val_get(global_section, "ELPA_NEIGVEC_MIN", i_val=globenv%elpa_neigvec_min)
549 CALL section_vals_val_get(global_section, "ELPA_QR", l_val=globenv%elpa_qr)
550 CALL section_vals_val_get(global_section, "ELPA_QR_UNSAFE", l_val=globenv%elpa_qr_unsafe)
551 unit_nr = cp_print_key_unit_nr(logger, global_section, "PRINT_ELPA", extension=".Log")
552 IF (unit_nr > 0) globenv%elpa_print = .true.
553 CALL cp_print_key_finished_output(unit_nr, logger, global_section, "PRINT_ELPA")
554 CALL section_vals_val_get(global_section, "DLAF_NEIGVEC_MIN", i_val=globenv%dlaf_neigvec_min)
555 CALL section_vals_val_get(global_section, "PREFERRED_FFT_LIBRARY", i_val=i_fft)
556 CALL section_vals_val_get(global_section, "PRINT_LEVEL", i_val=print_level)
557 CALL section_vals_val_get(global_section, "PROGRAM_NAME", i_val=globenv%prog_name_id)
558 CALL section_vals_val_get(global_section, "FFT_POOL_SCRATCH_LIMIT", i_val=globenv%fft_pool_scratch_limit)
559 CALL section_vals_val_get(global_section, "FFTW_PLAN_TYPE", i_val=globenv%fftw_plan_type)
560 CALL section_vals_val_get(global_section, "PROJECT_NAME", c_val=project_name)
561 CALL section_vals_val_get(global_section, "FFTW_WISDOM_FILE_NAME", c_val=globenv%fftw_wisdom_file_name)
562 CALL section_vals_val_get(global_section, "RUN_TYPE", i_val=globenv%run_type_id)
563 CALL cp2k_get_walltime(section=global_section, keyword_name="WALLTIME", &
564 walltime=globenv%cp2k_target_time)
565 CALL section_vals_val_get(global_section, "TRACE", l_val=trace)
566 CALL section_vals_val_get(global_section, "TRACE_MASTER", l_val=trace_master)
567 CALL section_vals_val_get(global_section, "TRACE_MAX", i_val=trace_max)
568 CALL section_vals_val_get(global_section, "TRACE_ROUTINES", explicit=explicit)
569 IF (explicit) THEN
570 CALL section_vals_val_get(global_section, "TRACE_ROUTINES", c_vals=trace_routines)
571 ELSE
572 NULLIFY (trace_routines)
573 END IF
574 CALL section_vals_val_get(global_section, "FLUSH_SHOULD_FLUSH", l_val=flush_should_flush)
575 CALL section_vals_val_get(global_section, "ECHO_ALL_HOSTS", l_val=do_echo_all_hosts)
576 report_maxloc = section_get_lval(global_section, "TIMINGS%REPORT_MAXLOC")
577 global_timings_level = section_get_ival(global_section, "TIMINGS%TIMINGS_LEVEL")
578 do_echo_all_hosts = do_echo_all_hosts .OR. report_maxloc
579 force_env_sections => section_vals_get_subs_vals(root_section, "FORCE_EVAL")
580 CALL section_vals_get(force_env_sections, n_repetition=nforce_eval)
581 output_unit = cp_print_key_unit_nr(logger, global_section, "PROGRAM_RUN_INFO", &
582 extension=".log")
583
584 CALL fm_setup(global_section)
585 CALL fm_diag_rules_setup(global_section)
586 CALL dgemm_setup(global_section)
587
588 IF (trace .AND. (.NOT. trace_master .OR. para_env%mepos == 0)) THEN
589 unit_nr = -1
590 IF (logger%para_env%is_source() .OR. .NOT. trace_master) &
591 unit_nr = cp_logger_get_default_unit_nr(logger, local=.true.)
592 WRITE (tracing_string, "(I6.6,A1,I6.6)") para_env%mepos, ":", para_env%num_pe
593 IF (ASSOCIATED(trace_routines)) THEN
594 CALL timings_setup_tracing(trace_max, unit_nr, tracing_string, trace_routines)
595 ELSE
596 CALL timings_setup_tracing(trace_max, unit_nr, tracing_string)
597 END IF
598 END IF
599
600 CALL section_vals_val_get(global_section, "TIMINGS%TIME_MPI", l_val=mp_collect_timings)
601
602 SELECT CASE (i_diag)
604 globenv%diag_library = "ScaLAPACK"
605 CASE (fm_diag_type_elpa)
606 globenv%diag_library = "ELPA"
609 globenv%diag_library = "cuSOLVER"
610 CASE (fm_diag_type_dlaf)
611 globenv%diag_library = "DLAF"
612 ! TODO: Add citation when available
613 CASE DEFAULT
614 cpabort("Unknown diagonalization library specified")
615 END SELECT
616
617 SELECT CASE (i_fft)
618 CASE (do_fft_sg)
619 globenv%default_fft_library = "FFTSG"
620 CASE (do_fft_fftw3)
621 globenv%default_fft_library = "FFTW3"
623 CASE DEFAULT
624 cpabort("Unknown FFT library specified")
625 END SELECT
626
627 SELECT CASE (i_dgemm)
628 CASE (do_dgemm_spla)
629 globenv%default_dgemm_library = "SPLA"
630 CASE (do_dgemm_blas)
631 globenv%default_dgemm_library = "BLAS"
632 CASE DEFAULT
633 cpabort("Unknown DGEMM library specified")
634 END SELECT
635
636 IF (globenv%run_type_id == 0) THEN
637 SELECT CASE (globenv%prog_name_id)
638 CASE (do_farming, do_test)
639 globenv%run_type_id = none_run
640 CASE (do_cp2k)
641 IF (nforce_eval /= 1) THEN
642 ! multiple force_eval corresponds at the moment to RESPA calculations only
643 ! default MD
644 globenv%run_type_id = mol_dyn_run
645 ELSE
646 CALL section_vals_val_get(force_env_sections, "METHOD", i_val=method_name_id)
647 SELECT CASE (method_name_id)
648 CASE (do_fist)
649 globenv%run_type_id = mol_dyn_run
650 CASE (do_eip)
651 globenv%run_type_id = mol_dyn_run
652 CASE (do_qs)
653 globenv%run_type_id = energy_run
654 CASE (do_sirius)
655 globenv%run_type_id = energy_run
656 END SELECT
657 END IF
658 END SELECT
659 END IF
660
661 IF (globenv%prog_name_id == do_farming .AND. globenv%run_type_id /= none_run) THEN
662 cpabort("FARMING program supports only NONE as run type")
663 END IF
664
665 IF (globenv%prog_name_id == do_test .AND. globenv%run_type_id /= none_run) &
666 cpabort("TEST program supports only NONE as run type")
667
668 CALL m_memory_details(memtotal, memfree, buffers, cached, slab, sreclaimable, memlikelyfree)
669 memtotal_avr = memtotal
670 memfree_avr = memfree
671 buffers_avr = buffers
672 cached_avr = cached
673 slab_avr = slab
674 sreclaimable_avr = sreclaimable
675 memlikelyfree_avr = memlikelyfree
676 CALL para_env%sum(memtotal_avr); memtotal_avr = memtotal_avr/para_env%num_pe/1024
677 CALL para_env%sum(memfree_avr); memfree_avr = memfree_avr/para_env%num_pe/1024
678 CALL para_env%sum(buffers_avr); buffers_avr = buffers_avr/para_env%num_pe/1024
679 CALL para_env%sum(cached_avr); cached_avr = cached_avr/para_env%num_pe/1024
680 CALL para_env%sum(slab_avr); slab_avr = slab_avr/para_env%num_pe/1024
681 CALL para_env%sum(sreclaimable_avr); sreclaimable_avr = sreclaimable_avr/para_env%num_pe/1024
682 CALL para_env%sum(memlikelyfree_avr); memlikelyfree_avr = memlikelyfree_avr/para_env%num_pe/1024
683
684 memtotal_min = -memtotal
685 memfree_min = -memfree
686 buffers_min = -buffers
687 cached_min = -cached
688 slab_min = -slab
689 sreclaimable_min = -sreclaimable
690 memlikelyfree_min = -memlikelyfree
691 CALL para_env%max(memtotal_min); memtotal_min = -memtotal_min/1024
692 CALL para_env%max(memfree_min); memfree_min = -memfree_min/1024
693 CALL para_env%max(buffers_min); buffers_min = -buffers_min/1024
694 CALL para_env%max(cached_min); cached_min = -cached_min/1024
695 CALL para_env%max(slab_min); slab_min = -slab_min/1024
696 CALL para_env%max(sreclaimable_min); sreclaimable_min = -sreclaimable_min/1024
697 CALL para_env%max(memlikelyfree_min); memlikelyfree_min = -memlikelyfree_min/1024
698
699 memtotal_max = memtotal
700 memfree_max = memfree
701 buffers_max = buffers
702 cached_max = cached
703 slab_max = slab
704 sreclaimable_max = sreclaimable
705 memlikelyfree_max = memlikelyfree
706 CALL para_env%max(memtotal_max); memtotal_max = memtotal_max/1024
707 CALL para_env%max(memfree_max); memfree_max = memfree_max/1024
708 CALL para_env%max(buffers_max); buffers_max = buffers_max/1024
709 CALL para_env%max(cached_max); cached_max = cached_max/1024
710 CALL para_env%max(slab_max); slab_max = slab_max/1024
711 CALL para_env%max(sreclaimable_max); sreclaimable_max = sreclaimable_max/1024
712 CALL para_env%max(memlikelyfree_max); memlikelyfree_max = memlikelyfree_max/1024
713
714 memtotal = memtotal/1024
715 memfree = memfree/1024
716 buffers = buffers/1024
717 cached = cached/1024
718 slab = slab/1024
719 sreclaimable = sreclaimable/1024
720 memlikelyfree = memlikelyfree/1024
721
722 ! Print a list of all started processes
723 IF (do_echo_all_hosts) THEN
724 CALL echo_all_hosts(para_env, output_unit)
725
726 ! Print the number of processes per host
727 CALL echo_all_process_host(para_env, output_unit)
728 END IF
729
730 num_threads = 1
731!$ num_threads = omp_get_max_threads()
732 IF (output_unit > 0) THEN
733 WRITE (unit=output_unit, fmt=*)
734 CALL multiple_fe_list(force_env_sections, root_section, i_force_eval, nforce_eval)
735 DO iforce_eval = 1, nforce_eval
736 dft_section => section_vals_get_subs_vals3(force_env_sections, "DFT", &
737 i_rep_section=i_force_eval(iforce_eval))
738 qmmm_section => section_vals_get_subs_vals3(force_env_sections, "QMMM", &
739 i_rep_section=i_force_eval(iforce_eval))
740 CALL section_vals_val_get(dft_section, "BASIS_SET_FILE_NAME", &
741 c_val=basis_set_file_name)
742 CALL section_vals_val_get(dft_section, "POTENTIAL_FILE_NAME", &
743 c_val=potential_file_name)
744
745 CALL section_vals_val_get(qmmm_section, "MM_POTENTIAL_FILE_NAME", &
746 c_val=mm_potential_file_name)
747 ! SUBSYS - If any
748 subsys_section => section_vals_get_subs_vals3(force_env_sections, "SUBSYS", &
749 i_rep_section=i_force_eval(iforce_eval))
750 CALL section_vals_get(subsys_section, explicit=explicit)
751 coord_file_name = "__STD_INPUT__"
752 IF (explicit) THEN
753 CALL section_vals_val_get(subsys_section, "TOPOLOGY%COORD_FILE_NAME", &
754 n_rep_val=n_rep_val)
755 IF (n_rep_val == 1) THEN
756 CALL section_vals_val_get(subsys_section, "TOPOLOGY%COORD_FILE_NAME", &
757 c_val=coord_file_name)
758 END IF
759 END IF
760 CALL integer_to_string(i_force_eval(iforce_eval), env_num)
761
762 WRITE (unit=output_unit, fmt="(T2,A,T41,A)") &
763 start_section_label//"| Force Environment number", &
764 adjustr(env_num(:40)), &
765 start_section_label//"| Basis set file name", &
766 adjustr(basis_set_file_name(:40)), &
767 start_section_label//"| Potential file name", &
768 adjustr(potential_file_name(:40)), &
769 start_section_label//"| MM Potential file name", &
770 adjustr(mm_potential_file_name(:40)), &
771 start_section_label//"| Coordinate file name", &
772 adjustr(coord_file_name(:40))
773 END DO
774 DEALLOCATE (i_force_eval)
775
776 NULLIFY (enum1, enum2, keyword, section)
777 CALL create_global_section(section)
778 keyword => section_get_keyword(section, "PROGRAM_NAME")
779 CALL keyword_get(keyword, enum=enum1)
780 keyword => section_get_keyword(section, "RUN_TYPE")
781 CALL keyword_get(keyword, enum=enum2)
782
783 WRITE (unit=output_unit, fmt="(T2,A,T41,A40)") &
784 start_section_label//"| Method name", &
785 adjustr(trim(enum_i2c(enum1, globenv%prog_name_id))), &
786 start_section_label//"| Project name", &
787 adjustr(project_name(:40)), &
788 start_section_label//"| Run type", &
789 adjustr(trim(enum_i2c(enum2, globenv%run_type_id))), &
790 start_section_label//"| FFT library", &
791 adjustr(globenv%default_fft_library(:40)), &
792 start_section_label//"| Diagonalization library", &
793 adjustr(globenv%diag_library(:40)), &
794 start_section_label//"| DGEMM library", &
795 adjustr(globenv%default_dgemm_library(:40))
796
797 IF (globenv%diag_library == "ELPA") THEN
798 WRITE (unit=output_unit, fmt="(T2,A,T71,I10)") &
799 start_section_label//"| Minimum number of eigenvectors for ELPA usage", &
800 globenv%elpa_neigvec_min
801 END IF
802
803 IF (globenv%diag_library == "DLAF") THEN
804 WRITE (unit=output_unit, fmt="(T2,A,T71,I10)") &
805 start_section_label//"| Minimum number of eigenvectors for DLAF usage", &
806 globenv%dlaf_neigvec_min
807 END IF
808
809#if defined(__CHECK_DIAG)
810 ! Perform default check if no threshold value has been specified explicitly
811 IF (globenv%eps_check_diag < 0.0_dp) THEN
812 WRITE (unit=output_unit, fmt="(T2,A,T71,ES10.3)") &
813 start_section_label//"| Orthonormality check for eigenvectors enabled", &
815 ELSE
816 WRITE (unit=output_unit, fmt="(T2,A,T71,ES10.3)") &
817 start_section_label//"| Orthonormality check for eigenvectors enabled", &
818 globenv%eps_check_diag
819 END IF
820#else
821 IF (globenv%eps_check_diag < 0.0_dp) THEN
822 WRITE (unit=output_unit, fmt="(T2,A,T73,A)") &
823 start_section_label//"| Orthonormality check for eigenvectors", &
824 "DISABLED"
825 ELSE
826 WRITE (unit=output_unit, fmt="(T2,A,T71,ES10.3)") &
827 start_section_label//"| Orthonormality check for eigenvectors enabled", &
828 globenv%eps_check_diag
829 END IF
830#endif
831 CALL section_release(section)
832
833 SELECT CASE (cp_fm_get_mm_type())
834 CASE (do_scalapack)
835 WRITE (unit=output_unit, fmt="(T2,A,T72,A)") &
836 start_section_label//"| Matrix multiplication library", "ScaLAPACK"
837 CASE (do_cosma)
838 WRITE (unit=output_unit, fmt="(T2,A,T76,A)") &
839 start_section_label//"| Matrix multiplication library", "COSMA"
840 END SELECT
841
842 CALL section_vals_val_get(global_section, "ALLTOALL_SGL", l_val=ata)
843 WRITE (unit=output_unit, fmt="(T2,A,T80,L1)") &
844 start_section_label//"| All-to-all communication in single precision", ata
845 CALL section_vals_val_get(global_section, "EXTENDED_FFT_LENGTHS", l_val=efl)
846 WRITE (unit=output_unit, fmt="(T2,A,T80,L1)") &
847 start_section_label//"| FFTs using library dependent lengths", efl
848
849 SELECT CASE (print_level)
850 CASE (silent_print_level)
851 print_level_string = "SILENT"
852 CASE (low_print_level)
853 print_level_string = " LOW"
854 CASE (medium_print_level)
855 print_level_string = "MEDIUM"
856 CASE (high_print_level)
857 print_level_string = " HIGH"
858 CASE (debug_print_level)
859 print_level_string = " DEBUG"
860 CASE DEFAULT
861 cpabort("Unknown print_level")
862 END SELECT
863
864 CALL section_vals_val_get(global_section, "GRID%BACKEND", i_val=i_grid_backend)
865 SELECT CASE (i_grid_backend)
866 CASE (grid_backend_auto)
867 WRITE (unit=output_unit, fmt="(T2,A,T75,A6)") &
868 start_section_label//"| Grid backend", "AUTO"
869 CASE (grid_backend_cpu)
870 WRITE (unit=output_unit, fmt="(T2,A,T75,A6)") &
871 start_section_label//"| Grid backend", "CPU"
872 CASE (grid_backend_dgemm)
873 WRITE (unit=output_unit, fmt="(T2,A,T75,A6)") &
874 start_section_label//"| Grid backend", "DGEMM"
875 CASE (grid_backend_gpu)
876 WRITE (unit=output_unit, fmt="(T2,A,T75,A6)") &
877 start_section_label//"| Grid backend", "GPU"
878 CASE (grid_backend_hip)
879 WRITE (unit=output_unit, fmt="(T2,A,T75,A6)") &
880 start_section_label//"| Grid backend", "HIP"
881 CASE (grid_backend_ref)
882 WRITE (unit=output_unit, fmt="(T2,A,T75,A6)") &
883 start_section_label//"| Grid backend", "REF"
884 END SELECT
885
886 WRITE (unit=output_unit, fmt="(T2,A,T75,A6)") &
887 start_section_label//"| Global print level", print_level_string
888 WRITE (unit=output_unit, fmt="(T2,A,T75,L6)") &
889 start_section_label//"| MPI I/O enabled", flag
890 WRITE (unit=output_unit, fmt="(T2,A,T75,I6)") &
891 start_section_label//"| Total number of message passing processes", &
892 para_env%num_pe, &
893 start_section_label//"| Number of threads for this process", &
894 num_threads, &
895 start_section_label//"| This output is from process", para_env%mepos
896
897 CALL m_get_omp_stacksize(omp_stacksize)
898 WRITE (unit=output_unit, fmt="(T2,A,T68,A13)") &
899 start_section_label//"| Stack size for threads created by OpenMP (OMP_STACKSIZE)", &
900 adjustr(omp_stacksize)
901
902 CALL m_cpuinfo(model_name)
903 WRITE (unit=output_unit, fmt="(T2,A,T30,A51)") &
904 start_section_label//"| CPU model name", adjustr(trim(model_name))
905
906 cpuid = m_cpuid()
907 cpuid_static = m_cpuid_static()
908
909 IF ((cpuid > 0) .OR. (cpuid_static > 0)) THEN
910 WRITE (unit=output_unit, fmt="(T2,A,T75,I6)") &
911 start_section_label//"| CPUID", cpuid
912 IF (cpuid /= cpuid_static) THEN
913 WRITE (unit=output_unit, fmt="(T2,A,T75,I6)") &
914 start_section_label//"| Compiled for CPUID", cpuid_static
915 END IF
916 END IF
917
918 IF (cpuid_static < cpuid) THEN
919 ! base/machine_cpuid.c relies on the (same) target flags as the Fortran code
920 CALL cp_hint(__location__, "The compiler target flags ("// &
921 trim(m_cpuid_name(cpuid_static))//") used to build this binary cannot exploit "// &
922 "all extensions of this CPU model ("//trim(m_cpuid_name(cpuid))//"). "// &
923 "Consider compiler target flags as part of FCFLAGS and CFLAGS (ARCH file).")
924 END IF
925
926 WRITE (unit=output_unit, fmt="()")
927 WRITE (unit=output_unit, fmt="(T2,A)") "MEMORY| system memory details [Kb]"
928 WRITE (unit=output_unit, fmt="(T2,A23,4A14)") "MEMORY| ", "rank 0", "min", "max", "average"
929 WRITE (unit=output_unit, fmt="(T2,A23,4I14)") "MEMORY| MemTotal ", memtotal, memtotal_min, memtotal_max, memtotal_avr
930 WRITE (unit=output_unit, fmt="(T2,A23,4I14)") "MEMORY| MemFree ", memfree, memfree_min, memfree_max, memfree_avr
931 WRITE (unit=output_unit, fmt="(T2,A23,4I14)") "MEMORY| Buffers ", buffers, buffers_min, buffers_max, buffers_avr
932 WRITE (unit=output_unit, fmt="(T2,A23,4I14)") "MEMORY| Cached ", cached, cached_min, cached_max, cached_avr
933 WRITE (unit=output_unit, fmt="(T2,A23,4I14)") "MEMORY| Slab ", slab, slab_min, slab_max, slab_avr
934 WRITE (unit=output_unit, fmt="(T2,A23,4I14)") &
935 "MEMORY| SReclaimable ", sreclaimable, sreclaimable_min, sreclaimable_max, &
936 sreclaimable_avr
937 WRITE (unit=output_unit, fmt="(T2,A23,4I14)") &
938 "MEMORY| MemLikelyFree ", memlikelyfree, memlikelyfree_min, memlikelyfree_max, &
939 memlikelyfree_avr
940 WRITE (unit=output_unit, fmt='()')
941
942 END IF
943
944 CALL cp_print_key_finished_output(output_unit, logger, global_section, &
945 "PROGRAM_RUN_INFO")
946
947 END SUBROUTINE read_global_section
948
949! **************************************************************************************************
950!> \brief ...
951!> \param root_section ...
952!> \param para_env ...
953!> \param globenv ...
954!> \par History
955!> 2-Dec-2000 (JGH) added default fft library
956!> \author JGH,MK
957! **************************************************************************************************
958 SUBROUTINE read_cp2k_section(root_section, para_env, globenv)
959
960 TYPE(section_vals_type), POINTER :: root_section
961 TYPE(mp_para_env_type), POINTER :: para_env
962 TYPE(global_environment_type), POINTER :: globenv
963
964 INTEGER :: output_unit
965 TYPE(cp_logger_type), POINTER :: logger
966 TYPE(section_vals_type), POINTER :: global_section
967
968 global_section => section_vals_get_subs_vals(root_section, "GLOBAL")
969 CALL read_global_section(root_section, para_env, globenv)
970 logger => cp_get_default_logger()
971 output_unit = cp_print_key_unit_nr(logger, global_section, "PROGRAM_RUN_INFO", &
972 extension=".log")
973
974 CALL fft_setup_library(globenv, global_section)
975 CALL diag_setup_library(globenv)
976
977 CALL cp_print_key_finished_output(output_unit, logger, global_section, &
978 "PROGRAM_RUN_INFO")
979
980 END SUBROUTINE read_cp2k_section
981
982! **************************************************************************************************
983!> \brief check FFT preferred library availability, if not switch
984!> \param globenv ...
985!> \param global_section ...
986!> \par History
987!> 2-Dec-2000 (JGH) added default fft library
988!> Nov-2013 (MI) refactoring
989!> \author JGH,MK
990! **************************************************************************************************
991 SUBROUTINE fft_setup_library(globenv, global_section)
992
993 TYPE(global_environment_type), POINTER :: globenv
994 TYPE(section_vals_type), POINTER :: global_section
995
996 CHARACTER(LEN=3*default_string_length) :: message
997 COMPLEX(KIND=dp), DIMENSION(4, 4, 4) :: zz
998 INTEGER :: stat
999 INTEGER, DIMENSION(3) :: n
1000 LOGICAL :: try_fftw
1001
1002 n(:) = 4
1003 zz(:, :, :) = 0.0_dp
1004
1005 ! Setup the FFT library
1006 ! If the user has specified PREFERRED_FFT_LIBRARY try that first (default FFTW3)
1007 ! If that one is not available, try FFTW3 (unless it has been tried already)
1008 ! If FFTW3 is not available use FFTSG
1009
1010 IF (globenv%default_fft_library == "FFTW3") THEN
1011 try_fftw = .false.
1012 ELSE
1013 try_fftw = .true.
1014 END IF
1015
1016 ! Initialize FFT library with the user's preferred FFT library
1017 CALL init_fft(fftlib=trim(globenv%default_fft_library), &
1018 alltoall=section_get_lval(global_section, "ALLTOALL_SGL"), &
1019 fftsg_sizes=.NOT. section_get_lval(global_section, "EXTENDED_FFT_LENGTHS"), &
1020 pool_limit=globenv%fft_pool_scratch_limit, &
1021 wisdom_file=globenv%fftw_wisdom_file_name, &
1022 plan_style=globenv%fftw_plan_type)
1023
1024 ! Check for FFT library
1025 CALL fft3d(1, n, zz, status=stat)
1026 IF (stat /= 0) THEN
1027 IF (try_fftw) THEN
1028 message = "FFT library "//trim(globenv%default_fft_library)// &
1029 " is not available. Trying FFT library FFTW3."
1030 cpwarn(trim(message))
1031 globenv%default_fft_library = "FFTW3"
1032 CALL init_fft(fftlib=trim(globenv%default_fft_library), &
1033 alltoall=section_get_lval(global_section, "ALLTOALL_SGL"), &
1034 fftsg_sizes=.NOT. section_get_lval(global_section, "EXTENDED_FFT_LENGTHS"), &
1035 pool_limit=globenv%fft_pool_scratch_limit, &
1036 wisdom_file=globenv%fftw_wisdom_file_name, &
1037 plan_style=globenv%fftw_plan_type)
1038
1039 CALL fft3d(1, n, zz, status=stat)
1040 END IF
1041 IF (stat /= 0) THEN
1042 message = "FFT library "//trim(globenv%default_fft_library)// &
1043 " is not available. Trying FFT library FFTSG."
1044 cpwarn(trim(message))
1045 globenv%default_fft_library = "FFTSG"
1046 CALL init_fft(fftlib=trim(globenv%default_fft_library), &
1047 alltoall=section_get_lval(global_section, "ALLTOALL_SGL"), &
1048 fftsg_sizes=.NOT. section_get_lval(global_section, "EXTENDED_FFT_LENGTHS"), &
1049 pool_limit=globenv%fft_pool_scratch_limit, &
1050 wisdom_file=globenv%fftw_wisdom_file_name, &
1051 plan_style=globenv%fftw_plan_type)
1052
1053 CALL fft3d(1, n, zz, status=stat)
1054 IF (stat /= 0) THEN
1055 cpabort("FFT library FFTSG does not work. No FFT library available.")
1056 END IF
1057 END IF
1058 END IF
1059
1060 END SUBROUTINE fft_setup_library
1061
1062! **************************************************************************************************
1063!> \brief availability diagonalizatioon library
1064!>
1065!> \param globenv ...
1066!> \author MI
1067! **************************************************************************************************
1068 SUBROUTINE diag_setup_library(globenv)
1069 TYPE(global_environment_type), POINTER :: globenv
1070
1071 CHARACTER(LEN=3*default_string_length) :: message
1072 LOGICAL :: fallback_applied
1073
1074 CALL diag_init(diag_lib=trim(globenv%diag_library), &
1075 fallback_applied=fallback_applied, &
1076 elpa_kernel=globenv%k_elpa, &
1077 elpa_neigvec_min_input=globenv%elpa_neigvec_min, &
1078 elpa_qr=globenv%elpa_qr, &
1079 elpa_print=globenv%elpa_print, &
1080 elpa_qr_unsafe=globenv%elpa_qr_unsafe, &
1081 dlaf_neigvec_min_input=globenv%dlaf_neigvec_min, &
1082 eps_check_diag_input=globenv%eps_check_diag)
1083
1084 IF (fallback_applied) THEN
1085 message = "Diagonalization library "//trim(globenv%diag_library)// &
1086 " is not available. The ScaLAPACK library is used as fallback."
1087 cpwarn(trim(message))
1088 END IF
1089
1090 END SUBROUTINE diag_setup_library
1091
1092! **************************************************************************************************
1093!> \brief ...
1094!> \param glob_section ...
1095! **************************************************************************************************
1096 SUBROUTINE fm_setup(glob_section)
1097 TYPE(section_vals_type), POINTER :: glob_section
1098
1099 INTEGER :: multiplication_type, ncb, nrb
1100 LOGICAL :: force_me
1101 TYPE(section_vals_type), POINTER :: fm_section
1102
1103 fm_section => section_vals_get_subs_vals(glob_section, "FM")
1104
1105 CALL section_vals_val_get(fm_section, "NROW_BLOCKS", i_val=nrb)
1106 CALL section_vals_val_get(fm_section, "NCOL_BLOCKS", i_val=ncb)
1107 CALL section_vals_val_get(fm_section, "FORCE_BLOCK_SIZE", l_val=force_me)
1108
1109 CALL cp_fm_struct_config(nrow_block=nrb, ncol_block=ncb, force_block=force_me)
1110
1111 CALL section_vals_val_get(fm_section, "TYPE_OF_MATRIX_MULTIPLICATION", &
1112 i_val=multiplication_type)
1113
1114 CALL cp_fm_setup(multiplication_type)
1115
1116 END SUBROUTINE fm_setup
1117
1118! **************************************************************************************************
1119!> \brief ...
1120!> \param glob_section ...
1121! **************************************************************************************************
1122 SUBROUTINE dgemm_setup(glob_section)
1123 TYPE(section_vals_type), POINTER :: glob_section
1124
1125 INTEGER :: dgemm_type
1126
1127 CALL section_vals_val_get(glob_section, "PREFERRED_DGEMM_LIBRARY", i_val=dgemm_type)
1128
1129 CALL local_gemm_set_library(dgemm_type)
1130
1131 END SUBROUTINE dgemm_setup
1132
1133! **************************************************************************************************
1134!> \brief Parses the input section used to define the heuristic rules which determine if
1135!> a FM matrix should be redistributed before diagonalizing it.
1136!> \param glob_section the global input section
1137!> \author Nico Holmberg [01.2018]
1138! **************************************************************************************************
1139 SUBROUTINE fm_diag_rules_setup(glob_section)
1140 TYPE(section_vals_type), POINTER :: glob_section
1141
1142 INTEGER :: a, x
1143 LOGICAL :: elpa_force_redistribute, should_print
1144 TYPE(section_vals_type), POINTER :: section
1145
1146 section => section_vals_get_subs_vals(glob_section, "FM_DIAG_SETTINGS")
1147
1148 CALL section_vals_val_get(section, "PARAMETER_A", i_val=a)
1149 CALL section_vals_val_get(section, "PARAMETER_X", i_val=x)
1150 CALL section_vals_val_get(section, "PRINT_FM_REDISTRIBUTE", l_val=should_print)
1151 CALL section_vals_val_get(section, "ELPA_FORCE_REDISTRIBUTE", l_val=elpa_force_redistribute)
1152
1153 CALL cp_fm_redistribute_init(a, x, should_print, elpa_force_redistribute)
1154
1155 END SUBROUTINE fm_diag_rules_setup
1156! **************************************************************************************************
1157!> \brief reads the Walltime also in format HH:MM:SS
1158!> \param section ...
1159!> \param keyword_name ...
1160!> \param walltime ...
1161!> \par History
1162!> none
1163!> \author Mandes
1164! **************************************************************************************************
1165 SUBROUTINE cp2k_get_walltime(section, keyword_name, walltime)
1166 TYPE(section_vals_type), POINTER :: section
1167 CHARACTER(len=*), INTENT(in) :: keyword_name
1168 REAL(kind=dp), INTENT(out) :: walltime
1169
1170 CHARACTER(LEN=1) :: c1, c2
1171 CHARACTER(LEN=100) :: txt
1172 INTEGER :: hours, ierr, minutes, n, seconds
1173
1174 CALL section_vals_val_get(section, keyword_name, c_val=txt)
1175 n = len_trim(txt)
1176
1177 IF (n == 0) THEN
1178 walltime = -1.0_dp
1179 ELSE IF (index(txt, ":") == 0) THEN
1180 READ (txt(1:n), fmt=*, iostat=ierr) walltime
1181 IF (ierr /= 0) cpabort('Could not parse WALLTIME: "'//txt(1:n)//'"')
1182 ELSE
1183 READ (txt(1:n), fmt="(I2,A1,I2,A1,I2)", iostat=ierr) hours, c1, minutes, c2, seconds
1184 IF (n /= 8 .OR. ierr /= 0 .OR. c1 .NE. ":" .OR. c2 .NE. ":") &
1185 cpabort('Could not parse WALLTIME: "'//txt(1:n)//'"')
1186 walltime = 3600.0_dp*real(hours, dp) + 60.0_dp*real(minutes, dp) + real(seconds, dp)
1187 END IF
1188 END SUBROUTINE cp2k_get_walltime
1189
1190! **************************************************************************************************
1191!> \brief Writes final timings and banner for CP2K
1192!> \param root_section ...
1193!> \param para_env ...
1194!> \param globenv ...
1195!> \param wdir ...
1196!> \param q_finalize ...
1197!> \par History
1198!> none
1199!> \author JGH,MK
1200!> \note
1201!> The following routines need to be synchronized wrt. adding/removing
1202!> of the default environments (logging, performance,error):
1203!> environment:cp2k_init, environment:cp2k_finalize,
1204!> f77_interface:f_env_add_defaults, f77_interface:f_env_rm_defaults,
1205!> f77_interface:create_force_env, f77_interface:destroy_force_env
1206! **************************************************************************************************
1207 SUBROUTINE cp2k_finalize(root_section, para_env, globenv, wdir, q_finalize)
1208
1209 TYPE(section_vals_type), POINTER :: root_section
1210 TYPE(mp_para_env_type), POINTER :: para_env
1211 TYPE(global_environment_type), POINTER :: globenv
1212 CHARACTER(LEN=*), OPTIONAL :: wdir
1213 LOGICAL, INTENT(IN), OPTIONAL :: q_finalize
1214
1215 CHARACTER(LEN=default_path_length) :: cg_filename
1216 INTEGER :: cg_mode, iw, unit_exit
1217 LOGICAL :: delete_it, do_finalize, report_maxloc, &
1218 sort_by_self_time
1219 REAL(kind=dp) :: r_timings
1220 TYPE(cp_logger_type), POINTER :: logger
1221
1222 ! Look if we inherited a failure, more care is needed if so
1223 ! i.e. the input is most likely not available
1224 ! Set flag if this is a development version
1225
1226 do_finalize = .true.
1227 IF (PRESENT(q_finalize)) do_finalize = q_finalize
1228 ! Clean up
1229 NULLIFY (logger)
1230 logger => cp_get_default_logger()
1231 IF (do_finalize) THEN
1235 CALL diag_finalize()
1236 ! finalize the fft (i.e. writes the wisdom if FFTW3 )
1237 CALL finalize_fft(para_env, globenv%fftw_wisdom_file_name)
1238 CALL finalize_libvori()
1239 END IF
1240
1241 ! Write message passing performance info
1242
1243 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%PROGRAM_RUN_INFO", &
1244 extension=".log")
1245 CALL describe_mp_perf_env(iw)
1246 CALL cp_print_key_finished_output(iw, logger, root_section, &
1247 "GLOBAL%PROGRAM_RUN_INFO")
1248
1249 CALL collect_citations_from_ranks(para_env)
1250 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%REFERENCES", &
1251 extension=".Log")
1252 IF (iw > 0) THEN
1253 WRITE (unit=iw, fmt="(/,T2,A)") repeat("-", 79)
1254 WRITE (unit=iw, fmt="(T2,A,T80,A)") "-", "-"
1255 WRITE (unit=iw, fmt="(T2,A,T30,A,T80,A)") "-", "R E F E R E N C E S", "-"
1256 WRITE (unit=iw, fmt="(T2,A,T80,A)") "-", "-"
1257 WRITE (unit=iw, fmt="(T2,A)") repeat("-", 79)
1258
1259 WRITE (unit=iw, fmt="(T2,A)") ""
1260 WRITE (unit=iw, fmt="(T2,A)") trim(cp2k_version)//", the CP2K developers group ("//trim(cp2k_year)//")."
1261 WRITE (unit=iw, fmt="(T2,A)") "CP2K is freely available from "//trim(cp2k_home)//" ."
1262
1263 CALL print_all_references(sorted=.true., cited_only=.true., &
1264 format=print_format_journal, unit=iw)
1265 END IF
1266 CALL cp_print_key_finished_output(iw, logger, root_section, &
1267 "GLOBAL%REFERENCES")
1268
1269 CALL timestop(globenv%handle) ! corresponding the "CP2K" in cp2k_init
1270
1271 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%TIMINGS", &
1272 extension=".Log")
1273 r_timings = section_get_rval(root_section, "GLOBAL%TIMINGS%THRESHOLD")
1274 sort_by_self_time = section_get_lval(root_section, "GLOBAL%TIMINGS%SORT_BY_SELF_TIME")
1275 report_maxloc = section_get_lval(root_section, "GLOBAL%TIMINGS%REPORT_MAXLOC")
1276 IF (m_energy() .NE. 0.0_dp) THEN
1277 CALL timings_report_print(iw, r_timings, sort_by_self_time, cost_type_energy, report_maxloc, para_env)
1278 END IF
1279 CALL timings_report_print(iw, r_timings, sort_by_self_time, cost_type_time, report_maxloc, para_env)
1280
1281 ! Write the callgraph, if desired by user
1282 CALL section_vals_val_get(root_section, "GLOBAL%CALLGRAPH", i_val=cg_mode)
1283 IF (cg_mode /= callgraph_none) THEN
1284 CALL section_vals_val_get(root_section, "GLOBAL%CALLGRAPH_FILE_NAME", c_val=cg_filename)
1285 IF (len_trim(cg_filename) == 0) cg_filename = trim(logger%iter_info%project_name)
1286 IF (cg_mode == callgraph_all) & !incorporate mpi-rank into filename
1287 cg_filename = trim(cg_filename)//"_"//trim(adjustl(cp_to_string(para_env%mepos)))
1288 IF (iw > 0) THEN
1289 WRITE (unit=iw, fmt="(T2,3X,A)") "Writing callgraph to: "//trim(cg_filename)//".callgraph"
1290 WRITE (unit=iw, fmt="()")
1291 WRITE (unit=iw, fmt="(T2,A)") "-------------------------------------------------------------------------------"
1292 END IF
1293 IF (cg_mode == callgraph_all .OR. para_env%is_source()) &
1294 CALL timings_report_callgraph(trim(cg_filename)//".callgraph")
1295 END IF
1296
1297 CALL cp_print_key_finished_output(iw, logger, root_section, &
1298 "GLOBAL%TIMINGS")
1299
1300 CALL rm_mp_perf_env()
1301 CALL rm_timer_env()
1302
1303 IF (para_env%is_source()) THEN
1304 iw = cp_print_key_unit_nr(logger, root_section, "GLOBAL%PROGRAM_RUN_INFO", &
1305 extension=".log")
1306
1307 ! Deleting (if existing) the external EXIT files
1308 delete_it = .false.
1309 INQUIRE (file="EXIT", exist=delete_it)
1310 IF (delete_it) THEN
1311 CALL open_file(file_name="EXIT", unit_number=unit_exit)
1312 CALL close_file(unit_number=unit_exit, file_status="DELETE")
1313 END IF
1314
1315 delete_it = .false.
1316 INQUIRE (file=trim(logger%iter_info%project_name)//".EXIT", exist=delete_it)
1317 IF (delete_it) THEN
1318 CALL open_file(file_name=trim(logger%iter_info%project_name)//".EXIT", unit_number=unit_exit)
1319 CALL close_file(unit_number=unit_exit, file_status="DELETE")
1320 END IF
1321
1322 ! Print warning counter
1323 IF (iw > 0) THEN
1324 WRITE (iw, "(T2,A,I0)") "The number of warnings for this run is : ", warning_counter
1325 WRITE (iw, *) ""
1326 WRITE (unit=iw, fmt="(T2,A)") repeat("-", 79)
1327 END IF
1328
1329 ! Update the runtime environment variables
1330 CALL get_runtime_info()
1331
1332 ! Just a choice, do not print the CP2K footer if there is a failure
1333 CALL cp2k_footer(iw, wdir)
1334 IF (iw > 0) FLUSH (iw) ! ignore &GLOBAL / FLUSH_SHOULD_FLUSH
1335
1336 CALL cp_print_key_finished_output(iw, logger, root_section, &
1337 "GLOBAL%PROGRAM_RUN_INFO")
1338 END IF
1339
1340 ! Release message passing environment
1342
1343 END SUBROUTINE cp2k_finalize
1344
1345END MODULE environment
Target architecture or instruction set extension according to compiler target flags.
Definition machine.F:83
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public marek2014
integer, save, public frigo2005
some minimal info about CP2K, including its version and license
Definition cp2k_info.F:16
character(len=default_string_length), public r_host_name
Definition cp2k_info.F:67
character(len= *), parameter, public cp2k_home
Definition cp2k_info.F:43
character(len= *), parameter, public compile_host
Definition cp2k_info.F:61
character(len= *), parameter, public compile_arch
Definition cp2k_info.F:49
integer, public r_pid
Definition cp2k_info.F:68
character(len= *), parameter, public compile_revision
Definition cp2k_info.F:37
character(len= *), parameter, public compile_date
Definition cp2k_info.F:55
character(len= *), parameter, public cp2k_year
Definition cp2k_info.F:42
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 ...
Definition cp2k_info.F:79
character(len= *), parameter, public cp2k_version
Definition cp2k_info.F:41
subroutine, public get_runtime_info()
...
Definition cp2k_info.F:311
character(len=default_string_length), public r_user_name
Definition cp2k_info.F:67
Module that contains the routines for error handling.
integer, save, public warning_counter
Utility routines to open and close files. Tracking of preconnections.
Definition cp_files.F:16
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.
Definition cp_files.F:308
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.
Definition cp_files.F:119
character(len=default_path_length) function, public get_data_dir()
Returns path of data directory if set, otherwise an empty string.
Definition cp_files.F:542
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...
Definition cp_fm_diag.F:17
real(kind=dp), parameter, public eps_check_diag_default
Definition cp_fm_diag.F:69
integer, parameter, public fm_diag_type_cusolver
Definition cp_fm_diag.F:87
integer, parameter, public fm_diag_type_dlaf
Definition cp_fm_diag.F:87
integer, parameter, public fm_diag_type_scalapack
Definition cp_fm_diag.F:87
subroutine, public diag_finalize()
Finalize the diagonalization library.
Definition cp_fm_diag.F:188
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.
Definition cp_fm_diag.F:134
integer, parameter, public fm_diag_type_elpa
Definition cp_fm_diag.F:87
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
Definition cp_fm_types.F:15
integer function, public cp_fm_get_mm_type()
...
subroutine, public cp_fm_setup(mult_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.
Definition environment.F:17
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
subroutine, public init_fft(fftlib, alltoall, fftsg_sizes, pool_limit, wisdom_file, plan_style)
...
Definition fft_tools.F:185
subroutine, public finalize_fft(para_env, wisdom_file)
does whatever is needed to finalize the current fft setup
Definition fft_tools.F:216
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...
Definition gamma.F:15
subroutine, public deallocate_md_ftable()
Deallocate the table of F_n(t) values.
Definition gamma.F:121
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.
Definition grid_api.F:12
integer, parameter, public grid_backend_auto
Definition grid_api.F:66
integer, parameter, public grid_backend_gpu
Definition grid_api.F:70
integer, parameter, public grid_backend_hip
Definition grid_api.F:71
integer, parameter, public grid_backend_dgemm
Definition grid_api.F:69
integer, parameter, public grid_backend_cpu
Definition grid_api.F:68
integer, parameter, public grid_backend_ref
Definition grid_api.F:67
subroutine, public cp2k_header(iw, wdir)
...
Definition header.F:40
subroutine, public cp2k_footer(iw, wdir)
...
Definition header.F:69
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public energy_run
integer, parameter, public do_fft_sg
integer, parameter, public callgraph_all
integer, parameter, public do_farming
integer, parameter, public do_cosma
integer, parameter, public do_cp2k
integer, parameter, public do_scalapack
integer, parameter, public do_eip
integer, parameter, public do_test
integer, parameter, public do_fist
integer, parameter, public do_sirius
integer, parameter, public do_dgemm_blas
integer, parameter, public callgraph_none
integer, parameter, public mol_dyn_run
integer, parameter, public do_fft_fftw3
integer, parameter, public none_run
integer, parameter, public do_qs
integer, parameter, public do_dgemm_spla
builds the global input section for cp2k
subroutine, public create_global_section(section)
section to hold global settings for the whole program
represents an enumeration, i.e. a mapping between integers and strings
character(len=default_string_length) function, public enum_i2c(enum, i)
maps an integer to a string
represents keywords in an input
subroutine, public keyword_get(keyword, names, usage, description, type_of_var, n_var, default_value, lone_keyword_value, repeats, enum, citations)
...
objects that represent the structure of input sections and the data contained in an input section
real(kind=dp) function, public section_get_rval(section_vals, keyword_name)
...
subroutine, public section_vals_val_set(section_vals, keyword_name, i_rep_section, i_rep_val, val, l_val, i_val, r_val, c_val, l_vals_ptr, i_vals_ptr, r_vals_ptr, c_vals_ptr)
sets the requested value
integer function, public section_get_ival(section_vals, keyword_name)
...
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
recursive type(keyword_type) function, pointer, public section_get_keyword(section, keyword_name)
returns the requested keyword
subroutine, public section_vals_get(section_vals, ref_count, n_repetition, n_subs_vals_rep, section, explicit)
returns various attributes about the section_vals
type(section_vals_type) function, pointer, public section_vals_get_subs_vals3(section_vals, subsection_name, i_rep_section)
returns the values of the n-th non default subsection (null if no such section exists (not so many no...
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
logical function, public section_get_lval(section_vals, keyword_name)
...
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public int_8
Definition kinds.F:54
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public default_path_length
Definition kinds.F:58
subroutine, public print_kind_info(iw)
Print informations about the used data types.
Definition kinds.F:72
subroutine, public local_gemm_set_library(dgemm_library)
...
Machine interface based on Fortran 2003 and POSIX.
Definition machine.F:17
logical, save, public flush_should_flush
Definition machine.F:91
subroutine, public m_get_omp_stacksize(omp_stacksize)
Retrieve environment variable OMP_STACKSIZE.
Definition machine.F:656
integer function, public m_procrun(pid)
Returns if a process is running on the local machine 1 if yes and 0 if not.
Definition machine.F:299
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...
Definition machine.F:404
pure integer function, public m_cpuid()
Target architecture or instruction set extension according to CPU-check at runtime.
Definition machine.F:169
real(kind=dp) function, public m_energy()
returns the energy used since some time in the past. The precise meaning depends on the infrastructur...
Definition machine.F:219
subroutine, public m_cpuinfo(model_name)
reads /proc/cpuinfo if it exists (i.e. Linux) to return relevant info
Definition machine.F:137
character(len=default_string_length) function, pointer, public m_cpuid_name(cpuid)
Determine name of target architecture for a given CPUID.
Definition machine.F:187
Interface to the message passing library MPI.
logical, save, public mp_collect_timings
Defines all routines to deal with the performance of MPI routines.
Definition mp_perf_env.F:11
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 ...
Definition mp_perf_env.F:76
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.
Calculation of the spherical harmonics and the corresponding orbital transformation matrices.
subroutine, public init_spherical_harmonics(maxl, output_unit)
Initialize or update the orbital transformation matrices.
subroutine, public deallocate_spherical_harmonics()
Deallocate the orbital transformation matrices.
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:
Definition physcon.F:68
real(kind=dp), parameter, public seconds
Definition physcon.F:150
subroutine, public write_physcon(output_unit)
Write all basic physical constants used by CP2K to a logical output unit.
Definition physcon.F:217
provides a uniform framework to add references to CP2K cite and output these
subroutine, public print_all_references(cited_only, sorted, format, unit, list)
printout of all references in a specific format optionally printing only those that are actually cite...
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.
integer, parameter, public print_format_journal
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.
Definition timings.F:17
integer, save, public global_timings_level
Definition timings.F:68
subroutine, public timings_setup_tracing(trace_max, unit_nr, trace_str, routine_names)
Set routine tracer.
Definition timings.F:398
subroutine, public add_timer_env(timer_env)
adds the given timer_env to the top of the stack
Definition timings.F:93
subroutine, public rm_timer_env()
removes the current timer env from the stack
Definition timings.F:134
character(len=default_string_length), parameter, public root_cp2k_name
Definition timings.F:70
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
represent a keyword in the input
represent a section of the input file
stores all the informations relevant to an mpi environment