45#include "../base/base_uses.f90"
50 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
51 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'gopt_f_types'
61 INTEGER :: ref_count = 0
64 LOGICAL :: dimer_rotation = .false., do_line_search = .false., eval_opt_geo = .false.
65 CHARACTER(LEN=default_string_length) :: label =
"", tag =
""
75 REAL(kind=
dp),
DIMENSION(3, 3) :: h_ref = 0.0_dp
76 LOGICAL :: require_consistent_energy_force = .false.
93 RECURSIVE SUBROUTINE gopt_f_create(gopt_env, gopt_param, force_env, globenv, geo_opt_section, &
101 LOGICAL,
INTENT(IN),
OPTIONAL :: eval_opt_geo
103 INTEGER :: natom, nshell
108 cpassert(.NOT.
ASSOCIATED(gopt_env))
112 NULLIFY (gopt_env%dimer_env, gopt_env%gopt_dimer_env, gopt_env%gopt_dimer_param, gopt_env%cell_env, gopt_env%spgr)
113 gopt_env%ref_count = 1
114 gopt_env%dimer_rotation = .false.
115 gopt_env%do_line_search = .false.
116 ALLOCATE (gopt_env%spgr)
118 gopt_env%force_env => force_env
120 gopt_env%geo_section => geo_opt_section
121 gopt_env%globenv => globenv
122 gopt_env%eval_opt_geo = .true.
123 IF (
PRESENT(eval_opt_geo)) gopt_env%eval_opt_geo = eval_opt_geo
124 gopt_env%require_consistent_energy_force = .true.
127 gopt_env%type_id = gopt_param%type_id
128 SELECT CASE (gopt_env%type_id)
131 particles=particles, &
132 shell_particles=shell_particles)
133 IF (
ASSOCIATED(shell_particles)) nshell = shell_particles%n_els
135 gopt_env%nfree = particles%n_els + nshell
136 gopt_env%label =
"GEO_OPT"
137 gopt_env%tag =
"GEOMETRY"
138 SELECT CASE (gopt_param%type_id)
140 gopt_env%ts_method_id = gopt_param%ts_method_id
141 SELECT CASE (gopt_param%ts_method_id)
151 ALLOCATE (gopt_env%gopt_dimer_param)
156 CALL gopt_f_create(gopt_env%gopt_dimer_env, gopt_env%gopt_dimer_param, force_env=force_env, &
157 globenv=globenv, geo_opt_section=rot_opt_section, eval_opt_geo=eval_opt_geo)
159 gopt_env%gopt_dimer_env%dimer_env => gopt_env%dimer_env
160 gopt_env%gopt_dimer_env%label =
"ROT_OPT"
161 gopt_env%gopt_dimer_env%dimer_rotation = .true.
166 gopt_env%label =
"CELL_OPT"
167 gopt_env%tag =
" CELL "
168 gopt_env%cell_method_id = gopt_param%cell_method_id
169 ALLOCATE (gopt_env%cell_env)
172 gopt_env%nfree = subsys%shell_particles%n_els
173 gopt_env%label =
"SHELL_OPT"
174 gopt_env%tag =
" SHELL-CORE "
175 gopt_env%shellcore_method_id = gopt_param%shellcore_method_id
188 cpassert(
ASSOCIATED(gopt_env))
189 cpassert(gopt_env%ref_count > 0)
190 gopt_env%ref_count = gopt_env%ref_count + 1
202 IF (
ASSOCIATED(gopt_env))
THEN
203 cpassert(gopt_env%ref_count > 0)
204 gopt_env%ref_count = gopt_env%ref_count - 1
205 IF (gopt_env%ref_count == 0)
THEN
207 NULLIFY (gopt_env%force_env, &
209 gopt_env%motion_section, &
210 gopt_env%geo_section)
211 IF (
ASSOCIATED(gopt_env%cell_env))
THEN
213 DEALLOCATE (gopt_env%cell_env)
217 IF (
ASSOCIATED(gopt_env%gopt_dimer_param))
DEALLOCATE (gopt_env%gopt_dimer_param)
219 DEALLOCATE (gopt_env)
Contains type used for a Simulation Cell Optimization.
subroutine, public cell_opt_env_release(cell_env)
...
subroutine, public cell_opt_env_create(cell_env, force_env, geo_section)
...
types that represent a subsys, i.e. a part of the system
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
Contains types used for a Dimer Method calculations.
subroutine, public dimer_env_retain(dimer_env)
...
subroutine, public dimer_env_release(dimer_env)
...
subroutine, public dimer_env_create(dimer_env, subsys, globenv, dimer_section)
...
Interface for the force calculations.
integer function, public force_env_get_natom(force_env)
returns the number of atoms
recursive subroutine, public force_env_get(force_env, in_use, fist_env, qs_env, meta_env, fp_env, subsys, para_env, potential_energy, additional_potential, kinetic_energy, harmonic_shell, kinetic_shell, cell, sub_force_env, qmmm_env, qmmmx_env, eip_env, pwdft_env, globenv, input, force_env_section, method_name_id, root_section, mixed_env, nnp_env, embed_env, ipi_env)
returns various attributes about the force environment
subroutine, public force_env_retain(force_env)
retains the given force env
recursive subroutine, public force_env_release(force_env)
releases the given force env
Define type storing the global information of a run. Keep the amount of stored data small....
contains a functional that calculates the energy and its derivatives for the geometry optimizer
recursive subroutine, public gopt_f_create(gopt_env, gopt_param, force_env, globenv, geo_opt_section, eval_opt_geo)
...
subroutine, public gopt_f_retain(gopt_env)
...
recursive subroutine, public gopt_f_release(gopt_env)
...
contains typo and related routines to handle parameters controlling the GEO_OPT module
subroutine, public gopt_param_read(gopt_param, gopt_section, type_id)
reads the parameters of the geopmetry optimizer
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_string_length
represent a simple array based list of the given type
Space Group Symmetry Type Module (version 1.0, Ferbruary 12, 2021)
subroutine, public release_spgr_type(spgr)
Release the SPGR type.
Type containing all informations abour the simulation cell optimization.
represents a system: atoms, molecules, their pos,vel,...
Defines the environment for a Dimer Method calculation.
wrapper to abstract the force evaluation of the various methods
contains the initially parsed file and the initial parallel environment
calculates the potential energy of a system, and its derivatives
represent a list of objects