Skip to content

Commit

Permalink
Nicer exit status handling (not yet refactored for entire code, but s…
Browse files Browse the repository at this point in the history
…ome important bits)
  • Loading branch information
pprcht committed Oct 10, 2024
1 parent 5467bdf commit 65e5140
Show file tree
Hide file tree
Showing 20 changed files with 189 additions and 60 deletions.
5 changes: 4 additions & 1 deletion src/algos/dynamics.f90
Original file line number Diff line number Diff line change
Expand Up @@ -69,9 +69,11 @@ subroutine crest_moleculardynamics(env,tim)
!>--- check if we have any MD & calculation settings allocated
if (.not. mddat%requested) then
write (stdout,*) 'MD requested, but no MD settings present.'
env%iostatus_meta = status_config
return
else if (calc%ncalculations < 0) then
write (stdout,*) 'MD requested, but no calculation settings present.'
env%iostatus_meta = status_config
return
end if

Expand Down Expand Up @@ -99,7 +101,8 @@ subroutine crest_moleculardynamics(env,tim)
write (stdout,*) 'MD run completed successfully'
write (stdout,*) 'Trajectory written to ',trjf
else
write (stdout,*) 'MD run terminated with error'
write (stdout,*) 'WARNING: MD run terminated ABNORMALLY'
env%iostatus_meta = status_failed
end if
!========================================================================================!
call tim%stop(14)
Expand Down
5 changes: 4 additions & 1 deletion src/algos/numhess.f90
Original file line number Diff line number Diff line change
Expand Up @@ -162,6 +162,8 @@ subroutine crest_numhess(env,tim)
write (stdout,*) 'At least two calculation level must be'
write (stdout,*) 'given for the calculation of the effective Hessian.'
write (stdout,*)
env%iostatus_meta = status_config
return

end if

Expand Down Expand Up @@ -388,7 +390,8 @@ subroutine thermo_standalone(env)
write(stdout,'(1x,a,a)') 'Reading frequencies from: ',trim(env%thermo%vibfile)
call rdfreq(env%thermo%vibfile,nat3,freq)
else
error stop 'No Hessian or vibspectrum file allocated for thermo routine!'
write(stdout,'(1x,a)') 'No Hessian or vibspectrum file allocated for thermo routine!'
call creststop(status_input)
endif
write(stdout,*)

Expand Down
23 changes: 17 additions & 6 deletions src/algos/optimization.f90
Original file line number Diff line number Diff line change
Expand Up @@ -98,6 +98,7 @@ subroutine crest_optimization(env,tim)
close (ich)
else
write (stdout,*) 'geometry optimization FAILED!'
env%iostatus_meta = status_failed
endif

write (stdout,*)
Expand Down Expand Up @@ -169,7 +170,8 @@ subroutine crest_ensemble_optimization(env,tim)
if (ex) then
ensnam = env%ensemblename
else
write (stdout,*) 'no ensemble file provided.'
write (stdout,*) '**ERROR** no ensemble file provided.'
env%iostatus_meta = status_input
return
end if

Expand All @@ -178,7 +180,11 @@ subroutine crest_ensemble_optimization(env,tim)

!>---- read the input ensemble
call rdensembleparam(ensnam,nat,nall)
if (nall .lt. 1) return
if (nall .lt. 1)then
write (stdout,*) '**ERROR** empty ensemble file.'
env%iostatus_meta = status_input
return
endif
allocate (xyz(3,nat,nall),at(nat),eread(nall))
call rdensemble(ensnam,nat,nall,at,xyz,eread)
!>>>>>>>>>>>>>>>>>>>>>>>>>>>><<<<<<<<<<<<<<<<<<<<<<<<<<<<<!
Expand Down Expand Up @@ -275,7 +281,8 @@ subroutine crest_ensemble_screening(env,tim)
if (ex) then
ensnam = env%ensemblename
else
write (stdout,*) 'no ensemble file provided.'
write (stdout,*) '**ERROR** no ensemble file provided.'
env%iostatus_meta = status_input
return
end if

Expand All @@ -284,8 +291,11 @@ subroutine crest_ensemble_screening(env,tim)

!>---- read the input ensemble
call rdensembleparam(ensnam,nat,nall)
if (nall .lt. 1) return

