Line data Source code
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 8528 : PROGRAM cp2k
43 :
44 8528 : 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,&
49 : print_cp2k_license
50 : USE cp2k_runs, ONLY: run_input,&
51 : write_xml_file
52 : USE cp2k_shell, ONLY: launch_cp2k_shell
53 : USE cp_files, ONLY: open_file
54 : USE f77_interface, ONLY: check_input,&
55 : default_para_env,&
56 : finalize_cp2k,&
57 : init_cp2k
58 : USE input_cp2k, ONLY: create_cp2k_root_section
59 : USE input_section_types, ONLY: section_release,&
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 8528 : DIMENSION(:, :), ALLOCATABLE :: initial_variables, initial_variables_tmp
73 8528 : 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 8528 : NULLIFY (input_declaration)
81 :
82 : ! output goes to the screen by default
83 8528 : output_unit = default_output_unit
84 :
85 : ! set default behaviour for the command line switches
86 8528 : check = .FALSE.
87 8528 : usage = .FALSE.
88 8528 : echo_input = .FALSE.
89 8528 : has_input = .FALSE.
90 8528 : run_it = .TRUE.
91 8528 : shell_mode = .FALSE.
92 8528 : force_run = .FALSE.
93 8528 : print_version = .FALSE.
94 8528 : print_license = .FALSE.
95 8528 : command_line_error = .FALSE.
96 8528 : xml = .FALSE.
97 8528 : input_file_name = "Missing input file name" ! no default
98 8528 : output_file_name = "__STD_OUT__" ! by default we go to std_out
99 8528 : ALLOCATE (initial_variables(2, 1:0))
100 :
101 : ! Get command and strip path
102 8528 : CALL GET_COMMAND_ARGUMENT(NUMBER=0, VALUE=command, STATUS=ierr)
103 8528 : CPASSERT(ierr == 0)
104 8528 : l = LEN_TRIM(command)
105 85280 : DO i = l, 1, -1
106 85280 : IF (command(i:i) == "/" .OR. command(i:i) == "\") EXIT
107 : END DO
108 8528 : command = command(i + 1:l)
109 :
110 : ! Consider output redirection
111 8528 : i_arg = 0
112 17056 : DO WHILE (i_arg < COMMAND_ARGUMENT_COUNT())
113 8528 : i_arg = i_arg + 1
114 8528 : CALL GET_COMMAND_ARGUMENT(NUMBER=i_arg, VALUE=arg_att, STATUS=ierr)
115 8528 : CPASSERT(ierr == 0)
116 8528 : SELECT CASE (arg_att)
117 : CASE ("-o")
118 8528 : IF (output_file_name == "__STD_OUT__") THEN
119 : ! Consider only the first -o flag
120 0 : i_arg = i_arg + 1
121 0 : CALL GET_COMMAND_ARGUMENT(NUMBER=i_arg, VALUE=arg_att, STATUS=ierr)
122 0 : CPASSERT(ierr == 0)
123 0 : IF (arg_att(1:1) == "-") THEN
124 : WRITE (output_unit, "(/,T2,A)") &
125 0 : "ERROR: The output file name "//TRIM(arg_att)//" starts with -"
126 0 : command_line_error = .TRUE.
127 : ELSE
128 0 : 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 0 : unit_number=output_unit)
135 : END IF
136 : ELSE
137 0 : i_arg = i_arg + 1
138 : WRITE (output_unit, "(/,T2,A)") &
139 0 : "ERROR: The command line flag -o has been specified multiple times"
140 0 : command_line_error = .TRUE.
141 : END IF
142 : END SELECT
143 : END DO
144 :
145 : ! Check if binary was invoked as cp2k_shell
146 8528 : IF (command(1:10) == "cp2k_shell") THEN
147 : shell_mode = .TRUE.
148 : run_it = .FALSE.
149 8528 : ELSE IF (COMMAND_ARGUMENT_COUNT() < 1) THEN
150 : WRITE (output_unit, "(/,T2,A)") &
151 0 : "ERROR: At least one command line argument must be specified"
152 0 : command_line_error = .TRUE.
153 : END IF
154 :
155 : ! Check if binary was invoked as sopt or popt alias
156 8528 : l = LEN_TRIM(command)
157 8528 : IF (command(l - 4:l) == ".sopt" .OR. command(l - 4:l) == ".popt") THEN
158 0 : 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 8528 : i_arg = 0
181 17056 : arg_loop: DO WHILE (i_arg < COMMAND_ARGUMENT_COUNT())
182 8528 : i_arg = i_arg + 1
183 8528 : CALL GET_COMMAND_ARGUMENT(i_arg, arg_att, status=ierr)
184 8528 : CPASSERT(ierr == 0)
185 8528 : SELECT CASE (arg_att)
186 : CASE ("--check", "-c")
187 0 : check = .TRUE.
188 0 : run_it = .FALSE.
189 0 : echo_input = .FALSE.
190 : CASE ("--echo", "-e")
191 0 : check = .TRUE.
192 0 : run_it = .FALSE.
193 0 : echo_input = .TRUE.
194 : CASE ("-v", "--version")
195 : print_version = .TRUE.
196 0 : run_it = .FALSE.
197 : CASE ("--license")
198 0 : print_license = .TRUE.
199 0 : run_it = .FALSE.
200 : CASE ("--run", "-r")
201 0 : force_run = .TRUE.
202 : CASE ("--shell", "-s")
203 0 : shell_mode = .TRUE.
204 0 : run_it = .FALSE.
205 : CASE ("-help", "--help", "-h")
206 0 : usage = .TRUE.
207 0 : run_it = .FALSE.
208 : CASE ("-i")
209 0 : i_arg = i_arg + 1
210 0 : CALL GET_COMMAND_ARGUMENT(i_arg, arg_att, status=ierr)
211 0 : CPASSERT(ierr == 0)
212 : ! argument does not start with a - it is an filename
213 0 : IF (.NOT. arg_att(1:1) == "-") THEN
214 0 : input_file_name = arg_att
215 0 : has_input = .TRUE.
216 : ELSE
217 : WRITE (output_unit, "(/,T2,A)") &
218 0 : "ERROR: The input file name "//TRIM(arg_att)//" starts with -"
219 0 : command_line_error = .TRUE.
220 0 : EXIT arg_loop
221 : END IF
222 : CASE ("-E", "--set")
223 0 : i_arg = i_arg + 1
224 0 : CALL GET_COMMAND_ARGUMENT(i_arg, arg_att, status=ierr)
225 0 : CPASSERT(ierr == 0)
226 :
227 0 : var_set_sep = INDEX(arg_att, '=')
228 :
229 0 : IF (var_set_sep < 2) THEN
230 0 : WRITE (output_unit, "(/,T2,A)") "ERROR: Invalid initializer for preprocessor variable: "//TRIM(arg_att)
231 0 : command_line_error = .TRUE.
232 0 : EXIT arg_loop
233 : END IF
234 :
235 0 : DO inp_var_idx = 1, SIZE(initial_variables, 2)
236 : ! check whether the variable was already set, in this case, overwrite
237 0 : IF (TRIM(initial_variables(1, inp_var_idx)) == arg_att(:var_set_sep - 1)) &
238 0 : EXIT
239 : END DO
240 :
241 0 : IF (inp_var_idx > SIZE(initial_variables, 2)) THEN
242 : ! if the variable was never set before, extend the array
243 0 : ALLOCATE (initial_variables_tmp(2, SIZE(initial_variables, 2) + 1))
244 0 : initial_variables_tmp(:, 1:SIZE(initial_variables, 2)) = initial_variables
245 0 : CALL MOVE_ALLOC(initial_variables_tmp, initial_variables)
246 : END IF
247 :
248 0 : initial_variables(1, inp_var_idx) = arg_att(:var_set_sep - 1)
249 0 : 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 0 : i_arg = i_arg + 1
253 0 : CALL GET_COMMAND_ARGUMENT(i_arg, arg_att, status=ierr)
254 0 : CPASSERT(ierr == 0)
255 0 : IF (arg_att(1:1) == "-") EXIT arg_loop
256 : CASE ("--xml")
257 0 : xml = .TRUE.
258 0 : 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 8526 : (i_arg == COMMAND_ARGUMENT_COUNT()) .AND. &
264 8528 : (.NOT. arg_att(1:1) == "-")) THEN
265 8526 : input_file_name = arg_att
266 8526 : has_input = .TRUE.
267 0 : ELSE IF (has_input .AND. &
268 : (.NOT. arg_att(1:1) == "-")) THEN
269 : WRITE (output_unit, "(/,T2,A)") &
270 0 : "Error: Tried to specify two input files"
271 0 : command_line_error = .TRUE.
272 0 : 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 8528 : (.NOT. has_input) .AND. (.NOT. command_line_error)) THEN
279 : WRITE (UNIT=output_unit, FMT="(/,T2,A)") &
280 0 : "ERROR: An input file name is required"
281 0 : command_line_error = .TRUE.
282 : END IF
283 :
284 8528 : CALL init_cp2k(init_mpi=.TRUE., ierr=ierr)
285 :
286 8528 : IF (ierr == 0) THEN
287 : ! some first info concerning how to run CP2K
288 :
289 8528 : IF (usage .OR. command_line_error) THEN
290 0 : IF (default_para_env%is_source()) THEN
291 0 : l = LEN_TRIM(command)
292 : WRITE (UNIT=output_unit, FMT="(/,(T2,A))") &
293 0 : TRIM(command)//" [-c|--check] [-e|--echo] [-h|--help]", &
294 0 : REPEAT(" ", l)//" [-i] <input_file>", &
295 0 : REPEAT(" ", l)//" [-mpi-mapping|--mpi-mapping] <method>", &
296 0 : REPEAT(" ", l)//" [-o] <output_file>", &
297 0 : REPEAT(" ", l)//" [-r|-run] [-s|--shell] [--xml]"
298 : WRITE (UNIT=output_unit, FMT="(/,T2,A,/,/,T2,A,/,/,T2,A,/,/,(T3,A))") &
299 0 : "starts the CP2K program, see <https://www.cp2k.org/>", &
300 0 : "The easiest way is "//TRIM(command)//" <input_file>", &
301 0 : "The following options can be used:", &
302 0 : "-i <input_file> : provides an input file name, if it is the last", &
303 0 : " argument, the -i flag is not needed", &
304 0 : "-o <output_file> : provides an output file name [default: screen]"
305 : WRITE (UNIT=output_unit, FMT="(/,T2,A,/,/,(T3,A))") &
306 0 : "These switches skip the simulation, unless [-r|-run] is specified:", &
307 0 : "--check, -c : performs a syntax check of the <input_file>", &
308 0 : "--echo, -e : echoes the <input_file>, and make all defaults explicit", &
309 0 : " The input is also checked, but only a failure is reported", &
310 0 : "--help, -h : writes this message", &
311 0 : "--license : prints the CP2K license", &
312 0 : "--mpi-mapping : applies a given MPI reordering to CP2K", &
313 0 : "--run, -r : forces a CP2K run regardless of other specified flags", &
314 0 : "--shell, -s : start interactive shell mode", &
315 0 : "--version, -v : prints the CP2K version and the revision number", &
316 0 : "--xml : dumps the whole CP2K input structure as a XML file", &
317 0 : " xml2htm generates a HTML manual from this XML file", &
318 0 : "--set, -E name=value : set the initial value of a preprocessor value", &
319 0 : ""
320 : END IF
321 : END IF
322 :
323 0 : IF (.NOT. command_line_error) THEN
324 :
325 : ! write the version string
326 8528 : IF (print_version) THEN
327 2 : IF (default_para_env%is_source()) THEN
328 1 : WRITE (output_unit, "(T2,A)") cp2k_version, &
329 1 : "Source code revision "//TRIM(compile_revision), &
330 2 : TRIM(cp2k_flags())
331 1 : compiler_options_string = compiler_options()
332 1 : WRITE (output_unit, "(T2,A,A)") "compiler: ", compiler_version()
333 1 : WRITE (output_unit, "(T2,A)") "compiler options:"
334 62 : DO i = 0, (LEN(compiler_options_string) - 1)/68
335 : WRITE (output_unit, "(T4,A)") &
336 62 : compiler_options_string(i*68 + 1:MIN(LEN(compiler_options_string), (i + 1)*68))
337 : END DO
338 1 : DEALLOCATE (compiler_options_string)
339 : END IF
340 : END IF
341 :
342 : ! write the license
343 8528 : IF (print_license) THEN
344 0 : IF (default_para_env%is_source()) THEN
345 0 : CALL print_cp2k_license(output_unit)
346 : END IF
347 : END IF
348 :
349 8528 : IF (xml) THEN
350 0 : IF (default_para_env%is_source()) THEN
351 0 : CALL write_xml_file()
352 : END IF
353 : END IF
354 :
355 8528 : CALL create_cp2k_root_section(input_declaration)
356 :
357 8528 : IF (check) THEN
358 : CALL check_input(input_declaration, input_file_name, output_file_name, &
359 0 : echo_input=echo_input, ierr=ierr, initial_variables=initial_variables)
360 0 : IF (default_para_env%is_source()) THEN
361 0 : IF (ierr == 0) THEN
362 0 : IF (.NOT. echo_input) THEN
363 0 : WRITE (output_unit, "(A)") "SUCCESS, the input could be parsed correctly."
364 0 : WRITE (output_unit, "(A)") " This does not guarantee that this input is meaningful"
365 0 : WRITE (output_unit, "(A)") " or will run successfully"
366 : END IF
367 : ELSE
368 0 : WRITE (output_unit, "(A)") "ERROR, the input could *NOT* be parsed correctly."
369 0 : WRITE (output_unit, "(A)") " Please, check and correct it"
370 : END IF
371 : END IF
372 : END IF
373 :
374 8528 : IF (shell_mode) THEN
375 0 : CALL launch_cp2k_shell(input_declaration)
376 : END IF
377 :
378 8528 : IF (run_it .OR. force_run) THEN
379 8526 : CALL run_input(input_declaration, input_file_name, output_file_name, initial_variables)
380 : END IF
381 :
382 8528 : CALL section_release(input_declaration)
383 : END IF
384 : ELSE
385 0 : WRITE (UNIT=output_unit, FMT="(/,A)") "initial setup (MPI ?) error"
386 : END IF
387 :
388 : ! and the final cleanup
389 8528 : CALL finalize_cp2k(finalize_mpi=.TRUE., ierr=ierr)
390 8528 : DEALLOCATE (initial_variables)
391 8528 : CPASSERT(ierr == 0)
392 :
393 8528 : END PROGRAM
|