51#include "./base/base_uses.f90"
59 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'pwdft_environment'
79 SUBROUTINE pwdft_init(pwdft_env, root_section, para_env, force_env_section, subsys_section, &
85 LOGICAL,
INTENT(IN) :: use_motion_section
87 CHARACTER(len=*),
PARAMETER :: routinen =
'pwdft_init'
89 INTEGER :: handle, iw, natom
90 LOGICAL :: use_ref_cell
92 TYPE(
cell_type),
POINTER :: my_cell, my_cell_ref
103 CALL timeset(routinen, handle)
105 cpassert(
ASSOCIATED(pwdft_env))
106 cpassert(
ASSOCIATED(force_env_section))
108 IF (.NOT.
ASSOCIATED(subsys_section))
THEN
116 CALL pwdft_env_set(pwdft_env=pwdft_env, pwdft_input=pwdft_section, &
117 force_env_input=force_env_section, xc_input=xc_section)
125 force_env_section=force_env_section, &
126 subsys_section=subsys_section, &
127 use_motion_section=use_motion_section, &
128 root_section=root_section)
131 NULLIFY (local_molecules)
132 NULLIFY (local_particles)
134 atomic_kind_set=atomic_kind_set, &
135 molecule_set=molecule_set, &
136 molecule_kind_set=molecule_kind_set)
139 particle_set=particle_set, &
140 local_particles=local_particles, &
141 molecule_kind_set=molecule_kind_set, &
142 molecule_set=molecule_set, &
143 local_molecules=local_molecules, &
144 force_env_section=force_env_section)
146 CALL qs_subsys_set(qs_subsys, local_molecules=local_molecules, &
147 local_particles=local_particles)
153 CALL qs_subsys_get(qs_subsys, cell=my_cell, cell_ref=my_cell_ref, use_ref_cell=use_ref_cell)
165 qs_kind_set=qs_kind_set, &
166 atomic_kind_set=atomic_kind_set, &
167 molecule_set=molecule_set, &
168 molecule_kind_set=molecule_kind_set)
172 ALLOCATE (pwdft_env%energy)
173 ALLOCATE (pwdft_env%forces(natom, 3))
174 pwdft_env%forces(1:natom, 1:3) = 0.0_dp
175 pwdft_env%stress(1:3, 1:3) = 0.0_dp
192 WRITE (iw,
'(A)')
"SIRIUS| INIT: FINISHED"
196 CALL timestop(handle)
211 LOGICAL,
INTENT(IN) :: calculate_forces, calculate_stress
213 CHARACTER(len=*),
PARAMETER :: routinen =
'pwdft_calc_energy_force'
215 INTEGER :: handle, iatom, iw, natom
216 REAL(kind=
dp),
DIMENSION(1:3, 1:3) :: stress
217 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: force
224 CALL timeset(routinen, handle)
226 cpassert(
ASSOCIATED(pwdft_env))
236 WRITE (iw,
'(A)')
"SIRIUS| UPDATE CONTEXT : FINISHED"
243 IF (calculate_forces)
THEN
246 CALL qs_subsys_get(qs_subsys, particle_set=particle_set, natom=natom)
248 particle_set(iatom)%f(1:3) = -force(iatom, 1:3)
252 IF (calculate_stress)
THEN
256 virial%pv_virial(1:3, 1:3) = -stress(1:3, 1:3)*my_cell%deth
259 CALL timestop(handle)
Define the atomic kind types and their sub types.
Handles all functions related to the CELL.
various routines to log and control the output. The idea is that decisions about where to log should ...
integer function, public cp_logger_get_default_io_unit(logger)
returns the unit nr for the ionode (-1 on all other processors) skips as well checks if the procs cal...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
subroutine, public write_symmetry(particle_set, cell, input_section)
Write symmetry information to output.
stores a lists of integer that are local to a processor. The idea is that these integers represent ob...
subroutine, public distribution_1d_release(distribution_1d)
releases the given distribution_1d
Distribution methods for atoms, particles, or molecules.
subroutine, public distribute_molecules_1d(atomic_kind_set, particle_set, local_particles, molecule_kind_set, molecule_set, local_molecules, force_env_section, prev_molecule_kind_set, prev_local_molecules)
Distribute molecules and particles.
Defines the basic variable types.
integer, parameter, public dp
Machine interface based on Fortran 2003 and POSIX.
subroutine, public m_flush(lunit)
flushes units if the &GLOBAL flag is set accordingly
Interface to the message passing library MPI.
Define the molecule kind structure types and the corresponding functionality.
Define the data structure for the molecule information.
Define methods related to particle_type.
subroutine, public write_qs_particle_coordinates(particle_set, qs_kind_set, subsys_section, label)
Write the atomic coordinates to the output unit.
subroutine, public write_structure_data(particle_set, cell, input_section)
Write structure data requested by a separate structure data input section to the output unit....
subroutine, public write_particle_distances(particle_set, cell, subsys_section)
Write the matrix of the particle distances to the output unit.
Define the data structure for the particle information.
The type definitions for the PWDFT environment.
subroutine, public pwdft_env_get(pwdft_env, pwdft_input, force_env_input, xc_input, cp_subsys, qs_subsys, para_env, energy, forces, stress, sctx, gs_handler, ks_handler)
Returns various attributes of the pwdft environment.
subroutine, public pwdft_env_set(pwdft_env, pwdft_input, force_env_input, xc_input, qs_subsys, cp_subsys, para_env, energy, forces, stress, sctx, gs_handler, ks_handler)
Sets various attributes of the pwdft environment.
Methods and functions on the PWDFT environment.
subroutine, public pwdft_calc_energy_force(pwdft_env, calculate_forces, calculate_stress)
Calculate energy and forces within the PWDFT/SIRIUS code.
subroutine, public pwdft_init(pwdft_env, root_section, para_env, force_env_section, subsys_section, use_motion_section)
Initialize the pwdft environment.
subroutine, public allocate_qs_energy(qs_energy)
Allocate and/or initialise a Quickstep energy data structure.
Define the quickstep kind type and their sub types.
subroutine, public write_qs_kind_set(qs_kind_set, subsys_section)
Write an atomic kind set data set to the output unit.
Routines that work on qs_subsys_type.
subroutine, public qs_subsys_create(subsys, para_env, root_section, force_env_section, subsys_section, use_motion_section, cp_subsys, cell, cell_ref, elkind, silent)
Creates a qs_subsys. Optionally an existsing cp_subsys is used.
types that represent a quickstep subsys
subroutine, public qs_subsys_get(subsys, 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, cell_ref, use_ref_cell, energy, force, qs_kind_set, cp_subsys, nelectron_total, nelectron_spin)
...
subroutine, public qs_subsys_set(subsys, cp_subsys, local_particles, local_molecules, cell, cell_ref, use_ref_cell, energy, force, qs_kind_set, nelectron_total, nelectron_spin)
...
Interface to the SIRIUS Library.
subroutine, public cp_sirius_update_context(pwdft_env)
Empty implementation in case SIRIUS is not compiled in.
subroutine, public cp_sirius_energy_force(pwdft_env, calculate_forces, calculate_stress)
Empty implementation in case SIRIUS is not compiled in.
subroutine, public cp_sirius_create_env(pwdft_env)
Empty implementation in case SIRIUS is not compiled in.
Provides all information about an atomic kind.
Type defining parameters related to the simulation cell.
type of a logger, at the moment it contains just a print level starting at which level it should be l...
structure to store local (to a processor) ordered lists of integers.
stores all the informations relevant to an mpi environment
The PWDFT environment type.
Provides all information about a quickstep kind.