79    integer, 
allocatable :: imin(:)
 
   80    integer, 
allocatable :: imax(:)
 
   81    integer, 
allocatable :: ri(:, :)
 
   87    type(stencil_t),   
public :: stencil
 
   88    type(mesh_t), 
pointer     :: mesh => null()  
 
   89    integer,      
allocatable :: nn(:)
 
   90    integer,           
public :: np = 0
 
   92    integer, 
allocatable, 
public :: index(:,:)
 
   93    real(real64),   
allocatable, 
public :: w(:,:)
 
   95    logical,          
public :: const_w = .
true.   
 
   97    type(accel_mem_t), 
public :: buff_weights
 
   98    type(accel_mem_t), 
public :: buff_half_weights
 
  100    character(len=40) :: label
 
  103    integer, 
public :: nri = 0
 
  104    integer, 
allocatable, 
public :: ri(:,:)
 
  105    integer, 
allocatable, 
public :: rimap(:)
 
  106    integer, 
allocatable, 
public :: rimap_inv(:)
 
  108    integer                   :: ninner = 0
 
  109    integer                   :: nouter = 0
 
  111    type(nl_operator_index_t) :: inner
 
  112    type(nl_operator_index_t) :: outer
 
  114    type(accel_kernel_t) :: kernel
 
  115    type(accel_mem_t) :: buff_imin
 
  116    type(accel_mem_t) :: buff_imax
 
  117    type(accel_mem_t) :: buff_ri
 
  118    type(accel_mem_t) :: buff_map
 
  119    type(accel_mem_t) :: buff_all
 
  120    type(accel_mem_t) :: buff_inner
 
  121    type(accel_mem_t) :: buff_outer
 
  122    type(accel_mem_t) :: buff_stencil
 
  123    type(accel_mem_t) :: buff_ip_to_xyz
 
  124    type(accel_mem_t) :: buff_xyz_to_ip
 
  127    type(nl_operator_t), 
public, 
pointer :: coarser => null()
 
  131  integer, 
parameter :: &
 
  137  integer, 
parameter ::     &
 
  144  logical :: compact_boundaries
 
  149      integer, 
intent(in) :: opid, type
 
  153  integer :: dfunction_global = -1
 
  154  integer :: zfunction_global = -1
 
  155  integer :: function_opencl
 
  163    type(namespace_t),         
intent(in)    :: namespace
 
  200    call parse_variable(namespace, 
'OperateComplex', default, zfunction_global)
 
  235    call parse_variable(namespace, 
'NLOperatorCompactBoundaries', .false., compact_boundaries)
 
  237    if (compact_boundaries) 
then 
  258    character(len=*),    
intent(in)    :: label
 
  286    safe_allocate_source_a(opo%nn, opi%nn)
 
  287    safe_allocate_source_a(opo%index, opi%index)
 
  288    safe_allocate_source_a(opo%w, opi%w)
 
  290    opo%const_w   = opi%const_w
 
  293    assert(
allocated(opi%ri))
 
  295    safe_allocate_source_a(opo%ri, opi%ri)
 
  296    safe_allocate_source_a(opo%rimap, opi%rimap)
 
  297    safe_allocate_source_a(opo%rimap_inv, opi%rimap_inv)
 
  299    if (opi%mesh%parallel_in_domains) 
then 
  300      opo%inner%nri = opi%inner%nri
 
  301      safe_allocate_source_a(opo%inner%imin, opi%inner%imin)
 
  302      safe_allocate_source_a(opo%inner%imax, opi%inner%imax)
 
  303      safe_allocate_source_a(opo%inner%ri,   opi%inner%ri)
 
  305      opo%outer%nri = opi%outer%nri
 
  306      safe_allocate_source_a(opo%outer%imin, opi%outer%imin)
 
  307      safe_allocate_source_a(opo%outer%imax, opi%outer%imax)
 
  308      safe_allocate_source_a(opo%outer%ri,   opi%outer%ri)
 
  326    class(
space_t),       
intent(in)    :: space
 
  327    type(
mesh_t), 
target, 
intent(in)    :: mesh
 
  329    integer,              
intent(in)    :: np
 
  330    logical, 
optional,    
intent(in)    :: const_w
 
  331    logical, 
optional,    
intent(in)    :: regenerate
 
  333    integer :: ii, jj, p1(space%dim), time, current
 
  334    integer, 
allocatable :: st1(:), st2(:), st1r(:)
 
  336    integer :: ir, maxp, iinner, iouter
 
  337    logical :: change, force_change
 
  338    character(len=200) :: flags
 
  339    integer, 
allocatable :: inner_points(:), outer_points(:), all_points(:)
 
  343    if (mesh%parallel_in_domains .and. .not. const_w) 
then 
  353    if (
present(const_w)) op%const_w = const_w
 
  357      safe_allocate(op%w(1:op%stencil%size, 1))
 
  359        message(1) = 
