I wrote unit tests for all the Fortran interface commands in this pull request
This commit is contained in:
52
unittest/fortran/test_fortran_properties.f90
Normal file
52
unittest/fortran/test_fortran_properties.f90
Normal file
@ -0,0 +1,52 @@
|
||||
FUNCTION f_lammps_version () BIND(C)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_int
|
||||
USE liblammps
|
||||
USE keepcmds, ONLY : lmp
|
||||
IMPLICIT NONE
|
||||
INTEGER (C_int) :: f_lammps_version
|
||||
|
||||
f_lammps_version = lmp%version()
|
||||
END FUNCTION f_lammps_version
|
||||
|
||||
SUBROUTINE f_lammps_memory_usage (meminfo) BIND(C)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_double
|
||||
USE liblammps
|
||||
USE keepcmds, ONLY : lmp
|
||||
IMPLICIT NONE
|
||||
REAL (C_double), DIMENSION(3), INTENT(OUT) :: meminfo
|
||||
|
||||
CALL lmp%memory_usage(meminfo)
|
||||
END SUBROUTINE f_lammps_memory_usage
|
||||
|
||||
FUNCTION f_lammps_get_mpi_comm () BIND(C)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_int
|
||||
USE liblammps
|
||||
USE keepcmds, ONLY : lmp
|
||||
IMPLICIT NONE
|
||||
INTEGER (C_int) :: f_lammps_get_mpi_comm
|
||||
|
||||
f_lammps_get_mpi_comm = lmp%get_mpi_comm()
|
||||
END FUNCTION f_lammps_get_mpi_comm
|
||||
|
||||
FUNCTION f_lammps_extract_setting (Cstr) BIND(C)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_int, C_char
|
||||
USE keepcmds, ONLY : lmp
|
||||
USE LIBLAMMPS
|
||||
IMPLICIT NONE
|
||||
INTEGER (C_int) :: f_lammps_extract_setting
|
||||
CHARACTER (KIND=C_char, LEN=1), DIMENSION(*), INTENT(IN) :: Cstr
|
||||
INTEGER :: strlen, i
|
||||
CHARACTER (LEN=:), ALLOCATABLE :: Fstr
|
||||
|
||||
i = 1
|
||||
DO WHILE (Cstr(i) /= ACHAR(0))
|
||||
i = i + 1
|
||||
END DO
|
||||
strlen = i
|
||||
allocate ( CHARACTER(LEN=strlen) :: Fstr)
|
||||
FORALL (i=1:strlen)
|
||||
Fstr(i:i) = Cstr(i)
|
||||
END FORALL
|
||||
f_lammps_extract_setting = lmp%extract_setting(Fstr)
|
||||
deallocate (Fstr)
|
||||
END FUNCTION f_lammps_extract_setting
|
||||
Reference in New Issue
Block a user