(git:34ef472)
force_env_types.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 Interface for the force calculations
10 !> \par History
11 !> cjm, FEB-20-2001: pass variable box_ref
12 !> cjm, SEPT-12-2002: major reorganization
13 !> fawzi, APR-12-2003: introduced force_env
14 !> cjm, FEB-27-2006: no more box_change
15 !> MK, Nov. 2010: new interfaces added and others were updated
16 !> \author CJM & JGH
17 ! **************************************************************************************************
19  USE cell_types, ONLY: cell_type
21  cp_logger_type,&
23  USE cp_subsys_types, ONLY: cp_subsys_get,&
24  cp_subsys_type,&
28  eip_environment_type
29  USE embed_types, ONLY: embed_env_release,&
30  embed_env_type,&
32  USE fist_energy_types, ONLY: fist_energy_type
35  fist_environment_type
36  USE fp_types, ONLY: fp_env_release,&
37  fp_type
38  USE global_types, ONLY: global_environment_type,&
43  section_vals_type,&
45  USE kinds, ONLY: dp
47  mp_para_env_type
49  meta_env_type
50  USE mixed_energy_types, ONLY: mixed_energy_type
53  mixed_environment_type
56  nnp_type
57  USE pwdft_environment_types, ONLY: pwdft_energy_type,&
60  pwdft_environment_type
61  USE qmmm_types, ONLY: qmmm_env_get,&
63  qmmm_env_type
64  USE qmmmx_types, ONLY: qmmmx_env_get,&
66  qmmmx_env_type
67  USE qs_energy_types, ONLY: qs_energy_type
68  USE qs_environment_types, ONLY: get_qs_env,&
70  qs_environment_type
71 #include "./base/base_uses.f90"
72 
73  IMPLICIT NONE
74 
75  PRIVATE
76 
77  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'force_env_types'
78 
79  INTEGER, PARAMETER, PUBLIC :: use_fist_force = 501, &
80  use_qs_force = 502, &
81  use_qmmm = 503, &
82  use_qmmmx = 504, &
83  use_eip_force = 505, &
84  use_mixed_force = 506, &
85  use_embed = 507, &
86  use_pwdft_force = 508, &
87  use_nnp_force = 509
88 
89  CHARACTER(LEN=10), DIMENSION(501:509), PARAMETER, PUBLIC :: &
90  use_prog_name = (/ &
91  "FIST ", &
92  "QS ", &
93  "QMMM ", &
94  "QMMMX ", &
95  "EIP ", &
96  "MIXED ", &
97  "EMBED ", &
98  "SIRIUS", &
99  "NNP "/)
100 
101  PUBLIC :: force_env_type, &
102  force_env_p_type
103 
104  PUBLIC :: force_env_retain, &
106  force_env_get, &
112  force_env_set, &
114 
115 ! **************************************************************************************************
116 !> \brief wrapper to abstract the force evaluation of the various methods
117 !> \param ref_count reference count (see doc/ReferenceCounting.html)
118 !> \param in_use which method is in use
119 !> \param fist_env the fist environment (allocated only if fist is in use)
120 !> \param qs_env qs_env (activated only if quickstep is in use)
121 !> \param globenv the globenv to have the input that generated this force_env
122 !> \param para_env the parallel environment that contains all the parallel
123 !> environment of the fragments
124 !> \param meta_env the metadynamics environment, allocated if there is
125 !> metadynamics
126 !> \param fp_env the flexible partitioning environment
127 !> read-only attributes (get them *only* through force_env_get):
128 !> \param subsys the fragments that build up the actual system.
129 !> \param cell the cell of the actual system
130 !> \note
131 !> as always direct manipulation of these attributes can have very
132 !> bad effects. In this case it can be quite bad and the variables
133 !> might not be up to date. You are warned, use only the get method...
134 !> \par History
135 !> 04.2003 created [fawzi]
136 !> 07.2003 tried to adapt to multiple mpi groups
137 !> \author fawzi
138 ! **************************************************************************************************
139  TYPE force_env_type
140  INTEGER :: ref_count = 0, in_use = 0, method_name_id = 0
141  REAL(kind=dp) :: additional_potential = 0.0_dp
142  TYPE(fist_environment_type), POINTER :: fist_env => null()
143  TYPE(meta_env_type), POINTER :: meta_env => null()
144  TYPE(fp_type), POINTER :: fp_env => null()
145  TYPE(qs_environment_type), POINTER :: qs_env => null()
146  TYPE(eip_environment_type), POINTER :: eip_env => null()
147  TYPE(pwdft_environment_type), POINTER :: pwdft_env => null()
148  TYPE(global_environment_type), POINTER :: globenv => null()
149  TYPE(mp_para_env_type), POINTER :: para_env => null()
150  TYPE(force_env_p_type), DIMENSION(:), POINTER :: sub_force_env => null()
151  TYPE(qmmm_env_type), POINTER :: qmmm_env => null()
152  TYPE(qmmmx_env_type), POINTER :: qmmmx_env => null()
153  TYPE(mixed_environment_type), POINTER :: mixed_env => null()
154  TYPE(nnp_type), POINTER :: nnp_env => null()
155  TYPE(embed_env_type), POINTER :: embed_env => null()
156  TYPE(section_vals_type), POINTER :: force_env_section => null()
157  TYPE(section_vals_type), POINTER :: root_section => null()
158  END TYPE force_env_type
159 
160 ! **************************************************************************************************
161 !> \brief allows for the creation of an array of force_env
162 !> \param force_env a force environment (see above)
163 !> \note
164 !> added by MJM for MC swap moves
165 !> \author MJM
166 ! **************************************************************************************************
167  TYPE force_env_p_type
168  TYPE(force_env_type), POINTER :: force_env => null()
169  END TYPE force_env_p_type
170 
171 CONTAINS
172 
173 ! **************************************************************************************************
174 !> \brief retains the given force env
175 !> \param force_env the force environment to retain
176 !> \par History
177 !> 04.2003 created [fawzi]
178 !> \author fawzi
179 !> \note
180 !> see doc/ReferenceCounting.html
181 ! **************************************************************************************************
182  SUBROUTINE force_env_retain(force_env)
183  TYPE(force_env_type), POINTER :: force_env
184 
185  cpassert(ASSOCIATED(force_env))
186  cpassert(force_env%ref_count > 0)
187  force_env%ref_count = force_env%ref_count + 1
188  END SUBROUTINE force_env_retain
189 
190 ! **************************************************************************************************
191 !> \brief releases the given force env
192 !> \param force_env the force environment to release
193 !> \par History
194 !> 04.2003 created [fawzi]
195 !> \author fawzi
196 !> \note
197 !> see doc/ReferenceCounting.html
198 ! **************************************************************************************************
199  RECURSIVE SUBROUTINE force_env_release(force_env)
200  TYPE(force_env_type), POINTER :: force_env
201 
202  INTEGER :: i, my_group
203  TYPE(cp_logger_type), POINTER :: my_logger
204 
205  IF (ASSOCIATED(force_env)) THEN
206  cpassert(force_env%ref_count > 0)
207  force_env%ref_count = force_env%ref_count - 1
208  IF (force_env%ref_count == 0) THEN
209  ! Deallocate SUB_FORCE_ENV
210  IF (ASSOCIATED(force_env%sub_force_env)) THEN
211  DO i = 1, SIZE(force_env%sub_force_env)
212  IF (.NOT. ASSOCIATED(force_env%sub_force_env(i)%force_env)) cycle
213  ! Use the proper logger to deallocate..
214  IF (force_env%in_use == use_mixed_force) THEN
215  my_group = force_env%mixed_env%group_distribution(force_env%para_env%mepos)
216  my_logger => force_env%mixed_env%sub_logger(my_group + 1)%p
217  CALL cp_add_default_logger(my_logger)
218  END IF
219  ! The same for embedding
220  IF (force_env%in_use == use_embed) THEN
221  my_group = force_env%embed_env%group_distribution(force_env%para_env%mepos)
222  my_logger => force_env%embed_env%sub_logger(my_group + 1)%p
223  CALL cp_add_default_logger(my_logger)
224  END IF
225  CALL force_env_release(force_env%sub_force_env(i)%force_env)
226  IF (force_env%in_use == use_mixed_force) &
227  CALL cp_rm_default_logger()
228  IF (force_env%in_use == use_embed) &
229  CALL cp_rm_default_logger()
230  END DO
231  DEALLOCATE (force_env%sub_force_env)
232  END IF
233 
234  SELECT CASE (force_env%in_use)
235  CASE (use_fist_force)
236  CALL fist_env_release(force_env%fist_env)
237  DEALLOCATE (force_env%fist_env)
238  CASE (use_qs_force)
239  CALL qs_env_release(force_env%qs_env)
240  DEALLOCATE (force_env%qs_env)
241  CASE (use_eip_force)
242  CALL eip_env_release(force_env%eip_env)
243  DEALLOCATE (force_env%eip_env)
244  CASE (use_pwdft_force)
245  CALL pwdft_env_release(force_env%pwdft_env)
246  DEALLOCATE (force_env%pwdft_env)
247  CASE (use_mixed_force)
248  CALL mixed_env_release(force_env%mixed_env)
249  DEALLOCATE (force_env%mixed_env)
250  CASE (use_nnp_force)
251  CALL nnp_env_release(force_env%nnp_env)
252  DEALLOCATE (force_env%nnp_env)
253  CASE (use_embed)
254  CALL embed_env_release(force_env%embed_env)
255  DEALLOCATE (force_env%embed_env)
256  END SELECT
257  CALL globenv_release(force_env%globenv)
258  CALL mp_para_env_release(force_env%para_env)
259  ! Not deallocated
260  cpassert(.NOT. ASSOCIATED(force_env%fist_env))
261  cpassert(.NOT. ASSOCIATED(force_env%qs_env))
262  cpassert(.NOT. ASSOCIATED(force_env%eip_env))
263  cpassert(.NOT. ASSOCIATED(force_env%pwdft_env))
264  cpassert(.NOT. ASSOCIATED(force_env%mixed_env))
265  cpassert(.NOT. ASSOCIATED(force_env%nnp_env))
266  cpassert(.NOT. ASSOCIATED(force_env%embed_env))
267  IF (ASSOCIATED(force_env%meta_env)) THEN
268  CALL meta_env_release(force_env%meta_env)
269  DEALLOCATE (force_env%meta_env)
270  END IF
271  IF (ASSOCIATED(force_env%fp_env)) THEN
272  CALL fp_env_release(force_env%fp_env)
273  DEALLOCATE (force_env%fp_env)
274  END IF
275  IF (ASSOCIATED(force_env%qmmm_env)) THEN
276  CALL qmmm_env_release(force_env%qmmm_env)
277  DEALLOCATE (force_env%qmmm_env)
278  END IF
279  IF (ASSOCIATED(force_env%qmmmx_env)) THEN
280  CALL qmmmx_env_release(force_env%qmmmx_env)
281  DEALLOCATE (force_env%qmmmx_env)
282  END IF
283  CALL section_vals_release(force_env%force_env_section)
284  CALL section_vals_release(force_env%root_section)
285  DEALLOCATE (force_env)
286  END IF
287  END IF
288  NULLIFY (force_env)
289  END SUBROUTINE force_env_release
290 
291 ! **************************************************************************************************
292 !> \brief returns various attributes about the force environment
293 !> \param force_env the force environment you what informations about
294 !> \param in_use ...
295 !> \param fist_env ...
296 !> \param qs_env ...
297 !> \param meta_env ...
298 !> \param fp_env ...
299 !> \param subsys ...
300 !> \param para_env ...
301 !> \param potential_energy ...
302 !> \param additional_potential ...
303 !> \param kinetic_energy ...
304 !> \param harmonic_shell ...
305 !> \param kinetic_shell ...
306 !> \param cell ...
307 !> \param sub_force_env ...
308 !> \param qmmm_env ...
309 !> \param qmmmx_env ...
310 !> \param eip_env ...
311 !> \param pwdft_env ...
312 !> \param globenv ...
313 !> \param input ...
314 !> \param force_env_section ...
315 !> \param method_name_id ...
316 !> \param root_section ...
317 !> \param mixed_env ...
318 !> \param nnp_env ...
319 !> \param embed_env ...
320 !> \par History
321 !> 04.2003 created [fawzi]
322 !> \author fawzi
323 ! **************************************************************************************************
324  RECURSIVE SUBROUTINE force_env_get(force_env, in_use, fist_env, qs_env, &
325  meta_env, fp_env, subsys, para_env, potential_energy, additional_potential, &
326  kinetic_energy, harmonic_shell, kinetic_shell, cell, sub_force_env, &
327  qmmm_env, qmmmx_env, eip_env, pwdft_env, globenv, input, force_env_section, &
328  method_name_id, root_section, mixed_env, nnp_env, embed_env)
329  TYPE(force_env_type), INTENT(IN) :: force_env
330  INTEGER, INTENT(out), OPTIONAL :: in_use
331  TYPE(fist_environment_type), OPTIONAL, POINTER :: fist_env
332  TYPE(qs_environment_type), OPTIONAL, POINTER :: qs_env
333  TYPE(meta_env_type), OPTIONAL, POINTER :: meta_env
334  TYPE(fp_type), OPTIONAL, POINTER :: fp_env
335  TYPE(cp_subsys_type), OPTIONAL, POINTER :: subsys
336  TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
337  REAL(kind=dp), INTENT(OUT), OPTIONAL :: potential_energy, additional_potential, &
338  kinetic_energy, harmonic_shell, &
339  kinetic_shell
340  TYPE(cell_type), OPTIONAL, POINTER :: cell
341  TYPE(force_env_p_type), DIMENSION(:), OPTIONAL, &
342  POINTER :: sub_force_env
343  TYPE(qmmm_env_type), OPTIONAL, POINTER :: qmmm_env
344  TYPE(qmmmx_env_type), OPTIONAL, POINTER :: qmmmx_env
345  TYPE(eip_environment_type), OPTIONAL, POINTER :: eip_env
346  TYPE(pwdft_environment_type), OPTIONAL, POINTER :: pwdft_env
347  TYPE(global_environment_type), OPTIONAL, POINTER :: globenv
348  TYPE(section_vals_type), OPTIONAL, POINTER :: input, force_env_section
349  INTEGER, INTENT(out), OPTIONAL :: method_name_id
350  TYPE(section_vals_type), OPTIONAL, POINTER :: root_section
351  TYPE(mixed_environment_type), OPTIONAL, POINTER :: mixed_env
352  TYPE(nnp_type), OPTIONAL, POINTER :: nnp_env
353  TYPE(embed_env_type), OPTIONAL, POINTER :: embed_env
354 
355  REAL(kind=dp) :: eip_kinetic_energy, eip_potential_energy
356  TYPE(cp_subsys_type), POINTER :: subsys_tmp
357  TYPE(fist_energy_type), POINTER :: thermo
358  TYPE(mixed_energy_type), POINTER :: mixed_energy
359  TYPE(pwdft_energy_type), POINTER :: pwdft_energy
360  TYPE(qs_energy_type), POINTER :: qs_energy
361 
362  NULLIFY (subsys_tmp)
363 
364  cpassert(force_env%ref_count > 0)
365 
366  SELECT CASE (force_env%in_use)
367  CASE (use_qs_force)
368  cpassert(ASSOCIATED(force_env%qs_env))
369  cpassert(.NOT. PRESENT(fist_env))
370  cpassert(.NOT. PRESENT(eip_env))
371  cpassert(.NOT. PRESENT(pwdft_env))
372  CALL get_qs_env(force_env%qs_env, &
373  energy=qs_energy, &
374  input=input, &
375  cp_subsys=subsys)
376  IF (PRESENT(potential_energy)) potential_energy = qs_energy%total
377  cpassert(.NOT. PRESENT(kinetic_energy))
378  CASE (use_fist_force)
379  cpassert(ASSOCIATED(force_env%fist_env))
380  cpassert(.NOT. PRESENT(input))
381  CALL fist_env_get(force_env%fist_env, &
382  thermo=thermo, &
383  subsys=subsys)
384  IF (PRESENT(potential_energy)) potential_energy = thermo%pot
385  IF (PRESENT(kinetic_energy)) kinetic_energy = thermo%kin
386  IF (PRESENT(kinetic_shell)) kinetic_shell = thermo%kin_shell
387  IF (PRESENT(harmonic_shell)) harmonic_shell = thermo%harm_shell
388  CASE (use_eip_force)
389  cpassert(ASSOCIATED(force_env%eip_env))
390  cpassert(.NOT. PRESENT(qs_env))
391  cpassert(.NOT. PRESENT(fist_env))
392  CALL eip_env_get(force_env%eip_env, &
393  eip_potential_energy=eip_potential_energy, &
394  eip_kinetic_energy=eip_kinetic_energy, &
395  subsys=subsys)
396  IF (PRESENT(potential_energy)) THEN
397  potential_energy = eip_potential_energy
398  END IF
399  IF (PRESENT(kinetic_energy)) kinetic_energy = eip_kinetic_energy
400  cpassert(.NOT. PRESENT(kinetic_energy))
401  CASE (use_pwdft_force)
402  cpassert(ASSOCIATED(force_env%pwdft_env))
403  cpassert(.NOT. PRESENT(qs_env))
404  cpassert(.NOT. PRESENT(fist_env))
405  CALL pwdft_env_get(force_env%pwdft_env, energy=pwdft_energy)
406  CALL pwdft_env_get(force_env%pwdft_env, cp_subsys=subsys)
407  IF (PRESENT(potential_energy)) potential_energy = pwdft_energy%etotal
408  cpassert(.NOT. PRESENT(kinetic_energy))
409  CASE (use_qmmm)
410  CALL qmmm_env_get(force_env%qmmm_env, &
411  subsys=subsys, &
412  potential_energy=potential_energy, &
413  kinetic_energy=kinetic_energy)
414  CASE (use_qmmmx)
415  CALL qmmmx_env_get(force_env%qmmmx_env, &
416  subsys=subsys, &
417  potential_energy=potential_energy, &
418  kinetic_energy=kinetic_energy)
419  CASE (use_mixed_force)
420  cpassert(ASSOCIATED(force_env%mixed_env))
421  cpassert(.NOT. PRESENT(input))
422  CALL get_mixed_env(force_env%mixed_env, &
423  mixed_energy=mixed_energy, &
424  subsys=subsys)
425  IF (PRESENT(potential_energy)) potential_energy = mixed_energy%pot
426  IF (PRESENT(kinetic_energy)) kinetic_energy = mixed_energy%kin
427  ! In embedding we only have potential energies (electronic energies)
428  CASE (use_embed)
429  cpassert(ASSOCIATED(force_env%embed_env))
430  cpassert(.NOT. PRESENT(input))
431  CALL get_embed_env(force_env%embed_env, &
432  pot_energy=potential_energy, &
433  subsys=subsys)
434  CASE (use_nnp_force)
435  cpassert(ASSOCIATED(force_env%nnp_env))
436  CALL nnp_env_get(force_env%nnp_env, &
437  nnp_potential_energy=potential_energy, &
438  subsys=subsys)
439  cpassert(.NOT. PRESENT(kinetic_energy))
440  CASE DEFAULT
441  cpabort("unknown in_use flag value ")
442  END SELECT
443 
444  IF (PRESENT(force_env_section)) force_env_section => force_env%force_env_section
445  IF (PRESENT(in_use)) in_use = force_env%in_use
446  IF (PRESENT(method_name_id)) method_name_id = force_env%method_name_id
447  IF (PRESENT(fist_env)) THEN
448  fist_env => force_env%fist_env
449  END IF
450  IF (PRESENT(qs_env)) THEN
451  qs_env => force_env%qs_env
452  END IF
453  IF (PRESENT(eip_env)) THEN
454  eip_env => force_env%eip_env
455  END IF
456  IF (PRESENT(pwdft_env)) THEN
457  pwdft_env => force_env%pwdft_env
458  END IF
459  IF (PRESENT(nnp_env)) THEN
460  nnp_env => force_env%nnp_env
461  END IF
462  IF (PRESENT(para_env)) para_env => force_env%para_env
463  ! adjust the total energy for the metadynamics
464  IF (ASSOCIATED(force_env%meta_env)) THEN
465  IF (PRESENT(potential_energy)) THEN
466  potential_energy = potential_energy + &
467  force_env%meta_env%epot_s + &
468  force_env%meta_env%epot_walls + &
469  force_env%meta_env%hills_env%energy
470  END IF
471  IF (PRESENT(kinetic_energy)) THEN
472  kinetic_energy = kinetic_energy + force_env%meta_env%ekin_s
473  END IF
474  END IF
475  ! adjust the total energy for the flexible partitioning
476  IF (ASSOCIATED(force_env%fp_env) .AND. PRESENT(potential_energy)) THEN
477  IF (force_env%fp_env%use_fp) THEN
478  potential_energy = potential_energy + force_env%fp_env%energy
479  END IF
480  END IF
481  IF (PRESENT(potential_energy)) THEN
482  potential_energy = potential_energy + force_env%additional_potential
483  END IF
484  IF (PRESENT(additional_potential)) THEN
485  additional_potential = force_env%additional_potential
486  END IF
487  IF (PRESENT(cell)) THEN
488  CALL force_env_get(force_env, subsys=subsys_tmp)
489  CALL cp_subsys_get(subsys_tmp, cell=cell)
490  END IF
491  IF (PRESENT(fp_env)) fp_env => force_env%fp_env
492  IF (PRESENT(meta_env)) meta_env => force_env%meta_env
493  IF (PRESENT(sub_force_env)) sub_force_env => force_env%sub_force_env
494  IF (PRESENT(qmmm_env)) qmmm_env => force_env%qmmm_env
495  IF (PRESENT(qmmmx_env)) qmmmx_env => force_env%qmmmx_env
496  IF (PRESENT(mixed_env)) mixed_env => force_env%mixed_env
497  IF (PRESENT(embed_env)) embed_env => force_env%embed_env
498  IF (PRESENT(globenv)) globenv => force_env%globenv
499  IF (PRESENT(root_section)) root_section => force_env%root_section
500 
501  END SUBROUTINE force_env_get
502 
503 ! **************************************************************************************************
504 !> \brief returns the number of atoms
505 !> \param force_env the force_env you what information about
506 !> \return the number of atoms
507 !> \date 22.11.2010 updated (MK)
508 !> \author fawzi
509 ! **************************************************************************************************
510  FUNCTION force_env_get_natom(force_env) RESULT(n_atom)
511 
512  TYPE(force_env_type), INTENT(IN) :: force_env
513  INTEGER :: n_atom
514 
515  TYPE(cp_subsys_type), POINTER :: subsys
516 
517  n_atom = 0
518  NULLIFY (subsys)
519  CALL force_env_get(force_env, subsys=subsys)
520  CALL cp_subsys_get(subsys, natom=n_atom)
521 
522  END FUNCTION force_env_get_natom
523 
524 ! **************************************************************************************************
525 !> \brief returns the number of particles in a force environment
526 !> \param force_env the force_env you what information about
527 !> \return the number of particles
528 !> \date 22.11.2010 (MK)
529 !> \author Matthias Krack
530 ! **************************************************************************************************
531  FUNCTION force_env_get_nparticle(force_env) RESULT(n_particle)
532 
533  TYPE(force_env_type), INTENT(IN) :: force_env
534  INTEGER :: n_particle
535 
536  TYPE(cp_subsys_type), POINTER :: subsys
537 
538  n_particle = 0
539  NULLIFY (subsys)
540  CALL force_env_get(force_env, subsys=subsys)
541  CALL cp_subsys_get(subsys, nparticle=n_particle)
542 
543  END FUNCTION force_env_get_nparticle
544 
545 ! **************************************************************************************************
546 !> \brief returns the particle forces in a dimension(*) array
547 !> \param force_env the force_env you want to get the forces
548 !> \param frc the array of the forces
549 !> \param n ...
550 !> \date 22.11.2010 Creation
551 !> \author Matthias Krack
552 ! **************************************************************************************************
553  SUBROUTINE force_env_get_frc(force_env, frc, n)
554 
555  TYPE(force_env_type), INTENT(IN) :: force_env
556  REAL(kind=dp), DIMENSION(*), INTENT(OUT) :: frc
557  INTEGER, INTENT(IN) :: n
558 
559  CHARACTER(LEN=*), PARAMETER :: routinen = 'force_env_get_frc'
560 
561  INTEGER :: handle
562  TYPE(cp_subsys_type), POINTER :: subsys
563 
564  CALL timeset(routinen, handle)
565  cpassert(force_env%ref_count > 0)
566  CALL force_env_get(force_env, subsys=subsys)
567  CALL pack_subsys_particles(subsys=subsys, f=frc(1:n))
568  CALL timestop(handle)
569 
570  END SUBROUTINE force_env_get_frc
571 
572 ! **************************************************************************************************
573 !> \brief returns the particle positions in a dimension(*) array
574 !> \param force_env the force_env you want to get the positions
575 !> \param pos the array of the positions
576 !> \param n ...
577 !> \date 22.11.2010 updated (MK)
578 !> \author fawzi
579 ! **************************************************************************************************
580  SUBROUTINE force_env_get_pos(force_env, pos, n)
581 
582  TYPE(force_env_type), INTENT(IN) :: force_env
583  REAL(kind=dp), DIMENSION(*), INTENT(OUT) :: pos
584  INTEGER, INTENT(IN) :: n
585 
586  CHARACTER(LEN=*), PARAMETER :: routinen = 'force_env_get_pos'
587 
588  INTEGER :: handle
589  TYPE(cp_subsys_type), POINTER :: subsys
590 
591  CALL timeset(routinen, handle)
592  cpassert(force_env%ref_count > 0)
593  CALL force_env_get(force_env, subsys=subsys)
594  CALL pack_subsys_particles(subsys=subsys, r=pos(1:n))
595  CALL timestop(handle)
596 
597  END SUBROUTINE force_env_get_pos
598 
599 ! **************************************************************************************************
600 !> \brief returns the particle velocities in a dimension(*) array
601 !> \param force_env the force_env you want to get the velocities
602 !> \param vel the array of the velocities
603 !> \param n ...
604 !> \date 22.11.2010 Creation (MK)
605 !> \author Matthias Krack
606 ! **************************************************************************************************
607  SUBROUTINE force_env_get_vel(force_env, vel, n)
608 
609  TYPE(force_env_type), INTENT(IN) :: force_env
610  REAL(kind=dp), DIMENSION(*), INTENT(OUT) :: vel
611  INTEGER, INTENT(IN) :: n
612 
613  CHARACTER(LEN=*), PARAMETER :: routinen = 'force_env_get_vel'
614 
615  INTEGER :: handle
616  TYPE(cp_subsys_type), POINTER :: subsys
617 
618  CALL timeset(routinen, handle)
619  cpassert(force_env%ref_count > 0)
620  CALL force_env_get(force_env, subsys=subsys)
621  CALL pack_subsys_particles(subsys=subsys, v=vel(1:n))
622  CALL timestop(handle)
623 
624  END SUBROUTINE force_env_get_vel
625 
626 ! **************************************************************************************************
627 !> \brief changes some attributes of the force_env
628 !> \param force_env the force environment where the cell should be changed
629 !> \param meta_env the new meta environment
630 !> \param fp_env ...
631 !> \param force_env_section ...
632 !> \param method_name_id ...
633 !> \param additional_potential ...
634 !> \par History
635 !> 09.2003 created [fawzi]
636 !> \author Fawzi Mohamed
637 ! **************************************************************************************************
638  SUBROUTINE force_env_set(force_env, meta_env, fp_env, force_env_section, &
639  method_name_id, additional_potential)
640 
641  TYPE(force_env_type), INTENT(INOUT) :: force_env
642  TYPE(meta_env_type), OPTIONAL, POINTER :: meta_env
643  TYPE(fp_type), OPTIONAL, POINTER :: fp_env
644  TYPE(section_vals_type), OPTIONAL, POINTER :: force_env_section
645  INTEGER, OPTIONAL :: method_name_id
646  REAL(kind=dp), INTENT(IN), OPTIONAL :: additional_potential
647 
648  cpassert(force_env%ref_count > 0)
649  IF (PRESENT(meta_env)) THEN
650  IF (ASSOCIATED(force_env%meta_env)) THEN
651  CALL meta_env_release(force_env%meta_env)
652  DEALLOCATE (force_env%meta_env)
653  END IF
654  force_env%meta_env => meta_env
655  END IF
656  IF (PRESENT(fp_env)) THEN
657  IF (ASSOCIATED(force_env%fp_env)) CALL fp_env_release(force_env%fp_env)
658  force_env%fp_env => fp_env
659  END IF
660  IF (PRESENT(force_env_section)) THEN
661  IF (ASSOCIATED(force_env_section)) THEN
662  CALL section_vals_retain(force_env_section)
663  CALL section_vals_release(force_env%force_env_section)
664  force_env%force_env_section => force_env_section
665  END IF
666  END IF
667  IF (PRESENT(additional_potential)) THEN
668  force_env%additional_potential = additional_potential
669  END IF
670  IF (PRESENT(method_name_id)) THEN
671  force_env%method_name_id = method_name_id
672  END IF
673 
674  END SUBROUTINE force_env_set
675 
676 ! **************************************************************************************************
677 !> \brief returns the order of the multiple force_env
678 !> \param force_env_sections ...
679 !> \param root_section ...
680 !> \param i_force_eval ...
681 !> \param nforce_eval ...
682 !> \author teo
683 ! **************************************************************************************************
684  SUBROUTINE multiple_fe_list(force_env_sections, root_section, i_force_eval, nforce_eval)
685 
686  TYPE(section_vals_type), INTENT(IN) :: force_env_sections, root_section
687  INTEGER, DIMENSION(:), POINTER :: i_force_eval
688  INTEGER :: nforce_eval
689 
690  INTEGER :: iforce_eval, main_force_eval
691  INTEGER, DIMENSION(:), POINTER :: my_i_force_eval
692 
693 ! Let's treat the case of Multiple force_eval
694 
695  CALL section_vals_get(force_env_sections, n_repetition=nforce_eval)
696  CALL section_vals_val_get(root_section, "MULTIPLE_FORCE_EVALS%FORCE_EVAL_ORDER", &
697  i_vals=my_i_force_eval)
698  ALLOCATE (i_force_eval(nforce_eval))
699  IF (nforce_eval > 0) THEN
700  IF (nforce_eval == SIZE(my_i_force_eval)) THEN
701  i_force_eval = my_i_force_eval
702  ELSE
703  ! The difference in the amount of defined force_env MUST be one..
704  cpassert(nforce_eval - SIZE(my_i_force_eval) == 1)
705  DO iforce_eval = 1, nforce_eval
706  IF (any(my_i_force_eval == iforce_eval)) cycle
707  main_force_eval = iforce_eval
708  EXIT
709  END DO
710  i_force_eval(1) = main_force_eval
711  i_force_eval(2:nforce_eval) = my_i_force_eval
712  END IF
713  END IF
714 
715  END SUBROUTINE multiple_fe_list
716 
717 END MODULE force_env_types
Handles all functions related to the CELL.
Definition: cell_types.F:15
various routines to log and control the output. The idea is that decisions about where to log should ...
subroutine, public cp_rm_default_logger()
the cousin of cp_add_default_logger, decrements the stack, so that the default logger is what it has ...
subroutine, public cp_add_default_logger(logger)
adds a default logger. MUST be called before logging occours
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
subroutine, public pack_subsys_particles(subsys, f, r, s, v, fscale, cell)
Pack components of a subsystem particle sets into a single vector.
The environment for the empirical interatomic potential methods.
subroutine, public eip_env_release(eip_env)
Releases the given eip environment (see doc/ReferenceCounting.html)
subroutine, public eip_env_get(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, cell_ref, use_ref_cell, eip_kinetic_energy, eip_potential_energy, virial)
Returns various attributes of the eip environment.
subroutine, public get_embed_env(embed_env, atomic_kind_set, particle_set, local_particles, local_molecules, molecule_kind_set, molecule_set, cell, cell_ref, para_env, sub_para_env, subsys, input, results, pot_energy)
Get the embed environment.
Definition: embed_types.F:167
subroutine, public embed_env_release(embed_env)
...
Definition: embed_types.F:326
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.
Interface for the force calculations.
integer function, public force_env_get_natom(force_env)
returns the number of atoms
subroutine, public force_env_get_vel(force_env, vel, n)
returns the particle velocities in a dimension(*) array
integer, parameter, public use_qmmm
subroutine, public multiple_fe_list(force_env_sections, root_section, i_force_eval, nforce_eval)
returns the order of the multiple force_env
character(len=10), dimension(501:509), parameter, public use_prog_name
integer, parameter, public use_mixed_force
integer, parameter, public use_eip_force
integer, parameter, public use_embed
integer, parameter, public use_qmmmx
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)
returns various attributes about the force environment
subroutine, public force_env_retain(force_env)
retains the given force env
subroutine, public force_env_get_pos(force_env, pos, n)
returns the particle positions in a dimension(*) array
subroutine, public force_env_set(force_env, meta_env, fp_env, force_env_section, method_name_id, additional_potential)
changes some attributes of the force_env
integer, parameter, public use_qs_force
subroutine, public force_env_get_frc(force_env, frc, n)
returns the particle forces in a dimension(*) array
integer, parameter, public use_pwdft_force
integer, parameter, public use_nnp_force
recursive subroutine, public force_env_release(force_env)
releases the given force env
integer, parameter, public use_fist_force
integer function, public force_env_get_nparticle(force_env)
returns the number of particles in a force environment
types used in the flexible partitioning scheme
Definition: fp_types.F:14
subroutine, public fp_env_release(fp_env)
...
Definition: fp_types.F:80
Define type storing the global information of a run. Keep the amount of stored data small....
Definition: global_types.F:21
subroutine, public globenv_release(globenv)
Releases the global environment globenv.
Definition: global_types.F:133
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_retain(section_vals)
retains the given section values (see doc/ReferenceCounting.html)
subroutine, public section_vals_get(section_vals, ref_count, n_repetition, n_subs_vals_rep, section, explicit)
returns various attributes about the section_vals
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
recursive subroutine, public section_vals_release(section_vals)
releases the given object
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
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)
defines types for metadynamics calculation
subroutine, public meta_env_release(meta_env)
releases the meta_env
subroutine, public mixed_env_release(mixed_env)
releases the given mixed_env (see doc/ReferenceCounting.html)
subroutine, public get_mixed_env(mixed_env, atomic_kind_set, particle_set, local_particles, local_molecules, molecule_kind_set, molecule_set, cell, cell_ref, mixed_energy, para_env, sub_para_env, subsys, input, results, cdft_control)
Get the MIXED environment.
Data types for neural network potentials.
subroutine, public nnp_env_get(nnp_env, nnp_forces, subsys, atomic_kind_set, particle_set, local_particles, molecule_kind_set, molecule_set, local_molecules, nnp_input, force_env_input, cell, cell_ref, use_ref_cell, nnp_potential_energy, virial)
Returns various attributes of the nnp environment.
subroutine, public nnp_env_release(nnp_env)
Release data structure that holds all the information for neural network potentials.
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_release(pwdft_env)
Releases the given pwdft environment (see doc/ReferenceCounting.html)
Basic container type for QM/MM.
Definition: qmmm_types.F:12
subroutine, public qmmm_env_release(qmmm_env)
releases the given qmmm_env (see doc/ReferenceCounting.html)
Definition: qmmm_types.F:81
subroutine, public qmmm_env_get(qmmm_env, subsys, potential_energy, kinetic_energy)
...
Definition: qmmm_types.F:50
Basic container type for QM/MM with force mixing.
Definition: qmmmx_types.F:12
subroutine, public qmmmx_env_release(qmmmx_env)
releases the given qmmmx_env (see doc/ReferenceCounting.html)
Definition: qmmmx_types.F:61
subroutine, public qmmmx_env_get(qmmmx_env, subsys, potential_energy, kinetic_energy)
...
Definition: qmmmx_types.F:42
Perform a QUICKSTEP wavefunction optimization (single point)
Definition: qs_energy.F:14
subroutine, public get_qs_env(qs_env, atomic_kind_set, qs_kind_set, cell, super_cell, cell_ref, use_ref_cell, kpoints, dft_control, mos, sab_orb, sab_all, qmmm, qmmm_periodic, sac_ae, sac_ppl, sac_lri, sap_ppnl, sab_vdw, sab_scp, sap_oce, sab_lrc, sab_se, sab_xtbe, sab_tbe, sab_core, sab_xb, sab_xtb_nonbond, sab_almo, sab_kp, sab_kp_nosym, particle_set, energy, force, matrix_h, matrix_h_im, matrix_ks, matrix_ks_im, matrix_vxc, run_rtp, rtp, matrix_h_kp, matrix_h_im_kp, matrix_ks_kp, matrix_ks_im_kp, matrix_vxc_kp, kinetic_kp, matrix_s_kp, matrix_w_kp, matrix_s_RI_aux_kp, matrix_s, matrix_s_RI_aux, matrix_w, matrix_p_mp2, matrix_p_mp2_admm, rho, rho_xc, pw_env, ewald_env, ewald_pw, active_space, mpools, input, para_env, blacs_env, scf_control, rel_control, kinetic, qs_charges, vppl, rho_core, rho_nlcc, rho_nlcc_g, ks_env, ks_qmmm_env, wf_history, scf_env, local_particles, local_molecules, distribution_2d, dbcsr_dist, molecule_kind_set, molecule_set, subsys, cp_subsys, oce, local_rho_set, rho_atom_set, task_list, task_list_soft, rho0_atom_set, rho0_mpole, rhoz_set, ecoul_1c, rho0_s_rs, rho0_s_gs, do_kpoints, has_unit_metric, requires_mo_derivs, mo_derivs, mo_loc_history, nkind, natom, nelectron_total, nelectron_spin, efield, neighbor_list_id, linres_control, xas_env, virial, cp_ddapc_env, cp_ddapc_ewald, outer_scf_history, outer_scf_ihistory, x_data, et_coupling, dftb_potential, results, se_taper, se_store_int_env, se_nddo_mpole, se_nonbond_env, admm_env, lri_env, lri_density, exstate_env, ec_env, dispersion_env, gcp_env, vee, rho_external, external_vxc, mask, mp2_env, bs_env, kg_env, WannierCentres, atprop, ls_scf_env, do_transport, transport_env, v_hartree_rspace, s_mstruct_changed, rho_changed, potential_changed, forces_up_to_date, mscfg_env, almo_scf_env, gradient_history, variable_history, embed_pot, spin_embed_pot, polar_env, mos_last_converged, rhs)
Get the QUICKSTEP environment.
subroutine, public qs_env_release(qs_env)
releases the given qs_env (see doc/ReferenceCounting.html)