address portability issues to the flang LLVM Fortran 2018 compiler
This commit is contained in:
@ -71,13 +71,13 @@ FUNCTION f_lammps_gather_atoms_concat_mask(i) BIND(C)
|
||||
|
||||
CALL lmp%gather_atoms_concat('mask', 1_c_int, mask)
|
||||
CALL lmp%gather_atoms_concat('id', 1_c_int, tag)
|
||||
f_lammps_gather_atoms_concat_mask = -1
|
||||
DO j = 1, SIZE(tag)
|
||||
IF (tag(j) == i) THEN
|
||||
f_lammps_gather_atoms_concat_mask = mask(j)
|
||||
RETURN
|
||||
EXIT
|
||||
END IF
|
||||
END DO
|
||||
f_lammps_gather_atoms_concat_mask = -1
|
||||
END FUNCTION f_lammps_gather_atoms_concat_mask
|
||||
|
||||
FUNCTION f_lammps_gather_atoms_concat_position(xyz, id) BIND(C)
|
||||
@ -93,6 +93,7 @@ FUNCTION f_lammps_gather_atoms_concat_position(xyz, id) BIND(C)
|
||||
|
||||
CALL lmp%gather_atoms_concat('x', 3_c_int, positions)
|
||||
CALL lmp%gather_atoms_concat('id', 1_c_int, tag)
|
||||
f_lammps_gather_atoms_concat_position = -1.0_c_double
|
||||
DO j = 1, SIZE(tag)
|
||||
IF (tag(j) == id) THEN
|
||||
f_lammps_gather_atoms_concat_position = positions((j-1)*3 + xyz)
|
||||
@ -112,13 +113,13 @@ FUNCTION f_lammps_gather_atoms_subset_mask(i) BIND(C)
|
||||
INTEGER(c_int), DIMENSION(*), PARAMETER :: tag = [3,2]
|
||||
|
||||
CALL lmp%gather_atoms_subset('mask', 1_c_int, tag, mask)
|
||||
f_lammps_gather_atoms_subset_mask = -1
|
||||
DO j = 1, SIZE(tag)
|
||||
IF (tag(j) == i) THEN
|
||||
f_lammps_gather_atoms_subset_mask = mask(j)
|
||||
RETURN
|
||||
EXIT
|
||||
END IF
|
||||
END DO
|
||||
f_lammps_gather_atoms_subset_mask = -1
|
||||
END FUNCTION f_lammps_gather_atoms_subset_mask
|
||||
|
||||
FUNCTION f_lammps_gather_atoms_subset_position(xyz,id) BIND(C)
|
||||
@ -133,13 +134,13 @@ FUNCTION f_lammps_gather_atoms_subset_position(xyz,id) BIND(C)
|
||||
INTEGER :: j
|
||||
|
||||
CALL lmp%gather_atoms_subset('x', 3_c_int, tag, positions)
|
||||
f_lammps_gather_atoms_subset_position = -1.0_c_double
|
||||
DO j = 1, SIZE(tag)
|
||||
IF (tag(j) == id) THEN
|
||||
f_lammps_gather_atoms_subset_position = positions((j-1)*3 + xyz)
|
||||
RETURN
|
||||
EXIT
|
||||
END IF
|
||||
END DO
|
||||
f_lammps_gather_atoms_subset_position = -1.0D0
|
||||
END FUNCTION f_lammps_gather_atoms_subset_position
|
||||
|
||||
SUBROUTINE f_lammps_scatter_atoms_masks() BIND(C)
|
||||
|
||||
Reference in New Issue
Block a user