'Info: nl_operator_build: working with constant weights.' 
  363      safe_allocate(op%w(1:op%stencil%size, 1:op%np))
 
  365        message(1) = 
'Info: nl_operator_build: working with non-constant weights.' 
  374    safe_allocate(st1(1:op%stencil%size))
 
  375    safe_allocate(st1r(1:op%stencil%size))
 
  376    safe_allocate(st2(1:op%stencil%size))
 
  385        do jj = 1, op%stencil%size
 
  394            st1(jj) = min(st1(jj), mesh%np + 1)
 
  399        st1(1:op%stencil%size) = st1(1:op%stencil%size) - ii
 
  401        change = any(st1 /= st2)
 
  405        force_change = any(st1 + ii > mesh%np) .and. all(st2 + ii - 1 <= mesh%np)
 
  409          do jj = 1, op%stencil%size
 
  410            if (st1(jj) + ii > mesh%np .and. st2(jj) + ii - 1 > mesh%np .and. st2(jj) + ii <= mesh%np_part) 
then 
  417          change = any(st1r /= st2)
 
  419          if (.not. change) st1 = st1r
 
  423        if (change .or. force_change) 
then 
  428          if (time == 1) op%nri = op%nri + 1
 
  432            current = current + 1
 
  433            op%ri(1:op%stencil%size, current) = st1(1:op%stencil%size)
 
  437        if (time == 2) op%rimap(ii) = current
 
  443        safe_deallocate_a(op%ri)
 
  444        safe_deallocate_a(op%rimap)
 
  445        safe_deallocate_a(op%rimap_inv)
 
  447        safe_allocate(op%ri(1:op%stencil%size, 1:op%nri))
 
  448        safe_allocate(op%rimap(1:op%np))
 
  449        safe_allocate(op%rimap_inv(1:op%nri + 1))
 
  456        if (mesh%use_curvilinear) 
then 
  457          safe_allocate(op%nn(1:op%nri))
 
  459          op%nn = op%stencil%size
 
  468      op%rimap_inv(op%rimap(jj) + 1) = jj
 
  470    op%rimap_inv(op%nri + 1) = op%np
 
  472    safe_deallocate_a(st1)
 
  473    safe_deallocate_a(st1r)
 
  474    safe_deallocate_a(st2)
 
  477      nn = op%rimap_inv(jj + 1) - op%rimap_inv(jj)
 
  480    if (op%mesh%parallel_in_domains) 
then 
  487        maxp = op%rimap_inv(ir + 1) + maxval(op%ri(1:op%stencil%size, ir))
 
  490          op%inner%nri = op%inner%nri + 1
 
  491          assert(op%inner%nri <= op%nri)
 
  494          op%outer%nri = op%outer%nri + 1
 
  495          assert(op%outer%nri <= op%nri)
 
  499      assert(op%inner%nri + op%outer%nri == op%nri)
 
  502        safe_deallocate_a(op%inner%imin)
 
  503        safe_deallocate_a(op%inner%imax)
 
  504        safe_deallocate_a(op%inner%ri)
 
  505        safe_deallocate_a(op%outer%imin)
 
  506        safe_deallocate_a(op%outer%imax)
 
  507        safe_deallocate_a(op%outer%ri)
 
  509      safe_allocate(op%inner%imin(1:op%inner%nri + 1))
 
  510      safe_allocate(op%inner%imax(1:op%inner%nri))
 
  511      safe_allocate(op%inner%ri(1:op%stencil%size, 1:op%inner%nri))
 
  513      safe_allocate(op%outer%imin(1:op%outer%nri + 1))
 
  514      safe_allocate(op%outer%imax(1:op%outer%nri))
 
  515      safe_allocate(op%outer%ri(1:op%stencil%size, 1:op%outer%nri))
 
  521        maxp = op%rimap_inv(ir + 1) + maxval(op%ri(1:op%stencil%size, ir))
 
  525          op%inner%imin(iinner) = op%rimap_inv(ir)
 
  526          op%inner%imax(iinner) = op%rimap_inv(ir + 1)
 
  527          op%inner%ri(1:op%stencil%size, iinner) = op%ri(1:op%stencil%size, ir)
 
  531          op%outer%imin(iouter) = op%rimap_inv(ir)
 
  532          op%outer%imax(iouter) = op%rimap_inv(ir + 1)
 
  533          op%outer%ri(1:op%stencil%size, iouter) = op%ri(1:op%stencil%size, ir)
 
  538      do ir = 1, op%inner%nri
 
  539        do ii = op%inner%imin(ir) + 1, op%inner%imax(ir)
 
  540          assert(all(ii + op%inner%ri(1:op%stencil%size, ir) <= mesh%np))
 
  548      write(flags, 
'(i5)') op%stencil%size
 
  549      flags=
