21 USE dbcsr_api,
ONLY: dbcsr_test_binary_io,&
23 dbcsr_type_complex_8,&
57#include "../base/base_uses.f90"
62 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
63 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'input_cp2k'
77 CHARACTER(len=*),
PARAMETER :: routinen =
'create_cp2k_root_section'
82 CALL timeset(routinen, handle)
84 cpassert(.NOT.
ASSOCIATED(root_section))
86 description=
"input file of cp2k", n_keywords=0, n_subsections=10, &
94 CALL create_test_section(section)
98 CALL create_debug_section(section)
106 CALL create_multi_force_section(section)
114 CALL create_farming_section(section)
130 CALL create_ext_restart_section(section)
145 CALL timestop(handle)
154 SUBROUTINE create_test_section(section)
161 description=
"Tests to perform on the supported libraries.", &
162 n_keywords=6, n_subsections=0, repeats=.false.)
164 NULLIFY (keyword, print_key)
166 description=
"Set the maximum amount of memory allocated for a given test (in bytes)", &
167 usage=
"MEMORY <REAL>", default_r_val=256.e6_dp)
172 description=
"Tests the performance to copy two vectors. "// &
173 "The results of these tests allow to determine the size of the cache "// &
174 "of the CPU. This can be used to optimize the performance of the "// &
175 "FFTSG library. Tests are repeated the given number of times.", &
176 usage=
"copy 10", default_i_val=0)
181 description=
"Tests the performance of different kinds of matrix matrix "// &
182 "multiply kernels for the F95 INTRINSIC matmul. Matrices up to 2**N+1 will be tested. ", &
183 usage=
"matmul 10", default_i_val=0)
188 description=
"Tests the performance of different kinds of matrix matrix "// &
189 "multiply kernels for the BLAS INTRINSIC DGEMM. Matrices up to 2**N+1 will be tested. ", &
190 usage=
"DGEMM 10", default_i_val=0)
195 description=
"Tests the performance of all available FFT libraries for "// &
196 "3D FFTs Tests are repeated the given number of times.", &
197 usage=
"fft 10", default_i_val=0)
202 description=
"Tests the performance and correctness of ERI libraries ", &
203 usage=
"eri 1", default_i_val=0)
207 CALL keyword_create(keyword, __location__, name=
"CLEBSCH_GORDON", variants=(/
"CLEBSCH"/), &
208 description=
"Tests the Clebsch-Gordon Coefficients. "// &
209 "Tests are repeated the given number of times.", &
210 usage=
"clebsch_gordon 10", default_i_val=0)
216 description=
"Tests mpi, quickly adapted benchmark code, "// &
217 "will ONLY work on an even number of CPUs. comm is the relevant, "// &
218 "initialized communicator. This test will produce messages "// &
219 "of the size 8*10**requested_size, where requested_size is the value "// &
220 "given to this keyword", &
221 usage=
"mpi 6", default_i_val=0)
227 description=
"Tests validity of minimax coefficients for approximating 1/x "// &
228 "as a sum of exponentials. "// &
229 "Checks numerical error against tabulated error, testing "// &
230 "the given number of different Rc values.", &
231 usage=
"MINIMAX 1000", default_i_val=0)
236 description=
"Tests accuracy of the integration weights gamma_ik from Kaltak, "// &
237 "Klimes, Kresse, JCTC 10, 2498 (2014), Eq. 30. Printed is the L1-error (=minimax "// &
238 "error for a given range and a given number of grid points. The input parameter is "// &
239 "the given number of different Rc values.", &
240 usage=
"LEAST_SQ_FT 1000", default_i_val=0)
245 print_key, __location__,
"GRID_INFORMATION", &
246 description=
"Controls the printing of information regarding the PW and RS grid structures"// &
247 " (ONLY for TEST run).", &
253 description=
"Controls the printing of the test output", &
259 CALL create_rs_pw_transfer_section(subsection)
263 CALL create_eigensolver_section(subsection)
267 CALL create_pw_transfer_section(subsection)
271 CALL create_cp_fm_gemm_section(subsection)
275 CALL create_cp_dbcsr_section(subsection)
279 CALL create_dbm_section(subsection)
291 END SUBROUTINE create_test_section
298 SUBROUTINE create_debug_section(section)
305 description=
"Section to setup parameters for debug runs.", &
306 n_keywords=7, n_subsections=0, repeats=.false.)
308 NULLIFY (keyword, print_key)
311 description=
"Activates the debugging of the atomic forces", &
312 usage=
"DEBUG_FORCES {LOGICAL}", default_l_val=.true., &
313 lone_keyword_l_val=.true.)
317 CALL keyword_create(keyword, __location__, name=
"DEBUG_STRESS_TENSOR", &
318 description=
"Activates the debugging of the stress tensor", &
319 usage=
"DEBUG_STRESS_TENSOR {LOGICAL}", default_l_val=.true., &
320 lone_keyword_l_val=.true.)
325 description=
"Activates the debugging of the dipole moment", &
326 usage=
"DEBUG_DIPOLE {LOGICAL}", default_l_val=.false., &
327 lone_keyword_l_val=.true.)
331 CALL keyword_create(keyword, __location__, name=
"DEBUG_POLARIZABILITY", &
332 description=
"Activates the debugging of the polarizability", &
333 usage=
"DEBUG_POLARIZABILITY {LOGICAL}", default_l_val=.false., &
334 lone_keyword_l_val=.true.)
339 description=
"Increment for the calculation of the numerical derivatives", &
340 usage=
"DX {REAL}", default_r_val=0.001_dp)
345 description=
"Increment for the calculation of the numerical electric field derivatives", &
346 usage=
"DE {REAL}", default_r_val=0.0001_dp)
350 CALL keyword_create(keyword, __location__, name=
"MAX_RELATIVE_ERROR", &
351 description=
"The maximum relative error that will be "// &
352 "flagged [in percent]. ", &
353 usage=
"MAX_RELATIVE_ERROR {REAL}", default_r_val=0.2_dp)
357 CALL keyword_create(keyword, __location__, name=
"EPS_NO_ERROR_CHECK", &
358 description=
"The mismatch between the numerical and the "// &
359 "analytical value is not checked for analytical "// &
360 "values smaller than this threshold value", &
361 usage=
"EPS_NO_ERROR_CHECK {REAL}", default_r_val=1.0e-5_dp)
365 CALL keyword_create(keyword, __location__, name=
"STOP_ON_MISMATCH", &
366 description=
"Stop the debug run when a mismatch between the numerical and "// &
367 "the analytical value is detected", &
368 usage=
"STOP_ON_MISMATCH {LOGICAL}", default_l_val=.true., &
369 lone_keyword_l_val=.true.)
373 CALL keyword_create(keyword, __location__, name=
"CHECK_DIPOLE_DIRS", &
374 description=
"Dipole coordinates to be checked", &
375 usage=
"CHECK_DIPOLE_DIRS XZ", type_of_var=
char_t, &
380 CALL keyword_create(keyword, __location__, name=
"CHECK_ATOM_FORCE", &
381 description=
"Atom force directions to be checked [atom_number coordinates]", &
382 usage=
"CHECK_ATOM_FORCE 1 XZ", &
383 type_of_var=
char_t, n_var=2, repeats=.true.)
388 description=
"Controls the printing of the DEBUG specific output", &
393 END SUBROUTINE create_debug_section
400 SUBROUTINE create_multi_force_section(section)
405 cpassert(.NOT.
ASSOCIATED(section))
406 CALL section_create(section, __location__, name=
"MULTIPLE_FORCE_EVALS", &
407 description=
"Describes how to handle multiple force_evals.", &
408 n_keywords=1, n_subsections=0, repeats=.false.)
411 CALL keyword_create(keyword, __location__, name=
"FORCE_EVAL_ORDER", &
412 description=
'Specify the orders of the different force_eval. When using a MIXED force_eval'// &
413 " this does not need to be specified in this list, because it that takes into account only the real"// &
414 " energy contributions", &
415 usage=
"FORCE_EVAL_ORDER <INTEGER> .. <INTEGER>", type_of_var=
integer_t, n_var=-1, &
416 default_i_vals=(/1/))
420 CALL keyword_create(keyword, __location__, name=
"MULTIPLE_SUBSYS", &
421 description=
"Specify if force_eval have different subsys. In case they share the same subsys,"// &
422 " it needs to be specified only in the MIXED force_eval (if using MIXED) or"// &
423 " in the force_eval corresponding to first force_eval of the previous order (when not using MIXED).", &
424 default_l_val=.false., lone_keyword_l_val=.true.)
428 END SUBROUTINE create_multi_force_section
435 SUBROUTINE create_ext_restart_section(section)
440 cpassert(.NOT.
ASSOCIATED(section))
442 description=
"Section for external restart, specifies an external "// &
443 "input file where to take positions, etc. "// &
444 "By default they are all set to TRUE", &
445 n_keywords=1, n_subsections=0, repeats=.false.)
448 CALL keyword_create(keyword, __location__, name=
"RESTART_FILE_NAME", variants=(/
"EXTERNAL_FILE"/), &
449 description=
"Specifies the name of restart file (or any other input file)"// &
450 " to be read. Only fields relevant to a restart will be used"// &
451 " (unless switched off with the keywords in this section)", &
456 CALL keyword_create(keyword, __location__, name=
"BINARY_RESTART_FILE_NAME", &
457 variants=(/
"BINARY_RESTART_FILE"/), &
458 description=
"Specifies the name of an additional restart file "// &
459 "from which selected input sections are read in binary format "// &
460 "(see SPLIT_RESTART_FILE).", &
465 CALL keyword_create(keyword, __location__, name=
"RESTART_DEFAULT", &
466 description=
"This keyword controls the default value for all possible"// &
467 " restartable keywords, unless explicitly defined. For example setting"// &
468 " this keyword to .FALSE. does not restart any quantity. If, at the"// &
469 " same time, one keyword is set to .TRUE. only that quantity will be"// &
470 " restarted.", default_l_val=.true.)
473 CALL keyword_create(keyword, __location__, name=
"RESTART_COUNTERS", &
474 description=
"Restarts the counters in MD schemes and optimization STEP", &
475 type_of_var=
logical_t, lone_keyword_l_val=.true.)
479 description=
"Takes the positions from the external file", &
480 type_of_var=
logical_t, lone_keyword_l_val=.true.)
484 description=
"Takes the velocities from the external file", &
485 type_of_var=
logical_t, lone_keyword_l_val=.true.)
488 CALL keyword_create(keyword, __location__, name=
"RESTART_RANDOMG", &
489 description=
"Restarts the random number generator from the external file", &
490 type_of_var=
logical_t, lone_keyword_l_val=.true.)
494 CALL keyword_create(keyword, __location__, name=
"RESTART_SHELL_POS", &
495 description=
"Takes the positions of the shells from the external file (only if shell-model)", &
496 type_of_var=
logical_t, lone_keyword_l_val=.true.)
499 CALL keyword_create(keyword, __location__, name=
"RESTART_CORE_POS", &
500 description=
"Takes the positions of the cores from the external file (only if shell-model)", &
501 type_of_var=
logical_t, lone_keyword_l_val=.true.)
504 CALL keyword_create(keyword, __location__, name=
"RESTART_OPTIMIZE_INPUT_VARIABLES", &
505 description=
"Restart with the optimize input variables", &
506 type_of_var=
logical_t, lone_keyword_l_val=.true.)
510 CALL keyword_create(keyword, __location__, name=
"RESTART_SHELL_VELOCITY", &
511 description=
"Takes the velocities of the shells from the external file (only if shell-model)", &
512 type_of_var=
logical_t, lone_keyword_l_val=.true.)
515 CALL keyword_create(keyword, __location__, name=
"RESTART_CORE_VELOCITY", &
516 description=
"Takes the velocities of the shells from the external file (only if shell-model)", &
517 type_of_var=
logical_t, lone_keyword_l_val=.true.)
520 CALL keyword_create(keyword, __location__, name=
"RESTART_BAROSTAT", &
521 description=
"Restarts the barostat from the external file", &
522 type_of_var=
logical_t, lone_keyword_l_val=.true.)
525 CALL keyword_create(keyword, __location__, name=
"RESTART_BAROSTAT_THERMOSTAT", &
526 description=
"Restarts the barostat thermostat from the external file", &
527 type_of_var=
logical_t, lone_keyword_l_val=.true.)
530 CALL keyword_create(keyword, __location__, name=
"RESTART_SHELL_THERMOSTAT", &
531 description=
"Restarts the shell thermostat from the external file", &
532 type_of_var=
logical_t, lone_keyword_l_val=.true.)
535 CALL keyword_create(keyword, __location__, name=
"RESTART_THERMOSTAT", &
536 description=
"Restarts the nose thermostats of the particles "// &
537 "from the EXTERNAL file", &
538 type_of_var=
logical_t, lone_keyword_l_val=.true.)
541 CALL keyword_create(keyword, __location__, name=
"RESTART_TEMPERATURE_ANNEALING", &
542 description=
"Restarts external temperature when using TEMPERATURE_ANNEALING.", &
543 type_of_var=
logical_t, lone_keyword_l_val=.true., default_l_val=.false.)
547 description=
"Restarts the cell (and cell_ref) "// &
548 "from the EXTERNAL file", &
549 type_of_var=
logical_t, lone_keyword_l_val=.true.)
552 CALL keyword_create(keyword, __location__, name=
"RESTART_METADYNAMICS", &
553 description=
"Restarts hills from a previous metadynamics run "// &
554 "from the EXTERNAL file", &
555 type_of_var=
logical_t, lone_keyword_l_val=.true.)
558 CALL keyword_create(keyword, __location__, name=
"RESTART_WALKERS", &
559 description=
"Restarts walkers informations from a previous metadynamics run "// &
560 "from the EXTERNAL file", &
561 type_of_var=
logical_t, lone_keyword_l_val=.true.)
565 description=
"Restarts positions and velocities of the Band.", &
566 type_of_var=
logical_t, lone_keyword_l_val=.true.)
570 description=
"Restarts the following specific QMMM info: translation vectors.", &
571 type_of_var=
logical_t, lone_keyword_l_val=.true.)
574 CALL keyword_create(keyword, __location__, name=
"RESTART_CONSTRAINT", &
575 description=
"Restarts constraint section. It's necessary when doing restraint"// &
576 " calculation to have a perfect energy conservation. For constraints only its"// &
577 " use is optional.", &
578 type_of_var=
logical_t, lone_keyword_l_val=.true.)
582 description=
"Restarts information for BSSE calculations.", &
583 type_of_var=
logical_t, lone_keyword_l_val=.true.)
586 CALL keyword_create(keyword, __location__, name=
"RESTART_DIMER", &
587 description=
"Restarts information for DIMER geometry optimizations.", &
588 type_of_var=
logical_t, lone_keyword_l_val=.true.)
591 CALL keyword_create(keyword, __location__, name=
"RESTART_AVERAGES", &
592 description=
"Restarts information for AVERAGES.", &
593 type_of_var=
logical_t, lone_keyword_l_val=.true.)
597 description=
"Restarts information for REAL TIME PROPAGATION and EHRENFEST DYNAMICS.", &
598 type_of_var=
logical_t, lone_keyword_l_val=.true.)
602 description=
"Restarts the given path from the EXTERNAL file. Allows a major flexibility for restarts.", &
603 type_of_var=
char_t, repeats=.true.)
608 CALL keyword_create(keyword, __location__, name=
"RESTART_PINT_POS", &
609 description=
"Restart bead positions from PINT%BEADS%COORD.", &
610 type_of_var=
logical_t, lone_keyword_l_val=.true.)
613 CALL keyword_create(keyword, __location__, name=
"RESTART_PINT_VEL", &
614 description=
"Restart bead velocities from PINT%BEADS%VELOCITY.", &
615 type_of_var=
logical_t, lone_keyword_l_val=.true.)
618 CALL keyword_create(keyword, __location__, name=
"RESTART_PINT_NOSE", &
619 description=
"Restart Nose thermostat for beads from PINT%NOSE.", &
620 type_of_var=
logical_t, lone_keyword_l_val=.true.)
623 CALL keyword_create(keyword, __location__, name=
"RESTART_PINT_GLE", &
624 description=
"Restart GLE thermostat for beads from PINT%GLE.", &
625 type_of_var=
logical_t, lone_keyword_l_val=.true.)
630 CALL keyword_create(keyword, __location__, name=
"RESTART_HELIUM_POS", &
631 description=
"Restart helium positions from PINT%HELIUM%COORD.", &
632 type_of_var=
logical_t, lone_keyword_l_val=.true.)
635 CALL keyword_create(keyword, __location__, name=
"RESTART_HELIUM_PERMUTATION", &
636 description=
"Restart helium permutation state from PINT%HELIUM%PERM.", &
637 type_of_var=
logical_t, lone_keyword_l_val=.true.)
640 CALL keyword_create(keyword, __location__, name=
"RESTART_HELIUM_FORCE", &
641 description=
"Restart helium forces exerted on the solute from PINT%HELIUM%FORCE.", &
642 type_of_var=
logical_t, lone_keyword_l_val=.true.)
645 CALL keyword_create(keyword, __location__, name=
"RESTART_HELIUM_RNG", &
646 description=
"Restarts helium random number generators from PINT%HELIUM%RNG_STATE.", &
647 type_of_var=
logical_t, lone_keyword_l_val=.true.)
650 CALL keyword_create(keyword, __location__, name=
"RESTART_HELIUM_DENSITIES", &
651 description=
"Restarts helium density distributions from PINT%HELIUM%RHO.", &
652 type_of_var=
logical_t, lone_keyword_l_val=.true., &
653 default_l_val=.false.)
656 CALL keyword_create(keyword, __location__, name=
"RESTART_HELIUM_AVERAGES", &
657 description=
"Restarts average properties from PINT%HELIUM%AVERAGES.", &
658 type_of_var=
logical_t, lone_keyword_l_val=.true., default_l_val=.false.)
662 END SUBROUTINE create_ext_restart_section
669 SUBROUTINE create_farming_section(section)
675 cpassert(.NOT.
ASSOCIATED(section))
677 description=
"Describes a farming job, in which multiple inputs are executed."//
newline// &
678 "The RUN_TYPE in the global section has to be set to NONE for FARMING."//
newline// &
679 "The different groups are executed in parallel. The jobs inside the same groups in series.", &
681 NULLIFY (keyword, print_key)
684 keyword, __location__, name=
"CAPTAIN_MINION", &
685 description=
"If a captain/minion setup should be employed, in which one process (captain) is used to distribute the tasks. "// &
686 "This is most useful to load-balance if not all jobs have the same length, "// &
687 "and a lot of CPUs/groups are available.", &
688 usage=
"CAPTAIN_MINION", default_l_val=.false., lone_keyword_l_val=.true.)
692 CALL keyword_create(keyword, __location__, name=
"NGROUPS", variants=(/
"NGROUP"/), &
693 description=
"Gives the preferred number of working groups.", &
694 usage=
"ngroups 4", type_of_var=
integer_t)
699 description=
"Gives the preferred size of a working group, "// &
700 "groups will always be equal or larger than this size.", &
701 usage=
"group_size 2", default_i_val=8)
706 description=
"Stride to be used when building working groups from the parent MPI comm. "// &
707 "Can be used to layout minion groups over nodes in advanced ways (1 rank per node / 2 groups per node).", &
708 usage=
"STRIDE 2", default_i_val=1)
712 CALL keyword_create(keyword, __location__, name=
"GROUP_PARTITION", &
713 description=
"gives the exact number of processors for each group.", &
714 usage=
"group_partition 2 2 4 2 4 ", type_of_var=
integer_t, n_var=-1)
718 CALL keyword_create(keyword, __location__, name=
"MAX_JOBS_PER_GROUP", &
719 variants=(/
"MAX_JOBS"/), &
720 description=
"maximum number of jobs executed per group", &
721 usage=
"MAX_JOBS_PER_GROUP 4", default_i_val=65535)
726 keyword, __location__, name=
"CYCLE", &
727 description=
"If farming should process all jobs in a cyclic way, stopping only if MAX_JOBS_PER_GROUP is exceeded.", &
728 usage=
"CYCLE", default_l_val=.false., lone_keyword_l_val=.true.)
733 keyword, __location__, name=
"WAIT_TIME", &
734 description=
"Time to wait [s] for a new task if no task is currently available, make this zero if no clock is available", &
735 usage=
"WAIT_TIME 0.1", default_r_val=0.5_dp)
739 NULLIFY (sub_section)
741 description=
"description of the jobs to be executed", &
745 description=
"the directory in which the job should be executed", &
746 usage=
"DIRECTORY /my/path", &
751 CALL keyword_create(keyword, __location__, name=
"INPUT_FILE_NAME", &
752 description=
"the filename of the input file", &
753 usage=
"INPUT_FILE_NAME my_input.inp", &
754 default_lc_val=
"input.inp")
759 keyword, __location__, name=
"OUTPUT_FILE_NAME", &
760 description=
"the filename of the output file, if not specified will use the project name in the &GLOBAL section.", &
761 usage=
"OUTPUT_FILE_NAME my_input.inp", &
767 description=
"An ID used to indentify a job in DEPENDENCIES. "// &
768 "JOB_IDs do not need to be unique, dependencies will be on all jobs with a given ID. "// &
769 "If no JOB_ID is given, the index of the &JOB section in the input file will be used.", &
770 usage=
"JOB_ID 13", type_of_var=
integer_t)
775 keyword, __location__, name=
"DEPENDENCIES", &
776 description=
"specifies a list of JOB_IDs on which the current job depends. "// &
777 "The current job will not be executed before all the dependencies have finished. "// &
778 "The keyword requires a CAPTAIN_MINION farming run. "// &
779 "Beyond the default case, some special cases might arise: "// &
780 "1) circular dependencies will lead to a deadlock. "// &
781 "2) This keyword is not compatible with CYCLE. "// &
782 "3) MAX_JOBS_PER_GROUP is ignored (though only a total of MAX_JOBS_PER_GROUP*NGROUPS jobs will be executed) "// &
783 "4) dependencies on jobs that will not be executed (due to RESTART or MAX_JOBS_PER_GROUP) are ignored. "// &
784 "Additionally, note that, on some file systems, "// &
785 "output (restart) files might not be immediately available on all compute nodes, "// &
786 "potentially resulting in unexpected failures.", &
787 usage=
"DEPENDENCIES 13 1 7", type_of_var=
integer_t, n_var=-1)
794 description=
"Controls the printing of FARMING specific output", &
800 description=
"Restart a farming job (and should pick up where the previous left off)", &
801 usage=
"DO_RESTART", default_l_val=.false., lone_keyword_l_val=.true.)
805 CALL keyword_create(keyword, __location__, name=
"RESTART_FILE_NAME", &
806 description=
"Name of the restart file to use for restarting a FARMING run. If not "// &
807 "specified the name is determined from PROJECT name.", &
808 usage=
"RESTART_FILE_NAME <FILENAME>", type_of_var=
lchar_t)
813 description=
"controls the printing of the restart for FARMING.", &
818 END SUBROUTINE create_farming_section
826 SUBROUTINE create_rs_pw_transfer_section(section)
832 cpassert(.NOT.
ASSOCIATED(section))
833 CALL section_create(section, __location__, name=
"RS_PW_TRANSFER", &
834 description=
"Describes how to benchmark the rs_pw_transfer routines.", &
835 n_keywords=1, n_subsections=0, repeats=.false.)
839 description=
"Specify the number of grid points (not all grid points are allowed)", &
840 usage=
"GRID_DIMENSIONS 128 128 128", type_of_var=
integer_t, n_var=3, &
841 default_i_vals=(/128, 128, 128/))
846 description=
"number of grid points of the halo", &
847 usage=
"HALO_SIZE 17", default_i_val=17)
852 description=
"Number of rs_pw_transfers being timed", &
853 usage=
"N_LOOP 100", default_i_val=10)
858 description=
"should the direction be rs2pw (pw2rs otherwise)", &
859 usage=
"rs2pw TRUE", default_l_val=.true.)
868 END SUBROUTINE create_rs_pw_transfer_section
876 SUBROUTINE create_pw_transfer_section(section)
881 cpassert(.NOT.
ASSOCIATED(section))
883 description=
"Benchmark and test the pw_transfer routines.", &
884 n_keywords=1, n_subsections=0, repeats=.true.)
888 description=
"Specify the number of grid points (not all grid points are allowed)", &
889 usage=
"GRID_DIMENSIONS 128 128 128", type_of_var=
integer_t, n_var=3, &
890 default_i_vals=(/128, 128, 128/))
895 description=
"Number of pw_transfers (backward&forward) being timed", &
896 usage=
"N_LOOP 100", default_i_val=100)
901 description=
"What kind of PW_GRID should be employed", &
902 usage=
"PW_GRID NS-FULLSPACE", &
903 enum_c_vals=
s2a(
"SPHERICAL",
"NS-FULLSPACE",
"NS-HALFSPACE"), &
904 enum_desc=
s2a(
"- not tested",
" tested",
" - not tested"), &
910 CALL keyword_create(keyword, __location__, name=
"PW_GRID_LAYOUT_ALL", &
911 description=
"loop overal all PW_GRID_LAYOUTs that are compatible with a given number of CPUs ", &
912 usage=
"PW_GRID_LAYOUT_ALL", default_l_val=.false., lone_keyword_l_val=.true.)
917 description=
"Do the FFT in debug mode in all cases", &
918 usage=
"DEBUG", default_l_val=.false., lone_keyword_l_val=.true.)
922 CALL keyword_create(keyword, __location__, name=
"PW_GRID_LAYOUT", &
923 description=
"Expert use only, leave the default... "// &
924 "Can be used to set the distribution for ray-distributed FFT.", &
925 usage=
"PW_GRID_LAYOUT", &
926 repeats=.false., n_var=2, &
927 default_i_vals=(/-1, -1/))
931 CALL keyword_create(keyword, __location__, name=
"PW_GRID_BLOCKED", &
932 description=
"Expert use only, leave the default... "// &
933 "Can be used to set the distribution in g-space for the pw grids and their FFT.", &
934 usage=
"PW_GRID_BLOCKED FREE", &
935 enum_c_vals=
s2a(
"FREE",
"TRUE",
"FALSE"), &
936 enum_desc=
s2a(
"CP2K will select the optimal value",
"blocked",
"not blocked"), &
942 END SUBROUTINE create_pw_transfer_section
950 SUBROUTINE create_cp_fm_gemm_section(section)
955 cpassert(.NOT.
ASSOCIATED(section))
957 description=
"Benchmark and test the cp_fm_gemm routines by multiplying C=A*B ", &
958 n_keywords=1, n_subsections=0, repeats=.true.)
962 description=
"Number of cp_fm_gemm operations being timed (useful for small matrices).", &
963 usage=
"N_LOOP 10", default_i_val=10)
968 description=
"Dimension 1 of C", &
969 usage=
"K 1024", default_i_val=256)
973 description=
"Inner dimension M ", &
974 usage=
"M 1024", default_i_val=256)
978 description=
"Dimension 2 of C", &
979 usage=
"N 1024", default_i_val=256)
984 description=
"block_size for rows", &
985 usage=
"nrow_block 64", default_i_val=32)
990 description=
"block_size for cols", &
991 usage=
"NCOL_BLOCK 64", default_i_val=32)
996 description=
"Use a row major blacs grid", &
997 usage=
"ROW_MAJOR .FALSE.", default_l_val=.true., lone_keyword_l_val=.true.)
1001 CALL keyword_create(keyword, __location__, name=
"FORCE_BLOCKSIZE", &
1002 description=
"Forces the blocksize, even if this implies that a few processes might have no data", &
1003 usage=
"FORCE_BLOCKSIZE", default_l_val=.false., lone_keyword_l_val=.true.)
1008 description=
"Explicitly set the blacs 2D processor layout."// &
1009 " If the product differs from the number of MPI ranks,"// &
1010 " it is ignored and a default nearly square layout is used.", n_var=2, &
1011 usage=
"GRID_2D 64 16 ", default_i_vals=(/1, 1/))
1016 description=
"Transpose matrix A", &
1017 usage=
"TRANSA", default_l_val=.false., lone_keyword_l_val=.true.)
1022 description=
"Transpose matrix B", &
1023 usage=
"TRANSB", default_l_val=.false., lone_keyword_l_val=.true.)
1027 END SUBROUTINE create_cp_fm_gemm_section
1035 SUBROUTINE create_eigensolver_section(section)
1040 cpassert(.NOT.
ASSOCIATED(section))
1042 description=
"Benchmark and test the eigensolver routines.", &
1043 n_keywords=1, n_subsections=0, repeats=.true.)
1047 description=
"Dimension of the square matrix", &
1048 usage=
"N 1024", default_i_val=256)
1053 description=
"Number of operations being timed (useful for small matrices).", &
1054 usage=
"N_LOOP 10", default_i_val=10)
1059 description=
"Diagonalization strategy", &
1060 usage=
"DIAG_METHOD syevd", &
1061 enum_c_vals=
s2a(
"syevd",
"syevx"), &
1062 enum_desc=
s2a(
"(sca)lapacks syevd",
"(sca)lapacks syevx"), &
1069 description=
"number of eigenvalues to be computed (all=<0) ", &
1070 usage=
"EIGENVALUES 13", default_i_val=-1)
1075 description=
"Initialization approach", &
1076 usage=
"INIT_METHOD RANDOM", &
1077 enum_c_vals=
s2a(
"random",
"read"), &
1078 enum_desc=
s2a(
"use a random initial matrix",
"read a matrix from file MATRIX"), &
1084 END SUBROUTINE create_eigensolver_section
1092 SUBROUTINE create_cp_dbcsr_section(section)
1097 cpassert(.NOT.
ASSOCIATED(section))
1099 description=
"Benchmark and test the cp_dbcsr routines", &
1100 n_keywords=1, n_subsections=0, repeats=.true.)
1104 description=
"Number of operations being timed (useful for small matrices).", &
1105 usage=
"N_LOOP 10", default_i_val=10)
1110 description=
"Data type of the matrices", &
1111 usage=
"DATA_TYPE real_8", &
1112 default_i_val=dbcsr_type_real_8, &
1113 enum_c_vals=
s2a(
"real_8",
"complex_8"), &
1114 enum_i_vals=(/dbcsr_type_real_8, dbcsr_type_complex_8/), &
1116 "Real (Double Precision)", &
1117 "Complex (Double Precision)"))
1122 description=
"Which part of DBCSR is tested", &
1123 usage=
"TEST_TYPE MM", &
1124 default_i_val=dbcsr_test_mm, &
1125 enum_c_vals=
s2a(
"MM",
"Binary_IO"), &
1126 enum_i_vals=(/dbcsr_test_mm, dbcsr_test_binary_io/), &
1128 "Run matrix multiplications", &
1129 "Run binary IO checks"))
1134 description=
"Dimension 1 of C", &
1135 usage=
"M 1024", default_i_val=256)
1139 description=
"Dimension 2 of C", &
1140 usage=
"N 1024", default_i_val=256)
1144 description=
"Inner dimension M ", &
1145 usage=
"K 1024", default_i_val=256)
1150 description=
"Transpose matrix A", &
1151 usage=
"TRANSA", default_l_val=.false., lone_keyword_l_val=.true.)
1156 description=
"Transpose matrix B", &
1157 usage=
"TRANSB", default_l_val=.false., lone_keyword_l_val=.true.)
1162 description=
"Row block sizes of C", n_var=-1, &
1163 usage=
"BS_M 1 13 2 5", default_i_vals=(/1, 13, 2, 15/))
1168 description=
"Column block sizes of C", n_var=-1, &
1169 usage=
"BS_N 1 13 2 5", default_i_vals=(/1, 13, 2, 15/))
1174 description=
"Block sizes of inner dimension", n_var=-1, &
1175 usage=
"BS_K 1 13 2 5", default_i_vals=(/1, 13, 2, 15/))
1180 description=
"Matrix A type", &
1181 usage=
"ATYPE N", default_c_val=
'N')
1185 description=
"Matrix B type", &
1186 usage=
"BTYPE N", default_c_val=
'N')
1190 description=
"Matrix C type", &
1191 usage=
"CTYPE N", default_c_val=
'N')
1196 description=
"Number of processors to test", n_var=-1, &
1197 usage=
"NPROC 128 16 1", default_i_vals=(/0/))
1202 description=
"Keep product sparse", &
1203 usage=
"KEEPSPARSE", default_l_val=.false., lone_keyword_l_val=.true.)
1208 description=
"Sparsity of A matrix", &
1209 usage=
"ASPARSITY 70", default_r_val=0.0_dp)
1214 description=
"Sparsity of B matrix", &
1215 usage=
"BSPARSITY 80", default_r_val=0.0_dp)
1220 description=
"Sparsity of C matrix", &
1221 usage=
"CSPARSITY 90", default_r_val=0.0_dp)
1226 description=
"Multiplication factor", &
1227 usage=
"ALPHA 2.0", default_r_val=1.0_dp)
1232 description=
"Product premultiplication factor", &
1233 usage=
"BETA 1.0", default_r_val=0.0_dp)
1238 description=
"Threshold for on-the-fly and final filtering.", &
1239 usage=
"FILTER_EPS 1.0", default_r_val=-1.0_dp)
1243 CALL keyword_create(keyword, __location__, name=
"ALWAYS_CHECKSUM", &
1244 description=
"perform a checksum after each multiplication", &
1245 usage=
"ALWAYS_CHECKSUM", default_l_val=.false., lone_keyword_l_val=.true.)
1249 END SUBROUTINE create_cp_dbcsr_section
1256 SUBROUTINE create_dbm_section(section)
1261 cpassert(.NOT.
ASSOCIATED(section))
1263 description=
"Benchmark and test the dbm routines", &
1264 n_keywords=1, n_subsections=0, repeats=.true.)
1268 description=
"Number of operations being timed (useful for small matrices).", &
1269 usage=
"N_LOOP 10", default_i_val=10)
1274 description=
"Dimension 1 of C", &
1275 usage=
"M 1024", default_i_val=256)
1279 description=
"Dimension 2 of C", &
1280 usage=
"N 1024", default_i_val=256)
1284 description=
"Inner dimension M ", &
1285 usage=
"K 1024", default_i_val=256)
1290 description=
"Transpose matrix A", &
1291 usage=
"TRANSA", default_l_val=.false., lone_keyword_l_val=.true.)
1296 description=
"Transpose matrix B", &
1297 usage=
"TRANSB", default_l_val=.false., lone_keyword_l_val=.true.)
1302 description=
"Row block sizes of C", n_var=-1, &
1303 usage=
"BS_M 1 13 2 5", default_i_vals=(/1, 13, 2, 15/))
1308 description=
"Column block sizes of C", n_var=-1, &
1309 usage=
"BS_N 1 13 2 5", default_i_vals=(/1, 13, 2, 15/))
1314 description=
"Block sizes of inner dimension", n_var=-1, &
1315 usage=
"BS_K 1 13 2 5", default_i_vals=(/1, 13, 2, 15/))
1320 description=
"Keep product sparse", &
1321 usage=
"KEEPSPARSE", default_l_val=.false., lone_keyword_l_val=.true.)
1326 description=
"Sparsity of A matrix", &
1327 usage=
"ASPARSITY 70", default_r_val=0.0_dp)
1332 description=
"Sparsity of B matrix", &
1333 usage=
"BSPARSITY 80", default_r_val=0.0_dp)
1338 description=
"Sparsity of C matrix", &
1339 usage=
"CSPARSITY 90", default_r_val=0.0_dp)
1344 description=
"Multiplication factor", &
1345 usage=
"ALPHA 2.0", default_r_val=1.0_dp)
1350 description=
"Product premultiplication factor", &
1351 usage=
"BETA 1.0", default_r_val=0.0_dp)
1356 description=
"Threshold for on-the-fly and final filtering.", &
1357 usage=
"FILTER_EPS 1.0", default_r_val=-1.0_dp)
1361 CALL keyword_create(keyword, __location__, name=
"ALWAYS_CHECKSUM", &
1362 description=
"perform a checksum after each multiplication", &
1363 usage=
"ALWAYS_CHECKSUM", default_l_val=.false., lone_keyword_l_val=.true.)
1367 END SUBROUTINE create_dbm_section
Interface to Minimax-Ewald method for periodic ERI's to be used in CP2K.
subroutine, public create_eri_mme_test_section(section)
Create input section for unit testing.
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public low_print_level
integer, parameter, public medium_print_level
integer, parameter, public add_last_numeric
integer, parameter, public silent_print_level
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
Defines the basic variable types.
integer, parameter, public dp
This module defines the grid data type and some basic operations on it.
integer, parameter, public do_pw_grid_blocked_false
integer, parameter, public do_pw_grid_blocked_true
integer, parameter, public do_pw_grid_blocked_free
Calculates 2-center integrals for different r12 operators comparing the Solid harmonic Gaussian integ...
subroutine, public create_shg_integrals_test_section(section)
Create input section for unit testing.
Utilities for string manipulations.
character(len=1), parameter, public newline