48    logical :: oct_exchange = .false.
 
   49    type(states_elec_t), 
pointer :: oct_st => null()
 
   50    real(real64), 
allocatable :: oct_fxc(:, :, :)
 
   51    real(real64), 
allocatable :: oct_pot(:, :)
 
   52    real(real64), 
allocatable :: oct_rho(:, :)
 
   59    type(oct_exchange_t), 
intent(in) :: this
 
   63    oct_exchange = this%oct_exchange
 
   71    type(oct_exchange_t),     
intent(inout) :: this
 
   72    type(states_elec_t), 
target, 
intent(in) :: st
 
   73    class(mesh_t),            
intent(in)    :: mesh
 
   83    this%oct_exchange = .
true.
 
   85    nspin = this%oct_st%d%nspin
 
   87    safe_allocate(this%oct_fxc(1:np, 1:nspin, 1:nspin))
 
   88    safe_allocate(this%oct_pot(1:np, 1:nspin))
 
   89    safe_allocate(this%oct_rho(1:np, 1:nspin))
 
  101    type(oct_exchange_t), 
intent(inout) :: this
 
  102    class(mesh_t),        
intent(in)    :: mesh
 
  103    complex(real64),      
intent(in)    :: psi(:, :, :, :)
 
  104    type(xc_t),           
intent(in)    :: xc
 
  105    type(poisson_t),      
intent(in)    :: psolver
 
  106    type(namespace_t),    
intent(in)    :: namespace
 
  108    integer :: jst, ip, ik
 
  109    complex(real64), 
allocatable :: psi2(:, :)
 
  113    safe_allocate(psi2(1:mesh%np, 1:this%oct_st%d%dim))
 
  115    select case (this%oct_st%d%ispin)
 
  117      assert(this%oct_st%nik == 1)
 
  121      do jst = 1, this%oct_st%nst
 
  124          this%oct_rho(ip, 1) = this%oct_rho(ip, 1) + this%oct_st%occ(jst, 1)*aimag(conjg(psi2(ip, 1))*psi(ip, 1, jst, 1))
 
  127      call dpoisson_solve(psolver, namespace, this%oct_pot(:, 1), this%oct_rho(:, 1), all_nodes = .false.)
 
  130      assert(this%oct_st%nik == 2)
 
  135        do jst = 1, this%oct_st%nst
 
  138            this%oct_rho(ip, ik) = this%oct_rho(ip, ik) + this%oct_st%occ(jst, ik) * aimag(conjg(psi2(ip, 1))*psi(ip, 1, jst, ik))
 
  144        call dpoisson_solve(psolver, namespace, this%oct_pot(:, ik), this%oct_rho(:, ik), all_nodes = .false.)
 
  150    call xc_get_fxc(xc, mesh, namespace, this%oct_st%rho, this%oct_st%d%ispin, this%oct_fxc)
 
  152    safe_deallocate_a(psi2)
 
  164    this%oct_exchange = .false.
 
  165    safe_deallocate_a(this%oct_fxc)
 
  166    safe_deallocate_a(this%oct_pot)
 
  167    safe_deallocate_a(this%oct_rho)
 
  176    class(
mesh_t),        
intent(in)    :: mesh
 
  177    complex(real64),      
intent(inout) :: hpsi(:, :)
 
  178    integer,              
intent(in)    :: ist
 
  179    integer,              
intent(in)    :: ik
 
  182    complex(real64), 
allocatable :: psi(:, :), psi2(:, :)
 
  187    safe_allocate(psi(1:mesh%np, 1:this%oct_st%d%dim))
 
  188    safe_allocate(psi2(1:mesh%np, 1:this%oct_st%d%dim))
 
  190    select case (this%oct_st%d%ispin)
 
  192      assert(this%oct_st%nik == 1)
 
  195        hpsi(ip, 1) = hpsi(ip, 1) + 
m_two*
m_zi*psi2(ip, 1)*(this%oct_pot(ip, 1) + this%oct_fxc(ip, 1, 1)*this%oct_rho(ip, 1))
 
  199      assert(this%oct_st%nik == 2)
 
  205          hpsi(ip, 1) = hpsi(ip, 1) + 
m_two * 
m_zi * this%oct_st%occ(ist, ik) * &
 
  206            psi2(ip, 1) * (this%oct_pot(ip, ik2) + this%oct_fxc(ip, ik, ik2)*this%oct_rho(ip, ik2))
 
  214    safe_deallocate_a(psi)
 
  215    safe_deallocate_a(psi2)
 
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
 
integer, parameter, public unpolarized
Parameters...
 
integer, parameter, public spinors
 
integer, parameter, public spin_polarized
 
real(real64), parameter, public m_two
 
real(real64), parameter, public m_zero
 
complex(real64), parameter, public m_zi
 
This module defines the meshes, which are used in Octopus.
 
subroutine, public messages_not_implemented(feature, namespace)
 
logical function, public oct_exchange_enabled(this)
 
subroutine, public oct_exchange_remove(this)
 
subroutine, public oct_exchange_set(this, st, mesh)
 
subroutine, public oct_exchange_operator(this, namespace, mesh, hpsi, ist, ik)
 
subroutine, public oct_exchange_prepare(this, mesh, psi, xc, psolver, namespace)
 
subroutine, public dpoisson_solve(this, namespace, pot, rho, all_nodes, kernel)
Calculates the Poisson equation. Given the density returns the corresponding potential.
 
This module handles spin dimensions of the states and the k-point distribution.
 
subroutine, public xc_get_fxc(xcs, mesh, namespace, rho, ispin, fxc, zfxc)
 
Describes mesh distribution to nodes.