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, nquip, nshell, nsiepmann, &
114 ntab, 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)
286 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + ngal + ngal21 + nsiepmann
289 CALL read_quip_section(inp_info%nonbonded, tmp_section2, ntot)
293 CALL section_vals_get(tmp_section2, explicit=explicit, n_repetition=nnequip)
294 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + ngal + ngal21 + nsiepmann + &
299 nnequip = nnequip - 1 +
SIZE(atm_names) + (
SIZE(atm_names)*
SIZE(atm_names) -
SIZE(atm_names))/2
301 CALL read_nequip_section(inp_info%nonbonded, tmp_section2, ntot)
305 CALL section_vals_get(tmp_section2, explicit=explicit, n_repetition=nallegro)
306 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + ngal + ngal21 + nsiepmann + &
311 nallegro = nallegro - 1 +
SIZE(atm_names) + (
SIZE(atm_names)*
SIZE(atm_names) -
SIZE(atm_names))/2
313 CALL read_allegro_section(inp_info%nonbonded, tmp_section2, ntot)
318 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + ngal + ngal21 + nsiepmann + &
319 nquip + nnequip + nallegro
322 CALL read_tabpot_section(inp_info%nonbonded, tmp_section2, ntot, para_env, mm_section)
326 CALL section_vals_get(tmp_section2, explicit=explicit, n_repetition=ndeepmd)
327 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + ngal + ngal21 + nsiepmann + &
328 nquip + nnequip + nallegro + ntab
332 ndeepmd = ndeepmd - 1 +
SIZE(atm_names) + (
SIZE(atm_names)*
SIZE(atm_names) -
SIZE(atm_names))/2
334 CALL read_deepmd_section(inp_info%nonbonded, tmp_section2, ntot)
339 ntot = nlj + nwl + neam + ngd + nipbv + nbmhft + nbmhftd + nb4 + nbm + ngp + ntersoff + ngal + ngal21 + nsiepmann + &
340 nquip + nnequip + nallegro + ntab + ndeepmd
344 nace = nace - 1 +
SIZE(atm_names) + (
SIZE(atm_names)*
SIZE(atm_names) -
SIZE(atm_names))/2
346 CALL read_ace_section(inp_info%nonbonded, tmp_section2, ntot)
353 IF (explicit .AND. ff_type%do_nonbonded)
THEN
377 ntot = nlj + nwl + ngd
398 CALL read_apol_section(inp_info%apol_atm, inp_info%apol, inp_info%damping_list, &
407 CALL read_cpol_section(inp_info%cpol_atm, inp_info%cpol, tmp_section, ntot)
414 CALL read_shell_section(inp_info%shell_list, tmp_section, ntot)
421 CALL reallocate(inp_info%bond_kind, 1, nbonds)
424 CALL reallocate(inp_info%bond_k, 1, 3, 1, nbonds)
427 CALL read_bonds_section(inp_info%bond_kind, inp_info%bond_a, inp_info%bond_b, inp_info%bond_k, &
428 inp_info%bond_r0, inp_info%bond_cs, tmp_section, ntot)
434 CALL reallocate(inp_info%bend_kind, 1, nbends)
439 CALL reallocate(inp_info%bend_theta0, 1, nbends)
441 CALL reallocate(inp_info%bend_r012, 1, nbends)
442 CALL reallocate(inp_info%bend_r032, 1, nbends)
443 CALL reallocate(inp_info%bend_kbs12, 1, nbends)
444 CALL reallocate(inp_info%bend_kbs32, 1, nbends)
446 IF (
ASSOCIATED(inp_info%bend_legendre))
THEN
447 DO i = 1,
SIZE(inp_info%bend_legendre)
448 IF (
ASSOCIATED(inp_info%bend_legendre(i)%coeffs))
THEN
449 DEALLOCATE (inp_info%bend_legendre(i)%coeffs)
450 NULLIFY (inp_info%bend_legendre(i)%coeffs)
453 DEALLOCATE (inp_info%bend_legendre)
454 NULLIFY (inp_info%bend_legendre)
456 ALLOCATE (inp_info%bend_legendre(1:nbends))
457 DO i = 1,
SIZE(inp_info%bend_legendre(1:nbends))
458 NULLIFY (inp_info%bend_legendre(i)%coeffs)
459 inp_info%bend_legendre(i)%order = 0
461 CALL read_bends_section(inp_info%bend_kind, inp_info%bend_a, inp_info%bend_b, inp_info%bend_c, &
462 inp_info%bend_k, inp_info%bend_theta0, inp_info%bend_cb, &
463 inp_info%bend_r012, inp_info%bend_r032, inp_info%bend_kbs12, &
464 inp_info%bend_kbs32, inp_info%bend_kss, &
465 inp_info%bend_legendre, tmp_section, ntot)
477 CALL read_ubs_section(inp_info%ub_kind, inp_info%ub_a, inp_info%ub_b, inp_info%ub_c, &
478 inp_info%ub_k, inp_info%ub_r0, tmp_section, ntot)
484 CALL reallocate(inp_info%torsion_kind, 1, ntors)
491 CALL reallocate(inp_info%torsion_phi0, 1, ntors)
492 CALL read_torsions_section(inp_info%torsion_kind, inp_info%torsion_a, inp_info%torsion_b, &
493 inp_info%torsion_c, inp_info%torsion_d, inp_info%torsion_k, inp_info%torsion_phi0, &
494 inp_info%torsion_m, tmp_section, ntot)
508 CALL read_improper_section(inp_info%impr_kind, inp_info%impr_a, inp_info%impr_b, &
509 inp_info%impr_c, inp_info%impr_d, inp_info%impr_k, inp_info%impr_phi0, &
517 CALL reallocate(inp_info%opbend_kind, 1, nopbend)
518 CALL reallocate(inp_info%opbend_a, 1, nopbend)
519 CALL reallocate(inp_info%opbend_b, 1, nopbend)
520 CALL reallocate(inp_info%opbend_c, 1, nopbend)
521 CALL reallocate(inp_info%opbend_d, 1, nopbend)
522 CALL reallocate(inp_info%opbend_k, 1, nopbend)
523 CALL reallocate(inp_info%opbend_phi0, 1, nopbend)
524 CALL read_opbend_section(inp_info%opbend_kind, inp_info%opbend_a, inp_info%opbend_b, &
525 inp_info%opbend_c, inp_info%opbend_d, inp_info%opbend_k, inp_info%opbend_phi0, &
529 END SUBROUTINE read_force_field_section1
538 SUBROUTINE set_ipbv_ff(at1, at2, ipbv)
539 CHARACTER(LEN=*),
INTENT(IN) :: at1, at2
540 TYPE(ipbv_pot_type),
POINTER :: ipbv
542 IF ((at1(1:1) ==
'O') .AND. (at2(1:1) ==
'O'))
THEN
544 ipbv%m = -1.2226442563398141e+11_dp
545 ipbv%b = 1.1791292385486696e+11_dp
548 ipbv%a(2) = 4.786380682394_dp
549 ipbv%a(3) = -1543.407053545_dp
550 ipbv%a(4) = 88783.31188529_dp
551 ipbv%a(5) = -2361200.155376_dp
552 ipbv%a(6) = 35940504.84679_dp
553 ipbv%a(7) = -339762743.6358_dp
554 ipbv%a(8) = 2043874926.466_dp
555 ipbv%a(9) = -7654856796.383_dp
556 ipbv%a(10) = 16195251405.65_dp
557 ipbv%a(11) = -13140392992.18_dp
558 ipbv%a(12) = -9285572894.245_dp
559 ipbv%a(13) = 8756947519.029_dp
560 ipbv%a(14) = 15793297761.67_dp
561 ipbv%a(15) = 12917180227.21_dp
562 ELSEIF (((at1(1:1) ==
'O') .AND. (at2(1:1) ==
'H')) .OR. &
563 ((at1(1:1) ==
'H') .AND. (at2(1:1) ==
'O')))
THEN
566 ipbv%m = -0.004025691139759147_dp
567 ipbv%b = -2.193731138097428_dp
569 ipbv%a(2) = -195.7716013277_dp
570 ipbv%a(3) = 15343.78613395_dp
571 ipbv%a(4) = -530864.4586516_dp
572 ipbv%a(5) = 10707934.39058_dp
573 ipbv%a(6) = -140099704.7890_dp
574 ipbv%a(7) = 1250943273.785_dp
575 ipbv%a(8) = -7795458330.676_dp
576 ipbv%a(9) = 33955897217.31_dp
577 ipbv%a(10) = -101135640744.0_dp
578 ipbv%a(11) = 193107995718.7_dp
579 ipbv%a(12) = -193440560940.0_dp
580 ipbv%a(13) = -4224406093.918e0_dp
581 ipbv%a(14) = 217192386506.5e0_dp
582 ipbv%a(15) = -157581228915.5_dp
583 ELSEIF ((at1(1:1) ==
'H') .AND. (at2(1:1) ==
'H'))
THEN
584 ipbv%rcore = 3.165_dp
585 ipbv%m = 0.002639704108787555_dp
586 ipbv%b = -0.2735482611857583_dp
588 ipbv%a(2) = -26.29456010782_dp
589 ipbv%a(3) = 2373.352548248_dp
590 ipbv%a(4) = -93880.43551360_dp
591 ipbv%a(5) = 2154624.884809_dp
592 ipbv%a(6) = -31965151.34955_dp
593 ipbv%a(7) = 322781785.3278_dp
594 ipbv%a(8) = -2271097368.668_dp
595 ipbv%a(9) = 11169163192.90_dp
596 ipbv%a(10) = -37684457778.47_dp
597 ipbv%a(11) = 82562104256.03_dp
598 ipbv%a(12) = -100510435213.4_dp
599 ipbv%a(13) = 24570342714.65e0_dp
600 ipbv%a(14) = 88766181532.94e0_dp
601 ipbv%a(15) = -79705131323.98_dp
603 cpabort(
"IPBV only for WATER")
605 END SUBROUTINE set_ipbv_ff
614 SUBROUTINE set_bmhft_ff(at1, at2, ft)
615 CHARACTER(LEN=*),
INTENT(IN) :: at1, at2
616 TYPE(ft_pot_type),
POINTER :: ft
619 IF ((at1(1:2) ==
'NA') .AND. (at2(1:2) ==
'NA'))
THEN
623 ELSEIF (((at1(1:2) ==
'NA') .AND. (at2(1:2) ==
'CL')) .OR. &
624 ((at1(1:2) ==
'CL') .AND. (at2(1:2) ==
'NA')))
THEN
628 ELSEIF ((at1(1:2) ==
'CL') .AND. (at2(1:2) ==
'CL'))
THEN
633 cpabort(
"BMHFT only for NaCl")
636 END SUBROUTINE set_bmhft_ff
642 SUBROUTINE set_bmhftd_ff()
644 cpabort(
"No default parameters present for BMHFTD")
646 END SUBROUTINE set_bmhftd_ff
657 SUBROUTINE read_eam_section(nonbonded, section, start, para_env, mm_section)
658 TYPE(pair_potential_p_type),
POINTER :: nonbonded
659 TYPE(section_vals_type),
POINTER :: section
660 INTEGER,
INTENT(IN) :: start
661 TYPE(mp_para_env_type),
POINTER :: para_env
662 TYPE(section_vals_type),
POINTER :: mm_section
664 CHARACTER(LEN=default_string_length), &
665 DIMENSION(:),
POINTER :: atm_names
666 INTEGER :: isec, n_items
672 nonbonded%pot(start + isec)%pot%type =
ea_type
673 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
674 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
675 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
676 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
678 c_val=nonbonded%pot(start + isec)%pot%set(1)%eam%eam_file_name)
679 CALL read_eam_data(nonbonded%pot(start + isec)%pot%set(1)%eam, para_env, mm_section)
680 nonbonded%pot(start + isec)%pot%rcutsq = nonbonded%pot(start + isec)%pot%set(1)%eam%acutal**2
682 END SUBROUTINE read_eam_section
690 SUBROUTINE read_ace_section(nonbonded, section, start)
691 TYPE(pair_potential_p_type),
POINTER :: nonbonded
692 TYPE(section_vals_type),
POINTER :: section
693 INTEGER,
INTENT(IN) :: start
695 CHARACTER(LEN=2),
ALLOCATABLE,
DIMENSION(:) :: ace_atype_symbol
696 CHARACTER(LEN=default_path_length) :: ace_filename
697 CHARACTER(LEN=default_string_length) :: ace_file_name
698 CHARACTER(LEN=default_string_length), &
699 DIMENSION(:),
POINTER :: atm_names
700 INTEGER :: ace_ntype, isec, jsec, n_items
701 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: rcutall
702 TYPE(ace_model_type) :: model
706 n_items = isec*n_items
709 ace_ntype =
SIZE(atm_names)
710 ALLOCATE (ace_atype_symbol(ace_ntype), rcutall(ace_ntype, ace_ntype))
711 DO isec = 1, ace_ntype
712 ace_atype_symbol(isec) = atm_names(isec) (1:2)
721 fname=trim(ace_filename), rcutc=rcutall, model=model)
723 cpabort(
"CP2K was compiled without ACE library.")
726 DO isec = 1,
SIZE(atm_names)
727 DO jsec = isec,
SIZE(atm_names)
728 nonbonded%pot(start + n_items)%pot%type =
ace_type
729 nonbonded%pot(start + n_items)%pot%at1 = atm_names(isec)
730 nonbonded%pot(start + n_items)%pot%at2 = atm_names(jsec)
731 CALL uppercase(nonbonded%pot(start + n_items)%pot%at1)
732 CALL uppercase(nonbonded%pot(start + n_items)%pot%at2)
734 nonbonded%pot(start + n_items)%pot%set(1)%ace%ace_file_name = ace_filename
735 nonbonded%pot(start + n_items)%pot%set(1)%ace%atom_ace_type = isec
736 nonbonded%pot(start + n_items)%pot%set(1)%ace%model = model
740 nonbonded%pot(start + n_items)%pot%rcutsq =
cp_unit_to_cp2k(rcutall(isec, jsec),
"angstrom")**2
742 n_items = n_items + 1
745 END SUBROUTINE read_ace_section
754 SUBROUTINE read_deepmd_section(nonbonded, section, start)
755 TYPE(pair_potential_p_type),
POINTER :: nonbonded
756 TYPE(section_vals_type),
POINTER :: section
757 INTEGER,
INTENT(IN) :: start
759 CHARACTER(LEN=default_string_length) :: deepmd_file_name
760 CHARACTER(LEN=default_string_length), &
761 DIMENSION(:),
POINTER :: atm_names
762 INTEGER :: isec, jsec, n_items
763 INTEGER,
DIMENSION(:),
POINTER :: atm_deepmd_types
767 n_items = isec*n_items
772 DO isec = 1,
SIZE(atm_names)
773 DO jsec = isec,
SIZE(atm_names)
774 nonbonded%pot(start + n_items)%pot%type =
deepmd_type
775 nonbonded%pot(start + n_items)%pot%at1 = atm_names(isec)
776 nonbonded%pot(start + n_items)%pot%at2 = atm_names(jsec)
777 CALL uppercase(nonbonded%pot(start + n_items)%pot%at1)
778 CALL uppercase(nonbonded%pot(start + n_items)%pot%at2)
780 nonbonded%pot(start + n_items)%pot%set(1)%deepmd%deepmd_file_name =
discover_file(deepmd_file_name)
781 nonbonded%pot(start + n_items)%pot%set(1)%deepmd%atom_deepmd_type = atm_deepmd_types(isec)
782 nonbonded%pot(start + n_items)%pot%rcutsq = 0.0_dp
783 n_items = n_items + 1
786 END SUBROUTINE read_deepmd_section
795 SUBROUTINE read_quip_section(nonbonded, section, start)
796 TYPE(pair_potential_p_type),
POINTER :: nonbonded
797 TYPE(section_vals_type),
POINTER :: section
798 INTEGER,
INTENT(IN) :: start
800 CHARACTER(LEN=default_string_length), &
801 DIMENSION(:),
POINTER :: args_str, atm_names
802 INTEGER :: is, isec, n_calc_args, n_items
808 nonbonded%pot(start + isec)%pot%type =
quip_type
809 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
810 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
811 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
812 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
814 c_val=nonbonded%pot(start + isec)%pot%set(1)%quip%quip_file_name)
817 nonbonded%pot(start + isec)%pot%set(1)%quip%init_args =
""
818 DO is = 1,
SIZE(args_str)
819 nonbonded%pot(start + isec)%pot%set(1)%quip%init_args = &
820 trim(nonbonded%pot(start + isec)%pot%set(1)%quip%init_args)// &
821 " "//trim(args_str(is))
824 n_rep_val=n_calc_args)
825 IF (n_calc_args > 0)
THEN
828 DO is = 1,
SIZE(args_str)
829 nonbonded%pot(start + isec)%pot%set(1)%quip%calc_args = &
830 trim(nonbonded%pot(start + isec)%pot%set(1)%quip%calc_args)// &
831 " "//trim(args_str(is))
834 nonbonded%pot(start + isec)%pot%rcutsq = 0.0_dp
836 END SUBROUTINE read_quip_section
845 SUBROUTINE read_nequip_section(nonbonded, section, start)
846 TYPE(pair_potential_p_type),
POINTER :: nonbonded
847 TYPE(section_vals_type),
POINTER :: section
848 INTEGER,
INTENT(IN) :: start
850 CHARACTER(LEN=default_string_length) :: nequip_file_name, unit_cell, &
851 unit_coords, unit_energy, unit_forces
852 CHARACTER(LEN=default_string_length), &
853 DIMENSION(:),
POINTER :: atm_names
854 INTEGER :: isec, jsec, n_items
855 TYPE(nequip_pot_type) :: nequip
859 n_items = isec*n_items
869 nequip%unit_coords = unit_coords
870 nequip%unit_forces = unit_forces
871 nequip%unit_energy = unit_energy
872 nequip%unit_cell = unit_cell
873 CALL read_nequip_data(nequip)
874 CALL check_cp2k_atom_names_in_torch(atm_names, nequip%type_names_torch)
876 DO isec = 1,
SIZE(atm_names)
877 DO jsec = isec,
SIZE(atm_names)
878 nonbonded%pot(start + n_items)%pot%type =
nequip_type
879 nonbonded%pot(start + n_items)%pot%at1 = atm_names(isec)
880 nonbonded%pot(start + n_items)%pot%at2 = atm_names(jsec)
881 CALL uppercase(nonbonded%pot(start + n_items)%pot%at1)
882 CALL uppercase(nonbonded%pot(start + n_items)%pot%at2)
883 nonbonded%pot(start + n_items)%pot%set(1)%nequip = nequip
884 nonbonded%pot(start + n_items)%pot%rcutsq = nequip%rcutsq
885 n_items = n_items + 1
889 END SUBROUTINE read_nequip_section
898 SUBROUTINE read_allegro_section(nonbonded, section, start)
899 TYPE(pair_potential_p_type),
POINTER :: nonbonded
900 TYPE(section_vals_type),
POINTER :: section
901 INTEGER,
INTENT(IN) :: start
903 CHARACTER(LEN=default_string_length) :: allegro_file_name, unit_cell, &
904 unit_coords, unit_energy, unit_forces
905 CHARACTER(LEN=default_string_length), &
906 DIMENSION(:),
POINTER :: atm_names
907 INTEGER :: isec, jsec, n_items
908 TYPE(allegro_pot_type) :: allegro
912 n_items = isec*n_items
922 allegro%unit_coords = unit_coords
923 allegro%unit_forces = unit_forces
924 allegro%unit_energy = unit_energy
925 allegro%unit_cell = unit_cell
926 CALL read_allegro_data(allegro)
927 CALL check_cp2k_atom_names_in_torch(atm_names, allegro%type_names_torch)
929 DO isec = 1,
SIZE(atm_names)
930 DO jsec = isec,
SIZE(atm_names)
932 nonbonded%pot(start + n_items)%pot%at1 = atm_names(isec)
933 nonbonded%pot(start + n_items)%pot%at2 = atm_names(jsec)
934 CALL uppercase(nonbonded%pot(start + n_items)%pot%at1)
935 CALL uppercase(nonbonded%pot(start + n_items)%pot%at2)
936 nonbonded%pot(start + n_items)%pot%set(1)%allegro = allegro
937 nonbonded%pot(start + n_items)%pot%rcutsq = allegro%rcutsq
938 n_items = n_items + 1
941 END SUBROUTINE read_allegro_section
953 INTEGER,
INTENT(IN) :: start
955 CHARACTER(LEN=default_string_length), &
956 DIMENSION(:),
POINTER :: atm_names
957 INTEGER :: isec, n_items, n_rep
958 REAL(kind=
dp) :: epsilon, rcut, sigma
968 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
969 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
970 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
971 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
972 nonbonded%pot(start + isec)%pot%set(1)%lj%epsilon = epsilon
973 nonbonded%pot(start + isec)%pot%set(1)%lj%sigma6 = sigma**6
974 nonbonded%pot(start + isec)%pot%set(1)%lj%sigma12 = sigma**12
975 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
979 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
982 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
996 INTEGER,
INTENT(IN) :: start
998 CHARACTER(LEN=default_string_length), &
999 DIMENSION(:),
POINTER :: atm_names
1000 INTEGER :: isec, n_items, n_rep
1001 REAL(kind=
dp) :: a, b, c, rcut
1004 DO isec = 1, n_items
1011 nonbonded%pot(start + isec)%pot%type =
wl_type
1012 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1013 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1014 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1015 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1016 nonbonded%pot(start + isec)%pot%set(1)%willis%a = a
1017 nonbonded%pot(start + isec)%pot%set(1)%willis%b = b
1018 nonbonded%pot(start + isec)%pot%set(1)%willis%c = c
1019 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
1023 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1026 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1040 INTEGER,
INTENT(IN) :: start
1042 CHARACTER(LEN=default_string_length), &
1043 DIMENSION(:),
POINTER :: atm_names
1044 INTEGER :: isec, m, mc, n_items, n_rep
1045 REAL(kind=
dp) :: d, dc, rcut, vr0
1048 DO isec = 1, n_items
1057 nonbonded%pot(start + isec)%pot%type =
gw_type
1058 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1059 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1060 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1061 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1062 nonbonded%pot(start + isec)%pot%set(1)%goodwin%vr0 = vr0
1063 nonbonded%pot(start + isec)%pot%set(1)%goodwin%d = d
1064 nonbonded%pot(start + isec)%pot%set(1)%goodwin%dc = dc
1065 nonbonded%pot(start + isec)%pot%set(1)%goodwin%m = m
1066 nonbonded%pot(start + isec)%pot%set(1)%goodwin%mc = mc
1067 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
1071 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1074 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1085 SUBROUTINE read_ipbv_section(nonbonded, section, start)
1088 INTEGER,
INTENT(IN) :: start
1090 CHARACTER(LEN=default_string_length), &
1091 DIMENSION(:),
POINTER :: atm_names
1092 INTEGER :: isec, n_items, n_rep
1093 REAL(kind=
dp) :: rcut
1096 DO isec = 1, n_items
1098 nonbonded%pot(start + isec)%pot%type =
ip_type
1099 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1100 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1101 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1102 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1103 CALL set_ipbv_ff(nonbonded%pot(start + isec)%pot%at1, nonbonded%pot(start + isec)%pot%at2, &
1104 nonbonded%pot(start + isec)%pot%set(1)%ipbv)
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_ipbv_section
1124 SUBROUTINE read_bmhft_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
1136 DO isec = 1, n_items
1140 nonbonded%pot(start + isec)%pot%type =
ft_type
1141 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1142 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1143 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1144 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1149 r_val=nonbonded%pot(start + isec)%pot%set(1)%ft%a)
1151 r_val=nonbonded%pot(start + isec)%pot%set(1)%ft%b)
1153 r_val=nonbonded%pot(start + isec)%pot%set(1)%ft%c)
1155 r_val=nonbonded%pot(start + isec)%pot%set(1)%ft%d)
1158 map_atoms = atm_names
1161 CALL set_bmhft_ff(map_atoms(1), map_atoms(2), nonbonded%pot(start + isec)%pot%set(1)%ft)
1164 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1168 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1171 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1173 END SUBROUTINE read_bmhft_section
1182 SUBROUTINE read_bmhftd_section(nonbonded, section, start)
1185 INTEGER,
INTENT(IN) :: start
1187 CHARACTER(LEN=default_string_length),
DIMENSION(2) :: map_atoms
1188 CHARACTER(LEN=default_string_length), &
1189 DIMENSION(:),
POINTER :: atm_names
1190 INTEGER :: i, isec, n_items, n_rep
1191 REAL(kind=
dp) :: rcut
1192 REAL(kind=
dp),
DIMENSION(:),
POINTER :: bd_vals
1198 DO isec = 1, n_items
1202 nonbonded%pot(start + isec)%pot%type =
ftd_type
1203 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1204 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1205 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1206 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1211 r_val=nonbonded%pot(start + isec)%pot%set(1)%ftd%a)
1213 r_val=nonbonded%pot(start + isec)%pot%set(1)%ftd%b)
1215 r_val=nonbonded%pot(start + isec)%pot%set(1)%ftd%c)
1217 r_val=nonbonded%pot(start + isec)%pot%set(1)%ftd%d)
1219 IF (
ASSOCIATED(bd_vals))
THEN
1220 SELECT CASE (
SIZE(bd_vals))
1222 cpabort(
"No values specified for parameter BD in section &BMHFTD")
1224 nonbonded%pot(start + isec)%pot%set(1)%ftd%bd(1:2) = bd_vals(1)
1226 nonbonded%pot(start + isec)%pot%set(1)%ftd%bd(1:2) = bd_vals(1:2)
1228 cpabort(
"Too many values specified for parameter BD in section &BMHFTD")
1231 cpabort(
"Parameter BD in section &BMHFTD was not specified")
1235 map_atoms = atm_names
1238 CALL set_bmhftd_ff()
1241 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1245 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1248 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1250 END SUBROUTINE read_bmhftd_section
1261 SUBROUTINE read_b4_section(nonbonded, section, start)
1265 INTEGER,
INTENT(IN) :: start
1267 CHARACTER(LEN=default_string_length), &
1268 DIMENSION(:),
POINTER :: atm_names
1269 INTEGER :: i, ir, isec, n_items, n_rep, np1, np2
1270 LOGICAL :: explicit_poly1, explicit_poly2
1271 REAL(kind=
dp) :: a, b, c, eval_error, r1, r2, r3, rcut
1272 REAL(kind=
dp),
DIMENSION(10) :: v, x
1273 REAL(kind=
dp),
DIMENSION(10, 10) :: p, p_inv
1274 REAL(kind=
dp),
DIMENSION(:),
POINTER :: coeff1, coeff2,
list
1281 DO isec = 1, n_items
1291 IF (explicit_poly1)
THEN
1296 IF (
ASSOCIATED(
list))
THEN
1298 DO i = 1,
SIZE(
list)
1299 coeff1(i + np1 - 1) =
list(i)
1301 np1 = np1 +
SIZE(
list)
1306 IF (explicit_poly2)
THEN
1311 IF (
ASSOCIATED(
list))
THEN
1313 DO i = 1,
SIZE(
list)
1314 coeff2(i + np2 - 1) =
list(i)
1316 np2 = np2 +
SIZE(
list)
1321 IF ((.NOT. explicit_poly1) .OR. (.NOT. explicit_poly2))
THEN
1328 p(1, i) = p(1, i - 1)*r1
1332 p(2, i) = real(i - 1, kind=
dp)*p(1, i - 1)
1336 p(3, i) = real(i - 1, kind=
dp)*p(2, i - 1)
1341 p(4, i) = p(4, i - 1)*r2
1345 p(4, i) = p(4, i - 1)*r2
1349 p(5, i) = real(i - 1, kind=
dp)*p(4, i - 1)
1352 p(5, i) = real(i - 7, kind=
dp)*p(4, i - 1)
1356 p(6, i) = real(i - 1, kind=
dp)*p(5, i - 1)
1359 p(6, i) = real(i - 7, kind=
dp)*p(5, i - 1)
1368 p(8, i) = p(8, i - 1)*r3
1372 p(9, i) = real(i - 7, kind=
dp)*p(8, i - 1)
1376 p(10, i) = real(i - 7, kind=
dp)*p(9, i - 1)
1383 v(8) = -c/p(8, 10)**2
1384 v(9) = -6.0_dp*v(8)/r3
1385 v(10) = -7.0_dp*v(9)/r3
1387 p_inv(:, :) = 0.0_dp
1389 IF (eval_error >= 1.0e-8_dp) &
1390 CALL cp_warn(__location__, &
1391 "The polynomial fit for the BUCK4RANGES potential is only accurate to "// &
1395 x(:) = matmul(p_inv(:, :), v(:))
1402 nonbonded%pot(start + isec)%pot%type =
b4_type
1403 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1404 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1405 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1406 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1407 nonbonded%pot(start + isec)%pot%set(1)%buck4r%a = a
1408 nonbonded%pot(start + isec)%pot%set(1)%buck4r%b = b
1409 nonbonded%pot(start + isec)%pot%set(1)%buck4r%c = c
1410 nonbonded%pot(start + isec)%pot%set(1)%buck4r%r1 = r1
1411 nonbonded%pot(start + isec)%pot%set(1)%buck4r%r2 = r2
1412 nonbonded%pot(start + isec)%pot%set(1)%buck4r%r3 = r3
1413 IF ((.NOT. explicit_poly1) .OR. (.NOT. explicit_poly2))
THEN
1414 nonbonded%pot(start + isec)%pot%set(1)%buck4r%npoly1 = 5
1415 nonbonded%pot(start + isec)%pot%set(1)%buck4r%poly1(0:5) = x(1:6)
1416 nonbonded%pot(start + isec)%pot%set(1)%buck4r%npoly2 = 3
1417 nonbonded%pot(start + isec)%pot%set(1)%buck4r%poly2(0:3) = x(7:10)
1419 nonbonded%pot(start + isec)%pot%set(1)%buck4r%npoly1 = np1 - 1
1420 cpassert(np1 - 1 <= 10)
1421 nonbonded%pot(start + isec)%pot%set(1)%buck4r%poly1(0:np1 - 1) = coeff1(0:np1 - 1)
1422 nonbonded%pot(start + isec)%pot%set(1)%buck4r%npoly2 = np2 - 1
1423 cpassert(np2 - 1 <= 10)
1424 nonbonded%pot(start + isec)%pot%set(1)%buck4r%poly2(0:np2 - 1) = coeff2(0:np2 - 1)
1426 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
1428 IF (
ASSOCIATED(coeff1))
THEN
1431 IF (
ASSOCIATED(coeff2))
THEN
1436 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1439 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1442 END SUBROUTINE read_b4_section
1454 INTEGER,
INTENT(IN) :: start
1456 CHARACTER(LEN=default_string_length), &
1457 DIMENSION(:),
POINTER :: atm_names
1458 INTEGER :: isec, n_items, n_rep
1459 REAL(kind=
dp) :: rcut
1462 DO isec = 1, n_items
1466 nonbonded%pot(start + isec)%pot%type =
gp_type
1467 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1468 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1469 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
1470 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1471 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1473 CALL get_generic_info(section,
"FUNCTION", nonbonded%pot(start + isec)%pot%set(1)%gp%potential, &
1474 nonbonded%pot(start + isec)%pot%set(1)%gp%parameters, &
1475 nonbonded%pot(start + isec)%pot%set(1)%gp%values, &
1476 size_variables=1, i_rep_sec=isec)
1477 nonbonded%pot(start + isec)%pot%set(1)%gp%variables = nonbonded%pot(start + isec)%pot%set(1)%gp%parameters(1)
1481 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1484 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1496 SUBROUTINE read_tersoff_section(nonbonded, section, start, tersoff_section)
1499 INTEGER,
INTENT(IN) :: start
1502 CHARACTER(LEN=default_string_length), &
1503 DIMENSION(:),
POINTER :: atm_names
1504 INTEGER :: isec, n_items, n_rep
1505 REAL(kind=
dp) :: rcut, rcutsq
1508 DO isec = 1, n_items
1513 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1514 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1515 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1516 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1519 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%A)
1521 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%B)
1523 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%lambda1)
1525 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%lambda2)
1527 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%alpha)
1529 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%beta)
1531 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%n)
1533 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%c)
1535 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%d)
1537 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%h)
1539 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%lambda3)
1541 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%bigR)
1543 r_val=nonbonded%pot(start + isec)%pot%set(1)%tersoff%bigD)
1545 rcutsq = (nonbonded%pot(start + isec)%pot%set(1)%tersoff%bigR + &
1546 nonbonded%pot(start + isec)%pot%set(1)%tersoff%bigD)**2
1547 nonbonded%pot(start + isec)%pot%set(1)%tersoff%rcutsq = rcutsq
1548 nonbonded%pot(start + isec)%pot%rcutsq = rcutsq
1552 IF (n_rep == 1)
THEN
1554 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1557 END SUBROUTINE read_tersoff_section
1567 SUBROUTINE read_gal_section(nonbonded, section, start, gal_section)
1570 INTEGER,
INTENT(IN) :: start
1573 CHARACTER(LEN=default_string_length), &
1574 DIMENSION(:),
POINTER :: atm_names
1575 INTEGER :: iatom, isec, n_items, n_rep, nval
1577 REAL(kind=
dp) :: rcut, rval
1578 REAL(kind=
dp),
DIMENSION(:),
POINTER :: rvalues
1584 DO isec = 1, n_items
1588 nonbonded%pot(start + isec)%pot%type =
gal_type
1589 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1590 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1591 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1592 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1595 IF (any(len_trim(atm_names(:)) > 2))
THEN
1596 cpwarn(
"The atom name will be truncated.")
1598 nonbonded%pot(start + isec)%pot%set(1)%gal%met1 = trim(atm_names(1))
1599 nonbonded%pot(start + isec)%pot%set(1)%gal%met2 = trim(atm_names(2))
1602 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%epsilon)
1604 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%bxy)
1606 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%bz)
1609 nonbonded%pot(start + isec)%pot%set(1)%gal%r1 = rvalues(1)
1610 nonbonded%pot(start + isec)%pot%set(1)%gal%r2 = rvalues(2)
1613 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a1)
1615 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a2)
1617 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a3)
1619 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a4)
1621 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%a)
1623 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%b)
1625 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal%c)
1629 ALLOCATE (nonbonded%pot(start + isec)%pot%set(1)%gal%gcn(nval))
1636 nonbonded%pot(start + isec)%pot%set(1)%gal%gcn(iatom) = rval
1640 l_val=nonbonded%pot(start + isec)%pot%set(1)%gal%express)
1644 IF (n_rep == 1)
THEN
1646 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1647 nonbonded%pot(start + isec)%pot%set(1)%gal%rcutsq = rcut**2
1650 END SUBROUTINE read_gal_section
1660 SUBROUTINE read_gal21_section(nonbonded, section, start, gal21_section)
1663 INTEGER,
INTENT(IN) :: start
1666 CHARACTER(LEN=default_string_length), &
1667 DIMENSION(:),
POINTER :: atm_names
1668 INTEGER :: iatom, isec, n_items, n_rep, nval
1670 REAL(kind=
dp) :: rcut, rval
1671 REAL(kind=
dp),
DIMENSION(:),
POINTER :: rvalues
1677 DO isec = 1, n_items
1681 nonbonded%pot(start + isec)%pot%type =
gal21_type
1682 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1683 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1684 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1685 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1688 IF (any(len_trim(atm_names(:)) > 2))
THEN
1689 cpwarn(
"The atom name will be truncated.")
1691 nonbonded%pot(start + isec)%pot%set(1)%gal21%met1 = trim(atm_names(1))
1692 nonbonded%pot(start + isec)%pot%set(1)%gal21%met2 = trim(atm_names(2))
1695 nonbonded%pot(start + isec)%pot%set(1)%gal21%epsilon1 = rvalues(1)
1696 nonbonded%pot(start + isec)%pot%set(1)%gal21%epsilon2 = rvalues(2)
1697 nonbonded%pot(start + isec)%pot%set(1)%gal21%epsilon3 = rvalues(3)
1700 nonbonded%pot(start + isec)%pot%set(1)%gal21%bxy1 = rvalues(1)
1701 nonbonded%pot(start + isec)%pot%set(1)%gal21%bxy2 = rvalues(2)
1704 nonbonded%pot(start + isec)%pot%set(1)%gal21%bz1 = rvalues(1)
1705 nonbonded%pot(start + isec)%pot%set(1)%gal21%bz2 = rvalues(2)
1708 nonbonded%pot(start + isec)%pot%set(1)%gal21%r1 = rvalues(1)
1709 nonbonded%pot(start + isec)%pot%set(1)%gal21%r2 = rvalues(2)
1712 nonbonded%pot(start + isec)%pot%set(1)%gal21%a11 = rvalues(1)
1713 nonbonded%pot(start + isec)%pot%set(1)%gal21%a12 = rvalues(2)
1714 nonbonded%pot(start + isec)%pot%set(1)%gal21%a13 = rvalues(3)
1717 nonbonded%pot(start + isec)%pot%set(1)%gal21%a21 = rvalues(1)
1718 nonbonded%pot(start + isec)%pot%set(1)%gal21%a22 = rvalues(2)
1719 nonbonded%pot(start + isec)%pot%set(1)%gal21%a23 = rvalues(3)
1722 nonbonded%pot(start + isec)%pot%set(1)%gal21%a31 = rvalues(1)
1723 nonbonded%pot(start + isec)%pot%set(1)%gal21%a32 = rvalues(2)
1724 nonbonded%pot(start + isec)%pot%set(1)%gal21%a33 = rvalues(3)
1727 nonbonded%pot(start + isec)%pot%set(1)%gal21%a41 = rvalues(1)
1728 nonbonded%pot(start + isec)%pot%set(1)%gal21%a42 = rvalues(2)
1729 nonbonded%pot(start + isec)%pot%set(1)%gal21%a43 = rvalues(3)
1732 nonbonded%pot(start + isec)%pot%set(1)%gal21%AO1 = rvalues(1)
1733 nonbonded%pot(start + isec)%pot%set(1)%gal21%AO2 = rvalues(2)
1736 nonbonded%pot(start + isec)%pot%set(1)%gal21%BO1 = rvalues(1)
1737 nonbonded%pot(start + isec)%pot%set(1)%gal21%BO2 = rvalues(2)
1740 r_val=nonbonded%pot(start + isec)%pot%set(1)%gal21%c)
1743 nonbonded%pot(start + isec)%pot%set(1)%gal21%AH1 = rvalues(1)
1744 nonbonded%pot(start + isec)%pot%set(1)%gal21%AH2 = rvalues(2)
1747 nonbonded%pot(start + isec)%pot%set(1)%gal21%BH1 = rvalues(1)
1748 nonbonded%pot(start + isec)%pot%set(1)%gal21%BH2 = rvalues(2)
1753 ALLOCATE (nonbonded%pot(start + isec)%pot%set(1)%gal21%gcn(nval))
1760 nonbonded%pot(start + isec)%pot%set(1)%gal21%gcn(iatom) = rval
1764 l_val=nonbonded%pot(start + isec)%pot%set(1)%gal21%express)
1768 IF (n_rep == 1)
THEN
1770 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1771 nonbonded%pot(start + isec)%pot%set(1)%gal21%rcutsq = rcut**2
1774 END SUBROUTINE read_gal21_section
1784 SUBROUTINE read_siepmann_section(nonbonded, section, start, siepmann_section)
1787 INTEGER,
INTENT(IN) :: start
1790 CHARACTER(LEN=default_string_length), &
1791 DIMENSION(:),
POINTER :: atm_names
1792 INTEGER :: isec, n_items, n_rep
1793 REAL(kind=
dp) :: rcut
1796 DO isec = 1, n_items
1801 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1802 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1803 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1804 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1807 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%B)
1809 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%D)
1811 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%E)
1813 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%F)
1815 r_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%beta)
1817 l_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%allow_oh_formation)
1819 l_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%allow_h3o_formation)
1821 l_val=nonbonded%pot(start + isec)%pot%set(1)%siepmann%allow_o_formation)
1825 IF (n_rep == 1)
THEN
1827 nonbonded%pot(start + isec)%pot%rcutsq = rcut**2
1828 nonbonded%pot(start + isec)%pot%set(1)%siepmann%rcutsq = rcut**2
1831 END SUBROUTINE read_siepmann_section
1840 SUBROUTINE read_bm_section(nonbonded, section, start)
1843 INTEGER,
INTENT(IN) :: start
1845 CHARACTER(LEN=default_string_length), &
1846 DIMENSION(:),
POINTER :: atm_names
1847 INTEGER :: isec, n_items, n_rep
1848 REAL(kind=
dp) :: a1, a2, b1, b2, beta, c, d, f0, r0, rcut
1851 DO isec = 1, n_items
1865 nonbonded%pot(start + isec)%pot%type =
bm_type
1866 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1867 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1868 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1869 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1870 nonbonded%pot(start + isec)%pot%set(1)%buckmo%f0 = f0
1871 nonbonded%pot(start + isec)%pot%set(1)%buckmo%a1 = a1
1872 nonbonded%pot(start + isec)%pot%set(1)%buckmo%a2 = a2
1873 nonbonded%pot(start + isec)%pot%set(1)%buckmo%b1 = b1
1874 nonbonded%pot(start + isec)%pot%set(1)%buckmo%b2 = b2
1875 nonbonded%pot(start + isec)%pot%set(1)%buckmo%c = c
1876 nonbonded%pot(start + isec)%pot%set(1)%buckmo%d = d
1877 nonbonded%pot(start + isec)%pot%set(1)%buckmo%r0 = r0
1878 nonbonded%pot(start + isec)%pot%set(1)%buckmo%beta = beta
1879 nonbonded%pot(start + isec)%pot%rcutsq = rcut*rcut
1883 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmin)
1886 r_val=nonbonded%pot(start + isec)%pot%set(1)%rmax)
1888 END SUBROUTINE read_bm_section
1899 SUBROUTINE read_tabpot_section(nonbonded, section, start, para_env, mm_section)
1902 INTEGER,
INTENT(IN) :: start
1906 CHARACTER(LEN=default_string_length), &
1907 DIMENSION(:),
POINTER :: atm_names
1908 INTEGER :: isec, n_items
1911 DO isec = 1, n_items
1913 nonbonded%pot(start + isec)%pot%type =
tab_type
1914 nonbonded%pot(start + isec)%pot%at1 = atm_names(1)
1915 nonbonded%pot(start + isec)%pot%at2 = atm_names(2)
1916 CALL uppercase(nonbonded%pot(start + isec)%pot%at1)
1917 CALL uppercase(nonbonded%pot(start + isec)%pot%at2)
1919 c_val=nonbonded%pot(start + isec)%pot%set(1)%tab%tabpot_file_name)
1920 CALL read_tabpot_data(nonbonded%pot(start + isec)%pot%set(1)%tab, para_env, mm_section)
1921 nonbonded%pot(start + isec)%pot%set(1)%tab%index = isec
1923 END SUBROUTINE read_tabpot_section
1934 CHARACTER(LEN=default_string_length), &
1935 DIMENSION(:),
POINTER :: charge_atm
1936 REAL(kind=
dp),
DIMENSION(:),
POINTER :: charge
1938 INTEGER,
INTENT(IN) :: start
1940 CHARACTER(LEN=default_string_length) :: atm_name
1941 INTEGER :: isec, n_items
1944 DO isec = 1, n_items
1946 charge_atm(start + isec) = atm_name
1947 CALL uppercase(charge_atm(start + isec))
1961 SUBROUTINE read_apol_section(apol_atm, apol, damping_list, section, &
1963 CHARACTER(LEN=default_string_length), &
1964 DIMENSION(:),
POINTER :: apol_atm
1965 REAL(kind=
dp),
DIMENSION(:),
POINTER :: apol
1968 INTEGER,
INTENT(IN) :: start
1970 CHARACTER(LEN=default_string_length) :: atm_name
1971 INTEGER :: isec, isec_damp, n_damp, n_items, &
1972 start_damp, tmp_damp
1976 NULLIFY (tmp_section)
1979 DO isec = 1, n_items
1983 n_damp = n_damp + tmp_damp
1987 IF (n_damp > 0)
THEN
1988 ALLOCATE (damping_list(1:n_damp))
1993 DO isec = 1, n_items
1995 apol_atm(start + isec) = atm_name
2002 DO isec_damp = 1, tmp_damp
2003 damping_list(start_damp + isec_damp)%atm_name1 = apol_atm(start + isec)
2006 damping_list(start_damp + isec_damp)%atm_name2 = atm_name
2007 CALL uppercase(damping_list(start_damp + isec_damp)%atm_name2)
2010 damping_list(start_damp + isec_damp)%dtype = atm_name
2011 CALL uppercase(damping_list(start_damp + isec_damp)%dtype)
2014 i_val=damping_list(start_damp + isec_damp)%order)
2016 r_val=damping_list(start_damp + isec_damp)%bij)
2018 r_val=damping_list(start_damp + isec_damp)%cij)
2020 start_damp = start_damp + tmp_damp
2024 END SUBROUTINE read_apol_section
2034 SUBROUTINE read_cpol_section(cpol_atm, cpol, section, start)
2035 CHARACTER(LEN=default_string_length), &
2036 DIMENSION(:),
POINTER :: cpol_atm
2037 REAL(kind=
dp),
DIMENSION(:),
POINTER :: cpol
2039 INTEGER,
INTENT(IN) :: start
2041 CHARACTER(LEN=default_string_length) :: atm_name
2042 INTEGER :: isec, n_items
2045 DO isec = 1, n_items
2047 cpol_atm(start + isec) = atm_name
2051 END SUBROUTINE read_cpol_section
2060 SUBROUTINE read_shell_section(shell_list, section, start)
2062 TYPE(
shell_p_type),
DIMENSION(:),
POINTER :: shell_list
2064 INTEGER,
INTENT(IN) :: start
2066 CHARACTER(LEN=default_string_length) :: atm_name
2067 INTEGER :: i_rep, n_rep
2068 REAL(
dp) :: ccharge, cutoff, k, maxdist, mfrac, &
2075 c_val=atm_name, i_rep_section=i_rep)
2077 shell_list(start + i_rep)%atm_name = atm_name
2079 shell_list(start + i_rep)%shell%charge_core = ccharge
2081 shell_list(start + i_rep)%shell%charge_shell = scharge
2083 shell_list(start + i_rep)%shell%massfrac = mfrac
2085 IF (k < 0.0_dp)
THEN
2086 CALL cp_abort(__location__, &
2087 "An invalid value was specified for the force constant k2 of the core-shell "// &
2090 shell_list(start + i_rep)%shell%k2_spring = k
2092 IF (k < 0.0_dp)
THEN
2093 CALL cp_abort(__location__, &
2094 "An invalid value was specified for the force constant k4 of the core-shell "// &
2097 shell_list(start + i_rep)%shell%k4_spring = k
2099 shell_list(start + i_rep)%shell%max_dist = maxdist
2101 shell_list(start + i_rep)%shell%shell_cutoff = cutoff
2104 END SUBROUTINE read_shell_section
2118 SUBROUTINE read_bonds_section(bond_kind, bond_a, bond_b, bond_k, bond_r0, bond_cs, section, start)
2119 INTEGER,
DIMENSION(:),
POINTER :: bond_kind
2120 CHARACTER(LEN=default_string_length), &
2121 DIMENSION(:),
POINTER :: bond_a, bond_b
2122 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: bond_k
2123 REAL(kind=
dp),
DIMENSION(:),
POINTER :: bond_r0, bond_cs
2125 INTEGER,
INTENT(IN) :: start
2127 CHARACTER(LEN=default_string_length), &
2128 DIMENSION(:),
POINTER :: atm_names
2129 INTEGER :: isec, k, n_items
2130 REAL(kind=
dp),
DIMENSION(:),
POINTER :: kvals
2132 NULLIFY (kvals, atm_names)
2134 DO isec = 1, n_items
2137 bond_a(start + isec) = atm_names(1)
2138 bond_b(start + isec) = atm_names(2)
2142 cpassert(
SIZE(kvals) <= 3)
2143 bond_k(:, start + isec) = 0.0_dp
2144 DO k = 1,
SIZE(kvals)
2145 bond_k(k, start + isec) = kvals(k)
2150 END SUBROUTINE read_bonds_section
2171 SUBROUTINE read_bends_section(bend_kind, bend_a, bend_b, bend_c, bend_k, bend_theta0, bend_cb, &
2172 bend_r012, bend_r032, bend_kbs12, bend_kbs32, bend_kss, bend_legendre, &
2174 INTEGER,
DIMENSION(:),
POINTER :: bend_kind
2175 CHARACTER(LEN=default_string_length), &
2176 DIMENSION(:),
POINTER :: bend_a, bend_b, bend_c
2177 REAL(kind=
dp),
DIMENSION(:),
POINTER :: bend_k, bend_theta0, bend_cb, bend_r012, &
2178 bend_r032, bend_kbs12, bend_kbs32, &
2182 INTEGER,
INTENT(IN) :: start
2184 CHARACTER(LEN=default_string_length), &
2185 DIMENSION(:),
POINTER :: atm_names
2186 INTEGER :: isec, k, n_items, n_rep
2187 REAL(kind=
dp),
DIMENSION(:),
POINTER :: kvals, r_values
2189 NULLIFY (kvals, atm_names)
2191 bend_legendre%order = 0
2192 DO isec = 1, n_items
2195 bend_a(start + isec) = atm_names(1)
2196 bend_b(start + isec) = atm_names(2)
2197 bend_c(start + isec) = atm_names(3)
2202 cpassert(
SIZE(kvals) == 1)
2203 bend_k(start + isec) = kvals(1)
2204 CALL section_vals_val_get(section,
"THETA0", i_rep_section=isec, r_val=bend_theta0(start + isec))
2208 CALL section_vals_val_get(section,
"KBS12", i_rep_section=isec, r_val=bend_kbs12(start + isec))
2209 CALL section_vals_val_get(section,
"KBS32", i_rep_section=isec, r_val=bend_kbs32(start + isec))
2214 CALL section_vals_val_get(section,
"LEGENDRE", i_rep_val=k, r_vals=r_values, i_rep_section=isec)
2215 bend_legendre(start + isec)%order =
SIZE(r_values)
2216 IF (
ASSOCIATED(bend_legendre(start + isec)%coeffs))
THEN
2217 DEALLOCATE (bend_legendre(start + isec)%coeffs)
2219 ALLOCATE (bend_legendre(start + isec)%coeffs(bend_legendre(start + isec)%order))
2220 bend_legendre(start + isec)%coeffs = r_values
2223 END SUBROUTINE read_bends_section
2236 SUBROUTINE read_ubs_section(ub_kind, ub_a, ub_b, ub_c, ub_k, ub_r0, section, start)
2237 INTEGER,
DIMENSION(:),
POINTER :: ub_kind
2238 CHARACTER(LEN=default_string_length), &
2239 DIMENSION(:),
POINTER :: ub_a, ub_b, ub_c
2240 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: ub_k
2241 REAL(kind=
dp),
DIMENSION(:),
POINTER :: ub_r0
2243 INTEGER,
INTENT(IN) :: start
2245 CHARACTER(LEN=default_string_length), &
2246 DIMENSION(:),
POINTER :: atm_names
2247 INTEGER :: isec, k, n_items
2249 REAL(kind=
dp),
DIMENSION(:),
POINTER :: kvals
2254 DO isec = 1, n_items
2260 ub_a(start + isec) = atm_names(1)
2261 ub_b(start + isec) = atm_names(2)
2262 ub_c(start + isec) = atm_names(3)
2267 cpassert(
SIZE(kvals) <= 3)
2268 ub_k(:, start + isec) = 0.0_dp
2269 DO k = 1,
SIZE(kvals)
2270 ub_k(k, start + isec) = kvals(k)
2275 END SUBROUTINE read_ubs_section
2291 SUBROUTINE read_torsions_section(torsion_kind, torsion_a, torsion_b, torsion_c, torsion_d, torsion_k, &
2292 torsion_phi0, torsion_m, section, start)
2293 INTEGER,
DIMENSION(:),
POINTER :: torsion_kind
2294 CHARACTER(LEN=default_string_length), &
2295 DIMENSION(:),
POINTER :: torsion_a, torsion_b, torsion_c, &
2297 REAL(kind=
dp),
DIMENSION(:),
POINTER :: torsion_k, torsion_phi0
2298 INTEGER,
DIMENSION(:),
POINTER :: torsion_m
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
2309 CALL section_vals_val_get(section,
"KIND", i_rep_section=isec, i_val=torsion_kind(start + isec))
2311 torsion_a(start + isec) = atm_names(1)
2312 torsion_b(start + isec) = atm_names(2)
2313 torsion_c(start + isec) = atm_names(3)
2314 torsion_d(start + isec) = atm_names(4)
2320 CALL section_vals_val_get(section,
"PHI0", i_rep_section=isec, r_val=torsion_phi0(start + isec))
2323 IF (torsion_kind(start + isec) .EQ.
do_ff_opls)
THEN
2324 IF (torsion_phi0(start + isec) .NE. 0.0_dp)
THEN
2325 CALL cp_warn(__location__,
"PHI0 parameter was non-zero "// &
2326 "for an OPLS-type TORSION. It will be ignored.")
2328 IF (
modulo(torsion_m(start + isec), 2) .EQ. 0)
THEN
2330 torsion_phi0(start + isec) =
pi
2333 torsion_k(start + isec) = torsion_k(start + isec)*0.5_dp
2336 END SUBROUTINE read_torsions_section
2351 SUBROUTINE read_improper_section(impr_kind, impr_a, impr_b, impr_c, impr_d, impr_k, &
2352 impr_phi0, section, start)
2353 INTEGER,
DIMENSION(:),
POINTER :: impr_kind
2354 CHARACTER(LEN=default_string_length), &
2355 DIMENSION(:),
POINTER :: impr_a, impr_b, impr_c, impr_d
2356 REAL(kind=
dp),
DIMENSION(:),
POINTER :: impr_k, impr_phi0
2358 INTEGER,
INTENT(IN) :: start
2360 CHARACTER(LEN=default_string_length), &
2361 DIMENSION(:),
POINTER :: atm_names
2362 INTEGER :: isec, n_items
2366 DO isec = 1, n_items
2369 impr_a(start + isec) = atm_names(1)
2370 impr_b(start + isec) = atm_names(2)
2371 impr_c(start + isec) = atm_names(3)
2372 impr_d(start + isec) = atm_names(4)
2380 END SUBROUTINE read_improper_section
2395 SUBROUTINE read_opbend_section(opbend_kind, opbend_a, opbend_b, opbend_c, opbend_d, opbend_k, &
2396 opbend_phi0, section, start)
2397 INTEGER,
DIMENSION(:),
POINTER :: opbend_kind
2398 CHARACTER(LEN=default_string_length), &
2399 DIMENSION(:),
POINTER :: opbend_a, opbend_b, opbend_c, opbend_d
2400 REAL(kind=
dp),
DIMENSION(:),
POINTER :: opbend_k, opbend_phi0
2402 INTEGER,
INTENT(IN) :: start
2404 CHARACTER(LEN=default_string_length), &
2405 DIMENSION(:),
POINTER :: atm_names
2406 INTEGER :: isec, n_items
2410 DO isec = 1, n_items
2411 CALL section_vals_val_get(section,
"KIND", i_rep_section=isec, i_val=opbend_kind(start + isec))
2413 opbend_a(start + isec) = atm_names(1)
2414 opbend_b(start + isec) = atm_names(2)
2415 opbend_c(start + isec) = atm_names(3)
2416 opbend_d(start + isec) = atm_names(4)
2422 CALL section_vals_val_get(section,
"PHI0", i_rep_section=isec, r_val=opbend_phi0(start + isec))
2424 END SUBROUTINE read_opbend_section
2443 NULLIFY (ff_section)
2445 CALL read_force_field_section1(ff_section, mm_section, ff_type, para_env)
2454 SUBROUTINE read_eam_data(eam, para_env, mm_section)
2459 CHARACTER(len=*),
PARAMETER :: routinen =
'read_eam_data'
2461 INTEGER :: handle, i, iw
2465 CALL timeset(routinen, handle)
2470 IF (iw > 0)
WRITE (iw, *)
"Reading EAM data from: ", trim(eam%eam_file_name)
2471 CALL parser_create(parser, trim(eam%eam_file_name), para_env=para_env)
2474 IF (iw > 0)
WRITE (iw, *)
"Title: ", parser%input_line
2477 READ (parser%input_line, *) eam%drar, eam%drhoar, eam%acutal, eam%npoints
2490 DO i = 1, eam%npoints
2492 READ (parser%input_line, *) eam%rho(i), eam%rhop(i)
2494 eam%rval(i) = real(i - 1, kind=
dp)*eam%drar
2495 eam%rhoval(i) = real(i - 1, kind=
dp)*eam%drhoar
2498 DO i = 1, eam%npoints
2500 READ (parser%input_line, *) eam%phi(i), eam%phip(i)
2505 DO i = 1, eam%npoints
2507 READ (parser%input_line, *) eam%frho(i), eam%frhop(i)
2512 IF (iw > 0)
WRITE (iw, *)
"Finished EAM data"
2515 CALL timestop(handle)
2517 END SUBROUTINE read_eam_data
2524 SUBROUTINE read_nequip_data(nequip)
2527 CHARACTER(LEN=*),
PARAMETER :: routinen =
'read_nequip_data'
2528 CHARACTER(LEN=1),
PARAMETER :: delimiter =
' '
2530 CHARACTER(LEN=100),
ALLOCATABLE,
DIMENSION(:) :: tokenized_string
2531 CHARACTER(LEN=default_path_length) :: allow_tf32_str, cutoff_str, &
2532 default_dtype, model_dtype, types_str
2534 LOGICAL :: allow_tf32, found
2536 CALL timeset(routinen, handle)
2538 INQUIRE (file=nequip%nequip_file_name, exist=found)
2539 IF (.NOT. found)
THEN
2540 CALL cp_abort(__location__, &
2541 "Nequip model file <"//trim(nequip%nequip_file_name)// &
2548 CALL tokenize_string(trim(types_str), delimiter, tokenized_string)
2550 IF (
ALLOCATED(nequip%type_names_torch))
THEN
2551 DEALLOCATE (nequip%type_names_torch)
2553 ALLOCATE (nequip%type_names_torch(
SIZE(tokenized_string)))
2555 nequip%type_names_torch(:) = tokenized_string(:)
2557 READ (cutoff_str, *) nequip%rcutsq
2559 nequip%rcutsq = nequip%rcutsq*nequip%rcutsq
2560 nequip%unit_coords_val =
cp_unit_to_cp2k(nequip%unit_coords_val, nequip%unit_coords)
2561 nequip%unit_forces_val =
cp_unit_to_cp2k(nequip%unit_forces_val, nequip%unit_forces)
2562 nequip%unit_energy_val =
cp_unit_to_cp2k(nequip%unit_energy_val, nequip%unit_energy)
2563 nequip%unit_cell_val =
cp_unit_to_cp2k(nequip%unit_cell_val, nequip%unit_cell)
2567 IF (trim(default_dtype) ==
"float32" .AND. trim(model_dtype) ==
"float32")
THEN
2568 nequip%do_nequip_sp = .true.
2569 ELSE IF (trim(default_dtype) ==
"float64" .AND. trim(model_dtype) ==
"float64")
THEN
2570 nequip%do_nequip_sp = .false.
2572 CALL cp_abort(__location__, &
2573 "Both default_dtype and model_dtype should be either float32 or float64. Currently, default_dtype is <"// &
2574 trim(default_dtype)//
"> and model_dtype is <"//trim(model_dtype)//
">.")
2578 allow_tf32 = (trim(allow_tf32_str) ==
"1")
2579 IF (trim(allow_tf32_str) /=
"1" .AND. trim(allow_tf32_str) /=
"0")
THEN
2580 CALL cp_abort(__location__, &
2581 "The value for allow_tf32 <"//trim(allow_tf32_str)// &
2582 "> is not supported. Check the .yaml and .pth files.")
2586 CALL timestop(handle)
2587 END SUBROUTINE read_nequip_data
2594 SUBROUTINE read_allegro_data(allegro)
2597 CHARACTER(len=*),
PARAMETER :: routinen =
'read_allegro_data'
2598 CHARACTER(LEN=1),
PARAMETER :: delimiter =
' '
2600 CHARACTER(LEN=100),
ALLOCATABLE,
DIMENSION(:) :: tokenized_string
2601 CHARACTER(LEN=default_path_length) :: allow_tf32_str, cutoff_str, &
2602 default_dtype, model_dtype, types_str
2604 LOGICAL :: allow_tf32, found
2606 CALL timeset(routinen, handle)
2608 INQUIRE (file=allegro%allegro_file_name, exist=found)
2609 IF (.NOT. found)
THEN
2610 CALL cp_abort(__location__, &
2611 "Allegro model file <"//trim(allegro%allegro_file_name)// &
2616 IF (allegro%nequip_version ==
"")
THEN
2617 CALL cp_abort(__location__, &
2618 "Allegro model file <"//trim(allegro%allegro_file_name)// &
2619 "> has not been deployed; did you forget to run `nequip-deploy`?")
2623 CALL tokenize_string(trim(types_str), delimiter, tokenized_string)
2625 IF (
ALLOCATED(allegro%type_names_torch))
THEN
2626 DEALLOCATE (allegro%type_names_torch)
2628 ALLOCATE (allegro%type_names_torch(
SIZE(tokenized_string)))
2629 allegro%type_names_torch(:) = tokenized_string(:)
2631 READ (cutoff_str, *) allegro%rcutsq
2633 allegro%rcutsq = allegro%rcutsq*allegro%rcutsq
2634 allegro%unit_coords_val =
cp_unit_to_cp2k(allegro%unit_coords_val, allegro%unit_coords)
2635 allegro%unit_forces_val =
cp_unit_to_cp2k(allegro%unit_forces_val, allegro%unit_forces)
2636 allegro%unit_energy_val =
cp_unit_to_cp2k(allegro%unit_energy_val, allegro%unit_energy)
2637 allegro%unit_cell_val =
cp_unit_to_cp2k(allegro%unit_cell_val, allegro%unit_cell)
2641 IF (trim(default_dtype) ==
"float32" .AND. trim(model_dtype) ==
"float32")
THEN
2642 allegro%do_allegro_sp = .true.
2643 ELSE IF (trim(default_dtype) ==
"float64" .AND. trim(model_dtype) ==
"float64")
THEN
2644 allegro%do_allegro_sp = .false.
2646 CALL cp_abort(__location__, &
2647 "Both default_dtype and model_dtype should be either float32 or float64. Currently, default_dtype is <"// &
2648 trim(default_dtype)//
"> and model_dtype is <"//trim(model_dtype)//
">.")
2652 allow_tf32 = (trim(allow_tf32_str) ==
"1")
2653 IF (trim(allow_tf32_str) /=
"1" .AND. trim(allow_tf32_str) /=
"0")
THEN
2654 CALL cp_abort(__location__, &
2655 "The value for allow_tf32 <"//trim(allow_tf32_str)// &
2656 "> is not supported. Check the .yaml and .pth files.")
2660 CALL timestop(handle)
2661 END SUBROUTINE read_allegro_data
2670 SUBROUTINE tokenize_string(element, delimiter, tokenized_array)
2671 CHARACTER(LEN=*),
INTENT(IN) :: element
2672 CHARACTER(LEN=1),
INTENT(IN) :: delimiter
2673 CHARACTER(LEN=100),
ALLOCATABLE,
DIMENSION(:), &
2674 INTENT(OUT) :: tokenized_array
2676 CHARACTER(LEN=100) :: temp_kinds
2677 INTEGER :: end_pos, i, num_elements, start
2678 LOGICAL,
ALLOCATABLE,
DIMENSION(:) :: delim_positions
2681 ALLOCATE (delim_positions(len(element)))
2682 delim_positions = .false.
2684 DO i = 1, len(element)
2685 IF (element(i:i) == delimiter) delim_positions(i) = .true.
2688 num_elements = count(delim_positions) + 1
2690 ALLOCATE (tokenized_array(num_elements))
2693 DO i = 1, num_elements
2694 IF (len(element) < 3 .AND. count(delim_positions) == 0)
THEN
2696 end_pos = len(element)
2698 end_pos = find_end_pos(start, delim_positions)
2700 temp_kinds = element(start:end_pos)
2701 IF (trim(temp_kinds) /=
'')
THEN
2702 tokenized_array(i) = temp_kinds
2706 DEALLOCATE (delim_positions)
2707 END SUBROUTINE tokenize_string
2716 INTEGER FUNCTION find_end_pos(start, delim_positions)
2717 INTEGER,
INTENT(IN) :: start
2718 LOGICAL,
DIMENSION(:),
INTENT(IN) :: delim_positions
2720 INTEGER :: end_pos, i
2723 DO i = start,
SIZE(delim_positions)
2724 IF (delim_positions(i))
THEN
2730 find_end_pos = end_pos
2731 END FUNCTION find_end_pos
2739 SUBROUTINE check_cp2k_atom_names_in_torch(cp2k_inp_atom_types, torch_atom_types)
2740 CHARACTER(LEN=*),
DIMENSION(:),
INTENT(IN) :: cp2k_inp_atom_types, torch_atom_types
2745 DO i = 1,
SIZE(cp2k_inp_atom_types)
2747 DO j = 1,
SIZE(torch_atom_types)
2748 IF (trim(cp2k_inp_atom_types(i)) == trim(torch_atom_types(j)))
THEN
2753 IF (.NOT. found)
THEN
2754 CALL cp_abort(__location__, &
2755 "Atom "//trim(cp2k_inp_atom_types(i))// &
2756 " is defined in the CP2K input file but is missing in the torch model file")
2759 END SUBROUTINE check_cp2k_atom_names_in_torch
2768 SUBROUTINE read_tabpot_data(tab, para_env, mm_section)
2773 CHARACTER(len=*),
PARAMETER :: routinen =
'read_tabpot_data'
2776 INTEGER :: d, handle, i, iw
2780 CALL timeset(routinen, handle)
2785 IF (iw > 0)
WRITE (iw, *)
"Reading TABPOT data from: ", trim(tab%tabpot_file_name)
2786 CALL parser_create(parser, trim(tab%tabpot_file_name), para_env=para_env)
2788 IF (iw > 0)
WRITE (iw, *)
"Title: ", parser%input_line
2793 READ (parser%input_line, *) d1, tab%npoints, d2, tab%dr, tab%rcut
2801 DO i = 1, tab%npoints
2803 READ (parser%input_line, *) d, tab%r(i), tab%e(i), tab%f(i)
2809 tab%dr = tab%r(2) - tab%r(1)
2812 IF (iw > 0)
WRITE (iw, *)
"Finished TABPOT data"
2815 CALL timestop(handle)
2816 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
integer, parameter, public ftd_type
integer, parameter, public ip_type
integer, parameter, public deepmd_type
subroutine, public pair_potential_reallocate(p, lb1_new, ub1_new, lj, lj_charmm, williams, goodwin, eam, quip, nequip, allegro, bmhft, bmhftd, ipbv, buck4r, buckmo, gp, tersoff, siepmann, gal, gal21, tab, deepmd, ace)
Cleans the potential parameter type.
integer, parameter, public quip_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