global_offsets_to_local Subroutine

public subroutine global_offsets_to_local(global_offsets, local_elements, local_offsets)

Converts global offsets to local

Global vs. Local Indexing local_offsets may be sized according to the local index (|local_elements+|1) or the global index (|global_offsets|).

Arguments

Type IntentOptional Attributes Name
integer, intent(in), DIMENSION(:) :: global_offsets

Offsets of elements in the global grid Which elements are local

integer, intent(in), DIMENSION(:) :: local_elements

Offsets of elements in the global grid Which elements are local

integer, intent(out), DIMENSION(:) :: local_offsets

Offsets of local elements.


Source Code

   SUBROUTINE global_offsets_to_local(global_offsets, &
                                      local_elements, local_offsets)
      !! Converts global offsets to local
      !!
      !! Global vs. Local Indexing
      !! local_offsets may be sized according to the
      !! local index (|local_elements+|1) or the
      !! global index (|global_offsets|).

      INTEGER, DIMENSION(:), INTENT(IN)                  :: global_offsets, local_elements
         !! Offsets of elements in the global grid
         !! Which elements are local
      INTEGER, DIMENSION(:), INTENT(OUT)                 :: local_offsets
         !! Offsets of local elements.

      INTEGER                                            :: acc, el, lel, nglobal, nlo, nlocal, &
                                                            prev_el, sz
      LOGICAL                                            :: local

!   ---------------------------------------------------------------------------

      nglobal = SIZE(global_offsets) - 1
      nlocal = SIZE(local_elements)
      nlo = SIZE(local_offsets) - 1
      local = .NOT. (nglobal .EQ. nlo)
      IF (local) THEN
         IF (nlocal /= nlo) &
            DBCSR_ABORT("Invalid size for local offsets")
      END IF
      IF (local) THEN
         acc = 1
         DO lel = 1, nlocal
            local_offsets(lel) = acc
            el = local_elements(lel)
            sz = global_offsets(el + 1) - global_offsets(el)
            acc = acc + sz
         END DO
         local_offsets(nlocal + 1) = acc
      ELSE
         acc = 1
         prev_el = 0
         DO lel = 1, nlocal
            el = local_elements(lel)
            local_offsets(prev_el + 1:el) = acc
            sz = global_offsets(el + 1) - global_offsets(el)
            acc = acc + sz
            prev_el = el
         END DO
         local_offsets(prev_el + 1:nglobal + 1) = acc
      END IF
   END SUBROUTINE global_offsets_to_local