2024-07-25 10:27:17 +02:00

4301 lines
179 KiB
Fortran

************************************************************************
program minp
************************************************************************
#include "MRCCCOMMON"
C
call mrccini
open(minpfile,file='MINP')
open(keywdfile,file='KEYWD',status='unknown')
C
call minpreader(minpfile,keywdfile,iout)
C
call mrccend(0)
end
C
************************************************************************
subroutine minpreader(minpfile,keywdfile,iout)
************************************************************************
* Input reader
************************************************************************
implicit none
integer minpfile,keywdfile,iout,i,j,k,n,ii,nnstate,nnsing,nntrip
integer clen,ierror,noptex,istat,filesize
integer*4 localccn
parameter(clen=32)
real*8 rr,tmp,cmp2,cmp2t,tmp2,tmp3,cmp3,cmp3s,cmp3t
character*1 xcalc1(clen),calc1(clen),dft1(clen),c32_1(clen)
character*2 c2,grt
character*3 lmp2dens,qro
character*3 ccsdmkl
character*4 ptthreads,ccsdthreads,ccsdrest,optex
character*4 charge,cctol,geom,itol,localcc,molden,mult,scfdiis
character*4 maxdim,localcorrsymm,theodore,nto,guido_ct,nafdens
character*4 scfext,scfmaxit,scftol,symm,unit,verbosity,nchol
character*4 ccprog,ovirt,nstate,nsing,ntrip,maxex,nacto,nactv
character*4 maxact,dboc,dens,rest,ciguess,uncontract,gtol,irlab
character*4 cmpgrp,talg,intalg,scfdiis_start,scfdiis_end,usedisk
character*4 scfdiis_step,scfdtol,cscr4,grtol,redcost_exc,mpitasks
character*4 maxmicroit,ip_ea,denscorr
character*4 scfdiis_watch,scfdiis_wrange,scfdiis_wlimit
character*4 scfdiis_delmax,scfdamp_end,scflshift_end
character*4 comprest
character*5 gauss,orbloco5,orblocc5,orblocv5,scftype,scfloc5
character*5 cscr5 !GA
character*6 orbloc6,core,diag,ovosnorb,rgrid,cscr6,fnonorb
character*7 scfiguess,mcscfiguess
character*8 qmreg,active,refdet,iface,ghost,dendec,qmmm,hamilton
character*8 optmaxit,optalg,nafalg,dfalg,dfintran,drpaalg,embed
character*8 lcorthr,gopt,scflshift,epert,popul,cialg,freq,dual
character*8 scflshift_gaptol,scflshift_dtol !HB
character*8 naftyp,tvirtcut,locintrf,mulmet,lccrest,scfalg,ccsdalg
character*8 ccmaxit,corembed,grdens,lcorsel,qscf,orblocguess,fmm
character*8 lccoporder,scfguessdens,boysalg,grid,grid_sm
character*8 fmmord,pssp,bfgstol,bfgsmem,occri,oniom,subminp!HB
character*8 oniom_eechg,oniom_pcm,oniom_type,cscr8 !HB
character*8 fitting,gridbatch_cos,dual_df,ldfgrad_tol
character*8 oniom_qcorr,num_grad
character*8 espcharge !GA
character*8 etemp !HB
character*10 dhexc
character*12 cscr12,scfdiis_dtol,scf_conv !HB
character*13 rohfcore,rohftype,agrid,agrid_pssp,agrid_pssp_sm
character*16 mem,orblocc,orbloco,orblocv,eps,osveps,gamma,scfloc
character*16 ptfreq,domrad,excrad,excrad_fin,lnoepsv,lnoepso,nab
character*16 naf_scf,naf_cor,scfdamp,bpcompo,ndeps,redcost_tddft
character*16 optetol,optgtol,optstol,ovltol,delocsomofact,naf_amp
character*16 wpairtol,spairtol,scsps,scspt,scspe,tprint,bpcompv
character*16 scsps_t,scspt_t,naf_f12,epairestfact,epairscale
character*16 olnof,vlnof,laptol,csapprox,tpao,tlmo,scsph,orbloce!HB
character*16 sqmprog,mmprog,scfdamp_mode,scfdamp_dtol
character*16 scfdamp_dampstep,scfdamp_minfact,scfdamp_maxfact !HB
character*16 coord_sys, pao_subsys_tol
real*8 olnofact,vlnofact,ltol
character*16 temp,pressure,c16,scspv
character*16 bppdo,bppdv,bpedo,bpedv,bpdfo,bpocc
character*20 basis,dfbasis_scf,dfbasis_cor,bfbasis,c20,ecp
character*20 basis_sm,dfbasis_cab,dfbasis_scf_sm
character*24 basopt
character*30 test
character*32 calc,dft,xcalc,c32,pcm
character*256 occ,docc,mact,edisp,edisp_embed,cvs
character*256 rism !GA
character*512 line
logical ldf,ll1,ll2,ll3,ldftfunc,localmp2,lanycc,localrpa,locdhdft
logical loccomp,locanycc,lstartwl,dhdft,l1,l2,l3,lccon,lstartwlno
logical localcc16p,localcc15p,linteger,dof12,lf12,externalsqm
logical lexist,lfno,ll4,l4,ll5,l5
equivalence(orbloco,orbloco5)
equivalence(orblocc,orblocc5)
equivalence(orblocv,orblocv5)
equivalence(xcalc,xcalc1)
equivalence(calc,calc1)
equivalence(c32,c32_1,c2)
equivalence(dft,dft1)
equivalence(scfloc5,scfloc)
equivalence(grt,grid)
C gridbatch_cos, naf_amp, nab, naf_f12
C theodore, scspv, rest(ccprog=cis esetben), orbloc(fragment, no, spade), f12
c scfiguess=lowlqm ? embed=SCH
c development options: bpdfo, bpocc, delocsomofact, locintrf, localcc=2022, epairestfact,epairscale
C Read input from MINP
write(iout,*) 'Reading input from MINP...'
write(iout,*)
write(iout,*) 'Input file:'
write(iout,*)
call ishell('cat MINP')
write(iout,*)
write(iout,*)
write(iout,*) 'Checking keyword combinations...'
write(iout,*)
C gridbatch_cos %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('numgrad',7,num_grad,8)
if(num_grad.eq.' ') num_grad='off '
C gridbatch_cos %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('gridbatch_cos',13,gridbatch_cos,8)
if(gridbatch_cos.eq.' ') gridbatch_cos='2000 '
C bfgsmem %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bfgsmem',7,bfgsmem,8)
if(bfgsmem.eq.' ') bfgsmem='10 '
C bfgstol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bfgstol',7,bfgstol,8)
if(bfgstol.eq.' ') bfgstol='1.0d-3 '
C iface %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('iface',5,iface,8)
if(iface.ne.'columbus'.and.iface.ne.'cfour '.and.
$iface.ne.'molpro '.and.iface.ne.'dirac '.and.
$iface.ne.'none '.and.iface.ne.' ')
$call unknown('iface',5)
if(iface.eq.' ') iface='none '
C active %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('active',6,active,8)
if(active.ne.' '.and.active.ne.'none '.and.
$ active.ne.'serialno'.and.active.ne.'vector ')
$call unknown('active',6)
if(active.eq.' ') active='none '
C grid %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('grid',4,grid,8)
if(grid.ne.' '.and.grid.ne.'auto '.and.
$ grid.ne.'ta1 '.and.grid.ne.'ta2 '.and.
$ grid.ne.'ta3 '.and.grid.ne.'ta4 '.and.
$ grid.ne.'ta5 ') call unknown('grid',4)
if(grid.eq.' ') grid='auto '
C grid_sm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('grid_sm',7,grid_sm,8)
if(grid_sm.ne.' '.and.grid_sm.ne.'auto '.and.
$ grid_sm.ne.'ta1 '.and.grid_sm.ne.'ta2 '.and.
$ grid_sm.ne.'ta3 '.and.grid_sm.ne.'ta4 '.and.
$ grid_sm.ne.'ta5 ') call unknown('grid_sm',7)
if(grid_sm.eq.' ') grid_sm=grid
C agrid %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('agrid',5,agrid,13)
if(agrid.eq.' '.or.grt.eq.'ta') agrid='ld0006-ld0590'
C agrid_pssp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('agrid_pssp',10,agrid_pssp,13)
if(agrid_pssp.eq.' ') agrid_pssp='ld0006-ld0194'
C agrid_pssp_sm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('agrid_pssp_sm',13,agrid_pssp_sm,13)
if(agrid_pssp_sm.eq.' ') agrid_pssp_sm='ld0006-ld0074'
C basis %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('basis',5,basis,20)
if(basis.eq.' '.and.iface.eq.'none ') then
write(iout,*)
write(iout,*) 'Basis set is not specified!'
call mrccend(1)
endif
C dfbasis_scf_sm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dfbasis_scf_sm',14,dfbasis_scf_sm,20)
if(dfbasis_scf_sm.eq.' ')
$dfbasis_scf_sm='auto '
C basis_sm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('basis_sm',8,basis_sm,20)
if(basis_sm.eq.' ')
$basis_sm='none '
C basopt %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('basopt',6,basopt,24)
if(basopt.ne.'on '.and.
$ basopt.ne.'cv '.and.
$ basopt.ne.'off '.and.
$ basopt.ne.' ') then
read(basopt,*) rr
if(rr.gt.0.d0) call unknown('basopt',6)
endif
if(basopt.eq.' ')
$ basopt='off '
C localcc %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('localcc',7,localcc,4)
if(localcc.ne.'on '.and.localcc.ne.'off '.and.
$ localcc.ne.' '.and.localcc.ne.'2013'.and.
$ localcc.ne.'2015'.and.localcc.ne.'2016'.and.
$ localcc.ne.'2018'.and.localcc.ne.'2021'
$ )
$ call unknown('localcc',7)
c
lccon=.false.
if(localcc.ne.'off '.and.localcc.ne.' ') lccon=.true. ! turn on local cc with localcc keyword (not with calc)
call getkeym('calc',4,calc,clen)
call getkeym('dft',3,dft,32)
lf12=dof12(calc)
localmp2=trim(calc).eq.'lmp2'.or. ! any kind of local MP2
$ trim(calc).eq.'lscs-mp2'.or.
$ trim(calc).eq.'lsos-mp2'
localrpa=trim(calc).eq.'ldrpa'.or. ! any kind of local drpa
$ trim(calc).eq.'lsosex'.or.
$ trim(calc).eq.'lsedrpa'.or.
$ trim(calc).eq.'lsesosex'.or.
$ trim(calc).eq.'lrpax2'.or.
$ trim(calc).eq.'ldrpa75'.or.
$ trim(calc).eq.'lscs-drpa75'
if((calc1(1).eq.'d'.and.calc1(2).eq.'f'.and.calc1(3).eq.'-').or.
$ (calc1(1).eq.'r'.and.calc1(2).eq.'i'.and.calc1(3).eq.'-'))then
call removeprefix(calc1,clen,3)
endif
edisp=' ' ! has to be initialized before the first setedisp call
call setedisp(calc1,edisp) ! set edisp and remove -D3 postfix if present
loccomp=.false.
if(lstartwl(calc)) then ! for the L- prefix
loccomp=.true.
if (lstartwlno(calc)) then ! for the synonym LNO- prefix
call removeprefix(calc1,clen,4)
else ! for the L prefix
call removeprefix(calc1,clen,1)
endif
endif
locanycc=(loccomp.or.lccon).and.lanycc(calc) ! any kind of local CI or CC
locdhdft=(dhdft(calc).or.dhdft(dft)).and.loccomp ! local double hybrid functional with local MP2 contribution; this does not work with the dft=user(d) option, set if for dft=user(d) below after the dft keyword
if (lccon) then
localmp2=localmp2.or.
$ trim(calc).eq.'mp2'.or.
$ trim(calc).eq.'scs-mp2'.or.
$ trim(calc).eq.'sos-mp2'
localrpa=localrpa.or.
$ trim(calc).eq.'drpa'.or.
$ trim(calc).eq.'sosex'.or.
$ trim(calc).eq.'sedrpa'.or.
$ trim(calc).eq.'sesosex'.or.
$ trim(calc).eq.'rpax2'.or.
$ trim(calc).eq.'drpa75'.or.
$ trim(calc).eq.'scs-drpa75'
locdhdft=locdhdft.or.dhdft(calc)
if(localcc.eq.' '.or.localcc.eq.'on ') then
if(localrpa.or.localcc.eq.'2015') then
localcc='2015'
elseif(localcc.eq.'2013') then
localcc='2013'
else
localcc='2021'
c localcc='2022' ! development, will be default later
endif
endif
endif ! lccon
localmp2=locdhdft.or.localmp2
loccomp=localmp2.or.localrpa.or.locanycc ! any kind of local correlation computation
if (loccomp.and.localcc.eq.'off ') then
write(iout,*)'Keyword values conflict with localcc=off'
call mrccend(1)
endif
c
if(localcc.eq.' ') then
if (.not.loccomp) then
localcc='off '
else
if (localrpa) then
localcc='2015'
elseif (localmp2.or.locanycc) then
localcc='2021'
c localcc='2022' ! development, will be default later
endif
endif ! .not.loccomp
endif ! localcc.eq.' '
c
if (localcc.eq.'2015'.and.trim(calc).eq.'scs-mp2') then
write(iout,*)'Local SCS-MP2 is only available via
$ localcc=<2016'
call mrccend(1)
endif
if (localcc.ne.'2015'.and.localrpa) then
write(iout,*)'Local dRPA, SOSEX or RPAX2 are available only',
$ ' via localcc=2015'
call mrccend(1)
endif
if (localcc.ne.'off '.and.trim(basis).eq.'sto-3g') then
write(iout,*)'Warning: STO-3G basis set is not sufficient ',
$'in combination with local correlation methods, numerical ',
$'problems may occur'
write(iout,*)
endif
c
if (localcc.eq.'off ') then
localccn=0
else
read(localcc,*) localccn
endif
localcc16p=localccn.ge.2016
C lcorthr %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('lcorthr',7,lcorthr,8)
if(lcorthr.ne.'tight '.and.lcorthr.ne.'loose '.and.
$ lcorthr.ne.'0 '.and.lcorthr.ne.' '.and.
$ lcorthr.ne.'vloose '.and.!lcorthr.ne.'vvloose '.and.
$ lcorthr.ne.'vtight '.and.lcorthr.ne.'vvtight '.and.
c $ lcorthr.ne.'v3tight '.and.lcorthr.ne.'v4tight '.and.
$ lcorthr.ne.'normal ')
$call unknown('lcorthr',7)
if (localccn.lt.2018.and.localccn.ne.0) then
if(lcorthr.eq.' ') lcorthr='loose '
if(lcorthr.eq.'normal ') lcorthr='loose '
else
if(lcorthr.eq.' ') lcorthr='normal '
endif
lcorsel='default '
if (lcorthr.eq.'vloose '.or.lcorthr.eq.'vvloose '.or.
$ (lcorthr.eq.'loose '.and.localccn.ge.2018)) ! loose is the default for localcc<2018
$ lcorsel='anyloose'
if(lcorthr.eq.'vtight '.or.lcorthr.eq.'vvtight '.or.
$ lcorthr.eq.'v3tight '.or.lcorthr.eq.'v4tight ')
$ lcorsel='vtightpp'
C bpcompv %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bpcompv',7,bpcompv,16)
if(bpcompv.ne.' ') then
read(bpcompv,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('bpcompv',7)
endif
if(bpcompv.eq.' ') then
if(lcorthr.eq.'0 ') then
bpcompv='1.d0 '
else
bpcompv='0.98 '
endif
endif
C coord_sys %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('coord_sys',9,coord_sys,16)
if(coord_sys.ne.'ric ' .and.
& coord_sys.ne.'deloc-ic ' .and.
& coord_sys.ne.' ') call unknown('coord_sys',9)
if(coord_sys.eq.' ')
& coord_sys='ric '
C dfbasis_cab %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dfbasis_cab',11,dfbasis_cab,20)
if(dfbasis_cab.eq.' ') then
if(lf12) then
dfbasis_cab='auto '
else
dfbasis_cab='none '
endif
endif
C dfbasis_cor %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dfbasis_cor',11,dfbasis_cor,20)
if(dfbasis_cor.eq.' ') then
if(localcc.ne.'off '.or.trim(calc).eq.'os-mp3') then
dfbasis_cor='auto '
else
dfbasis_cor='none '
endif
endif
if(trim(dfbasis_cor).eq.'none'.and.trim(calc).eq.'os-mp3') then
write(iout,*) 'Error: OS-MP3 calculation can only be ' //
$ 'performed with density fitting!'
call mrccend(1)
endif
C dfbasis_scf %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dfbasis_scf',11,dfbasis_scf,20)
c if(dfbasis_scf.eq.' ')
c $dfbasis_scf='none '
c if(dfbasis_scf.eq.' ') dfbasis_scf=dfbasis_cor
C mult %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('mult',4,mult,4)
ii=1
if (mult.ne.' ') read(mult,*) ii
if(ii.le.0) then
write(iout,*) 'Error: set a positive integer for mult!'
call mrccend(1)
endif
! Default is set by integ
C scftype %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scftype',7,scftype,5)
if(scftype.ne.'rhf '.and.scftype.ne.'uhf '.and.
$ scftype.ne.'rohf '.and.scftype.ne.'mcscf'.and.
$ scftype.ne.'rks '.and.scftype.ne.'uks '.and.
$ scftype.ne.'roks '.and.scftype.ne.' ')
$call unknown('scftype',7)
if(scftype.eq.' ') then
if(mult.ne.'1 '.and.mult.ne.' ') then
if (localcc.ne.'off ') then
scftype='rohf '
else
scftype='uhf '
endif
else
scftype=' ' ! Default is set by integ
endif
else
if(scftype.eq.'rks ') scftype='rhf '
if(scftype.eq.'uks ') scftype='uhf '
if(scftype.eq.'roks ') scftype='rohf '
endif
call oslccversioncheck(localcc,scftype,mult,calc,iout)
C scspe %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scspe',5,scspe,16)
if(scspe.eq.' ') scspe='1.d0 '
C scsph %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scsph',5,scsph,16)
if(scsph.eq.' ') scsph='1.d0 '
C scspv %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scspv',5,scspv,16)
if(scspv.eq.' ') scspv='1.d0 '
C nstate %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('nstate',6,nstate,4)
if(nstate.eq.' ') nstate='0 '
C nsing %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('nsing',5,nsing,4)
if(nsing.eq.' ') nsing='0 '
C ntrip %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ntrip',5,ntrip,4)
if(ntrip.eq.' ') ntrip='0 '
if(nstate.eq.'0 '.and.nsing.eq.'0 '.and.ntrip.eq.'0 ')
$nstate='1 '
read(nstate,*) nnstate
read(nsing ,*) nnsing
read(ntrip ,*) nntrip
if(nnstate.ne.0.and.nnsing.ne.0.and.nntrip.ne.0)
$ii=nnsing+nntrip
if(nnstate.eq.0.and.nnsing.ne.0.and.nntrip.ne.0)
$ii=nnsing+nntrip
if(nnstate.ne.0.and.nnsing.ne.0.and.nntrip.eq.0) ii=nnsing
if(nnstate.ne.0.and.nnsing.eq.0.and.nntrip.ne.0) ii=nntrip+1
if(nnstate.eq.0.and.nnsing.eq.0.and.nntrip.ne.0) ii=nntrip+1
if(nnstate.eq.0.and.nnsing.ne.0.and.nntrip.eq.0) ii=nnsing
if(nnstate.ne.0.and.nnsing.eq.0.and.nntrip.eq.0) ii=nnstate
nnstate=ii
nnsing=nnstate-nntrip-1
C optex %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('optex',5,optex,4)
if(optex.eq.' ') then
noptex=nnstate-1
write(optex,'(i4)') noptex
optex=adjustl(optex)
else
read(optex,*) noptex
endif
if(noptex+1.gt.nnstate) then
write(iout,*) 'optex should be smaller than the
$number of excited states!'
call mrccend(1)
endif
C tpao %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('tpao',4,tpao,16)
if(tpao.ne.' ') then
read(tpao,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('tpao',4)
endif
if(tpao.eq.' ') then
tpao='0.94 '
endif
C tlmo %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('tlmo',4,tlmo,16)
if(tlmo.ne.' ') then
read(tlmo,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('tlmo',4)
endif
if(tlmo.eq.' ') then
tlmo='0.999 '
endif
C bpcompo %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bpcompo',7,bpcompo,16)
if(bpcompo.ne.' ') then
read(bpcompo,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('bpcompo',7)
endif
if(bpcompo.eq.' ') then
if(lcorthr.eq.'0 ') then
bpcompo='1.d0 '
else
if(nnstate.eq.1) then
bpcompo='0.985 '
else
bpcompo='0.95 '
endif
endif
endif
C calc %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('calc',4,calc,32)
call setf12(calc)
call setedisp(calc1,edisp) ! set edisp and remove -D3 postfix if present
if(calc1(1).eq.'f'.and.calc1(2).eq.'n'.and.calc1(3).eq.'o'.and.
$ calc1(4).eq.'-')then
call removeprefix(calc1,clen,4)
lfno=.true.
else
lfno=.false.
end if
if(trim(calc).eq.'ccsd-ppl+') then
calc='ccsd '
lfno=.true.
else if(trim(calc).eq.'ccsd-ppl+(t+)') then
calc='ccsd(t) '
lfno=.true.
end if
if(lfno.and.trim(dfbasis_cor).eq.'none') then
ldf=.true.
dfbasis_cor='auto '
end if
if((calc1(1).eq.'d'.and.calc1(2).eq.'f'.and.calc1(3).eq.'-').or.
$ (calc1(1).eq.'r'.and.calc1(2).eq.'i'.and.calc1(3).eq.'-'))then
call removeprefix(calc1,clen,3)
ldf=.true.
else if(trim(calc).eq.'mp2'.or.
$ trim(calc).eq.'mp2-f12'.or.
$ trim(calc).eq.'ccsd-f12'.or.
$ trim(calc).eq.'ccsd(t)-f12'.or.
$ trim(calc).eq.'cis'.or.
$ (trim(calc).eq.'scf'.and.nnstate.gt.1).or.
$ (ldftfunc(calc).and.nnstate.gt.1).or.
$ trim(calc).eq.'cis(di)'.or.
$ trim(calc).eq.'adc(2)'.or.
$ trim(calc).eq.'cis(d)'.or.
$ trim(calc).eq.'tdhf'.or.
$ trim(calc).eq.'tddft'.or.
$ trim(calc).eq.'sos-cis(di)'.or.
$ trim(calc).eq.'scs-cis(di)'.or.
$ trim(calc).eq.'sos-adc(2)'.or.
$ trim(calc).eq.'scs-adc(2)'.or.
$ trim(calc).eq.'sos-cis(d)'.or.
$ trim(calc).eq.'scs-cis(d)'.or.
$ trim(calc).eq.'sos-cc2'.or.
$ trim(calc).eq.'scs-cc2'.or.
$ trim(calc).eq.'cc2'.or.
$ trim(calc).eq.'tda'.or.
$ trim(calc).eq.'scs-mp2'.or.
$ trim(calc).eq.'sos-mp2'.or.
$ trim(calc).eq.'drpa'.or.
$ trim(calc).eq.'sosex'.or.
$ trim(calc).eq.'sedrpa'.or.
$ trim(calc).eq.'sesosex'.or.
$ trim(calc).eq.'dsdrpa'.or.
$ trim(calc).eq.'dssosex'.or.
$ trim(calc).eq.'rpax2'.or.
$ trim(calc).eq.'rpa') then
call getkeym('ccprog',6,ccprog,4)
ldf=(ccprog.ne.'mrcc'.and.trim(calc).ne.'mp2').or.
$ trim(dfbasis_cor).ne.'none'
else
ldf=.false.
endif
ldf=ldf.or.lf12
#if defined (LIBXC)
call libxcconv(calc)
#endif
if(lstartwl(calc)) then
if(lstartwlno(calc)) then
call removeprefix(calc1,clen,4) ! remove LNO- prefix
else
call removeprefix(calc1,clen,1) ! remove L prefix
endif
if (localcc16p.and.
$ (trim(calc).eq.'sos-mp2'.or.trim(calc).eq.'scs-mp2'))
$ calc='mp2 '
call getkeym('dfbasis_cor',11,c20,20)
if(c20.ne.'none ') ldf=.true.
endif
if(trim(calc).eq.'hf'.or.trim(calc).eq.'ks') then
calc='scf '
else if(trim(calc).eq.'rhf'.or.trim(calc).eq.'rks') then
calc='scf '
scftype='rhf '
else if(trim(calc).eq.'uhf'.or.trim(calc).eq.'uks') then
calc='scf '
scftype='uhf '
else if(trim(calc).eq.'rohf'.or.trim(calc).eq.'roks') then
calc='scf '
scftype='rohf '
else if(trim(calc).eq.'mcscf') then
calc='scf '
scftype='mcscf'
else if(trim(calc).eq.'scs-mp2') then
calc='mp2 '
else if(trim(calc).eq.'sedrpa') then
calc='drpa '
scspe='0.8 '
else if(trim(calc).eq.'sesosex') then
calc='sosex '
scspe='0.8 '
else if(trim(calc).eq.'dsdrpa') then
calc='drpa '
scsph='0.85 '
else if(trim(calc).eq.'dssosex') then
calc='sosex '
scsph='0.85 '
endif
if(ldf) then
if(trim(calc).eq.'scf'.and.nnstate.eq.1) then
if(dfbasis_scf.eq.' ')
$dfbasis_scf='auto '
else
if(dfbasis_cor.eq.'none ') then
dfbasis_cor='auto '
if(dfbasis_scf.eq.' ')
$dfbasis_scf='auto '
endif
endif
endif
if(trim(calc).ne.'scf'.and.
$ trim(calc).ne.'mp2'.and.
$ trim(calc).ne.'mp3'.and.
c $ trim(calc).ne.'os-mp3'.and.
$ trim(calc).ne.'mp2-f12'.and.
$ trim(calc).ne.'ccsd-f12'.and.
$ trim(calc).ne.'ccsd(t)-f12'.and.
$ trim(calc).ne.'cis(di)'.and.
$ trim(calc).ne.'adc(2)'.and.
$ trim(calc).ne.'cis(d)'.and.
$ trim(calc).ne.'sos-cis(di)'.and.
$ trim(calc).ne.'scs-cis(di)'.and.
$ trim(calc).ne.'sos-adc(2)'.and.
$ trim(calc).ne.'scs-adc(2)'.and.
$ trim(calc).ne.'sos-cis(d)'.and.
$ trim(calc).ne.'scs-cis(d)'.and.
$ trim(calc).ne.'sos-cc2'.and.
$ trim(calc).ne.'scs-cc2'.and.
$ trim(calc).ne.'tdhf'.and.
$ trim(calc).ne.'tddft'.and.
$ trim(calc).ne.'tda'.and.
$ trim(calc).ne.'sos-mp2'.and.
$ trim(calc).ne.'drpa'.and.
$ trim(calc).ne.'sosex'.and.
$ trim(calc).ne.'rpax2'.and.
$ trim(calc).ne.'rpa'.and.
$ .not.lanycc(calc) .and.
$ .not.ldftfunc(calc).and.
$ .not.dhdft(calc).and.
$ trim(calc).ne.'drpa75'.and.
$ trim(calc).ne.'scs-drpa75'.and.
$ trim(calc).ne.'')
$call unknown('calc',4)
if(trim(calc).eq.'') calc='scf '
if(trim(calc).eq.'sos-mp2') then
calc='drpa '
scspe='0.d0 '
endif
if(dfbasis_scf.eq.' ') then
if(dfbasis_cor.eq.'none ') then
dfbasis_scf='none '
else
dfbasis_scf='auto '
endif
endif
if(ldftfunc(calc).or.dhdft(calc).or.trim(calc).eq.'drpa75'.or.
$ trim(calc).eq.'scs-drpa75') then
dft=calc
calc='scf '
else
dft=' '
endif
!NP
C bpdfo %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bpdfo',5,bpdfo,16)
if(bpdfo.ne.' ') then
read(bpdfo,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('bpdfo',5)
endif
if(bpdfo.eq.' ') bpdfo=bpcompo
C bppdo %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bppdo',5,bppdo,16)
if(bppdo.ne.' ') then
read(bppdo,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('bppdo',5)
endif
if(bppdo.eq.' ') then
if(lcorthr.eq.'0 ') then
bppdo= '1.d0 '
else
if(localcc16p) then
bppdo='0.999d0 '
else
bppdo=bpcompo
endif
endif
endif
C bppdv %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bppdv',5,bppdv,16)
if(bppdv.ne.' ') then
read(bppdv,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('bppdv',5)
endif
if(bppdv.eq.' ') then
if(lcorthr.eq.'0 ') then
bppdv='1.d0 '
else
bppdv=bpcompv
endif
endif
C bpedv %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bpedv',5,bpedv,16)
if(bpedv.ne.' ') then
read(bpedv,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('bpedv',5)
endif
if(bpedv.eq.' ') then
if(lcorthr.eq.'0 ') then
bpedv='1.d0 '
elseif (lcorthr.ne.'0 '.and..not.localcc16p) then
bpedv=bpcompv
elseif (lcorthr.ne.'0 '.and.localcc16p) then
bpedv='0.995d0 '
endif
endif
!NP
C ccmaxit %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ccmaxit',7,ccmaxit,8)
if(ccmaxit.eq.' ') ccmaxit='50 '
C charge %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('charge',6,charge,4)
if(charge.eq.' ') charge='0 '
C ciguess %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ciguess',7,ciguess,4)
if(ciguess.ne.' '.and.ciguess.ne.'on '.and.ciguess.ne.'off ')
$call unknown('ciguess',7)
if(ciguess.eq.' ') ciguess='off '
C cmpgrp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('cmpgrp',6,cmpgrp,4)
if( cmpgrp.ne.' '.and.cmpgrp.ne.'auto'.and.cmpgrp.ne.'c1 '
$.and.cmpgrp.ne.'ci '.and.cmpgrp.ne.'cs '.and.cmpgrp.ne.'c2 '
$.and.cmpgrp.ne.'c2v '.and.cmpgrp.ne.'c2h '.and.cmpgrp.ne.'d2 '
$.and.cmpgrp.ne.'d2h ') call unknown('cmpgrp',6)
if(cmpgrp.eq.' ') cmpgrp='auto'
C core %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('core',4,core,6)
if(core.ne.'frozen'.and.core.ne.'corr '.and.core.ne.' ')
$then
read(core,*) i
if(i.lt.0) call unknown('core',4)
if(i.eq.0) core='corr '
endif
if(core.eq.' ') core='frozen'
C cvs %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('cvs',3,cvs,256)
if(trim(cvs).ne.'') then
backspace(minpfile)
read(minpfile,"(a4,a256)") cscr4,cvs
else
cvs='off'
endif
C dboc %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dboc',4,dboc,4)
if(dboc.ne.' '.and.dboc.ne.'on '.and.dboc.ne.'off ')
$call unknown('dboc',4)
if(dboc.eq.' ') dboc='off '
C delocsomofact %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('delocsomofact',13,delocsomofact,16)
if(trim(delocsomofact).ne.'') then
read(delocsomofact,*) rr
if (rr.lt.0.d0.or.rr.gt.1.e15) call unknown('delocsomofact',13)
else
delocsomofact=''
endif
C dendec %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dendec',6,dendec,8)
if(dendec.ne.' '.and.
$ dendec.ne.'cholesky'.and.
$ dendec.ne.'laplace '.and.
$ dendec.ne.'off ') call unknown('dendec',6)
if(dendec.eq.' ') then
if(trim(calc).eq.'sos-cc2'.or.trim(calc).eq.'sos-cis(di)'
$.or.trim(calc).eq.'sos-adc(2)'.or.
$trim(calc).eq.'cc2'.or.trim(calc).eq.'cis(di)'
$.or.trim(calc).eq.'adc(2)'.or.
$trim(calc).eq.'sos-cis(d)'.or.
$trim(calc).eq.'cis(d)'.or.
$(trim(calc).eq.'drpa'.and.
$ scspe.eq.'0.d0 ')) then
dendec='laplace ' !SOS-MP2
else
dendec='cholesky'
endif
endif
C docc %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('docc',4,docc,256)
if(scftype.eq.'mcscf'.and.trim(docc).eq.'')call unknown('docc',5)
! Default is set by scf
C qmreg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('qmreg',5,qmreg,8)
if( qmreg .ne. ' ' ) then
read(qmreg,'(i8)',iostat=ierror) i
if(ierror.ne.0.or.i.lt.0) then
write(iout,*) 'Illegal specification of qmreg!'
call unknown('qmreg',6)
endif
endif
C qmmm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('qmmm',4,qmmm,8)
if(qmmm.ne.' '.and.qmmm.ne.'off '.and.
$ qmmm.ne.'charmm '.and.qmmm.ne.'amber ')
$call unknown('qmmm',4)
if(qmmm.eq.' ') qmmm='off '
C rism !GA %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('rism',4,rism,256)
C if(rism(1:8).ne.' ') call getkeymline('rism',4,rism,256)
if(rism(1:8).eq.' ') rism='off '
if(rism(1:8).ne.'on '.and.rism(1:8).ne.'off ') then
backspace(minpfile)
read(minpfile,"(a5,a256)") cscr5,rism
endif
C check if ambertools is installed
call ishell('echo "$AMBERHOME" > amberpath')
C call ishell('which rism3d.snglpnt > amberpath')
C call ishell('echo "$notAMBERHOME" > notamberhome')
inquire(file="amberpath",size=filesize)
C inquire(file="amberhome2",size=filesize)
if(filesize.le.1.and.rism(1:8).ne.'off ') then
write(iout,*) "EC-RISM calculation requires AmberTools!"
write(iout,*) "We have not found the $AMBERHOME folder."
write(iout,*) "Please install and setup correctly
$ your $AMBERHOME folder to use this function."
write(iout,*) "MRCC will stop now."
call mrccend(1)
endif
call ishell('rm amberpath')
C epairestfact %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('epairestfact',12,epairestfact,16)
if (trim(epairestfact).eq.'') then
if (localccn.le.2021) then
epairestfact = 'off '
else
epairestfact = '50.d0 '
endif ! localccn.le.2021
endif ! epairestfact.eq.''
C epairscale %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('epairscale',10,epairscale,16)
if (trim(epairscale).eq.'') then
if (trim(epairestfact).eq.'off'.or.localccn.le.2021) then
epairscale = '1.d0 '
else
epairscale = '5.d0 '
endif
endif ! epairestfact.eq.''
C ESP charge !GA %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('espcharge',9,espcharge,8)
if(espcharge.ne.' '.and.espcharge.ne.'off '.and.
$ espcharge.ne.'chelpg '.and.espcharge.ne.'mk ')
$call unknown('espcharge',9)
if(espcharge.eq.' ') espcharge='off '
C default espcharge if rism=on is chelpg
if(rism(1:8).ne.'off '.and.espcharge.eq.'off ') then
espcharge='chelpg '
endif
C gopt %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('gopt',4,gopt,8)
if(gopt.ne.' '.and.gopt.ne.'off '.and.
$ gopt.ne.'full '.and.gopt.ne.'freeze ')
$call unknown('gopt',4)
if(gopt.eq.' ') gopt='off '
C fmm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('fmm',3,fmm,8)
if(fmm.ne.'on '.and.fmm.ne.'off '.and.fmm.ne.' '
&.and.fmm.ne.'coulomb ') call unknown('fmm',3)
if(fmm.eq.' ') fmm='off '
C fmmord %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('fmmord',6,fmmord,8)
if(fmmord.eq.' ') then
fmmord='8 '
else
read(fmmord,*) i
if(i.lt.0) call unknown('fmmord',8)
endif
C freq %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('freq',4,freq,8)
if(freq.ne.'on '.and.freq.ne.'off '.and.
$freq.ne.' ') call unknown('freq',4)
if(freq.eq.' ') freq='off '
C grdens %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('grdens',6,grdens,8)
if(grdens.ne.'on '.and.grdens.ne.'off '.and.
$grdens.ne.' ') call unknown('grdens',6)
if(grdens.eq.' ') grdens='off '
C dens %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dens',4,dens,4)
if(dens.eq.' ') then
if(gopt.ne.'off ') then !.or.qmmm.ne.'off ') then
c if(gopt.ne.'off '.or.freq.ne.'off ') then !.or.qmmm.ne.'off ') then
dens='2 '
else
dens='0 '
endif
endif
if(qmmm.ne.'off '.and.qmreg.ne.'0 '.and.
$ qmreg.ne.' ') dens='0 '
read(dens,*) i
if(i.lt.0.or.i.gt.8) call unknown('dens',4)
C if espcharge is set, dens=1
if(espcharge.ne.'off '.and.dens.eq.'0 ') dens='1 '
C optetol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('optetol',7,optetol,16)
if(optetol.ne.' ') then
read(optetol,*) rr
if(rr.lt.0.d0) call unknown('optetol',7)
endif
if(optetol.eq.' ') then
optetol='1e-6'
endif
C optgtol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('optgtol',7,optgtol,16)
if(optgtol.ne.' ') then
read(optgtol,*) rr
if(rr.lt.0.d0) call unknown('optgtol',7)
endif
if(optgtol.eq.' ') then
! if(gopt.ne.'off ') then
optgtol='1e-4'
! else
! optgtol='1e-6'
! endif
endif
C optalg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('optalg',6,optalg,8)
if(optalg.ne.' '.and.optalg.ne.'simplex '.and.
$ optalg.ne.'bfgs '.and.optalg.ne.'rfo '.and.
$ optalg.ne.'l-bfgs ')
$ call unknown('optalg',6)
if(optalg.eq.' ') then
if(basopt.ne.'off ') then
optalg='simplex '
else if(gopt.ne.'off ') then
optalg='bfgs '
endif
endif
C optstol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('optstol',7,optstol,16)
if(optstol.ne.' ') then
read(optstol,*) rr
if(rr.lt.0.d0) call unknown('optstol',7)
endif
if(optstol.eq.' ') then
if(gopt.ne.'off '.and.optalg.ne.'simplex ') then
optstol='1e-4 '
else
optstol='1e-3 '
endif
endif
C cctol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('cctol',5,cctol,4)
if(cctol.eq.' ') then
cctol='6 '
if (localcc16p.and.lcorthr.ne.'0 '
$.and.nnstate.lt.2) cctol='5 '
if(dens.ne.'0 '.or.freq.ne.'off ') cctol='8 '
if(gopt.ne.'off ') then
read(optetol,*) rr
read(cctol,*) i
write(cctol,'(i4)') max(i,idnint(-dlog10(rr))+2)
cctol=adjustl(cctol)
endif
endif
C maxdim %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('maxdim',6,maxdim,4)
if(maxdim.eq.' ') then
write(maxdim,'(i4)') max(200,3*max(nntrip,nnsing))
maxdim=adjustl(maxdim)
endif
C dhexc %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dhexc',5,dhexc,10)
if(dhexc.ne.' '.and.trim(dhexc).ne.'adc(2)'
$ .and.trim(dhexc).ne.'cis(d)'
$ .and.trim(dhexc).ne.'sos-adc(2)'
$ .and.trim(dhexc).ne.'scs-adc(2)'
$ .and.trim(dhexc).ne.'sos-cis(d)'
$ .and.trim(dhexc).ne.'scs-cis(d)')
$call unknown('dhexc',5)
if(dhexc.eq.' ') dhexc='adc(2) '
C scsps %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scsps',5,scsps,16)
if((trim(calc).eq.'cis(di)'.or.trim(calc).eq.'adc(2)'.or.
$trim(calc).eq.'cc2'.or.trim(calc).eq.'cis(d)'.or.
$((trim(calc).eq.'cis'.or.trim(calc).eq.
$'tda'.or.trim(calc).eq.'scf'.or.trim(calc).eq.'tddft'.or.
$trim(calc).eq.'tdhf').and.nnstate.gt.1))
$.and.scsps.eq.' '.and.(
$trim(dhexc).ne.'scs-adc(2)'.and.trim(dhexc).ne.'scs-cis(d)'))
$scsps='0.0d0 '
if(scsps.eq.' ') scsps='1.2d0 '
if(trim(calc).eq.'sos-cis(di)'.or.trim(calc).eq.'sos-adc(2)'.or.
$trim(calc).eq.'sos-cc2'.or.trim(calc).eq.'sos-cis(d)'.or.
$trim(dhexc).eq.'sos-adc(2)'.or.trim(dhexc).eq.'sos-cis(d)')
$scsps='1.3d0 '
C scsps_t %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scsps_t',7,scsps_t,16)
if(scsps_t.eq.' ')
$scsps_t=scsps
C scspt %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scspt',5,scspt,16)
if((trim(calc).eq.'cis(di)'.or.trim(calc).eq.'adc(2)'.or.
$trim(calc).eq.'cc2'.or.trim(calc).eq.'cis(d)'.or.
$((trim(calc).eq.'cis'.or.trim(calc).eq.
$'tda'.or.trim(calc).eq.'scf'.or.trim(calc).eq.'tddft'.or.
$trim(calc).eq.'tdhf').and.nnstate.gt.1))
$.and.scspt.eq.' '.and.(
$trim(dhexc).ne.'scs-adc(2)'.and.trim(dhexc).ne.'scs-cis(d)'))
$scspt='0.0d0 '
if(scspt.eq.' ') scspt='0.33333333333333'
if(trim(calc).eq.'sos-cis(di)'.or.trim(calc).eq.'sos-adc(2)'.or.
$trim(calc).eq.'sos-cc2'.or.trim(calc).eq.'sos-cis(d)'.or.
$trim(dhexc).eq.'sos-adc(2)'.or.trim(dhexc).eq.'sos-cis(d)') then
scspt='0.0d0 '
if(trim(calc).eq.'sos-cis(di)')
$calc='cis(di) '
if(trim(calc).eq.'sos-cc2')
$calc='cc2 '
if(trim(calc).eq.'sos-adc(2)')
$calc='adc(2) '
if(trim(calc).eq.'sos-cis(d)')
$calc='cis(d) '
endif
if(trim(calc).eq.'scs-cis(di)')
$calc='cis(di) '
if(trim(calc).eq.'scs-cc2')
$calc='cc2 '
if(trim(calc).eq.'scs-adc(2)')
$calc='adc(2) '
if(trim(calc).eq.'scs-cis(d)')
$calc='cis(d) '
C scspt_t %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scspt_t',7,scspt_t,16)
if(scspt_t.eq.' ')
$scspt_t=scspt
C dft %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
if(dft.eq.' ') then
call getkeym('dft',3,dft,32)
call setedisp(dft1,edisp) ! set edisp and remove -D3 postfix if present
#if defined (LIBXC)
call libxcconv(dft)
#endif
if(.not.ldftfunc(dft).and.
$ .not.dhdft(dft).and.
$ trim(dft).ne.'drpa75'.and.
$ trim(dft).ne.'scs-drpa75'.and.
$ trim(dft).ne.'user'.and.
$ trim(dft).ne.'userd'.and.
$ trim(dft).ne.'rsdh'.and.
$ trim(dft).ne.'off'.and.
$ trim(dft).ne.'') call unknown('dft',3)
endif
if(trim(dft).eq.'') then
if((trim(calc).eq.'drpa'.and.trim(scspe).ne.'0.d0').or.
$ trim(calc).eq.'sosex'.or.
$ trim(calc).eq.'rpa') then
dft='pbe '
else if(trim(calc).eq.'rpax2') then
dft='pbex '
else
dft='off '
endif
endif
if(dft.ne.'off ') then
call getkeym('dfbasis_scf',11,c20,20)
if(c20.eq.' ')
$ dfbasis_scf='auto '
endif
l1=.false.
l2=.false.
l3=.false.
l4=.false.
l5=.false.
cmp2=0.d0
cmp2t=0.d0
cmp3=0.d0
cmp3s=0.d0
cmp3t=0.d0
if(trim(dft).eq.'user'.or.trim(dft).eq.'userd') then
call getkeym('dft',3,dft,32)
read(minpfile,*) n
do i=1,n
read(minpfile,*) tmp,c32
c32=adjustl(c32)
call lowercase(c32,c32,32)
if(c2.eq.'lr'.or.c2.eq.'sr') then
c2=' '
c32=adjustl(c32)
endif
if(trim(c32).eq.'mp2') cmp2=tmp
if(trim(c32).eq.'mp2t') cmp2t=tmp
ll1=trim(c32).eq.'mp2'.or.trim(c32).eq.'mp2s'.or.
$ trim(c32).eq.'mp2t'
ll2=trim(c32).eq.'drpa' .or.trim(c32).eq.'drpas'.or.
$ trim(c32).eq.'drpae'.or.trim(c32).eq.'drpat'
ll3=trim(c32).eq.'sosex'.or.trim(c32).eq.'sosexs'.or.
$ trim(c32).eq.'sosext'
if(trim(c32).eq.'mp3') cmp3=tmp
if(trim(c32).eq.'mp3s') cmp3s=tmp
if(trim(c32).eq.'mp3t') cmp3t=tmp
ll4=trim(c32).eq.'mp3'.or.trim(c32).eq.'mp3t'
ll5=trim(c32).eq.'mp3s'
if(ll1.or.ll2.or.ll3.or.ll4.or.ll5) then
l1=l1.or.ll1
l2=l2.or.ll2
l3=l3.or.ll3
l4=l4.or.ll4
l5=l5.or.ll5
if(trim(c32).eq.'drpae') then
write(scspe,'(f16.10)') tmp
scspe=adjustl(scspe)
endif
if((trim(c32).eq.'drpas'.or.trim(c32).eq.'mp2s'.or.
$ trim(c32).eq.'sosexs').and.nnstate.le.1) then
write(scsps,'(f16.10)') tmp
scsps=adjustl(scsps)
endif
if((trim(c32).eq.'drpat'.or.trim(c32).eq.'mp2t'.or.
$ trim(c32).eq.'sosext').and.nnstate.le.1) then
write(scspt,'(f16.10)') tmp
scspt=adjustl(scspt)
endif
endif
enddo
if(trim(dft).eq.'userd') then
read(minpfile,*) n
do i=1,n
read(minpfile,*) tmp,c32
c32=adjustl(c32)
call lowercase(c32,c32,32)
if(c2.eq.'lr'.or.c2.eq.'sr') then
c2=' '
c32=adjustl(c32)
endif
if(trim(c32).eq.'mp2') cmp2=tmp
if(trim(c32).eq.'mp2t') cmp2t=tmp
ll1=trim(c32).eq.'mp2'.or.trim(c32).eq.'mp2s'.or.
$ trim(c32).eq.'mp2t'
ll2=trim(c32).eq.'drpa' .or.trim(c32).eq.'drpas'.or.
$ trim(c32).eq.'drpae'.or.trim(c32).eq.'drpat'
ll3=trim(c32).eq.'sosex'.or.trim(c32).eq.'sosexs'.or.
$ trim(c32).eq.'sosext'
if(trim(c32).eq.'mp3') cmp3=tmp
if(trim(c32).eq.'mp3s') cmp3s=tmp
if(trim(c32).eq.'mp3t') cmp3t=tmp
ll4=trim(c32).eq.'mp3'.or.trim(c32).eq.'mp3t'
ll5=trim(c32).eq.'mp3s'
if(ll1.or.ll2.or.ll3.or.ll4.or.ll5) then
l1=l1.or.ll1
l2=l2.or.ll2
l3=l3.or.ll3
l4=l4.or.ll4
l5=l5.or.ll5
if(trim(c32).eq.'drpae') then
write(scspe,'(f16.10)') tmp
scspe=adjustl(scspe)
endif
if((trim(c32).eq.'drpas'.or.trim(c32).eq.'mp2s'.or.
$ trim(c32).eq.'sosexs').and.nnstate.le.1) then
write(scsps,'(f16.10)') tmp
scsps=adjustl(scsps)
endif
if((trim(c32).eq.'drpat'.or.trim(c32).eq.'mp2t'.or.
$ trim(c32).eq.'sosext').and.nnstate.le.1) then
write(scspt,'(f16.10)') tmp
scspt=adjustl(scspt)
endif
endif
enddo
endif
endif
if(dhdft(dft).or.l1.or.l4) then
if((trim(calc).eq.'cis'.or.trim(calc).eq.
$'tda'.or.trim(calc).eq.'scf'.or.trim(calc).eq.'tddft'.or.
$trim(calc).eq.'tdhf').and.nnstate.gt.1) then
if(trim(dhexc).eq.'adc(2)'.or.
$trim(dhexc).eq.'sos-adc(2)'.or.trim(dhexc).eq.'scs-adc(2)') then
calc='adc(2) '
if(trim(calc).eq.'scf'.or.trim(calc).eq.'tddft'.or.
$trim(calc).eq.'tdhf') then
write(iout,*) 'Double hybrid TDDFT for excited states
$is available only '
write(iout,*) 'with the TDA approximation!'
call mrccend(1)
endif
endif
else
calc='mp2 '
if(l1.and.dabs(cmp2).lt.1d-12.and.dabs(cmp2t).lt.1d-12) then
calc='drpa '
scspe='0.d0 '
endif
if(l5) then
calc='os-mp3 '
scspe='0.d0 ' ! ???
endif
if(l4) then
calc='mp3 '
scspe='0.d0 ' ! ???
endif
if(dfbasis_cor.eq.'none ')
$ dfbasis_cor='auto '
endif
endif
if(trim(dft).eq.'drpa75'.or.trim(dft).eq.'scs-drpa75'.or.l2) then
calc='drpa '
if(dfbasis_cor.eq.'none ')
$ dfbasis_cor='auto '
endif
if(l3) then
calc='sosex '
if(dfbasis_cor.eq.'none ')
$ dfbasis_cor='auto '
endif
if(trim(dens).eq.'0'.and.trim(grdens).ne.'off'.and.
$trim(calc).ne.'scf') then
dens='1 '
cctol='8 '
endif
if(trim(dft).eq.'user'.or.trim(dft).eq.'userd') then
locdhdft=locdhdft.or.(localccn.gt.0.and.(
$ cmp2.ne.0.d0.or.cmp2t.ne.0.d0))
localmp2=locdhdft.or.localmp2
endif
C bpedo %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bpedo',5,bpedo,16)
if(bpedo.ne.' ') then
read(bpedo,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('bpedo',5)
endif
if(bpedo.eq.' '.and..not.localcc16p) then
bpedo=bpcompo ! initialize for 2015
elseif (bpedo.eq.' '.and.localcc16p) then
if(lcorthr.eq.'0 ') then
bpedo= '1.d0 '
elseif(localcc.eq.'2016'.and.localmp2.and.
$ (lcorthr.eq.'loose '.or.lcorthr.eq.'normal ')) then
bpedo= '0.9998d0 ' ! default LMP2 in 2016 paper
elseif(lcorthr.eq.'tight ') then ! tight 2018 MP2 or LCC and tight 2016 LCC according to the released code
bpedo= '0.99995d0 '
if(localcc.eq.'2016'.and.localmp2) bpedo= '0.9999d0 '!tight 2016 LMP2
c elseif(lcorthr.eq.'tight '.and.localcc.eq.'2016') then !
c bpedo= '0.9999d0 ' ! this 2 commented lines matche the typo in previous manuals for localcc=2016
elseif(lcorsel.eq.'vtightpp'.and.(locanycc.or.localmp2)) then
bpedo= '0.99999d0 '
else
bpedo= '0.9999d0 ' ! default 2018 LMP2, normal (or looser) LCC for localcc>2015, tight 2016 LCC
endif
endif
if(localcc16p) then
read(bpedo,*) rr
read(bpcompo,*) tmp
if (rr.lt.tmp) then
write(iout,*)
$ 'BPcompo.gt.BPEDo is not supported and not recommeneded'
call mrccend(1)
endif
endif
C bpocc %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bpocc',5,bpocc,16)
if(bpocc.ne.' ') then
read(bpocc,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('bpocc',5)
endif
if(bpocc.eq.' ') bpocc=bpedo
C diag %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('diag',4,diag,6)
if(diag.ne.'david '.and.diag.ne.'olsen '.and.diag.ne.'follow'
$.and.diag.ne.' ') call unknown('diag',4)
if(diag.eq.' ') diag='david '
C domrad %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('domrad',6,domrad,16)
if(domrad.eq.' ') domrad='10.d0 '
rr=-1.d0
if(domrad.ne.'inf ') read(domrad,*) rr
if(rr.lt.0.d0.and.domrad.ne.'inf ')
$call unknown('domrad',6)
if(domrad.eq.'inf ') domrad='1e30 '
C drpaalg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('drpaalg',7,drpaalg,8)
if(drpaalg.ne.'fit '.and.drpaalg.ne.'nofit '.and.
$ drpaalg.ne.'auto '.and.drpaalg.ne.'plasmon '.and.
$drpaalg.ne.' ') call unknown('drpaalg',7)
if(drpaalg.eq.' ') then
if(localcc.ne.'off ') then
drpaalg='auto '
else
drpaalg='fit '
endif
endif
c if(drpaalg.eq.' ') drpaalg='auto '
if(trim(calc).eq.'sosex'.or.
$ trim(calc).eq.'rpax2') drpaalg='fit '
C pssp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('pssp',4,pssp,8)
if(pssp.ne.'on '.and.pssp.ne.'off '.and.
$ pssp.ne.' ') call unknown('pssp',8)
if(pssp.eq.' ') pssp='off '
C dual_df %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dual_df',7,dual_df,8)
if(dual_df.ne.'dab '.and.dual_df.ne.'off '.and.
$ dual_df.ne.'dm '.and.dual_df.ne.'grid '.and.
& dual_df.ne.' ') call unknown('dual_df',7)
if(pssp.eq.'on '.and.dual_df.ne.'off ')
& dual_df='grid '
if(dual_df.eq.' ') then
if(grid_sm.ne.grid) then
dual_df='dab '
else
dual_df='off '
endif
endif
C dual %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dual',4,dual,8)
if(dual.ne.'on '.and.dual.ne.'off '.and.
$ dual.ne.'e1 '.and.dual.ne.'e2 '.and.
$dual.ne.' ') call unknown('dual',4)
if(dual.eq.' ') dual='off '
if(lf12) then
if(dual.ne.'off ') then
write(iout,*)
$'Dual-basis SCF is not compatible with F12 calculations!'
call mrccend(1)
endif
dual='on '
basis_sm=basis
endif
C ecp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ecp',3,ecp,20)
if(ecp.eq.' ') ecp='auto '
C edisp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
if(trim(edisp).ne.'auto') then
call getkeym('edisp',5,edisp,256)
if(trim(edisp).ne.'') then
backspace(minpfile)
read(minpfile,"(a6,a256)") cscr6,edisp
else
edisp='off'
endif
endif
C embed %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('embed',5,embed,8)
if(embed.ne.' '.and.embed.ne.'off '.and.
$ embed.ne.'project '.and.embed.ne.'huzinaga'.and.
$ embed.ne.'scl '.and.embed.ne.'emft '.and.
$ embed.ne.'fdm '.and.embed.ne.'coulomb '.and.
$ embed.ne.'sch ')
$call unknown('embed',5)
if(embed.eq.' ') embed='off '
edisp_embed=' ' !HB
if(embed.ne.'off ') then
read(minpfile,*)
read(minpfile,*) c32
call lowercase(c32,c32,32)
call setedisp(c32,edisp_embed) !HB
if(.not.ldftfunc(c32).and.trim(c32).ne.'hf'.and.
$trim(c32).ne.'user') call unknown('embed',5)
if(dfbasis_scf.eq.'none ')
$dfbasis_scf='auto '
if(dfbasis_cor.eq.'none ')
$dfbasis_cor='auto '
endif
if((dual.eq.'e1 '.or.dual.eq.'e2 ').and.
$embed.eq.'off ') then
write(iout,*) 'dual=e* is not compatible with embed=off!'
call mrccend(1)
endif
if(dual.eq.'on '.and.embed.ne.'off '.and.
$embed.ne.'emft ') then
write(iout,*) 'dual=on is not compatible with embed=' //
$trim(embed) // '!'
call mrccend(1)
endif
C edisp_embed %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
! HB
if(trim(edisp_embed).ne.'auto') then
call getkeym('edisp_embed',11,edisp_embed,256)
if(trim(edisp_embed).ne.'') then
backspace(minpfile)
read(minpfile,"(a12,a256)") cscr12,edisp_embed
else
edisp_embed='off'
endif
endif
!NP
C corembed %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
c WARNING: any changes introduced here or in the default settings of the method
c for the environment should be made consitent with the settings of subroutine savelkey !NP
call getkeym('corembed',8,corembed,8)
if(corembed.ne.' '.and.corembed.ne.'off '.and.
$ corembed.ne.'on ') call unknown('corembed',8)
if(corembed.eq.' ') corembed='off '
if(corembed.ne.'off '.and..not.localcc15p(localcc)) then
write(iout,*) 'Error: corembed is only available with',
$ ' localcc>=2015'
call mrccend(1)
endif
if(corembed.ne.'off ') then
read(minpfile,*)
read(minpfile,*) c32
call lowercase(c32,c32,clen)
if (lstartwlno(c32).and.trim(c32).ne.'hf') then ! for the LNO- synonym
call removeprefix(c32_1,clen,4)
ll1=.false.
elseif (lstartwl(c32).and.trim(c32).ne.'hf') then ! for the L synonym
call removeprefix(c32_1,clen,1)
ll1=.false.
elseif(c32_1(1).ne.'l'.and.
$ (trim(c32).eq.'hf'.or.
$ trim(c32).eq.'hf+lrc')) then
ll1=.false.
else
ll1=.true.
endif
if( trim(c32).ne.'hf'.and.
$ trim(c32).ne.'hf+lrc'.and.
$ .not.lanycc(c32).and. ! RPA variants are not in lanycc and excluded from corembed calculations
$ trim(c32).ne.'mp2'.and.
$ trim(c32).ne.'scs-mp2'.and.
$ trim(c32).ne.'sos-mp2') ll1=.true.
if (ll1) call unknown('corembed',8)
if (.not.lanycc(calc).and.
$ trim(calc).ne.'mp2'.and.
$ trim(calc).ne.'scs-mp2'.and.
$ trim(calc).ne.'sos-mp2') then
write(iout,*) 'Error: choose from the list of allowed active',
$ 'subsystem models'
call mrccend(1)
endif
endif
!NP
C epert %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('epert',5,epert,8)
if(epert.ne.' '.and.epert.ne.'none ') then
read(epert,*) i
if(i.lt.0.or.i.gt.9) call unknown('epert',5)
endif
if(epert.eq.' ') epert='none '
C eps %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('eps',3,eps,16)
if(eps.ne.' ') then
read(eps,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('eps',3)
endif
c if(eps.eq.' ') eps='0.975 '
C excrad %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('excrad',6,excrad,16)
if(excrad.eq.' ') excrad='0.d0 '
read(excrad,*) rr
if(rr.lt.0.d0) call unknown('excrad',6)
C fitting %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('fitting',7,fitting,8)
if(dual_df.eq.'dm '.and.fitting.eq.'coulomb ') then
write(iout,*)
& ' Error: Set fitting=overlap for dual metric calculations '
call mrccend(1)
endif
if(fitting.eq.' '.and.dual_df.eq.'dm ')
& fitting='overlap '
if(fitting.eq.' ') fitting='coulomb '
if(fitting.ne.'coulomb '.and.fitting.ne.'overlap ') then
call unknown('fitting',7)
endif
C gamma %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('gamma',5,gamma,16)
if(gamma.eq.' ') then
gamma='1.d0 '
if(trim(basis).eq.'cc-pvdz-f12') gamma='0.9d0 '
if(trim(basis).eq.'cc-pvqz-f12') gamma='1.1d0 '
if(trim(basis).eq.'aug-cc-pvtz') gamma='1.1d0 '
if(trim(basis).eq.'aug-cc-pvqz') gamma='1.4d0 '
if(trim(basis).eq.'aug-cc-pv5z') gamma='1.4d0 '
endif
read(gamma,*) rr
if(rr.lt.0.d0) call unknown('gamma',6)
C gauss %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('gauss',5,gauss,5)
if(gauss.ne.'spher'.and.gauss.ne.'cart '.and.
$gauss.ne.' ') call unknown('gauss',5)
if(dens.ne.'0 '.and.dens.ne.'1 '.and.gauss.eq.'cart ') then
write(iout,*)
$'Analytic derivatives are not available with Cartesian Gaussians!'
call mrccend(1)
endif
if(gauss.eq.' ') gauss='spher'
C geom %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('geom',4,geom,4)
if(geom.ne.'xyz '.and.geom.ne.'zmat'.and.geom.ne.'tmol'.and.
$geom.ne.'mol '.and.geom.ne.' ') call unknown('geom',4)
if(geom.eq.' ') geom='zmat'
C ghost %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ghost',5,ghost,8)
if(ghost.ne.' '.and.ghost.ne.'none '.and.
$ ghost.ne.'serialno') call unknown('ghost',6)
if(ghost.eq.' ') ghost='none '
C gtol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('gtol',4,gtol,4)
if(gtol.eq.' ') gtol='7 '
C grtol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('grtol',5,grtol,4)
if(grtol.eq.' ') grtol='10 '
read(grtol,*) i
if(i.lt.0) call unknown('grtol',5)
!!!
C scf_conv %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scf_conv',8,scf_conv,12)
if(scf_conv.ne.' '.and.
$ scf_conv.ne.'manual '.and.
$ scf_conv.ne.'fast '.and.
$ scf_conv.ne.'auto '.and.
$ scf_conv.ne.'old '.and.
$ scf_conv.ne.'normal '.and.
$ scf_conv.ne.'difficult ')
$call unknown('scf_conv',8)
if(scf_conv.eq.' ') scf_conv='auto '
!!!
C scftol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scftol',6,scftol,4)
if(scftol.eq.' ') then
scftol='6 '
if(dens.ne.'0 '.or.freq.ne.'off ') scftol='8 '
if(trim(calc).ne.'scf') then
read(scftol,*) i
read(cctol ,*) j
write(scftol,'(i4)') max(i,j)
c write(scftol,'(i4)') max(i,j+1)
scftol=adjustl(scftol)
endif
endif
C scfdtol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdtol',7,scfdtol,4)
if(scfdtol.eq.' ') then
read(scftol,*) i
c i=i+1
if(freq.ne.'off ') then
i=i+2
else if(trim(calc).ne.'scf'.or.
$(trim(calc).eq.'scf'.and.nnstate.gt.1)) then
i=i+1
endif
write(scfdtol,'(i4)') i
scfdtol=adjustl(scfdtol)
endif
C ldfgrad_tol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ldfgrad_tol',11,ldfgrad_tol,8)
if(ldfgrad_tol.eq.' ') ldfgrad_tol='8 '
C hamilton %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('hamilton',8,hamilton,8)
if(hamilton.ne.' '.and.hamilton.ne.'dc '.and.
$ hamilton.ne.'x2cmmf ') call unknown('hamilton',8)
if(hamilton.eq.' ') hamilton='dc '
C intalg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('intalg',6,intalg,4)
if(intalg.ne.'os '.and.intalg.ne.'rys '.and.
$ intalg.ne.'auto'.and.intalg.ne.'herm'.and.
$ intalg.ne.' ') call unknown('intalg',6)
if(intalg.eq.' ') intalg='auto'
if((intalg.eq.'herm'.or.intalg.eq.'os ').and.gauss.eq.'cart ')
$then
write(iout,*)
$'Incompatible options for keywords intalg and gauss!'
call mrccend(1)
endif
if(intalg.eq.'auto'.and.gauss.eq.'cart ') intalg='rys '
if(dfbasis_cor.ne.'none '.and.intalg.eq.'herm')
$then
write(iout,*)
$'Incompatible options for keywords intalg and dfbasis_cor!'
call mrccend(1)
endif
if(dfbasis_scf.ne.'none '.and.intalg.eq.'herm')
$then
write(iout,*)
$'Incompatible options for keywords intalg and dfbasis_scf!'
call mrccend(1)
endif
if(lf12) intalg='os '
C itol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('itol',4,itol,4)
if(itol.eq.' ') then
itol='10 '
read(itol ,*) i
read(scftol,*) j
read(scfdtol,*) k
c if(gopt.ne.'off '.or.freq.ne.'off ') k=max(k,14)
write(itol,'(i4)') max(i,j+4,k)
itol=adjustl(itol)
endif
!NP
C laptol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('laptol',6,laptol,16)
if(laptol.ne.' ') then
read(laptol,*) ltol
if(ltol.le.0.d0) then
write(iout,*) 'Positive laptol value is expected'
call mrccend(1)
endif
if (lcorsel.eq.'vtightpp'.or.lcorthr.eq.'tight ') then
if(ltol.gt.1.d-3) write(iout,*) 'Warning: laptol.gt.1.d-3 is',
$' not recommended in combination with lcorthr tight settings'
endif
c write(laptol,'(es16.8)') ltol
else
c Warning: if laptol=1.d-2 default is changed, modify elaptol in the corembed part of dmrcc.f accordingly
laptol='1.d-2 ' ! normal 2016 or 2018 LNO-CC
if (lcorsel.eq.'vtightpp'.or.lcorthr.eq.'tight ')
$ laptol='1.d-3 '
if (lcorsel.eq.'anyloose') laptol='1.d-1 '
if(lcorthr.eq.'0 ') laptol='1.d-6 '
endif
C lmp2dens %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('lmp2dens',8,lmp2dens,3)
if(lmp2dens.ne.'on '.and.lmp2dens.ne.'off'.and.
$lmp2dens.ne.' ') call unknown('lmp2dens',8)
if(lmp2dens.eq.' ') lmp2dens='on '
C boysalg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('boysalg',7,boysalg,8)
if(boysalg.ne.'newton '.and.boysalg.ne.'jacobi '.and.
& boysalg.ne.' ') call unknown('boysalg',7)
if(boysalg.eq.' ') boysalg='jacobi '
C olnofact %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% ! for development NP
call getkeym('olnofact',8,olnof,16)
if(olnof.eq.' ') then
olnofact=1.d0
else
read(olnof,*) olnofact
endif
C vlnofact %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% ! for development NP
call getkeym('vlnofact',8,vlnof,16)
if(vlnof.eq.' ') then
vlnofact=1.d0
else
read(vlnof,*) vlnofact
endif
!NP
C mact %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('mact',4,mact,256)
if(scftype.eq.'mcscf'.and.trim(mact).eq.'')call unknown('mact',5)
! Default is set by scf
C nacto %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('nacto',5,nacto,4)
if(nacto.eq.' ') nacto='0 '
read(nacto,*) i
if(i.lt.0) call unknown('nacto',5)
C nactv %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('nactv',5,nactv,4)
if(nactv.eq.' ') nactv='0 '
read(nactv,*) i
if(i.lt.0) call unknown('nactv',5)
C ccprog %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ccprog',6,ccprog,4)
if(ccprog.ne.'mrcc'.and.ccprog.ne.'ccsd'.and.ccprog.ne.'cis '
$.and.ccprog.ne.' ') call unknown('ccprog',6)
if(ccprog.eq.' ') then
c if(dens.eq.'0 '.and.(mult.eq.'1 '.or.mult.eq.' ').and.
c $scftype.ne.'uhf '.and.scftype.ne.'rohf '.and.
if(dens.eq.'0 '.and.scftype.ne.'mcscf'.and.!scftype.ne.'rohf '.and. !Bernat
$((trim(calc).eq.'mp2'.and.trim(dfbasis_cor).eq.'none').or.
$trim(calc).eq.'mp3'.or.trim(calc).eq.'ccsd'.or.
$trim(calc).eq.'ccsd(t)'.or.trim(calc).eq.'ccsd-f12'.or.
$trim(calc).eq.'ccsd(t)-f12').and.
$nnstate.eq.1.and.iface.eq.'none '.and.
$nacto.eq.'0 '.and.nactv.eq.'0 '.and.freq.eq.'off ') then
ccprog='ccsd'
else if((trim(calc).eq.'cis'.or.trim(calc).eq.'cc2'.or.
$trim(calc).eq.'cis(di)'.or.trim(calc).eq.'adc(2)'.or.
$trim(calc).eq.'cis(d)'.or.
$trim(calc).eq.'tda'.or.trim(calc).eq.'tdhf'.or.
$(trim(calc).eq.'scf'.and.nnstate.gt.1).or.
$trim(calc).eq.'tddft').and.
$dfbasis_cor.ne.'none ') then
ccprog='cis '
if(trim(calc).eq.'tda')
$calc='cis '
if(trim(calc).eq.'tdhf'.or.trim(calc).eq.'tddft')
$calc='scf '
else
ccprog='mrcc'
c ! Default is set by integ
endif
endif
if(ccprog.ne.'ccsd'.and.trim(calc).eq.'mp3') then
write(iout,*)
write(iout,*)
$'MP3 calculation can only be performed with ccprog=ccsd!'
call mrccend(1)
endif
if(ccprog.eq.'ccsd'.and.
$trim(calc).ne.'mp2'.and.trim(calc).ne.'mp3'.and.
$trim(calc).ne.'ccsd'.and.trim(calc).ne.'ccsd(t)'.and.
$.not.lf12.and.trim(calc).ne.'scf') then
call uppercase(calc,calc,32)
write(iout,*)
write(iout,*) trim(calc) //
$' calculation cannot be performed with program ccsd!'
call mrccend(1)
else if(ccprog.ne.'ccsd'.and.ccprog.ne.'mrcc'.and.lf12) then
call uppercase(calc,calc,32)
write(iout,*)
write(iout,*) trim(calc) //
$' calculation cannot be performed with ccprog='//trim(ccprog)//'!'
call mrccend(1)
endif
c csapprox %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('csapprox',8,csapprox,16)
if (csapprox.ne.' '.and.trim(csapprox).ne.'off'
& .and.trim(csapprox).ne.'on') call unknown('csapprox',8)
if (csapprox.eq.' ') csapprox='off '
C ovirt %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ovirt',5,ovirt,4)
if(ovirt.ne.'off '.and.ovirt.ne.'mp2 '.and.ovirt.ne.'osv '.and.
$ovirt.ne.'ovos'.and.ovirt.ne.'ppl '.and.ovirt.ne.' ')
$call unknown('ovirt',5)
if(ovirt.eq.' ') then
if(lfno) then
if(trim(ccprog).eq.'ccsd'.and..not.lf12) then
ovirt='ppl '
elseif(trim(ccprog).eq.'mrcc'.or.lf12) then
ovirt='mp2 '
end if
else
ovirt='off '
end if
end if
if(ovirt.eq.'ppl '.and.ccprog.eq.'mrcc') then
write(iout,*)
$'Incompatible options for keywords ovirt and ccprog!'
call mrccend(1)
endif
if(ovirt.ne.'off '.and.localcc.ne.'off ') then
write(iout,*)
$'Incompatible options for keywords ovirt and localcc!'
call mrccend(1)
endif
C denscorr %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('denscorr',8,denscorr,4)
if(denscorr.ne.' '.and.denscorr.ne.'0 '.and.
$ denscorr.ne.'1 '.and.denscorr.ne.'2 ')
$call unknown('denscorr',8)
if(denscorr.eq.' ') denscorr='0 '
C redcost_exc %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('redcost_exc',11,redcost_exc,4)
if(redcost_exc.ne.' '.and.redcost_exc.ne.'on '.and.
$ redcost_exc.ne.'off '.and.redcost_exc.ne.'cust'.and.
$ redcost_exc.ne.'1 '.and.redcost_exc.ne.'2 '.and.
$ redcost_exc.ne.'3 '.and.redcost_exc.ne.'4 '.and.
$ redcost_exc.ne.'5 '.and.redcost_exc.ne.'6 '.and.
$ redcost_exc.ne.'7 '.and.redcost_exc.ne.'8 '.and.
$ redcost_exc.ne.'9 '.and.redcost_exc.ne.'10 ')
$call unknown('redcost_exc',11)
if(redcost_exc.eq.' ') redcost_exc='off '
if(redcost_exc.eq.'on '.and.localcc.ne.'off ') then
redcost_exc='6 '
elseif(redcost_exc.eq.'on '.and.localcc.eq.'off ') then
redcost_exc='1 '
endif
C nafdens %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('nafdens',7,nafdens,4)
if(nafdens.ne.' '.and.nafdens.ne.'on '.and.nafdens.ne.'off ')
$ call unknown('nafdens',7)
if(redcost_exc.eq.'6 '.and.localcc.ne.'off '.and.
$nafdens.eq.' ') nafdens='on '
if(nafdens.eq.' ') nafdens='off '
C lnoepsv %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('lnoepsv',7,lnoepsv,16)
if(lnoepsv.ne.' ') then
read(lnoepsv,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('lnoepsv',7)
endif
if(lnoepsv.eq.' ') then
if(trim(ccprog).eq.'cis') then ! MD
if(redcost_exc.eq.'3 '.or.redcost_exc.eq.'8 '.or.
$ redcost_exc.eq.'off '.or.(trim(calc).eq.'cis'.or.
$ trim(calc).eq.'scf')) then
lnoepsv='0.0d0 '
else
read(scspt,*) tmp
read(scspt_t,*) tmp3
tmp=max(tmp,tmp3)
read(scsps,*) tmp2
read(scsps_t,*) tmp3
tmp2=max(tmp2,tmp3)
if(tmp.ne.0.d0.or.tmp2.ne.0.d0) then
lnoepsv='0.000030d0 '
else
lnoepsv='0.000075d0 '
endif
endif
elseif(trim(ccprog).ne.'cis') then
if(lcorthr.eq.'0 ') then
lnoepsv='0.d0 '
else
if (localcc.eq.'2013') then
lnoepsv='1e-6 ' ! 2013 default LCC
elseif (localcc.eq.'2015'.and.(localrpa.or.lanycc(calc))) then
lnoepsv='1e-6 ' ! normal LdRPA and 2015/16 LNO-CC
if(lcorthr.eq.'tight ') lnoepsv='3e-7 ' ! 2015 tight for LdRPA or LCC
elseif(localcc.eq.'2016'.and.lanycc(calc)) then
if(lcorthr.eq.'vvloose ') then
lnoepsv='4e-6 '
else if(lcorthr.eq.'vloose ') then
lnoepsv='2e-6 '
else if(lcorthr.eq.'tight ') then
lnoepsv='5e-7 '
else if(lcorthr.eq.'vtight ') then
lnoepsv='2.5e-7 '
else if(lcorthr.eq.'vvtight ') then
lnoepsv='1.25e-7 '
else if(lcorthr.eq.'v3tight ') then
lnoepsv='5e-8 '
else if(lcorthr.eq.'v4tight ') then
lnoepsv='2.5e-8 '
else
lnoepsv='1e-6 ' ! normal/loose for 2016 LCC
endif
elseif(localccn.ge.2018.and.lanycc(calc)) then
if(lcorthr.eq.'vloose ') then
lnoepsv='1e-5 '
else if(lcorthr.eq.'loose ') then
lnoepsv='3e-6 '
else if(lcorthr.eq.'tight ') then
lnoepsv='3e-7 '
else if(lcorthr.eq.'vtight ') then
lnoepsv='1e-7 '
else if(lcorthr.eq.'vvtight ') then
lnoepsv='3e-8 '
else
lnoepsv='1e-6 ' ! normal 2018< LCC
endif
else if(ccprog .eq. 'ccsd') then
lnoepsv = '5e-5 '
else
lnoepsv='1e-6 ' ! initialize for the remaining cases, e.g. 2016/2018 localmp2
endif ! localcc.eq....
endif ! lcorthr.eq.'0 ')
if(lf12.and.trim(ovirt).ne.'off') then !Reduced-cost CC-F12
if(trim(basis).eq.'cc-pvdz-f12'.or.
$ trim(basis).eq.'aug-cc-pvdz') then
lnoepsv='1e-4 '
else if(trim(basis).eq.'cc-pvqz-f12'.or.
$ trim(basis).eq.'aug-cc-pvqz') then
lnoepsv='1e-6 '
else
lnoepsv='1e-5 '
endif
endif
endif ! trim(ccprog).eq.'cis'
endif !(lnoepsv.eq.' ')
c
if(vlnofact.ne.1.d0) then
read(lnoepsv,*) rr
write(lnoepsv,'(e16.8)') rr/vlnofact
lnoepsv=adjustl(lnoepsv)
endif
C lnoepso %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('lnoepso',7,lnoepso,16)
if(lnoepso.ne.' ') then
read(lnoepso,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('lnoepso',7)
endif
if(lnoepso.eq.' ') then
if(trim(ccprog).eq.'cis') then !MD
lnoepso='0.d0 '
elseif(trim(ccprog).ne.'cis') then
if(lcorthr.eq.'0 ') then
lnoepso='0.d0 '
else
if (localcc.eq.'2013') then
lnoepso='3e-5 ' ! 2013 default LCC
elseif (localcc.eq.'2015'.and.(localrpa.or.lanycc(calc))) then
lnoepso='3e-5 ' ! 2015 default for LdRPA or LCC
if(lcorthr.eq.'tight ') lnoepso='1e-5 ' ! 2015 tight for LdRPA or LCC
elseif(localcc.eq.'2016'.and.lanycc(calc)) then
if(lcorthr.eq.'vvloose ') then
lnoepso='8e-5 '
else if(lcorthr.eq.'vloose ') then
lnoepso='4e-5 '
else if(lcorthr.eq.'tight ') then
lnoepso='1e-5 '
else if(lcorthr.eq.'vtight ') then
lnoepso='5e-6 '
else if(lcorthr.eq.'vvtight ') then
lnoepso='2.5e-6 '
else if(lcorthr.eq.'v3tight ') then
lnoepso='1e-6 '
else if(lcorthr.eq.'v4tight ') then
lnoepso='5e-7 '
else
lnoepso='2e-5 ' ! normal/loose for 2016 LCC
endif
elseif(localccn.ge.2018.and.lanycc(calc)) then
if(lcorthr.eq.'vloose ') then
lnoepso='1e-4 '
else if(lcorthr.eq.'loose ') then
lnoepso='3e-5 '
else if(lcorthr.eq.'tight ') then
lnoepso='3e-6 ' ! tight 2018 LNO-CC
else if(lcorthr.eq.'vtight ') then
lnoepso='1e-6 '
else if(lcorthr.eq.'vvtight ') then
lnoepso='3e-7 '
else
lnoepso='1e-5 ' ! normal 2018 LNO-CC
endif
else
lnoepso='0.d0 ' ! initialize for the remaining cases
endif ! localcc.eq....
endif ! lcorthr.eq.'0 '
endif ! trim(ccprog).eq.'cis'
endif ! lnoepso.eq.' '
c
if (olnofact.ne.1.d0) then
read(lnoepso,*) rr
write(lnoepso,'(e16.8)') rr/olnofact
lnoepso=adjustl(lnoepso)
endif
C maxact %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('maxact',6,maxact,4)
if(maxact.ne.'on '.and.maxact.ne.'off '.and.maxact.ne.' ')
$call unknown('maxact',6)
if(maxact.eq.' ') maxact='off '
C maxex %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('maxex',5,maxex,4)
if(maxex.eq.' ') maxex='0 '
read(maxex,*) i
if(i.lt.0) call unknown('maxex',5)
C mcscfiguess %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('mcscfiguess',11,mcscfiguess,7)
if(mcscfiguess.ne.'core '.and.mcscfiguess.ne.'ao '.and.
$ mcscfiguess.ne.'restart'.and.mcscfiguess.ne.' '.and.
$ mcscfiguess.ne.'sad '.and.mcscfiguess.ne.'mo '.and.
$ mcscfiguess.ne.'hf ')
$call unknown('mcscfiguess',119)
if(mcscfiguess.eq.' ') mcscfiguess='hf '
C bfbasis %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('bfbasis',7,bfbasis,20)
if(bfbasis.eq.' ')
$bfbasis='none '
C mem %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('mem',3,mem,16)
if(mem.eq.' ') mem='256MB '
!NP
C usedisk %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('usedisk',7,usedisk,4)
if(usedisk.eq.' ') usedisk='2 '
read(usedisk,*) i
if(i.lt.-1.or.i.gt.2) call unknown('usedisk',7)
C lccoporder %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('lccoporder',10,lccoporder,8)
if(lccoporder.ne.'trffirst'.and.lccoporder.ne.'lccfirst'.and.
$ lccoporder.ne.' ') call unknown('lccoporder',10)
c
if(lccoporder.eq.' ') then
lccoporder='trffirst' ! default for localcc<2019
if((localccn.ge.2018.or.usedisk.eq.'0 ').and.ccprog.eq.'ccsd')
$ lccoporder='lccfirst'
endif
if(lccoporder.eq.'lccfirst'.and.localccn.lt.2018.and.
$ localccn.ne.0) then
write(iout,*)
$'Incompatible options for keywords lccoporder and localcc! ',
$'lccoporder=lccfirst is implemented only with localcc>=2018.'
call mrccend(1)
endif
if(lccoporder.eq.'lccfirst'.and.
$ (ccprog.ne.'ccsd'.and.locanycc.or.
$ ccprog.eq.'ccsd'.and..not.locanycc)) then
write(iout,*)
$ 'Incompatible options for lccoporder, localcc and ccprog! ',
$'lccoporder=lccfirst is compatible with ccprog=ccsd,localcc!=off'
call mrccend(1)
endif
C lccrest %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('lccrest',7,lccrest,8)
if(lccrest.ne.' '.and.lccrest.ne.'on '.and.
$ lccrest.ne.'off '.and.lccrest.ne.'domain '.and.
$ lccrest.ne.'restart ') call unknown('lccrest',7)
if (lccrest.eq.' ') lccrest='off '
if (lccrest.ne.'off '.and.localcc.eq.'2013') then
write(iout,*) 'Only 2015-19 version of localcc',
$ 'can be restarted'
call mrccend(1)
endif
if (lccrest.ne.'off '.and.ccprog.eq.'mrcc'.and.lanycc(calc))
$ then
write(iout,*) 'Only localcc with ccprog=ccsd can be restarted'
call mrccend(1)
endif
if (lccrest.eq.'restart '.and.localccn.lt.2018.and.
$ localccn.ne.0) then
write(iout,*)
$ 'localcc=restart is only compatible with localcc>=2018'
call mrccend(1)
endif
if ((lccrest.eq.'domain '.or.lccrest.eq.'on ').and.
$ lccoporder.ne.'trffirst') then
write(iout,*)
$ 'localcc=domain/on are only compatible with lccoporder=trffirst'
call mrccend(1)
endif
if (lccrest.eq.'restart '.and.lccoporder.ne.'lccfirst') then
write(iout,*) 'localcc=restart is only compatible with ',
$ 'localcc>=2018 and lccoporder=lccfirst'
call mrccend(1)
endif
c
if (lccrest.eq.'restart ') then
inquire(file='localcc.restart',exist=l1)
inquire(file='FOCK',exist=ll2)
inquire(file='VARS',exist=ll3)
inquire(file='MOCOEF.LOC',exist=ll1)
if (.not.(l1.and.ll1.and.ll2.and.ll3)) then
write(iout,*)'localcc.restart, MOCOEF.LOC, VARS, FOCK files ',
$ 'are required for lccrest=restart'
call mrccend(1)
endif
endif
C locintrf %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('locintrf',8,locintrf,8)
if(locintrf.ne.'disk '.and.locintrf.ne.'direct '.and.
$ locintrf.ne.'directai'.and.locintrf.ne.'directab'.and.
$ locintrf.ne.' ') call unknown('locintrf',8)
if (locintrf.eq.' ') then
if (corembed.eq.'off ') then
if (localcc16p.and.locanycc) locintrf='direct '
if (localcc16p.and.localmp2) locintrf='directai'
if (.not.localcc16p) locintrf='disk '
else
if(localcc16p) locintrf='direct '
if(localcc.eq.'2015') locintrf='directab'
endif
endif
if (locanycc.and.corembed.ne.'off '.and.
$ ((localcc16p.and.locintrf.ne.'direct ').or.
$ (localcc.eq.'2015'.and.locintrf.ne.'directab'))) then
write(iout,*)'Only locintrf=direct and localcc>=2016 OR ',
$ 'locintrf=directab and localcc=2015 are implemented for',
$ 'embedded locac CC computations'
call mrccend(1)
endif
if ((locintrf.eq.'disk '.or.locintrf.eq.'directai').and.
$(lccoporder.eq.'lccfirst')) then
write(iout,*)'locintrf=disk/directai is only compatible with ',
$'lccoporder=trffirst, locintrf=direct is recommended'
call mrccend(1)
endif
!NP
C scfiguess %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfiguess',9,scfiguess,7)
if(scfiguess.ne.'core '.and.scfiguess.ne.'ao '.and.
$ scfiguess.ne.'restart'.and.scfiguess.ne.' '.and.
$ scfiguess.ne.'sad '.and.scfiguess.ne.'mo '.and.
$ scfiguess.ne.'min '.and.scfiguess.ne.'small '.and.
$ scfiguess.ne.'gfn1 '.and.scfiguess.ne.'gfn2 '.and.
$ scfiguess.ne.'lowlqm '.and.scfiguess.ne.'off ')
$ call unknown('scfiguess',9)
if(scfiguess.eq.' ') then
scfiguess='sad '
if (lccrest.eq.'domain '.or.lccrest.eq.'restart ')
$ scfiguess='off '
endif
c
if(scfiguess.eq.'lowlqm '.and.embed.eq.'off ')then
write(iout,*)
$'scfiguess=lowlqm is only suitable for restaring embed jobs'
call mrccend(1)
endif
if(scfiguess.eq.'lowlqm ')then
inquire(file='FOCK',exist=ll2)
inquire(file='VARS',exist=ll3)
inquire(file='MOCOEF',exist=ll1)
if (.not.(ll1.and.ll2.and.ll3)) then
write(iout,*)'The MOCOEF, VARS, and FOCK files of total the ',
$"QM systems' low-level SCF are required for scfiguess=lowlqm"
call mrccend(1)
endif
endif
if((pssp.eq.'on '.or.fitting.eq.'overlap '.or.
& dual_df.ne.'off ').and.trim(basis_sm).eq.'none') then
basis_sm=basis
endif
if((scfiguess.eq.'small '.or.dual.ne.'off ').and.
$trim(basis_sm).eq.'none') then
write(iout,*)
$'Please specify the small basis set using keyword basis_sm!'
call mrccend(1)
endif
if(lf12.and.(scfiguess.eq.'min '.or.
$ scfiguess.eq.'small ')) then
write(iout,*)
$'This SCF initial guess is not compatible with F12 calculations!'
call mrccend(1)
endif
C scfguessdens %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfguessdens',12,scfguessdens,8)
if(scfguessdens.ne.'rohfscn '.and.scfguessdens.ne.'uhf '.and.
$ scfguessdens.ne.'rohfstd '.and.scfguessdens.ne.'rhf '.and.
$ scfguessdens.ne.' ')
$ call unknown('scfguessdens',12)
C qro %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('qro',3,qro,3)
if(qro.ne.' '.and.qro.ne.'on '.and.qro.ne.'off')
$ call unknown('qro',3)
if (qro.eq.' ') qro='off'
if (qro.eq.'on '.and.(scftype.ne.'uhf '.and.scftype.ne.'uks '))
$ then
write(iout,"(' Error:')")
write(iout,"(a81)") ' Quasi-restricted orbitals can only be ' //
$'constructed from an unresticted reference.'
write(iout,"(a28)") ' Please use scftype=UHF/UKS!'
call mrccend(1)
endif
if (localcc.ne.'off '.and.qro.ne.'on '.and.
$ (scftype.eq.'uhf '.or.scftype.eq.'uks ')) then
write(iout,"(' Warning:')")
write(iout,"(a63)") ' Local correlation calculations utilizing '//
$ 'unresticted reference'
write(iout,"(a60)") 'are only implemented with quasi-restricted'//
$' orbitals (QROs):'
write(iout,"(' qro=on will be set from here!')")
write(iout,*)
qro='on '
endif !localcc.and.not.qro.and.(uhf.or.uks)
if (qro.eq.'on ') then
if (scfiguess.eq.'off ') then
scftype='rohf '
rohftype='semicanonical'
endif
endif
if (localcc.ne.' off'.and.qro.ne.'off'.and.scfiguess.eq.'off ')
$ then
inquire(file='MOCOEF.QRO',exist=ll1)
if (.not.ll1) then
write(iout,*) 'MOCOEF.QRO file is needed for',
$ ' localcc!=off & qro!=off & scfiguess=off'
call mrccend(1)
endif
endif
C molden %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('molden',6,molden,4)
if(molden.ne.'on '.and.molden.ne.'off '.and.molden.ne.' ')
$call unknown('molden',6)
if(molden.eq.' ') molden='on '
if(scfiguess.eq.'off '.or.scfiguess.eq.'lowlqm ')molden='off '
C nto %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('nto',3,nto,4)
if(nto.ne.'on '.and.nto.ne.'off '.and.nto.ne.' ')
$call unknown('nto',3)
if(nto.eq.' ') nto='off '
if(trim(molden).eq.'off')nto='off '
C guido_ct %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('guido_ct',8,guido_ct,4)
if(guido_ct.ne.'on '.and.guido_ct.ne.'off '.
$and.guido_ct.ne.' ') call unknown('guido_ct',8)
if(guido_ct.eq.' ') guido_ct='off '
C ip_ea %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ip_ea',5,ip_ea,4)
if(ip_ea.ne.'ip '.and.ip_ea.ne.'ea '.and.ip_ea.ne.'off '.and.
$ip_ea.ne.' ') call unknown('ip_ea',5)
if(ip_ea.eq.' ') ip_ea='off '
C theodore %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('theodore',8,theodore,4)
if(theodore.ne.'on '.and.theodore.ne.'off '.and.
$theodore.ne.' ') call unknown('theodore',8)
if(theodore.eq.' ') theodore='off '
C mulmet %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('mulmet',6,mulmet,8)
if(mulmet.ne.'0 '.and.mulmet.ne.'1 '.and.
$ mulmet.ne.'2 '.and.mulmet.ne.'3 '.and.
$ mulmet.ne.' ') call unknown('mulmet',6)
if (mulmet.eq.' ') then
if (localcc16p) then
mulmet='3 '
else ! 2013/2015/off
mulmet='0 '
endif
endif
C nab %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('nab',3,nab,16)
if(nab.eq.' '.and.lfno) nab='on '
if(nab.ne.'on '.and.
$ nab.ne.'off '.and.
$ nab.ne.' ') then
read(nab,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('nab',3)
else if(nab.eq.'on ') then
nab='0.1d0 '
else
nab='off '
endif
C naf_cor %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('naf_cor',7,naf_cor,16)
if(naf_cor.eq.' '.and.lfno)
$ naf_cor='on '
if(naf_cor.ne.'on '.and.
$ naf_cor.ne.'off '.and.
$ naf_cor.ne.' ') then
read(naf_cor,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('naf_cor',7)
endif
ll1=calc.eq.'drpa '.or.
$ calc.eq.'sosex '.or.
$ calc.eq.'rpax2 '.or.
$ calc.eq.'mp2 '
if(naf_cor.eq.' ') then
if(lcorthr.eq.'0 ') then
naf_cor='off '
go to 101
endif
c for local RPA variants of the 2015 scheme
if(localcc.eq.'2015'.and..not.lanycc(calc)) then
if(trim(calc).eq.'drpa'.or. !Not for MP2!!!!!!!!!!!!!!!
$ trim(calc).eq.'sosex'.or.
$ trim(calc).eq.'rpax2'.or.localrpa) then
if(lcorthr.eq.'tight ') then
naf_cor='8e-3 '
elseif(lcorthr.eq.'normal '.or.lcorthr.eq.'loose ') then
naf_cor='1e-2 '
endif
ll1=.true.
elseif (localmp2) then
naf_cor='off '
ll1=.true.
endif
c for local MP2 of the 2016 or 2018 scheme
elseif(localcc16p.and.(localmp2.or.localrpa)) then
if (localmp2.and.localccn.lt.2021) then
if(lcorthr.ne.'0 ') naf_cor='2e-3 '
if (lcorsel.eq.'vtightpp') naf_cor='1e-3 ' ! vtight or tighter
else ! yet to be set for drpa !NP
naf_cor='off '
endif
c for any local CC
elseif (lanycc(calc).and.localcc.ne.'off '.and..not.ll1.and.
$ trim(ccprog).ne.'cis') then
if (localcc.eq.'2015') then ! for naftyp=jpi
if(lcorthr.eq.'tight ') then
naf_cor='5e-5 '
elseif(lcorthr.eq.'normal '.or.lcorthr.eq.'loose ')
$ then
naf_cor='1e-3 '
endif
elseif (localcc16p) then
naf_cor='1e-2 '
if (lcorsel.eq.'vtightpp')
$ naf_cor='1e-3 '
else
naf_cor='off ' ! for localcc=2013
endif
c for reduced cost excited state methods
elseif(trim(ccprog).eq.'cis') then !MD
if(redcost_exc.eq.'4 '.or.redcost_exc.eq.'5 '.or.
$redcost_exc.eq.'off '.or.((trim(calc).eq.'cis'.or.
$trim(calc).eq.'scf').and.redcost_exc.ne.'8 ')) then
naf_cor='0.d0 '
else
read(scspt,*) tmp
read(scspt_t,*) tmp3
tmp=max(tmp,tmp3)
read(scsps,*) tmp2
read(scsps_t,*) tmp3
tmp2=max(tmp2,tmp3)
if(tmp.ne.0.d0.or.tmp2.ne.0.d0) then
naf_cor='0.075d0 '
else
naf_cor='0.1d0 '
endif
endif
elseif(trim(calc).eq.'os-mp3') then
naf_cor='1.d-3'
else
naf_cor='off ' ! initalization if none of the above
endif
c for the rest of the canonical methods
elseif (naf_cor.eq.'on ') then
if (trim(ccprog).eq.'cis'.or.localcc.ne.'off ') then
write(iout,*) 'Please, set the numerical value of naf_cor',
$'if any other than the default setting is desired, or delete',
$'naf_cor=on from the input file to invoke the default settings'
call mrccend(1)
else if(trim(ccprog) .eq. 'ccsd') then
naf_cor='5e-2 '
else
naf_cor='5e-3 '
endif
endif ! naf_cor.eq.' '
101 continue
if(naf_cor.ne.'off '.and.localcc.eq.'off ')
$drpaalg='fit '
C naf_amp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('naf_amp',7,naf_amp,16)
if(naf_amp.ne.'on '.and.
$ naf_amp.ne.'off '.and.
$ naf_amp.ne.' ') then
read(naf_amp,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('naf_amp',7)
endif
if(naf_amp.eq.' ') then
naf_amp='3.16d-3'
elseif (naf_amp.eq.'on ') then
naf_amp='3.16d-3'
endif ! naf_amp.eq.' '
C naf_f12 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('naf_f12',7,naf_f12,16)
if(naf_f12.eq.' '.and.lfno)
$ naf_f12='on '
if(naf_f12.ne.'on '.and.
$ naf_f12.ne.'off '.and.
$ naf_f12.ne.' ') then
read(naf_f12,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('naf_f12',7)
else if(naf_f12.eq.'on ') then
naf_f12='5e-2 '
else
naf_f12='off '
endif
C redcost_tddft %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
rr=1.d0
call getkeym('redcost_tddft',13,redcost_tddft,16)
if(redcost_tddft.eq.' '.and..not.localcc16p)
$redcost_tddft='off '
if(redcost_tddft.eq.'off ') rr=0.d0
if(trim(redcost_tddft).eq.'on'.or.(redcost_tddft.eq.
$' '.and.localcc16p))
$redcost_tddft='0.985d0 '
if(rr.ne.0.d0) read(redcost_tddft,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('redcost_tddft',13)
C cialg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('cialg',5,cialg,8)
if(cialg.ne.'disk '.and.cialg.ne.'direct '.and.
$cialg.ne.'direct2 '.and.cialg.ne.'direct3 '
$.and.cialg.ne.'auto '
$.and.cialg.ne.' ') call unknown('cialg',5)
if(cialg.eq.' ') then
if(rr.eq.0.d0) then
if((ccprog.eq.'mrcc'.and.localcc.eq.'off ').or.
$(ccprog.eq.'cis '.and.redcost_exc.eq.'off '.and.
$trim(calc).ne.'cis')) then
cialg='disk '
else
cialg='auto '
endif
else
cialg='direct '
endif
endif
if(rr.gt.0.d0.and.(cialg.ne.'direct '))
$ then
write(iout,*) 'Local density fitting is only implemented for
$cialg=direct!'
call mrccend(1)
endif
cC warning messages in the case of excited state calculations
if(trim(ccprog).eq.'cis') then
if(trim(calc).eq.'scf'.and.(trim(cialg).eq.'direct2'.or.
$trim(cialg).eq.'direct3')) then
write(iout,*) 'The full TDDFT or THDF calculation
$is available only with cialg=disk or direct options!'
call mrccend(1)
endif
read(lnoepsv,*) tmp
read(lnoepso,*) tmp2
if(naf_cor.eq.'off ') then
tmp3=0.d0
else
read(naf_cor,*) tmp3
endif
cC
if(localcc.ne.'off '.and.(redcost_exc.eq.'off '
$.or.redcost_exc.eq.'3 '.or.redcost_exc.eq.'8 ')) then
write(iout,*) 'Inconsistent options for localcc '//
$'and redcost_exc!'
write(iout,*) 'The natural orbital approximation IS '//
$'required for local excited state calculations!'
write(iout,*) 'The available options for '//
$'redcost_exc are "on, 1, cust, 2, 4, 5, 6, 7, 9, or 10"!'
call mrccend(1)
endif
C
if((trim(calc).eq.'cis'.or.trim(calc).eq.'scf')
$.and.(redcost_exc.ne.'off '
$.and.redcost_exc.ne.'8 ')) then
write(iout,*) 'Inconsistent options for calc and redcost_exc!'
write(iout,*) 'If calc=cis or scf the available options for '//
$'redcost_exc are "off" or "8"!'
call mrccend(1)
endif
C
if((trim(calc).eq.'cis'.or.trim(calc).eq.'scf')
$.and.(tmp.ne.0.d0.or.tmp2.ne.0.d0)) then
write(iout,*) 'Inconsistent options for calc and '//
$'lnoepsv or lnoepso!'
write(iout,*) 'Natural orbital approximation is available ' //
$'only for second order methods!'
call mrccend(1)
endif
C
if((cialg.eq.'direct '.or.cialg.eq.'direct2 '
$.or.cialg.eq.'direct3 ').and.(redcost_exc.eq.'1 '.or.
$ redcost_exc.eq.'cust'.or.redcost_exc.eq.'7 '.or.
$ redcost_exc.eq.'8 '.or.redcost_exc.eq.'9 '.or.
$ redcost_exc.eq.'10 '.or.
$ redcost_exc.eq.'3 '.or.redcost_exc.eq.'4 '.or.
$ redcost_exc.eq.'5 ').and.(trim(calc).ne.'cis'.and.
$ trim(calc).ne.'scf')) then
write(iout,*) 'Inconsistent options for cialg and redcost_exc!'
write(iout,*) 'If cialg.eq.direct, the available options for '//
$'redcost_exc are "off, 2, or 6"!'
call mrccend(1)
endif
C
if((trim(calc).eq.'cis'.or.trim(calc).eq.'scf')
$.and.(cialg.eq.'direct '.or.cialg.eq.'direct2 '
$.or.cialg.eq.'direct3 ').and.redcost_exc.ne.'off ') then
write(iout,*) 'Inconsistent options for cialg and redcost_exc!'
write(iout,*) 'Approximations are not available for '//
$'CIS or TDDFT calculations if cialg=direct!'
call mrccend(1)
endif
C
C
if(tmp3.ne.0.d0.and.(redcost_exc.eq.'4 '.or.
$redcost_exc.eq.'5 '.or.redcost_exc.eq.'off ')) then
write(iout,*) 'Inconsistent options for naf_cor '//
$'and redcost_exc!'
write(iout,*) 'If redcost_exc is 4, 5 or "off" then '//
$'naf_cor must be 0.d0!'
call mrccend(1)
endif
C
if(tmp3.eq.0.d0.and.(redcost_exc.ne.'4 '.and.
$redcost_exc.ne.'5 '.and.redcost_exc.ne.'off ')) then
write(iout,*) 'Inconsistent options for naf_cor '//
$'and redcost_exc!'
write(iout,*) 'If redcost_exc is not 4, 5 or "off" then '//
$'naf_cor must be greater than 0.d0!'
call mrccend(1)
endif
C
if((tmp.ne.0.d0.or.tmp2.ne.0.d0).and.(redcost_exc.eq.'3 '
$.or.redcost_exc.eq.'8 '.or.redcost_exc.eq.'off ')) then
write(iout,*) 'Inconsistent options for lnoepso or lnoepsv '//
$'and redcost_exc!'
write(iout,*) 'If redcost_exc is 3, 8 or "off" then '//
$'lnoepso AND lnoepsv must be 0.d0!'
call mrccend(1)
endif
C
if((tmp.eq.0.d0.and.tmp2.eq.0.d0).and.(redcost_exc.ne.'3 '
$.and.redcost_exc.ne.'8 '.and.redcost_exc.ne.'off ')) then
write(iout,*) 'Inconsistent options for lnoepso or lnoepsv '//
$'and redcost_exc!'
write(iout,*) 'If redcost_exc is not 3, 8 or "off" then '//
$'lnoepso AND lnoepsv must be greater than 0.d0!'
call mrccend(1)
endif
C
if(nafdens.eq.'on '.and.localcc.eq.'off ') then
write(iout,*) 'Inconsistent options for nafdens and localcc!'
call mrccend(1)
endif
C
endif
if(redcost_exc.ne.'off '.and.trim(ccprog).ne.'cis') then
write(iout,*) 'Reduced cost excited state calculations '//
$'can be performed only with ccprog.eq.cis option!'
call mrccend(1)
endif
C
if(cvs.ne.'off'.and.ip_ea.ne.'off ') then
write(iout,*) 'CVS approximation is not available for '//
$'IP calculations!'
call mrccend(1)
endif
C naf_scf %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('naf_scf',7,naf_scf,16)
if(naf_scf.ne.'on '.and.
$ naf_scf.ne.'off '.and.
$ naf_scf.ne.' ') then
read(naf_scf,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('naf_scf',7)
endif
if(naf_scf.eq.' ') naf_scf='off '
if(naf_scf.eq.'on ') naf_scf='5e-3 '
C nafalg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('nafalg',6,nafalg,8)
if(nafalg.ne.'alpha '.and.
$ nafalg.ne.'albe '.and.
$ nafalg.ne.' ') call unknown('nafalg',6)
if(nafalg.eq.' ') nafalg='albe '
!NP
C naftyp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('naftyp',6,naftyp,8)
if(naftyp.ne.'jai '.and.
c $ naftyp.ne.'jmi '.and.
$ naftyp.ne.'jpi '.and.
$ naftyp.ne.'jpq '.and.
$ naftyp.ne.'jpipilot'.and.
$ naftyp.ne.'jpqpilot'.and.
$ naftyp.ne.'jpq_inv '.and.
$ naftyp.ne.' ') call unknown('naftyp',6)
if (naftyp.ne.' '.and.naf_cor.eq.'off ') then
write(iout,*) 'Inconsistent options for naf_cor and naftyp'
call mrccend(1)
endif
if (naf_cor.eq.'off ') then
naftyp=' '
else
if(naftyp.eq.' '.and.
$ (trim(calc).eq.'ccsd'.or.trim(calc).eq.'ccsd(t)'.or.
$ lanycc(calc))) then ! default for local CC
if (localcc.eq.'2015') naftyp='jpi '
if (localcc16p) naftyp='jpq '
endif
if(naftyp.eq.' '.and.naf_cor.ne.'off '.and.(
$ trim(calc).eq.'mp2'.or.
$ trim(calc).eq.'drpa'.or.
$ trim(calc).eq.'sosex'.or.
$ trim(calc).eq.'rpax2'.or.
$ localmp2.or.localrpa
$ )) naftyp='jai ' ! default for MP2, dRPA, SOSEX...
if(naftyp.eq.' '.and.redcost_exc.ne.'off ')
$naftyp ='jpq '
if(naftyp.ne.'jai '.and.naf_cor.ne.'off '.and.(
$ trim(calc).eq.'mp2'.or.
$ trim(calc).eq.'drpa'.or.
$ trim(calc).eq.'sosex'.or.
$ trim(calc).eq.'rpax2'.or.
$ localmp2.or.localrpa)
$ ) then
write(iout,*) 'Only naftyp=jai is implemented for calc=' //
$ adjustl(calc)
call mrccend(1)
endif
if(naftyp.eq.'jpqpilot'.and.corembed.ne.'off ') then
write(iout,*) 'Naftyp=jpqpilot is implemented only for',
$ ' corembed.ne.off'
call mrccend(1)
endif
if ((naftyp.eq.'jpqpilot'.or.naftyp.eq.'jpipilot').and.
$ .not.(locintrf.eq.'directai'.or.locintrf.eq.'disk ')) then
write(iout,*)'Naftyp=jpqpilot or jpipilot is only available',
$ ' with locintrf= directai OR disk'
call mrccend(1)
endif
if (naftyp.eq.'jpq '.and.lanycc(calc).and.
$ (localcc.eq.'2015').and.
$ (locintrf.eq.'directab'.or.locintrf.eq.'direct ')) then
write(iout,*) 'naftyp=jpq is not implemented for',
$ ' locintrf=direct or directab and localcc=2015,
$ naftyp=jpi is available'
call mrccend(1)
endif
if(naftyp.eq.' '.and.lf12) then
naftyp='jpq_inv '
end if
endif
!NP
C nchol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('nchol',5,nchol,4)
if(nchol.eq.' ') then
c if(localcc.ne.'off ') then
c nchol=cctol
c read(nchol,*) i
c i=max(1,i)
c i=i-2
c write(nchol,'(i4)') i
c nchol=adjustl(nchol)
c else
nchol='auto'
c endif
else if(nchol.ne.'auto') then
read(nchol,*) i
if(i.le.0) call unknown('nchol',5)
endif
C ndeps %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ndeps',5,ndeps,16)
if(ndeps.ne.' ') then
read(ndeps,*) rr
if(rr.le.0.d0) call unknown('ndeps',5)
endif
if(ndeps.eq.' ') ndeps='1e-3'
C occ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('occ',3,occ,256)
! Default is set by scf
C occri %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('occri',5,occri,8)
if(occri.ne.' '.and.occri.ne.'on '.and.
& occri.ne.'off ') call unknown('occri',5)
if(occri.eq.' '.and.fitting.eq.'overlap ') occri='on '
if(occri.eq.' ') occri='off '
C oniom %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('oniom',5,oniom,8)
externalsqm=.false.
if(oniom.ne.' ') then
call separate_string(oniom,8,'-',cscr8,8,oniom_type,8)
cscr8=trim(adjustl(cscr8))
oniom_type=trim(adjustl(oniom_type))
read(cscr8,'(i8)',iostat=ierror) i
if(ierror.ne.0.or.i.lt.0) then
write(iout,*) 'The number of ONIOM layers is not valid. It
$should be a positive integer.'
call unknown('oniom',5)
endif
if(i.eq.1) then
write(iout,*) 'Warning! The number of ONIOM layers is one.'
write(iout,*) 'This option is only useful for debugging.'
endif
if(oniom_type.ne.' '.and.
$ oniom_type.ne.'me '.and.
$ oniom_type.ne.'ee ') then
write(iout,'(a)') ' Unknown type of ONIOM calculation.'
call unknown('oniom',5)
endif
if(oniom_type.eq.' ') oniom_type='me '
call check_oniom_externalsqm(minpfile,externalsqm)
else
oniom='off'
endif
C oniom_eechg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('oniom_eechg',11,oniom_eechg,8)
if(oniom_eechg.ne.' '.and.
$ oniom_eechg.ne.'mulli '.and.
$ oniom_eechg.ne.'lowdin '.and.
$ oniom_eechg.ne.'iao '.and.
$ oniom_eechg.ne.'chelpg '.and.
$ oniom_eechg.ne.'mk '.and.
$ oniom_eechg.ne.'amber '.and.
$ oniom_eechg.ne.'user '.and.
$ oniom_eechg.ne.'external'.and.
$ oniom_eechg.ne.'off ') call unknown('oniom_eechg',11)
if(oniom_eechg.eq.' ') then
if(oniom.eq.'off'.or.oniom_type.eq.'me ') then
oniom_eechg='off '
else if(oniom_type.eq.'ee ') then
oniom_eechg='lowdin '
if(externalsqm) oniom_eechg='external'
endif
endif
C oniom_qcorr %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('oniom_qcorr',11,oniom_qcorr,8)
if(oniom_qcorr.ne.' '.and.
$ oniom_qcorr.ne.'0 '.and. ! zero upper-layer atoms only
$ oniom_qcorr.ne.'1 '.and. ! 0 + lower layer host atoms
$ oniom_qcorr.ne.'special '.and. ! 1 + selected atoms (note: nlay-1 lines are required in this case)
$ oniom_qcorr.ne.'off '.and.
$ oniom_qcorr.ne.'on ') call unknown('oniom_qcorr',11)
if(oniom_qcorr.eq.' ') then
if(oniom.eq.'off'.or.oniom_type.eq.'me ') then
oniom_qcorr='off '
else if(oniom_type.eq.'ee ') then
oniom_qcorr='1 '
endif
else if(oniom_qcorr.eq.'on ') then
oniom_qcorr='1 '
endif
C oniom_pcm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('oniom_pcm',9,oniom_pcm,8)
if(oniom_pcm.ne.'c '.and.
$ oniom_pcm.ne.'x '.and.
$ oniom_pcm.ne.'off '.and.
$ oniom_pcm.ne.' ') call unknown('oniom_pcm',9)
if(oniom.eq.'off') then
oniom_pcm='off '
endif
if(oniom_pcm.eq.'x '.and.oniom_type.eq.'ee ') then
write(iout,'(a)') ' oniom_pcm=x'
write(iout,'(a)') ' This ONIOM-PCM scheme is not supported with
$electronic embedding.'
call mrccend(1)
endif
C comprest %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('comprest',8,comprest,4)
if(comprest.eq.' ') comprest='off '
if(comprest.ne.'off '.and.comprest.ne.'auto') then
read(comprest,'(i8)',iostat=ierror) i
if(ierror.ne.0.or.i.lt.0) then
write(iout,'(a)')
$'Illegal specification for comprest. It '//
$'should be a non-negative integer.'
call unknown('comprest',8)
endif
endif
C optmaxit %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('optmaxit',8,optmaxit,8)
if(optmaxit.eq.' ') optmaxit='50 '
C orbloco %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('orbloco',7,orbloco,16)
if(orbloco.ne.'off '.and.
$ orbloco.ne.'cholesky '.and.
$ orbloco.ne.'pm '.and.
$ orbloco.ne.'boys '.and.
$ orbloco.ne.'ibo '.and.
$ orbloco.ne.'fragment '.and.
$ orbloco.ne.'no '.and.
$ orbloco.ne.'spade '.and.
$ orbloco5.ne.'gboys' .and.
$ orbloco.ne.' ') call unknown('orbloco',7)
if(orbloco.eq.' ') then
if(localcc.ne.'off '.or.(qmreg.ne.' '.and.
$ qmreg.ne.'0 ').or.
$redcost_tddft.ne.'off ') then
orbloco='boys '
else
orbloco='off '
endif
endif
if(orbloco5.eq.'gboys') boysalg='newton '
C orbloce %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
! HB! gboys????
call getkeym('orbloce',7,orbloce,16)
if(orbloce.ne.'off '.and.
$ orbloce.ne.'cholesky '.and.
$ orbloce.ne.'pm '.and.
$ orbloce.ne.'boys '.and.
$ orbloce.ne.'ibo '.and.
$ orbloce.ne.'fragment '.and.
$ orbloce.ne.'no '.and.
$ orbloce.ne.'spade '.and.
$ orbloce.ne.'special '.and.
$ orbloce.ne.' ') call unknown('orbloce',7)
if(orbloce.eq.' ') then
if (embed.ne.'off '.and.oniom.eq.'off ') then
orbloce='spade '
else if(oniom.ne.'off '.and.embed.eq.'off ') then
orbloce='pm '
else if(oniom.ne.'off '.and.embed.ne.'off ') then
orbloce='pm '
else
orbloce='off '
endif
endif
C orblocc %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('orblocc',7,orblocc,16)
if(orblocc.ne.'off '.and.
$ orblocc.ne.'cholesky '.and.
$ orblocc.ne.'pm '.and.
$ orblocc.ne.'boys '.and.
$ orblocc.ne.'ibo '.and.
$ orblocc.ne.'fragment '.and.
$ orblocc.ne.'no '.and.
$ orblocc.ne.'spade '.and.
$ orblocc5.ne.'gboys' .and.
$ orblocc.ne.' ') call unknown('orblocc',7)
if(orblocc.eq.' ') then
if((localcc.ne.'off '.and.core.eq.'corr').or.localcc.eq.'2013')
$ then
orblocc=orbloco
else
orblocc='off '
endif
endif
if(orblocc5.eq.'gboys') boysalg='newton '
C orblocv %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('orblocv',7,orblocv,16)
if(orblocv.ne.'off '.and.
$ orblocv.ne.'cholesky '.and.
$ orblocv.ne.'pm '.and. !HB
$ orblocv.ne.'boys '.and.
$ orblocv.ne.'fragment '.and.
$ orblocv.ne.'no '.and.
$ orblocv.ne.'spade '.and.
$ orblocv.ne.'pao '.and.
$ orblocv.ne.'pao-subsys '.and.
$ orblocv5.ne.'gboys' .and.
$ orblocv.ne.' ') call unknown('orblocv',7)
if(orblocv.eq.' ') then
if(localcc.ne.'off ') then
orblocv='pao '
else
orblocv='off '
endif
endif
if(orblocv5.eq.'gboys') boysalg='newton '
C orblocguess %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('orblocguess',11,orblocguess,8)
if(orblocguess.ne.'cholesky'.and.
$ orblocguess.ne.'restart '.and.
$ orblocguess.ne.'read '.and.
$ orblocguess.ne.' ') call unknown('orblocguess',11)
if (orblocguess.eq.' ') then
orblocguess='cholesky'
if (lccrest.eq.'restart '.or.lccrest.eq.'domain ')
$ orblocguess='read '
endif
c
if (orblocguess.eq.'restart '.or.orblocguess.eq.'read ') then
inquire(file='MOCOEF.LOC',exist=ll1)
if (.not.ll1) then
write(iout,*)'MOCOEF.LOC file is required for orblocguess'
call mrccend(1)
endif
endif
C osveps %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('osveps',6,osveps,16)
if(osveps.ne.' '.and.
$ osveps.ne.'off ') then
read(osveps,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('osveps',6)
endif
if(osveps.eq.' ') then
if (localcc16p) then
osveps='-1.d0' !NP OSVs are not constructed
else
if(lcorthr.eq.'0 ') then
osveps='0.d0'
else if(lcorthr.eq.'tight ') then
osveps='1e-4'
else
osveps='1e-3'
endif
endif
endif
if(osveps.eq.'off ') osveps='-1.d0' !NP OSVs are not constructed
C dfintran %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dfintran',8,dfintran,8)
if(dfintran.ne.' '.and.dfintran.ne.'ovirt '.and.
$dfintran.ne.'drpa ') call unknown('dfintran',8)
if(dfintran.eq.' ') dfintran='drpa '
if(dfbasis_cor.eq.'none ') dfintran='ovirt '
if(dfbasis_cor.ne.'none ') then
if(dfintran.eq.'ovirt') then
if(ovirt.ne.'off ') then
write(iout,*)
$ 'Warning: dfintran=ovirt and dfbasis_cor!=none can only be
$used with ovirt=off!'
call mrccend(1)
end if
elseif(dfintran.eq.'drpa ') then
if(ovirt.eq.'ovos') then
write(iout,*)
$ 'Warning: ovirt=ovos can only be used with dfintran=ovirt!'
call mrccend(1)
end if
end if
end if
if(dfintran.ne.'drpa '.and.corembed.ne.'off ') then
write(iout,*)
$'Only dfintran=drpa can be chosen if corembed.ne.off'
call mrccend(1)
endif
if(trim(dfbasis_cor).eq.'none'.and.ovirt.eq.'ppl ') ovirt='mp2 '
c if(dfintran.eq.'drpa '.and.ovirt.eq.'mp2 '.and.
c $ (ccprog.eq.'mrcc'.and.trim(calc).ne.'mp2'.and.
c $ trim(calc).ne.'drpa'.and.trim(calc).ne.'rpa'
c $ .and.trim(calc).ne.'sosex'.and.trim(calc).ne.'rpax2')) then
c ! incompatible because the number of alpha and beta orbitals must be the same for mrcc
c write(iout,*)
c $'Incompatible options for keywords dfintran, ovirt and ccprog!'
c call mrccend(1)
c endif
C ccsdalg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ccsdalg',7,ccsdalg,8)
if(ccsdalg.ne.' '.and.
$ ccsdalg.ne.'dfdirect'.and.
$ ccsdalg.ne.'disk ') call unknown('ccsdalg',7)
if(ccsdalg.eq.' ') then
if (ccprog.ne.'ccsd'.or.
$ dfbasis_cor.eq.'none '.or.
$ localcc.eq.'2013'.or.
$ dfintran.eq.'ovirt '.or.
$ naftyp.eq.'jpqpilot') then
ccsdalg='disk '
else
ccsdalg='dfdirect'
endif
endif
if(lf12.and.ccprog.ne.'mrcc') ccsdalg='dfdirect'
if(ccsdalg.eq.'dfdirect'.and.localcc.eq.'2013') then
write(iout,*)
$'Incompatible options for keywords ccsdalg and localcc! ',
$'Please set ccsdalg=disk if localcc=2013 is desired.'
call mrccend(1)
endif
if(ccsdalg.eq.'dfdirect'.and.dfintran.eq.'ovirt ') then
write(iout,*)
$'Incompatible options for keywords ccsdalg and dfintran! ',
$'dfintran=ovirt is compatible with ccsdalg=disk.'
call mrccend(1)
endif
if(ccsdalg.eq.'dfdirect'.and.naftyp.eq.'jpqpilot') then
write(iout,*)
$'Incompatible options for keywords ccsdalg and naftyp! ',
$'naftyp=jpqpilot is compatible with ccsdalg=disk.'
call mrccend(1)
endif
if(ccsdalg.eq.'dfdirect'.and.ccprog.ne.'ccsd') then
write(iout,*)
$'Incompatible options for keywords ccsdalg and ccprog! ',
$'ccprog=ccsd is compatible with ccsdalg=dfdirect.'
call mrccend(1)
endif
if(ccsdalg.ne.'dfdirect'.and.usedisk.eq.'0 ') then
write(iout,*)
$'Incompatible options for keywords ccsdalg and usedisk! ',
$'ccsdalg=dfdirect is compatible with usedisk=0.'
call mrccend(1)
endif
C ovosnorb %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ovosnorb',8,ovosnorb,6)
if(ovosnorb.eq.' ') ovosnorb='80.0 '
read(ovosnorb,*) rr
if(rr.lt.0.d0.or.rr.gt.100.d0) call unknown('ovosnorb',8)
C fnonorb %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('fnonorb',7,fnonorb,6)
C ovltol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ovltol',6,ovltol,16)
if(ovltol.ne.' ') then
read(ovltol,*) rr
if(rr.lt.0.d0) call unknown('ovltol',7)
endif
if(ovltol.eq.' ') ovltol='1e-7 '
C pao_subsys_tol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('pao_subsys_tol',14,pao_subsys_tol,16)
if(pao_subsys_tol.ne.' ') then
read(pao_subsys_tol,*) rr
if(rr.lt.0.d0) call unknown('pao_subsys_tol',14)
endif
if(pao_subsys_tol.eq.' ')
$ pao_subsys_tol='1e-3 '
C pcm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
! known bug-1: the solvent name is 16-character long, thus some of the solvents, e.g. Dimethylsulfoxide, cannot be used simply.
! known bug-2: the compact name of solvents are not identified by the api
call getkeym('pcm',3,pcm,32)
if(trim(pcm).eq.'') pcm='off '
if(.not.externalsqm) then
#if !defined (PCM)
if(trim(pcm).ne.'off') then
write(iout,*) 'PCMSolver library is not installed!'
write(iout,*) 'PCM calculations are not possible!'
call mrccend(1)
endif
#endif
else if(externalsqm.and.oniom_pcm.eq.'x ') then
write(iout,*)
$' oniom_pcm=x is not supported with an external program.'
call mrccend(1)
endif
!HB
if(trim(adjustl(pcm)) .ne.'off'.and.
$ trim(adjustl(oniom)).ne.'off') then
if( trim(adjustl(oniom_pcm)).eq.' ') then
if(oniom_type.eq.'me ') oniom_pcm='x '
if(oniom_type.eq.'ee ') oniom_pcm='c '
if(externalsqm) oniom_pcm='c '
else if(trim(adjustl(pcm)) .eq.'off'.and.
$ trim(adjustl(oniom)).ne.'off') then
oniom_pcm='off '
endif
endif
!HB
C ptfreq %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ptfreq',6,ptfreq,16)
if(ptfreq.eq.' ') ptfreq='0.0 '
C popul %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('popul',5,popul,8)
if(popul.ne.'off '.and.popul.ne.'mulli '.and.
$ popul.ne.'iao '.and.popul.ne.'deco '.and.
$popul.ne.' ') call unknown('popul',5)
if(popul.eq.' ') then
if(dens.ne.'0 ') then
popul='mulli '
else
popul='off '
endif
else
if(dens.eq.'0 ') then
dens='1 '
if(popul.eq.'deco '.and.trim(calc).ne.'scf') dens='2 '
if(lanycc(calc)) ccprog='mrcc'
endif
endif
C pressure %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('pressure',8,pressure,16)
if(pressure.ne.' ') then
read(pressure,*) i
if(i.lt.0) call unknown('pressure',8)
endif
if(pressure.eq.' ') pressure='100000 '
C qscf %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('qscf',4,qscf,8)
if(qscf.ne.' '.and.qscf.ne.'off '.and.
$ qscf.ne.'newton '.and.qscf.ne.'aughess '.and.
$ qscf.ne.'aughessg'.and.qscf.ne.'newtonl '.and.
& qscf.ne.'aughessl'.and.qscf.ne.'aughessm'.and.
& qscf.ne.'bfgs '.and.qscf.ne.'on ')
$call unknown('qscf',4)
if(qscf.eq.' ') then
if(trim(scftype).eq.'mcscf') then
qscf='aughessg'
else
qscf='off '
endif
endif
if(qscf.eq.'on ') qscf='aughessg'
C refdet %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('refdet',6,refdet,8)
if(refdet.ne.' '.and.refdet.ne.'none '.and.
$ refdet.ne.'serialno'.and.refdet.ne.'vector ')
$call unknown('refdet',6)
if(refdet.eq.' ') refdet='none '
C rest %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('rest',4,rest,4)
if(rest.eq.' ') rest='0 '
read(rest,*) i
if(i.lt.0.or.i.gt.4) call unknown('rest',4)
C rgrid %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('rgrid',5,rgrid,6)
if(rgrid.ne.'gc '.and.rgrid.ne.'em '.and.
$ rgrid.ne.'log3 '.and.rgrid.ne.'gcta '.and.rgrid.ne.' ')
$call unknown('rgrid',6)
if(rgrid.eq.' ') then
c if(grt.eq.'ta') then
c rgrid='gcta '
c else
rgrid='log3 '
c endif
endif
C rohfcore %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('rohfcore',8,rohfcore,13)
if(rohfcore.ne.'standard '.and.
$ rohfcore.ne.'semicanonical'.and.
$ rohfcore.ne.' ') call unknown('rohfcore',8)
if(rohfcore.eq.' ') then
if(localcc.eq.'off ') then
rohfcore='semicanonical'
else
rohfcore='standard '
endif
endif
C rohftype %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('rohftype',8,rohftype,13)
if(rohftype.ne.'standard '.and.
$ rohftype.ne.'semicanonical'.and.
$ rohftype.ne.' ') call unknown('rohftype',8)
xcalc=calc
do i=2,31
ii=ichar(xcalc1(i))
if(ii.ge.49.and.ii.le.57.and.(xcalc1(i-1).eq.'['.or.
$xcalc1(i-1).eq.'('.or.xcalc1(i+1).eq.']'.or.xcalc1(i+1).eq.')'.or.
$xcalc1(i-1).eq.'c'.or.xcalc1(i-1).eq.'n')) xcalc1(i)='n'
enddo
if(rohftype.eq.' ') then
if(calc.eq.'scf '.or.
$ (( calc.eq.'ccs '.or.
$ calc.eq.'ccsd '.or.
$ calc.eq.'ccsdt '.or.
$ calc.eq.'ccsdtq '.or.
$ calc.eq.'ccsdtqp '.or.
$ xcalc.eq.'cc(n) '.or.
$ xcalc.eq.'cc(nn) '.or.
$ calc.eq.'cis '.or.
$ calc.eq.'cisd '.or.
$ calc.eq.'cisdt '.or.
$ calc.eq.'cisdtq '.or.
$ calc.eq.'cisdtqp '.or.
$ calc.eq.'fci '.or.
$ xcalc.eq.'ci(n) '.or.
$ xcalc.eq.'ci(nn) ')
$ .and.trim(dfbasis_cor).eq.'none') ! DF intergral trf in drpa cannot handle rohftype=standard
$ ) then
rohftype='standard '
else
rohftype='semicanonical'
endif
if(trim(ccprog).eq.'ccsd'.or.localcc.ne.'off'.or.
$(trim(calc).ne.'scf'.and.
$(trim(pcm).ne.'off'.or.trim(dft).ne.'off')))
$ rohftype='semicanonical'
endif
C talg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('talg',4,talg,4)
if(talg.ne.'virt'.and.talg.ne.'occ '.and.talg.ne.'lapl'.and.
$talg.ne.'topr'.and.talg.ne.'to '.and.talg.ne.'lato'.and.
$talg.ne.' ')
$call unknown('talg',4)
if(talg.eq.' '.or.talg.eq.'occ ') then
talg='occ '
if(localcc.ne.'off ') talg='virt'
c if(localcc16p.and.lcorthr.ne.'0 '.and.
c $ ccprog.eq.'ccsd'.and.trim(calc).eq.'ccsd(t)') talg='lapl'
if(localcc16p.and.lcorthr.ne.'0 ') talg='lapl' ! pert.f does not care about talg so this is safe
if(localccn.ge.2021.and.trim(scftype).eq.'rohf'.and.
$ trim(lcorthr).eq.'0') talg='lapl' !CIM algorithm is not used if oslcc (if lcorthr=0 laptol is set to 6 at laptol keyword)
endif
if(talg.eq.'lapl'.and.dfbasis_cor .eq. 'none ')
$then
write(iout,*)
$'talg=lapl is only compatible with .not.(dfbasis_cor.eq.none)'
call mrccend(1)
endif
C mpitasks %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('mpitasks', 8, mpitasks, 4)
if(mpitasks .eq. ' ') mpitasks = '1 '
if(mpitasks .ne. '1 ') then
if (calc(1:2).ne.'cc' .and. calc(1:2).ne.'ci' .and.
$ calc(1:3).ne.'scf' .or. ccprog.eq.'cis ') then
write(iout, *) 'Warning: only programs scf, mrcc, and ' //
$'ccsd can be run with more MPI tasks!'
call mrccend(1)
end if
if(localcc .ne. 'off '.and.localccn.lt.2022) then
write(iout, *) 'Warning: local correlation calculation can',
$ ' not be performed with MPI!' ! and localcc < 2022!' ! development
call mrccend(1)
end if
if(trim(calc) .eq. 'ccsd' .or. trim(calc) .eq. 'ccsd(t)') then
if(ccprog .eq. 'ccsd') then
if(ccsdalg .ne. 'dfdirect') then
write(iout, *)
$ 'Warning: only ccsdalg=dfdirect can be run with more MPI tasks!'
call mrccend(1)
end if
if(talg .eq. 'virt') then
write(iout, *)
$ 'Warning: talg=virt can not be run with more MPI tasks!'
call mrccend(1)
end if
end if
end if
end if
C scfalg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfalg',6,scfalg,8)
if(scfalg.ne.'disk '.and.scfalg.ne.'direct '.and.
$ scfalg.ne.'auto '.and.scfalg.ne.' '.and.
$ scfalg.ne.'locfit1 '.and.scfalg.ne.'locfit2 ')
$call unknown('scfalg',8)
if(scfalg.eq.' ') then
if(dfbasis_scf.ne.'none '.and.
$ dfbasis_cor.eq.'none '.and.
$ trim(calc).ne.'scf') then
scfalg='direct '
else if(fmm.eq.'off '.and.(dens.ne.'0 '.and.
$dfbasis_scf.ne.'none '.and.
$trim(calc).ne.'scf').or.naf_scf.ne.'off ') then
scfalg='disk '
elseif(fmm.ne.'off ') then
scfalg='direct '
elseif(fitting.eq.'overlap ') then
scfalg='direct '
else
scfalg='auto '
endif
endif
if((scfalg.eq.'locfit1 '.or.scfalg.eq.'locfit2 ').and.
$trim(excrad).eq.'0.d0') excrad='1.0 '
if(embed.eq.'scl '.or.embed.eq.'emft '.or.
$ embed.eq.'fdm '.or.embed.eq.'sch '.or.
$scfiguess.eq.'off '.or.lf12) scfalg='direct '
if(trim(mpitasks).ne.'1'.and.(scfalg.eq.'disk '.or.
$scfalg.eq.'auto ')) scfalg='direct '
if((qscf.ne.'off '.and.(scftype.eq.'mcscf'.or.
$trim(dfbasis_scf).eq.'none')).or.(trim(calc).eq.'mp2'.and.
$dens.ne.'0 ')) then
scfalg='disk '
write(iout,*) 'Warning! scfalg has been set to disk!'
endif
if(scfalg.eq.'disk '.and.fitting.eq.'overlap ') then
write(iout,*) 'Error: Overlap fitting is only available for'//
& ' direct SCF calculations'
call mrccend(1)
endif
c if(lf12) scfalg='direct '
C store %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
c call getkeym('store',5,store,8)
c if(store.ne.'on '.and.store.ne.'off '.and.
c $ store.ne.' ') call unknown('store',5)
c if(store.eq.' ') then
c if(scfalg.eq.'disk ') then
c store='off '
c else
c store='on '
c endif
c endif
C scfloc %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfloc',6,scfloc,16)
if(trim(scfloc).ne.'boys'.and.trim(scfloc).ne.'pm'.and.
& trim(scfloc).ne.'pmm'.and.scfloc5.ne.'gboys'.and.
& trim(scfloc).ne.'off'.and.
& scfloc.ne.' ') call unknown('scfloc',6)
if(trim(scfloc).eq.'off'.and.
& (scfalg.eq.'locfit1 '.or.scfalg.eq.'locfit2 ')) then
write(iout,'(A)') " WARNING! scfloc=off is not compatible"//
&" with local SCF calulations!"
call mrccend(1)
endif
read(excrad,*) rr
if(scfloc.eq.' '.and.
& (scfalg.eq.'locfit1 '.or.scfalg.eq.'locfit2 '.or.rr.gt.0.0d0))
& scfloc='pm '
if(scfloc.eq.' ') scfloc='off '
if(scfloc5.eq.'gboys') scfalg='newton '
C excrad_fin %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('excrad_fin',10,excrad_fin,16)
if(excrad_fin.eq.' ') then
read(excrad,*) rr
rr=rr/1000.d0
write(excrad_fin,'(d16.9)') rr
excrad_fin=adjustl(excrad_fin)
endif
read(excrad_fin,*) rr
if(rr.lt.0.d0) call unknown('excrad_fin',10)
C dfalg %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('dfalg',5,dfalg,8)
if(dfalg.ne.' '.and.
$ dfalg.ne.'cholesky'.and.
$ dfalg.ne.'lineq '.and.
$ dfalg.ne.'invsqrt ') call unknown('dfalg',5)
if(dfalg.eq.' ') dfalg='lineq '
if(scfalg.eq.'disk '.or.
$(dens.ne.'0 '.and.trim(calc).ne.'scf')) dfalg='invsqrt '
C scfdamp_mode %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdamp_mode',12,scfdamp_mode,16)
if(scfdamp_mode.ne.'on '.and.
$ scfdamp_mode.ne.'1 '.and. ! static damping
$ scfdamp_mode.ne.'2 '.and. ! steadily decreasing dynamic damping
$ scfdamp_mode.ne.'3 '.and. ! dynamic damping (fixed factor variation)
$ scfdamp_mode.ne.'off '.and.
$ scfdamp_mode.ne.' ') then
call unknown('scfdamp_mode',12)
endif
if(scfdamp_mode.eq.' '.and.
$ (trim(dft).ne.'off'.and.denscorr.eq.'0 '))
$ scfdamp_mode='1 '
if(scfdamp_mode.eq.' '.and.
$ (trim(dft).eq.'off'.or.denscorr.ne.'0 '))
$ scfdamp_mode='off '
if(scfdamp_mode.eq.'on ')
$ scfdamp_mode='3 '
C scfdamp_end %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdamp_end',11,scfdamp_end,4)
read(scfdamp_end,'(i4)') i
if(i.lt.0) call unknown('scfdamp_end',11)
! default: scfmaxit (gets the value when scfmaxit is initalized
C scfdamp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdamp',7,scfdamp,16)
if(scfdamp.ne.' ') then
if(scfdamp.ne.'off ') then
read(scfdamp,*) rr
if(rr.lt.0.d0.or.rr.gt.1.d0) call unknown('scfdamp',7)
endif
if(scfdamp.eq.'off ') scfdamp='0.0d0 '
endif
if(scfdamp.eq.' '.and.
$ scfdamp_mode.ne.'off ')
$ scfdamp='0.7d0 '
if(scfdamp.eq.' '.and.
$ scfdamp_mode.eq.'off ')
$scfdamp='0.0d0 ' !
C scfdamp_dtol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdamp_dtol',12,scfdamp_dtol,16)
if(scfdamp_dtol.ne.' ') then
read(scfdamp_dtol,*) rr
if(rr.lt.0.d0) call unknown('scfdamp_dtol',12)
else
scfdamp_dtol='0.0d0 '
endif
C scfdamp_dampstep %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdamp_dampstep',16,scfdamp_dampstep,16)
if(scfdamp_dampstep.ne.' ') then
read(scfdamp_dampstep,*) rr
read(scfdamp,*) tmp
if(rr.lt.0.d0.and.rr.gt.tmp)
$ call unknown('scfdamp_dampstep',16)
else
if(scfdamp_mode.eq.'1 '.or.
$ scfdamp_mode.eq.'off ')
$scfdamp_dampstep='0.d0 '
if(scfdamp_mode.eq.'2 '.or.
$ scfdamp_mode.eq.'3 ')
$ scfdamp_dampstep='0.05d0 '
endif
C scfdamp_minfact %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdamp_minfact',15,scfdamp_minfact ,16)
if(scfdamp_minfact.ne.' ') then
read(scfdamp_minfact,*) rr
read(scfdamp,*) tmp
if(rr.lt.0.d0.and.rr.gt.tmp)
$ call unknown('scfdamp_minfact',15)
else
if(scfdamp_mode.eq.'1 '.or.
$ scfdamp_mode.eq.'off ')
$scfdamp_minfact=scfdamp
if(scfdamp_mode.eq.'2 '.or.
$ scfdamp_mode.eq.'3 ')
$scfdamp_minfact='0.1d0 '
endif
C scfdamp_maxfact %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdamp_maxfact',15,scfdamp_maxfact ,16)
if(scfdamp_maxfact.ne.' ') then
read(scfdamp_maxfact,*) rr
read(scfdamp,*) tmp
if(rr.lt.0.d0.and.rr.gt.1.d0.and.rr.lt.tmp)
$ call unknown('scfdamp_maxfact',16)
else
if(scfdamp_mode.eq.'1 '.or.
$ scfdamp_mode.eq.'off ')
$scfdamp_maxfact=scfdamp
if(scfdamp_mode.eq.'2 '.or.
$ scfdamp_mode.eq.'3 ')
$scfdamp_maxfact='0.95d0 '
endif
!!! !HB
C scfdiis %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdiis',7,scfdiis,4)
if(scfdiis.ne.'on '.and.scfdiis.ne.'off '.and.scfdiis.ne.' ')
$call unknown('scfdiis',7)
if(scfdiis.eq.' ') scfdiis='on '
C scfdiis_start %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdiis_start',13,cscr4,4)
if (cscr4.eq.' ') then
scfdiis_start='2 '
else
scfdiis_start=cscr4
endif
if(cscr4.ne.' ') then
read(cscr4,'(i4)') i
if(i.eq.1.and.scfiguess.eq.'core ') then
write(iout,'(a)') ' Cannot perform DIIS extrapolation in '//
$'the first SCF step if scfiguess=core'
call mrccend(1)
endif
if(i.le.0) then
write(iout,'(a)') ' Illegal parameter for scfdiis_start.'
call mrccend(1)
endif
endif
c%%% ez amiatt kell, mert a corfe guessbol nem lehet extrapolalni az elso lepesben!
C scfdiis_step %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdiis_step',12,scfdiis_step,4)
if(scfdiis_step.ne.' ') then
read(scfdiis_step,'(i4)') i
if(i.le.0) then
write(iout,'(a)') ' Illegal parameter for scfdiis_step.'
call mrccend(1)
endif
else
scfdiis_step='1 '
endif
C scfdiis_dtol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdiis_dtol',12,scfdiis_dtol,12)
if(scfdiis_dtol.eq.' ') then
scfdiis_dtol='0.0d0 '
else
read(scfdiis_step,*) rr
if(rr.lt.0) then
write(iout,'(a)') ' Illegal parameter for scfdiis_dtol.'
call mrccend(1)
endif
endif
C scfdiis_watch %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdiis_watch',13,scfdiis_watch,4)
if(scfdiis_watch.ne.' '.and.scfdiis_watch.ne.'on '.and.
$ scfdiis_watch.ne.'off ') call unknown('scfdiis_watch',13)
if(scfdiis_watch.eq.' ') scfdiis_watch='off '
C scfext %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfext',6,scfext,4)
if(scfext.eq.' ') then
scfext='10 '
else
read(scfext,'(i4)') i
if(i.le.0) then
write(iout,'(a)') ' Illegal parameter for scfext.'
call mrccend(1)
endif
endif
C scfdiis_wrange %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdiis_wrange',14,scfdiis_wrange,4)
if(scfdiis_wrange.eq.' ') then
scfdiis_wrange=scfext
else
read(scfdiis_wrange,'(i4)') i
if(i.le.0) then
write(iout,'(a)') ' Illegal parameter for scfext.'
call mrccend(1)
endif
endif
C scfdiis_wlimit %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdiis_wlimit',14,scfdiis_wlimit,4)
if(scfdiis_wlimit.eq.' ') then
read(scfdiis_wrange,'(i4)') i
if(MOD(i,2).eq.0) then
i=i/2
else
i=(i+1)/2
endif
write(scfdiis_wlimit,'(i4)') i
scfdiis_wlimit=trim(adjustl(scfdiis_wlimit))
endif
C scfdiis_delmax %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdiis_delmax',14,scfdiis_delmax,4)
if(scfdiis_delmax.eq.' ') then
scfdiis_delmax='2 '
else
read(scfdiis_delmax,'(i4)') i
if(i.lt.0) call unknown('scfdiis_delmax',14)
endif
C scfmaxit %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfmaxit',8,scfmaxit,4)
if(scfmaxit.eq.' ') scfmaxit='50 '
C maxmicroit %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('maxmicroit',10,maxmicroit,4)
if(maxmicroit.eq.' ') maxmicroit='100 '
C scflshift %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scflshift',9,scflshift,8)
if(scflshift.ne.'on '.and.
$ scflshift.ne.'off '.and.
$ scflshift.ne.' ') then
read(scflshift,*) rr
if(rr.lt.0.d0) call unknown('scflshift',9)
endif
c if(scflshift.eq.' ') scflshift='off '
if(scflshift.eq.' ') scflshift='0.20 '
if(scflshift.eq.'on ') scflshift='0.20 '
C scflshift_end %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scflshift_end',13,scflshift_end,4)
read(scflshift_end,'(i4)') i
if(i.lt.0) call unknown('scflshift_end',13)
if(scflshift_end.eq.' ') scflshift_end='8 '
!!! scfdamp_end can get a default value here now that scfmaxit is set.
if(scfdamp_end.eq.' '.and.
$ (trim(dft).ne.'off'.and.denscorr.eq.'0 '))
$scfdamp_end='3 '
if(scfdamp_end.eq.' ')
$scfdamp_end=scfmaxit
!!!
C scflshift_gaptol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scflshift_gaptol',16,scflshift_gaptol,8)
if(scflshift_gaptol.ne.' ') then
read(scflshift_gaptol,*) rr
if(rr.lt.0.d0) call unknown('scflshift_gaptol',16)
endif
! scflshift_gaptol=0.0d0 equals static level shifting
if(scflshift.ne.'off '.and.scflshift_gaptol.eq.' ')
$ scflshift_gaptol='0.20 '
if(scflshift.eq.'off '.and.scflshift_gaptol.eq.' ')
$ scflshift_gaptol='0.0 '
C scflshift_dtol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scflshift_dtol ',14,scflshift_dtol,8)
if(scflshift_dtol.ne.' ') then
read(scflshift_dtol,*) rr
if(rr.lt.0.d0) call unknown('scflshift_dtol',14)
endif
! scflshift_dtol=0.0d0 equals static level shifting
if(scflshift_dtol.eq.' ') scflshift_dtol='0.0 '
C scfdiis_end %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('scfdiis_end',11,scfdiis_end,4)
if(scfdiis_end.eq.' ') scfdiis_end=scfmaxit
C etemp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('etemp',5,etemp,8)
if(etemp.eq.' ') then
etemp='300 '
else
read(etemp,*) rr
if(rr.lt.0.0d0) call unknown('etemp',5)
endif
C spairtol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('spairtol',8,spairtol,16)
if(spairtol.ne.' '.and.
$ spairtol.ne.'off ') then !NP
read(spairtol,*) rr
if(rr.lt.0.d0) call unknown('spairtol',8)
endif
if(spairtol.eq.' ') then
if (localcc16p) then
spairtol='-1.d0'
else
if(lcorthr.eq.'0 ') then
spairtol='0.d0 '
else if(lcorthr.eq.'tight ') then
spairtol='1e-5 '
else
spairtol='1e-4 '
endif
endif
endif
if(spairtol.eq.'off ') spairtol='-1.d0 '
!!! !HB
C sqmprog %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('sqmprog',7,sqmprog,16)
if(sqmprog.ne.' '.and.
$ sqmprog.ne.'mopac2016 '.and.
$ sqmprog.ne.'xtb '.and.
$ sqmprog.ne.'off ')
$ call unknown('sqmprog',16)
C mmprog %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('mmprog',6,mmprog,16)
if(mmprog.ne.' '.and.
$ mmprog.ne.'xtb '.and.
$ mmprog.ne.'off ')
$ call unknown('mmprog',16)
!!! !HB
C subminp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('subminp',7,subminp,8)
if(subminp.ne.' '.and. ! use generated minp files
$ subminp.ne.'top'.and. ! use minp file only for the top layer calc
$ subminp.ne.'minp'.and. ! use minp file for all calc
$ subminp.ne.'temp'.and. ! use template files
$ subminp.ne.'t+t'.and. ! use option 1 and 3
$ subminp.ne.'m+t') ! use option 2 and 3
$ call unknown('subminp',8)
if(subminp.eq.' ') then
subminp='top'
endif
C symm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('symm',4,symm,4)
irlab='a' // char(39)
if((iface.eq.'none '.and.
$symm.ne.'0 '.and.symm.ne.'1 '.and.symm.ne.'2 '.and.
$symm.ne.'3 '.and.symm.ne.'4 '.and.symm.ne.'5 '.and.
$symm.ne.'6 '.and.symm.ne.'7 '.and.symm.ne.'8 '.and.
$symm.ne.'a '.and.symm.ne.'a1g '.and.symm.ne.'a1u '.and.
$symm.ne.irlab .and.symm.ne.'a" '.and.symm.ne.'b '.and.
$symm.ne.'a1 '.and.symm.ne.'b1 '.and.symm.ne.'b2 '.and.
$symm.ne.'a2 '.and.symm.ne.'ag '.and.symm.ne.'bg '.and.
$symm.ne.'au '.and.symm.ne.'bu '.and.symm.ne.'b3 '.and.
$symm.ne.'b1g '.and.symm.ne.'b2g '.and.symm.ne.'b3g '.and.
$symm.ne.'b1u '.and.symm.ne.'b2u '.and.symm.ne.'b3u '.and.
$symm.ne.'off '.and.symm.ne.' ').or.(iface.ne.'none '.and.
$symm.ne.'0 '.and.symm.ne.'1 '.and.symm.ne.'2 '.and.
$symm.ne.'3 '.and.symm.ne.'4 '.and.symm.ne.'5 '.and.
$symm.ne.'6 '.and.symm.ne.'7 '.and.symm.ne.'8 '.and.
$symm.ne.'off '.and.symm.ne.' ')) call unknown('symm',4)
if(symm.eq.'off ') symm='0 '
if(embed.ne.'off '.and.embed.ne.'coulomb ') symm='0 '
! Default is set by integ
C localcorrsymm %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('localcorrsymm',13,localcorrsymm,4)
if (localcorrsymm.ne.'on '.and.localcorrsymm.ne.'off '.and.
$ localcorrsymm.ne.'forc'.and.localcorrsymm.ne.' '.and.
$ localcorrsymm.ne.'read'.and.localcorrsymm.ne.'diag')
$ call unknown('localcorrsymm',13)
c if ='forc' : forced to try to identify symmetry equivalent LMOs, even if the structure is not symmetric up to gtol precision
if (localcorrsymm.eq.' ') then
c if (localcc16p.and.symm.ne.'off ') then
c localcorrsymm='on '
c else
localcorrsymm='off ' ! default until more reliably symmetric orbital localization is implemented
c endif
endif
if (localcorrsymm.ne.'off '.and..not.orblocguess.eq.'read '
$ .and.(lccrest.eq.'domain '.or.lccrest.eq.'restart ')) then
write(iout,*)
$'orblocguess=read is required for restarting with localcorrsymm'
call mrccend(1)
endif
if (localcorrsymm.ne.'off '.and.corembed.ne.'off ') then
write(iout,*)'Warning: corembed is not tested with localcorrsymm'
endif
C ccsdrest %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ccsdrest',8,ccsdrest,4)
if(ccsdrest.eq.' ') then
if ( !(trim(calc).eq.'ccsd'.or.trim(calc).eq.'ccsd(t)')
$ ccprog.eq.'ccsd' .and. talg.ne.'lapl') then
ccsdrest='trf '
else
ccsdrest = 'off '
end if
end if
if(ccsdrest.ne.'off '.and.ccsdrest.ne.'trf '.and.
$ ccsdrest.ne.'ccsd') call unknown('ccsdrest',8)
if(ccsdrest.ne.'off ' .and. talg.eq.'lapl') then
write(iout,*)
$ 'Incompatible options for keywords ccsdrest and lapl!'
call mrccend(1)
end if
C ccsdthreads %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ccsdthreads',11,ccsdthreads,4)
if(ccsdthreads .eq. ' ') ccsdthreads = '2 '
C ptthreads %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ptthreads',9,ptthreads,4)
if(ptthreads .eq. ' ') then
if(talg .ne. 'virt') then
ptthreads = '2 '
else
ptthreads = '1 '
end if
end if
if(talg .eq. 'virt' .and. ptthreads .ne. '1 ') then
write(iout,*)
$ 'Warning: talg=virt does not work with ptthreads>1!'
call mrccend(1)
end if
C ccsdmkl %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('ccsdmkl',7,ccsdmkl,3)
if(ccsdmkl .eq. ' ') then
if(talg .ne. 'virt') then
ccsdmkl = 'seq'
else
ccsdmkl = 'thr'
end if
end if
if(ccsdmkl .ne. 'thr' .and. talg .eq. 'virt') then
write(iout,*) 'Warning: talg=virt runs only with ccsdmkl=thr!'
call mrccend(1)
end if
C temp %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('temp',4,temp,16)
if(temp.ne.' ') then
read(temp,*) rr
if(rr.lt.0.d0) call unknown('temp',4)
endif
if(temp.eq.' ') temp='298.15 '
C test %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('test',4,test,30)
if(test.eq.' ')
$ test='off '
C tprint %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('tprint',6,tprint,16)
if(tprint.eq.' ') tprint='off '
!NP
C tvirtcut %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
cnp call getkeym('tvirtcut',8,tvirtcut,8)
cnp if(tvirtcut.eq.' ') tvirtcut='100 '
!NP
C uncontract %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('uncontract',10,uncontract,4)
if(uncontract.ne.'on '.and.uncontract.ne.'off '.and.
$uncontract.ne.' ') call unknown('uncontract',10)
if(uncontract.eq.' ') uncontract='off '
C unit %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('unit',4,unit,4)
if(unit.ne.'bohr'.and.unit.ne.'angs'.and.unit.ne.' ')
$call unknown('unit',4)
if(unit.eq.' ') unit='angs'
C verbosity %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('verbosity',9,verbosity,4)
if(verbosity.eq.' ') verbosity='2 '
if(.not.linteger(verbosity)) call unknown('verbosity',9)
C wpairtol %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
call getkeym('wpairtol',8,wpairtol,16)
if(wpairtol.ne.' ') then
read(wpairtol,*) rr
if(rr.lt.0.d0) call unknown('wpairtol',8)
endif
c
if(wpairtol.eq.' ') then
if(lcorthr.eq.'0 ') then
wpairtol= '0.d0 '
go to 102
endif
c
if (localcc.eq.'2016') then
if (lanycc(calc)) then
if(lcorthr.eq.'tight ') then
c wpairtol= '5.d-6 ' ! this matches the typo in previous manuals for localcc=2016 and lcorthr=tight
wpairtol= '3.d-6 '
else if(lcorthr.eq.'vtight ') then
wpairtol= '1.d-6 '
else if(lcorthr.eq.'vvtight ') then
wpairtol= '5.d-7 '
else if(lcorthr.eq.'v3tight ') then
wpairtol= '2.5d-7 '
else if(lcorthr.eq.'v4tight ') then
wpairtol= '1.d-7 '
else if(lcorthr.eq.'vloose ') then
wpairtol= '2.d-5 '
else if(lcorthr.eq.'vvloose ') then
wpairtol= '4.d-5 '
else
wpairtol= '1.d-5 ' ! default 2016 LCC
endif
elseif (localmp2) then
if (lcorthr.eq.'tight ') then
wpairtol= '1d-5 '
else
wpairtol= '1.5d-5 ' ! default 2016 LMP2
endif
else
wpairtol= '1.5d-5 ' ! initialization
endif
elseif (localccn.ge.2018) then
if (lanycc(calc).or.localmp2) then ! same set for LMP2 and LCC
if(lcorthr.eq.'tight ') then
wpairtol= '3.d-6 '
else if(lcorthr.eq.'vtight ') then
wpairtol= '1.d-6 '
else if(lcorthr.eq.'vvtight ') then
wpairtol= '3.d-7 '
else if(lcorthr.eq.'loose ') then
wpairtol= '3.d-5 '
else if(lcorthr.eq.'vloose ') then
wpairtol= '1.d-4 '
else
wpairtol= '1.d-5 ' ! normal 2018 LMP2 & LNO-CC
endif
else
wpairtol= '1d-5 ' ! initialization
endif
else ! for 2015 LMP2/LdRPA (initalize 2013)
read(spairtol,*) tmp
if (tmp.ge.0.d0) then
rr=min(1d-6,0.01d0*tmp)
else
rr=1d-5
endif
if ((tmp.ge.0.d0.and.rr.ge.0.d0).and.tmp.lt.rr) then
write(iout,*) 'spairtol > wpairtol is required'
call mrccend(1)
endif
write(wpairtol,'(e16.9)') rr
wpairtol=adjustl(wpairtol)
endif
102 continue
endif
C Wrong keyword combinations %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
if(dfbasis_scf.eq.'none '.and.dens.ne.'0 '.and.
$(trim(calc).eq.'mp2'.or.dhdft(calc))) then
write(iout,*)
$'MP2 and DH DFT gradient calculations are not possible with'
write(iout,*) 'dfbasis_scf=none.'
call mrccend(1)
endif
if(dfbasis_scf_sm.eq.'auto ')
$ dfbasis_scf_sm=dfbasis_scf
C%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
if(scf_conv.ne.'manual ') then
call setup_scfconv_parameters(minpfile,scf_conv,scflshift,
$scflshift_gaptol,scflshift_dtol,scflshift_end,scfdamp_mode,
$scfdamp,scfdamp_maxfact,scfdamp_minfact,scfdamp_dampstep,
$scfdamp_dtol,scfdamp_end,scfdiis,scfdiis_start,scfdiis_end,scfext,
$scfdiis_dtol,scfdiis_watch,scfdiis_step,scfdiis_wrange,
$scfdiis_wlimit,scfdiis_delmax,scfmaxit,qscf)
endif
C%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
C Set up KEYWD file
write(keywdfile,*) trim('active=' // active)
write(keywdfile,*) trim('agrid=' // agrid)
write(keywdfile,*) trim('agrid_pssp=' // agrid_pssp)
write(keywdfile,*) trim('agrid_pssp_sm=' // agrid_pssp_sm)
write(keywdfile,*) trim('basis=' // basis)
write(keywdfile,*) trim('basis_sm=' // basis_sm)
write(keywdfile,*) trim('basopt=' // basopt)
write(keywdfile,*) trim('bfbasis=' // bfbasis)
write(keywdfile,*) trim('bfgsmem=' // bfgsmem)
write(keywdfile,*) trim('bfgstol=' // bfgstol)
write(keywdfile,*) trim('boysalg=' // boysalg)
write(keywdfile,*) trim('bpcompo=' // bpcompo)
write(keywdfile,*) trim('bpcompv=' // bpcompv)
write(keywdfile,*) trim('bpdfo=' // bpdfo)
write(keywdfile,*) trim('bpocc=' // bpocc)
write(keywdfile,*) trim('bppdo=' // bppdo)
write(keywdfile,*) trim('bppdv=' // bppdv)
write(keywdfile,*) trim('bpedo=' // bpedo)
write(keywdfile,*) trim('bpedv=' // bpedv)
write(keywdfile,*) trim('calc=' // calc)
write(keywdfile,*) trim('ccmaxit=' // ccmaxit)
write(keywdfile,*) trim('ccprog=' // ccprog)
write(keywdfile,*) trim('ccsdalg=' // ccsdalg)
write(keywdfile,*) trim('ccsdmkl=' // ccsdmkl)
write(keywdfile,*) trim('ccsdrest=' // ccsdrest)
write(keywdfile,*) trim('ccsdthreads=' // ccsdthreads)
write(keywdfile,*) trim('cctol=' // cctol)
write(keywdfile,*) trim('charge=' // charge)
write(keywdfile,*) trim('cialg=' // cialg)
write(keywdfile,*) trim('ciguess=' // ciguess)
write(keywdfile,*) trim('cmpgrp=' // cmpgrp)
write(keywdfile,*) trim('comprest=' // comprest) !HB
write(keywdfile,*) trim('coord_sys=' // coord_sys)
write(keywdfile,*) trim('core=' // core)
write(keywdfile,*) trim('corembed=' // corembed)
write(keywdfile,*) trim('csapprox=' // csapprox)
write(keywdfile,*) trim('cvs=' // cvs)
write(keywdfile,*) trim('dboc=' // dboc)
write(keywdfile,*) trim('delocsomofact=' // delocsomofact)
write(keywdfile,*) trim('dendec=' // dendec)
write(keywdfile,*) trim('dens=' // dens)
write(keywdfile,*) trim('denscorr=' // denscorr)
write(keywdfile,*) trim('dfalg=' // dfalg)
write(keywdfile,*) trim('dfbasis_cab=' // dfbasis_cab)
write(keywdfile,*) trim('dfbasis_cor=' // dfbasis_cor)
write(keywdfile,*) trim('dfbasis_scf=' // dfbasis_scf)
write(keywdfile,*) trim('dfbasis_scf_sm=' // dfbasis_scf_sm)
write(keywdfile,*) trim('dfintran=' // dfintran)
write(keywdfile,*) trim('dft=' // dft)
write(keywdfile,*) trim('dhexc=' // dhexc)
write(keywdfile,*) trim('diag=' // diag)
write(keywdfile,*) trim('docc=' // docc)
write(keywdfile,*) trim('domrad=' // domrad)
write(keywdfile,*) trim('drpaalg=' // drpaalg)
write(keywdfile,*) trim('dual=' // dual)
write(keywdfile,*) trim('dual_df=' // dual_df)
write(keywdfile,*) trim('ecp=' // ecp)
write(keywdfile,*) trim('edisp=' // edisp)
write(keywdfile,*) trim('edisp_embed=' // edisp_embed) !HB
write(keywdfile,*) trim('embed=' // embed)
write(keywdfile,*) trim('epairestfact=' // epairestfact)
write(keywdfile,*) trim('epairscale=' // epairscale)
write(keywdfile,*) trim('etemp=' // etemp) !HB
write(keywdfile,*) trim('epert=' // epert)
write(keywdfile,*) trim('eps=' // eps)
write(keywdfile,*) trim('espcharge=' // espcharge) !GA
write(keywdfile,*) trim('excrad=' // excrad)
write(keywdfile,*) trim('excrad_fin=' // excrad_fin)
write(keywdfile,*) trim('fitting=' // fitting)
write(keywdfile,*) trim('fmm=' // fmm)
write(keywdfile,*) trim('fmmord=' // fmmord)
write(keywdfile,*) trim('fnonorb=' // fnonorb)
write(keywdfile,*) trim('freq=' // freq)
write(keywdfile,*) trim('gamma=' // gamma)
write(keywdfile,*) trim('gauss=' // gauss)
write(keywdfile,*) trim('geom=' // geom)
write(keywdfile,*) trim('gopt=' // gopt)
write(keywdfile,*) trim('ghost=' // ghost)
write(keywdfile,*) trim('gtol=' // gtol)
write(keywdfile,*) trim('grdens=' // grdens)
write(keywdfile,*) trim('grid=' // grid)
write(keywdfile,*) trim('grid_sm=' // grid_sm)
write(keywdfile,*) trim('gridbatch_cos=' // gridbatch_cos)
write(keywdfile,*) trim('grtol=' // grtol)
write(keywdfile,*) trim('guido_ct=' // guido_ct)
write(keywdfile,*) trim('hamilton=' // hamilton)
write(keywdfile,*) trim('iface=' // iface)
write(keywdfile,*) trim('intalg=' // intalg)
write(keywdfile,*) trim('ip_ea=' // ip_ea)
write(keywdfile,*) trim('itol=' // itol)
write(keywdfile,*) trim('laptol=' // laptol)
write(keywdfile,*) trim('lccoporder=' // lccoporder) !NP
write(keywdfile,*) trim('lcorthr=' // lcorthr)
write(keywdfile,*) trim('lccrest=' // lccrest) !NP
write(keywdfile,*) trim('ldfgrad_tol=' // ldfgrad_tol) !NP
write(keywdfile,*) trim('lmp2dens=' // lmp2dens)
write(keywdfile,*) trim('lnoepso=' // lnoepso)
write(keywdfile,*) trim('lnoepsv=' // lnoepsv)
write(keywdfile,*) trim('localcc=' // localcc)
write(keywdfile,*) trim('localcorrsymm=' // localcorrsymm) !NP
write(keywdfile,*) trim('locintrf=' // locintrf) !NP
write(keywdfile,*) trim('mact=' // mact)
write(keywdfile,*) trim('maxact=' // maxact)
write(keywdfile,*) trim('maxdim=' // maxdim)
write(keywdfile,*) trim('maxex=' // maxex)
write(keywdfile,*) trim('maxmicroit=' // maxmicroit)
write(keywdfile,*) trim('mcscfiguess=' // mcscfiguess)
write(keywdfile,*) trim('mem=' // mem)
write(keywdfile,*) trim('mmprog=' // mmprog)
write(keywdfile,*) trim('molden=' // molden)
write(keywdfile,*) trim('mpitasks=' // mpitasks)
write(keywdfile,*) trim('mulmet=' // mulmet) !NP
write(keywdfile,*) trim('mult=' // mult)
write(keywdfile,*) trim('nab=' // nab)
write(keywdfile,*) trim('nacto=' // nacto)
write(keywdfile,*) trim('nactv=' // nactv)
write(keywdfile,*) trim('naf_amp=' // naf_amp)
write(keywdfile,*) trim('naf_cor=' // naf_cor)
write(keywdfile,*) trim('naf_f12=' // naf_f12)
write(keywdfile,*) trim('naf_scf=' // naf_scf)
write(keywdfile,*) trim('nafalg=' // nafalg)
write(keywdfile,*) trim('nafdens=' // nafdens)
write(keywdfile,*) trim('naftyp=' // naftyp) !NP
write(keywdfile,*) trim('nchol=' // nchol)
write(keywdfile,*) trim('ndeps=' // ndeps)
write(keywdfile,*) trim('nstate=' // nstate)
write(keywdfile,*) trim('nsing=' // nsing)
write(keywdfile,*) trim('nto=' // nto)
write(keywdfile,*) trim('ntrip=' // ntrip)
write(keywdfile,*) trim('num_grad=' // num_grad)
write(keywdfile,*) trim('occ=' // occ)
write(keywdfile,*) trim('occri=' // occri)
write(keywdfile,*) trim('oniom=' // oniom) !HB
write(keywdfile,*) trim('oniom_eechg=' // oniom_eechg) !HB
write(keywdfile,*) trim('oniom_pcm=' // oniom_pcm) !HB
write(keywdfile,*) trim('oniom_qcorr=' // oniom_qcorr) !HB
write(keywdfile,*) trim('optalg=' // optalg)
write(keywdfile,*) trim('optmaxit=' // optmaxit)
write(keywdfile,*) trim('optetol=' // optetol)
write(keywdfile,*) trim('optex=' // optex)
write(keywdfile,*) trim('optgtol=' // optgtol)
write(keywdfile,*) trim('optstol=' // optstol)
write(keywdfile,*) trim('orblocc=' // orblocc)
write(keywdfile,*) trim('orbloce=' // orbloce) !HB
write(keywdfile,*) trim('orbloco=' // orbloco)
write(keywdfile,*) trim('orblocv=' // orblocv)
write(keywdfile,*) trim('orblocguess=' // orblocguess)
write(keywdfile,*) trim('osveps=' // osveps)
write(keywdfile,*) trim('ovirt=' // ovirt)
write(keywdfile,*) trim('ovltol=' // ovltol)
write(keywdfile,*) trim('ovosnorb=' // ovosnorb)
write(keywdfile,*) trim('pao_subsys_tol=' // pao_subsys_tol)
write(keywdfile,*) trim('pcm=' // pcm)
write(keywdfile,*) trim('popul=' // popul)
write(keywdfile,*) trim('pressure=' // pressure)
write(keywdfile,*) trim('pssp=' // pssp)
write(keywdfile,*) trim('ptfreq=' // ptfreq)
write(keywdfile,*) trim('ptthreads=' // ptthreads)
write(keywdfile,*) trim('qmreg=' // qmreg) !HB
write(keywdfile,*) trim('qmmm=' // qmmm)
write(keywdfile,*) trim('qro=' // qro)
write(keywdfile,*) trim('qscf=' // qscf)
write(keywdfile,*) trim('redcost_exc=' // redcost_exc)
write(keywdfile,*) trim('redcost_tddft=' // redcost_tddft)
write(keywdfile,*) trim('refdet=' // refdet)
write(keywdfile,*) trim('rest=' // rest)
write(keywdfile,*) trim('rgrid=' // rgrid)
write(keywdfile,*) trim('rism=' // rism) !GA
write(keywdfile,*) trim('rohfcore=' // rohfcore)
write(keywdfile,*) trim('rohftype=' // rohftype)
write(keywdfile,*) trim('scfalg=' // scfalg)
write(keywdfile,*) trim('scf_conv=' // scf_conv) !HB
write(keywdfile,*) trim('scfdamp=' // scfdamp) !HB ! watch the order or misread could happen !
write(keywdfile,*) trim('scfdamp_mode=' // scfdamp_mode)
write(keywdfile,*) trim('scfdamp_end=' // scfdamp_end) !HB
write(keywdfile,*) trim('scfdamp_dampstep=' // scfdamp_dampstep) !HB
write(keywdfile,*) trim('scfdamp_dtol=' // scfdamp_dtol) !HB
write(keywdfile,*) trim('scfdamp_maxfact=' // scfdamp_maxfact) !HB
write(keywdfile,*) trim('scfdamp_minfact=' // scfdamp_minfact) !HB
write(keywdfile,*) trim('scfdiis=' // scfdiis)
write(keywdfile,*) trim('scfdiis_dtol=' // scfdiis_dtol) !HB
write(keywdfile,*) trim('scfdiis_end=' // scfdiis_end)
write(keywdfile,*) trim('scfdiis_start=' // scfdiis_start)
write(keywdfile,*) trim('scfdiis_step=' // scfdiis_step)
write(keywdfile,*) trim('scfdiis_watch=' // scfdiis_watch) !HB
write(keywdfile,*) trim('scfdiis_wrange=' // scfdiis_wrange) !HB
write(keywdfile,*) trim('scfdiis_wlimit=' // scfdiis_wlimit) !HB
write(keywdfile,*) trim('scfdiis_delmax=' // scfdiis_delmax) !HB
write(keywdfile,*) trim('scfdtol=' // scfdtol)
write(keywdfile,*) trim('scfext=' // scfext)
write(keywdfile,*) trim('scfguessdens=' // scfguessdens)
write(keywdfile,*) trim('scfiguess=' // scfiguess)
write(keywdfile,*) trim('scfloc=' // scfloc)
write(keywdfile,*) trim('scflshift=' // scflshift)
write(keywdfile,*) trim('scflshift_end=' // scflshift_end) !HB
write(keywdfile,*) trim('scflshift_dtol=' // scflshift_dtol) !HB
write(keywdfile,*) trim('scflshift_gaptol=' // scflshift_gaptol) !HB
write(keywdfile,*) trim('scfmaxit=' // scfmaxit)
write(keywdfile,*) trim('scftype=' // scftype)
write(keywdfile,*) trim('scftol=' // scftol)
write(keywdfile,*) trim('scspe=' // scspe)
write(keywdfile,*) trim('scsph=' // scsph)
write(keywdfile,*) trim('scsps=' // scsps)
write(keywdfile,*) trim('scsps_t=' // scsps_t)
write(keywdfile,*) trim('scspt=' // scspt)
write(keywdfile,*) trim('scspt_t=' // scspt_t)
write(keywdfile,*) trim('scspv=' // scspv)
write(keywdfile,*) trim('spairtol=' // spairtol)
write(keywdfile,*) trim('sqmprog=' // sqmprog)
c write(keywdfile,*) trim('store=' // store)
write(keywdfile,*) trim('subminp=' // subminp) !HB
write(keywdfile,*) trim('symm=' // symm)
write(keywdfile,*) trim('talg=' // talg)
write(keywdfile,*) trim('temp=' // temp)
write(keywdfile,*) trim('test=' // test)
write(keywdfile,*) trim('theodore=' // theodore)
write(keywdfile,*) trim('tlmo=' // tlmo)
write(keywdfile,*) trim('tpao=' // tpao)
write(keywdfile,*) trim('tprint=' // tprint)
cnp write(keywdfile,*) trim('tvirtcut=' // tvirtcut) !NP
write(keywdfile,*) trim('uncontract=' // uncontract)
write(keywdfile,*) trim('unit=' // unit)
write(keywdfile,*) trim('usedisk=' // usedisk)
write(keywdfile,*) trim('verbosity=' // verbosity)
write(keywdfile,*) trim('wpairtol=' // wpairtol)
C Print keyword to output
close(keywdfile)
write(iout,*) 'Keywords:'
write(iout,*)
call ishell('cat KEYWD')
C
return
end
C
************************************************************************
logical function ldftfunc(calc)
************************************************************************
* Check DFT functional names
************************************************************************
#if defined (LIBXC)
use xc_f03_lib_m
#endif
implicit none
character(len=32) calc
C
ldftfunc=
$ calc.eq.'lda '.or.
$ calc.eq.'b88 '.or.
$ calc.eq.'pbex '.or.
$ calc.eq.'pw91x '.or.
$ calc.eq.'lyp '.or.
$ calc.eq.'vwn5 '.or.
$ calc.eq.'pw '.or.
$ calc.eq.'p86 '.or.
$ calc.eq.'pbec '.or.
$ calc.eq.'pw91c '.or.
$ calc.eq.'blyp '.or.
$ calc.eq.'bhlyp '.or.
$ calc.eq.'b3lyp '.or.
$ calc.eq.'b3pw91 '.or.
$ calc.eq.'b3lyp3 '.or.
$ calc.eq.'b97 '.or.
$ calc.eq.'bp86 '.or.
$ calc.eq.'pbe '.or.
$ calc.eq.'pbe0 '.or.
$ calc.eq.'pw91 '.or.
$ calc.eq.'hcth120 '.or.
$ calc.eq.'hcth147 '.or.
$ calc.eq.'hcth407 '.or.
$ calc.eq.'ncap '.or.
$ calc.eq.'rs-pbe-pbe '.or.
$ calc.eq.'rs-b88-lyp '.or.
$ calc.eq.'rs-pbex-p86 '.or.
$ calc.eq.'rs-pw91-pw91 '
C
#if defined (LIBXC)
if(.not.ldftfunc) ldftfunc=
$ xc_f03_functional_get_number(calc).gt.0.or.
$ calc.eq.'m06-2x '.or.
$ calc.eq.'m06-hf '.or.
$ calc.eq.'m06-l '.or.
$ calc.eq.'m08-hx '.or.
$ calc.eq.'m08-so '.or.
$ calc.eq.'m11 '.or.
$ calc.eq.'mn12-sx '.or.
$ calc.eq.'mn15 '.or.
$ calc.eq.'wb97 '.or.
$ calc.eq.'wb97x '.or.
$ calc.eq.'wb97x-v '.or.
$ calc.eq.'b97m-v '.or.
$ calc.eq.'wb97m-v '.or.
$ calc.eq.'revtpss '.or.
$ calc.eq.'tpss '.or.
$ calc.eq.'revscan0 '.or.
$ calc.eq.'revscan '.or.
$ calc.eq.'scan0 '.or.
$ calc.eq.'scan '.or.
$ calc.eq.'hse06 '.or.
$ calc.eq.'lc-wpbe '.or.
$ calc.eq.'cam-b3lyp '
#endif
C
return
end
C
************************************************************************
logical function dhdft(calc)
************************************************************************
* Check if a double-hybrid DFT computation is requested
************************************************************************
implicit none
character(len=32) calc
c
dhdft=trim(calc).eq.'b2plyp'.or.
$ trim(calc).eq.'b2gpplyp'.or.
$ trim(calc).eq.'dsdpbep86'.or.
$ trim(calc).eq.'dsdpbehb95'.or.
$ trim(calc).eq.'scan0-2'.or.
$ trim(calc).eq.'xyg3'.or.
$ trim(calc).eq.'rs-pbe-pbe'.or.
$ trim(calc).eq.'rs-b88-lyp'.or.
$ trim(calc).eq.'rs-pbe-p86'.or.
$ trim(calc).eq.'rs-pw91-pw91'.or.
$ trim(calc).eq.'rsdh'
return
end
C
************************************************************************
subroutine setedisp(calc1,edisp)
************************************************************************
* Set edisp='auto' if -D3 postfix is specified in the calc or dft keywords
************************************************************************
implicit none
character*1 calc1(*)
character*256 edisp
integer i
c
do i=1,30
if(calc1(i ).eq.'-'.and.
$ calc1(i+1).eq.'d'.and.
$ calc1(i+2).eq.'3') then
calc1(i:i+2)=' '
edisp='auto'
exit
endif
enddo
c
return
end
C
************************************************************************
subroutine setf12(calc1)
************************************************************************
* (F12*) -> -F12
************************************************************************
implicit none
character*1 calc1(*)
integer i
C
do i=1,24
if(calc1(i ).eq.'('.and.
$ calc1(i+1).eq.'f'.and.
$ calc1(i+2).eq.'1'.and.
$ calc1(i+3).eq.'2'.and.
$ calc1(i+4).eq.'*'.and.
$ calc1(i+5).eq.')') then
if((calc1(i+6).eq.'('.and.
c $ calc1(i+7).eq.'t'.and.
$ calc1(i+8).eq.')').or.
$ (calc1(i+6).eq.'('.and.
c $ calc1(i+7).eq.'t'.and.
$ calc1(i+8).eq.'+'.and.
$ calc1(i+9).eq.')')) then
calc1(i )='('
calc1(i+1)=calc1(i+7)
calc1(i+2)=')'
calc1(i+3)='-'
calc1(i+4)='f'
calc1(i+5)='1'
calc1(i+6)='2'
calc1(i+7)=' '
calc1(i+8)=' '
calc1(i+9)=' '
else
calc1(i )='-'
calc1(i+1)='f'
calc1(i+2)='1'
calc1(i+3)='2'
calc1(i+4)=' '
calc1(i+5)=' '
endif
exit
endif
enddo
C
return
end
C
************************************************************************
logical function linteger(string)
************************************************************************
* Check if string contains an integer
************************************************************************
implicit none
integer n,i
character string*(*)
C
linteger=.true.
i=0
do while(i.lt.len(string))
if(string(i+1:i+1).ne.' ') then
i=i+1
else
exit
endif
if(ichar(string(i:i)).lt.48.or.
$ ichar(string(i:i)).gt.57) linteger=.false.
enddo
if(i.eq.0) linteger=.false.
C
return
end
C
************************************************************************
subroutine check_oniom_externalsqm(minpfile,externalsqm)
************************************************************************
* Checks if an sqm or an mm method is specified for ONIOM.
* (the check is neccesary to use the oniom-pcm-infrastructure when
* one tries to utilize the built-in implicit solvation model of
* the external program, and not the pcmsolver library.)
************************************************************************
implicit none
integer minpfile
character*32 imet
logical externalsqm
read(minpfile,*)
read(minpfile,*) imet
call lowercase(imet,imet,32)
imet=trim(adjustl(imet))
if(imet.eq.'am1'.or.
$ imet.eq.'mndo'.or.
$ imet.eq.'mndod'.or.
$ imet.eq.'cis'.or.
$ imet.eq.'cisd'.or.
$ imet.eq.'cisdt'.or.
$ imet.eq.'pm3'.or.
$ imet.eq.'pm6'.or.
$ imet.eq.'pm6-d3'.or.
$ imet.eq.'pm6-dh+'.or.
$ imet.eq.'pm6-dh2'.or.
$ imet.eq.'pm6-dh2x'.or.
$ imet.eq.'pm6-d3h4'.or.
$ imet.eq.'pm6-d3h4x'.or.
$ imet.eq.'pm7'.or.
$ imet.eq.'pm7-ts'.or.
$ imet.eq.'rm1'.or.
$ imet.eq.'sqm'.or.
$ imet.eq.'gfn0-xtb'.or.
$ imet.eq.'gfn1-xtb'.or.
$ imet.eq.'gfn2-xtb'.or.
$ imet.eq.'gfn-ff') externalsqm=.true.
return
end
C
************************************************************************
subroutine setup_scfconv_parameters
$(minpfile,scf_conv,scflshift,scflshift_gaptol,scflshift_dtol,
$scflshift_end,scfdamp_mode,scfdamp,scfdamp_maxfact,
$scfdamp_minfact,scfdamp_dampstep,scfdamp_dtol,scfdamp_end,scfdiis,
$scfdiis_start,scfdiis_end,scfext,scfdiis_dtol,scfdiis_watch,
$scfdiis_step,scfdiis_wrange,scfdiis_wlimit,scfdiis_delmax,
$scfmaxit,qscf)
************************************************************************
* Setup scf converger parameters and seek for difficult cases
* tmol,mol, and zmat format is not checked !
************************************************************************
implicit none
integer minpfile,iatnum,ios,nentry,ientry,i
real*8 rscr
character*1 ch1
character*2 cscr2
character*4 scfdiis,scfext,scfmaxit,scfdiis_start,scfdiis_end
character*4 scfdiis_step,scfdiis_watch,scfdiis_wrange
character*4 scfdiis_wlimit,scfdiis_delmax
character*4 gval,scfdamp_end,scflshift_end
character*8 scflshift,scflshift_gaptol,scflshift_dtol
character*8 qscf
character*12 scfdiis_dtol,scf_conv
character*16 scfdamp_mode,scfdamp,scfdamp_dtol
character*16 scfdamp_dampstep,scfdamp_minfact,scfdamp_maxfact
logical atnumread
atnumread=.false.
if(scf_conv.eq.'auto ') then
! Check atoms
call getkeym('geom',4,gval,4)
if(gval.eq.'zmat') then
cscr2='xx'
read(minpfile,'(a)',iostat=ios) ch1
backspace(minpfile)
i=ichar(ch1)
if(i.ge.49.and.i.le.57) atnumread=.true.
do
read(minpfile,'(a)',iostat=ios) cscr2
if(cscr2.eq.' ') exit
cscr2=trim(adjustl(cscr2))
iatnum=0
if(.not.atnumread) then
call getatnum(cscr2,iatnum)
else
read(cscr2,*) iatnum
endif
! If a transition metal or a lanthanoide/actinoide is found, then initiate 'difficult' scf convergence parameters
if((iatnum.ge.21 .and.iatnum.le.30 ).or.
$ (iatnum.ge.39 .and.iatnum.le.48 ).or.
$ (iatnum.ge.72 .and.iatnum.le.80 ).or.
$ (iatnum.ge.57 .and.iatnum.le.71 ).or.
$ (iatnum.ge.89 .and.iatnum.le.103)
$ ) then
scf_conv='difficult '
exit
endif
if(ios.lt.0) exit
enddo
else if(gval.eq.'xyz '.or.gval.eq.'tmol'.or.gval.eq.'mol ') then
read(minpfile,*) nentry
if(gval.eq.'xyz '.or.gval.eq.'tmol') read(minpfile,*)
if(gval.eq.'xyz ') then
read(minpfile,*) ch1
else
read(minpfile,*) rscr,rscr,rscr,ch1
endif
backspace(minpfile)
i=ichar(ch1)
if(i.ge.49.and.i.le.57) atnumread=.true.
do ientry=1,nentry
if(gval.eq.'xyz ') then
read(minpfile,*) cscr2
else
read(minpfile,*) rscr,rscr,rscr,cscr2
endif
iatnum=0
if(.not.atnumread) then
call getatnum(cscr2,iatnum)
else
read(cscr2,*) iatnum
endif
if((iatnum.ge.21 .and.iatnum.le.30 ).or.
$ (iatnum.ge.39 .and.iatnum.le.48 ).or.
$ (iatnum.ge.72 .and.iatnum.le.80 ).or.
$ (iatnum.ge.57 .and.iatnum.le.71 ).or.
$ (iatnum.ge.89 .and.iatnum.le.103)
$ ) then
scf_conv='difficult '
exit
endif
enddo
endif
endif
if(.false.) then
if(scf_conv.eq.'auto ') scf_conv='normal '
if(scf_conv.eq.'difficult ') then
scfdiis_start='2 '
scfdamp_mode='1 '
scfdamp='0.70d0 '
scfdamp_end='3 '
scfdamp_dtol='0.0d0 '
scflshift='0.10 '
scflshift_gaptol='0.20 '
scflshift_dtol='0d0 '
scflshift_end='8 '
else if(scf_conv.eq.'normal ') then
scfdiis_start='2 '
scfext='10 '
scfdamp_mode='3 '
scfdamp='0.50d0 '
scfdamp_maxfact='0.90d0 '
scfdamp_minfact='0.10d0 '
scfdamp_dampstep='0.10d0 '
scfdamp_dtol='0.5d0 '
scflshift='0.10 '
scflshift_gaptol='0.10 '
scflshift_dtol='1d-2 '
endif
endif
return
end
C