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