16 USE iso_c_binding,
ONLY: c_associated
36#include "./base/base_uses.f90"
43 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'manybody_ace'
54 SUBROUTINE init_ace_data(particle_set, atomic_kind_set, potparm, &
57 TYPE(particle_type),
POINTER :: particle_set(:)
58 TYPE(atomic_kind_type),
POINTER :: atomic_kind_set(:)
59 TYPE(pair_potential_pp_type),
POINTER :: potparm
60 TYPE(ace_data_type),
POINTER :: ace_data
62 CHARACTER(LEN=*),
PARAMETER :: routineN =
'init_ace_data'
64 CHARACTER(2) :: element_symbol
65 INTEGER :: ace_natom, handle, i, iat, iat_use, &
66 ikind, jkind, lkind, n_atoms
67 INTEGER,
ALLOCATABLE :: use_atom_type(:)
68 INTEGER,
DIMENSION(:),
POINTER :: ak_alist
69 LOGICAL,
ALLOCATABLE :: use_atom(:)
70 TYPE(pair_potential_single_type),
POINTER :: pot
72 CALL timeset(routinen, handle)
75 IF (.NOT.
ASSOCIATED(ace_data))
THEN
79 n_atoms =
SIZE(particle_set)
80 ALLOCATE (use_atom(n_atoms))
81 ALLOCATE (use_atom_type(n_atoms))
85 DO ikind = 1,
SIZE(atomic_kind_set)
86 pot => potparm%pot(ikind, ikind)%pot
87 DO i = 1,
SIZE(pot%type)
90 element_symbol=element_symbol, &
91 natom=lkind, atom_list=ak_alist)
93 ace_data%model = pot%set(i)%ace%model
95 DO iat = 1,
SIZE(ace_data%model%symbolc)
96 IF (element_symbol == ace_data%model%symbolc(iat))
THEN
103 use_atom_type(ak_alist(iat)) = jkind
104 use_atom(ak_alist(iat)) = .true.
108 cpassert(c_associated(ace_data%model%c_ptr))
110 ace_natom = count(use_atom)
112 IF (.NOT.
ALLOCATED(ace_data%uctype))
THEN
113 ALLOCATE (ace_data%uctype(1:ace_natom))
118 IF (.NOT. use_atom(iat)) cycle
119 iat_use = iat_use + 1
120 ace_data%uctype(iat_use) = use_atom_type(iat)
123 IF (iat_use > 0)
THEN
129 IF (.NOT.
ALLOCATED(ace_data%force))
THEN
130 ALLOCATE (ace_data%force(3, ace_natom))
131 ALLOCATE (ace_data%use_indices(ace_natom))
132 ALLOCATE (ace_data%inverse_index_map(n_atoms))
134 cpassert(
SIZE(ace_data%force, 2) == ace_natom)
137 ace_data%inverse_index_map(:) = 0
139 IF (use_atom(iat))
THEN
140 iat_use = iat_use + 1
141 ace_data%use_indices(iat_use) = iat
142 ace_data%inverse_index_map(iat) = iat_use
145 ace_data%natom = ace_natom
146 DEALLOCATE (use_atom, use_atom_type)
148 CALL timestop(handle)
150 END SUBROUTINE init_ace_data
163 fist_nonbond_env, pot_ace)
170 REAL(kind=
dp),
INTENT(OUT) :: pot_ace
172 CHARACTER(LEN=*),
PARAMETER :: routinen =
'ace_energy_store_force_virial'
175 REAL(kind=
dp) :: ace_virial(1:6)
178 CALL timeset(routinen, handle)
182 IF (.NOT.
ASSOCIATED(ace_data))
THEN
185 CALL init_ace_data(particle_set, atomic_kind_set, potparm, ace_data)
190 pot_ace, ace_data%force, ace_virial, &
191 fist_nonbond_env, cell, ace_data)
194 pot_ace = pot_ace/
evolt
196 ace_virial = ace_virial/
evolt
199 ace_data%virial(1, 1) = -ace_virial(1)
200 ace_data%virial(2, 2) = -ace_virial(2)
201 ace_data%virial(3, 3) = -ace_virial(3)
202 ace_data%virial(1, 2) = -ace_virial(4)
203 ace_data%virial(2, 1) = -ace_virial(4)
204 ace_data%virial(1, 3) = -ace_virial(5)
205 ace_data%virial(3, 1) = -ace_virial(5)
206 ace_data%virial(2, 3) = -ace_virial(6)
207 ace_data%virial(3, 2) = -ace_virial(6)
209 CALL timestop(handle)
221 REAL(kind=
dp),
INTENT(INOUT) :: force(:, :), pv_nonbond(3, 3)
222 LOGICAL,
OPTIONAL :: use_virial
224 CHARACTER(LEN=*),
PARAMETER :: routinen =
'ace_add_force_virial'
226 INTEGER :: handle, iat, iat_use
229 CALL timeset(routinen, handle)
233 IF (.NOT.
ASSOCIATED(ace_data))
RETURN
235 DO iat_use = 1,
SIZE(ace_data%use_indices)
236 iat = ace_data%use_indices(iat_use)
237 cpassert(iat >= 1 .AND. iat <=
SIZE(force, 2))
238 force(1:3, iat) = force(1:3, iat) + ace_data%force(1:3, iat_use)
242 pv_nonbond = pv_nonbond + ace_data%virial
245 CALL timestop(handle)
subroutine, public ace_interface(ace_natom, ace_atype, pot_ace, ace_force, ace_virial, fist_nonbond_env, cell, ace_data)
...
Define the atomic kind types and their sub types.
subroutine, public get_atomic_kind(atomic_kind, fist_potential, element_symbol, name, mass, kind_number, natom, atom_list, rcov, rvdw, z, qeff, apol, cpol, mm_radius, shell, shell_active, damping)
Get attributes of an atomic kind.
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public drautz2019
integer, save, public lysogorskiy2021
integer, save, public bochkarev2024
Handles all functions related to the CELL.
subroutine, public fist_nonbond_env_get(fist_nonbond_env, potparm14, potparm, nonbonded, rlist_cut, rlist_lowsq, aup, lup, ei_scale14, vdw_scale14, shift_cutoff, do_electrostatics, r_last_update, r_last_update_pbc, rshell_last_update_pbc, rcore_last_update_pbc, cell_last_update, num_update, last_update, counter, natom_types, long_range_correction, ij_kind_full_fac, eam_data, quip_data, nequip_data, allegro_data, deepmd_data, ace_data, charges)
sets a fist_nonbond_env
subroutine, public fist_nonbond_env_set(fist_nonbond_env, potparm14, potparm, rlist_cut, rlist_lowsq, nonbonded, aup, lup, ei_scale14, vdw_scale14, shift_cutoff, do_electrostatics, r_last_update, r_last_update_pbc, rshell_last_update_pbc, rcore_last_update_pbc, cell_last_update, num_update, last_update, counter, natom_types, long_range_correction, eam_data, quip_data, nequip_data, allegro_data, deepmd_data, ace_data, charges)
sets a fist_nonbond_env
Defines the basic variable types.
integer, parameter, public dp
subroutine, public ace_energy_store_force_virial(particle_set, cell, atomic_kind_set, potparm, fist_nonbond_env, pot_ace)
... >
subroutine, public ace_add_force_virial(fist_nonbond_env, force, pv_nonbond, use_virial)
...
integer, parameter, public ace_type
Define the data structure for the particle information.
Definition of physical constants:
real(kind=dp), parameter, public evolt
real(kind=dp), parameter, public angstrom
Provides all information about an atomic kind.
Type defining parameters related to the simulation cell.