Skip to content

Commit

Permalink
Clean up
Browse files Browse the repository at this point in the history
  • Loading branch information
Thomas3R committed Dec 13, 2023
1 parent 209a468 commit 0b2fc39
Show file tree
Hide file tree
Showing 3 changed files with 7 additions and 15 deletions.
12 changes: 1 addition & 11 deletions src/gfnff/gfnff_eg.f90
Original file line number Diff line number Diff line change
Expand Up @@ -142,7 +142,6 @@ subroutine gfnff_eg(env,mol,pr,n,ichrg,at,xyz,sigma,g,etot,res_gff, &
implicit none

character(len=*), parameter :: source = 'gfnff_eg'
real(wp),allocatable :: transVec(:,:)
real(wp),allocatable :: rec_tVec(:,:)
type(TNeigh), intent(inout) :: neigh ! main type for introducing PBC
type(dftd_parameter) :: disp_par, mcdisp_par
Expand Down Expand Up @@ -221,15 +220,6 @@ subroutine gfnff_eg(env,mol,pr,n,ichrg,at,xyz,sigma,g,etot,res_gff, &
neigh%oldCutOff=0.0_wp
call neigh%getTransVec(mol,60.0_wp)

if (mol%boundaryCondition.ne.0) then
if(size(transVec,dim=2).le.neigh%numctr)then
! want at least 27 cells
if(allocated(transVec)) deallocate(transVec)
allocate(transVec(3,neigh%numctr))
transVec=neigh%transVec(:,1:neigh%numctr)
endif
endif

! get Distances between atoms for repulsion
call neigh%getTransVec(mol,sqrt(repthr))
if(allocated(neigh%distances)) deallocate(neigh%distances)
Expand Down Expand Up @@ -346,7 +336,7 @@ subroutine gfnff_eg(env,mol,pr,n,ichrg,at,xyz,sigma,g,etot,res_gff, &

if (pr) call timer%measure(2,'non bonded repulsion')
!$omp parallel do default(none) reduction(+:erep, g, sigma) &
!$omp shared(n, at, xyz, srab, sqrab, transVec, repthr, &
!$omp shared(n, at, xyz, srab, sqrab, repthr, &
!$omp topo, param, neigh, mcf_nrep) &
!$omp private(iat, jat, iTr, iTrDum, m, ij, ati, atj, rab, r2, r3, vec, t8, t16, t19, t26, t27)
do iat=1,n
Expand Down
6 changes: 4 additions & 2 deletions src/gfnff/neighbor.f90
Original file line number Diff line number Diff line change
Expand Up @@ -183,8 +183,10 @@ subroutine getTransVec(self,mol,cutoff)

! lattice might change during optimization. Therefore d might change
! between different runs and trVecInt needs to be adjusted.
if(allocated(self%trVecInt).and.size(self%trVecInt,dim=2).lt.d) then
deallocate(self%trVecInt)
if(allocated(self%trVecInt)) then
if(size(self%trVecInt,dim=2).lt.d) then
deallocate(self%trVecInt)
endif
endif

! get the linear combination coefficient vector
Expand Down
4 changes: 2 additions & 2 deletions test/unit/molstock.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1134,7 +1134,7 @@ end subroutine fe_cnx6
subroutine x06_benzene(mol)
type(TMolecule), intent(out) :: mol
integer, parameter :: nat = 48
character(len=*), parameter :: sym(nat) = [character(len=1) ::&
character(len=*), parameter :: sym(nat) = [character(len=4) ::&
& "C", "C", "C", "C", "C", "C", "C", "C", "C", "C", &
& "C", "C", "C", "C", "C", "C", "C", "C", "C", "C", &
& "C", "C", "C", "C", "H", "H", "H", "H", "H", "H", &
Expand Down Expand Up @@ -1203,7 +1203,7 @@ end subroutine x06_benzene
subroutine mcv15(mol)
type(TMolecule), intent(out) :: mol
integer, parameter :: nat = 64
character(len=*), parameter :: sym(nat) = [character(len=2) :: &
character(len=*), parameter :: sym(nat) = [character(len=4) :: &
& "S", "S", "P", "P", "O", "O", "O", "O", "N", "N", "N", "N", &
& "C", "C", "C", "C", "C", "C", "C", "C", "C", "C", "C", "C", &
& "C", "C", "C", "C", "C", "C", "C", "C", "C", "C", "H", "H", &
Expand Down

0 comments on commit 0b2fc39

Please sign in to comment.