32  use, 
intrinsic :: iso_fortran_env
 
   60    type(poisson_t), 
pointer :: psolver
 
   61    type(mesh_t),    
pointer :: mesh
 
   62    type(space_t),   
pointer :: space
 
   66    type(distributed_t), 
pointer, 
public :: atoms_dist => null()
 
   67    type(atom_t), 
pointer, 
public :: atom(:) => null()
 
   68    real(real64), 
pointer, 
public :: pos(:,:) => null()
 
   69    type(lattice_vectors_t), 
pointer :: latt => null()
 
   72    type(namespace_t), 
pointer :: namespace
 
   74    logical :: have_density
 
   92    class(interaction_partner_t), 
target, 
intent(inout) :: partner
 
   93    class(ion_electron_local_potential_t),               
pointer       :: this
 
   99    this%label = 
"ion-electron local" 
  101    this%partner => partner
 
  108    class(ion_electron_local_potential_t),    
intent(inout) :: this
 
  109    class(mesh_t),                    
target, 
intent(in)    :: mesh
 
  110    type(poisson_t),                  
target, 
intent(in)    :: psolver
 
  111    type(ions_t),                     
target, 
intent(in)    :: ions
 
  112    type(namespace_t),                
target, 
intent(in)    :: namespace
 
  119    this%psolver => psolver
 
  121    safe_allocate(this%potential(1:mesh%np, 1))
 
  123    this%have_density = .false.
 
  124    do ia = 1, ions%nspecies
 
  126        this%have_density = .
true.
 
  131    this%atoms_dist => ions%atoms_dist
 
  132    this%atom => ions%atom
 
  133    this%space => ions%space
 
  135    this%latt => ions%latt
 
  137    this%namespace => namespace
 
  145    class(ion_electron_local_potential_t),             
intent(inout) :: this
 
  147    real(real64), 
allocatable :: density(:), rho(:), vl(:)
 
  148    type(submesh_t) :: sphere
 
  149    type(ps_t), 
pointer :: ps
 
  151    real(real64) :: radius
 
  159    if (this%have_density) 
then 
  160      safe_allocate(density(1:this%mesh%np))
 
  164    do ia = this%atoms_dist%start, this%atoms_dist%end
 
  171        safe_allocate(rho(1:this%mesh%np))
 
  173          this%pos(:, ia), this%mesh, rho, sphere)
 
  175        safe_deallocate_a(rho)
 
  179        safe_allocate(vl(1:this%mesh%np))
 
  180        call species_get_local(this%atom(ia)%species, this%namespace, this%space, this%latt, &
 
  181          this%pos(:, ia), this%mesh, vl)
 
  183        safe_deallocate_a(vl)
 
  188      select type(spec=>this%atom(ia)%species)
 
  193        radius = ps%vl%x_threshold*1.05_real64
 
  194        if ( .not. 
submesh_compatible(sphere,radius,this%pos(:,ia), minval(this%mesh%spacing(1:this%space%dim))) ) 
then 
  195          call submesh_init(sphere, this%space, this%mesh, this%latt, this%pos(:, ia), radius)
 
  197        safe_allocate(vl(1:sphere%np))
 
  200          if(sphere%r(ip) <= radius) 
then 
  209        safe_deallocate_a(vl)
 
  216    if (this%atoms_dist%parallel) 
then 
  217      call comm_allreduce(this%atoms_dist%mpi_grp, this%potential(:,1), dim = this%mesh%np)
 
  218      if (this%have_density) 
then 
  219        call comm_allreduce(this%atoms_dist%mpi_grp, density, dim = this%mesh%np)
 
  224    if (this%have_density) 
then 
  226      safe_allocate(vl(1:this%mesh%np_part))
 
  229      safe_deallocate_a(vl)
 
  232    safe_deallocate_a(density)
 
  245    safe_deallocate_a(this%potential)
 
  247    nullify(this%psolver)
 
constant times a vector plus a vector
logical pure function, public local_potential_has_density(space, species)
real(real64), parameter, public m_zero
real(real64), parameter, public m_one
This module defines the abstract interaction_t class, and some auxiliary classes for interactions.
subroutine, public interaction_end(this)
This module defines classes and functions for interaction partners.
subroutine ion_electron_local_potential_calculate(this)
subroutine ion_electron_local_potential_finalize(this)
subroutine ion_electron_local_potential_calculate_energy(this)
class(ion_electron_local_potential_t) function, pointer ion_electron_local_potential_constructor(partner)
subroutine ion_electron_local_potential_end(this)
subroutine ion_electron_local_potential_init(this, mesh, psolver, ions, namespace)
This module defines the meshes, which are used in Octopus.
subroutine, public dpoisson_solve(this, namespace, pot, rho, all_nodes, kernel, reset)
Calculates the Poisson equation. Given the density returns the corresponding potential.
subroutine, public profiling_out(label)
Increment out counter and sum up difference between entry and exit time.
subroutine, public profiling_in(label, exclude)
Increment in counter and save entry time.
This module defines the quantity_t class and the IDs for quantities, which can be exposed by a system...
subroutine, public species_get_local(species, namespace, space, latt, pos, mesh, vl)
used when the density is not available, or otherwise the Poisson eqn would be used instead
subroutine, public species_get_long_range_density(species, namespace, space, latt, pos, mesh, rho, sphere_inout, nlr_x)
real(real64) function, public spline_eval(spl, x)
subroutine, public submesh_end(this)
logical function, public submesh_compatible(this, radius, center, dx)
subroutine, public submesh_init(this, space, mesh, latt, center, rc)