incorporate bugfixes and some suggestions from PR #3314

This commit is contained in:
Axel Kohlmeyer
2022-08-06 17:43:40 -04:00
parent d58b81afe2
commit 322dc9a4de
3 changed files with 83 additions and 51 deletions

View File

@ -38,11 +38,11 @@ found together with equivalent examples in C and C++ in the
.. note:: .. note::
A contributed (and complete!) Fortran interface that more A contributed (and more complete!) Fortran interface that more
closely resembles the C-library interface is available closely resembles the C-library interface is available in the
in the ``examples/COUPLE/fortran2`` folder. Please see the ``examples/COUPLE/fortran2`` folder. Please see the ``README`` file
``README`` file in that folder for more information about it in that folder for more information about it and how to contact its
and how to contact its author and maintainer. author and maintainer.
---------- ----------
@ -65,8 +65,9 @@ the optional logical argument set to ``.true.``. Here is a simple example:
PROGRAM testlib PROGRAM testlib
USE LIBLAMMPS ! include the LAMMPS library interface USE LIBLAMMPS ! include the LAMMPS library interface
IMPLICIT NONE
TYPE(lammps) :: lmp ! derived type to hold LAMMPS instance TYPE(lammps) :: lmp ! derived type to hold LAMMPS instance
CHARACTER(len=*), DIMENSION(*), PARAMETER :: args = & CHARACTER(len=*), PARAMETER :: args(3) = &
[ CHARACTER(len=12) :: 'liblammps', '-log', 'none' ] [ CHARACTER(len=12) :: 'liblammps', '-log', 'none' ]
! create a LAMMPS instance (and initialize MPI) ! create a LAMMPS instance (and initialize MPI)
@ -78,6 +79,41 @@ the optional logical argument set to ``.true.``. Here is a simple example:
END PROGRAM testlib END PROGRAM testlib
It is also possible to pass command line flags from Fortran to C/C++ and
thus make the resulting executable behave similar to the standalone
executable (it will ignore the `-in/-i` flag, though). This allows to
use the command line to configure accelerator and suffix settings,
configure screen and logfile output, or to set index style variables
from the command line and more. Here is a correspondingly adapted
version of the previous example:
.. code-block:: fortran
PROGRAM testlib2
USE LIBLAMMPS ! include the LAMMPS library interface
IMPLICIT NONE
TYPE(lammps) :: lmp ! derived type to hold LAMMPS instance
CHARACTER(len=128), ALLOCATABLE :: command_args(:)
INTEGER :: i, argc
! copy command line flags to `command_args()`
argc = COMMAND_ARGUMENT_COUNT()
ALLOCATE(command_args(0:argc))
DO i=0, argc
CALL GET_COMMAND_ARGUMENT(i, command_args(i))
END DO
! create a LAMMPS instance (and initialize MPI)
lmp = lammps(command_args)
! get and print numerical version code
PRINT*, 'Program name: ', command_args(0)
PRINT*, 'LAMMPS Version: ', lmp%version()
! delete LAMMPS instance (and shuts down MPI)
CALL lmp%close(.TRUE.)
DEALLOCATE(command_args)
END PROGRAM testlib2
-------------------- --------------------
Executing LAMMPS commands Executing LAMMPS commands
@ -102,7 +138,7 @@ Below is a small demonstration of the uses of the different functions:
USE LIBLAMMPS USE LIBLAMMPS
TYPE(lammps) :: lmp TYPE(lammps) :: lmp
CHARACTER(len=512) :: cmds CHARACTER(len=512) :: cmds
CHARACTER(len=40),ALLOCATABLE :: cmdlist(:) CHARACTER(len=40), ALLOCATABLE :: cmdlist(:)
CHARACTER(len=10) :: trimmed CHARACTER(len=10) :: trimmed
INTEGER :: i INTEGER :: i
@ -111,10 +147,10 @@ Below is a small demonstration of the uses of the different functions:
CALL lmp%command('variable zpos index 1.0') CALL lmp%command('variable zpos index 1.0')
! define 10 groups of 10 atoms each ! define 10 groups of 10 atoms each
ALLOCATE(cmdlist(10)) ALLOCATE(cmdlist(10))
DO i=1,10 DO i=1, 10
WRITE(trimmed,'(I10)') 10*i WRITE(trimmed,'(I10)') 10*i
WRITE(cmdlist(i),'(A,I1,A,I10,A,A)') & WRITE(cmdlist(i),'(A,I1,A,I10,A,A)') &
'group g',i-1,' id ',10*(i-1)+1,':',ADJUSTL(trimmed) 'group g', i-1, ' id ', 10*(i-1)+1, ':', ADJUSTL(trimmed)
END DO END DO
CALL lmp%commands_list(cmdlist) CALL lmp%commands_list(cmdlist)
! run multiple commands from multi-line string ! run multiple commands from multi-line string
@ -123,7 +159,7 @@ Below is a small demonstration of the uses of the different functions:
'create_box 1 box' // NEW_LINE('A') // & 'create_box 1 box' // NEW_LINE('A') // &
'create_atoms 1 single 1.0 1.0 ${zpos}' 'create_atoms 1 single 1.0 1.0 ${zpos}'
CALL lmp%commands_string(cmds) CALL lmp%commands_string(cmds)
CALL lmp%close() CALL lmp%close(.TRUE.)
END PROGRAM testcmd END PROGRAM testcmd
@ -137,9 +173,9 @@ of the contents of the ``LIBLAMMPS`` Fortran interface to LAMMPS.
.. f:type:: lammps .. f:type:: lammps
Derived type that is the general class of the Fortran interface. Derived type that is the general class of the Fortran interface. It
It holds a reference to the :cpp:class:`LAMMPS <LAMMPS_NS::LAMMPS>` class instance holds a reference to the :cpp:class:`LAMMPS <LAMMPS_NS::LAMMPS>`
that any of the included calls are forwarded to. class instance that any of the included calls are forwarded to.
:f c_ptr handle: reference to the LAMMPS class :f c_ptr handle: reference to the LAMMPS class
:f close: :f:func:`close` :f close: :f:func:`close`
@ -202,7 +238,7 @@ of the contents of the ``LIBLAMMPS`` Fortran interface to LAMMPS.
This method will call :cpp:func:`lammps_commands_list` to have LAMMPS This method will call :cpp:func:`lammps_commands_list` to have LAMMPS
execute a list of input lines. execute a list of input lines.
:p character(len=*) cmd(*): list of LAMMPS input lines :p character(len=*) cmd(:): list of LAMMPS input lines
.. f:subroutine:: commands_string(str) .. f:subroutine:: commands_string(str)
@ -210,4 +246,3 @@ of the contents of the ``LIBLAMMPS`` Fortran interface to LAMMPS.
execute a block of commands from a string. execute a block of commands from a string.
:p character(len=*) str: LAMMPS input in string :p character(len=*) str: LAMMPS input in string

