(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_barostats.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!> \par History
10!> 10.2005 split input_cp2k into smaller modules [fawzi]
11!> \author teo & fawzi
12! **************************************************************************************************
14 USE barostat_types, ONLY: do_clv_x,&
15 do_clv_xy,&
17 do_clv_xz,&
18 do_clv_y,&
19 do_clv_yz,&
23 USE cp_units, ONLY: cp_unit_to_cp2k
35 USE input_val_types, ONLY: real_t
36 USE kinds, ONLY: dp
37 USE string_utilities, ONLY: s2a
38#include "../../base/base_uses.f90"
39
40 IMPLICIT NONE
41 PRIVATE
42
43 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
44 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_barostats'
45
47
48!***
49CONTAINS
50
51! **************************************************************************************************
52!> \brief ...
53!> \param section will contain the coeff section
54!> \author teo
55! **************************************************************************************************
56 SUBROUTINE create_barostat_section(section)
57 TYPE(section_type), POINTER :: section
58
59 TYPE(keyword_type), POINTER :: keyword
60 TYPE(section_type), POINTER :: subsection, thermo_section
61
62 cpassert(.NOT. ASSOCIATED(section))
63 CALL section_create(section, __location__, name="barostat", &
64 description="Parameters of barostat.", &
65 n_keywords=1, n_subsections=0, repeats=.false.)
66
67 NULLIFY (keyword, subsection, thermo_section)
68 CALL keyword_create(keyword, __location__, name="PRESSURE", &
69 description="Initial pressure", &
70 usage="PRESSURE real", &
71 default_r_val=0._dp, unit_str='bar')
72 CALL section_add_keyword(section, keyword)
73 CALL keyword_release(keyword)
74
75 CALL keyword_create(keyword, __location__, name="TIMECON", &
76 description="Barostat time constant", &
77 usage="TIMECON real", &
78 default_r_val=cp_unit_to_cp2k(1000.0_dp, "fs"), &
79 unit_str='fs')
80 CALL section_add_keyword(section, keyword)
81 CALL keyword_release(keyword)
82
83 CALL keyword_create(keyword, __location__, name="TEMPERATURE", &
84 description="Barostat initial temperature. If not set, the ensemble temperature is used instead.", &
85 usage="TEMPERATURE real", type_of_var=real_t, &
86 unit_str='K')
87 CALL section_add_keyword(section, keyword)
88 CALL keyword_release(keyword)
89
90 CALL keyword_create(keyword, __location__, name="TEMP_TOL", &
91 description="Maximum oscillation of the Barostat temperature imposed by rescaling.", &
92 usage="TEMP_TOL real", default_r_val=0._dp, &
93 unit_str='K')
94 CALL section_add_keyword(section, keyword)
95 CALL keyword_release(keyword)
96
97 CALL keyword_create(keyword, __location__, name="VIRIAL", &
98 description="For NPT_F only: allows the screening of one or more components of the virial in order"// &
99 " to relax the cell only along specific cartesian axis", &
100 usage="VIRIAL (XYZ | X | Y | Z | XY| XZ | YZ)", &
101 enum_c_vals=s2a("XYZ", "X", "Y", "Z", "XY", "XZ", "YZ"), &
103 default_i_val=do_clv_xyz)
104 CALL section_add_keyword(section, keyword)
105 CALL keyword_release(keyword)
106
107 CALL create_velocity_section(subsection, "BAROSTAT")
108 CALL section_add_subsection(section, subsection)
109 CALL section_release(subsection)
110
111 CALL create_mass_section(subsection, "BAROSTAT")
112 CALL section_add_subsection(section, subsection)
113 CALL section_release(subsection)
114
115 CALL create_thermostat_section(thermo_section, coupled_thermostat=.true.)
116 CALL section_add_subsection(section, thermo_section)
117 CALL section_release(thermo_section)
118
119 CALL create_print_section(subsection)
120 CALL section_add_subsection(section, subsection)
121 CALL section_release(subsection)
122
123 END SUBROUTINE create_barostat_section
124
125! **************************************************************************************************
126!> \brief Creates print section for barostat section
127!> \param section ...
128!> \author teo [tlaino] - University of Zurich - 02.2008
129! **************************************************************************************************
130 SUBROUTINE create_print_section(section)
131 TYPE(section_type), POINTER :: section
132
133 TYPE(section_type), POINTER :: print_key
134
135 cpassert(.NOT. ASSOCIATED(section))
136 NULLIFY (print_key)
137 CALL section_create(section, __location__, name="PRINT", &
138 description="Collects all print_keys for barostat", &
139 n_keywords=1, n_subsections=0, repeats=.false.)
140
141 CALL cp_print_key_section_create(print_key, __location__, "ENERGY", &
142 description="Controls the output of kinetic energy, and potential energy "// &
143 "of the defined barostat.", print_level=high_print_level, common_iter_levels=1, &
144 filename="")
145 CALL section_add_subsection(section, print_key)
146 CALL section_release(print_key)
147 END SUBROUTINE create_print_section
148
149END MODULE input_cp2k_barostats
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
integer, parameter, public do_clv_xy
integer, parameter, public do_clv_z
integer, parameter, public do_clv_xz
integer, parameter, public do_clv_x
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public high_print_level
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
unit conversion facility
Definition cp_units.F:30
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
Definition cp_units.F:1150
subroutine, public create_barostat_section(section)
...
subroutine, public create_mass_section(section, name)
Creates the mass section.
subroutine, public create_thermostat_section(section, coupled_thermostat)
Specifies parameter for thermostat for constant temperature ensembles.
subroutine, public create_velocity_section(section, name)
Creates the velocity section.
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_create(section, location, name, description, n_keywords, n_subsections, repeats, citations)
creates a list of keywords
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
subroutine, public section_add_subsection(section, subsection)
adds a subsection to the given section
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
a wrapper for basic fortran types.
integer, parameter, public real_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file