tem_spacetime_vector_for_index Function

private function tem_spacetime_vector_for_index(me, grwPnt, idx, nVals, iLevel, time, nComps) result(res)

This function returns pre-stored value at given idx if spacetime function is predefined apesmate else evaluate a spacetime function for a point at given idx in growing array of points. Return value is a vector.

Arguments

Type IntentOptional Attributes Name
type(tem_spacetime_fun_type), intent(in) :: me

spacetime type

type(tem_grwPoints_type), intent(in) :: grwPnt

growing array of all spacetime point of a variable

integer, intent(in) :: idx(nVals)

Index position to return a pre-store value or to compute

integer, intent(in) :: nVals

number of return values

integer, intent(in) :: iLevel

Level to which the evaluated values to be returned

type(tem_time_type), intent(in) :: time

timer object incl. the current time information

integer, intent(in) :: nComps

number of components per returned value

Return Value real(kind=rk), (nVals,nComps)

return value of a function


Source Code

  function tem_spacetime_vector_for_index( me, grwPnt, idx, nVals, iLevel, &
    &                                      time, nComps ) result (res)
    ! -------------------------------------------------------------------- !
    !> spacetime type
    type(tem_spacetime_fun_type), intent(in) :: me
    !> number of return values
    integer, intent(in) :: nVals
    !> number of components per returned value
    integer, intent(in) :: nComps
    !> growing array of all spacetime point of a variable
    type(tem_grwPoints_type), intent(in) :: grwPnt
    !> Index position to return a pre-store value or to compute
    integer, intent(in) :: idx(nVals)
    !> return value of a function
    real( kind=rk ) :: res(nVals, nComps)
    !> Level to which the evaluated values to be returned
    integer, intent(in) :: iLevel
    !> timer object incl. the current time information
    type(tem_time_type), intent(in)  :: time
    ! -------------------------------------------------------------------- !
    integer :: iVal, iComp, iVar,offset
    real(kind=rk) :: coord(1,3), res_tmp(1, nComps), trans
    real(kind=rk), allocatable :: temp(:)
    ! -------------------------------------------------------------------- !
    select case (trim(me%fun_kind))
    case ('none')
      res = 0.0_rk
    case ('const')
      do iComp = 1, nComps
        res(:, iComp) = me%const(iComp)
      end do
    case ('lua_fun')
      do iVal = 1, nVals
        coord(1,:) =  (/ grwPnt%coordX%val( idx(iVal) ), &
          &              grwPnt%coordY%val( idx(iVal) ), &
          &              grwPnt%coordZ%val( idx(iVal) ) /)

        res_tmp = tem_spacetime_lua_for( fun_ref = me%lua_fun_ref, &
          &                              coord   = coord,          &
          &                              time    = time,           &
          &                              n       = 1,              &
          &                              nComp   = nComps,         &
          &                              conf    = me%conf         )

        res(iVal,:) = res_tmp(1,:)
      end do
    case ('combined')
      trans = tem_temporal_for( temporal   = me%temporal, &
        &                       time       = time         )
      res = tem_spatial_for( me     = me%spatial, &
        &                    grwPnt = grwPnt,     &
        &                    idx    = idx,        &
        &                    nVals  = nVals,      &
        &                    iLevel = iLevel,     &
        &                    nComps = nComps      )
      res = trans*res
    case ('apesmate')
      do iVal = 1, nVals
        offset = (idx(iVal)-1)*nComps
        res(iVal, :) = me%aps_coupling%valOnLvl(iLevel)                  &
          &                           %evalVal( offset+1 : offset+nComps )
      end do
    case('precice')
      allocate(temp(nVals))
      do iVar = 1, me%precice_coupling%readVar%nVars
        temp(1:nVals) = tem_precice_read(                          &
          & dataID  = me%precice_coupling%readVar%IDs(iVar),       &
          & posIDs  = me%precice_coupling%readVar%posIDLvl(iLevel) &
          &                                      %posIDs(idx(:)),  &
          & npoints = nVals                                        )
        res(1:nVals, iVar) = temp
      end do
      deallocate(temp)
    case default
      do iVal = 1, nVals
        coord(1,:) =  (/ grwPnt%coordX%val( idx(iVal) ), &
          &              grwPnt%coordY%val( idx(iVal) ), &
          &              grwPnt%coordZ%val( idx(iVal) ) /)

        res_tmp = tem_spacetime_vector_for_coord( me    = me,    &
          &                                       coord = coord, &
          &                                       time  = time,  &
          &                                       n     = 1,     &
          &                                       nComp = nComps )
        res(iVal,:) = res_tmp(1,:)
      end do
    end select

  end function tem_spacetime_vector_for_index