Merge branch 'development' into ft-write-lammpscac
This commit is contained in:
commit
d09ebfa7e0
10 changed files with 750 additions and 120 deletions
357
src/io.f90
357
src/io.f90
|
@ -3,6 +3,7 @@ module io
|
|||
use elements
|
||||
use parameters
|
||||
use atoms
|
||||
use box
|
||||
|
||||
implicit none
|
||||
|
||||
|
@ -13,6 +14,7 @@ module io
|
|||
public
|
||||
contains
|
||||
|
||||
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! Subroutines for writing out data files !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
subroutine get_out_file(filename)
|
||||
|
||||
implicit none
|
||||
|
@ -42,7 +44,6 @@ module io
|
|||
if((scan(overwrite, "n") > 0).or.(scan(overwrite, "N") > 0)) then
|
||||
print *, "Please specify a new filename with extension:"
|
||||
read(*,*) temp_outfile
|
||||
cycle
|
||||
else if((scan(overwrite, "y") > 0).or.(scan(overwrite, "Y") > 0)) then
|
||||
continue
|
||||
else
|
||||
|
@ -58,7 +59,7 @@ module io
|
|||
cycle
|
||||
end if
|
||||
select case(temp_outfile(scan(temp_outfile,'.',.true.)+1:))
|
||||
case('xyz','lmp','vtk')
|
||||
case('xyz', 'lmp', 'vtk', 'mb', 'restart')
|
||||
outfilenum=outfilenum+1
|
||||
outfiles(outfilenum) = temp_outfile
|
||||
exit
|
||||
|
@ -141,6 +142,10 @@ module io
|
|||
call write_lmp(outfiles(i))
|
||||
case('vtk')
|
||||
call write_vtk(outfiles(i))
|
||||
case('mb')
|
||||
call write_mb(outfiles(i))
|
||||
case('restart')
|
||||
call write_pycac(outfiles(i))
|
||||
case('cac')
|
||||
call write_lmpcac(outfiles(i))
|
||||
case default
|
||||
|
@ -158,16 +163,10 @@ module io
|
|||
!This is the simplest visualization subroutine, it writes out all nodal positions and atom positions to an xyz file
|
||||
character(len=100), intent(in) :: file
|
||||
|
||||
integer :: node_num, i, inod, ibasis
|
||||
integer :: i, inod, ibasis
|
||||
|
||||
open(unit=11, file=trim(adjustl(file)), action='write', status='replace',position='rewind')
|
||||
|
||||
!Calculate total node number
|
||||
node_num=0
|
||||
do i = 1, ele_num
|
||||
node_num = node_num + basisnum(lat_ele(i))*ng_node(lat_ele(i))
|
||||
end do
|
||||
|
||||
!Write total number of atoms + elements
|
||||
write(11, '(i16)') node_num+atom_num
|
||||
|
||||
|
@ -389,28 +388,336 @@ module io
|
|||
close(11)
|
||||
end subroutine
|
||||
|
||||
subroutine write_pycac(file)
|
||||
!This subroutine writes restart files meant to be used with the McDowell Group CAC code.
|
||||
!NOTE: This code doesn't work for arbitrary number of basis atoms per node. It assumes that the
|
||||
!each element has only 1 atom type at the node.
|
||||
character(len=100), intent(in) :: file
|
||||
integer :: interp_max, i, j, lat_size, inod, ibasis, ip
|
||||
real(kind=dp) :: box_vec(3)
|
||||
|
||||
! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! READ SUBROUTINES !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
! subroutine read_lmpcac(file, box_bd)
|
||||
! !This subroutine reads in a lmpcac file which can be used with different options and modes
|
||||
1 format('time' / i16, f23.15)
|
||||
2 format('number of elements' / i16)
|
||||
3 format('number of nodes' / i16)
|
||||
4 format('element types' / i16)
|
||||
5 format('number of atoms' / i16)
|
||||
6 format('number of grains' / i16)
|
||||
7 format('boundary ' / 3a1)
|
||||
8 format('box bound' / 6f23.15)
|
||||
9 format('box length' / 3f23.15)
|
||||
10 format('box matrix')
|
||||
11 format(3f23.15)
|
||||
12 format('coarse-grained domain')
|
||||
13 format('ie ele_type grain_ele lat_type_ele'/ 'ip ibasis type x y z')
|
||||
14 format('atomistic domain' / 'ia grain_atom type_atom x y z')
|
||||
15 format('maximum lattice periodicity length' / 3f23.15)
|
||||
16 format('Number of lattice types and atom types '/ 2i16)
|
||||
17 format('lattice type IDs')
|
||||
18 format('lattice types for grains')
|
||||
19 format('max nodes per element' / i16)
|
||||
20 format('max interpo per element' / i16)
|
||||
21 format('atom types to elements')
|
||||
|
||||
! !Arguments
|
||||
! character(len=100), intent(in) :: file
|
||||
! real(kind=wp), dimension(6), intent(out) :: box_bd
|
||||
open(unit=11, file=trim(adjustl(file)), action='write', status='replace',position='rewind')
|
||||
|
||||
! !Internal variables
|
||||
! character(len=1000) :: line
|
||||
! integer :: read_num, atom_lim, ele_lim
|
||||
write(11,1) timestep, total_time
|
||||
write(11,2) ele_num
|
||||
|
||||
! !Open the lmpcac file
|
||||
! open(unit=11, file=file, action='read', position='rewind')
|
||||
!Below writes the header information for the restart file
|
||||
|
||||
! !Skip header lines
|
||||
! read(11,*) line
|
||||
! read(11,*) line
|
||||
!Calculate the max number of atoms per element
|
||||
select case(max_ng_node)
|
||||
case(8)
|
||||
interp_max = (max_esize)**3
|
||||
end select
|
||||
write(11,20) interp_max
|
||||
write(11,3) node_num
|
||||
write(11,19) max_ng_node
|
||||
write(11,4) lattice_types
|
||||
write(11,2) atom_num
|
||||
write(11,6) 1 !Grain_num is ignored
|
||||
write(11,16) lattice_types, atom_types
|
||||
write(11,21)
|
||||
do i = 1, atom_types
|
||||
write(11,*) i, type_to_name(i)
|
||||
end do
|
||||
write(11,7) box_bc(1:1), box_bc(2:2), box_bc(3:3)
|
||||
write(11,18)
|
||||
write(11,'(2i16)') 1,1 !This is another throwaway line that is meaningless
|
||||
write(11,17)
|
||||
!This may have to be updated in the future but currently the only 8 node element is fcc
|
||||
do i = 1, lattice_types
|
||||
select case(ng_node(i))
|
||||
case(8)
|
||||
write(11, *) i, 'fcc'
|
||||
end select
|
||||
end do
|
||||
write(11,15) 1.0_dp, 1.0_dp, 1.0_dp !Another throwaway line that isn't needed
|
||||
write(11,8) box_bd
|
||||
write(11,9) box_bd(2)-box_bd(1), box_bd(4) - box_bd(3), box_bd(6)-box_bd(5)
|
||||
write(11,10)
|
||||
!Current boxes are limited to being rectangular
|
||||
do i = 1,3
|
||||
box_vec(:) = 0.0_dp
|
||||
box_vec(i) = box_bd(2*i) - box_bd(2*i-1)
|
||||
write(11,11) box_vec
|
||||
end do
|
||||
!We write this as box_mat ori and box_mat current
|
||||
do i = 1,3
|
||||
box_vec(:) = 0.0_dp
|
||||
box_vec(i) = box_bd(2*i) - box_bd(2*i-1)
|
||||
write(11,11) box_vec
|
||||
end do
|
||||
|
||||
! !Read total number of elements
|
||||
!write the element information
|
||||
if(ele_num > 0) then
|
||||
write(11,12)
|
||||
do i = 1, lattice_types
|
||||
do j = 1, ele_num
|
||||
if (lat_ele(j) == i) then
|
||||
lat_size = size_ele(j)-1
|
||||
exit
|
||||
end if
|
||||
end do
|
||||
write(11,'(3i16)') i, lat_size, basis_type(1,i)
|
||||
end do
|
||||
ip = 0
|
||||
write(11,13)
|
||||
do i = 1, ele_num
|
||||
write(11, '(4i16)') i, lat_ele(i), 1, basis_type(1,lat_ele(i))
|
||||
do inod = 1, ng_node(lat_ele(i))
|
||||
do ibasis = 1, basisnum(lat_ele(i))
|
||||
ip = ip + 1
|
||||
write(11, '(2i16, 3f23.15)') ip, ibasis, r_node(:, ibasis, inod, i)
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
end if
|
||||
|
||||
!Now write the atomic information
|
||||
if(atom_num /= 0) then
|
||||
write(11,14)
|
||||
do i = 1, atom_num
|
||||
write(11, '(3i16, 3f23.15)') i, 1, type_atom(i), r_atom(:,i)
|
||||
end do
|
||||
end if
|
||||
|
||||
close(11)
|
||||
end subroutine write_pycac
|
||||
|
||||
subroutine write_mb(file)
|
||||
|
||||
!This subroutine writes the cacmb formatted file which provides necessary information for building models
|
||||
character(len=100), intent(in) :: file
|
||||
|
||||
integer :: i, j, k, inod, ibasis
|
||||
|
||||
!Open the .mb file for writing
|
||||
open(unit=11, file=trim(adjustl(file)), action='write', status='replace',position='rewind')
|
||||
|
||||
!First write the box boundary information
|
||||
!Write the global box boundaries
|
||||
write(11,*) box_bd(:)
|
||||
!Write the number of sub_boxes in the system
|
||||
write(11,*) sub_box_num
|
||||
!For every subbox write the orientation, sub box boundary, and sub_box_array_bds
|
||||
do i = 1, sub_box_num
|
||||
write(11,*) sub_box_ori(:,:,i)
|
||||
write(11,*) sub_box_bd(:,i)
|
||||
write(11,*) ((sub_box_array_bd(j,k,i), j = 1, 2), k = 1, 2)
|
||||
end do
|
||||
|
||||
!Write the number of atom types in the current model and all of their names
|
||||
write(11,*) atom_types, (type_to_name(i), i=1, atom_types)
|
||||
!Write the number of lattice_types, basisnum and number of nodes for each lattice type
|
||||
write(11,*) lattice_types, (basisnum(i), i = 1, lattice_types), (ng_node(i), i = 1, lattice_types)
|
||||
!Now for every lattice type write the basis atom types
|
||||
write(11,*) ((basis_type(i,j), i = 1, basisnum(j)), j = 1, lattice_types)
|
||||
|
||||
!Now write the numbers of elements and atoms
|
||||
write(11,*) atom_num, ele_num
|
||||
|
||||
!Write out atoms first
|
||||
do i = 1, atom_num
|
||||
write(11,*) i, type_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), 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)
|
||||
end do
|
||||
end do
|
||||
end do
|
||||
|
||||
close(11)
|
||||
end subroutine write_mb
|
||||
|
||||
|
||||
!!!!!!!!!!!!! Below are subroutines for reading files !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
|
||||
subroutine get_in_file(filename)
|
||||
|
||||
implicit none
|
||||
|
||||
character(len=100), intent(in) :: filename
|
||||
character(len=100) :: temp_infile
|
||||
logical :: file_exists
|
||||
|
||||
!If no filename is provided then this function is called with none and prompts user input
|
||||
if (filename=='none') then
|
||||
print *, "Please specify a filename or extension to output to:"
|
||||
read(*,*) temp_infile
|
||||
else
|
||||
temp_infile = filename
|
||||
end if
|
||||
|
||||
!Infinite loop which only exists if user provides valid filetype
|
||||
do while(.true.)
|
||||
|
||||
!Check to see if file exists, if it does then ask user if they would like to overwrite the file
|
||||
inquire(file=trim(temp_infile), exist=file_exists)
|
||||
if (.not.file_exists) then
|
||||
print *, "The file ", trim(adjustl(filename)), " does not exist. Please input a filename that exists"
|
||||
read(*,*) temp_infile
|
||||
cycle
|
||||
end if
|
||||
|
||||
select case(temp_infile(scan(temp_infile,'.',.true.)+1:))
|
||||
case('xyz', 'lmp', 'vtk', 'mb')
|
||||
infilenum=infilenum+1
|
||||
infiles(infilenum) = temp_infile
|
||||
exit
|
||||
case default
|
||||
print *, "File type: ", trim(temp_infile(scan(temp_infile,'.',.true.):)), "not currently accepted. ", &
|
||||
"please input a filename with extension from following list: mb."
|
||||
read(*,*) temp_infile
|
||||
|
||||
end select
|
||||
end do
|
||||
|
||||
end subroutine get_in_file
|
||||
|
||||
subroutine read_in(i, displace, temp_box_bd)
|
||||
!This subroutine loops over alll of the outfile types defined and calls the correct writing subroutine
|
||||
|
||||
integer, intent(in) :: i
|
||||
real(kind=dp), dimension(3), intent(in) :: displace
|
||||
real(kind=dp), dimension(6), intent(out) :: temp_box_bd
|
||||
|
||||
!Pull out the extension of the file and call the correct write subroutine
|
||||
select case(trim(adjustl(infiles(i)(scan(infiles(i),'.',.true.)+1:))))
|
||||
case('mb')
|
||||
call read_mb(infiles(i), displace, temp_box_bd)
|
||||
case default
|
||||
print *, "The extension ", trim(adjustl(outfiles(i)(scan(outfiles(i),'.',.true.)+1:))), &
|
||||
" is not accepted for writing. Please select from: mb and try again"
|
||||
stop
|
||||
|
||||
end select
|
||||
|
||||
end subroutine read_in
|
||||
|
||||
subroutine read_mb(file, displace, temp_box_bd)
|
||||
!This subroutine reads in an mb file for operation
|
||||
|
||||
character(len=100), intent(in) :: file
|
||||
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, 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')
|
||||
|
||||
!Read in the box boundary and grow the current active box bd
|
||||
read(11, *) temp_box_bd(:)
|
||||
|
||||
do i = 1, 3
|
||||
newdisplace(i) = displace(i) - temp_box_bd(2*i-1)
|
||||
temp_box_bd(2*i-1) = temp_box_bd(2*i-1) + newdisplace(i)
|
||||
temp_box_bd(2*i) = temp_box_bd(2*i) + newdisplace(i)
|
||||
end do
|
||||
|
||||
!Read in the number of sub_boxes and allocate the variables
|
||||
read(11, *) n
|
||||
|
||||
! end subroutine read_lmpcac
|
||||
if (sub_box_num == 0) then
|
||||
call alloc_sub_box(n)
|
||||
else
|
||||
call grow_sub_box(n)
|
||||
end if
|
||||
|
||||
!Read in subbox orientations and boundaries
|
||||
do i = 1, n
|
||||
!Read in orientation with column major ordering
|
||||
read(11,*) ((sub_box_ori(j, k, sub_box_num+i), j = 1, 3), k = 1, 3)
|
||||
!Read in subbox boundaries
|
||||
read(11,*) sub_box_bd(:,sub_box_num+i)
|
||||
sub_box_bd(:,sub_box_num+i) = sub_box_bd(:, sub_box_num+i) + displace(:)
|
||||
!Read in sub_box_array_bd
|
||||
read(11,*) ((sub_box_ori(j, k, sub_box_num+i), j = 1, 2), k = 1, 2)
|
||||
|
||||
end do
|
||||
sub_box_num = sub_box_num + n
|
||||
|
||||
!Read in the number of atom types and all their names
|
||||
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,*) 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 = 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)
|
||||
allocate(r_innode(3,max_basisnum, max_ng_node))
|
||||
|
||||
!Read the atoms
|
||||
do i = 1, in_atoms
|
||||
read(11,*) j, type, r(:)
|
||||
call add_atom(new_type_to_type(type), r+newdisplace)
|
||||
end do
|
||||
|
||||
!Read the elements
|
||||
do i = 1, in_eles
|
||||
read(11, *) n, type, size, etype
|
||||
do inod = 1, ng_node(type)
|
||||
do ibasis =1, basisnum(type)
|
||||
read(11,*) j, k, r_innode(:, ibasis, inod)
|
||||
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)
|
||||
|
||||
!Only increment the lattice types if there are elements, if there are no elements then we
|
||||
!just overwrite the arrays
|
||||
if(in_eles > 0) 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