Octopus
external_potential.F90
Go to the documentation of this file.
1!! Copyright (C) 2020 N. Tancogne-Dejean
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18#include "global.h"
19
21 use debug_oct_m
22 use global_oct_m
23 use iihash_oct_m
31 use mesh_oct_m
34 use parser_oct_m
38 use space_oct_m
39 use string_oct_m
40 use unit_oct_m
43 implicit none
44
45 private
46 public :: &
49
51 private
52
53 type(space_t) :: space
54
55 integer, public :: type
56
57 character(len=1024) :: potential_formula
58 character(len=200) :: density_formula
59 character(len=MAX_PATH_LEN) :: filename
60 real(real64) :: omega
61
62 real(real64), allocatable, public :: pot(:)
63
64 real(real64), allocatable, public :: b_field(:)
65 integer :: gauge_2D
66 real(real64), allocatable, public :: a_static(:,:)
67 real(real64), allocatable, public :: e_field(:)
68 !Auxiliary arrays for the electrons only
69 !TODO: Suppress once electrons fully use the new framework
70 real(real64), allocatable, public :: v_ext(:)
71
72 contains
73 procedure :: calculate => external_potential_calculate
74 procedure :: allocate_memory => external_potential_allocate
75 procedure :: deallocate_memory => external_potential_deallocate
76 procedure :: init_interaction_as_partner => external_potential_init_interaction_as_partner
77 procedure :: copy_quantities_to_interaction => external_potential_copy_quantities_to_interaction
80
81 integer, public, parameter :: &
82 EXTERNAL_POT_USDEF = 201, & !< user-defined function for local potential
87
88
89 interface external_potential_t
90 module procedure external_potential_init
91 end interface external_potential_t
92
93contains
94
95 function external_potential_init(namespace) result(this)
96 class(external_potential_t), pointer :: this
97 type(namespace_t), intent(in) :: namespace
98
100
101 allocate(this)
102
103 this%namespace = namespace_t("ExternalPotential", parent=namespace)
104 this%space = space_t(namespace)
105
106 this%type = -1
107
108 allocate(this%supported_interactions_as_partner(0))
109
110 this%quantities(e_field)%always_available = .true.
111 this%quantities(e_field)%updated_on_demand = .false.
112 this%quantities(e_field)%iteration = iteration_counter_t()
114 this%quantities(b_field)%always_available = .true.
115 this%quantities(b_field)%updated_on_demand = .false.
116 this%quantities(b_field)%iteration = iteration_counter_t()
117
119 end function external_potential_init
120
121 ! ---------------------------------------------------------
122 subroutine external_potential_finalize(this)
123 type(external_potential_t), intent(inout) :: this
124
126
127 call this%deallocate_memory()
128
130 end subroutine external_potential_finalize
131
132 ! ---------------------------------------------------------
133 subroutine external_potential_allocate(this, mesh)
134 class(external_potential_t), intent(inout) :: this
135 class(mesh_t), intent(in) :: mesh
136
138
139 select case (this%type)
140 case (external_pot_usdef, external_pot_from_file, external_pot_charge_density)
141 safe_allocate(this%pot(1:mesh%np))
143 safe_allocate(this%a_static(1:mesh%np, 1:this%space%dim))
145 if (this%space%periodic_dim < this%space%dim) then
146 safe_allocate(this%pot(1:mesh%np))
147 safe_allocate(this%v_ext(1:mesh%np_part))
148 end if
149 end select
154 ! ---------------------------------------------------------
156 class(external_potential_t), intent(inout) :: this
160 safe_deallocate_a(this%pot)
161 safe_deallocate_a(this%b_field)
162 safe_deallocate_a(this%a_static)
163 safe_deallocate_a(this%e_field)
164 safe_deallocate_a(this%v_ext)
165
169 ! ---------------------------------------------------------
170 subroutine external_potential_init_interaction_as_partner(partner, interaction)
171 class(external_potential_t), intent(in) :: partner
172 class(interaction_surrogate_t), intent(inout) :: interaction
173
175
176 select type (interaction)
177 type is (lorentz_force_t)
178 ! Nothing to be initialized for the Lorentz force.
179 class default
180 message(1) = "Unsupported interaction."
181 call messages_fatal(1, namespace=partner%namespace)
182 end select
183
186
187 ! ---------------------------------------------------------
189 class(external_potential_t), intent(inout) :: partner
190 class(interaction_surrogate_t), intent(inout) :: interaction
191
192 integer :: ip
193
195
196 select type (interaction)
197 type is (lorentz_force_t)
198 if (partner%type == external_pot_static_efield) then
199 do ip = 1, interaction%system_np
200 interaction%partner_e_field(:, ip) = partner%e_field
201 interaction%partner_b_field(:, ip) = m_zero
202 end do
203 else if (partner%type == external_pot_static_bfield) then
204 do ip = 1, interaction%system_np
205 interaction%partner_e_field(:, ip) = m_zero
206 interaction%partner_b_field(:, ip) = partner%b_field
207 end do
208 else
209 assert(.false.) !This should never occur.
210 end if
211
212 class default
213 message(1) = "Unsupported interaction."
214 call messages_fatal(1, namespace=partner%namespace)
215 end select
216
219
220
221 ! ---------------------------------------------------------
222 subroutine external_potential_calculate(this, namespace, mesh, poisson)
223 class(external_potential_t), intent(inout) :: this
224 type(namespace_t), intent(in) :: namespace
225 class(mesh_t), intent(in) :: mesh
226 type(poisson_t), intent(in) :: poisson
227
228 real(real64) :: pot_re, pot_im, r, xx(this%space%dim)
229 real(real64), allocatable :: den(:), grx(:)
230 integer :: ip, err
231
233
234 select case (this%type)
235
236 case (external_pot_usdef)
237 assert(allocated(this%pot))
238
239 do ip = 1, mesh%np
240 call mesh_r(mesh, ip, r, coords = xx)
241 call parse_expression(pot_re, pot_im, this%space%dim, xx, r, m_zero, this%potential_formula)
242 this%pot(ip) = pot_re
243 end do
244
246 assert(allocated(this%pot))
247
248 call dio_function_input(trim(this%filename), namespace, this%space, mesh, this%pot, err)
249 if (err /= 0) then
250 write(message(1), '(a)') 'Error loading file '//trim(this%filename)//'.'
251 write(message(2), '(a,i4)') 'Error code returned = ', err
252 call messages_fatal(2, namespace=namespace)
253 end if
254
256 assert(allocated(this%pot))
257
258 safe_allocate(den(1:mesh%np))
259
260 do ip = 1, mesh%np
261 call mesh_r(mesh, ip, r, coords = xx)
262 call parse_expression(pot_re, pot_im, this%space%dim, xx, r, m_zero, this%potential_formula)
263 den(ip) = pot_re
264 end do
265
266 if (poisson_solver_is_iterative(poisson)) then
267 ! pot has to be initialized before entering routine
268 ! and our best guess for the potential is zero
269 this%pot(1:mesh%np) = m_zero
270 end if
271 call dpoisson_solve(poisson, namespace, this%pot, den, all_nodes = .false.)
272
273 safe_deallocate_a(den)
274
276 assert(allocated(this%b_field))
277
278 ! Compute the vector potential from a uniform B field.
279 ! The sign is determined by the relation $\vec{B} = \nabla \times \vec{A}$.
280 ! This leads to $\vec{A} = -\frac{1}{2}\vec{r}\times\vec{B}$.
281 ! A factor 1/c is already added, to avoid adding it everytime we update the Hamiltonian
282 safe_allocate(grx(1:this%space%dim))
283
284 select case (this%space%dim)
285 case (2)
286 select case (this%gauge_2d)
287 case (0) ! linear_xy
288 if (this%space%periodic_dim == 1) then
289 message(1) = "For 2D system, 1D-periodic, StaticMagneticField can only be "
290 message(2) = "applied for StaticMagneticField2DGauge = linear_y."
291 call messages_fatal(2, namespace=namespace)
292 end if
293 !$omp parallel do private(grx)
294 do ip = 1, mesh%np
295 grx(1:this%space%dim) = mesh%x(ip, 1:this%space%dim)
296 this%a_static(ip, :) = -m_half/p_c * (/grx(2), -grx(1)/) * this%b_field(3)
297 end do
298 case (1) ! linear y
299 !$omp parallel do private(grx)
300 do ip = 1, mesh%np
301 grx(1:this%space%dim) = mesh%x(ip, 1:this%space%dim)
302 this%a_static(ip, :) = -m_one/p_c * (/grx(2), m_zero/) * this%b_field(3)
303 end do
304 end select
305 case (3)
306 !$omp parallel do private(grx)
307 do ip = 1, mesh%np
308 grx(1:this%space%dim) = mesh%x(ip, 1:this%space%dim)
309 this%a_static(ip, 1) = -m_half/p_c*(grx(2) * this%b_field(3) - grx(3) * this%b_field(2))
310 this%a_static(ip, 2) = -m_half/p_c*(grx(3) * this%b_field(1) - grx(1) * this%b_field(3))
311 this%a_static(ip, 3) = -m_half/p_c*(grx(1) * this%b_field(2) - grx(2) * this%b_field(1))
312 end do
313 case default
314 assert(.false.)
315 end select
316
317 safe_deallocate_a(grx)
318
320 assert(allocated(this%e_field))
321
322 if (this%space%periodic_dim < this%space%dim) then
323 ! Compute the scalar potential
324 !
325 ! Note that the -1 sign is missing. This is because we
326 ! consider the electrons with +1 charge. The electric field
327 ! however retains the sign because we also consider protons to
328 ! have +1 charge when calculating the force.
329 !
330 ! NTD: This comment is very confusing and prone to error
331 ! TODO: Fix this to have physically sound quantities and interactions
332 do ip = 1, mesh%np
333 this%pot(ip) = sum(mesh%x(ip, this%space%periodic_dim + 1:this%space%dim) &
334 * this%e_field(this%space%periodic_dim + 1:this%space%dim))
335 end do
336 ! The following is needed to make interpolations.
337 ! It is used by PCM.
338 this%v_ext(1:mesh%np) = this%pot(1:mesh%np)
339 do ip = mesh%np+1, mesh%np_part
340 this%v_ext(ip) = sum(mesh%x(ip, this%space%periodic_dim + 1:this%space%dim) &
341 * this%e_field(this%space%periodic_dim + 1:this%space%dim))
342 end do
343 end if
344
345 end select
346
348 end subroutine external_potential_calculate
349
350 subroutine load_external_potentials(external_potentials, namespace)
351 class(partner_list_t), intent(inout) :: external_potentials
352 type(namespace_t), intent(in) :: namespace
353
354 integer :: n_pot_block, row, read_data
355 type(block_t) :: blk
356 class(external_potential_t), pointer :: pot
357
358 integer :: dim, periodic_dim, idir
359
361
362 !%Variable StaticExternalPotentials
363 !%Type block
364 !%Section System
365 !%Description
366 !% An static external potential is a model potential added to the local potential of the Hamiltonian
367 !%
368 !% The format of this block is the following:
369 !% The first field defines the type of species (the valid options are detailed
370 !% below).
371 !%
372 !% Then a list of parameters follows. The parameters are specified
373 !% by a first field with the parameter name and the field that
374 !% follows with the value of the parameter. Some parameters are
375 !% specific to a certain species while others are accepted by all
376 !% species. These are <tt>mass</tt>, <tt>max_spacing</tt>, and <tt>min_radius</tt>.
377 !%
378 !% These are examples of possible species:
379 !%
380 !% <tt>%ExternalPotential
381 !% <br>&nbsp;&nbsp; potential_user_defined | potential_formula | "1/2*r^2"
382 !% <br>%</tt>
383 !%Option potential_from_file -202
384 !% The potential is read from a file. Accepted file formats, detected by extension: obf, ncdf and csv.
385 !%Option potential_user_defined -201
386 !% Species with user-defined potential. The potential for the
387 !% species is defined by the formula given by the <tt>potential_formula</tt>
388 !% parameter.
389 !%Option potential_charge_density -203
390 !% The potential for this species is created from the distribution
391 !% of charge given by the <tt>density_formula</tt> parameter.
392 !%Option file -10010
393 !% The path for the file that describes the species.
394 !%Option potential_formula -10012
395 !% Mathematical expression that defines the potential for <tt>species_user_defined</tt>. You can use
396 !% any of the <i>x</i>, <i>y</i>, <i>z</i> or <i>r</i> variables.
397 !%Option density_formula -10013
398 !% Mathematical expression that defines the charge density for <tt>species_charge_density</tt>. You can use
399 !% any of the <i>x</i>, <i>y</i>, <i>z</i> or <i>r</i> variables.
400 !%End
401
402 ! First, find out if there is a Species block.
403 n_pot_block = 0
404 if (parse_block(namespace, 'StaticExternalPotentials', blk) == 0) then
405 n_pot_block = parse_block_n(blk)
406
407 do row = 0, n_pot_block-1
408 !Create a potential
409 pot => external_potential_t(namespace)
410 !Parse the information from the block
411 call read_from_block(pot, namespace, blk, row, read_data)
412 assert(read_data > 0)
413 !Add this to the list
414 call external_potentials%add(pot)
415 end do
416 call parse_block_end(blk)
417 end if
418
419
420 !Here I am parsing the variables Dimensions et PeriodicDimensions because we do not have access
421 !to this information here.
422 !TODO: This needs to be removed and replaced by something better
423 call parse_variable(namespace, 'Dimensions', 3, dim)
424 call parse_variable(namespace, 'PeriodicDimensions', 0, periodic_dim)
425
426
427 !%Variable StaticMagneticField
428 !%Type block
429 !%Section Hamiltonian
430 !%Description
431 !% A static constant magnetic field may be added to the usual Hamiltonian,
432 !% by setting the block <tt>StaticMagneticField</tt>.
433 !% The three possible components of the block (which should only have one
434 !% line) are the three components of the magnetic field vector. Note that
435 !% if you are running the code in 1D mode, this will not work, and if you
436 !% are running the code in 2D mode the magnetic field will have to be in
437 !% the <i>z</i>-direction, so that the first two columns should be zero.
438 !% Possible in periodic system only in these cases: 2D system, 1D periodic,
439 !% with <tt>StaticMagneticField2DGauge = linear_y</tt>;
440 !% 3D system, 1D periodic, field is zero in <i>y</i>- and <i>z</i>-directions (given
441 !% currently implemented gauges).
442 !%
443 !% The magnetic field should always be entered in atomic units, regardless
444 !% of the <tt>Units</tt> variable. Note that we use the "Gaussian" system
445 !% meaning 1 au[B] = <math> 2.350517568\times 10^9</math> Gauss, which corresponds to
446 !% <math>2.3505175678\times 10^5</math> Tesla.
447 !%End
448 if (parse_block(namespace, 'StaticMagneticField', blk) == 0) then
449 !Create a potential
450 pot => external_potential_t(namespace)
452 pot%supported_interactions_as_partner = [lorentz_force]
453
454 !%Variable StaticMagneticField2DGauge
455 !%Type integer
456 !%Default linear_xy
457 !%Section Hamiltonian
458 !%Description
459 !% The gauge of the static vector potential <math>A</math> when a magnetic field
460 !% <math>B = \left( 0, 0, B_z \right)</math> is applied to a 2D-system.
461 !%Option linear_xy 0
462 !% Linear gauge with <math>A = \frac{1}{2c} \left( -y, x \right) B_z</math>. (Cannot be used for periodic systems.)
463 !%Option linear_y 1
464 !% Linear gauge with <math>A = \frac{1}{c} \left( -y, 0 \right) B_z</math>. Can be used for <tt>PeriodicDimensions = 1</tt>
465 !% but not <tt>PeriodicDimensions = 2</tt>.
466 !%End
467 call parse_variable(namespace, 'StaticMagneticField2DGauge', 0, pot%gauge_2d)
468 if (.not. varinfo_valid_option('StaticMagneticField2DGauge', pot%gauge_2d)) then
469 call messages_input_error(namespace, 'StaticMagneticField2DGauge')
470 end if
471
472 safe_allocate(pot%b_field(1:3))
473 do idir = 1, 3
474 call parse_block_float(blk, 0, idir - 1, pot%b_field(idir))
475 end do
476 select case (dim)
477 case (1)
478 call messages_input_error(namespace, 'StaticMagneticField')
479 case (2)
480 if (periodic_dim == 2) then
481 message(1) = "StaticMagneticField cannot be applied in a 2D, 2D-periodic system."
482 call messages_fatal(1, namespace=namespace)
483 end if
484 if (pot%b_field(1)**2 + pot%b_field(2)**2 > m_zero) then
485 call messages_input_error(namespace, 'StaticMagneticField')
486 end if
487 case (3)
488 ! Consider cross-product below: if grx(1:this%space%periodic_dim) is used, it is not ok.
489 ! Therefore, if idir is periodic, b_field for all other directions must be zero.
490 ! 1D-periodic: only Bx. 2D-periodic or 3D-periodic: not allowed. Other gauges could allow 2D-periodic case.
491 if (periodic_dim >= 2) then
492 message(1) = "In 3D, StaticMagneticField cannot be applied when the system is 2D- or 3D-periodic."
493 call messages_fatal(1, namespace=namespace)
494 else if (periodic_dim == 1 .and. any(abs(pot%b_field(2:3)) > m_zero)) then
495 message(1) = "In 3D, 1D-periodic, StaticMagneticField must be zero in the y- and z-directions."
496 call messages_fatal(1, namespace=namespace)
497 end if
498 end select
499 call parse_block_end(blk)
500
501 if (dim > 3) call messages_not_implemented('Magnetic field for dim > 3', namespace=namespace)
502
503 !Add this to the list
504 call external_potentials%add(pot)
505
506 !The corresponding A field on the mesh is computed in the routine external_potential_calculate
507
508 end if
509
510 !%Variable StaticElectricField
511 !%Type block
512 !%Default 0
513 !%Section Hamiltonian
514 !%Description
515 !% A static constant electric field may be added to the usual Hamiltonian,
516 !% by setting the block <tt>StaticElectricField</tt>.
517 !% The three possible components of the block (which should only have one
518 !% line) are the three components of the electric field vector.
519 !% It can be applied in a periodic direction of a large supercell via
520 !% the single-point Berry phase.
521 !%End
522 if (parse_block(namespace, 'StaticElectricField', blk) == 0) then
523 !Create a potential
524 pot => external_potential_t(namespace)
526 pot%supported_interactions_as_partner = [lorentz_force]
527
528 safe_allocate(pot%e_field(1:dim))
529 do idir = 1, dim
530 call parse_block_float(blk, 0, idir - 1, pot%e_field(idir), units_inp%energy / units_inp%length)
531
532 !Electron-specific checks (k-points) are done in the hamiltonian_elec.F90 file
533 if (idir <= periodic_dim .and. abs(pot%e_field(idir)) > m_epsilon) then
534 message(1) = "Applying StaticElectricField in a periodic direction is only accurate for large supercells."
535 call messages_warning(1, namespace=namespace)
536 end if
537 end do
538 call parse_block_end(blk)
539
540 !Add this to the list
541 call external_potentials%add(pot)
542
543 !The corresponding A field on the mesh is computed in the routine external_potential_calculate
544 end if
545
546
548 end subroutine load_external_potentials
549
550 ! ---------------------------------------------------------
551 subroutine read_from_block(pot, namespace, blk, row, read_data)
552 type(external_potential_t), intent(inout) :: pot
553 type(namespace_t), intent(in) :: namespace
554 type(block_t), intent(in) :: blk
555 integer, intent(in) :: row
556 integer, intent(out) :: read_data
557
558 integer :: ncols, icol, flag
559 type(iihash_t) :: read_parameters
560
561
562 push_sub(read_from_block)
563
564 ncols = parse_block_cols(blk, row)
565 read_data = 0
566
567 call parse_block_integer(blk, row, 0, pot%type)
568
569 ! To detect the old species block format, options are represented
570 ! as negative values. If we get a non-negative value we know we
571 ! are reading a mass.
572 if (pot%type >= 0) then
573 message(1) = 'Error in reading the ExternalPotentials block'
574 call messages_fatal(1, namespace=namespace)
575 end if
576
577 ! now we convert back to positive
578 pot%type = -pot%type
579
580 read_data = 1
581
582 if (pot%type /= external_pot_charge_density .and. pot%type /= external_pot_usdef .and. pot%type /= external_pot_from_file) then
583 call messages_input_error(namespace, 'ExternalPotentials', "Unknown type of external potential")
584 end if
585
586 call iihash_init(read_parameters)
587
588 icol = read_data
589 do
590 if (icol >= ncols) exit
591
592 call parse_block_integer(blk, row, icol, flag)
593
594 select case (flag)
595
596 case (option__staticexternalpotentials__file)
597 call check_duplication(option__staticexternalpotentials__file)
598 call parse_block_string(blk, row, icol + 1, pot%filename)
599
600 case (option__staticexternalpotentials__potential_formula)
601 call check_duplication(option__staticexternalpotentials__potential_formula)
602 call parse_block_string(blk, row, icol + 1, pot%potential_formula)
603 call conv_to_c_string(pot%potential_formula)
604
605 if (pot%type /= external_pot_usdef) then
606 call messages_input_error(namespace, 'ExternalPotentials', 'potential_formula can only be used with user_defined')
607 end if
608
609 case (option__staticexternalpotentials__density_formula)
610 call check_duplication(option__staticexternalpotentials__density_formula)
611 call parse_block_string(blk, row, icol + 1, pot%density_formula)
612 call conv_to_c_string(pot%density_formula)
613
614 if (pot%type /= external_pot_charge_density) then
615 call messages_input_error(namespace, 'ExternalPotentials', 'density_formula can only be used with charge_density')
616 end if
617
618 case default
619 call messages_input_error(namespace, 'ExternalPotentials', "Unknown parameter ")
620
621 end select
622
623 icol = icol + 2
624 end do
625 ! CHECK THAT WHAT WE PARSED MAKES SENSE
626
627
628 if (pot%type == external_pot_usdef .and. .not. parameter_defined(option__staticexternalpotentials__potential_formula)) then
629 call messages_input_error(namespace, 'ExternalPotentials', "The 'potential_formula' parameter is missing.")
630 end if
631
632 if (pot%type == external_pot_charge_density .and. .not. parameter_defined(option__staticexternalpotentials__density_formula)) then
633 call messages_input_error(namespace, 'ExternalPotentials', "The 'density_formula' parameter is missing.")
634 end if
635
636 if (pot%type == external_pot_from_file .and. .not. (parameter_defined(option__staticexternalpotentials__file))) then
637 call messages_input_error(namespace, 'ExternalPotentials', "The 'file' parameter is missing.")
638 end if
639
640 call iihash_end(read_parameters)
641
642 pop_sub(read_from_block)
643
644 contains
645
646 logical function parameter_defined(param) result(defined)
647 integer(int64), intent(in) :: param
648
649 integer :: tmp
650
652
653 tmp = iihash_lookup(read_parameters, int(-param), defined)
654
656 end function parameter_defined
657
658 !------------------------------------------------------
659
660 subroutine check_duplication(param)
661 integer(int64), intent(in) :: param
662
664
665 if (parameter_defined(param)) then
666 call messages_input_error(namespace, 'ExternalPotentials', "Duplicated parameter in external potential.")
667 end if
668
669 call iihash_insert(read_parameters, int(-param), 1)
670
672 end subroutine check_duplication
673
674 end subroutine read_from_block
675 ! ---------------------------------------------------------
676
677
679
680!! Local Variables:
681!! mode: f90
682!! coding: utf-8
683!! End:
subroutine check_duplication(param)
logical function parameter_defined(param)
integer, parameter, public external_pot_from_file
potential, defined in a file
subroutine, public load_external_potentials(external_potentials, namespace)
class(external_potential_t) function, pointer external_potential_init(namespace)
subroutine read_from_block(pot, namespace, blk, row, read_data)
integer, parameter, public external_pot_charge_density
user-defined function for charge density
subroutine external_potential_finalize(this)
subroutine external_potential_calculate(this, namespace, mesh, poisson)
subroutine external_potential_init_interaction_as_partner(partner, interaction)
subroutine external_potential_deallocate(this)
subroutine external_potential_copy_quantities_to_interaction(partner, interaction)
integer, parameter, public external_pot_static_efield
Static electric field.
integer, parameter, public external_pot_static_bfield
Static magnetic field.
subroutine external_potential_allocate(this, mesh)
real(real64), parameter, public m_zero
Definition: global.F90:187
real(real64), parameter, public m_epsilon
Definition: global.F90:203
real(real64), parameter, public m_half
Definition: global.F90:193
real(real64), parameter, public p_c
Electron gyromagnetic ratio, see Phys. Rev. Lett. 130, 071801 (2023)
Definition: global.F90:223
real(real64), parameter, public m_one
Definition: global.F90:188
This module implements a simple hash table for non-negative integer keys and integer values.
Definition: iihash.F90:125
subroutine, public iihash_end(h)
Free a hash table.
Definition: iihash.F90:184
subroutine, public iihash_insert(h, key, val)
Insert a (key, val) pair into the hash table h.
Definition: iihash.F90:206
integer function, public iihash_lookup(h, key, found)
Look up a value in the hash table h. If found is present, it indicates if key could be found in the t...
Definition: iihash.F90:231
subroutine, public iihash_init(h)
Initialize a hash table h.
Definition: iihash.F90:161
integer, parameter, public lorentz_force
This module defines classes and functions for interaction partners.
subroutine, public dio_function_input(filename, namespace, space, mesh, ff, ierr, map)
Reads a mesh function from file filename, and puts it into ff. If the map argument is passed,...
This module defines the meshes, which are used in Octopus.
Definition: mesh.F90:118
pure subroutine, public mesh_r(mesh, ip, rr, origin, coords)
return the distance to the origin for a given grid point
Definition: mesh.F90:336
subroutine, public messages_not_implemented(feature, namespace)
Definition: messages.F90:1125
subroutine, public messages_warning(no_lines, all_nodes, namespace)
Definition: messages.F90:543
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:420
subroutine, public messages_input_error(namespace, var, details, row, column)
Definition: messages.F90:723
integer function, public parse_block(namespace, name, blk, check_varinfo_)
Definition: parser.F90:618
logical pure function, public poisson_solver_is_iterative(this)
Definition: poisson.F90:1300
subroutine, public dpoisson_solve(this, namespace, pot, rho, all_nodes, kernel)
Calculates the Poisson equation. Given the density returns the corresponding potential.
Definition: poisson.F90:892
This module defines the quantity_t class and the IDs for quantities, which can be exposed by a system...
Definition: quantity.F90:137
integer, parameter, public b_field
Definition: quantity.F90:146
integer, parameter, public e_field
Definition: quantity.F90:146
subroutine, public conv_to_c_string(str)
converts to c string
Definition: string.F90:252
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
Definition: unit.F90:132
This module defines the unit system, used for input and output.
type(unit_system_t), public units_inp
the units systems for reading and writing
abstract class for general interaction partners
surrogate interaction class to avoid circular dependencies between modules.
This class implements the iteration counter used by the multisystem algorithms. As any iteration coun...
Lorenz force between a systems of particles and an electromagnetic field.
Describes mesh distribution to nodes.
Definition: mesh.F90:186
int true(void)