(git:ed6f26b)
Loading...
Searching...
No Matches
topology_types.F
Go to the documentation of this file.
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! **************************************************************************************************
19 USE cell_types, ONLY: cell_release,&
21 USE colvar_types, ONLY: colvar_p_type,&
27 USE kinds, ONLY: default_path_length,&
29 dp
30#include "./base/base_uses.f90"
31
32 IMPLICIT NONE
33
34! **************************************************************************************************
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! **************************************************************************************************
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()
63
64! **************************************************************************************************
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! **************************************************************************************************
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.
178
179! **************************************************************************************************
181 INTEGER, DIMENSION(:), POINTER :: constr => null()
182 END TYPE constr_list_type
183
184 PUBLIC :: atom_info_type, &
189
190 PUBLIC :: init_topology, &
193
194 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'topology_types'
195 PRIVATE
196
197CONTAINS
198
199! **************************************************************************************************
200!> \brief 1. Just NULLIFY and zero all the stuff
201!> \param topology ...
202!> \par History
203!> none
204! **************************************************************************************************
205 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 ALLOCATE (topology%atom_info)
213 ALLOCATE (topology%conn_info)
214 ALLOCATE (topology%cons_info)
215 !-----------------------------------------------------------------------------
216 ! 2. Initialize and Nullify things in topology
217 !-----------------------------------------------------------------------------
218 NULLIFY (topology%cell, topology%cell_ref, topology%cell_muc)
219 topology%natoms = 0
220 topology%natom_type = 0
221 topology%nmol = 0
222 topology%nmol_type = 0
223 topology%nmol_conn = 0
224 topology%bondparm_type = do_bondparm_covalent
225 topology%reorder_atom = .false.
226 topology%create_molecules = .false.
227 topology%molecules_check = .false.
228 topology%coordinate = .false.
229 topology%use_g96_velocity = .false.
230 topology%coord_type = -1
231 topology%coord_file_name = ''
232 topology%conn_type = do_conn_generate
233 topology%conn_file_name = 'OFF'
234 topology%const_atom = .false.
235 topology%const_hydr = .false.
236 topology%const_colv = .false.
237 topology%const_33 = .false.
238 topology%const_46 = .false.
239 topology%const_vsite = .false.
240 topology%charge_occup = .false.
241 topology%charge_beta = .false.
242 topology%charge_extended = .false.
243 topology%para_res = .false.
244 topology%molname_generated = .false.
245 topology%aa_element = .false.
246 topology%exclude_vdw = do_skip_13
247 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 CALL init_constraint(topology%cons_info)
297 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 SUBROUTINE init_constraint(constraint_info)
306 TYPE(constraint_info_type), POINTER :: constraint_info
307
308! Bonds involving Hydrogens
309
310 constraint_info%hbonds_restraint = .false.
311 ! Fixed Atoms
312 constraint_info%nfixed_atoms = 0
313 constraint_info%freeze_mm = do_constr_none
314 constraint_info%freeze_qm = do_constr_none
315 NULLIFY (constraint_info%fixed_atoms)
316 NULLIFY (constraint_info%fixed_type)
317 NULLIFY (constraint_info%fixed_mol_type)
318 NULLIFY (constraint_info%fixed_molnames)
319 NULLIFY (constraint_info%fixed_restraint)
320 NULLIFY (constraint_info%fixed_k0)
321 NULLIFY (constraint_info%fixed_mol_restraint)
322 NULLIFY (constraint_info%fixed_mol_k0)
323 NULLIFY (constraint_info%fixed_exclude_qm, constraint_info%fixed_exclude_mm)
324 ! Collective Constraints
325 constraint_info%nconst_colv = 0
326 NULLIFY (constraint_info%colvar_set)
327 NULLIFY (constraint_info%const_colv_mol)
328 NULLIFY (constraint_info%const_colv_molname)
329 NULLIFY (constraint_info%const_colv_target)
330 NULLIFY (constraint_info%const_colv_target_growth)
331 NULLIFY (constraint_info%colv_intermolecular)
332 NULLIFY (constraint_info%colv_restraint)
333 NULLIFY (constraint_info%colv_k0)
334 NULLIFY (constraint_info%colv_exclude_qm, constraint_info%colv_exclude_mm)
335 ! G3x3
336 constraint_info%nconst_g33 = 0
337 NULLIFY (constraint_info%const_g33_mol)
338 NULLIFY (constraint_info%const_g33_molname)
339 NULLIFY (constraint_info%const_g33_a)
340 NULLIFY (constraint_info%const_g33_b)
341 NULLIFY (constraint_info%const_g33_c)
342 NULLIFY (constraint_info%const_g33_dab)
343 NULLIFY (constraint_info%const_g33_dac)
344 NULLIFY (constraint_info%const_g33_dbc)
345 NULLIFY (constraint_info%g33_intermolecular)
346 NULLIFY (constraint_info%g33_restraint)
347 NULLIFY (constraint_info%g33_k0)
348 NULLIFY (constraint_info%g33_exclude_qm, constraint_info%g33_exclude_mm)
349 ! G4x6
350 constraint_info%nconst_g46 = 0
351 NULLIFY (constraint_info%const_g46_mol)
352 NULLIFY (constraint_info%const_g46_molname)
353 NULLIFY (constraint_info%const_g46_a)
354 NULLIFY (constraint_info%const_g46_b)
355 NULLIFY (constraint_info%const_g46_c)
356 NULLIFY (constraint_info%const_g46_d)
357 NULLIFY (constraint_info%const_g46_dab)
358 NULLIFY (constraint_info%const_g46_dac)
359 NULLIFY (constraint_info%const_g46_dbc)
360 NULLIFY (constraint_info%const_g46_dad)
361 NULLIFY (constraint_info%const_g46_dbd)
362 NULLIFY (constraint_info%const_g46_dcd)
363 NULLIFY (constraint_info%g46_intermolecular)
364 NULLIFY (constraint_info%g46_restraint)
365 NULLIFY (constraint_info%g46_k0)
366 NULLIFY (constraint_info%g46_exclude_qm, constraint_info%g46_exclude_mm)
367 ! virtual_site
368 constraint_info%nconst_vsite = 0
369 NULLIFY (constraint_info%const_vsite_mol)
370 NULLIFY (constraint_info%const_vsite_molname)
371 NULLIFY (constraint_info%const_vsite_a)
372 NULLIFY (constraint_info%const_vsite_b)
373 NULLIFY (constraint_info%const_vsite_c)
374 NULLIFY (constraint_info%const_vsite_d)
375 NULLIFY (constraint_info%const_vsite_wbc)
376 NULLIFY (constraint_info%const_vsite_wdc)
377 NULLIFY (constraint_info%vsite_intermolecular)
378 NULLIFY (constraint_info%vsite_restraint)
379 NULLIFY (constraint_info%vsite_k0)
380 NULLIFY (constraint_info%vsite_exclude_qm, constraint_info%vsite_exclude_mm)
381
382 END SUBROUTINE init_constraint
383
384! **************************************************************************************************
385!> \brief 1. Just DEALLOCATE all the stuff
386!> \param topology ...
387!> \par History
388!> none
389! **************************************************************************************************
390 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 IF (ASSOCIATED(topology%atom_info%id_molname)) THEN
398 DEALLOCATE (topology%atom_info%id_molname)
399 END IF
400 IF (ASSOCIATED(topology%atom_info%id_resname)) THEN
401 DEALLOCATE (topology%atom_info%id_resname)
402 END IF
403 IF (ASSOCIATED(topology%atom_info%resid)) THEN
404 DEALLOCATE (topology%atom_info%resid)
405 END IF
406 IF (ASSOCIATED(topology%atom_info%id_atmname)) THEN
407 DEALLOCATE (topology%atom_info%id_atmname)
408 END IF
409 IF (ASSOCIATED(topology%atom_info%id_atom_names)) THEN
410 DEALLOCATE (topology%atom_info%id_atom_names)
411 END IF
412 IF (ASSOCIATED(topology%atom_info%r)) THEN
413 DEALLOCATE (topology%atom_info%r)
414 END IF
415 IF (ASSOCIATED(topology%atom_info%map_mol_typ)) THEN
416 DEALLOCATE (topology%atom_info%map_mol_typ)
417 END IF
418 IF (ASSOCIATED(topology%atom_info%map_mol_num)) THEN
419 DEALLOCATE (topology%atom_info%map_mol_num)
420 END IF
421 IF (ASSOCIATED(topology%atom_info%map_mol_res)) THEN
422 DEALLOCATE (topology%atom_info%map_mol_res)
423 END IF
424 IF (ASSOCIATED(topology%atom_info%atm_charge)) THEN
425 DEALLOCATE (topology%atom_info%atm_charge)
426 END IF
427 IF (ASSOCIATED(topology%atom_info%atm_mass)) THEN
428 DEALLOCATE (topology%atom_info%atm_mass)
429 END IF
430 IF (ASSOCIATED(topology%atom_info%occup)) THEN
431 DEALLOCATE (topology%atom_info%occup)
432 END IF
433 IF (ASSOCIATED(topology%atom_info%beta)) THEN
434 DEALLOCATE (topology%atom_info%beta)
435 END IF
436 IF (ASSOCIATED(topology%atom_info%id_element)) THEN
437 DEALLOCATE (topology%atom_info%id_element)
438 END IF
439 !-----------------------------------------------------------------------------
440 ! 2. DEALLOCATE things in topology%conn_info
441 !-----------------------------------------------------------------------------
442 IF (ASSOCIATED(topology%conn_info%bond_a)) THEN
443 DEALLOCATE (topology%conn_info%bond_a)
444 END IF
445 IF (ASSOCIATED(topology%conn_info%bond_b)) THEN
446 DEALLOCATE (topology%conn_info%bond_b)
447 END IF
448 IF (ASSOCIATED(topology%conn_info%bond_type)) THEN
449 DEALLOCATE (topology%conn_info%bond_type)
450 END IF
451 IF (ASSOCIATED(topology%conn_info%ub_a)) THEN
452 DEALLOCATE (topology%conn_info%ub_a)
453 END IF
454 IF (ASSOCIATED(topology%conn_info%ub_b)) THEN
455 DEALLOCATE (topology%conn_info%ub_b)
456 END IF
457 IF (ASSOCIATED(topology%conn_info%ub_c)) THEN
458 DEALLOCATE (topology%conn_info%ub_c)
459 END IF
460 IF (ASSOCIATED(topology%conn_info%theta_a)) THEN
461 DEALLOCATE (topology%conn_info%theta_a)
462 END IF
463 IF (ASSOCIATED(topology%conn_info%theta_b)) THEN
464 DEALLOCATE (topology%conn_info%theta_b)
465 END IF
466 IF (ASSOCIATED(topology%conn_info%theta_c)) THEN
467 DEALLOCATE (topology%conn_info%theta_c)
468 END IF
469 IF (ASSOCIATED(topology%conn_info%theta_type)) THEN
470 DEALLOCATE (topology%conn_info%theta_type)
471 END IF
472 IF (ASSOCIATED(topology%conn_info%phi_a)) THEN
473 DEALLOCATE (topology%conn_info%phi_a)
474 END IF
475 IF (ASSOCIATED(topology%conn_info%phi_b)) THEN
476 DEALLOCATE (topology%conn_info%phi_b)
477 END IF
478 IF (ASSOCIATED(topology%conn_info%phi_c)) THEN
479 DEALLOCATE (topology%conn_info%phi_c)
480 END IF
481 IF (ASSOCIATED(topology%conn_info%phi_d)) THEN
482 DEALLOCATE (topology%conn_info%phi_d)
483 END IF
484 IF (ASSOCIATED(topology%conn_info%phi_type)) THEN
485 DEALLOCATE (topology%conn_info%phi_type)
486 END IF
487 IF (ASSOCIATED(topology%conn_info%impr_a)) THEN
488 DEALLOCATE (topology%conn_info%impr_a)
489 END IF
490 IF (ASSOCIATED(topology%conn_info%impr_b)) THEN
491 DEALLOCATE (topology%conn_info%impr_b)
492 END IF
493 IF (ASSOCIATED(topology%conn_info%impr_c)) THEN
494 DEALLOCATE (topology%conn_info%impr_c)
495 END IF
496 IF (ASSOCIATED(topology%conn_info%impr_d)) THEN
497 DEALLOCATE (topology%conn_info%impr_d)
498 END IF
499 IF (ASSOCIATED(topology%conn_info%impr_type)) THEN
500 DEALLOCATE (topology%conn_info%impr_type)
501 END IF
502 IF (ASSOCIATED(topology%conn_info%onfo_a)) THEN
503 DEALLOCATE (topology%conn_info%onfo_a)
504 END IF
505 IF (ASSOCIATED(topology%conn_info%onfo_b)) THEN
506 DEALLOCATE (topology%conn_info%onfo_b)
507 END IF
508 IF (ASSOCIATED(topology%conn_info%c_bond_a)) THEN
509 DEALLOCATE (topology%conn_info%c_bond_a)
510 END IF
511 IF (ASSOCIATED(topology%conn_info%c_bond_b)) THEN
512 DEALLOCATE (topology%conn_info%c_bond_b)
513 END IF
514 IF (ASSOCIATED(topology%conn_info%c_bond_type)) THEN
515 DEALLOCATE (topology%conn_info%c_bond_type)
516 END IF
517 !-----------------------------------------------------------------------------
518 ! 3. DEALLOCATE things in topology%cons_info
519 !-----------------------------------------------------------------------------
520 IF (ASSOCIATED(topology%cons_info)) &
521 CALL deallocate_constraint(topology%cons_info)
522 !-----------------------------------------------------------------------------
523 ! 4. DEALLOCATE things in topology
524 !-----------------------------------------------------------------------------
525 CALL cell_release(topology%cell)
526 CALL cell_release(topology%cell_ref)
527 CALL cell_release(topology%cell_muc)
528 IF (ASSOCIATED(topology%atom_info)) THEN
529 DEALLOCATE (topology%atom_info)
530 END IF
531 IF (ASSOCIATED(topology%conn_info)) THEN
532 DEALLOCATE (topology%conn_info)
533 END IF
534 IF (ASSOCIATED(topology%cons_info)) THEN
535 DEALLOCATE (topology%cons_info)
536 END IF
537
538 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 SUBROUTINE deallocate_constraint(constraint_info)
547 TYPE(constraint_info_type), POINTER :: constraint_info
548
549 INTEGER :: i
550
551! Fixed Atoms
552
553 IF (ASSOCIATED(constraint_info%fixed_atoms)) THEN
554 DEALLOCATE (constraint_info%fixed_atoms)
555 END IF
556 IF (ASSOCIATED(constraint_info%fixed_type)) THEN
557 DEALLOCATE (constraint_info%fixed_type)
558 END IF
559 IF (ASSOCIATED(constraint_info%fixed_molnames)) THEN
560 DEALLOCATE (constraint_info%fixed_molnames)
561 END IF
562 IF (ASSOCIATED(constraint_info%fixed_mol_type)) THEN
563 DEALLOCATE (constraint_info%fixed_mol_type)
564 END IF
565 IF (ASSOCIATED(constraint_info%fixed_restraint)) THEN
566 DEALLOCATE (constraint_info%fixed_restraint)
567 END IF
568 IF (ASSOCIATED(constraint_info%fixed_k0)) THEN
569 DEALLOCATE (constraint_info%fixed_k0)
570 END IF
571 IF (ASSOCIATED(constraint_info%fixed_mol_restraint)) THEN
572 DEALLOCATE (constraint_info%fixed_mol_restraint)
573 END IF
574 IF (ASSOCIATED(constraint_info%fixed_mol_k0)) THEN
575 DEALLOCATE (constraint_info%fixed_mol_k0)
576 END IF
577 IF (ASSOCIATED(constraint_info%fixed_exclude_qm)) THEN
578 DEALLOCATE (constraint_info%fixed_exclude_qm)
579 END IF
580 IF (ASSOCIATED(constraint_info%fixed_exclude_mm)) THEN
581 DEALLOCATE (constraint_info%fixed_exclude_mm)
582 END IF
583 ! Collective Constraint
584 IF (ASSOCIATED(constraint_info%colvar_set)) THEN
585 DO i = 1, SIZE(constraint_info%colvar_set)
586 IF (ASSOCIATED(constraint_info%colvar_set(i)%colvar)) THEN
587 CALL colvar_release(constraint_info%colvar_set(i)%colvar)
588 NULLIFY (constraint_info%colvar_set(i)%colvar)
589 END IF
590 END DO
591 DEALLOCATE (constraint_info%colvar_set)
592 END IF
593 IF (ASSOCIATED(constraint_info%const_colv_mol)) THEN
594 DEALLOCATE (constraint_info%const_colv_mol)
595 END IF
596 IF (ASSOCIATED(constraint_info%const_colv_molname)) THEN
597 DEALLOCATE (constraint_info%const_colv_molname)
598 END IF
599 IF (ASSOCIATED(constraint_info%const_colv_target)) THEN
600 DEALLOCATE (constraint_info%const_colv_target)
601 END IF
602 IF (ASSOCIATED(constraint_info%const_colv_target_growth)) THEN
603 DEALLOCATE (constraint_info%const_colv_target_growth)
604 END IF
605 IF (ASSOCIATED(constraint_info%colv_intermolecular)) THEN
606 DEALLOCATE (constraint_info%colv_intermolecular)
607 END IF
608 IF (ASSOCIATED(constraint_info%colv_restraint)) THEN
609 DEALLOCATE (constraint_info%colv_restraint)
610 END IF
611 IF (ASSOCIATED(constraint_info%colv_k0)) THEN
612 DEALLOCATE (constraint_info%colv_k0)
613 END IF
614 IF (ASSOCIATED(constraint_info%colv_exclude_qm)) THEN
615 DEALLOCATE (constraint_info%colv_exclude_qm)
616 END IF
617 IF (ASSOCIATED(constraint_info%colv_exclude_mm)) THEN
618 DEALLOCATE (constraint_info%colv_exclude_mm)
619 END IF
620 ! G3x3
621 IF (ASSOCIATED(constraint_info%const_g33_mol)) THEN
622 DEALLOCATE (constraint_info%const_g33_mol)
623 END IF
624 IF (ASSOCIATED(constraint_info%const_g33_molname)) THEN
625 DEALLOCATE (constraint_info%const_g33_molname)
626 END IF
627 IF (ASSOCIATED(constraint_info%const_g33_a)) THEN
628 DEALLOCATE (constraint_info%const_g33_a)
629 END IF
630 IF (ASSOCIATED(constraint_info%const_g33_b)) THEN
631 DEALLOCATE (constraint_info%const_g33_b)
632 END IF
633 IF (ASSOCIATED(constraint_info%const_g33_c)) THEN
634 DEALLOCATE (constraint_info%const_g33_c)
635 END IF
636 IF (ASSOCIATED(constraint_info%const_g33_dab)) THEN
637 DEALLOCATE (constraint_info%const_g33_dab)
638 END IF
639 IF (ASSOCIATED(constraint_info%const_g33_dac)) THEN
640 DEALLOCATE (constraint_info%const_g33_dac)
641 END IF
642 IF (ASSOCIATED(constraint_info%const_g33_dbc)) THEN
643 DEALLOCATE (constraint_info%const_g33_dbc)
644 END IF
645 IF (ASSOCIATED(constraint_info%g33_intermolecular)) THEN
646 DEALLOCATE (constraint_info%g33_intermolecular)
647 END IF
648 IF (ASSOCIATED(constraint_info%g33_restraint)) THEN
649 DEALLOCATE (constraint_info%g33_restraint)
650 END IF
651 IF (ASSOCIATED(constraint_info%g33_k0)) THEN
652 DEALLOCATE (constraint_info%g33_k0)
653 END IF
654 IF (ASSOCIATED(constraint_info%g33_exclude_qm)) THEN
655 DEALLOCATE (constraint_info%g33_exclude_qm)
656 END IF
657 IF (ASSOCIATED(constraint_info%g33_exclude_mm)) THEN
658 DEALLOCATE (constraint_info%g33_exclude_mm)
659 END IF
660 ! G4x6
661 IF (ASSOCIATED(constraint_info%const_g46_mol)) THEN
662 DEALLOCATE (constraint_info%const_g46_mol)
663 END IF
664 IF (ASSOCIATED(constraint_info%const_g46_molname)) THEN
665 DEALLOCATE (constraint_info%const_g46_molname)
666 END IF
667 IF (ASSOCIATED(constraint_info%const_g46_a)) THEN
668 DEALLOCATE (constraint_info%const_g46_a)
669 END IF
670 IF (ASSOCIATED(constraint_info%const_g46_b)) THEN
671 DEALLOCATE (constraint_info%const_g46_b)
672 END IF
673 IF (ASSOCIATED(constraint_info%const_g46_c)) THEN
674 DEALLOCATE (constraint_info%const_g46_c)
675 END IF
676 IF (ASSOCIATED(constraint_info%const_g46_d)) THEN
677 DEALLOCATE (constraint_info%const_g46_d)
678 END IF
679 IF (ASSOCIATED(constraint_info%const_g46_dab)) THEN
680 DEALLOCATE (constraint_info%const_g46_dab)
681 END IF
682 IF (ASSOCIATED(constraint_info%const_g46_dac)) THEN
683 DEALLOCATE (constraint_info%const_g46_dac)
684 END IF
685 IF (ASSOCIATED(constraint_info%const_g46_dbc)) THEN
686 DEALLOCATE (constraint_info%const_g46_dbc)
687 END IF
688 IF (ASSOCIATED(constraint_info%const_g46_dad)) THEN
689 DEALLOCATE (constraint_info%const_g46_dad)
690 END IF
691 IF (ASSOCIATED(constraint_info%const_g46_dbd)) THEN
692 DEALLOCATE (constraint_info%const_g46_dbd)
693 END IF
694 IF (ASSOCIATED(constraint_info%const_g46_dcd)) THEN
695 DEALLOCATE (constraint_info%const_g46_dcd)
696 END IF
697 IF (ASSOCIATED(constraint_info%g46_intermolecular)) THEN
698 DEALLOCATE (constraint_info%g46_intermolecular)
699 END IF
700 IF (ASSOCIATED(constraint_info%g46_restraint)) THEN
701 DEALLOCATE (constraint_info%g46_restraint)
702 END IF
703 IF (ASSOCIATED(constraint_info%g46_k0)) THEN
704 DEALLOCATE (constraint_info%g46_k0)
705 END IF
706 IF (ASSOCIATED(constraint_info%g46_exclude_qm)) THEN
707 DEALLOCATE (constraint_info%g46_exclude_qm)
708 END IF
709 IF (ASSOCIATED(constraint_info%g46_exclude_mm)) THEN
710 DEALLOCATE (constraint_info%g46_exclude_mm)
711 END IF
712 ! virtual_site
713 IF (ASSOCIATED(constraint_info%const_vsite_mol)) THEN
714 DEALLOCATE (constraint_info%const_vsite_mol)
715 END IF
716 IF (ASSOCIATED(constraint_info%const_vsite_molname)) THEN
717 DEALLOCATE (constraint_info%const_vsite_molname)
718 END IF
719 IF (ASSOCIATED(constraint_info%const_vsite_a)) THEN
720 DEALLOCATE (constraint_info%const_vsite_a)
721 END IF
722 IF (ASSOCIATED(constraint_info%const_vsite_b)) THEN
723 DEALLOCATE (constraint_info%const_vsite_b)
724 END IF
725 IF (ASSOCIATED(constraint_info%const_vsite_c)) THEN
726 DEALLOCATE (constraint_info%const_vsite_c)
727 END IF
728 IF (ASSOCIATED(constraint_info%const_vsite_d)) THEN
729 DEALLOCATE (constraint_info%const_vsite_d)
730 END IF
731 IF (ASSOCIATED(constraint_info%const_vsite_wbc)) THEN
732 DEALLOCATE (constraint_info%const_vsite_wbc)
733 END IF
734 IF (ASSOCIATED(constraint_info%const_vsite_wdc)) THEN
735 DEALLOCATE (constraint_info%const_vsite_wdc)
736 END IF
737 IF (ASSOCIATED(constraint_info%vsite_intermolecular)) THEN
738 DEALLOCATE (constraint_info%vsite_intermolecular)
739 END IF
740 IF (ASSOCIATED(constraint_info%vsite_restraint)) THEN
741 DEALLOCATE (constraint_info%vsite_restraint)
742 END IF
743 IF (ASSOCIATED(constraint_info%vsite_k0)) THEN
744 DEALLOCATE (constraint_info%vsite_k0)
745 END IF
746 IF (ASSOCIATED(constraint_info%vsite_exclude_qm)) THEN
747 DEALLOCATE (constraint_info%vsite_exclude_qm)
748 END IF
749 IF (ASSOCIATED(constraint_info%vsite_exclude_mm)) THEN
750 DEALLOCATE (constraint_info%vsite_exclude_mm)
751 END IF
752 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 SUBROUTINE pre_read_topology(topology)
761 TYPE(topology_parameters_type), INTENT(INOUT) :: topology
762
763 TYPE(atom_info_type), POINTER :: atom_info
764
765 atom_info => topology%atom_info
766
767 IF (ASSOCIATED(atom_info%id_molname)) THEN
768 DEALLOCATE (atom_info%id_molname)
769 END IF
770
771 IF (ASSOCIATED(atom_info%resid)) THEN
772 DEALLOCATE (atom_info%resid)
773 END IF
774
775 IF (ASSOCIATED(atom_info%id_resname)) THEN
776 DEALLOCATE (atom_info%id_resname)
777 END IF
778
779 IF (ASSOCIATED(atom_info%id_atmname)) THEN
780 DEALLOCATE (atom_info%id_atmname)
781 END IF
782
783 IF (ASSOCIATED(atom_info%atm_charge)) THEN
784 DEALLOCATE (atom_info%atm_charge)
785 END IF
786
787 IF (ASSOCIATED(atom_info%atm_mass)) THEN
788 DEALLOCATE (atom_info%atm_mass)
789 END IF
790
791 END SUBROUTINE pre_read_topology
792
793END MODULE topology_types
Handles all functions related to the CELL.
Definition cell_types.F:15
subroutine, public cell_release(cell)
releases the given cell (see doc/ReferenceCounting.html)
Definition cell_types.F:559
Initialize the collective variables types.
recursive subroutine, public colvar_release(colvar)
releases the memory that might have been allocated by the colvar
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_skip_13
integer, parameter, public do_bondparm_covalent
integer, parameter, public do_conn_generate
integer, parameter, public do_constr_none
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public default_path_length
Definition kinds.F:58
subroutine, public deallocate_topology(topology)
Just DEALLOCATE all the stuff
subroutine, public pre_read_topology(topology)
Deallocate possibly allocated arrays before reading topology.
subroutine, public init_topology(topology)
Just NULLIFY and zero all the stuff
Control for reading in different topologies and coordinates.
Definition topology.F:13
Type defining parameters related to the simulation cell.
Definition cell_types.F:55