86    real(real64), 
allocatable :: dchi(:,:,:,:)
 
   87    complex(real64), 
allocatable :: zchi(:,:,:,:)
 
   91    type(states_elec_t), 
public, 
pointer :: st => null()
 
   92    real(real64) :: cam_omega = 
m_zero 
   93    real(real64) :: cam_alpha = 
m_zero 
   94    real(real64) :: cam_beta = 
m_zero 
   96    type(poisson_t) :: psolver
 
   98    type(singularity_t) :: singul
 
  100    logical       :: useACE = .false.
 
  104  type(fourier_space_op_t) :: coulb
 
  108  real(real64), 
parameter, 
private :: TOL_EXX_WEIGHT = 1.0e-3_real64 
 
  112  subroutine exchange_operator_init(this, namespace, space, st, der, mc, stencil, kpoints, omega, alpha, beta)
 
  113    type(exchange_operator_t), 
intent(inout) :: this
 
  114    type(namespace_t),         
intent(in)    :: namespace
 
  115    class(space_t),            
intent(in)    :: space
 
  116    type(states_elec_t),       
intent(in)    :: st
 
  117    type(derivatives_t),       
intent(in)    :: der
 
  118    type(multicomm_t),         
intent(in)    :: mc
 
  119    type(stencil_t),           
intent(in)    :: stencil
 
  120    type(kpoints_t),           
intent(in)    :: kpoints
 
  121    real(real64),              
intent(in)    :: alpha, beta, omega
 
  125    this%cam_omega = omega
 
  126    this%cam_alpha = alpha
 
  138    call parse_variable(namespace, 
'AdaptivelyCompressedExchange', .false., this%useACE)
 
  143      call poisson_init(this%psolver, namespace, space, der, mc, stencil, st%qtot, &
 
  144        force_serial = .
true., verbose = .false.)
 
  146      call poisson_init(this%psolver, namespace, space, der, mc, stencil, st%qtot, &
 
  147        force_serial = .
true., verbose = .false., force_cmplx = .
true.)
 
  154    type(exchange_operator_t),           
intent(inout) :: this
 
  155    real(real64),                        
intent(in)    :: omega, alpha, beta
 
  156    type(states_elec_t), 
target, 
optional, 
intent(in)  :: st
 
  160    if (
present(st)) 
then 
  164    this%cam_omega = omega
 
  165    this%cam_alpha = alpha
 
  172    type(exchange_operator_t), 
intent(inout) :: this
 
  176    if (
associated(this%st)) 
then 
  179      safe_deallocate_p(this%st)
 
  184    safe_deallocate_a(this%ace%dchi)
 
  185    safe_deallocate_a(this%ace%zchi)
 
  196    type(
mesh_t),              
intent(in) :: mesh
 
  203    call batch_scal(mesh%np, this%st%occ(:, hpsib%ik), hpsib)
 
  211#include "exchange_operator_inc.F90" 
  214#include "complex.F90" 
  215#include "exchange_operator_inc.F90" 
scale a batch by a constant or vector
 
This module implements batches of mesh functions.
 
This module implements common operations on batches of mesh functions.
 
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
 
subroutine, public dexchange_operator_hartree_apply(this, namespace, mesh, st_d, kpoints, exx_coef, psib, hpsib)
 
subroutine, public dexchange_operator_apply(this, namespace, space, mesh, st_d, kpoints, psib, hpsib, rdmft)
 
subroutine, public dexchange_operator_ace(this, namespace, mesh, st, xst, phase)
 
subroutine, public zexchange_operator_commute_r(this, namespace, mesh, st_d, ik, psi, gpsi)
 
subroutine, public zexchange_operator_compute_potentials(this, namespace, space, gr, st, xst, kpoints, ex, F_out)
 
subroutine, public dexchange_operator_compute_potentials(this, namespace, space, gr, st, xst, kpoints, ex, F_out)
 
subroutine, public dexchange_operator_commute_r(this, namespace, mesh, st_d, ik, psi, gpsi)
 
subroutine, public dexchange_operator_single(this, namespace, space, mesh, st_d, kpoints, ist, ik, psi, hpsi, rdmft)
 
subroutine, public exchange_operator_init(this, namespace, space, st, der, mc, stencil, kpoints, omega, alpha, beta)
 
subroutine, public zexchange_operator_hartree_apply(this, namespace, mesh, st_d, kpoints, exx_coef, psib, hpsib)
 
subroutine, public exchange_operator_end(this)
 
subroutine, public zexchange_operator_single(this, namespace, space, mesh, st_d, kpoints, ist, ik, psi, hpsi, rdmft)
 
subroutine, public zexchange_operator_ace(this, namespace, mesh, st, xst, phase)
 
subroutine, public exchange_operator_rdmft_occ_apply(this, mesh, hpsib)
 
subroutine, public exchange_operator_reinit(this, omega, alpha, beta, st)
 
subroutine, public zexchange_operator_apply(this, namespace, space, mesh, st_d, kpoints, psib, hpsib, rdmft)
 
subroutine, public fourier_space_op_end(this)
 
real(real64), parameter, public m_zero
 
This module implements the underlying real-space grid.
 
This module is intended to contain "only mathematical" functions and procedures.
 
This module defines functions over batches of mesh functions.
 
This module defines various routines, operating on mesh functions.
 
This module defines the meshes, which are used in Octopus.
 
subroutine, public messages_experimental(name, namespace)
 
This module handles the communicators for the various parallelization strategies.
 
Some general things and nomenclature:
 
subroutine, public poisson_init(this, namespace, space, der, mc, stencil, qtot, label, solver, verbose, force_serial, force_cmplx)
 
subroutine, public poisson_end(this)
 
This module is an helper to perform ring-pattern communications among all states.
 
subroutine, public singularity_end(this)
 
subroutine, public singularity_init(this, namespace, space, st, kpoints)
 
pure logical function, public states_are_real(st)
 
This module provides routines for communicating all batches in a ring-pattern scheme.
 
This module handles spin dimensions of the states and the k-point distribution.
 
subroutine, public states_elec_end(st)
finalize the states_elec_t object
 
This module provides routines for communicating states when using states parallelization.
 
subroutine, public states_elec_parallel_remote_access_stop(this)
stop remote memory access for states on other processors
 
This module defines stencils used in Octopus.
 
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.
 
Describes mesh distribution to nodes.
 
batches of electronic states