Skip to content

Commit

Permalink
merging after restart from coordinates
Browse files Browse the repository at this point in the history
  • Loading branch information
vtripath65 committed Nov 26, 2024
2 parents 2b922e9 + b525a37 commit 67ca0de
Show file tree
Hide file tree
Showing 11 changed files with 176 additions and 111 deletions.
25 changes: 20 additions & 5 deletions src/getMol.f90
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,8 @@ subroutine getMol(ierr)

implicit none

integer :: fail

logical :: present
integer :: i,j,k,itemp
integer, intent(inout) :: ierr
Expand All @@ -33,11 +35,24 @@ subroutine getMol(ierr)

! read xyz coordinates from the .in file
if(.not. isTemplate) then
call quick_open(infile,inFileName,'O','F','W',.true.,ierr)
CHECK_ERROR(ierr)
! read molecule coordinates
call read2(quick_molspec,inFile,ierr)
close(inFile)
if(quick_method%read_coord)then

open(unit=iDataFile,file=dataFileName,status='OLD',form='UNFORMATTED')
call rchk_darray(iDataFile, "xyz", 3, natom, 1, xyz, fail)
call rchk_iarray(iDataFile, "iattype", natom, 1, 1, quick_molspec%iattype, fail)
close(iDataFile)

quick_molspec%xyz => xyz

else

call quick_open(infile,inFileName,'O','F','W',.true.,ierr)
CHECK_ERROR(ierr)
! read molecule coordinates
call read2(quick_molspec,inFile,ierr)
close(inFile)

endif
endif

quick_molspec%nbasis => nbasis
Expand Down
13 changes: 13 additions & 0 deletions src/main.f90
Original file line number Diff line number Diff line change
Expand Up @@ -64,6 +64,9 @@ program quick

implicit none


integer :: fail

#if defined CUDA || defined HIP
integer :: gpu_device_id = -1
#endif
Expand Down Expand Up @@ -295,6 +298,16 @@ program quick
else
SAFE_CALL(lopt(ierr)) ! Cartesian
endif

if(master) then
if(quick_method%writexyz)then
call quick_open(iDataFile, dataFileName, 'R', 'U', 'A',.true.,ierr)
call wchk_int(iDataFile, "natom", natom, fail)
call wchk_iarray(iDataFile, "iattype", natom, 1, 1, quick_molspec%iattype, fail)
call wchk_darray(iDataFile, "xyz", 3, natom, 1, quick_molspec%xyz, fail)
close(iDataFile)
endif
endif
endif

if (.not.quick_method%opt .and. quick_method%grad) then
Expand Down
4 changes: 2 additions & 2 deletions src/modules/quick_api_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -62,8 +62,8 @@ module quick_api_module
double precision, allocatable, dimension(:,:) :: ptchg_crd

! job card for quick job, essentially the first line of regular quick input file
! default length is 256 characters
character(len=256) :: keywd
! default length is 300 characters
character(len=300) :: keywd

! Is the job card provided by passing a string? default is false
logical :: hasKeywd = .false.
Expand Down
6 changes: 4 additions & 2 deletions src/modules/quick_files_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -204,11 +204,13 @@ subroutine read_basis_file(keywd,ierr)

i = index(keywd,'BASIS=',.false.)

j = scan(keywd(i:lenkwd),' ',.false.)
! j = scan(keywd(i:lenkwd),' ',.false.)
j = scan(keywd(i+6:),' ',.false.)

basis_sets=trim(basisdir) // "/basis_link"

basisSetName = keywd(i+6:i+j-2)
! basisSetName = keywd(i+6:i+j-2)
basisSetName = keywd(i+6:i+5+j)
search_keywd= "#" // trim(basisSetName)
! Check if the basis_link file exists

