(git:b77b4be)
Loading...
Searching...
No Matches
input_cp2k_field.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief function that build the field section of the input
10!> \par History
11!> 02.2017 moved out of input_cp2k_dft [JHU]
12!> \author fawzi
13! **************************************************************************************************
15 USE bibliography, ONLY: souza2002,&
18 USE input_constants, ONLY: constant_env,&
20 gaussian,&
31 USE input_val_types, ONLY: char_t,&
32 real_t
33 USE kinds, ONLY: dp
34 USE string_utilities, ONLY: s2a
35#include "./base/base_uses.f90"
36
37 IMPLICIT NONE
38 PRIVATE
39
40 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_field'
41
43
44CONTAINS
45
46! **************************************************************************************************
47!> \brief creates the section for static periodic fields
48!> \param section ...
49!> \author Florian Schiffmann
50! **************************************************************************************************
51 SUBROUTINE create_per_efield_section(section)
52 TYPE(section_type), POINTER :: section
53
54 TYPE(keyword_type), POINTER :: keyword
55
56 cpassert(.NOT. ASSOCIATED(section))
57 CALL section_create(section, __location__, name="PERIODIC_EFIELD", &
58 description="parameters for finite periodic electric field computed using"// &
59 " the Berry phase approach. IMPORTANT: Can only be used in combination"// &
60 " with OT. Can not be used in combination with RTP or EMD,"// &
61 " e.g. RESTART_RTP has to be .FALSE. when restarting the job.", &
62 citations=(/souza2002, umari2002/), &
63 n_keywords=6, n_subsections=1, repeats=.true.)
64
65 NULLIFY (keyword)
66
67 CALL keyword_create(keyword, __location__, name="INTENSITY", &
68 description="Intensity of the electric field in a.u, "// &
69 "not allowed together with INTENSITY_LIST", &
70 usage="INTENSITY 0.001", &
71 default_r_val=0._dp)
72 CALL section_add_keyword(section, keyword)
73 CALL keyword_release(keyword)
74
75 CALL keyword_create(keyword, __location__, name="POLARISATION", &
76 description="Polarisation vector of electric field", &
77 usage="POLARISATION 0.0 0.0 1.0", &
78 repeats=.false., n_var=3, &
79 type_of_var=real_t, default_r_vals=(/0.0_dp, 0.0_dp, 1.0_dp/))
80 CALL section_add_keyword(section, keyword)
81 CALL keyword_release(keyword)
82
83 CALL keyword_create(keyword, __location__, name="DISPLACEMENT_FIELD", &
84 description="Use the displacement field formulation.", &
85 usage="DISPLACEMENT_FIELD T", &
86 citations=(/stengel2009/), &
87 default_l_val=.false., &
88 lone_keyword_l_val=.true.)
89 CALL section_add_keyword(section, keyword)
90 CALL keyword_release(keyword)
91
92 CALL keyword_create(keyword, __location__, name="D_FILTER", &
93 description="Filter for displacement field (x,y,z-direction)", &
94 usage="D_FILTER 1.0 0.0 0.0", &
95 repeats=.false., n_var=3, &
96 type_of_var=real_t, default_r_vals=(/1.0_dp, 1.0_dp, 1.0_dp/))
97 CALL section_add_keyword(section, keyword)
98 CALL keyword_release(keyword)
99
100 CALL keyword_create(keyword, __location__, name="INTENSITY_LIST", &
101 description="Intensities of the electric field in a.u. "// &
102 "They are applied sequentially, one per frame. "// &
103 "If the number of frames exceeds the number of values, "// &
104 "the list is cyclically repeated. Attention: not implemented for eeq.", &
105 usage="INTENSITY_LIST {real} {real} .. {real}", &
106 n_var=-1, type_of_var=real_t, default_r_vals=(/0.0_dp/))
107 CALL section_add_keyword(section, keyword)
108 CALL keyword_release(keyword)
109
110 CALL keyword_create(keyword, __location__, name="INTENSITIES_FILE_NAME", &
111 description="File containting a list of intensities, "// &
112 "one per line, in a.u. "// &
113 "They are applied sequentially, one per frame. "// &
114 "If the number of frames exceeds the number of values, "// &
115 "the list is cyclically repeated. Attention: not implemented for eeq.", &
116 usage="INTENSITIES_FILE_NAME filename", &
117 default_lc_val="")
118 CALL section_add_keyword(section, keyword)
119 CALL keyword_release(keyword)
120
121 CALL keyword_create(keyword, __location__, name="START_FRAME", &
122 description="First frame the field is applied. "// &
123 "(0: first frame) "// &
124 "Attention: ignored for eeq", &
125 usage="START_FRAME 0", &
126 default_i_val=0)
127 CALL section_add_keyword(section, keyword)
128 CALL keyword_release(keyword)
129
130 CALL keyword_create(keyword, __location__, name="END_FRAME", &
131 description="Last frame the field is applied. "// &
132 "If an end frame is specified, the number of active frames "// &
133 "must be a multiple of the number of "// &
134 "the given intensity values. (-1: no end) "// &
135 "Attention: ignored for eeq", &
136 usage="END_FRAME -1", &
137 default_i_val=-1)
138 CALL section_add_keyword(section, keyword)
139 CALL keyword_release(keyword)
140
141 END SUBROUTINE create_per_efield_section
142! **************************************************************************************************
143!> \brief creates the section for time dependent nonperiodic fields
144!> \param section ...
145!> \author Florian Schiffmann
146! **************************************************************************************************
147 SUBROUTINE create_efield_section(section)
148 TYPE(section_type), POINTER :: section
149
150 TYPE(keyword_type), POINTER :: keyword
151 TYPE(section_type), POINTER :: subsection
152
153 cpassert(.NOT. ASSOCIATED(section))
154 CALL section_create(section, __location__, name="EFIELD", &
155 description="Parameters for finite, time dependent electric fields. "// &
156 "For time dependent propagation in periodic systems, set "// &
157 "DFT%REAL_TIME_PROPAGATION%VELOCITY_GAUGE to true. "// &
158 "For static fields use EXTERNAL_POTENTIAL.", &
159 n_keywords=6, n_subsections=1, repeats=.true.)
160
161 NULLIFY (keyword, subsection)
162
163 CALL keyword_create(keyword, __location__, name="INTENSITY", &
164 description="Intensity of the electric field. For real-time propagation (RTP) units are "// &
165 "in W*cm-2 which corresponds "// &
166 "to a maximal amplitude in a.u. of sqrt(I/(3.50944*10^16)). "// &
167 "For a constant local field in isolated system calclulations, units are in a.u..", &
168 usage="INTENSITY 0.001", &
169 default_r_val=0._dp)
170 CALL section_add_keyword(section, keyword)
171 CALL keyword_release(keyword)
172
173 CALL keyword_create(keyword, __location__, name="POLARISATION", &
174 description="Polarisation vector of electric field", &
175 usage="POLARISATION 0.0 0.0 1.0", &
176 repeats=.false., n_var=3, &
177 type_of_var=real_t, default_r_vals=(/0.0_dp, 0.0_dp, 1.0_dp/))
178 CALL section_add_keyword(section, keyword)
179 CALL keyword_release(keyword)
180
181 CALL keyword_create(keyword, __location__, name="WAVELENGTH", &
182 description="Wavelength of efield field for real-time propagation (RTP) calculations.", &
183 usage="Wavelength 1.E0", &
184 default_r_val=0._dp, unit_str="nm")
185 CALL section_add_keyword(section, keyword)
186 CALL keyword_release(keyword)
187
188 CALL keyword_create(keyword, __location__, name="PHASE", &
189 description="Phase offset of the cosine given in multiples of pi. "// &
190 "Used in real-time propagation (RTP) calculations.", &
191 usage="Phase 1.E0", &
192 default_r_val=0._dp)
193 CALL section_add_keyword(section, keyword)
194 CALL keyword_release(keyword)
195
196 CALL keyword_create(keyword, __location__, name="ENVELOP", &
197 description="Shape of the efield pulse used in real-time propagation (RTP) calculations.", &
198 usage="ENVELOP CONSTANT", &
199 default_i_val=constant_env, &
200 enum_c_vals=s2a("CONSTANT", "GAUSSIAN", "RAMP", "CUSTOM"), &
201 enum_desc=s2a("No envelop function is applied to the strength", &
202 "A Gaussian function is used as envelop ", &
203 "Linear tune in/out of the field", &
204 "A custom field read from a file"), &
205 enum_i_vals=(/constant_env, gaussian_env, ramp_env, custom_env/))
206 CALL section_add_keyword(section, keyword)
207 CALL keyword_release(keyword)
208
209 CALL keyword_create(keyword, __location__, name="VEC_POT_INITIAL", &
210 description="Initial value of the vector "// &
211 "potential (for velocity gauge). This input is "// &
212 "made especially for restarting RTP calculation. "// &
213 "Unit is atomic unit. "// &
214 "Note that if several field sections are defined, only the first one will be used.", &
215 usage="vec_pot_initial 1.0E-2 0.0 0.0", &
216 repeats=.false., &
217 n_var=3, type_of_var=real_t, &
218 default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/))
219 CALL section_add_keyword(section, keyword)
220 CALL keyword_release(keyword)
221
222 CALL create_constant_env_section(subsection)
223 CALL section_add_subsection(section, subsection)
224 CALL section_release(subsection)
225
226 CALL create_gaussian_env_section(subsection)
227 CALL section_add_subsection(section, subsection)
228 CALL section_release(subsection)
229
230 CALL create_ramp_env_section(subsection)
231 CALL section_add_subsection(section, subsection)
232 CALL section_release(subsection)
233
234 CALL create_custom_env_section(subsection)
235 CALL section_add_subsection(section, subsection)
236 CALL section_release(subsection)
237
238 END SUBROUTINE create_efield_section
239
240! **************************************************************************************************
241!> \brief ...
242!> \param section ...
243! **************************************************************************************************
244 SUBROUTINE create_constant_env_section(section)
245 TYPE(section_type), POINTER :: section
246
247 TYPE(keyword_type), POINTER :: keyword
248
249 cpassert(.NOT. ASSOCIATED(section))
250 CALL section_create(section, __location__, name="CONSTANT_ENV", &
251 description="parameters for a constant envelop", &
252 n_keywords=6, n_subsections=1, repeats=.true.)
253
254 NULLIFY (keyword)
255
256 CALL keyword_create(keyword, __location__, name="START_STEP", &
257 description="First step the field is applied ", &
258 usage="START_STEP 0", &
259 default_i_val=0)
260 CALL section_add_keyword(section, keyword)
261 CALL keyword_release(keyword)
262
263 CALL keyword_create(keyword, __location__, name="END_STEP", &
264 description="Last step the field is applied", &
265 usage="END_STEP 2", &
266 default_i_val=-1)
267 CALL section_add_keyword(section, keyword)
268 CALL keyword_release(keyword)
269
270 END SUBROUTINE create_constant_env_section
271
272! **************************************************************************************************
273!> \brief ...
274!> \param section ...
275! **************************************************************************************************
276 SUBROUTINE create_gaussian_env_section(section)
277 TYPE(section_type), POINTER :: section
278
279 TYPE(keyword_type), POINTER :: keyword
280
281 cpassert(.NOT. ASSOCIATED(section))
282 CALL section_create(section, __location__, name="GAUSSIAN_ENV", &
283 description="parameters for a gaussian envelop", &
284 n_keywords=6, n_subsections=1, repeats=.true.)
285
286 NULLIFY (keyword)
287
288 CALL keyword_create(keyword, __location__, name="T0", &
289 description="Center of the gaussian envelop (maximum of the gaussian)", &
290 usage="T0 2.0E0", &
291 default_r_val=0.0e0_dp, &
292 unit_str="fs")
293 CALL section_add_keyword(section, keyword)
294 CALL keyword_release(keyword)
295
296 CALL keyword_create(keyword, __location__, name="SIGMA", &
297 description="Width of the gaussian ", &
298 usage="SIGMA 2.0E0", &
299 default_r_val=-1.0e0_dp, &
300 unit_str="fs")
301 CALL section_add_keyword(section, keyword)
302 CALL keyword_release(keyword)
303
304 END SUBROUTINE create_gaussian_env_section
305
306! **************************************************************************************************
307!> \brief ...
308!> \param section ...
309! **************************************************************************************************
310 SUBROUTINE create_ramp_env_section(section)
311 TYPE(section_type), POINTER :: section
312
313 TYPE(keyword_type), POINTER :: keyword
314
315 cpassert(.NOT. ASSOCIATED(section))
316 CALL section_create(section, __location__, name="RAMP_ENV", &
317 description="Parameters for an trapeziodal envelop ", &
318 n_keywords=6, n_subsections=1, repeats=.true.)
319
320 NULLIFY (keyword)
321
322 CALL keyword_create(keyword, __location__, name="START_STEP_IN", &
323 description="Step when the electric field starts to be applied ", &
324 usage="START_STEP_IN 0", &
325 default_i_val=0)
326 CALL section_add_keyword(section, keyword)
327 CALL keyword_release(keyword)
328
329 CALL keyword_create(keyword, __location__, name="END_STEP_IN", &
330 description="Step when the field reaches the full strength", &
331 usage="END_STEP_IN 2", &
332 default_i_val=-1)
333 CALL section_add_keyword(section, keyword)
334 CALL keyword_release(keyword)
335
336 CALL keyword_create(keyword, __location__, name="START_STEP_OUT", &
337 description="Step when the field starts to vanish ", &
338 usage="START_STEP_OUT 0", &
339 default_i_val=0)
340 CALL section_add_keyword(section, keyword)
341 CALL keyword_release(keyword)
342
343 CALL keyword_create(keyword, __location__, name="END_STEP_OUT", &
344 description="Step when the field disappears", &
345 usage="END_STEP_OUT 2", &
346 default_i_val=-1)
347 CALL section_add_keyword(section, keyword)
348 CALL keyword_release(keyword)
349
350 END SUBROUTINE create_ramp_env_section
351
352! **************************************************************************************************
353!> \brief ...
354!> \param section ...
355! **************************************************************************************************
356 SUBROUTINE create_custom_env_section(section)
357 TYPE(section_type), POINTER :: section
358
359 TYPE(keyword_type), POINTER :: keyword
360
361 cpassert(.NOT. ASSOCIATED(section))
362 CALL section_create(section, __location__, name="CUSTOM_ENV", &
363 description="Parameters for a custom efield", &
364 n_keywords=2, n_subsections=1, repeats=.true.)
365
366 NULLIFY (keyword)
367
368 CALL keyword_create(keyword, __location__, name="EFIELD_FILE_NAME", &
369 description="Specify file that contains the electric field [V/m].", &
370 usage="EFIELD_FILE_NAME filename", &
371 n_var=1, type_of_var=char_t, default_c_val="")
372 CALL section_add_keyword(section, keyword)
373 CALL keyword_release(keyword)
374
375 CALL keyword_create(keyword, __location__, name="TIMESTEP", &
376 description="The time step between the entries in the list with the electric field.", &
377 usage="TIMESTEP 1", &
378 unit_str="fs", &
379 default_r_val=1.0_dp)
380 CALL section_add_keyword(section, keyword)
381 CALL keyword_release(keyword)
382
383 END SUBROUTINE create_custom_env_section
384
385END MODULE input_cp2k_field
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public umari2002
integer, save, public stengel2009
integer, save, public souza2002
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public ramp_env
integer, parameter, public constant_env
integer, parameter, public gaussian_env
integer, parameter, public gaussian
integer, parameter, public custom_env
function that build the field section of the input
subroutine, public create_efield_section(section)
creates the section for time dependent nonperiodic fields
subroutine, public create_per_efield_section(section)
creates the section for static periodic fields
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
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, deprecation_notice)
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.
represent a keyword in the input
represent a section of the input file