44#include "./base/base_uses.f90"
49 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'ipi_environment_types'
72 REAL(kind=
dp) :: ipi_energy = 0.0_dp
73 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: ipi_forces => null()
77 INTEGER :: sockfd = -1
92 IF (
ASSOCIATED(ipi_env%ipi_forces))
THEN
93 DEALLOCATE (ipi_env%ipi_forces)
95 IF (
ASSOCIATED(ipi_env%subsys))
THEN
98 IF (
ASSOCIATED(ipi_env%force_env_input))
THEN
101 IF (
ASSOCIATED(ipi_env%cell_ref))
THEN
128 atomic_kind_set, particle_set, local_particles, &
129 molecule_kind_set, molecule_set, local_molecules, &
130 force_env_input, cell, cell_ref, virial, sockfd)
133 REAL(kind=
dp),
OPTIONAL :: ipi_energy
134 REAL(kind=
dp),
DIMENSION(:, :),
OPTIONAL,
POINTER :: ipi_forces
137 POINTER :: atomic_kind_set
139 POINTER :: particle_set
142 POINTER :: molecule_kind_set
144 POINTER :: molecule_set
147 TYPE(
cell_type),
OPTIONAL,
POINTER :: cell, cell_ref
149 INTEGER,
OPTIONAL :: sockfd
156 NULLIFY (atomic_kinds, particles, molecules, molecule_kinds)
158 IF (
PRESENT(ipi_energy)) ipi_energy = ipi_env%ipi_energy
159 IF (
PRESENT(ipi_forces)) ipi_forces = ipi_env%ipi_forces
160 IF (
PRESENT(subsys)) subsys => ipi_env%subsys
162 atomic_kinds=atomic_kinds, &
163 particles=particles, &
164 molecule_kinds=molecule_kinds, &
165 molecules=molecules, &
166 local_molecules=local_molecules, &
167 local_particles=local_particles, &
170 IF (
PRESENT(atomic_kind_set)) atomic_kind_set => atomic_kinds%els
171 IF (
PRESENT(particle_set)) particle_set => particles%els
172 IF (
PRESENT(molecule_kind_set)) molecule_kind_set => molecule_kinds%els
173 IF (
PRESENT(molecule_set)) molecule_set => molecules%els
175 IF (
PRESENT(force_env_input)) force_env_input => ipi_env%force_env_input
176 IF (
PRESENT(cell_ref)) cell_ref => ipi_env%cell_ref
177 IF (
PRESENT(sockfd)) sockfd = ipi_env%sockfd
201 atomic_kind_set, particle_set, local_particles, &
202 molecule_kind_set, molecule_set, local_molecules, &
203 force_env_input, cell_ref, sockfd)
206 REAL(kind=
dp),
OPTIONAL :: ipi_energy
207 REAL(kind=
dp),
DIMENSION(:, :),
OPTIONAL,
POINTER :: ipi_forces
210 POINTER :: atomic_kind_set
212 POINTER :: particle_set
215 POINTER :: molecule_kind_set
217 POINTER :: molecule_set
220 TYPE(
cell_type),
OPTIONAL,
POINTER :: cell_ref
221 INTEGER,
OPTIONAL :: sockfd
228 IF (
PRESENT(ipi_energy)) ipi_env%ipi_energy = ipi_energy
229 IF (
PRESENT(ipi_forces)) ipi_env%ipi_forces = ipi_forces
230 IF (
PRESENT(subsys))
THEN
231 IF (
ASSOCIATED(ipi_env%subsys))
THEN
232 IF (.NOT.
ASSOCIATED(ipi_env%subsys, subsys))
THEN
236 ipi_env%subsys => subsys
238 IF (
PRESENT(atomic_kind_set))
THEN
240 CALL cp_subsys_set(ipi_env%subsys, atomic_kinds=atomic_kinds)
243 IF (
PRESENT(particle_set))
THEN
248 IF (
PRESENT(molecule_kind_set))
THEN
250 CALL cp_subsys_set(ipi_env%subsys, molecule_kinds=molecule_kinds)
253 IF (
PRESENT(molecule_set))
THEN
258 IF (
PRESENT(local_particles))
THEN
259 CALL cp_subsys_set(ipi_env%subsys, local_particles=local_particles)
261 IF (
PRESENT(local_molecules))
THEN
262 CALL cp_subsys_set(ipi_env%subsys, local_molecules=local_molecules)
265 IF (
PRESENT(force_env_input))
THEN
268 ipi_env%force_env_input => force_env_input
270 IF (
PRESENT(cell_ref))
THEN
273 ipi_env%cell_ref => cell_ref
275 IF (
PRESENT(sockfd)) ipi_env%sockfd = sockfd
285 SUBROUTINE ipi_env_clear(ipi_env)
289 IF (
ASSOCIATED(ipi_env%ipi_forces))
THEN
290 ipi_env%ipi_forces(:, :) = 0.0_dp
292 IF (
ASSOCIATED(ipi_env%subsys))
THEN
295 IF (
ASSOCIATED(ipi_env%force_env_input))
THEN
298 IF (
ASSOCIATED(ipi_env%cell_ref))
THEN
301 END SUBROUTINE ipi_env_clear
314 NULLIFY (ipi_env%ipi_forces)
315 NULLIFY (ipi_env%subsys)
316 NULLIFY (ipi_env%force_env_input)
317 NULLIFY (ipi_env%cell_ref)
319 ipi_env%ipi_energy = 0_dp
321 CALL ipi_env_clear(ipi_env)
represent a simple array based list of the given type
subroutine, public atomic_kind_list_release(list)
releases a list (see doc/ReferenceCounting.html)
subroutine, public atomic_kind_list_create(list, els_ptr, owns_els, n_els)
creates a list
Define the atomic kind types and their sub types.
Handles all functions related to the CELL.
subroutine, public cell_release(cell)
releases the given cell (see doc/ReferenceCounting.html)
subroutine, public cell_retain(cell)
retains the given cell (see doc/ReferenceCounting.html)
types that represent a subsys, i.e. a part of the system
subroutine, public cp_subsys_release(subsys)
releases a subsys (see doc/ReferenceCounting.html)
subroutine, public cp_subsys_set(subsys, atomic_kinds, particles, local_particles, molecules, molecule_kinds, local_molecules, para_env, colvar_p, shell_particles, core_particles, gci, multipoles, results, cell)
sets various propreties of the subsys
subroutine, public cp_subsys_get(subsys, ref_count, atomic_kinds, atomic_kind_set, particles, particle_set, local_particles, molecules, molecule_set, molecule_kinds, molecule_kind_set, local_molecules, para_env, colvar_p, shell_particles, core_particles, gci, multipoles, natom, nparticle, ncore, nshell, nkind, atprop, virial, results, cell)
returns information about various attributes of the given subsys
stores a lists of integer that are local to a processor. The idea is that these integers represent ob...
The environment for the empirical interatomic potential methods.
subroutine, public ipi_env_get(ipi_env, ipi_energy, ipi_forces, subsys, atomic_kind_set, particle_set, local_particles, molecule_kind_set, molecule_set, local_molecules, force_env_input, cell, cell_ref, virial, sockfd)
Returns various attributes of the ipi environment.
subroutine, public ipi_env_set(ipi_env, ipi_energy, ipi_forces, subsys, atomic_kind_set, particle_set, local_particles, molecule_kind_set, molecule_set, local_molecules, force_env_input, cell_ref, sockfd)
Sets various attributes of the ipi environment.
subroutine, public ipi_env_release(ipi_env)
Releases the given ipi environment (see doc/ReferenceCounting.html)
subroutine, public ipi_env_create(ipi_env)
Creates the ipi environment.
Defines the basic variable types.
integer, parameter, public dp
represent a simple array based list of the given type
subroutine, public molecule_kind_list_create(list, els_ptr, owns_els, n_els)
creates a list
subroutine, public molecule_kind_list_release(list)
releases a list (see doc/ReferenceCounting.html)
Define the molecule kind structure types and the corresponding functionality.
represent a simple array based list of the given type
subroutine, public molecule_list_create(list, els_ptr, owns_els, n_els)
creates a list
subroutine, public molecule_list_release(list)
releases a list (see doc/ReferenceCounting.html)
Define the data structure for the molecule information.
represent a simple array based list of the given type
subroutine, public particle_list_create(list, els_ptr, owns_els, n_els)
creates a list
subroutine, public particle_list_release(list)
releases a list (see doc/ReferenceCounting.html)
Define the data structure for the particle information.
represent a list of objects
Provides all information about an atomic kind.
Type defining parameters related to the simulation cell.
represents a system: atoms, molecules, their pos,vel,...
structure to store local (to a processor) ordered lists of integers.
represent a list of objects
represent a list of objects
represent a list of objects