81#include "./base/base_uses.f90"
85 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'force_fields_input'
105 SUBROUTINE read_force_field_section1(ff_section, mm_section, ff_type, para_env)
106 TYPE(section_vals_type),
POINTER :: ff_section, mm_section
107 TYPE(force_field_type),
INTENT(INOUT) :: ff_type
108 TYPE(mp_para_env_type),
POINTER :: para_env
110 CHARACTER(LEN=default_string_length), &
111 DIMENSION(:),
POINTER :: atm_names
112 INTEGER :: nace, nallegro, nb4, nbends, nbm, nbmhft, nbmhftd, nbonds, nchg, ndeepmd, neam, &
113 ngal, ngal21, ngd, ngp, nimpr, nipbv, nlj, nnequip, nopbend, nshell, nsiepmann, ntab, &
114 ntersoff, ntors, ntot, nubs, nwl
115 LOGICAL :: explicit, unique_spline
116 REAL(KIND=
dp) :: min_eps_spline_allowed
117 TYPE(input_info_type),
POINTER :: inp_info
118 TYPE(section_vals_type),
POINTER :: tmp_section, tmp_section2
122 NULLIFY (tmp_section, tmp_section2)
123 inp_info => ff_type%inp_info
133 CALL section_vals_val_get(ff_section,
"IGNORE_MISSING_CRITICAL_PARAMS", l_val=ff_type%ignore_missing_critical)
134 cpassert(ff_type%max_energy <= ff_type%emax_spline)
136 SELECT CASE (ff_type%ff_type)
139 IF (trim(ff_type%ff_file_name) ==
"") &
140 cpabort(
"Force Field Parameter's filename is empty! Please check your input file.")
144 cpabort(
"Force field type not implemented")
152 min_eps_spline_allowed = 20.0_dp*max(ff_type%max_energy, 10.0_dp)*epsilon(0.0_dp)
153 IF (ff_type%eps_spline < min_eps_spline_allowed)
THEN
154 CALL cp_warn(__location__, &
155 "Requested spline accuracy ("//trim(
cp_to_string(ff_type%eps_spline))//
" ) "// &
156 "is smaller than the minimum value allowed ("//trim(
cp_to_string(min_eps_spline_allowed))// &
157 " ) with the present machine precision ("//trim(
cp_to_string(epsilon(0.0_dp)))//
" ). "// &
158 "New EPS_SPLINE value ("//trim(
cp_to_string(min_eps_spline_allowed))//
" ). ")
159 ff_type%eps_spline = min_eps_spline_allowed
172 IF (explicit .AND. ff_type%do_nonbonded)
THEN
194 CALL read_eam_section(inp_info%nonbonded, tmp_section2, ntot, para_env, mm_section)
199 ntot = nlj + nwl + neam
207 ntot = nlj + nwl + neam + ngd
210 CALL read_ipbv_section(inp_info%nonbonded, tmp_section2, ntot)
215 ntot = nlj + nwl + neam + ngd + nipbv
218 CALL read_bmhft_section(inp_info%nonbonded, tmp_section2, ntot)
222 CALL section_vals_get(tmp_section2, explicit=explicit, n_repetition=nbmhftd)
223 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft
226 CALL read_bmhftd_section(inp_info%nonbonded, tmp_section2, ntot)
231 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd
234 CALL read_b4_section(inp_info%nonbonded, tmp_section2, ntot)
239 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4
242 CALL read_bm_section(inp_info%nonbonded, tmp_section2, ntot)
247 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm
253 CALL section_vals_get(tmp_section2, explicit=explicit, n_repetition=ntersoff)
254 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp
257 CALL read_tersoff_section(inp_info%nonbonded, tmp_section2, ntot, tmp_section2)
262 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff
265 CALL read_gal_section(inp_info%nonbonded, tmp_section2, ntot, tmp_section2)
270 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + ngal
273 CALL read_gal21_section(inp_info%nonbonded, tmp_section2, ntot, tmp_section2)
277 CALL section_vals_get(tmp_section2, explicit=explicit, n_repetition=nsiepmann)
278 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + ngal + ngal21
281 CALL read_siepmann_section(inp_info%nonbonded, tmp_section2, ntot, tmp_section2)
285 CALL section_vals_get(tmp_section2, explicit=explicit, n_repetition=nnequip)
286 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + &
287 ngal + ngal21 + nsiepmann
291 nnequip = nnequip - 1 +
SIZE(atm_names) + (
SIZE(atm_names)*
SIZE(atm_names) -
SIZE(atm_names))/2
293 CALL read_nequip_section(inp_info%nonbonded, tmp_section2, ntot)
297 CALL section_vals_get(tmp_section2, explicit=explicit, n_repetition=nallegro)
298 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + &
299 ngal + ngal21 + nsiepmann + nnequip
303 nallegro = nallegro - 1 +
SIZE(atm_names) + (
SIZE(atm_names)*
SIZE(atm_names) -
SIZE(atm_names))/2
305 CALL read_allegro_section(inp_info%nonbonded, tmp_section2, ntot)
310 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + &
311 ngal + ngal21 + nsiepmann + nnequip + nallegro
314 CALL read_tabpot_section(inp_info%nonbonded, tmp_section2, ntot, para_env, mm_section)
318 CALL section_vals_get(tmp_section2, explicit=explicit, n_repetition=ndeepmd)
319 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + &
320 ngal + ngal21 + nsiepmann + nnequip + nallegro + ntab
324 ndeepmd = ndeepmd - 1 +
SIZE(atm_names) + (
SIZE(atm_names)*
SIZE(atm_names) -
SIZE(atm_names))/2
326 CALL read_deepmd_section(inp_info%nonbonded, tmp_section2, ntot)
331 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + &
332 ngal + ngal21 + nsiepmann + nnequip + nallegro + ntab + ndeepmd
336 nace = nace - 1 +
SIZE(atm_names) + (
SIZE(atm_names)*
SIZE(atm_names) -
SIZE(atm_names))/2
338 CALL read_ace_section(inp_info%nonbonded, tmp_section2, ntot)
345 IF (explicit .AND. ff_type%do_nonbonded)
THEN
369 ntot = nlj + nwl + ngd
390 CALL read_apol_section(inp_info%apol_atm, inp_info%apol, inp_info%damping_list, &
399 CALL read_cpol_section(inp_info%cpol_atm, inp_info%cpol, tmp_section, ntot)
406 CALL read_shell_section(inp_info%shell_list, tmp_section, ntot)
413 CALL reallocate(inp_info%bond_kind, 1, nbonds)
416 CALL reallocate(inp_info%bond_k, 1, 3, 1, nbonds)
419 CALL read_bonds_section(inp_info%bond_kind, inp_info%bond_a, inp_info%bond_b, inp_info%bond_k, &
420 inp_info%bond_r0, inp_info%bond_cs, tmp_section, ntot)
426 CALL reallocate(inp_info%bend_kind, 1, nbends)
431 CALL reallocate(inp_info%bend_theta0, 1, nbends)
433 CALL reallocate(inp_info%bend_r012, 1, nbends)
434 CALL reallocate(inp_info%bend_r032, 1, nbends)
435 CALL reallocate(inp_info%bend_kbs12, 1, nbends)
436 CALL reallocate(inp_info%bend_kbs32, 1, nbends)
438 IF (
ASSOCIATED(inp_info%bend_legendre))
THEN
439 DO i = 1,
SIZE(inp_info%bend_legendre)
440 IF (
ASSOCIATED(inp_info%bend_legendre(i)%coeffs))
THEN
441 DEALLOCATE (inp_info%bend_legendre(i)%coeffs)
442 NULLIFY (inp_info%bend_legendre(i)%coeffs)
445 DEALLOCATE (inp_info%bend_legendre)
446 NULLIFY (inp_info%bend_legendre)
448 ALLOCATE (inp_info%bend_legendre(1:nbends))
449 DO i = 1,
SIZE(inp_info%bend_legendre(1:nbends))
450 NULLIFY (inp_info%bend_legendre(i)%coeffs)
451 inp_info%bend_legendre(i)%order = 0
453 CALL read_bends_section(inp_info%bend_kind, inp_info%bend_a, inp_info%bend_b, inp_info%bend_c, &
454 inp_info%bend_k, inp_info%bend_theta0, inp_info%bend_cb, &
455 inp_info%bend_r012, inp_info%bend_r032, inp_info%bend_kbs12, &
456 inp_info%bend_kbs32, inp_info%bend_kss, &
457 inp_info%bend_legendre, tmp_section, ntot)
469 CALL read_ubs_section(inp_info%ub_kind, inp_info%ub_a, inp_info%ub_b, inp_info%ub_c, &
470 inp_info%ub_k, inp_info%ub_r0, tmp_section, ntot)
476 CALL reallocate(inp_info%torsion_kind, 1, ntors)
483 CALL reallocate(inp_info%torsion_phi0, 1, ntors)
484 CALL read_torsions_section(inp_info%torsion_kind, inp_info%torsion_a, inp_info%torsion_b, &
485 inp_info%torsion_c, inp_info%torsion_d, inp_info%torsion_k, inp_info%torsion_phi0, &
486 inp_info%torsion_m, tmp_section, ntot)
500 CALL read_improper_section(inp_info%impr_kind, inp_info%impr_a, inp_info%impr_b, &
501 inp_info%impr_c, inp_info%impr_d, inp_info%impr_k, inp_info%impr_phi0, &
509 CALL reallocate(inp_info%opbend_kind, 1, nopbend)
510 CALL reallocate(inp_info%opbend_a, 1, nopbend)
511 CALL reallocate(inp_info%opbend_b, 1, nopbend)
512 CALL reallocate(inp_info%opbend_c, 1, nopbend)
513 CALL reallocate(inp_info%opbend_d, 1, nopbend)
514 CALL reallocate(inp_info%opbend_k, 1, nopbend)
515 CALL reallocate(inp_info%opbend_phi0, 1, nopbend)
516 CALL read_opbend_section(inp_info%opbend_kind, inp_info%opbend_a, inp_info%opbend_b, &
517 inp_info%opbend_c, inp_info%opbend_d, inp_info%opbend_k, inp_info%opbend_phi0, &
521 END SUBROUTINE read_force_field_section1
530 SUBROUTINE set_ipbv_ff(at1, at2, ipbv)
531 CHARACTER(LEN=*),
INTENT(IN) :: at1, at2
532 TYPE(ipbv_pot_type),
POINTER :: ipbv
534 IF ((at1(1:1) ==
'O') .AND. (at2(1:1) ==
'O'))
THEN
536 ipbv%m = -1.2226442563398141e+11_dp
537 ipbv%b = 1.1791292385486696e+11_dp
540 ipbv%a(2) = 4.786380682394_dp
541 ipbv%a(3) = -1543.407053545_dp
542 ipbv%a(4) = 88783.31188529_dp
543 ipbv%a(5) = -2361200.155376_dp
544 ipbv%a(6) = 35940504.84679_dp
545 ipbv%a(7) = -339762743.6358_dp
546 ipbv%a(8) = 2043874926.466_dp
547 ipbv%a(9) = -7654856796.383_dp
548 ipbv%a(10) = 16195251405.65_dp
549 ipbv%a(11) = -13140392992.18_dp
550 ipbv%a(12) = -9285572894.245_dp
551 ipbv%a(13) = 8756947519.029_dp
552 ipbv%a(14) = 15793297761.67_dp
553 ipbv%a(15) = 12917180227.21_dp
554 ELSEIF (((at1(1:1) ==
'O') .AND. (at2(1:1) ==
'H')) .OR. &
555 ((at1(1:1) ==
'H') .AND. (at2(1:1) ==
'O')))
THEN
558 ipbv%m = -0.004025691139759147_dp
559 ipbv%b = -2.193731138097428_dp
561 ipbv%a(2) = -195.7716013277_dp
562 ipbv%a(3) = 15343.78613395_dp
563 ipbv%a(4) = -530864.4586516_dp
564 ipbv%a(5) = 10707934.39058_dp
565 ipbv%a(6) = -140099704.7890_dp
566 ipbv%a(7) = 1250943273.785_dp
567 ipbv%a(8) = -7795458330.676_dp
568 ipbv%a(9) = 33955897217.31_dp
569 ipbv%a(10) = -101135640744.0_dp
570 ipbv%a(11) = 193107995718.7_dp
571 ipbv%a(12) = -193440560940.0_dp
572 ipbv%a(13) = -4224406093.918e0_dp
573 ipbv%a(14) = 217192386506.5e0_dp
574 ipbv%a(15) = -157581228915.5_dp
575 ELSEIF ((at1(1:1) ==
'H') .AND. (at2(1:1) ==
'H'))
THEN
576 ipbv%rcore = 3.165_dp
577 ipbv%m = 0.002639704108787555_dp
578 ipbv%b = -0.2735482611857583_dp
580 ipbv%a(2) = -26.29456010782_dp
581 ipbv%a(3) = 2373.352548248_dp
582 ipbv%a(4) = -93880.43551360_dp
583 ipbv%a(5) = 2154624.884809_dp
584 ipbv%a(6) = -31965151.34955_dp
585 ipbv%a(7) = 322781785.3278_dp
586 ipbv%a(8) = -2271097368.668_dp
587 ipbv%a(9) = 11169163192.90_dp
588 ipbv%a(10) = -37684457778.47_dp
589 ipbv%a(11) = 82562104256.03_dp
590 ipbv%a(12) = -100510435213.4_dp
591 ipbv%a(13) = 24570342714.65e0_dp
592 ipbv%a(14) = 88766181532.94e0_dp
593 ipbv%a(15) = -79705131323.98_dp
595 cpabort(
"IPBV only for WATER")
597 END SUBROUTINE set_ipbv_ff
606 SUBROUTINE set_bmhft_ff(at1, at2, ft)
607 CHARACTER(LEN=*),
INTENT(IN) :: at1, at2
608 TYPE(ft_pot_type),
POINTER :: ft
611 IF ((at1(1:2) ==
'NA') .AND. (at2(1:2) ==
'NA'))
THEN
615 ELSEIF (((at1(1:2) ==
'NA') .AND. (at2(1:2) ==
'CL')) .OR. &
616 ((at1(1:2) ==
'CL') .AND. (at2(1:2) ==
'NA')))
THEN
620 ELSEIF ((at1(1:2) ==
'CL') .AND. (at2(1:2) ==
'CL'))
THEN
625 cpabort(
"BMHFT only for NaCl")
628 END SUBROUTINE set_bmhft_ff
634 SUBROUTINE set_bmhftd_ff()
636 cpabort(
"No default parameters present for BMHFTD")
638 END SUBROUTINE set_bmhftd_ff
649 SUBROUTINE read_eam_section(nonbonded, section, start, para_env, mm_section)
650 TYPE(pair_potential_p_type),
POINTER :: nonbonded
651 TYPE(section_vals_type),
POINTER :: section
652 INTEGER,
INTENT(IN) :: start
653 TYPE(mp_para_env_type),
POINTER :: para_env
654 TYPE(section_vals_type),
POINTER :: mm_section
656 CHARACTER(LEN=default_string_length), &
657 DIMENSION(:),
POINTER :: atm_names
658 INTEGER :: isec, n_items
664 nonbonded%pot(start + isec)%pot%type =
ea_type
665 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
666 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
667 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
668 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
670 c_val=nonbonded%pot(start + isec)%pot%set(1)%eam%eam_file_name)
671 CALL read_eam_data(nonbonded%pot(start + isec)%pot%set(1)%eam, para_env, mm_section)
672 nonbonded%pot(start + isec)%pot%rcutsq = nonbonded%pot(start + isec)%pot%set(1)%eam%acutal**2
674 END SUBROUTINE read_eam_section
682 SUBROUTINE read_ace_section(nonbonded, section, start)
683 TYPE(pair_potential_p_type),
POINTER :: nonbonded
684 TYPE(section_vals_type),
POINTER :: section
685 INTEGER,
INTENT(IN) :: start
687 CHARACTER(LEN=2),
ALLOCATABLE,
DIMENSION(:) :: ace_atype_symbol
688 CHARACTER(LEN=default_path_length) :: ace_filename
689 CHARACTER(LEN=default_string_length) :: ace_file_name
690 CHARACTER(LEN=default_string_length), &
691 DIMENSION(:),
POINTER :: atm_names
692 INTEGER :: ace_ntype, isec, jsec, n_items
693 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: rcutall
694 TYPE(ace_model_type) :: model
698 n_items = isec*n_items
701 ace_ntype =
SIZE(atm_names)
702 ALLOCATE (ace_atype_symbol(ace_ntype), rcutall(ace_ntype, ace_ntype))
703 DO isec = 1, ace_ntype
704 ace_atype_symbol(isec) = atm_names(isec) (1:2)
713 fname=trim(ace_filename), rcutc=rcutall, model=model)
715 cpabort(
"CP2K was compiled without ACE library.")
718 DO isec = 1,
SIZE(atm_names)
719 DO jsec = isec,
SIZE(atm_names)
720 nonbonded%pot(start + n_items)%pot%type =
ace_type
721 nonbonded%pot(start + n_items)%pot%at1 = atm_names(isec)
722 nonbonded%pot(start + n_items)%pot%at2 = atm_names(jsec)
723 CALL uppercase(nonbonded%pot(start + n_items)%pot%at1)
724 CALL uppercase(nonbonded%pot(start + n_items)%pot%at2)
726 nonbonded%pot(start + n_items)%pot%set(1)%ace%ace_file_name = ace_filename
727 nonbonded%pot(start + n_items)%pot%set(1)%ace%atom_ace_type = isec
728 nonbonded%pot(start + n_items)%pot%set(1)%ace%model = model
732 nonbonded%pot(start + n_items)%pot%rcutsq =
cp_unit_to_cp2k(rcutall(isec, jsec),
"angstrom")**2
734 n_items = n_items + 1
737 END SUBROUTINE read_ace_section
746 SUBROUTINE read_deepmd_section(nonbonded, section, start)
747 TYPE(pair_potential_p_type),
POINTER :: nonbonded
748 TYPE(section_vals_type),
POINTER :: section
749 INTEGER,
INTENT(IN) :: start
751 CHARACTER(LEN=default_string_length) :: deepmd_file_name
752 CHARACTER(LEN=default_string_length), &
753 DIMENSION(:),
POINTER :: atm_names
754 INTEGER :: isec, jsec, n_items
755 INTEGER,
DIMENSION(:),
POINTER :: atm_deepmd_types
759 n_items = isec*n_items
764 DO isec = 1,
SIZE(atm_names)
765 DO jsec = isec,
SIZE(atm_names)
766 nonbonded%pot(start + n_items)%pot%type =
deepmd_type
767 nonbonded%pot(start + n_items)%pot%at1 = atm_names(isec)
768 nonbonded%pot(start + n_items)%pot%at2 = atm_names(jsec)
769 CALL uppercase(nonbonded%pot(start + n_items)%pot%at1)
770 CALL uppercase(nonbonded%pot(start + n_items)%pot%at2)
772 nonbonded%pot(start + n_items)%pot%set(1)%deepmd%deepmd_file_name =
discover_file(deepmd_file_name)
773 nonbonded%pot(start + n_items)%pot%set(1)%deepmd%atom_deepmd_type = atm_deepmd_types(isec)
774 nonbonded%pot(start + n_items)%pot%rcutsq = 0.0_dp
775 n_items = n_items + 1
778 END SUBROUTINE read_deepmd_section
787 SUBROUTINE read_nequip_section(nonbonded, section, start)
788 TYPE(pair_potential_p_type),
POINTER :: nonbonded
789 TYPE(section_vals_type),
POINTER :: section
790 INTEGER,
INTENT(IN) :: start
792 CHARACTER(LEN=default_string_length) :: nequip_file_name, unit_cell, &
793 unit_coords, unit_energy, unit_forces
794 CHARACTER(LEN=default_string_length), &
795 DIMENSION(:),
POINTER :: atm_names
796 INTEGER :: isec, jsec, n_items
797 TYPE(nequip_pot_type) :: nequip
801 n_items = isec*n_items
811 nequip%unit_coords = unit_coords
812 nequip%unit_forces = unit_forces
813 nequip%unit_energy = unit_energy
814 nequip%unit_cell = unit_cell
815 CALL read_nequip_data(nequip)
816 CALL check_cp2k_atom_names_in_torch(atm_names, nequip%type_names_torch)
818 DO isec = 1,
SIZE(atm_names)
819 DO jsec = isec,
SIZE(atm_names)
820 nonbonded%pot(start + n_items)%pot%type =
nequip_type
821 nonbonded%pot(start + n_items)%pot%at1 = atm_names(isec)
822 nonbonded%pot(start + n_items)%pot%at2 = atm_names(jsec)
823 CALL uppercase(nonbonded%pot(start + n_items)%pot%at1)
824 CALL uppercase(nonbonded%pot(start + n_items)%pot%at2)
825 nonbonded%pot(start + n_items)%pot%set(1)%nequip = nequip
826 nonbonded%pot(start + n_items)%pot%rcutsq = nequip%rcutsq
827 n_items = n_items + 1
831 END SUBROUTINE read_nequip_section
840 SUBROUTINE read_allegro_section(nonbonded, section, start)
841 TYPE(pair_potential_p_type),
POINTER :: nonbonded
842 TYPE(section_vals_type),
POINTER :: section
843 INTEGER,
INTENT(IN) :: start
845 CHARACTER(LEN=default_string_length) :: allegro_file_name, unit_cell, &
846 unit_coords, unit_energy, unit_forces
847 CHARACTER(LEN=default_string_length), &
848 DIMENSION(:),
POINTER :: atm_names
849 INTEGER :: isec, jsec, n_items
850 TYPE(allegro_pot_type) :: allegro
854 n_items = isec*n_items
864 allegro%unit_coords = unit_coords
865 allegro%unit_forces = unit_forces
866 allegro%unit_energy = unit_energy
867 allegro%unit_cell = unit_cell
868 CALL read_allegro_data(allegro)
869 CALL check_cp2k_atom_names_in_torch(atm_names, allegro%type_names_torch)
871 DO isec = 1,
SIZE(atm_names)
872 DO jsec = isec,
SIZE(atm_names)
874 nonbonded%pot(start + n_items)%pot%at1 = atm_names(isec)
875 nonbonded%pot(start + n_items)%pot%at2 = atm_names(jsec)
876 CALL uppercase(nonbonded%pot(start + n_items)%pot%at1)
877 CALL uppercase(nonbonded%pot(start + n_items)%pot%at2)
878 nonbonded%pot(start + n_items)%pot%set(1)%allegro = allegro
879 nonbonded%pot(start + n_items)%pot%rcutsq = allegro%rcutsq
880 n_items = n_items + 1
883 END SUBROUTINE read_allegro_section
895 INTEGER,
INTENT(IN) :: start
897 CHARACTER(LEN=default_string_length), &
898 DIMENSION(:),
POINTER :: atm_names
899 INTEGER :: isec, n_items, n_rep
900 REAL(kind=
dp) :: epsilon, rcut, sigma
910 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
911 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
912 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
913 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
914 nonbonded%pot(start + isec)%pot%set(1)%lj%epsilon = epsilon
915 nonbonded%pot(start + isec)%pot%set(1)%lj%sigma6 = sigma**6
916 nonbonded%pot(start + isec)%pot%set(1)%lj%sigma12 = sigma**12
917 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
921 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
924 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
938 INTEGER,
INTENT(IN) :: start
940 CHARACTER(LEN=default_string_length), &
941 DIMENSION(:),
POINTER :: atm_names
942 INTEGER :: isec, n_items, n_rep
943 REAL(kind=
dp) :: a, b, c, rcut
953 nonbonded%pot(start + isec)%pot%type =
wl_type
954 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
955 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
956 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
957 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
958 nonbonded%pot(start + isec)%pot%set(1)%willis%a = a
959 nonbonded%pot(start + isec)%pot%set(1)%willis%b = b
960 nonbonded%pot(start + isec)%pot%set(1)%willis%c = c
961 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
965 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
968 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
982 INTEGER,
INTENT(IN) :: start
984 CHARACTER(LEN=default_string_length), &
985 DIMENSION(:),
POINTER :: atm_names
986 INTEGER :: isec, m, mc, n_items, n_rep
987 REAL(kind=
dp) :: d, dc, rcut, vr0
999 nonbonded%pot(start + isec)%pot%type =
gw_type
1000 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1001 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1002 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1003 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1004 nonbonded%pot(start + isec)%pot%set(1)%goodwin%vr0 = vr0
1005 nonbonded%pot(start + isec)%pot%set(1)%goodwin%d = d
1006 nonbonded%pot(start + isec)%pot%set(1)%goodwin%dc = dc
1007 nonbonded%pot(start + isec)%pot%set(1)%goodwin%m = m
1008 nonbonded%pot(start + isec)%pot%set(1)%goodwin%mc = mc
1009 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
1013 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1016 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1027 SUBROUTINE read_ipbv_section(nonbonded, section, start)
1030 INTEGER,
INTENT(IN) :: start
1032 CHARACTER(LEN=default_string_length), &
1033 DIMENSION(:),
POINTER :: atm_names
1034 INTEGER :: isec, n_items, n_rep
1035 REAL(kind=
dp) :: rcut
1038 DO isec = 1, n_items
1040 nonbonded%pot(start + isec)%pot%type =
ip_type
1041 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1042 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1043 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1044 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1045 CALL set_ipbv_ff(nonbonded%pot(start + isec)%pot%at1, nonbonded%pot(start + isec)%pot%at2, &
1046 nonbonded%pot(start + isec)%pot%set(1)%ipbv)
1048 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1052 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1055 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1057 END SUBROUTINE read_ipbv_section
1066 SUBROUTINE read_bmhft_section(nonbonded, section, start)
1069 INTEGER,
INTENT(IN) :: start
1071 CHARACTER(LEN=default_string_length),
DIMENSION(2) :: map_atoms
1072 CHARACTER(LEN=default_string_length), &
1073 DIMENSION(:),
POINTER :: atm_names
1074 INTEGER :: i, isec, n_items, n_rep
1075 REAL(kind=
dp) :: rcut
1078 DO isec = 1, n_items
1082 nonbonded%pot(start + isec)%pot%type =
ft_type
1083 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1084 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1085 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1086 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1091 r_val=nonbonded%pot(start + isec)%pot%set(1)%ft%a)
1093 r_val=nonbonded%pot(start + isec)%pot%set(1)%ft%b)
1095 r_val=nonbonded%pot(start + isec)%pot%set(1)%ft%c)
1097 r_val=nonbonded%pot(start + isec)%pot%set(1)%ft%d)
1100 map_atoms = atm_names
1103 CALL set_bmhft_ff(map_atoms(1), map_atoms(2), nonbonded%pot(start + isec)%pot%set(1)%ft)
1106 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1110 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1113 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1115 END SUBROUTINE read_bmhft_section
1124 SUBROUTINE read_bmhftd_section(nonbonded, section, start)
1127 INTEGER,
INTENT(IN) :: start
1129 CHARACTER(LEN=default_string_length),
DIMENSION(2) :: map_atoms
1130 CHARACTER(LEN=default_string_length), &
1131 DIMENSION(:),
POINTER :: atm_names
1132 INTEGER :: i, isec, n_items, n_rep
1133 REAL(kind=
dp) :: rcut
1134 REAL(kind=
dp),
DIMENSION(:),
POINTER :: bd_vals
1140 DO isec = 1, n_items
1144 nonbonded%pot(start + isec)%pot%type =
ftd_type
1145 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1146 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1147 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1148 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1153 r_val=nonbonded%pot(start + isec)%pot%set(1)%ftd%a)
1155 r_val=nonbonded%pot(start + isec)%pot%set(1)%ftd%b)
1157 r_val=nonbonded%pot(start + isec)%pot%set(1)%ftd%c)
1159 r_val=nonbonded%pot(start + isec)%pot%set(1)%ftd%d)
1161 IF (
ASSOCIATED(bd_vals))
THEN
1162 SELECT CASE (
SIZE(bd_vals))
1164 cpabort(
"No values specified for parameter BD in section &BMHFTD")
1166 nonbonded%pot(start + isec)%pot%set(1)%ftd%bd(1:2) = bd_vals(1)
1168 nonbonded%pot(start + isec)%pot%set(1)%ftd%bd(1:2) = bd_vals(1:2)
1170 cpabort(
"Too many values specified for parameter BD in section &BMHFTD")
1173 cpabort(
"Parameter BD in section &BMHFTD was not specified")
1177 map_atoms = atm_names
1180 CALL set_bmhftd_ff()
1183 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1187 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1190 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1192 END SUBROUTINE read_bmhftd_section
1203 SUBROUTINE read_b4_section(nonbonded, section, start)
1207 INTEGER,
INTENT(IN) :: start
1209 CHARACTER(LEN=default_string_length), &
1210 DIMENSION(:),
POINTER :: atm_names
1211 INTEGER :: i, ir, isec, n_items, n_rep, np1, np2
1212 LOGICAL :: explicit_poly1, explicit_poly2
1213 REAL(kind=
dp) :: a, b, c, eval_error, r1, r2, r3, rcut
1214 REAL(kind=
dp),
DIMENSION(10) :: v, x
1215 REAL(kind=
dp),
DIMENSION(10, 10) :: p, p_inv
1216 REAL(kind=
dp),
DIMENSION(:),
POINTER :: coeff1, coeff2,
list
1223 DO isec = 1, n_items
1233 IF (explicit_poly1)
THEN
1238 IF (
ASSOCIATED(
list))
THEN
1240 DO i = 1,
SIZE(
list)
1241 coeff1(i + np1 - 1) =
list(i)
1243 np1 = np1 +
SIZE(
list)
1248 IF (explicit_poly2)
THEN
1253 IF (
ASSOCIATED(
list))
THEN
1255 DO i = 1,
SIZE(
list)
1256 coeff2(i + np2 - 1) =
list(i)
1258 np2 = np2 +
SIZE(
list)
1263 IF ((.NOT. explicit_poly1) .OR. (.NOT. explicit_poly2))
THEN
1270 p(1, i) = p(1, i - 1)*r1
1274 p(2, i) = real(i - 1, kind=
dp)*p(1, i - 1)
1278 p(3, i) = real(i - 1, kind=
dp)*p(2, i - 1)
1283 p(4, i) = p(4, i - 1)*r2
1287 p(4, i) = p(4, i - 1)*r2
1291 p(5, i) = real(i - 1, kind=
dp)*p(4, i - 1)
1294 p(5, i) = real(i - 7, kind=
dp)*p(4, i - 1)
1298 p(6, i) = real(i - 1, kind=
dp)*p(5, i - 1)
1301 p(6, i) = real(i - 7, kind=
dp)*p(5, i - 1)
1310 p(8, i) = p(8, i - 1)*r3
1314 p(9, i) = real(i - 7, kind=
dp)*p(8, i - 1)
1318 p(10, i) = real(i - 7, kind=
dp)*p(9, i - 1)
1325 v(8) = -c/p(8, 10)**2
1326 v(9) = -6.0_dp*v(8)/r3
1327 v(10) = -7.0_dp*v(9)/r3
1329 p_inv(:, :) = 0.0_dp
1331 IF (eval_error >= 1.0e-8_dp) &
1332 CALL cp_warn(__location__, &
1333 "The polynomial fit for the BUCK4RANGES potential is only accurate to "// &
1337 x(:) = matmul(p_inv(:, :), v(:))
1344 nonbonded%pot(start + isec)%pot%type =
b4_type
1345 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1346 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1347 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1348 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1349 nonbonded%pot(start + isec)%pot%set(1)%buck4r%a = a
1350 nonbonded%pot(start + isec)%pot%set(1)%buck4r%b = b
1351 nonbonded%pot(start + isec)%pot%set(1)%buck4r%c = c
1352 nonbonded%pot(start + isec)%pot%set(1)%buck4r%r1 = r1
1353 nonbonded%pot(start + isec)%pot%set(1)%buck4r%r2 = r2
1354 nonbonded%pot(start + isec)%pot%set(1)%buck4r%r3 = r3
1355 IF ((.NOT. explicit_poly1) .OR. (.NOT. explicit_poly2))
THEN
1356 nonbonded%pot(start + isec)%pot%set(1)%buck4r%npoly1 = 5
1357 nonbonded%pot(start + isec)%pot%set(1)%buck4r%poly1(0:5) = x(1:6)
1358 nonbonded%pot(start + isec)%pot%set(1)%buck4r%npoly2 = 3
1359 nonbonded%pot(start + isec)%pot%set(1)%buck4r%poly2(0:3) = x(7:10)
1361 nonbonded%pot(start + isec)%pot%set(1)%buck4r%npoly1 = np1 - 1
1362 cpassert(np1 - 1 <= 10)
1363 nonbonded%pot(start + isec)%pot%set(1)%buck4r%poly1(0:np1 - 1) = coeff1(0:np1 - 1)
1364 nonbonded%pot(start + isec)%pot%set(1)%buck4r%npoly2 = np2 - 1
1365 cpassert(np2 - 1 <= 10)
1366 nonbonded%pot(start + isec)%pot%set(1)%buck4r%poly2(0:np2 - 1) = coeff2(0:np2 - 1)
1368 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
1370 IF (
ASSOCIATED(coeff1))
THEN
1373 IF (
ASSOCIATED(coeff2))
THEN
1378 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1381 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1384 END SUBROUTINE read_b4_section
1396 INTEGER,
INTENT(IN) :: start
1398 CHARACTER(LEN=default_string_length), &
1399 DIMENSION(:),
POINTER :: atm_names
1400 INTEGER :: isec, n_items, n_rep
1401 REAL(kind=
dp) :: rcut
1404 DO isec = 1, n_items
1408 nonbonded%pot(start + isec)%pot%type =
gp_type
1409 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1410 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1411 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
1412 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1413 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1415 CALL get_generic_info(section,
"FUNCTION", nonbonded%pot(start + isec)%pot%set(1)%gp%potential, &
1416 nonbonded%pot(start + isec)%pot%set(1)%gp%parameters, &
1417 nonbonded%pot(start + isec)%pot%set(1)%gp%values, &
1418 size_variables=1, i_rep_sec=isec)
1419 nonbonded%pot(start + isec)%pot%set(1)%gp%variables = nonbonded%pot(start + isec)%pot%set(1)%gp%parameters(1)
1423 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1426 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1438 SUBROUTINE read_tersoff_section(nonbonded, section, start, tersoff_section)
1441 INTEGER,
INTENT(IN) :: start
1444 CHARACTER(LEN=default_string_length), &
1445 DIMENSION(:),
POINTER :: atm_names
1446 INTEGER :: isec, n_items, n_rep
1447 REAL(kind=
dp) :: rcut, rcutsq
1450 DO isec = 1, n_items
1455 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1456 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1457 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1458 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1461 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%A)
1463 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%B)
1465 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%lambda1)
1467 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%lambda2)
1469 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%alpha)
1471 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%beta)
1473 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%n)
1475 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%c)
1477 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%d)
1479 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%h)
1481 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%lambda3)
1483 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%bigR)
1485 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%bigD)
1487 rcutsq = (nonbonded%pot(start + isec)%pot%set(1)%tersoff%bigR + &
1488 nonbonded%pot(start + isec)%pot%set(1)%tersoff%bigD)**2
1489 nonbonded%pot(start + isec)%pot%set(1)%tersoff%rcutsq = rcutsq
1490 nonbonded%pot(start + isec)%pot%rcutsq = rcutsq
1494 IF (n_rep == 1)
THEN
1496 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1499 END SUBROUTINE read_tersoff_section
1509 SUBROUTINE read_gal_section(nonbonded, section, start, gal_section)
1512 INTEGER,
INTENT(IN) :: start
1515 CHARACTER(LEN=default_string_length), &
1516 DIMENSION(:),
POINTER :: atm_names
1517 INTEGER :: iatom, isec, n_items, n_rep, nval
1519 REAL(kind=
dp) :: rcut, rval
1520 REAL(kind=
dp),
DIMENSION(:),
POINTER :: rvalues
1526 DO isec = 1, n_items
1530 nonbonded%pot(start + isec)%pot%type =
gal_type
1531 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1532 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1533 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1534 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1537 IF (any(len_trim(atm_names(:)) > 2))
THEN
1538 cpwarn(
"The atom name will be truncated.")
1540 nonbonded%pot(start + isec)%pot%set(1)%gal%met1 = trim(atm_names(1))
1541 nonbonded%pot(start + isec)%pot%set(1)%gal%met2 = trim(atm_names(2))
1544 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%epsilon)
1546 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%bxy)
1548 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%bz)
1551 nonbonded%pot(start + isec)%pot%set(1)%gal%r1 = rvalues(1)
1552 nonbonded%pot(start + isec)%pot%set(1)%gal%r2 = rvalues(2)
1555 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a1)
1557 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a2)
1559 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a3)
1561 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a4)
1563 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a)
1565 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%b)
1567 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%c)
1571 ALLOCATE (nonbonded%pot(start + isec)%pot%set(1)%gal%gcn(nval))
1578 nonbonded%pot(start + isec)%pot%set(1)%gal%gcn(iatom) = rval
1582 l_val=nonbonded%pot(start + isec)%pot%set(1)%gal%express)
1586 IF (n_rep == 1)
THEN
1588 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1589 nonbonded%pot(start + isec)%pot%set(1)%gal%rcutsq = rcut**2
1592 END SUBROUTINE read_gal_section
1602 SUBROUTINE read_gal21_section(nonbonded, section, start, gal21_section)
1605 INTEGER,
INTENT(IN) :: start
1608 CHARACTER(LEN=default_string_length), &
1609 DIMENSION(:),
POINTER :: atm_names
1610 INTEGER :: iatom, isec, n_items, n_rep, nval
1612 REAL(kind=
dp) :: rcut, rval
1613 REAL(kind=
dp),
DIMENSION(:),
POINTER :: rvalues
1619 DO isec = 1, n_items
1623 nonbonded%pot(start + isec)%pot%type =
gal21_type
1624 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1625 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1626 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1627 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1630 IF (any(len_trim(atm_names(:)) > 2))
THEN
1631 cpwarn(
"The atom name will be truncated.")
1633 nonbonded%pot(start + isec)%pot%set(1)%gal21%met1 = trim(atm_names(1))
1634 nonbonded%pot(start + isec)%pot%set(1)%gal21%met2 = trim(atm_names(2))
1637 nonbonded%pot(start + isec)%pot%set(1)%gal21%epsilon1 = rvalues(1)
1638 nonbonded%pot(start + isec)%pot%set(1)%gal21%epsilon2 = rvalues(2)
1639 nonbonded%pot(start + isec)%pot%set(1)%gal21%epsilon3 = rvalues(3)
1642 nonbonded%pot(start + isec)%pot%set(1)%gal21%bxy1 = rvalues(1)
1643 nonbonded%pot(start + isec)%pot%set(1)%gal21%bxy2 = rvalues(2)
1646 nonbonded%pot(start + isec)%pot%set(1)%gal21%bz1 = rvalues(1)
1647 nonbonded%pot(start + isec)%pot%set(1)%gal21%bz2 = rvalues(2)
1650 nonbonded%pot(start + isec)%pot%set(1)%gal21%r1 = rvalues(1)
1651 nonbonded%pot(start + isec)%pot%set(1)%gal21%r2 = rvalues(2)
1654 nonbonded%pot(start + isec)%pot%set(1)%gal21%a11 = rvalues(1)
1655 nonbonded%pot(start + isec)%pot%set(1)%gal21%a12 = rvalues(2)
1656 nonbonded%pot(start + isec)%pot%set(1)%gal21%a13 = rvalues(3)
1659 nonbonded%pot(start + isec)%pot%set(1)%gal21%a21 = rvalues(1)
1660 nonbonded%pot(start + isec)%pot%set(1)%gal21%a22 = rvalues(2)
1661 nonbonded%pot(start + isec)%pot%set(1)%gal21%a23 = rvalues(3)
1664 nonbonded%pot(start + isec)%pot%set(1)%gal21%a31 = rvalues(1)
1665 nonbonded%pot(start + isec)%pot%set(1)%gal21%a32 = rvalues(2)
1666 nonbonded%pot(start + isec)%pot%set(1)%gal21%a33 = rvalues(3)
1669 nonbonded%pot(start + isec)%pot%set(1)%gal21%a41 = rvalues(1)
1670 nonbonded%pot(start + isec)%pot%set(1)%gal21%a42 = rvalues(2)
1671 nonbonded%pot(start + isec)%pot%set(1)%gal21%a43 = rvalues(3)
1674 nonbonded%pot(start + isec)%pot%set(1)%gal21%AO1 = rvalues(1)
1675 nonbonded%pot(start + isec)%pot%set(1)%gal21%AO2 = rvalues(2)
1678 nonbonded%pot(start + isec)%pot%set(1)%gal21%BO1 = rvalues(1)
1679 nonbonded%pot(start + isec)%pot%set(1)%gal21%BO2 = rvalues(2)
1682 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal21%c)
1685 nonbonded%pot(start + isec)%pot%set(1)%gal21%AH1 = rvalues(1)
1686 nonbonded%pot(start + isec)%pot%set(1)%gal21%AH2 = rvalues(2)
1689 nonbonded%pot(start + isec)%pot%set(1)%gal21%BH1 = rvalues(1)
1690 nonbonded%pot(start + isec)%pot%set(1)%gal21%BH2 = rvalues(2)
1695 ALLOCATE (nonbonded%pot(start + isec)%pot%set(1)%gal21%gcn(nval))
1702 nonbonded%pot(start + isec)%pot%set(1)%gal21%gcn(iatom) = rval
1706 l_val=nonbonded%pot(start + isec)%pot%set(1)%gal21%express)
1710 IF (n_rep == 1)
THEN
1712 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1713 nonbonded%pot(start + isec)%pot%set(1)%gal21%rcutsq = rcut**2
1716 END SUBROUTINE read_gal21_section
1726 SUBROUTINE read_siepmann_section(nonbonded, section, start, siepmann_section)
1729 INTEGER,
INTENT(IN) :: start
1732 CHARACTER(LEN=default_string_length), &
1733 DIMENSION(:),
POINTER :: atm_names
1734 INTEGER :: isec, n_items, n_rep
1735 REAL(kind=
dp) :: rcut
1738 DO isec = 1, n_items
1743 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1744 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1745 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1746 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1749 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%B)
1751 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%D)
1753 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%E)
1755 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%F)
1757 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%beta)
1759 l_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%allow_oh_formation)
1761 l_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%allow_h3o_formation)
1763 l_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%allow_o_formation)
1767 IF (n_rep == 1)
THEN
1769 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1770 nonbonded%pot(start + isec)%pot%set(1)%siepmann%rcutsq = rcut**2
1773 END SUBROUTINE read_siepmann_section
1782 SUBROUTINE read_bm_section(nonbonded, section, start)
1785 INTEGER,
INTENT(IN) :: start
1787 CHARACTER(LEN=default_string_length), &
1788 DIMENSION(:),
POINTER :: atm_names
1789 INTEGER :: isec, n_items, n_rep
1790 REAL(kind=
dp) :: a1, a2, b1, b2, beta, c, d, f0, r0, rcut
1793 DO isec = 1, n_items
1807 nonbonded%pot(start + isec)%pot%type =
bm_type
1808 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1809 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1810 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1811 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1812 nonbonded%pot(start + isec)%pot%set(1)%buckmo%f0 = f0
1813 nonbonded%pot(start + isec)%pot%set(1)%buckmo%a1 = a1
1814 nonbonded%pot(start + isec)%pot%set(1)%buckmo%a2 = a2
1815 nonbonded%pot(start + isec)%pot%set(1)%buckmo%b1 = b1
1816 nonbonded%pot(start + isec)%pot%set(1)%buckmo%b2 = b2
1817 nonbonded%pot(start + isec)%pot%set(1)%buckmo%c = c
1818 nonbonded%pot(start + isec)%pot%set(1)%buckmo%d = d
1819 nonbonded%pot(start + isec)%pot%set(1)%buckmo%r0 = r0
1820 nonbonded%pot(start + isec)%pot%set(1)%buckmo%beta = beta
1821 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
1825 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1828 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1830 END SUBROUTINE read_bm_section
1841 SUBROUTINE read_tabpot_section(nonbonded, section, start, para_env, mm_section)
1844 INTEGER,
INTENT(IN) :: start
1848 CHARACTER(LEN=default_string_length), &
1849 DIMENSION(:),
POINTER :: atm_names
1850 INTEGER :: isec, n_items
1853 DO isec = 1, n_items
1855 nonbonded%pot(start + isec)%pot%type =
tab_type
1856 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1857 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1858 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1859 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1861 c_val=nonbonded%pot(start + isec)%pot%set(1)%tab%tabpot_file_name)
1862 CALL read_tabpot_data(nonbonded%pot(start + isec)%pot%set(1)%tab, para_env, mm_section)
1863 nonbonded%pot(start + isec)%pot%set(1)%tab%index = isec
1865 END SUBROUTINE read_tabpot_section
1876 CHARACTER(LEN=default_string_length), &
1877 DIMENSION(:),
POINTER :: charge_atm
1878 REAL(kind=
dp),
DIMENSION(:),
POINTER :: charge
1880 INTEGER,
INTENT(IN) :: start
1882 CHARACTER(LEN=default_string_length) :: atm_name
1883 INTEGER :: isec, n_items
1886 DO isec = 1, n_items
1888 charge_atm(start + isec) = atm_name
1889 CALL uppercase(charge_atm(start + isec))
1903 SUBROUTINE read_apol_section(apol_atm, apol, damping_list, section, &
1905 CHARACTER(LEN=default_string_length), &
1906 DIMENSION(:),
POINTER :: apol_atm
1907 REAL(kind=
dp),
DIMENSION(:),
POINTER :: apol
1910 INTEGER,
INTENT(IN) :: start
1912 CHARACTER(LEN=default_string_length) :: atm_name
1913 INTEGER :: isec, isec_damp, n_damp, n_items, &
1914 start_damp, tmp_damp
1918 NULLIFY (tmp_section)
1921 DO isec = 1, n_items
1925 n_damp = n_damp + tmp_damp
1929 IF (n_damp > 0)
THEN
1930 ALLOCATE (damping_list(1:n_damp))
1935 DO isec = 1, n_items
1937 apol_atm(start + isec) = atm_name
1944 DO isec_damp = 1, tmp_damp
1945 damping_list(start_damp + isec_damp)%atm_name1 = apol_atm(start + isec)
1948 damping_list(start_damp + isec_damp)%atm_name2 = atm_name
1949 CALL uppercase(damping_list(start_damp + isec_damp)%atm_name2)
1952 damping_list(start_damp + isec_damp)%dtype = atm_name
1953 CALL uppercase(damping_list(start_damp + isec_damp)%dtype)
1956 i_val=damping_list(start_damp + isec_damp)%order)
1958 r_val=damping_list(start_damp + isec_damp)%bij)
1960 r_val=damping_list(start_damp + isec_damp)%cij)
1962 start_damp = start_damp + tmp_damp
1966 END SUBROUTINE read_apol_section
1976 SUBROUTINE read_cpol_section(cpol_atm, cpol, section, start)
1977 CHARACTER(LEN=default_string_length), &
1978 DIMENSION(:),
POINTER :: cpol_atm
1979 REAL(kind=
dp),
DIMENSION(:),
POINTER :: cpol
1981 INTEGER,
INTENT(IN) :: start
1983 CHARACTER(LEN=default_string_length) :: atm_name
1984 INTEGER :: isec, n_items
1987 DO isec = 1, n_items
1989 cpol_atm(start + isec) = atm_name
1993 END SUBROUTINE read_cpol_section
2002 SUBROUTINE read_shell_section(shell_list, section, start)
2004 TYPE(
shell_p_type),
DIMENSION(:),
POINTER :: shell_list
2006 INTEGER,
INTENT(IN) :: start
2008 CHARACTER(LEN=default_string_length) :: atm_name
2009 INTEGER :: i_rep, n_rep
2010 REAL(
dp) :: ccharge, cutoff, k, maxdist, mfrac, &
2017 c_val=atm_name, i_rep_section=i_rep)
2019 shell_list(start + i_rep)%atm_name = atm_name
2021 shell_list(start + i_rep)%shell%charge_core = ccharge
2023 shell_list(start + i_rep)%shell%charge_shell = scharge
2025 shell_list(start + i_rep)%shell%massfrac = mfrac
2027 IF (k < 0.0_dp)
THEN
2028 CALL cp_abort(__location__, &
2029 "An invalid value was specified for the force constant k2 of the core-shell "// &
2032 shell_list(start + i_rep)%shell%k2_spring = k
2034 IF (k < 0.0_dp)
THEN
2035 CALL cp_abort(__location__, &
2036 "An invalid value was specified for the force constant k4 of the core-shell "// &
2039 shell_list(start + i_rep)%shell%k4_spring = k
2041 shell_list(start + i_rep)%shell%max_dist = maxdist
2043 shell_list(start + i_rep)%shell%shell_cutoff = cutoff
2046 END SUBROUTINE read_shell_section
2060 SUBROUTINE read_bonds_section(bond_kind, bond_a, bond_b, bond_k, bond_r0, bond_cs, section, start)
2061 INTEGER,
DIMENSION(:),
POINTER :: bond_kind
2062 CHARACTER(LEN=default_string_length), &
2063 DIMENSION(:),
POINTER :: bond_a, bond_b
2064 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: bond_k
2065 REAL(kind=
dp),
DIMENSION(:),
POINTER :: bond_r0, bond_cs
2067 INTEGER,
INTENT(IN) :: start
2069 CHARACTER(LEN=default_string_length), &
2070 DIMENSION(:),
POINTER :: atm_names
2071 INTEGER :: isec, k, n_items
2072 REAL(kind=
dp),
DIMENSION(:),
POINTER :: kvals
2074 NULLIFY (kvals, atm_names)
2076 DO isec = 1, n_items
2079 bond_a(start + isec) = atm_names(1)
2080 bond_b(start + isec) = atm_names(2)
2084 cpassert(
SIZE(kvals) <= 3)
2085 bond_k(:, start + isec) = 0.0_dp
2086 DO k = 1,
SIZE(kvals)
2087 bond_k(k, start + isec) = kvals(k)
2092 END SUBROUTINE read_bonds_section
2113 SUBROUTINE read_bends_section(bend_kind, bend_a, bend_b, bend_c, bend_k, bend_theta0, bend_cb, &
2114 bend_r012, bend_r032, bend_kbs12, bend_kbs32, bend_kss, bend_legendre, &
2116 INTEGER,
DIMENSION(:),
POINTER :: bend_kind
2117 CHARACTER(LEN=default_string_length), &
2118 DIMENSION(:),
POINTER :: bend_a, bend_b, bend_c
2119 REAL(kind=
dp),
DIMENSION(:),
POINTER :: bend_k, bend_theta0, bend_cb, bend_r012, &
2120 bend_r032, bend_kbs12, bend_kbs32, &
2124 INTEGER,
INTENT(IN) :: start
2126 CHARACTER(LEN=default_string_length), &
2127 DIMENSION(:),
POINTER :: atm_names
2128 INTEGER :: isec, k, n_items, n_rep
2129 REAL(kind=
dp),
DIMENSION(:),
POINTER :: kvals, r_values
2131 NULLIFY (kvals, atm_names)
2133 bend_legendre%order = 0
2134 DO isec = 1, n_items
2137 bend_a(start + isec) = atm_names(1)
2138 bend_b(start + isec) = atm_names(2)
2139 bend_c(start + isec) = atm_names(3)
2144 cpassert(
SIZE(kvals) == 1)
2145 bend_k(start + isec) = kvals(1)
2146 CALL section_vals_val_get(section,
"THETA0", i_rep_section=isec, r_val=bend_theta0(start + isec))
2150 CALL section_vals_val_get(section,
"KBS12", i_rep_section=isec, r_val=bend_kbs12(start + isec))
2151 CALL section_vals_val_get(section,
"KBS32", i_rep_section=isec, r_val=bend_kbs32(start + isec))
2156 CALL section_vals_val_get(section,
"LEGENDRE", i_rep_val=k, r_vals=r_values, i_rep_section=isec)
2157 bend_legendre(start + isec)%order =
SIZE(r_values)
2158 IF (
ASSOCIATED(bend_legendre(start + isec)%coeffs))
THEN
2159 DEALLOCATE (bend_legendre(start + isec)%coeffs)
2161 ALLOCATE (bend_legendre(start + isec)%coeffs(bend_legendre(start + isec)%order))
2162 bend_legendre(start + isec)%coeffs = r_values
2165 END SUBROUTINE read_bends_section
2178 SUBROUTINE read_ubs_section(ub_kind, ub_a, ub_b, ub_c, ub_k, ub_r0, section, start)
2179 INTEGER,
DIMENSION(:),
POINTER :: ub_kind
2180 CHARACTER(LEN=default_string_length), &
2181 DIMENSION(:),
POINTER :: ub_a, ub_b, ub_c
2182 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: ub_k
2183 REAL(kind=
dp),
DIMENSION(:),
POINTER :: ub_r0
2185 INTEGER,
INTENT(IN) :: start
2187 CHARACTER(LEN=default_string_length), &
2188 DIMENSION(:),
POINTER :: atm_names
2189 INTEGER :: isec, k, n_items
2191 REAL(kind=
dp),
DIMENSION(:),
POINTER :: kvals
2196 DO isec = 1, n_items
2202 ub_a(start + isec) = atm_names(1)
2203 ub_b(start + isec) = atm_names(2)
2204 ub_c(start + isec) = atm_names(3)
2209 cpassert(
SIZE(kvals) <= 3)
2210 ub_k(:, start + isec) = 0.0_dp
2211 DO k = 1,
SIZE(kvals)
2212 ub_k(k, start + isec) = kvals(k)
2217 END SUBROUTINE read_ubs_section
2233 SUBROUTINE read_torsions_section(torsion_kind, torsion_a, torsion_b, torsion_c, torsion_d, torsion_k, &
2234 torsion_phi0, torsion_m, section, start)
2235 INTEGER,
DIMENSION(:),
POINTER :: torsion_kind
2236 CHARACTER(LEN=default_string_length), &
2237 DIMENSION(:),
POINTER :: torsion_a, torsion_b, torsion_c, &
2239 REAL(kind=
dp),
DIMENSION(:),
POINTER :: torsion_k, torsion_phi0
2240 INTEGER,
DIMENSION(:),
POINTER :: torsion_m
2242 INTEGER,
INTENT(IN) :: start
2244 CHARACTER(LEN=default_string_length), &
2245 DIMENSION(:),
POINTER :: atm_names
2246 INTEGER :: isec, n_items
2250 DO isec = 1, n_items
2251 CALL section_vals_val_get(section,
"KIND", i_rep_section=isec, i_val=torsion_kind(start + isec))
2253 torsion_a(start + isec) = atm_names(1)
2254 torsion_b(start + isec) = atm_names(2)
2255 torsion_c(start + isec) = atm_names(3)
2256 torsion_d(start + isec) = atm_names(4)
2262 CALL section_vals_val_get(section,
"PHI0", i_rep_section=isec, r_val=torsion_phi0(start + isec))
2265 IF (torsion_kind(start + isec) ==
do_ff_opls)
THEN
2266 IF (torsion_phi0(start + isec) /= 0.0_dp)
THEN
2267 CALL cp_warn(__location__,
"PHI0 parameter was non-zero "// &
2268 "for an OPLS-type TORSION. It will be ignored.")
2270 IF (
modulo(torsion_m(start + isec), 2) == 0)
THEN
2272 torsion_phi0(start + isec) =
pi
2275 torsion_k(start + isec) = torsion_k(start + isec)*0.5_dp
2278 END SUBROUTINE read_torsions_section
2293 SUBROUTINE read_improper_section(impr_kind, impr_a, impr_b, impr_c, impr_d, impr_k, &
2294 impr_phi0, section, start)
2295 INTEGER,
DIMENSION(:),
POINTER :: impr_kind
2296 CHARACTER(LEN=default_string_length), &
2297 DIMENSION(:),
POINTER :: impr_a, impr_b, impr_c, impr_d
2298 REAL(kind=
dp),
DIMENSION(:),
POINTER :: impr_k, impr_phi0
2300 INTEGER,
INTENT(IN) :: start
2302 CHARACTER(LEN=default_string_length), &
2303 DIMENSION(:),
POINTER :: atm_names
2304 INTEGER :: isec, n_items
2308 DO isec = 1, n_items
2311 impr_a(start + isec) = atm_names(1)
2312 impr_b(start + isec) = atm_names(2)
2313 impr_c(start + isec) = atm_names(3)
2314 impr_d(start + isec) = atm_names(4)
2322 END SUBROUTINE read_improper_section
2337 SUBROUTINE read_opbend_section(opbend_kind, opbend_a, opbend_b, opbend_c, opbend_d, opbend_k, &
2338 opbend_phi0, section, start)
2339 INTEGER,
DIMENSION(:),
POINTER :: opbend_kind
2340 CHARACTER(LEN=default_string_length), &
2341 DIMENSION(:),
POINTER :: opbend_a, opbend_b, opbend_c, opbend_d
2342 REAL(kind=
dp),
DIMENSION(:),
POINTER :: opbend_k, opbend_phi0
2344 INTEGER,
INTENT(IN) :: start
2346 CHARACTER(LEN=default_string_length), &
2347 DIMENSION(:),
POINTER :: atm_names
2348 INTEGER :: isec, n_items
2352 DO isec = 1, n_items
2353 CALL section_vals_val_get(section,
"KIND", i_rep_section=isec, i_val=opbend_kind(start + isec))
2355 opbend_a(start + isec) = atm_names(1)
2356 opbend_b(start + isec) = atm_names(2)
2357 opbend_c(start + isec) = atm_names(3)
2358 opbend_d(start + isec) = atm_names(4)
2364 CALL section_vals_val_get(section,
"PHI0", i_rep_section=isec, r_val=opbend_phi0(start + isec))
2366 END SUBROUTINE read_opbend_section
2385 NULLIFY (ff_section)
2387 CALL read_force_field_section1(ff_section, mm_section, ff_type, para_env)
2396 SUBROUTINE read_eam_data(eam, para_env, mm_section)
2401 CHARACTER(len=*),
PARAMETER :: routinen =
'read_eam_data'
2403 INTEGER :: handle, i, iw
2407 CALL timeset(routinen, handle)
2412 IF (iw > 0)
WRITE (iw, *)
"Reading EAM data from: ", trim(eam%eam_file_name)
2413 CALL parser_create(parser, trim(eam%eam_file_name), para_env=para_env)
2416 IF (iw > 0)
WRITE (iw, *)
"Title: ", parser%input_line
2419 READ (parser%input_line, *) eam%drar, eam%drhoar, eam%acutal, eam%npoints
2432 DO i = 1, eam%npoints
2434 READ (parser%input_line, *) eam%rho(i), eam%rhop(i)
2436 eam%rval(i) = real(i - 1, kind=
dp)*eam%drar
2437 eam%rhoval(i) = real(i - 1, kind=
dp)*eam%drhoar
2440 DO i = 1, eam%npoints
2442 READ (parser%input_line, *) eam%phi(i), eam%phip(i)
2447 DO i = 1, eam%npoints
2449 READ (parser%input_line, *) eam%frho(i), eam%frhop(i)
2454 IF (iw > 0)
WRITE (iw, *)
"Finished EAM data"
2457 CALL timestop(handle)
2459 END SUBROUTINE read_eam_data
2466 SUBROUTINE read_nequip_data(nequip)
2469 CHARACTER(LEN=*),
PARAMETER :: routinen =
'read_nequip_data'
2470 CHARACTER(LEN=1),
PARAMETER :: delimiter =
' '
2472 CHARACTER(LEN=100),
ALLOCATABLE,
DIMENSION(:) :: tokenized_string
2473 CHARACTER(LEN=default_path_length) :: allow_tf32_str, cutoff_str, &
2474 default_dtype, model_dtype, types_str
2476 LOGICAL :: allow_tf32, found
2478 CALL timeset(routinen, handle)
2480 INQUIRE (file=nequip%nequip_file_name, exist=found)
2481 IF (.NOT. found)
THEN
2482 CALL cp_abort(__location__, &
2483 "Nequip model file <"//trim(nequip%nequip_file_name)// &
2490 CALL tokenize_string(trim(types_str), delimiter, tokenized_string)
2492 IF (
ALLOCATED(nequip%type_names_torch))
THEN
2493 DEALLOCATE (nequip%type_names_torch)
2495 ALLOCATE (nequip%type_names_torch(
SIZE(tokenized_string)))
2497 nequip%type_names_torch(:) = tokenized_string(:)
2499 READ (cutoff_str, *) nequip%rcutsq
2501 nequip%rcutsq = nequip%rcutsq*nequip%rcutsq
2502 nequip%unit_coords_val =
cp_unit_to_cp2k(nequip%unit_coords_val, nequip%unit_coords)
2503 nequip%unit_forces_val =
cp_unit_to_cp2k(nequip%unit_forces_val, nequip%unit_forces)
2504 nequip%unit_energy_val =
cp_unit_to_cp2k(nequip%unit_energy_val, nequip%unit_energy)
2505 nequip%unit_cell_val =
cp_unit_to_cp2k(nequip%unit_cell_val, nequip%unit_cell)
2509 IF (trim(default_dtype) ==
"float32" .AND. trim(model_dtype) ==
"float32")
THEN
2510 nequip%do_nequip_sp = .true.
2511 ELSE IF (trim(default_dtype) ==
"float64" .AND. trim(model_dtype) ==
"float64")
THEN
2512 nequip%do_nequip_sp = .false.
2514 CALL cp_abort(__location__, &
2515 "Both default_dtype and model_dtype should be either float32 or float64. Currently, default_dtype is <"// &
2516 trim(default_dtype)//
"> and model_dtype is <"//trim(model_dtype)//
">.")
2520 allow_tf32 = (trim(allow_tf32_str) ==
"1")
2521 IF (trim(allow_tf32_str) /=
"1" .AND. trim(allow_tf32_str) /=
"0")
THEN
2522 CALL cp_abort(__location__, &
2523 "The value for allow_tf32 <"//trim(allow_tf32_str)// &
2524 "> is not supported. Check the .yaml and .pth files.")
2528 CALL timestop(handle)
2529 END SUBROUTINE read_nequip_data
2536 SUBROUTINE read_allegro_data(allegro)
2539 CHARACTER(len=*),
PARAMETER :: routinen =
'read_allegro_data'
2540 CHARACTER(LEN=1),
PARAMETER :: delimiter =
' '
2542 CHARACTER(LEN=100),
ALLOCATABLE,
DIMENSION(:) :: tokenized_string
2543 CHARACTER(LEN=default_path_length) :: allow_tf32_str, cutoff_str, &
2544 default_dtype, model_dtype, types_str
2546 LOGICAL :: allow_tf32, found
2548 CALL timeset(routinen, handle)
2550 INQUIRE (file=allegro%allegro_file_name, exist=found)
2551 IF (.NOT. found)
THEN
2552 CALL cp_abort(__location__, &
2553 "Allegro model file <"//trim(allegro%allegro_file_name)// &
2558 IF (allegro%nequip_version ==
"")
THEN
2559 CALL cp_abort(__location__, &
2560 "Allegro model file <"//trim(allegro%allegro_file_name)// &
2561 "> has not been deployed; did you forget to run `nequip-deploy`?")
2565 CALL tokenize_string(trim(types_str), delimiter, tokenized_string)
2567 IF (
ALLOCATED(allegro%type_names_torch))
THEN
2568 DEALLOCATE (allegro%type_names_torch)
2570 ALLOCATE (allegro%type_names_torch(
SIZE(tokenized_string)))
2571 allegro%type_names_torch(:) = tokenized_string(:)
2573 READ (cutoff_str, *) allegro%rcutsq
2575 allegro%rcutsq = allegro%rcutsq*allegro%rcutsq
2576 allegro%unit_coords_val =
cp_unit_to_cp2k(allegro%unit_coords_val, allegro%unit_coords)
2577 allegro%unit_forces_val =
cp_unit_to_cp2k(allegro%unit_forces_val, allegro%unit_forces)
2578 allegro%unit_energy_val =
cp_unit_to_cp2k(allegro%unit_energy_val, allegro%unit_energy)
2579 allegro%unit_cell_val =
cp_unit_to_cp2k(allegro%unit_cell_val, allegro%unit_cell)
2583 IF (trim(default_dtype) ==
"float32" .AND. trim(model_dtype) ==
"float32")
THEN
2584 allegro%do_allegro_sp = .true.
2585 ELSE IF (trim(default_dtype) ==
"float64" .AND. trim(model_dtype) ==
"float64")
THEN
2586 allegro%do_allegro_sp = .false.
2588 CALL cp_abort(__location__, &
2589 "Both default_dtype and model_dtype should be either float32 or float64. Currently, default_dtype is <"// &
2590 trim(default_dtype)//
"> and model_dtype is <"//trim(model_dtype)//
">.")
2594 allow_tf32 = (trim(allow_tf32_str) ==
"1")
2595 IF (trim(allow_tf32_str) /=
"1" .AND. trim(allow_tf32_str) /=
"0")
THEN
2596 CALL cp_abort(__location__, &
2597 "The value for allow_tf32 <"//trim(allow_tf32_str)// &
2598 "> is not supported. Check the .yaml and .pth files.")
2602 CALL timestop(handle)
2603 END SUBROUTINE read_allegro_data
2612 SUBROUTINE tokenize_string(element, delimiter, tokenized_array)
2613 CHARACTER(LEN=*),
INTENT(IN) :: element
2614 CHARACTER(LEN=1),
INTENT(IN) :: delimiter
2615 CHARACTER(LEN=100),
ALLOCATABLE,
DIMENSION(:), &
2616 INTENT(OUT) :: tokenized_array
2618 CHARACTER(LEN=100) :: temp_kinds
2619 INTEGER :: end_pos, i, num_elements, start
2620 LOGICAL,
ALLOCATABLE,
DIMENSION(:) :: delim_positions
2623 ALLOCATE (delim_positions(len(element)))
2624 delim_positions = .false.
2626 DO i = 1, len(element)
2627 IF (element(i:i) == delimiter) delim_positions(i) = .true.
2630 num_elements = count(delim_positions) + 1
2632 ALLOCATE (tokenized_array(num_elements))
2635 DO i = 1, num_elements
2636 IF (len(element) < 3 .AND. count(delim_positions) == 0)
THEN
2638 end_pos = len(element)
2640 end_pos = find_end_pos(start, delim_positions)
2642 temp_kinds = element(start:end_pos)
2643 IF (trim(temp_kinds) /=
'')
THEN
2644 tokenized_array(i) = temp_kinds
2648 DEALLOCATE (delim_positions)
2649 END SUBROUTINE tokenize_string
2658 INTEGER FUNCTION find_end_pos(start, delim_positions)
2659 INTEGER,
INTENT(IN) :: start
2660 LOGICAL,
DIMENSION(:),
INTENT(IN) :: delim_positions
2662 INTEGER :: end_pos, i
2665 DO i = start,
SIZE(delim_positions)
2666 IF (delim_positions(i))
THEN
2672 find_end_pos = end_pos
2673 END FUNCTION find_end_pos
2681 SUBROUTINE check_cp2k_atom_names_in_torch(cp2k_inp_atom_types, torch_atom_types)
2682 CHARACTER(LEN=*),
DIMENSION(:),
INTENT(IN) :: cp2k_inp_atom_types, torch_atom_types
2687 DO i = 1,
SIZE(cp2k_inp_atom_types)
2689 DO j = 1,
SIZE(torch_atom_types)
2690 IF (trim(cp2k_inp_atom_types(i)) == trim(torch_atom_types(j)))
THEN
2695 IF (.NOT. found)
THEN
2696 CALL cp_abort(__location__, &
2697 "Atom "//trim(cp2k_inp_atom_types(i))// &
2698 " is defined in the CP2K input file but is missing in the torch model file")
2701 END SUBROUTINE check_cp2k_atom_names_in_torch
2710 SUBROUTINE read_tabpot_data(tab, para_env, mm_section)
2715 CHARACTER(len=*),
PARAMETER :: routinen =
'read_tabpot_data'
2718 INTEGER :: d, handle, i, iw
2722 CALL timeset(routinen, handle)
2727 IF (iw > 0)
WRITE (iw, *)
"Reading TABPOT data from: ", trim(tab%tabpot_file_name)
2728 CALL parser_create(parser, trim(tab%tabpot_file_name), para_env=para_env)
2730 IF (iw > 0)
WRITE (iw, *)
"Title: ", parser%input_line
2735 READ (parser%input_line, *) d1, tab%npoints, d2, tab%dr, tab%rcut
2743 DO i = 1, tab%npoints
2745 READ (parser%input_line, *) d, tab%r(i), tab%e(i), tab%f(i)
2751 tab%dr = tab%r(2) - tab%r(1)
2754 IF (iw > 0)
WRITE (iw, *)
"Finished TABPOT data"
2757 CALL timestop(handle)
2758 END SUBROUTINE read_tabpot_data
static GRID_HOST_DEVICE int modulo(int a, int m)
Equivalent of Fortran's MODULO, which always return a positive number. https://gcc....
Interface to ACE C wrapper.
subroutine, public ace_model_initialize(ntypec, symbolc, fname, rcutc, model)
...
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public tosi1964b
integer, save, public tersoff1988
integer, save, public tosi1964a
integer, save, public siepmann1995
integer, save, public yamada2000
integer, save, public clabaut2021
integer, save, public clabaut2020
Utility routines to open and close files. Tracking of preconnections.
character(len=default_path_length) function, public discover_file(file_name)
Checks various locations for a file name.
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,...
Utility routines to read data from files. Kept as close as possible to the old parser because.
subroutine, public parser_get_next_line(parser, nline, at_end)
Read the next input line and broadcast the input information. Skip (nline-1) lines and skip also all ...
Utility routines to read data from files. Kept as close as possible to the old parser because.
subroutine, public parser_release(parser)
releases the parser
subroutine, public parser_create(parser, file_name, unit_nr, para_env, end_section_label, separator_chars, comment_char, continuation_char, quote_char, section_char, parse_white_lines, initial_variables, apply_preprocessing)
Start a parser run. Initial variables allow to @SET stuff before opening the file.
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
Define all structure types related to force field kinds.
integer, parameter, public do_ff_undef
integer, parameter, public do_ff_charmm
integer, parameter, public do_ff_g87
integer, parameter, public do_ff_g96
integer, parameter, public do_ff_amber
integer, parameter, public do_ff_opls
Define all structures types related to force_fields.
subroutine, public get_generic_info(gen_section, func_name, xfunction, parameters, values, var_values, size_variables, i_rep_sec, input_variables)
Reads from the input structure all information for generic functions.
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_string_length
integer, parameter, public default_path_length
An array-based list which grows on demand. When the internal array is full, a new array of twice the ...
Definition of mathematical constants and functions.
real(kind=dp), parameter, public pi
Collection of simple mathematical functions and subroutines.
Utility routines for the memory handling.
Interface to the message passing library MPI.
integer, parameter, public lj_charmm_type
integer, parameter, public allegro_type
integer, parameter, public bm_type
integer, parameter, public gal_type
integer, parameter, public nequip_type
integer, parameter, public wl_type
integer, parameter, public ft_type
integer, parameter, public tab_type
subroutine, public pair_potential_reallocate(p, lb1_new, ub1_new, lj, lj_charmm, williams, goodwin, eam, nequip, allegro, bmhft, bmhftd, ipbv, buck4r, buckmo, gp, tersoff, siepmann, gal, gal21, tab, deepmd, ace)
Cleans the potential parameter type.
integer, parameter, public ftd_type
integer, parameter, public ip_type
integer, parameter, public deepmd_type
integer, parameter, public gp_type
integer, parameter, public siepmann_type
integer, parameter, public ace_type
integer, dimension(2), parameter, public do_potential_single_allocation
integer, parameter, public gw_type
integer, dimension(2), parameter, public no_potential_single_allocation
integer, parameter, public b4_type
integer, parameter, public gal21_type
integer, dimension(2), public potential_single_allocation
integer, parameter, public ea_type
integer, parameter, public tersoff_type
subroutine, public shell_p_create(shell_list, ndim)
...
Utilities for string manipulations.
elemental subroutine, public uppercase(string)
Convert all lower case characters in a string to upper case.
subroutine, public torch_allow_tf32(allow_tf32)
Set whether to allow the use of TF32. Needed due to changes in defaults from pytorch 1....
character(:) function, allocatable, public torch_model_read_metadata(filename, key)
Reads metadata entry from given "*.pth" file. (In Torch lingo they are called extra files)
type of a logger, at the moment it contains just a print level starting at which level it should be l...
stores all the informations relevant to an mpi environment