Manual merge of control box code
This commit is contained in:
commit
4dcaddb2cb
16 changed files with 773 additions and 101 deletions
|
@ -13,6 +13,8 @@ module elements
|
|||
character(len=100), allocatable :: type_ele(:) !Element type
|
||||
integer, allocatable :: size_ele(:), lat_ele(:), sbox_ele(:), tag_ele(:) !Element size
|
||||
real(kind=dp), allocatable :: r_node(:,:,:,:) !Nodal position array
|
||||
!Element result data structures
|
||||
real(kind=8), allocatable :: force_node(:,:,:,:), virial_node(:,:,:,:), energy_node(:,:,:)
|
||||
|
||||
integer, save :: ele_num !Number of elements
|
||||
integer, save :: node_num !Total number of nodes
|
||||
|
@ -22,6 +24,8 @@ module elements
|
|||
integer, allocatable :: sbox_atom(:), tag_atom(:)
|
||||
real(kind =dp),allocatable :: r_atom(:,:) !atom position
|
||||
integer :: atom_num=0 !Number of atoms
|
||||
!Atom result data structures information
|
||||
real(kind=8), allocatable :: force_atom(:,:), virial_atom(:,:), energy_atom(:)
|
||||
|
||||
!Mapping atom type to provided name
|
||||
character(len=2), dimension(10) :: type_to_name
|
||||
|
@ -512,6 +516,7 @@ module elements
|
|||
!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
|
||||
node_num = node_num - ng_node(lat_ele(sorted_index(i)))
|
||||
if(sorted_index(i) == ele_num) then
|
||||
r_node(:,:,:,sorted_index(i)) = 0.0_dp
|
||||
type_ele(sorted_index(i)) =''
|
||||
|
@ -520,7 +525,6 @@ module elements
|
|||
sbox_ele(sorted_index(i)) = 0
|
||||
tag_ele(sorted_index(i)) = 0
|
||||
else
|
||||
node_num = node_num - ng_node(lat_ele(sorted_index(i)))
|
||||
r_node(:,:,:,sorted_index(i)) = r_node(:,:,:,ele_num)
|
||||
type_ele(sorted_index(i)) = type_ele(ele_num)
|
||||
size_ele(sorted_index(i)) = size_ele(ele_num)
|
||||
|
@ -549,8 +553,7 @@ module elements
|
|||
|
||||
max_bd(:) = -huge(1.0_dp)
|
||||
min_bd(:) = huge(1.0_dp)
|
||||
|
||||
do i = 1, atom_num
|
||||
do i = 1, atom_num
|
||||
do j = 1, 3
|
||||
if (r_atom(j,i) > max_bd(j)) max_bd(j) = r_atom(j,i) + tol
|
||||
if (r_atom(j,i) < min_bd(j)) min_bd(j) = r_atom(j,i) - tol
|
||||
|
@ -775,4 +778,71 @@ module elements
|
|||
|
||||
end subroutine
|
||||
|
||||
subroutine alloc_dat_arrays(n,m)
|
||||
!This subroutine used to provide initial allocation for the atom and element data arrays
|
||||
integer, intent(in) :: n,m !n-size of element arrays, m-size of atom arrays
|
||||
integer :: allostat
|
||||
|
||||
!Allocate element arrays
|
||||
if (n > 0) then
|
||||
if (allocated(force_node)) then
|
||||
deallocate(force_node, virial_node, energy_node)
|
||||
end if
|
||||
allocate(force_node(3,max_basisnum, max_ng_node, n), &
|
||||
virial_node(6,max_basisnum, max_ng_node, n), &
|
||||
energy_node(max_basisnum,max_ng_node,n), &
|
||||
stat=allostat)
|
||||
if(allostat > 0) then
|
||||
print *, "Error allocating element data arrays in mode_metric because of:", allostat
|
||||
stop
|
||||
end if
|
||||
|
||||
end if
|
||||
|
||||
if (m > 0) then
|
||||
if (allocated(force_atom)) then
|
||||
deallocate(force_atom, virial_atom, energy_atom)
|
||||
end if
|
||||
allocate(force_atom(3, m), &
|
||||
virial_atom(6, m), &
|
||||
energy_atom(m), &
|
||||
stat=allostat)
|
||||
if(allostat > 0) then
|
||||
print *, "Error allocating atom data arrays in mode_metric because of:", allostat
|
||||
stop
|
||||
end if
|
||||
end if
|
||||
|
||||
end subroutine
|
||||
|
||||
subroutine add_atom_data(ia, eng, force, virial)
|
||||
!Function which sets the atom data arrays
|
||||
integer, intent(in) :: ia
|
||||
real(kind=dp), intent(in) :: eng, force(3), virial(6)
|
||||
|
||||
energy_atom(ia) = eng
|
||||
force_atom(:,ia) = force(:)
|
||||
virial_atom(:,ia) = virial(:)
|
||||
return
|
||||
end subroutine add_atom_data
|
||||
|
||||
subroutine add_element_data(ie, eng, force, virial)
|
||||
!Function which sets the element data arrays
|
||||
integer, intent(in) :: ie
|
||||
real(kind=dp), intent(in) :: eng(max_basisnum, max_ng_node), &
|
||||
force(3,max_basisnum, max_ng_node), &
|
||||
virial(6,max_basisnum,max_ng_node)
|
||||
energy_node(:,:,ie) = eng
|
||||
force_node(:,:,:,ie) = force
|
||||
virial_node(:,:,:,ie) = virial
|
||||
return
|
||||
end subroutine add_element_data
|
||||
|
||||
subroutine reset_data
|
||||
!This function resets all of the data arrays for the elements and atoms
|
||||
atom_num = 0
|
||||
ele_num = 0
|
||||
node_num = 0
|
||||
end subroutine reset_data
|
||||
|
||||
end module elements
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue