45#include "../base/base_uses.f90"
51 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'molecule_kind_types'
57 INTEGER :: id_name = 0
62 CHARACTER(LEN=default_string_length) :: name =
""
67 INTEGER :: a = 0, b = 0
73 INTEGER :: a = 0, b = 0, c = 0
79 INTEGER :: a = 0, b = 0, c = 0
85 INTEGER :: a = 0, b = 0, c = 0, d = 0
91 INTEGER :: a = 0, b = 0, c = 0, d = 0
97 INTEGER :: a = 0, b = 0, c = 0, d = 0
103 LOGICAL :: active = .false.
104 REAL(kind=
dp) :: k0 = 0.0_dp
105 END TYPE restraint_type
110 INTEGER :: inp_seq_num = 0
111 LOGICAL :: use_points = .false.
112 REAL(kind=
dp) :: expected_value = 0.0_dp
113 REAL(kind=
dp) :: expected_value_growth_speed = 0.0_dp
114 INTEGER,
POINTER,
DIMENSION(:) :: i_atoms => null()
119 INTEGER :: a = 0, b = 0, c = 0
120 REAL(kind=
dp) :: dab = 0.0_dp, dac = 0.0_dp, dbc = 0.0_dp
125 INTEGER :: a = 0, b = 0, c = 0, d = 0
126 REAL(kind=
dp) :: dab = 0.0_dp, dac = 0.0_dp, dbc = 0.0_dp, &
127 dad = 0.0_dp, dbd = 0.0_dp, dcd = 0.0_dp
132 INTEGER :: a = 0, b = 0, c = 0, d = 0
133 REAL(kind=
dp) :: wbc = 0.0_dp, wdc = 0.0_dp
139 INTEGER :: fixd = 0, itype = 0
140 REAL(kind=
dp),
DIMENSION(3) :: coord = 0.0_dp
144 INTEGER :: ifixd_index = 0, ikind = 0
149 TYPE(
atom_type),
DIMENSION(:),
POINTER :: atom_list => null()
151 TYPE(
bond_type),
DIMENSION(:),
POINTER :: bond_list => null()
153 TYPE(
bend_type),
DIMENSION(:),
POINTER :: bend_list => null()
155 TYPE(
ub_type),
DIMENSION(:),
POINTER :: ub_list => null()
159 TYPE(
impr_type),
DIMENSION(:),
POINTER :: impr_list => null()
163 POINTER :: colv_list => null()
168 TYPE(
shell_type),
DIMENSION(:),
POINTER :: shell_list => null()
169 CHARACTER(LEN=default_string_length) :: name =
""
170 REAL(kind=
dp) :: charge = 0.0_dp, &
172 INTEGER :: kind_number = 0, &
181 ng3x3_restraint = 0, &
183 ng4x6_restraint = 0, &
185 nvsite_restraint = 0, &
187 nfixd_restraint = 0, &
191 INTEGER :: nsgf = 0, &
193 nelectron_alpha = 0, &
195 INTEGER,
DIMENSION(:),
POINTER :: molecule_list => null()
196 LOGICAL :: molname_generated = .false.
239 IF (
ASSOCIATED(colv_list))
THEN
240 DO k = 1,
SIZE(colv_list)
241 IF (colv_list(k)%restraint%active) ncolv%nrestraint = ncolv%nrestraint + 1
242 SELECT CASE (colv_list(k)%type_id)
244 ncolv%nangle = ncolv%nangle + 1
246 ncolv%ncoord = ncolv%ncoord + 1
248 ncolv%npopulation = ncolv%npopulation + 1
250 ncolv%ngyration = ncolv%ngyration + 1
252 ncolv%nrot = ncolv%nrot + 1
254 ncolv%ndist = ncolv%ndist + 1
256 ncolv%ndfunct = ncolv%ndfunct + 1
258 ncolv%nplane_dist = ncolv%nplane_dist + 1
260 ncolv%nplane_angle = ncolv%nplane_angle + 1
262 ncolv%ntorsion = ncolv%ntorsion + 1
264 ncolv%nqparm = ncolv%nqparm + 1
266 ncolv%nxyz_diag = ncolv%nxyz_diag + 1
268 ncolv%nxyz_outerdiag = ncolv%nxyz_outerdiag + 1
270 ncolv%nhydronium_shell = ncolv%nhydronium_shell + 1
272 ncolv%nhydronium_dist = ncolv%nhydronium_dist + 1
274 ncolv%nacid_hyd_dist = ncolv%nacid_hyd_dist + 1
276 ncolv%nacid_hyd_shell = ncolv%nacid_hyd_shell + 1
278 ncolv%nreactionpath = ncolv%nreactionpath + 1
280 ncolv%ncombinecvs = ncolv%ncombinecvs + 1
286 ncolv%ntot = ncolv%ndist + &
290 ncolv%nplane_dist + &
291 ncolv%nplane_angle + &
296 ncolv%nxyz_outerdiag + &
297 ncolv%nhydronium_shell + &
298 ncolv%nhydronium_dist + &
299 ncolv%nacid_hyd_dist + &
300 ncolv%nacid_hyd_shell + &
301 ncolv%nreactionpath + &
302 ncolv%ncombinecvs + &
303 ncolv%npopulation + &
318 INTEGER,
INTENT(IN) :: nmolecule_kind
320 INTEGER :: imolecule_kind
322 IF (
ASSOCIATED(molecule_kind_set))
THEN
326 ALLOCATE (molecule_kind_set(nmolecule_kind))
328 DO imolecule_kind = 1, nmolecule_kind
329 molecule_kind_set(imolecule_kind)%kind_number = imolecule_kind
331 molecule_kind_set(imolecule_kind)%ncolv)
347 INTEGER :: i, imolecule_kind, j, nmolecule_kind
349 IF (
ASSOCIATED(molecule_kind_set))
THEN
351 nmolecule_kind =
SIZE(molecule_kind_set)
353 DO imolecule_kind = 1, nmolecule_kind
355 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%atom_list))
THEN
356 DEALLOCATE (molecule_kind_set(imolecule_kind)%atom_list)
358 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bend_kind_set))
THEN
359 DO i = 1,
SIZE(molecule_kind_set(imolecule_kind)%bend_kind_set)
360 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bend_kind_set(i)%legendre%coeffs)) &
361 DEALLOCATE (molecule_kind_set(imolecule_kind)%bend_kind_set(i)%legendre%coeffs)
363 DEALLOCATE (molecule_kind_set(imolecule_kind)%bend_kind_set)
365 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bend_list))
THEN
366 DEALLOCATE (molecule_kind_set(imolecule_kind)%bend_list)
368 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%ub_list))
THEN
369 DEALLOCATE (molecule_kind_set(imolecule_kind)%ub_list)
371 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%ub_kind_set))
THEN
374 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%impr_list))
THEN
375 DEALLOCATE (molecule_kind_set(imolecule_kind)%impr_list)
377 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%impr_kind_set))
THEN
378 DO i = 1,
SIZE(molecule_kind_set(imolecule_kind)%impr_kind_set)
381 DEALLOCATE (molecule_kind_set(imolecule_kind)%impr_kind_set)
383 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%opbend_list))
THEN
384 DEALLOCATE (molecule_kind_set(imolecule_kind)%opbend_list)
386 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%opbend_kind_set))
THEN
387 DEALLOCATE (molecule_kind_set(imolecule_kind)%opbend_kind_set)
389 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bond_kind_set))
THEN
390 DEALLOCATE (molecule_kind_set(imolecule_kind)%bond_kind_set)
392 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bond_list))
THEN
393 DEALLOCATE (molecule_kind_set(imolecule_kind)%bond_list)
395 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%colv_list))
THEN
396 DO j = 1,
SIZE(molecule_kind_set(imolecule_kind)%colv_list)
397 DEALLOCATE (molecule_kind_set(imolecule_kind)%colv_list(j)%i_atoms)
399 DEALLOCATE (molecule_kind_set(imolecule_kind)%colv_list)
401 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%g3x3_list))
THEN
402 DEALLOCATE (molecule_kind_set(imolecule_kind)%g3x3_list)
404 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%g4x6_list))
THEN
405 DEALLOCATE (molecule_kind_set(imolecule_kind)%g4x6_list)
407 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%vsite_list))
THEN
408 DEALLOCATE (molecule_kind_set(imolecule_kind)%vsite_list)
410 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%fixd_list))
THEN
411 DEALLOCATE (molecule_kind_set(imolecule_kind)%fixd_list)
413 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%torsion_kind_set))
THEN
414 DO i = 1,
SIZE(molecule_kind_set(imolecule_kind)%torsion_kind_set)
417 DEALLOCATE (molecule_kind_set(imolecule_kind)%torsion_kind_set)
419 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%shell_list))
THEN
420 DEALLOCATE (molecule_kind_set(imolecule_kind)%shell_list)
422 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%torsion_list))
THEN
423 DEALLOCATE (molecule_kind_set(imolecule_kind)%torsion_list)
425 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%molecule_list))
THEN
426 DEALLOCATE (molecule_kind_set(imolecule_kind)%molecule_list)
430 DEALLOCATE (molecule_kind_set)
432 NULLIFY (molecule_kind_set)
494 ub_list, impr_list, opbend_list, colv_list, fixd_list, &
495 g3x3_list, g4x6_list, vsite_list, torsion_list, shell_list, &
496 name, mass, charge, kind_number, natom, nbend, nbond, nub, &
497 nimpr, nopbend, nconstraint, nconstraint_fixd, nfixd, ncolv, ng3x3, ng4x6, &
498 nvsite, nfixd_restraint, ng3x3_restraint, ng4x6_restraint, &
499 nvsite_restraint, nrestraints, nmolecule, nsgf, nshell, ntorsion, &
500 molecule_list, nelectron, nelectron_alpha, nelectron_beta, &
501 bond_kind_set, bend_kind_set, &
502 ub_kind_set, impr_kind_set, opbend_kind_set, torsion_kind_set, &
506 TYPE(
atom_type),
DIMENSION(:),
OPTIONAL,
POINTER :: atom_list
507 TYPE(
bond_type),
DIMENSION(:),
OPTIONAL,
POINTER :: bond_list
508 TYPE(
bend_type),
DIMENSION(:),
OPTIONAL,
POINTER :: bend_list
509 TYPE(
ub_type),
DIMENSION(:),
OPTIONAL,
POINTER :: ub_list
510 TYPE(
impr_type),
DIMENSION(:),
OPTIONAL,
POINTER :: impr_list
511 TYPE(
opbend_type),
DIMENSION(:),
OPTIONAL,
POINTER :: opbend_list
513 OPTIONAL,
POINTER :: colv_list
515 OPTIONAL,
POINTER :: fixd_list
517 OPTIONAL,
POINTER :: g3x3_list
519 OPTIONAL,
POINTER :: g4x6_list
521 OPTIONAL,
POINTER :: vsite_list
523 POINTER :: torsion_list
524 TYPE(
shell_type),
DIMENSION(:),
OPTIONAL,
POINTER :: shell_list
525 CHARACTER(LEN=default_string_length), &
526 INTENT(OUT),
OPTIONAL :: name
527 REAL(kind=
dp),
OPTIONAL :: mass, charge
528 INTEGER,
INTENT(OUT),
OPTIONAL :: kind_number, natom, nbend, nbond, nub, &
529 nimpr, nopbend, nconstraint, &
530 nconstraint_fixd, nfixd
532 INTEGER,
INTENT(OUT),
OPTIONAL :: ng3x3, ng4x6, nvsite, nfixd_restraint, ng3x3_restraint, &
533 ng4x6_restraint, nvsite_restraint, nrestraints, nmolecule, nsgf, nshell, ntorsion
534 INTEGER,
DIMENSION(:),
OPTIONAL,
POINTER :: molecule_list
535 INTEGER,
INTENT(OUT),
OPTIONAL :: nelectron, nelectron_alpha, &
538 POINTER :: bond_kind_set
540 POINTER :: bend_kind_set
542 POINTER :: ub_kind_set
544 POINTER :: impr_kind_set
546 POINTER :: opbend_kind_set
548 POINTER :: torsion_kind_set
549 LOGICAL,
INTENT(OUT),
OPTIONAL :: molname_generated
553 IF (
PRESENT(atom_list)) atom_list => molecule_kind%atom_list
554 IF (
PRESENT(bend_list)) bend_list => molecule_kind%bend_list
555 IF (
PRESENT(bond_list)) bond_list => molecule_kind%bond_list
556 IF (
PRESENT(impr_list)) impr_list => molecule_kind%impr_list
557 IF (
PRESENT(opbend_list)) opbend_list => molecule_kind%opbend_list
558 IF (
PRESENT(ub_list)) ub_list => molecule_kind%ub_list
559 IF (
PRESENT(bond_kind_set)) bond_kind_set => molecule_kind%bond_kind_set
560 IF (
PRESENT(bend_kind_set)) bend_kind_set => molecule_kind%bend_kind_set
561 IF (
PRESENT(ub_kind_set)) ub_kind_set => molecule_kind%ub_kind_set
562 IF (
PRESENT(impr_kind_set)) impr_kind_set => molecule_kind%impr_kind_set
563 IF (
PRESENT(opbend_kind_set)) opbend_kind_set => molecule_kind%opbend_kind_set
564 IF (
PRESENT(torsion_kind_set)) torsion_kind_set => molecule_kind%torsion_kind_set
565 IF (
PRESENT(colv_list)) colv_list => molecule_kind%colv_list
566 IF (
PRESENT(g3x3_list)) g3x3_list => molecule_kind%g3x3_list
567 IF (
PRESENT(g4x6_list)) g4x6_list => molecule_kind%g4x6_list
568 IF (
PRESENT(vsite_list)) vsite_list => molecule_kind%vsite_list
569 IF (
PRESENT(fixd_list)) fixd_list => molecule_kind%fixd_list
570 IF (
PRESENT(torsion_list)) torsion_list => molecule_kind%torsion_list
571 IF (
PRESENT(shell_list)) shell_list => molecule_kind%shell_list
572 IF (
PRESENT(name)) name = molecule_kind%name
573 IF (
PRESENT(molname_generated)) molname_generated = molecule_kind%molname_generated
574 IF (
PRESENT(mass)) mass = molecule_kind%mass
575 IF (
PRESENT(charge)) charge = molecule_kind%charge
576 IF (
PRESENT(kind_number)) kind_number = molecule_kind%kind_number
577 IF (
PRESENT(natom)) natom = molecule_kind%natom
578 IF (
PRESENT(nbend)) nbend = molecule_kind%nbend
579 IF (
PRESENT(nbond)) nbond = molecule_kind%nbond
580 IF (
PRESENT(nub)) nub = molecule_kind%nub
581 IF (
PRESENT(nimpr)) nimpr = molecule_kind%nimpr
582 IF (
PRESENT(nopbend)) nopbend = molecule_kind%nopbend
583 IF (
PRESENT(nconstraint)) nconstraint = (molecule_kind%ncolv%ntot - molecule_kind%ncolv%nrestraint) + &
584 3*(molecule_kind%ng3x3 - molecule_kind%ng3x3_restraint) + &
585 6*(molecule_kind%ng4x6 - molecule_kind%ng4x6_restraint) + &
586 3*(molecule_kind%nvsite - molecule_kind%nvsite_restraint)
587 IF (
PRESENT(ncolv)) ncolv = molecule_kind%ncolv
588 IF (
PRESENT(ng3x3)) ng3x3 = molecule_kind%ng3x3
589 IF (
PRESENT(ng4x6)) ng4x6 = molecule_kind%ng4x6
590 IF (
PRESENT(nvsite)) nvsite = molecule_kind%nvsite
592 IF (
PRESENT(nfixd)) nfixd = molecule_kind%nfixd
594 IF (
PRESENT(nconstraint_fixd))
THEN
596 IF (molecule_kind%nfixd /= 0)
THEN
597 DO i = 1,
SIZE(molecule_kind%fixd_list)
598 IF (molecule_kind%fixd_list(i)%restraint%active) cycle
599 SELECT CASE (molecule_kind%fixd_list(i)%itype)
601 nconstraint_fixd = nconstraint_fixd + 1
603 nconstraint_fixd = nconstraint_fixd + 2
605 nconstraint_fixd = nconstraint_fixd + 3
610 IF (
PRESENT(ng3x3_restraint)) ng3x3_restraint = molecule_kind%ng3x3_restraint
611 IF (
PRESENT(ng4x6_restraint)) ng4x6_restraint = molecule_kind%ng4x6_restraint
612 IF (
PRESENT(nvsite_restraint)) nvsite_restraint = molecule_kind%nvsite_restraint
613 IF (
PRESENT(nfixd_restraint)) nfixd_restraint = molecule_kind%nfixd_restraint
614 IF (
PRESENT(nrestraints)) nrestraints = molecule_kind%ncolv%nrestraint + &
615 molecule_kind%ng3x3_restraint + &
616 molecule_kind%ng4x6_restraint + &
617 molecule_kind%nvsite_restraint
618 IF (
PRESENT(nmolecule)) nmolecule = molecule_kind%nmolecule
619 IF (
PRESENT(nshell)) nshell = molecule_kind%nshell
620 IF (
PRESENT(ntorsion)) ntorsion = molecule_kind%ntorsion
621 IF (
PRESENT(nsgf)) nsgf = molecule_kind%nsgf
622 IF (
PRESENT(nelectron)) nelectron = molecule_kind%nelectron
623 IF (
PRESENT(nelectron_alpha)) nelectron_alpha = molecule_kind%nelectron_beta
624 IF (
PRESENT(nelectron_beta)) nelectron_beta = molecule_kind%nelectron_alpha
625 IF (
PRESENT(molecule_list)) molecule_list => molecule_kind%molecule_list
649 nbond, nbend, nub, ntorsion, nimpr, nopbend, &
650 nconstraint, nconstraint_fixd, nmolecule, &
654 INTEGER,
INTENT(OUT),
OPTIONAL :: maxatom, natom, nbond, nbend, nub, &
655 ntorsion, nimpr, nopbend, nconstraint, &
656 nconstraint_fixd, nmolecule, &
659 INTEGER :: ibend, ibond, iimpr, imolecule_kind, iopbend, itorsion, iub, na, nc, nc_fixd, &
660 nfixd_restraint, nm, nmolecule_kind, nrestraints_tot
662 IF (
PRESENT(maxatom)) maxatom = 0
663 IF (
PRESENT(natom)) natom = 0
664 IF (
PRESENT(nbond)) nbond = 0
665 IF (
PRESENT(nbend)) nbend = 0
666 IF (
PRESENT(nub)) nub = 0
667 IF (
PRESENT(ntorsion)) ntorsion = 0
668 IF (
PRESENT(nimpr)) nimpr = 0
669 IF (
PRESENT(nopbend)) nopbend = 0
670 IF (
PRESENT(nconstraint)) nconstraint = 0
671 IF (
PRESENT(nconstraint_fixd)) nconstraint_fixd = 0
672 IF (
PRESENT(nrestraints)) nrestraints = 0
673 IF (
PRESENT(nmolecule)) nmolecule = 0
675 nmolecule_kind =
SIZE(molecule_kind_set)
677 DO imolecule_kind = 1, nmolecule_kind
678 associate(molecule_kind => molecule_kind_set(imolecule_kind))
689 nconstraint_fixd=nc_fixd, &
690 nfixd_restraint=nfixd_restraint, &
691 nrestraints=nrestraints_tot, &
693 IF (
PRESENT(maxatom)) maxatom = max(maxatom, na)
694 IF (
PRESENT(natom)) natom = natom + na*nm
695 IF (
PRESENT(nbond)) nbond = nbond + ibond*nm
696 IF (
PRESENT(nbend)) nbend = nbend + ibend*nm
697 IF (
PRESENT(nub)) nub = nub + iub*nm
698 IF (
PRESENT(ntorsion)) ntorsion = ntorsion + itorsion*nm
699 IF (
PRESENT(nimpr)) nimpr = nimpr + iimpr*nm
700 IF (
PRESENT(nopbend)) nopbend = nopbend + iopbend*nm
701 IF (
PRESENT(nconstraint)) nconstraint = nconstraint + nc*nm + nc_fixd
702 IF (
PRESENT(nconstraint_fixd)) nconstraint_fixd = nconstraint_fixd + nc_fixd
703 IF (
PRESENT(nmolecule)) nmolecule = nmolecule + nm
704 IF (
PRESENT(nrestraints)) nrestraints = nrestraints + nm*nrestraints_tot + nfixd_restraint
762 molecule_list, atom_list, nbond, bond_list, &
763 nbend, bend_list, nub, ub_list, nimpr, impr_list, &
764 nopbend, opbend_list, ntorsion, &
765 torsion_list, fixd_list, ncolv, colv_list, ng3x3, &
766 g3x3_list, ng4x6, nfixd, g4x6_list, nvsite, &
767 vsite_list, ng3x3_restraint, ng4x6_restraint, &
768 nfixd_restraint, nshell, shell_list, &
769 nvsite_restraint, bond_kind_set, bend_kind_set, &
770 ub_kind_set, torsion_kind_set, impr_kind_set, &
771 opbend_kind_set, nelectron, nsgf, &
775 CHARACTER(LEN=*),
INTENT(IN),
OPTIONAL :: name
776 REAL(kind=dp),
OPTIONAL :: mass, charge
777 INTEGER,
INTENT(IN),
OPTIONAL :: kind_number
778 INTEGER,
DIMENSION(:),
OPTIONAL,
POINTER :: molecule_list
779 TYPE(
atom_type),
DIMENSION(:),
OPTIONAL,
POINTER :: atom_list
780 INTEGER,
INTENT(IN),
OPTIONAL :: nbond
781 TYPE(
bond_type),
DIMENSION(:),
OPTIONAL,
POINTER :: bond_list
782 INTEGER,
INTENT(IN),
OPTIONAL :: nbend
783 TYPE(
bend_type),
DIMENSION(:),
OPTIONAL,
POINTER :: bend_list
784 INTEGER,
INTENT(IN),
OPTIONAL :: nub
785 TYPE(
ub_type),
DIMENSION(:),
OPTIONAL,
POINTER :: ub_list
786 INTEGER,
INTENT(IN),
OPTIONAL :: nimpr
787 TYPE(
impr_type),
DIMENSION(:),
OPTIONAL,
POINTER :: impr_list
788 INTEGER,
INTENT(IN),
OPTIONAL :: nopbend
789 TYPE(
opbend_type),
DIMENSION(:),
OPTIONAL,
POINTER :: opbend_list
790 INTEGER,
INTENT(IN),
OPTIONAL :: ntorsion
792 POINTER :: torsion_list
794 OPTIONAL,
POINTER :: fixd_list
795 TYPE(colvar_counters),
INTENT(IN),
OPTIONAL :: ncolv
797 OPTIONAL,
POINTER :: colv_list
798 INTEGER,
INTENT(IN),
OPTIONAL :: ng3x3
800 OPTIONAL,
POINTER :: g3x3_list
801 INTEGER,
INTENT(IN),
OPTIONAL :: ng4x6, nfixd
803 OPTIONAL,
POINTER :: g4x6_list
804 INTEGER,
INTENT(IN),
OPTIONAL :: nvsite
806 OPTIONAL,
POINTER :: vsite_list
807 INTEGER,
INTENT(IN),
OPTIONAL :: ng3x3_restraint, ng4x6_restraint, &
808 nfixd_restraint, nshell
809 TYPE(
shell_type),
DIMENSION(:),
OPTIONAL,
POINTER :: shell_list
810 INTEGER,
INTENT(IN),
OPTIONAL :: nvsite_restraint
811 TYPE(bond_kind_type),
DIMENSION(:),
OPTIONAL, &
812 POINTER :: bond_kind_set
813 TYPE(bend_kind_type),
DIMENSION(:),
OPTIONAL, &
814 POINTER :: bend_kind_set
815 TYPE(ub_kind_type),
DIMENSION(:),
OPTIONAL, &
816 POINTER :: ub_kind_set
817 TYPE(torsion_kind_type),
DIMENSION(:),
OPTIONAL, &
818 POINTER :: torsion_kind_set
819 TYPE(impr_kind_type),
DIMENSION(:),
OPTIONAL, &
820 POINTER :: impr_kind_set
821 TYPE(opbend_kind_type),
DIMENSION(:),
OPTIONAL, &
822 POINTER :: opbend_kind_set
823 INTEGER,
INTENT(IN),
OPTIONAL :: nelectron, nsgf
824 LOGICAL,
INTENT(IN),
OPTIONAL :: molname_generated
828 IF (
PRESENT(atom_list))
THEN
830 molecule_kind%natom = n
831 molecule_kind%atom_list => atom_list
833 IF (
PRESENT(molname_generated)) molecule_kind%molname_generated = molname_generated
834 IF (
PRESENT(name)) molecule_kind%name = name
835 IF (
PRESENT(mass)) molecule_kind%mass = mass
836 IF (
PRESENT(charge)) molecule_kind%charge = charge
837 IF (
PRESENT(kind_number)) molecule_kind%kind_number = kind_number
838 IF (
PRESENT(nbond)) molecule_kind%nbond = nbond
839 IF (
PRESENT(bond_list)) molecule_kind%bond_list => bond_list
840 IF (
PRESENT(nbend)) molecule_kind%nbend = nbend
841 IF (
PRESENT(nelectron)) molecule_kind%nelectron = nelectron
842 IF (
PRESENT(nsgf)) molecule_kind%nsgf = nsgf
843 IF (
PRESENT(bend_list)) molecule_kind%bend_list => bend_list
844 IF (
PRESENT(nub)) molecule_kind%nub = nub
845 IF (
PRESENT(ub_list)) molecule_kind%ub_list => ub_list
846 IF (
PRESENT(ntorsion)) molecule_kind%ntorsion = ntorsion
847 IF (
PRESENT(torsion_list)) molecule_kind%torsion_list => torsion_list
848 IF (
PRESENT(nimpr)) molecule_kind%nimpr = nimpr
849 IF (
PRESENT(impr_list)) molecule_kind%impr_list => impr_list
850 IF (
PRESENT(nopbend)) molecule_kind%nopbend = nopbend
851 IF (
PRESENT(opbend_list)) molecule_kind%opbend_list => opbend_list
852 IF (
PRESENT(ncolv)) molecule_kind%ncolv = ncolv
853 IF (
PRESENT(colv_list)) molecule_kind%colv_list => colv_list
854 IF (
PRESENT(ng3x3)) molecule_kind%ng3x3 = ng3x3
855 IF (
PRESENT(g3x3_list)) molecule_kind%g3x3_list => g3x3_list
856 IF (
PRESENT(ng4x6)) molecule_kind%ng4x6 = ng4x6
857 IF (
PRESENT(nvsite)) molecule_kind%nvsite = nvsite
858 IF (
PRESENT(nfixd)) molecule_kind%nfixd = nfixd
859 IF (
PRESENT(nfixd_restraint)) molecule_kind%nfixd_restraint = nfixd_restraint
860 IF (
PRESENT(ng3x3_restraint)) molecule_kind%ng3x3_restraint = ng3x3_restraint
861 IF (
PRESENT(ng4x6_restraint)) molecule_kind%ng4x6_restraint = ng4x6_restraint
862 IF (
PRESENT(nvsite_restraint)) molecule_kind%nvsite_restraint = nvsite_restraint
863 IF (
PRESENT(g4x6_list)) molecule_kind%g4x6_list => g4x6_list
864 IF (
PRESENT(vsite_list)) molecule_kind%vsite_list => vsite_list
865 IF (
PRESENT(fixd_list)) molecule_kind%fixd_list => fixd_list
866 IF (
PRESENT(bond_kind_set)) molecule_kind%bond_kind_set => bond_kind_set
867 IF (
PRESENT(bend_kind_set)) molecule_kind%bend_kind_set => bend_kind_set
868 IF (
PRESENT(ub_kind_set)) molecule_kind%ub_kind_set => ub_kind_set
869 IF (
PRESENT(torsion_kind_set)) molecule_kind%torsion_kind_set => torsion_kind_set
870 IF (
PRESENT(impr_kind_set)) molecule_kind%impr_kind_set => impr_kind_set
871 IF (
PRESENT(opbend_kind_set)) molecule_kind%opbend_kind_set => opbend_kind_set
872 IF (
PRESENT(nshell)) molecule_kind%nshell = nshell
873 IF (
PRESENT(shell_list)) molecule_kind%shell_list => shell_list
874 IF (
PRESENT(molecule_list))
THEN
875 n =
SIZE(molecule_list)
876 molecule_kind%nmolecule = n
877 molecule_kind%molecule_list => molecule_list
889 SUBROUTINE write_molecule_kind(molecule_kind, output_unit)
891 INTEGER,
INTENT(in) :: output_unit
893 CHARACTER(LEN=default_string_length) :: name
894 INTEGER :: iatom, imolecule, natom, nmolecule
895 TYPE(atomic_kind_type),
POINTER :: atomic_kind
897 IF (output_unit > 0)
THEN
898 natom =
SIZE(molecule_kind%atom_list)
899 nmolecule =
SIZE(molecule_kind%molecule_list)
902 atomic_kind => molecule_kind%atom_list(1)%atomic_kind
903 CALL get_atomic_kind(atomic_kind=atomic_kind, name=name)
904 WRITE (unit=output_unit, fmt=
"(/,T2,I5,A,T36,A,A,T64,A)") &
905 molecule_kind%kind_number, &
906 ". Molecule kind: "//trim(molecule_kind%name), &
907 "Atomic kind name: ", trim(name)
908 WRITE (unit=output_unit, fmt=
"(T9,A,L1,T55,A,T75,I6)") &
909 "Automatic name: ", molecule_kind%molname_generated, &
910 "Number of molecules:", nmolecule
912 WRITE (unit=output_unit, fmt=
"(/,T2,I5,A,T50,A,T75,I6,/,T22,A)") &
913 molecule_kind%kind_number, &
914 ". Molecule kind: "//trim(molecule_kind%name), &
915 "Number of atoms: ", natom, &
916 "Atom Atomic kind name"
918 atomic_kind => molecule_kind%atom_list(iatom)%atomic_kind
919 CALL get_atomic_kind(atomic_kind=atomic_kind, name=name)
920 WRITE (unit=output_unit, fmt=
"(T20,I6,(7X,A18))") &
923 WRITE (unit=output_unit, fmt=
"(/,T9,A,L1)") &
924 "The name was automatically generated: ", &
925 molecule_kind%molname_generated
926 WRITE (unit=output_unit, fmt=
"(T9,A,I6,/,T9,A,(T30,5I10))") &
927 "Number of molecules: ", nmolecule,
"Molecule list:", &
928 (molecule_kind%molecule_list(imolecule), imolecule=1, nmolecule)
929 IF (molecule_kind%nbond > 0) &
930 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
931 "Number of bonds: ", molecule_kind%nbond
932 IF (molecule_kind%nbend > 0) &
933 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
934 "Number of bends: ", molecule_kind%nbend
935 IF (molecule_kind%nub > 0) &
936 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
937 "Number of Urey-Bradley:", molecule_kind%nub
938 IF (molecule_kind%ntorsion > 0) &
939 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
940 "Number of torsions: ", molecule_kind%ntorsion
941 IF (molecule_kind%nimpr > 0) &
942 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
943 "Number of improper: ", molecule_kind%nimpr
944 IF (molecule_kind%nopbend > 0) &
945 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
946 "Number of out opbends: ", molecule_kind%nopbend
949 END SUBROUTINE write_molecule_kind
961 TYPE(section_vals_type),
INTENT(IN) :: subsys_section
963 CHARACTER(len=*),
PARAMETER :: routinen =
'write_molecule_kind_set'
965 INTEGER :: handle, imolecule_kind, natom, nbend, &
966 nbond, nimpr, nmolecule, &
967 nmolecule_kind, nopbend, ntors, &
968 ntotal, nub, output_unit
969 LOGICAL :: all_single_atoms
970 TYPE(cp_logger_type),
POINTER :: logger
972 CALL timeset(routinen, handle)
975 logger => cp_get_default_logger()
976 output_unit = cp_print_key_unit_nr(logger, subsys_section, &
977 "PRINT%MOLECULES", extension=
".Log")
978 IF (output_unit > 0)
THEN
979 WRITE (unit=output_unit, fmt=
"(/,/,T2,A)")
"MOLECULE KIND INFORMATION"
981 nmolecule_kind =
SIZE(molecule_kind_set)
983 all_single_atoms = .true.
984 DO imolecule_kind = 1, nmolecule_kind
985 natom =
SIZE(molecule_kind_set(imolecule_kind)%atom_list)
986 nmolecule =
SIZE(molecule_kind_set(imolecule_kind)%molecule_list)
987 IF (natom*nmolecule > 1) all_single_atoms = .false.
990 IF (all_single_atoms)
THEN
991 WRITE (unit=output_unit, fmt=
"(/,/,T2,A)") &
992 "All atoms are their own molecule, skipping detailed information"
994 DO imolecule_kind = 1, nmolecule_kind
995 CALL write_molecule_kind(molecule_kind_set(imolecule_kind), output_unit)
1006 ntotal = nbond + nbend + nub + ntors + nimpr + nopbend
1007 IF (ntotal > 0)
THEN
1008 WRITE (unit=output_unit, fmt=
"(/,/,T2,A,T45,A30,I6)") &
1009 "MOLECULE KIND SET INFORMATION", &
1010 "Total Number of bonds: ", nbond
1011 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1012 "Total Number of bends: ", nbend
1013 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1014 "Total Number of Urey-Bradley:", nub
1015 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1016 "Total Number of torsions: ", ntors
1017 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1018 "Total Number of improper: ", nimpr
1019 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1020 "Total Number of opbends: ", nopbend
1023 CALL cp_print_key_finished_output(output_unit, logger, subsys_section, &
1026 CALL timestop(handle)
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.
integer, parameter, public use_perd_xyz
integer, parameter, public use_perd_y
integer, parameter, public use_perd_xz
integer, parameter, public use_perd_x
integer, parameter, public use_perd_z
integer, parameter, public use_perd_yz
integer, parameter, public use_perd_xy
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.
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_string_length
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.
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...