if (nall .lt. 1)then
write (stdout,*) '**ERROR** empty ensemble file.'
env%iostatus_meta = status_input
return
endif
!>--- set OMP parallelization
call new_ompautoset(env,'auto',nall,T,Tn)

Expand All @@ -305,7 +315,8 @@ subroutine crest_ensemble_screening(env,tim)
call rmrfw('crest_rotamers_')
call optlev_to_multilev(3.0d0,multilevel)
call crest_multilevel_oloop(env,ensnam,multilevel)

if(env%iostatus_meta .ne. 0 ) return

!>--- printout
call catdel('cregen.out.tmp')
write (stdout,'(/,1x,a,1x,a)') 'Final ensemble on file','<'//trim(ensemblefile)//'>'
Expand Down
9 changes: 6 additions & 3 deletions src/algos/protonate.f90
Original file line number Diff line number Diff line change
Expand Up @@ -149,6 +149,7 @@ subroutine crest_new_protonate(env,tim)
write (stdout,*) 'WARNING: No suitable protonation sites found!'
write (stdout,*) ' Confirm whether you expect π- or LP-centers for your molecule!'
write (stdout,*)
env%iostatus_meta = status_failed
return
end if
deallocate (tmpcalc)
Expand Down Expand Up @@ -176,6 +177,7 @@ subroutine crest_new_protonate(env,tim)
write (stdout,*)
write (stdout,'(a)') '> WARNING: No remaining protonation sites after applying user defined conditions!'
write (stdout,'(a)') '> Modify the search criteria and check your input structure for sanity.'
env%iostatus_meta = status_failed
return
end if

Expand Down Expand Up @@ -368,7 +370,7 @@ subroutine protonation_candidates(env,mol,natp,np,protxyz,at,xyz,npnew)

if (natp .ne. mol%nat+env%protb%amount) then
write (stdout,'(a)') 'WARNING: Inconsistent number of atoms in protonation routine'
error stop
call creststop(status_args)
end if

if (env%protb%swelem) then
Expand Down Expand Up @@ -902,7 +904,7 @@ subroutine deprotonation_candidates(env,mol,natp,np,at,xyz,npnew)

if (natp .ne. mol%nat-env%protb%amount) then
write (stdout,'(a)') 'WARNING: Inconsistent number of atoms in deprotonation routine'
error stop
call creststop(status_args)
end if

if (env%protb%swelem) then
Expand Down Expand Up @@ -1114,6 +1116,7 @@ subroutine crest_new_tautomerize(env,tim)
write (stdout,*) 'WARNING: No suitable protonation sites found!'
write (stdout,*) ' Confirm whether you expect π- or LP-centers for your molecule!'
write (stdout,*)
env%iostatus_meta = status_failed
return
end if
deallocate (tmpcalc)
Expand Down Expand Up @@ -1340,7 +1343,7 @@ subroutine tautomer_candidates(env,mol,natp,npadd,npremove,protxyz,at,xyz,npnew)

if (natp .ne. mol%nat) then
write (stdout,'(a)') 'WARNING: Inconsistent number of atoms in protonation routine'
error stop
call creststop(status_args)
end if

ati = 1 !> always refer to Hydrogen for tautomers
Expand Down
3 changes: 2 additions & 1 deletion src/algos/search_1.f90
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,8 @@ subroutine crest_search_1(env,tim)
!>--- read ensemble
call rdensembleparam(ensnam,nat,nall)
if (nall .lt. 1) then
write(stdout,*) 'empty ensemble file'
write(stdout,*) '**ERROR** empty ensemble file'
env%iostatus_meta = status_failed
return
endif
allocate (xyz(3,nat,nall),at(nat),eread(nall))
Expand Down
24 changes: 18 additions & 6 deletions src/algos/search_conformers.f90
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,7 @@ subroutine crest_search_imtdgc(env,tim)
call tim%start(1,'Trial metadynamics (MTD)')
call trialmd(env)
call tim%stop(1)
if(env%iostatus_meta .ne. 0 ) return
end if

!===========================================================!
Expand Down Expand Up @@ -134,6 +135,7 @@ subroutine crest_search_imtdgc(env,tim)
call optlev_to_multilev(env%optlev,multilevel)
call crest_multilevel_oloop(env,ensnam,multilevel)
call tim%stop(3)
if(env%iostatus_meta .ne. 0 ) return

