|
|
@ -520,6 +520,8 @@ module io
|
|
|
|
12 format('coarse-grained domain')
|
|
|
|
12 format('coarse-grained domain')
|
|
|
|
13 format('ie basis_num ng_node esize'/ 'ip ibasis type x y z')
|
|
|
|
13 format('ie basis_num ng_node esize'/ 'ip ibasis type x y z')
|
|
|
|
14 format('atomistic domain' / 'ia type_atom x y z')
|
|
|
|
14 format('atomistic domain' / 'ia type_atom x y z')
|
|
|
|
|
|
|
|
15 format('ie basis_num ng_node esize'/ 'ip ibasis type x y z velx vely velz')
|
|
|
|
|
|
|
|
16 format('atomistic domain' / 'ia type_atom x y z velx vely velz')
|
|
|
|
19 format('max nodes per element and basis per nodes' / 2i16)
|
|
|
|
19 format('max nodes per element and basis per nodes' / 2i16)
|
|
|
|
20 format('max interpo per element' / i16)
|
|
|
|
20 format('max interpo per element' / i16)
|
|
|
|
21 format('atom types to elements')
|
|
|
|
21 format('atom types to elements')
|
|
|
@ -562,7 +564,11 @@ module io
|
|
|
|
if(ele_num > 0) then
|
|
|
|
if(ele_num > 0) then
|
|
|
|
write(11,12)
|
|
|
|
write(11,12)
|
|
|
|
ip = 0
|
|
|
|
ip = 0
|
|
|
|
|
|
|
|
if(allocated(vel_node)) then
|
|
|
|
|
|
|
|
write(11,15)
|
|
|
|
|
|
|
|
else
|
|
|
|
write(11,13)
|
|
|
|
write(11,13)
|
|
|
|
|
|
|
|
end if
|
|
|
|
do i = 1, ele_num
|
|
|
|
do i = 1, ele_num
|
|
|
|
select case(type_ele(i))
|
|
|
|
select case(type_ele(i))
|
|
|
|
case('fcc','bcc')
|
|
|
|
case('fcc','bcc')
|
|
|
@ -570,22 +576,39 @@ module io
|
|
|
|
case('20fcc')
|
|
|
|
case('20fcc')
|
|
|
|
write(11, '(4i16)') i, basisnum(lat_ele(i)), 3, (size_ele(i)-1)
|
|
|
|
write(11, '(4i16)') i, basisnum(lat_ele(i)), 3, (size_ele(i)-1)
|
|
|
|
end select
|
|
|
|
end select
|
|
|
|
|
|
|
|
if(allocated(vel_node)) then
|
|
|
|
|
|
|
|
do inod = 1, ng_node(lat_ele(i))
|
|
|
|
|
|
|
|
do ibasis = 1, basisnum(lat_ele(i))
|
|
|
|
|
|
|
|
ip = ip + 1
|
|
|
|
|
|
|
|
write(11, '(3i16, 6f23.15)') ip, ibasis, basis_type(ibasis, lat_ele(i)), r_node(:, ibasis, inod, i), &
|
|
|
|
|
|
|
|
vel_node(:,ibasis,inod,i)
|
|
|
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
else
|
|
|
|
do inod = 1, ng_node(lat_ele(i))
|
|
|
|
do inod = 1, ng_node(lat_ele(i))
|
|
|
|
do ibasis = 1, basisnum(lat_ele(i))
|
|
|
|
do ibasis = 1, basisnum(lat_ele(i))
|
|
|
|
ip = ip + 1
|
|
|
|
ip = ip + 1
|
|
|
|
write(11, '(3i16, 3f23.15)') ip, ibasis, basis_type(ibasis, lat_ele(i)), r_node(:, ibasis, inod, i)
|
|
|
|
write(11, '(3i16, 3f23.15)') ip, ibasis, basis_type(ibasis, lat_ele(i)), r_node(:, ibasis, inod, i)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
end if
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
!Now write the atomic information
|
|
|
|
!Now write the atomic information
|
|
|
|
if(atom_num /= 0) then
|
|
|
|
if(atom_num /= 0) then
|
|
|
|
|
|
|
|
if(allocated(vel_atom)) then
|
|
|
|
|
|
|
|
write(11, 16)
|
|
|
|
|
|
|
|
do i = 1, atom_num
|
|
|
|
|
|
|
|
write(11, '(2i16, 6f23.15)') i, type_atom(i), r_atom(:,i), vel_atom(:, i)
|
|
|
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
else
|
|
|
|
write(11,14)
|
|
|
|
write(11,14)
|
|
|
|
do i = 1, atom_num
|
|
|
|
do i = 1, atom_num
|
|
|
|
write(11, '(2i16, 3f23.15)') i, type_atom(i), r_atom(:,i)
|
|
|
|
write(11, '(2i16, 3f23.15)') i, type_atom(i), r_atom(:,i)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
|
|
|
|
close(11)
|
|
|
|
close(11)
|
|
|
|
end subroutine write_pycac
|
|
|
|
end subroutine write_pycac
|
|
|
@ -730,9 +753,10 @@ module io
|
|
|
|
real(kind = dp), dimension(6), intent(out) :: temp_box_bd
|
|
|
|
real(kind = dp), dimension(6), intent(out) :: temp_box_bd
|
|
|
|
|
|
|
|
|
|
|
|
integer :: i, j, k, l, n, inod, ibasis, type, size, in_atoms, in_eles, new_atom_types, &
|
|
|
|
integer :: i, j, k, l, n, inod, ibasis, type, size, in_atoms, in_eles, new_atom_types, &
|
|
|
|
new_type_to_type(10), new_lattice_types, sbox, new_lattice_map(10)
|
|
|
|
new_type_to_type(10), new_lattice_types, sbox, new_lattice_map(10), btype_map(10,10), bnum_map(10), &
|
|
|
|
|
|
|
|
node_map(10)
|
|
|
|
character(len=100) :: etype
|
|
|
|
character(len=100) :: etype
|
|
|
|
real(kind=dp) :: r(3), newdisplace(3)
|
|
|
|
real(kind=dp) :: r(3), newdisplace(3), lapa_map(10)
|
|
|
|
real(kind=dp), allocatable :: r_innode(:,:,:)
|
|
|
|
real(kind=dp), allocatable :: r_innode(:,:,:)
|
|
|
|
character(len = 2) :: new_type_to_name(10)
|
|
|
|
character(len = 2) :: new_type_to_name(10)
|
|
|
|
!First open the file
|
|
|
|
!First open the file
|
|
|
@ -782,45 +806,29 @@ module io
|
|
|
|
call add_atom_type(new_type_to_name(i), new_type_to_type(i), all_new)
|
|
|
|
call add_atom_type(new_type_to_name(i), new_type_to_type(i), all_new)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
!Read the number of lattice types, basisnum, and number of nodes for each lattice type
|
|
|
|
!Read the number of lattice types, basisnum, and number of nodes for each lattice type
|
|
|
|
read(11,*) new_lattice_types, (basisnum(i), i = lattice_types+1, lattice_types+new_lattice_types), &
|
|
|
|
read(11,*) new_lattice_types, (bnum_map(i), i = 1, new_lattice_types),(node_map(i), i =1, 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 the basis atom types for every lattice
|
|
|
|
read(11,*) ((basis_type(i,j), i = 1, basisnum(j)), j = lattice_types+1, lattice_types+new_lattice_types)
|
|
|
|
read(11,*) ((btype_map(i,j), i = 1, bnum_map(j)), j = 1, new_lattice_types)
|
|
|
|
!Convert the basis_atom types
|
|
|
|
!Convert the basis_atom types
|
|
|
|
do j = lattice_types+1, lattice_types+new_lattice_types
|
|
|
|
do j =1, new_lattice_types
|
|
|
|
do i = 1, basisnum(j)
|
|
|
|
do i = 1, bnum_map(j)
|
|
|
|
basis_type(i,j) = new_type_to_type(basis_type(i,j))
|
|
|
|
btype_map(i,j) = new_type_to_type(btype_map(i,j))
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
!Read the lattice parameters for every lattice type
|
|
|
|
!Read the lattice parameters for every lattice type
|
|
|
|
read(11,*) (lapa(i), i = lattice_types+1, lattice_types+new_lattice_types)
|
|
|
|
read(11,*) (lapa_map(i), i = 1, new_lattice_types)
|
|
|
|
|
|
|
|
|
|
|
|
!Now we loop over all new lattice types and check to see if they are exactly the same as any old lattice types
|
|
|
|
!Now we loop over all new lattice types and check to see if they are exactly the same as any old lattice types
|
|
|
|
!If they are then we map the new type to the old type.
|
|
|
|
!If they are then we map the new type to the old type.
|
|
|
|
k = lattice_types + 1
|
|
|
|
|
|
|
|
new_lattice_map(:) = 0
|
|
|
|
new_lattice_map(:) = 0
|
|
|
|
new_loop:do i = 1, new_lattice_types
|
|
|
|
new_loop:do i = 1, new_lattice_types
|
|
|
|
old_loop:do j = 1, lattice_types
|
|
|
|
call lattice_map(bnum_map(i), btype_map(:,i), node_map(i), lapa_map(i), new_lattice_map(i))
|
|
|
|
!First check all the lattice level variables
|
|
|
|
|
|
|
|
if ((basisnum(lattice_types + i) == basisnum(j)).and. &
|
|
|
|
|
|
|
|
(ng_node(lattice_types + i) == ng_node(j))) then
|
|
|
|
|
|
|
|
!Now check the basis level variables
|
|
|
|
|
|
|
|
do ibasis =1, basisnum(i)
|
|
|
|
|
|
|
|
if(basis_type(ibasis,lattice_types+i) /= basis_type(ibasis,j)) then
|
|
|
|
|
|
|
|
cycle old_loop
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
new_lattice_map(i) = j
|
|
|
|
|
|
|
|
cycle new_loop
|
|
|
|
|
|
|
|
end if
|
|
|
|
|
|
|
|
end do old_loop
|
|
|
|
|
|
|
|
new_lattice_map(i) = k
|
|
|
|
|
|
|
|
k = k+1
|
|
|
|
|
|
|
|
end do new_loop
|
|
|
|
end do new_loop
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
!Define max_ng_node and max_basis_num
|
|
|
|
|
|
|
|
max_basisnum = maxval(basisnum)
|
|
|
|
|
|
|
|
max_ng_node = maxval(ng_node)
|
|
|
|
|
|
|
|
|
|
|
|
!Read number of elements and atoms and allocate arrays
|
|
|
|
!Read number of elements and atoms and allocate arrays
|
|
|
|
read(11, *) in_atoms, in_eles
|
|
|
|
read(11, *) in_atoms, in_eles
|
|
|
|
call grow_ele_arrays(in_eles, in_atoms)
|
|
|
|
call grow_ele_arrays(in_eles, in_atoms)
|
|
|
@ -909,7 +917,7 @@ module io
|
|
|
|
!Read define atom_types by mass
|
|
|
|
!Read define atom_types by mass
|
|
|
|
print *, j
|
|
|
|
print *, j
|
|
|
|
do i = 1, j
|
|
|
|
do i = 1, j
|
|
|
|
call atommassspecies(atomic_masses(i), atomic_element)
|
|
|
|
call realatomspecies(atomic_masses(i), atomic_element)
|
|
|
|
call add_atom_type(atomic_element, atom_type_map(i), all_new)
|
|
|
|
call add_atom_type(atomic_element, atom_type_map(i), all_new)
|
|
|
|
print *, i, atom_type_map(i)
|
|
|
|
print *, i, atom_type_map(i)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
@ -1009,13 +1017,15 @@ module io
|
|
|
|
!Internal Variables
|
|
|
|
!Internal Variables
|
|
|
|
integer :: i, j, in_eles, in_atoms, inbtypes(10), lat_type, ia, ie, inod, &
|
|
|
|
integer :: i, j, in_eles, in_atoms, inbtypes(10), lat_type, ia, ie, inod, &
|
|
|
|
id, type_node, ilat, esize, tag, type, bnum, n, ibasis, ip, atom_type_map(100)
|
|
|
|
id, type_node, ilat, esize, tag, type, bnum, n, ibasis, ip, atom_type_map(100)
|
|
|
|
real(kind=dp) :: newdisplace(3), ra(3), in_lapa, ea, fa(3), va(6), &
|
|
|
|
real(kind=dp) :: newdisplace(3), ra(3), in_lapa, ea, fa(3), va(6), vela(3),&
|
|
|
|
ee(10,20), fe(3,10,20), ve(6,10,20), re(3,10,20), atomic_masses(10)
|
|
|
|
ee(10,20), fe(3,10,20), ve(6,10,20), re(3,10,20), vele(3,10,20), atomic_masses(10)
|
|
|
|
character(len=100) :: textholder, fcc
|
|
|
|
character(len=100) :: textholder, fcc
|
|
|
|
character(len=1000) :: line
|
|
|
|
character(len=1000) :: line
|
|
|
|
character(len=2) :: atomic_element
|
|
|
|
character(len=2) :: atomic_element
|
|
|
|
|
|
|
|
logical :: read_vel
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
read_vel =.false.
|
|
|
|
open(unit=11, file=trim(adjustl(file)), action='read',position='rewind')
|
|
|
|
open(unit=11, file=trim(adjustl(file)), action='read',position='rewind')
|
|
|
|
|
|
|
|
|
|
|
|
!Now initialize some important variables if they aren't defined
|
|
|
|
!Now initialize some important variables if they aren't defined
|
|
|
@ -1063,7 +1073,7 @@ module io
|
|
|
|
|
|
|
|
|
|
|
|
!Read define atom_types by mass
|
|
|
|
!Read define atom_types by mass
|
|
|
|
do i = 1, j
|
|
|
|
do i = 1, j
|
|
|
|
call atommassspecies(atomic_masses(i), atomic_element)
|
|
|
|
call realatomspecies(atomic_masses(i), atomic_element)
|
|
|
|
call add_atom_type(atomic_element, atom_type_map(i), all_new)
|
|
|
|
call add_atom_type(atomic_element, atom_type_map(i), all_new)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
|
@ -1077,12 +1087,22 @@ module io
|
|
|
|
|
|
|
|
|
|
|
|
if(in_atoms > 0 ) then
|
|
|
|
if(in_atoms > 0 ) then
|
|
|
|
!Read atom header
|
|
|
|
!Read atom header
|
|
|
|
read(11,*) textholder
|
|
|
|
read(11,'(a)') line
|
|
|
|
|
|
|
|
read(line, *) (textholder, i=1, 18)
|
|
|
|
|
|
|
|
if(textholder=="velx") then
|
|
|
|
|
|
|
|
call alloc_vel_arrays(in_eles, in_atoms)
|
|
|
|
|
|
|
|
read_vel = .true.
|
|
|
|
|
|
|
|
end if
|
|
|
|
do ia = 1, in_atoms
|
|
|
|
do ia = 1, in_atoms
|
|
|
|
read(11,'(a)') line(:)
|
|
|
|
read(11,'(a)') line(:)
|
|
|
|
|
|
|
|
if(read_vel) then
|
|
|
|
|
|
|
|
read(line,*) tag, type, ra(:), ea, fa(:), va(:), vela(:)
|
|
|
|
|
|
|
|
else
|
|
|
|
read(line,*) tag, type, ra(:), ea, fa(:), va(:)
|
|
|
|
read(line,*) tag, type, ra(:), ea, fa(:), va(:)
|
|
|
|
|
|
|
|
end if
|
|
|
|
call add_atom(tag, atom_type_map(type), sub_box_num, ra)
|
|
|
|
call add_atom(tag, atom_type_map(type), sub_box_num, ra)
|
|
|
|
call add_atom_data(atom_num, ea, fa, va)
|
|
|
|
call add_atom_data(atom_num, ea, fa, va)
|
|
|
|
|
|
|
|
if(read_vel) vel_atom(:,atom_num) = vela
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
|
|
end if
|
|
|
|
end if
|
|
|
@ -1096,9 +1116,16 @@ module io
|
|
|
|
do ie =1, in_eles
|
|
|
|
do ie =1, in_eles
|
|
|
|
read(11,*) tag, n, bnum, esize
|
|
|
|
read(11,*) tag, n, bnum, esize
|
|
|
|
inbtypes(:) = 0
|
|
|
|
inbtypes(:) = 0
|
|
|
|
|
|
|
|
if(read_vel) then
|
|
|
|
|
|
|
|
do inod =1, n*bnum
|
|
|
|
|
|
|
|
read(11,*) ip, ibasis, inbtypes(ibasis), re(:,ibasis,ip), ee(ibasis,ip), fe(:,ibasis,ip), &
|
|
|
|
|
|
|
|
ve(:,ibasis,ip), vele(:,ibasis,ip)
|
|
|
|
|
|
|
|
end do
|
|
|
|
|
|
|
|
else
|
|
|
|
do inod =1, n*bnum
|
|
|
|
do inod =1, n*bnum
|
|
|
|
read(11,*) ip, ibasis, inbtypes(ibasis), re(:,ibasis,ip), ee(ibasis,ip), fe(:,ibasis,ip), ve(:,ibasis,ip)
|
|
|
|
read(11,*) ip, ibasis, inbtypes(ibasis), re(:,ibasis,ip), ee(ibasis,ip), fe(:,ibasis,ip), ve(:,ibasis,ip)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
end if
|
|
|
|
do i = 1, bnum
|
|
|
|
do i = 1, bnum
|
|
|
|
inbtypes(ibasis) = atom_type_map(inbtypes(ibasis))
|
|
|
|
inbtypes(ibasis) = atom_type_map(inbtypes(ibasis))
|
|
|
|
end do
|
|
|
|
end do
|
|
|
@ -1110,11 +1137,12 @@ module io
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
call add_element(tag, fcc, esize+1, lat_type, sub_box_num, re)
|
|
|
|
call add_element(tag, fcc, esize+1, lat_type, sub_box_num, re)
|
|
|
|
call add_element_data(ele_num, ee, fe, ve)
|
|
|
|
call add_element_data(ele_num, ee, fe, ve)
|
|
|
|
|
|
|
|
if(read_vel) vel_node(:, :, :, ele_num) = vele(:,1:max_basisnum, 1:max_ng_node)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
call set_max_esize
|
|
|
|
call set_max_esize
|
|
|
|
return
|
|
|
|
return
|
|
|
|
end subroutine
|
|
|
|
end subroutine read_pycac_out
|
|
|
|
|
|
|
|
|
|
|
|
subroutine read_lmp(file, displace, temp_box_bd)
|
|
|
|
subroutine read_lmp(file, displace, temp_box_bd)
|
|
|
|
!This subroutine is used to read .cac files which are used with the lammpsCAC format
|
|
|
|
!This subroutine is used to read .cac files which are used with the lammpsCAC format
|
|
|
@ -1184,7 +1212,7 @@ module io
|
|
|
|
!Read atomic masses
|
|
|
|
!Read atomic masses
|
|
|
|
do i = 1, type_in
|
|
|
|
do i = 1, type_in
|
|
|
|
read(11,*) j, mass
|
|
|
|
read(11,*) j, mass
|
|
|
|
call ATOMMASSSPECIES(mass, atom_species)
|
|
|
|
call realatomspecies(mass, atom_species)
|
|
|
|
call add_atom_type(atom_species, type_map(i), all_new)
|
|
|
|
call add_atom_type(atom_species, type_map(i), all_new)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
|
@ -1272,7 +1300,7 @@ module io
|
|
|
|
!Read atomic masses
|
|
|
|
!Read atomic masses
|
|
|
|
do i = 1, type_in
|
|
|
|
do i = 1, type_in
|
|
|
|
read(11,*) j, mass, textholder
|
|
|
|
read(11,*) j, mass, textholder
|
|
|
|
call ATOMMASSSPECIES(mass, atom_species)
|
|
|
|
call realatomspecies(mass, atom_species)
|
|
|
|
call add_atom_type(atom_species, type_map(i), all_new)
|
|
|
|
call add_atom_type(atom_species, type_map(i), all_new)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
|
|