48#include "../base/base_uses.f90"
54 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'molecule_kind_types'
60 INTEGER :: id_name = 0
65 CHARACTER(LEN=default_string_length) :: name =
""
70 INTEGER :: a = 0, b = 0
76 INTEGER :: a = 0, b = 0, c = 0
82 INTEGER :: a = 0, b = 0, c = 0
88 INTEGER :: a = 0, b = 0, c = 0, d = 0
94 INTEGER :: a = 0, b = 0, c = 0, d = 0
100 INTEGER :: a = 0, b = 0, c = 0, d = 0
106 LOGICAL :: active = .false.
107 REAL(kind=
dp) :: k0 = 0.0_dp
108 END TYPE restraint_type
113 INTEGER :: inp_seq_num = 0
114 LOGICAL :: use_points = .false.
115 REAL(kind=
dp) :: expected_value = 0.0_dp
116 REAL(kind=
dp) :: expected_value_growth_speed = 0.0_dp
117 INTEGER,
POINTER,
DIMENSION(:) :: i_atoms => null()
122 INTEGER :: a = 0, b = 0, c = 0
123 REAL(kind=
dp) :: dab = 0.0_dp, dac = 0.0_dp, dbc = 0.0_dp
128 INTEGER :: a = 0, b = 0, c = 0, d = 0
129 REAL(kind=
dp) :: dab = 0.0_dp, dac = 0.0_dp, dbc = 0.0_dp, &
130 dad = 0.0_dp, dbd = 0.0_dp, dcd = 0.0_dp
135 INTEGER :: a = 0, b = 0, c = 0, d = 0
136 REAL(kind=
dp) :: wbc = 0.0_dp, wdc = 0.0_dp
142 INTEGER :: fixd = 0, itype = 0
143 REAL(kind=
dp),
DIMENSION(3) :: coord = 0.0_dp
147 INTEGER :: ifixd_index = 0, ikind = 0
152 TYPE(
atom_type),
DIMENSION(:),
POINTER :: atom_list => null()
154 TYPE(
bond_type),
DIMENSION(:),
POINTER :: bond_list => null()
156 TYPE(
bend_type),
DIMENSION(:),
POINTER :: bend_list => null()
158 TYPE(
ub_type),
DIMENSION(:),
POINTER :: ub_list => null()
162 TYPE(
impr_type),
DIMENSION(:),
POINTER :: impr_list => null()
166 POINTER :: colv_list => null()
171 TYPE(
shell_type),
DIMENSION(:),
POINTER :: shell_list => null()
172 CHARACTER(LEN=default_string_length) :: name =
""
173 REAL(kind=
dp) :: charge = 0.0_dp, &
175 INTEGER :: kind_number = 0, &
184 ng3x3_restraint = 0, &
186 ng4x6_restraint = 0, &
188 nvsite_restraint = 0, &
190 nfixd_restraint = 0, &
194 INTEGER :: nsgf = 0, &
196 nelectron_alpha = 0, &
198 INTEGER,
DIMENSION(:),
POINTER :: molecule_list => null()
199 LOGICAL :: molname_generated = .false.
247 IF (
ASSOCIATED(colv_list))
THEN
248 DO k = 1,
SIZE(colv_list)
249 IF (colv_list(k)%restraint%active) ncolv%nrestraint = ncolv%nrestraint + 1
250 SELECT CASE (colv_list(k)%type_id)
252 ncolv%nangle = ncolv%nangle + 1
254 ncolv%ncoord = ncolv%ncoord + 1
256 ncolv%npopulation = ncolv%npopulation + 1
258 ncolv%ngyration = ncolv%ngyration + 1
260 ncolv%nrot = ncolv%nrot + 1
262 ncolv%ndist = ncolv%ndist + 1
264 ncolv%ndfunct = ncolv%ndfunct + 1
266 ncolv%nplane_dist = ncolv%nplane_dist + 1
268 ncolv%nplane_angle = ncolv%nplane_angle + 1
270 ncolv%ntorsion = ncolv%ntorsion + 1
272 ncolv%nqparm = ncolv%nqparm + 1
274 ncolv%nxyz_diag = ncolv%nxyz_diag + 1
276 ncolv%nxyz_outerdiag = ncolv%nxyz_outerdiag + 1
278 ncolv%nhydronium_shell = ncolv%nhydronium_shell + 1
280 ncolv%nhydronium_dist = ncolv%nhydronium_dist + 1
282 ncolv%nacid_hyd_dist = ncolv%nacid_hyd_dist + 1
284 ncolv%nacid_hyd_shell = ncolv%nacid_hyd_shell + 1
286 ncolv%nreactionpath = ncolv%nreactionpath + 1
288 ncolv%ncombinecvs = ncolv%ncombinecvs + 1
294 ncolv%ntot = ncolv%ndist + &
298 ncolv%nplane_dist + &
299 ncolv%nplane_angle + &
304 ncolv%nxyz_outerdiag + &
305 ncolv%nhydronium_shell + &
306 ncolv%nhydronium_dist + &
307 ncolv%nacid_hyd_dist + &
308 ncolv%nacid_hyd_shell + &
309 ncolv%nreactionpath + &
310 ncolv%ncombinecvs + &
311 ncolv%npopulation + &
326 INTEGER,
INTENT(IN) :: nmolecule_kind
328 INTEGER :: imolecule_kind
330 IF (
ASSOCIATED(molecule_kind_set))
THEN
334 ALLOCATE (molecule_kind_set(nmolecule_kind))
336 DO imolecule_kind = 1, nmolecule_kind
337 molecule_kind_set(imolecule_kind)%kind_number = imolecule_kind
339 molecule_kind_set(imolecule_kind)%ncolv)
355 INTEGER :: i, imolecule_kind, j, nmolecule_kind
357 IF (
ASSOCIATED(molecule_kind_set))
THEN
359 nmolecule_kind =
SIZE(molecule_kind_set)
361 DO imolecule_kind = 1, nmolecule_kind
363 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%atom_list))
THEN
364 DEALLOCATE (molecule_kind_set(imolecule_kind)%atom_list)
366 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bend_kind_set))
THEN
367 DO i = 1,
SIZE(molecule_kind_set(imolecule_kind)%bend_kind_set)
368 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bend_kind_set(i)%legendre%coeffs)) &
369 DEALLOCATE (molecule_kind_set(imolecule_kind)%bend_kind_set(i)%legendre%coeffs)
371 DEALLOCATE (molecule_kind_set(imolecule_kind)%bend_kind_set)
373 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bend_list))
THEN
374 DEALLOCATE (molecule_kind_set(imolecule_kind)%bend_list)
376 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%ub_list))
THEN
377 DEALLOCATE (molecule_kind_set(imolecule_kind)%ub_list)
379 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%ub_kind_set))
THEN
382 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%impr_list))
THEN
383 DEALLOCATE (molecule_kind_set(imolecule_kind)%impr_list)
385 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%impr_kind_set))
THEN
386 DO i = 1,
SIZE(molecule_kind_set(imolecule_kind)%impr_kind_set)
389 DEALLOCATE (molecule_kind_set(imolecule_kind)%impr_kind_set)
391 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%opbend_list))
THEN
392 DEALLOCATE (molecule_kind_set(imolecule_kind)%opbend_list)
394 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%opbend_kind_set))
THEN
395 DEALLOCATE (molecule_kind_set(imolecule_kind)%opbend_kind_set)
397 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bond_kind_set))
THEN
398 DEALLOCATE (molecule_kind_set(imolecule_kind)%bond_kind_set)
400 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%bond_list))
THEN
401 DEALLOCATE (molecule_kind_set(imolecule_kind)%bond_list)
403 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%colv_list))
THEN
404 DO j = 1,
SIZE(molecule_kind_set(imolecule_kind)%colv_list)
405 DEALLOCATE (molecule_kind_set(imolecule_kind)%colv_list(j)%i_atoms)
407 DEALLOCATE (molecule_kind_set(imolecule_kind)%colv_list)
409 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%g3x3_list))
THEN
410 DEALLOCATE (molecule_kind_set(imolecule_kind)%g3x3_list)
412 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%g4x6_list))
THEN
413 DEALLOCATE (molecule_kind_set(imolecule_kind)%g4x6_list)
415 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%vsite_list))
THEN
416 DEALLOCATE (molecule_kind_set(imolecule_kind)%vsite_list)
418 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%fixd_list))
THEN
419 DEALLOCATE (molecule_kind_set(imolecule_kind)%fixd_list)
421 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%torsion_kind_set))
THEN
422 DO i = 1,
SIZE(molecule_kind_set(imolecule_kind)%torsion_kind_set)
425 DEALLOCATE (molecule_kind_set(imolecule_kind)%torsion_kind_set)
427 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%shell_list))
THEN
428 DEALLOCATE (molecule_kind_set(imolecule_kind)%shell_list)
430 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%torsion_list))
THEN
431 DEALLOCATE (molecule_kind_set(imolecule_kind)%torsion_list)
433 IF (
ASSOCIATED(molecule_kind_set(imolecule_kind)%molecule_list))
THEN
434 DEALLOCATE (molecule_kind_set(imolecule_kind)%molecule_list)
438 DEALLOCATE (molecule_kind_set)
440 NULLIFY (molecule_kind_set)
502 ub_list, impr_list, opbend_list, colv_list, fixd_list, &
503 g3x3_list, g4x6_list, vsite_list, torsion_list, shell_list, &
504 name, mass, charge, kind_number, natom, nbend, nbond, nub, &
505 nimpr, nopbend, nconstraint, nconstraint_fixd, nfixd, ncolv, ng3x3, ng4x6, &
506 nvsite, nfixd_restraint, ng3x3_restraint, ng4x6_restraint, &
507 nvsite_restraint, nrestraints, nmolecule, nsgf, nshell, ntorsion, &
508 molecule_list, nelectron, nelectron_alpha, nelectron_beta, &
509 bond_kind_set, bend_kind_set, &
510 ub_kind_set, impr_kind_set, opbend_kind_set, torsion_kind_set, &
514 TYPE(
atom_type),
DIMENSION(:),
OPTIONAL,
POINTER :: atom_list
515 TYPE(
bond_type),
DIMENSION(:),
OPTIONAL,
POINTER :: bond_list
516 TYPE(
bend_type),
DIMENSION(:),
OPTIONAL,
POINTER :: bend_list
517 TYPE(
ub_type),
DIMENSION(:),
OPTIONAL,
POINTER :: ub_list
518 TYPE(
impr_type),
DIMENSION(:),
OPTIONAL,
POINTER :: impr_list
519 TYPE(
opbend_type),
DIMENSION(:),
OPTIONAL,
POINTER :: opbend_list
521 OPTIONAL,
POINTER :: colv_list
523 OPTIONAL,
POINTER :: fixd_list
525 OPTIONAL,
POINTER :: g3x3_list
527 OPTIONAL,
POINTER :: g4x6_list
529 OPTIONAL,
POINTER :: vsite_list
531 POINTER :: torsion_list
532 TYPE(
shell_type),
DIMENSION(:),
OPTIONAL,
POINTER :: shell_list
533 CHARACTER(LEN=default_string_length), &
534 INTENT(OUT),
OPTIONAL :: name
535 REAL(kind=
dp),
OPTIONAL :: mass, charge
536 INTEGER,
INTENT(OUT),
OPTIONAL :: kind_number, natom, nbend, nbond, nub, &
537 nimpr, nopbend, nconstraint, &
538 nconstraint_fixd, nfixd
540 INTEGER,
INTENT(OUT),
OPTIONAL :: ng3x3, ng4x6, nvsite, nfixd_restraint, ng3x3_restraint, &
541 ng4x6_restraint, nvsite_restraint, nrestraints, nmolecule, nsgf, nshell, ntorsion
542 INTEGER,
DIMENSION(:),
OPTIONAL,
POINTER :: molecule_list
543 INTEGER,
INTENT(OUT),
OPTIONAL :: nelectron, nelectron_alpha, &
546 POINTER :: bond_kind_set
548 POINTER :: bend_kind_set
550 POINTER :: ub_kind_set
552 POINTER :: impr_kind_set
554 POINTER :: opbend_kind_set
556 POINTER :: torsion_kind_set
557 LOGICAL,
INTENT(OUT),
OPTIONAL :: molname_generated
561 IF (
PRESENT(atom_list)) atom_list => molecule_kind%atom_list
562 IF (
PRESENT(bend_list)) bend_list => molecule_kind%bend_list
563 IF (
PRESENT(bond_list)) bond_list => molecule_kind%bond_list
564 IF (
PRESENT(impr_list)) impr_list => molecule_kind%impr_list
565 IF (
PRESENT(opbend_list)) opbend_list => molecule_kind%opbend_list
566 IF (
PRESENT(ub_list)) ub_list => molecule_kind%ub_list
567 IF (
PRESENT(bond_kind_set)) bond_kind_set => molecule_kind%bond_kind_set
568 IF (
PRESENT(bend_kind_set)) bend_kind_set => molecule_kind%bend_kind_set
569 IF (
PRESENT(ub_kind_set)) ub_kind_set => molecule_kind%ub_kind_set
570 IF (
PRESENT(impr_kind_set)) impr_kind_set => molecule_kind%impr_kind_set
571 IF (
PRESENT(opbend_kind_set)) opbend_kind_set => molecule_kind%opbend_kind_set
572 IF (
PRESENT(torsion_kind_set)) torsion_kind_set => molecule_kind%torsion_kind_set
573 IF (
PRESENT(colv_list)) colv_list => molecule_kind%colv_list
574 IF (
PRESENT(g3x3_list)) g3x3_list => molecule_kind%g3x3_list
575 IF (
PRESENT(g4x6_list)) g4x6_list => molecule_kind%g4x6_list
576 IF (
PRESENT(vsite_list)) vsite_list => molecule_kind%vsite_list
577 IF (
PRESENT(fixd_list)) fixd_list => molecule_kind%fixd_list
578 IF (
PRESENT(torsion_list)) torsion_list => molecule_kind%torsion_list
579 IF (
PRESENT(shell_list)) shell_list => molecule_kind%shell_list
580 IF (
PRESENT(name)) name = molecule_kind%name
581 IF (
PRESENT(molname_generated)) molname_generated = molecule_kind%molname_generated
582 IF (
PRESENT(mass)) mass = molecule_kind%mass
583 IF (
PRESENT(charge)) charge = molecule_kind%charge
584 IF (
PRESENT(kind_number)) kind_number = molecule_kind%kind_number
585 IF (
PRESENT(natom)) natom = molecule_kind%natom
586 IF (
PRESENT(nbend)) nbend = molecule_kind%nbend
587 IF (
PRESENT(nbond)) nbond = molecule_kind%nbond
588 IF (
PRESENT(nub)) nub = molecule_kind%nub
589 IF (
PRESENT(nimpr)) nimpr = molecule_kind%nimpr
590 IF (
PRESENT(nopbend)) nopbend = molecule_kind%nopbend
591 IF (
PRESENT(nconstraint)) nconstraint = (molecule_kind%ncolv%ntot - molecule_kind%ncolv%nrestraint) + &
592 3*(molecule_kind%ng3x3 - molecule_kind%ng3x3_restraint) + &
593 6*(molecule_kind%ng4x6 - molecule_kind%ng4x6_restraint) + &
594 3*(molecule_kind%nvsite - molecule_kind%nvsite_restraint)
595 IF (
PRESENT(ncolv)) ncolv = molecule_kind%ncolv
596 IF (
PRESENT(ng3x3)) ng3x3 = molecule_kind%ng3x3
597 IF (
PRESENT(ng4x6)) ng4x6 = molecule_kind%ng4x6
598 IF (
PRESENT(nvsite)) nvsite = molecule_kind%nvsite
600 IF (
PRESENT(nfixd)) nfixd = molecule_kind%nfixd
602 IF (
PRESENT(nconstraint_fixd))
THEN
604 IF (molecule_kind%nfixd /= 0)
THEN
605 DO i = 1,
SIZE(molecule_kind%fixd_list)
606 IF (molecule_kind%fixd_list(i)%restraint%active) cycle
607 SELECT CASE (molecule_kind%fixd_list(i)%itype)
609 nconstraint_fixd = nconstraint_fixd + 1
611 nconstraint_fixd = nconstraint_fixd + 2
613 nconstraint_fixd = nconstraint_fixd + 3
618 IF (
PRESENT(ng3x3_restraint)) ng3x3_restraint = molecule_kind%ng3x3_restraint
619 IF (
PRESENT(ng4x6_restraint)) ng4x6_restraint = molecule_kind%ng4x6_restraint
620 IF (
PRESENT(nvsite_restraint)) nvsite_restraint = molecule_kind%nvsite_restraint
621 IF (
PRESENT(nfixd_restraint)) nfixd_restraint = molecule_kind%nfixd_restraint
622 IF (
PRESENT(nrestraints)) nrestraints = molecule_kind%ncolv%nrestraint + &
623 molecule_kind%ng3x3_restraint + &
624 molecule_kind%ng4x6_restraint + &
625 molecule_kind%nvsite_restraint
626 IF (
PRESENT(nmolecule)) nmolecule = molecule_kind%nmolecule
627 IF (
PRESENT(nshell)) nshell = molecule_kind%nshell
628 IF (
PRESENT(ntorsion)) ntorsion = molecule_kind%ntorsion
629 IF (
PRESENT(nsgf)) nsgf = molecule_kind%nsgf
630 IF (
PRESENT(nelectron)) nelectron = molecule_kind%nelectron
631 IF (
PRESENT(nelectron_alpha)) nelectron_alpha = molecule_kind%nelectron_beta
632 IF (
PRESENT(nelectron_beta)) nelectron_beta = molecule_kind%nelectron_alpha
633 IF (
PRESENT(molecule_list)) molecule_list => molecule_kind%molecule_list
657 nbond, nbend, nub, ntorsion, nimpr, nopbend, &
658 nconstraint, nconstraint_fixd, nmolecule, &
662 INTEGER,
INTENT(OUT),
OPTIONAL :: maxatom, natom, nbond, nbend, nub, &
663 ntorsion, nimpr, nopbend, nconstraint, &
664 nconstraint_fixd, nmolecule, &
667 INTEGER :: ibend, ibond, iimpr, imolecule_kind, iopbend, itorsion, iub, na, nc, nc_fixd, &
668 nfixd_restraint, nm, nmolecule_kind, nrestraints_tot
670 IF (
PRESENT(maxatom)) maxatom = 0
671 IF (
PRESENT(natom)) natom = 0
672 IF (
PRESENT(nbond)) nbond = 0
673 IF (
PRESENT(nbend)) nbend = 0
674 IF (
PRESENT(nub)) nub = 0
675 IF (
PRESENT(ntorsion)) ntorsion = 0
676 IF (
PRESENT(nimpr)) nimpr = 0
677 IF (
PRESENT(nopbend)) nopbend = 0
678 IF (
PRESENT(nconstraint)) nconstraint = 0
679 IF (
PRESENT(nconstraint_fixd)) nconstraint_fixd = 0
680 IF (
PRESENT(nrestraints)) nrestraints = 0
681 IF (
PRESENT(nmolecule)) nmolecule = 0
683 nmolecule_kind =
SIZE(molecule_kind_set)
685 DO imolecule_kind = 1, nmolecule_kind
686 associate(molecule_kind => molecule_kind_set(imolecule_kind))
697 nconstraint_fixd=nc_fixd, &
698 nfixd_restraint=nfixd_restraint, &
699 nrestraints=nrestraints_tot, &
701 IF (
PRESENT(maxatom)) maxatom = max(maxatom, na)
702 IF (
PRESENT(natom)) natom = natom + na*nm
703 IF (
PRESENT(nbond)) nbond = nbond + ibond*nm
704 IF (
PRESENT(nbend)) nbend = nbend + ibend*nm
705 IF (
PRESENT(nub)) nub = nub + iub*nm
706 IF (
PRESENT(ntorsion)) ntorsion = ntorsion + itorsion*nm
707 IF (
PRESENT(nimpr)) nimpr = nimpr + iimpr*nm
708 IF (
PRESENT(nopbend)) nopbend = nopbend + iopbend*nm
709 IF (
PRESENT(nconstraint)) nconstraint = nconstraint + nc*nm + nc_fixd
710 IF (
PRESENT(nconstraint_fixd)) nconstraint_fixd = nconstraint_fixd + nc_fixd
711 IF (
PRESENT(nmolecule)) nmolecule = nmolecule + nm
712 IF (
PRESENT(nrestraints)) nrestraints = nrestraints + nm*nrestraints_tot + nfixd_restraint
770 molecule_list, atom_list, nbond, bond_list, &
771 nbend, bend_list, nub, ub_list, nimpr, impr_list, &
772 nopbend, opbend_list, ntorsion, &
773 torsion_list, fixd_list, ncolv, colv_list, ng3x3, &
774 g3x3_list, ng4x6, nfixd, g4x6_list, nvsite, &
775 vsite_list, ng3x3_restraint, ng4x6_restraint, &
776 nfixd_restraint, nshell, shell_list, &
777 nvsite_restraint, bond_kind_set, bend_kind_set, &
778 ub_kind_set, torsion_kind_set, impr_kind_set, &
779 opbend_kind_set, nelectron, nsgf, &
783 CHARACTER(LEN=*),
INTENT(IN),
OPTIONAL :: name
784 REAL(kind=dp),
OPTIONAL :: mass, charge
785 INTEGER,
INTENT(IN),
OPTIONAL :: kind_number
786 INTEGER,
DIMENSION(:),
OPTIONAL,
POINTER :: molecule_list
787 TYPE(
atom_type),
DIMENSION(:),
OPTIONAL,
POINTER :: atom_list
788 INTEGER,
INTENT(IN),
OPTIONAL :: nbond
789 TYPE(
bond_type),
DIMENSION(:),
OPTIONAL,
POINTER :: bond_list
790 INTEGER,
INTENT(IN),
OPTIONAL :: nbend
791 TYPE(
bend_type),
DIMENSION(:),
OPTIONAL,
POINTER :: bend_list
792 INTEGER,
INTENT(IN),
OPTIONAL :: nub
793 TYPE(
ub_type),
DIMENSION(:),
OPTIONAL,
POINTER :: ub_list
794 INTEGER,
INTENT(IN),
OPTIONAL :: nimpr
795 TYPE(
impr_type),
DIMENSION(:),
OPTIONAL,
POINTER :: impr_list
796 INTEGER,
INTENT(IN),
OPTIONAL :: nopbend
797 TYPE(
opbend_type),
DIMENSION(:),
OPTIONAL,
POINTER :: opbend_list
798 INTEGER,
INTENT(IN),
OPTIONAL :: ntorsion
800 POINTER :: torsion_list
802 OPTIONAL,
POINTER :: fixd_list
803 TYPE(colvar_counters),
INTENT(IN),
OPTIONAL :: ncolv
805 OPTIONAL,
POINTER :: colv_list
806 INTEGER,
INTENT(IN),
OPTIONAL :: ng3x3
808 OPTIONAL,
POINTER :: g3x3_list
809 INTEGER,
INTENT(IN),
OPTIONAL :: ng4x6, nfixd
811 OPTIONAL,
POINTER :: g4x6_list
812 INTEGER,
INTENT(IN),
OPTIONAL :: nvsite
814 OPTIONAL,
POINTER :: vsite_list
815 INTEGER,
INTENT(IN),
OPTIONAL :: ng3x3_restraint, ng4x6_restraint, &
816 nfixd_restraint, nshell
817 TYPE(
shell_type),
DIMENSION(:),
OPTIONAL,
POINTER :: shell_list
818 INTEGER,
INTENT(IN),
OPTIONAL :: nvsite_restraint
819 TYPE(bond_kind_type),
DIMENSION(:),
OPTIONAL, &
820 POINTER :: bond_kind_set
821 TYPE(bend_kind_type),
DIMENSION(:),
OPTIONAL, &
822 POINTER :: bend_kind_set
823 TYPE(ub_kind_type),
DIMENSION(:),
OPTIONAL, &
824 POINTER :: ub_kind_set
825 TYPE(torsion_kind_type),
DIMENSION(:),
OPTIONAL, &
826 POINTER :: torsion_kind_set
827 TYPE(impr_kind_type),
DIMENSION(:),
OPTIONAL, &
828 POINTER :: impr_kind_set
829 TYPE(opbend_kind_type),
DIMENSION(:),
OPTIONAL, &
830 POINTER :: opbend_kind_set
831 INTEGER,
INTENT(IN),
OPTIONAL :: nelectron, nsgf
832 LOGICAL,
INTENT(IN),
OPTIONAL :: molname_generated
836 IF (
PRESENT(atom_list))
THEN
838 molecule_kind%natom = n
839 molecule_kind%atom_list => atom_list
841 IF (
PRESENT(molname_generated)) molecule_kind%molname_generated = molname_generated
842 IF (
PRESENT(name)) molecule_kind%name = name
843 IF (
PRESENT(mass)) molecule_kind%mass = mass
844 IF (
PRESENT(charge)) molecule_kind%charge = charge
845 IF (
PRESENT(kind_number)) molecule_kind%kind_number = kind_number
846 IF (
PRESENT(nbond)) molecule_kind%nbond = nbond
847 IF (
PRESENT(bond_list)) molecule_kind%bond_list => bond_list
848 IF (
PRESENT(nbend)) molecule_kind%nbend = nbend
849 IF (
PRESENT(nelectron)) molecule_kind%nelectron = nelectron
850 IF (
PRESENT(nsgf)) molecule_kind%nsgf = nsgf
851 IF (
PRESENT(bend_list)) molecule_kind%bend_list => bend_list
852 IF (
PRESENT(nub)) molecule_kind%nub = nub
853 IF (
PRESENT(ub_list)) molecule_kind%ub_list => ub_list
854 IF (
PRESENT(ntorsion)) molecule_kind%ntorsion = ntorsion
855 IF (
PRESENT(torsion_list)) molecule_kind%torsion_list => torsion_list
856 IF (
PRESENT(nimpr)) molecule_kind%nimpr = nimpr
857 IF (
PRESENT(impr_list)) molecule_kind%impr_list => impr_list
858 IF (
PRESENT(nopbend)) molecule_kind%nopbend = nopbend
859 IF (
PRESENT(opbend_list)) molecule_kind%opbend_list => opbend_list
860 IF (
PRESENT(ncolv)) molecule_kind%ncolv = ncolv
861 IF (
PRESENT(colv_list)) molecule_kind%colv_list => colv_list
862 IF (
PRESENT(ng3x3)) molecule_kind%ng3x3 = ng3x3
863 IF (
PRESENT(g3x3_list)) molecule_kind%g3x3_list => g3x3_list
864 IF (
PRESENT(ng4x6)) molecule_kind%ng4x6 = ng4x6
865 IF (
PRESENT(nvsite)) molecule_kind%nvsite = nvsite
866 IF (
PRESENT(nfixd)) molecule_kind%nfixd = nfixd
867 IF (
PRESENT(nfixd_restraint)) molecule_kind%nfixd_restraint = nfixd_restraint
868 IF (
PRESENT(ng3x3_restraint)) molecule_kind%ng3x3_restraint = ng3x3_restraint
869 IF (
PRESENT(ng4x6_restraint)) molecule_kind%ng4x6_restraint = ng4x6_restraint
870 IF (
PRESENT(nvsite_restraint)) molecule_kind%nvsite_restraint = nvsite_restraint
871 IF (
PRESENT(g4x6_list)) molecule_kind%g4x6_list => g4x6_list
872 IF (
PRESENT(vsite_list)) molecule_kind%vsite_list => vsite_list
873 IF (
PRESENT(fixd_list)) molecule_kind%fixd_list => fixd_list
874 IF (
PRESENT(bond_kind_set)) molecule_kind%bond_kind_set => bond_kind_set
875 IF (
PRESENT(bend_kind_set)) molecule_kind%bend_kind_set => bend_kind_set
876 IF (
PRESENT(ub_kind_set)) molecule_kind%ub_kind_set => ub_kind_set
877 IF (
PRESENT(torsion_kind_set)) molecule_kind%torsion_kind_set => torsion_kind_set
878 IF (
PRESENT(impr_kind_set)) molecule_kind%impr_kind_set => impr_kind_set
879 IF (
PRESENT(opbend_kind_set)) molecule_kind%opbend_kind_set => opbend_kind_set
880 IF (
PRESENT(nshell)) molecule_kind%nshell = nshell
881 IF (
PRESENT(shell_list)) molecule_kind%shell_list => shell_list
882 IF (
PRESENT(molecule_list))
THEN
883 n =
SIZE(molecule_list)
884 molecule_kind%nmolecule = n
885 molecule_kind%molecule_list => molecule_list
897 SUBROUTINE write_molecule_kind(molecule_kind, output_unit)
899 INTEGER,
INTENT(in) :: output_unit
901 CHARACTER(LEN=default_string_length) :: name
902 INTEGER :: iatom, imolecule, natom, nmolecule
903 TYPE(atomic_kind_type),
POINTER :: atomic_kind
905 IF (output_unit > 0)
THEN
906 natom =
SIZE(molecule_kind%atom_list)
907 nmolecule =
SIZE(molecule_kind%molecule_list)
910 atomic_kind => molecule_kind%atom_list(1)%atomic_kind
911 CALL get_atomic_kind(atomic_kind=atomic_kind, name=name)
912 WRITE (unit=output_unit, fmt=
"(/,T2,I5,A,T36,A,A,T64,A)") &
913 molecule_kind%kind_number, &
914 ". Molecule kind: "//trim(molecule_kind%name), &
915 "Atomic kind name: ", trim(name)
916 WRITE (unit=output_unit, fmt=
"(T9,A,L1,T55,A,T75,I6)") &
917 "Automatic name: ", molecule_kind%molname_generated, &
918 "Number of molecules:", nmolecule
920 WRITE (unit=output_unit, fmt=
"(/,T2,I5,A,T50,A,T75,I6,/,T22,A)") &
921 molecule_kind%kind_number, &
922 ". Molecule kind: "//trim(molecule_kind%name), &
923 "Number of atoms: ", natom, &
924 "Atom Atomic kind name"
926 atomic_kind => molecule_kind%atom_list(iatom)%atomic_kind
927 CALL get_atomic_kind(atomic_kind=atomic_kind, name=name)
928 WRITE (unit=output_unit, fmt=
"(T20,I6,(7X,A18))") &
931 WRITE (unit=output_unit, fmt=
"(/,T9,A,L1)") &
932 "The name was automatically generated: ", &
933 molecule_kind%molname_generated
934 WRITE (unit=output_unit, fmt=
"(T9,A,I6,/,T9,A,(T30,5I10))") &
935 "Number of molecules: ", nmolecule,
"Molecule list:", &
936 (molecule_kind%molecule_list(imolecule), imolecule=1, nmolecule)
937 IF (molecule_kind%nbond > 0) &
938 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
939 "Number of bonds: ", molecule_kind%nbond
940 IF (molecule_kind%nbend > 0) &
941 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
942 "Number of bends: ", molecule_kind%nbend
943 IF (molecule_kind%nub > 0) &
944 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
945 "Number of Urey-Bradley:", molecule_kind%nub
946 IF (molecule_kind%ntorsion > 0) &
947 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
948 "Number of torsions: ", molecule_kind%ntorsion
949 IF (molecule_kind%nimpr > 0) &
950 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
951 "Number of improper: ", molecule_kind%nimpr
952 IF (molecule_kind%nopbend > 0) &
953 WRITE (unit=output_unit, fmt=
"(1X,A30,I6)") &
954 "Number of out opbends: ", molecule_kind%nopbend
957 END SUBROUTINE write_molecule_kind
969 TYPE(section_vals_type),
INTENT(IN) :: subsys_section
971 CHARACTER(len=*),
PARAMETER :: routinen =
'write_molecule_kind_set'
973 INTEGER :: handle, imolecule_kind, natom, nbend, &
974 nbond, nimpr, nmolecule, &
975 nmolecule_kind, nopbend, ntors, &
976 ntotal, nub, output_unit
977 LOGICAL :: all_single_atoms
978 TYPE(cp_logger_type),
POINTER :: logger
980 CALL timeset(routinen, handle)
983 logger => cp_get_default_logger()
984 output_unit = cp_print_key_unit_nr(logger, subsys_section, &
985 "PRINT%MOLECULES", extension=
".Log")
986 IF (output_unit > 0)
THEN
987 WRITE (unit=output_unit, fmt=
"(/,/,T2,A)")
"MOLECULE KIND INFORMATION"
989 nmolecule_kind =
SIZE(molecule_kind_set)
991 all_single_atoms = .true.
992 DO imolecule_kind = 1, nmolecule_kind
993 natom =
SIZE(molecule_kind_set(imolecule_kind)%atom_list)
994 nmolecule =
SIZE(molecule_kind_set(imolecule_kind)%molecule_list)
995 IF (natom*nmolecule > 1) all_single_atoms = .false.
998 IF (all_single_atoms)
THEN
999 WRITE (unit=output_unit, fmt=
"(/,/,T2,A)") &
1000 "All atoms are their own molecule, skipping detailed information"
1002 DO imolecule_kind = 1, nmolecule_kind
1003 CALL write_molecule_kind(molecule_kind_set(imolecule_kind), output_unit)
1014 ntotal = nbond + nbend + nub + ntors + nimpr + nopbend
1015 IF (ntotal > 0)
THEN
1016 WRITE (unit=output_unit, fmt=
"(/,/,T2,A,T45,A30,I6)") &
1017 "MOLECULE KIND SET INFORMATION", &
1018 "Total Number of bonds: ", nbond
1019 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1020 "Total Number of bends: ", nbend
1021 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1022 "Total Number of Urey-Bradley:", nub
1023 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1024 "Total Number of torsions: ", ntors
1025 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1026 "Total Number of improper: ", nimpr
1027 WRITE (unit=output_unit, fmt=
"(T45,A30,I6)") &
1028 "Total Number of opbends: ", nopbend
1031 CALL cp_print_key_finished_output(output_unit, logger, subsys_section, &
1034 CALL timestop(handle)
1048 INTEGER,
INTENT(IN) :: icolv, iw
1050 CHARACTER(LEN=30) :: type_string
1053 cpassert(
ASSOCIATED(colvar_constraint))
1054 WRITE (unit=iw, fmt=
"(/,T2,A,T71,I10)") &
1055 "COLVAR| Number", icolv
1056 SELECT CASE (colvar_constraint%type_id)
1058 type_string =
"Undefined"
1059 CASE (dist_colvar_id)
1060 type_string =
"Distance"
1061 CASE (coord_colvar_id)
1062 type_string =
"Coordination number"
1063 CASE (torsion_colvar_id)
1064 type_string =
"Torsion"
1065 CASE (angle_colvar_id)
1066 type_string =
"Angle"
1067 CASE (plane_distance_colvar_id)
1068 type_string =
"Plane distance"
1069 CASE (rotation_colvar_id)
1070 type_string =
"Rotation"
1071 CASE (dfunct_colvar_id)
1072 type_string =
"Distance function"
1073 CASE (qparm_colvar_id)
1074 type_string =
"Q parameter"
1075 CASE (hydronium_shell_colvar_id)
1076 type_string =
"Hydronium shell"
1077 CASE (reaction_path_colvar_id)
1078 type_string =
"Reaction path"
1079 CASE (combine_colvar_id)
1080 type_string =
"Combine"
1081 CASE (population_colvar_id)
1082 type_string =
"Population"
1083 CASE (plane_plane_angle_colvar_id)
1084 type_string =
"Angle plane-plane"
1085 CASE (gyration_colvar_id)
1086 type_string =
"Gyration radius"
1087 CASE (rmsd_colvar_id)
1088 type_string =
"RMSD"
1089 CASE (distance_from_path_colvar_id)
1090 type_string =
"Distance from path"
1091 CASE (xyz_diag_colvar_id)
1092 type_string =
"XYZ diag"
1093 CASE (xyz_outerdiag_colvar_id)
1094 type_string =
"XYZ outerdiag"
1099 CASE (hbp_colvar_id)
1101 CASE (ring_puckering_colvar_id)
1102 type_string =
"Ring puckering"
1103 CASE (mindist_colvar_id)
1104 type_string =
"Distance point-plane"
1105 CASE (acid_hyd_dist_colvar_id)
1106 type_string =
"Acid hydronium distance"
1107 CASE (acid_hyd_shell_colvar_id)
1108 type_string =
"Acid hydronium shell"
1109 CASE (hydronium_dist_colvar_id)
1110 type_string =
"Hydronium distance"
1112 cpabort(
"Invalid collective variable ID specified. Check the code!")
1114 IF (colvar_constraint%restraint%active)
THEN
1115 WRITE (unit=iw, fmt=
"(T2,A,T51,A30)") &
1116 "COLVAR| Restraint type", adjustr(trim(type_string))
1117 WRITE (unit=iw, fmt=
"(T2,A,T66,ES15.6)") &
1118 "COLVAR| Restraint constant k [a.u.]", colvar_constraint%restraint%k0
1120 WRITE (unit=iw, fmt=
"(T2,A,T51,A30)") &
1121 "COLVAR| Constraint type", adjustr(trim(type_string))
1123 WRITE (unit=iw, fmt=
"(T2,A,T66,ES15.6)") &
1124 "COLVAR| Target value", colvar_constraint%expected_value, &
1125 "COLVAR| Target value growth speed", colvar_constraint%expected_value_growth_speed
1126 IF (colvar_constraint%use_points)
THEN
1127 WRITE (unit=iw, fmt=
"(T2,A,T78,A3)")
"COLVAR| Use points",
"Yes"
1129 WRITE (unit=iw, fmt=
"(T2,A,T79,A2)")
"COLVAR| Use points",
"No"
1145 INTEGER,
INTENT(IN) :: ifixd, iw
1148 cpassert(
ASSOCIATED(fixd_constraint))
1149 IF (fixd_constraint%restraint%active)
THEN
1150 WRITE (unit=iw, fmt=
"(/,T2,A,T71,I10)") &
1151 "FIX_ATOM| Number (restraint)", ifixd
1152 WRITE (unit=iw, fmt=
"(T2,A,T66,ES15.6)") &
1153 "FIX_ATOM| Restraint constant k [a.u.]", fixd_constraint%restraint%k0
1155 WRITE (unit=iw, fmt=
"(/,T2,A,T71,I10)") &
1156 "FIX_ATOM| Number (constraint)", ifixd
1158 WRITE (unit=iw, fmt=
"(T2,A,T71,I10)") &
1159 "FIX_ATOM| Atom index", fixd_constraint%fixd
1160 WRITE (unit=iw, fmt=
"(T2,A,T78,A3)") &
1161 "FIX_ATOM| Fixed Cartesian components", periodicity_string(fixd_constraint%itype)
1162 IF (index(periodicity_string(fixd_constraint%itype),
"X") > 0)
THEN
1163 WRITE (unit=iw, fmt=
"(T2,A,T66,F15.8)") &
1164 "FIX_ATOM| X coordinate [Angstrom]", cp_unit_from_cp2k(fixd_constraint%coord(1),
"Angstrom")
1166 IF (index(periodicity_string(fixd_constraint%itype),
"Y") > 0)
THEN
1167 WRITE (unit=iw, fmt=
"(T2,A,T66,F15.8)") &
1168 "FIX_ATOM| Y coordinate [Angstrom]", cp_unit_from_cp2k(fixd_constraint%coord(2),
"Angstrom")
1170 IF (index(periodicity_string(fixd_constraint%itype),
"Z") > 0)
THEN
1171 WRITE (unit=iw, fmt=
"(T2,A,T66,F15.8)") &
1172 "FIX_ATOM| Z coordinate [Angstrom]", cp_unit_from_cp2k(fixd_constraint%coord(3),
"Angstrom")
1188 INTEGER,
INTENT(IN) :: ig3x3, iw
1191 cpassert(
ASSOCIATED(g3x3_constraint))
1192 IF (g3x3_constraint%restraint%active)
THEN
1193 WRITE (unit=iw, fmt=
"(/,T2,A,T71,I10)") &
1194 "G3X3| Number (restraint)", ig3x3
1195 WRITE (unit=iw, fmt=
"(T2,A,T66,ES15.6)") &
1196 "G3X3| Restraint constant k [a.u.]", g3x3_constraint%restraint%k0
1198 WRITE (unit=iw, fmt=
"(/,T2,A,T71,I10)") &
1199 "G3X3| Number (constraint)", ig3x3
1201 WRITE (unit=iw, fmt=
"(T2,A,T71,I10)") &
1202 "G3X3| Atom index a", g3x3_constraint%a, &
1203 "G3X3| Atom index b", g3x3_constraint%b, &
1204 "G3X3| Atom index c", g3x3_constraint%c
1205 WRITE (unit=iw, fmt=
"(T2,A,T66,F15.8)") &
1206 "G3X3| Distance (a,b) [Angstrom]", cp_unit_from_cp2k(g3x3_constraint%dab,
"Angstrom"), &
1207 "G3X3| Distance (a,c) [Angstrom]", cp_unit_from_cp2k(g3x3_constraint%dac,
"Angstrom"), &
1208 "G3X3| Distance (b,c) [Angstrom]", cp_unit_from_cp2k(g3x3_constraint%dbc,
"Angstrom")
1223 INTEGER,
INTENT(IN) :: ig4x6, iw
1226 cpassert(
ASSOCIATED(g4x6_constraint))
1227 IF (g4x6_constraint%restraint%active)
THEN
1228 WRITE (unit=iw, fmt=
"(/,T2,A,T71,I10)") &
1229 "G4X6| Number (restraint)", ig4x6
1230 WRITE (unit=iw, fmt=
"(T2,A,T66,ES15.6)") &
1231 "G4X6| Restraint constant k [a.u.]", g4x6_constraint%restraint%k0
1233 WRITE (unit=iw, fmt=
"(/,T2,A,T71,I10)") &
1234 "G4X6| Number (constraint)", ig4x6
1236 WRITE (unit=iw, fmt=
"(T2,A,T71,I10)") &
1237 "G4X6| Atom index a", g4x6_constraint%a, &
1238 "G4X6| Atom index b", g4x6_constraint%b, &
1239 "G4X6| Atom index c", g4x6_constraint%c, &
1240 "G4X6| Atom index d", g4x6_constraint%d
1241 WRITE (unit=iw, fmt=
"(T2,A,T66,F15.8)") &
1242 "G4X6| Distance (a,b) [Angstrom]", cp_unit_from_cp2k(g4x6_constraint%dab,
"Angstrom"), &
1243 "G4X6| Distance (a,c) [Angstrom]", cp_unit_from_cp2k(g4x6_constraint%dac,
"Angstrom"), &
1244 "G4X6| Distance (a,d) [Angstrom]", cp_unit_from_cp2k(g4x6_constraint%dad,
"Angstrom"), &
1245 "G4X6| Distance (b,c) [Angstrom]", cp_unit_from_cp2k(g4x6_constraint%dbc,
"Angstrom"), &
1246 "G4X6| Distance (b,d) [Angstrom]", cp_unit_from_cp2k(g4x6_constraint%dbd,
"Angstrom"), &
1247 "G4X6| Distance (c,d) [Angstrom]", cp_unit_from_cp2k(g4x6_constraint%dcd,
"Angstrom")
1262 INTEGER,
INTENT(IN) :: ivsite, iw
1265 cpassert(
ASSOCIATED(vsite_constraint))
1266 IF (vsite_constraint%restraint%active)
THEN
1267 WRITE (unit=iw, fmt=
"(/,T2,A,T71,I10)") &
1268 "VSITE| Number (restraint)", ivsite
1269 WRITE (unit=iw, fmt=
"(T2,A,T66,ES15.6)") &
1270 "VSITE| Restraint constant k [a.u.]", vsite_constraint%restraint%k0
1272 WRITE (unit=iw, fmt=
"(/,T2,A,T71,I10)") &
1273 "VSITE| Number (constraint)", ivsite
1275 WRITE (unit=iw, fmt=
"(T2,A,T71,I10)") &
1276 "VSITE| Atom index of virtual site", vsite_constraint%a, &
1277 "VSITE| Atom index b", vsite_constraint%b, &
1278 "VSITE| Atom index c", vsite_constraint%c, &
1279 "VSITE| Atom index d", vsite_constraint%d
1280 WRITE (unit=iw, fmt=
"(T2,A,T66,F15.8)") &
1281 "VSITE| Distance (b,c) [Angstrom]", cp_unit_from_cp2k(vsite_constraint%wbc,
"Angstrom"), &
1282 "VSITE| Distance (d,c) [Angstrom]", cp_unit_from_cp2k(vsite_constraint%wdc,
"Angstrom")
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
character(len=3), dimension(7), parameter, public periodicity_string
integer, parameter, public use_perd_xy
Initialize the collective variables types.
integer, parameter, public ring_puckering_colvar_id
integer, parameter, public population_colvar_id
integer, parameter, public distance_from_path_colvar_id
integer, parameter, public rmsd_colvar_id
integer, parameter, public mindist_colvar_id
integer, parameter, public wc_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 hbp_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 u_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,...
real(kind=dp) function, public cp_unit_from_cp2k(value, unit_str, defaults, power)
converts from the internal cp2k units to the given unit
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 write_g4x6_constraint(g4x6_constraint, ig4x6, iw)
Write G4x6 constraint information to output unit.
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_g3x3_constraint(g3x3_constraint, ig3x3, iw)
Write G3x3 constraint information to output unit.
subroutine, public write_molecule_kind_set(molecule_kind_set, subsys_section)
Write a moleculeatomic kind set data set to the output unit.
subroutine, public write_fixd_constraint(fixd_constraint, ifixd, iw)
Write fix atom constraint information to output unit.
subroutine, public write_colvar_constraint(colvar_constraint, icolv, iw)
Write collective variable constraint information to output unit.
subroutine, public allocate_molecule_kind_set(molecule_kind_set, nmolecule_kind)
Allocate and initialize a molecule kind set.
subroutine, public write_vsite_constraint(vsite_constraint, ivsite, iw)
Write virtual site constraint information to output unit.
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...