!>--- save the CRE under a backup name
call checkname_xyz(crefile,atmp,str)
Expand Down Expand Up @@ -186,6 +188,7 @@ subroutine crest_search_imtdgc(env,tim)
call tim%start(4,'Molecular dynamics (MD)')
call crest_rotamermds(env,conformerfile)
call tim%stop(4)
if(env%iostatus_meta .ne. 0 ) return

!>--- Reoptimization of trajectories
call checkname_xyz(crefile,atmp,btmp)
Expand All @@ -195,6 +198,7 @@ subroutine crest_search_imtdgc(env,tim)
call tim%start(3,'Geometry optimization')
call crest_multilevel_wrap(env,trim(atmp),-1)
call tim%stop(3)
if(env%iostatus_meta .ne. 0 ) return

call elowcheck(lower,env)
if (lower) then
Expand All @@ -211,6 +215,8 @@ subroutine crest_search_imtdgc(env,tim)
call tim%start(5,'Genetic crossing (GC)')
call crest_newcross3(env)
call tim%stop(5)
if(env%iostatus_meta .ne. 0 ) return

call confg_chk3(env)
call elowcheck(lower,env)
if (lower) then
Expand All @@ -236,6 +242,7 @@ subroutine crest_search_imtdgc(env,tim)
call checkname_xyz(crefile,atmp,str)
call crest_multilevel_wrap(env,trim(atmp),0)
call tim%stop(3)
if(env%iostatus_meta .ne. 0 ) return

!==========================================================!
!>--- final ensemble sorting
Expand Down Expand Up @@ -357,7 +364,8 @@ end subroutine crest_refine
!>--- read ensemble
call rdensembleparam(ensnam,nat,nall)
if (nall .lt. 1) then
write(stdout,*) 'empty ensemble file ',trim(ensnam)
write(stdout,*) '**ERROR** empty ensemble file ',trim(ensnam)
env%iostatus_meta = status_failed
return
endif
allocate (xyz(3,nat,nall),at(nat),eread(nall))
Expand Down Expand Up @@ -389,8 +397,9 @@ end subroutine crest_refine
!>--- check for empty ensemble content
call rdensembleparam(trim(inpnam),nat,nall)
if (nall .lt. 1) then
write(stdout,*) 'empty ensemble file',trim(inpnam)
stop
write(stdout,*) '**ERROR** empty ensemble file',trim(inpnam)
env%iostatus_meta = status_failed
return
endif

write(stdout,*)
Expand All @@ -405,8 +414,9 @@ end subroutine crest_refine
!>--- check for empty ensemble content (again)
call rdensembleparam(trim(inpnam),nat,nall)
if (nall .lt. 1) then
write(stdout,*) 'empty ensemble file',trim(inpnam)
stop
write(stdout,*) '**ERROR** empty ensemble file',trim(inpnam)
env%iostatus_meta = status_failed
return
endif
!>--- read new ensemble for next iteration
allocate (xyz(3,nat,nall),at(nat),eread(nall))
Expand Down Expand Up @@ -508,7 +518,8 @@ subroutine crest_rotamermds(env,ensnam)
call env%ref%to(mol)
call rdensembleparam(ensnam,nat,nall)
if (nall .lt. 1) then
write(stdout,*) 'empty ensemble file',trim(ensnam)
write(stdout,*) '**ERROR** empty ensemble file',trim(ensnam)
env%iostatus_meta = status_failed
return
endif

Expand Down Expand Up @@ -615,6 +626,7 @@ subroutine crest_newcross3(env)
multilevel(4) = .true.
end if
call crest_multilevel_oloop(env,'confcross.xyz',multilevel)
if(env%iostatus_meta .ne. 0 ) return

!>-- append optimized crossed structures and original to a single file
call checkname_xyz(crefile,inpnam,outnam)
Expand Down
12 changes: 10 additions & 2 deletions src/algos/search_entropy.f90
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,7 @@ subroutine crest_search_entropy(env,tim)
call tim%start(1,'Trial metadynamics (MTD)')
call trialmd(env)
call tim%stop(1)
if(env%iostatus_meta .ne. 0) return
end if

!===========================================================!
Expand Down Expand Up @@ -140,6 +141,7 @@ subroutine crest_search_entropy(env,tim)
call optlev_to_multilev(env%optlev,multilevel)
call crest_multilevel_oloop(env,ensnam,multilevel)
call tim%stop(3)
if(env%iostatus_meta .ne. 0 ) return

