1!--------------------------------------------------------------------------------------------------!
2!   CP2K: A general program to perform molecular dynamics simulations                              !
3!   Copyright (C) 2000 - 2020  CP2K developers group                                               !
4!--------------------------------------------------------------------------------------------------!
5
6! **************************************************************************************************
7!> \brief builds the input structure for optimize_input
8!> \par History
9!>      09.2010 created [Joost VandeVondele]
10!> \author Joost VandeVondele
11! **************************************************************************************************
12MODULE input_optimize_input
13   USE cp_output_handling, ONLY: cp_print_key_section_create, &
14                                 low_print_level
15   USE input_constants, ONLY: opt_force_matching
16   USE input_keyword_types, ONLY: keyword_create, &
17                                  keyword_release, &
18                                  keyword_type
19   USE input_section_types, ONLY: section_add_keyword, &
20                                  section_add_subsection, &
21                                  section_create, &
22                                  section_release, &
23                                  section_type
24   USE input_val_types, ONLY: char_t, &
25                              real_t
26   USE kinds, ONLY: dp
27   USE string_utilities, ONLY: s2a
28#include "./base/base_uses.f90"
29
30   IMPLICIT NONE
31   PRIVATE
32
33   CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_optimize_input'
34   PUBLIC :: create_optimize_input_section
35
36CONTAINS
37
38! **************************************************************************************************
39!> \brief creates the optimize_input section
40!> \param section ...
41!> \author Joost VandeVondele
42! **************************************************************************************************
43   SUBROUTINE create_optimize_input_section(section)
44      TYPE(section_type), POINTER                        :: section
45
46      CHARACTER(len=*), PARAMETER :: routineN = 'create_optimize_input_section', &
47                                     routineP = moduleN//':'//routineN
48
49      TYPE(keyword_type), POINTER                        :: keyword
50      TYPE(section_type), POINTER                        :: sub_section, subsubsection
51
52      CPASSERT(.NOT. ASSOCIATED(section))
53      CALL section_create(section, __LOCATION__, name="OPTIMIZE_INPUT", &
54                          description="describes an input optimization job, in which parameters in input files get optimized.", &
55                          repeats=.FALSE.)
56      NULLIFY (keyword)
57
58      CALL keyword_create(keyword, __LOCATION__, name="METHOD", &
59                          description="What kind of input optimization to perform.", &
60                          usage="METHOD FORCE_MATCHING", &
61                          enum_c_vals=s2a("FORCE_MATCHING"), &
62                          enum_desc=s2a("Perform a force matching minimization."), &
63                          enum_i_vals=(/opt_force_matching/), &
64                          default_i_val=opt_force_matching)
65      CALL section_add_keyword(section, keyword)
66      CALL keyword_release(keyword)
67
68      CALL keyword_create(keyword, __LOCATION__, name="ACCURACY", &
69                          description="Final accuracy requested in optimization (RHOEND)", &
70                          usage="ACCURACY 0.00001", &
71                          default_r_val=1.e-5_dp)
72      CALL section_add_keyword(section, keyword)
73      CALL keyword_release(keyword)
74
75      CALL keyword_create(keyword, __LOCATION__, name="STEP_SIZE", &
76                          description="Initial step size for search algorithm (RHOBEG)", &
77                          usage="STEP_SIZE 0.005", &
78                          default_r_val=0.05_dp)
79      CALL section_add_keyword(section, keyword)
80      CALL keyword_release(keyword)
81
82      CALL keyword_create(keyword, __LOCATION__, name="MAX_FUN", &
83                          description="Maximum number of function evaluations", &
84                          usage="MAX_FUN 1000", &
85                          default_i_val=5000)
86      CALL section_add_keyword(section, keyword)
87      CALL keyword_release(keyword)
88
89      CALL keyword_create(keyword, __LOCATION__, name="ITER_START_VAL", &
90                          description="Used for restarting, starting value of the iteration", &
91                          usage="ITER_START_VAL 0", &
92                          default_i_val=0)
93      CALL section_add_keyword(section, keyword)
94      CALL keyword_release(keyword)
95
96      CALL keyword_create(keyword, __LOCATION__, name="RANDOMIZE_VARIABLES", &
97                          description="Percentage randomization of the free variables applied initially", &
98                          usage="RANDOMIZE_VARIABLES 20", &
99                          default_r_val=0.00_dp)
100      CALL section_add_keyword(section, keyword)
101      CALL keyword_release(keyword)
102
103      !
104      ! variables section
105      !
106
107      NULLIFY (sub_section)
108      CALL section_create(sub_section, __LOCATION__, name="VARIABLE", &
109                          description="Defines initial values for variables and their labels", &
110                          n_subsections=0, repeats=.TRUE.)
111
112      CALL keyword_create(keyword, __LOCATION__, name="VALUE", &
113                          description="Initial value of the variable", &
114                          usage="VALUE 0.0", &
115                          type_of_var=real_t, unit_str="internal_cp2k")
116      CALL section_add_keyword(sub_section, keyword)
117      CALL keyword_release(keyword)
118
119      CALL keyword_create(keyword, __LOCATION__, name="FIXED", &
120                          description="Is this variable fixed or should it be optimized.", &
121                          usage="FIXED", &
122                          default_l_val=.FALSE., lone_keyword_l_val=.TRUE.)
123      CALL section_add_keyword(sub_section, keyword)
124      CALL keyword_release(keyword)
125
126      CALL keyword_create(keyword, __LOCATION__, name="LABEL", &
127                          description="The label used in the input file, i.e. ${LABEL} will be replaced by the VALUE specified.", &
128                          usage="LABEL PRM01", &
129                          type_of_var=char_t)
130      CALL section_add_keyword(sub_section, keyword)
131      CALL keyword_release(keyword)
132
133      CALL section_add_subsection(section, sub_section)
134      CALL section_release(sub_section)
135
136      !
137      ! force matching sub sectiong
138      !
139
140      NULLIFY (sub_section)
141      CALL section_create(sub_section, __LOCATION__, name="FORCE_MATCHING", &
142                          description="Specify the force matching input.", &
143                          repeats=.TRUE.)
144
145      CALL keyword_create(keyword, __LOCATION__, name="OPTIMIZE_FILE_NAME", &
146                          description="the filename of the input file which contains the parameters to be optimized", &
147                          usage="OPTIMIZE_FILE_NAME my_input.inp", &
148                          default_lc_val="")
149      CALL section_add_keyword(sub_section, keyword)
150      CALL keyword_release(keyword)
151
152      CALL keyword_create(keyword, __LOCATION__, name="REF_TRAJ_FILE_NAME", &
153                          description="the filename of the reference coordinates.", &
154                          usage="REF_TRAJ_FILE_NAME pos.xyz", &
155                          default_lc_val="")
156      CALL section_add_keyword(sub_section, keyword)
157      CALL keyword_release(keyword)
158
159      CALL keyword_create(keyword, __LOCATION__, name="REF_FORCE_FILE_NAME", &
160                          description="the filename of the reference forces, should also contain the energy", &
161                          usage="REF_FORCE_FILE_NAME frc.xyz", &
162                          default_lc_val="")
163      CALL section_add_keyword(sub_section, keyword)
164      CALL keyword_release(keyword)
165
166      CALL keyword_create(keyword, __LOCATION__, name="REF_CELL_FILE_NAME", &
167                          description="the filename of the reference cell", &
168                          usage="REF_CELL_FILE_NAME project.cell", &
169                          default_lc_val="")
170      CALL section_add_keyword(sub_section, keyword)
171      CALL keyword_release(keyword)
172
173      CALL keyword_create(keyword, __LOCATION__, name="GROUP_SIZE", &
174                          description="Gives the preferred size of a working group, "// &
175                          "groups will always be equal or larger than this size."// &
176                          "Usually this should take the number of cores per socket into account for good performance.", &
177                          usage="group_size 2", default_i_val=6)
178      CALL section_add_keyword(sub_section, keyword)
179      CALL keyword_release(keyword)
180
181      CALL keyword_create(keyword, __LOCATION__, name="FRAME_START", &
182                          description="starting frame to be used from the reference trajectory", &
183                          usage="FRAME_START 1", default_i_val=1)
184      CALL section_add_keyword(sub_section, keyword)
185      CALL keyword_release(keyword)
186
187      CALL keyword_create(keyword, __LOCATION__, name="FRAME_STOP", &
188                          description="final frame to be used from the reference trajectory (all=-1)", &
189                          usage="FRAME_STOP -1", default_i_val=-1)
190      CALL section_add_keyword(sub_section, keyword)
191      CALL keyword_release(keyword)
192
193      CALL keyword_create(keyword, __LOCATION__, name="FRAME_STRIDE", &
194                          description="stride when using the reference trajectory", &
195                          usage="FRAME_STRIDE 1", default_i_val=1)
196      CALL section_add_keyword(sub_section, keyword)
197      CALL keyword_release(keyword)
198
199      CALL keyword_create(keyword, __LOCATION__, name="FRAME_COUNT", &
200                          description="Use at most FRAME_COUNT frames from the reference trajectory, "// &
201                          "adjusting the stride to have them as fas apart as possible (all=-1).", &
202                          usage="FRAME_COUNT 100", default_i_val=-1)
203      CALL section_add_keyword(sub_section, keyword)
204      CALL keyword_release(keyword)
205
206      CALL keyword_create(keyword, __LOCATION__, name="ENERGY_WEIGHT", &
207                          description="Relative weight of the energy RMSD vs the force RMSD", &
208                          usage="ENERGY_WEIGHT 0.1", default_r_val=0.1_dp)
209      CALL section_add_keyword(sub_section, keyword)
210      CALL keyword_release(keyword)
211
212      CALL keyword_create(keyword, __LOCATION__, name="SHIFT_AVERAGE", &
213                          description="Shift averages of the energies before computing energy RMSD.", &
214                          usage="SHIFT_AVERAGE", default_l_val=.FALSE., lone_keyword_l_val=.TRUE.)
215      CALL section_add_keyword(sub_section, keyword)
216      CALL keyword_release(keyword)
217
218      CALL keyword_create(keyword, __LOCATION__, name="SHIFT_QM", &
219                          description="Shift of the reference energies applied before computing energy RMSD.", &
220                          usage="SHIFT_QM -17.0", default_r_val=0.0_dp)
221      CALL section_add_keyword(sub_section, keyword)
222      CALL keyword_release(keyword)
223
224      CALL keyword_create(keyword, __LOCATION__, name="SHIFT_MM", &
225                          description="Shift of the fit energies applied before computing energy RMSD.", &
226                          usage="SHIFT_MM 0.0", default_r_val=0.0_dp)
227      CALL section_add_keyword(sub_section, keyword)
228      CALL keyword_release(keyword)
229
230      NULLIFY (subsubsection)
231      CALL cp_print_key_section_create(subsubsection, __LOCATION__, "COMPARE_ENERGIES", &
232                                       description="A comparison of energies between fit and reference", &
233                                       print_level=low_print_level, filename="compare_energies", common_iter_levels=1)
234      CALL section_add_subsection(sub_section, subsubsection)
235      CALL section_release(subsubsection)
236
237      NULLIFY (subsubsection)
238      CALL cp_print_key_section_create(subsubsection, __LOCATION__, "COMPARE_FORCES", &
239                                       description="A comparison of forces between fit and reference", &
240                                       print_level=low_print_level, filename="compare_forces", common_iter_levels=1)
241      CALL section_add_subsection(sub_section, subsubsection)
242      CALL section_release(subsubsection)
243
244      CALL section_add_subsection(section, sub_section)
245      CALL section_release(sub_section)
246
247      NULLIFY (subsubsection)
248      CALL cp_print_key_section_create(subsubsection, __LOCATION__, "HISTORY", &
249                                       description="writes a history of the function value and parameters", &
250                                       print_level=low_print_level, filename="history", common_iter_levels=1)
251      CALL section_add_subsection(section, subsubsection)
252      CALL section_release(subsubsection)
253
254      CALL cp_print_key_section_create(subsubsection, __LOCATION__, "RESTART", &
255                                       description="writes an input file that can be used to restart ", &
256                                       print_level=low_print_level, filename="optimize", common_iter_levels=1)
257      CALL keyword_create(keyword, __LOCATION__, name="BACKUP_COPIES", &
258                          description="Specifies the maximum index of backup copies.", &
259                          usage="BACKUP_COPIES {int}", &
260                          default_i_val=3)
261      CALL section_add_keyword(subsubsection, keyword)
262      CALL keyword_release(keyword)
263      CALL section_add_subsection(section, subsubsection)
264      CALL section_release(subsubsection)
265
266   END SUBROUTINE create_optimize_input_section
267
268END MODULE input_optimize_input
269
270