Removed extra variables from mode_create.f90, added a new module to contain simulation box information and changed code accordingly, new grow subroutine in elements.

This commit is contained in:
Alex Selimov 2019-12-05 11:03:18 -05:00
parent fa1cb6ce58
commit 03f69c6df7
4 changed files with 113 additions and 10 deletions

View file

@ -135,6 +135,10 @@ module mode_create
end if
end if
!The last thing we do is setup the sub_box_boundaries
call alloc_sub_box(1)
sub_box_ori(:,:,1) = orient
sub_box_bd(:,1) = box_bd
end subroutine create
!This subroutine parses the command and pulls out information needed for mode_create
subroutine parse_command()
@ -280,9 +284,9 @@ module mode_create
integer, dimension(3,8), intent(in) :: box_in_lat !The box vertices transformed to lattice space
real(kind=dp), dimension(3,3), intent(in) :: transform_matrix !The transformation matrix from lattice_space to real space
!Internal variables
integer :: i, inod, bd_in_lat(6), bd_in_array(6), ix, iy, iz, numlatpoints, templatpoints, ele(3,8), rzero(3), ilat, &
type_interp(basisnum(1)*esize**3), vlat(3), temp_lat(3,8), m, n, o
real(kind=dp) :: v(3), temp_nodes(3,1,8), ele_atoms(3,esize**3), r_interp(3,basisnum(1)*esize**3)
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)
real(kind=dp), allocatable :: resize_lat_array(:,:)
logical, allocatable :: lat_points(:,:,:)
logical :: node_in_bd(8)