Line data Source code
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 : !> \par History
10 : !> JGH (30.11.2001) : new entries in setup_parameters_type
11 : !> change name from input_file_name to coord_...
12 : !> added topology file
13 : !> added atom_names
14 : !> Teodoro Laino [tlaino] 12.2008 - Preparing for VIRTUAL SITE constraints
15 : !> (patch by Marcel Baer)
16 : !> \author CJM & JGH
17 : ! **************************************************************************************************
18 : MODULE topology_types
19 : USE cell_types, ONLY: cell_release,&
20 : cell_type
21 : USE colvar_types, ONLY: colvar_p_type,&
22 : colvar_release
23 : USE input_constants, ONLY: do_bondparm_covalent,&
24 : do_conn_generate,&
25 : do_constr_none,&
26 : do_skip_13
27 : USE kinds, ONLY: default_path_length,&
28 : default_string_length,&
29 : dp
30 : #include "./base/base_uses.f90"
31 :
32 : IMPLICIT NONE
33 :
34 : ! **************************************************************************************************
35 : TYPE atom_info_type
36 : INTEGER, DIMENSION(:), POINTER :: id_molname => NULL(), &
37 : id_resname => NULL(), &
38 : id_atmname => NULL(), &
39 : id_atom_names => NULL(), &
40 : id_element => NULL()
41 : INTEGER, POINTER :: resid(:) => NULL()
42 : REAL(KIND=dp), DIMENSION(:, :), POINTER :: r => NULL()
43 : INTEGER, POINTER :: map_mol_typ(:) => NULL()
44 : INTEGER, POINTER :: map_mol_num(:) => NULL()
45 : INTEGER, POINTER :: map_mol_res(:) => NULL()
46 : REAL(KIND=dp), POINTER :: atm_charge(:) => NULL()
47 : REAL(KIND=dp), POINTER :: atm_mass(:) => NULL()
48 : REAL(KIND=dp), POINTER :: occup(:) => NULL()
49 : REAL(KIND=dp), POINTER :: beta(:) => NULL()
50 : END TYPE atom_info_type
51 :
52 : ! **************************************************************************************************
53 : TYPE connectivity_info_type
54 : INTEGER, POINTER :: bond_a(:) => NULL(), bond_b(:) => NULL(), bond_type(:) => NULL()
55 : INTEGER, POINTER :: ub_a(:) => NULL(), ub_b(:) => NULL(), ub_c(:) => NULL()
56 : INTEGER, POINTER :: theta_a(:) => NULL(), theta_b(:) => NULL(), theta_c(:) => NULL(), theta_type(:) => NULL()
57 : INTEGER, POINTER :: phi_a(:) => NULL(), phi_b(:) => NULL(), phi_c(:) => NULL(), phi_d(:) => NULL(), phi_type(:) => NULL()
58 : INTEGER, POINTER :: impr_a(:) => NULL(), impr_b(:) => NULL(), impr_c(:) => NULL(), &
59 : impr_d(:) => NULL(), impr_type(:) => NULL()
60 : INTEGER, POINTER :: onfo_a(:) => NULL(), onfo_b(:) => NULL()
61 : INTEGER, POINTER :: c_bond_a(:) => NULL(), c_bond_b(:) => NULL(), c_bond_type(:) => NULL()
62 : END TYPE connectivity_info_type
63 :
64 : ! **************************************************************************************************
65 : TYPE constraint_info_type
66 : ! Bonds involving Hydrogens
67 : LOGICAL :: hbonds_restraint = .FALSE. ! Restraints control
68 : REAL(KIND=dp) :: hbonds_k0 = -1.0_dp ! Restraints control
69 : ! Fixed Atoms
70 : INTEGER :: nfixed_atoms = -1
71 : INTEGER, POINTER :: fixed_atoms(:) => NULL(), fixed_type(:) => NULL(), fixed_mol_type(:) => NULL()
72 : LOGICAL, POINTER :: fixed_restraint(:) => NULL() ! Restraints control
73 : REAL(KIND=dp), POINTER :: fixed_k0(:) => NULL() ! Restraints control
74 : ! Freeze QM or MM
75 : INTEGER :: freeze_qm = -1, freeze_mm = -1, freeze_qm_type = -1, freeze_mm_type = -1
76 : LOGICAL :: fixed_mm_restraint = .FALSE., fixed_qm_restraint = .FALSE. ! Restraints control
77 : REAL(KIND=dp) :: fixed_mm_k0 = -1.0_dp, fixed_qm_k0 = -1.0_dp ! Restraints control
78 : ! Freeze with molnames
79 : LOGICAL, POINTER :: fixed_mol_restraint(:) => NULL() ! Restraints control
80 : REAL(KIND=dp), POINTER :: fixed_mol_k0(:) => NULL() ! Restraints control
81 : CHARACTER(LEN=default_string_length), POINTER :: fixed_molnames(:) => NULL()
82 : LOGICAL, POINTER, DIMENSION(:) :: fixed_exclude_qm => NULL(), fixed_exclude_mm => NULL()
83 : ! Collective constraints
84 : INTEGER :: nconst_colv = -1
85 : INTEGER, POINTER :: const_colv_mol(:) => NULL()
86 : CHARACTER(LEN=default_string_length), POINTER :: const_colv_molname(:) => NULL()
87 : REAL(KIND=dp), POINTER :: const_colv_target(:) => NULL()
88 : REAL(KIND=dp), POINTER :: const_colv_target_growth(:) => NULL()
89 : TYPE(colvar_p_type), POINTER, DIMENSION(:) :: colvar_set => NULL()
90 : LOGICAL, POINTER :: colv_intermolecular(:) => NULL()
91 : LOGICAL, POINTER :: colv_restraint(:) => NULL() ! Restraints control
92 : REAL(KIND=dp), POINTER :: colv_k0(:) => NULL() ! Restraints control
93 : LOGICAL, POINTER, DIMENSION(:) :: colv_exclude_qm => NULL(), colv_exclude_mm => NULL()
94 : ! G3x3
95 : INTEGER :: nconst_g33 = -1
96 : INTEGER, POINTER :: const_g33_mol(:) => NULL()
97 : CHARACTER(LEN=default_string_length), POINTER :: const_g33_molname(:) => NULL()
98 : INTEGER, POINTER :: const_g33_a(:) => NULL()
99 : INTEGER, POINTER :: const_g33_b(:) => NULL()
100 : INTEGER, POINTER :: const_g33_c(:) => NULL()
101 : REAL(KIND=dp), POINTER :: const_g33_dab(:) => NULL()
102 : REAL(KIND=dp), POINTER :: const_g33_dac(:) => NULL()
103 : REAL(KIND=dp), POINTER :: const_g33_dbc(:) => NULL()
104 : LOGICAL, POINTER :: g33_intermolecular(:) => NULL()
105 : LOGICAL, POINTER :: g33_restraint(:) => NULL() ! Restraints control
106 : REAL(KIND=dp), POINTER :: g33_k0(:) => NULL() ! Restraints control
107 : LOGICAL, POINTER, DIMENSION(:) :: g33_exclude_qm => NULL(), g33_exclude_mm => NULL()
108 : ! G4x6
109 : INTEGER :: nconst_g46 = -1
110 : INTEGER, POINTER :: const_g46_mol(:) => NULL()
111 : CHARACTER(LEN=default_string_length), POINTER :: const_g46_molname(:) => NULL()
112 : INTEGER, POINTER :: const_g46_a(:) => NULL()
113 : INTEGER, POINTER :: const_g46_b(:) => NULL()
114 : INTEGER, POINTER :: const_g46_c(:) => NULL()
115 : INTEGER, POINTER :: const_g46_d(:) => NULL()
116 : REAL(KIND=dp), POINTER :: const_g46_dab(:) => NULL()
117 : REAL(KIND=dp), POINTER :: const_g46_dac(:) => NULL()
118 : REAL(KIND=dp), POINTER :: const_g46_dbc(:) => NULL()
119 : REAL(KIND=dp), POINTER :: const_g46_dad(:) => NULL()
120 : REAL(KIND=dp), POINTER :: const_g46_dbd(:) => NULL()
121 : REAL(KIND=dp), POINTER :: const_g46_dcd(:) => NULL()
122 : LOGICAL, POINTER :: g46_intermolecular(:) => NULL()
123 : LOGICAL, POINTER :: g46_restraint(:) => NULL() ! Restraints control
124 : REAL(KIND=dp), POINTER :: g46_k0(:) => NULL() ! Restraints control
125 : LOGICAL, POINTER, DIMENSION(:) :: g46_exclude_qm => NULL(), g46_exclude_mm => NULL()
126 : ! virtual_site
127 : INTEGER :: nconst_vsite = -1
128 : INTEGER, POINTER :: const_vsite_mol(:) => NULL()
129 : CHARACTER(LEN=default_string_length), POINTER :: const_vsite_molname(:) => NULL()
130 : INTEGER, POINTER :: const_vsite_a(:) => NULL()
131 : INTEGER, POINTER :: const_vsite_b(:) => NULL()
132 : INTEGER, POINTER :: const_vsite_c(:) => NULL()
133 : INTEGER, POINTER :: const_vsite_d(:) => NULL()
134 : REAL(KIND=dp), POINTER :: const_vsite_wbc(:) => NULL()
135 : REAL(KIND=dp), POINTER :: const_vsite_wdc(:) => NULL()
136 : LOGICAL, POINTER :: vsite_intermolecular(:) => NULL()
137 : LOGICAL, POINTER :: vsite_restraint(:) => NULL() ! Restraints control
138 : REAL(KIND=dp), POINTER :: vsite_k0(:) => NULL() ! Restraints control
139 : LOGICAL, POINTER, DIMENSION(:) :: vsite_exclude_qm => NULL(), vsite_exclude_mm => NULL()
140 : END TYPE constraint_info_type
141 :
142 : ! **************************************************************************************************
143 : TYPE topology_parameters_type
144 : TYPE(atom_info_type), POINTER :: atom_info => NULL()
145 : TYPE(connectivity_info_type), POINTER :: conn_info => NULL()
146 : TYPE(constraint_info_type), POINTER :: cons_info => NULL()
147 : TYPE(cell_type), POINTER :: cell => NULL(), cell_ref => NULL(), cell_muc => NULL()
148 : INTEGER :: conn_type = -1
149 : INTEGER :: coord_type = -1
150 : INTEGER :: exclude_vdw = -1
151 : INTEGER :: exclude_ei = -1
152 : INTEGER :: bondparm_type = -1
153 : !TRY TO REMOVE THIS FIVE VARIABLE IN THE FUTURE
154 : INTEGER :: natoms = -1, natom_type = -1, natom_muc = -1
155 : INTEGER :: nmol = -1, nmol_type = -1, nmol_conn = -1
156 : !TRY TO REMOVE THIS FIVE VARIABLE IN THE FUTURE
157 : LOGICAL :: aa_element = .FALSE.
158 : LOGICAL :: molname_generated = .FALSE.
159 : REAL(KIND=dp) :: bondparm_factor = -1.0_dp
160 : LOGICAL :: create_molecules = .FALSE.
161 : LOGICAL :: reorder_atom = .FALSE.
162 : LOGICAL :: molecules_check = .FALSE.
163 : LOGICAL :: coordinate = .FALSE.
164 : LOGICAL :: use_g96_velocity = .FALSE.
165 : CHARACTER(LEN=default_path_length) :: coord_file_name = ""
166 : CHARACTER(LEN=default_path_length) :: conn_file_name = ""
167 : LOGICAL :: const_atom = .FALSE.
168 : LOGICAL :: const_hydr = .FALSE.
169 : LOGICAL :: const_colv = .FALSE.
170 : LOGICAL :: const_33 = .FALSE.
171 : LOGICAL :: const_46 = .FALSE.
172 : LOGICAL :: const_vsite = .FALSE.
173 : LOGICAL :: charge_occup = .FALSE.
174 : LOGICAL :: charge_beta = .FALSE.
175 : LOGICAL :: charge_extended = .FALSE.
176 : LOGICAL :: para_res = .FALSE.
177 : END TYPE topology_parameters_type
178 :
179 : ! **************************************************************************************************
180 : TYPE constr_list_type
181 : INTEGER, DIMENSION(:), POINTER :: constr => NULL()
182 : END TYPE constr_list_type
183 :
184 : PUBLIC :: atom_info_type, &
185 : connectivity_info_type, &
186 : constraint_info_type, &
187 : topology_parameters_type, &
188 : constr_list_type
189 :
190 : PUBLIC :: init_topology, &
191 : deallocate_topology, &
192 : pre_read_topology
193 :
194 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'topology_types'
195 : PRIVATE
196 :
197 : CONTAINS
198 :
199 : ! **************************************************************************************************
200 : !> \brief 1. Just NULLIFY and zero all the stuff
201 : !> \param topology ...
202 : !> \par History
203 : !> none
204 : ! **************************************************************************************************
205 10274 : SUBROUTINE init_topology(topology)
206 : TYPE(topology_parameters_type), INTENT(INOUT) :: topology
207 :
208 : !-----------------------------------------------------------------------------
209 : ! 1. Nullify and allocate things in topology
210 : !-----------------------------------------------------------------------------
211 :
212 10274 : ALLOCATE (topology%atom_info)
213 10274 : ALLOCATE (topology%conn_info)
214 10274 : ALLOCATE (topology%cons_info)
215 : !-----------------------------------------------------------------------------
216 : ! 2. Initialize and Nullify things in topology
217 : !-----------------------------------------------------------------------------
218 10274 : NULLIFY (topology%cell, topology%cell_ref, topology%cell_muc)
219 10274 : topology%natoms = 0
220 10274 : topology%natom_muc = 0
221 10274 : topology%natom_type = 0
222 10274 : topology%nmol = 0
223 10274 : topology%nmol_type = 0
224 10274 : topology%nmol_conn = 0
225 10274 : topology%bondparm_type = do_bondparm_covalent
226 10274 : topology%reorder_atom = .FALSE.
227 10274 : topology%create_molecules = .FALSE.
228 10274 : topology%molecules_check = .FALSE.
229 10274 : topology%coordinate = .FALSE.
230 10274 : topology%use_g96_velocity = .FALSE.
231 10274 : topology%coord_type = -1
232 10274 : topology%coord_file_name = ''
233 10274 : topology%conn_type = do_conn_generate
234 10274 : topology%conn_file_name = 'OFF'
235 10274 : topology%const_atom = .FALSE.
236 10274 : topology%const_hydr = .FALSE.
237 10274 : topology%const_colv = .FALSE.
238 10274 : topology%const_33 = .FALSE.
239 10274 : topology%const_46 = .FALSE.
240 10274 : topology%const_vsite = .FALSE.
241 10274 : topology%charge_occup = .FALSE.
242 10274 : topology%charge_beta = .FALSE.
243 10274 : topology%charge_extended = .FALSE.
244 10274 : topology%para_res = .FALSE.
245 10274 : topology%molname_generated = .FALSE.
246 10274 : topology%aa_element = .FALSE.
247 10274 : topology%exclude_vdw = do_skip_13
248 10274 : topology%exclude_ei = do_skip_13
249 : !-----------------------------------------------------------------------------
250 : ! 3. Initialize and Nullify things in topology%atom_info
251 : !-----------------------------------------------------------------------------
252 : NULLIFY (topology%atom_info%id_molname)
253 : NULLIFY (topology%atom_info%id_resname)
254 : NULLIFY (topology%atom_info%resid)
255 : NULLIFY (topology%atom_info%id_atmname)
256 : NULLIFY (topology%atom_info%id_atom_names)
257 : NULLIFY (topology%atom_info%r)
258 : NULLIFY (topology%atom_info%map_mol_typ)
259 : NULLIFY (topology%atom_info%map_mol_num)
260 : NULLIFY (topology%atom_info%map_mol_res)
261 : NULLIFY (topology%atom_info%atm_charge)
262 : NULLIFY (topology%atom_info%atm_mass)
263 : NULLIFY (topology%atom_info%occup)
264 : NULLIFY (topology%atom_info%beta)
265 : NULLIFY (topology%atom_info%id_element)
266 : !-----------------------------------------------------------------------------
267 : ! 4. Initialize and Nullify things in topology%conn_info
268 : !-----------------------------------------------------------------------------
269 : NULLIFY (topology%conn_info%bond_a)
270 : NULLIFY (topology%conn_info%bond_b)
271 : NULLIFY (topology%conn_info%bond_type)
272 : NULLIFY (topology%conn_info%ub_a)
273 : NULLIFY (topology%conn_info%ub_b)
274 : NULLIFY (topology%conn_info%ub_c)
275 : NULLIFY (topology%conn_info%theta_a)
276 : NULLIFY (topology%conn_info%theta_b)
277 : NULLIFY (topology%conn_info%theta_c)
278 : NULLIFY (topology%conn_info%theta_type)
279 : NULLIFY (topology%conn_info%phi_a)
280 : NULLIFY (topology%conn_info%phi_b)
281 : NULLIFY (topology%conn_info%phi_c)
282 : NULLIFY (topology%conn_info%phi_d)
283 : NULLIFY (topology%conn_info%phi_type)
284 : NULLIFY (topology%conn_info%impr_a)
285 : NULLIFY (topology%conn_info%impr_b)
286 : NULLIFY (topology%conn_info%impr_c)
287 : NULLIFY (topology%conn_info%impr_d)
288 : NULLIFY (topology%conn_info%impr_type)
289 : NULLIFY (topology%conn_info%onfo_a)
290 : NULLIFY (topology%conn_info%onfo_b)
291 : NULLIFY (topology%conn_info%c_bond_a)
292 : NULLIFY (topology%conn_info%c_bond_b)
293 : NULLIFY (topology%conn_info%c_bond_type)
294 : !-----------------------------------------------------------------------------
295 : ! 5. Initialize and Nullify things in topology%cons_info
296 : !-----------------------------------------------------------------------------
297 10274 : CALL init_constraint(topology%cons_info)
298 10274 : END SUBROUTINE init_topology
299 :
300 : ! **************************************************************************************************
301 : !> \brief 1. Just NULLIFY and zero all the stuff
302 : !> \param constraint_info ...
303 : !> \par History
304 : !> none
305 : ! **************************************************************************************************
306 10274 : SUBROUTINE init_constraint(constraint_info)
307 : TYPE(constraint_info_type), POINTER :: constraint_info
308 :
309 : ! Bonds involving Hydrogens
310 :
311 10274 : constraint_info%hbonds_restraint = .FALSE.
312 : ! Fixed Atoms
313 10274 : constraint_info%nfixed_atoms = 0
314 10274 : constraint_info%freeze_mm = do_constr_none
315 10274 : constraint_info%freeze_qm = do_constr_none
316 10274 : NULLIFY (constraint_info%fixed_atoms)
317 10274 : NULLIFY (constraint_info%fixed_type)
318 10274 : NULLIFY (constraint_info%fixed_mol_type)
319 10274 : NULLIFY (constraint_info%fixed_molnames)
320 10274 : NULLIFY (constraint_info%fixed_restraint)
321 10274 : NULLIFY (constraint_info%fixed_k0)
322 10274 : NULLIFY (constraint_info%fixed_mol_restraint)
323 10274 : NULLIFY (constraint_info%fixed_mol_k0)
324 10274 : NULLIFY (constraint_info%fixed_exclude_qm, constraint_info%fixed_exclude_mm)
325 : ! Collective Constraints
326 10274 : constraint_info%nconst_colv = 0
327 10274 : NULLIFY (constraint_info%colvar_set)
328 10274 : NULLIFY (constraint_info%const_colv_mol)
329 10274 : NULLIFY (constraint_info%const_colv_molname)
330 10274 : NULLIFY (constraint_info%const_colv_target)
331 10274 : NULLIFY (constraint_info%const_colv_target_growth)
332 10274 : NULLIFY (constraint_info%colv_intermolecular)
333 10274 : NULLIFY (constraint_info%colv_restraint)
334 10274 : NULLIFY (constraint_info%colv_k0)
335 10274 : NULLIFY (constraint_info%colv_exclude_qm, constraint_info%colv_exclude_mm)
336 : ! G3x3
337 10274 : constraint_info%nconst_g33 = 0
338 10274 : NULLIFY (constraint_info%const_g33_mol)
339 10274 : NULLIFY (constraint_info%const_g33_molname)
340 10274 : NULLIFY (constraint_info%const_g33_a)
341 10274 : NULLIFY (constraint_info%const_g33_b)
342 10274 : NULLIFY (constraint_info%const_g33_c)
343 10274 : NULLIFY (constraint_info%const_g33_dab)
344 10274 : NULLIFY (constraint_info%const_g33_dac)
345 10274 : NULLIFY (constraint_info%const_g33_dbc)
346 10274 : NULLIFY (constraint_info%g33_intermolecular)
347 10274 : NULLIFY (constraint_info%g33_restraint)
348 10274 : NULLIFY (constraint_info%g33_k0)
349 10274 : NULLIFY (constraint_info%g33_exclude_qm, constraint_info%g33_exclude_mm)
350 : ! G4x6
351 10274 : constraint_info%nconst_g46 = 0
352 10274 : NULLIFY (constraint_info%const_g46_mol)
353 10274 : NULLIFY (constraint_info%const_g46_molname)
354 10274 : NULLIFY (constraint_info%const_g46_a)
355 10274 : NULLIFY (constraint_info%const_g46_b)
356 10274 : NULLIFY (constraint_info%const_g46_c)
357 10274 : NULLIFY (constraint_info%const_g46_d)
358 10274 : NULLIFY (constraint_info%const_g46_dab)
359 10274 : NULLIFY (constraint_info%const_g46_dac)
360 10274 : NULLIFY (constraint_info%const_g46_dbc)
361 10274 : NULLIFY (constraint_info%const_g46_dad)
362 10274 : NULLIFY (constraint_info%const_g46_dbd)
363 10274 : NULLIFY (constraint_info%const_g46_dcd)
364 10274 : NULLIFY (constraint_info%g46_intermolecular)
365 10274 : NULLIFY (constraint_info%g46_restraint)
366 10274 : NULLIFY (constraint_info%g46_k0)
367 10274 : NULLIFY (constraint_info%g46_exclude_qm, constraint_info%g46_exclude_mm)
368 : ! virtual_site
369 10274 : constraint_info%nconst_vsite = 0
370 10274 : NULLIFY (constraint_info%const_vsite_mol)
371 10274 : NULLIFY (constraint_info%const_vsite_molname)
372 10274 : NULLIFY (constraint_info%const_vsite_a)
373 10274 : NULLIFY (constraint_info%const_vsite_b)
374 10274 : NULLIFY (constraint_info%const_vsite_c)
375 10274 : NULLIFY (constraint_info%const_vsite_d)
376 10274 : NULLIFY (constraint_info%const_vsite_wbc)
377 10274 : NULLIFY (constraint_info%const_vsite_wdc)
378 10274 : NULLIFY (constraint_info%vsite_intermolecular)
379 10274 : NULLIFY (constraint_info%vsite_restraint)
380 10274 : NULLIFY (constraint_info%vsite_k0)
381 10274 : NULLIFY (constraint_info%vsite_exclude_qm, constraint_info%vsite_exclude_mm)
382 :
383 10274 : END SUBROUTINE init_constraint
384 :
385 : ! **************************************************************************************************
386 : !> \brief 1. Just DEALLOCATE all the stuff
387 : !> \param topology ...
388 : !> \par History
389 : !> none
390 : ! **************************************************************************************************
391 10274 : SUBROUTINE deallocate_topology(topology)
392 : TYPE(topology_parameters_type), INTENT(INOUT) :: topology
393 :
394 : !-----------------------------------------------------------------------------
395 : ! 1. DEALLOCATE things in topology%atom_info
396 : !-----------------------------------------------------------------------------
397 :
398 10274 : IF (ASSOCIATED(topology%atom_info%id_molname)) THEN
399 10274 : DEALLOCATE (topology%atom_info%id_molname)
400 : END IF
401 10274 : IF (ASSOCIATED(topology%atom_info%id_resname)) THEN
402 10274 : DEALLOCATE (topology%atom_info%id_resname)
403 : END IF
404 10274 : IF (ASSOCIATED(topology%atom_info%resid)) THEN
405 9736 : DEALLOCATE (topology%atom_info%resid)
406 : END IF
407 10274 : IF (ASSOCIATED(topology%atom_info%id_atmname)) THEN
408 10274 : DEALLOCATE (topology%atom_info%id_atmname)
409 : END IF
410 10274 : IF (ASSOCIATED(topology%atom_info%id_atom_names)) THEN
411 10274 : DEALLOCATE (topology%atom_info%id_atom_names)
412 : END IF
413 10274 : IF (ASSOCIATED(topology%atom_info%r)) THEN
414 10274 : DEALLOCATE (topology%atom_info%r)
415 : END IF
416 10274 : IF (ASSOCIATED(topology%atom_info%map_mol_typ)) THEN
417 10274 : DEALLOCATE (topology%atom_info%map_mol_typ)
418 : END IF
419 10274 : IF (ASSOCIATED(topology%atom_info%map_mol_num)) THEN
420 10274 : DEALLOCATE (topology%atom_info%map_mol_num)
421 : END IF
422 10274 : IF (ASSOCIATED(topology%atom_info%map_mol_res)) THEN
423 10274 : DEALLOCATE (topology%atom_info%map_mol_res)
424 : END IF
425 10274 : IF (ASSOCIATED(topology%atom_info%atm_charge)) THEN
426 10274 : DEALLOCATE (topology%atom_info%atm_charge)
427 : END IF
428 10274 : IF (ASSOCIATED(topology%atom_info%atm_mass)) THEN
429 10274 : DEALLOCATE (topology%atom_info%atm_mass)
430 : END IF
431 10274 : IF (ASSOCIATED(topology%atom_info%occup)) THEN
432 2069 : DEALLOCATE (topology%atom_info%occup)
433 : END IF
434 10274 : IF (ASSOCIATED(topology%atom_info%beta)) THEN
435 2069 : DEALLOCATE (topology%atom_info%beta)
436 : END IF
437 10274 : IF (ASSOCIATED(topology%atom_info%id_element)) THEN
438 10274 : DEALLOCATE (topology%atom_info%id_element)
439 : END IF
440 : !-----------------------------------------------------------------------------
441 : ! 2. DEALLOCATE things in topology%conn_info
442 : !-----------------------------------------------------------------------------
443 10274 : IF (ASSOCIATED(topology%conn_info%bond_a)) THEN
444 10274 : DEALLOCATE (topology%conn_info%bond_a)
445 : END IF
446 10274 : IF (ASSOCIATED(topology%conn_info%bond_b)) THEN
447 10274 : DEALLOCATE (topology%conn_info%bond_b)
448 : END IF
449 10274 : IF (ASSOCIATED(topology%conn_info%bond_type)) THEN
450 14 : DEALLOCATE (topology%conn_info%bond_type)
451 : END IF
452 10274 : IF (ASSOCIATED(topology%conn_info%ub_a)) THEN
453 10260 : DEALLOCATE (topology%conn_info%ub_a)
454 : END IF
455 10274 : IF (ASSOCIATED(topology%conn_info%ub_b)) THEN
456 10260 : DEALLOCATE (topology%conn_info%ub_b)
457 : END IF
458 10274 : IF (ASSOCIATED(topology%conn_info%ub_c)) THEN
459 10260 : DEALLOCATE (topology%conn_info%ub_c)
460 : END IF
461 10274 : IF (ASSOCIATED(topology%conn_info%theta_a)) THEN
462 10274 : DEALLOCATE (topology%conn_info%theta_a)
463 : END IF
464 10274 : IF (ASSOCIATED(topology%conn_info%theta_b)) THEN
465 10274 : DEALLOCATE (topology%conn_info%theta_b)
466 : END IF
467 10274 : IF (ASSOCIATED(topology%conn_info%theta_c)) THEN
468 10274 : DEALLOCATE (topology%conn_info%theta_c)
469 : END IF
470 10274 : IF (ASSOCIATED(topology%conn_info%theta_type)) THEN
471 14 : DEALLOCATE (topology%conn_info%theta_type)
472 : END IF
473 10274 : IF (ASSOCIATED(topology%conn_info%phi_a)) THEN
474 10274 : DEALLOCATE (topology%conn_info%phi_a)
475 : END IF
476 10274 : IF (ASSOCIATED(topology%conn_info%phi_b)) THEN
477 10274 : DEALLOCATE (topology%conn_info%phi_b)
478 : END IF
479 10274 : IF (ASSOCIATED(topology%conn_info%phi_c)) THEN
480 10274 : DEALLOCATE (topology%conn_info%phi_c)
481 : END IF
482 10274 : IF (ASSOCIATED(topology%conn_info%phi_d)) THEN
483 10274 : DEALLOCATE (topology%conn_info%phi_d)
484 : END IF
485 10274 : IF (ASSOCIATED(topology%conn_info%phi_type)) THEN
486 14 : DEALLOCATE (topology%conn_info%phi_type)
487 : END IF
488 10274 : IF (ASSOCIATED(topology%conn_info%impr_a)) THEN
489 10274 : DEALLOCATE (topology%conn_info%impr_a)
490 : END IF
491 10274 : IF (ASSOCIATED(topology%conn_info%impr_b)) THEN
492 10274 : DEALLOCATE (topology%conn_info%impr_b)
493 : END IF
494 10274 : IF (ASSOCIATED(topology%conn_info%impr_c)) THEN
495 10274 : DEALLOCATE (topology%conn_info%impr_c)
496 : END IF
497 10274 : IF (ASSOCIATED(topology%conn_info%impr_d)) THEN
498 10274 : DEALLOCATE (topology%conn_info%impr_d)
499 : END IF
500 10274 : IF (ASSOCIATED(topology%conn_info%impr_type)) THEN
501 14 : DEALLOCATE (topology%conn_info%impr_type)
502 : END IF
503 10274 : IF (ASSOCIATED(topology%conn_info%onfo_a)) THEN
504 10268 : DEALLOCATE (topology%conn_info%onfo_a)
505 : END IF
506 10274 : IF (ASSOCIATED(topology%conn_info%onfo_b)) THEN
507 10268 : DEALLOCATE (topology%conn_info%onfo_b)
508 : END IF
509 10274 : IF (ASSOCIATED(topology%conn_info%c_bond_a)) THEN
510 7947 : DEALLOCATE (topology%conn_info%c_bond_a)
511 : END IF
512 10274 : IF (ASSOCIATED(topology%conn_info%c_bond_b)) THEN
513 7947 : DEALLOCATE (topology%conn_info%c_bond_b)
514 : END IF
515 10274 : IF (ASSOCIATED(topology%conn_info%c_bond_type)) THEN
516 0 : DEALLOCATE (topology%conn_info%c_bond_type)
517 : END IF
518 : !-----------------------------------------------------------------------------
519 : ! 3. DEALLOCATE things in topology%cons_info
520 : !-----------------------------------------------------------------------------
521 10274 : IF (ASSOCIATED(topology%cons_info)) &
522 10274 : CALL deallocate_constraint(topology%cons_info)
523 : !-----------------------------------------------------------------------------
524 : ! 4. DEALLOCATE things in topology
525 : !-----------------------------------------------------------------------------
526 10274 : CALL cell_release(topology%cell)
527 10274 : CALL cell_release(topology%cell_ref)
528 10274 : CALL cell_release(topology%cell_muc)
529 10274 : IF (ASSOCIATED(topology%atom_info)) THEN
530 10274 : DEALLOCATE (topology%atom_info)
531 : END IF
532 10274 : IF (ASSOCIATED(topology%conn_info)) THEN
533 10274 : DEALLOCATE (topology%conn_info)
534 : END IF
535 10274 : IF (ASSOCIATED(topology%cons_info)) THEN
536 10274 : DEALLOCATE (topology%cons_info)
537 : END IF
538 :
539 10274 : END SUBROUTINE deallocate_topology
540 :
541 : ! **************************************************************************************************
542 : !> \brief 1. Just DEALLOCATE all the stuff
543 : !> \param constraint_info ...
544 : !> \par History
545 : !> none
546 : ! **************************************************************************************************
547 10274 : SUBROUTINE deallocate_constraint(constraint_info)
548 : TYPE(constraint_info_type), POINTER :: constraint_info
549 :
550 : INTEGER :: i
551 :
552 : ! Fixed Atoms
553 :
554 10274 : IF (ASSOCIATED(constraint_info%fixed_atoms)) THEN
555 110 : DEALLOCATE (constraint_info%fixed_atoms)
556 : END IF
557 10274 : IF (ASSOCIATED(constraint_info%fixed_type)) THEN
558 110 : DEALLOCATE (constraint_info%fixed_type)
559 : END IF
560 10274 : IF (ASSOCIATED(constraint_info%fixed_molnames)) THEN
561 110 : DEALLOCATE (constraint_info%fixed_molnames)
562 : END IF
563 10274 : IF (ASSOCIATED(constraint_info%fixed_mol_type)) THEN
564 110 : DEALLOCATE (constraint_info%fixed_mol_type)
565 : END IF
566 10274 : IF (ASSOCIATED(constraint_info%fixed_restraint)) THEN
567 110 : DEALLOCATE (constraint_info%fixed_restraint)
568 : END IF
569 10274 : IF (ASSOCIATED(constraint_info%fixed_k0)) THEN
570 110 : DEALLOCATE (constraint_info%fixed_k0)
571 : END IF
572 10274 : IF (ASSOCIATED(constraint_info%fixed_mol_restraint)) THEN
573 110 : DEALLOCATE (constraint_info%fixed_mol_restraint)
574 : END IF
575 10274 : IF (ASSOCIATED(constraint_info%fixed_mol_k0)) THEN
576 110 : DEALLOCATE (constraint_info%fixed_mol_k0)
577 : END IF
578 10274 : IF (ASSOCIATED(constraint_info%fixed_exclude_qm)) THEN
579 110 : DEALLOCATE (constraint_info%fixed_exclude_qm)
580 : END IF
581 10274 : IF (ASSOCIATED(constraint_info%fixed_exclude_mm)) THEN
582 110 : DEALLOCATE (constraint_info%fixed_exclude_mm)
583 : END IF
584 : ! Collective Constraint
585 10274 : IF (ASSOCIATED(constraint_info%colvar_set)) THEN
586 586 : DO i = 1, SIZE(constraint_info%colvar_set)
587 586 : IF (ASSOCIATED(constraint_info%colvar_set(i)%colvar)) THEN
588 450 : CALL colvar_release(constraint_info%colvar_set(i)%colvar)
589 450 : NULLIFY (constraint_info%colvar_set(i)%colvar)
590 : END IF
591 : END DO
592 136 : DEALLOCATE (constraint_info%colvar_set)
593 : END IF
594 10274 : IF (ASSOCIATED(constraint_info%const_colv_mol)) THEN
595 136 : DEALLOCATE (constraint_info%const_colv_mol)
596 : END IF
597 10274 : IF (ASSOCIATED(constraint_info%const_colv_molname)) THEN
598 136 : DEALLOCATE (constraint_info%const_colv_molname)
599 : END IF
600 10274 : IF (ASSOCIATED(constraint_info%const_colv_target)) THEN
601 136 : DEALLOCATE (constraint_info%const_colv_target)
602 : END IF
603 10274 : IF (ASSOCIATED(constraint_info%const_colv_target_growth)) THEN
604 136 : DEALLOCATE (constraint_info%const_colv_target_growth)
605 : END IF
606 10274 : IF (ASSOCIATED(constraint_info%colv_intermolecular)) THEN
607 136 : DEALLOCATE (constraint_info%colv_intermolecular)
608 : END IF
609 10274 : IF (ASSOCIATED(constraint_info%colv_restraint)) THEN
610 136 : DEALLOCATE (constraint_info%colv_restraint)
611 : END IF
612 10274 : IF (ASSOCIATED(constraint_info%colv_k0)) THEN
613 136 : DEALLOCATE (constraint_info%colv_k0)
614 : END IF
615 10274 : IF (ASSOCIATED(constraint_info%colv_exclude_qm)) THEN
616 136 : DEALLOCATE (constraint_info%colv_exclude_qm)
617 : END IF
618 10274 : IF (ASSOCIATED(constraint_info%colv_exclude_mm)) THEN
619 136 : DEALLOCATE (constraint_info%colv_exclude_mm)
620 : END IF
621 : ! G3x3
622 10274 : IF (ASSOCIATED(constraint_info%const_g33_mol)) THEN
623 156 : DEALLOCATE (constraint_info%const_g33_mol)
624 : END IF
625 10274 : IF (ASSOCIATED(constraint_info%const_g33_molname)) THEN
626 156 : DEALLOCATE (constraint_info%const_g33_molname)
627 : END IF
628 10274 : IF (ASSOCIATED(constraint_info%const_g33_a)) THEN
629 156 : DEALLOCATE (constraint_info%const_g33_a)
630 : END IF
631 10274 : IF (ASSOCIATED(constraint_info%const_g33_b)) THEN
632 156 : DEALLOCATE (constraint_info%const_g33_b)
633 : END IF
634 10274 : IF (ASSOCIATED(constraint_info%const_g33_c)) THEN
635 156 : DEALLOCATE (constraint_info%const_g33_c)
636 : END IF
637 10274 : IF (ASSOCIATED(constraint_info%const_g33_dab)) THEN
638 156 : DEALLOCATE (constraint_info%const_g33_dab)
639 : END IF
640 10274 : IF (ASSOCIATED(constraint_info%const_g33_dac)) THEN
641 156 : DEALLOCATE (constraint_info%const_g33_dac)
642 : END IF
643 10274 : IF (ASSOCIATED(constraint_info%const_g33_dbc)) THEN
644 156 : DEALLOCATE (constraint_info%const_g33_dbc)
645 : END IF
646 10274 : IF (ASSOCIATED(constraint_info%g33_intermolecular)) THEN
647 156 : DEALLOCATE (constraint_info%g33_intermolecular)
648 : END IF
649 10274 : IF (ASSOCIATED(constraint_info%g33_restraint)) THEN
650 156 : DEALLOCATE (constraint_info%g33_restraint)
651 : END IF
652 10274 : IF (ASSOCIATED(constraint_info%g33_k0)) THEN
653 156 : DEALLOCATE (constraint_info%g33_k0)
654 : END IF
655 10274 : IF (ASSOCIATED(constraint_info%g33_exclude_qm)) THEN
656 156 : DEALLOCATE (constraint_info%g33_exclude_qm)
657 : END IF
658 10274 : IF (ASSOCIATED(constraint_info%g33_exclude_mm)) THEN
659 156 : DEALLOCATE (constraint_info%g33_exclude_mm)
660 : END IF
661 : ! G4x6
662 10274 : IF (ASSOCIATED(constraint_info%const_g46_mol)) THEN
663 16 : DEALLOCATE (constraint_info%const_g46_mol)
664 : END IF
665 10274 : IF (ASSOCIATED(constraint_info%const_g46_molname)) THEN
666 16 : DEALLOCATE (constraint_info%const_g46_molname)
667 : END IF
668 10274 : IF (ASSOCIATED(constraint_info%const_g46_a)) THEN
669 16 : DEALLOCATE (constraint_info%const_g46_a)
670 : END IF
671 10274 : IF (ASSOCIATED(constraint_info%const_g46_b)) THEN
672 16 : DEALLOCATE (constraint_info%const_g46_b)
673 : END IF
674 10274 : IF (ASSOCIATED(constraint_info%const_g46_c)) THEN
675 16 : DEALLOCATE (constraint_info%const_g46_c)
676 : END IF
677 10274 : IF (ASSOCIATED(constraint_info%const_g46_d)) THEN
678 16 : DEALLOCATE (constraint_info%const_g46_d)
679 : END IF
680 10274 : IF (ASSOCIATED(constraint_info%const_g46_dab)) THEN
681 16 : DEALLOCATE (constraint_info%const_g46_dab)
682 : END IF
683 10274 : IF (ASSOCIATED(constraint_info%const_g46_dac)) THEN
684 16 : DEALLOCATE (constraint_info%const_g46_dac)
685 : END IF
686 10274 : IF (ASSOCIATED(constraint_info%const_g46_dbc)) THEN
687 16 : DEALLOCATE (constraint_info%const_g46_dbc)
688 : END IF
689 10274 : IF (ASSOCIATED(constraint_info%const_g46_dad)) THEN
690 16 : DEALLOCATE (constraint_info%const_g46_dad)
691 : END IF
692 10274 : IF (ASSOCIATED(constraint_info%const_g46_dbd)) THEN
693 16 : DEALLOCATE (constraint_info%const_g46_dbd)
694 : END IF
695 10274 : IF (ASSOCIATED(constraint_info%const_g46_dcd)) THEN
696 16 : DEALLOCATE (constraint_info%const_g46_dcd)
697 : END IF
698 10274 : IF (ASSOCIATED(constraint_info%g46_intermolecular)) THEN
699 16 : DEALLOCATE (constraint_info%g46_intermolecular)
700 : END IF
701 10274 : IF (ASSOCIATED(constraint_info%g46_restraint)) THEN
702 16 : DEALLOCATE (constraint_info%g46_restraint)
703 : END IF
704 10274 : IF (ASSOCIATED(constraint_info%g46_k0)) THEN
705 16 : DEALLOCATE (constraint_info%g46_k0)
706 : END IF
707 10274 : IF (ASSOCIATED(constraint_info%g46_exclude_qm)) THEN
708 16 : DEALLOCATE (constraint_info%g46_exclude_qm)
709 : END IF
710 10274 : IF (ASSOCIATED(constraint_info%g46_exclude_mm)) THEN
711 16 : DEALLOCATE (constraint_info%g46_exclude_mm)
712 : END IF
713 : ! virtual_site
714 10274 : IF (ASSOCIATED(constraint_info%const_vsite_mol)) THEN
715 8 : DEALLOCATE (constraint_info%const_vsite_mol)
716 : END IF
717 10274 : IF (ASSOCIATED(constraint_info%const_vsite_molname)) THEN
718 8 : DEALLOCATE (constraint_info%const_vsite_molname)
719 : END IF
720 10274 : IF (ASSOCIATED(constraint_info%const_vsite_a)) THEN
721 8 : DEALLOCATE (constraint_info%const_vsite_a)
722 : END IF
723 10274 : IF (ASSOCIATED(constraint_info%const_vsite_b)) THEN
724 8 : DEALLOCATE (constraint_info%const_vsite_b)
725 : END IF
726 10274 : IF (ASSOCIATED(constraint_info%const_vsite_c)) THEN
727 8 : DEALLOCATE (constraint_info%const_vsite_c)
728 : END IF
729 10274 : IF (ASSOCIATED(constraint_info%const_vsite_d)) THEN
730 8 : DEALLOCATE (constraint_info%const_vsite_d)
731 : END IF
732 10274 : IF (ASSOCIATED(constraint_info%const_vsite_wbc)) THEN
733 8 : DEALLOCATE (constraint_info%const_vsite_wbc)
734 : END IF
735 10274 : IF (ASSOCIATED(constraint_info%const_vsite_wdc)) THEN
736 8 : DEALLOCATE (constraint_info%const_vsite_wdc)
737 : END IF
738 10274 : IF (ASSOCIATED(constraint_info%vsite_intermolecular)) THEN
739 8 : DEALLOCATE (constraint_info%vsite_intermolecular)
740 : END IF
741 10274 : IF (ASSOCIATED(constraint_info%vsite_restraint)) THEN
742 8 : DEALLOCATE (constraint_info%vsite_restraint)
743 : END IF
744 10274 : IF (ASSOCIATED(constraint_info%vsite_k0)) THEN
745 8 : DEALLOCATE (constraint_info%vsite_k0)
746 : END IF
747 10274 : IF (ASSOCIATED(constraint_info%vsite_exclude_qm)) THEN
748 8 : DEALLOCATE (constraint_info%vsite_exclude_qm)
749 : END IF
750 10274 : IF (ASSOCIATED(constraint_info%vsite_exclude_mm)) THEN
751 8 : DEALLOCATE (constraint_info%vsite_exclude_mm)
752 : END IF
753 10274 : END SUBROUTINE deallocate_constraint
754 :
755 : ! **************************************************************************************************
756 : !> \brief Deallocate possibly allocated arrays before reading topology
757 : !> \param topology ...
758 : !> \par History
759 : !> none
760 : ! **************************************************************************************************
761 797 : SUBROUTINE pre_read_topology(topology)
762 : TYPE(topology_parameters_type), INTENT(INOUT) :: topology
763 :
764 : TYPE(atom_info_type), POINTER :: atom_info
765 :
766 797 : atom_info => topology%atom_info
767 :
768 797 : IF (ASSOCIATED(atom_info%id_molname)) THEN
769 797 : DEALLOCATE (atom_info%id_molname)
770 : END IF
771 :
772 797 : IF (ASSOCIATED(atom_info%resid)) THEN
773 797 : DEALLOCATE (atom_info%resid)
774 : END IF
775 :
776 797 : IF (ASSOCIATED(atom_info%id_resname)) THEN
777 797 : DEALLOCATE (atom_info%id_resname)
778 : END IF
779 :
780 797 : IF (ASSOCIATED(atom_info%id_atmname)) THEN
781 797 : DEALLOCATE (atom_info%id_atmname)
782 : END IF
783 :
784 797 : IF (ASSOCIATED(atom_info%atm_charge)) THEN
785 797 : DEALLOCATE (atom_info%atm_charge)
786 : END IF
787 :
788 797 : IF (ASSOCIATED(atom_info%atm_mass)) THEN
789 797 : DEALLOCATE (atom_info%atm_mass)
790 : END IF
791 :
792 797 : END SUBROUTINE pre_read_topology
793 :
794 0 : END MODULE topology_types
|