Removed extra variables from mode_create.f90, added a new module to contain simulation box information and changed code accordingly, new grow subroutine in elements.

This commit is contained in:
Alex Selimov 2019-12-05 11:03:18 -05:00
parent fa1cb6ce58
commit 03f69c6df7
4 changed files with 113 additions and 10 deletions

View file

@ -7,7 +7,6 @@ module elements
implicit none
!Data structures used to represent the CAC elements. Each index represents an element
integer,allocatable :: tag_ele(:) !Element tag (used to keep track of id's
character(len=100), allocatable :: type_ele(:) !Element type
integer, allocatable :: size_ele(:), lat_ele(:) !Element siz
real(kind=dp), allocatable :: r_node(:,:,:,:) !Nodal position array
@ -16,7 +15,7 @@ module elements
integer :: node_num=0 !Total number of nodes
!Data structure used to represent atoms
integer, allocatable :: tag_atom(:), type_atom(:)!atom id
integer, allocatable :: type_atom(:)!atom type
real(kind =dp),allocatable :: r_atom(:,:) !atom position
integer :: atom_num=0 !Number of atoms
@ -119,7 +118,7 @@ module elements
!Allocate element arrays
if(n > 0) then
allocate(tag_ele(n), 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), 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
@ -129,7 +128,7 @@ module elements
if(m > 0) then
!Allocate atom arrays
allocate(tag_atom(m), type_atom(m), r_atom(3,m), stat=allostat)
allocate(type_atom(m), r_atom(3,m), stat=allostat)
if(allostat > 0) then
print *, "Error allocating atom arrays in elements.f90 because of: ", allostat
stop
@ -137,6 +136,58 @@ module elements
end if
end subroutine
subroutine grow_ele_arrays(n, m)
integer, intent(in) :: n, m
integer :: ele_size, atom_size, buffer_size
integer, allocatable :: temp_int(:)
real(kind=dp), allocatable :: temp_ele_real(:,:,:,:), temp_real(:,:)
character(len=100), allocatable :: char_temp(:)
!The default size we grow the
buffer_size = 1024
!Figure out the size of the atom and element arrays
ele_size = size(size_ele)
atom_size = size(type_atom)
!Check if we need to grow the ele_size, if so grow all the variables
if ( n > size(size_ele)) then
allocate(temp_int(n+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)
allocate(temp_int(n+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)
allocate(char_temp(n+buffer_size))
char_temp(1:ele_size) = type_ele
call move_alloc(char_temp, type_ele)
allocate(temp_ele_real(3, max_basisnum, max_ng_node, n+buffer_size))
temp_ele_real(:,:,:,1:ele_size) = r_node
temp_ele_real(:,:,:,ele_size+1:) = 0.0_dp
call move_alloc(temp_ele_real, r_node)
end if
!Now grow atom arrays if needed
if (m > atom_size) then
allocate(temp_int(m+buffer_size))
temp_int(1:atom_size) = type_atom
temp_int(atom_size+1:) = 0
call move_alloc(temp_int, type_atom)
allocate(temp_real(3,m+buffer_size))
temp_real(:,1:atom_size) = r_atom
temp_real(:, atom_size+1:) = 0.0_dp
call move_alloc(temp_real, r_atom)
end if
end subroutine
subroutine add_element(type, size, lat, r)
!Subroutine which adds an element to the element arrays
integer, intent(in) :: size, lat
@ -144,7 +195,6 @@ module elements
real(kind=dp), intent(in) :: r(3, max_basisnum, max_ng_node)
ele_num = ele_num + 1
tag_ele(ele_num) = ele_num
type_ele(ele_num) = type
size_ele(ele_num) = size
lat_ele(ele_num) = lat
@ -160,7 +210,6 @@ module elements
real(kind=dp), intent(in), dimension(3) :: r
atom_num = atom_num+1
tag_atom(atom_num) = atom_num
type_atom(atom_num) = type
r_atom(:,atom_num) = r(:)