Working commit for dislocation generation branch

This commit is contained in:
Alex 2019-12-25 16:30:18 -05:00
parent 41024b9674
commit d0e6253d64
9 changed files with 114 additions and 17 deletions

View file

@ -1,7 +1,7 @@
module box
!This module contains information on the properties of the current box.
use parameters
use functions
implicit none
real(kind=dp) :: box_bd(6) !Global box boundaries
@ -34,8 +34,14 @@ module box
integer, intent(in) :: n
allocate(sub_box_ori(3,3,n), sub_box_bd(6,n), sub_box_array_bd(2,2,n))
integer :: i
allocate(sub_box_ori(3,3,n), sub_box_bd(6,n), sub_box_array_bd(2,2,n))
do i = 1, n
sub_box_ori(:,:,i) = identity_mat(3)
sub_box_bd(:,i) = 0.0_dp
sub_box_array_bd(:,:,i) = 1
end do
end subroutine alloc_sub_box
subroutine grow_sub_box(n)
@ -58,7 +64,7 @@ module box
call move_alloc(temp_bd, sub_box_bd)
temp_array_bd(:,:,1:sub_box_num) = sub_box_array_bd
temp_array_bd(:,:,sub_box_num+1:) = 0.0_dp
temp_array_bd(:,:,sub_box_num+1:) = 1
call move_alloc(temp_array_bd, sub_box_array_bd)
return