26  use, 
intrinsic :: iso_fortran_env
 
   45  integer, 
parameter :: COS2 = 1
 
   58    logical, 
public :: grid_based_partner = .
true.
 
   59    complex(real64), 
allocatable :: rs_current(:, :)
 
   62    integer, 
public :: partner_np = 0
 
   63    real(real64), 
allocatable, 
public :: partner_charge(:)
 
   64    real(real64), 
allocatable, 
public :: partner_pos(:,:)
 
   65    real(real64), 
allocatable, 
public :: partner_vel(:,:)
 
   68    real(real64)   :: reg_width
 
   69    real(real64), 
allocatable :: reg(:)
 
   71    type(space_t), 
pointer :: system_space => null()
 
   72    type(lattice_vectors_t), 
pointer :: system_latt => null()
 
   95    class(current_to_mxll_field_t), 
intent(inout) :: this
 
   96    type(grid_t), 
target,           
intent(in)    :: gr
 
   97    integer,                        
intent(in)    :: ndim
 
  102    safe_allocate(this%rs_current(1:gr%np, 1:ndim))
 
  109    class(interaction_partner_t), 
target, 
intent(inout) :: partner
 
  110    class(current_to_mxll_field_t),               
pointer       :: this
 
  116    this%label = 
"current_to_mxll_field" 
  117    this%partner => partner
 
  123    this%couplings_from_partner = [
current]
 
  138    call parse_variable(partner%namespace, 
'RegularizationFunction', cos2, this%reg_type)
 
  153    call parse_variable(partner%namespace, 
'RegularizationFunctionWidth', 2.0_real64, &
 
  156    this%intra_interaction = .false.
 
  169    this%system_space => space
 
  170    this%system_latt => latt
 
  182    nullify(this%system_space)
 
  183    nullify(this%system_latt)
 
  184    safe_deallocate_a(this%rs_current)
 
  193    integer :: part_ind, i_dim, ip
 
  195    real(real64) :: norm, time
 
  199    if(this%grid_based_partner) 
then 
  200      call this%regridding%do_transfer(this%system_field, this%partner_field)
 
  202      this%system_field = 
m_zero 
  203      do part_ind = 1, this%partner_np
 
  204        call submesh_init(submesh, this%system_space, this%system_gr, &
 
  205          this%system_latt, this%partner_pos(:,part_ind), this%reg_width)
 
  207        safe_allocate(this%reg(1:submesh%np))
 
  208        if (this%reg_type == cos2) 
then 
  209          do ip = 1, submesh%np
 
  210            this%reg(ip) = 
cos( (
m_pi/
m_two) * (submesh%r(ip)/this%reg_width) )**2
 
  216        do i_dim = 1, this%system_space%dim
 
  218            this%partner_charge(part_ind)*this%partner_vel(i_dim,part_ind)/norm)
 
  220        safe_deallocate_a(this%reg)
 
  228    assert(this%interpolation_initialized)
 
  229    time = this%partner%quantities(this%couplings_from_partner(1))%iteration%value()
 
  230    call this%interpolation%add_time(time, this%rs_current)
 
double cos(double __x) __attribute__((__nothrow__
 
subroutine current_to_mxll_field_init_space_latt(this, space, latt)
 
subroutine current_to_mxll_field_finalize(this)
 
class(current_to_mxll_field_t) function, pointer current_to_mxll_field_constructor(partner)
 
subroutine current_to_mxll_field_do_mapping(this)
 
subroutine current_to_mxll_field_init(this, gr, ndim)
 
subroutine current_to_mxll_field_calculate_energy(this)
 
This module implements the field transfer.
 
subroutine, public field_transfer_init(this, gr, ndim)
the system field is allocated and initialized to 0
 
real(real64), parameter, public m_two
 
real(real64), parameter, public m_zero
 
real(real64), parameter, public m_pi
some mathematical constants
 
This module implements the underlying real-space grid.
 
This module defines classes and functions for interaction partners.
 
This module defines the meshes, which are used in Octopus.
 
subroutine, public messages_input_error(namespace, var, details, row, column)
 
This module defines the quantity_t class and the IDs for quantities, which can be exposed by a system...
 
integer, parameter, public current
 
Implementation details for regridding.
 
subroutine, public build_rs_current_state(current_state, mesh, rs_current_state, ep_field, np)
 
real(real64) function, public dsm_integrate(mesh, sm, ff, reduce)
 
subroutine, public submesh_end(this)
 
subroutine, public submesh_init(this, space, mesh, latt, center, rc)
 
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.
 
type(unit_system_t), public units_inp
the units systems for reading and writing
 
Class to transfer a current to a Maxwell field.
 
class defining the field_transfer interaction
 
A submesh is a type of mesh, used for the projectors in the pseudopotentials It contains points on a ...