(git:e7e05ae)
cp2k.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 Main program of CP2K
10 !> \par Copyright
11 !> CP2K: A general program to perform molecular dynamics simulations
12 !> Copyright (C) 2000, 2001, 2002, 2003 CP2K developers group
13 !> Copyright (C) 2004, 2005, 2006, 2007 CP2K developers group
14 !> Copyright (C) 2008, 2009, 2010, 2011 CP2K developers group
15 !> Copyright (C) 2012, 2013, 2014, 2015 CP2K developers group
16 !> Copyright (C) 2016 CP2K developers group
17 !> \par
18 !> This program is free software; you can redistribute it and/or modify
19 !> it under the terms of the GNU General Public License as published by
20 !> the Free Software Foundation; either version 2 of the License, or
21 !> (at your option) any later version.
22 !> \par
23 !> This program is distributed in the hope that it will be useful,
24 !> but WITHOUT ANY WARRANTY; without even the implied warranty of
25 !> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
26 !> GNU General Public License for more details.
27 !> \par
28 !> You should have received a copy of the GNU General Public License
29 !> along with this program; if not, write to the Free Software
30 !> Foundation, Inc., 51 Franklin Street, Fifth Floor,
31 !> Boston, MA 02110-1301, USA.
32 !> \par
33 !> See also https://www.fsf.org/licensing/licenses/gpl.html
34 !> \par
35 !> CP2K, including its sources and pointers to the authors
36 !> can be found at https://www.cp2k.org/
37 !> \note
38 !> should be kept as lean as possible.
39 !> see cp2k_run for more comments
40 !> \author Joost VandeVondele
41 ! **************************************************************************************************
42 PROGRAM cp2k
43 
44  USE omp_lib, ONLY: omp_get_max_threads,&
45  omp_set_num_threads
46  USE cp2k_info, ONLY: compile_revision,&
47  cp2k_flags,&
48  cp2k_version,&
50  USE cp2k_runs, ONLY: run_input,&
52  USE cp2k_shell, ONLY: launch_cp2k_shell
53  USE cp_files, ONLY: open_file
54  USE f77_interface, ONLY: check_input,&
57  init_cp2k
60  section_type
61  USE iso_fortran_env, ONLY: compiler_options,&
62  compiler_version
63  USE kinds, ONLY: default_path_length
64  USE machine, ONLY: default_output_unit
65 #include "../base/base_uses.f90"
66 
67  IMPLICIT NONE
68 
69  CHARACTER(LEN=default_path_length) :: input_file_name, output_file_name, &
70  arg_att, command
71  CHARACTER(LEN=default_path_length), &
72  DIMENSION(:, :), ALLOCATABLE :: initial_variables, initial_variables_tmp
73  CHARACTER(LEN=:), ALLOCATABLE :: compiler_options_string
74  INTEGER :: output_unit, l, i, var_set_sep, inp_var_idx
75  INTEGER :: ierr, i_arg
76  LOGICAL :: check, usage, echo_input, command_line_error
77  LOGICAL :: run_it, force_run, has_input, xml, print_version, print_license, shell_mode
78  TYPE(section_type), POINTER :: input_declaration
79 
80  NULLIFY (input_declaration)
81 
82  ! output goes to the screen by default
83  output_unit = default_output_unit
84 
85  ! set default behaviour for the command line switches
86  check = .false.
87  usage = .false.
88  echo_input = .false.
89  has_input = .false.
90  run_it = .true.
91  shell_mode = .false.
92  force_run = .false.
93  print_version = .false.
94  print_license = .false.
95  command_line_error = .false.
96  xml = .false.
97  input_file_name = "Missing input file name" ! no default
98  output_file_name = "__STD_OUT__" ! by default we go to std_out
99  ALLOCATE (initial_variables(2, 1:0))
100 
101  ! Get command and strip path
102  CALL get_command_argument(number=0, VALUE=command, status=ierr)
103  cpassert(ierr == 0)
104  l = len_trim(command)
105  DO i = l, 1, -1
106  IF (command(i:i) == "/" .OR. command(i:i) == "\") EXIT
107  END DO
108  command = command(i + 1:l)
109 
110  ! Consider output redirection
111  i_arg = 0
112  DO WHILE (i_arg < command_argument_count())
113  i_arg = i_arg + 1
114  CALL get_command_argument(number=i_arg, VALUE=arg_att, status=ierr)
115  cpassert(ierr == 0)
116  SELECT CASE (arg_att)
117  CASE ("-o")
118  IF (output_file_name == "__STD_OUT__") THEN
119  ! Consider only the first -o flag
120  i_arg = i_arg + 1
121  CALL get_command_argument(number=i_arg, VALUE=arg_att, status=ierr)
122  cpassert(ierr == 0)
123  IF (arg_att(1:1) == "-") THEN
124  WRITE (output_unit, "(/,T2,A)") &
125  "ERROR: The output file name "//trim(arg_att)//" starts with -"
126  command_line_error = .true.
127  ELSE
128  output_file_name = arg_att
129  CALL open_file(file_name=output_file_name, &
130  file_status="UNKNOWN", &
131  file_action="WRITE", &
132  file_position="APPEND", &
133  skip_get_unit_number=.true., &
134  unit_number=output_unit)
135  END IF
136  ELSE
137  i_arg = i_arg + 1
138  WRITE (output_unit, "(/,T2,A)") &
139  "ERROR: The command line flag -o has been specified multiple times"
140  command_line_error = .true.
141  END IF
142  END SELECT
143  END DO
144 
145  ! Check if binary was invoked as cp2k_shell
146  IF (command(1:10) == "cp2k_shell") THEN
147  shell_mode = .true.
148  run_it = .false.
149  ELSE IF (command_argument_count() < 1) THEN
150  WRITE (output_unit, "(/,T2,A)") &
151  "ERROR: At least one command line argument must be specified"
152  command_line_error = .true.
153  END IF
154 
155  ! Check if binary was invoked as sopt or popt alias
156  l = len_trim(command)
157  IF (command(l - 4:l) == ".sopt" .OR. command(l - 4:l) == ".popt") THEN
158  CALL omp_set_num_threads(1)
159  END IF
160 
161 #ifdef __ACCELERATE
162  IF (omp_get_max_threads() > 1) THEN
163  block
164  CHARACTER(len=default_path_length) :: env_var
165  INTEGER :: veclib_max_threads, ierr
166  CALL get_environment_variable("VECLIB_MAXIMUM_THREADS", env_var, status=ierr)
167  veclib_max_threads = 0
168  IF (ierr == 0) &
169  READ (env_var, *) veclib_max_threads
170  IF (ierr == 1 .OR. (ierr == 0 .AND. veclib_max_threads > 1)) THEN
171  CALL cp_warn(__location__, &
172  "macOS' Accelerate framework has its own threading enabled which may interfere"// &
173  " with the OpenMP threading. You can disable the Accelerate threading by setting"// &
174  " the environment variable VECLIB_MAXIMUM_THREADS=1")
175  END IF
176  END block
177  END IF
178 #endif
179 
180  i_arg = 0
181  arg_loop: DO WHILE (i_arg < command_argument_count())
182  i_arg = i_arg + 1
183  CALL get_command_argument(i_arg, arg_att, status=ierr)
184  cpassert(ierr == 0)
185  SELECT CASE (arg_att)
186  CASE ("--check", "-c")
187  check = .true.
188  run_it = .false.
189  echo_input = .false.
190  CASE ("--echo", "-e")
191  check = .true.
192  run_it = .false.
193  echo_input = .true.
194  CASE ("-v", "--version")
195  print_version = .true.
196  run_it = .false.
197  CASE ("--license")
198  print_license = .true.
199  run_it = .false.
200  CASE ("--run", "-r")
201  force_run = .true.
202  CASE ("--shell", "-s")
203  shell_mode = .true.
204  run_it = .false.
205  CASE ("-help", "--help", "-h")
206  usage = .true.
207  run_it = .false.
208  CASE ("-i")
209  i_arg = i_arg + 1
210  CALL get_command_argument(i_arg, arg_att, status=ierr)
211  cpassert(ierr == 0)
212  ! argument does not start with a - it is an filename
213  IF (.NOT. arg_att(1:1) == "-") THEN
214  input_file_name = arg_att
215  has_input = .true.
216  ELSE
217  WRITE (output_unit, "(/,T2,A)") &
218  "ERROR: The input file name "//trim(arg_att)//" starts with -"
219  command_line_error = .true.
220  EXIT arg_loop
221  END IF
222  CASE ("-E", "--set")
223  i_arg = i_arg + 1
224  CALL get_command_argument(i_arg, arg_att, status=ierr)
225  cpassert(ierr == 0)
226 
227  var_set_sep = index(arg_att, '=')
228 
229  IF (var_set_sep < 2) THEN
230  WRITE (output_unit, "(/,T2,A)") "ERROR: Invalid initializer for preprocessor variable: "//trim(arg_att)
231  command_line_error = .true.
232  EXIT arg_loop
233  END IF
234 
235  DO inp_var_idx = 1, SIZE(initial_variables, 2)
236  ! check whether the variable was already set, in this case, overwrite
237  IF (trim(initial_variables(1, inp_var_idx)) == arg_att(:var_set_sep - 1)) &
238  EXIT
239  END DO
240 
241  IF (inp_var_idx > SIZE(initial_variables, 2)) THEN
242  ! if the variable was never set before, extend the array
243  ALLOCATE (initial_variables_tmp(2, SIZE(initial_variables, 2) + 1))
244  initial_variables_tmp(:, 1:SIZE(initial_variables, 2)) = initial_variables
245  CALL move_alloc(initial_variables_tmp, initial_variables)
246  END IF
247 
248  initial_variables(1, inp_var_idx) = arg_att(:var_set_sep - 1)
249  initial_variables(2, inp_var_idx) = arg_att(var_set_sep + 1:)
250  CASE ("-o")
251  ! Skip -o flag which have been processed already
252  i_arg = i_arg + 1
253  CALL get_command_argument(i_arg, arg_att, status=ierr)
254  cpassert(ierr == 0)
255  IF (arg_att(1:1) == "-") EXIT arg_loop
256  CASE ("--xml")
257  xml = .true.
258  run_it = .false.
259  CASE DEFAULT
260  ! if the last argument does not start with a - it is an input filename
261  !MK in order to digest the additional flags of mpirun
262  IF ((.NOT. has_input) .AND. &
263  (i_arg == command_argument_count()) .AND. &
264  (.NOT. arg_att(1:1) == "-")) THEN
265  input_file_name = arg_att
266  has_input = .true.
267  ELSE IF (has_input .AND. &
268  (.NOT. arg_att(1:1) == "-")) THEN
269  WRITE (output_unit, "(/,T2,A)") &
270  "Error: Tried to specify two input files"
271  command_line_error = .true.
272  EXIT arg_loop
273  END IF
274  END SELECT
275  END DO arg_loop
276 
277  IF ((run_it .OR. force_run .OR. check .OR. echo_input) .AND. &
278  (.NOT. has_input) .AND. (.NOT. command_line_error)) THEN
279  WRITE (unit=output_unit, fmt="(/,T2,A)") &
280  "ERROR: An input file name is required"
281  command_line_error = .true.
282  END IF
283 
284  CALL init_cp2k(init_mpi=.true., ierr=ierr)
285 
286  IF (ierr == 0) THEN
287  ! some first info concerning how to run CP2K
288 
289  IF (usage .OR. command_line_error) THEN
290  IF (default_para_env%is_source()) THEN
291  l = len_trim(command)
292  WRITE (unit=output_unit, fmt="(/,(T2,A))") &
293  trim(command)//" [-c|--check] [-e|--echo] [-h|--help]", &
294  repeat(" ", l)//" [-i] <input_file>", &
295  repeat(" ", l)//" [-mpi-mapping|--mpi-mapping] <method>", &
296  repeat(" ", l)//" [-o] <output_file>", &
297  repeat(" ", l)//" [-r|-run] [-s|--shell] [--xml]"
298  WRITE (unit=output_unit, fmt="(/,T2,A,/,/,T2,A,/,/,T2,A,/,/,(T3,A))") &
299  "starts the CP2K program, see <https://www.cp2k.org/>", &
300  "The easiest way is "//trim(command)//" <input_file>", &
301  "The following options can be used:", &
302  "-i <input_file> : provides an input file name, if it is the last", &
303  " argument, the -i flag is not needed", &
304  "-o <output_file> : provides an output file name [default: screen]"
305  WRITE (unit=output_unit, fmt="(/,T2,A,/,/,(T3,A))") &
306  "These switches skip the simulation, unless [-r|-run] is specified:", &
307  "--check, -c : performs a syntax check of the <input_file>", &
308  "--echo, -e : echoes the <input_file>, and make all defaults explicit", &
309  " The input is also checked, but only a failure is reported", &
310  "--help, -h : writes this message", &
311  "--license : prints the CP2K license", &
312  "--mpi-mapping : applies a given MPI reordering to CP2K", &
313  "--run, -r : forces a CP2K run regardless of other specified flags", &
314  "--shell, -s : start interactive shell mode", &
315  "--version, -v : prints the CP2K version and the revision number", &
316  "--xml : dumps the whole CP2K input structure as a XML file", &
317  " xml2htm generates a HTML manual from this XML file", &
318  "--set, -E name=value : set the initial value of a preprocessor value", &
319  ""
320  END IF
321  END IF
322 
323  IF (.NOT. command_line_error) THEN
324 
325  ! write the version string
326  IF (print_version) THEN
327  IF (default_para_env%is_source()) THEN
328  WRITE (output_unit, "(T2,A)") cp2k_version, &
329  "Source code revision "//trim(compile_revision), &
330  trim(cp2k_flags())
331  compiler_options_string = compiler_options()
332  WRITE (output_unit, "(T2,A,A)") "compiler: ", compiler_version()
333  WRITE (output_unit, "(T2,A)") "compiler options:"
334  DO i = 0, (len(compiler_options_string) - 1)/68
335  WRITE (output_unit, "(T4,A)") &
336  compiler_options_string(i*68 + 1:min(len(compiler_options_string), (i + 1)*68))
337  END DO
338  DEALLOCATE (compiler_options_string)
339  END IF
340  END IF
341 
342  ! write the license
343  IF (print_license) THEN
344  IF (default_para_env%is_source()) THEN
345  CALL print_cp2k_license(output_unit)
346  END IF
347  END IF
348 
349  IF (xml) THEN
350  IF (default_para_env%is_source()) THEN
351  CALL write_xml_file()
352  END IF
353  END IF
354 
355  CALL create_cp2k_root_section(input_declaration)
356 
357  IF (check) THEN
358  CALL check_input(input_declaration, input_file_name, output_file_name, &
359  echo_input=echo_input, ierr=ierr, initial_variables=initial_variables)
360  IF (default_para_env%is_source()) THEN
361  IF (ierr == 0) THEN
362  IF (.NOT. echo_input) THEN
363  WRITE (output_unit, "(A)") "SUCCESS, the input could be parsed correctly."
364  WRITE (output_unit, "(A)") " This does not guarantee that this input is meaningful"
365  WRITE (output_unit, "(A)") " or will run successfully"
366  END IF
367  ELSE
368  WRITE (output_unit, "(A)") "ERROR, the input could *NOT* be parsed correctly."
369  WRITE (output_unit, "(A)") " Please, check and correct it"
370  END IF
371  END IF
372  END IF
373 
374  IF (shell_mode) THEN
375  CALL launch_cp2k_shell(input_declaration)
376  END IF
377 
378  IF (run_it .OR. force_run) THEN
379  CALL run_input(input_declaration, input_file_name, output_file_name, initial_variables)
380  END IF
381 
382  CALL section_release(input_declaration)
383  END IF
384  ELSE
385  WRITE (unit=output_unit, fmt="(/,A)") "initial setup (MPI ?) error"
386  END IF
387 
388  ! and the final cleanup
389  CALL finalize_cp2k(finalize_mpi=.true., ierr=ierr)
390  DEALLOCATE (initial_variables)
391  cpassert(ierr == 0)
392 
393 END PROGRAM
program cp2k
Main program of CP2K.
Definition: cp2k.F:42
some minimal info about CP2K, including its version and license
Definition: cp2k_info.F:16
subroutine, public print_cp2k_license(iunit)
...
Definition: cp2k_info.F:280
character(len= *), parameter, public compile_revision
Definition: cp2k_info.F:37
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:78
character(len= *), parameter, public cp2k_version
Definition: cp2k_info.F:40
subroutine, public run_input(input_declaration, input_file_path, output_file_path, initial_variables, mpi_comm)
runs the given input
Definition: cp2k_runs.F:958
subroutine, public write_xml_file()
...
Definition: cp2k_runs.F:894
Interactive shell of CP2K.
Definition: cp2k_shell.F:33
subroutine, public launch_cp2k_shell(input_declaration)
Launch the interactive CP2K shell.
Definition: cp2k_shell.F:92
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
interface to use cp2k as library
Definition: f77_interface.F:20
type(mp_para_env_type), pointer, save, public default_para_env
subroutine, public init_cp2k(init_mpi, ierr)
initializes cp2k, needs to be called once before using any of the other functions when using cp2k as ...
subroutine, public finalize_cp2k(finalize_mpi, ierr)
cleanup after you have finished using this interface
subroutine, public check_input(input_declaration, input_file_path, output_file_path, echo_input, mpi_comm, initial_variables, ierr)
performs a check of the input
builds the input structure for cp2k
Definition: input_cp2k.F:14
subroutine, public create_cp2k_root_section(root_section)
creates the input structure of the file used by cp2k
Definition: input_cp2k.F:75
objects that represent the structure of input sections and the data contained in an input section
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public default_path_length
Definition: kinds.F:58
Machine interface based on Fortran 2003 and POSIX.
Definition: machine.F:17
integer, parameter, public default_output_unit
Definition: machine.F:45