53    type(space_t)   :: space
 
   55    integer, 
public :: 
type 
   57    character(len=1024) :: potential_formula
 
   58    character(len=200)  :: density_formula
 
   59    character(len=MAX_PATH_LEN) :: filename
 
   62    real(real64), 
allocatable, 
public :: pot(:)
 
   64    real(real64), 
allocatable, 
public :: b_field(:)
 
   66    real(real64), 
allocatable, 
public :: a_static(:,:)
 
   67    real(real64), 
allocatable, 
public :: e_field(:)
 
   70    real(real64), 
allocatable, 
public :: v_ext(:)
 
   81  integer, 
public, 
parameter ::  &
 
   82    EXTERNAL_POT_USDEF          = 201,           & !< user-defined function for local potential
 
   96    class(external_potential_t), 
pointer :: this
 
   97    type(namespace_t), 
intent(in) :: namespace
 
  103    this%namespace = 
namespace_t(
"ExternalPotential", parent=namespace)
 
  104    this%space = 
space_t(namespace)
 
  108    allocate(this%supported_interactions_as_partner(0))
 
  111    this%quantities(
e_field)%updated_on_demand = .false.
 
  115    this%quantities(
b_field)%updated_on_demand = .false.
 
  123    type(external_potential_t), 
intent(inout) :: this
 
  127    call this%deallocate_memory()
 
  134    class(external_potential_t), 
intent(inout) :: this
 
  135    class(mesh_t),               
intent(in)    :: mesh
 
  139    select case (this%type)
 
  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))
 
  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)
 
  176    select type (interaction)
 
  180      message(1) = 
"Unsupported interaction." 
  196    select type (interaction)
 
  199        do ip = 1, interaction%system_np
 
  200          interaction%partner_e_field(:, ip) = partner%e_field
 
  201          interaction%partner_b_field(:, ip) = 
m_zero 
  204        do ip = 1, interaction%system_np
 
  205          interaction%partner_e_field(:, ip) = 
m_zero 
  206          interaction%partner_b_field(:, ip) = partner%b_field
 
  213      message(1) = 
"Unsupported interaction." 
  225    class(
mesh_t),               
intent(in)    :: mesh
 
  228    real(real64) :: pot_re, pot_im, r, xx(this%space%dim)
 
  229    real(real64), 
allocatable :: den(:), grx(:)
 
  234    select case (this%type)
 
  236    case (external_pot_usdef)
 
  237      assert(
allocated(this%pot))
 
  240        call mesh_r(mesh, ip, r, coords = xx)
 
  242        this%pot(ip) = pot_re
 
  246      assert(
allocated(this%pot))
 
  250        write(
message(1), 
'(a)')    
'Error loading file '//trim(this%filename)//
'.' 
  251        write(
message(2), 
'(a,i4)') 
'Error code returned = ', err
 
  256      assert(
allocated(this%pot))
 
  258      safe_allocate(den(1:mesh%np))
 
  261        call mesh_r(mesh, ip, r, coords = xx)
 
  269        this%pot(1:mesh%np) = 
m_zero 
  271      call dpoisson_solve(poisson, namespace, this%pot, den, all_nodes = .false.)
 
  273      safe_deallocate_a(den)
 
  276      assert(
allocated(this%b_field))
 
  282      safe_allocate(grx(1:this%space%dim))
 
  284      select case (this%space%dim)
 
  286        select case (this%gauge_2d)
 
  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." 
  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)
 
  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)
 
  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))
 
  317      safe_deallocate_a(grx)
 
  320      assert(
allocated(this%e_field))
 
  322      if (this%space%periodic_dim < this%space%dim) 
