This subroutine load spatial boundary state variable.
If spatial is defined as block than read block for predefined Fortran function variables else it is defined as constant. Valid definitions:
spatial = 1.0
spatial = lua_fun_name
spatial = {fun=lua_fun_name, store=<>}
Note. Lua function take 3 input arguments (x,y,z) i.e barycentric coordinates of an element - Predefined Fortran function
spatial = {predefined = "fun_name", fun_parameters}
example given in subroutine load_spatial_parabol definition
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(tem_spatial_type), | intent(out) | :: | me |
spatial boundary state type |
||
type(flu_State) | :: | conf |
lua state type |
|||
integer, | intent(in) | :: | parent |
aotus parent handle |
||
character(len=*), | intent(in), | optional | :: | key |
state variable key string defined in lua |
|
real(kind=rk), | intent(in), | optional | :: | defaultValue |
What should be set s a default value for the quantities if no quantity was given in the lua file |
|
integer, | intent(in), | optional | :: | nComp |
number of components of the variable |
|
integer, | intent(out), | optional | :: | errCode |
Error code from lua loading |
subroutine tem_load_spatial( me, conf, parent, key, defaultValue, nComp, &
& errCode )
! -------------------------------------------------------------------- !
!> spatial boundary state type
type(tem_spatial_type), intent(out) :: me
!> lua state type
type(flu_State) :: conf
!> aotus parent handle
integer, intent(in) :: parent
!> state variable key string defined in lua
character(len=*), intent(in), optional :: key
!> What should be set s a default value for the quantities if no
!! quantity was given in the lua file
real(kind=rk), intent(in), optional :: defaultValue
!> number of components of the variable
integer, intent(in), optional :: nComp
!> Error code from lua loading
integer, intent(out), optional :: errCode
! -------------------------------------------------------------------- !
integer :: thandle, iError
integer :: loc_nComp
type(aot_fun_type) :: fun
character(len=labelLen) :: local_key
real(kind=rk) :: local_default
logical :: loadasConst
! -------------------------------------------------------------------- !
if( present( nComp ))then
loc_nComp = nComp
else
loc_nComp = 1
end if
if(present(defaultValue)) then
local_default = defaultValue
else
local_default = 1._rk
endif
if(present(key)) then
local_key = trim(key)
else
local_key = 'spatial'
endif
write(logUnit(1),"(A)") 'Loading spatial for '//trim(local_key)
! default values
loadasConst = .false.
! First test for a lua function
call aot_fun_open(L=conf, parent=parent, fun=fun, key=trim(local_key))
me%conf = conf
if_fun: if (fun%handle /= 0) then
! There was a function found for the spatial entry, go on using it
me%kind = 'lua_fun'
! Create a reference for this function and store it.
me%lua_fun_ref = aot_reference_for(conf)
call aot_fun_close( L=conf, fun=fun )
iError = 0
else ! Not a LUA function
call aot_fun_close( L=conf, fun=fun )
! Not a function, try to interpret it as a table'
call aot_table_open( L = conf, &
& thandle = thandle, &
& parent = parent, &
& key = trim(local_key) )
! table is defined
if_table: if (thandle /= 0) then
! check whether to store spatial values during initialization or not
call aot_get_val( L = conf, &
& thandle = thandle, &
& key = 'store', &
& val = me%isStored, &
& default = .false., &
& ErrCode = iError )
! inside table try to open lua function with key 'fun'
call aot_fun_open( L = conf, &
& parent = thandle, &
& fun = fun, &
& key = 'fun' )
! lua function defined with key 'fun'
if (fun%handle /= 0) then
me%kind = 'lua_fun'
! Create a reference for this function and store it.
me%lua_fun_ref = aot_reference_for(conf)
call aot_fun_close( L=conf, fun=fun )
iError = 0
else
call aot_fun_close( L=conf, fun=fun )
! Not a lua function with key 'fun'.
! Try to interpret it as a predefined'
call aot_get_val( L = conf, &
& thandle = thandle, &
& key = 'predefined', &
& val = me%kind, &
& default = 'unknown', &
& ErrCode = iError )
if( btest(iError, aoterr_WrongType) ) then
call tem_abort('Error in retrieving the function kind.')
end if
! predefined key word is not defined.
! try to interpret as constant with key "const"
if ( btest(iError, aoterr_NonExistent) ) then
call load_spatial_asConst( const = me%const, &
& conf = conf, &
& errCode = iError, &
& parent = thandle, &
& key = 'const', &
& nComp = loc_nComp )
if (iError == 0) then
me%kind = 'const'
else
call aot_table_close( L=conf, thandle=thandle )
! Constant is not defined with key "const"
! Try to interpret directly from local_key
loadasConst = .true.
end if
else ! predefined exist
call load_spatial_predefined( me = me, &
& conf = conf, &
& thandle = thandle, &
& nComp = loc_nComp )
iError = 0
end if ! not predefined
end if ! not lua_fun with key "fun"
else
! not a table try to interprect as constant
loadasConst = .true.
end if if_table
call aot_table_close( L=conf, thandle=thandle )
end if if_fun
if (loadasConst) then
! Not a table with specific key word like "fun", "const", "predefined"
! Try to interpret it as a constant with key
write(logUnit(7),"(A)") 'Try to load as constant with key ' &
& // trim(local_key)
call load_spatial_asConst( const = me%const, &
& conf = conf, &
& errCode = iError, &
& parent = parent, &
& key = trim(local_key), &
& nComp = loc_nComp )
if (iError == 0) then
me%kind = 'const'
else
write(logUnit(1),"(A)") ' WARNING: variable is non-existent!'
write(logUnit(1),"(A)") ' Setting kind to be "none" and value = ' &
& // trim( tem_toStr(local_default) ) &
& // ' for all ' // &
& trim( tem_toStr(loc_nComp) ) // ' components'
if (allocated(me%const)) deallocate(me%const)
allocate(me%const(loc_nComp))
me%const = local_default
me%kind = 'none'
end if
end if
write(logUnit(3),"(A)") ' Spatial for ' // trim(local_key) &
& // ' is a defined as ' // trim(me%kind)
if (trim(me%kind) == 'const') then
if ( loc_nComp == 1 ) then
write(logUnit(3),"(A)") 'value = ' // trim(tem_toStr(me%const(1)))
else
write(logUnit(3),"(A)") 'value = ' &
& // trim(tem_toStr(me%const(1:loc_nComp),','))
end if
end if
if (present(errCode)) errCode = iError
end subroutine tem_load_spatial