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 : ! **************************************************************************************************
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 : INTEGER, DIMENSION(:), POINTER :: id_resname => NULL()
38 : INTEGER, DIMENSION(:), POINTER :: id_atmname => NULL()
39 : INTEGER, DIMENSION(:), POINTER :: id_atom_names => NULL()
40 : INTEGER, DIMENSION(:), POINTER :: 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
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 9512 : 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 9512 : ALLOCATE (topology%atom_info)
213 9512 : ALLOCATE (topology%conn_info)
214 9512 : ALLOCATE (topology%cons_info)
215 : !-----------------------------------------------------------------------------
216 : ! 2. Initialize and Nullify things in topology
217 : !-----------------------------------------------------------------------------
218 9512 : NULLIFY (topology%cell, topology%cell_ref, topology%cell_muc)
219 9512 : topology%natoms = 0
220 9512 : topology%natom_type = 0
221 9512 : topology%nmol = 0
222 9512 : topology%nmol_type = 0
223 9512 : topology%nmol_conn = 0
224 9512 : topology%bondparm_type = do_bondparm_covalent
225 9512 : topology%reorder_atom = .FALSE.
226 9512 : topology%create_molecules = .FALSE.
227 9512 : topology%molecules_check = .FALSE.
228 9512 : topology%coordinate = .FALSE.
229 9512 : topology%use_g96_velocity = .FALSE.
230 9512 : topology%coord_type = -1
231 9512 : topology%coord_file_name = ''
232 9512 : topology%conn_type = do_conn_generate
233 9512 : topology%conn_file_name = 'OFF'
234 9512 : topology%const_atom = .FALSE.
235 9512 : topology%const_hydr = .FALSE.
236 9512 : topology%const_colv = .FALSE.
237 9512 : topology%const_33 = .FALSE.
238 9512 : topology%const_46 = .FALSE.
239 9512 : topology%const_vsite = .FALSE.
240 9512 : topology%charge_occup = .FALSE.
241 9512 : topology%charge_beta = .FALSE.
242 9512 : topology%charge_extended = .FALSE.
243 9512 : topology%para_res = .FALSE.
244 9512 : topology%molname_generated = .FALSE.
245 9512 : topology%aa_element = .FALSE.
246 9512 : topology%exclude_vdw = do_skip_13
247 9512 : topology%exclude_ei = do_skip_13
248 : !-----------------------------------------------------------------------------
249 : ! 3. Initialize and Nullify things in topology%atom_info
250 : !-----------------------------------------------------------------------------
251 : NULLIFY (topology%atom_info%id_molname)
252 : NULLIFY (topology%atom_info%id_resname)
253 : NULLIFY (topology%atom_info%resid)
254 : NULLIFY (topology%atom_info%id_atmname)
255 : NULLIFY (topology%atom_info%id_atom_names)
256 : NULLIFY (topology%atom_info%r)
257 : NULLIFY (topology%atom_info%map_mol_typ)
258 : NULLIFY (topology%atom_info%map_mol_num)
259 : NULLIFY (topology%atom_info%map_mol_res)
260 : NULLIFY (topology%atom_info%atm_charge)
261 : NULLIFY (topology%atom_info%atm_mass)
262 : NULLIFY (topology%atom_info%occup)
263 : NULLIFY (topology%atom_info%beta)
264 : NULLIFY (topology%atom_info%id_element)
265 : !-----------------------------------------------------------------------------
266 : ! 4. Initialize and Nullify things in topology%conn_info
267 : !-----------------------------------------------------------------------------
268 : NULLIFY (topology%conn_info%bond_a)
269 : NULLIFY (topology%conn_info%bond_b)
270 : NULLIFY (topology%conn_info%bond_type)
271 : NULLIFY (topology%conn_info%ub_a)
272 : NULLIFY (topology%conn_info%ub_b)
273 : NULLIFY (topology%conn_info%ub_c)
274 : NULLIFY (topology%conn_info%theta_a)
275 : NULLIFY (topology%conn_info%theta_b)
276 : NULLIFY (topology%conn_info%theta_c)
277 : NULLIFY (topology%conn_info%theta_type)
278 : NULLIFY (topology%conn_info%phi_a)
279 : NULLIFY (topology%conn_info%phi_b)
280 : NULLIFY (topology%conn_info%phi_c)
281 : NULLIFY (topology%conn_info%phi_d)
282 : NULLIFY (topology%conn_info%phi_type)
283 : NULLIFY (topology%conn_info%impr_a)
284 : NULLIFY (topology%conn_info%impr_b)
285 : NULLIFY (topology%conn_info%impr_c)
286 : NULLIFY (topology%conn_info%impr_d)
287 : NULLIFY (topology%conn_info%impr_type)
288 : NULLIFY (topology%conn_info%onfo_a)
289 : NULLIFY (topology%conn_info%onfo_b)
290 : NULLIFY (topology%conn_info%c_bond_a)
291 : NULLIFY (topology%conn_info%c_bond_b)
292 : NULLIFY (topology%conn_info%c_bond_type)
293 : !-----------------------------------------------------------------------------
294 : ! 5. Initialize and Nullify things in topology%cons_info
295 : !-----------------------------------------------------------------------------
296 9512 : CALL init_constraint(topology%cons_info)
297 9512 : END SUBROUTINE init_topology
298 :
299 : ! **************************************************************************************************
300 : !> \brief 1. Just NULLIFY and zero all the stuff
301 : !> \param constraint_info ...
302 : !> \par History
303 : !> none
304 : ! **************************************************************************************************
305 9512 : SUBROUTINE init_constraint(constraint_info)
306 : TYPE(constraint_info_type), POINTER :: constraint_info
307 :
308 : ! Bonds involving Hydrogens
309 :
310 9512 : constraint_info%hbonds_restraint = .FALSE.
311 : ! Fixed Atoms
312 9512 : constraint_info%nfixed_atoms = 0
313 9512 : constraint_info%freeze_mm = do_constr_none
314 9512 : constraint_info%freeze_qm = do_constr_none
315 9512 : NULLIFY (constraint_info%fixed_atoms)
316 9512 : NULLIFY (constraint_info%fixed_type)
317 9512 : NULLIFY (constraint_info%fixed_mol_type)
318 9512 : NULLIFY (constraint_info%fixed_molnames)
319 9512 : NULLIFY (constraint_info%fixed_restraint)
320 9512 : NULLIFY (constraint_info%fixed_k0)
321 9512 : NULLIFY (constraint_info%fixed_mol_restraint)
322 9512 : NULLIFY (constraint_info%fixed_mol_k0)
323 9512 : NULLIFY (constraint_info%fixed_exclude_qm, constraint_info%fixed_exclude_mm)
324 : ! Collective Constraints
325 9512 : constraint_info%nconst_colv = 0
326 9512 : NULLIFY (constraint_info%colvar_set)
327 9512 : NULLIFY (constraint_info%const_colv_mol)
328 9512 : NULLIFY (constraint_info%const_colv_molname)
329 9512 : NULLIFY (constraint_info%const_colv_target)
330 9512 : NULLIFY (constraint_info%const_colv_target_growth)
331 9512 : NULLIFY (constraint_info%colv_intermolecular)
332 9512 : NULLIFY (constraint_info%colv_restraint)
333 9512 : NULLIFY (constraint_info%colv_k0)
334 9512 : NULLIFY (constraint_info%colv_exclude_qm, constraint_info%colv_exclude_mm)
335 : ! G3x3
336 9512 : constraint_info%nconst_g33 = 0
337 9512 : NULLIFY (constraint_info%const_g33_mol)
338 9512 : NULLIFY (constraint_info%const_g33_molname)
339 9512 : NULLIFY (constraint_info%const_g33_a)
340 9512 : NULLIFY (constraint_info%const_g33_b)
341 9512 : NULLIFY (constraint_info%const_g33_c)
342 9512 : NULLIFY (constraint_info%const_g33_dab)
343 9512 : NULLIFY (constraint_info%const_g33_dac)
344 9512 : NULLIFY (constraint_info%const_g33_dbc)
345 9512 : NULLIFY (constraint_info%g33_intermolecular)
346 9512 : NULLIFY (constraint_info%g33_restraint)
347 9512 : NULLIFY (constraint_info%g33_k0)
348 9512 : NULLIFY (constraint_info%g33_exclude_qm, constraint_info%g33_exclude_mm)
349 : ! G4x6
350 9512 : constraint_info%nconst_g46 = 0
351 9512 : NULLIFY (constraint_info%const_g46_mol)
352 9512 : NULLIFY (constraint_info%const_g46_molname)
353 9512 : NULLIFY (constraint_info%const_g46_a)
354 9512 : NULLIFY (constraint_info%const_g46_b)
355 9512 : NULLIFY (constraint_info%const_g46_c)
356 9512 : NULLIFY (constraint_info%const_g46_d)
357 9512 : NULLIFY (constraint_info%const_g46_dab)
358 9512 : NULLIFY (constraint_info%const_g46_dac)
359 9512 : NULLIFY (constraint_info%const_g46_dbc)
360 9512 : NULLIFY (constraint_info%const_g46_dad)
361 9512 : NULLIFY (constraint_info%const_g46_dbd)
362 9512 : NULLIFY (constraint_info%const_g46_dcd)
363 9512 : NULLIFY (constraint_info%g46_intermolecular)
364 9512 : NULLIFY (constraint_info%g46_restraint)
365 9512 : NULLIFY (constraint_info%g46_k0)
366 9512 : NULLIFY (constraint_info%g46_exclude_qm, constraint_info%g46_exclude_mm)
367 : ! virtual_site
368 9512 : constraint_info%nconst_vsite = 0
369 9512 : NULLIFY (constraint_info%const_vsite_mol)
370 9512 : NULLIFY (constraint_info%const_vsite_molname)
371 9512 : NULLIFY (constraint_info%const_vsite_a)
372 9512 : NULLIFY (constraint_info%const_vsite_b)
373 9512 : NULLIFY (constraint_info%const_vsite_c)
374 9512 : NULLIFY (constraint_info%const_vsite_d)
375 9512 : NULLIFY (constraint_info%const_vsite_wbc)
376 9512 : NULLIFY (constraint_info%const_vsite_wdc)
377 9512 : NULLIFY (constraint_info%vsite_intermolecular)
378 9512 : NULLIFY (constraint_info%vsite_restraint)
379 9512 : NULLIFY (constraint_info%vsite_k0)
380 9512 : NULLIFY (constraint_info%vsite_exclude_qm, constraint_info%vsite_exclude_mm)
381 :
382 9512 : END SUBROUTINE init_constraint
383 :
384 : ! **************************************************************************************************
385 : !> \brief 1. Just DEALLOCATE all the stuff
386 : !> \param topology ...
387 : !> \par History
388 : !> none
389 : ! **************************************************************************************************
390 9512 : SUBROUTINE deallocate_topology(topology)
391 : TYPE(topology_parameters_type), INTENT(INOUT) :: topology
392 :
393 : !-----------------------------------------------------------------------------
394 : ! 1. DEALLOCATE things in topology%atom_info
395 : !-----------------------------------------------------------------------------
396 :
397 9512 : IF (ASSOCIATED(topology%atom_info%id_molname)) THEN
398 9512 : DEALLOCATE (topology%atom_info%id_molname)
399 : END IF
400 9512 : IF (ASSOCIATED(topology%atom_info%id_resname)) THEN
401 9512 : DEALLOCATE (topology%atom_info%id_resname)
402 : END IF
403 9512 : IF (ASSOCIATED(topology%atom_info%resid)) THEN
404 8984 : DEALLOCATE (topology%atom_info%resid)
405 : END IF
406 9512 : IF (ASSOCIATED(topology%atom_info%id_atmname)) THEN
407 9512 : DEALLOCATE (topology%atom_info%id_atmname)
408 : END IF
409 9512 : IF (ASSOCIATED(topology%atom_info%id_atom_names)) THEN
410 9512 : DEALLOCATE (topology%atom_info%id_atom_names)
411 : END IF
412 9512 : IF (ASSOCIATED(topology%atom_info%r)) THEN
413 9512 : DEALLOCATE (topology%atom_info%r)
414 : END IF
415 9512 : IF (ASSOCIATED(topology%atom_info%map_mol_typ)) THEN
416 9512 : DEALLOCATE (topology%atom_info%map_mol_typ)
417 : END IF
418 9512 : IF (ASSOCIATED(topology%atom_info%map_mol_num)) THEN
419 9512 : DEALLOCATE (topology%atom_info%map_mol_num)
420 : END IF
421 9512 : IF (ASSOCIATED(topology%atom_info%map_mol_res)) THEN
422 9512 : DEALLOCATE (topology%atom_info%map_mol_res)
423 : END IF
424 9512 : IF (ASSOCIATED(topology%atom_info%atm_charge)) THEN
425 9512 : DEALLOCATE (topology%atom_info%atm_charge)
426 : END IF
427 9512 : IF (ASSOCIATED(topology%atom_info%atm_mass)) THEN
428 9512 : DEALLOCATE (topology%atom_info%atm_mass)
429 : END IF
430 9512 : IF (ASSOCIATED(topology%atom_info%occup)) THEN
431 2067 : DEALLOCATE (topology%atom_info%occup)
432 : END IF
433 9512 : IF (ASSOCIATED(topology%atom_info%beta)) THEN
434 2067 : DEALLOCATE (topology%atom_info%beta)
435 : END IF
436 9512 : IF (ASSOCIATED(topology%atom_info%id_element)) THEN
437 9512 : DEALLOCATE (topology%atom_info%id_element)
438 : END IF
439 : !-----------------------------------------------------------------------------
440 : ! 2. DEALLOCATE things in topology%conn_info
441 : !-----------------------------------------------------------------------------
442 9512 : IF (ASSOCIATED(topology%conn_info%bond_a)) THEN
443 9512 : DEALLOCATE (topology%conn_info%bond_a)
444 : END IF
445 9512 : IF (ASSOCIATED(topology%conn_info%bond_b)) THEN
446 9512 : DEALLOCATE (topology%conn_info%bond_b)
447 : END IF
448 9512 : IF (ASSOCIATED(topology%conn_info%bond_type)) THEN
449 14 : DEALLOCATE (topology%conn_info%bond_type)
450 : END IF
451 9512 : IF (ASSOCIATED(topology%conn_info%ub_a)) THEN
452 9498 : DEALLOCATE (topology%conn_info%ub_a)
453 : END IF
454 9512 : IF (ASSOCIATED(topology%conn_info%ub_b)) THEN
455 9498 : DEALLOCATE (topology%conn_info%ub_b)
456 : END IF
457 9512 : IF (ASSOCIATED(topology%conn_info%ub_c)) THEN
458 9498 : DEALLOCATE (topology%conn_info%ub_c)
459 : END IF
460 9512 : IF (ASSOCIATED(topology%conn_info%theta_a)) THEN
461 9512 : DEALLOCATE (topology%conn_info%theta_a)
462 : END IF
463 9512 : IF (ASSOCIATED(topology%conn_info%theta_b)) THEN
464 9512 : DEALLOCATE (topology%conn_info%theta_b)
465 : END IF
466 9512 : IF (ASSOCIATED(topology%conn_info%theta_c)) THEN
467 9512 : DEALLOCATE (topology%conn_info%theta_c)
468 : END IF
469 9512 : IF (ASSOCIATED(topology%conn_info%theta_type)) THEN
470 14 : DEALLOCATE (topology%conn_info%theta_type)
471 : END IF
472 9512 : IF (ASSOCIATED(topology%conn_info%phi_a)) THEN
473 9512 : DEALLOCATE (topology%conn_info%phi_a)
474 : END IF
475 9512 : IF (ASSOCIATED(topology%conn_info%phi_b)) THEN
476 9512 : DEALLOCATE (topology%conn_info%phi_b)
477 : END IF
478 9512 : IF (ASSOCIATED(topology%conn_info%phi_c)) THEN
479 9512 : DEALLOCATE (topology%conn_info%phi_c)
480 : END IF
481 9512 : IF (ASSOCIATED(topology%conn_info%phi_d)) THEN
482 9512 : DEALLOCATE (topology%conn_info%phi_d)
483 : END IF
484 9512 : IF (ASSOCIATED(topology%conn_info%phi_type)) THEN
485 14 : DEALLOCATE (topology%conn_info%phi_type)
486 : END IF
487 9512 : IF (ASSOCIATED(topology%conn_info%impr_a)) THEN
488 9512 : DEALLOCATE (topology%conn_info%impr_a)
489 : END IF
490 9512 : IF (ASSOCIATED(topology%conn_info%impr_b)) THEN
491 9512 : DEALLOCATE (topology%conn_info%impr_b)
492 : END IF
493 9512 : IF (ASSOCIATED(topology%conn_info%impr_c)) THEN
494 9512 : DEALLOCATE (topology%conn_info%impr_c)
495 : END IF
496 9512 : IF (ASSOCIATED(topology%conn_info%impr_d)) THEN
497 9512 : DEALLOCATE (topology%conn_info%impr_d)
498 : END IF
499 9512 : IF (ASSOCIATED(topology%conn_info%impr_type)) THEN
500 14 : DEALLOCATE (topology%conn_info%impr_type)
501 : END IF
502 9512 : IF (ASSOCIATED(topology%conn_info%onfo_a)) THEN
503 9506 : DEALLOCATE (topology%conn_info%onfo_a)
504 : END IF
505 9512 : IF (ASSOCIATED(topology%conn_info%onfo_b)) THEN
506 9506 : DEALLOCATE (topology%conn_info%onfo_b)
507 : END IF
508 9512 : IF (ASSOCIATED(topology%conn_info%c_bond_a)) THEN
509 7195 : DEALLOCATE (topology%conn_info%c_bond_a)
510 : END IF
511 9512 : IF (ASSOCIATED(topology%conn_info%c_bond_b)) THEN
512 7195 : DEALLOCATE (topology%conn_info%c_bond_b)
513 : END IF
514 9512 : IF (ASSOCIATED(topology%conn_info%c_bond_type)) THEN
515 0 : DEALLOCATE (topology%conn_info%c_bond_type)
516 : END IF
517 : !-----------------------------------------------------------------------------
518 : ! 3. DEALLOCATE things in topology%cons_info
519 : !-----------------------------------------------------------------------------
520 9512 : IF (ASSOCIATED(topology%cons_info)) &
521 9512 : CALL deallocate_constraint(topology%cons_info)
522 : !-----------------------------------------------------------------------------
523 : ! 4. DEALLOCATE things in topology
524 : !-----------------------------------------------------------------------------
525 9512 : CALL cell_release(topology%cell)
526 9512 : CALL cell_release(topology%cell_ref)
527 9512 : CALL cell_release(topology%cell_muc)
528 9512 : IF (ASSOCIATED(topology%atom_info)) THEN
529 9512 : DEALLOCATE (topology%atom_info)
530 : END IF
531 9512 : IF (ASSOCIATED(topology%conn_info)) THEN
532 9512 : DEALLOCATE (topology%conn_info)
533 : END IF
534 9512 : IF (ASSOCIATED(topology%cons_info)) THEN
535 9512 : DEALLOCATE (topology%cons_info)
536 : END IF
537 :
538 9512 : END SUBROUTINE deallocate_topology
539 :
540 : ! **************************************************************************************************
541 : !> \brief 1. Just DEALLOCATE all the stuff
542 : !> \param constraint_info ...
543 : !> \par History
544 : !> none
545 : ! **************************************************************************************************
546 9512 : SUBROUTINE deallocate_constraint(constraint_info)
547 : TYPE(constraint_info_type), POINTER :: constraint_info
548 :
549 : INTEGER :: i
550 :
551 : ! Fixed Atoms
552 :
553 9512 : IF (ASSOCIATED(constraint_info%fixed_atoms)) THEN
554 110 : DEALLOCATE (constraint_info%fixed_atoms)
555 : END IF
556 9512 : IF (ASSOCIATED(constraint_info%fixed_type)) THEN
557 110 : DEALLOCATE (constraint_info%fixed_type)
558 : END IF
559 9512 : IF (ASSOCIATED(constraint_info%fixed_molnames)) THEN
560 110 : DEALLOCATE (constraint_info%fixed_molnames)
561 : END IF
562 9512 : IF (ASSOCIATED(constraint_info%fixed_mol_type)) THEN
563 110 : DEALLOCATE (constraint_info%fixed_mol_type)
564 : END IF
565 9512 : IF (ASSOCIATED(constraint_info%fixed_restraint)) THEN
566 110 : DEALLOCATE (constraint_info%fixed_restraint)
567 : END IF
568 9512 : IF (ASSOCIATED(constraint_info%fixed_k0)) THEN
569 110 : DEALLOCATE (constraint_info%fixed_k0)
570 : END IF
571 9512 : IF (ASSOCIATED(constraint_info%fixed_mol_restraint)) THEN
572 110 : DEALLOCATE (constraint_info%fixed_mol_restraint)
573 : END IF
574 9512 : IF (ASSOCIATED(constraint_info%fixed_mol_k0)) THEN
575 110 : DEALLOCATE (constraint_info%fixed_mol_k0)
576 : END IF
577 9512 : IF (ASSOCIATED(constraint_info%fixed_exclude_qm)) THEN
578 110 : DEALLOCATE (constraint_info%fixed_exclude_qm)
579 : END IF
580 9512 : IF (ASSOCIATED(constraint_info%fixed_exclude_mm)) THEN
581 110 : DEALLOCATE (constraint_info%fixed_exclude_mm)
582 : END IF
583 : ! Collective Constraint
584 9512 : IF (ASSOCIATED(constraint_info%colvar_set)) THEN
585 586 : DO i = 1, SIZE(constraint_info%colvar_set)
586 586 : IF (ASSOCIATED(constraint_info%colvar_set(i)%colvar)) THEN
587 450 : CALL colvar_release(constraint_info%colvar_set(i)%colvar)
588 450 : NULLIFY (constraint_info%colvar_set(i)%colvar)
589 : END IF
590 : END DO
591 136 : DEALLOCATE (constraint_info%colvar_set)
592 : END IF
593 9512 : IF (ASSOCIATED(constraint_info%const_colv_mol)) THEN
594 136 : DEALLOCATE (constraint_info%const_colv_mol)
595 : END IF
596 9512 : IF (ASSOCIATED(constraint_info%const_colv_molname)) THEN
597 136 : DEALLOCATE (constraint_info%const_colv_molname)
598 : END IF
599 9512 : IF (ASSOCIATED(constraint_info%const_colv_target)) THEN
600 136 : DEALLOCATE (constraint_info%const_colv_target)
601 : END IF
602 9512 : IF (ASSOCIATED(constraint_info%const_colv_target_growth)) THEN
603 136 : DEALLOCATE (constraint_info%const_colv_target_growth)
604 : END IF
605 9512 : IF (ASSOCIATED(constraint_info%colv_intermolecular)) THEN
606 136 : DEALLOCATE (constraint_info%colv_intermolecular)
607 : END IF
608 9512 : IF (ASSOCIATED(constraint_info%colv_restraint)) THEN
609 136 : DEALLOCATE (constraint_info%colv_restraint)
610 : END IF
611 9512 : IF (ASSOCIATED(constraint_info%colv_k0)) THEN
612 136 : DEALLOCATE (constraint_info%colv_k0)
613 : END IF
614 9512 : IF (ASSOCIATED(constraint_info%colv_exclude_qm)) THEN
615 136 : DEALLOCATE (constraint_info%colv_exclude_qm)
616 : END IF
617 9512 : IF (ASSOCIATED(constraint_info%colv_exclude_mm)) THEN
618 136 : DEALLOCATE (constraint_info%colv_exclude_mm)
619 : END IF
620 : ! G3x3
621 9512 : IF (ASSOCIATED(constraint_info%const_g33_mol)) THEN
622 156 : DEALLOCATE (constraint_info%const_g33_mol)
623 : END IF
624 9512 : IF (ASSOCIATED(constraint_info%const_g33_molname)) THEN
625 156 : DEALLOCATE (constraint_info%const_g33_molname)
626 : END IF
627 9512 : IF (ASSOCIATED(constraint_info%const_g33_a)) THEN
628 156 : DEALLOCATE (constraint_info%const_g33_a)
629 : END IF
630 9512 : IF (ASSOCIATED(constraint_info%const_g33_b)) THEN
631 156 : DEALLOCATE (constraint_info%const_g33_b)
632 : END IF
633 9512 : IF (ASSOCIATED(constraint_info%const_g33_c)) THEN
634 156 : DEALLOCATE (constraint_info%const_g33_c)
635 : END IF
636 9512 : IF (ASSOCIATED(constraint_info%const_g33_dab)) THEN
637 156 : DEALLOCATE (constraint_info%const_g33_dab)
638 : END IF
639 9512 : IF (ASSOCIATED(constraint_info%const_g33_dac)) THEN
640 156 : DEALLOCATE (constraint_info%const_g33_dac)
641 : END IF
642 9512 : IF (ASSOCIATED(constraint_info%const_g33_dbc)) THEN
643 156 : DEALLOCATE (constraint_info%const_g33_dbc)
644 : END IF
645 9512 : IF (ASSOCIATED(constraint_info%g33_intermolecular)) THEN
646 156 : DEALLOCATE (constraint_info%g33_intermolecular)
647 : END IF
648 9512 : IF (ASSOCIATED(constraint_info%g33_restraint)) THEN
649 156 : DEALLOCATE (constraint_info%g33_restraint)
650 : END IF
651 9512 : IF (ASSOCIATED(constraint_info%g33_k0)) THEN
652 156 : DEALLOCATE (constraint_info%g33_k0)
653 : END IF
654 9512 : IF (ASSOCIATED(constraint_info%g33_exclude_qm)) THEN
655 156 : DEALLOCATE (constraint_info%g33_exclude_qm)
656 : END IF
657 9512 : IF (ASSOCIATED(constraint_info%g33_exclude_mm)) THEN
658 156 : DEALLOCATE (constraint_info%g33_exclude_mm)
659 : END IF
660 : ! G4x6
661 9512 : IF (ASSOCIATED(constraint_info%const_g46_mol)) THEN
662 16 : DEALLOCATE (constraint_info%const_g46_mol)
663 : END IF
664 9512 : IF (ASSOCIATED(constraint_info%const_g46_molname)) THEN
665 16 : DEALLOCATE (constraint_info%const_g46_molname)
666 : END IF
667 9512 : IF (ASSOCIATED(constraint_info%const_g46_a)) THEN
668 16 : DEALLOCATE (constraint_info%const_g46_a)
669 : END IF
670 9512 : IF (ASSOCIATED(constraint_info%const_g46_b)) THEN
671 16 : DEALLOCATE (constraint_info%const_g46_b)
672 : END IF
673 9512 : IF (ASSOCIATED(constraint_info%const_g46_c)) THEN
674 16 : DEALLOCATE (constraint_info%const_g46_c)
675 : END IF
676 9512 : IF (ASSOCIATED(constraint_info%const_g46_d)) THEN
677 16 : DEALLOCATE (constraint_info%const_g46_d)
678 : END IF
679 9512 : IF (ASSOCIATED(constraint_info%const_g46_dab)) THEN
680 16 : DEALLOCATE (constraint_info%const_g46_dab)
681 : END IF
682 9512 : IF (ASSOCIATED(constraint_info%const_g46_dac)) THEN
683 16 : DEALLOCATE (constraint_info%const_g46_dac)
684 : END IF
685 9512 : IF (ASSOCIATED(constraint_info%const_g46_dbc)) THEN
686 16 : DEALLOCATE (constraint_info%const_g46_dbc)
687 : END IF
688 9512 : IF (ASSOCIATED(constraint_info%const_g46_dad)) THEN
689 16 : DEALLOCATE (constraint_info%const_g46_dad)
690 : END IF
691 9512 : IF (ASSOCIATED(constraint_info%const_g46_dbd)) THEN
692 16 : DEALLOCATE (constraint_info%const_g46_dbd)
693 : END IF
694 9512 : IF (ASSOCIATED(constraint_info%const_g46_dcd)) THEN
695 16 : DEALLOCATE (constraint_info%const_g46_dcd)
696 : END IF
697 9512 : IF (ASSOCIATED(constraint_info%g46_intermolecular)) THEN
698 16 : DEALLOCATE (constraint_info%g46_intermolecular)
699 : END IF
700 9512 : IF (ASSOCIATED(constraint_info%g46_restraint)) THEN
701 16 : DEALLOCATE (constraint_info%g46_restraint)
702 : END IF
703 9512 : IF (ASSOCIATED(constraint_info%g46_k0)) THEN
704 16 : DEALLOCATE (constraint_info%g46_k0)
705 : END IF
706 9512 : IF (ASSOCIATED(constraint_info%g46_exclude_qm)) THEN
707 16 : DEALLOCATE (constraint_info%g46_exclude_qm)
708 : END IF
709 9512 : IF (ASSOCIATED(constraint_info%g46_exclude_mm)) THEN
710 16 : DEALLOCATE (constraint_info%g46_exclude_mm)
711 : END IF
712 : ! virtual_site
713 9512 : IF (ASSOCIATED(constraint_info%const_vsite_mol)) THEN
714 8 : DEALLOCATE (constraint_info%const_vsite_mol)
715 : END IF
716 9512 : IF (ASSOCIATED(constraint_info%const_vsite_molname)) THEN
717 8 : DEALLOCATE (constraint_info%const_vsite_molname)
718 : END IF
719 9512 : IF (ASSOCIATED(constraint_info%const_vsite_a)) THEN
720 8 : DEALLOCATE (constraint_info%const_vsite_a)
721 : END IF
722 9512 : IF (ASSOCIATED(constraint_info%const_vsite_b)) THEN
723 8 : DEALLOCATE (constraint_info%const_vsite_b)
724 : END IF
725 9512 : IF (ASSOCIATED(constraint_info%const_vsite_c)) THEN
726 8 : DEALLOCATE (constraint_info%const_vsite_c)
727 : END IF
728 9512 : IF (ASSOCIATED(constraint_info%const_vsite_d)) THEN
729 8 : DEALLOCATE (constraint_info%const_vsite_d)
730 : END IF
731 9512 : IF (ASSOCIATED(constraint_info%const_vsite_wbc)) THEN
732 8 : DEALLOCATE (constraint_info%const_vsite_wbc)
733 : END IF
734 9512 : IF (ASSOCIATED(constraint_info%const_vsite_wdc)) THEN
735 8 : DEALLOCATE (constraint_info%const_vsite_wdc)
736 : END IF
737 9512 : IF (ASSOCIATED(constraint_info%vsite_intermolecular)) THEN
738 8 : DEALLOCATE (constraint_info%vsite_intermolecular)
739 : END IF
740 9512 : IF (ASSOCIATED(constraint_info%vsite_restraint)) THEN
741 8 : DEALLOCATE (constraint_info%vsite_restraint)
742 : END IF
743 9512 : IF (ASSOCIATED(constraint_info%vsite_k0)) THEN
744 8 : DEALLOCATE (constraint_info%vsite_k0)
745 : END IF
746 9512 : IF (ASSOCIATED(constraint_info%vsite_exclude_qm)) THEN
747 8 : DEALLOCATE (constraint_info%vsite_exclude_qm)
748 : END IF
749 9512 : IF (ASSOCIATED(constraint_info%vsite_exclude_mm)) THEN
750 8 : DEALLOCATE (constraint_info%vsite_exclude_mm)
751 : END IF
752 9512 : END SUBROUTINE deallocate_constraint
753 :
754 : ! **************************************************************************************************
755 : !> \brief Deallocate possibly allocated arrays before reading topology
756 : !> \param topology ...
757 : !> \par History
758 : !> none
759 : ! **************************************************************************************************
760 795 : SUBROUTINE pre_read_topology(topology)
761 : TYPE(topology_parameters_type), INTENT(INOUT) :: topology
762 :
763 : TYPE(atom_info_type), POINTER :: atom_info
764 :
765 795 : atom_info => topology%atom_info
766 :
767 795 : IF (ASSOCIATED(atom_info%id_molname)) THEN
768 795 : DEALLOCATE (atom_info%id_molname)
769 : END IF
770 :
771 795 : IF (ASSOCIATED(atom_info%resid)) THEN
772 795 : DEALLOCATE (atom_info%resid)
773 : END IF
774 :
775 795 : IF (ASSOCIATED(atom_info%id_resname)) THEN
776 795 : DEALLOCATE (atom_info%id_resname)
777 : END IF
778 :
779 795 : IF (ASSOCIATED(atom_info%id_atmname)) THEN
780 795 : DEALLOCATE (atom_info%id_atmname)
781 : END IF
782 :
783 795 : IF (ASSOCIATED(atom_info%atm_charge)) THEN
784 795 : DEALLOCATE (atom_info%atm_charge)
785 : END IF
786 :
787 795 : IF (ASSOCIATED(atom_info%atm_mass)) THEN
788 795 : DEALLOCATE (atom_info%atm_mass)
789 : END IF
790 :
791 795 : END SUBROUTINE pre_read_topology
792 :
793 0 : END MODULE topology_types
|