(git:d657d38)
Loading...
Searching...
No Matches
cp2k_info.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief some minimal info about CP2K, including its version and license
10!> \par History
11!> - created (2007-09, Joost VandeVondele)
12!> - moved into this module information related to runtime:pid, user_name,
13!> host_name, cwd, datx (2009-06, Teodoro Laino)
14!> \author Joost VandeVondele
15! **************************************************************************************************
17
18 USE iso_fortran_env, ONLY: compiler_options
19 USE kinds, ONLY: default_path_length,&
21 USE machine, ONLY: m_datum,&
22 m_getcwd,&
23 m_getlog,&
24 m_getpid,&
27
28 IMPLICIT NONE
29 PRIVATE
30
34
35#if defined(__COMPILE_REVISION)
36 CHARACTER(LEN=*), PARAMETER :: compile_revision = __compile_revision
37#else
38 CHARACTER(LEN=*), PARAMETER :: compile_revision = "unknown"
39#endif
40
41 !!! Keep version in sync with CMakeLists.txt !!!
42 CHARACTER(LEN=*), PARAMETER :: cp2k_version = "CP2K version 2025.1 (Development Version)"
43 CHARACTER(LEN=*), PARAMETER :: cp2k_year = "2025"
44 CHARACTER(LEN=*), PARAMETER :: cp2k_home = "https://www.cp2k.org/"
45
46 ! compile time information
47#if defined(__COMPILE_ARCH)
48 CHARACTER(LEN=*), PARAMETER :: compile_arch = __compile_arch
49#else
50 CHARACTER(LEN=*), PARAMETER :: compile_arch = "unknown: -D__COMPILE_ARCH=?"
51#endif
52
53#if defined(__COMPILE_DATE)
54 CHARACTER(LEN=*), PARAMETER :: compile_date = __compile_date
55#else
56 CHARACTER(LEN=*), PARAMETER :: compile_date = "unknown: -D__COMPILE_DATE=?"
57#endif
58
59#if defined(__COMPILE_HOST)
60 CHARACTER(LEN=*), PARAMETER :: compile_host = __compile_host
61#else
62 CHARACTER(LEN=*), PARAMETER :: compile_host = "unknown: -D__COMPILE_HOST=?"
63#endif
64
65 ! Local runtime informations
66 CHARACTER(LEN=26), PUBLIC :: r_datx
67 CHARACTER(LEN=default_path_length), PUBLIC :: r_cwd
68 CHARACTER(LEN=default_string_length), PUBLIC :: r_host_name, r_user_name
69 INTEGER, PUBLIC :: r_pid
70
71 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'cp2k_info'
72CONTAINS
73
74! **************************************************************************************************
75!> \brief list all compile time options that influence the capabilities of cp2k.
76!> All new flags should be added here (and be unique grep-able)
77!> \return ...
78! **************************************************************************************************
79 FUNCTION cp2k_flags() RESULT(flags)
80 CHARACTER(len=10*default_string_length) :: flags
81
82 CHARACTER(len=default_string_length) :: tmp_str
83
84 flags = "cp2kflags:"
85
86 ! Ensure that tmp_str is used to silence compiler warnings
87 tmp_str = ""
88 flags = trim(flags)//trim(tmp_str)
89
90 IF (index(compiler_options(), "-fsanitize=leak") > 0) THEN
91 flags = trim(flags)//" lsan"
92 END IF
93
94!$ flags = TRIM(flags)//" omp"
95#if defined(__LIBINT)
96 flags = trim(flags)//" libint"
97#endif
98#if defined(__FFTW3)
99 flags = trim(flags)//" fftw3"
100#endif
101#if defined(__FFTW3_MKL)
102 flags = trim(flags)//" fftw3_mkl"
103#endif
104#if defined(__LIBXC)
105 flags = trim(flags)//" libxc"
106#endif
107#if defined(__LIBGRPP)
108 flags = trim(flags)//" libgrpp"
109#endif
110#if defined(__PEXSI)
111 flags = trim(flags)//" pexsi"
112#endif
113#if defined(__ELPA)
114 flags = trim(flags)//" elpa"
115#endif
116#if defined(__ELPA_NVIDIA_GPU)
117 flags = trim(flags)//" elpa_nvidia_gpu"
118#endif
119#if defined(__ELPA_AMD_GPU)
120 flags = trim(flags)//" elpa_amd_gpu"
121#endif
122#if defined(__ELPA_INTEL_GPU)
123 flags = trim(flags)//" elpa_intel_gpu"
124#endif
125#if defined(__parallel)
126 flags = trim(flags)//" parallel scalapack"
127#endif
128#if defined(__MPI_F08)
129 flags = trim(flags)//" mpi_f08"
130#endif
131#if defined(__COSMA)
132 flags = trim(flags)//" cosma"
133#endif
134
135#if defined(__QUIP)
136 flags = trim(flags)//" quip"
137#endif
138
139#if defined(__HAS_PATCHED_CUFFT_70)
140 flags = trim(flags)//" patched_cufft_70"
141#endif
142
143#if defined(__ACE)
144 flags = trim(flags)//" ace"
145#endif
146
147#if defined(__DEEPMD)
148 flags = trim(flags)//" deepmd"
149#endif
150
151#if defined(__PW_FPGA)
152 flags = trim(flags)//" pw_fpga"
153#endif
154
155#if defined(__PW_FPGA_SP)
156 flags = trim(flags)//" pw_fpga_sp"
157#endif
158
159#if defined(__LIBXSMM)
160 flags = trim(flags)//" xsmm"
161#endif
162
163#if defined(__CRAY_PM_ACCEL_ENERGY)
164 flags = trim(flags)//" cray_pm_accel_energy"
165#endif
166#if defined(__CRAY_PM_ENERGY)
167 flags = trim(flags)//" cray_pm_energy"
168#endif
169#if defined(__CRAY_PM_FAKE_ENERGY)
170 flags = trim(flags)//" cray_pm_fake_energy"
171#endif
172#if defined(__DBCSR_ACC)
173 flags = trim(flags)//" dbcsr_acc"
174#endif
175#if defined(__MAX_CONTR)
176 CALL integer_to_string(__max_contr, tmp_str)
177 flags = trim(flags)//" max_contr="//trim(tmp_str)
178#endif
179#if defined(__NO_SOCKETS)
180 flags = trim(flags)//" no_sockets"
181#endif
182#if defined(__NO_MPI_THREAD_SUPPORT_CHECK)
183 flags = trim(flags)//" no_mpi_thread_support_check"
184#endif
185#if defined(__NO_STATM_ACCESS)
186 flags = trim(flags)//" no_statm_access"
187#endif
188#if defined(__MINGW)
189 flags = trim(flags)//" mingw"
190#endif
191#if defined(__PW_CUDA_NO_HOSTALLOC)
192 flags = trim(flags)//" pw_cuda_no_hostalloc"
193#endif
194#if defined(__STATM_RESIDENT)
195 flags = trim(flags)//" statm_resident"
196#endif
197#if defined(__STATM_TOTAL)
198 flags = trim(flags)//" statm_total"
199#endif
200#if defined(__PLUMED2)
201 flags = trim(flags)//" plumed2"
202#endif
203#if defined(__HAS_IEEE_EXCEPTIONS)
204 flags = trim(flags)//" has_ieee_exceptions"
205#endif
206#if defined(__NO_ABORT)
207 flags = trim(flags)//" no_abort"
208#endif
209#if defined(__SPGLIB)
210 flags = trim(flags)//" spglib"
211#endif
212#if defined(__ACCELERATE)
213 flags = trim(flags)//" accelerate"
214#endif
215#if defined(__MKL)
216 flags = trim(flags)//" mkl"
217#endif
218#if defined(__DFTD4)
219 flags = trim(flags)//" libdftd4"
220#endif
221#if defined(__TBLITE)
222 flags = trim(flags)//" mctc-lib"
223 flags = trim(flags)//" tblite"
224#endif
225#if defined(__SIRIUS)
226 flags = trim(flags)//" sirius"
227#endif
228#if defined(__SIRIUS_NLCG)
229 flags = trim(flags)//" sirius_nlcg"
230#endif
231#if defined(__SIRIUS_DFTD4)
232 flags = trim(flags)//" sirius_dftd4"
233#endif
234#if defined(__SIRIUS_VCSQNM)
235 flags = trim(flags)//" sirius_vcsqnm"
236#endif
237#if defined(__CHECK_DIAG)
238 flags = trim(flags)//" check_diag"
239#endif
240#if defined(__LIBVORI)
241 flags = trim(flags)//" libvori"
242 flags = trim(flags)//" libbqb"
243#endif
244#if defined(__LIBMAXWELL)
245 flags = trim(flags)//" libmaxwell"
246#endif
247#if defined(__LIBTORCH)
248 flags = trim(flags)//" libtorch"
249#endif
250#if defined(__OFFLOAD_CUDA)
251 flags = trim(flags)//" offload_cuda"
252#endif
253#if defined(__OFFLOAD_HIP)
254 flags = trim(flags)//" offload_hip"
255#endif
256#if defined(__OFFLOAD_OPENCL)
257 flags = trim(flags)//" offload_opencl"
258#endif
259#if defined(__NO_OFFLOAD_GRID)
260 flags = trim(flags)//" no_offload_grid"
261#endif
262#if defined(__NO_OFFLOAD_DBM)
263 flags = trim(flags)//" no_offload_dbm"
264#endif
265#if defined(__NO_OFFLOAD_PW)
266 flags = trim(flags)//" no_offload_pw"
267#endif
268#if defined(__OFFLOAD_PROFILING)
269 flags = trim(flags)//" offload_profiling"
270#endif
271
272#if defined(__SPLA) && defined(__OFFLOAD_GEMM)
273 flags = trim(flags)//" spla_gemm_offloading"
274#endif
275
276#if defined(__CUSOLVERMP)
277 flags = trim(flags)//" cusolvermp"
278#endif
279
280#if defined(__DLAF)
281 flags = trim(flags)//" dlaf"
282#endif
283
284#if defined(__LIBVDWXC)
285 flags = trim(flags)//" libvdwxc"
286#endif
287
288#if defined(__HDF5)
289 flags = trim(flags)//" hdf5"
290#endif
291
292#if defined(__TREXIO)
293 flags = trim(flags)//" trexio"
294#endif
295
296#if defined(__OFFLOAD_UNIFIED_MEMORY)
297 flags = trim(flags)//" offload_unified_memory"
298#endif
299
300#if defined(__SMEAGOL)
301 flags = trim(flags)//" libsmeagol"
302#endif
303
304#if defined(__GREENX)
305 flags = trim(flags)//" greenx"
306#endif
307
308 END FUNCTION cp2k_flags
309
310! **************************************************************************************************
311!> \brief ...
312!> \param iunit ...
313! **************************************************************************************************
314 SUBROUTINE print_cp2k_license(iunit)
315
316 INTEGER :: iunit
317
318 WRITE (unit=iunit, fmt="(T2,A)") &
319 "******************************************************************************", &
320 "* *", &
321 "* CP2K: A general program to perform molecular dynamics simulations *", &
322 "* Copyright (C) 2000-2025 CP2K developer group <https://www.cp2k.org/> *", &
323 "* *", &
324 "* This program is free software: you can redistribute it and/or modify *", &
325 "* it under the terms of the GNU General Public License as published by *", &
326 "* the Free Software Foundation, either version 2 of the License, or *", &
327 "* (at your option) any later version. *", &
328 "* *", &
329 "* This program is distributed in the hope that it will be useful, *", &
330 "* but WITHOUT ANY WARRANTY; without even the implied warranty of *", &
331 "* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the *", &
332 "* GNU General Public License for more details. *", &
333 "* *", &
334 "* You should have received a copy of the GNU General Public License *", &
335 "* along with this program. If not, see <https://www.gnu.org/licenses/>. *", &
336 "* *", &
337 "******************************************************************************"
338
339 END SUBROUTINE print_cp2k_license
340
341! **************************************************************************************************
342!> \brief ...
343! **************************************************************************************************
344 SUBROUTINE get_runtime_info()
345
346 r_datx = ""
347 r_cwd = ""
348 r_host_name = ""
349 r_user_name = ""
350 r_pid = -1
351
352 CALL m_getpid(r_pid)
355 CALL m_datum(r_datx)
356 CALL m_getcwd(r_cwd)
357
358 END SUBROUTINE
359
360! **************************************************************************************************
361!> \brief Writes the header for the restart file
362!> \param iunit ...
363!> \par History
364!> 01.2008 [created] - Split from write_restart
365!> \author Teodoro Laino - University of Zurich - 01.2008
366! **************************************************************************************************
367 SUBROUTINE write_restart_header(iunit)
368 INTEGER, INTENT(IN) :: iunit
369
370 CHARACTER(LEN=256) :: cwd, datx
371
372 CALL m_datum(datx)
373 CALL m_getcwd(cwd)
374
375 WRITE (unit=iunit, fmt="(T2,A)") "# Version information for this restart file "
376 WRITE (unit=iunit, fmt="(T2,A)") "# current date "//trim(datx)
377 WRITE (unit=iunit, fmt="(T2,A)") "# current working dir "//trim(cwd)
378
379 WRITE (unit=iunit, fmt="(T2,A,T31,A50)") &
380 "# Program compiled at", &
381 adjustr(compile_date(1:min(50, len(compile_date))))
382 WRITE (unit=iunit, fmt="(T2,A,T31,A50)") &
383 "# Program compiled on", &
384 adjustr(compile_host(1:min(50, len(compile_host))))
385 WRITE (unit=iunit, fmt="(T2,A,T31,A50)") &
386 "# Program compiled for", &
387 adjustr(compile_arch(1:min(50, len(compile_arch))))
388 WRITE (unit=iunit, fmt="(T2,A,T31,A50)") &
389 "# Source code revision number", &
390 adjustr(compile_revision)
391
392 END SUBROUTINE write_restart_header
393
394END MODULE cp2k_info
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:68
character(len= *), parameter, public cp2k_home
Definition cp2k_info.F:44
character(len= *), parameter, public compile_host
Definition cp2k_info.F:62
character(len= *), parameter, public compile_arch
Definition cp2k_info.F:50
integer, public r_pid
Definition cp2k_info.F:69
subroutine, public print_cp2k_license(iunit)
...
Definition cp2k_info.F:315
subroutine, public write_restart_header(iunit)
Writes the header for the restart file.
Definition cp2k_info.F:368
character(len= *), parameter, public compile_revision
Definition cp2k_info.F:38
character(len= *), parameter, public compile_date
Definition cp2k_info.F:56
character(len= *), parameter, public cp2k_year
Definition cp2k_info.F:43
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:80
character(len= *), parameter, public cp2k_version
Definition cp2k_info.F:42
character(len=default_path_length), public r_cwd
Definition cp2k_info.F:67
subroutine, public get_runtime_info()
...
Definition cp2k_info.F:345
character(len=default_string_length), public r_user_name
Definition cp2k_info.F:68
character(len=26), public r_datx
Definition cp2k_info.F:66
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public default_path_length
Definition kinds.F:58
Machine interface based on Fortran 2003 and POSIX.
Definition machine.F:17
subroutine, public m_getpid(pid)
...
Definition machine.F:661
subroutine, public m_datum(cal_date)
returns a datum in human readable format using a standard Fortran routine
Definition machine.F:378
subroutine, public m_getcwd(curdir)
...
Definition machine.F:613
subroutine, public m_getlog(user)
...
Definition machine.F:738
subroutine, public m_hostnm(hname)
...
Definition machine.F:580
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,...