45  integer, 
parameter, 
public :: &
 
   46    ZORA_NONE                = 0,     &  !< no ZORA
 
   55    real(real64), 
allocatable  :: pot(:,:)
 
   56    real(real64), 
allocatable  :: grad_pot(:,:,:)
 
   57    real(real64), 
allocatable  :: soc(:,:,:)
 
   59    real(real64)   :: so_strength = 
m_zero 
   60    real(real64)   :: mass        = 
m_zero 
   62    integer :: zora_level  = zora_none
 
   72    procedure zora_constructor
 
   82    type(namespace_t),           
intent(in)    :: namespace
 
   83    type(derivatives_t),         
intent(in)    :: der
 
   84    type(states_elec_dim_t),     
intent(in)    :: st_d
 
   85    type(epot_t),                
intent(in)    :: ep
 
   86    real(real64),                
intent(in)    :: mass
 
   87    class(zora_t), 
pointer                     :: this
 
   93    this%so_strength   = ep%so_strength
 
   96    select case (ep%reltype)
 
  102      this%zora_level = zora_none
 
  107    if (der%dim /= 3) 
then 
  111    safe_allocate(this%pot(1:der%mesh%np_part, 1:st_d%nspin))
 
  112    safe_allocate(this%grad_pot(1:der%mesh%np, 1:st_d%nspin, 1:der%dim))
 
  116      assert(st_d%nspin == 4)
 
  117      safe_allocate(this%soc(1:der%mesh%np, 1:st_d%nspin, 1:der%dim))
 
  128    type(zora_t), 
intent(inout) :: this
 
  132    safe_deallocate_a(this%pot)
 
  133    safe_deallocate_a(this%grad_pot)
 
  134    safe_deallocate_a(this%soc)
 
  162    real(real64), 
contiguous,     
intent(in)    :: potential(:, :)
 
  164    real(real64), 
allocatable :: zora_scpot(:), grad_pot(:,:)
 
  165    real(real64)       :: prefactor, two_c2
 
  172    if (this%zora_level == zora_none) 
then 
  177    nspin = 
size(this%pot, dim=2)
 
  182    safe_allocate( zora_scpot(1:der%mesh%np_part) )
 
  183    safe_allocate( grad_pot(1:der%mesh%np_part, 1:der%dim) )
 
  187    do ip = 1, der%mesh%np
 
  189      zora_scpot(ip) = potential(ip, 1)
 
  192      this%pot(ip,1) = two_c2 / (this%mass * two_c2 - zora_scpot(ip) )
 
  198      do ip = 1, der%mesh%np
 
  199        this%pot(ip,2) = this%pot(ip,1)
 
  205      do ip = 1, der%mesh%np
 
  220      do ip = 1, der%mesh%np
 
  221        this%grad_pot(ip, 1, idir)= grad_pot(ip,idir)
 
  227        do ip = 1, der%mesh%np
 
  228          this%grad_pot(ip, 2, idir)= grad_pot(ip,idir)
 
  235        do ip = 1, der%mesh%np
 
  236          this%grad_pot(ip, 3, idir)= 
m_zero 
  237          this%grad_pot(ip, 4, idir)= 
m_zero 
  250    safe_deallocate_a( zora_scpot )
 
  251    safe_deallocate_a( grad_pot )
 
  265      real(real64), 
allocatable :: grad_v(:,:)
 
  269      safe_allocate(grad_v(1:der%mesh%np, 1:der%dim))
 
  277      do ip = 1, der%mesh%np
 
  280        prefactor = this%so_strength *  two_c2 / (this%mass*two_c2 - zora_scpot(ip))**2
 
  282        grad_v(ip, 1) = grad_v(ip, 1) * prefactor
 
  283        grad_v(ip, 2) = grad_v(ip, 2) * prefactor
 
  284        grad_v(ip, 3) = grad_v(ip, 3) * prefactor
 
  288        this%soc(ip, 1, 1) = -grad_v(ip, 2)
 
  289        this%soc(ip, 2, 1) =  grad_v(ip, 2)
 
  290        this%soc(ip, 3, 1) =  
m_zero 
  291        this%soc(ip, 4, 1) = -grad_v(ip, 3)
 
  293        this%soc(ip, 1, 2) =  grad_v(ip, 1)
 
  294        this%soc(ip, 2, 2) = -grad_v(ip, 1)
 
  295        this%soc(ip, 3, 2) = -grad_v(ip, 3)
 
  296        this%soc(ip, 4, 2) =  
m_zero 
  298        this%soc(ip, 1, 3) =  
m_zero 
  299        this%soc(ip, 2, 3) =  
m_zero 
  300        this%soc(ip, 3, 3) =  grad_v(ip, 2)
 
  301        this%soc(ip, 4, 3) =  grad_v(ip, 1)
 
  307      safe_deallocate_a(grad_v)
 
  316#include "zora_inc.F90" 
  319#include "complex.F90" 
  320#include "zora_inc.F90" 
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 dderivatives_grad(der, ff, op_ff, ghost_update, set_bc, to_cartesian)
apply the gradient to a mesh function
 
integer, parameter, public scalar_relativistic_zora
 
integer, parameter, public fully_relativistic_zora
 
real(real64), parameter, public m_two
 
real(real64), parameter, public m_zero
 
real(real64), parameter, public p_c
Electron gyromagnetic ratio, see Phys. Rev. Lett. 130, 071801 (2023)
 
This module implements the underlying real-space grid.
 
This module defines the meshes, which are used in Octopus.
 
subroutine, public messages_not_implemented(feature, namespace)
 
This module handles spin dimensions of the states and the k-point distribution.
 
This module implements the ZORA terms for the Hamoiltonian.
 
subroutine zzora_apply_batch(this, mesh, der, states_dim, psib, hpsib)
apply the ZORA to a batch of states psib
 
integer, parameter, public zora_scalar_relativistic
ZORA for scalar relativistic calculations.
 
subroutine zora_update(this, der, potential)
update the ZORA potentials
 
subroutine dzora_apply_batch(this, mesh, der, states_dim, psib, hpsib)
apply the ZORA to a batch of states psib
 
class(zora_t) function, pointer zora_constructor(namespace, der, st_d, ep, mass)
initialize the ZORA
 
subroutine zora_finalize(this)
finalize the ZORA object and free memory
 
integer, parameter, public zora_fully_relativistic
ZORA for fully relativistic calculations.
 
class representing derivatives
 
This class is responsible for calculating and applying the ZORA.
 
subroutine zora_update_fully_relativistic()
update quantities, necessary only for fully relativistic ZORA