then 
  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))
 
  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))
 
  354    integer :: n_pot_block, row, read_data
 
  358    integer :: dim, periodic_dim, idir
 
  404    if (
parse_block(namespace, 
'StaticExternalPotentials', blk) == 0) 
then 
  407      do row = 0, n_pot_block-1
 
  412        assert(read_data > 0)
 
  414        call external_potentials%add(pot)
 
  424    call parse_variable(namespace, 
'PeriodicDimensions', 0, periodic_dim)
 
  448    if (
parse_block(namespace, 
'StaticMagneticField', blk) == 0) 
then 
  467      call parse_variable(namespace, 
'StaticMagneticField2DGauge', 0, pot%gauge_2d)
 
  472      safe_allocate(pot%b_field(1:3))
 
  480        if (periodic_dim == 2) 
then 
  481          message(1) = 
"StaticMagneticField cannot be applied in a 2D, 2D-periodic system." 
  484        if (pot%b_field(1)**2 + pot%b_field(2)**2 > 
m_zero) 
then 
  491        if (periodic_dim >= 2) 
then 
  492          message(1) = 
"In 3D, StaticMagneticField cannot be applied when the system is 2D- or 3D-periodic." 
  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." 
  504      call external_potentials%add(pot)
 
  522    if (
parse_block(namespace, 
'StaticElectricField', blk) == 0) 
then 
  528      safe_allocate(pot%e_field(1:dim))
 
  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." 
  541      call external_potentials%add(pot)
 
  554    type(
block_t),              
intent(in)    :: blk
 
  555    integer,                    
intent(in)    :: row
 
  556    integer,                    
intent(out)   :: read_data
 
  558    integer :: ncols, icol, flag
 
  572    if (pot%type >= 0) 
then 
  573      message(1) = 
'Error in reading the ExternalPotentials block' 
  583      call messages_input_error(namespace, 
'ExternalPotentials', 
"Unknown type of external potential")
 
  590      if (icol >= ncols) 
exit 
  596      case (option__staticexternalpotentials__file)
 
  600      case (option__staticexternalpotentials__potential_formula)
 
  605        if (pot%type /= external_pot_usdef) 
then 
  606          call messages_input_error(namespace, 
'ExternalPotentials', 
'potential_formula can only be used with user_defined')
 
  609      case (option__staticexternalpotentials__density_formula)
 
  615          call messages_input_error(namespace, 
'ExternalPotentials', 
'density_formula can only be used with charge_density')
 
  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.")
 
  633      call messages_input_error(namespace, 
'ExternalPotentials', 
"The 'density_formula' parameter is missing.")
 
  647      integer(int64), 
intent(in) :: param
 
  661      integer(int64), 
intent(in) :: param
 
  666        call messages_input_error(namespace, 
'ExternalPotentials', 
"Duplicated parameter in external potential.")
 
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
 
real(real64), parameter, public m_epsilon
 
real(real64), parameter, public m_half
 
real(real64), parameter, public p_c
Electron gyromagnetic ratio, see Phys. Rev. Lett. 130, 071801 (2023)
 
real(real64), parameter, public m_one
 
This module implements a simple hash table for non-negative integer keys and integer values.
 
subroutine, public iihash_end(h)
Free a hash table.
 
subroutine, public iihash_insert(h, key, val)
Insert a (key, val) pair into the hash table h.
 
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...
 
subroutine, public iihash_init(h)
Initialize a hash table h.
 
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.
 
pure subroutine, public mesh_r(mesh, ip, rr, origin, coords)
return the distance to the origin for a given grid point
 
subroutine, public messages_not_implemented(feature, namespace)
 
subroutine, public messages_warning(no_lines, all_nodes, namespace)
 
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
 
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
 
subroutine, public messages_input_error(namespace, var, details, row, column)
 
integer function, public parse_block(namespace, name, blk, check_varinfo_)
 
logical pure function, public poisson_solver_is_iterative(this)
 
subroutine, public dpoisson_solve(this, namespace, pot, rho, all_nodes, kernel)
Calculates the Poisson equation. Given the density returns the corresponding potential.
 
This module defines the quantity_t class and the IDs for quantities, which can be exposed by a system...
 
integer, parameter, public b_field
 
integer, parameter, public e_field
 
subroutine, public conv_to_c_string(str)
converts to c string
 
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
 
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.