Changes to how the adjustment to nodal positions is performed for lammpscac output
This commit is contained in:
parent
55fbe679e5
commit
849da1d24a
4 changed files with 69 additions and 54 deletions
|
@ -9,7 +9,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(:) !Element siz
|
||||
integer, allocatable :: size_ele(:), lat_ele(:), sbox_ele(:) !Element size
|
||||
real(kind=dp), allocatable :: r_node(:,:,:,:) !Nodal position array
|
||||
|
||||
integer, save :: ele_num !Number of elements
|
||||
|
@ -39,6 +39,7 @@ module elements
|
|||
!This can be easily increased with no change to efficiency
|
||||
integer :: max_basisnum, basisnum(10) !Max basis atom number, number of basis atoms in each lattice type
|
||||
integer :: basis_type(10,10)
|
||||
real(kind=dp) :: lapa(10)
|
||||
|
||||
public
|
||||
contains
|
||||
|
@ -140,7 +141,7 @@ module elements
|
|||
|
||||
!Allocate element arrays
|
||||
if(n > 0) then
|
||||
allocate(type_ele(n), size_ele(n), lat_ele(n), r_node(3,max_basisnum, max_ng_node,n), &
|
||||
allocate(type_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
|
||||
|
@ -179,12 +180,17 @@ module elements
|
|||
allocate(temp_int(n+ele_num+buffer_size))
|
||||
temp_int(1:ele_size) = lat_ele
|
||||
temp_int(ele_size+1:) = 0
|
||||
call move_alloc(temp_int(1:ele_size), lat_ele)
|
||||
call move_alloc(temp_int, lat_ele)
|
||||
|
||||
allocate(temp_int(n+ele_num+buffer_size))
|
||||
temp_int(1:ele_size) = size_ele
|
||||
temp_int(ele_size+1:) = 0
|
||||
call move_alloc(temp_int(1:ele_size), size_ele)
|
||||
call move_alloc(temp_int, size_ele)
|
||||
|
||||
allocate(temp_int(n+ele_num+buffer_size))
|
||||
temp_int(1:ele_size) = lat_ele
|
||||
temp_int(ele_size+1:) = 0
|
||||
call move_alloc(temp_int, sbox_ele)
|
||||
|
||||
allocate(char_temp(n+ele_num+buffer_size))
|
||||
char_temp(1:ele_size) = type_ele
|
||||
|
@ -210,9 +216,9 @@ module elements
|
|||
end if
|
||||
end subroutine
|
||||
|
||||
subroutine add_element(type, size, lat, r)
|
||||
subroutine add_element(type, size, lat, sbox, r)
|
||||
!Subroutine which adds an element to the element arrays
|
||||
integer, intent(in) :: size, lat
|
||||
integer, intent(in) :: size, lat, sbox
|
||||
character(len=100), intent(in) :: type
|
||||
real(kind=dp), intent(in) :: r(3, max_basisnum, max_ng_node)
|
||||
|
||||
|
@ -220,6 +226,7 @@ module elements
|
|||
type_ele(ele_num) = type
|
||||
size_ele(ele_num) = size
|
||||
lat_ele(ele_num) = lat
|
||||
sbox_ele(ele_num) = sbox
|
||||
r_node(:,:,:,ele_num) = r(:,:,:)
|
||||
node_num = node_num + ng_node(lat)
|
||||
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue