Working changes for reading .cac files
This commit is contained in:
parent
e6d7741060
commit
b3e05da6a4
5 changed files with 83 additions and 16 deletions
47
src/io.f90
47
src/io.f90
|
@ -8,9 +8,9 @@ module io
|
|||
implicit none
|
||||
|
||||
integer :: outfilenum = 0, infilenum = 0
|
||||
character(len=100) :: outfiles(100), infiles(100)
|
||||
character(len=100) :: outfiles(100), infiles(100), in_lattice_type=''
|
||||
logical :: force_overwrite
|
||||
|
||||
real(kind=dp) :: in_lapa=0.0
|
||||
public
|
||||
contains
|
||||
|
||||
|
@ -958,12 +958,15 @@ module io
|
|||
|
||||
character(len=100) :: textholder, element_type, esize
|
||||
character(len=2) :: atom_species
|
||||
integer :: i, j, ele_in, type_in, type_map(10), in_basis, node_types(10,8), inod, ibasis, in_basis_types(10)
|
||||
|
||||
real(kind=dp) :: mass, r_in(3,10,8)
|
||||
integer :: i, j, ele_in, type_in, type_map(10), in_basis, node_types(10,8), inod, ibasis, in_basis_types(10)
|
||||
real(kind=dp) :: mass, r_in(3,10,8), lat_vec(3), in_ori(3,3)
|
||||
|
||||
|
||||
!First open the file
|
||||
!First check to make sure that we have set the needed variables
|
||||
if(is_equal(in_lapa,0.0_dp).or.(in_lattice_type=='')) then
|
||||
print *, "Please use set_cac to set needed parameters to read in .cac file"
|
||||
stop 3
|
||||
end if
|
||||
!Open the file
|
||||
open(unit=11, file=trim(adjustl(file)), action='read',position='rewind')
|
||||
|
||||
!Read header information
|
||||
|
@ -978,8 +981,7 @@ module io
|
|||
read(11,*) textholder
|
||||
read(11,*) box_bd(1:2), texholder
|
||||
read(11,*) box_bd(3:4), texholder
|
||||
read(11,*) box_bd(5:6), texholder
|
||||
|
||||
read(11,*) box_bd(5:6), texholder
|
||||
!Read useless information
|
||||
read(11,*) textholder
|
||||
read(11,*) textholder
|
||||
|
@ -1005,10 +1007,35 @@ module io
|
|||
do j = 1, 8*in_basis
|
||||
read(11, *) inod, ibasis, in_basis_types(ibasis), r_in(:,ibasis,inod)
|
||||
end do
|
||||
|
||||
!Now calculate the orientation matrix based on the lattice type.
|
||||
lat_vec = r_in(:,1,2) - r_in(:,1,1)
|
||||
lat_vec = lat_vec / norm2(lat_vec)
|
||||
|
||||
!Now figure out if is an existing lattice_type
|
||||
call lattice_map(in_basis, in_basis_types, 8, in_lapa, lat_type)
|
||||
|
||||
!
|
||||
|
||||
end select
|
||||
end do
|
||||
|
||||
end subroutine read_cac
|
||||
|
||||
subroutine set_cac(apos)
|
||||
!This code parses input values
|
||||
integer, intent(in) :: apos
|
||||
integer :: arglen, arg_pos
|
||||
|
||||
arg_pos = apos + 1
|
||||
call get_command_argument(arg_pos, in_lapa, arglen)
|
||||
if (arglen==0) then
|
||||
print *, "Missing lattice parameter for set_input_lat"
|
||||
end if
|
||||
|
||||
arg_pos = arg_pos + 1
|
||||
call get_command_argument(arg_pos, in_lattice_type, arglen)
|
||||
if (arglen==0) then
|
||||
print *, "Missing lattice type for set_input_lat"
|
||||
end if
|
||||
end subroutine set_input_lat(arg_pos)
|
||||
end module io
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue