Skip to content

Commit

Permalink
add cli argument -E to set preprocessor variables
Browse files Browse the repository at this point in the history
  • Loading branch information
dev-zero committed Jan 23, 2020
1 parent ff33c0d commit ef30ff0
Show file tree
Hide file tree
Showing 5 changed files with 77 additions and 32 deletions.
9 changes: 6 additions & 3 deletions src/f77_interface.F
Original file line number Diff line number Diff line change
Expand Up @@ -538,7 +538,7 @@ END SUBROUTINE f_env_rm_defaults
!> instead of parsing from file
!> \param ierr will return a number different from 0 if there was an error
!> \param work_dir ...
!> \param initial_variables ...
!> \param initial_variables key-value list of initial preprocessor variables
!> \author fawzi
!> \note
!> The following routines need to be synchronized wrt. adding/removing
Expand Down Expand Up @@ -1420,15 +1420,18 @@ END SUBROUTINE calc_force
!> defaults made explicit
!> \param mpi_comm the mpi communicator (if not given it uses the default
!> one)
!> \param initial_variables key-value list of initial preprocessor variables
!> \param ierr error control, if different from 0 there was an error
!> \author fawzi
! **************************************************************************************************
SUBROUTINE check_input(input_declaration, input_file_path, output_file_path, &
echo_input, mpi_comm, ierr)
echo_input, mpi_comm, initial_variables, ierr)
TYPE(section_type), POINTER :: input_declaration
CHARACTER(len=*), INTENT(in) :: input_file_path, output_file_path
LOGICAL, INTENT(in), OPTIONAL :: echo_input
INTEGER, INTENT(in), OPTIONAL :: mpi_comm
CHARACTER(len=default_path_length), &
DIMENSION(:, :), INTENT(IN) :: initial_variables
INTEGER, INTENT(out) :: ierr

CHARACTER(len=*), PARAMETER :: routineN = 'check_input', routineP = moduleN//':'//routineN
Expand Down Expand Up @@ -1468,7 +1471,7 @@ SUBROUTINE check_input(input_declaration, input_file_path, output_file_path, &
CALL cp_add_default_logger(logger)
CALL cp_logger_release(logger)

input_file => read_input(input_declaration, input_file_path, initial_variables=empty_initial_variables, &
input_file => read_input(input_declaration, input_file_path, initial_variables=initial_variables, &
para_env=para_env)
CALL check_cp2k_input(input_declaration, input_file, para_env=para_env, output_unit=unit_nr)
IF (my_echo_input .AND. para_env%ionode) THEN
Expand Down
67 changes: 50 additions & 17 deletions src/start/cp2k.F
Original file line number Diff line number Diff line change
Expand Up @@ -67,8 +67,10 @@ PROGRAM cp2k
CHARACTER(LEN=default_path_length) :: input_file_name, output_file_name, &
arg_att, command
CHARACTER(LEN=default_string_length) :: dev_flag
CHARACTER(LEN=default_path_length), &
DIMENSION(:, :), ALLOCATABLE :: initial_variables, initial_variables_tmp
CHARACTER(LEN=:), ALLOCATABLE :: compiler_options_string
INTEGER :: output_unit, l, i
INTEGER :: output_unit, l, i, var_set_sep, inp_var_idx
INTEGER :: ierr, i_arg
LOGICAL :: check, usage, echo_input, command_line_error
LOGICAL :: run_it, force_run, has_input, xml, print_version, print_license, shell_mode
Expand All @@ -93,6 +95,7 @@ PROGRAM cp2k
xml = .FALSE.
input_file_name = "Missing input file name" ! no default
output_file_name = "__STD_OUT__" ! by default we go to std_out
ALLOCATE (initial_variables(2, 1:0))

! get command and strip path
CALL GET_COMMAND(command, status=ierr)
Expand Down Expand Up @@ -155,6 +158,34 @@ PROGRAM cp2k
command_line_error = .TRUE.
EXIT arg_loop
ENDIF
CASE ("-E", "--set")
i_arg = i_arg + 1
CALL GET_COMMAND_ARGUMENT(i_arg, arg_att, status=ierr)
CPASSERT(ierr == 0)

var_set_sep = INDEX(arg_att, '=')

IF (var_set_sep < 2) THEN
WRITE (output_unit, "(/,T2,A)") "ERROR: Invalid initializer for preprocessor variable: "//TRIM(arg_att)
command_line_error = .TRUE.
EXIT arg_loop
ENDIF

DO inp_var_idx = 1, SIZE(initial_variables, 2)
! check whether the variable was already set, in this case, overwrite
IF (TRIM(initial_variables(1, inp_var_idx)) == arg_att(:var_set_sep - 1)) &
EXIT
END DO

IF (inp_var_idx > SIZE(initial_variables, 2)) THEN
! if the variable was never set before, extend the array
ALLOCATE (initial_variables_tmp(2, SIZE(initial_variables, 2) + 1))
initial_variables_tmp(:, 1:SIZE(initial_variables, 2)) = initial_variables
CALL MOVE_ALLOC(initial_variables_tmp, initial_variables)
ENDIF

initial_variables(1, inp_var_idx) = arg_att(:var_set_sep - 1)
initial_variables(2, inp_var_idx) = arg_att(var_set_sep + 1:)
CASE ("-o")
i_arg = i_arg + 1
CALL GET_COMMAND_ARGUMENT(i_arg, arg_att, status=ierr)
Expand Down Expand Up @@ -213,22 +244,23 @@ PROGRAM cp2k
"starts the CP2K program, see <https://www.cp2k.org/>", &
"The easiest way is "//TRIM(command)//" <input_file>", &
"The following options can be used:", &
"-i <input_file> : provides an input file name, if it is the last", &
" argument, the -i flag is not needed", &
"-o <output_file> : provides an output file name [default: screen]"
"-i <input_file> : provides an input file name, if it is the last", &
" argument, the -i flag is not needed", &
"-o <output_file> : provides an output file name [default: screen]"
WRITE (UNIT=output_unit, FMT="(/,T2,A,/,/,(T3,A))") &
"These switches skip the simulation, unless [-r|-run] is specified:", &
"--check, -c : performs a syntax check of the <input_file>", &
"--echo, -e : echoes the <input_file>, and make all defaults explicit", &
" The input is also checked, but only a failure is reported", &
"--help, -h : writes this message", &
"--license : prints the CP2K license", &
"--mpi-mapping : applies a given MPI reordering to CP2K", &
"--run, -r : forces a CP2K run regardless of other specified flags", &
"--shell, -s : start interactive shell mode", &
"--version, -v : prints the CP2K version and the revision number", &
"--xml : dumps the whole CP2K input structure as a XML file", &
" xml2htm generates a HTML manual from this XML file", &
"--check, -c : performs a syntax check of the <input_file>", &
"--echo, -e : echoes the <input_file>, and make all defaults explicit", &
" The input is also checked, but only a failure is reported", &
"--help, -h : writes this message", &
"--license : prints the CP2K license", &
"--mpi-mapping : applies a given MPI reordering to CP2K", &
"--run, -r : forces a CP2K run regardless of other specified flags", &
"--shell, -s : start interactive shell mode", &
"--version, -v : prints the CP2K version and the revision number", &
"--xml : dumps the whole CP2K input structure as a XML file", &
" xml2htm generates a HTML manual from this XML file", &
"--set, -E name=value : set the initial value of a preprocessor value", &
""
END IF
END IF
Expand Down Expand Up @@ -273,7 +305,7 @@ PROGRAM cp2k

IF (check) THEN
CALL check_input(input_declaration, input_file_name, output_file_name, &
echo_input=echo_input, ierr=ierr)
echo_input=echo_input, ierr=ierr, initial_variables=initial_variables)
IF (default_para_env%ionode) THEN
IF (ierr == 0) THEN
IF (.NOT. echo_input) THEN
Expand All @@ -293,7 +325,7 @@ PROGRAM cp2k
ENDIF

IF (run_it .OR. force_run) THEN
CALL run_input(input_declaration, input_file_name, output_file_name)
CALL run_input(input_declaration, input_file_name, output_file_name, initial_variables)
END IF

CALL section_release(input_declaration)
Expand All @@ -304,6 +336,7 @@ PROGRAM cp2k

! and the final cleanup
CALL finalize_cp2k(finalize_mpi=.TRUE., ierr=ierr)
DEALLOCATE (initial_variables)
CPASSERT(ierr == 0)

END PROGRAM
25 changes: 16 additions & 9 deletions src/start/cp2k_runs.F
Original file line number Diff line number Diff line change
Expand Up @@ -85,8 +85,7 @@ MODULE cp2k_runs
USE input_cp2k, ONLY: create_cp2k_root_section
USE input_cp2k_check, ONLY: check_cp2k_input
USE input_cp2k_global, ONLY: create_global_section
USE input_cp2k_read, ONLY: empty_initial_variables,&
read_input
USE input_cp2k_read, ONLY: read_input
USE input_keyword_types, ONLY: keyword_release
USE input_parsing, ONLY: section_vals_parse
USE input_section_types, ONLY: &
Expand Down Expand Up @@ -152,6 +151,7 @@ MODULE cp2k_runs
!> \param input_file_name name of the file to be opened for input
!> \param output_unit unit to which output should be written
!> \param mpi_comm ...
!> \param initial_variables key-value list of initial preprocessor variables
!> \author Joost VandeVondele
!> \note
!> para_env should be a valid communicator
Expand All @@ -168,10 +168,12 @@ MODULE cp2k_runs
!> able to run simultaneously / multithreaded / sequential / parallel / ...
!> and able to fail safe
! **************************************************************************************************
RECURSIVE SUBROUTINE cp2k_run(input_declaration, input_file_name, output_unit, mpi_comm)
RECURSIVE SUBROUTINE cp2k_run(input_declaration, input_file_name, output_unit, mpi_comm, initial_variables)
TYPE(section_type), POINTER :: input_declaration
CHARACTER(LEN=*), INTENT(IN) :: input_file_name
INTEGER, INTENT(IN) :: output_unit, mpi_comm
CHARACTER(len=default_path_length), &
DIMENSION(:, :), INTENT(IN) :: initial_variables

CHARACTER(LEN=*), PARAMETER :: routineN = 'cp2k_run', routineP = moduleN//':'//routineN

Expand Down Expand Up @@ -209,7 +211,7 @@ RECURSIVE SUBROUTINE cp2k_run(input_declaration, input_file_name, output_unit, m
CALL cite_reference(Hutter2014)

! parse the input
input_file => read_input(input_declaration, input_file_name, initial_variables=empty_initial_variables, &
input_file => read_input(input_declaration, input_file_name, initial_variables=initial_variables, &
para_env=para_env)

CALL mp_sync(para_env%group)
Expand Down Expand Up @@ -265,7 +267,7 @@ RECURSIVE SUBROUTINE cp2k_run(input_declaration, input_file_name, output_unit, m
CALL cp_sirius_finalize()
CALL pw_cuda_finalize()
CALL pw_fpga_finalize()
CALL farming_run(input_declaration, root_section, para_env)
CALL farming_run(input_declaration, root_section, para_env, initial_variables)
CALL cp_sirius_init()
CALL dbcsr_init_lib(mpi_comm, io_unit=output_unit)
CALL pw_cuda_init()
Expand Down Expand Up @@ -435,15 +437,17 @@ END SUBROUTINE cp2k_run
!> \param input_declaration ...
!> \param root_section ...
!> \param para_env ...
!> \param initial_variables ...
!> \author Joost VandeVondele
!> \note
!> needs to be part of this module as the cp2k_run -> farming_run -> cp2k_run
!> calling style creates a hard circular dependency
! **************************************************************************************************
RECURSIVE SUBROUTINE farming_run(input_declaration, root_section, para_env)
RECURSIVE SUBROUTINE farming_run(input_declaration, root_section, para_env, initial_variables)
TYPE(section_type), POINTER :: input_declaration
TYPE(section_vals_type), POINTER :: root_section
TYPE(cp_para_env_type), POINTER :: para_env
CHARACTER(len=default_path_length), DIMENSION(:, :), INTENT(IN) :: initial_variables

CHARACTER(len=*), PARAMETER :: routineN = 'farming_run', &
routineP = moduleN//':'//routineN
Expand Down Expand Up @@ -835,7 +839,7 @@ RECURSIVE SUBROUTINE execute_job(i)
new_output_unit = -1
ENDIF
CALL cp2k_run(input_declaration, TRIM(farming_env%Job(i)%input), new_output_unit, new_group)
CALL cp2k_run(input_declaration, TRIM(farming_env%Job(i)%input), new_output_unit, new_group, initial_variables)
IF (new_rank == 0) CALL close_file(unit_number=new_output_unit)
Expand Down Expand Up @@ -928,15 +932,18 @@ END SUBROUTINE write_xml_file
!> \param input_file_path the path of the input file
!> \param output_file_path path of the output file (to which it is appended)
!> if it is "__STD_OUT__" the default_output_unit is used
!> \param initial_variables key-value list of initial preprocessor variables
!> \param mpi_comm the mpi communicator to be used for this environment
!> it will not be freed
!> \author fawzi
!> \note
!> moved here because of circular dependencies
! **************************************************************************************************
SUBROUTINE run_input(input_declaration, input_file_path, output_file_path, mpi_comm)
SUBROUTINE run_input(input_declaration, input_file_path, output_file_path, initial_variables, mpi_comm)
TYPE(section_type), POINTER :: input_declaration
CHARACTER(len=*), INTENT(in) :: input_file_path, output_file_path
CHARACTER(len=default_path_length), &
DIMENSION(:, :), INTENT(IN) :: initial_variables
INTEGER, INTENT(in), OPTIONAL :: mpi_comm
CHARACTER(len=*), PARAMETER :: routineN = 'run_input', routineP = moduleN//':'//routineN
Expand All @@ -962,7 +969,7 @@ SUBROUTINE run_input(input_declaration, input_file_path, output_file_path, mpi_c
ELSE
unit_nr = -1
END IF
CALL cp2k_run(input_declaration, input_file_path, unit_nr, para_env%group)
CALL cp2k_run(input_declaration, input_file_path, unit_nr, para_env%group, initial_variables)
CALL cp_para_env_release(para_env) !XXXXXXXXXXXX uninitiliased error
END SUBROUTINE run_input
Expand Down
3 changes: 2 additions & 1 deletion src/start/cp2k_shell.F
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ MODULE cp2k_shell
calc_energy_force, calc_force, create_force_env, destroy_force_env, get_cell, get_energy, &
get_force, get_natom, get_pos, get_stress_tensor, set_cell, set_pos
USE input_constants, ONLY: id_development_version
USE input_cp2k_read, ONLY: empty_initial_variables
USE input_section_types, ONLY: section_type
USE kinds, ONLY: default_path_length,&
default_string_length,&
Expand Down Expand Up @@ -844,7 +845,7 @@ SUBROUTINE run_command(shell, input_declaration, arg1, arg2)

IF (.NOT. my_assert(LEN_TRIM(arg1) > 0, "input-file argument missing", shell)) RETURN
IF (.NOT. my_assert(LEN_TRIM(arg2) > 0, "input-file argument missing", shell)) RETURN
CALL run_input(input_declaration, arg1, arg2)
CALL run_input(input_declaration, arg1, arg2, empty_initial_variables)
END SUBROUTINE run_command

! **************************************************************************************************
Expand Down
5 changes: 3 additions & 2 deletions src/start/libcp2k.F
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ MODULE libcp2k
USE force_env_types, ONLY: force_env_get,&
use_qs_force
USE input_cp2k, ONLY: create_cp2k_root_section
USE input_cp2k_read, ONLY: empty_initial_variables
USE input_section_types, ONLY: section_release,&
section_type
USE kinds, ONLY: default_path_length,&
Expand Down Expand Up @@ -355,7 +356,7 @@ SUBROUTINE cp2k_run_input(input_file_path, output_file_path) BIND(C)

NULLIFY (input_declaration)
CALL create_cp2k_root_section(input_declaration)
CALL run_input(input_declaration, ifp, ofp)
CALL run_input(input_declaration, ifp, ofp, empty_initial_variables)
CALL section_release(input_declaration)
END SUBROUTINE cp2k_run_input

Expand All @@ -378,7 +379,7 @@ SUBROUTINE cp2k_run_input_comm(input_file_path, output_file_path, mpi_comm) BIND

NULLIFY (input_declaration)
CALL create_cp2k_root_section(input_declaration)
CALL run_input(input_declaration, ifp, ofp, mpi_comm)
CALL run_input(input_declaration, ifp, ofp, empty_initial_variables, mpi_comm)
CALL section_release(input_declaration)
END SUBROUTINE cp2k_run_input_comm

Expand Down

0 comments on commit ef30ff0

Please sign in to comment.