Skip to content

Commit

Permalink
Fix multilevel activation for MD (#350)
Browse files Browse the repository at this point in the history
  • Loading branch information
pprcht authored Sep 27, 2024
2 parents 5ca82fe + c8893c4 commit a71e303
Show file tree
Hide file tree
Showing 3 changed files with 42 additions and 6 deletions.
4 changes: 1 addition & 3 deletions src/algos/dynamics.f90
Original file line number Diff line number Diff line change
Expand Up @@ -81,14 +81,12 @@ subroutine crest_moleculardynamics(env,tim)
!>--- init SHAKE? --> we need connectivity info
if (mddat%shake) then
calc%calcs(1)%rdwbo = .true.
if(.not.calc%calcs(1)%active) calc%calcs(1)%active=.true.
allocate (grad(3,mol%nat),source=0.0_wp)
call engrad(mol,calc,energy,grad,io)
deallocate (grad)
calc%calcs(1)%rdwbo = .false.
call move_alloc(calc%calcs(1)%wbo,mddat%shk%wbo)
!> moved to within the MD call
!call init_shake(mol%nat,mol%at,mol%xyz,mddat%shk,pr)
!mddat%nshake = mddat%shk%ncons
end if

!>--- complete real-time settings to steps
Expand Down
13 changes: 10 additions & 3 deletions src/calculator/calc_type.f90
Original file line number Diff line number Diff line change
Expand Up @@ -203,6 +203,7 @@ module calc_type
real(wp),allocatable :: grdtmp(:,:,:)
real(wp),allocatable :: eweight(:)
real(wp),allocatable :: weightbackup(:)
logical,allocatable :: activebackup(:)
real(wp),allocatable :: etmp2(:)
real(wp),allocatable :: grdtmp2(:,:,:)
real(wp),allocatable :: eweight2(:)
Expand Down Expand Up @@ -640,18 +641,23 @@ subroutine calc_set_active(self,ids)
integer,intent(in) :: ids(:)
integer :: i,j,k,l
if (allocated(self%weightbackup)) deallocate (self%weightbackup)
if (allocated(self%activebackup)) deallocate (self%activebackup)
!>--- on-the-fly multiscale definition
allocate (self%weightbackup(self%ncalculations),source=1.0_wp)
allocate (self%activebackup(self%ncalculations),source=.true.)
do i = 1,self%ncalculations
!>--- save backup weights
self%weightbackup(i) = self%calcs(i)%weight
self%activebackup(i) = self%calcs(i)%active
!>--- set the weight of all unwanted calculations to 0
if (.not.any(ids(:) .eq. i)) then
self%calcs(i)%weight = 0.0_wp
self%calcs(i)%active = .false.
else
!>--- and all other to 1
self%calcs(i)%weight = 1.0_wp
!>--- and all other to active
if(self%calcs(i)%weight == 0.0_wp)then
self%calcs(i)%weight = 1.0_wp
endif
self%calcs(i)%active = .true.
end if
end do
Expand All @@ -662,10 +668,11 @@ subroutine calc_set_active_restore(self)
class(calcdata) :: self
integer :: i,j,k,l
if (.not.allocated(self%weightbackup)) return
if (.not.allocated(self%activebackup)) return
do i = 1,self%ncalculations
!>--- set all to active and restore saved weights
self%calcs(i)%weight = self%weightbackup(i)
self%calcs(i)%active = .true.
self%calcs(i)%active = self%activebackup(i)
self%eweight(i) = self%weightbackup(i)
end do
deallocate (self%weightbackup)
Expand Down
31 changes: 31 additions & 0 deletions src/parsing/confparse2.f90
Original file line number Diff line number Diff line change
Expand Up @@ -109,6 +109,7 @@ subroutine parseinputfile(env,fname)
call parse_dynamics_data(env,mddat,dict,l1,readstatus)
if (l1) then
env%mddat = mddat
call env_mddat_specialcases(env)
end if

!>--- terminate if there were any unrecognized keywords
Expand Down Expand Up @@ -212,3 +213,33 @@ subroutine env_calcdat_specialcases(env)
end if

end subroutine env_calcdat_specialcases

!========================================================================================!

subroutine env_mddat_specialcases(env)
!****************************************************
!* Some special treatments are sometimes necessary
!* depending on a choosen calculation level,
!* e.g. for on-the-fly multilevel setup
!* These depend on both the calc data and md data
!***************************************************
use crest_parameters
use crest_data
use crest_calculator
implicit none
type(systemdata) :: env
integer :: nac,ii,iac

!>--- Check for MD-active only levels
if(allocated(env%mddat%active_potentials))then
nac = size(env%mddat%active_potentials)
do ii=1,nac
!>--- deactivate by default (the MD routine will set them to active automatically)
iac = env%mddat%active_potentials(ii)
if(iac <= env%calc%ncalculations)then
env%calc%calcs(iac)%active = .false.
endif
enddo
endif

end subroutine env_mddat_specialcases

0 comments on commit a71e303

Please sign in to comment.