(git:e5b1968)
Loading...
Searching...
No Matches
manybody_ace.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \par History
10!> HAF (16-Apr-2025) : Import into CP2K
11!> \author HAF and yury-lysogorskiy and ralf-drautz
12! **************************************************************************************************
13
15
16 USE iso_c_binding, ONLY: c_associated
17 USE ace_nlist, ONLY: ace_interface
20 USE bibliography, ONLY: bochkarev2024,&
23 cite_reference
24 USE cell_types, ONLY: cell_type
29 USE kinds, ONLY: dp
34 USE physcon, ONLY: angstrom,&
35 evolt
36#include "./base/base_uses.f90"
37
38 IMPLICIT NONE
39
40 PRIVATE
42
43 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'manybody_ace'
44
45CONTAINS
46
47! **************************************************************************************************
48!> \brief ...
49!> \param particle_set ...
50!> \param atomic_kind_set ...
51!> \param potparm ...
52!> \param ace_data ...
53! **************************************************************************************************
54 SUBROUTINE init_ace_data(particle_set, atomic_kind_set, potparm, &
55 ace_data)
56
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
61
62 CHARACTER(LEN=*), PARAMETER :: routineN = 'init_ace_data'
63
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
71
72 CALL timeset(routinen, handle)
73
74 ! init ace_data
75 IF (.NOT. ASSOCIATED(ace_data)) THEN
76 ALLOCATE (ace_data)
77 END IF
78
79 n_atoms = SIZE(particle_set)
80 ALLOCATE (use_atom(n_atoms))
81 ALLOCATE (use_atom_type(n_atoms))
82 use_atom = .false.
83 use_atom_type = 0
84
85 DO ikind = 1, SIZE(atomic_kind_set)
86 pot => potparm%pot(ikind, ikind)%pot
87 DO i = 1, SIZE(pot%type)
88 IF (pot%type(i) /= ace_type) cycle
89 CALL get_atomic_kind(atomic_kind=atomic_kind_set(ikind), &
90 element_symbol=element_symbol, &
91 natom=lkind, atom_list=ak_alist)
92 IF (lkind < 1) cycle
93 ace_data%model = pot%set(i)%ace%model
94 jkind = 0
95 DO iat = 1, SIZE(ace_data%model%symbolc)
96 IF (element_symbol == ace_data%model%symbolc(iat)) THEN
97 jkind = iat
98 EXIT
99 END IF
100 END DO
101 cpassert(jkind > 0)
102 DO iat = 1, lkind
103 use_atom_type(ak_alist(iat)) = jkind
104 use_atom(ak_alist(iat)) = .true.
105 END DO
106 END DO ! i
107 END DO ! ikind
108 cpassert(c_associated(ace_data%model%c_ptr))
109
110 ace_natom = count(use_atom)
111
112 IF (.NOT. ALLOCATED(ace_data%uctype)) THEN
113 ALLOCATE (ace_data%uctype(1:ace_natom))
114 END IF
115
116 iat_use = 0
117 DO iat = 1, n_atoms
118 IF (.NOT. use_atom(iat)) cycle
119 iat_use = iat_use + 1
120 ace_data%uctype(iat_use) = use_atom_type(iat)
121 END DO
122
123 IF (iat_use > 0) THEN
124 CALL cite_reference(drautz2019)
125 CALL cite_reference(lysogorskiy2021)
126 CALL cite_reference(bochkarev2024)
127 END IF
128
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))
133 END IF
134 cpassert(SIZE(ace_data%force, 2) == ace_natom)
135
136 iat_use = 0
137 ace_data%inverse_index_map(:) = 0
138 DO iat = 1, n_atoms
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
143 END IF
144 END DO
145 ace_data%natom = ace_natom
146 DEALLOCATE (use_atom, use_atom_type)
147
148 CALL timestop(handle)
149
150 END SUBROUTINE init_ace_data
151
152! **************************************************************************************************
153!> \brief ...
154!> > \param particle_set ...
155!> \param particle_set ...
156!> \param cell ...
157!> \param atomic_kind_set ...
158!> \param potparm ...
159!> \param fist_nonbond_env ...
160!> \param pot_ace ...
161! **************************************************************************************************
162 SUBROUTINE ace_energy_store_force_virial(particle_set, cell, atomic_kind_set, potparm, &
163 fist_nonbond_env, pot_ace)
164
165 TYPE(particle_type), POINTER :: particle_set(:)
166 TYPE(cell_type), POINTER :: cell
167 TYPE(atomic_kind_type), POINTER :: atomic_kind_set(:)
168 TYPE(pair_potential_pp_type), POINTER :: potparm
169 TYPE(fist_nonbond_env_type), POINTER :: fist_nonbond_env
170 REAL(kind=dp), INTENT(OUT) :: pot_ace
171
172 CHARACTER(LEN=*), PARAMETER :: routinen = 'ace_energy_store_force_virial'
173
174 INTEGER :: handle
175 REAL(kind=dp) :: ace_virial(1:6)
176 TYPE(ace_data_type), POINTER :: ace_data
177
178 CALL timeset(routinen, handle)
179
180 ! get ace_data to save force, virial info
181 CALL fist_nonbond_env_get(fist_nonbond_env, ace_data=ace_data)
182 IF (.NOT. ASSOCIATED(ace_data)) THEN
183 ALLOCATE (ace_data)
184 !initialize ace_data:
185 CALL init_ace_data(particle_set, atomic_kind_set, potparm, ace_data)
186 CALL fist_nonbond_env_set(fist_nonbond_env, ace_data=ace_data)
187 END IF
188
189 CALL ace_interface(ace_data%natom, ace_data%uctype, &
190 pot_ace, ace_data%force, ace_virial, &
191 fist_nonbond_env, cell, ace_data)
192
193 ! convert units
194 pot_ace = pot_ace/evolt
195 ace_data%force = ace_data%force/(evolt/angstrom)
196 ace_virial = ace_virial/evolt
197
198 ! minus sign due to CP2K conventions
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)
208
209 CALL timestop(handle)
210 END SUBROUTINE ace_energy_store_force_virial
211
212! **************************************************************************************************
213!> \brief ...
214!> \param fist_nonbond_env ...
215!> \param force ...
216!> \param pv_nonbond ...
217!> \param use_virial ...
218! **************************************************************************************************
219 SUBROUTINE ace_add_force_virial(fist_nonbond_env, force, pv_nonbond, use_virial)
220 TYPE(fist_nonbond_env_type), POINTER :: fist_nonbond_env
221 REAL(kind=dp), INTENT(INOUT) :: force(:, :), pv_nonbond(3, 3)
222 LOGICAL, OPTIONAL :: use_virial
223
224 CHARACTER(LEN=*), PARAMETER :: routinen = 'ace_add_force_virial'
225
226 INTEGER :: handle, iat, iat_use
227 TYPE(ace_data_type), POINTER :: ace_data
228
229 CALL timeset(routinen, handle)
230
231 CALL fist_nonbond_env_get(fist_nonbond_env, ace_data=ace_data)
232
233 IF (.NOT. ASSOCIATED(ace_data)) RETURN
234
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)
239 END DO
240
241 IF (use_virial) THEN
242 pv_nonbond = pv_nonbond + ace_data%virial
243 END IF
244
245 CALL timestop(handle)
246 END SUBROUTINE ace_add_force_virial
247
248END MODULE manybody_ace
subroutine, public ace_interface(ace_natom, ace_atype, pot_ace, ace_force, ace_virial, fist_nonbond_env, cell, ace_data)
...
Definition ace_nlist.F:53
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.
Definition cell_types.F:15
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.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
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:
Definition physcon.F:68
real(kind=dp), parameter, public evolt
Definition physcon.F:183
real(kind=dp), parameter, public angstrom
Definition physcon.F:144
Provides all information about an atomic kind.
Type defining parameters related to the simulation cell.
Definition cell_types.F:55