Added remesh option to group

This commit is contained in:
Alex Selimov 2020-01-28 09:36:00 -05:00
parent 94e1c9fd7b
commit fd143783ec
2 changed files with 83 additions and 2 deletions

View file

@ -223,6 +223,8 @@ module elements
real(kind=dp), intent(in) :: r(3, max_basisnum, max_ng_node)
ele_num = ele_num + 1
!Check to see if we need to grow the arrays
call grow_ele_arrays(1,0)
type_ele(ele_num) = type
size_ele(ele_num) = size
lat_ele(ele_num) = lat
@ -239,6 +241,8 @@ module elements
real(kind=dp), intent(in), dimension(3) :: r
atom_num = atom_num+1
!Check to see if we need to grow the arrays
call grow_ele_arrays(0,1)
type_atom(atom_num) = type
r_atom(:,atom_num) = r(:)
@ -356,7 +360,7 @@ module elements
end do
end select
if (ia /= esize**3) then
if (ia /= bnum*esize**3) then
print *, "Incorrect interpolation"
stop 3
end if
@ -403,4 +407,34 @@ module elements
atom_num = atom_num - 1
end do
end subroutine
subroutine delete_elements(num, index)
!This subroutine deletes elements from the element array
integer, intent(in) :: num
integer, intent(inout), dimension(num) :: index
integer :: i, j
call heapsort(index)
!We go from largest index to smallest index just to make sure that we don't miss
!accidentally overwrite values which need to be deleted
do i = num, 1, -1
if(index(i) == ele_num) then
r_node(:,:,:,index(i)) = 0.0_dp
type_ele(index(i)) =''
size_ele(index(i)) = 0
lat_ele(index(i)) = 0
sbox_ele(index(i)) = 0
else
node_num = node_num - ng_node(lat_ele(index(i)))
r_node(:,:,:,index(i)) = r_node(:,:,:,ele_num)
type_ele(index(i)) = type_ele(ele_num)
size_ele(index(i)) = size_ele(ele_num)
lat_ele(index(i)) = lat_ele(ele_num)
sbox_ele(index(i)) = sbox_ele(ele_num)
end if
ele_num = ele_num - 1
end do
end subroutine delete_elements
end module elements