(git:374b731)
Loading...
Searching...
No Matches
barostat_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 Barostat structure: module containing barostat available for MD
10!> \author teo [tlaino] - University of Zurich - 09.2007
11! **************************************************************************************************
13 USE cell_types, ONLY: cell_type
30 USE kinds, ONLY: dp
31 USE simpar_types, ONLY: simpar_type
32#include "../../base/base_uses.f90"
33
34 IMPLICIT NONE
35
36 INTEGER, PARAMETER, PUBLIC :: do_clv_geo_center = 0, &
37 do_clv_fix_point = 1, &
38 do_clv_xyz = 0, &
39 do_clv_x = 1, &
40 do_clv_y = 2, &
41 do_clv_z = 3, &
42 do_clv_xy = 4, &
43 do_clv_xz = 5, &
44 do_clv_yz = 6
45
46 PRIVATE
47 PUBLIC :: barostat_type, &
50
51! **************************************************************************************************
53 INTEGER :: ref_count = 0
54 INTEGER :: virial_components = do_clv_geo_center
55 REAL(kind=dp) :: temp_ext = 0.0_dp
56 TYPE(npt_info_type), POINTER :: npt(:, :) => null()
57 TYPE(section_vals_type), POINTER :: section => null()
58 END TYPE barostat_type
59
60! *** Global parameters ***
61
62 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'barostat_types'
63
64CONTAINS
65
66! **************************************************************************************************
67!> \brief ...
68!> \param barostat ...
69!> \param md_section ...
70!> \param force_env ...
71!> \param simpar ...
72!> \param globenv ...
73!> \par History
74!> 09.2007 created [tlaino]
75!> \author Teodoro Laino
76! **************************************************************************************************
77 SUBROUTINE create_barostat_type(barostat, md_section, force_env, simpar, &
78 globenv)
79 TYPE(barostat_type), POINTER :: barostat
80 TYPE(section_vals_type), POINTER :: md_section
81 TYPE(force_env_type), POINTER :: force_env
82 TYPE(simpar_type), POINTER :: simpar
83 TYPE(global_environment_type), POINTER :: globenv
84
85 LOGICAL :: check, explicit
86 TYPE(cell_type), POINTER :: cell
87 TYPE(section_vals_type), POINTER :: barostat_section
88
89 check = .NOT. ASSOCIATED(barostat)
90 cpassert(check)
91 barostat_section => section_vals_get_subs_vals(md_section, "BAROSTAT")
92 CALL section_vals_get(barostat_section, explicit=explicit)
93 IF (simpar%ensemble == npt_i_ensemble .OR. &
94 simpar%ensemble == npt_ia_ensemble .OR. &
95 simpar%ensemble == npt_f_ensemble .OR. &
96 simpar%ensemble == npe_f_ensemble .OR. &
97 simpar%ensemble == npe_i_ensemble .OR. &
98 simpar%ensemble == nph_uniaxial_ensemble .OR. &
99 simpar%ensemble == nph_uniaxial_damped_ensemble) THEN
100 ALLOCATE (barostat)
101 barostat%ref_count = 1
102 barostat%section => barostat_section
103 NULLIFY (barostat%npt)
104 CALL force_env_get(force_env, cell=cell)
105
106 barostat%temp_ext = simpar%temp_baro_ext
107 CALL section_vals_val_get(barostat_section, "TEMP_TOL", r_val=simpar%temp_baro_tol)
108 ! Initialize or possibly restart Barostat
109 CALL initialize_npt(simpar, globenv, barostat%npt, &
110 cell, work_section=barostat_section)
111
112 ! If none of the possible barostat has been allocated let's deallocate
113 ! the full structure
114 IF (.NOT. ASSOCIATED(barostat%npt)) THEN
115 CALL release_barostat_type(barostat)
116 END IF
117
118 ! User defined virial screening
119 CALL section_vals_val_get(barostat_section, "VIRIAL", i_val=barostat%virial_components)
120 check = barostat%virial_components == do_clv_xyz .OR. simpar%ensemble == npt_f_ensemble
121 IF (.NOT. check) &
122 CALL cp_abort(__location__, "The screening of the components of "// &
123 "the virial is available only with the NPT_F ensemble!")
124 ELSE
125 IF (explicit) &
126 CALL cp_warn(__location__, &
127 "A barostat has been defined with an MD ensemble which does not support barostat! "// &
128 "Its definition will be ignored!")
129 END IF
130
131 END SUBROUTINE create_barostat_type
132
133! **************************************************************************************************
134!> \brief ...
135!> \param barostat ...
136!> \par History
137!> 09.2007 created [tlaino]
138!> \author Teodoro Laino
139! **************************************************************************************************
140 SUBROUTINE release_barostat_type(barostat)
141 TYPE(barostat_type), POINTER :: barostat
142
143 LOGICAL :: check
144
145 IF (ASSOCIATED(barostat)) THEN
146 check = barostat%ref_count > 0
147 cpassert(check)
148 barostat%ref_count = barostat%ref_count - 1
149 IF (barostat%ref_count < 1) THEN
150 IF (ASSOCIATED(barostat%npt)) THEN
151 DEALLOCATE (barostat%npt)
152 END IF
153 NULLIFY (barostat%section)
154 DEALLOCATE (barostat)
155 END IF
156 END IF
157
158 END SUBROUTINE release_barostat_type
159
160END MODULE barostat_types
Barostat structure: module containing barostat available for MD.
integer, parameter, public do_clv_y
integer, parameter, public do_clv_xyz
integer, parameter, public do_clv_yz
subroutine, public create_barostat_type(barostat, md_section, force_env, simpar, globenv)
...
subroutine, public release_barostat_type(barostat)
...
integer, parameter, public do_clv_xy
integer, parameter, public do_clv_geo_center
integer, parameter, public do_clv_z
integer, parameter, public do_clv_fix_point
integer, parameter, public do_clv_xz
integer, parameter, public do_clv_x
Handles all functions related to the CELL.
Definition cell_types.F:15
subroutine, public initialize_npt(simpar, globenv, npt_info, cell, work_section)
...
Lumps all possible extended system variables into one type for easy access and passing.
Interface for the force calculations.
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
Define type storing the global information of a run. Keep the amount of stored data small....
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public nph_uniaxial_ensemble
integer, parameter, public npt_i_ensemble
integer, parameter, public nph_uniaxial_damped_ensemble
integer, parameter, public npe_f_ensemble
integer, parameter, public npe_i_ensemble
integer, parameter, public npt_ia_ensemble
integer, parameter, public npt_f_ensemble
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_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
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Type for storing MD parameters.
Type defining parameters related to the simulation cell.
Definition cell_types.F:55
wrapper to abstract the force evaluation of the various methods
contains the initially parsed file and the initial parallel environment
Simulation parameter type for molecular dynamics.