'-DNDIM=3 -DSTENCIL_SIZE='//trim(adjustl(flags))
 
  551      if (op%mesh%parallel_in_domains) flags = 
'-DINDIRECT '//trim(flags)
 
  553      select case (function_opencl)
 
  564      select case (function_opencl)
 
  576        if (op%mesh%parallel_in_domains) 
then 
  578          safe_allocate(inner_points(1:op%mesh%np))
 
  579          safe_allocate(outer_points(1:op%mesh%np))
 
  580          safe_allocate(all_points(1:op%mesh%np))
 
  585          do ii = 1, op%mesh%np
 
  586            all_points(ii) = ii - 1
 
  587            maxp = ii + maxval(op%ri(1:op%stencil%size, op%rimap(ii)))
 
  588            if (maxp <= op%mesh%np) 
then 
  589              op%ninner = op%ninner + 1
 
  590              inner_points(op%ninner) = ii - 1
 
  592              op%nouter = op%nouter + 1
 
  593              outer_points(op%nouter) = ii - 1
 
  606          safe_deallocate_a(inner_points)
 
  607          safe_deallocate_a(outer_points)
 
  608          safe_deallocate_a(all_points)
 
  622    integer :: istencil, idir
 
  628      write(
message(1), 
'(3a)') 
'Debug info: Finite difference weights for ', trim(this%label), 
'.' 
  629      write(
message(2), 
'(a)')  
'            Spacing:' 
  630      do idir = 1, this%mesh%box%dim
 
  631        write(
message(2), 
'(a,f16.8)') trim(
message(2)), this%mesh%spacing(idir)
 
  635      do istencil = 1, this%stencil%size
 
  636        select case(this%mesh%box%dim)
 
  638          write(
message(1), 
'(a,i3,1i4,f25.10)') 
'      ', istencil, this%stencil%points(1:1, istencil), this%w(istencil, 1)
 
  640          write(
message(1), 
'(a,i3,2i4,f25.10)') 
'      ', istencil, this%stencil%points(1:2, istencil), this%w(istencil, 1)
 
  642          write(
message(1), 
'(a,i3,3i4,f25.10)') 
'      ', istencil, this%stencil%points(1:3, istencil), this%w(istencil, 1)
 
  658    type(
mesh_t),        
target, 
intent(in)  :: mesh
 
  659    logical,                     
intent(in)  :: self_adjoint
 
  661    integer :: ip, jp, kp, lp, index, ii, p1(1:mesh%box%dim)
 
  662    real(real64), 
pointer, 
contiguous   :: vol_pp(:), 
weights(:, :), tmp(:)
 
  663    real(real64) :: factor
 
  667    if (self_adjoint) 
then 
  677    if (mesh%parallel_in_domains) 
then 
  679      safe_allocate(vol_pp(1:mesh%np_part))
 
  680      vol_pp(1:mesh%np) = mesh%vol_pp(1:mesh%np)
 
  683      if (.not.op%const_w) 
then 
  684        safe_allocate(
weights(1:op%stencil%size, 1:mesh%np_part))
 
  685        safe_allocate(tmp(1:mesh%np_part))
 
  686        do ii = 1, op%stencil%size
 
  687          tmp(1:mesh%np) = op%w(ii, 1:mesh%np)
 
  689          weights(ii, 1:mesh%np_part) = tmp(1:mesh%np_part)
 
  691        safe_deallocate_p(tmp)
 
  694      vol_pp => mesh%vol_pp
 
  698    if (.not.op%const_w) 
then 
  701        do jp = 1, op%stencil%size
 
  703          if (index <= mesh%np) 
then 
  705            do lp = 1, op%stencil%size
 
  711          else if (index <= mesh%np + mesh%pv%np_ghost) 
then 
  714            do lp = 1, op%stencil%size
 
  716                op%stencil%points(1:mesh%box%dim, lp))
 
  725      opt%w(1:op%stencil%size, 1) = op%w(1:op%stencil%size, 1)
 
  730    if (mesh%parallel_in_domains) 
then 
  731      safe_deallocate_p(vol_pp)
 
  747      select case (function_opencl)
 
  754        if (op%mesh%parallel_in_domains) 
then 
  771    safe_deallocate_a(op%inner%imin)
 
  772    safe_deallocate_a(op%inner%imax)
 
  773    safe_deallocate_a(op%inner%ri)
 
  774    safe_deallocate_a(op%outer%imin)
 
  775    safe_deallocate_a(op%outer%imax)
 
  776    safe_deallocate_a(op%outer%ri)
 
  778    safe_deallocate_a(op%index)
 
  779    safe_deallocate_a(op%w)
 
  781    safe_deallocate_a(op%ri)
 
  782    safe_deallocate_a(op%rimap)
 
  783    safe_deallocate_a(op%rimap_inv)
 
  784    safe_deallocate_a(op%nn)
 
  795    integer,             
