Changes to how the adjustment to nodal positions is performed for lammpscac output

This commit is contained in:
Alex Selimov 2020-01-15 09:39:30 -05:00
parent 55fbe679e5
commit 849da1d24a
4 changed files with 69 additions and 54 deletions

View file

@ -12,7 +12,7 @@ module mode_create
character(len=100) :: name, element_type
real(kind = dp) :: lattice_parameter, orient(3,3), cell_mat(3,8), box_len(3), basis(3,3), origin(3), maxlen(3), &
orient_inv(3,3), box_vert(3,8), maxbd(3), lattice_space(3), duplicate(3), adjustVar(3,8)
orient_inv(3,3), box_vert(3,8), maxbd(3), lattice_space(3), duplicate(3)
integer :: esize, ix, iy, iz, box_lat_vert(3,8), lat_ele_num, lat_atom_num, bd_in_lat(6), &
basis_pos(3,10)
logical :: dup_flag, dim_flag
@ -105,7 +105,7 @@ module mode_create
box_bd(2*i) = maxval(r_node_temp(i,:,:))
box_bd(2*i-1) = origin(i)
end do
call add_element(element_type, esize, 1, r_node_temp)
call add_element(element_type, esize, 1, 1, r_node_temp)
end if
!If we passed the dup_flag or dim_flag then we have to convert the lattice points and add them to the atom/element arrays
@ -141,7 +141,7 @@ module mode_create
r_node_temp(:,ibasis,inod) = (r_lat(:,inod,i)*lattice_parameter)+basis_pos(:,ibasis)
end do
end do
call add_element(element_type, esize, 1, r_node_temp)
call add_element(element_type, esize, 1, 1, r_node_temp)
end do
end if
end if
@ -199,7 +199,20 @@ module mode_create
call get_command_argument(arg_pos, orient_string, arglen)
if (arglen==0) STOP "Missing orientation in orient command of mode create"
arg_pos = arg_pos+1
call parse_ori_vec(orient_string, orient(i,:))
ori_pos=2
do j = 1,3
if (orient_string(ori_pos:ori_pos) == '-') then
ori_pos = ori_pos + 1
read(orient_string(ori_pos:ori_pos), *, iostat=stat) orient(i,j)
if (stat>0) STOP "Error reading orient value"
orient(i,j) = -orient(i,j)
ori_pos = ori_pos + 1
else
read(orient_string(ori_pos:ori_pos), *, iostat=stat) orient(i,j)
if(stat>0) STOP "Error reading orient value"
ori_pos=ori_pos + 1
end if
end do
end do
@ -234,6 +247,7 @@ module mode_create
exit
end select
end do
!Calculate the lattice periodicity length in lattice units
do i = 1, 3
lattice_space(i) = norm2(orient(i,:))
@ -264,8 +278,9 @@ module mode_create
!Now normalize the orientation matrix
orient = matrix_normal(orient,3)
!Set lattice_num to 1
!Set lattice_num to 1 and add the lattice_parameter to the elements module lattice paramter variable
lattice_types = 1
lapa(1) = lattice_parameter
!If we haven't defined a basis then define the basis and add the default basis atom type and position
if (basisnum(1) == 0) then
@ -286,7 +301,7 @@ module mode_create
!Internal variables
integer :: i, inod, bd_in_lat(6), bd_in_array(6), ix, iy, iz, numlatpoints, ele(3,8), rzero(3), &
vlat(3), temp_lat(3,8), m, n, o
real(kind=dp) :: v(3), temp_nodes(3,1,8), adjustVar(3,8)
real(kind=dp) :: v(3), temp_nodes(3,1,8)
real(kind=dp), allocatable :: resize_lat_array(:,:)
logical, allocatable :: lat_points(:,:,:)
logical :: node_in_bd(8)
@ -294,23 +309,6 @@ module mode_create
!Do some value initialization
max_esize = esize
!If we are writing out to lammpscac format then we have to adjust the nodal positions
if(lmpcac) then
do inod = 1, 8
do i = 1,3
if(is_equal(cubic_cell(i, inod),0.0_dp)) then
adjustVar(i,inod) = -0.5_dp
else
adjustVar(i, inod) = 0.5_dp
end if
end do
end do
adjustVar(:,1:8) = matmul(orient,matmul(fcc_mat,adjustVar(:,1:8)))
else
adjustVar(:,:)=0.0_dp
end if
!First find the bounding lattice points (min and max points for the box in each dimension)
numlatpoints = 1
do i = 1, 3
@ -328,6 +326,7 @@ module mode_create
continue
end select
!Loop over all of lattice points within the boundary, we choose between two loops. One for the atomistic case
!and one for the regular case
if (esize==2) then
@ -440,11 +439,9 @@ module mode_create
end do
if(all(node_in_bd)) then
lat_ele_num = lat_ele_num+1
do inod = 1, 8
r_lat(:,inod,lat_ele_num) = temp_nodes(:,1,inod) + adjustVar(:,inod)
end do
lat_ele_num = lat_ele_num+1
r_lat(:,:,lat_ele_num) = temp_nodes(:,1,:)
!Now set all the lattice points contained within an element to false
do o = minval(temp_lat(3,:)), maxval(temp_lat(3,:))
do n = minval(temp_lat(2,:)), maxval(temp_lat(2,:))
@ -510,4 +507,4 @@ module mode_create
end subroutine error_message
end module mode_create
end module mode_create