Fixes to file reading to ensure that mode_merge works correctly
This commit is contained in:
parent
95060bc0d9
commit
b0941e4482
3 changed files with 68 additions and 30 deletions
28
src/io.f90
28
src/io.f90
|
@ -394,10 +394,12 @@ module io
|
|||
real(kind=dp), dimension(3), intent(in) :: displace
|
||||
real(kind = dp), dimension(6), intent(out) :: temp_box_bd
|
||||
|
||||
integer :: i, j, k, n, inod, ibasis, type, size, in_atoms, in_eles
|
||||
integer :: i, j, k, n, inod, ibasis, type, size, in_atoms, in_eles, new_atom_types, &
|
||||
new_type_to_type(10), new_lattice_types
|
||||
character(len=100) :: etype
|
||||
real(kind=dp) :: r(3), newdisplace(3)
|
||||
real(kind=dp), allocatable :: r_innode(:,:,:)
|
||||
character(len = 2) :: new_type_to_name(10)
|
||||
!First open the file
|
||||
open(unit=11, file=trim(adjustl(file)), action='read',position='rewind')
|
||||
|
||||
|
@ -433,15 +435,26 @@ module io
|
|||
sub_box_num = sub_box_num + n
|
||||
|
||||
!Read in the number of atom types and all their names
|
||||
read(11, *) atom_types, (type_to_name(i), i = 1, atom_types)
|
||||
read(11, *) new_atom_types, (new_type_to_name(i), i = 1, new_atom_types)
|
||||
!Now fit these into the global list of atom types, after this new_type_to_type is the actual global
|
||||
!type of the atoms within this file
|
||||
do i = 1, new_atom_types
|
||||
call add_atom_type(new_type_to_name(i), new_type_to_type(i))
|
||||
end do
|
||||
!Read the number of lattice types, basisnum, and number of nodes for each lattice type
|
||||
read(11,*) lattice_types, (basisnum(i), i = 1, lattice_types), (ng_node(i), i = 1, lattice_types)
|
||||
read(11,*) new_lattice_types, (basisnum(i), i = lattice_types+1, lattice_types+new_lattice_types), &
|
||||
(ng_node(i), i = lattice_types+1, lattice_types+new_lattice_types)
|
||||
!Define max_ng_node and max_basis_num
|
||||
max_basisnum = maxval(basisnum)
|
||||
max_ng_node = maxval(ng_node)
|
||||
!Read the basis atom types for every lattice
|
||||
read(11,*) ((basis_type(i,j), i = 1, basisnum(j)), j = 1, lattice_types)
|
||||
|
||||
read(11,*) ((basis_type(i,j), i = 1, basisnum(j)), j = lattice_types+1, lattice_types+new_lattice_types)
|
||||
!Convert the basis_atom types
|
||||
do j = lattice_types+1, lattice_types+new_lattice_types
|
||||
do i = 1, basisnum(j)
|
||||
basis_type(i,j) = new_type_to_type(basis_type(i,j))
|
||||
end do
|
||||
end do
|
||||
!Read number of elements and atoms and allocate arrays
|
||||
read(11, *) in_atoms, in_eles
|
||||
call grow_ele_arrays(in_eles, in_atoms)
|
||||
|
@ -450,7 +463,7 @@ module io
|
|||
!Read the atoms
|
||||
do i = 1, in_atoms
|
||||
read(11,*) j, type, r(:)
|
||||
call add_atom(type, r+newdisplace)
|
||||
call add_atom(new_type_to_type(type), r+newdisplace)
|
||||
end do
|
||||
|
||||
!Read the elements
|
||||
|
@ -462,11 +475,12 @@ module io
|
|||
r_innode(:,ibasis,inod) = r_innode(:, ibasis, inod) + newdisplace
|
||||
end do
|
||||
end do
|
||||
|
||||
type = type + lattice_types
|
||||
call add_element(etype, size, type, r_innode)
|
||||
end do
|
||||
|
||||
!Close the file being read
|
||||
close(11)
|
||||
lattice_types = lattice_types + new_lattice_types
|
||||
end subroutine read_mb
|
||||
end module io
|
Loading…
Add table
Add a link
Reference in a new issue