Skip to content

Commit 7112c04

Browse files
authored
Safer toml input parsing (#325)
2 parents f1b6928 + c8c520e commit 7112c04

19 files changed

+1370
-1030
lines changed

src/algos/parallel.f90

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -225,16 +225,18 @@ end subroutine crest_sploop
225225
!========================================================================================!
226226
!========================================================================================!
227227
subroutine crest_oloop(env,nat,nall,at,xyz,eread,dump,customcalc)
228-
!***************************************************************
228+
!*******************************************************************************
229229
!* subroutine crest_oloop
230230
!* This subroutine performs concurrent geometry optimizations
231231
!* for the given ensemble. Inputs xyz and eread are overwritten
232232
!* env - contains parallelization and other program settings
233233
!* dump - decides on whether to dump an ensemble file
234+
!* WARNING: the ensemble file will NOT be in the same order
235+
!* as the input xyz array. However, the overwritten xyz will be!
234236
!* customcalc - customized (optional) calculation level data
235237
!*
236238
!* IMPORTANT: xyz should be in Bohr(!) for this routine
237-
!***************************************************************
239+
!******************************************************************************
238240
use crest_parameters,only:wp,stdout,sep
239241
use crest_calculator
240242
use omp_lib
@@ -369,6 +371,11 @@ subroutine crest_oloop(env,nat,nall,at,xyz,eread,dump,customcalc)
369371
end if
370372
eread(zcopy) = energy
371373
xyz(:,:,zcopy) = molsnew(job)%xyz(:,:)
374+
else if(io==calculations(job)%maxcycle .and. calculations(job)%anopt) then
375+
!>--- allow partial optimization?
376+
c = c+1
377+
eread(zcopy) = energy
378+
xyz(:,:,zcopy) = molsnew(job)%xyz(:,:)
372379
else
373380
eread(zcopy) = 1.0_wp
374381
end if

src/algos/protonate.f90

Lines changed: 208 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,7 @@ subroutine crest_new_protonate(env,tim)
3737
use optimize_module
3838
use parallel_interface
3939
use cregen_interface
40+
use iomod
4041
implicit none
4142
type(systemdata),intent(inout) :: env
4243
type(timer),intent(inout) :: tim
@@ -51,12 +52,14 @@ subroutine crest_new_protonate(env,tim)
5152
real(wp) :: energy,dip
5253
real(wp),allocatable :: grad(:,:)
5354
type(calcdata),allocatable :: tmpcalc
55+
type(calcdata),allocatable :: tmpcalc_ff
56+
type(calculation_settings) :: tmpset
5457
real(wp),allocatable :: protxyz(:,:)
55-
integer :: natp
58+
integer :: natp,pstep,npnew
5659
integer,allocatable :: atp(:)
57-
real(wp),allocatable :: xyzp(:,:,:)
60+
real(wp),allocatable :: xyzp(:,:,:)
5861
real(wp),allocatable :: ep(:)
59-
character(len=*),parameter :: partial = '∂E/∂'
62+
logical,allocatable :: atlist(:)
6063
!========================================================================================!
6164
write (stdout,*)
6265
!call system('figlet singlepoint')
@@ -68,10 +71,11 @@ subroutine crest_new_protonate(env,tim)
6871
write (stdout,*) "|_| "
6972
write (stdout,*) "-----------------------------------------------"
7073
write (stdout,*) " automated protonation site screening script "
74+
write (stdout,*) " revised version (c) P.Pracht 2024 "
7175
write (stdout,*) 'Cite as:'
72-
write (stdout,*) 'P.Pracht, C.A.Bauer, S.Grimme'
73-
write (stdout,*) 'JCC, 2017, 38, 2618–2631.'
74-
write (stdout,*)
76+
write (stdout,*) ' P.Pracht, C.A.Bauer, S.Grimme'
77+
write (stdout,*) ' JCC, 2017, 38, 2618–2631.'
78+
write (stdout,*)
7579

7680
!========================================================================================!
7781
call new_ompautoset(env,'max',0,T,Tn)
@@ -84,18 +88,22 @@ subroutine crest_new_protonate(env,tim)
8488
write (stdout,*)
8589
!========================================================================================!
8690
!>--- The first step is to perfom a LMO calculation to identify suitable protonation sites
91+
!>--- in this version of the program this step is always done with GFN0-xTB.
92+
8793
call tim%start(14,'LMO center calculation')
8894
write (stdout,'(a)') repeat('-',80)
8995
write (stdout,'(a)')
9096
write (stdout,'(a)',advance='no') '> Setting up GFN0-xTB for LMO center calculation ... '
9197
flush (stdout)
9298

9399
allocate (grad(3,mol%nat),source=0.0_wp)
100+
!>--- GFN0 job adapted from global settings
94101
allocate (tmpcalc)
95102
call env2calc(env,tmpcalc,mol)
96103
tmpcalc%calcs(1)%id = jobtype%gfn0
97104
tmpcalc%calcs(1)%rdwbo = .true.
98105
tmpcalc%calcs(1)%getlmocent = .true.
106+
tmpcalc%calcs(1)%chrg = env%chrg
99107
tmpcalc%ncalculations = 1
100108
write (stdout,'(a)') 'done.'
101109
!>--- and then start it
@@ -119,15 +127,25 @@ subroutine crest_new_protonate(env,tim)
119127
!>--- check LMO center
120128
np = tmpcalc%calcs(1)%nprot
121129
if (np > 0) then
122-
write (stdout,'(a,i0,a)') '> ',np,' π- or LP-centers identified as protonation candidates'
130+
write (stdout,'(a,i0,a)') '> ',np,' π- or LP-centers identified as protonation candidates:'
123131
call move_alloc(tmpcalc%calcs(1)%protxyz,protxyz)
124-
!do i=1,np
125-
! write(stdout,*) protxyz(1:3,i)
126-
!enddo
132+
write (stdout,'(1x,a5,1x,a,5x,a)') 'LMO','type','center(xyz/Ang)'
133+
do i = 1,np
134+
select case (nint(protxyz(4,i)))
135+
case (1)
136+
write (stdout,'(1x,i5,1x,a,3F12.5)') i,'LP ',protxyz(1:3,i)*autoaa
137+
case (2)
138+
write (stdout,'(1x,i5,1x,a,3F12.5)') i,'π ',protxyz(1:3,i)*autoaa
139+
case (3)
140+
write (stdout,'(1x,i5,1x,a,3F12.5)') i,'del.π',protxyz(1:3,i)*autoaa
141+
case default
142+
write (stdout,'(1x,i5,1x,a,3F12.5)') i,'??? ',protxyz(1:3,i)*autoaa
143+
end select
144+
end do
127145
else
128146
write (stdout,*)
129147
write (stdout,*) 'WARNING: No suitable protonation sites found!'
130-
write (stdout,*) ' Check if you expect π- or LP-centers for your molecule!'
148+
write (stdout,*) ' Confirm whether you expect π- or LP-centers for your molecule!'
131149
write (stdout,*)
132150
return
133151
end if
@@ -136,47 +154,164 @@ subroutine crest_new_protonate(env,tim)
136154

137155
!========================================================================================!
138156
!>--- If we reached this point, we have candidate positions for our protonation!
139-
write(stdout,'(a)',advance='yes') '> Generating candidate structures ... '
140-
flush(stdout)
157+
pstep = 0
158+
write (stdout,'(a)',advance='yes') '> Generating candidate structures ... '
159+
flush (stdout)
141160
natp = mol%nat+1
142-
allocate(atp(natp), source=0)
143-
allocate(xyzp(3,natp,np),ep(np),source=0.0_wp)
144-
call protonation_candidates(env,mol,natp,np,protxyz,atp,xyzp)
145-
write(stdout,'(a)') '> Write protonate_0.xyz with candidates ... '
146-
call wrensemble('protonate_0.xyz',natp,np,atp,xyzp*autoaa,ep)
147-
write(stdout,'(a)') '> done.'
148-
write(stdout,*)
161+
allocate (atp(natp),source=0)
162+
allocate (xyzp(3,natp,np),ep(np),source=0.0_wp)
149163

150-
!>--- Enforce further constraints, conditions, etc.
151-
! (TODO)
164+
call protonation_candidates(env,mol,natp,np,protxyz,atp,xyzp,npnew)
165+
!>--- NOTE: after this the global charge (env%chrg) and all charges saved in the calc levels have been increased
166+
167+
if (npnew < 1) then
168+
write (stdout,*)
169+
write (stdout,'(a)') '> WARNING: No remaining protonation sites after applying user defined conditions!'
170+
write (stdout,'(a)') '> Modify the search criteria and check your input structure for sanity.'
171+
return
172+
end if
173+
174+
write (atmp,'(a,i0,a)') 'protonate_',pstep,'.xyz'
175+
write (stdout,'(a,a,a,i0,a)') '> Write ',trim(atmp),' with ',npnew,' candidates ... '
152176

153-
!>--- Optimize candidates
154-
call smallhead('Protomer Ensemble Optimization')
155-
call tim%start(15,'Ensemble optimization')
156-
call print_opt_data(env%calc,stdout)
157-
call crest_oloop(env,natp,np,atp,xyzp,ep,.true.)
158-
call tim%stop(15)
159-
write(stdout,'(a)') '> Write protonate_1.xyz with optimized structures ... '
160-
call rename(ensemblefile,'protonate_1.xyz')
177+
call wrensemble('protonate_0.xyz',natp,npnew,atp,xyzp(:,:,1:npnew)*autoaa,ep(1:npnew))
161178

179+
write (stdout,'(a)') '> done.'
180+
write (stdout,*)
162181

182+
!========================================================================================!
183+
!>--- Optimize candidates, optional FF pre-step
184+
if (env%protb%ffopt) then
185+
call smallhead('Protomer Ensemble FF Pre-Optimization')
186+
!>--- set up a temporary calculation object
187+
write (stdout,'(a)') '> LMO centers can be very close to atoms, leading to initial'
188+
write (stdout,'(a)') ' extremely high-energy candidates which may undergo unwanted'
189+
write (stdout,'(a)') ' chemical changes in optimizations. Classical force-fields'
190+
write (stdout,'(a)') ' with defined bond-topology can help circumvent this issue.'
191+
write (stdout,'(a)') '> Setting up force-field structure pre-optimization ...'
192+
allocate (tmpcalc_ff)
193+
tmpcalc_ff%optnewinit = .true.
194+
env%calc%optnewinit = .true.
195+
tmpcalc_ff%optnewinit=.true.
196+
call tmpset%create('gfnff')
197+
tmpset%chrg = env%chrg
198+
call tmpcalc_ff%add(tmpset)
199+
tmpcalc_ff%maxcycle = 10000
200+
call tmpcalc_ff%info(stdout)
163201

202+
!>--- Run optimizations
203+
call tim%start(15,'Ensemble optimization (FF)')
204+
call print_opt_data(tmpcalc_ff,stdout)
205+
write (stdout,'(a,i0,a)') '> ',npnew,' structures to optimize ...'
206+
call crest_oloop(env,natp,npnew,atp,xyzp(:,:,1:npnew),ep(1:npnew),.false.,tmpcalc_ff)
207+
call tim%stop(15)
164208

209+
deallocate (tmpcalc_ff)
165210

166-
!>--- sorting
167-
write(stdout,'(a)') '> Sorting structures by energy ...'
168-
call newcregen(env,6,'protonate_1.xyz')
169-
write(stdout,'(a)') '> sorted file was renamed to protonated.xyz'
170-
call rename('protonate_1.xyz.sorted','protonated.xyz')
211+
pstep = pstep+1
212+
write (atmp,'(a,i0,a)') 'protonate_',pstep,'.xyz'
213+
write (stdout,'(a,a,a)') '> Write ',trim(atmp),' with optimized structures ... '
214+
call wrensemble(trim(atmp),natp,npnew,atp,xyzp(:,:,1:npnew)*autoaa,ep(1:npnew))
215+
216+
!>--- sorting
217+
write (stdout,'(a)') '> Sorting structures by energy to remove failed opts. ...'
218+
env%ewin = 5000.0_wp
219+
call newcregen(env,7,trim(atmp))
220+
call rename(trim(atmp)//'.sorted',trim(atmp))
221+
write (stdout,'(a)') '> WARNING: These are force-field energies which are '
222+
write (stdout,'(a)') ' NOT(!) accurate for bond formation and breaking!'
223+
write (stdout,*)
224+
225+
!>--- re-read sorted ensemble
226+
deallocate (xyzp,atp) !> clear this space to re-use it
227+
call rdensemble(trim(atmp),natp,npnew,atp,xyzp)
228+
xyzp = xyzp*aatoau !> don't forget to restore BOHR
229+
end if
171230

231+
!========================================================================================!
232+
!>--- H-position-only optimization (only makes sense after FF preoptimization)
233+
if (env%protb%hnewopt.and.env%protb%ffopt) then
234+
call smallhead('Protomer Ensemble Frozen-Atom Optimization')
235+
!>--- create temporary calculation from our intended level of theory
236+
write (stdout,'(a)') '> Setting up frozen structure optimization ...'
237+
allocate (tmpcalc)
238+
call env2calc(env,tmpcalc,mol)
239+
!>--- freeze all atoms, EXCEPT the new one
240+
allocate (atlist(natp),source=.true.)
241+
atlist(natp) = .false. !> the new one is always last
242+
do i = 1,natp
243+
if (atp(i) == 1) then
244+
atlist(i) = .false. !> additionally un-freeze all H's (this seems to be beneficial)
245+
end if
246+
end do
247+
tmpcalc%nfreeze = count(atlist)
248+
write (stdout,'(a,i0,a)') '> ',tmpcalc%nfreeze,' frozen atoms. All H non-frozen.'
249+
call move_alloc(atlist,tmpcalc%freezelist)
250+
call tmpcalc%info(stdout)
251+
252+
!>--- run opt
253+
call tim%start(16,'Ensemble optimization (frozen)')
254+
write (stdout,'(a,i0,a)') '> ',npnew,' structures to optimize ...'
255+
call crest_oloop(env,natp,npnew,atp,xyzp(:,:,1:npnew),ep(1:npnew),.false.,tmpcalc)
256+
call tim%stop(16)
257+
258+
pstep = pstep+1
259+
write (atmp,'(a,i0,a)') 'protonate_',pstep,'.xyz'
260+
write (stdout,'(a,a,a)') '> Write ',trim(atmp),' with optimized structures ... '
261+
call wrensemble(trim(atmp),natp,npnew,atp,xyzp(:,:,1:npnew)*autoaa,ep(1:npnew))
262+
263+
!>--- sorting
264+
write (stdout,'(a)') '> Sorting structures by energy to remove failed opts. ...'
265+
env%ewin = env%protb%ewin*10.0_wp !> large energy threshold
266+
call newcregen(env,7,trim(atmp))
267+
call rename(trim(atmp)//'.sorted',trim(atmp))
268+
write (stdout,*)
269+
270+
!>--- re-read sorted ensemble
271+
deallocate (xyzp,atp) !> clear this space to re-use it
272+
call rdensemble(trim(atmp),natp,npnew,atp,xyzp)
273+
xyzp = xyzp*aatoau !> don't forget to restore BOHR
274+
275+
deallocate (tmpcalc)
276+
end if
277+
278+
!========================================================================================!
279+
!>--- Optimize with global settings
280+
if (env%protb%finalopt.and.env%protb%ffopt) then
281+
call smallhead('Final Protomer Ensemble Optimization')
282+
allocate(tmpcalc)
283+
call env2calc(env,tmpcalc,mol)
284+
call tmpcalc%info(stdout)
285+
!tmpcalc%maxcycle=5
286+
!tmpcalc%anopt=.true.
287+
call tim%start(20,'Ensemble optimization')
288+
call print_opt_data(env%calc,stdout)
289+
write (stdout,'(a,i0,a)') '> ',npnew,' structures to optimize ...'
290+
call crest_oloop(env,natp,npnew,atp,xyzp(:,:,1:npnew),ep,.false.,tmpcalc)
291+
call tim%stop(20)
292+
293+
pstep = pstep+1
294+
write (atmp,'(a,i0,a)') 'protonate_',pstep,'.xyz'
295+
write (stdout,'(a,a,a)') '> Write ',trim(atmp),' with optimized structures ... '
296+
call wrensemble(trim(atmp),natp,npnew,atp,xyzp(:,:,1:npnew)*autoaa,ep(1:npnew))
297+
298+
!>--- sorting
299+
write (stdout,'(a)') '> Sorting structures by energy ...'
300+
env%ewin = env%protb%ewin
301+
call newcregen(env,7,trim(atmp))
302+
call rename(trim(atmp)//'.sorted','protonated.xyz')
303+
else
304+
call rename(trim(atmp),'protonated.xyz')
305+
end if
306+
write (stdout,'(a)') '> sorted file was renamed to protonated.xyz'
172307
!========================================================================================!
173308
return
174309
end subroutine crest_new_protonate
175310

176311
!========================================================================================!
177312
!========================================================================================!
178313

179-
subroutine protonation_candidates(env,mol,natp,np,protxyz,at,xyz)
314+
subroutine protonation_candidates(env,mol,natp,np,protxyz,at,xyz,npnew)
180315
!********************************************************
181316
!* generate protonation/ionization candidate structures
182317
!* The outputs are at and xyz, the latter being in Bohr
@@ -190,30 +325,60 @@ subroutine protonation_candidates(env,mol,natp,np,protxyz,at,xyz)
190325
type(coord),intent(in) :: mol
191326
integer,intent(in) :: natp
192327
integer,intent(in) :: np
193-
real(wp),intent(in) :: protxyz(3,np)
328+
real(wp),intent(in) :: protxyz(4,np)
194329
!> OUTPUT
195330
integer,intent(out) :: at(natp)
196331
real(wp),intent(out) :: xyz(3,natp,np)
332+
integer,intent(out) :: npnew
197333
!> LOCAL
198-
integer :: i,j,k,l
334+
integer :: i,j,k,l,ii
335+
integer :: ati,ichrg,ctype
199336

200337
if (natp .ne. mol%nat+1) then
201338
write (stdout,'(a)') 'WARNING: Inconsistent number of atoms in protonation routine'
202339
error stop
203340
end if
204341

205-
write(stdout,'(a)') '> Increasing the molecular charge by 1'
206-
call env%calc%increase_charge()
342+
if (env%protb%swelem) then
343+
!>--- User-defined monoatomic ion
344+
ichrg = env%protb%swchrg
345+
ati = env%protb%swat
346+
else
347+
!>--- DEFAULT: H⁺
348+
ichrg = 1
349+
ati = 1
350+
endif
351+
write (stdout,'(a,i0)') '> Increasing the molecular charge by ',ichrg
352+
call env%calc%increase_charge(ichrg)
353+
env%chrg = env%chrg + ichrg
354+
355+
!>--- Check if we have some other conditions
356+
if(any(.not.env%protb%active_lmo(:)))then
357+
write(stdout,'(a)',advance='no') '> User-defined: IGNORING '
358+
if(.not.env%protb%active_lmo(1)) write(stdout,'(a)',advance='no') 'π '
359+
if(.not.env%protb%active_lmo(2)) write(stdout,'(a)',advance='no') 'LP '
360+
if(.not.env%protb%active_lmo(3)) write(stdout,'(a)',advance='no') 'deloc.π '
361+
write(stdout,'(a)') 'LMOs ...'
362+
endif
207363

208364
!>--- Populate
365+
npnew = 0
366+
ii = 0
209367
do i = 1,np
368+
!>--- Enforce further constraints, conditions, etc.
369+
ctype = nint(protxyz(4,i))
370+
if(.not.env%protb%active_lmo(ctype)) cycle !> skip unselected LMO types
371+
372+
ii= ii + 1 !> counter of actually created structures
210373
do j = 1,mol%nat
211-
xyz(1:3,j,i) = mol%xyz(1:3,j)
374+
xyz(1:3,j,ii) = mol%xyz(1:3,j)
212375
at(j) = mol%at(j)
213376
end do
214-
xyz(1:3,natp,i) = protxyz(1:3,i)
215-
at(natp) = 1
377+
xyz(1:3,natp,ii) = protxyz(1:3,i)
378+
at(natp) = ati
216379
end do
380+
npnew = ii
381+
217382
end subroutine protonation_candidates
218383

219384
!========================================================================================!

0 commit comments

Comments
 (0)