You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
177 lines
5.8 KiB
177 lines
5.8 KiB
5 years ago
|
module io
|
||
|
|
||
|
use elements
|
||
|
use parameters
|
||
|
use atoms
|
||
|
|
||
|
implicit none
|
||
|
|
||
|
integer :: outfilenum = 0
|
||
|
character(len=100) :: outfiles(10)
|
||
|
|
||
|
public
|
||
|
contains
|
||
|
|
||
|
subroutine get_out_file(filename)
|
||
|
|
||
|
implicit none
|
||
|
|
||
|
character(len=100), intent(in) :: filename
|
||
|
character(len=100) :: temp_outfile
|
||
|
character(len=1) :: overwrite
|
||
|
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_outfile
|
||
|
else
|
||
|
temp_outfile = filename
|
||
|
end if
|
||
|
|
||
|
!Infinite loop which only exists if user provides valid filetype
|
||
|
overwrite = 'r'
|
||
|
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_outfile), exist=file_exists)
|
||
|
if (file_exists) then
|
||
|
if (overwrite == 'r') print *, "File ", trim(temp_outfile), " already exists. Would you like to overwrite? (Y/N)"
|
||
|
read(*,*) overwrite
|
||
|
if((scan(overwrite, "n") > 0).or.(scan(overwrite, "N") > 0)) then
|
||
|
print *, "Please specify a new filename with extension:"
|
||
|
read(*,*) temp_outfile
|
||
|
else if((scan(overwrite, "y") > 0).or.(scan(overwrite, "Y") > 0)) then
|
||
|
continue
|
||
|
else
|
||
|
print *, "Please pick either y or n"
|
||
|
read(*,*) overwrite
|
||
|
end if
|
||
|
|
||
|
end if
|
||
|
|
||
|
if (scan(temp_outfile,'.',.true.) == 0) then
|
||
|
print *, "No extension included on filename, please type a full filename that includes an extension."
|
||
|
read(*,*) temp_outfile
|
||
|
cycle
|
||
|
end if
|
||
|
select case(temp_outfile(scan(temp_outfile,'.',.true.)+1:))
|
||
|
case('xyz')
|
||
|
outfilenum=outfilenum+1
|
||
|
outfiles(outfilenum) = temp_outfile
|
||
|
exit
|
||
|
case('lmp')
|
||
|
outfilenum=outfilenum+1
|
||
|
outfiles(outfilenum) = temp_outfile
|
||
|
exit
|
||
|
|
||
|
case default
|
||
|
print *, "File type: ", trim(temp_outfile(scan(temp_outfile,'.',.true.):)), "not currently accepted. ", &
|
||
|
"please input a filename with extension from following list: xyz."
|
||
|
read(*,*) temp_outfile
|
||
|
|
||
|
end select
|
||
|
end do
|
||
|
|
||
|
end subroutine get_out_file
|
||
|
|
||
|
|
||
|
subroutine write_out
|
||
|
!This subroutine loops over alll of the outfile types defined and calls the correct writing subroutine
|
||
|
|
||
|
integer :: i
|
||
|
|
||
|
do i = 1, outfilenum
|
||
|
!Pull out the extension of the file and call the correct write subroutine
|
||
|
select case(trim(adjustl(outfiles(i)(scan(outfiles(i),'.',.true.)+1:))))
|
||
|
case('xyz')
|
||
|
call write_xyz(outfiles(i))
|
||
|
case('lmp')
|
||
|
call write_lmp(outfiles(i))
|
||
|
case default
|
||
|
print *, "The extension ", trim(adjustl(outfiles(i)(scan(outfiles(i),'.',.true.)+1:))), &
|
||
|
" is not accepted for writing. Please select from: xyz and try again"
|
||
|
stop
|
||
|
|
||
|
end select
|
||
|
end do
|
||
|
end subroutine write_out
|
||
|
|
||
|
|
||
|
|
||
|
subroutine write_xyz(file)
|
||
|
!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
|
||
|
|
||
|
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
|
||
|
|
||
|
!Write comment line
|
||
|
write(11, '(a)') "#Node + atom file created using cacmb"
|
||
|
|
||
|
!Write nodal positions
|
||
|
do i = 1, ele_num
|
||
|
do inod = 1, ng_node(lat_ele(i))
|
||
|
do ibasis = 1, basisnum(lat_ele(i))
|
||
|
write(11, '(a, 3f23.15)') basis_type(ibasis,lat_ele(i)), r_node(:,ibasis,inod,i)
|
||
|
end do
|
||
|
end do
|
||
|
end do
|
||
|
|
||
|
!Write atom positions
|
||
|
do i = 1, atom_num
|
||
|
write(11, '(a, 3f23.15)') type_atom(i), r_atom(:,i)
|
||
|
end do
|
||
|
|
||
|
!Finish writing
|
||
|
close(11)
|
||
|
end subroutine write_xyz
|
||
|
|
||
|
subroutine write_lmp(file)
|
||
|
|
||
|
integer :: write_num, i
|
||
|
character(len=100), intent(in) :: file
|
||
|
!This subroutine writes out a .lmp style dump file
|
||
|
|
||
|
open(unit=11, file=trim(adjustl(file)), action='write', status='replace',position='rewind')
|
||
|
|
||
|
!Comment line
|
||
|
write(11, '(a)') '# lmp file made with cacmb'
|
||
|
write(11, '(a)')
|
||
|
!Calculate total atom number
|
||
|
write_num = atom_num
|
||
|
!Write total number of atoms + elements
|
||
|
write(11, '(i16, a)') write_num, ' atoms'
|
||
|
!Write number of atom types
|
||
|
write(11, '(i16, a)') 1, ' atom types'
|
||
|
|
||
|
write(11,'(a)') ' '
|
||
|
!Write box bd
|
||
|
write(11, '(2f23.15, a)') box_bd(1:2), ' xlo xhi'
|
||
|
write(11, '(2f23.15, a)') box_bd(3:4), ' ylo yhi'
|
||
|
write(11, '(2f23.15, a)') box_bd(5:6), ' zlo zhi'
|
||
|
|
||
|
!Masses
|
||
|
write(11, '(a)') 'Masses'
|
||
|
write(11, '(a)') ' '
|
||
|
write(11, '(i16, f23.15)') 1, 63.546
|
||
|
write(11, '(a)') ' '
|
||
|
|
||
|
!Write atom positions
|
||
|
write(11, '(a)') 'Atoms'
|
||
|
write(11, '(a)') ' '
|
||
|
do i = 1, atom_num
|
||
|
write(11, '(2i16, 3f23.15)') i, 1, r_atom(:,i)
|
||
|
end do
|
||
|
end subroutine write_lmp
|
||
|
end module io
|