Added tags to the element and atom arrays
This commit is contained in:
parent
de15d0f8ae
commit
a47c384a3f
5 changed files with 54 additions and 26 deletions
|
@ -11,7 +11,7 @@ module elements
|
|||
|
||||
!Data structures used to represent the CAC elements. Each index represents an element
|
||||
character(len=100), allocatable :: type_ele(:) !Element type
|
||||
integer, allocatable :: size_ele(:), lat_ele(:), sbox_ele(:) !Element size
|
||||
integer, allocatable :: size_ele(:), lat_ele(:), sbox_ele(:), tag_ele(:) !Element size
|
||||
real(kind=dp), allocatable :: r_node(:,:,:,:) !Nodal position array
|
||||
|
||||
integer, save :: ele_num !Number of elements
|
||||
|
@ -19,7 +19,7 @@ module elements
|
|||
|
||||
!Data structure used to represent atoms
|
||||
integer, allocatable :: type_atom(:)!atom type
|
||||
integer, allocatable :: sbox_atom(:)
|
||||
integer, allocatable :: sbox_atom(:), tag_atom(:)
|
||||
real(kind =dp),allocatable :: r_atom(:,:) !atom position
|
||||
integer :: atom_num=0 !Number of atoms
|
||||
|
||||
|
@ -146,7 +146,7 @@ module elements
|
|||
|
||||
!Allocate element arrays
|
||||
if(n > 0) then
|
||||
allocate(type_ele(n), size_ele(n), lat_ele(n), sbox_ele(n), r_node(3,max_basisnum, max_ng_node,n), &
|
||||
allocate(type_ele(n), tag_ele(n), size_ele(n), lat_ele(n), sbox_ele(n), r_node(3,max_basisnum, max_ng_node,n), &
|
||||
stat=allostat)
|
||||
if(allostat > 0) then
|
||||
print *, "Error allocating element arrays in elements.f90 because of: ", allostat
|
||||
|
@ -156,7 +156,7 @@ module elements
|
|||
|
||||
if(m > 0) then
|
||||
!Allocate atom arrays
|
||||
allocate(type_atom(m), sbox_atom(m), r_atom(3,m), stat=allostat)
|
||||
allocate(type_atom(m), sbox_atom(m), tag_atom(m), r_atom(3,m), stat=allostat)
|
||||
if(allostat > 0) then
|
||||
print *, "Error allocating atom arrays in elements.f90 because of: ", allostat
|
||||
stop
|
||||
|
@ -187,6 +187,11 @@ module elements
|
|||
temp_int(ele_size+1:) = 0
|
||||
call move_alloc(temp_int, lat_ele)
|
||||
|
||||
allocate(temp_int(n+ele_num+buffer_size))
|
||||
temp_int(1:ele_size) = tag_ele
|
||||
temp_int(ele_size+1:) = 0
|
||||
call move_alloc(temp_int, tag_ele)
|
||||
|
||||
allocate(temp_int(n+ele_num+buffer_size))
|
||||
temp_int(1:ele_size) = size_ele
|
||||
temp_int(ele_size+1:) = 0
|
||||
|
@ -214,6 +219,11 @@ module elements
|
|||
temp_int(atom_size+1:) = 0
|
||||
call move_alloc(temp_int, type_atom)
|
||||
|
||||
allocate(temp_int(m+atom_num+buffer_size))
|
||||
temp_int(1:atom_size) = tag_atom
|
||||
temp_int(atom_size+1:) = 0
|
||||
call move_alloc(temp_int, tag_atom)
|
||||
|
||||
allocate(temp_int(m+atom_num+buffer_size))
|
||||
temp_int(1:atom_size) = sbox_atom
|
||||
temp_int(atom_size+1:) = 0
|
||||
|
@ -226,15 +236,25 @@ module elements
|
|||
end if
|
||||
end subroutine
|
||||
|
||||
subroutine add_element(type, size, lat, sbox, r)
|
||||
subroutine add_element(tag, type, size, lat, sbox, r)
|
||||
!Subroutine which adds an element to the element arrays
|
||||
integer, intent(in) :: size, lat, sbox
|
||||
integer, intent(in) :: size, lat, sbox, tag
|
||||
character(len=100), intent(in) :: type
|
||||
real(kind=dp), intent(in) :: r(3, max_basisnum, max_ng_node)
|
||||
|
||||
integer :: newtag
|
||||
|
||||
ele_num = ele_num + 1
|
||||
|
||||
if (tag==0) then
|
||||
newtag = ele_num !If we don't assign a tag then pass the tag as the ele_num
|
||||
else
|
||||
newtag = tag
|
||||
end if
|
||||
|
||||
!Check to see if we need to grow the arrays
|
||||
call grow_ele_arrays(1,0)
|
||||
tag_ele(ele_num) = newtag
|
||||
type_ele(ele_num) = type
|
||||
size_ele(ele_num) = size
|
||||
lat_ele(ele_num) = lat
|
||||
|
@ -245,14 +265,22 @@ module elements
|
|||
|
||||
end subroutine add_element
|
||||
|
||||
subroutine add_atom(type, sbox, r)
|
||||
subroutine add_atom(tag, type, sbox, r)
|
||||
!Subroutine which adds an atom to the atom arrays
|
||||
integer, intent(in) :: type, sbox
|
||||
integer, intent(in) :: type, sbox, tag
|
||||
real(kind=dp), intent(in), dimension(3) :: r
|
||||
|
||||
integer :: newtag
|
||||
|
||||
atom_num = atom_num+1
|
||||
if(tag==0) then
|
||||
newtag = atom_num !If we don't assign a tag then pass the tag as the atom_num
|
||||
else
|
||||
newtag = tag
|
||||
end if
|
||||
!Check to see if we need to grow the arrays
|
||||
call grow_ele_arrays(0,1)
|
||||
tag_atom(atom_num) = tag
|
||||
type_atom(atom_num) = type
|
||||
r_atom(:,atom_num) = r(:)
|
||||
sbox_atom(atom_num) = sbox
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue