从Fortran将数组作为函数参数传递给Lua

3

我正在寻找Fortran用于将数组作为参数传递给lua函数的示例(还有接口函数)。我可以使用FortLua项目来开始。但提供的示例一次只传递一个元素。感谢任何帮助。

--Lua code 

local q1
local q2
function getoutput( qout1, qout2)
-- qout1 and qout2 are arrays with some dimension
  q1 = qout1
  q2 = qout2
end

-- 在Fortran中我使用了

config_function('getoutput', args, 2, cstatus)

但是我需要帮助设置参数。下面的代码可以处理标量参数变量,而不是数组。

!> Evaluate a function in the config file and get its result.
FUNCTION config_function(name,args,nargs,status)
    REAL :: config_function
    CHARACTER(LEN=*) :: name
    REAL, DIMENSION(nargs) :: args
    REAL(KIND=c_double) :: anarg
    INTEGER :: nargs
    INTEGER :: status
    INTEGER :: iargs
    INTEGER(c_int) :: stackstart

    stackstart = lua_gettop(mluastate)

    config_function = 0
    status = 0


    CALL lua_getglobal(mluastate,TRIM(name)//C_NULL_CHAR)
    IF ( lua_type(mluastate,-1) .eq. LUA_TFUNCTION ) THEN
        DO iargs = 1,nargs
          anarg = args(iargs)
          CALL lua_pushnumber(mluastate,anarg)
        ENDDO
        IF (lua_pcall(mluastate,nargs,1,0) .eq. 0) THEN
          if (lua_isnumber(mluastate,-1) .ne. 0) THEN
            config_function = lua_tonumber(mluastate,-1)
            CALL lua_settop(mluastate,-2)
          ELSE
            ! Nothing to pop here
            status=-3
          ENDIF
        ELSE
          CALL lua_settop(mluastate,-2)
          status=-2
        ENDIF
    ELSE
        CALL lua_settop(mluastate,-2)
        status=-1
    ENDIF
    IF (stackstart .ne. lua_gettop(mluastate)) THEN
       WRITE(*,*) 'The stack is a different size coming out of config_function'
    ENDIF
END FUNCTION config_function

1
所有Fortran问题请使用标签[tag:fortran]。 - Vladimir F Героям слава
2
你可以将东西推入表中,然后将该表传递给函数。但是,您仍然可能会逐个将元素推入表中。我猜,如果您正在查看大块数据,最好使用userdata,尽管这可能会变得非常复杂。在aotus中,我们还使用将单个标量放入堆栈的方法,尽管您可以循环遍历任意数量的元素:https://geb.sts.nt.uni-siegen.de/doxy/aotus/module/aot_fun_module.html - haraldkl
1个回答

1

稍微解释一下我的评论,这里有一个小程序,借助Aotus实现了一个数组参数:

program aot_vecarg_test
  use flu_binding, only: flu_State, flu_settop

  use aotus_module, only: open_config_file, close_config
  use aot_fun_module, only: aot_fun_type, aot_fun_do, &
    &                       aot_fun_put, aot_fun_open, &
    &                       aot_fun_close
  use aot_references_module, only: aot_reference_for, aot_reference_to_top
  use aot_table_module, only: aot_table_open, aot_table_close, &
    &                         aot_table_from_1Darray

  implicit none

  type(flu_State) :: conf
  type(aot_fun_type) :: luafun
  integer :: iError
  character(len=80) :: ErrString
  real :: args(2)
  integer :: argref
  integer :: arghandle

  args(1) = 1.0
  args(2) = 2.0

  call create_script('aot_vecarg_test_config.lua')
  write(*,*)
  write(*,*) 'Running aot_vecarg_test...'
  write(*,*) ' * open_config_file (aot_vecarg_test_config.lua)'
  call open_config_file(L = conf, filename = 'aot_vecarg_test_config.lua', &
    &                   ErrCode = iError, ErrString = ErrString)
  if (iError /= 0) then
    write(*,*) ' : unexpected FATAL Error occured !!!'
    write(*,*) ' : Could not open the config file aot_ref_test_config.lua:'
    write(*,*) trim(ErrString)
    STOP
  end if
  write(*,*) '  : success.'

  ! Create a table with data
  call aot_table_from_1Darray( L       = conf,      &
    &                          thandle = arghandle, &
    &                          val     = args       )
  ! Create a reference to this table
  call flu_setTop(L = conf, n = arghandle)
  argref = aot_reference_for(L = conf)

  ! Start the processing of the function
  call aot_fun_open(L = conf, fun = luafun, key = 'print_array')
  ! Put the previously defined table onto the stack by using the reference
  call aot_reference_to_top(L = conf, ref = argref)
  ! Put the top of the stack to the argument list of the Lua function
  call aot_fun_put(L = conf, fun = luafun)
  ! Execute the Lua function
  call aot_fun_do(L = conf, fun = luafun, nresults = 0)
  call aot_fun_close(L = conf, fun = luafun)

  write(*,*) ' * close_conf'
  call close_config(conf)
  write(*,*) '  : success.'
  write(*,*) '... Done with aot_vecarg_test.'
  write(*,*) 'PASSED'

contains

  subroutine create_script(filename)
    character(len=*) :: filename

    open(file=trim(filename), unit=22, action='write', status='replace')
    write(22,*) '-- test script for vectorial argument'
    write(22,*) 'function print_array(x)'
    write(22,*) '  for i, num in ipairs(x) do'
    write(22,*) '    print("Lua:"..num)'
    write(22,*) '  end'
    write(22,*) 'end'
    close(22)
  end subroutine create_script

end program aot_vecarg_test

这里使用一个小助手aot_table_from_1Darray来创建实数数组的Lua表格。可以查看其代码以了解如何将数据放入表中。
然后我们创建对该表的引用,以便稍后轻松查找并将其作为参数传递给Lua函数。 该示例创建相应的Lua脚本,定义一个简单的函数,期望单个表作为输入,并打印每个表项。运行结果如下:
 Running aot_vecarg_test...
  * open_config_file (aot_vecarg_test_config.lua)
   : success.
Lua:1.0
Lua:2.0
  * close_conf
   : success.
 ... Done with aot_vecarg_test.
 PASSED

两行以Lua开头的代码是由Lua函数print_array编写的。

还有其他可能的解决方案,但我希望这至少能给出一些关于如何完成此操作的想法。我们还可以考虑扩展aot_fun_put接口来处理数组本身。


1
@kumar,使用https://bitbucket.org/apesteam/aotus/commits/eb52ed11e6c1c71b2d66f667010995707df81a88,现在可以将数组作为表传递给函数,如下所示:real :: args(2); call aot_fun_put(L, fun, args)。如上所述,这仍然涉及将数组的每个条目单独放入表中,对于大量数据可能不可取,但对于小向量应该可以。 - haraldkl

网页内容由stack overflow 提供, 点击上面的
可以查看英文原文,
原文链接