TABLE OF CONTENTS


ABINIT/chkinp [ Functions ]

[ Top ] [ Functions ]

NAME

 chkinp

FUNCTION

 Check consistency of input data against itself.
 Please: use the alphabetic order
 Please: use the routines chkint_eq, chkint_ne, chkint_ge, chkint_le, and chkdpr

INPUTS

  dtsets(0:ndtset_alloc)=<type datafiles_type>contains all input variables
  iout=unit number for output file
  mpi_enregs(0:ndtset_alloc)=information about MPI parallelization
  ndtset=number of datasets
  ndtset_alloc=number of datasets, corrected for allocation of at least one data set.
  npsp=number of pseudopotentials
  pspheads(npsp)=<type pspheader_type>all the important information from the
   pseudopotential file header, as well as the psp file name
  comm: MPI communicator (MPI_COMM_WORLD)

OUTPUT

SOURCE

  79 subroutine chkinp(dtsets,iout,mpi_enregs,ndtset,ndtset_alloc,npsp,pspheads,comm)
  80 
  81 !Arguments ------------------------------------
  82 !scalars
  83  integer,intent(in) :: iout,ndtset,ndtset_alloc,npsp, comm
  84  type(MPI_type),intent(in) :: mpi_enregs(0:ndtset_alloc)
  85 !arrays
  86  type(dataset_type),intent(in) :: dtsets(0:ndtset_alloc)
  87  type(pspheader_type),intent(in) :: pspheads(npsp)
  88 
  89 !Local variables-------------------------------
  90 !scalars
  91  integer :: bantot,fixed_mismatch,ia,iatom,ib,iband,idtset,ierr,iexit,ii,iimage,ikpt,ilang,intimage,ierrgrp
  92  integer :: ipsp,isppol,isym,itypat,iz,jdtset,jj,kk,maxiatsph,maxidyn,minplowan_iatom,maxplowan_iatom
  93  integer :: mband,miniatsph,minidyn,mod10,mpierr,all_nprocs
  94  integer :: mu,natom,nfft,nfftdg,nkpt,nloc_mem,nlpawu
  95  integer :: nproc,nspden,nspinor,nsppol,optdriver,mismatch_fft_tnons,response
  96  integer :: fftalg,usepaw,usewvl
  97  integer :: ttoldfe,ttoldff,ttolrff,ttolvrs,ttolwfr
  98  logical :: twvl,allowed,berryflag
  99  logical :: wvlbigdft=.false.
 100  logical :: xc_is_lda,xc_is_gga,xc_is_mgga,xc_is_hybrid,xc_is_tb09,xc_need_kden
 101  real(dp) :: dz,sumalch,summix,sumocc,ucvol,wvl_hgrid,zatom
 102  character(len=1000) :: msg
 103  type(dataset_type) :: dt
 104 !arrays
 105  integer :: cond_values(4),nprojmax(0:3)
 106  integer :: gpu_devices(12)=(/-2,-2,-2,-2,-2,-2,-2,-2,-2,-2,-2,-2/)
 107  integer,allocatable :: ierr_dtset(:)
 108  real(dp) :: gmet(3,3),gprimd(3,3),rmet(3,3),rprimd(3,3)
 109  real(dp),allocatable :: frac(:,:),tnons_new(:,:),xred(:,:)
 110  character(len=32) :: cond_string(4)
 111  character(len=32) :: input_name
 112  type(libxc_functional_type) :: xcfunc(2)
 113 
 114 ! *************************************************************************
 115 
 116  DBG_ENTER("COLL")
 117 
 118  all_nprocs = xmpi_comm_size(comm)
 119 
 120 !Some initialisations
 121  cond_string(1:4)='#####'
 122  cond_values(1:4)=(/0,0,0,0/)
 123  ABI_MALLOC(ierr_dtset,(ndtset_alloc))
 124  ierr_dtset=0
 125 
 126 !Do loop on idtset (allocate statements are present)
 127  do idtset=1,ndtset_alloc
 128    if(mpi_enregs(idtset)%me<0) cycle
 129    jdtset=dtsets(idtset)%jdtset
 130    if(ndtset==0)jdtset=0
 131    ierr=0
 132 
 133    if(jdtset/=0)then
 134      write(msg, '(a,a,a,i4,a)' ) ch10,' chkinp: Checking input parameters for consistency,',' jdtset=',jdtset,'.'
 135    else
 136      write(msg, '(a,a)' ) ch10,' chkinp: Checking input parameters for consistency.'
 137    end if
 138    call wrtout(iout,msg)
 139    call wrtout(std_out,msg)
 140 
 141    ! Will test directly on the dataset "dt"
 142    dt = dtsets(idtset)%copy()
 143 
 144    ! Copy or initialize locally a few input dataset values
 145    fftalg   =dt%ngfft(7)
 146    !fftalga  =fftalg/100; fftalgc=mod(fftalg,10)
 147    natom    =dt%natom
 148    nkpt     =dt%nkpt
 149    nspden   =dt%nspden
 150    nspinor  =dt%nspinor
 151    nsppol   =dt%nsppol
 152    optdriver=dt%optdriver
 153    usepaw   =dt%usepaw
 154    usewvl   =dt%usewvl
 155    intimage=1 ; if(dtsets(idtset)%nimage>2)intimage=2
 156    rprimd(:,:)=dtsets(idtset)%rprimd_orig(:,:,intimage)    ! For the purpose of checking symmetries
 157    response=0
 158    if(dt%rfelfd/=0.or.dt%rfphon/=0.or.dt%rfstrs/=0.or.dt%rfddk/=0.or.dt%rfuser/=0 &
 159 &   .or.dt%rf2_dkdk/=0.or.dt%rf2_dkde/=0.or.dt%rfmagn/=0.or.dt%d3e_pert1_elfd/=0 &
 160 &   .or.dt%d3e_pert2_elfd/=0.or.dt%d3e_pert3_elfd/=0.or.dt%d3e_pert1_phon/=0 &
 161 &   .or.dt%d3e_pert2_phon/=0.or.dt%d3e_pert3_phon/=0) response=1
 162    call metric(gmet,gprimd,-1,rmet,rprimd,ucvol)
 163    nproc=mpi_enregs(idtset)%nproc
 164 
 165 !  Some properties of the XC functional
 166    if (dt%ixc>=0) then
 167      xc_is_lda=((dt%ixc>=1.and.dt%ixc<=10).or.dt%ixc==50)
 168      xc_is_gga=((dt%ixc>=11.and.dt%ixc<=16).or.(dt%ixc>=23.and.dt%ixc<=39))
 169      xc_is_mgga=(dt%ixc>=31.and.dt%ixc<=35)
 170      xc_is_tb09=.false.
 171      xc_is_hybrid=(dt%ixc==40.or.dt%ixc==41.or.dt%ixc==42)
 172      xc_need_kden=(dt%ixc==31.or.dt%ixc==34.or.dt%ixc==35)
 173    else
 174      call libxc_functionals_init(dt%ixc,nspden,xc_functionals=xcfunc,xc_tb09_c=dt%xc_tb09_c)
 175      xc_is_lda=libxc_functionals_islda(xc_functionals=xcfunc)
 176      xc_is_gga=libxc_functionals_isgga(xc_functionals=xcfunc)
 177      xc_is_mgga=libxc_functionals_ismgga(xc_functionals=xcfunc)
 178      xc_is_tb09=libxc_functionals_is_tb09(xc_functionals=xcfunc)
 179      xc_is_hybrid=libxc_functionals_is_hybrid(xc_functionals=xcfunc)
 180      xc_need_kden=xc_is_mgga  ! We shoud discriminate with Laplacian based mGGa functionals
 181      call libxc_functionals_end(xc_functionals=xcfunc)
 182    end if
 183 
 184 !  =====================================================================================================
 185 !  Check the values of variables, using alphabetical order
 186 !  PLEASE: use the routines chkint_eq, chkint_ne, chkint_ge, chkint_le, chkdpr
 187 
 188     !  iomode Must be one of 0, 1, 3
 189    call chkint_eq(0,0,cond_string,cond_values,ierr,'iomode',dt%iomode,3, [IO_MODE_FORTRAN,IO_MODE_MPI,IO_MODE_ETSF],iout)
 190 !  However, if mpi_io is not enabled, must be one of 0, 3.
 191    if(xmpi_mpiio==0)then
 192      cond_string(1)='enable_mpi_io' ;  cond_values(1)=0
 193 !    Make sure that iomode is 0 or 3
 194      call chkint_eq(1,1,cond_string,cond_values,ierr,'iomode',dt%iomode,2,[IO_MODE_FORTRAN,IO_MODE_ETSF],iout)
 195    end if
 196    if (dt%iomode == IO_MODE_NETCDF .and. dt%npspinor == 2) then
 197      ABI_ERROR_NOSTOP("npspinor == 2 not compatible with netcdf", ierr)
 198    end if
 199 
 200 !  accuracy
 201    call chkint_eq(0,0,cond_string,cond_values,ierr,'accuracy',dt%accuracy,7,(/0,1,2,3,4,5,6/),iout)
 202 
 203 !  adpimd
 204    call chkint_eq(0,0,cond_string,cond_values,ierr,'accuracy',dt%adpimd,2,(/0,1/),iout)
 205 
 206 !  amu Check that atomic masses are > 0 if ionmov = 1
 207    do iimage=1,dt%nimage
 208      if (dt%ionmov==1) then
 209        do itypat=1,dt%ntypat
 210          cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
 211          write(input_name,'(a4,i2,a1,i2,a1)')'amu(',itypat,',',iimage,')'
 212          call chkdpr(1,1,cond_string,cond_values,ierr,input_name,dt%amu_orig(itypat,iimage),1,tol8,iout)
 213        end do
 214      end if
 215    end do
 216 
 217 !  autoparal
 218    call chkint_eq(0,0,cond_string,cond_values,ierr,'autoparal',dt%autoparal,5,(/0,1,2,3,4/),iout)
 219    if(dt%chkparal/=0.and.(dt%autoparal/=0.and.dt%optdriver/=RUNL_GSTATE)) then
 220        cond_string(1)='optdriver' ; cond_values(1)=dt%optdriver
 221        cond_string(2)='chkparal' ; cond_values(2)=dt%chkparal
 222        call chkint_eq(2,2,cond_string,cond_values,ierr,'autoparal',dt%autoparal,1,(/0/),iout)
 223    end if
 224 
 225 !  auxc_scal
 226    call chkdpr(0,0,cond_string,cond_values,ierr,'auxc_scal',dt%auxc_scal,1,0.0_dp,iout)
 227 
 228 !  bdberry
 229    if(dt%berryopt>0.and.dt%nberry>0.and.&
 230       dt%berryopt/= 4.and.dt%berryopt/= 6.and.dt%berryopt/= 7.and.&
 231       dt%berryopt/=14.and.dt%berryopt/=16.and.dt%berryopt/=17) then
 232      do ii=1,2*nsppol
 233        cond_string(1)='berryopt' ; cond_values(1)=dt%berryopt
 234        cond_string(2)='nberry'   ; cond_values(2)=dt%nberry
 235        write(input_name,'(a4,i1,a1)')'bdberry(',ii,')'
 236        call chkint_ge(2,2,cond_string,cond_values,ierr,input_name,dt%bdberry(ii),1,iout)
 237      end do
 238 !    bdberry(2) must be greater than bdberry(1)
 239      cond_string(1)='berryopt' ; cond_values(1)=dt%berryopt
 240      cond_string(2)='nberry'   ; cond_values(2)=dt%nberry
 241      cond_string(3)='bdberry(1)'   ; cond_values(3)=dt%bdberry(1)
 242      call chkint_ge(3,3,cond_string,cond_values,ierr,'bdberry(2)',dt%bdberry(2),dt%bdberry(1),iout)
 243      if(nsppol==2)then
 244 !      bdberry(4) must be greater than bdberry(3)
 245        cond_string(1)='berryopt' ; cond_values(1)=dt%berryopt
 246        cond_string(2)='nberry'   ; cond_values(2)=dt%nberry
 247        cond_string(3)='bdberry(3)'   ; cond_values(3)=dt%bdberry(3)
 248        call chkint_ge(3,3,cond_string,cond_values,ierr,'bdberry(4)',dt%bdberry(4),dt%bdberry(3),iout)
 249      end if
 250 !    Make sure all nband(nkpt) are >= bdberry
 251      do isppol=1,nsppol
 252        do ikpt=1,nkpt
 253          if (dt%nband(ikpt+(isppol-1)*nkpt)<=dt%bdberry(2*isppol)) then
 254            cond_string(1)='ikpt'   ; cond_values(1)=ikpt
 255            cond_string(2)='isppol' ; cond_values(2)=isppol
 256            cond_string(3)='nband'  ; cond_values(3)=dt%nband(ikpt+(isppol-1)*nkpt)
 257            call chkint_le(0,3,cond_string,cond_values,ierr,&
 258              'bdberry',dt%bdberry(2*isppol),dt%nband(ikpt+(isppol-1)*nkpt),iout)
 259            if(ierr==1)exit
 260          end if
 261        end do
 262      end do
 263    end if
 264 
 265 !  berryopt
 266 !  berryopt must be between -3 to +4, 6,7,14,16,17
 267    call chkint_eq(0,0,cond_string,cond_values,ierr,'berryopt',dt%berryopt,13,(/-3,-2,-1,0,1,2,3,4,6,7,14,16,17/),iout)
 268 !  berryopt must be positive when mkmem==0
 269    if(dt%mkmem==0)then
 270      cond_string(1)='mkmem' ; cond_values(1)=dt%mkmem
 271      call chkint_ge(1,1,cond_string,cond_values,ierr,'berryopt',dt%berryopt,0,iout)
 272    end if
 273 !  berryopt must be positive when occopt/=1
 274    if(dt%occopt/=1)then
 275      cond_string(1)='occopt' ; cond_values(1)=dt%occopt
 276      call chkint_ge(1,1,cond_string,cond_values,ierr,'berryopt',dt%berryopt,0,iout)
 277    end if
 278 !  berryopt cannot be 4,6,7,14,16,17 when toldfe, tolvrs, toldff and tolrff are zero (or negative)
 279    if (any(dt%berryopt== [4,6,7,14,16,17] ) ) then
 280      cond_string(1)='berryopt' ; cond_values(1)=dt%berryopt
 281      call chkdpr(1,1,cond_string,cond_values,ierr,'max(toldfe,toldff,tolrff,tolvrs)',&
 282 &      max(dt%toldfe,dt%toldff,dt%tolrff,dt%tolvrs),1,tol16*tol16,iout)
 283    endif
 284 !  Non-zero berryopt and usepaw==1 cannot be done unless response==0
 285    if (usepaw==1.and.dt%berryopt/=0) then
 286      cond_string(1)='usepaw' ; cond_values(1)=usepaw
 287      cond_string(2)='berryopt' ; cond_values(2)=dt%berryopt
 288      call chkint_eq(1,2,cond_string,cond_values,ierr,'response',response,1,(/0/),iout)
 289    end if
 290 !  Non-zero berryopt and usepaw==1 and kptopt/=3 cannot be done unless symmorphi=0
 291 !  (that is, nonsymmorphic symmetries do not work yet
 292 !  Update MT 2017-05-31: nonsymmorphic symmetries seem also to be an issue for NCPP
 293    if (usepaw==1.and.dt%berryopt/=0.and.dt%kptopt/=3) then
 294   !if (dt%berryopt/=0.and.dt%kptopt/=3) then
 295      cond_string(1)='usepaw'; cond_values(1)=usepaw
 296      cond_string(2)='berryopt'; cond_values(2)=dt%berryopt
 297      cond_string(3)='kptopt'; cond_values(3)=dt%kptopt
 298      call chkint_eq(1,3,cond_string,cond_values,ierr,'symmorphi',dt%symmorphi,1,(/0/),iout)
 299    end if
 300 !  Restrictions for berryopt=4,6,7,14,16,17
 301    if (usepaw==1.and.&
 302       (dt%berryopt== 4.or.dt%berryopt== 6.or.dt%berryopt== 7.or.&
 303        dt%berryopt==14.or.dt%berryopt==16.or.dt%berryopt==17)) then
 304 !     if (nsppol==2.and.nproc>1) then
 305 !       write(msg,'(3a)') &
 306 !&       'For berryopt = 4,6,7,14,16,17 and nsppol=2, nproc must = 1 ',ch10,&
 307 !&       'Action: change number of processes'
 308 !       ABI_ERROR_NOSTOP(msg, ierr)
 309 !     end if
 310    end if
 311 !  Non-zero berryopt and usepaw==1 and kpt // requires nproc to be a divisor of nkpt
 312    if (usepaw==1.and.dt%berryopt/=0.and.nproc>1.and.mod(dt%nkpt,nproc)/=0) then
 313      write(msg, '(3a)' )&
 314       'For berryopt /= 0 with PAW in parallel, nproc must be a divisor of nkpt ',ch10,&
 315       'Action: change number of processes or kpts such that nproc divides nkpt evenly'
 316      ABI_ERROR_NOSTOP(msg, ierr)
 317    end if
 318 
 319 !  Finite electric/displacement field checks
 320    if (dt%berryopt==4) then
 321      if (maxval(abs(dt%dfield(1:3)))>tiny(0.0_dp).or.&
 322          maxval(abs(dt%red_dfield(1:3)))>tiny(0.0_dp).or.&
 323          maxval(abs(dt%red_efield(1:3)))>tiny(0.0_dp).or.&
 324          maxval(abs(dt%red_efieldbar(1:3)))>tiny(0.0_dp)) then
 325        write(msg,'(5a)' ) &
 326         'When berryopt==4, only efield is needed, other input field',ch10,&
 327         '(dfield,red_dfield,red_efield,red_efieldbar) should be zero.',ch10,&
 328         'Action: delete unneeded field in input file.'
 329        ABI_ERROR_NOSTOP(msg, ierr)
 330      end if
 331    end if
 332    if (dt%berryopt==14) then
 333      if (maxval(abs(dt%dfield(1:3)))>tiny(0.0_dp).or.&
 334          maxval(abs(dt%red_dfield(1:3)))>tiny(0.0_dp).or.&
 335          maxval(abs(dt%red_efield(1:3)))>tiny(0.0_dp).or.&
 336          maxval(abs(dt%efield(1:3)))>tiny(0.0_dp)) then
 337        write(msg,'(5a)') &
 338         'When berryopt==14, only red_efieldbar is needed, other input field',ch10,&
 339         '(dfield,red_dfield,efield,red_efield) should be zero.',ch10,&
 340         'Action: delete unneeded field in input file.'
 341        ABI_ERROR_NOSTOP(msg, ierr)
 342      end if
 343    end if
 344    if (dt%berryopt==6) then
 345      if (maxval(abs(dt%red_dfield(1:3)))>tiny(0.0_dp).or.&
 346          maxval(abs(dt%red_efield(1:3)))>tiny(0.0_dp).or.&
 347          maxval(abs(dt%red_efieldbar(1:3)))>tiny(0.0_dp)) then
 348        write(msg,'(5a)') &
 349          'When berryopt==6, only dfield and efield are needed, other input field',ch10,&
 350          '(red_dfield,red_efield,red_efieldbar) should be zero.',ch10,&
 351          'Action: delete unneeded field in input file.'
 352        ABI_ERROR_NOSTOP(msg, ierr)
 353      end if
 354    end if
 355    if (dt%berryopt==16) then
 356      if (maxval(abs(dt%dfield(1:3)))>tiny(0.0_dp).or.&
 357          maxval(abs(dt%efield(1:3)))>tiny(0.0_dp).or.&
 358          maxval(abs(dt%red_efieldbar(1:3)))>tiny(0.0_dp)) then
 359        write(msg,'(5a)')  &
 360          'When berryopt==16, only red_dfield and red_efield are needed, other input field',ch10,&
 361          '(dfield,efield,red_efieldbar) should be zero.',ch10,&
 362          'Action: delete unneeded field in input file.'
 363        ABI_ERROR_NOSTOP(msg, ierr)
 364      end if
 365    end if
 366    if (dt%berryopt==17) then
 367      if (maxval(abs(dt%dfield(1:3)))>tiny(0.0_dp).or.&
 368          maxval(abs(dt%efield(1:3)))>tiny(0.0_dp).or.&
 369          maxval(abs(dt%red_efield(1:3)))>tiny(0.0_dp)) then
 370        write(msg,'(5a)') &
 371         'When berryopt==17, only red_dfield and red_efieldbar are needed, other input field',ch10,&
 372         '(dfield,efield,red_efield) should be zero.',ch10,&
 373         'Action: delete unneeded field in input file.'
 374         ABI_ERROR_NOSTOP(msg, ierr)
 375      end if
 376      if ((dt%jfielddir(1)/=1.and.dt%jfielddir(1)/=2).or.&
 377          (dt%jfielddir(2)/=1.and.dt%jfielddir(2)/=2).or.&
 378          (dt%jfielddir(3)/=1 .and.dt%jfielddir(3)/=2)) then
 379        write(msg,'(5a)') &
 380         'When berryopt==17, jfielddir can only be 1 or 2 to controls whether reduced electric field',ch10,&
 381         '(jfielddir=1) or reduced electric displacement field (jfielddir=2) is chosen to be fixed', ch10,&
 382         'Action: change jfielddir to be 1 or 2 in input file.'
 383        ABI_ERROR_NOSTOP(msg, ierr)
 384      end if
 385    end if
 386 
 387 !  berrystep
 388    call chkint_ge(0,0,cond_string,cond_values,ierr,'berrystep',dt%berrystep,1,iout)
 389    if(nproc>1)then
 390      cond_string(1)='nproc'; cond_values(1)=mpi_enregs(idtset)%nproc
 391      call chkint_eq(1,1,cond_string,cond_values,ierr,'berrystep',dt%berrystep,1,(/1/),iout)
 392    end if
 393 
 394 !  boxcutmin
 395    call chkdpr(0,0,cond_string,cond_values,ierr,'dilatmx',dt%dilatmx,1,zero,iout)
 396 !  if(response==1)then
 397 !    cond_string(1)='response' ; cond_values(1)=response
 398 !    call chkdpr(1,1,cond_string,cond_values,ierr,'boxcutmin',dt%boxcutmin,1,two,iout)
 399 !  end if
 400 
 401 !  builtintest
 402    call chkint_eq(0,0,cond_string,cond_values,ierr,'builtintest',dt%builtintest,8,(/0,1,2,3,4,5,6,7/),iout)
 403 
 404 !  cellcharge
 405 !  The value  of cellcharge cannot change between images, except when imgmov=6 and (occopt=0 or occopt=2)
 406    if(dt%imgmov/=6 .or. (dt%occopt/=0 .and. dt%occopt/=2))then
 407      do iimage=1,dt%nimage
 408        if(abs(dt%cellcharge(iimage)-dt%cellcharge(1))>tol8)then
 409          write(msg, '(2a,i4,a,i4,2a,es12.4,a,i4,es12.4)' )ch10,&
 410 &         ' chkinp : imgmov=',dt%imgmov,', occopt=',dt%occopt,ch10,&
 411 &         ' chkinp : cellcharge(1)=',dt%cellcharge(1),', while for image=',iimage,', cellcharge=',dt%cellcharge(iimage)
 412          call wrtout(iout,msg)
 413          call wrtout(std_out,  msg)
 414          write(msg, '(a,i4,2a,i4,2a,f8.2,4a)' )&
 415           ' This is not allowed : cellcharge is allowed to vary only when imgmov=6 and occopt=0 or 2.',ch10,&
 416 &         ' Action: check the content of the input variables cellcharge, imgmov anf occopt.'
 417          ABI_ERROR_NOSTOP(msg, ierr)
 418        end if
 419      end do
 420    end if
 421 
 422 !  chkdilatmx
 423    call chkint_eq(0,0,cond_string,cond_values,ierr,'chkdilatmx',dt%chkdilatmx,2,(/0,1/),iout)
 424 
 425 !  chkparal
 426    call chkint_eq(0,0,cond_string,cond_values,ierr,'chkparal',dt%chkparal,2,(/0,1/),iout)
 427 
 428 !  chksymbreak
 429    call chkint_eq(0,0,cond_string,cond_values,ierr,'chksymbreak',dt%chksymbreak,2,(/0,1/),iout)
 430 
 431 !  chksymtnons
 432    call chkint_eq(0,0,cond_string,cond_values,ierr,'chksymtnons',dt%chksymtnons,4,(/0,1,2,3/),iout)
 433 
 434    if(dt%chksymtnons>0)then
 435 !    Check the values of tnons
 436      ABI_MALLOC(tnons_new,(3,dt%nsym))
 437      ABI_MALLOC(xred,(3,dt%natom))
 438      xred(:,:)=dt%xred_orig(:,1:dt%natom,1)
 439 !    Use the largest significant value of tolsym, namely, one.
 440      call symmetrize_xred(dt%natom,dt%nsym,dt%symrel,dt%tnons,xred,&
 441 &      fixed_mismatch=fixed_mismatch,mismatch_fft_tnons=mismatch_fft_tnons,tnons_new=tnons_new,tolsym=one)
 442      ABI_FREE(tnons_new)
 443 
 444      if(mismatch_fft_tnons/=0)then
 445        if(fixed_mismatch==1)then
 446          write(msg, '(2a)' ) ch10,' chkinp: COMMENT -'
 447          call wrtout(std_out,msg)
 448          write(msg, '(4a,3es20.10)' )  &
 449 &          '   Found potentially symmetry-breaking value of tnons (see input variable chksymtnons). ', ch10,&
 450 &          '   The following shift of all reduced symmetry-corrected atomic positions might possibly remove this problem:',ch10,&
 451 &          xred(:,1)-dt%xred_orig(:,1,1)
 452          call wrtout(std_out,msg)
 453          call wrtout(iout,msg)
 454          write(msg, '(4a)' ) ch10,&
 455 &          '   For your convenience, you might cut+paste the shifted new atomic positions (for image 1 only):',ch10,&
 456 &          '   xred'
 457          call wrtout(std_out,msg)
 458          call wrtout(iout,msg)
 459          do iatom=1,dt%natom
 460            write(msg,'(a,3es20.10)') '        ',xred(:,iatom)
 461            call wrtout(std_out,msg)
 462            call wrtout(iout,msg)
 463          enddo
 464          call wrtout(std_out,' ')
 465        endif
 466 
 467        if(dt%chksymtnons==1 .or. dt%chksymtnons==3)then
 468          write(msg, '(8a,i4,2a,9i3,2a,3es20.10,11a)' ) ch10,&
 469           ' chkinp: ERROR -',ch10,&
 470           '   Chksymtnons=1 or 3 . Found potentially symmetry-breaking value of tnons, ', ch10,&
 471           '   which is neither a rational fraction in 1/8th nor in 1/12th (1/9th and 1/10th are tolerated also) :', ch10,&
 472           '   for the symmetry number ',mismatch_fft_tnons,ch10,&
 473           '   symrel is ',dt%symrel(1:3,1:3,mismatch_fft_tnons),ch10,&
 474           '   tnons is ',dt%tnons(1:3,mismatch_fft_tnons),ch10,&
 475           '   So, your atomic positions are not aligned with the FFT grid.',ch10,&
 476           '   Please, read the description of the input variable chksymtnons.',ch10,&
 477           '   If you are planning cDFT, GW or BSE calculations, such tnons value is very problematic.',ch10,&
 478           '   Otherwise, you might set chksymtnons=0.',&
 479           '   But do not be surprised if ABINIT does not converge for cDFT, or crashes for GW or BSE.',ch10,&
 480           '   Better solution : you might shift your atomic positions to better align the FFT grid and the symmetry axes.'
 481          call wrtout(std_out,msg)
 482          if(fixed_mismatch==1)then
 483            call flush_unit(std_out)
 484            write(msg, '(a)' )&
 485 &          '   ABINIT has detected such a possible shift. See the suggestion given in the COMMENT above (or in output or log file).'
 486            call wrtout(std_out,msg)
 487          endif
 488          ierr=ierr+1 ! Previously a warning: for slab geometries arbitrary tnons can appear along the vacuum direction.
 489                      ! But then simply set chksymtnons=0 ...
 490        endif
 491      endif
 492      ABI_FREE(xred)
 493    end if
 494 
 495 !  constraint_kind
 496    do itypat=1,dt%ntypat
 497      cond_string(1)='itypat';cond_values(1)=itypat
 498      call chkint_eq(0,1,cond_string,cond_values,ierr,'constraint_kind',dt%constraint_kind(itypat),&
 499 &     10,(/0,1,2,3,4,10,11,12,13,14/),iout)
 500      !Only potential self-consistency is currently allowed with constrained_dft
 501      if (dt%iscf>10) then
 502        cond_string(1)='itypat';cond_values(1)=itypat
 503        cond_string(2)='iscf';cond_values(2)=dt%iscf
 504        call chkint_eq(2,2,cond_string,cond_values,ierr,'constraint_kind',dt%constraint_kind(itypat),1,(/0/),iout)
 505      endif
 506      if (dt%ionmov==4) then
 507        cond_string(1)='itypat';cond_values(1)=itypat
 508        cond_string(2)='ionmov';cond_values(2)=dt%ionmov
 509        call chkint_eq(2,2,cond_string,cond_values,ierr,'constraint_kind',dt%constraint_kind(itypat),1,(/0/),iout)
 510      endif
 511      if (dt%nspden==2) then
 512        cond_string(1)='itypat';cond_values(1)=itypat
 513        cond_string(2)='nspden';cond_values(2)=dt%nspden
 514        call chkint_eq(2,2,cond_string,cond_values,ierr,'constraint_kind',dt%constraint_kind(itypat),8,(/0,1,2,3,10,11,12,13/),iout)
 515      endif
 516      if (dt%chksymtnons==1 .or. dt%chksymtnons==2) then
 517        cond_string(1)='itypat';cond_values(1)=itypat
 518        cond_string(2)='chksymtnons';cond_values(2)=dt%chksymtnons
 519        call chkint_eq(2,2,cond_string,cond_values,ierr,'constraint_kind',dt%constraint_kind(itypat),1,(/0/),iout)
 520      endif
 521 
 522    enddo
 523 
 524 !  d3e_pert1_atpol
 525    call chkint_ge(0,0,cond_string,cond_values,ierr,'d3e_pert1_atpol(1)',dt%d3e_pert1_atpol(1),1,iout)
 526    cond_string(1)='natom' ; cond_values(1)=natom
 527    call chkint_le(1,1,cond_string,cond_values,ierr,'d3e_pert1_atpol(2)',dt%d3e_pert1_atpol(2),natom,iout)
 528 
 529 !  d3e_pert2_atpol
 530    call chkint_ge(0,0,cond_string,cond_values,ierr,'d3e_pert2_atpol(1)',dt%d3e_pert2_atpol(1),1,iout)
 531    cond_string(1)='natom' ; cond_values(1)=natom
 532    call chkint_le(1,1,cond_string,cond_values,ierr,'d3e_pert2_atpol(2)',dt%d3e_pert2_atpol(2),natom,iout)
 533 
 534 !  d3e_pert3_atpol
 535    call chkint_ge(0,0,cond_string,cond_values,ierr,'d3e_pert3_atpol(1)',dt%d3e_pert3_atpol(1),1,iout)
 536    cond_string(1)='natom' ; cond_values(1)=natom
 537    call chkint_le(1,1,cond_string,cond_values,ierr,'d3e_pert3_atpol(2)',dt%d3e_pert3_atpol(2),natom,iout)
 538 
 539 !  densfor_pred
 540    if(dt%iscf>0)then
 541      cond_string(1)='iscf';cond_values(1)=dt%iscf
 542      call chkint_le(0,1,cond_string,cond_values,ierr,'densfor_pred',dt%densfor_pred,6,iout)
 543      call chkint_ge(0,1,cond_string,cond_values,ierr,'densfor_pred',dt%densfor_pred,-6,iout)
 544      if (dt%densfor_pred<0.and.mod(dt%iprcel,100)>=61.and.(dt%iprcel<71.or.dt%iprcel>79)) then
 545        cond_string(1)='iscf';cond_values(1)=dt%iscf
 546        cond_string(2)='iprcel';cond_values(2)=dt%iprcel
 547        call chkint_ge(1,2,cond_string,cond_values,ierr,'densfor_pred',dt%densfor_pred,0,iout)
 548      end if
 549      ! densfor_pred<0 not valid for mGGA
 550      ! Yet it is but contribution from Laplacian and/or kin. ene. density are not taken into account
 551      !if(dt%densfor_pred<0.and.xc_is_mgga.and.dt%iscf>=10)then
 552      !  msg='densfor_pred<0 (full correction for forces) is not allowed for density mixing and meta-GGA XC!'
 553      !  ABI_ERROR_NOSTOP(msg, ierr)
 554      !end if
 555    end if
 556 
 557 !  diecut
 558    if(dt%iscf==-1)then
 559      cond_string(1)='iscf' ; cond_values(1)=dt%iscf
 560      cond_string(2)='4*ecut==diecut' ; cond_values(2)=0
 561 !    Checks that presently diecut is 4*ecut
 562      call chkdpr(1,2,cond_string,cond_values,ierr,'diecut',dt%diecut,0,4*dt%ecut,iout)
 563    end if
 564 
 565 !  diemac
 566    call chkdpr(0,0,cond_string,cond_values,ierr,'diemac',dt%diemac,1,0.01_dp,iout)
 567 
 568 !  dilatmx
 569    call chkdpr(0,0,cond_string,cond_values,ierr,'dilatmx',dt%dilatmx,1,zero,iout)
 570    if(dt%chkdilatmx==1)then
 571      cond_string(1)='chkdilatmx' ; cond_values(1)=dt%chkdilatmx
 572 !    Checks that presently chkdilatmx is smaller than 1.15
 573      call chkdpr(1,1,cond_string,cond_values,ierr,'dilatmx',dt%dilatmx,-1,1.15_dp,iout)
 574    end if
 575 
 576 !  dmatpuopt
 577    if (dt%usepawu>0) then
 578      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
 579      call chkint_eq(0,1,cond_string,cond_values,ierr,'dmatpuopt',dt%dmatpuopt,10,(/1,2,3,4,5,6,7,8,9,10/),iout)
 580    end if
 581 
 582 !  dmatudiag
 583    if (dt%usepawu>0) then
 584      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
 585      call chkint_eq(0,1,cond_string,cond_values,ierr,'dmatudiag',dt%dmatudiag,3,(/0,1,2/),iout)
 586    end if
 587 
 588 
 589 !  dmftbandi, dmftbandf
 590    if (dt%usedmft>0) then
 591      call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftcheck',dt%dmftcheck,4,(/-1,0,1,2/),iout)
 592      if(dt%dmftcheck/=-1) then
 593 
 594        cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
 595        call chkint_eq(1,1,cond_string,cond_values,ierr,'occopt',dt%occopt,1,(/3/),iout)
 596 
 597        call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftbandi',dt%dmftbandi,1,iout)
 598        call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftbandf',dt%dmftbandf,dt%dmftbandi,iout)
 599 
 600        cond_string(1)='mband' ; cond_values(1)=dt%mband
 601        call chkint_le(0,1,cond_string,cond_values,ierr,'dmftbandi',dt%dmftbandi,dt%mband,iout)
 602        call chkint_le(0,1,cond_string,cond_values,ierr,'dmftbandf',dt%dmftbandf,dt%mband,iout)
 603 
 604        cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
 605        call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_entropy',dt%dmft_entropy,0,iout)
 606        call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_iter',dt%dmft_iter,0,iout)
 607        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_kspectralfunc',dt%dmft_kspectralfunc,2,(/0,1/),iout)
 608 
 609        if(dt%dmft_kspectralfunc==1) then
 610          cond_string(1)='dmft_kspectralfunc' ; cond_values(1)=dt%dmft_kspectralfunc
 611          call chkint_eq(0,1,cond_string,cond_values,ierr,'iscf',dt%iscf,2,(/-2,-3/),iout)
 612        endif
 613 
 614        if((dt%dmft_solv<6.or.dt%dmft_solv>7).and.dt%ucrpa==0.and.dt%dmft_solv/=9) then
 615          cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
 616          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_nwlo',dt%dmft_nwlo,1,iout)
 617          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_nwli',dt%dmft_nwli,1,iout)
 618        end if
 619 
 620        cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
 621        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_read_occnd',dt%dmft_read_occnd,3,(/0,1,2/),iout)
 622        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_occnd_imag',dt%dmft_occnd_imag,2,(/0,1/),iout)
 623        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_rslf',dt%dmft_rslf,3,(/-1,0,1/),iout)
 624        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_mxsf',dt%dmft_mxsf,1,zero,iout)
 625        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_mxsf',dt%dmft_mxsf,-1,one,iout)
 626        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_solv',dt%dmft_solv,10,(/-2,-1,0,1,2,5,6,7,8,9/),iout)
 627        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_tolfreq',dt%dmft_tolfreq,-1,0.01_dp,iout)
 628        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_tollc',dt%dmft_tollc,-1,tol5,iout)
 629        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_charge_prec',dt%dmft_charge_prec,-1,tol4,iout)
 630        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_charge_prec',dt%dmft_charge_prec,1,tol20,iout)
 631        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_dc',dt%dmft_dc,5,(/0,1,2,5,6/),iout)
 632        if(dt%usepawu==14) then
 633          cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
 634          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_dc',dt%dmft_dc,2,(/5,6/),iout)
 635        endif
 636        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_wanorthnorm',dt%dmft_wanorthnorm,2,(/2,3/),iout)
 637        if(dt%getwfk==0.and.dt%irdwfk==0.and.dt%irdden==0.and.dt%getden==0.and.dt%ucrpa==0) then
 638          write(msg,'(3a,i3,a,i3,a,i3,a,i3,a)' )&
 639          'When usedmft==1, A WFK file or a DEN file have to be read. In the current calculation:',ch10, &
 640          '  getwfk =',dt%getwfk, &
 641          '  irdwfk =',dt%irdwfk, &
 642          '  getden =',dt%getden, &
 643          '  irdden =',dt%irdden, &
 644          '  Action: use a restart density or WFK file'
 645          if(dt%iscf>0) ABI_ERROR(msg)
 646        end if
 647        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_t2g',dt%dmft_t2g,2,(/0,1/),iout)
 648 !      call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_x2my2d',dt%dmft_x2my2d,2,(/0,1/),iout)
 649        if (dt%dmft_solv>=5.and.dt%ucrpa==0.and.dt%dmft_solv/=9) then
 650          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftqmc_l',dt%dmftqmc_l,1,iout)
 651          call chkdpr(0,1,cond_string,cond_values,ierr,'dmftqmc_n',dt%dmftqmc_n,1,one,iout)
 652          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftqmc_seed',dt%dmftqmc_seed,0,iout)
 653          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftqmc_therm',dt%dmftqmc_therm,1,iout)
 654        end if
 655 
 656        if (dt%dmft_solv>=5) then
 657          cond_string(1)='dmft_solv' ; cond_values(1)=dt%dmft_solv
 658          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_basis',dt%dmftctqmc_basis,3,(/0,1,2/),iout)
 659          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_check',dt%dmftctqmc_check,4,(/0,1,2,3/),iout)
 660          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_gmove',dt%dmftctqmc_gmove,0,iout)
 661          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_meas',dt%dmftctqmc_meas,1,iout)
 662 #if defined HAVE_TRIQS_v2_0 || defined HAVE_TRIQS_v1_4
 663          if (dt%dmft_solv==6.or.dt%dmft_solv==7.or.dt%dmft_solv==9) then
 664            call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftqmc_l',dt%dmftqmc_l,2*dt%dmft_nwli+1,iout)
 665            cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
 666            call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_triqs_nleg',dt%dmftctqmc_triqs_nleg,1,iout)
 667          end if
 668 #endif
 669 #if !defined HAVE_PYTHON_INVOCATION
 670          if (dt%dmft_solv==9) then
 671            write(msg,'(2a)')&
 672             'ABINIT must have been compiled with the flag enable_python_invocation="yes" in order to allow', &
 673             ' dmft_solv==9. You need to recompile ABINIT or change the value of dmft_solv.'
 674            ABI_ERROR(msg)
 675          end if
 676 #endif
 677        end if
 678 
 679        if (dt%dmft_solv==5) then
 680          cond_string(1)='dmft_solv' ; cond_values(1)=dt%dmft_solv
 681          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_correl',dt%dmftctqmc_correl,2,(/0,1/),iout)
 682          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_grnns',dt%dmftctqmc_grnns,2,(/0,1/),iout)
 683          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_mrka',dt%dmftctqmc_mrka,0,iout)
 684          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_mov',dt%dmftctqmc_mov,2,(/0,1/),iout)
 685          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_order',dt%dmftctqmc_order,0,iout)
 686          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_nwlo',dt%dmft_nwlo,2*dt%dmftqmc_l,iout)
 687        end if
 688        cond_string(1)='dmft_solv' ; cond_values(1)=dt%dmft_solv
 689        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_config',dt%dmftctqmc_config,4,(/0,1,2,3/),iout)
 690        if (dt%dmft_entropy>=1) then
 691          cond_string(1)='dmft_entropy' ; cond_values(1)=dt%dmft_entropy
 692          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_nlambda',dt%dmft_nlambda,3,iout)
 693          call chkint_le(0,1,cond_string,cond_values,ierr,'dmft_entropy',dt%dmft_entropy,dt%dmft_nlambda,iout)
 694          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_dc',dt%dmft_dc,1,(/1/),iout)
 695          if (dt%dmft_solv /= 5 ) then
 696            write(msg,'(3a,i3,a,i3,a,i3,a,i3,a)' )&
 697            'When dmft_entropy>=1, the impurity solver has to be currently  dmft_solv=5:',ch10, &
 698            'Action: change your dmft_solv input'
 699            ABI_ERROR(msg)
 700          end if
 701        end if
 702      end if
 703    end if
 704 
 705 #if !defined HAVE_TRIQS_v2_0 && !defined HAVE_TRIQS_v1_4
 706    if(dt%dmft_solv>=6.and.dt%dmft_solv<=7) then
 707      write(msg, '(a,a,a)' )&
 708      ' dmft_solv=6, or 7 is only relevant if the TRIQS library is linked',ch10,&
 709      ' Action: check compilation options'
 710      ABI_ERROR(msg)
 711    end if
 712 #endif
 713 
 714 !  dosdeltae
 715    call chkdpr(0,0,cond_string,cond_values,ierr,'dosdeltae',dt%dosdeltae,1,0.0_dp,iout)
 716 
 717 !  dynimage between 0 and 1
 718    maxidyn=maxval(dt%dynimage(:))
 719    minidyn=minval(dt%dynimage(:))
 720    call chkint_ge(0,0,cond_string,cond_values,ierr,'dynimage',minidyn,0,iout)
 721    call chkint_le(0,0,cond_string,cond_values,ierr,'dynimage',maxidyn,1,iout)
 722 
 723 !  ecut
 724 !  With planewaves, one must use positive ecut
 725    if(usewvl==0)then
 726      if (dt%ecut < tol2) then
 727        write(msg, '(3a)' )&
 728         'The input keyword "ecut" is compulsory !',ch10,&
 729         'Action: add a value for "ecut" in the input file.'
 730        ABI_ERROR_NOSTOP(msg, ierr)
 731      else
 732        cond_string(1)='usewvl' ; cond_values(1)=usewvl
 733        call chkdpr(1,1,cond_string,cond_values,ierr,'ecut',dt%ecut,1,tol8,iout)
 734      end if
 735    end if
 736 
 737 !  pawecutdg (placed here to stop before ngfftdg)
 738    if (usepaw==1) then
 739      if(usewvl==0) then
 740        call chkdpr(1,0,cond_string,cond_values,ierr,'pawecutdg',dt%pawecutdg,1,tol8,iout)
 741        cond_string(1)='pawecutdg>=ecut' ; cond_values(1)=0
 742        call chkdpr(1,1,cond_string,cond_values,ierr,'pawecutdg',dt%pawecutdg,1,dt%ecut,iout)
 743      else
 744        if(dt%pawecutdg > tol8) then
 745          ABI_ERROR('In PAW+WVL do not use pawecutdg')
 746        end if
 747      end if
 748    end if
 749 
 750 !  ecuteps
 751    if( ANY(optdriver == [RUNL_SCREENING]) )then
 752      call chkdpr(0,0,cond_string,cond_values,ierr,'ecuteps',dt%ecuteps,1,0.0_dp,iout)
 753      if (dt%ecuteps <= 0) then
 754        ABI_ERROR_NOSTOP("ecuteps must be > 0 if optdriver == 3", ierr)
 755      end if
 756      if(dt%fftgw<20 .and. dt%fftgw/=0)then
 757        if(dt%ecutwfn<dt%ecuteps-tol8)then
 758          write(msg,'(a,es16.6,a,es16.6,a,6a)')&
 759           'The values of ecutwfn and ecuteps are ', dt%ecutwfn,' and ',dt%ecuteps,ch10,&
 760           'With fftgw lower than 20, one expect ecuteps to be smaller or equal to ecutwfn.',ch10,&
 761           'Indeed, one is wasting memory without gaining CPU time or accuracy.',ch10,&
 762           'Action: use another value of fftgw (e.g. 21), or adjust ecutwfn with ecuteps.'
 763          ABI_ERROR_NOSTOP(msg, ierr)
 764        end if
 765      end if
 766    end if
 767 
 768 !  ecutsigx
 769 !  @MG FIXME reinstate this check, after having rewritten FFT treatment in GW
 770    if( ANY( optdriver == [RUNL_SIGMA] ) .and..FALSE.)then
 771      call chkdpr(0,0,cond_string,cond_values,ierr,'ecutsigx',dt%ecutsigx,1,0.0_dp,iout)
 772      if(dt%fftgw<20)then
 773        if(dt%ecutwfn<dt%ecutsigx-tol8)then
 774          write(msg,'(a,es16.6,a,es16.6,a,6a)')&
 775           'The values of ecutwfn and ecutsigx are ', dt%ecutwfn,' and ',dt%ecutsigx,ch10,&
 776           'With fftgw lower than 20, one expect ecutsigx to be smaller or equal to ecutwfn.',ch10,&
 777           'Indeed, one is wasting memory without gaining CPU time or accuracy.',ch10,&
 778           'Action: use another value of fftgw (e.g. 21), or adjust ecutwfn with ecutsigx.'
 779          ABI_ERROR_NOSTOP(msg, ierr)
 780        end if
 781      end if
 782    end if
 783 
 784    if ( optdriver == RUNL_BSE) then
 785      ! Check for BSE calculations that are not implemented.
 786      if (dt%nspinor == 2) then
 787        ABI_ERROR_NOSTOP("BSE with nspinor 2 not implemented", ierr)
 788      end if
 789    end if
 790 
 791 !  ecutsigx
 792 
 793    ! Check for GW calculations that are not implemented.
 794    if (ANY(optdriver == [RUNL_SCREENING, RUNL_SIGMA])) then
 795      if (dt%nspinor == 2) then
 796        if (dt%usepaw == 1) then
 797          ABI_ERROR_NOSTOP("GW with PAW and nspinor 2 not implemented", ierr)
 798        end if
 799        !if (optdriver == RUNL_SCREENING .and. dt%symchi == 1) then
 800        !  ABI_ERROR_NOSTOP("Screening with symchi 1 and nspinor 2 not implemented", ierr)
 801        !end if
 802        !if (optdriver == RUNL_SIGMA .and. dt%symsigma == 1) then
 803        !  ABI_ERROR_NOSTOP("Self-energy with symsigma 1 and nspinor 2 not implemented", ierr)
 804        !end if
 805        if (optdriver == RUNL_SIGMA .and. &
 806            any(mod(dt%gwcalctyp, 10) == [SIG_GW_AC, SIG_QPGW_PPM, SIG_QPGW_CD])) then
 807          ABI_ERROR_NOSTOP("analytic-continuation, model GW with nspinor 2 are not implemented", ierr)
 808        end if
 809        !if (optdriver == RUNL_SIGMA .and. mod(dt%gwcalctyp, 100) >= 10) then
 810        !  ABI_ERROR_NOSTOP("Self-consistent GW with nspinor == 2 not implemented", ierr)
 811        !end if
 812        if (optdriver == RUNL_SIGMA .and. dt%symsigma > 0 .and. dt%gwcalctyp >= 20) then
 813          ABI_ERROR_NOSTOP("gwcalctyp >= 0 requires symsigma == 0 in input. New default in Abinit9 is symsigma 1!", ierr)
 814        end if
 815        if (optdriver == RUNL_SIGMA .and. dt%symsigma > 0 .and. dt%ucrpa > 0) then
 816          ABI_ERROR_NOSTOP("ucrpa requires symsigma == 0 in input. New default in Abinit9 is symsigma 1!", ierr)
 817        end if
 818        if (dt%gwcomp /= 0) then
 819          ABI_ERROR_NOSTOP("gwcomp /= 0 with nspinor 2 not implemented", ierr)
 820        end if
 821      end if ! nspinor 2
 822 
 823      if (maxval(abs(dt%istwfk(1:nkpt))) > 1 .and. mod(dt%gwcalctyp, 100) >= 20) then
 824        write(msg, "(3a)")"Self-consistent GW with istwfk > 1 not supported.",ch10, &
 825        "Please regenerate your WFK file with istwfk *1"
 826        ABI_ERROR_NOSTOP(msg, ierr)
 827      end if
 828 
 829      ! Avoid wasting CPUs if nsppol==2.
 830      if (dt%nsppol == 2 .and. .not. iseven(nproc) .and. nproc > 1) then
 831        write(msg,'(3a)') "Spin-polarized GW calculations should be run with an even number of processors ",ch10,&
 832         " for achieving an optimal distribution of memory and CPU load. Please change the number of processors."
 833        ABI_ERROR_NOSTOP(msg, ierr)
 834      end if
 835    end if
 836 
 837 !  ecutsm
 838    call chkdpr(0,0,cond_string,cond_values,ierr,'ecutsm',dt%ecutsm,1,0.0_dp,iout)
 839 !  With non-zero optcell, one must use non-zero ecutsm
 840    if(dt%optcell/=0 )then
 841      cond_string(1)='optcell' ; cond_values(1)=dt%optcell
 842      call chkdpr(1,1,cond_string,cond_values,ierr,'ecutsm',dt%ecutsm,1,tol8,iout)
 843    end if
 844 
 845 !  ecutwfn <= ecut. This is also needed for the correct evaluation
 846 !  of the Kleynman-Bylander form factors as the spline in Psps% is done with ecut
 847 !  while we need |q+G| up to ecut. enlargement due to the q is already
 848 !  taken into account by enlarging the spline mesh by around 20%.
 849    if ( ANY(optdriver == [RUNL_SCREENING, RUNL_SIGMA, RUNL_BSE]) ) then
 850      call chkdpr(0,0,cond_string,cond_values,ierr,'ecutwfn',dt%ecuteps,1,0.0_dp,iout)
 851      if(dt%ecut<dt%ecutwfn-tol8)then
 852        write(msg,'(a,es16.6,a,es16.6,a,6a)')&
 853         'The values of ecut and ecutwfn are ', dt%ecut,' and ',dt%ecutwfn,ch10,&
 854         'One expects ecutwfn to be smaller or equal to ecut.',ch10,&
 855         'Action: adjust ecutwfn with ecut.'
 856        ABI_ERROR_NOSTOP(msg, ierr)
 857      end if
 858    end if
 859 
 860    ! Check variables used to specify k-points in self-energy.
 861    if (dt%nkptgw /= 0 .and. (any(dt%sigma_erange > tol8 .or. dt%gw_qprange /= 0))) then
 862      ABI_ERROR_NOSTOP("nkptw cannot be used with sigma_erange or gw_qprange", ierr)
 863    end if
 864    if (any(dt%sigma_erange > tol8) .and. dt%gw_qprange /= 0) then
 865      ABI_ERROR_NOSTOP("sigma_erange and gw_qprange are mutually exclusive", ierr)
 866    end if
 867    if (any(dt%sigma_erange < -tol8) .and. any(dt%sigma_erange > tol8)) then
 868      ABI_ERROR_NOSTOP("Found negative sigma_erange entry (metals) with another positive entry (semiconductors)!", ierr)
 869    end if
 870 
 871 !  effmass_free
 872    if(abs(dt%effmass_free-one)>tol8.and.dt%ixc/=31.and.dt%ixc/=35.and.xc_is_mgga)then
 873      write(msg, '(5a)' )&
 874       'A modified electronic effective mass is not useable with a meta-GGA XC functional!',ch10,&
 875       'Except with some fake metaGGAs (ixc=31 or ixc=35).',ch10,&
 876       'effmass should be included in kinetic energy density (tau).'
 877      ABI_ERROR_NOSTOP(msg, ierr)
 878    end if
 879 
 880 !  efmas
 881    if(optdriver==RUNL_RESPFN) then !.and.usepaw==1)then
 882      cond_string(1)='optdriver' ; cond_values(1)=RUNL_RESPFN
 883      cond_string(2)='usepaw'    ; cond_values(2)=dt%usepaw !usepaw
 884      cond_string(3)='ieig2rf'   ; cond_values(3)=dt%ieig2rf
 885      cond_string(4)='nsym'      ; cond_values(4)=dt%nsym
 886      call chkint_eq(1,4,cond_string,cond_values,ierr,'efmas',dt%efmas,2,(/0,1/),iout)
 887      if (dt%paral_rf==1) then
 888        cond_string(1)='paral_rf' ; cond_values(1)=dt%paral_rf
 889        call chkint_eq(1,1,cond_string,cond_values,ierr,'efmas',dt%efmas,1,(/0/),iout)
 890      end if
 891    end if
 892 
 893    if (dt%efmas==1) then
 894      ! Consistency check for efmas calculations.
 895      call chkint_eq(0,0,cond_string,cond_values,ierr,'efmas_calc_dirs',dt%efmas_calc_dirs,7,[-3,-2,-1,0,1,2,3],iout)
 896 
 897      call chkint_eq(0,0,cond_string,cond_values,ierr,'efmas_deg',dt%efmas_deg,2,[0,1],iout)
 898 
 899      call chkdpr(0,0,cond_string,cond_values,ierr,'efmas_deg_tol',dt%efmas_deg_tol,1,0.0_dp,iout)
 900 
 901      call chkint_eq(0,0,cond_string,cond_values,ierr,'efmas_dim',dt%efmas_dim,3,[1,2,3],iout)
 902 
 903      call chkint_ge(0,0,cond_string,cond_values,ierr,'efmas_n_dirs',dt%efmas_n_dirs,0,iout)
 904 
 905      call chkint_ge(0,0,cond_string,cond_values,ierr,'efmas_ntheta',dt%efmas_ntheta,1,iout)
 906 
 907      ABI_CHECK_NOSTOP(all_nprocs == 1, "efmas 1 is not compabitle with MPI. Use 1 processor", ierr)
 908    end if
 909 
 910 !  enable_mpi_io
 911    if(dt%iomode==IO_MODE_MPI) then
 912      cond_string(1)='iomode' ; cond_values(1)=dt%iomode
 913      call chkint_eq(1,1,cond_string,cond_values,ierr,'enable_mpi_io',xmpi_mpiio,1,(/1/),iout)
 914    end if
 915 
 916    ! eph variables
 917    if (optdriver == RUNL_EPH) then
 918      cond_string(1)='optdriver'; cond_values(1)=optdriver
 919      call chkint_eq(1,1,cond_string,cond_values,ierr,'eph_task',dt%eph_task, &
 920        21, [0, 1, 2, -2, 3, 4, -4, 5, -5, 6, 7, -7, 8, 9, 10, 11, -12, 14, 15, -15, 16], iout)
 921 
 922      if (any(dt%ddb_ngqpt <= 0)) then
 923        ABI_ERROR_NOSTOP("ddb_ngqpt must be specified when performing EPH calculations.", ierr)
 924      end if
 925 
 926      if (dt%eph_task == 1 .and. dt%ph_nqpath <= 0) then
 927        ABI_ERROR("When eph_task == 1, the q-path for the linewidth must be specified via ph_nqpath and ph_qpath")
 928      end if
 929      if (dt%eph_task == 1 .and. dt%nshiftk <= 0) then
 930        ABI_ERROR_NOSTOP('phgamma does not work with multiple k-shifts ', ierr)
 931      end if
 932      if (dt%eph_task == 1 .and. .not. isdiagmat(dt%kptrlatt)) then
 933        ABI_ERROR_NOSTOP("kptrlatt must be diagonal in phgamma.", ierr)
 934      end if
 935      if (dt%eph_task == 2 .and. dt%irdwfq == 0 .and. dt%getwfq == 0) then
 936        ABI_ERROR_NOSTOP('Either getwfq or irdwfq must be non-zero in order to compute the gkk', ierr)
 937      end if
 938      if (any(dt%eph_task == [-5])) then
 939        ABI_CHECK(dt%ph_nqpath > 0, "ph_nqpath must be specified when eph_task in [-5]")
 940      end if
 941      !if (dt%eph_task == -4 .and. dt%occopt /= 3) then
 942      !  ABI_ERROR_NOSTOP("eph_task -4 requires occopt 3 in the input file (Fermi-Dirac with physical Temperature!", ierr)
 943      !end if
 944      if (dt%eph_fermie /= zero .and. nint(dt%tmesh(3)) /= 1) then
 945        ABI_ERROR_NOSTOP("eph_fermie does not support multiple temperatures in tmesh !", ierr)
 946      end if
 947      if (dt%eph_fermie /= zero .and. dt%eph_extrael /= zero) then
 948        ABI_ERROR_NOSTOP("eph_fermie and (eph_extrael|eph_doping) are mutually exclusive", ierr)
 949      end if
 950 
 951      cond_string(1)='optdriver' ; cond_values(1)=optdriver
 952      call chkint_eq(1,1,cond_string,cond_values,ierr,'eph_frohlichm',dt%eph_frohlichm,2,[0,1],iout)
 953 
 954      if (dt%eph_stern /= 0) then
 955        ! Check requirements for Sternheimer.
 956        if (dt%tolwfr == zero) then
 957          ABI_ERROR_NOSTOP("tolwfr must be specified when eph_stern /= 0", ierr)
 958        end if
 959        if (dt%getpot_filepath == ABI_NOFILE) then
 960          ABI_ERROR_NOSTOP(" getpot_filepath is required when eph_stern /= 0", ierr)
 961        end if
 962        if (all(dt%sigma_bsum_range /= 0)) then
 963          ABI_ERROR_NOSTOP("sigma_bsum_range cannot be used when eph_stern /= 0", ierr)
 964        end if
 965      end if
 966 
 967      if (dt%ibte_prep /= 0 .and. any(dt%sigma_ngkpt /= 0)) then
 968        ABI_ERROR_NOSTOP("sigma_ngkpt cannot be used to downsample the k-mesh when ibte_prep is used.", ierr)
 969      end if
 970    end if ! RUNL_EPH
 971 
 972    if (any(dt%eph_np_pqbks /= 0)) then
 973      ! Perform basic consistency check for MPI grid.
 974      ! (q-points and k-points will be computed at runtime so cannot perform checks at this level.
 975      if (product(dt%eph_np_pqbks) /= all_nprocs) then
 976        write(msg, "(a,i0,3a, 6(a,1x,i0))") &
 977          "Cannot create 5d Cartesian grid with nprocs: ", all_nprocs, ch10, &
 978          "Idle processes are not supported. The product of the `nproc_*` vars should be equal to nproc.", ch10, &
 979          "nprocs_pert (", dt%eph_np_pqbks(1), ") x nprocs_qpt (", dt%eph_np_pqbks(2), &
 980          ") x nprocs_bsum (", dt%eph_np_pqbks(3), ") x nprocs_kcalc (", dt%eph_np_pqbks(4), &
 981          ") x nprocs_spin (", dt%eph_np_pqbks(5), ") != ", all_nprocs
 982        ABI_ERROR_NOSTOP(msg, ierr)
 983      end if
 984 
 985      ! Check spin
 986      if (all(dt%eph_np_pqbks(5) /= [0, 1])) then
 987        if (dt%nspinor == 2) then
 988          ABI_ERROR_NOSTOP("Spin parallelism cannot be used when nspinor == 2", ierr)
 989        else if (dt%nspinor == 1 .and. dt%eph_np_pqbks(5) > dt%nsppol) then
 990          ABI_ERROR_NOSTOP("nproc for spin parallelism cannot be greater than nsppol", ierr)
 991        end if
 992      end if
 993 
 994     if (dt%eph_np_pqbks(1) /= 0 .and. dt%eph_np_pqbks(1) > 3 * dt%natom ) then
 995       ABI_ERROR_NOSTOP("nproc for pert parallelism cannot be greater than 3 * natom", ierr)
 996     end if
 997 
 998     if (mod(3 * dt%natom, dt%eph_np_pqbks(1)) /= 0) then
 999       ABI_ERROR_NOSTOP("nproc for pert parallelism must divide 3 * natom.", ierr)
1000     end if
1001 
1002 #ifndef HAVE_NETCDF_MPI
1003     if (abs(dt%eph_task) == 4 .and. (dt%eph_np_pqbks(4) /= 1 .or. dt%eph_np_pqbks(5) /= 1)) then
1004       ABI_ERROR_NOSTOP("k-point and/or spin parallelism in EPH code requires Netcdf4 with MPI-IO support!", ierr)
1005     end if
1006 #endif
1007    end if
1008 
1009    ! exchmix
1010    call chkdpr(0,0,cond_string,cond_values,ierr,'exchmix',dt%exchmix,1,0.0_dp,iout)
1011 
1012    ! extrapwf
1013    call chkint_eq(0,0,cond_string,cond_values,ierr,'extrapwf',dt%extrapwf,3, [0,1,2], iout)
1014    if (dt%extrapwf>0.and.dt%densfor_pred<5) then
1015      write(msg,'(3a)')&
1016      'extrapwf keyword (extrapolation of WF) is only compatible with',ch10,&
1017      'densfor_pred=5 or 6; please change densfor_pred value.'
1018      ABI_ERROR_NOSTOP(msg,ierr)
1019      ! MT oct 14: Should use chkint_eq but the msg is not clear enough
1020    end if
1021 
1022 !  expert_user
1023    call chkint_eq(0,0,cond_string,cond_values,ierr,'expert_user',dt%expert_user,4, [0,1,2,3],iout)
1024 
1025    ! fermie_nest
1026    call chkdpr(0,0,cond_string,cond_values,ierr,'fermie_nest',dt%fermie_nest,1,0.0_dp,iout)
1027 
1028 !  ffnl_lw
1029    call chkint_eq(0,0,cond_string,cond_values,ierr,'ffnl_lw',dt%ffnl_lw,2,(/0,1/),iout)
1030 
1031 
1032    ! fftgw
1033    call chkint_eq(0,0,cond_string,cond_values,ierr,'fftgw',dt%fftgw,8, [00,01,10,11,20,21,30,31],iout)
1034 
1035    !  fockoptmix
1036    call chkint_eq(0,0,cond_string,cond_values,ierr,'fockoptmix',&
1037      dt%fockoptmix,12,[0,1,11,201,211,301,401,501,601,701,801,901],iout)
1038    if(dt%paral_kgb/=0)then
1039      cond_string(1)='paral_kgb' ; cond_values(1)=dt%paral_kgb
1040      ! Make sure that dt%fockoptmix is 0, 1 or 11 (wfmixalg==0)
1041      call chkint_eq(1,1,cond_string,cond_values,ierr,'fockoptmix',dt%fockoptmix,3,(/0,1,11/),iout)
1042    end if
1043 
1044    ! fock_icutcoul
1045    call chkint_eq(0,0,cond_string,cond_values,ierr,'fock_icutcoul',dt%fock_icutcoul,6,[0,1,2,3,4,5],iout)
1046 
1047    ! frzfermi
1048    call chkint_eq(0,0,cond_string,cond_values,ierr,'frzfermi',dt%frzfermi,2,[0,1],iout)
1049 
1050    ! fxcartfactor
1051    call chkdpr(0,0,cond_string,cond_values,ierr,'fxcartfactor',dt%fxcartfactor,1,zero,iout)
1052 
1053    ! ga_algor
1054    call chkint_eq(0,0,cond_string,cond_values,ierr,'ga_algor',dt%ga_algor,3,[1,2,3],iout)
1055 
1056    ! ga_fitness
1057    call chkint_eq(0,0,cond_string,cond_values,ierr,'ga_fitness',dt%ga_fitness,3,[1,2,3],iout)
1058 
1059    ! ga_opt_percent
1060    call chkdpr(0,0,cond_string,cond_values,ierr,'ga_opt_percent',dt%ga_opt_percent,1,tol8,iout)
1061 
1062    ! getxred
1063    if(dt%getxcart/=0)then
1064      cond_string(1)='getxcart' ; cond_values(1)=dt%getxcart
1065      ! Make sure that dt%getxred is 0
1066      call chkint_eq(1,1,cond_string,cond_values,ierr,'getxred',dt%getxred,1,[0],iout)
1067    end if
1068 
1069    ! goprecon
1070    call chkint_eq(0,0,cond_string,cond_values,ierr,'goprecon',dt%goprecon,4,[0,1,2,3],iout)
1071 
1072    ! gpu_devices
1073    if (dt%gpu_option/=ABI_GPU_DISABLED) then
1074      if (all(gpu_devices(:)==-2)) then
1075        gpu_devices(:)=dt%gpu_devices(:)
1076      else if (any(dt%gpu_devices(:)/=gpu_devices(:))) then
1077        write(msg,'(3a)')&
1078         'GPU device(s) selection cannot be different from one dataset to another!',ch10,&
1079         'Action: change gpu_devices in input file.'
1080        ABI_ERROR_NOSTOP(msg, ierr)
1081      end if
1082    end if
1083 
1084 !  gpu_kokkos_nthrd
1085    call chkint_ge(0,0,cond_string,cond_values,ierr,'gpu_kokkos_nthrd',dt%gpu_kokkos_nthrd,1,iout)
1086 
1087 !  gpu_option
1088    call chkint_eq(0,0,cond_string,cond_values,ierr,'gpu_option',dt%gpu_option,4, &
1089    &        (/ABI_GPU_DISABLED,ABI_GPU_LEGACY,ABI_GPU_OPENMP,ABI_GPU_KOKKOS/),iout)
1090    if (dt%gpu_option/=ABI_GPU_DISABLED) then
1091      if (dt%nspinor==2) then
1092        write(msg,'(3a)')&
1093 &       'Use of GPU is not allowed when nspinor==2 !',ch10,&
1094 &       'Action: impose gpu_option=0 in your input file.'
1095        ABI_ERROR_NOSTOP(msg, ierr)
1096      end if
1097 !    if (dt%optdriver==RUNL_GSTATE.and.mod(dt%wfoptalg,10)/=4) then
1098 !    write(msg,'(6a)') ch10,&
1099 !    &       ' chkinp : ERROR -',ch10,&
1100 !    &       '  When GPU is in use (gpu_option>0), wfoptalg must be 4 or 14 !',ch10,&
1101 !    &       '  Action: change wfoptalg in your input file.'
1102 !    call wrtout(std_out,msg)
1103 !    ierr=ierr+1
1104 !    end if
1105      if (dt%useylm == 0 .and. dt%optdriver /= RUNL_GWR) then
1106        write(msg,'(3a)')&
1107         'Use of GPU is not allowed when useylm==0 !',ch10,&
1108         'Action: impose uselym=1 in your input file.'
1109        ABI_ERROR_NOSTOP(msg, ierr)
1110      end if
1111      if (dt%tfkinfunc>0) then
1112        write(msg,'(5a)')&
1113 &       'gpu_option/=0 (use of GPU) is not allowed when tfkinfunc>0 !',ch10,&
1114 &       'Action: suppress gpu_option from your input file',ch10,&
1115 &       '        (GPU will be used but with another mechanism)'
1116        ABI_ERROR_NOSTOP(msg, ierr)
1117      end if
1118      if (dt%ngfft(4)/=dt%ngfft(1).or.dt%ngfft(5)/=dt%ngfft(2).or.dt%ngfft(6)/=dt%ngfft(3)) then
1119        write(msg,'(3a)')&
1120 &       'When GPU is in use (gpu_option/=0), ngfft(4:6) must be equal to ngfft(1:3) !',ch10,&
1121 &       'Action: suppress ngfft in input file or change it.'
1122        ABI_ERROR_NOSTOP(msg, ierr)
1123      end if
1124 #ifndef HAVE_GPU
1125      write(msg,'(6a)') ch10,&
1126 &     ' invars0: ERROR -',ch10,&
1127 &     '   Input variable gpu_option is on but abinit hasn''t been built with GPU mode enabled !',ch10,&
1128 &     '   Action: suppress the input variable gpu_option or re-compile ABINIT with GPU enabled.'
1129      call wrtout(std_out,msg)
1130      ierr=ierr+1
1131 #endif
1132 !#ifndef HAVE_GPU_CUDA_DP
1133 !     write(msg,'(10a)') ch10,&
1134 !&     ' invars0: ERROR -',ch10,&
1135 !&     '   Input variable gpu_option is on but abinit hasn''t been built',ch10,&
1136 !&     '   with GPU mode in DOUBLE PRECISION enabled !',ch10,&
1137 !&     '   Action: suppress input variable gpu_option',ch10,&
1138 !&     '   or re-compile ABINIT with double precision GPU enabled.'
1139 !     call wrtout(std_out,msg)
1140 !     ierr=ierr+1
1141 !#endif
1142    end if
1143 
1144    ! RT-TDDFT
1145    if (dt%optdriver == RUNL_RTTDDFT) then
1146      ! getwfk / getwfk_filepath / irdwfk
1147      if (dt%getwfk == 0 .and. dt%irdwfk == 0 .and. dt%getwfk_filepath==ABI_NOFILE .and. dt%td_restart==0) then
1148        write(msg, '(3a)' ) &
1149         'Initial KS orbitals need to be read in WFK file for RT-TDDFT runs!',ch10,&
1150         'Action: set irdwfk or getwfk /= 0 or specify the WFK filename using getwfk_filepath.'
1151        ABI_ERROR_NOSTOP(msg, ierr)
1152      endif
1153      ! usewvl
1154      if (dt%usewvl /= 0) then
1155         ABI_ERROR_NOSTOP('RT-TDDFT and wavelets are not compatible, set usewvl to 0.', ierr)
1156      endif
1157      ! nimage
1158      if (dt%nimage > 1) then
1159         ABI_ERROR_NOSTOP('RT-TDDFT and multiple images are not compatible, set nimage to 1.', ierr)
1160      endif
1161      ! tfkinfunc
1162      if (dt%tfkinfunc == 2) then
1163         write(msg,'(a)') 'RT-TDDFT and Thomas-Fermi functional using the recursion method &
1164          & are not compatible, set tfkinfunc /= 2.'
1165         ABI_ERROR_NOSTOP(msg, ierr)
1166      endif
1167      ! positron
1168      if (dt%positron /= 0) then
1169         ABI_ERROR_NOSTOP('RT-TDDFT and Positron are not compatible, set positron to 0.', ierr)
1170      endif
1171      ! usefock
1172      if (dt%usefock==1) then
1173         ABI_ERROR_NOSTOP('RT-TDDFT and Exact exchange are not compatible, set usefock to 0.', ierr)
1174      end if
1175      ! usedmft
1176      if (dt%usedmft /= 0) then
1177         ABI_ERROR_NOSTOP('RT-TDDFT and DFT+DMFT are not compatible, set usedmft to 0.', ierr)
1178      endif
1179      ! usepawu
1180      if (dt%usepawu /= 0) then
1181         ABI_ERROR_NOSTOP('RT-TDDFT with DFT+U has not been tested yet, set usepawu to 0.', ierr)
1182      endif
1183      ! usekden
1184      if (xc_is_mgga) then
1185         ABI_ERROR_NOSTOP('RT-TDDFT with mGGA has not been tested yet! Not available.', ierr)
1186      end if
1187      ! vdw_xc
1188      if (dt%vdw_xc /= 0) then
1189         ABI_ERROR_NOSTOP('RT-TDDFT with VDW corrected functionals has not been tested yet, set vdw_xc to 0.', ierr)
1190      endif
1191      !TODO FB: Should probably be made possible later
1192      ! useextfpmd
1193      if (dt%useextfpmd /= 0) then
1194         write(msg,'(a)') 'RT-TDDFT and extFPMD has not been tested yet, set useextfpmd to 0.'
1195         ABI_ERROR_NOSTOP(msg, ierr)
1196      endif
1197    endif
1198 
1199    ! gw_invalid_freq
1200    call chkint_eq(0,0,cond_string,cond_values,ierr,'gw_invalid_freq',dt%gw_invalid_freq,3,[0,1,2],iout)
1201 
1202    ! gw_icutcoul
1203    call chkint_eq(0,0,cond_string,cond_values,ierr,'gw_icutcoul',dt%gw_icutcoul,11,[0,1,2,3,4,5,6,7,14,15,16],iout)
1204 
1205    ! gw_sigxcore
1206    call chkint_eq(0,0,cond_string,cond_values,ierr,'gw_sigxcore',dt%gw_sigxcore,2,[0,1],iout)
1207 
1208    ! gwcomp
1209    call chkint_eq(0,0,cond_string,cond_values,ierr,'gwcomp',dt%gwcomp,2,[0,1],iout)
1210    if (dt%gwcomp/=0) then
1211      if (optdriver==RUNL_SCREENING .and. (dt%awtr /=1 .or. dt%spmeth /=0)) then
1212        write(msg,'(3a)' )&
1213         'When gwcomp /= 0, the Adler-Wiser formula with time-reversal should be used',ch10,&
1214         'Action: set awtr to 1 or/and spmeth to 0'
1215        ABI_ERROR_NOSTOP(msg, ierr)
1216      end if
1217 
1218      ! Extrapolar trick with HF, SEX and COHSEX is meaningless for Sigma
1219      if(optdriver == RUNL_SIGMA) then
1220        mod10=MOD(dt%gwcalctyp,10)
1221        if ( ANY(mod10 == [SIG_HF, SIG_SEX, SIG_COHSEX]) ) then
1222          write(msg,'(3a)' )&
1223          'gwcomp/=0, is meaningless in the case of HF, SEX or COHSEX calculations. ',ch10,&
1224          'Action: set gwcomp to 0 or change gwcalctyp'
1225          ABI_ERROR_NOSTOP(msg, ierr)
1226        end if
1227      end if
1228      if (optdriver==RUNL_SIGMA .and. ALL( dt%ppmodel /= [0,1,2] )) then
1229        write(msg,'(a,i0,a)')&
1230          'The completeness trick cannot be used when ppmodel is ',dt%ppmodel,'. It should be set to 0, 1 or 2. '
1231        ABI_ERROR_NOSTOP(msg, ierr)
1232      end if
1233    end if
1234 
1235    call chkint_eq(0,0,cond_string,cond_values,ierr,'gwmem',dt%gwmem,4,[0,1,10,11],iout)
1236 
1237    ! gwpara
1238    call chkint_eq(0,0,cond_string,cond_values,ierr,'gwpara',dt%gwpara,3,[0,1,2],iout)
1239 !  if(dt%chkparal/=0.and.(dt%gwpara==0.and.(dt%optdriver==RUNL_SCREENING.and.dt%optdriver==RUNL_SIGMA))) then
1240 !      cond_string(1)='optdriver' ; cond_values(1)=dt%optdriver
1241 !      cond_string(2)='chkparal' ; cond_values(2)=dt%chkparal
1242 !      call chkint_eq(2,2,cond_string,cond_values,ierr,'gwpara',dt%gwpara,1,(/0/),iout)
1243 !  end if
1244 
1245    ! gwrpacorr
1246    if(dt%gwrpacorr>0) then
1247      mod10=MOD(dt%gwcalctyp,10)
1248      if (optdriver /= RUNL_SCREENING) then
1249        write(msg,'(3a)' )&
1250        'gwrpacorr>0 can only be used when calculating the screening',ch10,&
1251        'Action: set gwrpacorr to 0 or optdriver to 3'
1252        ABI_ERROR_NOSTOP(msg, ierr)
1253      end if
1254      if( mod10 /= SIG_GW_AC ) then
1255        write(msg,'(3a)' )&
1256        'gwrpacorr > 0 can only be used with purely imaginary frequencies',ch10,&
1257        'Action: set gwrpacorr to 0 or change gwcalctyp'
1258        ABI_ERROR_NOSTOP(msg, ierr)
1259      end if
1260    end if
1261    ! gwgmcorr
1262    if(dt%gwgmcorr==1 .and. dt%gwrpacorr==0) then
1263      write(msg,'(3a)' )&
1264      'gwgmcorr=1 can only be used with gwrpacorr/=0',ch10,&
1265      'Action: set gwgmcorr to 0 or gwrpacorr > 0'
1266       ABI_ERROR_NOSTOP(msg, ierr)
1267    end if
1268 
1269    ! gwls_stern_kmax
1270    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_stern_kmax',dt%gwls_stern_kmax,1,iout)
1271 
1272    ! gwls_npt_gauss_quad
1273    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_npt_gauss_quad',dt%gwls_npt_gauss_quad,1,iout)
1274 
1275    ! gwls_diel_model
1276    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_diel_model',dt%gwls_diel_model,1,iout)
1277    call chkint_le(0,0,cond_string,cond_values,ierr,'gwls_diel_model',dt%gwls_diel_model,3,iout)
1278 
1279    ! gwls_model_parameter
1280    call chkdpr(0,0,cond_string,cond_values,ierr,'gwls_model_parameter',dt%gwls_model_parameter,1,zero,iout)
1281 
1282    ! gwls_print_debug
1283    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_print_debug',dt%gwls_print_debug,0,iout)
1284 
1285    ! gwls_nseeds
1286    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_nseeds',dt%gwls_nseeds,1,iout)
1287 
1288    ! gwls_kmax_complement
1289    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_kmax_complement',dt%gwls_kmax_complement,0,iout)
1290 
1291    ! gwls_kmax_poles
1292    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_kmax_poles',dt%gwls_kmax_poles,0,iout)
1293 
1294    ! gwls_kmax_analytic
1295    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_kmax_analytic',dt%gwls_kmax_analytic,0,iout)
1296 
1297    ! gwls_kmax_numeric
1298    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_kmax_numeric',dt%gwls_kmax_numeric,0,iout)
1299 
1300    ! gwls_band_index
1301    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_band_index',dt%gwls_band_index,1,iout)
1302 
1303    ! gwls_exchange
1304    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_exchange',dt%gwls_exchange,0,iout)
1305 
1306    ! gwls_correlation
1307    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_correlation',dt%gwls_correlation,0,iout)
1308 
1309    ! gwls_first_seed
1310    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_first_seed',dt%gwls_first_seed,1,iout)
1311 
1312    ! gwls_recycle
1313    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_recycle',dt%gwls_recycle,0,iout)
1314    call chkint_le(0,0,cond_string,cond_values,ierr,'gwls_recycle',dt%gwls_recycle,2,iout)
1315 
1316    ! iatsph must between 1 and natom
1317    maxiatsph=maxval(dt%iatsph(1:dt%natsph))
1318    miniatsph=minval(dt%iatsph(1:dt%natsph))
1319    call chkint_ge(0,0,cond_string,cond_values,ierr,'iatsph',miniatsph,1,iout)
1320    call chkint_le(0,0,cond_string,cond_values,ierr,'iatsph',maxiatsph,natom,iout)
1321 
1322    ! icoulomb
1323    call chkint_eq(0,0,cond_string,cond_values,ierr,'icoulomb',dt%icoulomb,3,[0,1,2],iout)
1324    if (dt%nspden > 2) then
1325      cond_string(1)='nspden' ; cond_values(1)=nspden
1326      call chkint_eq(1,1,cond_string,cond_values,ierr,'icoulomb',dt%icoulomb,1,[0],iout)
1327    end if
1328 
1329    ! icutcoul
1330    call chkint_eq(0,0,cond_string,cond_values,ierr,'icutcoul',dt%icutcoul,11,[0,1,2,3,4,5,6,7,14,15,16],iout)
1331 
1332    ! ieig2rf
1333    if(optdriver==RUNL_RESPFN.and.usepaw==1)then
1334      cond_string(1)='optdriver' ; cond_values(1)=optdriver
1335      cond_string(2)='usepaw'    ; cond_values(2)=usepaw
1336      call chkint_eq(1,2,cond_string,cond_values,ierr,'ieig2rf',dt%ieig2rf,1,[0],iout)
1337    end if
1338    if(optdriver==RUNL_RESPFN.and.dt%paral_rf==1)then
1339      cond_string(1)='paral_rf' ; cond_values(1)=dt%paral_rf
1340      call chkint_eq(1,1,cond_string,cond_values,ierr,'ieig2rf',dt%ieig2rf,1,[0],iout)
1341    end if
1342 
1343    ! imgmov
1344    call chkint_eq(0,0,cond_string,cond_values,ierr,'imgmov',dt%imgmov,9,(/0,1,2,4,5,6,9,10,13/),iout)
1345    if (dt%imgmov>0 .and. dt%imgmov/=6) then ! when imgmov>0, except imgmov==6, allow only ionmov0 and optcell 0 (temporary)
1346      cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
1347      call chkint_eq(1,1,cond_string,cond_values,ierr,'ionmov',dt%ionmov,1,(/0/),iout)
1348      if (dt%imgmov==9.or.dt%imgmov==10.or.dt%imgmov==13) then
1349        cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
1350        !Temporarily deactivate NPT algorithms (not yet usable)
1351        call chkint_eq(1,1,cond_string,cond_values,ierr,'optcell',dt%optcell,1,(/0/),iout)
1352      else
1353        cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
1354        call chkint_eq(1,1,cond_string,cond_values,ierr,'optcell',dt%optcell,1,(/0/),iout)
1355      end if
1356    end if
1357 
1358    ! imgwfstor
1359    call chkint_eq(0,0,cond_string,cond_values,ierr,'imgwfstor',dt%imgwfstor,2,(/0,1/),iout)
1360    if (dt%extrapwf/=0) then ! extrapwf/=0 not allowed presently with imgwfstor
1361      cond_string(1)='extrapwf' ; cond_values(1)=dt%extrapwf
1362      call chkint_eq(1,1,cond_string,cond_values,ierr,'imgwfstor',dt%imgwfstor,1,(/0/),iout)
1363    endif
1364    if (dt%ntimimage<=1) then ! imgwfstor activate only when there is more than one time step for images
1365      cond_string(1)='ntimimage' ; cond_values(1)=dt%ntimimage
1366      call chkint_eq(1,1,cond_string,cond_values,ierr,'imgwfstor',dt%imgwfstor,1,(/0/),iout)
1367    endif
1368 
1369 !  inclvkb
1370    call chkint_eq(0,0,cond_string,cond_values,ierr,'inclvkb',dt%inclvkb,2,(/0,2/),iout)
1371 
1372 !  intxc
1373    call chkint_eq(0,0,cond_string,cond_values,ierr,'intxc',dt%intxc,2,(/0,1/),iout)
1374    if(dt%iscf==-1)then
1375      cond_string(1)='iscf' ; cond_values(1)=dt%iscf
1376      ! Make sure that dt%intxc is 0
1377      call chkint_eq(1,1,cond_string,cond_values,ierr,'intxc',dt%intxc,1,(/0/),iout)
1378    end if
1379 !  TEMPORARY
1380    if(optdriver==RUNL_RESPFN)then ! Make sure that dt%intxc is 0
1381      cond_string(1)='optdriver' ; cond_values(1)=optdriver
1382      call chkint_eq(1,1,cond_string,cond_values,ierr,'intxc',dt%intxc,1,(/0/),iout)
1383    end if
1384 
1385    ! ionmov
1386    call chkint_eq(0,0,cond_string,cond_values,ierr,'ionmov',&
1387      dt%ionmov,24, [0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,20,21,22,23,24,25,26,28],iout)
1388 
1389    ! When optcell/=0, ionmov must be 2, 3, 13, 22 or 25, 28 (except if imgmov>0)
1390    if(dt%optcell/=0)then
1391      if (dt%imgmov==0) then
1392        cond_string(1)='optcell' ; cond_values(1)=dt%optcell
1393        call chkint_eq(1,1,cond_string,cond_values,ierr,'ionmov',dt%ionmov,7,[2,3,13,15,22,25,28],iout)
1394      else
1395        cond_string(1)='optcell' ; cond_values(1)=dt%optcell
1396        call chkint_eq(1,1,cond_string,cond_values,ierr,'ionmov',dt%ionmov,1,(/0/),iout)
1397      end if
1398    end if
1399    if (dt%ionmov == 13) then
1400      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
1401 !    Make sure that nnos is not null
1402      call chkint_ge(1,1,cond_string,cond_values,ierr,'nnos',dt%nnos,1,iout)
1403    end if
1404 
1405 !  iprcel
1406    call chkint(0,0,cond_string,cond_values,ierr,'iprcel',dt%iprcel,1,(/0/),1,21,iout)
1407    if(nsppol==2 .and. (dt%occopt>=3 .and. dt%occopt<=9).and.mod(dt%iprcel,10)>49 )then
1408      write(msg,'(5a)')&
1409      'For spin-polarized metallic systems (occopt>3),',ch10,&
1410      'only RPA dielectric matrix can be evaluated) !',ch10,&
1411      'Action: change iprcel value in input file (mod(iprcel,100)<50) !'
1412      ABI_ERROR_NOSTOP(msg, ierr)
1413    end if
1414    if(dt%npspinor>1.and.dt%iprcel>0)then
1415      write(msg,'(5a)')&
1416      'When parallelization over spinorial components is activated (npspinor>1),',ch10,&
1417      'only model dielectric function is allowed (iprcel=0) !',ch10,&
1418      'Action: change iprcel value in input file !'
1419      ABI_ERROR_NOSTOP(msg, ierr)
1420    end if
1421 
1422    ! irandom
1423    call chkint_eq(0,0,cond_string,cond_values,ierr,'irandom',dt%irandom,3, [1,2,3], iout)
1424 
1425    ! iscf
1426    if (usewvl ==0) then
1427      call chkint_eq(0,0,cond_string,cond_values,ierr,&
1428       'iscf',dt%iscf,18, [-3,-2,-1,1,2,3,4,5,6,7,11,12,13,14,15,16,17,22], iout)
1429    else
1430 !    If usewvl: wvlbigdft indicates that the BigDFT workflow will be followed
1431      wvlbigdft=(dt%usewvl==1.and.dt%wvl_bigdft_comp==1)
1432      cond_string(1)='wvl_bigdft_comp' ; cond_values(1)=dt%wvl_bigdft_comp
1433      if(wvlbigdft) then
1434        call chkint_eq(1,1,cond_string,cond_values,ierr,&
1435         'iscf',dt%iscf,15,(/0,1,2,3,4,5,6,7,11,12,13,14,15,16,17/),iout)
1436      else
1437        call chkint_eq(1,1,cond_string,cond_values,ierr,&
1438         'iscf',dt%iscf,18,(/-3,-2,-1,1,2,3,4,5,6,7,11,12,13,14,15,16,17,22/),iout)
1439      end if
1440 !    If wvl+metal, iscf cannot be 0
1441      if (dt%occopt>2) then
1442        cond_string(1)='occopt' ; cond_values(1)=dt%occopt
1443        call chkint_eq(1,1,cond_string,cond_values,ierr,&
1444         'iscf',dt%iscf,18,(/-3,-2,-1,1,2,3,4,5,6,7,11,12,13,14,15,16,17,22/),iout)
1445      end if
1446    end if
1447 
1448    ! If ionmov==4, iscf must be 2, 12, 5 or 6.
1449    if(dt%ionmov==4)then
1450      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
1451      call chkint_eq(1,1,cond_string,cond_values,ierr,'iscf',dt%iscf,4,(/2,12,5,6/),iout)
1452    end if
1453 !  If PAW, iscf cannot be -1, 11
1454    if (usepaw==1 .and. usewvl==0) then
1455      cond_string(1)='usepaw' ; cond_values(1)=usepaw
1456      call chkint_eq(1,1,cond_string,cond_values,ierr,'iscf',dt%iscf,11,(/-3,-2,2,3,4,7,12,13,14,17,22/),iout)
1457    end if
1458 !  Mixing on density is only allowed for GS calculations or for drivers where it is not used.
1459    if(optdriver /= RUNL_GSTATE .and. all(optdriver /= [RUNL_SCREENING,RUNL_SIGMA,RUNL_BSE,RUNL_EPH, &
1460      RUNL_WFK,RUNL_NONLINEAR,RUNL_RTTDDFT, RUNL_GWR])) then
1461      cond_string(1)='optdriver' ; cond_values(1)=optdriver
1462      call chkint_le(1,1,cond_string,cond_values,ierr,'iscf',dt%iscf,9,iout)
1463    end if
1464 !  When pawoptmix=1 and nspden=4, iscf must be >=10
1465    if(dt%pawoptmix/=0.and.nspden==4)then
1466      cond_string(1)='nspden'    ; cond_values(1)=nspden
1467      cond_string(2)='pawoptmix' ; cond_values(2)=dt%pawoptmix
1468      call chkint_ge(2,2,cond_string,cond_values,ierr,'iscf',dt%iscf,10,iout)
1469    end if
1470 
1471 !  istatimg
1472    call chkint_eq(0,0,cond_string,cond_values,ierr,'istatimg',dt%istatimg,2,(/0,1/),iout)
1473    if (dt%string_algo==2) then
1474      cond_string(1)='string_algo' ; cond_values(1)=dt%string_algo
1475      call chkint_eq(1,1,cond_string,cond_values,ierr,'istatimg',dt%istatimg,1,(/1/),iout)
1476    end if
1477 
1478 !  istwfk
1479    if(dt%usefock==1 .and. dt%optdriver/=RUNL_SIGMA .and. mod(dt%wfoptalg,10)/=5 .and. maxval( abs(dt%istwfk(1:nkpt)-1) ) >0)then
1480      write(msg,'(3a)' )&
1481       'When usefock==1, unless sigma calculation, all the components of istwfk must be 1.',ch10,&
1482       'Action: set istwfk to 1 for all k-points'
1483      ABI_ERROR_NOSTOP(msg, ierr)
1484    end if
1485 
1486    if(dt%usewvl==1 .and. maxval( abs(dt%istwfk(1:nkpt)-1) ) >0)then
1487      write(msg,'(3a)' )&
1488       'When usewvl==1, all the components of istwfk must be 1.',ch10,&
1489       'Action: set istwfk to 1 for all k-points'
1490      ABI_ERROR_NOSTOP(msg, ierr)
1491    end if
1492 
1493    if(response==1 .and. maxval( abs(dt%istwfk(1:nkpt)-1) ) >0)then
1494      ! Force istwfk to be 1 for RF calculations
1495      ! Other choices cannot be realized yet, because of the ddk perturbation.
1496      write(msg,'(5a)' )&
1497      'When response==1, all the components of istwfk must be 1.',ch10,&
1498      'Not yet programmed for time-reversal symmetry.',ch10,&
1499      'Action: set istwfk to 1 for all k-points'
1500      ABI_ERROR_NOSTOP(msg, ierr)
1501    end if
1502    if(dt%nbandkss/=0 .and. dt%kssform/=3 .and. maxval( abs(dt%istwfk(1:nkpt)-1) ) >0)then
1503      write(msg,'(5a)' )&
1504      'When nbandkss/=0 and kssform/=3 all the components of istwfk must be 1.',ch10,&
1505      'Not yet programmed for time-reversal symmetry.',ch10,&
1506      'Action: set istwfk to 1 for all k-points'
1507      ABI_ERROR_NOSTOP(msg, ierr)
1508    end if
1509    if(dt%berryopt/=0 .and. maxval(dt%istwfk(:))/=1)then
1510      write(msg,'(5a)' )&
1511      'When berryopt/=0, all the components of istwfk must be 1.',ch10,&
1512      'Not yet programmed for time-reversal symmetry.',ch10,&
1513      'Action: set istwfk to 1 for all k-points'
1514      ABI_ERROR_NOSTOP(msg, ierr)
1515    end if
1516    if (dt%optdriver==RUNL_GSTATE) then
1517      if ((dt%wfoptalg==4.or.dt%wfoptalg==14.or.dt%wfoptalg==114).and.maxval(dt%istwfk(:)-2)>0) then
1518        write(msg, '(a,a,a,a,a)' )&
1519        'Only the gamma point can use time-reversal and wfoptalg=4 or 14',ch10,&
1520        'Action: put istwfk to 1 or remove k points with half integer coordinates ',ch10,&
1521        'Also contact ABINIT group to say that you need that option.'
1522        ABI_ERROR_NOSTOP(msg, ierr)
1523      end if
1524 !     if ((dt%wfoptalg==4.or.dt%wfoptalg==14).and.any(dt%istwfk(:)==2) .and.dt%paral_kgb==1.and.fftalg/=401.and.fftalg/=312) then
1525 !       write(msg, '(a,i3,a,a,a)' )&
1526 !&       ' For istwfk=2, the value fftalg= ',fftalg, &
1527 !&       ' is not allowed in case of wfoptalg=4 or 14 !', ch10,&
1528 !&       ' Change if to fftalg=401.'
1529 !       ABI_ERROR_NOSTOP(msg, ierr)
1530 !     end if
1531    end if
1532 
1533 !  ixc
1534    call chkint(0,0,cond_string,cond_values,ierr,&
1535 &   'ixc',dt%ixc,34,(/0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,20,21,22,23,24,26,27,31,32,33,34,35,40,41,42,50/),-1,0,iout) ! One of the values, or negative
1536    if(dt%iscf==-1)then
1537      cond_string(1)='iscf' ; cond_values(1)=dt%iscf
1538 !    Make sure that ixc is 1, 7, 8, 20, 21 or 22  (native functionals only for TDDFT - LibXC functionals have not been tested !)
1539      call chkint(1,1,cond_string,cond_values,ierr,'ixc',dt%ixc,6,(/1,7,8,20,21,22/),0,0,iout)
1540    end if
1541    if(response==1)then
1542      cond_string(1)='response' ; cond_values(1)=response
1543 !    Make sure that ixc is between 0 and 9, or 11, 12, 14, 15, 23 or 24 or negative
1544      call chkint(1,1,cond_string,cond_values,ierr,&
1545 &     'ixc',dt%ixc,16,(/0,1,2,3,4,5,6,7,8,9,11,12,14,15,23,24/),-1,0,iout)
1546    end if
1547    if(nspden/=1)then
1548      cond_string(1)='nspden' ; cond_values(1)=nspden
1549 !    Make sure that ixc is 0, 1 , the gga, or Fermi-Amaldi, or negative
1550      call chkint(1,1,cond_string,cond_values,ierr,&
1551 &     'ixc',dt%ixc,25,(/0,1,7,8,9,11,12,13,14,15,16,17,20,23,24,26,27,31,32,33,34,35,40,41,42/),-1,0,iout)
1552    end if
1553    if (dt%usepaw>0.and.(dt%ixc==-427.or.dt%ixc==-428)) then
1554      ABI_WARNING('Range-separated Hybrid Functionals have not been extensively tested in PAW!!!')
1555    end if
1556    allowed=((xc_is_lda.and.dt%ixc<0).or.dt%ixc==0.or.dt%ixc==3.or.dt%ixc==7.or.dt%ixc==8)
1557    if(.not.allowed)then
1558      cond_string(1)='ixc' ; cond_values(1)=dt%ixc
1559      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_NONLINEAR/),iout)
1560    end if
1561    if (xc_is_mgga) then
1562 !    mGGA not allowed for different drivers
1563      cond_string(1)='ixc' ; cond_values(1)=dt%ixc
1564      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,5, &
1565 &      (/RUNL_SCREENING,RUNL_SIGMA,RUNL_BSE,RUNL_NONLINEAR,RUNL_LONGWAVE/),iout)
1566    end if
1567 
1568 
1569 
1570 !  ixcpositron
1571    call chkint_eq(0,0,cond_string,cond_values,ierr,'ixcpositron',dt%ixcpositron,8,(/0,-1,1,11,2,3,31,4/),iout)
1572 
1573 !  ixcrot
1574    call chkint_eq(0,0,cond_string,cond_values,ierr,'ixcrot',dt%ixcrot,3,(/1,2,3/),iout)
1575    if(dt%rfmagn/=0)then
1576      if(dt%ixcrot/=3)then
1577        cond_string(1)='rfmagn' ; cond_values(1)=dt%rfmagn
1578        cond_string(2)='ixcrot' ; cond_values(2)=dt%ixcrot
1579        call chkdpr(1,2,cond_string,cond_values,ierr,'qptn(1)',dt%qptn(1),0,zero,iout)
1580        call chkdpr(1,2,cond_string,cond_values,ierr,'qptn(2)',dt%qptn(2),0,zero,iout)
1581        call chkdpr(1,2,cond_string,cond_values,ierr,'qptn(3)',dt%qptn(3),0,zero,iout)
1582      end if
1583    endif
1584 
1585 !  tim1rev
1586    call chkint_eq(0,0,cond_string,cond_values,ierr,'tim1rev',dt%tim1rev,2,(/0,1/),iout)
1587 
1588 !  kptnrm and kpt
1589 !  Coordinates components must be between -1 and 1.
1590    if(dt%kptnrm<1.0-1.0d-10)then
1591      write(msg, '(a,es22.14,a,a,a)' )&
1592       'The input variable kptnrm is',dt%kptnrm,' while it must be >=1.0_dp.',ch10,&
1593       'Action: change the input variable kptnrm.'
1594      ABI_ERROR_NOSTOP(msg, ierr)
1595    end if
1596    do ikpt=1,nkpt
1597      do mu=1,3
1598        if ( abs(dt%kpt(mu,ikpt))> dt%kptnrm*1.0000001_dp ) then
1599          write(msg, '(a,i5,a,a,a,a,3es22.14,a,a,a,a)' )&
1600           'For k point number',ikpt,'  the reduced coordinates',ch10,&
1601           'generated by the input variables kpt and kptnrm are',ch10,&
1602           dt%kpt(1,ikpt)/dt%kptnrm,dt%kpt(2,ikpt)/dt%kptnrm,dt%kpt(3,ikpt)/dt%kptnrm,ch10,&
1603           'while they must be between -1.0_dp and 1.0_dp (included).',ch10,&
1604           'Action: check kpt and kptnrm in the input file.'
1605          ABI_ERROR_NOSTOP(msg, ierr)
1606        end if
1607      end do
1608    end do
1609 
1610 !  jellslab
1611    call chkint_eq(0,0,cond_string,cond_values,ierr,'jellslab',dt%jellslab,2,(/0,1/),iout)
1612 
1613    if (dt%jellslab==1) then
1614      if(dt%nimage>1)then
1615        cond_string(1)='nimage' ; cond_values(1)=dt%nimage
1616        call chkint_eq(1,1,cond_string,cond_values,ierr,'jellslab',dt%jellslab,1,(/0/),iout)
1617      end if
1618 !    slabwsrad must be positive
1619      cond_string(1)='jellslab' ; cond_values(1)=dt%jellslab
1620      call chkdpr(1,1,cond_string,cond_values,ierr,'slabwsrad',dt%slabwsrad,1,zero,iout)
1621 !    slabzbeg must be positive
1622      call chkdpr(1,1,cond_string,cond_values,ierr,'slabzbeg',dt%slabzbeg,1,zero,iout)
1623 !    slabzend must be bigger than slabzbeg
1624      call chkdpr(1,1,cond_string,cond_values,ierr,'slabzend',dt%slabzend,1,dt%slabzbeg,iout)
1625 !    rprimd(3,3) must be bigger than slabzend
1626      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd33',rprimd(3,3),1,dt%slabzend,iout)
1627 !    Third real space primitive translation has to be orthogonal to the other ones,
1628 !    actually, for convenience it is useful that rprimd is something like:
1629 !    a  b  0
1630 !    c  d  0
1631 !    0  0  e
1632      if(abs(rprimd(1,3))+abs(rprimd(2,3))+abs(rprimd(3,1))+abs(rprimd(3,2))>tol12) then
1633        write(msg,'(3a)')&
1634         'Third real space vector is not orthogonal to the other ones,',ch10,&
1635         'this is needed to use jellium'
1636        ABI_ERROR_NOSTOP(msg, ierr)
1637      end if
1638 
1639 !    Atoms have to be placed in the vacuum space
1640      do iatom=1,natom
1641        zatom=(dt%xred_orig(3,iatom,intimage)-anint(dt%xred_orig(3,iatom,intimage)-half+tol6))*rprimd(3,3)
1642        if(abs(zatom-dt%slabzbeg)<tol8 .or. abs(zatom-dt%slabzend)<tol8) then
1643          if(dt%znucl(dt%typat(iatom))>tol6) then
1644            write(msg,'(a,i0,a)')'atom number=',iatom,' lies precisely on the jellium edge !'
1645            ABI_WARNING(msg)
1646          end if
1647          cycle
1648        end if
1649        if(zatom>dt%slabzbeg .and. zatom<dt%slabzend) then
1650          write(msg,'(a,i0,a)')' atom number=',iatom,' is inside the jellium slab.'
1651          ABI_ERROR_NOSTOP(msg, ierr)
1652        end if
1653      end do
1654    end if
1655 
1656 !  kssform
1657    call chkint_eq(0,0,cond_string,cond_values,ierr,'kssform',dt%kssform,3,(/0,1,3/),iout)
1658 
1659    if (dt%kssform/=0 .and. dt%nbandkss/=0) then ! Check for outkss limitations.
1660      call wrtout(std_out," Checking if input is consistent with KSS generation")
1661      call chkint_eq(0,0,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,1,(/0/),iout)
1662      call chkint_eq(0,0,cond_string,cond_values,ierr,'iomode',dt%iomode,2,(/IO_MODE_FORTRAN,IO_MODE_ETSF/),iout)
1663    end if
1664 
1665 !  localrdwf
1666    call chkint_eq(0,0,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,2,(/0,1/),iout)
1667    if(dt%mkmem==0)then
1668      cond_string(1)='mkmem' ; cond_values(1)=dt%mkmem
1669      call chkint_eq(1,1,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,1,(/1/),iout)
1670    end if
1671    if(dt%mkqmem==0)then
1672      cond_string(1)='mkqmem' ; cond_values(1)=dt%mkqmem
1673      call chkint_eq(1,1,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,1,(/1/),iout)
1674    end if
1675    if(dt%mk1mem==0)then
1676      cond_string(1)='mk1mem' ; cond_values(1)=dt%mk1mem
1677      call chkint_eq(1,1,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,1,(/1/),iout)
1678    end if
1679    if(dt%iomode==IO_MODE_MPI)then
1680      cond_string(1)='iomode' ; cond_values(1)=dt%iomode
1681      call chkint_eq(1,1,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,1,(/1/),iout)
1682    end if
1683 
1684 
1685 !  LOTF
1686 #if defined HAVE_LOTF
1687    if (dt%ionmov==23) then
1688      write(msg, '(a,a)' ) ch10, '=== LOTF METHOD ================================================================'
1689      call wrtout(ab_out,msg)
1690      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
1691      call chkint_eq(0,1,cond_string,cond_values,ierr,'lotf_classic',dt%lotf_classic,1,(/5/),iout)
1692      call chkint_ge(0,1,cond_string,cond_values,ierr,'lotf_nitex',dt%lotf_nitex,1,iout)
1693      call chkint_ge(0,1,cond_string,cond_values,ierr,'lotf_nneigx',dt%lotf_nneigx,2,iout)
1694      call chkint_eq(0,1,cond_string,cond_values,ierr,'lotf_version',dt%lotf_version,1,(/2/),iout)
1695    end if
1696 #endif
1697 
1698 ! lw_flexo
1699   call chkint_eq(0,0,cond_string,cond_values,ierr,'lw_flexo',dt%lw_flexo,5,(/0,1,2,3,4/),iout)
1700   if(dt%lw_flexo/=0)then
1701     cond_string(1)='lw_flexo' ; cond_values(1)=dt%lw_flexo
1702     call chkint_eq(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_LONGWAVE/),iout)
1703   end if
1704 
1705 ! lw_qdrpl
1706   call chkint_eq(0,0,cond_string,cond_values,ierr,'lw_qdrpl',dt%lw_qdrpl,2,(/0,1/),iout)
1707   if(dt%lw_qdrpl/=0)then
1708     cond_string(1)='lw_qdrpl' ; cond_values(1)=dt%lw_qdrpl
1709     call chkint_eq(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_LONGWAVE/),iout)
1710   end if
1711 
1712 ! lw_natopt
1713   call chkint_eq(0,0,cond_string,cond_values,ierr,'lw_natopt',dt%lw_natopt,2,(/0,1/),iout)
1714   if(dt%lw_natopt/=0)then
1715     cond_string(1)='lw_natopt' ; cond_values(1)=dt%lw_natopt
1716     call chkint_eq(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_LONGWAVE/),iout)
1717   end if
1718 
1719 !  magconon
1720    call chkint_eq(0,0,cond_string,cond_values,ierr,'magconon',dt%magconon,3,(/0,1,2/),iout)
1721 !!  impose nspden 4 for the moment and spinors
1722 !   if (dt%magconon == 1) then
1723 !     if (dt%nspinor /= 2 .or. dt%nspden /= 4) then
1724 !       write (msg, '(4a)') &
1725 !&       ' magnetization direction constraint is only compatible with non-collinear calculations', ch10,&
1726 !&       ' Action: set nspinor 2 and nspden 4 in the input file.'
1727 !       ABI_ERROR_NOSTOP(msg,ierr)
1728 !     end if
1729 !   end if
1730 
1731 !  macro_uj
1732    if(dt%macro_uj/=0) then
1733      if (dt%ionmov/=0) then
1734        write(msg, '(3a,i2,2a,i2,3a)' )&
1735         'Determination of U can not be combined with ionic movements.',ch10,&
1736         'Here  ionmov= ',dt%ionmov,ch10,&
1737         'and macro_uj=',dt%macro_uj,'.',ch10,&
1738         'Action: change ionmov in input file.'
1739        ABI_ERROR_NOSTOP(msg, ierr)
1740      else if (dt%nstep<3) then
1741        write(msg, '(3a,i1,2a,i2,3a)' )&
1742         'Determination of U needs at least 3 scf steps:',ch10,&
1743         ' nstep = ',dt%nstep,ch10,&
1744         ' and macro_uj=',dt%macro_uj,'.',ch10,&
1745         'Action: increase nstep in input file.'
1746        ABI_ERROR_NOSTOP(msg, ierr)
1747      else if ((dt%pawujv==0.0d0).or.(sum(abs(dt%atvshift(1:dt%natvshift,1:dt%nsppol,dt%pawujat)))<1.0d-9)) then
1748        write(msg,'(5a)')&
1749        'pawujv and/or atvshift found to be 0.0d0.',ch10,&
1750        'When engaging the linear response procedure, the perturbation strength',ch10,&
1751        'must be non-zero. Action: change pawujv and/or atvshift to a non-zero value.'
1752        call flush_unit(std_out)
1753        ABI_ERROR(msg)
1754      end if
1755    end if
1756 
1757 !  mep_solver
1758    call chkint_eq(0,0,cond_string,cond_values,ierr,'mep_solver',dt%mep_solver,5,(/0,1,2,3,4/),iout)
1759 !  String method
1760    if(dt%imgmov==2) then
1761      cond_string(1)='imgmov'      ; cond_values(1)=dt%imgmov
1762 !    Some restriction for the solver
1763      if(dt%string_algo==0)then
1764        cond_string(2)='string_algo' ; cond_values(2)=dt%string_algo
1765        call chkint_eq(1,1,cond_string,cond_values,ierr,'mep_solver',dt%mep_solver,1,(/0/),iout)
1766      end if
1767      if(dt%string_algo==1.or.dt%string_algo==2)then
1768        cond_string(2)='string_algo' ; cond_values(2)=dt%string_algo
1769        call chkint_eq(1,1,cond_string,cond_values,ierr,'mep_solver',dt%mep_solver,2,(/0,4/),iout)
1770      end if
1771    end if
1772 !  NEB
1773    if(dt%imgmov==5)then
1774      cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
1775 !    Some restriction for the solver
1776      call chkint_eq(1,1,cond_string,cond_values,ierr,'mep_solver',dt%mep_solver,4,(/0,1,2,3/),iout)
1777 !    Static image energy is needed if spring constant is variable
1778      if (abs(dt%neb_spring(1)-dt%neb_spring(2))>=tol8.and.dt%istatimg==0) then
1779        write(msg, '(7a)' )&
1780         'When using variable NEB spring constants (which is the default for CI-NEB),',ch10,&
1781         'all the energies of the cell images are needed (including static images!).',ch10,&
1782         'You cannot use istatimg=0!',ch10,&
1783         'Action: put istatimg=1 in input file.'
1784        ABI_ERROR_NOSTOP(msg, ierr)
1785      end if
1786 !    Static image energy is needed for CI-NEB or improved tangent
1787      if ((dt%neb_algo==1.or.dt%neb_algo==2).and.dt%istatimg==0) then
1788        write(msg, '(7a)' )&
1789         'When using Improved-tangent-NEB or CI-NEB,',ch10,&
1790         'all the energies of the cell images are needed (including static images!).',ch10,&
1791         'You cannot use istatimg=0!',ch10,&
1792         'Action: put istatimg=1 in input file.'
1793        ABI_ERROR_NOSTOP(msg, ierr)
1794      end if
1795    end if
1796 
1797 !  mffmem
1798    call chkint_eq(0,0,cond_string,cond_values,ierr,'mffmem',dt%mffmem,2,(/0,1/),iout)
1799 
1800 !  mixalch_orig
1801 !  For each type of atom, the sum of the psp components must be one.
1802    do iimage=1,dt%nimage
1803      if(dt%ntypalch>0)then
1804        do itypat=1,dt%ntypalch
1805          sumalch=sum(dt%mixalch_orig(:,itypat,iimage))
1806          if(abs(sumalch-one)>tol10)then
1807            if(dt%npspalch<=6)then
1808              write(msg, '(2a,6es12.4)' )ch10,' chkinp : mixalch(:,itypat,iimage)=',dt%mixalch_orig(:,itypat,iimage)
1809            end if
1810            call wrtout(iout,msg)
1811            call wrtout(std_out,  msg)
1812            write(msg, '(a,i4,2a,i4,2a,f8.2,4a)' )&
1813             'For the alchemical atom number',itypat,ch10,&
1814             'image number',iimage,ch10,&
1815             'the sum of the pseudopotential coefficients is',sumalch,ch10,&
1816             'while it should be one.',ch10,&
1817             'Action: check the content of the input variable mixalch.'
1818            ABI_ERROR_NOSTOP(msg, ierr)
1819          end if
1820        end do
1821      end if
1822    end do
1823 
1824 !  mixesimgf
1825 !  The sum of the mixing image factors must be one
1826    if(dt%imgmov==6)then
1827      summix=sum(dt%mixesimgf(1:dt%nimage))
1828      if(abs(summix-one)>tol10)then
1829        write(msg, '(2a,20es12.4)' )ch10,' chkinp : mixesimgf(1:dt%nimage)=',dt%mixesimgf(1:dt%nimage)
1830        call wrtout(iout,msg)
1831        call wrtout(std_out,  msg)
1832        write(msg, '(a,es12.4,4a)' )&
1833         'The sum of the mixing image factors is',summix,ch10,&
1834         'while it should be one.',ch10,&
1835         'Action: check the content of the input variable mixesimgf.'
1836        ABI_ERROR_NOSTOP(msg, ierr)
1837      end if
1838    end if
1839 
1840 !  natom
1841    if(dt%prtgeo>0)then
1842      cond_string(1)='prtgeo' ; cond_values(1)=dt%prtgeo
1843      call chkint_le(1,1,cond_string,cond_values,ierr,'natom',natom,9999,iout)
1844    end if
1845 
1846 !  nband
1847 !  Make sure all nband(nkpt) are > 0
1848    do isppol=1,nsppol
1849      do ikpt=1,nkpt
1850        if (dt%nband(ikpt+(isppol-1)*nkpt)<=0) then
1851          cond_string(1)='ikpt' ; cond_values(1)=ikpt
1852          cond_string(2)='isppol' ; cond_values(2)=isppol
1853          call chkint_ge(0,2,cond_string,cond_values,ierr,'nband',dt%nband(ikpt+(isppol-1)*nkpt),1,iout)
1854        end if
1855      end do
1856    end do
1857    if(nproc/=1.and.nsppol==2.and.usewvl==0)then
1858      do ikpt=1,nkpt
1859        if (dt%nband(ikpt)/=dt%nband(ikpt+nkpt)) then
1860          write(msg, '(5a,i4,a,2i5,a)' )&
1861           'the number of bands in the spin up case must be equal to',ch10,&
1862           'the number of bands in the spin down case.',ch10,&
1863           'This is not the case for the k point number :',ikpt,&
1864           'The number of bands spin up and down are :',dt%nband(ikpt),dt%nband(ikpt+nkpt),&
1865           'Action: change nband, or use the sequential version of ABINIT.'
1866          ABI_ERROR_NOSTOP(msg, ierr)
1867        end if
1868      end do
1869    end if
1870 
1871 !  nbandkss
1872 !  Must be greater or equal to -1
1873    call chkint_ge(0,0,cond_string,cond_values,ierr,'nbandkss',dt%nbandkss,-1,iout)
1874 !  When ionmov/=0
1875    if(dt%ionmov/=0 .and. dt%nbandkss/=0)then
1876      write(msg,'(11a)')&
1877       'Ions (or cell) are allowed to move (ionmov/=0),',ch10,&
1878       'and a _KSS file is requested (nbandkss/=0).',ch10,&
1879       'A _KSS file will be created at each geometry-optimisation step.',ch10,&
1880       'Note that this is time consuming !',ch10,&
1881       'Action: use datasets (one for geometry optimisation,',ch10,&
1882       '        one for states output).'
1883      ABI_WARNING(msg)
1884    end if
1885 
1886 !  nbdblock
1887 !  Must be greater or equal to 1
1888    call chkint_ge(0,0,cond_string,cond_values,ierr,'nbdblock',dt%nbdblock,1,iout)
1889 !  When wfoptalg==0, nbdblock must be 1
1890    if(mod(dt%wfoptalg,10)==0)then
1891      cond_string(1)='wfoptalg' ; cond_values(1)=dt%wfoptalg
1892      call chkint_eq(1,1,cond_string,cond_values,ierr,'nbdblock',dt%nbdblock,1,(/1/),iout)
1893    end if
1894 !  When wfoptalg==2, nbdblock must be 1
1895    if(dt%wfoptalg==2)then
1896      cond_string(1)='wfoptalg' ; cond_values(1)=dt%wfoptalg
1897      call chkint_eq(1,1,cond_string,cond_values,ierr,'nbdblock',dt%nbdblock,1,(/1/),iout)
1898    end if
1899 !  When wfoptalg==3, nbdblock must be 1, and iscf must be -2
1900    if(dt%wfoptalg==3)then
1901      cond_string(1)='wfoptalg' ; cond_values(1)=dt%wfoptalg
1902      call chkint_eq(1,1,cond_string,cond_values,ierr,'nbdblock',dt%nbdblock,1,(/1/),iout)
1903      call chkint_eq(1,1,cond_string,cond_values,ierr,'iscf',dt%iscf,1,(/-2/),iout)
1904    end if
1905 !  When wfoptalg==4, nbdblock must be a divisor of nband
1906    if(mod(dt%wfoptalg,10)==4.and.dt%optdriver==RUNL_GSTATE)then
1907      do isppol=1,nsppol
1908        do ikpt=1,nkpt
1909          if(mod(dt%nband(ikpt+(isppol-1)*nkpt),dt%nbdblock)/=0) then
1910            write(msg, '(5a)' )&
1911             'For the moment, when wfoptalg=4,',ch10,&
1912             'nband must be a multiple of nbdblock.',ch10,&
1913             'Action: check the value of the input variable nbdblock.'
1914            ABI_ERROR_NOSTOP(msg, ierr)
1915          end if
1916        end do
1917      end do
1918    end if
1919 
1920 !  nberry
1921 !  must be between 0 and 20
1922    if(dt%berryopt/=0)then
1923      call chkint_ge(0,0,cond_string,cond_values,ierr,'nberry',dt%nberry,0,iout)
1924      call chkint_le(0,0,cond_string,cond_values,ierr,'nberry',dt%nberry,20,iout)
1925      if(xmpi_paral==1)then
1926 !      MPI Parallel case
1927        if (dt%nberry/=0.and.dt%berryopt>0.and.&
1928            dt%berryopt/= 4.and.dt%berryopt/= 5.and.dt%berryopt/= 6.and.dt%berryopt/= 7.and.&
1929            dt%berryopt/=14.and.dt%berryopt/=15.and.dt%berryopt/=16.and.dt%berryopt/=17) then
1930          write(msg,'(a,a,a,a,a,i4,a,a,a)')&
1931           'Berry phase calculation of polarisation with positive berryopt is not',ch10,&
1932           'allowed in the parallel version of ABINIT.',ch10,&
1933           'So, the value of nberry=',dt%nberry,' is not allowed,',ch10,&
1934           'Action: change berryopt to negative values or change nberry, or use the sequential version.'
1935          ABI_ERROR_NOSTOP(msg, ierr)
1936        end if
1937      end if
1938    end if
1939 
1940    if (dt%optcell /=0 .and. dt%berryopt == 4)  then
1941      write(msg,'(a,a,a,a,a,a,a,a,a,a,a,a,a)') ch10,&
1942       ' chkinp : WARNING -',ch10,&
1943       '  Constant unreduced E calculation with relaxation of cell parameters is allowed.',ch10,&
1944       '  But we strongly recommend users to use reduced ebar calculation (berryopt=14)',ch10,&
1945       '  with the relaxation of cell parameters, for internal consistency purpose.',ch10, &
1946       '  For more information, please refer to "M. Stengel, N.A. Spaldin and D.Vanderbilt,', ch10, &
1947       '  Nat. Phys., 5, 304,(2009)" and its supplementary notes.', ch10 ! [[cite:Stengel2009]]
1948      call wrtout(ab_out,msg)
1949      call wrtout(std_out,msg)
1950    end if
1951 
1952    if (dt%optcell /=0 .and. (dt%berryopt == 6 ))  then
1953      write(msg,'(12a)') ch10,&
1954       ' chkinp : WARNING -',ch10,&
1955       '  Constant unreduced D calculation with relaxation of cell parameters is allowed.',ch10,&
1956       '  But we strongly recommend users to use reduced d calculation (berryopt=16)',ch10,&
1957       '  with the relaxation of cell parameters, for internal consistency purpose.',ch10, &
1958       '  For more information, please refer to "M. Stengel, N.A. Spaldin and D.Vanderbilt,', ch10, &
1959       '  Nat. Phys., 5, 304,(2009)" and its supplementary notes.' ! [[cite:Stengel2009]]
1960      call wrtout(ab_out,msg)
1961      call wrtout(std_out,msg)
1962    end if
1963 
1964 !  ndynimage
1965 !  Must be greater or equal to 1
1966    call chkint_ge(0,0,cond_string,cond_values,ierr,'ndynimage',dt%ndynimage,1,iout)
1967 
1968 !  neb_algo
1969    call chkint_eq(0,0,cond_string,cond_values,ierr,'neb_algo',dt%neb_algo,4,(/0,1,2,3/),iout)
1970 
1971 !  nfft and nfftdg
1972 !  Must have nfft<=nfftdg
1973    if (usepaw==1) then
1974      nfft  =dt%ngfft(1)  *dt%ngfft(2)  *dt%ngfft(3)
1975      nfftdg=dt%ngfftdg(1)*dt%ngfftdg(2)*dt%ngfftdg(3)
1976      cond_string(1)='nfft' ; cond_values(1)=nfft
1977      call chkint(1,1,cond_string,cond_values,ierr,'nfftdg',nfftdg,1,(/0/),1,nfft,iout) ! Must be 0 or nfft
1978    end if
1979 
1980 !  diismemory
1981 !  Must be greater or equal to 1
1982    call chkint_ge(0,0,cond_string,cond_values,ierr,'diismemory',dt%diismemory,1,iout)
1983 
1984 !  nimage
1985 !  Must be greater or equal to 1
1986    call chkint_ge(0,0,cond_string,cond_values,ierr,'nimage',dt%nimage,1,iout)
1987    if (usewvl==1) then
1988      cond_string(1)='usewvl' ; cond_values(1)=usewvl
1989      call chkint_eq(1,1,cond_string,cond_values,ierr,'nimage',dt%nimage,1,(/1/),iout)
1990    end if
1991    if (optdriver/=RUNL_GSTATE) then
1992      cond_string(1)='optdriver' ; cond_values(1)=optdriver
1993      call chkint_eq(1,1,cond_string,cond_values,ierr,'nimage',dt%nimage,1,(/1/),iout)
1994    end if
1995    if (dt%tfkinfunc==2) then
1996      cond_string(1)='tfkinfunc' ; cond_values(1)=dt%tfkinfunc
1997      call chkint_eq(1,1,cond_string,cond_values,ierr,'nimage',dt%nimage,1,(/1/),iout)
1998    end if
1999    if (dt%prtxml==1) then
2000      cond_string(1)='prtxml' ; cond_values(1)=dt%prtxml
2001      call chkint_eq(1,1,cond_string,cond_values,ierr,'nimage',dt%nimage,1,(/1/),iout)
2002    end if
2003    if (dt%imgmov==9.or.dt%imgmov==13) then
2004      if (dt%pitransform==1.and.(mod(dt%nimage,2)/=0)) then
2005        write(msg,'(6a)')ch10,&
2006         'Path-Integral Molecular Dynamics (imgmov=9,13)',ch10,&
2007         'in normal mode tranformation (pitransform=1).',ch10,&
2008         'requires nimage to be even!'
2009        ABI_ERROR_NOSTOP(msg, ierr)
2010      end if
2011    end if
2012    if (dt%imgmov==10.and.dt%pitransform>0) then
2013      write(msg,'(4a)')ch10,&
2014       'Path-Integral Molecular Dynamics (imgmov=10) with QTB',ch10,&
2015       'requires primitive coordinates (pitransform=0).'
2016      ABI_ERROR_NOSTOP(msg, ierr)
2017    end if
2018 
2019 !  nkpt
2020 !  Must be greater or equal to 1
2021    call chkint_ge(0,0,cond_string,cond_values,ierr,'nkpt',nkpt,1,iout)
2022 !  If prtdos>=2, nkpt must be greater or equal to 2
2023    if(dt%prtdos>=2)then
2024      cond_string(1)='prtdos' ; cond_values(1)=dt%prtdos
2025      call chkint_ge(1,1,cond_string,cond_values,ierr,'nkpt',nkpt,2,iout)
2026    end if
2027 !  Must be smaller than 50 if iscf=-2 (band structure)
2028 !  while prteig=0 and prtvol<2, except if kptopt>0
2029    if(dt%iscf==-2 .and. dt%prteig==0 .and. dt%prtvol<2 .and. dt%kptopt<=0)then
2030      cond_string(1)='iscf'   ; cond_values(1)=dt%iscf
2031      cond_string(2)='prteig' ; cond_values(2)=dt%prteig
2032      cond_string(3)='prtvol' ; cond_values(3)=dt%prtvol
2033      call chkint_le(1,3,cond_string,cond_values,ierr,'nkpt',nkpt,50,iout)
2034    end if
2035 
2036 !  nloalg(1)= nloc_alg
2037    if(dt%useylm==0) then
2038 !    Must be 2, 3, 4
2039      call chkint_eq(0,0,cond_string,cond_values,ierr,'nloc_alg',dt%nloalg(1),3,(/2,3,4/),iout)
2040    else
2041 !    Must be between 2 and 10
2042      call chkint_eq(0,0,cond_string,cond_values,ierr,'nloc_alg',dt%nloalg(1),9,(/2,3,4,5,6,7,8,9,10/),iout)
2043    end if
2044 
2045 !  nloc_mem= nloalg(2)*(nloalg(3)+1)
2046 !  nloalg(2) must be -1 or 1 ; nloalg(3) is 0 or 1.
2047    nloc_mem=dt%nloalg(2)*(dt%nloalg(3)+1)
2048    call chkint_eq(0,0,cond_string,cond_values,ierr,'nloc_mem',nloc_mem,4,(/-2,-1,1,2/),iout)
2049 
2050 !  npband
2051 !  Must be greater or equal to 1
2052    call chkint_ge(0,0,cond_string,cond_values,ierr,'npband',dt%npband,1,iout)
2053 
2054 !  npfft
2055 !  Must be greater or equal to 1
2056    call chkint_ge(0,0,cond_string,cond_values,ierr,'npfft',dt%npfft,1,iout)
2057 !  If usepaw==1 and pawmixdg==0, npfft must be equal to 1
2058    if(usepaw==1 .and. dt%pawmixdg==0)then
2059      cond_string(1)='usepaw  ' ; cond_values(1)=usepaw
2060      cond_string(2)='pawmixdg' ; cond_values(2)=dt%pawmixdg
2061      call chkint_eq(1,2,cond_string,cond_values,ierr,'npfft',dt%npfft,1,(/1/),iout)
2062    end if
2063 #ifdef HAVE_OPENMP
2064    if (dt%wfoptalg==114 .or. dt%wfoptalg==1 .or. dt%wfoptalg==111) then
2065      if ( xomp_get_num_threads(.true.) > 1 ) then
2066        if ( dt%npfft > 1 ) then
2067          write(msg,'(4a,i4,a,i4,a)') "Using LOBPCG algorithm (wfoptalg=114), the FFT parallelization is not ",&
2068           "compatible with multiple threads.",ch10,"Please set npfft to 1 (currently npfft=",dt%npfft,&
2069           ") or export OMP_NUM_THREADS=1 (currently: the number of threads is ",xomp_get_num_threads(.true.),")"
2070          ABI_ERROR_NOSTOP(msg, ierr)
2071        end if
2072        if ( dt%npspinor > 1 ) then
2073          write(msg,'(4a,i1,a,i4,a)') "Using LOBPCG algorithm (wfoptalg=114), the parallelization on spinorial components is not",&
2074           " compatible with multiple threads.",ch10,"Please set npspinor to 1 (currently npspinor=",dt%npspinor,&
2075           ") or export OMP_NUM_THREADS=1 (currently: the number of threads is ",xomp_get_num_threads(.true.),")"
2076          ABI_ERROR_NOSTOP(msg, ierr)
2077        end if
2078      end if
2079    end if
2080 #endif
2081    !Not yet implemented
2082    if (dt%wfoptalg==111 .and. dt%npfft > 1) then
2083      write(msg,'(5a,i3,5a)') "The FFT parallelization (npfft>1) is not compatible ",&
2084 &      "with Chebyshev filtering algorithm (wfoptalg=111)!",ch10,&
2085 &      "Please use multithreading instead (export OMP_NUM_THREADS=...)",&
2086 &      " and set npfft to 1 (currently npfft=",dt%npfft,&
2087 #ifdef HAVE_OPENMP
2088 &      ")."
2089 #else
2090 &      ").",ch10,"But for that, you need to recompile ABINIT for multithreading,",ch10,&
2091 &      "setting --enable-openmp at configure stage."
2092 #endif
2093      ABI_ERROR_NOSTOP(msg, ierr)
2094    end if
2095 
2096 !  npimage
2097 !  Must be greater or equal to 1
2098    call chkint_ge(0,0,cond_string,cond_values,ierr,'npimage',dt%npimage,1,iout)
2099 !  At present, parallelism over images is not coded ...
2100 !  call chkint_eq(0,0,cond_string,cond_values,ierr,'npimage',dt%npimage,1,(/1/),iout)
2101 
2102 !  np_spkpt
2103 !  Must be greater or equal to 1
2104    call chkint_ge(0,0,cond_string,cond_values,ierr,'np_spkpt',dt%np_spkpt,1,iout)
2105 
2106 !  nppert
2107    call chkint_ge(0,0,cond_string,cond_values,ierr,'nppert',dt%nppert,1,iout)
2108 
2109 !  nproc
2110    if (response==1.and.nsppol==2.and.nproc>1.and.modulo(nproc,2)>0) then
2111      write(msg,'(3a)' ) &
2112       'For DFPT parallel calculations on spin-polarized systems (nsppol=2),',ch10,&
2113       'the number of processors must be even!'
2114      ABI_ERROR_NOSTOP(msg, ierr)
2115    end if
2116 
2117 !  nproj
2118 !  If there is more than one projector for some angular momentum channel of some pseudopotential
2119    do ilang=0,3
2120      nprojmax(ilang)=pspheads(1)%nproj(ilang)
2121      if(npsp>=2)then
2122        do ii=2,npsp
2123          nprojmax(ilang)=max(pspheads(ii)%nproj(ilang),nprojmax(ilang))
2124        end do
2125      end if
2126    end do
2127 
2128 !  npspinor
2129 !  Must be equal to 1 or 2
2130    call chkint_eq(0,0,cond_string,cond_values,ierr,'npspinor',dt%npspinor,2,(/1,2/),iout)
2131 !  If nspinor==1, npspinor must be equal to 1
2132    if(dt%nspinor==1 )then
2133      cond_string(1)='nspinor' ; cond_values(1)=dt%nspinor
2134      call chkint_eq(0,1,cond_string,cond_values,ierr,'npspinor',dt%npspinor,1,(/1/),iout)
2135    end if
2136 
2137 !  npvel (must be positive)
2138    call chkint_ge(0,0,cond_string,cond_values,ierr,'npvel',dt%npvel,0,iout)
2139 
2140 !  npwkss
2141 !  Must be greater or equal to -1
2142    call chkint_ge(0,0,cond_string,cond_values,ierr,'npwkss',dt%npwkss,-1,iout)
2143 
2144 !  nqpt
2145    call chkint_eq(0,0,cond_string,cond_values,ierr,'nqpt',dt%nqpt,2,(/0,1/),iout)
2146 
2147 !  nscforder
2148    call chkint_eq(0,0,cond_string,cond_values,ierr,'nscforder',dt%nscforder,10,(/8,14,16,20,24,30,40,50,60,100/),iout)
2149 
2150 !  nshiftk
2151    call chkint_eq(0,0,cond_string,cond_values,ierr,'nshiftk',dt%nshiftk,8,(/1,2,3,4,5,6,7,8/),iout)
2152 !  If chksymbreak=1, nshiftk must be equal to 1, 2, 4.
2153    if(dt%chksymbreak==1 )then
2154      cond_string(1)='chksymbreak' ; cond_values(1)=dt%chksymbreak
2155      call chkint_eq(0,1,cond_string,cond_values,ierr,'nshiftk',dt%nshiftk,3,(/1,2,4/),iout)
2156    end if
2157 
2158 !  nspden
2159    call chkint_eq(0,0,cond_string,cond_values,ierr,'nspden',nspden,3,(/1,2,4/),iout)
2160 
2161    if(nsppol==2)then  !  When nsppol=2, nspden must be 2
2162      cond_string(1)='nsppol' ; cond_values(1)=nsppol
2163      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspden',nspden,1,(/2/),iout)
2164    end if
2165    if(nspden==2 .and. nsppol==1 .and. response==1)then
2166      write(msg,'(13a)')&
2167       'nspden==2 together with nsppol==1 is not allowed',ch10,&
2168       'for response function calculations.',ch10,&
2169       'For antiferromagnetic materials, use nspden==2 and nsppol=2.',ch10,&
2170       'In this case, Shubnikov symmetries will be used to decrease',ch10,&
2171       'the number of perturbations. In a future version, it will also be',ch10,&
2172       'used to decrease the number of spin components (to be coded).',ch10,&
2173       'Action: change nsppol to 1, or check nspden.'
2174      ABI_ERROR_NOSTOP(msg, ierr)
2175    end if
2176    if(nspden==4.and.response==1)then
2177      write(msg,'(3a)')&
2178       'nspden==4 allowed in response formalism.',ch10,&
2179       'BUT Non collinear magnetism under development in perturbative treatment.'
2180      ABI_WARNING(msg)
2181    end if
2182 !  TR symmetry not allowed for NC magnetism, in the present version
2183 !  (to be investigated further)
2184    if (nspden==4.and.(dt%kptopt==1.or.dt%kptopt==2)) then
2185      write(msg, '(8a)' ) ch10,&
2186       'When non-collinear magnetism is activated (nspden=4),',ch10,&
2187       'time-reversal symmetry cannot be used in the present',ch10,&
2188       'state of the code (to be checked and validated).',ch10,&
2189       'Action: choose kptopt different from 1 or 2.'
2190      ABI_ERROR_NOSTOP(msg, ierr)
2191    end if
2192 !  When densfor_pred<0 or 3, nspden must be 1 or 2
2193    if(dt%densfor_pred<0.or.dt%densfor_pred==3)then
2194      cond_string(1)='densfor_pred' ; cond_values(1)=dt%densfor_pred
2195      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspden',nspden,2,(/1,2/),iout)
2196    end if
2197 !  When ionmov=4 and iscf>10, nspden must be 1 or 2
2198    if(dt%ionmov==4.and.dt%iscf>10)then
2199      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
2200      cond_string(2)='iscf' ; cond_values(2)=dt%iscf
2201      call chkint_eq(1,2,cond_string,cond_values,ierr,'nspden',nspden,2,(/1,2/),iout)
2202    end if
2203 !  When iprcel>49, nspden must be 1 or 2
2204    if(mod(dt%iprcel,100)>49)then
2205      cond_string(1)='iprcel' ; cond_values(1)=dt%iprcel
2206      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspden',nspden,2,(/1,2/),iout)
2207    end if
2208    if(xc_is_mgga.and.nspden==4)then
2209      write(msg, '(3a)' )&
2210       'The meta-GGA XC kernel is not yet implemented for non-colinear magnetism case',ch10, &
2211       'Please use "nspden=1 or 2".'
2212      ABI_ERROR(msg)
2213    end if
2214 !  When abs(usepawu) is not 0, 1, 4, 10 or 14, nspden must be 1 or 2
2215    if( abs(dt%usepawu)/=0 .and. abs(dt%usepawu)/=1 .and. abs(dt%usepawu)/=4 .and. &
2216 &      abs(dt%usepawu)/=10 .and. abs(dt%usepawu)/=14 )then
2217      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
2218      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspden',nspden,2,(/1,2/),iout)
2219    end if
2220 
2221 !  nspinor
2222    call chkint_eq(0,0,cond_string,cond_values,ierr,'nspinor',nspinor,2,(/1,2/),iout)
2223    if(nspden==2)then !  When nspden=2, nspinor must be 1
2224      cond_string(1)='nspden' ; cond_values(1)=nspden
2225      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/1/),iout)
2226    end if
2227 
2228    if(nspden==4)then  !  When nspden=4, nspinor must be 2
2229      cond_string(1)='nspden' ; cond_values(1)=nspden
2230      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/2/),iout)
2231    end if
2232 !  When iscf=-1, nspinor must be 1
2233    if(dt%iscf==-1)then
2234      cond_string(1)='iscf' ; cond_values(1)=dt%iscf
2235 !    Make sure that nsppol is 1
2236      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/1/),iout)
2237    end if
2238 !  spin-orbit is not implemented for the strain perturbation
2239    if(dt%rfstrs/=0)then
2240      cond_string(1)='rfstrs' ; cond_values(1)=dt%rfstrs
2241      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/1/),iout)
2242    end if
2243 !  When usepawu=2 or -2, nspinor must be 1
2244    if(abs(dt%usepawu)==2)then
2245      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
2246 !    Make sure that nspinor is 1
2247      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/1/),iout)
2248    end if
2249 
2250 !  nsppol
2251    call chkint_eq(0,0,cond_string,cond_values,ierr,'nsppol',nsppol,2,(/1,2/),iout)
2252 
2253 !  nstep
2254    call chkint_ge(0,0,cond_string,cond_values,ierr,'nstep',dt%nstep,0,iout)
2255    if(dt%nstep==0)then
2256 !    nstep==0 computation of energy not yet implemented with Fock term, see m_energy.F90
2257      cond_string(1)='usefock' ; cond_values(1)=dt%usefock
2258      if(dt%usefock/=1) then
2259        call chkint_eq(1,1,cond_string,cond_values,ierr,'usefock',dt%usefock,1,(/0/),iout)
2260      else
2261        write(msg,'(a)')&
2262        'For usefock=1 and nstep=0, the Fock energy is not available and will not be computed.'
2263        ABI_WARNING(msg)
2264      endif
2265    endif
2266 
2267 !  nsym
2268    call chkint_ge(0,0,cond_string,cond_values,ierr,'nsym',dt%nsym,1,iout)
2269 !  check if nsym=1 in phonon calculation in finite electric field
2270    if (response==1.and.&
2271       (dt%berryopt== 4.or.dt%berryopt== 6.or.dt%berryopt== 7.or.&
2272        dt%berryopt==14.or.dt%berryopt==16.or.dt%berryopt==17)) then
2273      cond_string(1)='response' ; cond_values(1)=response
2274      cond_string(2)='berryopt' ; cond_values(2)=dt%berryopt
2275      call chkint_eq(1,2,cond_string,cond_values,ierr,'nsym',dt%nsym,1,(/1/),iout)
2276    end if
2277 
2278 !  ntime
2279    call chkint_ge(0,0,cond_string,cond_values,ierr,'ntime',dt%ntime,0,iout)
2280 
2281 !  ntimimage
2282    call chkint_ge(0,0,cond_string,cond_values,ierr,'ntimimage',dt%ntimimage,1,iout)
2283 
2284 !  ntypalch
2285    if (usepaw==1) then
2286      cond_string(1)='usepaw' ; cond_values(1)=dt%usepaw
2287      call chkint_eq(1,1,cond_string,cond_values,ierr,'ntypalch',dt%ntypalch,1,(/0/),iout)
2288    end if
2289 
2290 !  nucdipmom
2291 
2292    if (any(abs(dt%nucdipmom)>tol8)) then
2293 
2294 !    nucdipmom requires PAW
2295      if(usepaw/=1)then
2296        write(msg, '(3a)' )&
2297         'Nuclear dipole moments (variable nucdipmom) input as nonzero but PAW not activated => stop',ch10,&
2298         'Action: re-run with PAW '
2299        ABI_ERROR_NOSTOP(msg, ierr)
2300      end if
2301 
2302 !    nucdipmom requires complex rhoij
2303      if(dt%pawcpxocc/=2)then
2304        write(msg, '(3a)' )&
2305        'Nuclear dipole moments (variable nucdipmom) require complex rhoij => stop',ch10,&
2306        'Action: re-run with pawcpxocc = 2 '
2307        ABI_ERROR_NOSTOP(msg, ierr)
2308      end if
2309 
2310 !    nucdipmom requires no force or stress calculation
2311      if(dt%optforces/=0 .OR. dt%optstress/=0)then
2312        write(msg, '(3a)' )&
2313        'Nuclear dipole moments (variable nucdipmom) cannot be used with force or stress calculations => stop',ch10,&
2314        'Action: re-run with optforces = 0 and optstress = 0 '
2315        ABI_ERROR_NOSTOP(msg, ierr)
2316      end if
2317 
2318 !    nucdipmom requires kptopt 3 or zero
2319      ! if( (dt%kptopt .EQ. 1) .OR. (dt%kptopt .EQ. 2) .OR. (dt%kptopt .EQ. 4) ) then
2320      if( (dt%kptopt .EQ. 1) .OR. (dt%kptopt .EQ. 2) ) then
2321        write(msg, '(a,i4,a,a,a)' )&
2322        ' Nuclear dipole moments (variable nucdipmom) break time reveral symmetry but kptopt = ',dt%kptopt,&
2323        ' => stop ',ch10,&
2324        'Action: re-run with kptopt of 3 or 0 '
2325        ABI_ERROR_NOSTOP(msg, ierr)
2326      end if
2327 
2328      ! nucdipmom is not currently compatible with spinat (this is necessary because both are used in symfind)
2329      if( any(abs(dt%spinat) > tol8) ) then
2330        write(msg, '(3a)' )&
2331         ' Nuclear dipole moments (variable nucdipmom) input as nonzero but spinat is also nonzero => stop',ch10,&
2332         'Action: re-run with spinat zero '
2333        ABI_ERROR_NOSTOP(msg, ierr)
2334      end if
2335 
2336    end if
2337 
2338 !  nzchempot
2339    call chkint_ge(0,0,cond_string,cond_values,ierr,'nzchempot',dt%nzchempot,0,iout)
2340 !  Cannot be used with response functions at present
2341    if (response==1) then
2342      cond_string(1)='response' ; cond_values(1)=response
2343      call chkint_eq(1,1,cond_string,cond_values,ierr,'nzchempot',dt%nzchempot,1,(/0/),iout)
2344    end if
2345    if(dt%nzchempot>0)then
2346      do itypat=1,dt%ntypat
2347        do iz=2,dt%nzchempot
2348          dz=dt%chempot(1,iz,itypat)-dt%chempot(1,iz-1,itypat)
2349          if(dz<-tol12)then
2350            write(msg, '(a,2i6,a,a,d17.10,a,a, a,d17.10,a,a, a,a,a)' )&
2351             ' For izchempot,itypat=',iz,itypat,ch10,&
2352             ' chempot(1,izchempot-1,itypat) = ',dt%chempot(1,iz-1,itypat),' and', ch10,&
2353             ' chempot(1,izchempot  ,itypat) = ',dt%chempot(1,iz  ,itypat),',',ch10,&
2354             ' while they should be ordered in increasing values =>stop',ch10,&
2355             'Action: correct chempot(1,*,itypat) in input file.'
2356            ABI_ERROR_NOSTOP(msg, ierr)
2357          end if
2358        end do
2359        dz=dt%chempot(1,dt%nzchempot,itypat)-dt%chempot(1,1,itypat)
2360        if(dz>one)then
2361          write(msg, '(a,2i6,a,a,d17.10,a,a, a,d17.10,a,a, a,a,a)' )&
2362           ' For nzchempot,itypat=',dt%nzchempot,itypat,ch10,&
2363           ' chempot(1,1,itypat) = ',dt%chempot(1,1,itypat),' and', ch10,&
2364           ' chempot(1,nzchempot  ,itypat) = ',dt%chempot(1,dt%nzchempot,itypat),'.',ch10,&
2365           ' However, the latter should, at most, be one more than the former =>stop',ch10,&
2366           'Action: correct chempot(1,nzchempot,itypat) in input file.'
2367          ABI_ERROR_NOSTOP(msg, ierr)
2368        end if
2369      end do
2370    end if
2371 
2372 !  occ
2373 !  Do following tests only for occopt==0 or 2, when occupation numbers are needed
2374    if ((dt%iscf>0.or.dt%iscf==-1.or.dt%iscf==-3) .and. (dt%occopt==0 .or. dt%occopt==2) ) then
2375      do iimage=1,dt%nimage
2376 !      make sure occupation numbers (occ(n)) were defined:
2377        sumocc=zero
2378        bantot=0
2379        do isppol=1,nsppol
2380          do ikpt=1,nkpt
2381            do iband=1,dt%nband(ikpt+(isppol-1)*nkpt)
2382              bantot=bantot+1
2383              sumocc=sumocc+dt%occ_orig(bantot,iimage)
2384              if (dt%occ_orig(bantot,iimage)<-tol8) then
2385                write(msg, '(a,3i6,a,e20.10,a,a,a)' )&
2386                 'iband,ikpt,iimage=',iband,ikpt,iimage,' has negative occ=',dt%occ_orig(bantot,iimage),' =>stop',ch10,&
2387                 'Action: correct this occupation number in input file.'
2388                ABI_ERROR_NOSTOP(msg, ierr)
2389              end if
2390            end do
2391          end do
2392        end do
2393        if (sumocc<=1.0d-8) then
2394          write(msg, '(a,1p,e20.10,a,a,a)')&
2395           'Sum of occ=',sumocc, ' =>occ not defined => stop',ch10,&
2396           'Action: correct the array occ in input file.'
2397          ABI_ERROR_NOSTOP(msg, ierr)
2398        end if
2399      enddo
2400    end if
2401 
2402 !  occopt
2403    call chkint_eq(0,0,cond_string,cond_values,ierr,'occopt',dt%occopt,10,(/0,1,2,3,4,5,6,7,8,9/),iout)
2404 !  When prtdos==1 or 4, occopt must be between 3 and 8
2405    if(dt%prtdos==1.or.dt%prtdos==4)then
2406      cond_string(1)='prtdos' ; cond_values(1)=dt%prtdos
2407 !    Make sure that occopt is 3,4,5,6,7, or 8
2408      call chkint_eq(1,1,cond_string,cond_values,ierr,'occopt',dt%occopt,7,(/3,4,5,6,7,8,9/),iout)
2409    end if
2410 !  When nsppol==2 and spinmagntarget is the default value (-99.99d0), occopt cannot be 1.
2411    if(nsppol==2.and.dt%occopt==1.and.abs(dt%spinmagntarget+99.99d0)<tol8)then
2412      if(natom/=1 .or. abs(dt%znucl(dt%typat(1))-one)>tol8)then
2413        write(msg,'(a,i3,2a,i3,4a,f7.2,7a)' )&
2414         'This is a calculation with spin-up and spin-down wavefunctions,         ... nsppol=',nsppol,ch10,&
2415         'in which the occupation numbers are to be determined automatically.     ... occopt=',dt%occopt,ch10,&
2416         'However, in this case, the target total spin magnetization',ch10,&
2417         'must be specified, while the default value is observed.                 ... spinmagntarget=',dt%spinmagntarget,ch10,&
2418         'Action: if you are doing an antiferromagnetic calculation, please use nsppol=1 with nspden=2;',ch10,&
2419         'on the other hand, if you are doing a ferromagnetic calculation, either specify your own spinmagntarget,',ch10,&
2420         'or let the code determine the total spin-polarization, by using a metallic value for occopt (e.g. 7 or 4 ...).'
2421        ABI_ERROR_NOSTOP(msg, ierr)
2422      end if
2423    end if
2424 
2425 !  optcell
2426    call chkint_eq(0,0,cond_string,cond_values,ierr,'optcell',dt%optcell,10,(/0,1,2,3,4,5,6,7,8,9/),iout)
2427 !  With dt%berryopt=4, one must have optcell==0
2428 !  if(dt%berryopt==4)then
2429 !  cond_string(1)='berryopt' ; cond_values(1)=dt%berryopt
2430 !  call chkint_eq(1,1,cond_string,cond_values,ierr,'optcell',dt%optcell,1,(/0/),iout)
2431 !  end if
2432 
2433 !  optdcmagpawu
2434    if (dt%usepawu/=0.and.dt%nspden==4) then
2435      call chkint_eq(0,0,cond_string,cond_values,ierr,'optdcmagpawu',dt%optdcmagpawu,3,(/1,2,3/),iout)
2436    end if
2437 
2438 !  Check the value of optdriver
2439    call chkint_eq(0, 0, cond_string, cond_values, ierr, 'optdriver', optdriver, 12,&
2440                   [RUNL_GSTATE,RUNL_RESPFN,RUNL_SCREENING,RUNL_SIGMA,RUNL_NONLINEAR,RUNL_GWR, RUNL_BSE, &
2441                    RUNL_GWLS, RUNL_WFK,RUNL_EPH,RUNL_LONGWAVE,RUNL_RTTDDFT], iout)
2442 
2443    if (response==1.and.all(dt%optdriver/=[RUNL_RESPFN,RUNL_NONLINEAR,RUNL_LONGWAVE])) then
2444      write(msg,'(a,i3,3a,14(a,i2),4a)' )&
2445 &     'The input variable optdriver=',dt%optdriver,ch10,&
2446 &     'This is in conflict with the values of the other input variables,',ch10,&
2447 &     'rfphon=',dt%rfphon,' rfddk=',dt%rfddk,' rf2_dkdk=',dt%rf2_dkdk,' rf2_dkde=',dt%rf2_dkde,&
2448 &     ' rfelfd=',dt%rfelfd,'  rfmagn=',dt%rfmagn,' rfstrs=',dt%rfstrs,' rfuser=',dt%rfuser,&
2449 &     ' d3e_pert1_elfd=',dt%d3e_pert1_elfd,' d3e_pert2_elfd=',dt%d3e_pert2_elfd,' d3e_pert3_elfd=',dt%d3e_pert3_elfd,&
2450 &     ' d3e_pert1_phon=',dt%d3e_pert1_phon,' d3e_pert2_phon=',dt%d3e_pert2_phon,' d3e_pert3_phon=',dt%d3e_pert3_phon,ch10,&
2451 &     'Action: check the values of optdriver, rfphon, rfddk, rf2dkdk, rf2dkde, rfelfd, rfmagn, rfstrs, rfuser,',ch10,&
2452 &     'd3e_pert1_elfd, d3e_pert2_elfd, d3e_pert3_elfd, d3e_pert1_phon, d3e_pert2_phon, and d3e_pert3_phon in your input file.'
2453      ABI_ERROR_NOSTOP(msg, ierr)
2454    end if
2455    if (response==1 .and. (sum(dt%qptn(:)**2)>tol12 .or. nspden==4) .and. &
2456 &      .not.(dt%kptopt==3 .or. dt%kptopt==0 .or. dt%nsym==1 .or. dt%iscf<0)) then
2457      write(msg,'(a,i3,2a,a,3f16.6,2a,2a,a)' )&
2458 &      'The input variable optdriver=',dt%optdriver,' which implies response functions.',ch10,&
2459 &      'Also qptn=',dt%qptn(:),' that is non-zero, or one has a calculation with non-collinear magnetism.',ch10,&
2460 &      'This requires kptopt 3 (or 0 for expert users) or nsym=1, or non-self-consistent calculation (iscf<0).',ch10,&
2461 &      'Set kptopt to 3 to let the code reduce the k with the correct small group of symmetries.'
2462        ABI_ERROR_NOSTOP(msg, ierr)
2463    end if
2464    if (response==1 .and. (sum(dt%qptn(:)**2)<tol12 .and. nspden/=4) .and. &
2465 &      .not.(dt%kptopt==3 .or. dt%kptopt==0 .or. dt%kptopt==2 .or. dt%nsym==1 .or. dt%iscf<0)) then
2466      write(msg,'(a,i3,2a,2a,2a,a)' )&
2467 &      'The input variable optdriver=',dt%optdriver,' which implies response functions.',ch10,&
2468 &      'Also qptn is null, and there is no non-collinear magnetism.',ch10,&
2469 &      'This requires kptopt 3 or 2 (or 0 for expert users) or nsym=1, or non-self-consistent calculation (iscf<0).',ch10,&
2470 &      'Set kptopt to 2 to let the code reduce the k with the correct small group of symmetries.'
2471        ABI_ERROR_NOSTOP(msg, ierr)
2472    end if
2473    if(usepaw==1)then
2474      ! Is optdriver compatible with PAW?
2475      cond_string(1)='usepaw' ; cond_values(1)=usepaw
2476      call chkint_eq(1,1,cond_string,cond_values,ierr,'optdriver',optdriver,9,&
2477         [RUNL_GSTATE,RUNL_RESPFN,RUNL_SCREENING,RUNL_SIGMA,RUNL_BSE,RUNL_WFK,RUNL_NONLINEAR,RUNL_RTTDDFT,RUNL_GWR],iout)
2478    end if
2479 
2480 !  Linear and Non-linear response calculations
2481    !Non-linear response not compatible with spinors
2482    if(nspinor/=1)then
2483      cond_string(1)='nspinor' ; cond_values(1)=nspinor
2484      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,2,(/RUNL_NONLINEAR,RUNL_LONGWAVE/),iout)
2485    end if
2486    !Non-linear response only for insulators
2487    if(dt%occopt/=1 .and. dt%occopt/=2)then
2488      cond_string(1)='occopt' ; cond_values(1)=dt%occopt
2489      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,2,(/RUNL_NONLINEAR,RUNL_LONGWAVE/),iout)
2490    end if
2491    !Non-linear response not compatible with mkmem=0
2492    if(dt%mkmem==0)then
2493      cond_string(1)='mkmem' ; cond_values(1)=dt%mkmem
2494      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_NONLINEAR/),iout)
2495    end if
2496    !Longwave needs all k-points
2497    if(dt%kptopt==1 .or. dt%kptopt==4) then
2498      cond_string(1)='kptopt' ; cond_values(1)=dt%kptopt
2499      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_LONGWAVE/),iout)
2500    end if
2501 
2502    !dkdk and dkde non-linear response only for occopt=1 (insulators)
2503    if (dt%rf2_dkdk==1 .or. dt%rf2_dkdk==2 .or. dt%rf2_dkdk==3) then
2504      cond_string(1)='rf2_dkdk' ; cond_values(1)=dt%rf2_dkdk
2505      call chkint_eq(1,1,cond_string,cond_values,ierr,'occopt',dt%occopt,1,(/1/),iout)
2506    end if
2507    if (dt%rf2_dkdk/=0) then
2508      cond_string(1)='rf2_dkdk' ; cond_values(1)=dt%rf2_dkdk
2509      call chkint_eq(1,1,cond_string,cond_values,ierr,'useylm',dt%useylm,1,(/1/),iout)
2510    end if
2511 
2512    if (dt%rf2_dkde==1) then
2513      cond_string(1)='rf2_dkde' ; cond_values(1)=dt%rf2_dkde
2514      call chkint_eq(1,1,cond_string,cond_values,ierr,'occopt',dt%occopt,1,(/1/),iout)
2515    end if
2516    if (dt%rf2_dkde/=0) then
2517      cond_string(1)='rf2_dkde' ; cond_values(1)=dt%rf2_dkde
2518      call chkint_eq(1,1,cond_string,cond_values,ierr,'useylm',dt%useylm,1,(/1/),iout)
2519    end if
2520 
2521    !PEAD non-linear response only for occopt=1 (insulators)
2522    if(dt%usepead==0.and.dt%optdriver==RUNL_NONLINEAR)then
2523      cond_string(1)='usepead'   ; cond_values(1)=dt%usepead
2524      cond_string(2)='optdriver' ; cond_values(2)=dt%optdriver
2525      call chkint_eq(1,2,cond_string,cond_values,ierr,'occopt',dt%occopt,1,(/1/),iout)
2526    end if
2527    !PAW non-linear response only with DFPT (PEAD not allowed)
2528    if(usepaw==1.and.dt%optdriver==RUNL_NONLINEAR)then
2529      cond_string(1)='usepaw'    ; cond_values(1)=usepaw
2530      cond_string(2)='optdriver' ; cond_values(2)=dt%optdriver
2531      call chkint_eq(1,2,cond_string,cond_values,ierr,'usepead',dt%usepead,1,(/0/),iout)
2532      cond_string(1)='usepaw'    ; cond_values(1)=usepaw
2533      cond_string(2)='optdriver' ; cond_values(2)=dt%optdriver
2534      call chkint_eq(1,2,cond_string,cond_values,ierr,'pawxcdev',dt%pawxcdev,1,(/0/),iout)
2535    end if
2536    !Non-linear response not compatible with autoparal
2537    if(dt%optdriver==RUNL_NONLINEAR)then
2538      cond_string(1)='optdriver' ; cond_values(1)=dt%optdriver
2539      call chkint_eq(1,1,cond_string,cond_values,ierr,'autoparal',dt%autoparal,1,(/0/),iout)
2540    end if
2541    ! !Linear Response function only for LDA/GGA
2542    ! allowed=((xc_is_lda.or.xc_is_gga.or.dt%ixc==0).and.dt%ixc/=50)
2543    ! if(.not.allowed)then
2544    !   cond_string(1)='ixc' ; cond_values(1)=dt%ixc
2545    !   call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_RESPFN/),iout)
2546    ! end if
2547    !PAW+Linear Response+GGA function restricted to pawxcdev=0
2548    !PAW+response_to_strain only allowed for LDA
2549    if (dt%usepaw==1.and.dt%optdriver==RUNL_RESPFN) then
2550      if( xc_is_gga.and. &
2551 &       (dt%rfphon/=0.or.dt%rfelfd==1.or.dt%rfelfd==3.or.dt%rfstrs/=0.or.dt%rf2_dkde/=0) ) then
2552        if (dt%pawxcdev/=0)then
2553          write(msg,'(7a)' )&
2554          'You are performing a DFPT+PAW calculation using a GGA XC functional:',ch10,&
2555          '  This is restricted to pawxcdev = 0!',ch10,&
2556          '  Action: change pawxcdev value in your input file!',ch10,&
2557          '    and be careful to run the preparatory Ground-State calculations also with pawxcdev = 0!'
2558          ABI_ERROR_NOSTOP(msg, ierr)
2559        else
2560          write(msg,'(5a)' )&
2561          'You are performing a DFPT+PAW calculation using a GGA XC functional:',ch10,&
2562          '  - This is restricted to pawxcdev = 0!',ch10,&
2563          '  - Be careful to run the preparatory Ground-State calculations also with pawxcdev = 0!'
2564          ABI_WARNING(msg)
2565        end if
2566        if (dt%rfstrs/=0) then
2567          write(msg,'(3a)' )&
2568          'You are performing a DFPT+PAW calculation using a GGA XC functional:',ch10,&
2569          '  Response to strain perturbation is not yet available!'
2570          ABI_ERROR_NOSTOP(msg, ierr)
2571        end if
2572      end if
2573    end if
2574    !PAW+mGGA function restricted to pawxcdev=0
2575    if (dt%usepaw==1.and.xc_is_mgga.and.dt%pawxcdev/=0) then
2576      write(msg,'(5a)' ) &
2577      'You are performing a PAW calculation using a meta-GGA XC functional:',ch10,&
2578      '  This is restricted to pawxcdev = 0!',ch10,&
2579      '  Action: change pawxcdev value in your input file!'
2580      ABI_ERROR_NOSTOP(msg, ierr)
2581    end if
2582    !Non linear Response function only for LDA (restricted to ixc=3/7/8)
2583    allowed=((xc_is_lda.and.dt%ixc<0).or.dt%ixc==0.or.dt%ixc==3.or.dt%ixc==7.or.dt%ixc==8)
2584    if(.not.allowed)then
2585      cond_string(1)='ixc' ; cond_values(1)=dt%ixc
2586      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_NONLINEAR/),iout)
2587    end if
2588    !Longwave calculation not compatible with nonlinear core corrections
2589    if(dt%optdriver==RUNL_LONGWAVE)then
2590      do ipsp=1,npsp
2591   !    Check that xccc is zero
2592        if (pspheads(ipsp)%xccc/=0) then
2593          write(msg, '(5a,i0,3a)' )&
2594          'For a longwave calculation it is not possible to use norm-conserving pseudopotentials',ch10,&
2595          'with a non-linear core correction.',ch10,&
2596          'However, for pseudopotential number ',ipsp,', there is such a core correction.',ch10,&
2597          'Action: change this pseudopotential file.'
2598          ABI_ERROR_NOSTOP(msg, ierr)
2599        end if
2600      end do
2601    end if
2602    !Longwave calculation function only for useylm=1
2603    if(dt%optdriver==RUNL_LONGWAVE.and.dt%useylm/=1.and.(dt%lw_qdrpl/=0.or.dt%lw_flexo/=0))then
2604     write(msg, '(3a,2a,2a)' )&
2605      'A longwave calculation can only be run with the input variable useylm/=1',ch10 ,&
2606      'for lw_natopt=1, while this seems not to be the case in your input,',ch10,&
2607      'where lw_qdrpl/= and/or lw_flexo/=0.',ch10,&
2608      'Action: change "useylm" value in your input file.'
2609      ABI_ERROR_NOSTOP(msg, ierr)
2610    end if
2611    !Longwave calculation not compatible with PAW
2612    if(dt%optdriver==RUNL_LONGWAVE)then
2613      cond_string(1)='optdriver' ; cond_values(1)=dt%optdriver
2614      call chkint_eq(1,1,cond_string,cond_values,ierr,'usepaw',dt%usepaw,1,(/0/),iout)
2615    endif
2616    !Longwave calculation not compatible with spin-dependent calculations
2617    if(dt%nsppol/=1.or.dt%nspden/=1)then
2618      cond_string(1)='nsppol' ; cond_values(1)=dt%nsppol
2619      cond_string(2)='nspden' ; cond_values(2)=dt%nspden
2620      call chkint_ne(1,2,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_LONGWAVE/),iout)
2621    end if
2622 
2623    if (dt%useylm == 1 .and. dt%usepaw == 0 .and. dt%nspinor == 2 .and. any(pspheads(:)%pspso /= 0)) then
2624      ABI_ERROR_NOSTOP("spin-orbit (pspso /=0 ) with NC pseudos and Yml for nonlop (useyml = 1) not yet allowed.", ierr)
2625    end if
2626 
2627 !  optforces
2628    call chkint_eq(0,0,cond_string,cond_values,ierr,'optforces',dt%optforces,3,(/0,1,2/),iout)
2629 !  When ionmov>0, optforces must be >0
2630    if(dt%ionmov>0)then
2631      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
2632      call chkint_eq(1,1,cond_string,cond_values,ierr,'optforces',dt%optforces,2,(/1,2/),iout)
2633    end if
2634 !  When imgmov>0, optforces must be >0
2635    if(dt%imgmov>0)then
2636      cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
2637      call chkint_eq(1,1,cond_string,cond_values,ierr,'optforces',dt%optforces,2,(/1,2/),iout)
2638    end if
2639 !  When iscf=22, optforces must be 0 or 2
2640    if(dt%iscf==22)then
2641      cond_string(1)='iscf' ; cond_values(1)=dt%iscf
2642      call chkint_eq(1,1,cond_string,cond_values,ierr,'optforces',dt%optforces,2,(/0,2/),iout)
2643    end if
2644 !  When usedmft=1, optforces must be 0
2645    if(dt%usedmft==1)then
2646      cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
2647      call chkint_eq(1,1,cond_string,cond_values,ierr,'optforces',dt%optforces,1,(/0/),iout)
2648    end if
2649 
2650 !  optstress
2651 !  Por mGGA, optstress not yet allowed (temporary, hopefully)
2652    if(dt%optstress>0.and.xc_is_mgga)then
2653      msg='Computation of stress tensor is not yet implemented for meta-GGA XC functionals!'
2654      ABI_ERROR_NOSTOP(msg, ierr)
2655    end if
2656 !  When optcell>0, optstress must be >0
2657    if(dt%optcell>0)then
2658      cond_string(1)='optcell' ; cond_values(1)=dt%optcell
2659      call chkint_eq(1,1,cond_string,cond_values,ierr,'optstress',dt%optstress,1,(/1/),iout)
2660    end if
2661 !  TB09 XC functional cannot provide forces/stresses
2662    if((dt%optforces/=0.or.dt%optstress/=0).and.xc_is_tb09)then
2663      write(msg, '(9a)' ) &
2664 &      'When the selected XC functional is Tran-Blaha 2009 functional (modified Becke-Johnson),',ch10,&
2665 &        'which is a potential-only functional, calculations cannot be self-consistent',ch10,&
2666 &        'with respect to the total energy.',ch10, &
2667 &        'For that reason, neither forces nor stresses can be computed.',ch10,&
2668 &        'You should set optforces and optstress to 0!'
2669      ABI_WARNING(msg)
2670   end if
2671 
2672   !  orbmag
2673   ! only values of 0,1,2 are allowed. 0 is the default.
2674   call chkint_eq(0,0,cond_string,cond_values,ierr,'orbmag',dt%orbmag,3,(/0,1,2/),iout)
2675   ! when orbmag /= 0, symmorphi must be 0 (no tnons)
2676   if(dt%orbmag .NE. 0) then
2677      cond_string(1)='orbmag';cond_values(1)=dt%orbmag
2678      call chkint_eq(1,1,cond_string,cond_values,ierr,'symmorphi',dt%symmorphi,1,(/0/),iout)
2679   !  only kptopt 3 or 0 are allowed
2680      call chkint_eq(1,1,cond_string,cond_values,ierr,'kptopt',dt%kptopt,2,(/0,3/),iout)
2681   !  only kpt parallelism is allowed at present
2682      call chkint_eq(1,1,cond_string,cond_values,ierr,'paral_atom',dt%paral_atom,1,(/0/),iout)
2683      call chkint_eq(1,1,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,1,(/0/),iout)
2684   !  require usexcnhat 0
2685      call chkint_eq(1,1,cond_string,cond_values,ierr,'usexcnhat',dt%usexcnhat_orig,1,(/0/),iout)
2686   !  require pawxcdev 0
2687      call chkint_eq(1,1,cond_string,cond_values,ierr,'pawxcdev',dt%pawxcdev,1,(/0/),iout)
2688   !  require PAW
2689      call chkint_eq(1,1,cond_string,cond_values,ierr,'usepaw',dt%usepaw,1,(/1/),iout)
2690   end if
2691 
2692 !  paral_atom
2693    call chkint_eq(0,0,cond_string,cond_values,ierr,'paral_atom',dt%paral_atom,2,(/0,1/),iout)
2694    if (dt%paral_atom/=0) then
2695      if (dt%optdriver/=RUNL_GSTATE.and.dt%optdriver/=RUNL_RESPFN) then
2696        write(msg, '(5a)' )&
2697         'Parallelisation over atoms is only compatible with',ch10,&
2698         'ground-state or response function calculations !',ch10,&
2699         'Action: change paral_atom in input file.'
2700        ABI_ERROR_NOSTOP(msg, ierr)
2701      end if
2702      if (dt%optdriver==RUNL_NONLINEAR) then
2703        cond_string(1)='optdriver' ; cond_values(1)=dt%optdriver
2704        call chkint_eq(1,1,cond_string,cond_values,ierr,'paral_atom',dt%paral_atom,1,(/0/),iout)
2705      end if
2706      if (dt%usedmft==1) then
2707        cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
2708        call chkint_eq(1,1,cond_string,cond_values,ierr,'paral_atom',dt%paral_atom,1,(/0/),iout)
2709      end if
2710      if (dt%prtden>1.and.dt%paral_kgb==0) then
2711        cond_string(1)='paral_kgb' ; cond_values(1)=dt%paral_kgb
2712        cond_string(2)='prtden' ; cond_values(2)=dt%prtden
2713        call chkint_eq(1,2,cond_string,cond_values,ierr,'paral_atom',dt%paral_atom,1,(/0/),iout)
2714      end if
2715    end if
2716 
2717 !  paral_kgb
2718    call chkint_eq(0,0,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,2,(/0,1/),iout)
2719 !  Warning
2720    if(dt%paral_kgb==1.and.dt%iomode/=IO_MODE_MPI) then
2721      write(msg,'(11a)' )&
2722       'When k-points/bands/FFT parallelism is activated',ch10,&
2723       '(paral_kgb=1), only MPI-IO input/output is allowed !',ch10,&
2724       'iomode/=1 in your input file',ch10,&
2725       'You will not be able to perform input/output !'
2726      ABI_WARNING(msg)
2727    end if
2728 
2729    if(dt%paral_kgb==1.and.dt%nstep==0) then
2730      ABI_ERROR_NOSTOP('When k-points/bands/FFT parallelism is activated, nstep=0 is not allowed!', ierr)
2731    end if
2732    if(dt%paral_kgb==1.and.dt%usefock>0) then
2733      ABI_ERROR_NOSTOP('Hartree-Fock or Hybrid Functionals are not compatible with bands/FFT parallelism!', ierr)
2734    end if
2735    if(dt%chkparal/=0.and.(dt%paral_kgb/=0.and.(dt%optdriver/=RUNL_GSTATE .and. dt%optdriver/=RUNL_GWLS))) then
2736        cond_string(1)='optdriver' ; cond_values(1)=dt%optdriver
2737        cond_string(2)='chkparal' ; cond_values(2)=dt%chkparal
2738        call chkint_eq(2,2,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,1,(/0/),iout)
2739    end if
2740 
2741 !  paral_rf
2742    if (response==0 .and. dt%paral_rf/=0) then
2743      write(msg,'(a,i3,3a,14(a,i2),4a)' )&
2744      'The input variable optdriver=',dt%optdriver,ch10,&
2745      'This is in conflict with the values of the other input variables,',ch10,&
2746      'rfphon=',dt%rfphon,' rfddk=',dt%rfddk,' rf2_dkdk=',dt%rf2_dkdk,' rf2_dkde=',dt%rf2_dkde,&
2747      ' rfelfd=',dt%rfelfd,'  rfmagn=',dt%rfmagn,' rfstrs=',dt%rfstrs,' rfuser=',dt%rfuser,&
2748      ' d3e_pert1_elfd=',dt%d3e_pert1_elfd,' d3e_pert2_elfd=',dt%d3e_pert2_elfd,' d3e_pert3_elfd=',dt%d3e_pert3_elfd,&
2749      ' d3e_pert1_phon=',dt%d3e_pert1_phon,' d3e_pert2_phon=',dt%d3e_pert2_phon,' d3e_pert3_phon=',dt%d3e_pert3_phon,ch10,&
2750      'Action: check the values of optdriver, rfphon, rfddk, rf2dkdk, rf2dkde, rfelfd, rfmagn, rfstrs, rfuser,',ch10,&
2751      'd3e_pert1_elfd, d3e_pert2_elfd, d3e_pert3_elfd, d3e_pert1_phon, d3e_pert2_phon, and d3e_pert3_phon in your input file.'
2752      ABI_ERROR_NOSTOP(msg, ierr)
2753    end if
2754 
2755 !  pawcpxocc
2756    if (usepaw==1) then
2757      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawcpxocc',dt%pawcpxocc,2,(/1,2/),iout)
2758      if (dt%usepawu/=0.and.nspinor==2.and.dt%pawcpxocc==1) then
2759        write(msg, '(5a)' )&
2760        'When non-collinear magnetism is activated ,',ch10,&
2761        'and DFT+U activated ',ch10,&
2762        'PAW occupancies must be complex !'
2763        ABI_ERROR_NOSTOP(msg, ierr)
2764      else if (dt%pawspnorb==1.and.(dt%kptopt==0.or.dt%kptopt>=3).and.dt%pawcpxocc==1) then
2765        if (optdriver==RUNL_GSTATE.and.dt%iscf<10) then
2766          write(msg, '(11a)' )&
2767          'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2768          'and time-reversal symmetry is broken (kptopt/=1 and kptopt/=2)',ch10,&
2769          'PAW occupancies are complex !',ch10,&
2770          'Their imaginary part is used to evaluate total energy by direct',ch10,&
2771          'scheme, needed here because SCF potential mixing has been chosen (iscf<10).',ch10,&
2772          'Action: put pawcpxocc=2 in input file, or choose SCF density mixing (iscf>=10).'
2773          ABI_ERROR_NOSTOP(msg, ierr)
2774        else if (optdriver==RUNL_GSTATE.and.dt%iscf>=10) then
2775          write(msg, '(11a)' )&
2776          'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2777          'and time-reversal symmetry is broken (kptopt/=1 and kptopt/=2)',ch10,&
2778          'PAW occupancies are complex !',ch10,&
2779          'By setting pawcpxocc=1 in input file, their imaginary part',ch10,&
2780          'is not computed. As a consequence, total energy computed',ch10,&
2781          'is not available. Put pawcpxocc=2 in input file if you want it.'
2782          ABI_WARNING(msg)
2783        else
2784          write(msg, '(11a)' )&
2785          'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2786          'and time-reversal symmetry is broken (kptopt/=1 and kptopt/=2)',ch10,&
2787          'PAW occupancies are complex !',ch10,&
2788          'Action: put pawcpxocc=2 in input file to compute their imaginary part.'
2789          ABI_ERROR_NOSTOP(msg, ierr)
2790        end if
2791      end if
2792      if (dt%pawspnorb==1.and.dt%kptopt==0) then
2793        write(msg, '(7a)' )&
2794        'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2795        'time-reversal symmetry might be broken.',ch10,&
2796        'Using kptopt=0 might be risky: if (kx,ky,kz) is present in k-points list,',ch10,&
2797        '(-kx,-ky,-kz) (or equivalent) should also be present.'
2798        ABI_WARNING(msg)
2799      end if
2800    end if
2801 
2802 !  pawcross
2803    if (usepaw==1) then
2804      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawcross',dt%pawcross,2,(/0,1/),iout)
2805    endif
2806 
2807 !  pawfatbnd
2808    call chkint_eq(0,0,cond_string,cond_values,ierr,'pawfatbnd',dt%pawfatbnd,3,(/0,1,2/),iout)
2809    if(usepaw/=1.and.dt%pawfatbnd>1) then
2810      ABI_ERROR_NOSTOP('pawfatbnd without PAW is not possible', ierr)
2811    end if
2812    if(dt%prtdosm==1.and.dt%pawfatbnd>0)then
2813      ABI_ERROR_NOSTOP('pawfatbnd>0  and prtdosm=1 are not compatible', ierr)
2814    end if
2815 !  for the moment pawfatbnd is not compatible with fft or band parallelization
2816    !if (dt%pawfatbnd > 0 .and. (dt%npfft > 1 .or. dt%npband > 1)) then
2817    !  msg = 'pawfatbnd and FFT or band parallelization are not compatible yet. Set pawfatbnd to 0  '
2818    !  ABI_ERROR_NOSTOP(msg,ierr)
2819    !end if
2820 
2821 !  pawlcutd
2822    if (usepaw==1) then
2823      call chkint_ge(0,0,cond_string,cond_values,ierr,'pawlcutd',dt%pawlcutd,0,iout)
2824    endif
2825 
2826 !  pawlmix
2827    if (usepaw==1) then
2828      call chkint_ge(0,0,cond_string,cond_values,ierr,'pawlmix',dt%pawlmix,0,iout)
2829    endif
2830 
2831 !  pawmixdg
2832    if (usepaw==1) then
2833      if(dt%ionmov==4)then
2834        cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
2835        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawmixdg',dt%pawmixdg,1,(/1/),iout)
2836      end if
2837      if(dt%iscf==5.or.dt%iscf==6.or.dt%iscf==15.or.dt%iscf==16)then
2838        cond_string(1)='iscf' ; cond_values(1)=dt%iscf
2839        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawmixdg',dt%pawmixdg,1,(/1/),iout)
2840      end if
2841      if(usewvl==1)then
2842        cond_string(1)='usewvl' ; cond_values(1)=usewvl
2843        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawmixdg',dt%pawmixdg,1,(/1/),iout)
2844      end if
2845    end if
2846 
2847 !  pawnhatxc
2848    if (usepaw==1) then
2849      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawnhatxc',dt%pawnhatxc,2,(/0,1/),iout)
2850    endif
2851 
2852 !  pawnzlm
2853    if (usepaw==1) then
2854      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawnzlm',dt%pawnzlm,2,(/0,1/),iout)
2855    endif
2856 
2857 !  pawoptmix
2858    if (usepaw==1) then
2859      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawoptmix',dt%pawoptmix,2,(/0,1/),iout)
2860    endif
2861 
2862 !  pawprtdos
2863    if (usepaw==1) then
2864      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawprtdos',dt%pawprtdos,3,(/0,1,2/),iout)
2865    endif
2866 
2867 !  pawprtvol
2868    if (usepaw==1) then
2869      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawprtvol',dt%pawprtvol,7,(/-3,-2,-1,0,1,2,3/),iout)
2870    endif
2871 
2872 !  pawspnorb
2873    if (usepaw==1) then
2874      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawspnorb',dt%pawspnorb,2,(/0,1/),iout)
2875      if (dt%pawspnorb==1.and.(dt%kptopt==1.or.dt%kptopt==2)) then
2876        write(msg, '(7a)' )&
2877         'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2878         'time-reversal symmetry is broken; k-points cannot',ch10,&
2879         'be generated using TR-symmetry.',ch10,&
2880         'Action: choose kptopt different from 1 or 2.'
2881        ABI_ERROR_NOSTOP(msg, ierr)
2882      end if
2883    end if
2884 
2885 !  pawstgylm, pawsushat
2886    if (usepaw==1) then
2887      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawstgylm',dt%pawstgylm,2,(/0,1/),iout)
2888      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawsushat',dt%pawstgylm,2,(/0,1/),iout)
2889    end if
2890 
2891 !  pawusecp
2892    if (usepaw==1) then
2893      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawusecp',dt%pawusecp,2,(/0,1/),iout)
2894 !      if (dt%mkmem/=0)then
2895 !        cond_string(1)='mkmem' ; cond_values(1)=dt%mkmem
2896 !        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawusecp',dt%pawusecp,1,(/1/),iout)
2897 !      end if
2898 !      if (dt%mk1mem/=0)then
2899 !        cond_string(1)='mk1mem' ; cond_values(1)=dt%mk1mem
2900 !        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawusecp',dt%pawusecp,1,(/1/),iout)
2901 !      end if
2902 !      if (dt%mkqmem/=0)then
2903 !        cond_string(1)='mkqmem' ; cond_values(1)=dt%mkqmem
2904 !        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawusecp',dt%pawusecp,1,(/1/),iout)
2905 !      end if
2906    end if
2907 
2908 !  pawxcdev
2909    if (usepaw==1) then
2910      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawxcdev',dt%pawxcdev,3,(/0,1,2/),iout)
2911    endif
2912 
2913 !  pimass
2914 !  Check that masses are > 0 if imgmov = 9 or 13
2915    if (dt%imgmov==9.or.dt%imgmov==13) then
2916      do itypat=1,dt%ntypat
2917        cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
2918        write(input_name,'(a4,i1,a1)')'pimass(',itypat,')'
2919        call chkdpr(1,1,cond_string,cond_values,ierr,input_name,dt%pimass(itypat),1,tol8,iout)
2920      end do
2921    end if
2922 
2923 !  pimd_constraint
2924    call chkint_eq(0,0,cond_string,cond_values,ierr,'pimd_constraint',dt%pimd_constraint,2,(/0,1/),iout)
2925    if(dt%pimd_constraint==1.and.dt%nconeq>1 )then
2926      cond_string(1)='pimd_constraint' ; cond_values(1)=dt%pimd_constraint
2927 !    Make sure that nconeq=1
2928      call chkint_eq(1,1,cond_string,cond_values,ierr,'nconeq',dt%nconeq,1,(/1/),iout)
2929    end if
2930 
2931 !  pitransform
2932    call chkint_eq(0,0,cond_string,cond_values,ierr,'pitransform',dt%pitransform,3,(/0,1,2/),iout)
2933 !  When imgmov is not one of 9 or 13, pitransform must be 0
2934    if(dt%imgmov/=9 .and. dt%imgmov/=13 )then
2935      cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
2936 !    Make sure that pitransform=0
2937      call chkint_eq(1,1,cond_string,cond_values,ierr,'pitransform',dt%pitransform,1,(/0/),iout)
2938    end if
2939    if(dt%pimd_constraint/=0 )then
2940      cond_string(1)='pimd_constraint' ; cond_values(1)=dt%pimd_constraint
2941 !    Make sure that pitransform=0
2942      call chkint_eq(1,1,cond_string,cond_values,ierr,'pitransform',dt%pitransform,1,(/0/),iout)
2943    end if
2944 
2945 !  plowan_compute
2946    cond_string(1)='usepaw' ; cond_values(1)=usepaw
2947    call chkint_eq(1,1,cond_string,cond_values,ierr,'plowan_compute',dt%plowan_compute,4,(/0,1,2,10/),iout)
2948    if(dt%plowan_compute>0) then
2949 !    plowan_bandi/plowan_bandf
2950      !call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_bandi',dt%plowan_bandi,              1,iout)
2951      !call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_bandf',dt%plowan_bandf,dt%plowan_bandi,iout)
2952 
2953      !call chkint_le(0,0,cond_string,cond_values,ierr,'plowan_bandi',dt%plowan_bandi,dt%plowan_bandf,iout)
2954      !call chkint_le(0,0,cond_string,cond_values,ierr,'plowan_bandi',dt%plowan_bandf,dt%mband       ,iout)
2955 
2956      call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_natom',dt%plowan_natom,              0,iout)
2957 
2958      maxplowan_iatom=maxval(dt%plowan_iatom(1:dt%plowan_natom))
2959      minplowan_iatom=minval(dt%plowan_iatom(1:dt%plowan_natom))
2960      call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_iatom',minplowan_iatom,              1,iout)
2961      call chkint_le(0,0,cond_string,cond_values,ierr,'plowan_iatom',maxplowan_iatom,          natom,iout)
2962 
2963      kk=0
2964      do jj = 1, dt%plowan_natom
2965        do ii = 1, dt%plowan_nbl(jj)
2966          kk=kk+1
2967          cond_string(1)='usepaw' ; cond_values(1)=usepaw
2968          call chkint_eq(1,1,cond_string,cond_values,ierr,'plowan_lcalc',dt%plowan_lcalc(kk),4,(/0,1,2,3/),iout)
2969        end do
2970      end do
2971 
2972      call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_nt'   ,dt%plowan_nt,                 0,iout)
2973      cond_string(1)='usepaw' ; cond_values(1)=usepaw
2974      call chkint_eq(1,1,cond_string,cond_values,ierr,'plowan_realspace',dt%plowan_realspace,3,(/0,1,2/),iout)
2975    end if
2976 
2977 !  posdoppler
2978    call chkint_eq(0,0,cond_string,cond_values,ierr,'posdoppler',dt%posdoppler,2,(/0,1/),iout)
2979 
2980 !  positron
2981    call chkint_eq(0,0,cond_string,cond_values,ierr,'positron',dt%positron,7,(/-20,-10,-2,-1,0,1,2/),iout)
2982    if ((dt%positron==2.or.dt%positron<0).and.(dt%ixcpositron==3.or.dt%ixcpositron==31)) then
2983      if ((dt%ixc<11.or.dt%ixc>17).and.dt%ixc/=23.and.dt%ixc/=26.and.dt%ixc/=27) then
2984        write(msg, '(7a)' )&
2985 &       'For the electronic ground-state calculation in presence of a positron,',ch10,&
2986 &       'when GGA is selected for electron-positron correlation (ixcpositron=3 or 31),',ch10,&
2987 &       'electron-electron XC must also be GGA !',ch10,&
2988 &       'Action: choose another psp file.'
2989        ABI_ERROR_NOSTOP(msg, ierr)
2990      end if
2991    end if
2992    if (dt%positron/=0.and.xc_is_mgga) then
2993      msg='Electron-positron calculation is not compatible with meta-GGA XC functional!'
2994      ABI_ERROR_NOSTOP(msg, ierr)
2995    end if
2996    if (dt%positron/=0.and.dt%ionmov==5) then
2997      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
2998      call chkint_eq(1,1,cond_string,cond_values,ierr,'positron',dt%positron,1,(/0/),iout)
2999    end if
3000    if (dt%positron<0.and.usepaw==0) then
3001      write(msg, '(5a)' )&
3002 &     'You cannot use positron<0 (automatic two-component DFT)',ch10,&
3003 &     'with norm-conserving pseudopotentials !',ch10,&
3004 &     'Action: choose PAW.'
3005      ABI_ERROR_NOSTOP(msg, ierr)
3006    end if
3007    if ((dt%positron==1.or.dt%positron<0).and.dt%iscf<10.and.dt%tolvrs>tiny(one)) then
3008      write(msg, '(7a)' )&
3009 &     'You cannot perform a positronic ground-state calculation (positron=1 or <0)',ch10,&
3010 &     'using SCF potential mixing (iscf<10) and tolvrs !',ch10,&
3011 &     '(in that case, the potential is constant)',ch10,&
3012 &     'Action: change iscf or select another convergence criterion.'
3013      ABI_ERROR_NOSTOP(msg, ierr)
3014    end if
3015 
3016 !  posocc
3017    call chkdpr(0,0,cond_string,cond_values,ierr,'posocc',dt%posocc,-1,one,iout)
3018 
3019 !  postoldfe, postoldff
3020    call chkdpr(0,0,cond_string,cond_values,ierr,'postoldff',dt%postoldff,1,zero,iout)
3021    if (dt%positron<0) then
3022      if ( (abs(dt%postoldfe)> tiny(0.0_dp).and.abs(dt%postoldff)> tiny(0.0_dp)).or.&
3023           (abs(dt%postoldfe)<=tiny(0.0_dp).and.abs(dt%postoldff)<=tiny(0.0_dp))) then
3024        write(msg,'(5a)' )&
3025 &       'One and only one of the input tolerance criteria postoldfe or postoldff',ch10,&
3026 &       'must differ from zero !',ch10,&
3027 &       'Action: change postoldfe or postldff in input file.'
3028        ABI_ERROR_NOSTOP(msg, ierr)
3029      end if
3030      if (abs(dt%postoldff)>tiny(0.0_dp).and.dt%optforces/=1)then
3031        write(msg,'(3a)' )&
3032 &       'When postoldff is set to a non-zero value, optforces must be set to 1 !',ch10,&
3033 &       'Action: change your input file.'
3034        ABI_ERROR_NOSTOP(msg, ierr)
3035      end if
3036    end if
3037 
3038 ! prepalw
3039   call chkint_eq(0,0,cond_string,cond_values,ierr,'prepalw',dt%prepalw,5,(/0,1,2,3,4/),iout)
3040 
3041 !  prepanl
3042 !  Must have prtden=1 to prepare a nonlinear calculation
3043    if (dt%prepanl==1.and.(dt%rfelfd/=0.or.dt%rfphon/=0)) then
3044      cond_string(1)='rfelfd'  ; cond_values(1)=dt%rfelfd
3045      cond_string(2)='rfphon'  ; cond_values(2)=dt%rfphon
3046      cond_string(3)='prepanl' ; cond_values(3)=dt%prepanl
3047      call chkint_eq(1,3,cond_string,cond_values,ierr,'prtden',dt%prtden,1,(/1/),iout)
3048    end if
3049 
3050 !  prtbbb
3051 !  Not allowed for PAW
3052    if(usepaw==1.and.dt%prtbbb==1)then
3053      cond_string(1)='usepaw' ; cond_values(1)=usepaw
3054      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtbbb',dt%prtbbb,1,(/0/),iout)
3055    end if
3056 
3057 !  prtden
3058    if (usepaw==1) then
3059      call chkint_le(0,0,cond_string,cond_values,ierr,'prtden',dt%prtden,7,iout)
3060    else
3061      call chkint_le(0,0,cond_string,cond_values,ierr,'prtden',dt%prtden,1,iout)
3062    end if
3063 
3064 !  prtdensph
3065    if (usepaw==1) then
3066      call chkint_eq(0,0,cond_string,cond_values,ierr,'prtdensph',dt%prtdensph,2,(/0,1/),iout)
3067    endif
3068 
3069    !  prt_lorbmag
3070    if (usepaw==1) call chkint_eq(0,0,cond_string,cond_values,ierr,'prt_lorbmag',dt%prt_lorbmag,2,(/0,1/),iout)
3071 
3072 !  prtdos
3073    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtdos',dt%prtdos,6,(/0,1,2,3,4,5/),iout)
3074 
3075 ! for the moment prtdos 3,4,5 are not compatible with fft or band parallelization
3076    if (dt%prtdos > 3 .and. (dt%npfft > 1 .or. dt%npband > 1)) then
3077      ABI_ERROR_NOSTOP('prtdos>3 and FFT or band parallelization are not compatible yet. Set prtdos <= 2', ierr)
3078    end if
3079 
3080 ! prtdos 5 only makes sense for nspinor == 2. Otherwise reset to prtdos 2
3081    if (dt%prtdos == 5 .and. dt%nspinor /= 2) then
3082      dt%prtdos = 2
3083      ABI_WARNING('prtdos==5 is only useful for nspinor 2. Has been reset to 2')
3084    end if
3085    if (dt%prtdos == 5 .and. dt%npspinor /= 1) then
3086      ABI_ERROR_NOSTOP('prtdos==5 not available with npspinor==2', ierr)
3087    end if
3088    ! Consistency check for prtdos 5 with PAW
3089    if (dt%prtdos == 5 .and. dt%usepaw == 1) then
3090      if (dt%pawprtdos == 2) then
3091        ABI_ERROR_NOSTOP('prtdos==5 is not compatible with pawprtdos 2', ierr)
3092      end if
3093      ABI_ERROR_NOSTOP('prtdos==5 is not available with PAW', ierr)
3094    end if
3095 
3096 !  prtdosm
3097    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtdosm',dt%prtdosm,3,(/0,1,2/),iout)
3098    if(usepaw==1.and.dt%pawprtdos==1)then
3099      cond_string(1)='pawprtdos' ; cond_values(1)=dt%pawprtdos
3100      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtdosm',dt%prtdosm,1,(/0/),iout)
3101    end if
3102    if(usepaw==1.and.dt%prtdosm>=1)then
3103      cond_string(1)='prtdosm' ; cond_values(1)=dt%prtdosm
3104      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtdos',dt%prtdos,1,(/3/),iout)
3105    end if
3106    if(dt%prtdosm==2.and.dt%pawprtdos/=2)then
3107      ABI_ERROR(' pawprtdos/=2  and prtdosm=2 are not compatible')
3108    end if
3109 
3110    !  prtefmas
3111    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtefmas',dt%prtefmas,2,(/0,1/),iout)
3112    !if(optdriver/=RUNL_RESPFN)then
3113    !  cond_string(1)='optdriver' ; cond_values(1)=optdriver
3114    !  call chkint_eq(0,1,cond_string,cond_values,ierr,'prtefmas',dt%prtefmas,1,(/0/),iout)
3115    !end if
3116 
3117 !  prtelf
3118    call chkint_ge(0,0,cond_string,cond_values,ierr,'prtelf',dt%prtkden,0,iout)
3119    if(optdriver/=RUNL_GSTATE)then
3120      cond_string(1)='optdriver' ; cond_values(1)=optdriver
3121      call chkint_eq(0,1,cond_string,cond_values,ierr,'prtelf',dt%prtelf,1,(/0/),iout)
3122    end if
3123    if(usepaw/=0)then
3124      cond_string(1)='usepaw' ; cond_values(1)=usepaw
3125      call chkint_eq(0,1,cond_string,cond_values,ierr,'prtelf',dt%prtelf,1,(/0/),iout)
3126    end if
3127 
3128 !  prtfsurf only one shift allowed (gamma)
3129    if (dt%prtfsurf == 1) then
3130 
3131      if (.not. isdiagmat(dt%kptrlatt)) then
3132        write(msg,'(4a)')ch10,&
3133          'prtfsurf does not work with non-diagonal kptrlatt ', ch10,&
3134          'Action: set nshift 1 and shiftk 0 0 0'
3135        ABI_ERROR_NOSTOP(msg, ierr)
3136      end if
3137      if (dt%nshiftk > 1) then
3138        ABI_ERROR_NOSTOP('prtfsurf does not work with multiple kpt shifts ', ierr)
3139      end if
3140      if (sum(abs(dt%shiftk(:,1:dt%nshiftk))) > tol8) then
3141        write(msg,'(4a)')ch10,&
3142         'prtfsurf does not work with non-zero k-shifts ',ch10,&
3143         'Action: set nshift 1 and shiftk 0 0 0'
3144        ABI_ERROR_NOSTOP(msg, ierr)
3145      end if
3146 
3147 !    Occcupations, Fermi level and k weights have to be calculated correctly.
3148      if (.not.(dt%iscf>1.or.dt%iscf==-3)) then
3149        write(msg,'(4a)')ch10,&
3150         'prtfsurf==1 requires either iscf>1 or iscf==-3 ',ch10,&
3151         'Action: change iscf in the input file. '
3152        ABI_ERROR_NOSTOP(msg, ierr)
3153      end if
3154 
3155 !    Make sure all nband are equal (well it is always enforced for metals)
3156      if (any(dt%nband(1:nkpt*nsppol) /= maxval(dt%nband(1:nkpt*nsppol)) )) then
3157        write(msg,'(3a)')&
3158         'The number of bands has to be constant for the output of the Fermi surface.',ch10,&
3159         'Action: set all the nbands to the same value in your input file'
3160        ABI_ERROR_NOSTOP(msg,ierr)
3161      end if
3162    end if ! prtfsurf==1
3163 
3164 !  prtgden
3165    call chkint(0,0,cond_string,cond_values,ierr,'prtgden',dt%prtgden,1,(/0/),1,0,iout)
3166    if(optdriver/=RUNL_GSTATE)then
3167      cond_string(1)='optdriver' ; cond_values(1)=optdriver
3168      call chkint(0,1,cond_string,cond_values,ierr,'prtgden',dt%prtgden,1,(/0/),0,0,iout)
3169    end if
3170    if(usepaw/=0)then
3171      cond_string(1)='usepaw' ; cond_values(1)=usepaw
3172      call chkint(0,1,cond_string,cond_values,ierr,'prtgden',dt%prtgden,1,(/0/),0,0,iout)
3173    end if
3174 
3175 !  prtkden
3176    ! call chkint_ge(0,0,cond_string,cond_values,ierr,'prtkden',dt%prtkden,0,iout)
3177    ! if(optdriver/=RUNL_GSTATE)then
3178    !   cond_string(1)='optdriver' ; cond_values(1)=optdriver
3179    !   call chkint_eq(0,1,cond_string,cond_values,ierr,'prtkden',dt%prtkden,1,(/0/),iout)
3180    !end if
3181    !if(usepaw/=0)then
3182    !  cond_string(1)='usepaw' ; cond_values(1)=usepaw
3183    !  call chkint_eq(0,1,cond_string,cond_values,ierr,'prtkden',dt%prtkden,1,(/0/),iout)
3184    !end if
3185 
3186 !  prtlden
3187    call chkint(0,0,cond_string,cond_values,ierr,'prtlden',dt%prtlden,1,(/0/),1,0,iout)
3188    if(optdriver/=RUNL_GSTATE)then
3189      cond_string(1)='optdriver' ; cond_values(1)=optdriver
3190      call chkint(0,1,cond_string,cond_values,ierr,'prtlden',dt%prtlden,1,(/0/),0,0,iout)
3191    end if
3192    !if(usepaw/=0)then
3193    !  cond_string(1)='usepaw' ; cond_values(1)=usepaw
3194    !  call chkint(0,1,cond_string,cond_values,ierr,'prtlden',dt%prtlden,1,(/0/),0,0,iout)
3195    !end if
3196 
3197 !  prtstm
3198    call chkint_le(0,0,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,iout)
3199    call chkint_ge(0,0,cond_string,cond_values,ierr,'prtstm',dt%prtstm,-dt%mband,iout)
3200    if(optdriver/=RUNL_GSTATE)then
3201      cond_string(1)='optdriver' ; cond_values(1)=optdriver
3202      call chkint_eq(0,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
3203    end if
3204    if(dt%occopt/=7)then
3205      cond_string(1)='occopt' ; cond_values(1)=dt%occopt
3206      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
3207    end if
3208    if(dt%nstep/=1)then
3209      cond_string(1)='nstep' ; cond_values(1)=dt%nstep
3210      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
3211    end if
3212    if(dt%ionmov/=0)then
3213      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
3214      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
3215    end if
3216 !  tolwfr must be 0 to make a problem (another tol variable is used). Here, check that it is very very small.
3217    if(abs(dt%tolwfr)<tol16*tol16)then
3218      cond_string(1)='prtstm' ; cond_values(1)=dt%prtstm
3219      call chkdpr(1,1,cond_string,cond_values,ierr,'tolwfr',dt%tolwfr,1,tol16*tol16,iout)
3220    end if
3221    if(dt%prtden/=0)then
3222      cond_string(1)='prtden' ; cond_values(1)=dt%prtden
3223      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
3224    end if
3225 
3226 !  prtnabla
3227    if(dt%prtnabla>0)then
3228      cond_string(1)='prtnabla' ; cond_values(1)=dt%prtnabla
3229      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
3230      if(dt%npspinor>1.and.(dt%prtnabla==1.or.dt%prtnabla==2).and.dt%pawspnorb==1)then
3231        msg='Parallelization over spinorial components not allowed with prtnabla=(1 or 2) and SOC!'
3232        ABI_ERROR_NOSTOP(msg, ierr)
3233      end if
3234    end if
3235 
3236    if(dt%prtvxc>0)then
3237      cond_string(1)='prtvxc' ; cond_values(1)=dt%prtvxc
3238      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
3239    end if
3240    if(dt%prtvha>0)then
3241      cond_string(1)='prtvha' ; cond_values(1)=dt%prtvha
3242      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
3243    end if
3244    if(dt%prtvhxc>0)then
3245      cond_string(1)='prtvhxc' ; cond_values(1)=dt%prtvhxc
3246      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
3247    end if
3248 
3249 !  prtvclmb - needs prtvha as well
3250    if(dt%prtvclmb > 0)then
3251      cond_string(1)='prtvclmb' ; cond_values(1)=dt%prtvclmb
3252      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtvha',dt%prtvha,1,(/1/),iout)
3253    end if
3254 
3255 !  prtvolimg
3256    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtvolimg',dt%prtvolimg,3,(/0,1,2/),iout)
3257 
3258 !  prtwant
3259    if (dt%prtwant/=0) then
3260      cond_string(1)='prtwant' ; cond_values(1)=dt%prtwant
3261      call chkint_eq(0,0,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,1,(/0/),iout)
3262    end if
3263 #if !defined HAVE_WANNIER90
3264    if(dt%prtwant==2) then
3265      write(msg, '(a,a,a)' )&
3266      ' prtwant==2 is only relevant if wannier90 library is linked',ch10,&
3267      ' Action: check compilation options'
3268      ABI_ERROR_NOSTOP(msg,ierr)
3269    end if
3270 #endif
3271 
3272 !  prtwf
3273    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtwf',dt%prtwf,5,[-1,0,1,2,3],iout)
3274 
3275    if (dt%prtkbff == 1 .and. dt%useylm /= 0) then
3276      ABI_ERROR_NOSTOP("prtkbff == 1 requires useylm == 0", ierr)
3277    end if
3278 
3279 !  prtwf_full
3280    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtwf_full',dt%prtwf_full,2,[0,1],iout)
3281    if (dt%prtwf==0) then
3282      cond_string(1)='prtwf' ; cond_values(1)=dt%prtwf
3283      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtwf_full',dt%prtwf_full,1,(/0/),iout)
3284    end if
3285 
3286 
3287 !  random_atpos
3288    call chkint_eq(0,0,cond_string,cond_values,ierr,'random_atpos',dt%random_atpos,5,(/0,1,2,3,4/),iout)
3289 
3290 !  ratsph
3291 !  If PAW and (prtdos==3 or dt%prtdensph==1), must be greater than PAW radius
3292    if(usepaw==1.and.(dt%prtdos==3.or.dt%prtdensph==1))then
3293      do itypat=1,dt%ntypat
3294        if (pspheads(itypat)%pawheader%rpaw>dt%ratsph(itypat)) then
3295          write(msg, '(7a,i2,a,f15.12,3a)' )&
3296          'Projected DOS/density is required in the framework of PAW !',ch10,&
3297          'The radius of spheres in which DOS/density has to be projected',ch10,&
3298          'must be greater or equal than the (max.) PAW radius !',ch10,&
3299          'Rpaw(atom_type ',itypat,')= ',pspheads(itypat)%pawheader%rpaw,' au',ch10,&
3300          'Action: modify value of ratsph in input file.'
3301          ABI_ERROR_NOSTOP(msg, ierr)
3302        end if
3303      end do
3304    end if
3305 
3306 
3307 !  recgratio
3308    if (dt%tfkinfunc==2) then
3309      write(msg, '(a,a)' ) ch10,'=== RECURSION METHOD ==========================================================='
3310      call wrtout(ab_out,msg)
3311      cond_string(1)='tfkinfunc' ; cond_values(1)=dt%tfkinfunc
3312      call chkint_ge(0,1,cond_string,cond_values,ierr,'recgratio',dt%recgratio,1,iout)
3313      if(dt%recgratio>1) then
3314        write(msg, '(a,a)' )'=== Coarse Grid is used in recursion ==========================================='
3315        call wrtout(ab_out,msg)
3316        write(msg, '(a,i3,a,a,i3,a,i3,a,i3)' ) 'grid ratio =',dt%recgratio,&
3317         ch10,'fine grid =   ',dt%ngfft(1),' ',dt%ngfft(2),' ',dt%ngfft(3)
3318        call wrtout(ab_out,msg)
3319        write(msg, '(a,i2,a,i2,a,i2)' ) 'coarse grid = ',&
3320         dt%ngfft(1)/dt%recgratio,' ',dt%ngfft(2)/dt%recgratio,' ',dt%ngfft(3)/dt%recgratio
3321        call wrtout(ab_out,msg)
3322      else
3323        write(msg, '(a,i2,a,i2,a,i2)' ) 'fine grid =   ',dt%ngfft(1),' ',dt%ngfft(2),' ',dt%ngfft(3)
3324        call wrtout(ab_out,msg)
3325      end if
3326    end if
3327 
3328 !  restartxf
3329    call chkint_eq(0,0,cond_string,cond_values,ierr,'restartxf',dt%restartxf,4,(/0,-1,-2,-3/),iout)
3330 
3331 !  rfatpol
3332    call chkint_ge(0,0,cond_string,cond_values,ierr,'rfatpol(1)',dt%rfatpol(1),1,iout)
3333    cond_string(1)='natom' ; cond_values(1)=natom
3334    call chkint_le(1,1,cond_string,cond_values,ierr,'rfatpol(2)',dt%rfatpol(2),natom,iout)
3335 
3336 !  rfmeth
3337    call chkint_eq(0,0,cond_string,cond_values,ierr,'rfmeth',dt%rfmeth,6,(/-3,-2,-1,1,2,3/),iout)
3338 
3339 !  rprimd
3340 !  With optcell beyond 4, one has constraints on rprimd.
3341    cond_string(1)='optcell' ; cond_values(1)=dt%optcell
3342    if( dt%optcell==7 )then
3343      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(1,2)',rprimd(1,2),0,0.0_dp,iout)
3344      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(1,3)',rprimd(1,3),0,0.0_dp,iout)
3345      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(2,1)',rprimd(2,1),0,0.0_dp,iout)
3346      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(3,1)',rprimd(3,1),0,0.0_dp,iout)
3347    else if( dt%optcell==8 )then
3348      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(2,1)',rprimd(2,1),0,0.0_dp,iout)
3349      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(2,3)',rprimd(2,3),0,0.0_dp,iout)
3350      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(1,2)',rprimd(1,2),0,0.0_dp,iout)
3351      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(3,2)',rprimd(3,2),0,0.0_dp,iout)
3352    else if( dt%optcell==9 )then
3353      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(3,1)',rprimd(3,1),0,0.0_dp,iout)
3354      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(3,2)',rprimd(3,2),0,0.0_dp,iout)
3355      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(1,3)',rprimd(1,3),0,0.0_dp,iout)
3356      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(2,3)',rprimd(2,3),0,0.0_dp,iout)
3357    end if
3358 
3359    if (dt%rmm_diis /= 0) then
3360      ! Check for calculations that are not implemented with RMM-DIIS
3361      ABI_CHECK(dt%usefock == 0, "RMM-DIIS with Hartree-Fock or Hybrid Functionals is not implemented")
3362      ABI_CHECK(dt%wfoptalg /= 1, "RMM-DIIS with Chebyshev is not supported.")
3363      ABI_CHECK(dt%gpu_option == ABI_GPU_DISABLED, "RMM-DIIS does not support GPUs.")
3364      berryflag = any(dt%berryopt == [4, 14, 6, 16, 7, 17])
3365      ABI_CHECK(.not. berryflag, "RMM-DIIS with Electric field is not supported.")
3366    end if
3367 
3368 !  so_psp
3369    if(usepaw==0)then
3370      do ipsp=1,npsp
3371 !      Check that so_psp is between 0 and 3
3372        if ( dt%so_psp(ipsp)<0 .or. dt%so_psp(ipsp)>3 ) then
3373          write(msg, '(a,i3,a,i3,a,a,a,a,a)' )&
3374          'so_psp(',ipsp,' ) was input as ',dt%so_psp(ipsp),' .',ch10,&
3375          'Input value must be 0, 1, 2, or 3.',ch10,&
3376          'Action: modify value of so_psp (old name : so_typat) in input file.'
3377          ABI_ERROR_NOSTOP(msg, ierr)
3378        end if
3379 !      If nspinor=1, the spin-orbit contribution cannot be taken into account
3380        if ( nspinor==1 .and. (dt%so_psp(ipsp)==2 .or. dt%so_psp(ipsp)==3) ) then
3381          write(msg, '(a,i2,a,i3,a,a,a,a,a)' )&
3382          'so_psp(',ipsp,') was input as ',dt%so_psp(ipsp),', with nspinor=1 and usepaw=0.',ch10,&
3383          'When nspinor=1, so_psp cannot be required to be 2 or 3.',ch10,&
3384          'Action: modify value of so_psp (old name : so_typat) or nspinor in input file.'
3385          ABI_ERROR_NOSTOP(msg, ierr)
3386        end if
3387 !      If nspinor=2, the spin-orbit contribution should be present in the pseudopotentials,
3388 !      unless the user explicitly allows not to treat it.
3389        if ( nspinor==2 .and. dt%so_psp(ipsp)/=0 .and. pspheads(ipsp)%pspso==0 ) then
3390          write(msg, '(2(a,i0),9a)' )&
3391          'so_psp(',ipsp,') was input as ',dt%so_psp(ipsp),', with nspinor=2 and usepaw=0.',ch10,&
3392          'This requires a treatment of the spin-orbit interaction. However, it has been detected ',ch10,&
3393          'that the pseudopotential that you want to use does not specify the spin-orbit coupling.',ch10,&
3394          'Action: choose a pseudopotential that contains information about the spin-orbit interaction,',ch10,&
3395          ' or deliberately switch off the spin-orbit interaction by setting so_psp=0 for that pseudopotential in the input file.'
3396          ABI_ERROR_NOSTOP(msg, ierr)
3397        end if
3398      end do ! ipsp
3399    end if ! usepaw==0
3400 
3401 !  spinat
3402 !  Not allowed with nspden=1 (PAW)
3403    !if(any(abs(dt%spinat)>tol8).and.nspden==1.and.usepaw==1) then
3404    !  write(msg, '(3a)' )&
3405    !   'A spinat/=0 is not allowed when magnetization is forced to zero (nspden=1)!',ch10,&
3406    !   'Action: re-run with spinat zero '
3407    !  ABI_ERROR_NOSTOP(msg, ierr)
3408    !end if
3409 
3410 !  spinmagntarget
3411    if(abs(dt%spinmagntarget+99.99d0)>tol8 .and. abs(dt%spinmagntarget)>tol8)then
3412      if(nsppol==1)then
3413        write(msg, '(a,f8.2,4a)' )&
3414        'spinmagntarget was input as ',dt%spinmagntarget,ch10,&
3415        'When nsppol=1, spinmagntarget is required to be 0.0d0 or the default value.',ch10,&
3416        'Action: modify value spinmagntarget or nsppol in input file.'
3417        ABI_ERROR_NOSTOP(msg, ierr)
3418      end if
3419      if(optdriver==RUNL_RESPFN)then
3420        write(msg, '(a,f8.2,8a)' )&
3421        'spinmagntarget was input as ',dt%spinmagntarget,ch10,&
3422        'For a response function run, spinmagntarget is required to be 0.0d0 or the default value.',ch10,&
3423        'A spin-polarized response function calculation for a ferromagnetic insulator needs occopt=0, 1 or 2',ch10,&
3424 &      '  the default value of spinmagntarget, and explicit definition of occ. ',ch10,&
3425        'Action: modify spinmagntarget, occopt or nsppol in your input file.'
3426        ABI_ERROR_NOSTOP(msg, ierr)
3427      end if
3428      if(dt%prtdos==1)then
3429        write(msg, '(a,f8.2,8a)' )&
3430        'spinmagntarget was input as ',dt%spinmagntarget,ch10,&
3431        'When prtdos==1, spinmagntarget is required to be 0.0d0 or the default value.',ch10,&
3432        'A spin-polarized DOS calculation for a ferromagnetic insulator needs occopt=0, 1 or 2',ch10,&
3433 &      '  the default value of spinmagntarget, and explicit definition of occ.',ch10,&
3434        'Action: modify spinmagntarget, occopt or nsppol in your input file.'
3435        ABI_ERROR_NOSTOP(msg, ierr)
3436      end if
3437    end if
3438 !  If nsppol==2 and spinmagntarget==0.0 , suggest to use anti-ferromagnetic capability of ABINIT.
3439    if(nsppol==2.and.abs(dt%spinmagntarget)<tol8)then
3440      write(msg,'(a,i3,2a,f7.2,6a)' )&
3441      ' This is a calculation with spin-up and spin-down wavefunctions,         ... nsppol=',nsppol,ch10,&
3442      ' in which the target spin-polarization is zero.                  ... spinmagntarget=',dt%spinmagntarget,ch10,&
3443      ' Tip ... It might be possible that the ground state is either non-spin-polarized, or antiferromagnetic.',ch10,&
3444      ' In the former case, it is advantageous to use nsppol=1 and nspden=1,',ch10,&
3445      ' while in the latter  case, it is advantageous to use nsppol=1 and nspden=2.'
3446      call wrtout(iout,msg)
3447    end if
3448 
3449 !  stmbias
3450    cond_string(1)='prtstm' ; cond_values(1)=dt%prtstm
3451    if(dt%prtstm/=0)then
3452 !    If non-zero prtstm, stmbias cannot be zero : test is positive or zero
3453      if(dt%stmbias>-tol10)then
3454 !      Then, enforce positive
3455        call chkdpr(1,1,cond_string,cond_values,ierr,'stmbias',dt%stmbias,1,2*tol10,iout)
3456      end if
3457    else
3458      call chkdpr(1,1,cond_string,cond_values,ierr,'stmbias',dt%stmbias,0,zero,iout)
3459    end if
3460 
3461 !  string_algo
3462    call chkint_eq(0,0,cond_string,cond_values,ierr,'string_algo',dt%string_algo,2,(/1,2/),iout)
3463 
3464 !  symafm
3465    if(nsppol==1 .and. nspden==2)then
3466 !    At least one of the symmetry operations must be antiferromagnetic
3467      if(minval(dt%symafm(1:dt%nsym))/=-1)then
3468        write(msg, '(5a)' )&
3469        'When nsppol==1 and nspden==2, at least one of the symmetry operations',ch10,&
3470        'must be anti-ferromagnetic (symafm=-1), in order to deduce the spin-down density',ch10,&
3471        'from the spin-up density.'
3472        call wrtout(iout,msg)
3473        call wrtout(std_out,  msg)
3474        write(msg, '(7a)' ) &
3475        'However, it is observed that none of the symmetry operations is anti-ferromagnetic.',ch10,&
3476        'Action: Check the atomic positions, the input variables spinat, symrel, tnons, symafm.',ch10,&
3477        '        In case your system is not antiferromagnetic (it might be ferrimagnetic ...),',ch10,&
3478        '        you must use nsppol=2 with nspden=2 (the latter being the default when nsppol=2).'
3479        ABI_ERROR_NOSTOP(msg,ierr)
3480      end if
3481    end if
3482 
3483 !  symrel and tnons
3484 !  Check the point group closure
3485    call sg_multable(dt%nsym,dt%symafm,dt%symrel,ierrgrp, tnons=dt%tnons, tnons_tol=tol5)
3486    if (ierrgrp==1) ierr=ierr+1
3487 
3488 !  Check the orthogonality of the symmetry operations
3489 !  (lengths and absolute values of scalar products should be preserved)
3490    iexit=0
3491 
3492    call chkorthsy(gprimd,iexit,dt%nsym,rmet,rprimd,dt%symrel,tol8)
3493 
3494 !  symchi
3495    if (all(dt%symchi /= [0, 1])) then
3496      write(msg, '(a,i0,2a)' )'symchi was input as ',dt%symchi,ch10,'Input value must be 0, 1.'
3497      ABI_ERROR_NOSTOP(msg, ierr)
3498    end if
3499 
3500 !  symsigma
3501    if (all(dt%symsigma /= [0, 1, -1])) then
3502      write(msg, '(a,i0,a,a,a,a)' )&
3503       'symsigma was input as ',dt%symsigma,ch10,&
3504       'Input value must be 0, 1, or -1.',ch10,&
3505       'Action: modify value of symsigma in input file.'
3506      ABI_ERROR_NOSTOP(msg, ierr)
3507    end if
3508 
3509 !  MG now it is possible to perform a GW calculation with non-symmorphic operations if required by the user
3510 !  tnons
3511    if (dt%symmorphi==0) then
3512      if(dt%nbandkss/=0)then
3513        do isym=1,dt%nsym
3514          if(sum(dt%tnons(:,isym)**2)>tol6)then
3515            write(msg, '(3a,i3,a,3f8.4,3a)' )&
3516            'When nbandkss/=0, all the components of tnons must be zero.',ch10,&
3517            'However, for the symmetry operation number ',isym,', tnons =',dt%tnons(:,isym),'.',ch10,&
3518            'Action: use the symmetry finder (nsym=0) with symmorphi==0.'
3519            ABI_ERROR_NOSTOP(msg,ierr)
3520          end if
3521        end do
3522      end if
3523      if (ANY(optdriver ==[RUNL_SCREENING,RUNL_SIGMA])) then
3524        do isym=1,dt%nsym
3525          if (sum(dt%tnons(:,isym)**2)>tol6) then
3526            write(msg,'(3a,i3,a,3f8.4,3a)')&
3527            'When optdriver==RUNL_SCREENING or RUNL_SIGMA, all the components of tnons must be zero.',ch10,&
3528            'However, for the symmetry operation number ',isym,', tnons =',dt%tnons(:,isym),'.',ch10,&
3529            'Action: use the symmetry finder (nsym=0) with symmorphi==0.'
3530            ABI_ERROR_NOSTOP(msg, ierr)
3531          end if
3532        end do
3533      end if
3534    end if !of symmorphi
3535 
3536 !  tfkinfunc
3537    call chkint_eq(0,0,cond_string,cond_values,ierr,'tfwkinfunc',dt%tfkinfunc,5,(/0,1,2,11,12/),iout)
3538    if(dt%ionmov==4)then
3539      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
3540      call chkint_eq(1,1,cond_string,cond_values,ierr,'tkinfunc',dt%tfkinfunc,1,(/0/),iout)
3541    end if
3542    if(dt%tfkinfunc==2)then
3543      cond_string(1)='tfkinfunc' ; cond_values(1)=dt%tfkinfunc
3544      call chkint_eq(1,1,cond_string,cond_values,ierr,'useylm',dt%useylm,1,(/1/),iout)
3545      cond_string(1)='prtwf' ; cond_values(1)=dt%prtwf
3546      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtwf',dt%prtwf,1,(/0/),iout)
3547    end if
3548 
3549 !  tolmxde
3550    call chkdpr(0,0,cond_string,cond_values,ierr,'tolmxde',dt%tolmxde,1,zero,iout)
3551 
3552 !  toldff
3553    call chkdpr(0,0,cond_string,cond_values,ierr,'toldff',dt%toldff,1,zero,iout)
3554 
3555 !  tolimg
3556    call chkdpr(0,0,cond_string,cond_values,ierr,'tolimg',dt%tolimg,1,zero,iout)
3557 
3558 !  tolrde
3559    call chkdpr(0,0,cond_string,cond_values,ierr,'tolrde',dt%tolrde,1,zero,iout)
3560 
3561 !  tolrff
3562    call chkdpr(0,0,cond_string,cond_values,ierr,'tolrff',dt%tolrff,1,zero,iout)
3563 
3564 !  tolwfr
3565    call chkdpr(0,0,cond_string,cond_values,ierr,'tolwfr',dt%tolwfr,1,zero,iout)
3566 
3567 !  tsmear
3568    call chkdpr(0,0,cond_string,cond_values,ierr,'tsmear',dt%tsmear,1,zero,iout)
3569 !  Check that tsmear is non-zero positive for metallic occupation functions
3570    if(3<=dt%occopt .and. dt%occopt<=9)then
3571      cond_string(1)='occopt' ; cond_values(1)=dt%occopt
3572      call chkdpr(1,1,cond_string,cond_values,ierr,'tsmear',dt%tsmear,1,tol8,iout)
3573    end if
3574 
3575 !  ucrpa
3576    call chkint_eq(0,0,cond_string,cond_values,ierr,'ucrpa',dt%ucrpa,5,(/0,1,2,3,4/),iout)
3577    if (dt%ucrpa>=1) then
3578      cond_string(1)='ucrpa' ; cond_values(1)=dt%ucrpa
3579      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',dt%nspinor,1,(/1/),iout)
3580    end if
3581 
3582 !  usedmatpu
3583    if (usepaw==1.and.dt%usepawu>0) then
3584      cond_string(1)='nstep' ; cond_values(1)=dt%nstep
3585      call chkint_le(1,1,cond_string,cond_values,ierr,'abs(usedmatpu)',abs(dt%usedmatpu),dt%nstep,iout)
3586 !    lpawu must be constant or -1
3587      if (dt%usedmatpu/=0) then
3588        do itypat=1,dt%ntypat
3589          if (dt%lpawu(itypat)/=-1.and.dt%lpawu(itypat)/=maxval(dt%lpawu(:))) then
3590            write(msg, '(3a)' )&
3591            'When usedmatpu/=0 (use of an initial density matrix for DFT+U),',ch10,&
3592            'lpawu must be equal for all types of atoms on which +U is applied !'
3593            ABI_ERROR_NOSTOP(msg,ierr)
3594          end if
3595        end do
3596      end if
3597    end if
3598    !usedmatpu not allowed with experimental usepawu<0
3599    if (usepaw==1.and.dt%usepawu<0) then
3600      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
3601      call chkint_eq(1,1,cond_string,cond_values,ierr,'usedmatpu',dt%usedmatpu,1,(/0/),iout)
3602    end if
3603    !usedmatpu only allowed for GS
3604    if (usepaw==1.and.dt%usedmatpu/=0.and.dt%optdriver/=RUNL_GSTATE) then
3605      ABI_ERROR_NOSTOP('usedmatpu/=0 is only allowed for Ground-State calculations!', ierr)
3606    end if
3607 
3608 !  usedmft
3609    if (dt%usedmft>0) then
3610      cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
3611      call chkint_eq(0,1,cond_string,cond_values,ierr,'usedmft',dt%usedmft,2,(/0,1/),iout)
3612      if (dt%paral_kgb>0) then
3613        cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
3614        call chkint_eq(1,1,cond_string,cond_values,ierr,'npspinor',dt%npspinor,1,(/1/),iout)
3615      end if
3616 !    call chkint_eq(1,1,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,1,(/0/),iout)
3617    end if
3618 
3619 !  useexexch and lexexch
3620 !  Local exact-exchange and restrictions
3621    if(dt%useexexch/=0)then
3622      cond_string(1)='useexexch' ; cond_values(1)=dt%useexexch
3623      call chkint_eq(1,1,cond_string,cond_values,ierr,'useexexch',dt%useexexch,1,(/1/),iout)
3624      call chkint_eq(1,1,cond_string,cond_values,ierr,'usepaw',usepaw,1,(/1/),iout)
3625      call chkint_eq(1,1,cond_string,cond_values,ierr,'pawxcdev',dt%pawxcdev,2,(/1,2/),iout)
3626      call chkint_eq(1,1,cond_string,cond_values,ierr,'ixc',dt%ixc,2,(/11,23/),iout)
3627      do itypat=1,dt%ntypat
3628        cond_string(1)='lexexch' ; cond_values(1)=dt%lexexch(itypat)
3629        call chkint_eq(1,1,cond_string,cond_values,ierr,'lexexch',dt%lexexch(itypat),5,(/-1,0,1,2,3/),iout)
3630      end do
3631    end if
3632 
3633 !  usefock and restrictions
3634    call chkint_eq(0,0,cond_string,cond_values,ierr,'usefock',dt%usefock,2,(/0,1/),iout)
3635 
3636    if (dt%use_gemm_nonlop == 1) then
3637      if (dt%useylm /= 1) then
3638        ABI_ERROR_NOSTOP('use_gemm_nonlop requires the input variable "useylm" to be 1',ierr)
3639      end if
3640    end if
3641 
3642 !  usekden
3643    call chkint_eq(0,0,cond_string,cond_values,ierr,'usekden',dt%usekden,2,(/0,1/),iout)
3644 !  The following test is only a way to practically prevent the usage of mGGA with nspden=4 (not allowed yet),
3645 !  while allowing to have usekden=1 with nspden=4. Indeed, while mGGA is not allowed for the non-collinear case,
3646 !  the computation of the kinetic energy density in the non-collinear spin case is working, and there are tests of this ...
3647 !  What should be done : modify the definition of xclevel, to index differently GGAs and mGGAs, etc, and test on xclevel instead of usekden.
3648    if(dt%nspden==4 .and. dt%prtkden==0)then
3649      cond_string(1)='nspden' ; cond_values(1)=dt%nspden
3650      cond_string(1)='prtkden' ; cond_values(2)=dt%prtkden
3651      call chkint_eq(1,2,cond_string,cond_values,ierr,'usekden',dt%usekden,1,(/0/),iout)
3652    endif
3653    if(dt%usekden==0)then
3654      cond_string(1)='usekden' ; cond_values(1)=dt%usekden
3655      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtkden',dt%prtkden,1,(/0/),iout)
3656      if(xc_need_kden.and.dt%usekden<1)then
3657        write(msg, '(3a)' )&
3658        'The functional is a MGGA using kinetic energy density, but the kinetic energy density',ch10, &
3659        'is not present. Please set "usekden 1" in the input file.'
3660        ABI_ERROR(msg)
3661      end if
3662    else if(dt%usekden/=0)then
3663      cond_string(1)='usekden' ; cond_values(1)=dt%usekden
3664      call chkint_eq(1,1,cond_string,cond_values,ierr,'usewvl',usewvl,1,(/0/),iout)
3665 !     call chkint_eq(1,1,cond_string,cond_values,ierr,'usepaw',usepaw,1,(/0/),iout)
3666      call chkint_eq(1,1,cond_string,cond_values,ierr,'intxc',dt%intxc,1,(/0/),iout)
3667      do ipsp=1,npsp
3668 !      Check that xccc is zero (NCPP metaGGAs cannot be used at present with non-linear core corrections)
3669        if (pspheads(ipsp)%xccc/=0.and.usepaw==0) then
3670          write(msg, '(5a,i0,3a)' )&
3671 &         'When usekden/=0, it is not possible to use norm-conserving pseudopotentials',ch10,&
3672 &         'with a non-linear core correction.',ch10,&
3673 &         'However, for pseudopotential number ',ipsp,', there is such a core correction.',ch10,&
3674 &         'Action: either set usekden=0 in input file, or change this pseudopotential file.'
3675          ABI_ERROR_NOSTOP(msg, ierr)
3676        end if
3677      end do
3678    end if
3679 
3680 !  usepawu and lpawu
3681 !  PAW+U and restrictions
3682    call chkint_eq(0,0,cond_string,cond_values,ierr,'usepawu',dt%usepawu,11,(/-4,-3,-2,-1,0,1,2,3,4,10,14/),iout)
3683    if(dt%usedmft==1)then
3684      cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
3685      call chkint_eq(1,1,cond_string,cond_values,ierr,'usepawu',dt%usepawu,2,(/10,14/),iout)
3686    end if
3687    if(dt%usedmft==0)then
3688      cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
3689      call chkint_eq(1,1,cond_string,cond_values,ierr,'usepawu',dt%usepawu,9,(/-4,-3,-2,-1,0,1,2,3,4/),iout)
3690    end if
3691    if(dt%usepawu/=0)then
3692      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
3693      call chkint_eq(1,1,cond_string,cond_values,ierr,'usepaw',dt%usepaw,1,(/1/),iout)
3694      do itypat=1,dt%ntypat
3695        cond_string(1)='lpawu' ; cond_values(1)=dt%lpawu(itypat)
3696        call chkint_eq(1,1,cond_string,cond_values,ierr,'lpawu',dt%lpawu(itypat),5,(/-1,0,1,2,3/),iout)
3697      end do
3698      if(dt%pawspnorb>0) then
3699        write(msg,'(3a)' ) &
3700 &       '  DFT+U+SpinOrbit is still on test ',ch10,&
3701 &       '  (not yet in production)'
3702        ABI_WARNING(msg)
3703      end if
3704    end if
3705 
3706 !  usepawu and response : q must be zero
3707    if(dt%usepawu/=0.and.response==1) then
3708      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
3709      call chkdpr(1,1,cond_string,cond_values,ierr,'norm(qpt)',sum(dt%qptn(:)**2),0,zero,iout)
3710    end if
3711 
3712 !  useexexch AND usepawu
3713 !  Restriction when use together
3714    if(dt%useexexch/=0.and.dt%usepawu/=0)then
3715      do itypat=1,dt%ntypat
3716        if (dt%lpawu(itypat)/=dt%lexexch(itypat).and.dt%lpawu(itypat)/=-1.and.dt%lexexch(itypat)/=-1) then
3717          write(msg, '(5a,i2,3a)' )&
3718 &         'When PAW+U (usepawu/=0) and local exact-exchange (useexexch/=0)',ch10,&
3719 &         'are selected together, they must apply on the same',ch10,&
3720 &         'angular momentum (lpawu/=lexexch forbidden, here for typat=',itypat,') !',ch10,&
3721 &         'Action: correct your input file.'
3722          ABI_ERROR_NOSTOP(msg,ierr)
3723        end if
3724      end do
3725    end if
3726 
3727 !  usedmft/usepawu and lpawu
3728 !  Restriction when use together
3729    if(dt%usedmft>0.or.dt%usepawu/=0)then
3730      nlpawu=0
3731      do itypat=1,dt%ntypat
3732        if (dt%lpawu(itypat)/=-1) then
3733          nlpawu=nlpawu+1
3734        end if
3735      end do
3736      if(nlpawu==0) then
3737        write(msg, '(6a)' )&
3738 &       'When DFT+U or DFT+DMFT is used',ch10,&
3739 &       'at least one value of lpawu should be different from -1',ch10,&
3740 &       'Action: correct your input file.'
3741        ABI_ERROR(msg)
3742      end if
3743    end if
3744 
3745 !  usepotzero
3746    if(dt%usepotzero/=0)then
3747      if(dt%iscf<10) then
3748        write(msg, '(3a)' )&
3749         'usepotzero can only be used with density mixing (not implemented yet)',ch10,&
3750         'Action: choose iscf > 10 '
3751        ABI_ERROR_NOSTOP(msg,ierr)
3752      end if
3753    end if
3754 
3755 !  usexcnhat
3756    call chkint_eq(0,0,cond_string,cond_values,ierr,'usexcnhat',dt%usexcnhat_orig,3,(/-1,0,1/),iout)
3757 
3758 !  useylm
3759    call chkint_eq(0,0,cond_string,cond_values,ierr,'useylm',dt%useylm,2,(/0,1/),iout)
3760    if (usepaw==1) then
3761      cond_string(1)='usepaw' ; cond_values(1)=usepaw
3762      cond_string(2)='usewvl' ; cond_values(2)=usewvl
3763      if(usewvl==0) then
3764        call chkint_eq(1,1,cond_string,cond_values,ierr,'useylm',dt%useylm,1,(/1/),iout)
3765      else
3766        call chkint_eq(1,1,cond_string,cond_values,ierr,'useylm',dt%useylm,1,(/0/),iout)
3767      end if
3768    end if
3769 
3770 !  use_slk
3771    if (dt%paral_kgb==1) then
3772      call chkint_eq(0,0,cond_string,cond_values,ierr,'use_slk',dt%use_slk,2,(/0,1/),iout)
3773    end if
3774 
3775 !  use_oldchi
3776    call chkint_eq(0,0,cond_string,cond_values,ierr,'use_oldchi',dt%use_oldchi,2,(/0,1/),iout)
3777 
3778 !  vdw_xc
3779    call chkint_eq(0,0,cond_string,cond_values,ierr,'vdw_xc',dt%vdw_xc,9,(/0,1,2,5,6,7,10,11,14/),iout)
3780    if (dt%usepaw==1.and.(.not.(dt%vdw_xc==0.or.dt%vdw_xc==5.or.dt%vdw_xc==6.or.dt%vdw_xc==7))) then
3781      write(msg,'(a,i2,a)')'vdw_xc=',dt%vdw_xc,' is not yet available with Projector Augmented-Wave (PAW) formalism!'
3782      ABI_ERROR_NOSTOP(msg, ierr)
3783    end if
3784 
3785 !  vdw DFT-D2
3786    if (dt%vdw_xc==5.or.dt%vdw_xc==6.or.dt%vdw_xc==7) then
3787 !    Only for GS or RF calculations
3788      if(optdriver/=RUNL_GSTATE.and.optdriver/=RUNL_RESPFN) then
3789        cond_string(1)='vdw_xc' ; cond_values(1)=dt%vdw_xc
3790        call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',optdriver,2,(/RUNL_GSTATE,RUNL_RESPFN/),iout)
3791      end if
3792 !    Restriction for DFT-D2
3793      if (dt%vdw_xc==5) then
3794 !    Only with PBE, BP86 or BLYP GGA XC
3795        if(dt%ixc/=11.and.dt%ixc/=-101130.and.dt%ixc/=-130101.and. &
3796 &         dt%ixc/=18.and.dt%ixc/=-106131.and.dt%ixc/=-131106.and. &
3797 &         dt%ixc/=19.and.dt%ixc/=-106132.and.dt%ixc/=-132106.and. &
3798 &         dt%ixc/=-202231.and.dt%ixc/=-231202) then
3799          write(msg,'(8a)') ch10,&
3800 &         ' chkinp : ERROR -',ch10,&
3801 &         '  Van der Waals DFT-D2 correction (vdw_xc=5) only available for the following XC functionals:',ch10,&
3802 &         '      GGA-PBE, GGA-BLYP, GGA-BP86, mGGA-TPSS',ch10,&
3803 &         '  Action: change your pseudopotential file.'
3804          call wrtout(std_out,msg)
3805          ierr=ierr+1
3806        end if
3807 !       Only for the first 5 lines of the periodic table
3808        do itypat=1,dt%ntypat
3809          if (dt%znucl(itypat)<0.or.dt%znucl(itypat)>54) then
3810            write(msg,'(4a,f5.1,a)') ch10,&
3811 &           ' chkinp : ERROR -',ch10,&
3812 &           '  Van der Waals DFT-D2 correction (vdw_xc=5) not available for atom type Z=',dt%znucl(itypat),' !'
3813            call wrtout(std_out,msg)
3814            ierr=ierr+1
3815          end if
3816        end do
3817      end if
3818 !    Restriction for DFT-D3/DFT-D3(BJ)
3819      if (dt%vdw_xc==6.or.dt%vdw_xc==7) then
3820 !    Only with PBE, BP86  or BLYP GGA XC
3821        if(dt%ixc/=11.and.dt%ixc/=-101130.and.dt%ixc/=-130101.and. &
3822 &         dt%ixc/=18.and.dt%ixc/=-106131.and.dt%ixc/=-131106.and. &
3823 &         dt%ixc/=19.and.dt%ixc/=-106132.and.dt%ixc/=-132106.and. &
3824 &         dt%ixc/=-202231.and.dt%ixc/=-231202.and.&
3825 &         dt%ixc/=14.and.dt%ixc/=-102130.and.dt%ixc/=-130102.and. &
3826 &         dt%ixc/=-170.and.dt%ixc/=41.and.dt%ixc/=-406) then
3827          write(msg,'(4a,i2,5a)') ch10,&
3828 &         ' chkinp : ERROR -',ch10,&
3829 &         '  Van der Waals DFT-D correction (vdw_xc=',dt%vdw_xc,') only available for the following XC functionals:',ch10,&
3830 &         '      GGA-PBE, GGA-BLYP, GGA-BP86, mGGA-TPSS, GGA-RevPBE, PBE0',ch10,&
3831 &         '  Action: change your pseudopotential file.'
3832          call wrtout(std_out,msg)
3833          ierr=ierr+1
3834        end if
3835 !       Only up to chemical species 96
3836        do itypat=1,dt%ntypat
3837          if (dt%znucl(itypat)<0.or.dt%znucl(itypat)>96) then
3838            write(msg,'(4a,i2,1a,f5.1,a)') ch10,&
3839 &           ' chkinp : ERROR -',ch10,&
3840 &           '  Van der Waals DFT-D correction (vdw_xc=',dt%vdw_xc,') not available for atom type Z=',dt%znucl(itypat),' !'
3841            call wrtout(std_out,msg)
3842            ierr=ierr+1
3843          end if
3844        end do
3845      end if
3846    end if
3847 
3848 !  wfoptalg
3849 !  Must be greater or equal to 0
3850    call chkint_ge(0,0,cond_string,cond_values,ierr,'wfoptalg',dt%wfoptalg,0,iout)
3851 !  wfoptalg==0,1,4,10,14 or 114 if PAW
3852    if (usepaw==1) then
3853      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
3854      call chkint_eq(0,1,cond_string,cond_values,ierr,'wfoptalg',dt%wfoptalg,7,(/0,1,4,10,14,111,114/),iout)
3855    end if
3856 !  wfoptalg/=114 if PAW+Fock
3857    if (usepaw==1 .and. dt%usefock==1) then
3858      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
3859      cond_string(2)='usefock' ; cond_values(2)=dt%usefock
3860      call chkint_ne(1,2,cond_string,cond_values,ierr,'wfoptalg',dt%wfoptalg,1,(/114/),iout)
3861    end if
3862 
3863    ! Check if FFT library supports MPI-FFT.
3864    if (dt%npfft > 1 .and..not. fftalg_has_mpi(fftalg)) then
3865      write(msg,"(a,i0,a)")"fftalg: ",fftalg," cannot be used in MPI-FFT mode (npfft > 1)"
3866      ABI_ERROR_NOSTOP(msg,ierr)
3867    end if
3868 
3869    ! Chebyshev
3870    if(dt%wfoptalg == 1 .or. dt%wfoptalg == 111) then
3871      if(dt%nspinor > 1 .and. dt%wfoptalg == 1) then
3872        msg='Nspinor > 1 not yet compatible with wfoptalg 1. Use chebfi V2 instead (wfoptalg=111).'
3873        ABI_ERROR_NOSTOP(msg, ierr)
3874      end if
3875      if(dt%usefock > 0) then
3876        ABI_ERROR_NOSTOP('Fock not yet compatible with wfoptalg 1 (use Fock-level parallelism)', ierr)
3877      end if
3878      if(maxval(abs(dt%istwfk(1:nkpt))) > 2) then
3879        ABI_ERROR_NOSTOP('Istwfk > 2 not compatible with wfoptalg 1', ierr)
3880      end if
3881      if(dt%ecutsm > 0) then
3882        ABI_ERROR_NOSTOP('Ecutsm > 0 not yet compatible with wfoptalg 1', ierr)
3883      end if
3884      !! TODO check bandpp instead of overwriting it
3885    end if
3886 
3887 !  np_slk
3888    call chkint_ge(0,0,cond_string,cond_values,ierr,'np_slk',dt%np_slk,0,iout)
3889    if (dt%np_slk>0 .and. dt%wfoptalg /= 114 ) then
3890      if(dt%np_slk <= dt%npfft*dt%npband*dt%npspinor .and. MOD(dt%npfft*dt%npband*dt%npspinor, dt%np_slk) /= 0) then
3891        ABI_ERROR_NOSTOP('np_slk must divide npfft*npband*npspinor.',ierr)
3892      end if
3893    end if
3894 !  slk_rankpp
3895    call chkint_ge(0,0,cond_string,cond_values,ierr,'slk_rankpp',dt%slk_rankpp,0,iout)
3896 
3897 !  wtk
3898 !  Check that no k point weight is < 0:
3899    do ikpt=1,nkpt
3900      if (dt%wtk(ikpt)< -tiny(0.0_dp) ) then
3901        write(msg, '(a,i5,a,1p,e12.4,a,a,a)' )&
3902 &       'At k point number',ikpt,'  wtk=',dt%wtk(ikpt),' <0.',ch10,&
3903 &       'Action: check wtk in input file. Each wtk must be >=0.'
3904        ABI_ERROR_NOSTOP(msg,ierr)
3905      end if
3906    end do
3907 
3908 !  w90prtunk
3909    call chkint_ge(0,0,cond_string,cond_values,ierr,'w90prtunk',dt%w90prtunk,0,iout)
3910 
3911 !  xc_denpos
3912    call chkdpr(0,0,cond_string,cond_values,ierr,'xc_denpos',dt%xc_denpos,1,tiny(one),iout)
3913 
3914 !  xc_taupos
3915 !  Allow for negative value of xc_taupos (to deactivate it)
3916 !  call chkdpr(0,0,cond_string,cond_values,ierr,'xc_taupos',dt%xc_taupos,1,tiny(one),iout)
3917 
3918 !  xc_tb09_c
3919    call chkdpr(0,0,cond_string,cond_values,ierr,'xc_tb09_c',dt%xc_tb09_c,1,0.0_dp,iout)
3920    !if (dt%xc_tb09_c>99._dp.and.dt%iscf==22) then
3921    !  write(msg, '(a,i4,a,i4,a,a,a,a,a,a)' )&
3922    !&   'TB09 XC functional with variable c is not compatible with ODA mixing (iscf=22)!'
3923    !  ABI_ERROR_NOSTOP(msg,ierr)
3924    !end if
3925 
3926 !  xred
3927 !  Check that two atoms are not on top of each other
3928    do iimage=1,dt%nimage
3929      if(natom>1)then
3930        ABI_MALLOC(frac,(3,natom))
3931        do ia=1,natom
3932 !        Map reduced coordinate xred(mu,ia) into [0,1)
3933          frac(1,ia)=dt%xred_orig(1,ia,iimage)-aint(dt%xred_orig(1,ia,iimage))+0.5_dp-sign(0.5_dp,dt%xred_orig(1,ia,iimage))
3934          frac(2,ia)=dt%xred_orig(2,ia,iimage)-aint(dt%xred_orig(2,ia,iimage))+0.5_dp-sign(0.5_dp,dt%xred_orig(2,ia,iimage))
3935          frac(3,ia)=dt%xred_orig(3,ia,iimage)-aint(dt%xred_orig(3,ia,iimage))+0.5_dp-sign(0.5_dp,dt%xred_orig(3,ia,iimage))
3936        end do
3937        do ia=1,natom-1
3938          do ib=ia+1,natom
3939            if( abs(frac(1,ia)-frac(1,ib))<1.0d-6 .and. &
3940 &           abs(frac(2,ia)-frac(2,ib))<1.0d-6 .and. &
3941 &           abs(frac(3,ia)-frac(3,ib))<1.0d-6         ) then
3942              if(iimage>1)then
3943                write(msg,'(2a,i5)') ch10,' The following was observed for image=',iimage
3944                call wrtout(iout,msg)
3945                call wrtout(std_out,msg)
3946              end if
3947              write(msg, '(a,i4,a,i4,a,a,a,a,a,a)' )&
3948 &             'Atoms number',ia,' and',ib,' are located at the same point',' of the unit cell',ch10,&
3949 &             '(periodic images are taken into account).',ch10,&
3950 &             'Action: change the coordinate of one of these atoms in the input file.'
3951              ABI_ERROR_NOSTOP(msg,ierr)
3952            end if
3953          end do
3954        end do
3955        ABI_FREE(frac)
3956      end if
3957    end do
3958 
3959 !  znucl
3960 !  Check that znucl and znuclpsp agree
3961    do ipsp=1,npsp
3962      if (abs(dt%znucl(ipsp)-pspheads(ipsp)%znuclpsp)> tol12 ) then
3963        write(msg, '(a,i0,a,es12.4,a,a,es12.4,2a)' )&
3964 &       'For pseudopotential ',ipsp,'  znucl from user input file= ',dt%znucl(ipsp),ch10,&
3965 &       'while znucl from pseudopotential file=',pspheads(ipsp)%znuclpsp,ch10,&
3966 &       'Action: check znucl in input file, or check psp file. They must agree.'
3967        ABI_ERROR_NOSTOP(msg,ierr)
3968      end if
3969    end do
3970 
3971 !  bandFFT
3972    if(dt%paral_kgb==1.and.dt%optdriver==RUNL_GSTATE) then
3973      if (mod(dt%wfoptalg,10) /= 4 .and. mod(dt%wfoptalg,10) /= 1) then
3974        write(msg,'(a,i0,a,a,a,a)')&
3975 &       'The value of wfoptalg is found to be ',dt%wfoptalg,ch10,&
3976 &       'This is not allowed in the case of band-FFT parallelization.',ch10,&
3977 &       'Action: put wfoptalg = 4, 14 or 114 in your input file'
3978        ABI_ERROR_NOSTOP(msg,ierr)
3979      end if
3980 !    Make sure all nband are equal
3981      if (any(dt%nband(1:nkpt*nsppol) /= maxval(dt%nband(1:nkpt*nsppol)) )) then
3982        write(msg,'(a,a,a)')&
3983 &       'The number of bands have to remain constant in the case of band-FFT parallelization.',ch10,&
3984 &       'Action: set all the nbands to the same value in your input file'
3985        ABI_ERROR_NOSTOP(msg,ierr)
3986      end if
3987      if(maxval(abs(dt%istwfk(1:nkpt)-1)) > 1)then
3988        write(msg,'(5a)' )&
3989 &       'One of the components of istwfk is not equal to 1 or 2.',ch10,&
3990 &       'Time-reversal symmetry is not yet programmed in the case of band-FFT parallelization.',ch10,&
3991 &       'Action: set istwfk to 1 or 2 for all k-points'
3992        ABI_ERROR_NOSTOP(msg,ierr)
3993      end if
3994      if (dt%mkmem == 0) then
3995        write(msg,'(a,i0,a,a,a,a)')&
3996 &       'The value of mkmem is found to be ',dt%mkmem,ch10,&
3997 &       'An out-of-core solution can''t be used in the case of band-FFT parallelization.',ch10,&
3998 &       'Action: put mkmem = nkpt in your input file'
3999        ABI_ERROR_NOSTOP(msg,ierr)
4000      end if
4001    end if
4002 
4003 !  WVL - wavelets checks and limitations
4004    if(dt%usewvl == 1) then
4005      if (dt%wvl_hgrid <= 0) then
4006        write(msg,'(a,i0,a,a,a,a)')&
4007 &       'The value of wvl_hgrid is found to be ',dt%wvl_hgrid,ch10,&
4008 &       'This value is mandatory and must be positive.',ch10,&
4009 &       'Action: put wvl_hgrid to a positive value in your input file'
4010        ABI_ERROR_NOSTOP(msg,ierr)
4011      end if
4012      if (dt%nsym /= 1 .and. dt%icoulomb == 1) then
4013        write(msg,'(a,i0,a,a,a,a)')&
4014 &       'The value of nsym is found to be ',dt%nsym,ch10,&
4015 &       'No symetry operations are allowed for isolated systems.',ch10,&
4016 &       'Action: put nsym = 1 in your input file'
4017        ABI_ERROR_NOSTOP(msg,ierr)
4018      end if
4019      if (dt%optstress > 0) then
4020        write(msg,'(a,i0,a,a,a,a)')&
4021 &       'The value of optstress is found to be ', dt%optstress, ch10,&
4022 &       'There is no stress computation available with the wavelet code.',ch10,&
4023 &       'Action: put optstress = 0 in your input file'
4024        ABI_ERROR_NOSTOP(msg,ierr)
4025      end if
4026      if (usepaw == 1) then
4027        ABI_WARNING('WVL+PAW is under development')
4028      end if
4029      if (dt%nspden > 2) then
4030        write(msg,'(a,i0,a,a,a,a)')&
4031 &       'The value of nspden is found to be ', dt%nspden, ch10, &
4032 &       'The wavelet computation is not allowed with non-colinear spin.',ch10,&
4033 &       'Action: put nspden = 1 or 2 in your input file'
4034        ABI_ERROR_NOSTOP(msg,ierr)
4035      end if
4036      if (dt%nspden /= dt%nsppol) then
4037        write(msg,'(a,i0,a,a,i0,a,a)')&
4038 &       'The value of nspden is found to be ', dt%nspden, ch10, &
4039 &       'and the one of nsppol is found to be ', dt%nsppol, ch10, &
4040 &       'In wavelet computation, nspden and nsppol must be equal.'
4041        ABI_ERROR_NOSTOP(msg,ierr)
4042      end if
4043 !    We check the consistency of occupation, empty bands are not allowed.
4044      if (dt%nsppol == 2) then
4045        mband = dt%nelect
4046      else
4047        mband = dt%mband
4048      end if
4049      do iimage=1,dt%nimage
4050        do ii = 1, mband, 1
4051          if (dt%occ_orig(ii,iimage) < tol8 .and. dt%iscf == 0) then
4052            write(msg,'(a,f7.4,a,a,a,a,a,a)')&
4053 &           'One value of occ is found to be ', dt%occ_orig(ii,iimage), ch10, &
4054 &           'The direct minimization is not allowed with empty bands.',ch10,&
4055 &           'Action: use occopt = 1 for automatic band filling or', ch10, &
4056 &           'change occ value in your input file'
4057            ABI_ERROR_NOSTOP(msg,ierr)
4058          end if
4059        end do
4060      enddo
4061      if (npsp /= dt%ntypat) then
4062        write(msg, '(a,a,a,a,I0,a,I0,a,a,a)' ) ch10,&
4063 &       'wvl_wfs_set:  consistency checks failed,', ch10, &
4064 &       'dtset%npsp (', npsp, ') /= dtset%ntypat (', dt%ntypat, ').', ch10, &
4065 &       'No alchemy pseudo are allowed with wavelets.'
4066        ABI_ERROR_NOSTOP(msg,ierr)
4067      end if
4068    end if
4069 
4070    ! Test on tolerances (similar tests are performed in scprqt, so keep the two versions in synch)
4071    if (any(optdriver == [RUNL_GSTATE, RUNL_RESPFN])) then
4072      ttolwfr=0 ; ttoldff=0 ; ttoldfe=0 ; ttolvrs=0; ttolrff=0
4073      if(abs(dt%tolwfr)>tiny(zero))ttolwfr=1
4074      if(abs(dt%toldff)>tiny(zero))ttoldff=1
4075      if(abs(dt%tolrff)>tiny(zero))ttolrff=1
4076      if(abs(dt%toldfe)>tiny(zero))ttoldfe=1
4077      if(abs(dt%tolvrs)>tiny(zero))ttolvrs=1
4078 
4079      ! If non-scf calculations, tolwfr must be defined
4080      if(ttolwfr /= 1 .and. ((dt%iscf<0 .and. dt%iscf/=-3) .or. dt%rf2_dkdk/=0 .or. dt%rf2_dkde/=0))then
4081        write(msg,'(a,a,a,es14.6,a,a)')&
4082         'When iscf < 0 and /= -3, or when rf2_dkdk /= 0 or rf2_dkde /= 0, tolwfr must be strictly',ch10,&
4083         'positive as this is the only convergence criterion that can be used, while it is: ',dt%tolwfr,ch10,&
4084         'Action: use tolwfr in your input file and resubmit the job.'
4085        ABI_ERROR_NOSTOP(msg, ierr)
4086      end if
4087      !  toldff only allowed when prtfor==1
4088      !if((ttoldff == 1 .or. ttolrff == 1) .and. dt%prtfor==0 )then
4089      !  ABI_ERROR_NOSTOP('toldff only allowed when prtfor=1!', ierr)
4090      !end if
4091 
4092      ! If SCF calculations, one and only one of these can differ from zero
4093      if ( (dt%iscf>0 .or. dt%iscf==-3) .and. &
4094        & ( (ttolwfr==1.and.ttoldff+ttoldfe+ttolvrs+ttolrff>1) .or. (ttolwfr==0.and.ttoldff+ttoldfe+ttolvrs+ttolrff/=1) ) ) then
4095        write(msg,'(6a,es14.6,a,es14.6,a,es14.6,a,a,es14.6,a,i0,2a)' )&
4096         'For the SCF case, one and only one of the input tolerance criteria ',ch10,&
4097         'toldff, tolrff, toldfe or tolvrs ','must differ from zero, while they are',ch10,&
4098         'toldff=',dt%toldff,', tolrff=',dt%tolrff,', toldfe=',dt%toldfe,ch10,&
4099         'and tolvrs=',dt%tolvrs,' for idtset: ', idtset, ch10,&
4100         'Action: change your input file and resubmit the job.'
4101        ABI_ERROR_NOSTOP(msg, ierr)
4102      end if
4103 
4104      if (ttolwfr==1.and.dt%tolwfr_diago>dt%tolwfr) then
4105        write(msg, '(2a,2(a,es14.6),a)' )&
4106         ' tolwfr diago cannot be bigger than tolwfr !',ch10,&
4107         ' tolwfr=',dt%tolwfr,' and tolwfr_diago=',dt%tolwfr_diago,&
4108         ' Action: change the value of tolwfr or tolwfr_diago in the input file.'
4109        ABI_ERROR_NOSTOP(msg, ierr)
4110      end if
4111 
4112    end if
4113 
4114    if (optdriver == RUNL_GWR) then
4115      msg = "G0W0, HDIAGO, HDIAGO_FULL, RPA_ENERGY, EGEW, EGW0, G0EW, G0V, CC4S, CC4S_FULL, GAMMA_GW, CHI0"
4116      if (.not. string_in(dt%gwr_task, msg)) then
4117        ABI_ERROR_NOSTOP(sjoin("Invalid gwr_task:`", dt%gwr_task, "`, must be among:", msg), ierr)
4118      end if
4119 #ifndef HAVE_LINALG_SCALAPACK
4120      ABI_ERROR("GWR code requires scalapack library")
4121 #endif
4122 
4123      ! Avoid wasting CPUs if nsppol==2.
4124      !if (dt%nsppol == 2 .and. .not. iseven(nproc) .and. nproc > 1) then
4125      !  write(msg,'(3a)') "Spin-polarized GW calculations should be run with an even number of processors ",ch10,&
4126      !   " for achieving an optimal distribution of memory and CPU load. Please change the number of processors."
4127      !  ABI_ERROR_NOSTOP(msg, ierr)
4128      !end if
4129      !if (dt%usepaw == 1) then
4130      !  ABI_ERROR_NOSTOP("GWR with PAW not yet implemented", ierr)
4131      !end if
4132      if (dt%nshiftk /= 1 .or. any(abs(dt%shiftk(:,1)) > tol6)) then
4133        ABI_ERROR_NOSTOP('GWR requires Gamma-centered k-meshes', ierr)
4134      end if
4135    end if
4136 
4137    ! ===========================================================
4138    ! Write COMMENTs if some combination of input vars look weird
4139    ! ===========================================================
4140    if (optdriver == RUNL_EPH .and. dt%dipdip /= 0 .and. any(dt%occopt == [3, 4, 5, 6, 7])) then
4141      ABI_COMMENT("dipdip can be set to 0 in case of metals whereas dipdip 1 should be used in polar materials.")
4142    end if
4143 
4144 !  If molecular dynamics or structural optimization is being done
4145 !  (dt%ionmov>0), make sure not all atoms are fixed
4146 !  if (dt%ionmov > 0) then
4147 !  if (natfix == natom) then
4148 !  write(msg, '(a,a,a,a,i4,a,i5,a,a,i5,a,a,a,a,a,a)' ) ch10,&
4149 !  &   ' setup1: ERROR -',ch10,&
4150 !  &   '  ionmov is ',dt%ionmov,' and number of fixed atoms is ',natfix,ch10,&
4151 !  &   '  while number of atoms natom is ',natom,'.',ch10,&
4152 !  &   '  Thus all atoms are fixed and option ionmov to move atoms',&
4153 !  &           ' is inconsistent.',ch10,&
4154 !  &   '  Action: change ionmov or natfix and iatfix in input file and resubmit.'
4155 !  call wrtout(std_out,msg)
4156 !  ierr = ierr + 1
4157 !  end if
4158 !  end if
4159 
4160 !  Should check that the symmetry operations are consistent with iatfixx,
4161 !  iatfixy and iatfixz (diagonal symmetry operations)
4162 
4163 !  Should check values of fftalg
4164 
4165 !  Must have nqpt=1 for rfphon=1
4166 
4167 !  ** Here ends the checking section **************************************
4168 
4169    call dt%free()
4170    ierr_dtset(idtset)=ierr
4171 
4172  end do !  End do loop on idtset
4173 
4174  if (maxval(dtsets(:)%usewvl) > 0) then
4175    write(msg,'(4a)') ch10,&
4176 &   ' Comparison between wvl_hgrid and ecut',ch10,&
4177 &   '  real-space mesh | eq. Ec around atoms | eq. Ec further from atoms'
4178    ABI_COMMENT(msg)
4179    wvl_hgrid = zero
4180    twvl = .false.
4181    do idtset=1,ndtset_alloc
4182 !    Give an indication to the equivalent ecut corresponding to
4183 !    given hgrid.
4184      if (dtsets(idtset)%usewvl == 1 .and. wvl_hgrid /= dtsets(idtset)%wvl_hgrid) then
4185        write(msg,'(F11.3,A,F16.1,A,F16.1,A)') &
4186 &       dtsets(idtset)%wvl_hgrid, " bohr  |", &
4187 &       two * pi * pi / (dtsets(idtset)%wvl_hgrid ** 2), " Ht  | ", &
4188 &       half * pi * pi / (dtsets(idtset)%wvl_hgrid ** 2), " Ht"
4189        call wrtout(std_out,msg)
4190        wvl_hgrid = dtsets(idtset)%wvl_hgrid
4191      end if
4192      twvl = twvl .or. (dtsets(idtset)%usewvl == 1 .and. dtsets(idtset)%iomode /= IO_MODE_ETSF)
4193    end do
4194    if (twvl) then
4195      write(msg,'(5a)') &
4196 &     'Restart files from wavelets in non ETSF format does not follow', ch10, &
4197 &     'the ABINIT standards.', ch10, &
4198 &     'Set iomode to 3 to use ETSF retart files.'
4199      ABI_WARNING(msg)
4200    end if
4201  end if
4202 
4203  ! If there was a problem, then stop.
4204  call xmpi_sum(ierr_dtset, comm, mpierr)
4205  ierr=sum(ierr_dtset(1:ndtset_alloc)/mpi_enregs(1:ndtset_alloc)%nproc)
4206 
4207  if (ierr==1) then
4208    write(msg,'(6a)')ch10,&
4209    'Checking consistency of input data against itself revealed some problem(s).',ch10,&
4210    'So, stopping. The details of the problem(s) are given in the error file or the standard output file (= "log" file).',ch10,&
4211    'In parallel, the details might not even be printed there. Then, try running in sequential to see the details.'
4212    call wrtout(iout,msg)
4213    write(msg,'(a,i0,5a)')&
4214    'Checking consistency of input data against itself gave ',ierr,' inconsistency.',ch10,&
4215    'The details of the problem can be found above (or in output or log file).',ch10,&
4216    'In parallel, the details might not even be printed there. Then, try running in sequential to see the details.'
4217    call flush_unit(std_out)
4218    ABI_ERROR(msg)
4219  end if
4220  if (ierr>1) then
4221    write(msg,'(a,i0,5a)')&
4222    'Checking consistency of input data against itself gave ',ierr,' inconsistencies.',ch10,&
4223    'The details of the problems can be found above (or in output or log file), in an earlier WARNING.',ch10,&
4224    'In parallel, the details might not even be printed there. Then, try running in sequential to see the details.'
4225    call flush_unit(std_out)
4226    ABI_ERROR(msg)
4227  end if
4228 
4229  ABI_FREE(ierr_dtset)
4230 
4231  if (ndtset_alloc /= 1 .and. get_timelimit() > zero) then
4232    ABI_ERROR("--timelimit option cannot be used when ndtset > 1")
4233  end if
4234 
4235  DBG_EXIT("COLL")
4236 
4237 end subroutine chkinp

ABINIT/m_chkinp [ Modules ]

[ Top ] [ Modules ]

NAME

  m_chkinp

FUNCTION

 Check consistency of Abinit input data against itself.

COPYRIGHT

  Copyright (C) 1998-2024 ABINIT group (DCA, XG, GMR, MKV, DRH, MVer)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

SOURCE

16 #if defined HAVE_CONFIG_H
17 #include "config.h"
18 #endif
19 
20 #include "abi_common.h"
21 
22 module m_chkinp
23 
24  use defs_basis
25  use m_gwdefs
26  use m_abicore
27  use m_errors
28  use m_xmpi
29  use m_xomp
30  use libxc_functionals
31  use m_dtset
32 
33  use defs_datatypes,   only : pspheader_type
34  use defs_abitypes,    only : MPI_type
35  use m_io_tools,       only : flush_unit
36  use m_numeric_tools,  only : iseven, isdiagmat
37  use m_symtk,          only : sg_multable, chkorthsy, symmetrize_xred
38  use m_fstrings,       only : string_in, sjoin
39  use m_geometry,       only : metric
40  use m_fftcore,        only : fftalg_has_mpi
41  use m_exit,           only : get_timelimit
42  use m_parser,         only : chkdpr, chkint, chkint_eq, chkint_ge, chkint_le, chkint_ne
43 
44  implicit none
45 
46  private