|
|
@ -70,8 +70,10 @@ module opt_group
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
if(remesh_size > 0)then
|
|
|
|
if(remesh_size > 0)then
|
|
|
|
|
|
|
|
print *, "Remesh command has been dropped"
|
|
|
|
|
|
|
|
stop 1
|
|
|
|
call get_group
|
|
|
|
call get_group
|
|
|
|
call remesh_group
|
|
|
|
! call remesh_group
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
if(group_type > 0) then
|
|
|
|
if(group_type > 0) then
|
|
|
@ -84,8 +86,10 @@ module opt_group
|
|
|
|
call displace_group
|
|
|
|
call displace_group
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
if(insert_type > 0) then
|
|
|
|
if(insert_type > 0) then
|
|
|
|
|
|
|
|
print *, "Insert command has been dropped"
|
|
|
|
|
|
|
|
stop 1
|
|
|
|
call get_group
|
|
|
|
call get_group
|
|
|
|
call insert_group
|
|
|
|
! call insert_group
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
if(num_species > 0) then
|
|
|
|
if(num_species > 0) then
|
|
|
@ -705,7 +709,7 @@ module opt_group
|
|
|
|
!here as well to make sure they are in the box
|
|
|
|
!here as well to make sure they are in the box
|
|
|
|
do j = 1, basisnum(lat_ele(ie))*size_ele(ie)**3
|
|
|
|
do j = 1, basisnum(lat_ele(ie))*size_ele(ie)**3
|
|
|
|
call apply_periodic(r_interp(:,j))
|
|
|
|
call apply_periodic(r_interp(:,j))
|
|
|
|
call add_atom(0,type_interp(j), sbox_ele(ie), r_interp(:,j))
|
|
|
|
call add_atom(0,type_interp(j), r_interp(:,j))
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
!Once all atoms are added we delete all of the elements
|
|
|
|
!Once all atoms are added we delete all of the elements
|
|
|
@ -778,7 +782,7 @@ module opt_group
|
|
|
|
if (.not.in_group_ele(esize, lat_ele(ie), rfill)) then
|
|
|
|
if (.not.in_group_ele(esize, lat_ele(ie), rfill)) then
|
|
|
|
nump_ele=nump_ele - esize**3
|
|
|
|
nump_ele=nump_ele - esize**3
|
|
|
|
lat_points(m:m+esize-1, n:n+esize-1, o:o+esize-1) = .false.
|
|
|
|
lat_points(m:m+esize-1, n:n+esize-1, o:o+esize-1) = .false.
|
|
|
|
call add_element(0,type_ele(ie), esize, lat_ele(ie), sbox_ele(ie), rfill)
|
|
|
|
call add_element(0,type_ele(ie), esize, lat_ele(ie), rfill)
|
|
|
|
new_ele_num = new_ele_num + 1
|
|
|
|
new_ele_num = new_ele_num + 1
|
|
|
|
added_points = added_points + esize**3
|
|
|
|
added_points = added_points + esize**3
|
|
|
|
end if
|
|
|
|
end if
|
|
|
@ -797,7 +801,7 @@ module opt_group
|
|
|
|
call get_interp_pos(m,n,o, ie, ratom(:,:))
|
|
|
|
call get_interp_pos(m,n,o, ie, ratom(:,:))
|
|
|
|
do ibasis = 1, basisnum(lat_ele(ie))
|
|
|
|
do ibasis = 1, basisnum(lat_ele(ie))
|
|
|
|
call apply_periodic(ratom(:,ibasis))
|
|
|
|
call apply_periodic(ratom(:,ibasis))
|
|
|
|
call add_atom(0, basis_type(ibasis,lat_ele(ie)), sbox_ele(ie), ratom(:,ibasis))
|
|
|
|
call add_atom(0, basis_type(ibasis,lat_ele(ie)), ratom(:,ibasis))
|
|
|
|
added_points=added_points + 1
|
|
|
|
added_points=added_points + 1
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end if
|
|
|
|
end if
|
|
|
@ -818,270 +822,270 @@ module opt_group
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine refinefill_group
|
|
|
|
end subroutine refinefill_group
|
|
|
|
|
|
|
|
|
|
|
|
subroutine remesh_group
|
|
|
|
! subroutine remesh_group
|
|
|
|
!This command is used to remesh the group to a desired element size
|
|
|
|
! !This command is used to remesh the group to a desired element size
|
|
|
|
|
|
|
|
!
|
|
|
|
integer :: i, j, k, ix, iy, iz, inod, ibasis, ie, type_interp(max_basisnum*max_esize**3), add_atom_num, orig_atom_num, &
|
|
|
|
! integer :: i, j, k, ix, iy, iz, inod, ibasis, ie, type_interp(max_basisnum*max_esize**3), add_atom_num, orig_atom_num, &
|
|
|
|
current_esize, dof, max_lat(3), r_lat(3), ele(3,8), vlat(3), bd_in_lat(6), bd_in_array(3), new_ele, new_atom, &
|
|
|
|
! current_esize, dof, max_lat(3), r_lat(3), ele(3,8), vlat(3), bd_in_lat(6), bd_in_array(3), new_ele, new_atom, &
|
|
|
|
max_loops, working_esize, group_lat_num, lat_list(10), group_sbox_num, sbox_list(100), is, ilat, tot_dof
|
|
|
|
! max_loops, working_esize, group_lat_num, lat_list(10), is, ilat, tot_dof
|
|
|
|
|
|
|
|
!
|
|
|
|
real(kind=dp) :: r_interp(3, max_basisnum*max_esize**3), ori_inv(3,3), r(3), &
|
|
|
|
! real(kind=dp) :: r_interp(3, max_basisnum*max_esize**3), ori_inv(3,3), r(3), &
|
|
|
|
r_new_node(3,max_basisnum, max_ng_node), orient(3,3), group_in_lat(3,8), group_bd(6)
|
|
|
|
! r_new_node(3,max_basisnum, max_ng_node), orient(3,3), group_in_lat(3,8), group_bd(6)
|
|
|
|
logical, allocatable :: lat_points(:,:,:), new_sbox, new_lat
|
|
|
|
! logical, allocatable :: lat_points(:,:,:), new_sbox, new_lat
|
|
|
|
character(len=100) :: remesh_ele_type
|
|
|
|
! character(len=100) :: remesh_ele_type
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
!
|
|
|
|
!Right now we just hardcode only remeshing to elements
|
|
|
|
! !Right now we just hardcode only remeshing to elements
|
|
|
|
remesh_ele_type = 'fcc'
|
|
|
|
! remesh_ele_type = 'fcc'
|
|
|
|
|
|
|
|
!
|
|
|
|
! Determine which sub_boxes and lattices types are within in the group
|
|
|
|
! ! Determine which sub_boxes and lattices types are within in the group
|
|
|
|
group_sbox_num = 0
|
|
|
|
! group_sbox_num = 0
|
|
|
|
group_lat_num = 0
|
|
|
|
! group_lat_num = 0
|
|
|
|
do i = 1, group_atom_num
|
|
|
|
! do i = 1, group_atom_num
|
|
|
|
new_sbox=.true.
|
|
|
|
! new_sbox=.true.
|
|
|
|
new_lat=.true.
|
|
|
|
! new_lat=.true.
|
|
|
|
do j = 1, group_sbox_num
|
|
|
|
! do j = 1, group_sbox_num
|
|
|
|
if (sbox_list(j) == sbox_atom(atom_index(i))) then
|
|
|
|
! if (sbox_list(j) == sbox_atom(atom_index(i))) then
|
|
|
|
new_sbox=.false.
|
|
|
|
! new_sbox=.false.
|
|
|
|
exit
|
|
|
|
! exit
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
if(new_sbox) then
|
|
|
|
! if(new_sbox) then
|
|
|
|
group_sbox_num = group_sbox_num + 1
|
|
|
|
! group_sbox_num = group_sbox_num + 1
|
|
|
|
sbox_list(group_sbox_num) = sbox_atom(atom_index(i))
|
|
|
|
! sbox_list(group_sbox_num) = sbox_atom(atom_index(i))
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
|
|
|
|
!
|
|
|
|
do j = 1, group_lat_num
|
|
|
|
! do j = 1, group_lat_num
|
|
|
|
if (basis_type(1,lat_list(j)) == type_atom(atom_index(i))) then
|
|
|
|
! if (basis_type(1,lat_list(j)) == type_atom(atom_index(i))) then
|
|
|
|
new_lat = .false.
|
|
|
|
! new_lat = .false.
|
|
|
|
exit
|
|
|
|
! exit
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
if (new_lat) then
|
|
|
|
! if (new_lat) then
|
|
|
|
group_lat_num = group_lat_num + 1
|
|
|
|
! group_lat_num = group_lat_num + 1
|
|
|
|
do k = 1, lattice_types
|
|
|
|
! do k = 1, lattice_types
|
|
|
|
if (basis_type(1,k) == type_atom(atom_index(i))) lat_list(group_lat_num) = k
|
|
|
|
! if (basis_type(1,k) == type_atom(atom_index(i))) lat_list(group_lat_num) = k
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
|
|
|
|
!
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
do i = 1, group_ele_num
|
|
|
|
! do i = 1, group_ele_num
|
|
|
|
new_sbox=.true.
|
|
|
|
! new_sbox=.true.
|
|
|
|
new_lat = .true.
|
|
|
|
! new_lat = .true.
|
|
|
|
do j = 1, group_sbox_num
|
|
|
|
! do j = 1, group_sbox_num
|
|
|
|
if (sbox_list(j) == sbox_ele(element_index(i))) then
|
|
|
|
! if (sbox_list(j) == sbox_ele(element_index(i))) then
|
|
|
|
new_sbox = .false.
|
|
|
|
! new_sbox = .false.
|
|
|
|
exit
|
|
|
|
! exit
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
if (new_sbox) then
|
|
|
|
! if (new_sbox) then
|
|
|
|
group_sbox_num = group_sbox_num + 1
|
|
|
|
! group_sbox_num = group_sbox_num + 1
|
|
|
|
sbox_list(group_sbox_num) = sbox_ele(element_index(i))
|
|
|
|
! sbox_list(group_sbox_num) = sbox_ele(element_index(i))
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
|
|
|
|
!
|
|
|
|
do j = 1, group_lat_num
|
|
|
|
! do j = 1, group_lat_num
|
|
|
|
if (lat_list(group_lat_num) == lat_ele(element_index(i))) then
|
|
|
|
! if (lat_list(group_lat_num) == lat_ele(element_index(i))) then
|
|
|
|
new_lat=.false.
|
|
|
|
! new_lat=.false.
|
|
|
|
exit
|
|
|
|
! exit
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
if (new_lat) then
|
|
|
|
! if (new_lat) then
|
|
|
|
group_lat_num = group_lat_num + 1
|
|
|
|
! group_lat_num = group_lat_num + 1
|
|
|
|
lat_list(group_lat_num) = lat_ele(element_index(i))
|
|
|
|
! lat_list(group_lat_num) = lat_ele(element_index(i))
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
new_atom = 0
|
|
|
|
! new_atom = 0
|
|
|
|
new_ele=0
|
|
|
|
! new_ele=0
|
|
|
|
tot_dof=0
|
|
|
|
! tot_dof=0
|
|
|
|
do is = 1, group_sbox_num
|
|
|
|
! do is = 1, group_sbox_num
|
|
|
|
|
|
|
|
!
|
|
|
|
orient = sub_box_ori(:, :, sbox_list(is))
|
|
|
|
! orient = sub_box_ori(:, :, sbox_list(is))
|
|
|
|
call matrix_inverse(orient,3,ori_inv)
|
|
|
|
! call matrix_inverse(orient,3,ori_inv)
|
|
|
|
|
|
|
|
!
|
|
|
|
do ilat = 1, group_lat_num
|
|
|
|
! do ilat = 1, group_lat_num
|
|
|
|
|
|
|
|
!
|
|
|
|
!First calculate max position in lattice space to be able to allocate lat_points array, also sum the total number
|
|
|
|
! !First calculate max position in lattice space to be able to allocate lat_points array, also sum the total number
|
|
|
|
!of degrees of freedom which are added
|
|
|
|
! !of degrees of freedom which are added
|
|
|
|
dof = 0
|
|
|
|
! dof = 0
|
|
|
|
do j = 1, 3
|
|
|
|
! do j = 1, 3
|
|
|
|
group_bd(2*j) = -huge(1.0_dp)
|
|
|
|
! group_bd(2*j) = -huge(1.0_dp)
|
|
|
|
group_bd(2*j-1) = huge(1.0_dp)
|
|
|
|
! group_bd(2*j-1) = huge(1.0_dp)
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
do i = 1, group_atom_num
|
|
|
|
! do i = 1, group_atom_num
|
|
|
|
if ((type_atom(atom_index(i)) == basis_type(1,ilat)).and.(sbox_atom(atom_index(i)) == is)) then
|
|
|
|
! if ((type_atom(atom_index(i)) == basis_type(1,ilat)).and.(sbox_atom(atom_index(i)) == is)) then
|
|
|
|
do j =1 ,3
|
|
|
|
! do j =1 ,3
|
|
|
|
if (r_atom(j,atom_index(i)) > group_bd(2*j)) group_bd(2*j) = r_atom(j,atom_index(i))
|
|
|
|
! if (r_atom(j,atom_index(i)) > group_bd(2*j)) group_bd(2*j) = r_atom(j,atom_index(i))
|
|
|
|
if (r_atom(j,atom_index(i)) < group_bd(2*j-1)) group_bd(2*j-1) = r_atom(j,atom_index(i))
|
|
|
|
! if (r_atom(j,atom_index(i)) < group_bd(2*j-1)) group_bd(2*j-1) = r_atom(j,atom_index(i))
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
dof = dof + 1
|
|
|
|
! dof = dof + 1
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
do i = 1, group_ele_num
|
|
|
|
! do i = 1, group_ele_num
|
|
|
|
if ((lat_ele(element_index(i)) == ilat).and.(sbox_ele(element_index(i)) == is)) then
|
|
|
|
! if ((lat_ele(element_index(i)) == ilat).and.(sbox_ele(element_index(i)) == is)) then
|
|
|
|
do inod =1, ng_node(ilat)
|
|
|
|
! do inod =1, ng_node(ilat)
|
|
|
|
do ibasis = 1, basisnum(ilat)
|
|
|
|
! do ibasis = 1, basisnum(ilat)
|
|
|
|
do j = 1, 3
|
|
|
|
! do j = 1, 3
|
|
|
|
r =r_node(j,ibasis,inod,element_index(i))
|
|
|
|
! r =r_node(j,ibasis,inod,element_index(i))
|
|
|
|
if (r(j) > group_bd(2*j)) group_bd(2*j) = r(j)
|
|
|
|
! if (r(j) > group_bd(2*j)) group_bd(2*j) = r(j)
|
|
|
|
if (r(j) < group_bd(2*j-1)) group_bd(2*j-1) = r(j)
|
|
|
|
! if (r(j) < group_bd(2*j-1)) group_bd(2*j-1) = r(j)
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
dof = dof + size_ele(element_index(i))**3
|
|
|
|
! dof = dof + size_ele(element_index(i))**3
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
!If for some reason there are no dof in this loop then cycle out
|
|
|
|
! !If for some reason there are no dof in this loop then cycle out
|
|
|
|
if(dof == 0) cycle
|
|
|
|
! if(dof == 0) cycle
|
|
|
|
tot_dof = tot_dof+dof
|
|
|
|
! tot_dof = tot_dof+dof
|
|
|
|
|
|
|
|
!
|
|
|
|
group_in_lat = reshape((/ group_bd(1),group_bd(3),group_bd(5), &
|
|
|
|
! group_in_lat = reshape((/ group_bd(1),group_bd(3),group_bd(5), &
|
|
|
|
group_bd(2),group_bd(3),group_bd(5), &
|
|
|
|
! group_bd(2),group_bd(3),group_bd(5), &
|
|
|
|
group_bd(2),group_bd(4),group_bd(5), &
|
|
|
|
! group_bd(2),group_bd(4),group_bd(5), &
|
|
|
|
group_bd(1),group_bd(4),group_bd(5), &
|
|
|
|
! group_bd(1),group_bd(4),group_bd(5), &
|
|
|
|
group_bd(1),group_bd(3),group_bd(6), &
|
|
|
|
! group_bd(1),group_bd(3),group_bd(6), &
|
|
|
|
group_bd(2),group_bd(3),group_bd(6), &
|
|
|
|
! group_bd(2),group_bd(3),group_bd(6), &
|
|
|
|
group_bd(2),group_bd(4),group_bd(6), &
|
|
|
|
! group_bd(2),group_bd(4),group_bd(6), &
|
|
|
|
group_bd(1),group_bd(4),group_bd(6) /), [3,8])
|
|
|
|
! group_bd(1),group_bd(4),group_bd(6) /), [3,8])
|
|
|
|
|
|
|
|
!
|
|
|
|
group_in_lat = matmul(fcc_inv, matmul(ori_inv, group_in_lat/lapa(ilat)))
|
|
|
|
! group_in_lat = matmul(fcc_inv, matmul(ori_inv, group_in_lat/lapa(ilat)))
|
|
|
|
do i = 1, 3
|
|
|
|
! do i = 1, 3
|
|
|
|
bd_in_lat(2*i-1) = nint(minval(group_in_lat(i,:)))
|
|
|
|
! bd_in_lat(2*i-1) = nint(minval(group_in_lat(i,:)))
|
|
|
|
bd_in_lat(2*i) = nint(maxval(group_in_lat(i,:)))
|
|
|
|
! bd_in_lat(2*i) = nint(maxval(group_in_lat(i,:)))
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
allocate(lat_points(bd_in_lat(2)-bd_in_lat(1)+10, bd_in_lat(4)-bd_in_lat(3)+10, bd_in_lat(6)-bd_in_lat(5)+10))
|
|
|
|
! allocate(lat_points(bd_in_lat(2)-bd_in_lat(1)+10, bd_in_lat(4)-bd_in_lat(3)+10, bd_in_lat(6)-bd_in_lat(5)+10))
|
|
|
|
lat_points(:,:,:) = .false.
|
|
|
|
! lat_points(:,:,:) = .false.
|
|
|
|
dof = 0
|
|
|
|
! dof = 0
|
|
|
|
|
|
|
|
!
|
|
|
|
!Now place all group atoms and group interpolated atoms into lat_points
|
|
|
|
! !Now place all group atoms and group interpolated atoms into lat_points
|
|
|
|
do i = 1, group_atom_num
|
|
|
|
! do i = 1, group_atom_num
|
|
|
|
if (.not.((sbox_atom(atom_index(i)) == is).and.(basis_type(1,ilat) == type_atom(atom_index(i))))) cycle
|
|
|
|
! if (.not.((sbox_atom(atom_index(i)) == is).and.(basis_type(1,ilat) == type_atom(atom_index(i))))) cycle
|
|
|
|
r = r_atom(:,atom_index(i))/lapa(ilat)
|
|
|
|
! r = r_atom(:,atom_index(i))/lapa(ilat)
|
|
|
|
r = matmul(fcc_inv,matmul(ori_inv,r))
|
|
|
|
! r = matmul(fcc_inv,matmul(ori_inv,r))
|
|
|
|
do j = 1, 3
|
|
|
|
! do j = 1, 3
|
|
|
|
r_lat(j) = nint(r(j))
|
|
|
|
! r_lat(j) = nint(r(j))
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
!Do a check to make sure the code is working and that lattice points aren't being written on top of each other.
|
|
|
|
! !Do a check to make sure the code is working and that lattice points aren't being written on top of each other.
|
|
|
|
!This is primarily a debugging statement
|
|
|
|
! !This is primarily a debugging statement
|
|
|
|
if(lat_points(r_lat(1)-bd_in_lat(1)+5,r_lat(2)-bd_in_lat(3)+5,r_lat(3)-bd_in_lat(5)+5)) then
|
|
|
|
! if(lat_points(r_lat(1)-bd_in_lat(1)+5,r_lat(2)-bd_in_lat(3)+5,r_lat(3)-bd_in_lat(5)+5)) then
|
|
|
|
stop "Multiple atoms share same position in lat point array, this shouldn't happen"
|
|
|
|
! stop "Multiple atoms share same position in lat point array, this shouldn't happen"
|
|
|
|
else
|
|
|
|
! else
|
|
|
|
lat_points(r_lat(1)-bd_in_lat(1)+5, r_lat(2)-bd_in_lat(3)+5, r_lat(3)-bd_in_lat(5)+5) = .true.
|
|
|
|
! lat_points(r_lat(1)-bd_in_lat(1)+5, r_lat(2)-bd_in_lat(3)+5, r_lat(3)-bd_in_lat(5)+5) = .true.
|
|
|
|
dof = dof + 1
|
|
|
|
! dof = dof + 1
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
!Now place interpolated atoms within lat_points array
|
|
|
|
! !Now place interpolated atoms within lat_points array
|
|
|
|
do i =1, group_ele_num
|
|
|
|
! do i =1, group_ele_num
|
|
|
|
if (.not.((sbox_ele(element_index(i)) == is).and.( lat_ele(element_index(i)) == ilat))) cycle
|
|
|
|
! if (.not.((sbox_ele(element_index(i)) == is).and.( lat_ele(element_index(i)) == ilat))) cycle
|
|
|
|
ie = element_index(i)
|
|
|
|
! ie = element_index(i)
|
|
|
|
call interpolate_atoms(type_ele(ie), size_ele(ie), lat_ele(ie), r_node(:,:,:,ie), type_interp, r_interp)
|
|
|
|
! call interpolate_atoms(type_ele(ie), size_ele(ie), lat_ele(ie), r_node(:,:,:,ie), type_interp, r_interp)
|
|
|
|
do j = 1, size_ele(ie)**3 * basisnum(lat_ele(ie))
|
|
|
|
! do j = 1, size_ele(ie)**3 * basisnum(lat_ele(ie))
|
|
|
|
r = r_interp(:,j)/lapa(ilat)
|
|
|
|
! r = r_interp(:,j)/lapa(ilat)
|
|
|
|
r = matmul(fcc_inv,matmul(ori_inv,r))
|
|
|
|
! r = matmul(fcc_inv,matmul(ori_inv,r))
|
|
|
|
do k = 1, 3
|
|
|
|
! do k = 1, 3
|
|
|
|
r_lat(k) = nint(r(k))
|
|
|
|
! r_lat(k) = nint(r(k))
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
!Do a check to make sure the code is working and that lattice points aren't being written on top of each
|
|
|
|
! !Do a check to make sure the code is working and that lattice points aren't being written on top of each
|
|
|
|
!other. This is primarily a debugging statement
|
|
|
|
! !other. This is primarily a debugging statement
|
|
|
|
if(lat_points(r_lat(1)-bd_in_lat(1)+5,r_lat(2)-bd_in_lat(3)+5,r_lat(3)-bd_in_lat(5)+5)) then
|
|
|
|
! if(lat_points(r_lat(1)-bd_in_lat(1)+5,r_lat(2)-bd_in_lat(3)+5,r_lat(3)-bd_in_lat(5)+5)) then
|
|
|
|
stop "Multiple atoms/interpolated atoms share same position in lat point array, this shouldn't happen"
|
|
|
|
! stop "Multiple atoms/interpolated atoms share same position in lat point array, this shouldn't happen"
|
|
|
|
else
|
|
|
|
! else
|
|
|
|
lat_points(r_lat(1)-bd_in_lat(1)+5, r_lat(2)-bd_in_lat(3)+5, r_lat(3)-bd_in_lat(5)+5) = .true.
|
|
|
|
! lat_points(r_lat(1)-bd_in_lat(1)+5, r_lat(2)-bd_in_lat(3)+5, r_lat(3)-bd_in_lat(5)+5) = .true.
|
|
|
|
dof = dof + 1
|
|
|
|
! dof = dof + 1
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
!Now run remeshing algorithm, not the most optimized or efficient but gets the job done
|
|
|
|
! !Now run remeshing algorithm, not the most optimized or efficient but gets the job done
|
|
|
|
!Figure out new looping boundaries
|
|
|
|
! !Figure out new looping boundaries
|
|
|
|
bd_in_array(1) = bd_in_lat(2) - bd_in_lat(1) + 10
|
|
|
|
! bd_in_array(1) = bd_in_lat(2) - bd_in_lat(1) + 10
|
|
|
|
bd_in_array(2) = bd_in_lat(4) - bd_in_lat(3) + 10
|
|
|
|
! bd_in_array(2) = bd_in_lat(4) - bd_in_lat(3) + 10
|
|
|
|
bd_in_array(3) = bd_in_lat(6) - bd_in_lat(5) + 10
|
|
|
|
! bd_in_array(3) = bd_in_lat(6) - bd_in_lat(5) + 10
|
|
|
|
|
|
|
|
!
|
|
|
|
|
|
|
|
!
|
|
|
|
if (max_remesh) then
|
|
|
|
! if (max_remesh) then
|
|
|
|
max_loops = (remesh_size-3)/2
|
|
|
|
! max_loops = (remesh_size-3)/2
|
|
|
|
else
|
|
|
|
! else
|
|
|
|
max_loops = 1
|
|
|
|
! max_loops = 1
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
do j = 1, max_loops
|
|
|
|
! do j = 1, max_loops
|
|
|
|
working_esize = remesh_size - 2*(j-1)
|
|
|
|
! working_esize = remesh_size - 2*(j-1)
|
|
|
|
ele = (working_esize-1)*cubic_cell
|
|
|
|
! ele = (working_esize-1)*cubic_cell
|
|
|
|
zloop: do iz = 1, bd_in_array(3)
|
|
|
|
! zloop: do iz = 1, bd_in_array(3)
|
|
|
|
yloop: do iy = 1, bd_in_array(2)
|
|
|
|
! yloop: do iy = 1, bd_in_array(2)
|
|
|
|
xloop: do ix = 1, bd_in_array(1)
|
|
|
|
! xloop: do ix = 1, bd_in_array(1)
|
|
|
|
if (lat_points(ix, iy,iz)) then
|
|
|
|
! if (lat_points(ix, iy,iz)) then
|
|
|
|
r_new_node(:,:,:) = 0.0_dp
|
|
|
|
! r_new_node(:,:,:) = 0.0_dp
|
|
|
|
|
|
|
|
!
|
|
|
|
!Check to see if the element overshoots the bound
|
|
|
|
! !Check to see if the element overshoots the bound
|
|
|
|
if (iz+working_esize-1 > bd_in_array(3)) then
|
|
|
|
! if (iz+working_esize-1 > bd_in_array(3)) then
|
|
|
|
exit zloop
|
|
|
|
! exit zloop
|
|
|
|
else if (iy+working_esize-1 > bd_in_array(2)) then
|
|
|
|
! else if (iy+working_esize-1 > bd_in_array(2)) then
|
|
|
|
cycle zloop
|
|
|
|
! cycle zloop
|
|
|
|
else if (ix+working_esize-1 > bd_in_array(1)) then
|
|
|
|
! else if (ix+working_esize-1 > bd_in_array(1)) then
|
|
|
|
cycle yloop
|
|
|
|
! cycle yloop
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
|
|
|
|
!
|
|
|
|
if (all(lat_points(ix:ix+working_esize-1,iy:iy+working_esize-1,iz:iz+working_esize-1))) then
|
|
|
|
! if (all(lat_points(ix:ix+working_esize-1,iy:iy+working_esize-1,iz:iz+working_esize-1))) then
|
|
|
|
do inod = 1, ng_node(ilat)
|
|
|
|
! do inod = 1, ng_node(ilat)
|
|
|
|
vlat = ele(:,inod) + (/ix, iy, iz /)
|
|
|
|
! vlat = ele(:,inod) + (/ix, iy, iz /)
|
|
|
|
do i = 1, 3
|
|
|
|
! do i = 1, 3
|
|
|
|
vlat(i) = vlat(i) + bd_in_lat(2*i-1)-5
|
|
|
|
! vlat(i) = vlat(i) + bd_in_lat(2*i-1)-5
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
r_new_node(:,1,inod) = matmul(orient, matmul(fcc_mat, vlat))*lapa(ilat)
|
|
|
|
! r_new_node(:,1,inod) = matmul(orient, matmul(fcc_mat, vlat))*lapa(ilat)
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
lat_points(ix:ix+working_esize-1,iy:iy+working_esize-1,iz:iz+working_esize-1) = .false.
|
|
|
|
! lat_points(ix:ix+working_esize-1,iy:iy+working_esize-1,iz:iz+working_esize-1) = .false.
|
|
|
|
!Add the element, for the sbox we just set it to the same sbox that we get the orientation
|
|
|
|
! !Add the element, for the sbox we just set it to the same sbox that we get the orientation
|
|
|
|
!from. In this case it is from the sbox of the first atom in the group.
|
|
|
|
! !from. In this case it is from the sbox of the first atom in the group.
|
|
|
|
new_ele = new_ele+1
|
|
|
|
! new_ele = new_ele+1
|
|
|
|
call add_element(0,remesh_ele_type, working_esize, ilat, &
|
|
|
|
! call add_element(0,remesh_ele_type, working_esize, ilat, &
|
|
|
|
sbox_atom(atom_index(1)),r_new_node)
|
|
|
|
! sbox_atom(atom_index(1)),r_new_node)
|
|
|
|
|
|
|
|
!
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do xloop
|
|
|
|
! end do xloop
|
|
|
|
end do yloop
|
|
|
|
! end do yloop
|
|
|
|
end do zloop
|
|
|
|
! end do zloop
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
!Now we have to add any leftover lattice points as atoms
|
|
|
|
! !Now we have to add any leftover lattice points as atoms
|
|
|
|
do iz = 1, bd_in_array(3)
|
|
|
|
! do iz = 1, bd_in_array(3)
|
|
|
|
do iy=1, bd_in_array(2)
|
|
|
|
! do iy=1, bd_in_array(2)
|
|
|
|
do ix = 1, bd_in_array(1)
|
|
|
|
! do ix = 1, bd_in_array(1)
|
|
|
|
if(lat_points(ix,iy,iz)) then
|
|
|
|
! if(lat_points(ix,iy,iz)) then
|
|
|
|
vlat = (/ ix, iy, iz /)
|
|
|
|
! vlat = (/ ix, iy, iz /)
|
|
|
|
do i = 1, 3
|
|
|
|
! do i = 1, 3
|
|
|
|
vlat(i) = vlat(i) + bd_in_lat(2*i-1)-5
|
|
|
|
! vlat(i) = vlat(i) + bd_in_lat(2*i-1)-5
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
lat_points(ix,iy,iz) = .false.
|
|
|
|
! lat_points(ix,iy,iz) = .false.
|
|
|
|
r = matmul(orient, matmul(fcc_mat, vlat))*lapa(ilat)
|
|
|
|
! r = matmul(orient, matmul(fcc_mat, vlat))*lapa(ilat)
|
|
|
|
new_atom=new_atom+1
|
|
|
|
! new_atom=new_atom+1
|
|
|
|
call add_atom(0,basis_type(1,ilat), is, r)
|
|
|
|
! call add_atom(0,basis_type(1,ilat), is, r)
|
|
|
|
end if
|
|
|
|
! end if
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
deallocate(lat_points)
|
|
|
|
! deallocate(lat_points)
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
|
|
|
|
!
|
|
|
|
!Delete all elements and atoms to make space for new elements and atoms
|
|
|
|
! !Delete all elements and atoms to make space for new elements and atoms
|
|
|
|
call delete_atoms(group_atom_num, atom_index)
|
|
|
|
! call delete_atoms(group_atom_num, atom_index)
|
|
|
|
call delete_elements(group_ele_num, element_index)
|
|
|
|
! call delete_elements(group_ele_num, element_index)
|
|
|
|
|
|
|
|
!
|
|
|
|
print *, tot_dof, " degrees of freedom in group"
|
|
|
|
! print *, tot_dof, " degrees of freedom in group"
|
|
|
|
print *, "remesh_group creates ", new_atom, " atoms and ", new_ele, " elements."
|
|
|
|
! print *, "remesh_group creates ", new_atom, " atoms and ", new_ele, " elements."
|
|
|
|
end subroutine remesh_group
|
|
|
|
! end subroutine remesh_group
|
|
|
|
|
|
|
|
|
|
|
|
subroutine delete_group
|
|
|
|
subroutine delete_group
|
|
|
|
!This subroutine deletes all atoms/elements within a group
|
|
|
|
!This subroutine deletes all atoms/elements within a group
|
|
|
@ -1120,71 +1124,71 @@ module opt_group
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine change_group_type
|
|
|
|
end subroutine change_group_type
|
|
|
|
|
|
|
|
|
|
|
|
subroutine insert_group
|
|
|
|
! subroutine insert_group
|
|
|
|
!This code inserts atoms into interstitial sites. This only works on atoms within the group due to the limitations with the
|
|
|
|
! !This code inserts atoms into interstitial sites. This only works on atoms within the group due to the limitations with the
|
|
|
|
!Coarse-graining methodology which doesn't allow for concentration fluctuations.
|
|
|
|
! !Coarse-graining methodology which doesn't allow for concentration fluctuations.
|
|
|
|
real(kind=dp) interstitial_sites(3,14), rand, rinsert(3)
|
|
|
|
! real(kind=dp) interstitial_sites(3,14), rand, rinsert(3)
|
|
|
|
integer :: add_num, i, j, rindex, sindex, ia, rlo, rhi, sbox
|
|
|
|
! integer :: add_num, i, j, rindex, sindex, ia, rlo, rhi
|
|
|
|
integer, allocatable :: used_sites(:,:)
|
|
|
|
! integer, allocatable :: used_sites(:,:)
|
|
|
|
|
|
|
|
!
|
|
|
|
!First save all of the displacement vectors from a lattice site to interstitial site
|
|
|
|
! !First save all of the displacement vectors from a lattice site to interstitial site
|
|
|
|
!The first 6 are the octohedral sites and the next 8 are the tetrahedral sites
|
|
|
|
! !The first 6 are the octohedral sites and the next 8 are the tetrahedral sites
|
|
|
|
interstitial_sites= reshape( (/ -0.5_dp, 0.0_dp, 0.0_dp, &
|
|
|
|
! interstitial_sites= reshape( (/ -0.5_dp, 0.0_dp, 0.0_dp, &
|
|
|
|
0.5_dp, 0.0_dp, 0.0_dp, &
|
|
|
|
! 0.5_dp, 0.0_dp, 0.0_dp, &
|
|
|
|
0.0_dp,-0.5_dp, 0.0_dp, &
|
|
|
|
! 0.0_dp,-0.5_dp, 0.0_dp, &
|
|
|
|
0.0_dp, 0.5_dp, 0.0_dp, &
|
|
|
|
! 0.0_dp, 0.5_dp, 0.0_dp, &
|
|
|
|
0.0_dp, 0.0_dp,-0.5_dp, &
|
|
|
|
! 0.0_dp, 0.0_dp,-0.5_dp, &
|
|
|
|
0.0_dp, 0.0_dp, 0.5_dp, &
|
|
|
|
! 0.0_dp, 0.0_dp, 0.5_dp, &
|
|
|
|
-0.25_dp,-0.25_dp,-0.25_dp, &
|
|
|
|
! -0.25_dp,-0.25_dp,-0.25_dp, &
|
|
|
|
-0.25_dp,-0.25_dp, 0.25_dp, &
|
|
|
|
! -0.25_dp,-0.25_dp, 0.25_dp, &
|
|
|
|
-0.25_dp, 0.25_dp,-0.25_dp, &
|
|
|
|
! -0.25_dp, 0.25_dp,-0.25_dp, &
|
|
|
|
-0.25_dp, 0.25_dp, 0.25_dp, &
|
|
|
|
! -0.25_dp, 0.25_dp, 0.25_dp, &
|
|
|
|
0.25_dp,-0.25_dp,-0.25_dp, &
|
|
|
|
! 0.25_dp,-0.25_dp,-0.25_dp, &
|
|
|
|
0.25_dp,-0.25_dp, 0.25_dp, &
|
|
|
|
! 0.25_dp,-0.25_dp, 0.25_dp, &
|
|
|
|
0.25_dp, 0.25_dp,-0.25_dp, &
|
|
|
|
! 0.25_dp, 0.25_dp,-0.25_dp, &
|
|
|
|
0.25_dp, 0.25_dp, 0.25_dp /), &
|
|
|
|
! 0.25_dp, 0.25_dp, 0.25_dp /), &
|
|
|
|
shape(interstitial_sites))
|
|
|
|
! shape(interstitial_sites))
|
|
|
|
|
|
|
|
!
|
|
|
|
!First we calculate the number of atoms needed based on the number of atoms in the group and the concentration
|
|
|
|
! !First we calculate the number of atoms needed based on the number of atoms in the group and the concentration
|
|
|
|
interstitial_sites=interstitial_sites*insert_lattice
|
|
|
|
! interstitial_sites=interstitial_sites*insert_lattice
|
|
|
|
|
|
|
|
!
|
|
|
|
add_num = (insert_conc*group_atom_num)/(1-insert_conc)
|
|
|
|
! add_num = (insert_conc*group_atom_num)/(1-insert_conc)
|
|
|
|
allocate(used_sites(2,add_num))
|
|
|
|
! allocate(used_sites(2,add_num))
|
|
|
|
|
|
|
|
!
|
|
|
|
print *, "Inserting ", add_num, " atoms as atom type ", insert_type
|
|
|
|
! print *, "Inserting ", add_num, " atoms as atom type ", insert_type
|
|
|
|
|
|
|
|
!
|
|
|
|
!Now set up the random number generator for the desired interstitial type
|
|
|
|
! !Now set up the random number generator for the desired interstitial type
|
|
|
|
select case(insert_site)
|
|
|
|
! select case(insert_site)
|
|
|
|
case(1)
|
|
|
|
! case(1)
|
|
|
|
rlo=1
|
|
|
|
! rlo=1
|
|
|
|
rhi=6
|
|
|
|
! rhi=6
|
|
|
|
case(2)
|
|
|
|
! case(2)
|
|
|
|
rlo=7
|
|
|
|
! rlo=7
|
|
|
|
rhi = 14
|
|
|
|
! rhi = 14
|
|
|
|
case(3)
|
|
|
|
! case(3)
|
|
|
|
rlo=1
|
|
|
|
! rlo=1
|
|
|
|
rhi=14
|
|
|
|
! rhi=14
|
|
|
|
end select
|
|
|
|
! end select
|
|
|
|
|
|
|
|
!
|
|
|
|
!Now add the atoms
|
|
|
|
! !Now add the atoms
|
|
|
|
i = 1
|
|
|
|
! i = 1
|
|
|
|
addloop:do while ( i < add_num)
|
|
|
|
! addloop:do while ( i < add_num)
|
|
|
|
call random_number(rand)
|
|
|
|
! call random_number(rand)
|
|
|
|
rindex = int(1+rand*(group_atom_num-1))
|
|
|
|
! rindex = int(1+rand*(group_atom_num-1))
|
|
|
|
ia=atom_index(rindex)
|
|
|
|
! ia=atom_index(rindex)
|
|
|
|
call random_number(rand)
|
|
|
|
! call random_number(rand)
|
|
|
|
sindex = int(rlo+rand*(rhi-rlo))
|
|
|
|
! sindex = int(rlo+rand*(rhi-rlo))
|
|
|
|
do j = 1, i
|
|
|
|
! do j = 1, i
|
|
|
|
if((ia == used_sites(1,i)).and.(sindex == used_sites(2,i))) cycle addloop
|
|
|
|
! if((ia == used_sites(1,i)).and.(sindex == used_sites(2,i))) cycle addloop
|
|
|
|
end do
|
|
|
|
! end do
|
|
|
|
rinsert = r_atom(:,ia) + matmul(sub_box_ori(:,:,sbox_atom(ia)),interstitial_sites(:,sindex))
|
|
|
|
! rinsert = r_atom(:,ia) + matmul(sub_box_ori(:,:,sbox_atom(ia)),interstitial_sites(:,sindex))
|
|
|
|
sbox = sbox_atom(ia)
|
|
|
|
! sbox = sbox_atom(ia)
|
|
|
|
call add_atom(0, insert_type, sbox, rinsert)
|
|
|
|
! call add_atom(0, insert_type, sbox, rinsert)
|
|
|
|
used_sites(1,i) = ia
|
|
|
|
! used_sites(1,i) = ia
|
|
|
|
used_sites(2,i) = sindex
|
|
|
|
! used_sites(2,i) = sindex
|
|
|
|
i = i + 1
|
|
|
|
! i = i + 1
|
|
|
|
end do addloop
|
|
|
|
! end do addloop
|
|
|
|
end subroutine insert_group
|
|
|
|
! end subroutine insert_group
|
|
|
|
|
|
|
|
|
|
|
|
subroutine alloy_group
|
|
|
|
subroutine alloy_group
|
|
|
|
!This subroutine randomizes the atom types to reach desired concentrations, this only operates on atoms
|
|
|
|
!This subroutine randomizes the atom types to reach desired concentrations, this only operates on atoms
|
|
|
|