intent(in)   :: is
 
  796    integer,             
intent(in)   :: ip
 
  798    res = ip + op%ri(is, op%rimap(ip))
 
  809    if (accel_is_enabled() .and. op%const_w) 
then 
  810      call accel_create_buffer(op%buff_weights, accel_mem_read_only, type_float, op%stencil%size)
 
  811      call accel_create_buffer(op%buff_half_weights, accel_mem_read_only, type_float, op%stencil%size)
 
  826    if (accel_is_enabled() .and. op%const_w) 
then 
  827      call accel_write_buffer(op%buff_weights, op%stencil%size, op%w(:, 1))
 
  828      call accel_write_buffer(op%buff_half_weights, op%stencil%size, -m_half*op%w(:, 1))
 
  843      ii = op%rimap_inv(jj + 1) + maxval(op%ri(1:op%stencil%size, jj))
 
  844      np_bc = max(np_bc, ii)
 
  859#include "nl_operator_inc.F90" 
  862#include "complex.F90" 
  863#include "nl_operator_inc.F90" 
subroutine, public accel_release_buffer(this)
 
subroutine, public accel_kernel_build(this, file_name, kernel_name, flags)
 
pure logical function, public accel_is_enabled()
 
integer, parameter, public accel_mem_read_only
 
integer pure function, public accel_max_workgroup_size()
 
This module implements batches of mesh functions.
 
Module implementing boundary conditions in Octopus.
 
subroutine, public dpar_vec_ghost_update(pv, v_local)
Updates ghost points of every node.
 
type(debug_t), save, public debug
 
real(real64), parameter, public m_zero
 
real(real64), parameter, public m_half
 
real(real64), parameter, public m_one
 
This module implements the index, used for the mesh points.
 
This module is intended to contain "only mathematical" functions and procedures.
 
subroutine, public weights(N, M, cc, side)
Compute the weights for finite-difference calculations:
 
This module defines the meshes, which are used in Octopus.
 
integer function, public mesh_local_index_from_coords(mesh, ix)
This function returns the local index of the point for a given vector of integer coordinates.
 
subroutine, public mesh_local_index_to_coords(mesh, ip, ix)
Given a local point index, this function returns the set of integer coordinates of the point.
 
logical pure function, public mesh_compact_boundaries(mesh)
 
subroutine, public messages_obsolete_variable(namespace, name, rep)
 
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
 
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
 
subroutine, public messages_input_error(namespace, var, details, row, column)
 
subroutine, public messages_experimental(name, namespace)
 
This module handles the communicators for the various parallelization strategies.
 
This module defines non-local operators.
 
subroutine, public dnl_operator_operate_diag(op, fo)
 
subroutine, public nl_operator_init(op, label)
initialize an instance of a non-local operator by setting the label
 
integer, parameter op_map
 
integer, parameter op_max
 
integer, parameter op_vec
 
subroutine, public dnl_operator_operate_batch(op, fi, fo, ghost_update, profile, points, factor, async)
 
subroutine, public dnl_operator_operate(op, fi, fo, ghost_update, profile, points)
 
subroutine, public nl_operator_update_gpu_buffers(op)
 
subroutine, public nl_operator_global_init(namespace)
initialize global settings for non-local operators
 
subroutine, public nl_operator_copy(opo, opi)
 
subroutine, public nl_operator_output_weights(this)
 
subroutine, public nl_operator_end(op)
 
integer, parameter, public op_inner
 
subroutine, public znl_operator_operate(op, fi, fo, ghost_update, profile, points)
 
logical pure function, public nl_operator_compact_boundaries()
 
subroutine, public nl_operator_global_end()
 
integer, parameter, public op_outer
 
subroutine, public nl_operator_build(space, mesh, op, np, const_w, regenerate)
 
logical compact_boundaries
 
subroutine, public znl_operator_operate_batch(op, fi, fo, ghost_update, profile, points, factor, async)
 
integer, parameter op_nomap
 
subroutine, public nl_operator_adjoint(op, opt, mesh, self_adjoint)
opt has to be initialised and built.
 
integer pure function, public nl_operator_np_zero_bc(op)
 
subroutine, public znl_operator_operate_diag(op, fo)
 
integer pure function, public nl_operator_get_index(op, is, ip)
 
subroutine, public nl_operator_allocate_gpu_buffers(op)
 
integer, parameter op_min
 
This module contains interfaces for routines in operate.c.
 
Some general things and nomenclature:
 
This module defines stencils used in Octopus.
 
subroutine, public stencil_end(this)
 
subroutine, public stencil_copy(input, output)
 
type(type_t), public type_float
 
type(type_t), public type_integer
 
Describes mesh distribution to nodes.
 
index type for non-local operators
 
data type for non local operators