View File

@ -54,20 +54,18 @@ MODULE LIBLAMMPS
! interface definitions for calling functions in library.cpp ! interface definitions for calling functions in library.cpp
INTERFACE INTERFACE
FUNCTION lammps_open(argc,argv,comm) & FUNCTION lammps_open(argc, argv, comm) BIND(C, name='lammps_open_fortran')
BIND(C, name='lammps_open_fortran')
IMPORT :: c_ptr, c_int IMPORT :: c_ptr, c_int
INTEGER(c_int), VALUE, INTENT(in) :: argc, comm INTEGER(c_int), VALUE, INTENT(in) :: argc, comm
TYPE(c_ptr), DIMENSION(*), INTENT(in) :: argv TYPE(c_ptr), DIMENSION(*), INTENT(in) :: argv
TYPE(c_ptr) :: lammps_open TYPE(c_ptr) :: lammps_open
END FUNCTION lammps_open END FUNCTION lammps_open
FUNCTION lammps_open_no_mpi(argc,argv,handle) & FUNCTION lammps_open_no_mpi(argc, argv, handle) BIND(C, name='lammps_open_no_mpi')
BIND(C, name='lammps_open_no_mpi')
IMPORT :: c_ptr, c_int IMPORT :: c_ptr, c_int
INTEGER(c_int), VALUE, INTENT(in) :: argc INTEGER(c_int), VALUE, INTENT(in) :: argc
TYPE(c_ptr), DIMENSION(*), INTENT(in) :: argv TYPE(c_ptr), DIMENSION(*), INTENT(in) :: argv
TYPE(c_ptr), INTENT(out) :: handle TYPE(c_ptr), VALUE :: handle
TYPE(c_ptr) :: lammps_open_no_mpi TYPE(c_ptr) :: lammps_open_no_mpi
END FUNCTION lammps_open_no_mpi END FUNCTION lammps_open_no_mpi
@ -85,28 +83,26 @@ MODULE LIBLAMMPS
SUBROUTINE lammps_kokkos_finalize() BIND(C, name='lammps_kokkos_finalize') SUBROUTINE lammps_kokkos_finalize() BIND(C, name='lammps_kokkos_finalize')
END SUBROUTINE lammps_kokkos_finalize END SUBROUTINE lammps_kokkos_finalize
SUBROUTINE lammps_file(handle,filename) BIND(C, name='lammps_file') SUBROUTINE lammps_file(handle, filename) BIND(C, name='lammps_file')
IMPORT :: c_ptr IMPORT :: c_ptr
TYPE(c_ptr), VALUE :: handle TYPE(c_ptr), VALUE :: handle
TYPE(c_ptr), VALUE :: filename TYPE(c_ptr), VALUE :: filename
END SUBROUTINE lammps_file END SUBROUTINE lammps_file
SUBROUTINE lammps_command(handle,cmd) BIND(C, name='lammps_command') SUBROUTINE lammps_command(handle, cmd) BIND(C, name='lammps_command')
IMPORT :: c_ptr IMPORT :: c_ptr
TYPE(c_ptr), VALUE :: handle TYPE(c_ptr), VALUE :: handle
TYPE(c_ptr), VALUE :: cmd TYPE(c_ptr), VALUE :: cmd
END SUBROUTINE lammps_command END SUBROUTINE lammps_command
SUBROUTINE lammps_commands_list(handle,ncmd,cmds) & SUBROUTINE lammps_commands_list(handle, ncmd, cmds) BIND(C, name='lammps_commands_list')
BIND(C, name='lammps_commands_list')
IMPORT :: c_ptr, c_int IMPORT :: c_ptr, c_int
TYPE(c_ptr), VALUE :: handle TYPE(c_ptr), VALUE :: handle
INTEGER(c_int), VALUE, INTENT(in) :: ncmd INTEGER(c_int), VALUE, INTENT(in) :: ncmd
TYPE(c_ptr), DIMENSION(*), INTENT(in) :: cmds TYPE(c_ptr), DIMENSION(*), INTENT(in) :: cmds
END SUBROUTINE lammps_commands_list END SUBROUTINE lammps_commands_list
SUBROUTINE lammps_commands_string(handle,str) & SUBROUTINE lammps_commands_string(handle, str) BIND(C, name='lammps_commands_string')
BIND(C, name='lammps_commands_string')
IMPORT :: c_ptr IMPORT :: c_ptr
TYPE(c_ptr), VALUE :: handle TYPE(c_ptr), VALUE :: handle
TYPE(c_ptr), VALUE :: str TYPE(c_ptr), VALUE :: str
@ -137,24 +133,23 @@ MODULE LIBLAMMPS
END INTERFACE END INTERFACE
CONTAINS CONTAINS
! Fortran wrappers and helper functions. ! Fortran wrappers and helper functions.
! Constructor for the LAMMPS class. ! Constructor for the LAMMPS class.
! Combined wrapper around lammps_open_fortran() and lammps_open_no_mpi() ! Combined wrapper around lammps_open_fortran() and lammps_open_no_mpi()
TYPE(lammps) FUNCTION lmp_open(args,comm) TYPE(lammps) FUNCTION lmp_open(args, comm)
IMPLICIT NONE IMPLICIT NONE
INTEGER,INTENT(in), OPTIONAL :: comm INTEGER, INTENT(in), OPTIONAL :: comm
CHARACTER(len=*), INTENT(in), OPTIONAL :: args(:) CHARACTER(len=*), INTENT(in), OPTIONAL :: args(:)
TYPE(c_ptr), ALLOCATABLE :: argv(:) TYPE(c_ptr), ALLOCATABLE :: argv(:)
TYPE(c_ptr) :: dummy=c_null_ptr TYPE(c_ptr) :: dummy=c_null_ptr
INTEGER :: i,argc INTEGER(c_int) :: i, c_comm, argc
IF (PRESENT(args)) THEN IF (PRESENT(args)) THEN
! convert argument list to c style ! convert fortran argument list to c style
argc = SIZE(args) argc = SIZE(args)
ALLOCATE(argv(argc)) ALLOCATE(argv(argc))
DO i=1,argc DO i=1, argc
argv(i) = f2c_string(args(i)) argv(i) = f2c_string(args(i))
END DO END DO
ELSE ELSE
@ -164,23 +159,24 @@ CONTAINS
ENDIF ENDIF
IF (PRESENT(comm)) THEN IF (PRESENT(comm)) THEN
lmp_open%handle = lammps_open(argc,argv,comm) c_comm = comm
lmp_open%handle = lammps_open(argc, argv, c_comm)
ELSE ELSE
lmp_open%handle = lammps_open_no_mpi(argc,argv,dummy) lmp_open%handle = lammps_open_no_mpi(argc, argv, dummy)
END IF END IF
! Clean up allocated memory ! Clean up allocated memory
DO i=1,argc DO i=1, argc
CALL lammps_free(argv(i)) CALL lammps_free(argv(i))
END DO END DO
DEALLOCATE(argv) DEALLOCATE(argv)
END FUNCTION lmp_open END FUNCTION lmp_open
! Combined Fortran wrapper around lammps_close() and lammps_mpi_finalize() ! Combined Fortran wrapper around lammps_close() and lammps_mpi_finalize()
SUBROUTINE lmp_close(self,finalize) SUBROUTINE lmp_close(self, finalize)
IMPLICIT NONE IMPLICIT NONE
CLASS(lammps) :: self CLASS(lammps) :: self
LOGICAL,INTENT(in),OPTIONAL :: finalize LOGICAL, INTENT(in), OPTIONAL :: finalize
CALL lammps_close(self%handle) CALL lammps_close(self%handle)
@ -206,68 +202,69 @@ CONTAINS
lmp_get_natoms = lammps_get_natoms(self%handle) lmp_get_natoms = lammps_get_natoms(self%handle)
END FUNCTION lmp_get_natoms END FUNCTION lmp_get_natoms
SUBROUTINE lmp_file(self,filename) SUBROUTINE lmp_file(self, filename)
IMPLICIT NONE IMPLICIT NONE
CLASS(lammps) :: self CLASS(lammps) :: self
CHARACTER(len=*) :: filename CHARACTER(len=*) :: filename
TYPE(c_ptr) :: str TYPE(c_ptr) :: str
str = f2c_string(filename) str = f2c_string(filename)
CALL lammps_file(self%handle,str) CALL lammps_file(self%handle, str)
CALL lammps_free(str) CALL lammps_free(str)
END SUBROUTINE lmp_file END SUBROUTINE lmp_file
! equivalent function to lammps_command() ! equivalent function to lammps_command()
SUBROUTINE lmp_command(self,cmd) SUBROUTINE lmp_command(self, cmd)
IMPLICIT NONE IMPLICIT NONE
CLASS(lammps) :: self CLASS(lammps) :: self
CHARACTER(len=*) :: cmd CHARACTER(len=*) :: cmd
TYPE(c_ptr) :: str TYPE(c_ptr) :: str
str = f2c_string(cmd) str = f2c_string(cmd)
CALL lammps_command(self%handle,str) CALL lammps_command(self%handle, str)
CALL lammps_free(str) CALL lammps_free(str)
END SUBROUTINE lmp_command END SUBROUTINE lmp_command
! equivalent function to lammps_commands_list() ! equivalent function to lammps_commands_list()
SUBROUTINE lmp_commands_list(self,cmds) SUBROUTINE lmp_commands_list(self, cmds)
IMPLICIT NONE IMPLICIT NONE
CLASS(lammps) :: self CLASS(lammps) :: self
CHARACTER(len=*), INTENT(in), OPTIONAL :: cmds(:) CHARACTER(len=*), INTENT(in), OPTIONAL :: cmds(:)
TYPE(c_ptr), ALLOCATABLE :: cmdv(:) TYPE(c_ptr), ALLOCATABLE :: cmdv(:)
INTEGER :: i,ncmd INTEGER :: i, ncmd
! convert command list to c style ! convert command list to c style
ncmd = SIZE(cmds) ncmd = SIZE(cmds)
ALLOCATE(cmdv(ncmd)) ALLOCATE(cmdv(ncmd))
DO i=1,ncmd DO i=1, ncmd
cmdv(i) = f2c_string(cmds(i)) cmdv(i) = f2c_string(cmds(i))
END DO END DO
CALL lammps_commands_list(self%handle,ncmd,cmdv) CALL lammps_commands_list(self%handle, ncmd, cmdv)
! Clean up allocated memory ! Clean up allocated memory
DO i=1,ncmd DO i=1, ncmd
CALL lammps_free(cmdv(i)) CALL lammps_free(cmdv(i))
END DO END DO
DEALLOCATE(cmdv) DEALLOCATE(cmdv)
END SUBROUTINE lmp_commands_list END SUBROUTINE lmp_commands_list
! equivalent function to lammps_commands_string() ! equivalent function to lammps_commands_string()
SUBROUTINE lmp_commands_string(self,str) SUBROUTINE lmp_commands_string(self, str)
IMPLICIT NONE IMPLICIT NONE
CLASS(lammps) :: self CLASS(lammps) :: self
CHARACTER(len=*) :: str CHARACTER(len=*) :: str
TYPE(c_ptr) :: tmp TYPE(c_ptr) :: tmp
tmp = f2c_string(str) tmp = f2c_string(str)
CALL lammps_commands_string(self%handle,tmp) CALL lammps_commands_string(self%handle, tmp)
CALL lammps_free(tmp) CALL lammps_free(tmp)
END SUBROUTINE lmp_commands_string END SUBROUTINE lmp_commands_string
! ---------------------------------------------------------------------- ! ----------------------------------------------------------------------
! local helper functions ! local helper functions
! copy fortran string to zero terminated c string ! copy fortran string to zero terminated c string
! ----------------------------------------------------------------------
FUNCTION f2c_string(f_string) RESULT(ptr) FUNCTION f2c_string(f_string) RESULT(ptr)
CHARACTER (len=*), INTENT(in) :: f_string CHARACTER (len=*), INTENT(in) :: f_string
CHARACTER (len=1, kind=c_char), POINTER :: c_string(:) CHARACTER (len=1, kind=c_char), POINTER :: c_string(:)
@ -276,8 +273,8 @@ CONTAINS
n = LEN_TRIM(f_string) n = LEN_TRIM(f_string)
ptr = lammps_malloc(n+1) ptr = lammps_malloc(n+1)
CALL C_F_POINTER(ptr,c_string,[1]) CALL C_F_POINTER(ptr, c_string, [1])
DO i=1,n DO i=1, n
c_string(i) = f_string(i:i) c_string(i) = f_string(i:i)
END DO END DO
c_string(n+1) = c_null_char c_string(n+1) = c_null_char

View File

@ -234,7 +234,7 @@ fails a null pointer is returned.
void *lammps_open_no_mpi(int argc, char **argv, void **ptr) void *lammps_open_no_mpi(int argc, char **argv, void **ptr)
{ {
return lammps_open(argc,argv,MPI_COMM_WORLD,ptr); return lammps_open(argc, argv, MPI_COMM_WORLD, ptr);
} }
/* ---------------------------------------------------------------------- */ /* ---------------------------------------------------------------------- */