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