61#include "./base/base_uses.f90"
73 LOGICAL :: qmmm = .false.
74 LOGICAL :: shell_model = .false., shell_model_ad = .false.
97 CHARACTER(len=*),
PARAMETER,
PRIVATE :: modulen =
'fist_environment_types'
135 SUBROUTINE fist_env_get(fist_env, atomic_kind_set, particle_set, ewald_pw, &
136 local_particles, local_molecules, molecule_kind_set, molecule_set, cell, &
137 cell_ref, ewald_env, fist_nonbond_env, thermo, para_env, subsys, qmmm, &
138 qmmm_env, input, shell_model, shell_model_ad, shell_particle_set, &
139 core_particle_set, multipoles, results, exclusions, efield)
148 TYPE(
cell_type),
OPTIONAL,
POINTER :: cell, cell_ref
154 LOGICAL,
OPTIONAL :: qmmm
157 LOGICAL,
OPTIONAL :: shell_model, shell_model_ad
158 TYPE(
particle_type),
OPTIONAL,
POINTER :: shell_particle_set(:), &
163 POINTER :: exclusions
173 NULLIFY (atomic_kinds, particles, molecules, molecule_kinds, fist_multipoles)
175 IF (
PRESENT(input)) input => fist_env%input
176 IF (
PRESENT(qmmm)) qmmm = fist_env%qmmm
177 IF (
PRESENT(qmmm_env)) qmmm_env => fist_env%qmmm_env
178 IF (
PRESENT(cell_ref)) cell_ref => fist_env%cell_ref
179 IF (
PRESENT(ewald_env)) ewald_env => fist_env%ewald_env
180 IF (
PRESENT(thermo)) thermo => fist_env%thermo
181 IF (
PRESENT(exclusions)) exclusions => fist_env%exclusions
182 IF (
PRESENT(para_env)) para_env => fist_env%para_env
183 IF (
PRESENT(ewald_pw)) ewald_pw => fist_env%ewald_pw
184 IF (
PRESENT(fist_nonbond_env)) fist_nonbond_env => fist_env%fist_nonbond_env
185 IF (
PRESENT(shell_model)) shell_model = fist_env%shell_model
186 IF (
PRESENT(shell_model_ad)) shell_model_ad = fist_env%shell_model_ad
187 IF (
PRESENT(subsys)) subsys => fist_env%subsys
188 IF (
PRESENT(efield)) efield => fist_env%efield
190 IF (
ASSOCIATED(fist_env%subsys)) &
192 atomic_kinds=atomic_kinds, &
193 local_molecules=local_molecules, &
194 local_particles=local_particles, &
195 particles=particles, &
196 molecule_kinds=molecule_kinds, &
197 molecules=molecules, &
198 shell_particles=shell_particles, &
199 core_particles=core_particles, &
200 multipoles=fist_multipoles, &
203 IF (
PRESENT(atomic_kind_set)) atomic_kind_set => atomic_kinds%els
204 IF (
PRESENT(particle_set)) particle_set => particles%els
205 IF (
PRESENT(molecule_kind_set)) molecule_kind_set => molecule_kinds%els
206 IF (
PRESENT(molecule_set)) molecule_set => molecules%els
207 IF (
PRESENT(shell_particle_set)) shell_particle_set => shell_particles%els
208 IF (
PRESENT(core_particle_set)) core_particle_set => core_particles%els
209 IF (
PRESENT(multipoles)) multipoles => fist_multipoles
220 SUBROUTINE init_fist_env(fist_env, para_env)
225 NULLIFY (fist_env%input)
226 NULLIFY (fist_env%qmmm_env)
227 NULLIFY (fist_env%cell_ref)
228 NULLIFY (fist_env%ewald_env)
229 NULLIFY (fist_env%ewald_pw)
230 NULLIFY (fist_env%thermo)
231 NULLIFY (fist_env%fist_nonbond_env)
232 NULLIFY (fist_env%subsys)
233 NULLIFY (fist_env%exclusions)
234 NULLIFY (fist_env%efield)
235 fist_env%qmmm = .false.
236 fist_env%shell_model = .false.
237 fist_env%shell_model_ad = .false.
238 ALLOCATE (fist_env%qmmm_env)
240 NULLIFY (fist_env%subsys)
241 CALL para_env%retain()
242 fist_env%para_env => para_env
244 END SUBROUTINE init_fist_env
272 SUBROUTINE fist_env_set(fist_env, atomic_kind_set, particle_set, ewald_pw, &
273 local_particles, local_molecules, molecule_kind_set, &
274 molecule_set, cell_ref, ewald_env, &
275 fist_nonbond_env, thermo, subsys, qmmm, qmmm_env, &
276 input, shell_model, shell_model_ad, exclusions, efield)
285 TYPE(
cell_type),
OPTIONAL,
POINTER :: cell_ref
290 LOGICAL,
OPTIONAL :: qmmm
293 LOGICAL,
OPTIONAL :: shell_model, shell_model_ad
295 POINTER :: exclusions
303 IF (
PRESENT(qmmm)) fist_env%qmmm = qmmm
304 IF (
PRESENT(qmmm_env))
THEN
305 IF (
ASSOCIATED(fist_env%qmmm_env))
THEN
307 DEALLOCATE (fist_env%qmmm_env)
309 fist_env%qmmm_env => qmmm_env
311 IF (
PRESENT(ewald_env))
THEN
312 IF (
ASSOCIATED(fist_env%ewald_env))
THEN
313 IF (.NOT.
ASSOCIATED(fist_env%ewald_env, ewald_env))
THEN
315 DEALLOCATE (fist_env%ewald_env)
318 fist_env%ewald_env => ewald_env
320 IF (
PRESENT(ewald_pw))
THEN
321 IF (
ASSOCIATED(fist_env%ewald_pw))
THEN
322 IF (.NOT.
ASSOCIATED(fist_env%ewald_pw, ewald_pw))
THEN
324 DEALLOCATE (fist_env%ewald_pw)
327 fist_env%ewald_pw => ewald_pw
329 IF (
PRESENT(cell_ref))
THEN
332 fist_env%cell_ref => cell_ref
334 IF (
PRESENT(fist_nonbond_env))
THEN
335 IF (
ASSOCIATED(fist_env%fist_nonbond_env))
THEN
336 IF (.NOT.
ASSOCIATED(fist_env%fist_nonbond_env, fist_nonbond_env))
THEN
338 DEALLOCATE (fist_env%fist_nonbond_env)
341 fist_env%fist_nonbond_env => fist_nonbond_env
343 IF (
PRESENT(input))
THEN
346 fist_env%input => input
348 IF (
PRESENT(thermo)) fist_env%thermo => thermo
349 IF (
PRESENT(subsys))
THEN
350 IF (
ASSOCIATED(fist_env%subsys))
THEN
351 IF (.NOT.
ASSOCIATED(fist_env%subsys, subsys))
THEN
355 fist_env%subsys => subsys
357 IF (
PRESENT(atomic_kind_set))
THEN
359 els_ptr=atomic_kind_set)
361 atomic_kinds=atomic_kinds)
364 IF (
PRESENT(particle_set))
THEN
366 els_ptr=particle_set)
371 IF (
PRESENT(local_particles))
THEN
373 local_particles=local_particles)
375 IF (
PRESENT(local_molecules))
THEN
377 local_molecules=local_molecules)
379 IF (
PRESENT(molecule_kind_set))
THEN
381 els_ptr=molecule_kind_set)
383 molecule_kinds=molecule_kinds)
386 IF (
PRESENT(molecule_set))
THEN
388 els_ptr=molecule_set)
393 IF (
PRESENT(exclusions)) fist_env%exclusions => exclusions
394 IF (
PRESENT(shell_model))
THEN
395 fist_env%shell_model = shell_model
397 IF (
PRESENT(shell_model_ad))
THEN
398 fist_env%shell_model_ad = shell_model_ad
400 IF (
PRESENT(efield)) fist_env%efield => efield
416 CALL init_fist_env(fist_env, para_env=para_env)
429 IF (
ASSOCIATED(fist_env%qmmm_env))
THEN
431 DEALLOCATE (fist_env%qmmm_env)
434 IF (
ASSOCIATED(fist_env%ewald_pw))
THEN
436 DEALLOCATE (fist_env%ewald_pw)
438 IF (
ASSOCIATED(fist_env%ewald_env))
THEN
440 DEALLOCATE (fist_env%ewald_env)
445 IF (
ASSOCIATED(fist_env%fist_nonbond_env))
THEN
447 DEALLOCATE (fist_env%fist_nonbond_env)
453 IF (
ASSOCIATED(fist_env%efield))
THEN
454 DEALLOCATE (fist_env%efield)
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)
set of type/routines to handle the storage of results in force_envs
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...
subroutine, public ewald_env_release(ewald_env)
releases the given ewald_env (see doc/ReferenceCounting.html)
subroutine, public ewald_pw_release(ewald_pw)
releases the memory used by the ewald_pw
subroutine, public exclusion_release(exclusions)
Release exclusion type.
subroutine, public deallocate_fist_energy(fist_energy)
Deallocate a Fist energy data structure.
subroutine, public fist_env_release(fist_env)
releases the given fist_env (see doc/ReferenceCounting.html)
subroutine, public fist_env_get(fist_env, atomic_kind_set, particle_set, ewald_pw, local_particles, local_molecules, molecule_kind_set, molecule_set, cell, cell_ref, ewald_env, fist_nonbond_env, thermo, para_env, subsys, qmmm, qmmm_env, input, shell_model, shell_model_ad, shell_particle_set, core_particle_set, multipoles, results, exclusions, efield)
Purpose: Get the FIST environment.
subroutine, public fist_env_create(fist_env, para_env)
allocates and intitializes a fist_env
subroutine, public fist_env_set(fist_env, atomic_kind_set, particle_set, ewald_pw, local_particles, local_molecules, molecule_kind_set, molecule_set, cell_ref, ewald_env, fist_nonbond_env, thermo, subsys, qmmm, qmmm_env, input, shell_model, shell_model_ad, exclusions, efield)
Set the FIST environment.
subroutine, public fist_nonbond_env_release(fist_nonbond_env)
releases the given fist_nonbond_env (see doc/ReferenceCounting.html)
Interface to the message passing library MPI.
subroutine, public mp_para_env_release(para_env)
releases the para object (to be called when you don't want anymore the shared copy of this object)
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.
Multipole structure: for multipole (fixed and induced) in FF based MD.
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.
subroutine, public qmmm_env_mm_create(qmmm_env)
...
subroutine, public qmmm_env_mm_release(qmmm_env)
releases the given qmmm_env (see doc/ReferenceCounting.html)
represent a list of objects
Provides all information about an atomic kind.
Type defining parameters related to the simulation cell.
contains arbitrary information which need to be stored
represents a system: atoms, molecules, their pos,vel,...
structure to store local (to a processor) ordered lists of integers.
to build arrays of pointers
A type used to store lists of exclusions and onfos.
stores all the informations relevant to an mpi environment
represent a list of objects
represent a list of objects
represent a list of objects