(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_negf.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 Input section for NEGF based quantum transport calculations.
10! **************************************************************************************************
11
13 USE bibliography, ONLY: bailey2006,&
31 USE input_val_types, ONLY: char_t,&
32 integer_t,&
33 real_t
34 USE kinds, ONLY: dp
35 USE physcon, ONLY: kelvin
37 USE string_utilities, ONLY: s2a
38#include "./base/base_uses.f90"
39
40 IMPLICIT NONE
41 PRIVATE
42
43 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_negf'
44
45 PUBLIC :: create_negf_section
46
47CONTAINS
48
49! **************************************************************************************************
50!> \brief Create NEGF input section.
51!> \param section input section
52!> \par History
53!> * 02.2017 created [Sergey Chulkov]
54! **************************************************************************************************
55 SUBROUTINE create_negf_section(section)
56 TYPE(section_type), POINTER :: section
57
58 TYPE(keyword_type), POINTER :: keyword
59 TYPE(section_type), POINTER :: print_key, subsection
60
61 cpassert(.NOT. ASSOCIATED(section))
62 CALL section_create(section, __location__, name="NEGF", &
63 description="Parameters which control quantum transport calculation"// &
64 " based on Non-Equilibrium Green's Function method.", &
65 citations=(/bailey2006, papior2017/), &
66 n_keywords=18, n_subsections=6, repeats=.false.)
67
68 NULLIFY (keyword, print_key, subsection)
69
70 CALL create_contact_section(subsection)
71 CALL section_add_subsection(section, subsection)
72 CALL section_release(subsection)
73
74 CALL create_atomlist_section(subsection, "SCATTERING_REGION", "Defines atoms which form the scattering region.", .false.)
75 CALL section_add_subsection(section, subsection)
76 CALL section_release(subsection)
77
78 ! mixing section
79 CALL create_mixing_section(subsection, ls_scf=.false.)
80 CALL section_add_subsection(section, subsection)
81 CALL section_release(subsection)
82
83 CALL keyword_create(keyword, __location__, name="DISABLE_CACHE", &
84 description="Do not keep contact self-energy matrices for future reuse", &
85 default_l_val=.false., lone_keyword_l_val=.true.)
86 CALL section_add_keyword(section, keyword)
87 CALL keyword_release(keyword)
88
89 ! convergence thresholds
90 CALL keyword_create(keyword, __location__, name="EPS_DENSITY", &
91 description="Target accuracy for electronic density.", &
92 n_var=1, type_of_var=real_t, default_r_val=1.0e-5_dp)
93 CALL section_add_keyword(section, keyword)
94 CALL keyword_release(keyword)
95
96 CALL keyword_create(keyword, __location__, name="EPS_GREEN", &
97 description="Target accuracy for surface Green's functions.", &
98 n_var=1, type_of_var=real_t, default_r_val=1.0e-5_dp)
99 CALL section_add_keyword(section, keyword)
100 CALL keyword_release(keyword)
101
102 CALL keyword_create(keyword, __location__, name="EPS_SCF", &
103 description="Target accuracy for SCF convergence.", &
104 n_var=1, type_of_var=real_t, default_r_val=1.0e-5_dp)
105 CALL section_add_keyword(section, keyword)
106 CALL keyword_release(keyword)
107
108 CALL keyword_create(keyword, __location__, name="EPS_GEO", &
109 description="Accuracy in mapping atoms between different force environments.", &
110 n_var=1, type_of_var=real_t, unit_str="angstrom", &
111 default_r_val=1.0e-6_dp)
112 CALL section_add_keyword(section, keyword)
113 CALL keyword_release(keyword)
114
115 CALL keyword_create(keyword, __location__, name="ENERGY_LBOUND", &
116 description="Lower bound energy of the conductance band.", &
117 n_var=1, type_of_var=real_t, unit_str="hartree", &
118 default_r_val=-5.0_dp)
119 CALL section_add_keyword(section, keyword)
120 CALL keyword_release(keyword)
121
122 CALL keyword_create(keyword, __location__, name="ETA", &
123 description="Infinitesimal offset from the real axis.", &
124 n_var=1, type_of_var=real_t, unit_str="hartree", &
125 default_r_val=1.0e-5_dp)
126 CALL section_add_keyword(section, keyword)
127 CALL keyword_release(keyword)
128
129 CALL keyword_create(keyword, __location__, name="HOMO_LUMO_GAP", &
130 description="The gap between the HOMO and some fictitious LUMO. This option is used as"// &
131 " an initial offset to determine the actual Fermi level of bulk contacts."// &
132 " It does not need to be exact HOMO-LUMO gap, just some value to start with.", &
133 n_var=1, type_of_var=real_t, unit_str="hartree", &
134 default_r_val=0.2_dp)
135 CALL section_add_keyword(section, keyword)
136 CALL keyword_release(keyword)
137
138 CALL keyword_create(keyword, __location__, name="DELTA_NPOLES", &
139 description="Number of poles of Fermi function to consider.", &
140 n_var=1, type_of_var=integer_t, &
141 default_i_val=4)
142 CALL section_add_keyword(section, keyword)
143 CALL keyword_release(keyword)
144
145 CALL keyword_create(keyword, __location__, name="GAMMA_KT", &
146 description="Offset from the axis (in terms of k*T)"// &
147 " where poles of the Fermi function reside.", &
148 n_var=1, type_of_var=integer_t, &
149 default_i_val=20)
150 CALL section_add_keyword(section, keyword)
151 CALL keyword_release(keyword)
152
153 CALL keyword_create(keyword, __location__, name="INTEGRATION_METHOD", &
154 description="Method to integrate Green's functions along a closed-circuit contour.", &
155 default_i_val=negfint_method_cc, &
156 enum_c_vals=s2a("CLENSHAW-CURTIS", "SIMPSON"), &
157 enum_desc=s2a( &
158 "Adaptive Clenshaw-Curtis quadrature method. Requires FFTW3 library.", &
159 "Adaptive Simpson method. Works without FFTW3."), &
161 CALL section_add_keyword(section, keyword)
162 CALL keyword_release(keyword)
163
164 CALL keyword_create(keyword, __location__, name="INTEGRATION_MIN_POINTS", &
165 description="Initial (minimal) number of grid point for adaptive numerical integration.", &
166 n_var=1, type_of_var=integer_t, &
167 default_i_val=16)
168 CALL section_add_keyword(section, keyword)
169 CALL keyword_release(keyword)
170
171 CALL keyword_create(keyword, __location__, name="INTEGRATION_MAX_POINTS", &
172 description="Maximal number of grid point for adaptive numerical integration.", &
173 n_var=1, type_of_var=integer_t, &
174 default_i_val=512)
175 CALL section_add_keyword(section, keyword)
176 CALL keyword_release(keyword)
177
178 CALL keyword_create(keyword, __location__, name="MAX_SCF", &
179 description="Maximum number of SCF iterations to be performed.", &
180 n_var=1, type_of_var=integer_t, &
181 default_i_val=30)
182 CALL section_add_keyword(section, keyword)
183 CALL keyword_release(keyword)
184
185 CALL keyword_create(keyword, __location__, name="NPROC_POINT", &
186 description="Number of MPI processes to be used per energy point."// &
187 " Default is to use all processors (0).", &
188 n_var=1, type_of_var=integer_t, &
189 default_i_val=0)
190 CALL section_add_keyword(section, keyword)
191 CALL keyword_release(keyword)
192
193 CALL keyword_create(keyword, __location__, name="V_SHIFT", &
194 description="Initial value of the Hartree potential shift", &
195 n_var=1, type_of_var=real_t, unit_str="hartree", &
196 default_r_val=0.0_dp)
197 CALL section_add_keyword(section, keyword)
198 CALL keyword_release(keyword)
199
200 CALL keyword_create(keyword, __location__, name="V_SHIFT_OFFSET", &
201 description="Initial offset to determine the optimal shift in Hartree potential.", &
202 n_var=1, type_of_var=real_t, default_r_val=0.10_dp)
203 CALL section_add_keyword(section, keyword)
204 CALL keyword_release(keyword)
205
206 CALL keyword_create(keyword, __location__, name="V_SHIFT_MAX_ITERS", &
207 description="Maximal number of iteration to determine the optimal shift in Hartree potential.", &
208 n_var=1, type_of_var=integer_t, default_i_val=30)
209 CALL section_add_keyword(section, keyword)
210 CALL keyword_release(keyword)
211
212 ! PRINT subsection
213 CALL section_create(subsection, __location__, "PRINT", "Printing of information during the NEGF.", &
214 repeats=.false.)
215
216 CALL create_print_program_run_info_section(print_key)
217 CALL section_add_subsection(subsection, print_key)
218 CALL section_release(print_key)
219
220 CALL create_print_dos_section(print_key, "DOS", "the Density of States (DOS) in the scattering region")
221 CALL section_add_subsection(subsection, print_key)
222 CALL section_release(print_key)
223
224 CALL create_print_dos_section(print_key, "TRANSMISSION", "the transmission coefficient")
225 CALL section_add_subsection(subsection, print_key)
226 CALL section_release(print_key)
227
228 CALL section_add_subsection(section, subsection)
229 CALL section_release(subsection)
230
231 END SUBROUTINE create_negf_section
232
233! **************************************************************************************************
234!> \brief Create NEGF%CONTACT input section.
235!> \param section input section
236!> \par History
237!> * 09.2017 split from create_negf_section() [Sergey Chulkov]
238! **************************************************************************************************
239 SUBROUTINE create_contact_section(section)
240 TYPE(section_type), POINTER :: section
241
242 TYPE(keyword_type), POINTER :: keyword
243 TYPE(section_type), POINTER :: print_key, subsection, subsection2
244
245 cpassert(.NOT. ASSOCIATED(section))
246
247 CALL section_create(section, __location__, name="CONTACT", &
248 description="Section defining the contact region of NEGF setup.", &
249 n_keywords=5, n_subsections=3, repeats=.true.)
250
251 NULLIFY (keyword, print_key, subsection, subsection2)
252
253 CALL create_atomlist_section(subsection, "BULK_REGION", &
254 "the bulk contact adjacent to the screening region.", .false.)
255 CALL section_add_subsection(section, subsection)
256 CALL create_atomlist_section(subsection2, "CELL", &
257 "a single bulk contact unit cell. Bulk Hamiltonian will be contstructed "// &
258 "using two such unit cells instead of performing k-point bulk calculation. "// &
259 "FORCE_EVAL_SECTION must be 0.", .true.)
260 CALL section_add_subsection(subsection, subsection2)
261 CALL section_release(subsection2)
262 CALL section_release(subsection)
263
264 CALL create_atomlist_section(subsection, "SCREENING_REGION", &
265 "the given contact adjacent to the scattering region.", .false.)
266 CALL section_add_subsection(section, subsection)
267 CALL section_release(subsection)
268
269 CALL keyword_create(keyword, __location__, name="FORCE_EVAL_SECTION", &
270 description=" Index of the FORCE_EVAL section which will be used for bulk calculation.", &
271 n_var=1, type_of_var=integer_t, default_i_val=0)
272 CALL section_add_keyword(section, keyword)
273 CALL keyword_release(keyword)
274
275 CALL keyword_create(keyword, __location__, name="ELECTRIC_POTENTIAL", &
276 description="External electrostatic potential applied to the given contact.", &
277 n_var=1, type_of_var=real_t, unit_str="hartree", &
278 default_r_val=0.0_dp)
279 CALL section_add_keyword(section, keyword)
280 CALL keyword_release(keyword)
281
282 CALL keyword_create(keyword, __location__, name="FERMI_LEVEL", &
283 description="Contact Fermi level at the given temperature."// &
284 " If this keyword is not given explicitly, the Fermi level"// &
285 " will be automatically computed prior the actual NEGF calculation.", &
286 n_var=1, type_of_var=real_t, unit_str="hartree", &
287 default_r_val=0.0_dp)
288 CALL section_add_keyword(section, keyword)
289 CALL keyword_release(keyword)
290
291 CALL keyword_create(keyword, __location__, name="REFINE_FERMI_LEVEL", &
292 description="Compute the Fermi level using the value from the FERMI_LEVEL keyword"// &
293 " as a starting point. By default the Fermi level is computed only"// &
294 " when the keyword FERMI_LEVEL is not given explicitly.", &
295 default_l_val=.false., lone_keyword_l_val=.true.)
296 CALL section_add_keyword(section, keyword)
297 CALL keyword_release(keyword)
298
299 CALL keyword_create(keyword, __location__, name="TEMPERATURE", &
300 description="Electronic temperature.", &
301 n_var=1, type_of_var=real_t, unit_str="K", &
302 default_r_val=300.0_dp/kelvin)
303 CALL section_add_keyword(section, keyword)
304 CALL keyword_release(keyword)
305
306 ! PRINT subsection
307 CALL section_create(subsection, __location__, "PRINT", "Print properties for the given contact.", &
308 repeats=.false.)
309
310 CALL create_print_dos_section(print_key, "DOS", "the Density of States (DOS)")
311 CALL section_add_subsection(subsection, print_key)
312 CALL section_release(print_key)
313
314 CALL section_add_subsection(section, subsection)
315 CALL section_release(subsection)
316
317 END SUBROUTINE create_contact_section
318
319! **************************************************************************************************
320!> \brief Create an atomic list section.
321!> \param section NEGF section
322!> \param name name of the new section
323!> \param description section description
324!> \param repeats whether the section can be repeated
325!> \par History
326!> * 02.2017 created [Sergey Chulkov]
327! **************************************************************************************************
328 SUBROUTINE create_atomlist_section(section, name, description, repeats)
329 TYPE(section_type), POINTER :: section
330 CHARACTER(len=*), INTENT(in) :: name, description
331 LOGICAL, INTENT(in) :: repeats
332
333 TYPE(keyword_type), POINTER :: keyword
334
335 cpassert(.NOT. ASSOCIATED(section))
336
337 CALL section_create(section, __location__, name=trim(adjustl(name)), &
338 description="Atoms belonging to "//trim(adjustl(description)), &
339 n_keywords=2, n_subsections=0, repeats=repeats)
340
341 NULLIFY (keyword)
342
343 CALL keyword_create(keyword, __location__, name="LIST", &
344 description="Specifies a list of atoms.", &
345 usage="LIST {integer} {integer} .. {integer}", repeats=.true., &
346 n_var=-1, type_of_var=integer_t)
347 CALL section_add_keyword(section, keyword)
348 CALL keyword_release(keyword)
349
350 CALL keyword_create(keyword, __location__, name="MOLNAME", &
351 description="Specifies a list of named molecular fragments.", &
352 usage="MOLNAME WAT MEOH", repeats=.true., &
353 n_var=-1, type_of_var=char_t)
354 CALL section_add_keyword(section, keyword)
355 CALL keyword_release(keyword)
356 END SUBROUTINE create_atomlist_section
357
358! **************************************************************************************************
359!> \brief Create the PROGRAM_RUN_INFO print section.
360!> \param section section to create
361!> \par History
362!> * 11.2020 created [Dmitry Ryndyk]
363! **************************************************************************************************
364 SUBROUTINE create_print_program_run_info_section(section)
365
366 TYPE(section_type), POINTER :: section
367
368 TYPE(keyword_type), POINTER :: keyword
369
370 CALL cp_print_key_section_create(section, __location__, "PROGRAM_RUN_INFO", &
371 description="Controls the printing of basic information during the NEGF.", &
372 print_level=low_print_level, filename="__STD_OUT__")
373 NULLIFY (keyword)
374
375 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
376 description="Level starting at which this property is printed", &
377 usage="_SECTION_PARAMETERS_", &
378 default_i_val=low_print_level, lone_keyword_i_val=low_print_level, &
379 enum_c_vals=s2a("on", "off", "silent", "low", "medium", "high", "debug"), &
380 enum_i_vals=(/silent_print_level - 1, debug_print_level + 1, &
383 CALL section_add_keyword(section, keyword)
384 CALL keyword_release(keyword)
385
386 CALL keyword_create(keyword, __location__, name="PRINT_LEVEL", &
387 variants=(/"IOLEVEL"/), &
388 description="Determines the verbose level for this section "// &
389 "additionally to GLOBAL%PRINT_LEVEL and SECTION_PARAMETERS, "// &
390 "which switch on printing.", &
391 usage="PRINT_LEVEL HIGH", &
392 default_i_val=low_print_level, enum_c_vals= &
393 s2a("SILENT", "LOW", "MEDIUM", "HIGH", "DEBUG"), &
394 enum_desc=s2a("No output", &
395 "Little output", "Quite some output", "Lots of output", &
396 "Everything is written out, useful for debugging purposes only"), &
399 CALL section_add_keyword(section, keyword)
400 CALL keyword_release(keyword)
401
402 END SUBROUTINE create_print_program_run_info_section
403
404! **************************************************************************************************
405!> \brief Create the DOS print section.
406!> \param section section to create
407!> \param name name of the new section
408!> \param description section description
409!> \par History
410!> * 11.2017 created [Sergey Chulkov]
411! **************************************************************************************************
412 SUBROUTINE create_print_dos_section(section, name, description)
413 TYPE(section_type), POINTER :: section
414 CHARACTER(len=*), INTENT(in) :: name, description
415
416 TYPE(keyword_type), POINTER :: keyword
417
418 CALL cp_print_key_section_create(section, __location__, trim(adjustl(name)), &
419 description="Controls the printing of "//trim(adjustl(description))//".", &
420 print_level=high_print_level, filename="__STD_OUT__")
421 NULLIFY (keyword)
422
423 CALL keyword_create(keyword, __location__, name="FROM_ENERGY", &
424 description="Energy point to start with.", &
425 n_var=1, type_of_var=real_t, unit_str="hartree", &
426 default_r_val=-1.0_dp)
427 CALL section_add_keyword(section, keyword)
428 CALL keyword_release(keyword)
429
430 CALL keyword_create(keyword, __location__, name="TILL_ENERGY", &
431 description="Energy point to end with.", &
432 n_var=1, type_of_var=real_t, unit_str="hartree", &
433 default_r_val=1.0_dp)
434 CALL section_add_keyword(section, keyword)
435 CALL keyword_release(keyword)
436
437 CALL keyword_create(keyword, __location__, name="N_GRIDPOINTS", &
438 description="Number of points to compute.", &
439 n_var=1, type_of_var=integer_t, default_i_val=201)
440 CALL section_add_keyword(section, keyword)
441 CALL keyword_release(keyword)
442 END SUBROUTINE create_print_dos_section
443END MODULE input_cp2k_negf
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public papior2017
integer, save, public bailey2006
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public debug_print_level
integer, parameter, public low_print_level
integer, parameter, public medium_print_level
integer, parameter, public high_print_level
integer, parameter, public silent_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 negfint_method_simpson
integer, parameter, public negfint_method_cc
Input section for NEGF based quantum transport calculations.
subroutine, public create_negf_section(section)
Create NEGF input section.
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
integer, parameter, public integer_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Definition of physical constants:
Definition physcon.F:68
real(kind=dp), parameter, public kelvin
Definition physcon.F:165
module that contains the definitions of the scf types
subroutine, public create_mixing_section(section, ls_scf)
Create CP2K input section for the mixing of the density matrix to be used only with diagonalization m...
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file