implemented create_atoms and encode_image_flags and unit tests for them; added IMGMASK and friends to extract_setting and unit tests for them; wrote documentation for them
This commit is contained in:
@ -24,7 +24,7 @@ END SUBROUTINE f_lammps_close
|
||||
|
||||
SUBROUTINE f_lammps_setup_create_atoms() BIND(C)
|
||||
USE LIBLAMMPS
|
||||
USE keepstuff, ONLY : lmp, big_input, cont_input, more_input
|
||||
USE keepstuff, ONLY : lmp, big_input, cont_input, more_input, pair_input
|
||||
IMPLICIT NONE
|
||||
|
||||
!CALL lmp%command('atom_modify map array')
|
||||
@ -35,7 +35,7 @@ END SUBROUTINE f_lammps_setup_create_atoms
|
||||
|
||||
SUBROUTINE f_lammps_create_three_atoms() BIND(C)
|
||||
USE ISO_C_BINDING, ONLY: c_double, c_int, c_int64_t
|
||||
USE keepstuff, ONLY : lmp, big_input, cont_input, more_input
|
||||
USE keepstuff, ONLY : lmp
|
||||
USE LIBLAMMPS
|
||||
IMPLICIT NONE
|
||||
INTEGER(c_int), DIMENSION(3) :: new_ids, new_images, new_types
|
||||
@ -46,8 +46,16 @@ SUBROUTINE f_lammps_create_three_atoms() BIND(C)
|
||||
|
||||
new_ids = [4, 6, 5]
|
||||
new_big_ids = [4, 6, 5]
|
||||
new_images = [0, 0, 1]
|
||||
new_big_images = [0, 0, 1]
|
||||
tagint_size = lmp%extract_setting('tagint')
|
||||
IF ( tagint_size == 4_c_int ) THEN
|
||||
new_images(1) = lmp%encode_image_flags(1, -1, 3)
|
||||
new_images(2) = lmp%encode_image_flags(-2, 0, 0)
|
||||
new_images(3) = lmp%encode_image_flags(-2, -2, 1)
|
||||
ELSE
|
||||
new_big_images(1) = lmp%encode_image_flags(1, -1, 3)
|
||||
new_big_images(2) = lmp%encode_image_flags(-2, 0, 0)
|
||||
new_big_images(3) = lmp%encode_image_flags(-2, -2, 1)
|
||||
END IF
|
||||
new_types = [1, 1, 1]
|
||||
new_x = [ 1.0_c_double, 1.8_c_double, 2.718281828_c_double, &
|
||||
0.6_c_double, 0.8_c_double, 2.2_c_double, &
|
||||
@ -56,7 +64,6 @@ SUBROUTINE f_lammps_create_three_atoms() BIND(C)
|
||||
0.1_c_double, 0.2_c_double, -0.2_c_double, &
|
||||
1.0_c_double, -1.0_c_double, 3.0_c_double ]
|
||||
wrap = .FALSE.
|
||||
tagint_size = lmp%extract_setting('tagint')
|
||||
IF ( tagint_size == 4_c_int ) THEN
|
||||
CALL lmp%create_atoms(new_ids, new_types, new_x, new_v, new_images, wrap)
|
||||
ELSE
|
||||
@ -65,4 +72,86 @@ SUBROUTINE f_lammps_create_three_atoms() BIND(C)
|
||||
END IF
|
||||
END SUBROUTINE f_lammps_create_three_atoms
|
||||
|
||||
SUBROUTINE f_lammps_create_two_more() BIND(C)
|
||||
USE ISO_C_BINDING, ONLY: c_double, c_int
|
||||
USE keepstuff, ONLY : lmp
|
||||
USE LIBLAMMPS
|
||||
IMPLICIT NONE
|
||||
INTEGER(c_int), DIMENSION(2) :: new_types
|
||||
REAL(c_double), DIMENSION(6) :: new_x
|
||||
|
||||
new_types = [1_c_int, 1_c_int]
|
||||
new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
|
||||
1.2_c_double, 2.1_c_double, 1.25_c_double]
|
||||
CALL lmp%create_atoms(type=new_types, x=new_x)
|
||||
END SUBROUTINE f_lammps_create_two_more
|
||||
|
||||
SUBROUTINE f_lammps_create_two_more_small() BIND(C)
|
||||
USE ISO_C_BINDING, ONLY: c_double, c_int
|
||||
USE keepstuff, ONLY : lmp
|
||||
USE LIBLAMMPS
|
||||
IMPLICIT NONE
|
||||
INTEGER(c_int), DIMENSION(2) :: new_types
|
||||
REAL(c_double), DIMENSION(6) :: new_x
|
||||
INTEGER(c_int), DIMENSION(2) :: new_id, new_image
|
||||
|
||||
new_types = [1_c_int, 1_c_int]
|
||||
new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
|
||||
1.2_c_double, 2.1_c_double, 1.25_c_double]
|
||||
new_id = [8_c_int, 7_c_int]
|
||||
new_image(1) = lmp%encode_image_flags(1,0,0)
|
||||
new_image(2) = lmp%encode_image_flags(-1,0,0)
|
||||
CALL lmp%create_atoms(id=new_id, image=new_image, type=new_types, x=new_x)
|
||||
END SUBROUTINE f_lammps_create_two_more_small
|
||||
|
||||
SUBROUTINE f_lammps_create_two_more_big() BIND(C)
|
||||
USE ISO_C_BINDING, ONLY: c_double, c_int, c_int64_t
|
||||
USE keepstuff, ONLY : lmp
|
||||
USE LIBLAMMPS
|
||||
IMPLICIT NONE
|
||||
INTEGER(c_int), DIMENSION(2) :: new_types
|
||||
REAL(c_double), DIMENSION(6) :: new_x
|
||||
INTEGER(c_int64_t), DIMENSION(2) :: new_id, new_image
|
||||
|
||||
new_types = [1_c_int, 1_c_int]
|
||||
new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
|
||||
1.2_c_double, 2.1_c_double, 1.25_c_double]
|
||||
new_id = [8_c_int64_t, 7_c_int64_t]
|
||||
new_image(1) = lmp%encode_image_flags(1,0,0)
|
||||
new_image(2) = lmp%encode_image_flags(-1,0,0)
|
||||
CALL lmp%create_atoms(id=new_id, image=new_image, type=new_types, x=new_x)
|
||||
END SUBROUTINE f_lammps_create_two_more_big
|
||||
|
||||
SUBROUTINE f_lammps_create_two_more_small2() BIND(C)
|
||||
USE ISO_C_BINDING, ONLY: c_double, c_int
|
||||
USE keepstuff, ONLY : lmp
|
||||
USE LIBLAMMPS
|
||||
IMPLICIT NONE
|
||||
INTEGER(c_int), DIMENSION(2) :: new_types
|
||||
REAL(c_double), DIMENSION(6) :: new_x
|
||||
INTEGER(c_int), DIMENSION(2) :: new_id
|
||||
|
||||
new_types = [1_c_int, 1_c_int]
|
||||
new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
|
||||
1.2_c_double, 2.1_c_double, 1.25_c_double]
|
||||
new_id = [8_c_int, 7_c_int]
|
||||
CALL lmp%create_atoms(id=new_id, type=new_types, x=new_x)
|
||||
END SUBROUTINE f_lammps_create_two_more_small2
|
||||
|
||||
SUBROUTINE f_lammps_create_two_more_big2() BIND(C)
|
||||
USE ISO_C_BINDING, ONLY: c_double, c_int, c_int64_t
|
||||
USE keepstuff, ONLY : lmp
|
||||
USE LIBLAMMPS
|
||||
IMPLICIT NONE
|
||||
INTEGER(c_int), DIMENSION(2) :: new_types
|
||||
REAL(c_double), DIMENSION(6) :: new_x
|
||||
INTEGER(c_int64_t), DIMENSION(2) :: new_id
|
||||
|
||||
new_types = [1_c_int, 1_c_int]
|
||||
new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
|
||||
1.2_c_double, 2.1_c_double, 1.25_c_double]
|
||||
new_id = [8_c_int64_t, 7_c_int64_t]
|
||||
CALL lmp%create_atoms(id=new_id, type=new_types, x=new_x)
|
||||
END SUBROUTINE f_lammps_create_two_more_big2
|
||||
|
||||
! vim: ts=2 sts=2 sw=2 et
|
||||
|
||||
Reference in New Issue
Block a user