!>--- save the CRE under a backup name
call checkname_xyz(crefile,atmp,str)
Expand Down Expand Up @@ -210,6 +212,7 @@ subroutine crest_search_entropy(env,tim)
!>-- start from the current crest_conformers.xyz
call crest_smtd_mds(env,conformerfile)
call tim%stop(6)
if(env%iostatus_meta .ne. 0) return
call emtdcheckempty(env,fail,env%emtd%nbias)

if (fail) then
Expand All @@ -226,6 +229,7 @@ subroutine crest_search_entropy(env,tim)
multilevel = (/.true.,.false.,.false.,.false.,.false.,.true./)
call crest_multilevel_oloop(env,trim(atmp),multilevel)
call tim%stop(3)
if(env%iostatus_meta .ne. 0 ) return

!>--- if in the entropy mode a lower structure was found -> cycle (required for extrapolation)
call elowcheck(lower,env)
Expand Down Expand Up @@ -311,7 +315,8 @@ subroutine crest_smtd_mds(env,ensnam)
call env%ref%to(mol)
call rdensembleparam(ensnam,nat,nall)
if (nall .lt. 1) then
write (stdout,*) 'empty ensemble file',trim(ensnam)
write (stdout,*) '**ERROR** empty ensemble file',trim(ensnam)
env%iostatus_meta = status_failed
return
end if

Expand Down Expand Up @@ -449,7 +454,10 @@ subroutine crest_init_multimd_smtd(env,mddats,nsim,biasfile)

!>--- load static bias stuctures
inquire (file=biasfile,exist=ex)
if (.not.ex) error stop 'Could not initialize static metadynamics'
if (.not.ex)then
write(stdout,'(a,a)') 'Could not initialize static metadynamics: missing ',trim(biasfile)
call creststop(status_input)
endif
call rdensembleparam(biasfile,nat,nall)
allocate (xyz(3,nat,nall),at(nat),eread(nall))
call rdensemble(biasfile,nat,nall,at,xyz,eread)
Expand Down
10 changes: 6 additions & 4 deletions src/algos/search_mecp.f90
Original file line number Diff line number Diff line change
Expand Up @@ -50,8 +50,9 @@ subroutine crest_search_mecp(env,tim)
!>--- check calculation setup
ex = env%calc%ncalculations > 1
if (.not.ex) then
write (stdout,*) 'not enough calculation levels specified for MECP search.'
error stop
write (stdout,*) '**ERROR** Not enough calculation levels specified for MECP search.'
env%iostatus_meta = status_config
return
end if
call print_gapcons(env%calc)

Expand Down Expand Up @@ -120,6 +121,7 @@ end subroutine crest_search_mecp

subroutine print_gapcons(calc)
use crest_parameters
use crest_data
use crest_calculator
implicit none

Expand Down Expand Up @@ -152,8 +154,8 @@ subroutine print_gapcons(calc)
end do

if (.not.ex) then
write (stdout,*) 'no gap constraint provided'
error stop
write (stdout,*) '**ERROR** no gap constraint provided'
call creststop(status_config)
else
write (stdout,*)
end if
Expand Down
3 changes: 3 additions & 0 deletions src/algos/search_newnci.f90
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ subroutine crest_search_newnci(env,tim)
call tim%start(1,'Trial metadynamics (MTD)')
call trialmd(env)
call tim%stop(1)
if(env%iostatus_meta .ne. 0 ) return
end if

!===========================================================!
Expand Down Expand Up @@ -131,6 +132,7 @@ subroutine crest_search_newnci(env,tim)
call optlev_to_multilev(env%optlev,multilevel)
call crest_multilevel_oloop(env,ensnam,multilevel)
call tim%stop(3)
if(env%iostatus_meta .ne. 0 ) return

!>--- save the CRE under a backup name
call checkname_xyz(crefile,atmp,str)
Expand Down Expand Up @@ -192,6 +194,7 @@ subroutine crest_search_newnci(env,tim)
call checkname_xyz(crefile,atmp,str)
call crest_multilevel_wrap(env,trim(atmp),0)
call tim%stop(3)
if(env%iostatus_meta .ne. 0 ) return

!==========================================================!
!>--- print CREGEN results and clean up Directory a bit
Expand Down
Loading

0 comments on commit 65e5140

Please sign in to comment.