Expand Down
21 changes: 18 additions & 3 deletions src/modules/quick_method_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,9 @@ module quick_method_module
logical :: nodirect = .false. ! conventional scf
logical :: readDMX = .false. ! flag to read density matrix
logical :: readden = .false. ! flag to read density matrix
logical :: read_coord = .false. ! flag to read coordinates
logical :: writeden = .false. ! flag to write density matrix
logical :: writexyz = .false. ! flag to write coordinates
logical :: readSAD = .true. ! flag to read SAD guess
logical :: writeSAD = .false. ! flag to write SAD guess
logical :: diisSCF = .false. ! DIIS SCF
Expand Down Expand Up @@ -248,7 +250,9 @@ subroutine broadcast_quick_method(self, ierr)
call MPI_BCAST(self%gridspacing,1,mpi_double_precision,0,MPI_COMM_WORLD,mpierror)
call MPI_BCAST(self%lapGridSpacing,1,mpi_double_precision,0,MPI_COMM_WORLD,mpierror)
call MPI_BCAST(self%readden,1,mpi_logical,0,MPI_COMM_WORLD,mpierror)
call MPI_BCAST(self%read_coord,1,mpi_logical,0,MPI_COMM_WORLD,mpierror)
call MPI_BCAST(self%writeden,1,mpi_logical,0,MPI_COMM_WORLD,mpierror)
call MPI_BCAST(self%writexyz,1,mpi_logical,0,MPI_COMM_WORLD,mpierror)
call MPI_BCAST(self%extCharges,1,mpi_logical,0,MPI_COMM_WORLD,mpierror)
call MPI_BCAST(self%ext_grid,1,mpi_logical,0,MPI_COMM_WORLD,mpierror)
call MPI_BCAST(self%extgrid_angstrom,1,mpi_logical,0,MPI_COMM_WORLD,mpierror)
Expand Down Expand Up @@ -424,8 +428,10 @@ subroutine print_quick_method(self,io,ierr)
if (self%printEnergy) write(io,'(" PRINT ENERGY EVERY CYCLE")')

if (self%readDMX) write(io,'(" READ DENSITY MATRIX FROM FILE")')
if (self%read_coord) write(io,'(" READ COORDINATES From DATAFILE")')
if (self%readden) write(io,'(" READ DENSITY MATRIX From DATAFILE")')
if (self%writeden) write(io,'(" WRITE DENSITY MATRIX TO FILE")')
if (self%writeden) write(io,'(" WRITE DENSITY MATRIX TO DATA FILE")')
if (self%writexyz) write(io,'(" WRITE COORDINATES TO DATA FILE")')
if (self%readSAD) write(io,'(" READ SAD GUESS FROM FILE")')
if (self%writeSAD) write(io,'(" WRITE SAD GUESS TO FILE")')

Expand Down Expand Up @@ -656,7 +662,11 @@ subroutine read_quick_method(self,keywd,ierr)
end if
if (index(keyWD,'ZMAKE').ne.0) self%zmat=.true.
if (index(keyWD,'DIPOLE').ne.0) self%dipole=.true.
if (index(keyWD,'WRITE').ne.0) self%writeden=.true.
if (index(keyWD,'WRITE').ne.0)then
self%writeden=.true.
self%writexyz=.true.
end if

if (index(keyWD,'EXTCHARGES').ne.0) self%EXTCHARGES=.true.
if (index(keyWD,'EXTGRID').ne.0) self%ext_grid=.true.
!if (index(keyWD,'EXTGRID_ANGSTROM').ne.0) self%extgrid_angstrom=.true.
Expand All @@ -680,6 +690,9 @@ subroutine read_quick_method(self,keywd,ierr)
!Read density matrix
if (index(keyWD,'READDEN').ne.0) self%readden=.true.

!Read coordinates
if (index(keyWD,'READ_COORD').ne.0) self%read_coord=.true.

