(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_nnp.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 Creates the NNP section of the input
10!> \author Christoph Schran (christoph.schran@rub.de)
11!> \date 2020-10-10
12! **************************************************************************************************
14
15 USE bibliography, ONLY: behler2007,&
21 USE cp_units, ONLY: cp_unit_to_cp2k
30 USE input_val_types, ONLY: char_t,&
31 real_t
32 USE kinds, ONLY: dp
33#include "./base/base_uses.f90"
34
35 IMPLICIT NONE
36 PRIVATE
37
38 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
39 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_nnp'
40
41 PUBLIC :: create_nnp_section
42
43CONTAINS
44
45! **************************************************************************************************
46!> \brief Create the input section for NNP
47!> \param section the section to create
48!> \date 2020-10-10
49!> \author Christoph Schran (christoph.schran@rub.de)
50! **************************************************************************************************
51 SUBROUTINE create_nnp_section(section)
52 TYPE(section_type), POINTER :: section
53
54 TYPE(keyword_type), POINTER :: keyword
55 TYPE(section_type), POINTER :: subsection, subsubsection
56
57 cpassert(.NOT. ASSOCIATED(section))
58 CALL section_create(section, __location__, name="NNP", &
59 description="This section contains all information to run a "// &
60 "Neural Network Potential (NNP) calculation.", &
61 n_keywords=3, n_subsections=3, repeats=.false., &
63
64 NULLIFY (subsection, subsubsection, keyword)
65
66 CALL keyword_create(keyword, __location__, name="NNP_INPUT_FILE_NAME", &
67 description="File containing the input information for "// &
68 "the setup of the NNP (n2p2/RuNNer format).", &
69 repeats=.false., default_lc_val="input.nn")
70 CALL section_add_keyword(section, keyword)
71 CALL keyword_release(keyword)
72 CALL keyword_create(keyword, __location__, name="SCALE_FILE_NAME", &
73 description="File containing the scaling information for "// &
74 "the symmetry functions of the NNP.", &
75 repeats=.false., default_lc_val="scaling.data")
76 CALL section_add_keyword(section, keyword)
77 CALL keyword_release(keyword)
78
79 ! BIAS subsection
80 CALL section_create(subsection, __location__, name="BIAS", &
81 description="Section to bias the committee disagreement (sigma) by "// &
82 "E = 0.5 * K_B * (sigma - SIGMA_0)**2, if sigma > SIGMA_0.", &
83 n_keywords=2, n_subsections=0, repeats=.false., &
84 citations=(/schran2020b/))
85 CALL keyword_create(keyword, __location__, name="K_B", &
86 description="Harmonic spring constant of the bias potential [1/hartree].", &
87 repeats=.false., &
88 n_var=1, &
89 type_of_var=real_t, &
90 default_r_val=cp_unit_to_cp2k(value=0.1_dp, unit_str="hartree^-1"), &
91 unit_str="hartree^-1", &
92 usage="K_B [hartree^-1] 0.1")
93 CALL section_add_keyword(subsection, keyword)
94 CALL keyword_release(keyword)
95 CALL keyword_create(keyword, __location__, name="SIGMA_0", &
96 description="Shift of the harmonic bias potential.", &
97 repeats=.false., &
98 n_var=1, &
99 type_of_var=real_t, &
100 default_r_val=cp_unit_to_cp2k(value=0.1_dp, unit_str="hartree"), &
101 unit_str="hartree", &
102 usage="SIGMA_0 [hartree] 0.1")
103 CALL section_add_keyword(subsection, keyword)
104 CALL keyword_release(keyword)
105 CALL keyword_create(keyword, __location__, name="ALIGN_NNP_ENERGIES", &
106 description="Remove PES shifts within the committee by "// &
107 "subtracting energy for each committee member. Provide "// &
108 "one number per C-NNP member.", &
109 repeats=.false., &
110 n_var=-1, &
111 type_of_var=real_t, &
112 usage="ALIGN_NNP_ENERGIES <REAL> <REAL> ... <REAL>")
113 CALL section_add_keyword(subsection, keyword)
114 CALL keyword_release(keyword)
115 ! print bias subsubsection:
116 CALL create_nnp_bias_print_section(subsubsection)
117 CALL section_add_subsection(subsection, subsubsection)
118 CALL section_release(subsubsection)
119
120 CALL section_add_subsection(section, subsection)
121 CALL section_release(subsection)
122 ! end BIAS subsection
123
124 CALL section_create(subsection, __location__, name="MODEL", &
125 description="Section for a single NNP model. "// &
126 "If this section is repeated, a committee model (C-NNP) "// &
127 "is used where the NNP members share the same symmetry functions.", &
128 n_keywords=1, n_subsections=0, repeats=.true.)
129 CALL keyword_create(keyword, __location__, name="WEIGHTS", &
130 description="File containing the weights for the "// &
131 "artificial neural networks of the NNP. "// &
132 "The specified name is extended by .XXX.data", &
133 repeats=.false., default_lc_val="weights")
134 CALL section_add_keyword(subsection, keyword)
135 CALL keyword_release(keyword)
136 CALL section_add_subsection(section, subsection)
137 CALL section_release(subsection)
138
139 CALL create_nnp_print_section(subsection)
140 CALL section_add_subsection(section, subsection)
141 CALL section_release(subsection)
142
143 END SUBROUTINE create_nnp_section
144
145! **************************************************************************************************
146!> \brief Creates the print section for the nnp subsection
147!> \param section the section to create
148!> \date 2020-10-10
149!> \author Christoph Schran (christoph.schran@rub.de)
150! **************************************************************************************************
151 SUBROUTINE create_nnp_print_section(section)
152 TYPE(section_type), POINTER :: section
153
154 TYPE(keyword_type), POINTER :: keyword
155 TYPE(section_type), POINTER :: print_key
156
157 cpassert(.NOT. ASSOCIATED(section))
158 CALL section_create(section, __location__, name="PRINT", &
159 description="Section of possible print options in NNP code.", &
160 n_keywords=0, n_subsections=5, repeats=.false.)
161
162 NULLIFY (print_key, keyword)
163
164 CALL cp_print_key_section_create(print_key, __location__, "ENERGIES", &
165 description="Controls the printing of the NNP energies.", &
166 print_level=medium_print_level, common_iter_levels=1)
167 CALL section_add_subsection(section, print_key)
168 CALL section_release(print_key)
169
170 CALL cp_print_key_section_create(print_key, __location__, "FORCES", &
171 description="Controls the printing of the NNP forces.", &
172 print_level=medium_print_level, common_iter_levels=1)
173 CALL section_add_subsection(section, print_key)
174 CALL section_release(print_key)
175
176 CALL cp_print_key_section_create(print_key, __location__, "FORCES_SIGMA", &
177 description="Controls the printing of the STD per atom of the NNP forces.", &
178 print_level=medium_print_level, common_iter_levels=1)
179 CALL section_add_subsection(section, print_key)
180 CALL section_release(print_key)
181
182 CALL cp_print_key_section_create(print_key, __location__, "EXTRAPOLATION", &
183 description="If activated, output structures with extrapolation "// &
184 "warning in xyz-format", &
185 print_level=medium_print_level, common_iter_levels=1)
186 CALL section_add_subsection(section, print_key)
187 CALL section_release(print_key)
188
189 CALL cp_print_key_section_create(print_key, __location__, "SUM_FORCE", &
190 description="If activated, output summed force over specified atoms. "// &
191 "Used in Green-Kubo relation for friction at liquid-solid interfaces.", &
192 print_level=medium_print_level, common_iter_levels=1)
193
194 CALL keyword_create(keyword, __location__, name="ATOM_LIST", &
195 description="List of atoms over which to calculate summed force", &
196 usage="ATOM_LISTS {O} {H} .. {X}", repeats=.false., &
197 n_var=-1, type_of_var=char_t)
198 CALL section_add_keyword(print_key, keyword)
199 CALL keyword_release(keyword)
200
201 CALL section_add_subsection(section, print_key)
202 CALL section_release(print_key)
203
204 END SUBROUTINE create_nnp_print_section
205
206! **************************************************************************************************
207!> \brief Creates the print section for the nnp bias subsubsection
208!> \param section the section to create
209!> \date 2020-10-10
210!> \author Christoph Schran (christoph.schran@rub.de)
211! **************************************************************************************************
212 SUBROUTINE create_nnp_bias_print_section(section)
213 TYPE(section_type), POINTER :: section
214
215 TYPE(section_type), POINTER :: print_key
216
217 cpassert(.NOT. ASSOCIATED(section))
218 CALL section_create(section, __location__, name="PRINT", &
219 description="Section of possible print options in NNP code.", &
220 n_keywords=0, n_subsections=3, repeats=.false.)
221
222 NULLIFY (print_key)
223
224 CALL cp_print_key_section_create(print_key, __location__, "BIAS_ENERGY", &
225 description="Controls the printing of the BIAS energy.", &
226 print_level=medium_print_level, common_iter_levels=1)
227 CALL section_add_subsection(section, print_key)
228 CALL section_release(print_key)
229
230 CALL cp_print_key_section_create(print_key, __location__, "BIAS_FORCES", &
231 description="Controls the printing of the BIAS forces.", &
232 print_level=medium_print_level, common_iter_levels=1)
233 CALL section_add_subsection(section, print_key)
234 CALL section_release(print_key)
235
236 END SUBROUTINE create_nnp_bias_print_section
237
238END MODULE input_cp2k_nnp
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public schran2020b
integer, save, public schran2020a
integer, save, public behler2011
integer, save, public behler2007
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public medium_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
Creates the NNP section of the input.
subroutine, public create_nnp_section(section)
Create the input section for NNP.
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
integer, parameter, public char_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
represent a keyword in the input
represent a section of the input file