(git:374b731)
Loading...
Searching...
No Matches
input_optimize_basis.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 builds the input structure for optimize_basis
10!> \par History
11!> 03.2012 created [Florian Schiffmann]
12!> \author Florian Schiffmann
13! **************************************************************************************************
15
16 USE input_constants, ONLY: do_opt_all,&
28 USE input_val_types, ONLY: char_t,&
29 integer_t,&
30 real_t
31 USE kinds, ONLY: dp
32 USE string_utilities, ONLY: s2a
33#include "./base/base_uses.f90"
34
35 IMPLICIT NONE
36 PRIVATE
37
38 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_optimize_basis'
40
41CONTAINS
42
43! **************************************************************************************************
44!> \brief creates the optimize_basis section
45!> \param section ...
46!> \author Florian Schiffmann
47! **************************************************************************************************
49 TYPE(section_type), POINTER :: section
50
51 TYPE(keyword_type), POINTER :: keyword
52 TYPE(section_type), POINTER :: subsection
53
54 cpassert(.NOT. ASSOCIATED(section))
55 CALL section_create(section, __location__, name="OPTIMIZE_BASIS", &
56 description="describes a basis optimization job, in which an ADMM like approach is used to"// &
57 " find the best exponents and/or coefficients to match a given training set.", &
58 repeats=.false.)
59 NULLIFY (keyword, subsection)
60
61 CALL keyword_create(keyword, __location__, name="BASIS_TEMPLATE_FILE", &
62 description="Name of the basis set file, containing the structure of the new basis set", &
63 usage="BASIS_TEMPLATE_FILE <FILENAME>", &
64 type_of_var=char_t, repeats=.false., &
65 default_c_val="BASIS_SET", n_var=-1)
66 CALL section_add_keyword(section, keyword)
67 CALL keyword_release(keyword)
68
69 CALL keyword_create(keyword, __location__, name="BASIS_WORK_FILE", &
70 description="Name of the basis set file which is created to be read as initial guess", &
71 usage="BASIS_WORK_FILE <FILENAME>", &
72 type_of_var=char_t, repeats=.false., &
73 default_c_val="BASIS_WORK_FILE", n_var=-1)
74 CALL section_add_keyword(section, keyword)
75 CALL keyword_release(keyword)
76
77 CALL keyword_create(keyword, __location__, name="BASIS_OUTPUT_FILE", &
78 description="Name of the basis set file containing the optimized basis", &
79 usage="BASIS_OUTPUT_FILE <FILENAME>", &
80 type_of_var=char_t, repeats=.false., &
81 default_c_val="BASIS_OUTPUT_FILE", n_var=-1)
82 CALL section_add_keyword(section, keyword)
83 CALL keyword_release(keyword)
84
85 CALL keyword_create(keyword, __location__, name="WRITE_FREQUENCY", &
86 description="Frequency at which the intermediate results should be written", &
87 usage="WRITE_FREQUENCY 1000", &
88 default_i_val=5000)
89 CALL section_add_keyword(section, keyword)
90 CALL keyword_release(keyword)
91
92 CALL keyword_create(keyword, __location__, name="USE_CONDITION_NUMBER", &
93 description="Determines whether condition number should be part of optimization or not", &
94 usage="USE_CONDITION_NUMBER", &
95 default_l_val=.false., lone_keyword_l_val=.true.)
96 CALL section_add_keyword(section, keyword)
97 CALL keyword_release(keyword)
98
99 CALL keyword_create( &
100 keyword, __location__, name="BASIS_COMBINATIONS", &
101 description="If multiple atomic kinds are fitted at the same time, this keyword "// &
102 "allows to specify which basis sets should be used together in optimization (underived set ID=0). "// &
103 "If skipped all combinations are used. The order is taken as the kinds and sets are specified in the input", &
104 repeats=.true., &
105 usage="BASIS_COMBINATIONS SET_ID(KIND1) SET_ID(KIND2) ... ", type_of_var=integer_t, n_var=-1)
106 CALL section_add_keyword(section, keyword)
107 CALL keyword_release(keyword)
108
109 CALL keyword_create( &
110 keyword, __location__, name="RESIDUUM_WEIGHT", &
111 description="This keyword allows to give different weight factors to the "// &
112 "residuum of the different basis combinations. "// &
113 "The first entry corresponds to the original basis sets. Every further value is assigned to the combinations "// &
114 "in the order given for BASIS_COMBINATIONS.", &
115 repeats=.true., &
116 usage="RESIDUUM_WEIGHT REAL ", default_r_val=1.0_dp)
117 CALL section_add_keyword(section, keyword)
118 CALL keyword_release(keyword)
119
120 CALL keyword_create( &
121 keyword, __location__, name="CONDITION_WEIGHT", &
122 description="This keyword allows to give different weight factors to the "// &
123 "condition number of different basis combinations (LOG(cond) is used). "// &
124 "The first entry corresponds to the original basis sets. Every further value is assigned to the combinations "// &
125 "in the order given for BASIS_COMBINATIONS.", &
126 repeats=.true., &
127 usage="CONTITION_WEIGHT REAL ", default_r_val=1.0_dp)
128 CALL section_add_keyword(section, keyword)
129 CALL keyword_release(keyword)
130
131 CALL keyword_create(keyword, __location__, name="GROUP_PARTITION", &
132 description="Allows the specification of the group mpi group sizes in parallel "// &
133 "runs. If less Groups than tasks are speciefied, consecutive calculations "// &
134 "Will be assigned to one group (derived basis sets and then training sets) "// &
135 "If keyword is skipped, equal group sizes will be generated trying to fit all calculations.", &
136 repeats=.true., &
137 usage="GROUP_PARTITION INT INT ... ", type_of_var=integer_t, n_var=-1)
138 CALL section_add_keyword(section, keyword)
139 CALL keyword_release(keyword)
140
141 CALL create_fit_kinds_section(subsection)
142 CALL section_add_subsection(section, subsection)
143 CALL section_release(subsection)
144
145 CALL create_training_section(subsection)
146 CALL section_add_subsection(section, subsection)
147 CALL section_release(subsection)
148
149 CALL create_powell_section(subsection)
150 CALL section_add_subsection(section, subsection)
151 CALL section_release(subsection)
152
153 END SUBROUTINE create_optimize_basis_section
154
155! **************************************************************************************************
156!> \brief ...
157!> \param section ...
158! **************************************************************************************************
159 SUBROUTINE create_fit_kinds_section(section)
160 TYPE(section_type), POINTER :: section
161
162 TYPE(keyword_type), POINTER :: keyword
163 TYPE(section_type), POINTER :: subsection
164
165 NULLIFY (keyword, subsection)
166 cpassert(.NOT. ASSOCIATED(section))
167 CALL section_create(section, __location__, name="FIT_KIND", &
168 description="specicifies the atomic kinds to be fitted and the basis"// &
169 " sets associated with the kind.", &
170 repeats=.true.)
171
172 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
173 description="The name of the kind described in this section.", &
174 usage="H", default_c_val="DEFAULT")
175 CALL section_add_keyword(section, keyword)
176 CALL keyword_release(keyword)
177
178 CALL keyword_create(keyword, __location__, name="BASIS_SET", &
179 description="The name of the basis set for the kind. Has to be specified in BASIS_TEMPLATE_FILE.", &
180 usage="H", default_c_val="DEFAULT")
181 CALL section_add_keyword(section, keyword)
182 CALL keyword_release(keyword)
183
184 CALL keyword_create(keyword, __location__, name="INITIAL_DEGREES_OF_FREEDOM", &
185 description="Specifies the initial degrees of freedom in the basis optimization. "// &
186 "This can be used to make further specifications easier", &
187 usage="INITIAL_DEGREES_OF_FREEDOM ALL", &
188 enum_c_vals=s2a("ALL", "NONE", "COEFFICIENTS", "EXPONENTS"), &
189 enum_desc=s2a("Set all parameters in the basis to be variable.", &
190 "Set all parameters in the basis to be fixed.", &
191 "Set all coefficients in the basis set to be variable.", &
192 "Set all exponents in the basis to be variable."), &
193 enum_i_vals=(/do_opt_all, do_opt_none, do_opt_coeff, do_opt_exps/), &
194 default_i_val=do_opt_coeff)
195 CALL section_add_keyword(section, keyword)
196 CALL keyword_release(keyword)
197
198 CALL keyword_create(keyword, __location__, name="SWITCH_COEFF_STATE", &
199 description="Allows to switch the state of a given coefficient from current state "// &
200 "(varibale/fixed)) to the opposite state. The three integers indicate "// &
201 "the set number, the angular momentum i'th contraction and i'th coefficient", repeats=.true., &
202 usage="SWITCH_COEFF_STATE SET L CONTRACTION IPGF", type_of_var=integer_t, n_var=4)
203 CALL section_add_keyword(section, keyword)
204 CALL keyword_release(keyword)
205
206 CALL keyword_create(keyword, __location__, name="SWITCH_CONTRACTION_STATE", &
207 description="Allows to switch the state of a given contraction from current state "// &
208 "(varibale/fixed)) to the opposite state. The three integers indicate "// &
209 "the set number, the angular momentum and i'th contraction ", repeats=.true., &
210 usage="SWITCH_CONTRACTION_STATE SET L CONTRACTION ", type_of_var=integer_t, n_var=3)
211 CALL section_add_keyword(section, keyword)
212 CALL keyword_release(keyword)
213
214 CALL keyword_create(keyword, __location__, name="SWITCH_EXP_STATE", &
215 description="Allows to switch the state of a given exponent from current state "// &
216 "(varibale/fixed)) to the opposite state. The two integers indicate "// &
217 "the set number and i'th exponent", repeats=.true., &
218 usage="SWITCH_EXP_STATE SET IEXP", type_of_var=integer_t, n_var=2)
219 CALL section_add_keyword(section, keyword)
220 CALL keyword_release(keyword)
221
222 CALL keyword_create(keyword, __location__, name="SWITCH_SET_STATE", &
223 description="Allows to switch the states of in a set from current state "// &
224 "(varibale/fixed)) to the opposite state. The two integers indicate "// &
225 "the affected part (0=ALL,1=EXPS,2=COEFF) and i'th set", repeats=.true., &
226 usage="SWITCH_SET_STATE SET IEXP", type_of_var=integer_t, n_var=2)
227 CALL section_add_keyword(section, keyword)
228 CALL keyword_release(keyword)
229
230 CALL create_constrain_exp_section(subsection)
231 CALL section_add_subsection(section, subsection)
232 CALL section_release(subsection)
233
234 CALL create_derived_sets_section(subsection)
235 CALL section_add_subsection(section, subsection)
236 CALL section_release(subsection)
237
238 END SUBROUTINE create_fit_kinds_section
239
240! **************************************************************************************************
241!> \brief ...
242!> \param section ...
243! **************************************************************************************************
244 SUBROUTINE create_derived_sets_section(section)
245 TYPE(section_type), POINTER :: section
246
247 TYPE(keyword_type), POINTER :: keyword
248
249 NULLIFY (keyword)
250 cpassert(.NOT. ASSOCIATED(section))
251 CALL section_create(section, __location__, name="DERIVED_BASIS_SETS", &
252 description="This section can be used to create subsets of a basis"// &
253 " which will be fitted at the same time. This is especially useful if connected"// &
254 " bsis sets e.g. TZVP, DZVP, SZV should be fitted.", &
255 repeats=.true.)
256
257 CALL keyword_create(keyword, __location__, name="BASIS_SET_NAME", &
258 description="Defines the name of the derived basis set, which will be "// &
259 "automatically generated otherwise.", &
260 usage="BASIS_SET_NAME {word}", &
261 type_of_var=char_t, &
262 repeats=.false., &
263 default_c_val="")
264 CALL section_add_keyword(section, keyword)
265 CALL keyword_release(keyword)
266
267 CALL keyword_create(keyword, __location__, name="REFERENCE_SET", &
268 description="Specifies the reference basis ID which is used as template to create the new set. "// &
269 "The original basis has ID 0. All following sets are counted in order as specified in the Input."// &
270 " The descriptors always assume the structure of the input basis set.", &
271 repeats=.false., usage="REFERNCE_SET INTEGER", default_i_val=0)
272 CALL section_add_keyword(section, keyword)
273 CALL keyword_release(keyword)
274
275 CALL keyword_create(keyword, __location__, name="REMOVE_CONTRACTION", &
276 description="Can be used to remove a contraction from the reference basis set. "// &
277 "The contraction is speciefied by set number, angular momentum and number of contraction."// &
278 " The descriptors always assume the structure of the input basis set.", &
279 repeats=.true., usage="REMOVE_CONTRACTION SET L ICONTRACTION", type_of_var=integer_t, n_var=3)
280 CALL section_add_keyword(section, keyword)
281 CALL keyword_release(keyword)
282
283 CALL keyword_create(keyword, __location__, name="REMOVE_SET", &
284 description="Can be used to remove a set from the reference basis set. ", &
285 repeats=.true., usage="REMOVE_SET SET", type_of_var=integer_t, n_var=1)
286 CALL section_add_keyword(section, keyword)
287 CALL keyword_release(keyword)
288
289 END SUBROUTINE create_derived_sets_section
290
291! **************************************************************************************************
292!> \brief ...
293!> \param section ...
294! **************************************************************************************************
295 SUBROUTINE create_constrain_exp_section(section)
296 TYPE(section_type), POINTER :: section
297
298 TYPE(keyword_type), POINTER :: keyword
299
300 NULLIFY (keyword)
301 cpassert(.NOT. ASSOCIATED(section))
302 CALL section_create(section, __location__, name="CONSTRAIN_EXPONENTS", &
303 description="specicifies constraints for the exponents to be fitted."// &
304 " Only a single constraint can be applied to an exponent", &
305 repeats=.true.)
306
307 CALL keyword_create(keyword, __location__, name="USE_EXP", &
308 description="Defines the exponent to be constraint. The two integers indicate "// &
309 "the set number and i'th exponent. The value -1 can be used to mark all sets/exponents in a set.", &
310 repeats=.false., usage="USE_EXP SET IEXP", type_of_var=integer_t, n_var=2)
311 CALL section_add_keyword(section, keyword)
312 CALL keyword_release(keyword)
313
314 CALL keyword_create(keyword, __location__, name="BOUNDARIES", &
315 description="Defines the boundaries to which the optimization is restricted."// &
316 " First value is the lower bound, second value is the upper bound.", &
317 repeats=.false., usage="BOUNDARIES LOWER UPPER", type_of_var=real_t, n_var=2)
318 CALL section_add_keyword(section, keyword)
319 CALL keyword_release(keyword)
320
321 CALL keyword_create(keyword, __location__, name="MAX_VAR_FRACTION", &
322 description="Defines the maximum fractionr by which the exponent is allowed to vary."// &
323 " e.g. 0.5 allows the exp to vary by 0.5*exp in both directions.", &
324 repeats=.false., usage="MAX_VAR_FRACTION REAL", type_of_var=real_t, n_var=1)
325 CALL section_add_keyword(section, keyword)
326 CALL keyword_release(keyword)
327
328 END SUBROUTINE create_constrain_exp_section
329
330! **************************************************************************************************
331!> \brief ...
332!> \param section ...
333! **************************************************************************************************
334 SUBROUTINE create_training_section(section)
335 TYPE(section_type), POINTER :: section
336
337 TYPE(keyword_type), POINTER :: keyword
338
339 NULLIFY (keyword)
340 cpassert(.NOT. ASSOCIATED(section))
341 CALL section_create(section, __location__, name="TRAINING_FILES", &
342 description="specicifies the location in which the files necessary for"// &
343 " fitting procedure are located. Each Training set needs a repetition of this section.", &
344 repeats=.true.)
345
346 CALL keyword_create(keyword, __location__, name="DIRECTORY", &
347 description="the directory in which the files are placed", &
348 usage="DIRECTORY /my/path", &
349 default_lc_val=".")
350 CALL section_add_keyword(section, keyword)
351 CALL keyword_release(keyword)
352
353 CALL keyword_create(keyword, __location__, name="INPUT_FILE_NAME", &
354 description="the filename of the input file used to run the original calculation", &
355 usage="INPUT_FILE_NAME my_input.inp", &
356 default_lc_val="input.inp")
357 CALL section_add_keyword(section, keyword)
358 CALL keyword_release(keyword)
359
360 END SUBROUTINE create_training_section
361
362! **************************************************************************************************
363!> \brief ...
364!> \param section ...
365! **************************************************************************************************
366 SUBROUTINE create_powell_section(section)
367 TYPE(section_type), POINTER :: section
368
369 TYPE(keyword_type), POINTER :: keyword
370
371 NULLIFY (keyword)
372 cpassert(.NOT. ASSOCIATED(section))
373 CALL section_create(section, __location__, name="OPTIMIZATION", &
374 description="sets the parameters for optimizition, output frequency and restarts", &
375 repeats=.false.)
376
377 CALL keyword_create(keyword, __location__, name="ACCURACY", &
378 description="Final accuracy requested in optimization (RHOEND)", &
379 usage="ACCURACY 0.00001", &
380 default_r_val=1.e-5_dp)
381 CALL section_add_keyword(section, keyword)
382 CALL keyword_release(keyword)
383
384 CALL keyword_create(keyword, __location__, name="STEP_SIZE", &
385 description="Initial step size for search algorithm (RHOBEG)", &
386 usage="STEP_SIZE 0.005", &
387 default_r_val=0.1_dp)
388 CALL section_add_keyword(section, keyword)
389 CALL keyword_release(keyword)
390
391 CALL keyword_create(keyword, __location__, name="MAX_FUN", &
392 description="Maximum number of function evaluations", &
393 usage="MAX_FUN 1000", &
394 default_i_val=5000)
395 CALL section_add_keyword(section, keyword)
396 CALL keyword_release(keyword)
397
398 END SUBROUTINE create_powell_section
399
400END MODULE input_optimize_basis
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_opt_coeff
integer, parameter, public do_opt_all
integer, parameter, public do_opt_exps
integer, parameter, public do_opt_none
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
builds the input structure for optimize_basis
subroutine, public create_optimize_basis_section(section)
creates the optimize_basis section
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
integer, parameter, public integer_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