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 call this%quantities%add(quantity_t("E field", always_available = .true., updated_on_demand = .false., &
111 iteration = iteration_counter_t()))
112 call this%quantities%add(quantity_t("B field", always_available = .true., updated_on_demand = .false., &
113 iteration = iteration_counter_t()))
114
116 end function external_potential_init
117
118 ! ---------------------------------------------------------
119 subroutine external_potential_finalize(this)
120 type(external_potential_t), intent(inout) :: this
121
123
124 call this%deallocate_memory()
125
127 end subroutine external_potential_finalize
128
129 ! ---------------------------------------------------------
130 subroutine external_potential_allocate(this, mesh)
131 class(external_potential_t), intent(inout) :: this
132 class(mesh_t), intent(in) :: mesh
133
135
136 select case (this%type)
137 case (external_pot_usdef, external_pot_from_file, external_pot_charge_density)
138 safe_allocate(this%pot(1:mesh%np))
140 safe_allocate(this%a_static(1:mesh%np, 1:this%space%dim))
142 if (this%space%periodic_dim < this%space%dim) then
143 safe_allocate(this%pot(1:mesh%np))
144 safe_allocate(this%v_ext(1:mesh%np_part))
145 end if
146 end select
147
149 end subroutine external_potential_allocate
151 ! ---------------------------------------------------------
153 class(external_potential_t), intent(inout) :: this
154
156
157 safe_deallocate_a(this%pot)
158 safe_deallocate_a(this%b_field)
159 safe_deallocate_a(this%a_static)
160 safe_deallocate_a(this%e_field)
161 safe_deallocate_a(this%v_ext)
162
164 end subroutine external_potential_deallocate
165
166 ! ---------------------------------------------------------
167 subroutine external_potential_init_interaction_as_partner(partner, interaction)
168 class(external_potential_t), intent(in) :: partner
169 class(interaction_surrogate_t), intent(inout) :: interaction
172
173 select type (interaction)
175 ! Nothing to be initialized for the Lorentz force.
176 class default
177 message(1) = "Unsupported interaction."
178 call messages_fatal(1, namespace=partner%namespace)
179 end select
180
183
184 ! ---------------------------------------------------------
185 subroutine external_potential_copy_quantities_to_interaction(partner, interaction)
186 class(external_potential_t), intent(inout) :: partner
187 class(interaction_surrogate_t), intent(inout) :: interaction
189 integer :: ip
190
192
193 select type (interaction)
194 type is (lorentz_force_t)
195 if (partner%type == external_pot_static_efield) then
196 do ip = 1, interaction%system_np
197 interaction%partner_e_field(:, ip) = partner%e_field
198 interaction%partner_b_field(:, ip) = m_zero
199 end do
200 else if (partner%type == external_pot_static_bfield) then
201 do ip = 1, interaction%system_np
202 interaction%partner_e_field(:, ip) = m_zero
203 interaction%partner_b_field(:, ip) = partner%b_field
204 end do
205 else
206 assert(.false.) !This should never occur.
207 end if
208
209 class default
210 message(1) = "Unsupported interaction."
211 call messages_fatal(1, namespace=partner%namespace)
212 end select
213
216
217
218 ! ---------------------------------------------------------
219 subroutine external_potential_calculate(this, namespace, mesh, poisson)
220 class(external_potential_t), intent(inout) :: this
221 type(namespace_t), intent(in) :: namespace
222 class(mesh_t), intent(in) :: mesh
223 type(poisson_t), intent(in) :: poisson
224
225 real(real64) :: pot_re, pot_im, r, xx(this%space%dim)
226 real(real64), allocatable :: den(:), grx(:)
227 integer :: ip, err
228
230
231 select case (this%type)
232
233 case (external_pot_usdef)
234 assert(allocated(this%pot))
235
236 do ip = 1, mesh%np
237 call mesh_r(mesh, ip, r, coords = xx)
238 call parse_expression(pot_re, pot_im, this%space%dim, xx, r, m_zero, this%potential_formula)
239 this%pot(ip) = pot_re
240 end do
241
243 assert(allocated(this%pot))
244
245 call dio_function_input(trim(this%filename), namespace, this%space, mesh, this%pot, err)
246 if (err /= 0) then
247 write(message(1), '(a)') 'Error loading file '//trim(this%filename)//'.'
248 write(message(2), '(a,i4)') 'Error code returned = ', err
249 call messages_fatal(2, namespace=namespace)
250 end if
251
253 assert(allocated(this%pot))
254
255 safe_allocate(den(1:mesh%np))
256
257 do ip = 1, mesh%np
258 call mesh_r(mesh, ip, r, coords = xx)
259 call parse_expression(pot_re, pot_im, this%space%dim, xx, r, m_zero, this%potential_formula)
260 den(ip) = pot_re
261 end do
262
263 call dpoisson_solve(poisson, namespace, this%pot, den, all_nodes = .false.)
264
265 safe_deallocate_a(den)
266
268 assert(allocated(this%b_field))
269
270 ! Compute the vector potential from a uniform B field.
271 ! The sign is determined by the relation $\vec{B} = \nabla \times \vec{A}$.
272 ! This leads to $\vec{A} = -\frac{1}{2}\vec{r}\times\vec{B}$.
273 ! A factor 1/c is already added, to avoid adding it everytime we update the Hamiltonian
274 safe_allocate(grx(1:this%space%dim))
275
276 select case (this%space%dim)
277 case (2)
278 select case (this%gauge_2d)
279 case (0) ! linear_xy
280 if (this%space%periodic_dim == 1) then
281 message(1) = "For 2D system, 1D-periodic, StaticMagneticField can only be "
282 message(2) = "applied for StaticMagneticField2DGauge = linear_y."
283 call messages_fatal(2, namespace=namespace)
284 end if
285 !$omp parallel do private(grx)
286 do ip = 1, mesh%np
287 grx(1:this%space%dim) = mesh%x(ip, 1:this%space%dim)
288 this%a_static(ip, :) = -m_half/p_c * (/grx(2), -grx(1)/) * this%b_field(3)
289 end do
290 case (1) ! linear y
291 !$omp parallel do private(grx)
292 do ip = 1, mesh%np
293 grx(1:this%space%dim) = mesh%x(ip, 1:this%space%dim)
294 this%a_static(ip, :) = -m_one/p_c * (/grx(2), m_zero/) * this%b_field(3)
295 end do
296 end select
297 case (3)
298 !$omp parallel do private(grx)
299 do ip = 1, mesh%np
300 grx(1:this%space%dim) = mesh%x(ip, 1:this%space%dim)
301 this%a_static(ip, 1) = -m_half/p_c*(grx(2) * this%b_field(3) - grx(3) * this%b_field(2))
302 this%a_static(ip, 2) = -m_half/p_c*(grx(3) * this%b_field(1) - grx(1) * this%b_field(3))
303 this%a_static(ip, 3) = -m_half/p_c*(grx(1) * this%b_field(2) - grx(2) * this%b_field(1))
304 end do
305 case default
306 assert(.false.)
307 end select
308
309 safe_deallocate_a(grx)
310
312 assert(allocated(this%e_field))
313
314 if (this%space%periodic_dim < this%space%dim) then
315 ! Compute the scalar potential
316 !
317 ! Note that the -1 sign is missing. This is because we
318 ! consider the electrons with +1 charge. The electric field
319 ! however retains the sign because we also consider protons to
320 ! have +1 charge when calculating the force.
321 !
322 ! NTD: This comment is very confusing and prone to error
323 ! TODO: Fix this to have physically sound quantities and interactions
324 do ip = 1, mesh%np
325 this%pot(ip) = sum(mesh%x(ip, this%space%periodic_dim + 1:this%space%dim) &
326 * this%e_field(this%space%periodic_dim + 1:this%space%dim))
327 end do
328 ! The following is needed to make interpolations.
329 ! It is used by PCM.
330 this%v_ext(1:mesh%np) = this%pot(1:mesh%np)
331 do ip = mesh%np+1, mesh%np_part
332 this%v_ext(ip) = sum(mesh%x(ip, this%space%periodic_dim + 1:this%space%dim) &
333 * this%e_field(this%space%periodic_dim + 1:this%space%dim))
334 end do
335 end if
336
337 end select
338
340 end subroutine external_potential_calculate
341
342 subroutine load_external_potentials(external_potentials, namespace)
343 class(partner_list_t), intent(inout) :: external_potentials
344 type(namespace_t), intent(in) :: namespace
345
346 integer :: n_pot_block, row, read_data
347 type(block_t) :: blk
348 class(external_potential_t), pointer :: pot
349
350 integer :: dim, periodic_dim, idir
351
353
354 !%Variable StaticExternalPotentials
355 !%Type block
356 !%Section System
357 !%Description
358 !% An static external potential is a model potential added to the local potential of the Hamiltonian
359 !%
360 !% The format of this block is the following:
361 !% The first field defines the type of species (the valid options are detailed
362 !% below).
363 !%
364 !% Then a list of parameters follows. The parameters are specified
365 !% by a first field with the parameter name and the field that
366 !% follows with the value of the parameter. Some parameters are
367 !% specific to a certain species while others are accepted by all
368 !% species. These are <tt>mass</tt>, <tt>max_spacing</tt>, and <tt>min_radius</tt>.
369 !%
370 !% These are examples of possible species:
371 !%
372 !% <tt>%ExternalPotential
373 !% <br>&nbsp;&nbsp; potential_user_defined | potential_formula | "1/2*r^2"
374 !% <br>%</tt>
375 !%Option potential_from_file -202
376 !% The potential is read from a file. Accepted file formats, detected by extension: obf, ncdf and csv.
377 !%Option potential_user_defined -201
378 !% Species with user-defined potential. The potential for the
379 !% species is defined by the formula given by the <tt>potential_formula</tt>
380 !% parameter.
381 !%Option potential_charge_density -203
382 !% The potential for this species is created from the distribution
383 !% of charge given by the <tt>density_formula</tt> parameter.
384 !%Option file -10010
385 !% The path for the file that describes the species.
386 !%Option potential_formula -10012
387 !% Mathematical expression that defines the potential for <tt>species_user_defined</tt>. You can use
388 !% any of the <i>x</i>, <i>y</i>, <i>z</i> or <i>r</i> variables.
389 !%Option density_formula -10013
390 !% Mathematical expression that defines the charge density for <tt>species_charge_density</tt>. You can use
391 !% any of the <i>x</i>, <i>y</i>, <i>z</i> or <i>r</i> variables.
392 !%End
393
394 ! First, find out if there is a Species block.
395 n_pot_block = 0
396 if (parse_block(namespace, 'StaticExternalPotentials', blk) == 0) then
397 n_pot_block = parse_block_n(blk)
398
399 do row = 0, n_pot_block-1
400 !Create a potential
401 pot => external_potential_t(namespace)
402 !Parse the information from the block
403 call read_from_block(pot, namespace, blk, row, read_data)
404 assert(read_data > 0)
405 !Add this to the list
406 call external_potentials%add(pot)
407 end do
408 call parse_block_end(blk)
409 end if
410
411
412 !Here I am parsing the variables Dimensions et PeriodicDimensions because we do not have access
413 !to this information here.
414 !TODO: This needs to be removed and replaced by something better
415 call parse_variable(namespace, 'Dimensions', 3, dim)
416 call parse_variable(namespace, 'PeriodicDimensions', 0, periodic_dim)
417
418
419 !%Variable StaticMagneticField
420 !%Type block
421 !%Section Hamiltonian
422 !%Description
423 !% A static constant magnetic field may be added to the usual Hamiltonian,
424 !% by setting the block <tt>StaticMagneticField</tt>.
425 !% The three possible components of the block (which should only have one
426 !% line) are the three components of the magnetic field vector. Note that
427 !% if you are running the code in 1D mode, this will not work, and if you
428 !% are running the code in 2D mode the magnetic field will have to be in
429 !% the <i>z</i>-direction, so that the first two columns should be zero.
430 !% Possible in periodic system only in these cases: 2D system, 1D periodic,
431 !% with <tt>StaticMagneticField2DGauge = linear_y</tt>;
432 !% 3D system, 1D periodic, field is zero in <i>y</i>- and <i>z</i>-directions (given
433 !% currently implemented gauges).
434 !%
435 !% The magnetic field should always be entered in atomic units, regardless
436 !% of the <tt>Units</tt> variable. Note that we use the "Gaussian" system
437 !% meaning 1 au[B] = <math> 2.350517568\times 10^9</math> Gauss, which corresponds to
438 !% <math>2.3505175678\times 10^5</math> Tesla.
439 !%End
440 if (parse_block(namespace, 'StaticMagneticField', blk) == 0) then
441 !Create a potential
442 pot => external_potential_t(namespace)
444 pot%supported_interactions_as_partner = [lorentz_force]
445
446 !%Variable StaticMagneticField2DGauge
447 !%Type integer
448 !%Default linear_xy
449 !%Section Hamiltonian
450 !%Description
451 !% The gauge of the static vector potential <math>A</math> when a magnetic field
452 !% <math>B = \left( 0, 0, B_z \right)</math> is applied to a 2D-system.
453 !%Option linear_xy 0
454 !% Linear gauge with <math>A = \frac{1}{2c} \left( -y, x \right) B_z</math>. (Cannot be used for periodic systems.)
455 !%Option linear_y 1
456 !% Linear gauge with <math>A = \frac{1}{c} \left( -y, 0 \right) B_z</math>. Can be used for <tt>PeriodicDimensions = 1</tt>
457 !% but not <tt>PeriodicDimensions = 2</tt>.
458 !%End
459 call parse_variable(namespace, 'StaticMagneticField2DGauge', 0, pot%gauge_2d)
460 if (.not. varinfo_valid_option('StaticMagneticField2DGauge', pot%gauge_2d)) then
461 call messages_input_error(namespace, 'StaticMagneticField2DGauge')
462 end if
463
464 safe_allocate(pot%b_field(1:3))
465 do idir = 1, 3
466 call parse_block_float(blk, 0, idir - 1, pot%b_field(idir))
467 end do
468 select case (dim)
469 case (1)
470 call messages_input_error(namespace, 'StaticMagneticField')
471 case (2)
472 if (periodic_dim == 2) then
473 message(1) = "StaticMagneticField cannot be applied in a 2D, 2D-periodic system."
474 call messages_fatal(1, namespace=namespace)
475 end if
476 if (pot%b_field(1)**2 + pot%b_field(2)**2 > m_zero) then
477 call messages_input_error(namespace, 'StaticMagneticField')
478 end if
479 case (3)
480 ! Consider cross-product below: if grx(1:this%space%periodic_dim) is used, it is not ok.
481 ! Therefore, if idir is periodic, b_field for all other directions must be zero.
482 ! 1D-periodic: only Bx. 2D-periodic or 3D-periodic: not allowed. Other gauges could allow 2D-periodic case.
483 if (periodic_dim >= 2) then
484 message(1) = "In 3D, StaticMagneticField cannot be applied when the system is 2D- or 3D-periodic."
485 call messages_fatal(1, namespace=namespace)
486 else if (periodic_dim == 1 .and. any(abs(pot%b_field(2:3)) > m_zero)) then
487 message(1) = "In 3D, 1D-periodic, StaticMagneticField must be zero in the y- and z-directions."
488 call messages_fatal(1, namespace=namespace)
489 end if
490 end select
491 call parse_block_end(blk)
492
493 if (dim > 3) call messages_not_implemented('Magnetic field for dim > 3', namespace=namespace)
494
495 !Add this to the list
496 call external_potentials%add(pot)
497
498 !The corresponding A field on the mesh is computed in the routine external_potential_calculate
499
500 end if
501
502 !%Variable StaticElectricField
503 !%Type block
504 !%Default 0
505 !%Section Hamiltonian
506 !%Description
507 !% A static constant electric field may be added to the usual Hamiltonian,
508 !% by setting the block <tt>StaticElectricField</tt>.
509 !% The three possible components of the block (which should only have one
510 !% line) are the three components of the electric field vector.
511 !% It can be applied in a periodic direction of a large supercell via
512 !% the single-point Berry phase.
513 !%End
514 if (parse_block(namespace, 'StaticElectricField', blk) == 0) then
515 !Create a potential
516 pot => external_potential_t(namespace)
518 pot%supported_interactions_as_partner = [lorentz_force]
519
520 safe_allocate(pot%e_field(1:dim))
521 do idir = 1, dim
522 call parse_block_float(blk, 0, idir - 1, pot%e_field(idir), units_inp%energy / units_inp%length)
523
524 !Electron-specific checks (k-points) are done in the hamiltonian_elec.F90 file
525 if (idir <= periodic_dim .and. abs(pot%e_field(idir)) > m_epsilon) then
526 message(1) = "Applying StaticElectricField in a periodic direction is only accurate for large supercells."
527 call messages_warning(1, namespace=namespace)
528 end if
529 end do
530 call parse_block_end(blk)
531
532 !Add this to the list
533 call external_potentials%add(pot)
534
535 !The corresponding A field on the mesh is computed in the routine external_potential_calculate
536 end if
537
538
540 end subroutine load_external_potentials
541
542 ! ---------------------------------------------------------
543 subroutine read_from_block(pot, namespace, blk, row, read_data)
544 type(external_potential_t), intent(inout) :: pot
545 type(namespace_t), intent(in) :: namespace
546 type(block_t), intent(in) :: blk
547 integer, intent(in) :: row
548 integer, intent(out) :: read_data
549
550 integer :: ncols, icol, flag
551 type(iihash_t) :: read_parameters
552
553
554 push_sub(read_from_block)
555
556 ncols = parse_block_cols(blk, row)
557 read_data = 0
558
559 call parse_block_integer(blk, row, 0, pot%type)
560
561 ! To detect the old species block format, options are represented
562 ! as negative values. If we get a non-negative value we know we
563 ! are reading a mass.
564 if (pot%type >= 0) then
565 message(1) = 'Error in reading the ExternalPotentials block'
566 call messages_fatal(1, namespace=namespace)
567 end if
568
569 ! now we convert back to positive
570 pot%type = -pot%type
571
572 read_data = 1
573
574 if (pot%type /= external_pot_charge_density .and. pot%type /= external_pot_usdef .and. pot%type /= external_pot_from_file) then
575 call messages_input_error(namespace, 'ExternalPotentials', "Unknown type of external potential")
576 end if
577
578 call iihash_init(read_parameters)
579
580 icol = read_data
581 do
582 if (icol >= ncols) exit
583
584 call parse_block_integer(blk, row, icol, flag)
585
586 select case (flag)
587
588 case (option__staticexternalpotentials__file)
589 call check_duplication(option__staticexternalpotentials__file)
590 call parse_block_string(blk, row, icol + 1, pot%filename)
591
592 case (option__staticexternalpotentials__potential_formula)
593 call check_duplication(option__staticexternalpotentials__potential_formula)
594 call parse_block_string(blk, row, icol + 1, pot%potential_formula)
595 call conv_to_c_string(pot%potential_formula)
596
597 if (pot%type /= external_pot_usdef) then
598 call messages_input_error(namespace, 'ExternalPotentials', 'potential_formula can only be used with user_defined')
599 end if
600
601 case (option__staticexternalpotentials__density_formula)
602 call check_duplication(option__staticexternalpotentials__density_formula)
603 call parse_block_string(blk, row, icol + 1, pot%density_formula)
604 call conv_to_c_string(pot%density_formula)
605
606 if (pot%type /= external_pot_charge_density) then
607 call messages_input_error(namespace, 'ExternalPotentials', 'density_formula can only be used with charge_density')
608 end if
609
610 case default
611 call messages_input_error(namespace, 'ExternalPotentials', "Unknown parameter ")
612
613 end select
614
615 icol = icol + 2
616 end do
617 ! CHECK THAT WHAT WE PARSED MAKES SENSE
618
619
620 if (pot%type == external_pot_usdef .and. .not. parameter_defined(option__staticexternalpotentials__potential_formula)) then
621 call messages_input_error(namespace, 'ExternalPotentials', "The 'potential_formula' parameter is missing.")
622 end if
623
624 if (pot%type == external_pot_charge_density .and. .not. parameter_defined(option__staticexternalpotentials__density_formula)) then
625 call messages_input_error(namespace, 'ExternalPotentials', "The 'density_formula' parameter is missing.")
626 end if
627
628 if (pot%type == external_pot_from_file .and. .not. (parameter_defined(option__staticexternalpotentials__file))) then
629 call messages_input_error(namespace, 'ExternalPotentials', "The 'file' parameter is missing.")
630 end if
631
632 call iihash_end(read_parameters)
633
634 pop_sub(read_from_block)
635
636 contains
637
638 logical function parameter_defined(param) result(defined)
639 integer(int64), intent(in) :: param
640
641 integer :: tmp
642
644
645 tmp = iihash_lookup(read_parameters, int(-param), defined)
646
648 end function parameter_defined
649
650 !------------------------------------------------------
651
652 subroutine check_duplication(param)
653 integer(int64), intent(in) :: param
654
656
657 if (parameter_defined(param)) then
658 call messages_input_error(namespace, 'ExternalPotentials', "Duplicated parameter in external potential.")
659 end if
660
661 call iihash_insert(read_parameters, int(-param), 1)
662
664 end subroutine check_duplication
665
666 end subroutine read_from_block
667 ! ---------------------------------------------------------
668
669
671
672!! Local Variables:
673!! mode: f90
674!! coding: utf-8
675!! 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:188
real(real64), parameter, public m_epsilon
Definition: global.F90:204
real(real64), parameter, public m_half
Definition: global.F90:194
real(real64), parameter, public p_c
Electron gyromagnetic ratio, see Phys. Rev. Lett. 130, 071801 (2023)
Definition: global.F90:224
real(real64), parameter, public m_one
Definition: global.F90:189
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:1113
subroutine, public messages_warning(no_lines, all_nodes, namespace)
Definition: messages.F90:537
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:414
subroutine, public messages_input_error(namespace, var, details, row, column)
Definition: messages.F90:713
integer function, public parse_block(namespace, name, blk, check_varinfo_)
Definition: parser.F90:618
subroutine, public dpoisson_solve(this, namespace, pot, rho, all_nodes, kernel, reset)
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:138
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
Systems (system_t) can expose quantities that can be used to calculate interactions with other system...
Definition: quantity.F90:171
int true(void)