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