if (self%DFT) then
if (index(keyWD,'SG0').ne.0) then
self%iSG=0
Expand Down Expand Up @@ -899,7 +912,9 @@ subroutine init_quick_method(self,ierr)
self%calcDens = .false. ! calculate density
self%calcDensLap = .false. ! calculate density lap
self%readden = .false. ! Input density matrix
self%writeden = .false. ! Output density matrix
self%read_coord = .false. ! Input coordinates
self%writeden = .false. ! Write density matrix to data file
self%writexyz = .false. ! Write coordinates to data file
self%extCharges = .false. ! external charge
self%ext_grid = .false. ! external grid points
self%extgrid_angstrom = .false. ! external grid points (same as above) output in angstrom
Expand Down
171 changes: 94 additions & 77 deletions src/modules/quick_molspec_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -325,8 +325,13 @@ subroutine read_quick_molspec(self,input,isTemplate, hasKeywd, apiKeywd,ierr)

use quick_constants_module
use quick_exception_module
use quick_method_module, only: quick_method
use quick_files_module, only : iDataFile, dataFileName

implicit none

integer :: fail

type (quick_molspec_type) :: self
integer, intent(inout) :: ierr
integer :: input,rdinml,i,j,k
Expand All @@ -335,13 +340,14 @@ subroutine read_quick_molspec(self,input,isTemplate, hasKeywd, apiKeywd,ierr)
integer :: nextatom
integer :: nextpoint
double precision :: temp,rdnml
character(len=200) :: keywd
character(len=300) :: keywd
character(len=300) :: tempstring
logical :: is_extcharge = .false.
logical :: is_extgrid = .false.
logical :: is_blank
logical, intent(in) :: isTemplate
logical, intent(in) :: hasKeywd
character(len=200), intent(in) :: apikeywd
character(len=300), intent(in) :: apikeywd

!---------------------
! PART I
Expand All @@ -350,12 +356,19 @@ subroutine read_quick_molspec(self,input,isTemplate, hasKeywd, apiKeywd,ierr)

if( .not. hasKeywd ) then
rewind(input)
read (input,'(A132)') keywd
keyWD(:)=''
do while(.true.)
read (input,'(A300)') tempstring
if(trim(tempstring).eq.'') exit
if(tempstring(1:1).ne.'$')then
keyWD=trim(keyWD)//' '//trim(tempstring)
endif
enddo
else
keywd = apikeywd
endif

call upcase(keywd,200)
call upcase(keywd,300)

! Read Charge
if (index(keywd,'CHARGE=') /= 0) self%molchg = rdinml(keywd,'CHARGE')
Expand All @@ -379,85 +392,89 @@ subroutine read_quick_molspec(self,input,isTemplate, hasKeywd, apiKeywd,ierr)

if( .not. isTemplate) then

call findBlock(input,1)

! first is to read atom and atom kind
iAtomType = 1
natom = 0
nextatom = 0
nextpoint = 0
do
read(input,'(A80)',end=111,err=111) keywd
i=1;j=80
call upcase(keywd,80)
call rdword(keywd,i,j)
if (is_blank(keywd,1,80)) exit

do k=0,92
if (keywd(i:j) == symbol(k)) then
natom=natom+1
! check if atom type has been shown before
if (.not.(any(self%atom_type_sym(1:iatomtype).eq.symbol(k)))) then
!write(*,*) "Assigning value to atom_type_sym:", k, symbol(k)
self%atom_type_sym(iAtomType)=symbol(k)
iAtomType=iAtomType+1
endif
endif
enddo
enddo

111 continue

! ! read external charge part
! if (is_extcharge) then
! rewind(input)
! call findBlock(input,2)
! do
! read(input,'(A80)',end=112,err=112) keywd
! if (is_blank(keywd,1,80)) exit
! nextatom=nextatom+1
! enddo
! endif

! read external charge part
if (is_extcharge) then
rewind(input)
call findBlock(input,2)
do
read(input,'(A80)',end=112,err=112) keywd
if (is_blank(keywd,1,80)) exit
nextatom = nextatom + 1
! If reading from data file
if(quick_method%read_coord)then

