Line data Source code
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 : ! **************************************************************************************************
12 : MODULE barostat_types
13 : USE cell_types, ONLY: cell_type
14 : USE extended_system_init, ONLY: initialize_npt
15 : USE extended_system_types, ONLY: npt_info_type
16 : USE force_env_types, ONLY: force_env_get,&
17 : force_env_type
18 : USE global_types, ONLY: global_environment_type
19 : USE input_constants, ONLY: npe_f_ensemble,&
20 : npe_i_ensemble,&
21 : nph_uniaxial_damped_ensemble,&
22 : nph_uniaxial_ensemble,&
23 : npt_f_ensemble,&
24 : npt_i_ensemble,&
25 : npt_ia_ensemble
26 : USE input_section_types, ONLY: section_vals_get,&
27 : section_vals_get_subs_vals,&
28 : section_vals_type,&
29 : section_vals_val_get
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, &
48 : create_barostat_type, &
49 : release_barostat_type
50 :
51 : ! **************************************************************************************************
52 : TYPE barostat_type
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 :
64 : CONTAINS
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 3572 : 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 1786 : check = .NOT. ASSOCIATED(barostat)
90 1786 : CPASSERT(check)
91 1786 : barostat_section => section_vals_get_subs_vals(md_section, "BAROSTAT")
92 1786 : 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 1786 : simpar%ensemble == nph_uniaxial_ensemble .OR. &
99 : simpar%ensemble == nph_uniaxial_damped_ensemble) THEN
100 172 : ALLOCATE (barostat)
101 172 : barostat%ref_count = 1
102 172 : barostat%section => barostat_section
103 : NULLIFY (barostat%npt)
104 172 : CALL force_env_get(force_env, cell=cell)
105 :
106 172 : barostat%temp_ext = simpar%temp_baro_ext
107 172 : 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 172 : cell, work_section=barostat_section)
111 :
112 : ! If none of the possible barostat has been allocated let's deallocate
113 : ! the full structure
114 172 : IF (.NOT. ASSOCIATED(barostat%npt)) THEN
115 0 : CALL release_barostat_type(barostat)
116 : END IF
117 :
118 : ! User defined virial screening
119 172 : CALL section_vals_val_get(barostat_section, "VIRIAL", i_val=barostat%virial_components)
120 172 : 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 0 : "the virial is available only with the NPT_F ensemble!")
124 : ELSE
125 1614 : IF (explicit) &
126 : CALL cp_warn(__LOCATION__, &
127 : "A barostat has been defined with an MD ensemble which does not support barostat! "// &
128 2 : "Its definition will be ignored!")
129 : END IF
130 :
131 1786 : 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 1786 : SUBROUTINE release_barostat_type(barostat)
141 : TYPE(barostat_type), POINTER :: barostat
142 :
143 : LOGICAL :: check
144 :
145 1786 : IF (ASSOCIATED(barostat)) THEN
146 172 : check = barostat%ref_count > 0
147 172 : CPASSERT(check)
148 172 : barostat%ref_count = barostat%ref_count - 1
149 172 : IF (barostat%ref_count < 1) THEN
150 172 : IF (ASSOCIATED(barostat%npt)) THEN
151 172 : DEALLOCATE (barostat%npt)
152 : END IF
153 172 : NULLIFY (barostat%section)
154 172 : DEALLOCATE (barostat)
155 : END IF
156 : END IF
157 :
158 1786 : END SUBROUTINE release_barostat_type
159 :
160 0 : END MODULE barostat_types
|