(git:ccc2433)
md_util.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 Utilities for Molecular Dynamics
10 !> \author Teodoro Laino [tlaino] - University of Zurich - 09.2007
11 ! **************************************************************************************************
12 MODULE md_util
13 
14  USE cp_files, ONLY: close_file,&
15  open_file
17  cp_logger_type
21  section_vals_type,&
23  USE kinds, ONLY: default_path_length,&
24  dp
25  USE md_energies, ONLY: md_write_output
26  USE md_environment_types, ONLY: md_environment_type
27  USE message_passing, ONLY: mp_para_env_type
28 #include "../base/base_uses.f90"
29 
30  IMPLICIT NONE
31 
32  PRIVATE
33 
34 ! *** Global parameters ***
35 
36  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'md_util'
37 
38  PUBLIC :: md_output, &
40 
41 CONTAINS
42 
43 ! **************************************************************************************************
44 !> \brief collects the part of the MD that, basically, does the output
45 !> \param md_env ...
46 !> \param md_section ...
47 !> \param root_section ...
48 !> \param forced_io ...
49 !> \par History
50 !> 03.2006 created [Joost VandeVondele]
51 ! **************************************************************************************************
52  SUBROUTINE md_output(md_env, md_section, root_section, forced_io)
53  TYPE(md_environment_type), POINTER :: md_env
54  TYPE(section_vals_type), POINTER :: md_section, root_section
55  LOGICAL, INTENT(IN) :: forced_io
56 
57  CHARACTER(LEN=*), PARAMETER :: routinen = 'md_output'
58 
59  INTEGER :: handle
60  LOGICAL :: do_print
61  TYPE(section_vals_type), POINTER :: print_section
62 
63  CALL timeset(routinen, handle)
64  do_print = .true.
65  IF (forced_io) THEN
66  print_section => section_vals_get_subs_vals(md_section, "PRINT")
67  CALL section_vals_val_get(print_section, "FORCE_LAST", l_val=do_print)
68  END IF
69  IF (do_print) THEN
70  ! Dumps all files related to the MD run
71  CALL md_write_output(md_env)
72  CALL write_restart(md_env=md_env, root_section=root_section)
73  END IF
74  CALL timestop(handle)
75 
76  END SUBROUTINE md_output
77 
78 ! **************************************************************************************************
79 !> \brief read eigenvalues and eigenvectors of Hessian from vibrational analysis results, for use
80 !> of initialising MD simulations. Expects to read an unformatted binary file
81 !> \param md_section : input section object containing MD subsections and keywords. This should
82 !> provide the filename to read vib analysis eigenvalues and eigenvectors.
83 !> If the filename is not explicitly specified by the user in the input, then
84 !> it will use the default CARTESIAN_EIGS print key filename defined in the
85 !> vibrational analysis input section as the filename.
86 !> \param vib_section : input section object containing vibrational analysis subsections
87 !> and keywords
88 !> \param para_env : cp2k mpi environment object, needed for IO in parallel computations
89 !> \param dof : outputs the total number of eigenvalues (no. degrees of freedom) read from the file
90 !> \param eigenvalues : outputs the eigenvalues (Cartesian frequencies) read from the file
91 !> \param eigenvectors : outputs the corresponding eigenvectors read from the file
92 !> \author Lianheng Tong, lianheng.tong@kcl.ac.uk
93 ! **************************************************************************************************
94  SUBROUTINE read_vib_eigs_unformatted(md_section, &
95  vib_section, &
96  para_env, &
97  dof, &
98  eigenvalues, &
99  eigenvectors)
100  TYPE(section_vals_type), POINTER :: md_section, vib_section
101  TYPE(mp_para_env_type), POINTER :: para_env
102  INTEGER, INTENT(OUT) :: dof
103  REAL(kind=dp), DIMENSION(:), INTENT(OUT) :: eigenvalues
104  REAL(kind=dp), DIMENSION(:, :), INTENT(OUT) :: eigenvectors
105 
106  CHARACTER(LEN=default_path_length) :: filename
107  INTEGER :: jj, n_rep_val, unit_nr
108  LOGICAL :: exist
109  TYPE(cp_logger_type), POINTER :: logger
110  TYPE(section_vals_type), POINTER :: print_key
111 
112  logger => cp_get_default_logger()
113  dof = 0
114  eigenvalues = 0.0_dp
115  eigenvectors = 0.0_dp
116  ! obtain file name
117  CALL section_vals_val_get(md_section, "INITIAL_VIBRATION%VIB_EIGS_FILE_NAME", &
118  n_rep_val=n_rep_val)
119  IF (n_rep_val > 0) THEN
120  CALL section_vals_val_get(md_section, "INITIAL_VIBRATION%VIB_EIGS_FILE_NAME", c_val=filename)
121  ELSE
122  print_key => section_vals_get_subs_vals(vib_section, "PRINT%CARTESIAN_EIGS")
123  filename = cp_print_key_generate_filename(logger, print_key, extension="eig", &
124  my_local=.false.)
125  END IF
126  ! read file
127  IF (para_env%is_source()) THEN
128  INQUIRE (file=filename, exist=exist)
129  IF (.NOT. exist) THEN
130  cpabort("File "//filename//" is not found.")
131  END IF
132  CALL open_file(file_name=filename, &
133  file_action="READ", &
134  file_form="UNFORMATTED", &
135  file_status="OLD", &
136  unit_number=unit_nr)
137  ! the first record contains one integer giving degrees of freedom
138  READ (unit_nr) dof
139  IF (dof .GT. SIZE(eigenvalues)) THEN
140  cpabort("Too many DoFs found in "//filename)
141  END IF
142  ! the second record contains the eigenvalues
143  READ (unit_nr) eigenvalues(1:dof)
144  ! the rest of the records contain the eigenvectors
145  DO jj = 1, dof
146  READ (unit_nr) eigenvectors(1:dof, jj)
147  END DO
148  END IF
149  ! broadcast to all compulational nodes. note that it is assumed
150  ! that source is the ionode
151  CALL para_env%bcast(dof)
152  CALL para_env%bcast(eigenvalues)
153  CALL para_env%bcast(eigenvectors)
154  ! close file
155  IF (para_env%is_source()) THEN
156  CALL close_file(unit_number=unit_nr)
157  END IF
158  END SUBROUTINE read_vib_eigs_unformatted
159 
160 END MODULE md_util
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
subroutine, public close_file(unit_number, file_status, keep_preconnection)
Close an open file given by its logical unit number. Optionally, keep the file and unit preconnected.
Definition: cp_files.F:119
various routines to log and control the output. The idea is that decisions about where to log should ...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
character(len=default_path_length) function, public cp_print_key_generate_filename(logger, print_key, middle_name, extension, my_local)
Utility function that returns a unit number to write the print key. Might open a file with a unique f...
Set of routines to dump the restart file of CP2K.
subroutine, public write_restart(md_env, force_env, root_section, coords, vels, pint_env, helium_env)
checks if a restart needs to be written and does so, updating all necessary fields in the input file....
objects that represent the structure of input sections and the data contained in an input section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
integer, parameter, public default_path_length
Definition: kinds.F:58
prints all energy info per timestep to the screen or to user defined output files
Definition: md_energies.F:16
subroutine, public md_write_output(md_env)
This routine computes the conserved quantity, temperature and things like that and prints them out.
Definition: md_energies.F:252
Utilities for Molecular Dynamics.
Definition: md_util.F:12
subroutine, public md_output(md_env, md_section, root_section, forced_io)
collects the part of the MD that, basically, does the output
Definition: md_util.F:53
subroutine, public read_vib_eigs_unformatted(md_section, vib_section, para_env, dof, eigenvalues, eigenvectors)
read eigenvalues and eigenvectors of Hessian from vibrational analysis results, for use of initialisi...
Definition: md_util.F:100
Interface to the message passing library MPI.