open(unit=iDataFile,file=dataFileName,status='OLD',form='UNFORMATTED')
call rchk_int(iDataFile, "natom", natom, fail)
if (.not. allocated(self%iattype)) allocate(self%iattype(natom))
call rchk_iarray(iDataFile, "iattype", natom, 1, 1, self%iattype, fail)
close(iDataFile)

! Reading external charges from data file is not yet implemented
nextatom = 0
self%nextatom = nextatom

iAtomType = 0

do i = 1, natom
if (.not.(any(self%atom_type_sym(1:iAtomType).eq.symbol(self%iattype(i))))) then
iAtomType=iAtomType+1
self%atom_type_sym(iAtomType) = symbol(self%iattype(i))
endif
enddo
endif

! read external grid part
if (is_extgrid) then
rewind(input)
call findBlock(input,2)

self%iAtomType = iAtomType

! Reading from input file
else
call findBlock(input,1)

! first is to read atom and atom kind
iAtomType = 1
natom = 0
nextatom = 0
nextpoint = 0
do
read(input,'(A80)',end=112,err=112) keywd
if (is_blank(keywd,1,80)) exit
nextpoint = nextpoint + 1
read(input,'(A80)',end=111,err=111) keywd
i=1;j=80
call upcase(keywd,80)
call rdword(keywd,i,j)
if (is_blank(keywd,1,80)) exit
do k=0,92
if (keywd(i:j) == symbol(k)) then
natom=natom+1
! check if atom type has been shown before
if (.not.(any(self%atom_type_sym(1:iatomtype).eq.symbol(k)))) then
!write(*,*) "Assigning value to atom_type_sym:", k, symbol(k)
self%atom_type_sym(iAtomType)=symbol(k)
iAtomType=iAtomType+1
endif
endif
enddo
enddo
endif
111 continue

! 112 continue
! read external charge part
if (is_extcharge) then
rewind(input)
call findBlock(input,2)
do
read(input,'(A80)',end=112,err=112) keywd
if (is_blank(keywd,1,80)) exit
nextatom=nextatom+1
enddo
endif

! iAtomType=iAtomType-1
! self%iAtomType = iAtomType
! self%nextatom = nextatom
! endif
112 continue
! read external grid part
if (is_extgrid) then
rewind(input)
call findBlock(input,2)
do
read(input,'(A80)',end=112,err=112) keywd
if (is_blank(keywd,1,80)) exit
nextpoint = nextpoint + 1
enddo
endif

iAtomType = iAtomType - 1
self%iAtomType = iAtomType
self%nextatom = nextatom
112 continue

! Check if the external grid part was processed
if (is_extgrid) then
iAtomType=iAtomType-1
self%iAtomType = iAtomType
self%nextatom = nextatom
self%nextpoint = nextpoint
endif
endif
endif
endif

end subroutine read_quick_molspec

Expand All @@ -477,7 +494,7 @@ subroutine read_quick_molspec_2(self,input,ierr)
integer i,j,k,istart,ifinal
integer ierror
double precision temp
character(len=200) keywd
character(len=300) keywd


rewind(input)
Expand Down Expand Up @@ -537,7 +554,7 @@ subroutine read_quick_molespec_extcharges(self,input,ierr)
integer i,j,k,istart,ifinal
integer nextatom,ierror
double precision temp
character(len=200) keywd
character(len=300) keywd

rewind(input)
call findBlock(input,2)
Expand Down
1 change: 1 addition & 0 deletions src/modules/quick_sad_guess_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,7 @@ subroutine getmolsad(ierr)
quick_method%ZMAT=.false.
quick_method%divcon=.false.
quick_method%nodirect=.false.

call allocate_mol_sad(quick_molspec%iatomtype)


Expand Down
Loading

0 comments on commit 67ca0de

Please sign in to comment.