tem_varSys_append_stFun_raw Subroutine

private subroutine tem_varSys_append_stFun_raw(varSys, stFun, varname, nComp, evaltype, st_funList, solverData_evalElem)

subroutine to add the variables from the input lua script to the varsys

Arguments

Type IntentOptional Attributes Name
type(tem_varSys_type), intent(inout) :: varSys

global variable system to which stFunVar to be appended

type(tem_spacetime_fun_type), intent(in), pointer :: stFun(:)

variables defined in the lua file

character(len=*), intent(in) :: varname
integer, intent(in), optional :: nComp
character(len=*), intent(in), optional :: evaltype
type(tem_st_fun_linkedList_type), intent(inout), optional :: st_funList

contains spacetime functions of all variables

type(tem_varSys_solverData_evalElem_type), intent(in), optional :: solverData_evalElem

A setter routine that allows the caller to define routine for the construction of an element representation.


Source Code

  subroutine tem_varSys_append_stFun_raw( varSys, stFun, varname, nComp, &
    &                                     evaltype, st_funList,          &
    &                                     solverData_evalElem            )
    ! -------------------------------------------------------------------------
    !> global variable system to which stFunVar to be appended
    type(tem_varSys_type), intent(inout) :: varSys

    !> variables defined in the lua file
    type(tem_spacetime_fun_type), pointer, intent(in) :: stFun(:)

    character(len=*), intent(in) :: varname

    integer, intent(in), optional :: nComp

    character(len=*), intent(in), optional :: evaltype

    !> contains spacetime functions of all variables
    type(tem_st_fun_linkedList_type), intent(inout), optional :: st_funList

    !> A setter routine that allows the caller to define routine for the
    !! construction of an element representation.
    type(tem_varSys_solverData_evalElem_type), &
      &  optional, intent(in) :: solverData_evalElem
    ! -------------------------------------------------------------------------
    type(tem_st_fun_listElem_type), pointer :: stfun_listelem
    integer :: addedPos
    logical :: wasAdded
    type(c_ptr) :: method_data
    integer :: ncomp_loc
    character(len=labelLen) :: evaltype_loc
    procedure(tem_varSys_proc_point), pointer :: get_point => NULL()
    procedure(tem_varSys_proc_element), pointer :: get_element => NULL()
    procedure(tem_varSys_proc_setParams), pointer :: set_params => null()
    procedure(tem_varSys_proc_getParams), pointer :: get_params => null()
    procedure(tem_varSys_proc_setupIndices), pointer :: &
      &                                      setup_indices => null()
    procedure(tem_varSys_proc_getValOfIndex), pointer :: &
      &                                       get_valOfIndex => null()
    type(tem_st_fun_listElem_type),pointer :: newElem
    ! -------------------------------------------------------------------------
    nullify(get_point, get_element, set_params, get_params, setup_indices, &
      &     get_valOfIndex)

    nComp_loc = 1
    if (present(nComp)) nComp_loc = nComp

    evaltype_loc = 'add'
    if (present(evaltype)) evaltype_loc = evaltype

    if (present(st_funList)) then
      ! append space time function to linked list of spacetime functions
      call append( st_funList, stfun, newElem )

      ! c pointer to list of spacetime functions of current variable
      method_data = c_loc(newElem)
    else
      allocate(stfun_listelem)
      stfun_listelem%val => stfun
      stfun_listelem%nvals = size(stfun)
      method_data = c_loc(stfun_Listelem)
    end if


    ! assign function pointer depends on evaluation type
    call tem_varSys_assignEvalType( evaltype       = evaltype_loc,  &
      &                             nComp          = nComp_loc,     &
      &                             get_point      = get_point,     &
      &                             get_element    = get_element,   &
      &                             get_valOfIndex = get_valOfIndex )

    set_params => set_params_spacetime
    get_params => get_params_spacetime
    setup_indices => setup_indices_spacetime

    if (.not. associated(get_point)) then
      write(logUnit(1),*) 'Error: No evaluation is defined for variable '//&
        &                 trim(varname)
      call tem_abort()
    end if

    ! append variable to varSys
    call tem_varSys_append_derVar( me             = varSys,         &
      &                            varName        = varName,        &
      &                            operType       = 'st_fun',       &
      &                            nComponents    = nComp_loc,      &
      &                            method_data    = method_data,    &
      &                            get_point      = get_point,      &
      &                            get_element    = get_element,    &
      &                            set_params     = set_params,     &
      &                            get_params     = get_params,     &
      &                            setup_indices  = setup_indices,  &
      &                            get_valOfIndex = get_valOfIndex, &
      &                            pos            = addedPos,       &
      &                            wasAdded       = wasAdded        )

    if (wasAdded) then
      if (present(solverData_evalElem)) then
        ! If an solverData_evalElem function is provided, override
        ! the get_element pointer and use the provided setter
        ! solverData_evalElem instead to define the get_element routine.
        call solverData_evalElem%stFun_setter(varSys%method%val(addedPos))
      end if
      write(logUnit(9),*) 'Successfully appended variable "' &
        & // trim(varname) // '" to the variable system'

    else if (addedpos < 1) then
      write(logUnit(1),*) 'WARNING: variable '//trim(varname)// &
        &                 ' is not added to variable system'
    end if

  end subroutine tem_varSys_append_stFun_raw