(git:ccc2433)
topology_xyz.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 ! **************************************************************************************************
10  cp_logger_type
14  parser_get_object,&
16  USE cp_parser_types, ONLY: cp_parser_type,&
19  USE cp_units, ONLY: cp_unit_to_cp2k
20  USE input_section_types, ONLY: section_vals_type
21  USE kinds, ONLY: default_string_length,&
22  dp,&
24  USE memory_utilities, ONLY: reallocate
25  USE message_passing, ONLY: mp_para_env_type
26  USE periodic_table, ONLY: nelem,&
27  ptable
28  USE string_table, ONLY: id2str,&
29  s2s,&
30  str2id
31  USE topology_types, ONLY: atom_info_type,&
33 #include "./base/base_uses.f90"
34 
35  IMPLICIT NONE
36 
37  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'topology_xyz'
38 
39  PRIVATE
40  PUBLIC :: read_coordinate_xyz
41 
42 CONTAINS
43 
44 ! **************************************************************************************************
45 !> \brief ...
46 !> \param topology ...
47 !> \param para_env ...
48 !> \param subsys_section ...
49 !> \author Teodoro Laino
50 ! **************************************************************************************************
51  SUBROUTINE read_coordinate_xyz(topology, para_env, subsys_section)
53  TYPE(mp_para_env_type), POINTER :: para_env
54  TYPE(section_vals_type), POINTER :: subsys_section
55 
56  CHARACTER(len=*), PARAMETER :: routinen = 'read_coordinate_xyz'
57 
58  CHARACTER(LEN=default_string_length) :: my_default_index, strtmp
59  CHARACTER(LEN=max_line_length) :: error_message
60  INTEGER :: frame, handle, ian, iw, j, natom
61  LOGICAL :: my_end
62  TYPE(atom_info_type), POINTER :: atom_info
63  TYPE(cp_logger_type), POINTER :: logger
64  TYPE(cp_parser_type) :: parser
65 
66  CALL timeset(routinen, handle)
67 
68  NULLIFY (logger)
69  logger => cp_get_default_logger()
70  iw = cp_print_key_unit_nr(logger, subsys_section, "PRINT%TOPOLOGY_INFO/XYZ_INFO", &
71  extension=".subsysLog")
72 
73  atom_info => topology%atom_info
74 
75  IF (iw > 0) THEN
76  WRITE (unit=iw, fmt="(T2,A)") &
77  "BEGIN of XYZ data read from file "//trim(topology%coord_file_name)
78  END IF
79 
80  CALL parser_create(parser, topology%coord_file_name, para_env=para_env, &
81  parse_white_lines=.true.)
82 
83  ! Element is assigned on the basis of the atm_name
84  topology%aa_element = .true.
85 
86  natom = 0
87  frame = 0
88  CALL parser_get_next_line(parser, 1)
89  frames: DO
90  ! Atom numbers
91  CALL parser_get_object(parser, natom)
92  frame = frame + 1
93  IF (frame == 1) THEN
94  CALL reallocate(atom_info%id_molname, 1, natom)
95  CALL reallocate(atom_info%id_resname, 1, natom)
96  CALL reallocate(atom_info%resid, 1, natom)
97  CALL reallocate(atom_info%id_atmname, 1, natom)
98  CALL reallocate(atom_info%r, 1, 3, 1, natom)
99  CALL reallocate(atom_info%atm_mass, 1, natom)
100  CALL reallocate(atom_info%atm_charge, 1, natom)
101  CALL reallocate(atom_info%occup, 1, natom)
102  CALL reallocate(atom_info%beta, 1, natom)
103  CALL reallocate(atom_info%id_element, 1, natom)
104  ELSE IF (natom > SIZE(atom_info%id_atmname)) THEN
105  cpabort("Atom number differs in different frames!")
106  END IF
107  ! Dummy line
108  CALL parser_get_next_line(parser, 2)
109  DO j = 1, natom
110  ! Atom coordinates
111  READ (parser%input_line, *) strtmp, &
112  atom_info%r(1, j), &
113  atom_info%r(2, j), &
114  atom_info%r(3, j)
115  error_message = ""
116  CALL read_integer_object(strtmp, ian, error_message)
117  IF (len_trim(error_message) == 0) THEN
118  ! Integer value found: assume atomic number, check it, and load
119  ! the corresponding element symbol if valid
120  IF ((ian < 0) .OR. (ian > nelem)) THEN
121  error_message = "Invalid atomic number <"//trim(strtmp)// &
122  "> found in the xyz file <"//trim(topology%coord_file_name)//">!"
123  cpabort(trim(error_message))
124  ELSE
125  atom_info%id_atmname(j) = str2id(s2s(ptable(ian)%symbol))
126  END IF
127  ELSE
128  atom_info%id_atmname(j) = str2id(s2s(strtmp))
129  END IF
130  ! For default, set atom name to residue name to molecule name
131  WRITE (my_default_index, '(I0)') j
132  atom_info%id_molname(j) = str2id(s2s(trim(id2str(atom_info%id_atmname(j)))//trim(my_default_index)))
133  atom_info%id_resname(j) = atom_info%id_molname(j)
134  atom_info%resid(j) = 1
135  atom_info%id_element(j) = atom_info%id_atmname(j)
136  atom_info%atm_mass(j) = huge(0.0_dp)
137  atom_info%atm_charge(j) = -huge(0.0_dp)
138  IF (iw > 0) THEN
139  WRITE (unit=iw, fmt="(T2,A4,3F8.3,2X,A)") &
140  trim(id2str(atom_info%id_atmname(j))), &
141  atom_info%r(1, j), &
142  atom_info%r(2, j), &
143  atom_info%r(3, j), &
144  adjustl(trim(id2str(atom_info%id_molname(j))))
145  END IF
146  atom_info%r(1, j) = cp_unit_to_cp2k(atom_info%r(1, j), "angstrom")
147  atom_info%r(2, j) = cp_unit_to_cp2k(atom_info%r(2, j), "angstrom")
148  atom_info%r(3, j) = cp_unit_to_cp2k(atom_info%r(3, j), "angstrom")
149  ! If there's a white line or end of file exit.. otherwise read other available
150  ! snapshots
151  CALL parser_get_next_line(parser, 1, at_end=my_end)
152  my_end = my_end .OR. (len_trim(parser%input_line) == 0)
153  IF (my_end) THEN
154  IF (j /= natom) &
155  CALL cp_abort(__location__, &
156  "Number of lines in XYZ format not equal to the number of atoms."// &
157  " Error in XYZ format. Very probably the line with title is missing or is empty."// &
158  " Please check the XYZ file and rerun your job!")
159  EXIT frames
160  END IF
161  END DO
162  END DO frames
163  CALL parser_release(parser)
164 
165  IF (iw > 0) THEN
166  WRITE (unit=iw, fmt="(T2,A)") &
167  "END of XYZ frame data read from file "//trim(topology%coord_file_name)
168  END IF
169 
170  topology%natoms = natom
171  topology%molname_generated = .true.
172 
173  CALL cp_print_key_finished_output(iw, logger, subsys_section, &
174  "PRINT%TOPOLOGY_INFO/XYZ_INFO")
175 
176  CALL timestop(handle)
177 
178  END SUBROUTINE read_coordinate_xyz
179 
180 END MODULE topology_xyz
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...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
subroutine, public cp_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, on_file, mpi_io)
should be called after you finish working with a unit obtained with cp_print_key_unit_nr,...
Utility routines to read data from files. Kept as close as possible to the old parser because.
elemental subroutine, public read_integer_object(string, object, error_message)
Returns an integer number read from a string including products of integer numbers like iz1*iz2*iz3.
subroutine, public parser_get_next_line(parser, nline, at_end)
Read the next input line and broadcast the input information. Skip (nline-1) lines and skip also all ...
Utility routines to read data from files. Kept as close as possible to the old parser because.
subroutine, public parser_release(parser)
releases the parser
subroutine, public parser_create(parser, file_name, unit_nr, para_env, end_section_label, separator_chars, comment_char, continuation_char, quote_char, section_char, parse_white_lines, initial_variables, apply_preprocessing)
Start a parser run. Initial variables allow to @SET stuff before opening the file.
unit conversion facility
Definition: cp_units.F:30
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
Definition: cp_units.F:1150
objects that represent the structure of input sections and the data contained in an input section
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public max_line_length
Definition: kinds.F:59
integer, parameter, public dp
Definition: kinds.F:34
integer, parameter, public default_string_length
Definition: kinds.F:57
Utility routines for the memory handling.
Interface to the message passing library MPI.
Periodic Table related data definitions.
type(atom), dimension(0:nelem), public ptable
integer, parameter, public nelem
generates a unique id number for a string (str2id) that can be used two compare two strings....
Definition: string_table.F:22
character(len=default_string_length) function, public s2s(str)
converts a string in a string of default_string_length
Definition: string_table.F:141
integer function, public str2id(str)
returns a unique id for a given string, and stores the string for later retrieval using the id.
Definition: string_table.F:72
character(len=default_string_length) function, public id2str(id)
returns the string associated with a given id
Definition: string_table.F:115
subroutine, public read_coordinate_xyz(topology, para_env, subsys_section)
...
Definition: topology_xyz.F:52
Control for reading in different topologies and coordinates.
Definition: topology.F:13