53    type(symmetries_t), 
pointer :: symm
 
   54    integer(int64), 
allocatable :: map(:,:)
 
   55    integer(int64), 
allocatable :: map_inv(:,:)
 
   62    type(symmetrizer_t),         
intent(out) :: this
 
   63    class(mesh_t),               
intent(in)  :: mesh
 
   64    type(symmetries_t),  
target, 
intent(in)  :: symm
 
   66    integer :: nops, ip, iop, idir, idx(3)
 
   67    real(real64) :: destpoint(3), srcpoint(3), srcpoint_inv(3), lsize(3), offset(3)
 
   71    assert(mesh%box%dim <= 3)
 
   78    safe_allocate(this%map(1:mesh%np, 1:nops))
 
   79    safe_allocate(this%map_inv(1:mesh%np, 1:nops))
 
   83    lsize = real(mesh%idx%ll, real64)
 
   84    offset = real(mesh%idx%nr(1, :) + mesh%idx%enlarge, real64)
 
   88      destpoint = real(idx, real64)  - offset
 
   91      assert(all(destpoint >= 0))
 
   92      assert(all(destpoint < lsize))
 
   95      destpoint = destpoint + offset
 
   98      destpoint = destpoint/lsize
 
  107        srcpoint = srcpoint*lsize
 
  108        srcpoint_inv = srcpoint_inv*lsize
 
  111        srcpoint = srcpoint - offset
 
  112        srcpoint_inv = srcpoint_inv - offset
 
  114        do idir = 1, symm%periodic_dim
 
  115          if (nint(srcpoint(idir)) < 0 .or. nint(srcpoint(idir)) >= mesh%idx%ll(idir)) 
then 
  116            srcpoint(idir) = real(modulo(nint(srcpoint(idir)), mesh%idx%ll(idir)), real64)
 
  118          if (nint(srcpoint_inv(idir)) < 0 .or. nint(srcpoint_inv(idir)) >= mesh%idx%ll(idir)) 
then 
  119            srcpoint_inv(idir) = real(modulo(nint(srcpoint_inv(idir)), mesh%idx%ll(idir)), real64)
 
  122        assert(all(nint(srcpoint) >= 0))
 
  123        assert(all(nint(srcpoint) < mesh%idx%ll))
 
  124        srcpoint = srcpoint + offset
 
  126        assert(all(nint(srcpoint_inv) >= 0))
 
  127        assert(all(nint(srcpoint_inv) < mesh%idx%ll))
 
  128        srcpoint_inv = srcpoint_inv + offset
 
  131        assert(this%map(ip, iop) <= mesh%np_global)
 
  133        assert(this%map_inv(ip, iop) <= mesh%np_global)
 
  145    type(symmetrizer_t), 
intent(inout) :: this
 
  150    safe_deallocate_a(this%map)
 
  151    safe_deallocate_a(this%map_inv)
 
  160#include "symmetrizer_inc.F90" 
  163#include "complex.F90" 
  164#include "symmetrizer_inc.F90" 
This module implements the index, used for the mesh points.
 
This module defines the meshes, which are used in Octopus.
 
integer(int64) function, public mesh_global_index_from_coords(mesh, ix)
This function returns the true global 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.
 
Some general things and nomenclature:
 
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.
 
integer pure function, public symmetries_number(this)
 
subroutine, public dsymmetrizer_apply(this, mesh, field, field_vector, symmfield, symmfield_vector, suppress_warning, reduced_quantity)
supply field and symmfield, and/or field_vector and symmfield_vector
 
subroutine, public dsymmetrize_magneto_optics_cart(symm, tensor)
 
subroutine, public symmetrizer_end(this)
 
subroutine, public zsymmetrizer_apply_single(this, mesh, iop, field, symmfield)
 
subroutine, public zsymmetrizer_apply(this, mesh, field, field_vector, symmfield, symmfield_vector, suppress_warning, reduced_quantity)
supply field and symmfield, and/or field_vector and symmfield_vector
 
subroutine, public dsymmetrizer_apply_single(this, mesh, iop, field, symmfield)
 
subroutine, public dsymmetrize_tensor_cart(symm, tensor, use_non_symmorphic)
Symmetric a rank-2 tensor defined in Cartesian space.
 
subroutine, public zsymmetrize_tensor_cart(symm, tensor, use_non_symmorphic)
Symmetric a rank-2 tensor defined in Cartesian space.
 
subroutine, public zsymmetrize_magneto_optics_cart(symm, tensor)
 
subroutine, public symmetrizer_init(this, mesh, symm)