(git:ccc2433)
eip_environment.F
Go to the documentation of this file.
1 !--------------------------------------------------------------------------------------------------!
2 ! CP2K: A general program to perform molecular dynamics simulations !
3 ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 ! !
5 ! SPDX-License-Identifier: GPL-2.0-or-later !
6 !--------------------------------------------------------------------------------------------------!
7 
8 ! **************************************************************************************************
9 !> \brief Methods and functions on the EIP environment
10 !> \par History
11 !> 03.2006 initial create [tdk]
12 !> \author Thomas D. Kuehne (tkuehne@phys.chem.ethz.ch)
13 ! **************************************************************************************************
15  USE atomic_kind_types, ONLY: atomic_kind_type,&
17  USE cell_methods, ONLY: read_cell,&
19  USE cell_types, ONLY: cell_release,&
20  cell_type,&
21  get_cell
23  USE cp_subsys_types, ONLY: cp_subsys_set,&
24  cp_subsys_type
26  distribution_1d_type
29  eip_environment_type
31  section_vals_type,&
33  USE kinds, ONLY: default_string_length,&
34  dp
35  USE message_passing, ONLY: mp_para_env_type
36  USE molecule_kind_types, ONLY: molecule_kind_type,&
38  USE molecule_types, ONLY: molecule_type
42  USE particle_types, ONLY: particle_type
43 #include "./base/base_uses.f90"
44 
45  IMPLICIT NONE
46 
47  PRIVATE
48 
49 ! *** Global parameters ***
50 
51  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'eip_environment'
52 
53 ! *** Public subroutines ***
54 
55  PUBLIC :: eip_init
56 
57 CONTAINS
58 
59 ! **************************************************************************************************
60 !> \brief Initialize the eip environment
61 !> \param eip_env The eip environment to retain
62 !> \param root_section ...
63 !> \param para_env ...
64 !> \param force_env_section ...
65 !> \param subsys_section ...
66 !> \par History
67 !> 03.2006 initial create [tdk]
68 !> \author Thomas D. Kuehne (tkuehne@phys.chem.ethz.ch)
69 ! **************************************************************************************************
70  SUBROUTINE eip_init(eip_env, root_section, para_env, force_env_section, &
71  subsys_section)
72  TYPE(eip_environment_type), POINTER :: eip_env
73  TYPE(section_vals_type), POINTER :: root_section
74  TYPE(mp_para_env_type), POINTER :: para_env
75  TYPE(section_vals_type), POINTER :: force_env_section, subsys_section
76 
77  CHARACTER(len=*), PARAMETER :: routinen = 'eip_init'
78 
79  INTEGER :: handle
80  LOGICAL :: use_ref_cell
81  REAL(kind=dp), DIMENSION(3) :: abc
82  TYPE(cell_type), POINTER :: cell, cell_ref
83  TYPE(cp_subsys_type), POINTER :: subsys
84  TYPE(section_vals_type), POINTER :: cell_section, colvar_section, eip_section
85 
86  CALL timeset(routinen, handle)
87 
88  cpassert(ASSOCIATED(eip_env))
89 
90  ! nullifying pointers
91  NULLIFY (cell_section, colvar_section, eip_section, cell, cell_ref, &
92  subsys)
93 
94  IF (.NOT. ASSOCIATED(subsys_section)) THEN
95  subsys_section => section_vals_get_subs_vals(force_env_section, "SUBSYS")
96  END IF
97  cell_section => section_vals_get_subs_vals(subsys_section, "CELL")
98  colvar_section => section_vals_get_subs_vals(subsys_section, "COLVAR")
99  eip_section => section_vals_get_subs_vals(force_env_section, "EIP")
100 
101  CALL eip_env_set(eip_env=eip_env, eip_input=eip_section, &
102  force_env_input=force_env_section)
103 
104  CALL read_cell(cell=cell, cell_ref=cell_ref, use_ref_cell=use_ref_cell, cell_section=cell_section, &
105  para_env=para_env)
106  CALL get_cell(cell=cell, abc=abc)
107  CALL write_cell(cell=cell, subsys_section=subsys_section)
108 
109  CALL cp_subsys_create(subsys, para_env, root_section)
110 
111  CALL eip_init_subsys(eip_env=eip_env, subsys=subsys, cell=cell, &
112  cell_ref=cell_ref, use_ref_cell=use_ref_cell, &
113  subsys_section=subsys_section)
114 
115  CALL cell_release(cell)
116  CALL cell_release(cell_ref)
117 
118  CALL timestop(handle)
119 
120  END SUBROUTINE eip_init
121 
122 ! **************************************************************************************************
123 !> \brief Initialize the eip environment
124 !> \param eip_env The eip environment of matter
125 !> \param subsys the subsys
126 !> \param cell Pointer to the actual simulation cell
127 !> \param cell_ref Pointer to the reference cell, used e.g. in NPT simulations
128 !> \param use_ref_cell Logical which indicates if cell_ref is in use
129 !> \param subsys_section ...
130 !> \par History
131 !> 03.2006 initial create [tdk]
132 !> \author Thomas D. Kuehne (tkuehne@phys.chem.ethz.ch)
133 ! **************************************************************************************************
134  SUBROUTINE eip_init_subsys(eip_env, subsys, cell, cell_ref, use_ref_cell, subsys_section)
135  TYPE(eip_environment_type), POINTER :: eip_env
136  TYPE(cp_subsys_type), POINTER :: subsys
137  TYPE(cell_type), POINTER :: cell, cell_ref
138  LOGICAL, INTENT(in) :: use_ref_cell
139  TYPE(section_vals_type), POINTER :: subsys_section
140 
141  CHARACTER(len=*), PARAMETER :: routinen = 'eip_init_subsys'
142 
143  INTEGER :: handle, natom
144  TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
145  TYPE(distribution_1d_type), POINTER :: local_molecules, local_particles
146  TYPE(molecule_kind_type), DIMENSION(:), POINTER :: molecule_kind_set
147  TYPE(molecule_type), DIMENSION(:), POINTER :: molecule_set
148  TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
149 
150 ! ------------------------------------------------------------------------
151 
152  CALL timeset(routinen, handle)
153 
154  NULLIFY (atomic_kind_set, molecule_kind_set, particle_set, molecule_set, &
155  local_molecules, local_particles)
156 
157  particle_set => subsys%particles%els
158  atomic_kind_set => subsys%atomic_kinds%els
159  molecule_kind_set => subsys%molecule_kinds%els
160  molecule_set => subsys%molecules%els
161 
162 ! *** Print the molecule kind set ***
163  CALL write_molecule_kind_set(molecule_kind_set, subsys_section)
164 
165 ! *** Print the atomic coordinates
166  CALL write_fist_particle_coordinates(particle_set, subsys_section)
167  CALL write_particle_distances(particle_set, cell=cell, &
168  subsys_section=subsys_section)
169  CALL write_structure_data(particle_set, cell=cell, &
170  input_section=subsys_section)
171 
172 ! *** Distribute molecules and atoms using the new data structures ***
173  CALL distribute_molecules_1d(atomic_kind_set=atomic_kind_set, &
174  particle_set=particle_set, &
175  local_particles=local_particles, &
176  molecule_kind_set=molecule_kind_set, &
177  molecule_set=molecule_set, &
178  local_molecules=local_molecules, &
179  force_env_section=eip_env%force_env_input)
180 
181  natom = SIZE(particle_set)
182 
183  ALLOCATE (eip_env%eip_forces(3, natom))
184 
185  eip_env%eip_forces(:, :) = 0.0_dp
186 
187  CALL cp_subsys_set(subsys, cell=cell)
188  CALL eip_env_set(eip_env=eip_env, subsys=subsys, &
189  cell_ref=cell_ref, use_ref_cell=use_ref_cell, &
190  local_molecules=local_molecules, &
191  local_particles=local_particles)
192 
193  CALL distribution_1d_release(local_particles)
194  CALL distribution_1d_release(local_molecules)
195 
196  CALL eip_init_model(eip_env=eip_env)
197 
198  CALL timestop(handle)
199 
200  END SUBROUTINE eip_init_subsys
201 
202 ! **************************************************************************************************
203 !> \brief Initialize the empirical interatomic potnetial (force field) model
204 !> \param eip_env The eip environment to retain
205 !> \par History
206 !> 03.2006 initial create [tdk]
207 !> \author Thomas D. Kuehne (tkuehne@phys.chem.ethz.ch)
208 ! **************************************************************************************************
209  SUBROUTINE eip_init_model(eip_env)
210  TYPE(eip_environment_type), POINTER :: eip_env
211 
212  CHARACTER(len=*), PARAMETER :: routinen = 'eip_init_model'
213 
214  CHARACTER(LEN=default_string_length) :: eip_atomic_kind_name
215  INTEGER :: handle, i
216  TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
217  TYPE(atomic_kind_type), POINTER :: atomic_kind_ptr
218  TYPE(section_vals_type), POINTER :: eip_section
219 
220 ! ------------------------------------------------------------------------
221 
222  CALL timeset(routinen, handle)
223 
224  NULLIFY (atomic_kind_set, atomic_kind_ptr, eip_section)
225 
226  eip_section => section_vals_get_subs_vals(eip_env%force_env_input, &
227  "EIP")
228 
229  atomic_kind_set => eip_env%subsys%atomic_kinds%els
230 
231  ! loop over all kinds
232  DO i = 1, SIZE(atomic_kind_set)
233  atomic_kind_ptr => eip_env%subsys%atomic_kinds%els(i)
234  CALL get_atomic_kind(atomic_kind=atomic_kind_ptr, &
235  name=eip_atomic_kind_name)
236  SELECT CASE (eip_atomic_kind_name)
237  CASE ("SI", "Si")
238  CALL section_vals_val_get(section_vals=eip_section, &
239  keyword_name="EIP-Model", &
240  i_val=eip_env%eip_model)
241  CASE DEFAULT
242  cpabort("EIP models for other elements than Si isn't implemented yet.")
243  END SELECT
244  END DO
245 
246  CALL timestop(handle)
247 
248  END SUBROUTINE eip_init_model
249 
250 END MODULE eip_environment
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.
Handles all functions related to the CELL.
Definition: cell_methods.F:15
recursive subroutine, public read_cell(cell, cell_ref, use_ref_cell, cell_section, check_for_ref, para_env)
...
Definition: cell_methods.F:272
subroutine, public write_cell(cell, subsys_section, tag)
Write the cell parameters to the output unit.
Definition: cell_methods.F:731
Handles all functions related to the CELL.
Definition: cell_types.F:15
subroutine, public cell_release(cell)
releases the given cell (see doc/ReferenceCounting.html)
Definition: cell_types.F:559
subroutine, public get_cell(cell, alpha, beta, gamma, deth, orthorhombic, abc, periodic, h, h_inv, symmetry_id, tag)
Get informations about a simulation cell.
Definition: cell_types.F:195
Initialize a small environment for a particular calculation.
subroutine, public cp_subsys_create(subsys, para_env, root_section, force_env_section, subsys_section, use_motion_section, qmmm, qmmm_env, exclusions, elkind)
Creates allocates and fills subsys from given input.
types that represent a subsys, i.e. a part of the system
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
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.
The environment for the empirical interatomic potential methods.
subroutine, public eip_env_set(eip_env, eip_model, eip_energy, eip_energy_var, eip_forces, coord_avg, coord_var, count, subsys, atomic_kind_set, particle_set, local_particles, molecule_kind_set, molecule_set, local_molecules, eip_input, force_env_input, cell_ref, use_ref_cell, eip_kinetic_energy, eip_potential_energy)
Sets various attributes of the eip environment.
Methods and functions on the EIP environment.
subroutine, public eip_init(eip_env, root_section, para_env, force_env_section, subsys_section)
Initialize the eip environment.
objects that represent the structure of input sections and the data contained in an input section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
integer, parameter, public default_string_length
Definition: kinds.F:57
Interface to the message passing library MPI.
Define the molecule kind structure types and the corresponding functionality.
subroutine, public write_molecule_kind_set(molecule_kind_set, subsys_section)
Write a moleculeatomic kind set data set to the output unit.
Define the data structure for the molecule information.
Define methods related to particle_type.
subroutine, public write_fist_particle_coordinates(particle_set, subsys_section, charges)
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.