(git:374b731)
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-2024 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 usage="INTENSITY 0.001", &
70 default_r_val=0._dp)
71 CALL section_add_keyword(section, keyword)
72 CALL keyword_release(keyword)
73
74 CALL keyword_create(keyword, __location__, name="POLARISATION", &
75 description="Polarisation vector of electric field", &
76 usage="POLARISIATION 0.0 0.0 1.0", &
77 repeats=.false., n_var=3, &
78 type_of_var=real_t, default_r_vals=(/0.0_dp, 0.0_dp, 1.0_dp/))
79 CALL section_add_keyword(section, keyword)
80 CALL keyword_release(keyword)
81
82 CALL keyword_create(keyword, __location__, name="DISPLACEMENT_FIELD", &
83 description="Use the displacement field formulation.", &
84 usage="DISPLACEMENT_FIELD T", &
85 citations=(/stengel2009/), &
86 default_l_val=.false., &
87 lone_keyword_l_val=.true.)
88 CALL section_add_keyword(section, keyword)
89 CALL keyword_release(keyword)
90
91 CALL keyword_create(keyword, __location__, name="D_FILTER", &
92 description="Filter for displacement field (x,y,z-dirction)", &
93 usage="D_FILTER 1.0 0.0 0.0", &
94 repeats=.false., n_var=3, &
95 type_of_var=real_t, default_r_vals=(/1.0_dp, 1.0_dp, 1.0_dp/))
96 CALL section_add_keyword(section, keyword)
97 CALL keyword_release(keyword)
98
99 END SUBROUTINE create_per_efield_section
100! **************************************************************************************************
101!> \brief creates the section for time dependent nonperiodic fields
102!> \param section ...
103!> \author Florian Schiffmann
104! **************************************************************************************************
105 SUBROUTINE create_efield_section(section)
106 TYPE(section_type), POINTER :: section
107
108 TYPE(keyword_type), POINTER :: keyword
109 TYPE(section_type), POINTER :: subsection
110
111 cpassert(.NOT. ASSOCIATED(section))
112 CALL section_create(section, __location__, name="EFIELD", &
113 description="Parameters for finite, time dependent electric fields. "// &
114 "For time dependent propagation in periodic systems, set "// &
115 "DFT%REAL_TIME_PROPAGATION%VELOCITY_GAUGE to true. "// &
116 "For static fields use EXTERNAL_POTENTIAL.", &
117 n_keywords=6, n_subsections=1, repeats=.true.)
118
119 NULLIFY (keyword, subsection)
120
121 CALL keyword_create(keyword, __location__, name="INTENSITY", &
122 description="Intensity of the electric field. For real-time propagation (RTP) units are "// &
123 "in W*cm-2 which corresponds "// &
124 "to a maximal amplitude in a.u. of sqrt(I/(3.50944*10^16)). "// &
125 "For a constant local field in isolated system calclulations, units are in a.u..", &
126 usage="INTENSITY 0.001", &
127 default_r_val=0._dp)
128 CALL section_add_keyword(section, keyword)
129 CALL keyword_release(keyword)
130
131 CALL keyword_create(keyword, __location__, name="POLARISATION", &
132 description="Polarisation vector of electric field", &
133 usage="POLARISATION 0.0 0.0 1.0", &
134 repeats=.false., n_var=3, &
135 type_of_var=real_t, default_r_vals=(/0.0_dp, 0.0_dp, 1.0_dp/))
136 CALL section_add_keyword(section, keyword)
137 CALL keyword_release(keyword)
138
139 CALL keyword_create(keyword, __location__, name="WAVELENGTH", &
140 description="Wavelength of efield field for real-time propagation (RTP) calculations.", &
141 usage="Wavelength 1.E0", &
142 default_r_val=0._dp, unit_str="nm")
143 CALL section_add_keyword(section, keyword)
144 CALL keyword_release(keyword)
145
146 CALL keyword_create(keyword, __location__, name="PHASE", &
147 description="Phase offset of the cosine given in multiples of pi. "// &
148 "Used in real-time propagation (RTP) calculations.", &
149 usage="Phase 1.E0", &
150 default_r_val=0._dp)
151 CALL section_add_keyword(section, keyword)
152 CALL keyword_release(keyword)
153
154 CALL keyword_create(keyword, __location__, name="ENVELOP", &
155 description="Shape of the efield pulse used in real-time propagation (RTP) calculations.", &
156 usage="ENVELOP CONSTANT", &
157 default_i_val=constant_env, &
158 enum_c_vals=s2a("CONSTANT", "GAUSSIAN", "RAMP", "CUSTOM"), &
159 enum_desc=s2a("No envelop function is applied to the strength", &
160 "A Gaussian function is used as envelop ", &
161 "Linear tune in/out of the field", &
162 "A custom field read from a file"), &
163 enum_i_vals=(/constant_env, gaussian_env, ramp_env, custom_env/))
164 CALL section_add_keyword(section, keyword)
165 CALL keyword_release(keyword)
166
167 CALL keyword_create(keyword, __location__, name="VEC_POT_INITIAL", &
168 description="Initial value of the vector "// &
169 "potential (for velocity gauge). This input is "// &
170 "made especially for restarting RTP calculation. "// &
171 "Unit is atomic unit. "// &
172 "Note that if several field sections are defined, only the first one will be used.", &
173 usage="vec_pot_initial 1.0E-2 0.0 0.0", &
174 repeats=.false., &
175 n_var=3, type_of_var=real_t, &
176 default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/))
177 CALL section_add_keyword(section, keyword)
178 CALL keyword_release(keyword)
179
180 CALL create_constant_env_section(subsection)
181 CALL section_add_subsection(section, subsection)
182 CALL section_release(subsection)
183
184 CALL create_gaussian_env_section(subsection)
185 CALL section_add_subsection(section, subsection)
186 CALL section_release(subsection)
187
188 CALL create_ramp_env_section(subsection)
189 CALL section_add_subsection(section, subsection)
190 CALL section_release(subsection)
191
192 CALL create_custom_env_section(subsection)
193 CALL section_add_subsection(section, subsection)
194 CALL section_release(subsection)
195
196 END SUBROUTINE create_efield_section
197
198! **************************************************************************************************
199!> \brief ...
200!> \param section ...
201! **************************************************************************************************
202 SUBROUTINE create_constant_env_section(section)
203 TYPE(section_type), POINTER :: section
204
205 TYPE(keyword_type), POINTER :: keyword
206
207 cpassert(.NOT. ASSOCIATED(section))
208 CALL section_create(section, __location__, name="CONSTANT_ENV", &
209 description="parameters for a constant envelop", &
210 n_keywords=6, n_subsections=1, repeats=.true.)
211
212 NULLIFY (keyword)
213
214 CALL keyword_create(keyword, __location__, name="START_STEP", &
215 description="First step the field is applied ", &
216 usage="START_STEP 0", &
217 default_i_val=0)
218 CALL section_add_keyword(section, keyword)
219 CALL keyword_release(keyword)
220
221 CALL keyword_create(keyword, __location__, name="END_STEP", &
222 description="Last step the field is applied", &
223 usage="END_STEP 2", &
224 default_i_val=-1)
225 CALL section_add_keyword(section, keyword)
226 CALL keyword_release(keyword)
227
228 END SUBROUTINE create_constant_env_section
229
230! **************************************************************************************************
231!> \brief ...
232!> \param section ...
233! **************************************************************************************************
234 SUBROUTINE create_gaussian_env_section(section)
235 TYPE(section_type), POINTER :: section
236
237 TYPE(keyword_type), POINTER :: keyword
238
239 cpassert(.NOT. ASSOCIATED(section))
240 CALL section_create(section, __location__, name="GAUSSIAN_ENV", &
241 description="parameters for a gaussian envelop", &
242 n_keywords=6, n_subsections=1, repeats=.true.)
243
244 NULLIFY (keyword)
245
246 CALL keyword_create(keyword, __location__, name="T0", &
247 description="Center of the gaussian envelop (maximum of the gaussian)", &
248 usage="T0 2.0E0", &
249 default_r_val=0.0e0_dp, &
250 unit_str="fs")
251 CALL section_add_keyword(section, keyword)
252 CALL keyword_release(keyword)
253
254 CALL keyword_create(keyword, __location__, name="SIGMA", &
255 description="Width of the gaussian ", &
256 usage="SIGMA 2.0E0", &
257 default_r_val=-1.0e0_dp, &
258 unit_str="fs")
259 CALL section_add_keyword(section, keyword)
260 CALL keyword_release(keyword)
261
262 END SUBROUTINE create_gaussian_env_section
263
264! **************************************************************************************************
265!> \brief ...
266!> \param section ...
267! **************************************************************************************************
268 SUBROUTINE create_ramp_env_section(section)
269 TYPE(section_type), POINTER :: section
270
271 TYPE(keyword_type), POINTER :: keyword
272
273 cpassert(.NOT. ASSOCIATED(section))
274 CALL section_create(section, __location__, name="RAMP_ENV", &
275 description="Parameters for an trapeziodal envelop ", &
276 n_keywords=6, n_subsections=1, repeats=.true.)
277
278 NULLIFY (keyword)
279
280 CALL keyword_create(keyword, __location__, name="START_STEP_IN", &
281 description="Step when the electric field starts to be applied ", &
282 usage="START_STEP_IN 0", &
283 default_i_val=0)
284 CALL section_add_keyword(section, keyword)
285 CALL keyword_release(keyword)
286
287 CALL keyword_create(keyword, __location__, name="END_STEP_IN", &
288 description="Step when the field reaches the full strength", &
289 usage="END_STEP_IN 2", &
290 default_i_val=-1)
291 CALL section_add_keyword(section, keyword)
292 CALL keyword_release(keyword)
293
294 CALL keyword_create(keyword, __location__, name="START_STEP_OUT", &
295 description="Step when the field starts to vanish ", &
296 usage="START_STEP 0", &
297 default_i_val=0)
298 CALL section_add_keyword(section, keyword)
299 CALL keyword_release(keyword)
300
301 CALL keyword_create(keyword, __location__, name="END_STEP_OUT", &
302 description="Step when the field disappears", &
303 usage="END_TIME 2", &
304 default_i_val=-1)
305 CALL section_add_keyword(section, keyword)
306 CALL keyword_release(keyword)
307
308 END SUBROUTINE create_ramp_env_section
309
310! **************************************************************************************************
311!> \brief ...
312!> \param section ...
313! **************************************************************************************************
314 SUBROUTINE create_custom_env_section(section)
315 TYPE(section_type), POINTER :: section
316
317 TYPE(keyword_type), POINTER :: keyword
318
319 cpassert(.NOT. ASSOCIATED(section))
320 CALL section_create(section, __location__, name="CUSTOM_ENV", &
321 description="Parameters for a custom efield", &
322 n_keywords=2, n_subsections=1, repeats=.true.)
323
324 NULLIFY (keyword)
325
326 CALL keyword_create(keyword, __location__, name="EFIELD_FILE_NAME", &
327 description="Specify file that contains the electric field [V/m].", &
328 usage="EFIELD_FILE_NAME filename", &
329 n_var=1, type_of_var=char_t, default_c_val="")
330 CALL section_add_keyword(section, keyword)
331 CALL keyword_release(keyword)
332
333 CALL keyword_create(keyword, __location__, name="TIMESTEP", &
334 description="The time step between the entries in the list with the electric field.", &
335 usage="TIME_STEP 1", &
336 unit_str="fs", &
337 default_r_val=1.0_dp)
338 CALL section_add_keyword(section, keyword)
339 CALL keyword_release(keyword)
340
341 END SUBROUTINE create_custom_env_section
342
343END 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)
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