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 Creates the NNP section of the input
10 : !> \author Christoph Schran (christoph.schran@rub.de)
11 : !> \date 2020-10-10
12 : ! **************************************************************************************************
13 : MODULE input_cp2k_nnp
14 :
15 : USE bibliography, ONLY: Behler2007,&
16 : Behler2011,&
17 : Schran2020a,&
18 : Schran2020b
19 : USE cp_output_handling, ONLY: cp_print_key_section_create,&
20 : medium_print_level
21 : USE cp_units, ONLY: cp_unit_to_cp2k
22 : USE input_keyword_types, ONLY: keyword_create,&
23 : keyword_release,&
24 : keyword_type
25 : USE input_section_types, ONLY: section_add_keyword,&
26 : section_add_subsection,&
27 : section_create,&
28 : section_release,&
29 : section_type
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 :
43 : CONTAINS
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 8530 : 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 8530 : 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., &
62 42650 : citations=(/Behler2007, Behler2011, Schran2020a, Schran2020b/))
63 :
64 8530 : 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 8530 : repeats=.FALSE., default_lc_val="input.nn")
70 8530 : CALL section_add_keyword(section, keyword)
71 8530 : 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 8530 : repeats=.FALSE., default_lc_val="scaling.data")
76 8530 : CALL section_add_keyword(section, keyword)
77 8530 : 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 17060 : 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 8530 : usage="K_B [hartree^-1] 0.1")
93 8530 : CALL section_add_keyword(subsection, keyword)
94 8530 : 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 8530 : usage="SIGMA_0 [hartree] 0.1")
103 8530 : CALL section_add_keyword(subsection, keyword)
104 8530 : 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 8530 : usage="ALIGN_NNP_ENERGIES <REAL> <REAL> ... <REAL>")
113 8530 : CALL section_add_keyword(subsection, keyword)
114 8530 : CALL keyword_release(keyword)
115 : ! print bias subsubsection:
116 8530 : CALL create_nnp_bias_print_section(subsubsection)
117 8530 : CALL section_add_subsection(subsection, subsubsection)
118 8530 : CALL section_release(subsubsection)
119 :
120 8530 : CALL section_add_subsection(section, subsection)
121 8530 : 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 8530 : 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 8530 : repeats=.FALSE., default_lc_val="weights")
134 8530 : CALL section_add_keyword(subsection, keyword)
135 8530 : CALL keyword_release(keyword)
136 8530 : CALL section_add_subsection(section, subsection)
137 8530 : CALL section_release(subsection)
138 :
139 8530 : CALL create_nnp_print_section(subsection)
140 8530 : CALL section_add_subsection(section, subsection)
141 8530 : CALL section_release(subsection)
142 :
143 8530 : 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 8530 : 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 8530 : CPASSERT(.NOT. ASSOCIATED(section))
158 : CALL section_create(section, __LOCATION__, name="PRINT", &
159 : description="Section of possible print options in NNP code.", &
160 8530 : n_keywords=0, n_subsections=5, repeats=.FALSE.)
161 :
162 8530 : 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 8530 : print_level=medium_print_level, common_iter_levels=1)
167 8530 : CALL section_add_subsection(section, print_key)
168 8530 : 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 8530 : print_level=medium_print_level, common_iter_levels=1)
173 8530 : CALL section_add_subsection(section, print_key)
174 8530 : 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 8530 : print_level=medium_print_level, common_iter_levels=1)
179 8530 : CALL section_add_subsection(section, print_key)
180 8530 : 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 8530 : print_level=medium_print_level, common_iter_levels=1)
186 8530 : CALL section_add_subsection(section, print_key)
187 8530 : 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 8530 : 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 8530 : n_var=-1, type_of_var=char_t)
198 8530 : CALL section_add_keyword(print_key, keyword)
199 8530 : CALL keyword_release(keyword)
200 :
201 8530 : CALL section_add_subsection(section, print_key)
202 8530 : CALL section_release(print_key)
203 :
204 8530 : 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 8530 : SUBROUTINE create_nnp_bias_print_section(section)
213 : TYPE(section_type), POINTER :: section
214 :
215 : TYPE(section_type), POINTER :: print_key
216 :
217 8530 : CPASSERT(.NOT. ASSOCIATED(section))
218 : CALL section_create(section, __LOCATION__, name="PRINT", &
219 : description="Section of possible print options in NNP code.", &
220 8530 : n_keywords=0, n_subsections=3, repeats=.FALSE.)
221 :
222 8530 : 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 8530 : print_level=medium_print_level, common_iter_levels=1)
227 8530 : CALL section_add_subsection(section, print_key)
228 8530 : 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 8530 : print_level=medium_print_level, common_iter_levels=1)
233 8530 : CALL section_add_subsection(section, print_key)
234 8530 : CALL section_release(print_key)
235 :
236 8530 : END SUBROUTINE create_nnp_bias_print_section
237 :
238 : END MODULE input_cp2k_nnp
|