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 : MODULE topology_cp2k
9 :
10 : USE cell_types, ONLY: cell_type,&
11 : scaled_to_real
12 : USE cp_log_handling, ONLY: cp_get_default_logger,&
13 : cp_logger_type
14 : USE cp_output_handling, ONLY: cp_print_key_finished_output,&
15 : cp_print_key_unit_nr
16 : USE cp_parser_methods, ONLY: parser_get_object,&
17 : parser_test_next_token,&
18 : read_integer_object
19 : USE cp_parser_types, ONLY: cp_parser_type,&
20 : parser_create,&
21 : parser_release
22 : USE cp_units, ONLY: cp_unit_to_cp2k
23 : USE input_section_types, ONLY: section_get_ival,&
24 : section_get_rval,&
25 : section_vals_get,&
26 : section_vals_get_subs_vals,&
27 : section_vals_type,&
28 : section_vals_val_get,&
29 : section_vals_val_set
30 : USE kinds, ONLY: default_string_length,&
31 : dp,&
32 : max_line_lengTh
33 : USE memory_utilities, ONLY: reallocate
34 : USE message_passing, ONLY: mp_para_env_type
35 : USE periodic_table, ONLY: nelem,&
36 : ptable
37 : USE string_table, ONLY: id2str,&
38 : s2s,&
39 : str2id
40 : USE topology_types, ONLY: atom_info_type,&
41 : topology_parameters_type
42 : #include "./base/base_uses.f90"
43 :
44 : IMPLICIT NONE
45 :
46 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'topology_cp2k'
47 :
48 : PRIVATE
49 : PUBLIC :: read_coordinate_cp2k
50 :
51 : CONTAINS
52 :
53 : ! **************************************************************************************************
54 : !> \brief Read the CP2K &COORD section from an external file, i.e. read
55 : !> atomic coordinates and molecule/residue information in CP2K format.
56 : !> \param topology ...
57 : !> \param para_env ...
58 : !> \param subsys_section ...
59 : !> \date 17.01.2011 (Creation, MK)
60 : !> \author Matthias Krack (MK)
61 : !> \version 1.0
62 : ! **************************************************************************************************
63 36 : SUBROUTINE read_coordinate_cp2k(topology, para_env, subsys_section)
64 :
65 : TYPE(topology_parameters_type) :: topology
66 : TYPE(mp_para_env_type), POINTER :: para_env
67 : TYPE(section_vals_type), POINTER :: subsys_section
68 :
69 : CHARACTER(LEN=*), PARAMETER :: routineN = 'read_coordinate_cp2k'
70 :
71 : CHARACTER(LEN=default_string_length) :: string
72 : CHARACTER(LEN=max_line_length) :: error_message
73 : INTEGER :: handle, i, ian, iw, natom, newsize, &
74 : number_of_atoms
75 : LOGICAL :: eof, explicit, scaled_coordinates
76 : REAL(KIND=dp) :: pfactor, unit_conv
77 : REAL(KIND=dp), DIMENSION(3) :: r
78 : TYPE(atom_info_type), POINTER :: atom_info
79 : TYPE(cell_type), POINTER :: cell
80 : TYPE(cp_logger_type), POINTER :: logger
81 : TYPE(cp_parser_type), POINTER :: parser
82 : TYPE(section_vals_type), POINTER :: coord_section
83 :
84 12 : CALL timeset(routineN, handle)
85 :
86 12 : NULLIFY (coord_section)
87 12 : NULLIFY (logger)
88 12 : NULLIFY (parser)
89 12 : logger => cp_get_default_logger()
90 : iw = cp_print_key_unit_nr(logger, subsys_section, "PRINT%TOPOLOGY_INFO/XYZ_INFO", &
91 12 : extension=".subsysLog")
92 :
93 : ! Check if there is a &COORD section
94 12 : coord_section => section_vals_get_subs_vals(subsys_section, "COORD")
95 12 : CALL section_vals_get(coord_section, explicit=explicit)
96 12 : IF (explicit) THEN
97 10 : CALL section_vals_val_get(coord_section, "UNIT", c_val=string)
98 10 : CALL section_vals_val_get(coord_section, "SCALED", l_val=scaled_coordinates)
99 : ELSE
100 : ! The default is Cartesian coordinates in Angstrom
101 2 : scaled_coordinates = .FALSE.
102 2 : string = "angstrom"
103 : END IF
104 12 : unit_conv = cp_unit_to_cp2k(1.0_dp, TRIM(string))
105 :
106 12 : atom_info => topology%atom_info
107 12 : cell => topology%cell_muc
108 :
109 12 : IF (iw > 0) THEN
110 : WRITE (UNIT=iw, FMT="(T2,A)") &
111 6 : "BEGIN of COORD section data read from file "//TRIM(topology%coord_file_name)
112 : END IF
113 :
114 12 : pfactor = section_get_rval(subsys_section, "TOPOLOGY%MEMORY_PROGRESSION_FACTOR")
115 12 : number_of_atoms = section_get_ival(subsys_section, "TOPOLOGY%NUMBER_OF_ATOMS")
116 12 : IF (number_of_atoms < 1) THEN
117 12 : newsize = 1000
118 : ELSE
119 0 : newsize = number_of_atoms
120 : END IF
121 :
122 12 : CALL reallocate(atom_info%id_molname, 1, newsize)
123 12 : CALL reallocate(atom_info%id_resname, 1, newsize)
124 12 : CALL reallocate(atom_info%resid, 1, newsize)
125 12 : CALL reallocate(atom_info%id_atmname, 1, newsize)
126 12 : CALL reallocate(atom_info%r, 1, 3, 1, newsize)
127 12 : CALL reallocate(atom_info%atm_mass, 1, newsize)
128 12 : CALL reallocate(atom_info%atm_charge, 1, newsize)
129 12 : CALL reallocate(atom_info%occup, 1, newsize)
130 12 : CALL reallocate(atom_info%beta, 1, newsize)
131 12 : CALL reallocate(atom_info%id_element, 1, newsize)
132 :
133 12 : topology%molname_generated = .FALSE.
134 : ! Element is assigned on the basis of the atm_name
135 12 : topology%aa_element = .TRUE.
136 :
137 36 : ALLOCATE (parser)
138 12 : CALL parser_create(parser, topology%coord_file_name, para_env=para_env)
139 :
140 12 : natom = 0
141 : DO
142 1164 : CALL parser_get_object(parser, object=string, newline=.TRUE., at_end=eof)
143 1164 : IF (eof) EXIT
144 1152 : natom = natom + 1
145 1152 : IF (natom > SIZE(atom_info%id_atmname)) THEN
146 0 : newsize = INT(pfactor*natom)
147 0 : CALL reallocate(atom_info%id_molname, 1, newsize)
148 0 : CALL reallocate(atom_info%id_resname, 1, newsize)
149 0 : CALL reallocate(atom_info%resid, 1, newsize)
150 0 : CALL reallocate(atom_info%id_atmname, 1, newsize)
151 0 : CALL reallocate(atom_info%r, 1, 3, 1, newsize)
152 0 : CALL reallocate(atom_info%atm_mass, 1, newsize)
153 0 : CALL reallocate(atom_info%atm_charge, 1, newsize)
154 0 : CALL reallocate(atom_info%occup, 1, newsize)
155 0 : CALL reallocate(atom_info%beta, 1, newsize)
156 0 : CALL reallocate(atom_info%id_element, 1, newsize)
157 : END IF
158 1152 : error_message = ""
159 1152 : CALL read_integer_object(string, ian, error_message)
160 1152 : IF (LEN_TRIM(error_message) == 0) THEN
161 : ! Integer value found: assume atomic number, check it, and load
162 : ! the corresponding element symbol if valid
163 0 : IF ((ian < 0) .OR. (ian > nelem)) THEN
164 : error_message = "Invalid atomic number <"//TRIM(string)// &
165 0 : "> found in the xyz file <"//TRIM(topology%coord_file_name)//">!"
166 0 : CPABORT(TRIM(error_message))
167 : ELSE
168 0 : atom_info%id_atmname(natom) = str2id(s2s(ptable(ian)%symbol))
169 : END IF
170 : ELSE
171 1152 : atom_info%id_atmname(natom) = str2id(s2s(string))
172 : END IF
173 : ! Read x, y, and z coordinate of the current atom
174 4608 : DO i = 1, 3
175 4608 : CALL parser_get_object(parser, object=r(i))
176 : END DO
177 1152 : IF (scaled_coordinates) THEN
178 576 : CALL scaled_to_real(atom_info%r(1:3, natom), r, cell)
179 : ELSE
180 2304 : atom_info%r(1:3, natom) = r(1:3)*unit_conv
181 : END IF
182 1152 : IF (parser_test_next_token(parser) /= "EOL") THEN
183 768 : CALL parser_get_object(parser, object=string)
184 768 : atom_info%id_molname(natom) = str2id(s2s(string))
185 768 : IF (parser_test_next_token(parser) /= "EOL") THEN
186 384 : CALL parser_get_object(parser, object=string)
187 384 : atom_info%id_resname(natom) = str2id(s2s(string))
188 : ELSE
189 1152 : atom_info%id_resname(natom) = atom_info%id_molname(natom)
190 : END IF
191 : ELSE
192 384 : string = ""
193 384 : WRITE (UNIT=string, FMT="(I0)") natom
194 384 : atom_info%id_molname(natom) = str2id(s2s(TRIM(id2str(atom_info%id_atmname(natom)))//TRIM(string)))
195 384 : atom_info%id_resname(natom) = atom_info%id_molname(natom)
196 1536 : topology%molname_generated = .TRUE.
197 : END IF
198 1152 : atom_info%resid(natom) = 1
199 1152 : atom_info%id_element(natom) = atom_info%id_atmname(natom)
200 1152 : atom_info%atm_mass(natom) = HUGE(0.0_dp)
201 1152 : atom_info%atm_charge(natom) = -HUGE(0.0_dp)
202 1152 : IF (iw > 0) THEN
203 : WRITE (UNIT=iw, FMT="(T2,A,3F20.8,2(2X,A))") &
204 576 : TRIM(id2str(atom_info%id_atmname(natom))), atom_info%r(1:3, natom), &
205 576 : ADJUSTL(TRIM(id2str(atom_info%id_molname(natom)))), &
206 1152 : ADJUSTL(TRIM(id2str(atom_info%id_resname(natom))))
207 : END IF
208 1164 : IF (natom == number_of_atoms) EXIT
209 : END DO
210 :
211 12 : CALL parser_release(parser)
212 12 : DEALLOCATE (parser)
213 :
214 12 : topology%natoms = natom
215 12 : CALL reallocate(atom_info%id_molname, 1, natom)
216 12 : CALL reallocate(atom_info%id_resname, 1, natom)
217 12 : CALL reallocate(atom_info%resid, 1, natom)
218 12 : CALL reallocate(atom_info%id_atmname, 1, natom)
219 12 : CALL reallocate(atom_info%r, 1, 3, 1, natom)
220 12 : CALL reallocate(atom_info%atm_mass, 1, natom)
221 12 : CALL reallocate(atom_info%atm_charge, 1, natom)
222 12 : CALL reallocate(atom_info%occup, 1, natom)
223 12 : CALL reallocate(atom_info%beta, 1, natom)
224 12 : CALL reallocate(atom_info%id_element, 1, natom)
225 :
226 12 : CALL section_vals_val_set(subsys_section, "TOPOLOGY%NUMBER_OF_ATOMS", i_val=natom)
227 :
228 12 : IF (iw > 0) THEN
229 : WRITE (UNIT=iw, FMT="(T2,A)") &
230 6 : "END of COORD section data read from file "//TRIM(topology%coord_file_name)
231 : END IF
232 :
233 : CALL cp_print_key_finished_output(iw, logger, subsys_section, &
234 12 : "PRINT%TOPOLOGY_INFO/XYZ_INFO")
235 :
236 12 : CALL timestop(handle)
237 :
238 12 : END SUBROUTINE read_coordinate_cp2k
239 :
240 : END MODULE topology_cp2k
|