25  use, 
intrinsic :: iso_fortran_env
 
   46  integer, 
public, 
parameter ::        &
 
   54    integer, 
public    :: level
 
   55    real(real64)       :: lambda
 
   56    real(real64), 
allocatable :: constrain(:,:)
 
   57    real(real64), 
allocatable, 
public :: pot(:,:)
 
   58    real(real64),       
public :: energy
 
   62    real(real64), 
pointer     :: rho(:,:)
 
   68    type(magnetic_constrain_t), 
intent(inout) :: this
 
   69    type(namespace_t),         
intent(in)    :: namespace
 
   70    class(mesh_t),             
intent(in)    :: mesh
 
   71    type(states_elec_dim_t),   
intent(in)    :: std
 
   72    real(real64), 
target,             
intent(in)    :: rho(:,:)
 
   73    integer,                   
intent(in)    :: natoms
 
   74    real(real64),              
intent(in)    :: min_dist
 
   77    real(real64)   :: rmin, norm
 
   97    call parse_variable(namespace, 
'MagneticConstrain', constrain_none, this%level)
 
   99    if (this%level == constrain_none) 
then 
  113    call parse_variable(namespace, 
'MagneticConstrainStrength', 0.01_real64, this%lambda)
 
  118    if (
parse_block(namespace, 
'AtomsMagnetDirection', blk) < 0) 
then 
  119      message(1) = 
"AtomsMagnetDirection block is not defined." 
  120      message(2) = 
"Magnetic constrained DFT cannot be used without it." 
  125      message(1) = 
"AtomsMagnetDirection block has the wrong number of rows." 
  130      message(1) = 
"Magnetic constrains can only be used for spin-polized and spinor calculations." 
  134    safe_allocate(this%constrain(1:3, natoms))
 
  140      elseif (std%ispin == 
spinors) 
then 
  143          if (abs(this%constrain(idir, ia)) < 1.0e-20_real64) this%constrain(idir, ia) = 
m_zero 
  149        norm = norm2(this%constrain(1:3, ia))
 
  150        this%constrain(1:3, ia) = this%constrain(1:3, ia) / norm
 
  155    safe_allocate(this%pot(1:mesh%np, std%nspin))
 
  159    call parse_variable(namespace, 
'LocalMagneticMomentsSphereRadius', min(
m_half*rmin, 100.0_real64), &
 
  172    safe_deallocate_a(this%constrain)
 
  173    safe_deallocate_a(this%pot)
 
  182    class(
mesh_t),              
intent(in)    :: mesh
 
  184    class(
space_t),             
intent(in)    :: space
 
  186    real(real64),               
intent(in)    :: pos(:,:)
 
  188    integer :: ia, idir, ip
 
  189    real(real64) :: bb(3), b2, lmm(3), dotp, norm, xx
 
  190    real(real64), 
allocatable :: md(:,:), mdf(:), mask(:)
 
  194    if (this%level == constrain_none) 
return 
  203    safe_allocate(md(1:mesh%np, 1:max(space%dim, 3)))
 
  204    safe_allocate(mdf(1:mesh%np))
 
  207    natoms = 
size(pos, dim=2)
 
  210      call submesh_init(sphere, space, mesh, latt, pos(:, ia), this%lmm_r)
 
  212      safe_allocate(mask(1:sphere%np))
 
  215        xx = sphere%r(ip) * 
m_pi / this%lmm_r
 
  230      do idir = 1, max(space%dim, 3)
 
  232          mdf(sphere%map(ip)) = md(sphere%map(ip), idir) * mask(ip)
 
  239      select case(this%level)
 
  241        norm = max(norm2(lmm),1e-10_real64)
 
  242        dotp = dot_product(lmm, this%constrain(1:3, ia))
 
  243        this%energy = this%energy + this%lambda * (norm - dotp)
 
  244        bb = lmm/norm - this%constrain(:,ia)
 
  246        this%energy = this%energy + this%lambda * sum((lmm - this%constrain(:,ia))**2)
 
  247        bb = 
m_two * (lmm - this%constrain(:,ia))
 
  258      do idir = 1, max(space%dim, 3)
 
  259        if(abs(bb(idir)) < 1.e-3_real64) 
then 
  260          bb(idir) = -this%constrain(idir, ia) * 1.e-2_real64
 
  262          bb(idir) = bb(idir) * this%lambda
 
  267      select case(std%ispin)
 
  269        b2 = norm2(bb(1:max(space%dim, 3)))
 
  271          this%pot(sphere%map(ip), 1) = this%pot(sphere%map(ip), 1) + b2 * mask(ip)
 
  272          this%pot(sphere%map(ip), 2) = this%pot(sphere%map(ip), 2) - b2 * mask(ip)
 
  277          this%pot(sphere%map(ip), 1) = this%pot(sphere%map(ip), 1) + bb(3) * mask(ip)
 
  278          this%pot(sphere%map(ip), 2) = this%pot(sphere%map(ip), 2) - bb(3) * mask(ip)
 
  279          this%pot(sphere%map(ip), 3) = this%pot(sphere%map(ip), 3) + bb(1) * mask(ip)
 
  280          this%pot(sphere%map(ip), 4) = this%pot(sphere%map(ip), 4) - bb(2) * mask(ip)
 
  285      safe_deallocate_a(mask)
 
  289    safe_deallocate_a(md)
 
  290    safe_deallocate_a(mdf)
 
Prints out to iunit a message in the form: ["InputVariable" = value] where "InputVariable" is given b...
 
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
 
real(real64), parameter, public m_pi
some mathematical constants
 
real(real64), parameter, public m_half
 
real(real64), parameter, public m_one
 
subroutine, public magnetic_constrain_end(this)
 
integer, parameter, public constrain_full
 
integer, parameter, public constrain_dir
 
subroutine, public magnetic_constrain_update(this, mesh, std, space, latt, pos)
 
subroutine, public magnetic_constrain_init(this, namespace, mesh, std, rho, natoms, min_dist)
 
subroutine, public magnetic_density(mesh, std, rho, md)
 
This module defines the meshes, which are used in Octopus.
 
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_experimental(name, namespace)
 
integer function, public parse_block(namespace, name, blk, check_varinfo_)
 
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 handles spin dimensions of the states and the k-point distribution.
 
real(real64) function, public dsm_integrate_frommesh(mesh, sm, ff, reduce)
 
subroutine, public submesh_end(this)
 
subroutine, public submesh_init(this, space, mesh, latt, center, rc)
 
Describes mesh distribution to nodes.
 
class for organizing spins and k-points
 
A submesh is a type of mesh, used for the projectors in the pseudopotentials It contains points on a ...