several bugs fixed; unit tests updated
This commit is contained in:
@ -8,6 +8,36 @@ FUNCTION f_lammps_version() BIND(C)
|
||||
f_lammps_version = lmp%version()
|
||||
END FUNCTION f_lammps_version
|
||||
|
||||
FUNCTION f_lammps_os_info(ptr) BIND(C)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_ptr, c_char, c_int, c_size_t, &
|
||||
C_F_POINTER
|
||||
USE LIBLAMMPS
|
||||
USE keepstuff, ONLY : lmp, c_strlen
|
||||
IMPLICIT NONE
|
||||
TYPE(c_ptr), INTENT(IN), VALUE :: ptr
|
||||
INTEGER(c_int) :: f_lammps_os_info
|
||||
CHARACTER(LEN=:), ALLOCATABLE :: string, os_info
|
||||
CHARACTER(LEN=1, KIND=c_char), POINTER :: C_string(:)
|
||||
INTEGER(c_size_t) :: length, i
|
||||
|
||||
length = c_strlen(ptr)
|
||||
CALL C_F_POINTER(ptr, C_string, [length])
|
||||
ALLOCATE(CHARACTER(LEN=length) :: string)
|
||||
DO i = 1, length
|
||||
string(i:i) = C_string(i)
|
||||
END DO
|
||||
|
||||
ALLOCATE(CHARACTER(LEN=1000) :: os_info)
|
||||
CALL lmp%get_os_info(os_info)
|
||||
os_info = TRIM(os_info)
|
||||
|
||||
IF (os_info(1:length) == string) THEN
|
||||
f_lammps_os_info = 1_c_int
|
||||
ELSE
|
||||
f_lammps_os_info = 0_c_int
|
||||
END IF
|
||||
END FUNCTION f_lammps_os_info
|
||||
|
||||
FUNCTION f_lammps_mpi_support() BIND(C)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int
|
||||
USE LIBLAMMPS
|
||||
@ -143,6 +173,23 @@ FUNCTION f_lammps_package_name(idx) BIND(C)
|
||||
END IF
|
||||
END FUNCTION f_lammps_package_name
|
||||
|
||||
FUNCTION f_lammps_installed_packages(idx) BIND(C) RESULT(package)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int, c_ptr, c_null_ptr
|
||||
USE keepstuff, ONLY : lmp, f2c_string
|
||||
IMPLICIT NONE
|
||||
INTEGER(c_int), INTENT(IN), VALUE :: idx
|
||||
TYPE(c_ptr) :: package
|
||||
CHARACTER(LEN=:), DIMENSION(:), ALLOCATABLE :: all_packages
|
||||
|
||||
CALL lmp%installed_packages(all_packages)
|
||||
|
||||
IF (idx > SIZE(all_packages) .OR. idx <= 0) THEN
|
||||
package = c_null_ptr
|
||||
ELSE
|
||||
package = f2c_string(all_packages(idx))
|
||||
END IF
|
||||
END FUNCTION f_lammps_installed_packages
|
||||
|
||||
FUNCTION f_lammps_config_accelerator(package, category, setting) BIND(C)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int, c_ptr, c_size_t, c_char, &
|
||||
C_F_POINTER
|
||||
@ -240,3 +287,24 @@ FUNCTION f_lammps_has_style(Ccategory, Cname) BIND(C)
|
||||
f_lammps_has_style = 0_c_int
|
||||
END IF
|
||||
END FUNCTION f_lammps_has_style
|
||||
|
||||
FUNCTION f_lammps_style_count(ptr) BIND(C)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_ptr, c_int, c_char, c_size_t, &
|
||||
C_F_POINTER
|
||||
USE LIBLAMMPS
|
||||
USE keepstuff, ONLY : lmp, c_strlen
|
||||
IMPLICIT NONE
|
||||
TYPE(c_ptr), VALUE :: ptr
|
||||
INTEGER(c_int) :: f_lammps_style_count
|
||||
CHARACTER(LEN=1, KIND=c_char), DIMENSION(:), POINTER :: C_category
|
||||
INTEGER(c_size_t) :: length, i
|
||||
CHARACTER(LEN=:), ALLOCATABLE :: category
|
||||
|
||||
length = c_strlen(ptr)
|
||||
CALL C_F_POINTER(ptr, C_category, [length])
|
||||
ALLOCATE(CHARACTER(LEN=length) :: category)
|
||||
DO i = 1, length
|
||||
category(i:i) = C_category(i)
|
||||
END DO
|
||||
f_lammps_style_count = lmp%style_count(category)
|
||||
END FUNCTION f_lammps_style_count
|
||||
|
||||
@ -200,3 +200,65 @@ SUBROUTINE f_lammps_scatter_atoms_subset_mask() BIND(C)
|
||||
|
||||
CALL lmp%scatter_atoms_subset('mask', tags, masks) ! push the swap to LAMMPS
|
||||
END SUBROUTINE f_lammps_scatter_atoms_subset_mask
|
||||
|
||||
SUBROUTINE f_lammps_setup_gather_bonds() BIND(C)
|
||||
USE LIBLAMMPS
|
||||
USE keepstuff, ONLY : lmp, cont_input, more_input, pair_input
|
||||
IMPLICIT NONE
|
||||
|
||||
INTERFACE
|
||||
SUBROUTINE f_lammps_setup_gather_scatter() BIND(C)
|
||||
END SUBROUTINE f_lammps_setup_gather_scatter
|
||||
END INTERFACE
|
||||
|
||||
CALL lmp%command('atom_modify map array')
|
||||
CALL lmp%command('atom_style full')
|
||||
CALL lmp%command('region simbox block 0 4 0 5 0 4')
|
||||
CALL lmp%command('create_box 1 simbox bond/types 1 extra/bond/per/atom 2')
|
||||
CALL lmp%command('create_atoms 1 single 1.0 1.0 ${zpos}')
|
||||
CALL lmp%commands_list(cont_input)
|
||||
CALL lmp%commands_list(more_input)
|
||||
CALL lmp%commands_list(pair_input)
|
||||
CALL lmp%command('bond_style zero')
|
||||
CALL lmp%command('bond_coeff *')
|
||||
CALL lmp%command('create_bonds many all all 1 0.0 1.5')
|
||||
CALL lmp%command('run 0')
|
||||
END SUBROUTINE f_lammps_setup_gather_bonds
|
||||
|
||||
FUNCTION f_lammps_test_gather_bonds_small() BIND(C) RESULT(success)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int, c_int64_t
|
||||
USE LIBLAMMPS
|
||||
USE keepstuff, ONLY : lmp, pair_input
|
||||
IMPLICIT NONE
|
||||
INTEGER(c_int) :: success
|
||||
INTEGER(c_int), DIMENSION(:), ALLOCATABLE, TARGET :: bonds
|
||||
INTEGER(c_int), DIMENSION(:,:), POINTER :: bonds_array
|
||||
|
||||
CALL lmp%gather_bonds(bonds)
|
||||
bonds_array(1:3,1:SIZE(bonds)/3) => bonds
|
||||
IF ( ALL(bonds_array(:,1) == [INTEGER(c_int) :: 1,1,3]) &
|
||||
.AND. ALL(bonds_array(:,2) == [INTEGER(c_int) :: 1,2,3])) THEN
|
||||
success = 1_c_int
|
||||
ELSE
|
||||
success = 0_c_int
|
||||
END IF
|
||||
END FUNCTION f_lammps_test_gather_bonds_small
|
||||
|
||||
FUNCTION f_lammps_test_gather_bonds_big() BIND(C) RESULT(success)
|
||||
USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_int, c_int64_t
|
||||
USE LIBLAMMPS
|
||||
USE keepstuff, ONLY : lmp, pair_input
|
||||
IMPLICIT NONE
|
||||
INTEGER(c_int) :: success
|
||||
INTEGER(c_int64_t), DIMENSION(:), ALLOCATABLE, TARGET :: bonds
|
||||
INTEGER(c_int64_t), DIMENSION(:,:), POINTER :: bonds_array
|
||||
|
||||
CALL lmp%gather_bonds(bonds)
|
||||
bonds_array(1:3,1:SIZE(bonds)/3) => bonds
|
||||
IF ( ALL(bonds_array(:,1) == [INTEGER(c_int64_t) :: 1,1,3]) &
|
||||
.AND. ALL(bonds_array(:,2) == [INTEGER(c_int64_t) :: 1,2,3])) THEN
|
||||
success = 1_c_int
|
||||
ELSE
|
||||
success = 0_c_int
|
||||
END IF
|
||||
END FUNCTION f_lammps_test_gather_bonds_big
|
||||
|
||||
@ -13,6 +13,7 @@ extern "C" {
|
||||
void *f_lammps_with_args();
|
||||
void f_lammps_close();
|
||||
int f_lammps_version();
|
||||
int f_lammps_os_info(const char*);
|
||||
int f_lammps_mpi_support();
|
||||
int f_lammps_gzip_support();
|
||||
int f_lammps_png_support();
|
||||
@ -22,11 +23,12 @@ int f_lammps_has_exceptions();
|
||||
int f_lammps_has_package(const char*);
|
||||
int f_lammps_package_count();
|
||||
char* f_lammps_package_name(int);
|
||||
char* f_lammps_installed_packages(int);
|
||||
int f_lammps_config_accelerator(const char*, const char*, const char*);
|
||||
int f_lammps_has_gpu();
|
||||
char* f_lammps_get_gpu_info(size_t);
|
||||
int f_lammps_has_style(const char*, const char*);
|
||||
int f_lammps_style_count();
|
||||
int f_lammps_style_count(const char*);
|
||||
int f_lammps_style_name();
|
||||
}
|
||||
namespace LAMMPS_NS {
|
||||
@ -62,6 +64,12 @@ TEST_F(LAMMPS_configuration, version)
|
||||
EXPECT_EQ(lmp->num_ver, f_lammps_version());
|
||||
};
|
||||
|
||||
TEST_F(LAMMPS_configuration, os_info)
|
||||
{
|
||||
std::string str = platform::os_info();
|
||||
EXPECT_EQ(f_lammps_os_info(str.c_str()), 1);
|
||||
};
|
||||
|
||||
TEST_F(LAMMPS_configuration, MPI_support)
|
||||
{
|
||||
#ifdef MPI_STUBS
|
||||
@ -138,6 +146,19 @@ TEST_F(LAMMPS_configuration, package_name)
|
||||
}
|
||||
};
|
||||
|
||||
TEST_F(LAMMPS_configuration, installed_packages)
|
||||
{
|
||||
const char *package_name;
|
||||
int npackages = lammps_config_package_count();
|
||||
char *pkg;
|
||||
for (int i=0; i < npackages; i++) {
|
||||
package_name = LAMMPS::installed_packages[i];
|
||||
pkg = f_lammps_installed_packages(i+1);
|
||||
EXPECT_STREQ(package_name, pkg);
|
||||
if (pkg) std::free(pkg);
|
||||
}
|
||||
};
|
||||
|
||||
TEST_F(LAMMPS_configuration, config_accelerator)
|
||||
{
|
||||
const int npackage = 4;
|
||||
@ -215,4 +236,17 @@ TEST_F(LAMMPS_configuration, has_style)
|
||||
EXPECT_EQ(f_lammps_has_style("atom","none"), 0);
|
||||
};
|
||||
|
||||
TEST_F(LAMMPS_configuration, style_count)
|
||||
{
|
||||
Info info(lmp);
|
||||
std::vector<std::string> category = {"atom","integrate","minimize","pair",
|
||||
"bond","angle","dihedral","improper","kspace","fix","compute","region",
|
||||
"dump","command"};
|
||||
for (int i = 0; i < category.size(); i++)
|
||||
{
|
||||
EXPECT_EQ(f_lammps_style_count(category[i].c_str()),
|
||||
info.get_available_styles(category[i].c_str()).size());
|
||||
}
|
||||
};
|
||||
|
||||
} // namespace LAMMPS_NS
|
||||
|
||||
@ -23,8 +23,13 @@ int f_lammps_gather_atoms_subset_mask(int);
|
||||
double f_lammps_gather_atoms_subset_position(int, int);
|
||||
void f_lammps_scatter_atoms_masks();
|
||||
void f_lammps_scatter_atoms_positions();
|
||||
void f_lammps_setup_gather_bonds();
|
||||
int f_lammps_test_gather_bonds_small();
|
||||
int f_lammps_test_gather_bonds_big();
|
||||
}
|
||||
|
||||
using namespace LAMMPS_NS;
|
||||
|
||||
class LAMMPS_gather_scatter : public ::testing::Test {
|
||||
protected:
|
||||
LAMMPS_NS::LAMMPS *lmp;
|
||||
@ -200,3 +205,14 @@ TEST_F(LAMMPS_gather_scatter, scatter_atoms_subset_mask)
|
||||
EXPECT_EQ(f_lammps_gather_atoms_mask(1), 9);
|
||||
EXPECT_EQ(f_lammps_gather_atoms_mask(3), 3);
|
||||
};
|
||||
|
||||
TEST_F(LAMMPS_gather_scatter, gather_bonds)
|
||||
{
|
||||
f_lammps_setup_gather_bonds();
|
||||
#ifdef LAMMPS_BIGBIG
|
||||
EXPECT_EQ(f_lammps_test_gather_bonds_big(), 1);
|
||||
#else
|
||||
EXPECT_EQ(f_lammps_test_gather_bonds_small(), 1);
|
||||
#endif
|
||||
|
||||
};
|
||||
|
||||
Reference in New Issue
Block a user