(git:374b731)
Loading...
Searching...
No Matches
molecule_kind_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!> \brief Define the molecule kind structure types and the corresponding
10!> functionality
11!> \par History
12!> Teodoro Laino [tlaino] 12.2008 - Preparing for VIRTUAL SITE constraints
13!> (patch by Marcel Baer)
14!> \author MK (22.08.2003)
15! **************************************************************************************************
19 USE cell_types, ONLY: use_perd_x,&
26 USE colvar_types, ONLY: &
37 USE force_field_kind_types, ONLY: &
42 USE kinds, ONLY: default_string_length,&
43 dp
45#include "../base/base_uses.f90"
46
47 IMPLICIT NONE
48
49 PRIVATE
50
51 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'molecule_kind_types'
52
53! *** Define the derived structure types ***
54
55! **************************************************************************************************
57 TYPE(atomic_kind_type), POINTER :: atomic_kind => null()
58 INTEGER :: id_name = 0
59 END TYPE atom_type
60
61! **************************************************************************************************
63 INTEGER :: a = 0
64 CHARACTER(LEN=default_string_length) :: name = ""
65 TYPE(shell_kind_type), POINTER :: shell_kind => null()
66 END TYPE shell_type
67
68! **************************************************************************************************
70 INTEGER :: a = 0, b = 0
71 INTEGER :: id_type = do_ff_undef, itype = 0
72 TYPE(bond_kind_type), POINTER :: bond_kind => null()
73 END TYPE bond_type
74
75! **************************************************************************************************
77 INTEGER :: a = 0, b = 0, c = 0
78 INTEGER :: id_type = do_ff_undef, itype = 0
79 TYPE(bend_kind_type), POINTER :: bend_kind => null()
80 END TYPE bend_type
81
82! **************************************************************************************************
84 INTEGER :: a = 0, b = 0, c = 0
85 INTEGER :: id_type = do_ff_undef, itype = 0
86 TYPE(ub_kind_type), POINTER :: ub_kind => null()
87 END TYPE ub_type
88
89! **************************************************************************************************
91 INTEGER :: a = 0, b = 0, c = 0, d = 0
92 INTEGER :: id_type = do_ff_undef, itype = 0
93 TYPE(torsion_kind_type), POINTER :: torsion_kind => null()
94 END TYPE torsion_type
95
96! **************************************************************************************************
98 INTEGER :: a = 0, b = 0, c = 0, d = 0
99 INTEGER :: id_type = do_ff_undef, itype = 0
100 TYPE(impr_kind_type), POINTER :: impr_kind => null()
101 END TYPE impr_type
102
103! **************************************************************************************************
105 INTEGER :: a = 0, b = 0, c = 0, d = 0
106 INTEGER :: id_type = do_ff_undef, itype = 0
107 TYPE(opbend_kind_type), POINTER :: opbend_kind => null()
108 END TYPE opbend_type
109
110! **************************************************************************************************
111 TYPE restraint_type
112 LOGICAL :: active = .false.
113 REAL(kind=dp) :: k0 = 0.0_dp
114 END TYPE restraint_type
115
116! **************************************************************************************************
118 INTEGER :: type_id = no_colvar_id
119 INTEGER :: inp_seq_num = 0
120 LOGICAL :: use_points = .false.
121 REAL(kind=dp) :: expected_value = 0.0_dp
122 REAL(kind=dp) :: expected_value_growth_speed = 0.0_dp
123 INTEGER, POINTER, DIMENSION(:) :: i_atoms => null()
124 TYPE(restraint_type) :: restraint = restraint_type()
126
127! **************************************************************************************************
129 INTEGER :: a = 0, b = 0, c = 0
130 REAL(kind=dp) :: dab = 0.0_dp, dac = 0.0_dp, dbc = 0.0_dp
131 TYPE(restraint_type) :: restraint = restraint_type()
132 END TYPE g3x3_constraint_type
133
134! **************************************************************************************************
136 INTEGER :: a = 0, b = 0, c = 0, d = 0
137 REAL(kind=dp) :: dab = 0.0_dp, dac = 0.0_dp, dbc = 0.0_dp, dad = 0.0_dp, dbd = 0.0_dp, dcd = 0.0_dp
138 TYPE(restraint_type) :: restraint = restraint_type()
139 END TYPE g4x6_constraint_type
140
141! **************************************************************************************************
143 INTEGER :: a = 0, b = 0, c = 0, d = 0
144 REAL(kind=dp) :: wbc = 0.0_dp, wdc = 0.0_dp
145 TYPE(restraint_type) :: restraint = restraint_type()
146 END TYPE vsite_constraint_type
147
148! **************************************************************************************************
150 TYPE(restraint_type) :: restraint = restraint_type()
151 INTEGER :: fixd = 0, itype = 0
152 REAL(kind=dp), DIMENSION(3) :: coord = 0.0_dp
153 END TYPE fixd_constraint_type
154
155! **************************************************************************************************
157 INTEGER :: ifixd_index = 0, ikind = 0
159
160! **************************************************************************************************
162 TYPE(atom_type), DIMENSION(:), POINTER :: atom_list => null()
163 TYPE(bond_kind_type), DIMENSION(:), POINTER :: bond_kind_set => null()
164 TYPE(bond_type), DIMENSION(:), POINTER :: bond_list => null()
165 TYPE(bend_kind_type), DIMENSION(:), POINTER :: bend_kind_set => null()
166 TYPE(bend_type), DIMENSION(:), POINTER :: bend_list => null()
167 TYPE(ub_kind_type), DIMENSION(:), POINTER :: ub_kind_set => null()
168 TYPE(ub_type), DIMENSION(:), POINTER :: ub_list => null()
169 TYPE(torsion_kind_type), DIMENSION(:), POINTER :: torsion_kind_set => null()
170 TYPE(torsion_type), DIMENSION(:), POINTER :: torsion_list => null()
171 TYPE(impr_kind_type), DIMENSION(:), POINTER :: impr_kind_set => null()
172 TYPE(impr_type), DIMENSION(:), POINTER :: impr_list => null()
173 TYPE(opbend_kind_type), DIMENSION(:), POINTER :: opbend_kind_set => null()
174 TYPE(opbend_type), DIMENSION(:), POINTER :: opbend_list => null()
175 TYPE(colvar_constraint_type), DIMENSION(:), POINTER :: colv_list => null()
176 TYPE(g3x3_constraint_type), DIMENSION(:), POINTER :: g3x3_list => null()
177 TYPE(g4x6_constraint_type), DIMENSION(:), POINTER :: g4x6_list => null()
178 TYPE(vsite_constraint_type), DIMENSION(:), POINTER :: vsite_list => null()
179 TYPE(fixd_constraint_type), DIMENSION(:), POINTER :: fixd_list => null()
180 TYPE(shell_type), DIMENSION(:), POINTER :: shell_list => null()
181 CHARACTER(LEN=default_string_length) :: name = ""
182 REAL(kind=dp) :: charge = 0.0_dp, &
183 mass = 0.0_dp
184 INTEGER :: kind_number = 0, &
185 natom = 0, &
186 nbond = 0, &
187 nbend = 0, &
188 nimpr = 0, &
189 nopbend = 0, &
190 ntorsion = 0, &
191 nub = 0, &
192 ng3x3 = 0, ng3x3_restraint = 0, &
193 ng4x6 = 0, ng4x6_restraint = 0, &
194 nvsite = 0, nvsite_restraint = 0, &
195 nfixd = 0, nfixd_restraint = 0, &
196 nmolecule = 0, nshell = 0
198 INTEGER :: nsgf = 0, nelectron = 0, &
199 nelectron_alpha = 0, &
200 nelectron_beta = 0
201 INTEGER, DIMENSION(:), POINTER :: molecule_list => null()
202 LOGICAL :: molname_generated = .false.
203 END TYPE molecule_kind_type
204
205 ! *** Public subroutines ***
206 PUBLIC :: allocate_molecule_kind_set, &
213
214 ! *** Public data types ***
215 PUBLIC :: atom_type, &
216 bend_type, &
217 bond_type, &
218 ub_type, &
219 torsion_type, &
220 impr_type, &
221 opbend_type, &
230
231CONTAINS
232
233! **************************************************************************************************
234!> \brief ...
235!> \param colv_list ...
236!> \param ncolv ...
237! **************************************************************************************************
238 SUBROUTINE setup_colvar_counters(colv_list, ncolv)
239 TYPE(colvar_constraint_type), DIMENSION(:), &
240 POINTER :: colv_list
241 TYPE(colvar_counters), INTENT(OUT) :: ncolv
242
243 INTEGER :: k
244
245 IF (ASSOCIATED(colv_list)) THEN
246 DO k = 1, SIZE(colv_list)
247 IF (colv_list(k)%restraint%active) ncolv%nrestraint = ncolv%nrestraint + 1
248 SELECT CASE (colv_list(k)%type_id)
249 CASE (angle_colvar_id)
250 ncolv%nangle = ncolv%nangle + 1
251 CASE (coord_colvar_id)
252 ncolv%ncoord = ncolv%ncoord + 1
254 ncolv%npopulation = ncolv%npopulation + 1
255 CASE (gyration_colvar_id)
256 ncolv%ngyration = ncolv%ngyration + 1
257 CASE (rotation_colvar_id)
258 ncolv%nrot = ncolv%nrot + 1
259 CASE (dist_colvar_id)
260 ncolv%ndist = ncolv%ndist + 1
261 CASE (dfunct_colvar_id)
262 ncolv%ndfunct = ncolv%ndfunct + 1
264 ncolv%nplane_dist = ncolv%nplane_dist + 1
266 ncolv%nplane_angle = ncolv%nplane_angle + 1
267 CASE (torsion_colvar_id)
268 ncolv%ntorsion = ncolv%ntorsion + 1
269 CASE (qparm_colvar_id)
270 ncolv%nqparm = ncolv%nqparm + 1
271 CASE (xyz_diag_colvar_id)
272 ncolv%nxyz_diag = ncolv%nxyz_diag + 1
274 ncolv%nxyz_outerdiag = ncolv%nxyz_outerdiag + 1
276 ncolv%nhydronium_shell = ncolv%nhydronium_shell + 1
278 ncolv%nhydronium_dist = ncolv%nhydronium_dist + 1
280 ncolv%nacid_hyd_dist = ncolv%nacid_hyd_dist + 1
282 ncolv%nacid_hyd_shell = ncolv%nacid_hyd_shell + 1
284 ncolv%nreactionpath = ncolv%nreactionpath + 1
285 CASE (combine_colvar_id)
286 ncolv%ncombinecvs = ncolv%ncombinecvs + 1
287 CASE DEFAULT
288 cpabort("")
289 END SELECT
290 END DO
291 END IF
292 ncolv%ntot = ncolv%ndist + &
293 ncolv%nangle + &
294 ncolv%ntorsion + &
295 ncolv%ncoord + &
296 ncolv%nplane_dist + &
297 ncolv%nplane_angle + &
298 ncolv%ndfunct + &
299 ncolv%nrot + &
300 ncolv%nqparm + &
301 ncolv%nxyz_diag + &
302 ncolv%nxyz_outerdiag + &
303 ncolv%nhydronium_shell + &
304 ncolv%nhydronium_dist + &
305 ncolv%nacid_hyd_dist + &
306 ncolv%nacid_hyd_shell + &
307 ncolv%nreactionpath + &
308 ncolv%ncombinecvs + &
309 ncolv%npopulation + &
310 ncolv%ngyration
311
312 END SUBROUTINE setup_colvar_counters
313
314! **************************************************************************************************
315!> \brief Allocate and initialize a molecule kind set.
316!> \param molecule_kind_set ...
317!> \param nmolecule_kind ...
318!> \date 22.08.2003
319!> \author MK
320!> \version 1.0
321! **************************************************************************************************
322 SUBROUTINE allocate_molecule_kind_set(molecule_kind_set, nmolecule_kind)
323 TYPE(molecule_kind_type), DIMENSION(:), POINTER :: molecule_kind_set
324 INTEGER, INTENT(IN) :: nmolecule_kind
325
326 INTEGER :: imolecule_kind
327
328 IF (ASSOCIATED(molecule_kind_set)) THEN
329 CALL deallocate_molecule_kind_set(molecule_kind_set)
330 END IF
331
332 ALLOCATE (molecule_kind_set(nmolecule_kind))
333
334 DO imolecule_kind = 1, nmolecule_kind
335 molecule_kind_set(imolecule_kind)%kind_number = imolecule_kind
336 CALL setup_colvar_counters(molecule_kind_set(imolecule_kind)%colv_list, &
337 molecule_kind_set(imolecule_kind)%ncolv)
338 END DO
339
340 END SUBROUTINE allocate_molecule_kind_set
341
342! **************************************************************************************************
343!> \brief Deallocate a molecule kind set.
344!> \param molecule_kind_set ...
345!> \date 22.08.2003
346!> \author MK
347!> \version 1.0
348! **************************************************************************************************
349 SUBROUTINE deallocate_molecule_kind_set(molecule_kind_set)
350
351 TYPE(molecule_kind_type), DIMENSION(:), POINTER :: molecule_kind_set
352
353 INTEGER :: i, imolecule_kind, j, nmolecule_kind
354
355 IF (ASSOCIATED(molecule_kind_set)) THEN
356
357 nmolecule_kind = SIZE(molecule_kind_set)
358
359 DO imolecule_kind = 1, nmolecule_kind
360
361 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%atom_list)) THEN
362 DEALLOCATE (molecule_kind_set(imolecule_kind)%atom_list)
363 END IF
364 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%bend_kind_set)) THEN
365 DO i = 1, SIZE(molecule_kind_set(imolecule_kind)%bend_kind_set)
366 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%bend_kind_set(i)%legendre%coeffs)) &
367 DEALLOCATE (molecule_kind_set(imolecule_kind)%bend_kind_set(i)%legendre%coeffs)
368 END DO
369 DEALLOCATE (molecule_kind_set(imolecule_kind)%bend_kind_set)
370 END IF
371 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%bend_list)) THEN
372 DEALLOCATE (molecule_kind_set(imolecule_kind)%bend_list)
373 END IF
374 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%ub_list)) THEN
375 DEALLOCATE (molecule_kind_set(imolecule_kind)%ub_list)
376 END IF
377 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%ub_kind_set)) THEN
378 CALL ub_kind_dealloc_ref(molecule_kind_set(imolecule_kind)%ub_kind_set)
379 END IF
380 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%impr_list)) THEN
381 DEALLOCATE (molecule_kind_set(imolecule_kind)%impr_list)
382 END IF
383 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%impr_kind_set)) THEN
384 DO i = 1, SIZE(molecule_kind_set(imolecule_kind)%impr_kind_set)
385 CALL impr_kind_dealloc_ref() !This Subroutine doesn't deallocate anything, maybe needs to be implemented
386 END DO
387 DEALLOCATE (molecule_kind_set(imolecule_kind)%impr_kind_set)
388 END IF
389 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%opbend_list)) THEN
390 DEALLOCATE (molecule_kind_set(imolecule_kind)%opbend_list)
391 END IF
392 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%opbend_kind_set)) THEN
393 DEALLOCATE (molecule_kind_set(imolecule_kind)%opbend_kind_set)
394 END IF
395 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%bond_kind_set)) THEN
396 DEALLOCATE (molecule_kind_set(imolecule_kind)%bond_kind_set)
397 END IF
398 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%bond_list)) THEN
399 DEALLOCATE (molecule_kind_set(imolecule_kind)%bond_list)
400 END IF
401 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%colv_list)) THEN
402 DO j = 1, SIZE(molecule_kind_set(imolecule_kind)%colv_list)
403 DEALLOCATE (molecule_kind_set(imolecule_kind)%colv_list(j)%i_atoms)
404 END DO
405 DEALLOCATE (molecule_kind_set(imolecule_kind)%colv_list)
406 END IF
407 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%g3x3_list)) THEN
408 DEALLOCATE (molecule_kind_set(imolecule_kind)%g3x3_list)
409 END IF
410 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%g4x6_list)) THEN
411 DEALLOCATE (molecule_kind_set(imolecule_kind)%g4x6_list)
412 END IF
413 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%vsite_list)) THEN
414 DEALLOCATE (molecule_kind_set(imolecule_kind)%vsite_list)
415 END IF
416 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%fixd_list)) THEN
417 DEALLOCATE (molecule_kind_set(imolecule_kind)%fixd_list)
418 END IF
419 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%torsion_kind_set)) THEN
420 DO i = 1, SIZE(molecule_kind_set(imolecule_kind)%torsion_kind_set)
421 CALL torsion_kind_dealloc_ref(molecule_kind_set(imolecule_kind)%torsion_kind_set(i))
422 END DO
423 DEALLOCATE (molecule_kind_set(imolecule_kind)%torsion_kind_set)
424 END IF
425 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%shell_list)) THEN
426 DEALLOCATE (molecule_kind_set(imolecule_kind)%shell_list)
427 END IF
428 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%torsion_list)) THEN
429 DEALLOCATE (molecule_kind_set(imolecule_kind)%torsion_list)
430 END IF
431 IF (ASSOCIATED(molecule_kind_set(imolecule_kind)%molecule_list)) THEN
432 DEALLOCATE (molecule_kind_set(imolecule_kind)%molecule_list)
433 END IF
434 END DO
435
436 DEALLOCATE (molecule_kind_set)
437 END IF
438 NULLIFY (molecule_kind_set)
439
440 END SUBROUTINE deallocate_molecule_kind_set
441
442! **************************************************************************************************
443!> \brief Get informations about a molecule kind.
444!> \param molecule_kind ...
445!> \param atom_list ...
446!> \param bond_list ...
447!> \param bend_list ...
448!> \param ub_list ...
449!> \param impr_list ...
450!> \param opbend_list ...
451!> \param colv_list ...
452!> \param fixd_list ...
453!> \param g3x3_list ...
454!> \param g4x6_list ...
455!> \param vsite_list ...
456!> \param torsion_list ...
457!> \param shell_list ...
458!> \param name ...
459!> \param mass ...
460!> \param charge ...
461!> \param kind_number ...
462!> \param natom ...
463!> \param nbend ...
464!> \param nbond ...
465!> \param nub ...
466!> \param nimpr ...
467!> \param nopbend ...
468!> \param nconstraint ...
469!> \param nconstraint_fixd ...
470!> \param nfixd ...
471!> \param ncolv ...
472!> \param ng3x3 ...
473!> \param ng4x6 ...
474!> \param nvsite ...
475!> \param nfixd_restraint ...
476!> \param ng3x3_restraint ...
477!> \param ng4x6_restraint ...
478!> \param nvsite_restraint ...
479!> \param nrestraints ...
480!> \param nmolecule ...
481!> \param nsgf ...
482!> \param nshell ...
483!> \param ntorsion ...
484!> \param molecule_list ...
485!> \param nelectron ...
486!> \param nelectron_alpha ...
487!> \param nelectron_beta ...
488!> \param bond_kind_set ...
489!> \param bend_kind_set ...
490!> \param ub_kind_set ...
491!> \param impr_kind_set ...
492!> \param opbend_kind_set ...
493!> \param torsion_kind_set ...
494!> \param molname_generated ...
495!> \date 27.08.2003
496!> \author MK
497!> \version 1.0
498! **************************************************************************************************
499 SUBROUTINE get_molecule_kind(molecule_kind, atom_list, bond_list, bend_list, &
500 ub_list, impr_list, opbend_list, colv_list, fixd_list, &
501 g3x3_list, g4x6_list, vsite_list, torsion_list, shell_list, &
502 name, mass, charge, kind_number, natom, nbend, nbond, nub, &
503 nimpr, nopbend, nconstraint, nconstraint_fixd, nfixd, ncolv, ng3x3, ng4x6, &
504 nvsite, nfixd_restraint, ng3x3_restraint, ng4x6_restraint, &
505 nvsite_restraint, nrestraints, nmolecule, nsgf, nshell, ntorsion, &
506 molecule_list, nelectron, nelectron_alpha, nelectron_beta, &
507 bond_kind_set, bend_kind_set, &
508 ub_kind_set, impr_kind_set, opbend_kind_set, torsion_kind_set, &
509 molname_generated)
510
511 TYPE(molecule_kind_type), INTENT(IN) :: molecule_kind
512 TYPE(atom_type), DIMENSION(:), OPTIONAL, POINTER :: atom_list
513 TYPE(bond_type), DIMENSION(:), OPTIONAL, POINTER :: bond_list
514 TYPE(bend_type), DIMENSION(:), OPTIONAL, POINTER :: bend_list
515 TYPE(ub_type), DIMENSION(:), OPTIONAL, POINTER :: ub_list
516 TYPE(impr_type), DIMENSION(:), OPTIONAL, POINTER :: impr_list
517 TYPE(opbend_type), DIMENSION(:), OPTIONAL, POINTER :: opbend_list
518 TYPE(colvar_constraint_type), DIMENSION(:), &
519 OPTIONAL, POINTER :: colv_list
520 TYPE(fixd_constraint_type), DIMENSION(:), &
521 OPTIONAL, POINTER :: fixd_list
522 TYPE(g3x3_constraint_type), DIMENSION(:), &
523 OPTIONAL, POINTER :: g3x3_list
524 TYPE(g4x6_constraint_type), DIMENSION(:), &
525 OPTIONAL, POINTER :: g4x6_list
526 TYPE(vsite_constraint_type), DIMENSION(:), &
527 OPTIONAL, POINTER :: vsite_list
528 TYPE(torsion_type), DIMENSION(:), OPTIONAL, &
529 POINTER :: torsion_list
530 TYPE(shell_type), DIMENSION(:), OPTIONAL, POINTER :: shell_list
531 CHARACTER(LEN=default_string_length), &
532 INTENT(OUT), OPTIONAL :: name
533 REAL(kind=dp), OPTIONAL :: mass, charge
534 INTEGER, INTENT(OUT), OPTIONAL :: kind_number, natom, nbend, nbond, nub, &
535 nimpr, nopbend, nconstraint, &
536 nconstraint_fixd, nfixd
537 TYPE(colvar_counters), INTENT(out), OPTIONAL :: ncolv
538 INTEGER, INTENT(OUT), OPTIONAL :: ng3x3, ng4x6, nvsite, nfixd_restraint, ng3x3_restraint, &
539 ng4x6_restraint, nvsite_restraint, nrestraints, nmolecule, nsgf, nshell, ntorsion
540 INTEGER, DIMENSION(:), OPTIONAL, POINTER :: molecule_list
541 INTEGER, INTENT(OUT), OPTIONAL :: nelectron, nelectron_alpha, &
542 nelectron_beta
543 TYPE(bond_kind_type), DIMENSION(:), OPTIONAL, &
544 POINTER :: bond_kind_set
545 TYPE(bend_kind_type), DIMENSION(:), OPTIONAL, &
546 POINTER :: bend_kind_set
547 TYPE(ub_kind_type), DIMENSION(:), OPTIONAL, &
548 POINTER :: ub_kind_set
549 TYPE(impr_kind_type), DIMENSION(:), OPTIONAL, &
550 POINTER :: impr_kind_set
551 TYPE(opbend_kind_type), DIMENSION(:), OPTIONAL, &
552 POINTER :: opbend_kind_set
553 TYPE(torsion_kind_type), DIMENSION(:), OPTIONAL, &
554 POINTER :: torsion_kind_set
555 LOGICAL, INTENT(OUT), OPTIONAL :: molname_generated
556
557 INTEGER :: i
558
559 IF (PRESENT(atom_list)) atom_list => molecule_kind%atom_list
560 IF (PRESENT(bend_list)) bend_list => molecule_kind%bend_list
561 IF (PRESENT(bond_list)) bond_list => molecule_kind%bond_list
562 IF (PRESENT(impr_list)) impr_list => molecule_kind%impr_list
563 IF (PRESENT(opbend_list)) opbend_list => molecule_kind%opbend_list
564 IF (PRESENT(ub_list)) ub_list => molecule_kind%ub_list
565 IF (PRESENT(bond_kind_set)) bond_kind_set => molecule_kind%bond_kind_set
566 IF (PRESENT(bend_kind_set)) bend_kind_set => molecule_kind%bend_kind_set
567 IF (PRESENT(ub_kind_set)) ub_kind_set => molecule_kind%ub_kind_set
568 IF (PRESENT(impr_kind_set)) impr_kind_set => molecule_kind%impr_kind_set
569 IF (PRESENT(opbend_kind_set)) opbend_kind_set => molecule_kind%opbend_kind_set
570 IF (PRESENT(torsion_kind_set)) torsion_kind_set => molecule_kind%torsion_kind_set
571 IF (PRESENT(colv_list)) colv_list => molecule_kind%colv_list
572 IF (PRESENT(g3x3_list)) g3x3_list => molecule_kind%g3x3_list
573 IF (PRESENT(g4x6_list)) g4x6_list => molecule_kind%g4x6_list
574 IF (PRESENT(vsite_list)) vsite_list => molecule_kind%vsite_list
575 IF (PRESENT(fixd_list)) fixd_list => molecule_kind%fixd_list
576 IF (PRESENT(torsion_list)) torsion_list => molecule_kind%torsion_list
577 IF (PRESENT(shell_list)) shell_list => molecule_kind%shell_list
578 IF (PRESENT(name)) name = molecule_kind%name
579 IF (PRESENT(molname_generated)) molname_generated = molecule_kind%molname_generated
580 IF (PRESENT(mass)) mass = molecule_kind%mass
581 IF (PRESENT(charge)) charge = molecule_kind%charge
582 IF (PRESENT(kind_number)) kind_number = molecule_kind%kind_number
583 IF (PRESENT(natom)) natom = molecule_kind%natom
584 IF (PRESENT(nbend)) nbend = molecule_kind%nbend
585 IF (PRESENT(nbond)) nbond = molecule_kind%nbond
586 IF (PRESENT(nub)) nub = molecule_kind%nub
587 IF (PRESENT(nimpr)) nimpr = molecule_kind%nimpr
588 IF (PRESENT(nopbend)) nopbend = molecule_kind%nopbend
589 IF (PRESENT(nconstraint)) nconstraint = (molecule_kind%ncolv%ntot - molecule_kind%ncolv%nrestraint) + &
590 3*(molecule_kind%ng3x3 - molecule_kind%ng3x3_restraint) + &
591 6*(molecule_kind%ng4x6 - molecule_kind%ng4x6_restraint) + &
592 3*(molecule_kind%nvsite - molecule_kind%nvsite_restraint)
593 IF (PRESENT(ncolv)) ncolv = molecule_kind%ncolv
594 IF (PRESENT(ng3x3)) ng3x3 = molecule_kind%ng3x3
595 IF (PRESENT(ng4x6)) ng4x6 = molecule_kind%ng4x6
596 IF (PRESENT(nvsite)) nvsite = molecule_kind%nvsite
597 ! Number of atoms that have one or more components fixed
598 IF (PRESENT(nfixd)) nfixd = molecule_kind%nfixd
599 ! Number of degrees of freedom fixed
600 IF (PRESENT(nconstraint_fixd)) THEN
601 nconstraint_fixd = 0
602 IF (molecule_kind%nfixd /= 0) THEN
603 DO i = 1, SIZE(molecule_kind%fixd_list)
604 IF (molecule_kind%fixd_list(i)%restraint%active) cycle
605 SELECT CASE (molecule_kind%fixd_list(i)%itype)
607 nconstraint_fixd = nconstraint_fixd + 1
609 nconstraint_fixd = nconstraint_fixd + 2
610 CASE (use_perd_xyz)
611 nconstraint_fixd = nconstraint_fixd + 3
612 END SELECT
613 END DO
614 END IF
615 END IF
616 IF (PRESENT(ng3x3_restraint)) ng3x3_restraint = molecule_kind%ng3x3_restraint
617 IF (PRESENT(ng4x6_restraint)) ng4x6_restraint = molecule_kind%ng4x6_restraint
618 IF (PRESENT(nvsite_restraint)) nvsite_restraint = molecule_kind%nvsite_restraint
619 IF (PRESENT(nfixd_restraint)) nfixd_restraint = molecule_kind%nfixd_restraint
620 IF (PRESENT(nrestraints)) nrestraints = molecule_kind%ncolv%nrestraint + &
621 molecule_kind%ng3x3_restraint + &
622 molecule_kind%ng4x6_restraint + &
623 molecule_kind%nvsite_restraint
624 IF (PRESENT(nmolecule)) nmolecule = molecule_kind%nmolecule
625 IF (PRESENT(nshell)) nshell = molecule_kind%nshell
626 IF (PRESENT(ntorsion)) ntorsion = molecule_kind%ntorsion
627 IF (PRESENT(nsgf)) nsgf = molecule_kind%nsgf
628 IF (PRESENT(nelectron)) nelectron = molecule_kind%nelectron
629 IF (PRESENT(nelectron_alpha)) nelectron_alpha = molecule_kind%nelectron_beta
630 IF (PRESENT(nelectron_beta)) nelectron_beta = molecule_kind%nelectron_alpha
631 IF (PRESENT(molecule_list)) molecule_list => molecule_kind%molecule_list
632
633 END SUBROUTINE get_molecule_kind
634
635! **************************************************************************************************
636!> \brief Get informations about a molecule kind set.
637!> \param molecule_kind_set ...
638!> \param maxatom ...
639!> \param natom ...
640!> \param nbond ...
641!> \param nbend ...
642!> \param nub ...
643!> \param ntorsion ...
644!> \param nimpr ...
645!> \param nopbend ...
646!> \param nconstraint ...
647!> \param nconstraint_fixd ...
648!> \param nmolecule ...
649!> \param nrestraints ...
650!> \date 27.08.2003
651!> \author MK
652!> \version 1.0
653! **************************************************************************************************
654 SUBROUTINE get_molecule_kind_set(molecule_kind_set, maxatom, natom, &
655 nbond, nbend, nub, ntorsion, nimpr, nopbend, &
656 nconstraint, nconstraint_fixd, nmolecule, &
657 nrestraints)
658
659 TYPE(molecule_kind_type), DIMENSION(:), INTENT(IN) :: molecule_kind_set
660 INTEGER, INTENT(OUT), OPTIONAL :: maxatom, natom, nbond, nbend, nub, &
661 ntorsion, nimpr, nopbend, nconstraint, &
662 nconstraint_fixd, nmolecule, &
663 nrestraints
664
665 INTEGER :: ibend, ibond, iimpr, imolecule_kind, iopbend, itorsion, iub, na, nc, nc_fixd, &
666 nfixd_restraint, nm, nmolecule_kind, nrestraints_tot
667
668 IF (PRESENT(maxatom)) maxatom = 0
669 IF (PRESENT(natom)) natom = 0
670 IF (PRESENT(nbond)) nbond = 0
671 IF (PRESENT(nbend)) nbend = 0
672 IF (PRESENT(nub)) nub = 0
673 IF (PRESENT(ntorsion)) ntorsion = 0
674 IF (PRESENT(nimpr)) nimpr = 0
675 IF (PRESENT(nopbend)) nopbend = 0
676 IF (PRESENT(nconstraint)) nconstraint = 0
677 IF (PRESENT(nconstraint_fixd)) nconstraint_fixd = 0
678 IF (PRESENT(nrestraints)) nrestraints = 0
679 IF (PRESENT(nmolecule)) nmolecule = 0
680
681 nmolecule_kind = SIZE(molecule_kind_set)
682
683 DO imolecule_kind = 1, nmolecule_kind
684 associate(molecule_kind => molecule_kind_set(imolecule_kind))
685
686 CALL get_molecule_kind(molecule_kind=molecule_kind, &
687 natom=na, &
688 nbond=ibond, &
689 nbend=ibend, &
690 nub=iub, &
691 ntorsion=itorsion, &
692 nimpr=iimpr, &
693 nopbend=iopbend, &
694 nconstraint=nc, &
695 nconstraint_fixd=nc_fixd, &
696 nfixd_restraint=nfixd_restraint, &
697 nrestraints=nrestraints_tot, &
698 nmolecule=nm)
699 IF (PRESENT(maxatom)) maxatom = max(maxatom, na)
700 IF (PRESENT(natom)) natom = natom + na*nm
701 IF (PRESENT(nbond)) nbond = nbond + ibond*nm
702 IF (PRESENT(nbend)) nbend = nbend + ibend*nm
703 IF (PRESENT(nub)) nub = nub + iub*nm
704 IF (PRESENT(ntorsion)) ntorsion = ntorsion + itorsion*nm
705 IF (PRESENT(nimpr)) nimpr = nimpr + iimpr*nm
706 IF (PRESENT(nopbend)) nopbend = nopbend + iopbend*nm
707 IF (PRESENT(nconstraint)) nconstraint = nconstraint + nc*nm + nc_fixd
708 IF (PRESENT(nconstraint_fixd)) nconstraint_fixd = nconstraint_fixd + nc_fixd
709 IF (PRESENT(nmolecule)) nmolecule = nmolecule + nm
710 IF (PRESENT(nrestraints)) nrestraints = nrestraints + nm*nrestraints_tot + nfixd_restraint
711
712 END associate
713 END DO
714
715 END SUBROUTINE get_molecule_kind_set
716
717! **************************************************************************************************
718!> \brief Set the components of a molecule kind.
719!> \param molecule_kind ...
720!> \param name ...
721!> \param mass ...
722!> \param charge ...
723!> \param kind_number ...
724!> \param molecule_list ...
725!> \param atom_list ...
726!> \param nbond ...
727!> \param bond_list ...
728!> \param nbend ...
729!> \param bend_list ...
730!> \param nub ...
731!> \param ub_list ...
732!> \param nimpr ...
733!> \param impr_list ...
734!> \param nopbend ...
735!> \param opbend_list ...
736!> \param ntorsion ...
737!> \param torsion_list ...
738!> \param fixd_list ...
739!> \param ncolv ...
740!> \param colv_list ...
741!> \param ng3x3 ...
742!> \param g3x3_list ...
743!> \param ng4x6 ...
744!> \param nfixd ...
745!> \param g4x6_list ...
746!> \param nvsite ...
747!> \param vsite_list ...
748!> \param ng3x3_restraint ...
749!> \param ng4x6_restraint ...
750!> \param nfixd_restraint ...
751!> \param nshell ...
752!> \param shell_list ...
753!> \param nvsite_restraint ...
754!> \param bond_kind_set ...
755!> \param bend_kind_set ...
756!> \param ub_kind_set ...
757!> \param torsion_kind_set ...
758!> \param impr_kind_set ...
759!> \param opbend_kind_set ...
760!> \param nelectron ...
761!> \param nsgf ...
762!> \param molname_generated ...
763!> \date 27.08.2003
764!> \author MK
765!> \version 1.0
766! **************************************************************************************************
767 SUBROUTINE set_molecule_kind(molecule_kind, name, mass, charge, kind_number, &
768 molecule_list, atom_list, nbond, bond_list, &
769 nbend, bend_list, nub, ub_list, nimpr, impr_list, &
770 nopbend, opbend_list, ntorsion, &
771 torsion_list, fixd_list, ncolv, colv_list, ng3x3, &
772 g3x3_list, ng4x6, nfixd, g4x6_list, nvsite, &
773 vsite_list, ng3x3_restraint, ng4x6_restraint, &
774 nfixd_restraint, nshell, shell_list, &
775 nvsite_restraint, bond_kind_set, bend_kind_set, &
776 ub_kind_set, torsion_kind_set, impr_kind_set, &
777 opbend_kind_set, nelectron, nsgf, &
778 molname_generated)
779
780 TYPE(molecule_kind_type), INTENT(INOUT) :: molecule_kind
781 CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: name
782 REAL(kind=dp), OPTIONAL :: mass, charge
783 INTEGER, INTENT(IN), OPTIONAL :: kind_number
784 INTEGER, DIMENSION(:), OPTIONAL, POINTER :: molecule_list
785 TYPE(atom_type), DIMENSION(:), OPTIONAL, POINTER :: atom_list
786 INTEGER, INTENT(IN), OPTIONAL :: nbond
787 TYPE(bond_type), DIMENSION(:), OPTIONAL, POINTER :: bond_list
788 INTEGER, INTENT(IN), OPTIONAL :: nbend
789 TYPE(bend_type), DIMENSION(:), OPTIONAL, POINTER :: bend_list
790 INTEGER, INTENT(IN), OPTIONAL :: nub
791 TYPE(ub_type), DIMENSION(:), OPTIONAL, POINTER :: ub_list
792 INTEGER, INTENT(IN), OPTIONAL :: nimpr
793 TYPE(impr_type), DIMENSION(:), OPTIONAL, POINTER :: impr_list
794 INTEGER, INTENT(IN), OPTIONAL :: nopbend
795 TYPE(opbend_type), DIMENSION(:), OPTIONAL, POINTER :: opbend_list
796 INTEGER, INTENT(IN), OPTIONAL :: ntorsion
797 TYPE(torsion_type), DIMENSION(:), OPTIONAL, &
798 POINTER :: torsion_list
799 TYPE(fixd_constraint_type), DIMENSION(:), &
800 OPTIONAL, POINTER :: fixd_list
801 TYPE(colvar_counters), INTENT(IN), OPTIONAL :: ncolv
802 TYPE(colvar_constraint_type), DIMENSION(:), &
803 OPTIONAL, POINTER :: colv_list
804 INTEGER, INTENT(IN), OPTIONAL :: ng3x3
805 TYPE(g3x3_constraint_type), DIMENSION(:), &
806 OPTIONAL, POINTER :: g3x3_list
807 INTEGER, INTENT(IN), OPTIONAL :: ng4x6, nfixd
808 TYPE(g4x6_constraint_type), DIMENSION(:), &
809 OPTIONAL, POINTER :: g4x6_list
810 INTEGER, INTENT(IN), OPTIONAL :: nvsite
811 TYPE(vsite_constraint_type), DIMENSION(:), &
812 OPTIONAL, POINTER :: vsite_list
813 INTEGER, INTENT(IN), OPTIONAL :: ng3x3_restraint, ng4x6_restraint, &
814 nfixd_restraint, nshell
815 TYPE(shell_type), DIMENSION(:), OPTIONAL, POINTER :: shell_list
816 INTEGER, INTENT(IN), OPTIONAL :: nvsite_restraint
817 TYPE(bond_kind_type), DIMENSION(:), OPTIONAL, &
818 POINTER :: bond_kind_set
819 TYPE(bend_kind_type), DIMENSION(:), OPTIONAL, &
820 POINTER :: bend_kind_set
821 TYPE(ub_kind_type), DIMENSION(:), OPTIONAL, &
822 POINTER :: ub_kind_set
823 TYPE(torsion_kind_type), DIMENSION(:), OPTIONAL, &
824 POINTER :: torsion_kind_set
825 TYPE(impr_kind_type), DIMENSION(:), OPTIONAL, &
826 POINTER :: impr_kind_set
827 TYPE(opbend_kind_type), DIMENSION(:), OPTIONAL, &
828 POINTER :: opbend_kind_set
829 INTEGER, INTENT(IN), OPTIONAL :: nelectron, nsgf
830 LOGICAL, INTENT(IN), OPTIONAL :: molname_generated
831
832 INTEGER :: n
833
834 IF (PRESENT(atom_list)) THEN
835 n = SIZE(atom_list)
836 molecule_kind%natom = n
837 molecule_kind%atom_list => atom_list
838 END IF
839 IF (PRESENT(molname_generated)) molecule_kind%molname_generated = molname_generated
840 IF (PRESENT(name)) molecule_kind%name = name
841 IF (PRESENT(mass)) molecule_kind%mass = mass
842 IF (PRESENT(charge)) molecule_kind%charge = charge
843 IF (PRESENT(kind_number)) molecule_kind%kind_number = kind_number
844 IF (PRESENT(nbond)) molecule_kind%nbond = nbond
845 IF (PRESENT(bond_list)) molecule_kind%bond_list => bond_list
846 IF (PRESENT(nbend)) molecule_kind%nbend = nbend
847 IF (PRESENT(nelectron)) molecule_kind%nelectron = nelectron
848 IF (PRESENT(nsgf)) molecule_kind%nsgf = nsgf
849 IF (PRESENT(bend_list)) molecule_kind%bend_list => bend_list
850 IF (PRESENT(nub)) molecule_kind%nub = nub
851 IF (PRESENT(ub_list)) molecule_kind%ub_list => ub_list
852 IF (PRESENT(ntorsion)) molecule_kind%ntorsion = ntorsion
853 IF (PRESENT(torsion_list)) molecule_kind%torsion_list => torsion_list
854 IF (PRESENT(nimpr)) molecule_kind%nimpr = nimpr
855 IF (PRESENT(impr_list)) molecule_kind%impr_list => impr_list
856 IF (PRESENT(nopbend)) molecule_kind%nopbend = nopbend
857 IF (PRESENT(opbend_list)) molecule_kind%opbend_list => opbend_list
858 IF (PRESENT(ncolv)) molecule_kind%ncolv = ncolv
859 IF (PRESENT(colv_list)) molecule_kind%colv_list => colv_list
860 IF (PRESENT(ng3x3)) molecule_kind%ng3x3 = ng3x3
861 IF (PRESENT(g3x3_list)) molecule_kind%g3x3_list => g3x3_list
862 IF (PRESENT(ng4x6)) molecule_kind%ng4x6 = ng4x6
863 IF (PRESENT(nvsite)) molecule_kind%nvsite = nvsite
864 IF (PRESENT(nfixd)) molecule_kind%nfixd = nfixd
865 IF (PRESENT(nfixd_restraint)) molecule_kind%nfixd_restraint = nfixd_restraint
866 IF (PRESENT(ng3x3_restraint)) molecule_kind%ng3x3_restraint = ng3x3_restraint
867 IF (PRESENT(ng4x6_restraint)) molecule_kind%ng4x6_restraint = ng4x6_restraint
868 IF (PRESENT(nvsite_restraint)) molecule_kind%nvsite_restraint = nvsite_restraint
869 IF (PRESENT(g4x6_list)) molecule_kind%g4x6_list => g4x6_list
870 IF (PRESENT(vsite_list)) molecule_kind%vsite_list => vsite_list
871 IF (PRESENT(fixd_list)) molecule_kind%fixd_list => fixd_list
872 IF (PRESENT(bond_kind_set)) molecule_kind%bond_kind_set => bond_kind_set
873 IF (PRESENT(bend_kind_set)) molecule_kind%bend_kind_set => bend_kind_set
874 IF (PRESENT(ub_kind_set)) molecule_kind%ub_kind_set => ub_kind_set
875 IF (PRESENT(torsion_kind_set)) molecule_kind%torsion_kind_set => torsion_kind_set
876 IF (PRESENT(impr_kind_set)) molecule_kind%impr_kind_set => impr_kind_set
877 IF (PRESENT(opbend_kind_set)) molecule_kind%opbend_kind_set => opbend_kind_set
878 IF (PRESENT(nshell)) molecule_kind%nshell = nshell
879 IF (PRESENT(shell_list)) molecule_kind%shell_list => shell_list
880 IF (PRESENT(molecule_list)) THEN
881 n = SIZE(molecule_list)
882 molecule_kind%nmolecule = n
883 molecule_kind%molecule_list => molecule_list
884 END IF
885 END SUBROUTINE set_molecule_kind
886
887! **************************************************************************************************
888!> \brief Write a molecule kind data set to the output unit.
889!> \param molecule_kind ...
890!> \param output_unit ...
891!> \date 24.09.2003
892!> \author MK
893!> \version 1.0
894! **************************************************************************************************
895 SUBROUTINE write_molecule_kind(molecule_kind, output_unit)
896 TYPE(molecule_kind_type), INTENT(IN) :: molecule_kind
897 INTEGER, INTENT(in) :: output_unit
898
899 CHARACTER(LEN=default_string_length) :: name
900 INTEGER :: iatom, imolecule, natom, nmolecule
901 TYPE(atomic_kind_type), POINTER :: atomic_kind
902
903 IF (output_unit > 0) THEN
904 natom = SIZE(molecule_kind%atom_list)
905 nmolecule = SIZE(molecule_kind%molecule_list)
906
907 IF (natom == 1) THEN
908 atomic_kind => molecule_kind%atom_list(1)%atomic_kind
909 CALL get_atomic_kind(atomic_kind=atomic_kind, name=name)
910 WRITE (unit=output_unit, fmt="(/,T2,I5,A,T36,A,A,T64,A)") &
911 molecule_kind%kind_number, &
912 ". Molecule kind: "//trim(molecule_kind%name), &
913 "Atomic kind name: ", trim(name)
914 WRITE (unit=output_unit, fmt="(T9,A,L1,T55,A,T75,I6)") &
915 "Automatic name: ", molecule_kind%molname_generated, &
916 "Number of molecules:", nmolecule
917 ELSE
918 WRITE (unit=output_unit, fmt="(/,T2,I5,A,T50,A,T75,I6,/,T22,A)") &
919 molecule_kind%kind_number, &
920 ". Molecule kind: "//trim(molecule_kind%name), &
921 "Number of atoms: ", natom, &
922 "Atom Atomic kind name"
923 DO iatom = 1, natom
924 atomic_kind => molecule_kind%atom_list(iatom)%atomic_kind
925 CALL get_atomic_kind(atomic_kind=atomic_kind, name=name)
926 WRITE (unit=output_unit, fmt="(T20,I6,(7X,A18))") &
927 iatom, trim(name)
928 END DO
929 WRITE (unit=output_unit, fmt="(/,T9,A,L1)") &
930 "The name was automatically generated: ", &
931 molecule_kind%molname_generated
932 WRITE (unit=output_unit, fmt="(T9,A,I6,/,T9,A,(T30,5I10))") &
933 "Number of molecules: ", nmolecule, "Molecule list:", &
934 (molecule_kind%molecule_list(imolecule), imolecule=1, nmolecule)
935 IF (molecule_kind%nbond > 0) &
936 WRITE (unit=output_unit, fmt="(1X,A30,I6)") &
937 "Number of bonds: ", molecule_kind%nbond
938 IF (molecule_kind%nbend > 0) &
939 WRITE (unit=output_unit, fmt="(1X,A30,I6)") &
940 "Number of bends: ", molecule_kind%nbend
941 IF (molecule_kind%nub > 0) &
942 WRITE (unit=output_unit, fmt="(1X,A30,I6)") &
943 "Number of Urey-Bradley:", molecule_kind%nub
944 IF (molecule_kind%ntorsion > 0) &
945 WRITE (unit=output_unit, fmt="(1X,A30,I6)") &
946 "Number of torsions: ", molecule_kind%ntorsion
947 IF (molecule_kind%nimpr > 0) &
948 WRITE (unit=output_unit, fmt="(1X,A30,I6)") &
949 "Number of improper: ", molecule_kind%nimpr
950 IF (molecule_kind%nopbend > 0) &
951 WRITE (unit=output_unit, fmt="(1X,A30,I6)") &
952 "Number of out opbends: ", molecule_kind%nopbend
953 END IF
954 END IF
955 END SUBROUTINE write_molecule_kind
956
957! **************************************************************************************************
958!> \brief Write a moleculeatomic kind set data set to the output unit.
959!> \param molecule_kind_set ...
960!> \param subsys_section ...
961!> \date 24.09.2003
962!> \author MK
963!> \version 1.0
964! **************************************************************************************************
965 SUBROUTINE write_molecule_kind_set(molecule_kind_set, subsys_section)
966 TYPE(molecule_kind_type), DIMENSION(:), INTENT(IN) :: molecule_kind_set
967 TYPE(section_vals_type), INTENT(IN) :: subsys_section
968
969 CHARACTER(len=*), PARAMETER :: routinen = 'write_molecule_kind_set'
970
971 INTEGER :: handle, imolecule_kind, natom, nbend, &
972 nbond, nimpr, nmolecule, &
973 nmolecule_kind, nopbend, ntors, &
974 ntotal, nub, output_unit
975 LOGICAL :: all_single_atoms
976 TYPE(cp_logger_type), POINTER :: logger
977
978 CALL timeset(routinen, handle)
979
980 NULLIFY (logger)
981 logger => cp_get_default_logger()
982 output_unit = cp_print_key_unit_nr(logger, subsys_section, &
983 "PRINT%MOLECULES", extension=".Log")
984 IF (output_unit > 0) THEN
985 WRITE (unit=output_unit, fmt="(/,/,T2,A)") "MOLECULE KIND INFORMATION"
986
987 nmolecule_kind = SIZE(molecule_kind_set)
988
989 all_single_atoms = .true.
990 DO imolecule_kind = 1, nmolecule_kind
991 natom = SIZE(molecule_kind_set(imolecule_kind)%atom_list)
992 nmolecule = SIZE(molecule_kind_set(imolecule_kind)%molecule_list)
993 IF (natom*nmolecule > 1) all_single_atoms = .false.
994 END DO
995
996 IF (all_single_atoms) THEN
997 WRITE (unit=output_unit, fmt="(/,/,T2,A)") &
998 "All atoms are their own molecule, skipping detailed information"
999 ELSE
1000 DO imolecule_kind = 1, nmolecule_kind
1001 CALL write_molecule_kind(molecule_kind_set(imolecule_kind), output_unit)
1002 END DO
1003 END IF
1004
1005 CALL get_molecule_kind_set(molecule_kind_set=molecule_kind_set, &
1006 nbond=nbond, &
1007 nbend=nbend, &
1008 nub=nub, &
1009 ntorsion=ntors, &
1010 nimpr=nimpr, &
1011 nopbend=nopbend)
1012 ntotal = nbond + nbend + nub + ntors + nimpr + nopbend
1013 IF (ntotal > 0) THEN
1014 WRITE (unit=output_unit, fmt="(/,/,T2,A,T45,A30,I6)") &
1015 "MOLECULE KIND SET INFORMATION", &
1016 "Total Number of bonds: ", nbond
1017 WRITE (unit=output_unit, fmt="(T45,A30,I6)") &
1018 "Total Number of bends: ", nbend
1019 WRITE (unit=output_unit, fmt="(T45,A30,I6)") &
1020 "Total Number of Urey-Bradley:", nub
1021 WRITE (unit=output_unit, fmt="(T45,A30,I6)") &
1022 "Total Number of torsions: ", ntors
1023 WRITE (unit=output_unit, fmt="(T45,A30,I6)") &
1024 "Total Number of improper: ", nimpr
1025 WRITE (unit=output_unit, fmt="(T45,A30,I6)") &
1026 "Total Number of opbends: ", nopbend
1027 END IF
1028 END IF
1029 CALL cp_print_key_finished_output(output_unit, logger, subsys_section, &
1030 "PRINT%MOLECULES")
1031
1032 CALL timestop(handle)
1033
1034 END SUBROUTINE write_molecule_kind_set
1035
1036END MODULE molecule_kind_types
Define the atomic kind types and their sub types.
subroutine, public get_atomic_kind(atomic_kind, fist_potential, element_symbol, name, mass, kind_number, natom, atom_list, rcov, rvdw, z, qeff, apol, cpol, mm_radius, shell, shell_active, damping)
Get attributes of an atomic kind.
Handles all functions related to the CELL.
Definition cell_types.F:15
integer, parameter, public use_perd_xyz
Definition cell_types.F:42
integer, parameter, public use_perd_y
Definition cell_types.F:42
integer, parameter, public use_perd_xz
Definition cell_types.F:42
integer, parameter, public use_perd_x
Definition cell_types.F:42
integer, parameter, public use_perd_z
Definition cell_types.F:42
integer, parameter, public use_perd_yz
Definition cell_types.F:42
integer, parameter, public use_perd_xy
Definition cell_types.F:42
Initialize the collective variables types.
integer, parameter, public population_colvar_id
integer, parameter, public acid_hyd_dist_colvar_id
integer, parameter, public xyz_outerdiag_colvar_id
integer, parameter, public plane_plane_angle_colvar_id
integer, parameter, public plane_distance_colvar_id
integer, parameter, public combine_colvar_id
integer, parameter, public gyration_colvar_id
integer, parameter, public rotation_colvar_id
integer, parameter, public hydronium_dist_colvar_id
integer, parameter, public coord_colvar_id
integer, parameter, public dfunct_colvar_id
integer, parameter, public no_colvar_id
integer, parameter, public angle_colvar_id
integer, parameter, public qparm_colvar_id
integer, parameter, public dist_colvar_id
integer, parameter, public hydronium_shell_colvar_id
integer, parameter, public torsion_colvar_id
integer, parameter, public xyz_diag_colvar_id
integer, parameter, public reaction_path_colvar_id
integer, parameter, public acid_hyd_shell_colvar_id
various routines to log and control the output. The idea is that decisions about where to log should ...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
subroutine, public cp_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, on_file, mpi_io)
should be called after you finish working with a unit obtained with cp_print_key_unit_nr,...
Define all structure types related to force field kinds.
integer, parameter, public do_ff_undef
pure subroutine, public torsion_kind_dealloc_ref(torsion_kind)
Deallocate a torsion kind element.
pure subroutine, public ub_kind_dealloc_ref(ub_kind_set)
Deallocate a ub kind set.
pure subroutine, public impr_kind_dealloc_ref()
Deallocate a impr kind element.
objects that represent the structure of input sections and the data contained in an input section
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
Define the molecule kind structure types and the corresponding functionality.
subroutine, public get_molecule_kind(molecule_kind, atom_list, bond_list, bend_list, ub_list, impr_list, opbend_list, colv_list, fixd_list, g3x3_list, g4x6_list, vsite_list, torsion_list, shell_list, name, mass, charge, kind_number, natom, nbend, nbond, nub, nimpr, nopbend, nconstraint, nconstraint_fixd, nfixd, ncolv, ng3x3, ng4x6, nvsite, nfixd_restraint, ng3x3_restraint, ng4x6_restraint, nvsite_restraint, nrestraints, nmolecule, nsgf, nshell, ntorsion, molecule_list, nelectron, nelectron_alpha, nelectron_beta, bond_kind_set, bend_kind_set, ub_kind_set, impr_kind_set, opbend_kind_set, torsion_kind_set, molname_generated)
Get informations about a molecule kind.
subroutine, public setup_colvar_counters(colv_list, ncolv)
...
subroutine, public set_molecule_kind(molecule_kind, name, mass, charge, kind_number, molecule_list, atom_list, nbond, bond_list, nbend, bend_list, nub, ub_list, nimpr, impr_list, nopbend, opbend_list, ntorsion, torsion_list, fixd_list, ncolv, colv_list, ng3x3, g3x3_list, ng4x6, nfixd, g4x6_list, nvsite, vsite_list, ng3x3_restraint, ng4x6_restraint, nfixd_restraint, nshell, shell_list, nvsite_restraint, bond_kind_set, bend_kind_set, ub_kind_set, torsion_kind_set, impr_kind_set, opbend_kind_set, nelectron, nsgf, molname_generated)
Set the components of a molecule kind.
subroutine, public deallocate_molecule_kind_set(molecule_kind_set)
Deallocate a molecule kind set.
subroutine, public get_molecule_kind_set(molecule_kind_set, maxatom, natom, nbond, nbend, nub, ntorsion, nimpr, nopbend, nconstraint, nconstraint_fixd, nmolecule, nrestraints)
Get informations about a molecule kind set.
subroutine, public write_molecule_kind_set(molecule_kind_set, subsys_section)
Write a moleculeatomic kind set data set to the output unit.
subroutine, public allocate_molecule_kind_set(molecule_kind_set, nmolecule_kind)
Allocate and initialize a molecule kind set.
Handles all possible kinds of restraints in CP2K.
Definition restraint.F:14
Provides all information about an atomic kind.
type of a logger, at the moment it contains just a print level starting at which level it should be l...