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
20
src/io.f90
20
src/io.f90
|
@ -543,13 +543,13 @@ module io
|
|||
|
||||
!Write out atoms first
|
||||
do i = 1, atom_num
|
||||
write(11,*) i, type_atom(i), sbox_atom(i), r_atom(:,i)
|
||||
write(11,*) tag_atom(i), type_atom(i), sbox_atom(i), r_atom(:,i)
|
||||
end do
|
||||
|
||||
!Write out the elements, this is written in two stages, one line for the element and then 1 line for
|
||||
!every basis at every node
|
||||
do i = 1, ele_num
|
||||
write(11, *) i, lat_ele(i), size_ele(i), sbox_ele(i), type_ele(i)
|
||||
write(11, *) tag_ele(i), lat_ele(i), size_ele(i), sbox_ele(i), type_ele(i)
|
||||
do inod = 1, ng_node(lat_ele(i))
|
||||
do ibasis =1, basisnum(lat_ele(i))
|
||||
write(11,*) inod, ibasis, r_node(:, ibasis, inod, i)
|
||||
|
@ -738,19 +738,19 @@ module io
|
|||
do i = 1, in_atoms
|
||||
read(11,*) j, type, sbox, r(:)
|
||||
r = r+newdisplace
|
||||
call add_atom(new_type_to_type(type), sbox+sub_box_num, r)
|
||||
call add_atom(j, new_type_to_type(type), sbox+sub_box_num, r)
|
||||
end do
|
||||
|
||||
!Read the elements
|
||||
do i = 1, in_eles
|
||||
read(11, *) l, type, size, sbox, etype
|
||||
read(11, *) j, type, size, sbox, etype
|
||||
do inod = 1, ng_node(type)
|
||||
do ibasis =1, basisnum(type)
|
||||
read(11,*) j, k, r_innode(:, ibasis, inod)
|
||||
read(11,*) k, l, r_innode(:, ibasis, inod)
|
||||
r_innode(:,ibasis,inod) = r_innode(:, ibasis, inod) + newdisplace
|
||||
end do
|
||||
end do
|
||||
call add_element(etype, size, new_lattice_map(type), sbox+sub_box_num, r_innode)
|
||||
call add_element(j, etype, size, new_lattice_map(type), sbox+sub_box_num, r_innode)
|
||||
end do
|
||||
|
||||
!Close the file being read
|
||||
|
@ -773,7 +773,7 @@ module io
|
|||
real(kind=dp), dimension(3), intent(in) :: displace
|
||||
real(kind = dp), dimension(6), intent(out) :: temp_box_bd
|
||||
|
||||
integer :: i, inod, ibasis, j, k, in_eles, in_atoms, ele_types, in_lat_num, in_atom_types, &
|
||||
integer :: i, inod, ibasis, j, k, l, in_eles, in_atoms, ele_types, in_lat_num, in_atom_types, &
|
||||
atom_type_map(100), etype_map(100), etype, lat_type, new_lattice_map(100), &
|
||||
atom_type
|
||||
real(kind=dp) :: newdisplace(3), r_in(3,1,8), r_in_atom(3), new_displace(3)
|
||||
|
@ -919,10 +919,10 @@ module io
|
|||
do i = 1, in_eles
|
||||
read(11,*) j, etype, k, lat_type
|
||||
do inod = 1, 8
|
||||
read(11, *) j, k, r_in(:,1,inod)
|
||||
read(11, *) k, l, r_in(:,1,inod)
|
||||
r_in(:,1,inod) = r_in(:,1,inod) + newdisplace
|
||||
end do
|
||||
call add_element(in_lattype_map(lat_type), etype_map(etype), new_lattice_map(lat_type), sub_box_num + 1, r_in)
|
||||
call add_element(j, in_lattype_map(lat_type), etype_map(etype), new_lattice_map(lat_type), sub_box_num + 1, r_in)
|
||||
end do
|
||||
end if
|
||||
|
||||
|
@ -937,7 +937,7 @@ module io
|
|||
do i = 1, in_atoms
|
||||
read(11,*) j, k, atom_type, r_in_atom(:)
|
||||
r_in_atom = r_in_atom + newdisplace
|
||||
call add_atom(atom_type_map(atom_type), sub_box_num + 1, r_in_atom)
|
||||
call add_atom(j,atom_type_map(atom_type), sub_box_num + 1, r_in_atom)
|
||||
end do
|
||||
!Close file
|
||||
close(11)
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue