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

COPYRIGHT

 Copyright (C) 1998-2018 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 .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

INPUTS

  dtsets(0:ndtset_alloc)=<type datafiles_type>contains all input variables
  iout=unit number for output file
  mpi_enregs(0:ndtset_alloc)=informations 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

OUTPUT

SIDE EFFECTS

NOTES

PARENTS

      abinit

CHILDREN

      chkdpr,chkgrp,chkint,chkint_eq,chkint_ge,chkint_le,chkint_ne,chkorthsy
      dtset_copy,dtset_free,metric,wrtout,xmpi_sum

SOURCE

  43 #if defined HAVE_CONFIG_H
  44 #include "config.h"
  45 #endif
  46 
  47 #include "abi_common.h"
  48 
  49 subroutine chkinp(dtsets,iout,mpi_enregs,ndtset,ndtset_alloc,npsp,pspheads)
  50 
  51  use defs_basis
  52  use defs_datatypes
  53  use defs_abitypes
  54  use m_gwdefs
  55  use m_profiling_abi
  56  use m_errors
  57  use m_xmpi
  58  use m_xomp
  59  use libxc_functionals
  60 
  61  use m_numeric_tools,  only : iseven
  62  use m_geometry,       only : metric
  63  use m_fftcore,        only : fftalg_has_mpi
  64  use m_dtset,          only : dtset_copy, dtset_free
  65  use m_exit,           only : get_timelimit
  66  use m_parser,         only : chkdpr, chkint, chkint_eq, chkint_ge, chkint_le, chkint_ne
  67 
  68 !This section has been created automatically by the script Abilint (TD).
  69 !Do not modify the following lines by hand.
  70 #undef ABI_FUNC
  71 #define ABI_FUNC 'chkinp'
  72  use interfaces_14_hidewrite
  73  use interfaces_41_geometry
  74 !End of the abilint section
  75 
  76  implicit none
  77 
  78 !Arguments ------------------------------------
  79 !scalars
  80  integer,intent(in) :: iout,ndtset,ndtset_alloc,npsp
  81  type(MPI_type),intent(in) :: mpi_enregs(0:ndtset_alloc)
  82 !arrays
  83  type(dataset_type),intent(in) :: dtsets(0:ndtset_alloc)
  84  type(pspheader_type),intent(in) :: pspheads(npsp)
  85 
  86 !Local variables-------------------------------
  87 !scalars
  88  logical :: twvl,allow
  89  logical :: wvlbigdft=.false.
  90  integer :: ttoldfe,ttoldff,ttolrff,ttolvrs,ttolwfr
  91  integer :: bantot,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,mgga,miniatsph,minidyn,mod10,mpierr
  94  integer :: mu,natom,nfft,nfftdg,nkpt,nloc_mem,nlpawu,nproc,nspden,nspinor,nsppol,optdriver,response,usepaw,usewvl
  95  integer :: fftalg !,fftalga,fftalgc,
  96  real(dp) :: delta,dz,sumalch,sumocc,ucvol,wvl_hgrid,zatom
  97  character(len=1000) :: message,msg
  98  type(dataset_type) :: dt
  99 !arrays
 100  integer :: cond_values(4),nprojmax(0:3)
 101  integer :: gpu_devices(5)=(/-2,-2,-2,-2,-2/)
 102  integer,allocatable :: ierr_dtset(:)
 103  real(dp) :: gmet(3,3),gprimd(3,3),rmet(3,3),rprimd(3,3)
 104  real(dp),allocatable :: frac(:,:)
 105  character(len=32) :: cond_string(4)
 106  character(len=32) :: input_name
 107 
 108 ! *************************************************************************
 109 
 110  DBG_ENTER("COLL")
 111 
 112 !Some initialisations
 113  cond_string(1:4)='#####'
 114  cond_values(1:4)=(/0,0,0,0/)
 115  ABI_ALLOCATE(ierr_dtset,(ndtset_alloc))
 116  ierr_dtset=0
 117 
 118 !Do loop on idtset (allocate statements are present)
 119  do idtset=1,ndtset_alloc
 120    if(mpi_enregs(idtset)%me<0) cycle
 121    jdtset=dtsets(idtset)%jdtset
 122    if(ndtset==0)jdtset=0
 123    ierr=0
 124 
 125    if(jdtset/=0)then
 126      write(message, '(a,a,a,i4,a)' ) ch10,&
 127 &     ' chkinp: Checking input parameters for consistency,',&
 128 &     ' jdtset=',jdtset,'.'
 129    else
 130      write(message, '(a,a)' ) ch10,&
 131 &     ' chkinp: Checking input parameters for consistency.'
 132    end if
 133    call wrtout(iout,message,'COLL')
 134    call wrtout(std_out,  message,'COLL')
 135 
 136 !  Will test directly on the dataset "dt"
 137    call dtset_copy(dt, dtsets(idtset))
 138 
 139 !  Copy or initialize locally a few input dataset values
 140    fftalg   =dt%ngfft(7)
 141    !fftalga  =fftalg/100; fftalgc=mod(fftalg,10)
 142    natom    =dt%natom
 143    nkpt     =dt%nkpt
 144    nspden   =dt%nspden
 145    nspinor  =dt%nspinor
 146    nsppol   =dt%nsppol
 147    optdriver=dt%optdriver
 148    usepaw   =dt%usepaw
 149    usewvl   =dt%usewvl
 150    intimage=1 ; if(dtsets(idtset)%nimage>2)intimage=2
 151    rprimd(:,:)=dtsets(idtset)%rprimd_orig(:,:,intimage)    ! For the purpose of checking symmetries
 152    response=0
 153    if(dt%rfelfd/=0.or.dt%rfphon/=0.or.dt%rfstrs/=0.or.dt%rfddk/=0.or.dt%rfuser/=0 &
 154 &   .or.dt%rf2_dkdk/=0.or.dt%rf2_dkde/=0.or.dt%rfmagn/=0) response=1
 155    call metric(gmet,gprimd,-1,rmet,rprimd,ucvol)
 156    nproc=mpi_enregs(idtset)%nproc
 157    mgga=0;if(dt%ixc>=31.and.dt%ixc<=34)mgga=1
 158    if (dt%ixc<0.and.libxc_functionals_ismgga()) mgga=1
 159 
 160 
 161 !  =====================================================================================================
 162 !  Check the values of variables, using alphabetical order
 163 !  PLEASE : use the routines chkint_eq, chkint_ne, chkint_ge, chkint_le, chkdpr
 164 
 165 !  iomode
 166 !  Must be one of 0, 1, 3
 167    call chkint_eq(0,0,cond_string,cond_values,ierr,'iomode',dt%iomode,3,&
 168 &   [IO_MODE_FORTRAN,IO_MODE_MPI,IO_MODE_ETSF],iout)
 169 !  However, if mpi_io is not enabled, must be one of 0, 3.
 170    if(xmpi_mpiio==0)then
 171      cond_string(1)='enable_mpi_io' ;  cond_values(1)=0
 172 !    Make sure that iomode is 0 or 3
 173      call chkint_eq(1,1,cond_string,cond_values,ierr,'iomode',dt%iomode,2,[IO_MODE_FORTRAN,IO_MODE_ETSF],iout)
 174    end if
 175    if (dt%iomode == IO_MODE_NETCDF .and. dt%npspinor == 2) then
 176      MSG_ERROR_NOSTOP("npspinor == 2 not compatible with netcdf", ierr)
 177    end if
 178 
 179 !  accuracy
 180    call chkint_eq(0,0,cond_string,cond_values,ierr,'accuracy',dt%accuracy,7,(/0,1,2,3,4,5,6/),iout)
 181 
 182 !  adpimd
 183    call chkint_eq(0,0,cond_string,cond_values,ierr,'accuracy',dt%adpimd,2,(/0,1/),iout)
 184 
 185 !  amu
 186 !  Check that atomic masses are > 0 if ionmov = 1
 187    do iimage=1,dt%nimage
 188      if (dt%ionmov==1) then
 189        do itypat=1,dt%ntypat
 190          cond_string(1)='ionmov' ; cond_values(1)=1
 191          write(input_name,'(a4,i2,a1,i2,a1)')'amu(',itypat,',',iimage,')'
 192          call chkdpr(1,1,cond_string,cond_values,ierr,input_name,dt%amu_orig(itypat,iimage),1,tol8,iout)
 193        end do
 194      end if
 195    end do
 196 
 197 !  autoparal
 198    call chkint_eq(0,0,cond_string,cond_values,ierr,'autoparal',dt%autoparal,5,(/0,1,2,3,4/),iout)
 199 
 200 !  auxc_scal
 201    call chkdpr(0,0,cond_string,cond_values,ierr,'auxc_scal',dt%auxc_scal,1,0.0_dp,iout)
 202 
 203 !  bdberry
 204    if(dt%berryopt>0.and.dt%nberry>0.and.&
 205 &   dt%berryopt/= 4.and.dt%berryopt/= 6.and.dt%berryopt/= 7.and.&
 206 &   dt%berryopt/=14.and.dt%berryopt/=16.and.dt%berryopt/=17) then
 207      do ii=1,2*nsppol
 208        cond_string(1)='berryopt' ; cond_values(1)=dt%berryopt
 209        cond_string(2)='nberry'   ; cond_values(2)=dt%nberry
 210        write(input_name,'(a4,i1,a1)')'bdberry(',ii,')'
 211        call chkint_ge(2,2,cond_string,cond_values,ierr,input_name,dt%bdberry(ii),1,iout)
 212      end do
 213 !    bdberry(2) must be greater than bdberry(1)
 214      cond_string(1)='berryopt' ; cond_values(1)=dt%berryopt
 215      cond_string(2)='nberry'   ; cond_values(2)=dt%nberry
 216      cond_string(3)='bdberry(1)'   ; cond_values(3)=dt%bdberry(1)
 217      call chkint_ge(3,3,cond_string,cond_values,ierr,'bdberry(2)',dt%bdberry(2),dt%bdberry(1),iout)
 218      if(nsppol==2)then
 219 !      bdberry(4) must be greater than bdberry(3)
 220        cond_string(1)='berryopt' ; cond_values(1)=dt%berryopt
 221        cond_string(2)='nberry'   ; cond_values(2)=dt%nberry
 222        cond_string(3)='bdberry(3)'   ; cond_values(3)=dt%bdberry(3)
 223        call chkint_ge(3,3,cond_string,cond_values,ierr,'bdberry(4)',dt%bdberry(4),dt%bdberry(3),iout)
 224      end if
 225 !    Make sure all nband(nkpt) are >= bdberry
 226      do isppol=1,nsppol
 227        do ikpt=1,nkpt
 228          if (dt%nband(ikpt+(isppol-1)*nkpt)<=dt%bdberry(2*isppol)) then
 229            cond_string(1)='ikpt'   ; cond_values(1)=ikpt
 230            cond_string(2)='isppol' ; cond_values(2)=isppol
 231            cond_string(3)='nband'  ; cond_values(3)=dt%nband(ikpt+(isppol-1)*nkpt)
 232            call chkint_le(0,3,cond_string,cond_values,ierr,&
 233 &           'bdberry',dt%bdberry(2*isppol),dt%nband(ikpt+(isppol-1)*nkpt),iout)
 234            if(ierr==1)exit
 235          end if
 236        end do
 237      end do
 238    end if
 239 
 240 !  berryopt
 241 !  berryopt must be between -3 to +4, 6,7,14,16,17
 242    call chkint_eq(0,0,cond_string,cond_values,ierr,&
 243 &   'berryopt',dt%berryopt,13,(/-3,-2,-1,0,1,2,3,4,6,7,14,16,17/),iout)
 244 !  berryopt must be positive when mkmem==0
 245    if(dt%mkmem==0)then
 246      cond_string(1)='mkmem' ; cond_values(1)=dt%mkmem
 247      call chkint_ge(1,1,cond_string,cond_values,ierr,'berryopt',dt%berryopt,0,iout)
 248    end if
 249 !  berryopt must be positive when occopt/=1
 250    if(dt%occopt/=1)then
 251      cond_string(1)='occopt' ; cond_values(1)=dt%occopt
 252      call chkint_ge(1,1,cond_string,cond_values,ierr,'berryopt',dt%berryopt,0,iout)
 253    end if
 254 !  berryopt cannot be 4,6,7,14,16,17 when toldfe, tolvrs, toldff and tolrff are zero or negative
 255    if ((dt%toldfe < tiny(one)).and.(dt%tolvrs < tiny(one)).and.&
 256 &   (dt%toldff < tiny(one)).and.(dt%tolrff < tiny(one))) then
 257      cond_string(1)='toldfe' ; cond_values(1)=dt%toldfe
 258      cond_string(2)='toldff' ; cond_values(2)=dt%toldff
 259      cond_string(3)='tolrff' ; cond_values(3)=dt%tolrff
 260      cond_string(4)='tolvrs' ; cond_values(4)=dt%tolvrs
 261      call chkint_ne(4,4,cond_string,cond_values,ierr,'berryopt',dt%berryopt,1,(/4/),iout)
 262      cond_string(1)='toldfe' ; cond_string(2)='toldff' ; cond_string(3)='tolrff' ; cond_string(4)='tolvrs'
 263      call chkint_ne(4,4,cond_string,cond_values,ierr,'berryopt',dt%berryopt,1,(/6/),iout)
 264      cond_string(1)='toldfe' ; cond_string(2)='toldff' ; cond_string(3)='tolrff' ; cond_string(4)='tolvrs'
 265      call chkint_ne(4,4,cond_string,cond_values,ierr,'berryopt',dt%berryopt,1,(/7/),iout)
 266      cond_string(1)='toldfe' ; cond_string(2)='toldff' ; cond_string(3)='tolrff' ; cond_string(4)='tolvrs'
 267      call chkint_ne(4,4,cond_string,cond_values,ierr,'berryopt',dt%berryopt,1,(/14/),iout)
 268      cond_string(1)='toldfe' ; cond_string(2)='toldff' ; cond_string(3)='tolrff' ; cond_string(4)='tolvrs'
 269      call chkint_ne(4,4,cond_string,cond_values,ierr,'berryopt',dt%berryopt,1,(/16/),iout)
 270      cond_string(1)='toldfe' ; cond_string(2)='toldff' ; cond_string(3)='tolrff' ; cond_string(4)='tolvrs'
 271      call chkint_ne(4,4,cond_string,cond_values,ierr,'berryopt',dt%berryopt,1,(/17/),iout)
 272    end if
 273 !  Non-zero berryopt and usepaw==1 cannot be done unless response==0
 274    if (usepaw==1.and.dt%berryopt/=0) then
 275      cond_string(1)='usepaw' ; cond_values(1)=1
 276      cond_string(2)='berryopt' ; cond_values(2)=dt%berryopt
 277      call chkint_eq(1,2,cond_string,cond_values,ierr,'response',response,1,(/0/),iout)
 278    end if
 279 !  Non-zero berryopt and usepaw==1 and kptopt/=3 cannot be done unless symmorphi=0
 280 !  (that is, nonsymmorphic symmetries do not work yet
 281 !  Update MT 2017-05-31: nonsymmorphic symmetries seem also to be an issue for NCPP
 282    if (usepaw==1.and.dt%berryopt/=0.and.dt%kptopt/=3) then
 283   !if (dt%berryopt/=0.and.dt%kptopt/=3) then
 284      cond_string(1)='usepaw'; cond_values(1)=1
 285      cond_string(2)='berryopt'; cond_values(2)=dt%berryopt
 286      cond_string(3)='kptopt'; cond_values(3)=dt%kptopt
 287      call chkint_eq(1,3,cond_string,cond_values,ierr,'symmorphi',dt%symmorphi,1,(/0/),iout)
 288    end if
 289 !  Restrictions for berryopt=4,6,7,14,16,17
 290    if (usepaw==1.and.&
 291 &   (dt%berryopt== 4.or.dt%berryopt== 6.or.dt%berryopt== 7.or.&
 292 &   dt%berryopt==14.or.dt%berryopt==16.or.dt%berryopt==17)) then
 293 !     if (nsppol==2.and.nproc>1) then
 294 !       write(message,'(3a)') &
 295 !&       'For berryopt = 4,6,7,14,16,17 and nsppol=2, nproc must = 1 ',ch10,&
 296 !&       'Action: change number of processes'
 297 !       MSG_ERROR_NOSTOP(message,ierr)
 298 !     end if
 299    end if
 300 !  Non-zero berryopt and usepaw==1 and kpt // requires nproc to be a divisor of nkpt
 301    if (usepaw==1.and.dt%berryopt/=0.and.nproc>1.and.mod(dt%nkpt,nproc)/=0) then
 302      write(message, '(3a)' )&
 303 &     'For berryopt /= 0 with PAW in parallel, nproc must be a divisor of nkpt ',ch10,&
 304 &     'Action: change number of processes or kpts such that nproc divides nkpt evenly'
 305      MSG_ERROR_NOSTOP(message,ierr)
 306    end if
 307 
 308 !  Finite electric/displacement field checks
 309    if (dt%berryopt==4) then
 310      if (maxval(abs(dt%dfield(1:3)))>tiny(0.0_dp).or.&
 311 &     maxval(abs(dt%red_dfield(1:3)))>tiny(0.0_dp).or.&
 312 &     maxval(abs(dt%red_efield(1:3)))>tiny(0.0_dp).or.&
 313 &     maxval(abs(dt%red_efieldbar(1:3)))>tiny(0.0_dp)) then
 314        write(message,'(5a)' ) &
 315 &       'When berryopt==4, only efield is needed, other input field',ch10,&
 316 &       '(dfield,red_dfield,red_efield,red_efieldbar) should be zero.',ch10,&
 317 &       'Action: delete unneeded field in input file.'
 318        MSG_ERROR_NOSTOP(message,ierr)
 319      end if
 320    end if
 321    if (dt%berryopt==14) then
 322      if (maxval(abs(dt%dfield(1:3)))>tiny(0.0_dp).or.&
 323 &     maxval(abs(dt%red_dfield(1:3)))>tiny(0.0_dp).or.&
 324 &     maxval(abs(dt%red_efield(1:3)))>tiny(0.0_dp).or.&
 325 &     maxval(abs(dt%efield(1:3)))>tiny(0.0_dp)) then
 326        write(message,'(5a)') &
 327 &       'When berryopt==14, only red_efieldbar is needed, other input field',ch10,&
 328 &       '(dfield,red_dfield,efield,red_efield) should be zero.',ch10,&
 329 &       'Action: delete unneeded field in input file.'
 330        MSG_ERROR_NOSTOP(message,ierr)
 331      end if
 332    end if
 333    if (dt%berryopt==6) then
 334      if (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%red_efieldbar(1:3)))>tiny(0.0_dp)) then
 337        write(message,'(5a)') &
 338 &       'When berryopt==6, only dfield and efield are needed, other input field',ch10,&
 339 &       '(red_dfield,red_efield,red_efieldbar) should be zero.',ch10,&
 340 &       'Action: delete unneeded field in input file.'
 341        MSG_ERROR_NOSTOP(message,ierr)
 342      end if
 343    end if
 344    if (dt%berryopt==16) then
 345      if (maxval(abs(dt%dfield(1:3)))>tiny(0.0_dp).or.&
 346 &     maxval(abs(dt%efield(1:3)))>tiny(0.0_dp).or.&
 347 &     maxval(abs(dt%red_efieldbar(1:3)))>tiny(0.0_dp)) then
 348        write(message,'(5a)')  &
 349 &       'When berryopt==16, only red_dfield and red_efield are needed, other input field',ch10,&
 350 &       '(dfield,efield,red_efieldbar) should be zero.',ch10,&
 351 &       'Action: delete unneeded field in input file.'
 352        MSG_ERROR_NOSTOP(message,ierr)
 353      end if
 354    end if
 355    if (dt%berryopt==17) 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_efield(1:3)))>tiny(0.0_dp)) then
 359        write(message,'(5a)') &
 360 &       'When berryopt==17, only red_dfield and red_efieldbar are needed, other input field',ch10,&
 361 &       '(dfield,efield,red_efield) should be zero.',ch10,&
 362 &       'Action: delete unneeded field in input file.'
 363        MSG_ERROR_NOSTOP(message,ierr)
 364      end if
 365      if ((dt%jfielddir(1)/=1.and.dt%jfielddir(1)/=2).or.&
 366 &     (dt%jfielddir(2)/=1.and.dt%jfielddir(2)/=2).or.&
 367 &     (dt%jfielddir(3)/=1 .and.dt%jfielddir(3)/=2)) then
 368        write(message,'(5a)') &
 369 &       'When berryopt==17, jfielddir can only be 1 or 2 to controls whether reduced electric field',ch10,&
 370 &       '(jfielddir=1) or reduced electric displacement field (jfielddir=2) is chosen to be fixed', ch10,&
 371 &       'Action: change jfielddir to be 1 or 2 in input file.'
 372        MSG_ERROR_NOSTOP(message,ierr)
 373      end if
 374    end if
 375 
 376 !  berrystep
 377    call chkint_ge(0,0,cond_string,cond_values,ierr,'berrystep',dt%berrystep,1,iout)
 378    if(nproc>1)then
 379      cond_string(1)='nproc'; cond_values(1)=mpi_enregs(idtset)%nproc
 380      call chkint_eq(1,1,cond_string,cond_values,ierr,'berrystep',dt%berrystep,1,(/1/),iout)
 381    end if
 382 
 383 !  boxcutmin
 384    if(response==1)then
 385      cond_string(1)='response' ; cond_values(1)=1
 386      call chkdpr(1,1,cond_string,cond_values,ierr,'boxcutmin',dt%boxcutmin,1,two,iout)
 387    end if
 388 
 389 !  builtintest
 390    call chkint_eq(0,0,cond_string,cond_values,ierr,'builtintest',dt%builtintest,8,(/0,1,2,3,4,5,6,7/),iout)
 391 
 392 !  chkdilatmx
 393    call chkint_eq(0,0,cond_string,cond_values,ierr,'chkdilatmx',dt%chkdilatmx,2,(/0,1/),iout)
 394 
 395 !  chksymbreak
 396    call chkint_eq(0,0,cond_string,cond_values,ierr,'chksymbreak',dt%chksymbreak,3,(/0,1,-1/),iout)
 397    if(dt%chksymbreak==1)then
 398 !    Check the values of tnons
 399      do isym=1,dt%nsym
 400        do ii=1,3
 401          delta=dt%tnons(ii,isym)*eight
 402          if(abs(delta-nint(delta))>tol6)then
 403            delta=dt%tnons(ii,isym)*three*four
 404            if(abs(delta-nint(delta))>tol6)then
 405              write(message, '(8a,i4,2a,9i3,2a,3es16.6,4a)' ) ch10,&
 406 &             ' chkinp: WARNING -',ch10,&
 407 &             '   Chksymbreak=1 . Found potentially symmetry-breaking value of tnons, ', ch10,&
 408 &             '   which is neither a rational fraction in 1/8th nor in 1/12th :', ch10,&
 409 &             '   for the symmetry number ',isym,ch10,&
 410 &             '   symrel is ',dt%symrel(1:3,1:3,isym),ch10,&
 411 &             '   tnons is ',dt%tnons(1:3,isym),ch10,&
 412 &             '   Please, read the description of the input variable chksymbreak,',ch10,&
 413 &             '   then, if you feel confident, you might switch it to zero, or consult with the forum.'
 414              call wrtout(iout,message,'COLL')
 415              call wrtout(std_out,message,'COLL')
 416              !ierr=ierr+1 ! moved this to a warning: for slab geometries arbitrary tnons can appear along the vacuum direction
 417            end if
 418          end if
 419        end do
 420      end do
 421    end if
 422 
 423 !  densfor_pred
 424    if(dt%iscf>0)then
 425      cond_string(1)='iscf';cond_values(1)=dt%iscf
 426      call chkint_le(0,1,cond_string,cond_values,ierr,'densfor_pred',dt%densfor_pred,6,iout)
 427      call chkint_ge(0,1,cond_string,cond_values,ierr,'densfor_pred',dt%densfor_pred,-6,iout)
 428      if (dt%densfor_pred<0.and.mod(dt%iprcel,100)>=61.and.(dt%iprcel<71.or.dt%iprcel>79)) then
 429        cond_string(1)='iscf';cond_values(1)=dt%iscf
 430        cond_string(2)='iprcel';cond_values(2)=dt%iprcel
 431        call chkint_ge(1,2,cond_string,cond_values,ierr,'densfor_pred',dt%densfor_pred,0,iout)
 432      end if
 433    end if
 434 
 435 !  diecut
 436    if(dt%iscf==-1)then
 437      cond_string(1)='iscf' ; cond_values(1)=-1
 438      cond_string(2)='4*ecut' ; cond_values(1)=4*dt%ecut
 439 !    Checks that presently diecut is 4*ecut
 440      call chkdpr(1,1,cond_string,cond_values,ierr,'diecut',dt%diecut,0,4*dt%ecut,iout)
 441    end if
 442 
 443 !  diemac
 444    call chkdpr(0,0,cond_string,cond_values,ierr,'diemac',dt%diemac,1,0.01_dp,iout)
 445 
 446 !  dilatmx
 447    call chkdpr(0,0,cond_string,cond_values,ierr,'dilatmx',dt%dilatmx,1,zero,iout)
 448    if(dt%chkdilatmx==1)then
 449      cond_string(1)='chkdilatmx' ; cond_values(1)=1
 450 !    Checks that presently chkdilatmx is smaller than 1.15
 451      call chkdpr(1,1,cond_string,cond_values,ierr,'dilatmx',dt%dilatmx,-1,1.15_dp,iout)
 452    end if
 453 
 454 !  dmatpuopt
 455    if (dt%usepawu==1.or.dt%usepawu==2.or.dt%usepawu==3.or.dt%usepawu==4.or.dt%usepawu==10.or.dt%usepawu==14) then
 456      cond_string(1)='usepawu' ; cond_values(1)=1
 457      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)
 458    end if
 459 
 460 !  dmatudiag
 461    if (dt%usepawu==1.or.dt%usepawu==2.or.dt%usepawu==3.or.dt%usepawu==4.or.dt%usepawu==10.or.dt%usepawu==14) then
 462      cond_string(1)='usepawu' ; cond_values(1)=1
 463      call chkint_eq(0,1,cond_string,cond_values,ierr,'dmatudiag',dt%dmatudiag,3,(/0,1,2/),iout)
 464    end if
 465 
 466 
 467 !  dmftbandi, dmftbandf
 468    if (dt%usedmft>0) then
 469      call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftcheck',dt%dmftcheck,4,(/-1,0,1,2/),iout)
 470      if(dt%dmftcheck/=-1) then
 471        cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
 472        call chkint_eq(1,1,cond_string,cond_values,ierr,'occopt',dt%occopt,1,(/3/),iout)
 473        cond_string(1)='usedmft' ; cond_values(1)=1
 474        call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftbandi',dt%dmftbandi,1,iout)
 475        cond_string(1)='usedmft' ; cond_values(1)=1
 476        call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftbandf',dt%dmftbandf,dt%dmftbandi,iout)
 477        cond_string(1)='mband' ; cond_values(1)=dt%mband
 478        call chkint_le(0,1,cond_string,cond_values,ierr,'dmftbandi',dt%dmftbandi,dt%mband,iout)
 479        cond_string(1)='mband' ; cond_values(1)=dt%mband
 480        call chkint_le(0,1,cond_string,cond_values,ierr,'dmftbandf',dt%dmftbandf,dt%mband,iout)
 481        cond_string(1)='usedmft' ; cond_values(1)=1
 482        call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_entropy',dt%dmft_entropy,0,iout)
 483        cond_string(1)='usedmft' ; cond_values(1)=1
 484        call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_iter',dt%dmft_iter,0,iout)
 485        if((dt%dmft_solv<6.or.dt%dmft_solv>7).and.dt%ucrpa==0) then
 486          cond_string(1)='usedmft' ; cond_values(1)=1
 487          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_nwlo',dt%dmft_nwlo,1,iout)
 488          cond_string(1)='usedmft' ; cond_values(1)=1
 489          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_nwli',dt%dmft_nwli,1,iout)
 490        end if
 491        cond_string(1)='usedmft' ; cond_values(1)=1
 492        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_read_occnd',dt%dmft_read_occnd,3,(/0,1,2/),iout)
 493        cond_string(1)='usedmft' ; cond_values(1)=1
 494        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_rslf',dt%dmft_rslf,3,(/-1,0,1/),iout)
 495        cond_string(1)='usedmft' ; cond_values(1)=1
 496        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_mxsf',dt%dmft_mxsf,1,zero,iout)
 497        cond_string(1)='usedmft' ; cond_values(1)=1
 498        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_mxsf',dt%dmft_mxsf,-1,one,iout)
 499        cond_string(1)='usedmft' ; cond_values(1)=1
 500        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_solv',dt%dmft_solv,7,(/-1,0,1,2,5,6,7/),iout)
 501        cond_string(1)='usedmft' ; cond_values(1)=1
 502        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_tolfreq',dt%dmft_tolfreq,-1,0.01_dp,iout)
 503        cond_string(1)='usedmft' ; cond_values(1)=1
 504        call chkdpr(0,1,cond_string,cond_values,ierr,'dmft_tollc',dt%dmft_tollc,-1,tol5,iout)
 505        if(dt%usepawu==14) then
 506          cond_string(1)='usepawu' ; cond_values(1)=14
 507          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_dc',dt%dmft_dc,1,(/5/),iout)
 508        endif
 509        cond_string(1)='usedmft' ; cond_values(1)=1
 510        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_dc',dt%dmft_dc,4,(/0,1,2,5/),iout)
 511        if(dt%getwfk==0.and.dt%irdwfk==0.and.dt%irdden==0.and.dt%getden==0.and.dt%ucrpa==0) then
 512          write(message,'(3a,i3,a,i3,a,i3,a,i3,a)' )&
 513 &         'When usedmft==1, A WFC file or a DEN file have to be read. In the current calculation:',ch10, &
 514 &         '  getwfk =',dt%getwfk, &
 515 &         '  irdwfk =',dt%irdwfk, &
 516 &         '  getden =',dt%getden, &
 517 &         '  irdden =',dt%irdden, &
 518 &         '  Action: use a restart density or wfc file'
 519          if(dt%iscf>0) MSG_ERROR(message)
 520        end if
 521        cond_string(1)='usedmft' ; cond_values(1)=1
 522        call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_t2g',dt%dmft_t2g,2,(/0,1/),iout)
 523        if (dt%dmft_solv>=4.and.dt%ucrpa==0) then
 524          cond_string(1)='usedmft' ; cond_values(1)=1
 525          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftqmc_l',dt%dmftqmc_l,1,iout)
 526          cond_string(1)='usedmft' ; cond_values(1)=1
 527          call chkdpr(0,1,cond_string,cond_values,ierr,'dmftqmc_n',dt%dmftqmc_n,1,one,iout)
 528          cond_string(1)='usedmft' ; cond_values(1)=1
 529          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftqmc_seed',dt%dmftqmc_seed,0,iout)
 530          cond_string(1)='usedmft' ; cond_values(1)=1
 531          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftqmc_therm',dt%dmftqmc_therm,1,iout)
 532        end if
 533        if (dt%dmft_solv>=5) then
 534          cond_string(1)='dmft_solv' ; cond_values(1)=5
 535          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_basis',dt%dmftctqmc_basis,3,(/0,1,2/),iout)
 536          cond_string(1)='dmft_solv' ; cond_values(1)=5
 537          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_check',dt%dmftctqmc_check,4,(/0,1,2,3/),iout)
 538          cond_string(1)='dmft_solv' ; cond_values(1)=5
 539          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_gmove',dt%dmftctqmc_gmove,0,iout)
 540          cond_string(1)='dmft_solv' ; cond_values(1)=5
 541          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_meas',dt%dmftctqmc_meas,1,iout)
 542 #if defined HAVE_TRIQS
 543          if (dt%dmft_solv>=6) then
 544            cond_string(1)='dmft_solv' ; cond_values(1)=5
 545            call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_qmc_l',dt%dmftqmc_l,2*dt%dmft_nwli+1,iout)
 546            cond_string(1)='usedmft' ; cond_values(1)=1
 547            call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_triqs_nleg',dt%dmftctqmc_triqs_nleg,1,iout)
 548          end if
 549 #endif
 550        end if
 551        if (dt%dmft_solv==5) then
 552          cond_string(1)='dmft_solv' ; cond_values(1)=5
 553          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_correl',dt%dmftctqmc_correl,2,(/0,1/),iout)
 554          cond_string(1)='dmft_solv' ; cond_values(1)=5
 555          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_grnns',dt%dmftctqmc_grnns,2,(/0,1/),iout)
 556          cond_string(1)='dmft_solv' ; cond_values(1)=5
 557          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_mrka',dt%dmftctqmc_mrka,0,iout)
 558          cond_string(1)='dmft_solv' ; cond_values(1)=5
 559          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmftctqmc_mov',dt%dmftctqmc_mov,2,(/0,1/),iout)
 560          cond_string(1)='dmft_solv' ; cond_values(1)=5
 561          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmftctqmc_order',dt%dmftctqmc_order,0,iout)
 562          cond_string(1)='dmft_solv' ; cond_values(1)=5
 563          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_nwlo',dt%dmft_nwlo,2*dt%dmftqmc_l,iout)
 564        end if
 565        if (dt%dmft_entropy>=1) then
 566          cond_string(1)='dmft_solv' ; cond_values(1)=5
 567          call chkint_ge(0,1,cond_string,cond_values,ierr,'dmft_nlambda',dt%dmft_nlambda,3,iout)
 568          cond_string(1)='dmft_solv' ; cond_values(1)=5
 569          call chkint_le(0,1,cond_string,cond_values,ierr,'dmft_entropy',dt%dmft_entropy,dt%dmft_nlambda,iout)
 570          cond_string(1)='dmft_solv' ; cond_values(1)=5
 571          call chkint_eq(0,1,cond_string,cond_values,ierr,'dmft_dc',dt%dmft_dc,1,(/1/),iout)
 572          if (dt%dmft_solv /= 5 ) then
 573            write(message,'(3a,i3,a,i3,a,i3,a,i3,a)' )&
 574 &           'When dmft_entropy>=1, the impurity solver has to be currently  dmft_solv=5:',ch10, &
 575 &           'Action: change your dmft_solv input'
 576            MSG_ERROR(message)
 577          end if
 578        end if
 579      end if
 580    end if
 581 
 582 #if !defined HAVE_TRIQS
 583    if(dt%dmft_solv>=6) then
 584      write(message, '(a,a,a)' )&
 585 &     ' dmft_solv>=6 is only relevant if the TRIQS library is linked',ch10,&
 586 &     ' Action: check compilation options'
 587      MSG_ERROR(message)
 588    end if
 589 #endif
 590 
 591 !  dosdeltae
 592    call chkdpr(0,0,cond_string,cond_values,ierr,'dosdeltae',dt%dosdeltae,1,0.0_dp,iout)
 593 
 594 !  dynimage between 0 and 1
 595    maxidyn=maxval(dt%dynimage(:))
 596    minidyn=minval(dt%dynimage(:))
 597    call chkint_ge(0,0,cond_string,cond_values,ierr,'dynimage',minidyn,0,iout)
 598    call chkint_le(0,0,cond_string,cond_values,ierr,'dynimage',maxidyn,1,iout)
 599 
 600 !  ecut
 601 !  With planewaves, one must use positive ecut
 602    if(usewvl==0)then
 603      if (abs(dt%ecut+1._dp)<tol8) then
 604        write(message, '(3a)' )&
 605 &       'The input keyword "ecut" is compulsory !',ch10,&
 606 &       'Action: add a value for "ecut" in the input file.'
 607        MSG_ERROR_NOSTOP(message,ierr)
 608      else
 609        cond_string(1)='usewvl' ; cond_values(1)=usewvl
 610        call chkdpr(1,1,cond_string,cond_values,ierr,'ecut',dt%ecut,1,tol8,iout)
 611      end if
 612    end if
 613 
 614 !  pawecutdg (placed here to stop before ngfftdg)
 615    if (usepaw==1) then
 616      if(usewvl==0) then
 617        call chkdpr(1,0,cond_string,cond_values,ierr,'pawecutdg',dt%pawecutdg,1,tol8,iout)
 618        cond_string(1)='ecut' ; cond_values(1)=dt%ecut
 619        call chkdpr(1,1,cond_string,cond_values,ierr,'pawecutdg',dt%pawecutdg,1,dt%ecut,iout)
 620      else
 621        if(dt%pawecutdg > 0.d0) then
 622          MSG_ERROR('In PAW+WVL do not use pawecutdg')
 623        end if
 624      end if
 625    end if
 626 
 627 !  ecuteps
 628    if( ANY(optdriver == [RUNL_SCREENING]) )then
 629      call chkdpr(0,0,cond_string,cond_values,ierr,'ecuteps',dt%ecuteps,1,0.0_dp,iout)
 630      if (dt%ecuteps <= 0) then
 631        MSG_ERROR_NOSTOP("ecuteps must be > 0 if optdriver == 3", ierr)
 632      end if
 633      if(dt%fftgw<20 .and. dt%fftgw/=0)then
 634        if(dt%ecutwfn<dt%ecuteps-tol8)then
 635          write(message,'(a,es16.6,a,es16.6,a,6a)')&
 636 &         'The values of ecutwfn and ecuteps are ', dt%ecutwfn,' and ',dt%ecuteps,ch10,&
 637 &         'With fftgw lower than 20, one expect ecuteps to be smaller or equal to ecutwfn.',ch10,&
 638 &         'Indeed, one is wasting memory without gaining CPU time or accuracy.',ch10,&
 639 &         'Action: use another value of fftgw (e.g. 21), or adjust ecutwfn with ecuteps.'
 640          MSG_ERROR_NOSTOP(message,ierr)
 641        end if
 642      end if
 643    end if
 644 
 645 !  ecutsigx
 646 !  @MG FIXME reinstate this check, after having rewritten FFT treatment in GW
 647    if( ANY( optdriver==(/RUNL_SIGMA/) ) .and..FALSE.)then
 648      call chkdpr(0,0,cond_string,cond_values,ierr,'ecutsigx',dt%ecutsigx,1,0.0_dp,iout)
 649      if(dt%fftgw<20)then
 650        if(dt%ecutwfn<dt%ecutsigx-tol8)then
 651          write(message,'(a,es16.6,a,es16.6,a,6a)')&
 652 &         'The values of ecutwfn and ecutsigx are ', dt%ecutwfn,' and ',dt%ecutsigx,ch10,&
 653 &         'With fftgw lower than 20, one expect ecutsigx to be smaller or equal to ecutwfn.',ch10,&
 654 &         'Indeed, one is wasting memory without gaining CPU time or accuracy.',ch10,&
 655 &         'Action: use another value of fftgw (e.g. 21), or adjust ecutwfn with ecutsigx.'
 656          MSG_ERROR_NOSTOP(message,ierr)
 657        end if
 658      end if
 659    end if
 660 
 661    if ( optdriver==RUNL_BSE) then
 662      ! Check for BSE calculations that are not implemented.
 663      if (dt%nspinor == 2) then
 664        MSG_ERROR_NOSTOP("BSE with nspinor 2 not implemented", ierr)
 665      end if
 666    end if
 667 
 668    ! Check for GW calculations that are not implemented.
 669    if (ANY(optdriver == [RUNL_SCREENING, RUNL_SIGMA])) then
 670      if (dt%nspinor == 2) then
 671        if (dt%usepaw == 1) then
 672          MSG_ERROR_NOSTOP("GW with PAW and nspinor 2 not implemented", ierr)
 673        end if
 674        !if (optdriver == RUNL_SCREENING .and. dt%symchi == 1) then
 675        !  MSG_ERROR_NOSTOP("Screening with symchi 1 and nspinor 2 not implemented", ierr)
 676        !end if
 677        !if (optdriver == RUNL_SIGMA .and. dt%symsigma == 1) then
 678        !  MSG_ERROR_NOSTOP("Self-energy with symsigma 1 and nspinor 2 not implemented", ierr)
 679        !end if
 680        if (optdriver == RUNL_SIGMA .and. &
 681        any(mod(dt%gwcalctyp, 10) == [SIG_GW_AC, SIG_QPGW_PPM, SIG_QPGW_CD])) then
 682          MSG_ERROR_NOSTOP("analytic-continuation, model GW with nspinor 2 are not implemented", ierr)
 683        end if
 684        !if (optdriver == RUNL_SIGMA .and. mod(dt%gwcalctyp, 100) >= 10) then
 685        !  MSG_ERROR_NOSTOP("Self-consistent GW with nspinor == 2 not implemented", ierr)
 686        !end if
 687        if (dt%gwcomp /= 0) then
 688          MSG_ERROR_NOSTOP("gwcomp /= 0 with nspinor 2 not implemented", ierr)
 689        end if
 690      end if ! nspinor 2
 691 
 692      if (maxval(abs(dt%istwfk(1:nkpt))) > 1 .and. mod(dt%gwcalctyp, 100) >= 20) then
 693        write(msg, "(3a)")"Self-consistent GW with istwfk > 1 not supported.",ch10, &
 694        "Please regenerate your WFK file with istwfk *1"
 695        MSG_ERROR_NOSTOP(msg, ierr)
 696      end if
 697 
 698      ! Avoid wasting CPUs if nsppol==2.
 699      if (dt%nsppol==2 .and. .not. iseven(nproc) .and. nproc > 1) then
 700        write(msg,'(3a)') "Spin-polarized GW calculations should be run with an even number of processors ",ch10,&
 701 &       " for achieving an optimal distribution of memory and CPU load. Change the number of processors."
 702        MSG_ERROR_NOSTOP(msg, ierr)
 703      end if
 704    end if
 705 
 706 !  ecutsm
 707    call chkdpr(0,0,cond_string,cond_values,ierr,'ecutsm',dt%ecutsm,1,0.0_dp,iout)
 708 !  With non-zero optcell, one must use non-zero ecutsm
 709    if(dt%optcell/=0 )then
 710      cond_string(1)='optcell' ; cond_values(1)=dt%optcell
 711      call chkdpr(1,1,cond_string,cond_values,ierr,'ecutsm',dt%ecutsm,1,tol8,iout)
 712    end if
 713 
 714 !  ecutwfn <= ecut. This is also needed for the correct evaluation
 715 !  of the Kleynman-Bylander form factors as the spline in Psps% is done with ecut
 716 !  while we need |q+G| up to ecut. enlargement due to the q is already
 717 !  taken into account by enlarging the spline mesh by around 20%.
 718    if ( ANY(optdriver == [RUNL_SCREENING, RUNL_SIGMA, RUNL_BSE]) ) then
 719      call chkdpr(0,0,cond_string,cond_values,ierr,'ecutwfn',dt%ecuteps,1,0.0_dp,iout)
 720      if(dt%ecut<dt%ecutwfn-tol8)then
 721        write(message,'(a,es16.6,a,es16.6,a,6a)')&
 722 &       'The values of ecut and ecutwfn are ', dt%ecut,' and ',dt%ecutwfn,ch10,&
 723 &       'One expects ecutwfn to be smaller or equal to ecut.',ch10,&
 724 &       'Action: adjust ecutwfn with ecut.'
 725        MSG_ERROR_NOSTOP(message,ierr)
 726      end if
 727    end if
 728 
 729 !  efmas
 730    if(optdriver==RUNL_RESPFN) then !.and.usepaw==1)then
 731      cond_string(1)='optdriver' ; cond_values(1)=1
 732      cond_string(2)='usepaw'    ; cond_values(2)=0 !usepaw
 733      cond_string(3)='ieig2rf'   ; cond_values(3)=1
 734      cond_string(4)='nsym'      ; cond_values(4)=1
 735      !cond_string(5)='useylm'    ; cond_values(5)=1
 736      call chkint_eq(1,4,cond_string,cond_values,ierr,'efmas',dt%efmas,2,(/0,1/),iout)
 737      if (dt%paral_rf==1) then
 738        cond_string(1)='paral_rf' ; cond_values(1)=1
 739        call chkint_eq(1,1,cond_string,cond_values,ierr,'efmas',dt%efmas,1,(/0/),iout)
 740      end if
 741    end if
 742 
 743 !  efmas_calc_dirs
 744    if(dt%efmas==1) then
 745      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)
 746    end if
 747 
 748 !  efmas_deg
 749    if(dt%efmas==1) then
 750      call chkint_eq(0,0,cond_string,cond_values,ierr,'efmas_deg',dt%efmas_deg,2,(/0,1/),iout)
 751    end if
 752 
 753 !  efmas_deg_tol
 754    if(dt%efmas==1) then
 755      call chkdpr(0,0,cond_string,cond_values,ierr,'efmas_deg_tol',dt%efmas_deg_tol,1,0.0_dp,iout)
 756    end if
 757 
 758 !  efmas_dim
 759    if(dt%efmas==1) then
 760      call chkint_eq(0,0,cond_string,cond_values,ierr,'efmas_dim',dt%efmas_dim,3,(/1,2,3/),iout)
 761    end if
 762 
 763 !  efmas_n_dirs
 764    if(dt%efmas==1) then
 765      call chkint_ge(0,0,cond_string,cond_values,ierr,'efmas_n_dirs',dt%efmas_n_dirs,0,iout)
 766    end if
 767 
 768 !  efmas_ntheta
 769    if(dt%efmas==1) then
 770      call chkint_ge(0,0,cond_string,cond_values,ierr,'efmas_ntheta',dt%efmas_ntheta,1,iout)
 771    end if
 772 
 773 !  enable_mpi_io
 774    if(dt%iomode==IO_MODE_MPI) then
 775      cond_string(1)='iomode' ; cond_values(1)=1
 776      call chkint_eq(1,1,cond_string,cond_values,ierr,'enable_mpi_io',xmpi_mpiio,1,(/1/),iout)
 777    end if
 778 
 779 !  eph variables
 780    if (optdriver==RUNL_EPH) then
 781      cond_string(1)='optdriver' ; cond_values(1)=RUNL_EPH
 782      call chkint_eq(1,1,cond_string,cond_values,ierr,'eph_task',dt%eph_task,6,[0,1,2,3,4,5],iout)
 783 
 784      if (any(dt%ddb_ngqpt <= 0)) then
 785        MSG_ERROR_NOSTOP("ddb_ngqpt must be specified when performing EPH calculations.", ierr)
 786      end if
 787      if (dt%eph_task==2 .and. dt%irdwfq==0 .and. dt%getwfq==0) then
 788        MSG_ERROR_NOSTOP('Either getwfq or irdwfq must be non-zero in order to compute the gkk', ierr)
 789      end if
 790 
 791    end if
 792 
 793 !  exchmix
 794    call chkdpr(0,0,cond_string,cond_values,ierr,'exchmix',dt%exchmix,1,0.0_dp,iout)
 795 
 796 !  extrapwf
 797    call chkint_eq(0,0,cond_string,cond_values,ierr,'extrapwf',dt%extrapwf,2,(/0,1/),iout)
 798    if (dt%extrapwf>0.and.dt%densfor_pred<5) then
 799      write(message,'(3a)')&
 800 &     'extrapwf keyword (extrapolation of WF) is only compatible with',ch10,&
 801 &     'densfor_pred=5 or 6; please change densfor_pred value.'
 802      MSG_ERROR_NOSTOP(message,ierr)
 803 !    MT oct 14: Should use chkint_eq but the msg is not clear enough
 804    end if
 805 
 806 !  fermie_nest
 807    call chkdpr(0,0,cond_string,cond_values,ierr,'fermie_nest',dt%fermie_nest,1,0.0_dp,iout)
 808 
 809 !  fftgw
 810    call chkint_eq(0,0,cond_string,cond_values,ierr,'fftgw',dt%fftgw,8, [00,01,10,11,20,21,30,31],iout)
 811 
 812 !  fockoptmix
 813    call chkint_eq(0,0,cond_string,cond_values,ierr,'fockoptmix',&
 814 &   dt%fockoptmix,12,(/0,1,11,201,211,301,401,501,601,701,801,901/),iout)
 815    if(dt%paral_kgb/=0)then
 816      cond_string(1)='paral_kgb' ; cond_values(1)=dt%paral_kgb
 817 !    Make sure that dt%fockoptmix is 0, 1 or 11 (wfmixalg==0)
 818      call chkint_eq(1,1,cond_string,cond_values,ierr,'fockoptmix',dt%fockoptmix,3,(/0,1,11/),iout)
 819    end if
 820 
 821 !  frzfermi
 822    call chkint_eq(0,0,cond_string,cond_values,ierr,'frzfermi',dt%frzfermi,2,(/0,1/),iout)
 823 
 824 !  fxcartfactor
 825    call chkdpr(0,0,cond_string,cond_values,ierr,'fxcartfactor',dt%fxcartfactor,1,zero,iout)
 826 
 827 !  ga_algor
 828    call chkint_eq(0,0,cond_string,cond_values,ierr,'ga_algor',dt%ga_algor,3,(/1,2,3/),iout)
 829 
 830 !  ga_fitness
 831    call chkint_eq(0,0,cond_string,cond_values,ierr,'ga_fitness',dt%ga_fitness,3,(/1,2,3/),iout)
 832 
 833 !  ga_opt_percent
 834    call chkdpr(0,0,cond_string,cond_values,ierr,'ga_opt_percent',dt%ga_opt_percent,1,tol8,iout)
 835 
 836 !  getxred
 837    if(dt%getxcart/=0)then
 838      cond_string(1)='getxcart' ; cond_values(1)=dt%getxcart
 839 !    Make sure that dt%getxred is 0
 840      call chkint_eq(1,1,cond_string,cond_values,ierr,'getxred',dt%getxred,1,(/0/),iout)
 841    end if
 842 
 843 !  goprecon
 844    call chkint_eq(0,0,cond_string,cond_values,ierr,'goprecon',dt%goprecon,4,(/0,1,2,3/),iout)
 845 
 846 !  gpu_devices
 847    if (dt%use_gpu_cuda==1) then
 848      if (all(gpu_devices(:)==-2)) then
 849        gpu_devices(:)=dt%gpu_devices(:)
 850      else if (any(dt%gpu_devices(:)/=gpu_devices(:))) then
 851        write(message,'(3a)')&
 852 &       'GPU device(s) selection cannot be different from one dataset to another!',ch10,&
 853 &       'Action: change gpu_devices in input file.'
 854        MSG_ERROR_NOSTOP(message, ierr)
 855      end if
 856    end if
 857 
 858 !  gw_invalid_freq
 859    call chkint_eq(0,0,cond_string,cond_values,ierr,'gw_invalid_freq',dt%gw_invalid_freq,3,(/0,1,2/),iout)
 860 
 861 !  gw_sctype
 862    call chkint_eq(0,0,cond_string,cond_values,ierr,'gw_sctype',dt%gw_sctype,&
 863 &   4,(/GWSC_one_shot,GWSC_only_W,GWSC_only_G,GWSC_both_G_and_W/),iout)
 864 
 865 !  gw_sigxcore
 866    call chkint_eq(0,0,cond_string,cond_values,ierr,'gw_sigxcore',dt%gw_sigxcore,2,[0,1],iout)
 867 
 868 !  gwcomp
 869    call chkint_eq(0,0,cond_string,cond_values,ierr,'gwcomp',dt%gwcomp,2,[0,1],iout)
 870    if (dt%gwcomp/=0) then
 871      if (optdriver==RUNL_SCREENING .and. (dt%awtr /=1 .or. dt%spmeth /=0)) then
 872        write(message,'(3a)' )&
 873 &       'When gwcomp/=0, the Adler-Wiser formula with time-reversal should be used',ch10,&
 874 &       'Action: set awtr to 1 or/and spmeth to 0'
 875        MSG_ERROR_NOSTOP(message,ierr)
 876      end if
 877 
 878 !    Extrapolar trick with HF, SEX and COHSEX is meaningless for Sigma
 879      if(optdriver==RUNL_SIGMA) then
 880        mod10=MOD(dt%gwcalctyp,10)
 881        if ( ANY(mod10 == [SIG_HF, SIG_SEX, SIG_COHSEX]) ) then
 882          write(message,'(3a)' )&
 883          'gwcomp/=0, is meaningless in the case of HF, SEX or COHSEX calculations. ',ch10,&
 884          'Action: set gwcomp to 0 or change gwcalctyp'
 885          MSG_ERROR_NOSTOP(message,ierr)
 886        end if
 887      end if
 888      if (optdriver==RUNL_SIGMA .and. ALL( dt%ppmodel /= [0,1,2] )) then
 889        write(message,'(a,i0,a)')&
 890 &       'The completeness trick cannot be used when ppmodel is ',dt%ppmodel,'. It should be set to 0, 1 or 2. '
 891        MSG_ERROR_NOSTOP(message,ierr)
 892      end if
 893    end if
 894 
 895 !  gwmem
 896    call chkint_eq(0,0,cond_string,cond_values,ierr,'gwmem',dt%gwmem,4,[0,1,10,11],iout)
 897 
 898 !  gwpara
 899    call chkint_eq(0,0,cond_string,cond_values,ierr,'gwpara',dt%gwpara,3,[0,1,2],iout)
 900 
 901 !  gwrpacorr
 902    if(dt%gwrpacorr>0) then
 903      mod10=MOD(dt%gwcalctyp,10)
 904      if (optdriver /= RUNL_SCREENING) then
 905        write(message,'(3a)' )&
 906        'gwrpacorr>0 can only be used when calculating the screening',ch10,&
 907        'Action: set gwrpacorr to 0 or optdriver to 3'
 908        MSG_ERROR_NOSTOP(message,ierr)
 909      end if
 910      if( mod10 /= SIG_GW_AC ) then
 911        write(message,'(3a)' )&
 912        'gwrpacorr>0 can only be used with purely imaginary frequencies',ch10,&
 913        'Action: set gwrpacorr to 0 or change gwcalctyp'
 914        MSG_ERROR_NOSTOP(message,ierr)
 915      end if
 916    end if
 917 
 918 !  gwls_stern_kmax
 919    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_stern_kmax',dt%gwls_stern_kmax,1,iout)
 920 
 921 !  gwls_npt_gauss_quad
 922    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_npt_gauss_quad',dt%gwls_npt_gauss_quad,1,iout)
 923 
 924 ! gwls_diel_model
 925    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_diel_model',dt%gwls_diel_model,1,iout)
 926    call chkint_le(0,0,cond_string,cond_values,ierr,'gwls_diel_model',dt%gwls_diel_model,3,iout)
 927 
 928 ! gwls_model_parameter
 929    call chkdpr(0,0,cond_string,cond_values,ierr,'gwls_model_parameter',dt%gwls_model_parameter,1,zero,iout)
 930 
 931 ! gwls_print_debug
 932    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_print_debug',dt%gwls_print_debug,0,iout)
 933 
 934 ! gwls_nseeds
 935    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_nseeds',dt%gwls_nseeds,1,iout)
 936 
 937 ! gwls_kmax_complement
 938    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_kmax_complement',dt%gwls_kmax_complement,0,iout)
 939 
 940 ! gwls_kmax_poles
 941    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_kmax_poles',dt%gwls_kmax_poles,0,iout)
 942 
 943 ! gwls_kmax_analytic
 944    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_kmax_analytic',dt%gwls_kmax_analytic,0,iout)
 945 
 946 ! gwls_kmax_numeric
 947    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_kmax_numeric',dt%gwls_kmax_numeric,0,iout)
 948 
 949 ! gwls_band_index
 950    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_band_index',dt%gwls_band_index,1,iout)
 951 
 952 ! gwls_exchange
 953    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_exchange',dt%gwls_exchange,0,iout)
 954 
 955 ! gwls_correlation
 956    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_correlation',dt%gwls_correlation,0,iout)
 957 
 958 ! gwls_first_seed
 959    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_first_seed',dt%gwls_first_seed,1,iout)
 960 
 961 ! gwls_recycle
 962    call chkint_ge(0,0,cond_string,cond_values,ierr,'gwls_recycle',dt%gwls_recycle,0,iout)
 963    call chkint_le(0,0,cond_string,cond_values,ierr,'gwls_recycle',dt%gwls_recycle,2,iout)
 964 
 965 !  iatsph between 1 and natom
 966    maxiatsph=maxval(dt%iatsph(1:dt%natsph))
 967    miniatsph=minval(dt%iatsph(1:dt%natsph))
 968    call chkint_ge(0,0,cond_string,cond_values,ierr,'iatsph',miniatsph,1,iout)
 969    call chkint_le(0,0,cond_string,cond_values,ierr,'iatsph',maxiatsph,natom,iout)
 970 
 971 !  icoulomb
 972    call chkint_eq(0,0,cond_string,cond_values,ierr,'icoulomb',dt%icoulomb,3,(/0,1,2/),iout)
 973    if (dt%nspden > 2) then
 974      cond_string(1)='nspden' ; cond_values(1)=nspden
 975      call chkint_eq(1,1,cond_string,cond_values,ierr,'icoulomb',dt%icoulomb,1,(/0/),iout)
 976    end if
 977 
 978 !  ieig2rf
 979    if(optdriver==RUNL_RESPFN.and.usepaw==1)then
 980      cond_string(1)='optdriver' ; cond_values(1)=1
 981      cond_string(2)='usepaw'    ; cond_values(2)=usepaw
 982      call chkint_eq(1,2,cond_string,cond_values,ierr,'ieig2rf',dt%ieig2rf,1,(/0/),iout)
 983    end if
 984    if(optdriver==RUNL_RESPFN.and.dt%paral_rf==1)then
 985      cond_string(1)='paral_rf' ; cond_values(1)=1
 986      call chkint_eq(1,1,cond_string,cond_values,ierr,'ieig2rf',dt%ieig2rf,1,(/0/),iout)
 987    end if
 988 
 989 !  imgmov
 990    call chkint_eq(0,0,cond_string,cond_values,ierr,'imgmov',dt%imgmov,8,(/0,1,2,4,5,9,10,13/),iout)
 991    if (dt%imgmov>0) then ! when imgmov>0, allow only ionmov0 and optcell 0 (temporary)
 992      cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
 993      call chkint_eq(1,1,cond_string,cond_values,ierr,'ionmov',dt%ionmov,1,(/0/),iout)
 994      if (dt%imgmov==9.or.dt%imgmov==10.or.dt%imgmov==13) then
 995        cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
 996        !Temporarily deactivate NPT algorithms (not yet usable)
 997        call chkint_eq(1,1,cond_string,cond_values,ierr,'optcell',dt%optcell,1,(/0/),iout)
 998      else
 999        cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
1000        call chkint_eq(1,1,cond_string,cond_values,ierr,'optcell',dt%optcell,1,(/0/),iout)
1001      end if
1002    end if
1003 
1004 !  intxc
1005    if(dt%iscf==-1)then
1006      cond_string(1)='iscf' ; cond_values(1)=-1
1007 !    Make sure that dt%intxc is 0
1008      call chkint_eq(1,1,cond_string,cond_values,ierr,'intxc',dt%intxc,1,(/0/),iout)
1009    end if
1010 !  TEMPORARY
1011    if(optdriver==RUNL_RESPFN)then ! Make sure that dt%intxc is 0
1012      cond_string(1)='optdriver' ; cond_values(1)=1
1013      call chkint_eq(1,1,cond_string,cond_values,ierr,'intxc',dt%intxc,1,(/0/),iout)
1014    end if
1015 
1016 !  ionmov
1017    call chkint_eq(0,0,cond_string,cond_values,ierr,'ionmov',&
1018 &   dt%ionmov,21,(/0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,20,21,22,23,24,25/),iout)
1019 
1020 !  When optcell/=0, ionmov must be 2, 3, 13 or 22 (except if imgmov>0)
1021    if(dt%optcell/=0)then
1022      if (dt%imgmov==0) then
1023        cond_string(1)='optcell' ; cond_values(1)=dt%optcell
1024        call chkint_eq(1,1,cond_string,cond_values,ierr,'ionmov',dt%ionmov,4,(/2,3,13,22/),iout)
1025      else
1026        cond_string(1)='optcell' ; cond_values(1)=dt%optcell
1027        call chkint_eq(1,1,cond_string,cond_values,ierr,'ionmov',dt%ionmov,1,(/0/),iout)
1028      end if
1029    end if
1030    if (dt%ionmov == 13) then
1031      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
1032 !    Make sure that nnos is not null
1033      call chkint_ge(1,1,cond_string,cond_values,ierr,'nnos',dt%nnos,1,iout)
1034    end if
1035 
1036 !  iprcel
1037    call chkint(0,0,cond_string,cond_values,ierr,'iprcel',dt%iprcel,1,(/0/),1,21,iout)   !  0 or superior to 21
1038    if(nsppol==2 .and. (dt%occopt>=3 .and. dt%occopt<=8).and.mod(dt%iprcel,10)>49 )then
1039      write(message,'(5a)')&
1040 &     'For spin-polarized metallic systems (occopt>3),',ch10,&
1041 &     'only RPA dielectric matrix can be evaluated) !',ch10,&
1042 &     'Action: change iprcel value in input file (mod(iprcel,100)<50) !'
1043      MSG_ERROR_NOSTOP(message, ierr)
1044    end if
1045    if(dt%npspinor>1.and.dt%iprcel>0)then
1046      write(message,'(5a)')&
1047 &     'When parallelization over spinorial components is activated (npspinor>1),',ch10,&
1048 &     'only model dielectric function is allowed (iprcel=0) !',ch10,&
1049 &     'Action: change iprcel value in input file !'
1050      MSG_ERROR_NOSTOP(message, ierr)
1051    end if
1052 
1053 !  irandom
1054    call chkint_eq(0,0,cond_string,cond_values,ierr,'irandom',dt%irandom,3,(/1,2,3/),iout)
1055 
1056 !  iscf
1057    if (usewvl ==0) then
1058      call chkint_eq(0,0,cond_string,cond_values,ierr,&
1059 &     'iscf',dt%iscf,18,(/-3,-2,-1,1,2,3,4,5,6,7,11,12,13,14,15,16,17,22/),iout)
1060    else
1061 !    If usewvl: wvlbigdft indicates that the BigDFT workflow will be followed
1062      wvlbigdft=(dt%usewvl==1.and.dt%wvl_bigdft_comp==1)
1063      cond_string(1)='wvl_bigdft_comp' ; cond_values(1)=dt%wvl_bigdft_comp
1064      if(wvlbigdft) then
1065        call chkint_eq(1,1,cond_string,cond_values,ierr,&
1066 &       'iscf',dt%iscf,15,(/0,1,2,3,4,5,6,7,11,12,13,14,15,16,17/),iout)
1067      else
1068        call chkint_eq(1,1,cond_string,cond_values,ierr,&
1069 &       'iscf',dt%iscf,18,(/-3,-2,-1,1,2,3,4,5,6,7,11,12,13,14,15,16,17,22/),iout)
1070      end if
1071 !    If wvl+metal, iscf cannot be 0
1072      if (dt%occopt>2) then
1073        cond_string(1)='occopt' ; cond_values(1)=dt%occopt
1074        call chkint_eq(1,1,cond_string,cond_values,ierr,&
1075 &       'iscf',dt%iscf,18,(/-3,-2,-1,1,2,3,4,5,6,7,11,12,13,14,15,16,17,22/),iout)
1076      end if
1077    end if
1078 !  If ionmov==4, iscf must be 2, 12, 5 or 6.
1079    if(dt%ionmov==4)then
1080      cond_string(1)='ionmov' ; cond_values(1)=4
1081      call chkint_eq(1,1,cond_string,cond_values,ierr,'iscf',dt%iscf,4,(/2,12,5,6/),iout)
1082    end if
1083 !  If PAW, iscf cannot be -1, 11
1084    if (usepaw==1 .and. usewvl==0) then
1085      cond_string(1)='PAW' ; cond_values(1)=1
1086      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)
1087    end if
1088 !  Mixing on density is only allowed for GS calculations or for drivers where it is not used.
1089    if(optdriver /= RUNL_GSTATE .and. all(optdriver/=[RUNL_SCREENING,RUNL_SIGMA,RUNL_BSE,RUNL_EPH,RUNL_WFK])) then
1090      cond_string(1)='optdriver' ; cond_values(1)=optdriver
1091      call chkint_le(1,1,cond_string,cond_values,ierr,'iscf',dt%iscf,9,iout)
1092    end if
1093 !  When pawoptmix=1 and nspden=4, iscf must be >=10
1094    if(dt%pawoptmix/=0.and.nspden==4)then
1095      cond_string(1)='nspden'    ; cond_values(1)=nspden
1096      cond_string(2)='pawoptmix' ; cond_values(2)=dt%pawoptmix
1097      call chkint_ge(2,2,cond_string,cond_values,ierr,'iscf',dt%iscf,10,iout)
1098    end if
1099 
1100 !  istatimg
1101    call chkint_eq(0,0,cond_string,cond_values,ierr,'istatimg',dt%istatimg,2,(/0,1/),iout)
1102    if (dt%string_algo==2) then
1103      cond_string(1)='string_algo' ; cond_values(1)=dt%string_algo
1104      call chkint_eq(1,1,cond_string,cond_values,ierr,'istatimg',dt%istatimg,1,(/1/),iout)
1105    end if
1106 
1107 !  istwfk
1108    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
1109      write(message,'(3a)' )&
1110 &     'When usefock==1, unless sigma calculation, all the components of istwfk must be 1.',ch10,&
1111 &     'Action: set istwfk to 1 for all k-points'
1112      MSG_ERROR_NOSTOP(message,ierr)
1113    end if
1114 
1115    if(dt%usewvl==1 .and. maxval( abs(dt%istwfk(1:nkpt)-1) ) >0)then
1116      write(message,'(3a)' )&
1117 &     'When usewvl==1, all the components of istwfk must be 1.',ch10,&
1118 &     'Action: set istwfk to 1 for all k-points'
1119      MSG_ERROR_NOSTOP(message,ierr)
1120    end if
1121 
1122    if(response==1 .and. maxval( abs(dt%istwfk(1:nkpt)-1) ) >0)then
1123 !    Force istwfk to be 1 for RF calculations
1124 !    Other choices cannot be realized yet, because of the ddk perturbation.
1125      write(message,'(5a)' )&
1126 &     'When response==1, all the components of istwfk must be 1.',ch10,&
1127 &     'Not yet programmed for time-reversal symmetry.',ch10,&
1128 &     'Action: set istwfk to 1 for all k-points'
1129      MSG_ERROR_NOSTOP(message,ierr)
1130    end if
1131    if(dt%nbandkss/=0 .and. dt%kssform/=3 .and. maxval( abs(dt%istwfk(1:nkpt)-1) ) >0)then
1132      write(message,'(5a)' )&
1133 &     'When nbandkss/=0 and kssform/=3 all the components of istwfk must be 1.',ch10,&
1134 &     'Not yet programmed for time-reversal symmetry.',ch10,&
1135 &     'Action: set istwfk to 1 for all k-points'
1136      MSG_ERROR_NOSTOP(message,ierr)
1137    end if
1138    if(dt%berryopt/=0 .and. maxval(dt%istwfk(:))/=1)then
1139      write(message,'(5a)' )&
1140 &     'When berryopt/=0, all the components of istwfk must be 1.',ch10,&
1141 &     'Not yet programmed for time-reversal symmetry.',ch10,&
1142 &     'Action: set istwfk to 1 for all k-points'
1143      MSG_ERROR_NOSTOP(message,ierr)
1144    end if
1145    if (dt%optdriver==RUNL_GSTATE) then
1146      if ((dt%wfoptalg==4.or.dt%wfoptalg==14.or.dt%wfoptalg==114).and.maxval(dt%istwfk(:)-2)>0) then
1147        write(message, '(a,a,a,a,a)' )&
1148 &       'Only the gamma point can use time-reversal and wfoptalg=4 or 14',ch10,&
1149 &       'Action: put istwfk to 1 or remove k points with half integer coordinates ',ch10,&
1150 &       'Also contact ABINIT group to say that you need that option.'
1151        MSG_ERROR_NOSTOP(message,ierr)
1152      end if
1153 !     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
1154 !       write(message, '(a,i3,a,a,a)' )&
1155 !&       ' For istwfk=2, the value fftalg= ',fftalg, &
1156 !&       ' is not allowed in case of wfoptalg=4 or 14 !', ch10,&
1157 !&       ' Change if to fftalg=401.'
1158 !       MSG_ERROR_NOSTOP(message,ierr)
1159 !     end if
1160    end if
1161 
1162 !  ixc
1163    call chkint(0,0,cond_string,cond_values,ierr,&
1164 &   'ixc',dt%ixc,33,(/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,40,41,42,50/),-1,0,iout) ! One of the values, or negative
1165    if(dt%iscf==-1)then
1166      cond_string(1)='iscf' ; cond_values(1)=-1
1167 !    Make sure that ixc is 1, 7, 8, 20, 21 or 22 or negative
1168      call chkint(1,1,cond_string,cond_values,ierr,'ixc',dt%ixc,6,(/1,7,8,20,21,22/),-1,0,iout)
1169    end if
1170    if(response==1)then
1171      cond_string(1)='response' ; cond_values(1)=1
1172 !    Make sure that ixc is between 0 and 9, or 11, 12, 14, 15, 23 or 24 or negative
1173      call chkint(1,1,cond_string,cond_values,ierr,&
1174 &     'ixc',dt%ixc,16,(/0,1,2,3,4,5,6,7,8,9,11,12,14,15,23,24/),-1,0,iout)
1175    end if
1176    if(nspden/=1)then
1177      cond_string(1)='nspden' ; cond_values(1)=nspden
1178 !    Make sure that ixc is 0, 1 , the gga, or Fermi-Amaldi, or negative
1179      call chkint(1,1,cond_string,cond_values,ierr,&
1180 &     'ixc',dt%ixc,24,(/0,1,7,8,9,11,12,13,14,15,16,17,20,23,24,26,27,31,32,33,34,40,41,42/),-1,0,iout)
1181    end if
1182    if(dt%usepaw>0.and.dt%ixc<0) then
1183      if (libxc_functionals_is_hybrid()) then
1184        message='Meta-GGA functionals are not compatible with PAW!'
1185        MSG_ERROR_NOSTOP(message,ierr)
1186      end if
1187    end if
1188    if (dt%usepaw>0.and.(dt%ixc==-427.or.dt%ixc==-428)) then
1189      message='Range-separated Hybrid Functionals have not been extensively tested in PAW!!!'
1190      MSG_WARNING(message)
1191    end if
1192    allow=(dt%ixc > 0).and.(dt%ixc /= 3).and.(dt%ixc /= 7).and.(dt%ixc /= 8)
1193    if(.not.allow)then
1194      allow=(dt%ixc < 0).and.(libxc_functionals_is_hybrid().or.libxc_functionals_ismgga())
1195    end if
1196    if(allow)then
1197      cond_string(1)='ixc' ; cond_values(1)=dt%ixc
1198      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_NONLINEAR/),iout)
1199    end if
1200 
1201 !  ixcpositron
1202    call chkint_eq(0,0,cond_string,cond_values,ierr,'ixcpositron',dt%ixcpositron,8,(/0,-1,1,11,2,3,31,4/),iout)
1203 
1204 !  ixcrot
1205    call chkint_eq(0,0,cond_string,cond_values,ierr,'ixcrot',dt%ixcrot,3,(/1,2,3/),iout)
1206 
1207 !  tim1rev
1208    call chkint_eq(0,0,cond_string,cond_values,ierr,'tim1rev',dt%tim1rev,2,(/0,1/),iout)
1209 
1210 !  kptnrm and kpt
1211 !  Coordinates components must be between -1 and 1.
1212    if(dt%kptnrm<1.0-1.0d-10)then
1213      write(message, '(a,es22.14,a,a,a)' )&
1214 &     'The input variable kptnrm is',dt%kptnrm,' while it must be >=1.0_dp.',ch10,&
1215 &     'Action: change the input variable kptnrm.'
1216      MSG_ERROR_NOSTOP(message,ierr)
1217    end if
1218    do ikpt=1,nkpt
1219      do mu=1,3
1220        if ( abs(dt%kpt(mu,ikpt))> dt%kptnrm*1.0000001_dp ) then
1221          write(message, '(a,i5,a,a,a,a,3es22.14,a,a,a,a)' )&
1222 &         'For k point number',ikpt,'  the reduced coordinates',ch10,&
1223 &         'generated by the input variables kpt and kptnrm are',ch10,&
1224 &         dt%kpt(1,ikpt)/dt%kptnrm,dt%kpt(2,ikpt)/dt%kptnrm,dt%kpt(3,ikpt)/dt%kptnrm,ch10,&
1225 &         'while they must be between -1.0_dp and 1.0_dp (included).',ch10,&
1226 &         'Action: check kpt and kptnrm in the input file.'
1227          MSG_ERROR_NOSTOP(message,ierr)
1228        end if
1229      end do
1230    end do
1231 
1232 !  jellslab
1233    call chkint_eq(0,0,cond_string,cond_values,ierr,'jellslab',dt%jellslab,2,(/0,1/),iout)
1234 
1235    if (dt%jellslab==1) then
1236      if(dt%nimage>1)then
1237        cond_string(1)='nimage' ; cond_values(1)=dt%nimage
1238        call chkint_eq(1,1,cond_string,cond_values,ierr,'jellslab',dt%jellslab,1,(/0/),iout)
1239      end if
1240 !    slabwsrad must be positive
1241      cond_string(1)='jellslab' ; cond_values(1)=dt%jellslab
1242      call chkdpr(1,0,cond_string,cond_values,ierr,'slabwsrad',dt%slabwsrad,1,zero,iout)
1243 !    slabzbeg must be positive
1244      call chkdpr(1,0,cond_string,cond_values,ierr,'slabzbeg',dt%slabzbeg,1,zero,iout)
1245 !    slabzend must be bigger than slabzbeg
1246      call chkdpr(1,0,cond_string,cond_values,ierr,'slabzend',dt%slabzend,1,dt%slabzbeg,iout)
1247 !    rprimd(3,3) must be bigger than slabzend
1248      call chkdpr(1,0,cond_string,cond_values,ierr,'rprimd33',rprimd(3,3),1,dt%slabzend,iout)
1249 !    Third real space primitive translation has to be orthogonal to the other ones,
1250 !    actually, for convenience it is useful that rprimd is something like:
1251 !    a  b  0
1252 !    c  d  0
1253 !    0  0  e
1254      if(abs(rprimd(1,3))+abs(rprimd(2,3))+abs(rprimd(3,1))+abs(rprimd(3,2))>tol12) then
1255        write(message,'(a,a,a)')&
1256 &       'Third real space vector is not orthogonal to the other ones,',ch10,&
1257 &       'this is needed to use jellium'
1258        MSG_ERROR_NOSTOP(message, ierr)
1259      end if
1260 
1261 !    Atoms have to be placed in the vacuum space
1262      do iatom=1,natom
1263        zatom=(dt%xred_orig(3,iatom,intimage)-anint(dt%xred_orig(3,iatom,intimage)-half+tol6))*rprimd(3,3)
1264        if(abs(zatom-dt%slabzbeg)<tol8 .or. abs(zatom-dt%slabzend)<tol8) then
1265          if(dt%znucl(dt%typat(iatom))>tol6) then
1266            write(message,'(a,i0,a)')'atom number=',iatom,' lies precisely on the jellium edge !'
1267            MSG_WARNING(message)
1268          end if
1269          cycle
1270        end if
1271        if(zatom>dt%slabzbeg .and. zatom<dt%slabzend) then
1272          write(message,'(a,i0,a)')' atom number=',iatom,' is inside the jellium slab.'
1273          MSG_ERROR_NOSTOP(message, ierr)
1274        end if
1275      end do
1276    end if
1277 
1278 !  kssform
1279    call chkint_eq(0,0,cond_string,cond_values,ierr,'kssform',dt%kssform,3,(/0,1,3/),iout)
1280 
1281    if (dt%kssform/=0 .and. dt%nbandkss/=0) then ! Check for outkss limitations.
1282      call wrtout(std_out," Checking if input is consistent with KSS generation",'COLL')
1283      call chkint_eq(0,0,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,1,(/0/),iout)
1284      call chkint_eq(0,0,cond_string,cond_values,ierr,'iomode',dt%iomode,2,(/IO_MODE_FORTRAN,IO_MODE_ETSF/),iout)
1285    end if
1286 
1287 !  localrdwf
1288    call chkint_eq(0,0,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,2,(/0,1/),iout)
1289    if(dt%mkmem==0)then
1290      cond_string(1)='mkmem' ; cond_values(1)=dt%mkmem
1291      call chkint_eq(1,1,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,1,(/1/),iout)
1292    end if
1293    if(dt%mkqmem==0)then
1294      cond_string(1)='mkqmem' ; cond_values(1)=dt%mkqmem
1295      call chkint_eq(1,1,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,1,(/1/),iout)
1296    end if
1297    if(dt%mk1mem==0)then
1298      cond_string(1)='mk1mem' ; cond_values(1)=dt%mk1mem
1299      call chkint_eq(1,1,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,1,(/1/),iout)
1300    end if
1301    if(dt%iomode==IO_MODE_MPI)then
1302      cond_string(1)='iomode' ; cond_values(1)=dt%iomode
1303      call chkint_eq(1,1,cond_string,cond_values,ierr,'localrdwf',dt%localrdwf,1,(/1/),iout)
1304    end if
1305 
1306 
1307 !  LOTF
1308 #if defined HAVE_LOTF
1309    if (dt%ionmov==23) then
1310      write(message, '(a,a)' ) ch10,&
1311 &     '=== LOTF METHOD ================================================================'
1312      call wrtout(ab_out,message,'COLL')
1313      cond_string(1)='ionmov' ; cond_values(1)=23
1314      call chkint_eq(0,1,cond_string,cond_values,ierr,'lotf_classic',dt%lotf_classic,1,(/5/),iout)
1315      cond_string(1)='ionmov' ; cond_values(1)=23
1316      call chkint_ge(0,1,cond_string,cond_values,ierr,'lotf_nitex',dt%lotf_nitex,1,iout)
1317      cond_string(1)='ionmov' ; cond_values(1)=23
1318      call chkint_ge(0,1,cond_string,cond_values,ierr,'lotf_nneigx',dt%lotf_nneigx,2,iout)
1319      cond_string(1)='ionmov' ; cond_values(1)=23
1320      call chkint_eq(0,1,cond_string,cond_values,ierr,'lotf_version',dt%lotf_version,1,(/2/),iout)
1321    end if
1322 #endif
1323 
1324 !  magconon
1325    call chkint_eq(0,0,cond_string,cond_values,ierr,'magconon',dt%magconon,3,(/0,1,2/),iout)
1326 !!  impose nspden 4 for the moment and spinors
1327 !   if (dt%magconon == 1) then
1328 !     if (dt%nspinor /= 2 .or. dt%nspden /= 4) then
1329 !       write (message, '(4a)') &
1330 !&       ' magnetization direction constraint is only compatible with non-collinear calculations', ch10,&
1331 !&       ' Action: set nspinor 2 and nspden 4 in the input file.'
1332 !       MSG_ERROR_NOSTOP(message,ierr)
1333 !     end if
1334 !   end if
1335 
1336 !  macro_uj
1337    if(dt%macro_uj/=0) then
1338      if (dt%ionmov/=0) then
1339        write(message, '(3a,i2,2a,i2,3a)' )&
1340 &       'Determination of U can not be combined with ionic movements.',ch10,&
1341 &       'Here  ionmov= ',dt%ionmov,ch10,&
1342 &       'and macro_uj=',dt%macro_uj,'.',ch10,&
1343 &       'Action: change ionmov in input file.'
1344        MSG_ERROR_NOSTOP(message,ierr)
1345      else if (dt%nstep<3) then
1346        write(message, '(3a,i1,2a,i2,3a)' )&
1347 &       'Determination of U needs at least 3 scf steps:',ch10,&
1348 &       ' nstep = ',dt%nstep,ch10,&
1349 &       ' and macro_uj=',dt%macro_uj,'.',ch10,&
1350 &       'Action: increase nstep in input file.'
1351        MSG_ERROR_NOSTOP(message,ierr)
1352      end if
1353    end if
1354 
1355 !  mep_solver
1356    call chkint_eq(0,0,cond_string,cond_values,ierr,'mep_solver',dt%mep_solver,5,(/0,1,2,3,4/),iout)
1357 !  String method
1358    if(dt%imgmov==2) then
1359      cond_string(1)='imgmov'      ; cond_values(1)=dt%imgmov
1360      if(dt%string_algo==0)then
1361        cond_string(2)='string_algo' ; cond_values(2)=dt%string_algo
1362        call chkint_eq(1,1,cond_string,cond_values,ierr,'mep_solver',dt%mep_solver,1,(/0/),iout)
1363      end if
1364      if(dt%string_algo==1.or.dt%string_algo==2)then
1365        cond_string(2)='string_algo' ; cond_values(2)=dt%string_algo
1366        call chkint_eq(1,1,cond_string,cond_values,ierr,'mep_solver',dt%mep_solver,2,(/0,4/),iout)
1367      end if
1368    end if
1369 !  NEB
1370    if(dt%imgmov==5)then
1371      cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
1372      call chkint_eq(1,1,cond_string,cond_values,ierr,'mep_solver',dt%mep_solver,4,(/0,1,2,3/),iout)
1373    end if
1374 
1375 !  mffmem
1376    call chkint_eq(0,0,cond_string,cond_values,ierr,'mffmem',dt%mffmem,2,(/0,1/),iout)
1377 
1378 !  mixalch_orig
1379 !  For each type of atom, the sum of the psp components
1380 !  must be one.
1381    do iimage=1,dt%nimage
1382      if(dt%ntypalch>0)then
1383        do itypat=1,dt%ntypalch
1384          sumalch=sum(dt%mixalch_orig(:,itypat,iimage))
1385          if(abs(sumalch-one)>tol10)then
1386            if(dt%npspalch<=6)then
1387              write(message, '(2a,6es12.4)' )ch10,' chkinp : mixalch(:,itypat,iimage)=',dt%mixalch_orig(:,itypat,iimage)
1388            end if
1389            call wrtout(iout,message,'COLL')
1390            call wrtout(std_out,  message,'COLL')
1391            write(message, '(a,i4,2a,i4,2a,f8.2,4a)' )&
1392 &           'For the alchemical atom number',itypat,ch10,&
1393 &           'image number',iimage,ch10,&
1394 &           'the sum of the pseudopotential coefficients is',sumalch,ch10,&
1395 &           'while it should be one.',ch10,&
1396 &           'Action: check the content of the input variable mixalch.'
1397            MSG_ERROR_NOSTOP(message,ierr)
1398          end if
1399        end do
1400      end if
1401    end do
1402 
1403 !  natom
1404    if(dt%prtgeo>0)then
1405      cond_string(1)='prtgeo' ; cond_values(1)=dt%prtgeo
1406      call chkint_le(1,1,cond_string,cond_values,ierr,'natom',natom,9999,iout)
1407    end if
1408 
1409 !  nband
1410 !  Make sure all nband(nkpt) are > 0
1411    do isppol=1,nsppol
1412      do ikpt=1,nkpt
1413        if (dt%nband(ikpt+(isppol-1)*nkpt)<=0) then
1414          cond_string(1)='ikpt' ; cond_values(1)=ikpt
1415          cond_string(2)='isppol' ; cond_values(2)=isppol
1416          call chkint_ge(0,2,cond_string,cond_values,ierr,'nband',dt%nband(ikpt+(isppol-1)*nkpt),1,iout)
1417        end if
1418      end do
1419    end do
1420    if(nproc/=1.and.nsppol==2.and.usewvl==0)then
1421      do ikpt=1,nkpt
1422        if (dt%nband(ikpt)/=dt%nband(ikpt+nkpt)) then
1423          write(message, '(5a,i4,a,2i5,a)' )&
1424 &         'the number of bands in the spin up case must be equal to',ch10,&
1425 &         'the number of bands in the spin down case.',ch10,&
1426 &         'This is not the case for the k point number :',ikpt,&
1427 &         'The number of bands spin up and down are :',dt%nband(ikpt),dt%nband(ikpt+nkpt),&
1428 &         'Action: change nband, or use the sequential version of ABINIT.'
1429          MSG_ERROR_NOSTOP(message,ierr)
1430        end if
1431      end do
1432    end if
1433 
1434 !  nbandkss
1435 !  Must be greater or equal to -1
1436    call chkint_ge(0,0,cond_string,cond_values,ierr,'nbandkss',dt%nbandkss,-1,iout)
1437 !  When ionmov/=0
1438    if(dt%ionmov/=0 .and. dt%nbandkss/=0)then
1439      write(message,'(11a)')&
1440 &     'Ions (or cell) are allowed to move (ionmov/=0),',ch10,&
1441 &     'and a _KSS file is requested (nbandkss/=0).',ch10,&
1442 &     'A _KSS file will be created at each geometry-optimisation step.',ch10,&
1443 &     'Note that this is time consuming !',ch10,&
1444 &     'Action: use datasets (one for geometry optimisation,',ch10,&
1445 &     '        one for states output).'
1446      MSG_WARNING(message)
1447    end if
1448 
1449 !  nbdblock
1450 !  Must be greater or equal to 1
1451    call chkint_ge(0,0,cond_string,cond_values,ierr,'nbdblock',dt%nbdblock,1,iout)
1452 !  When wfoptalg==0, nbdblock must be 1
1453    if(mod(dt%wfoptalg,10)==0)then
1454      cond_string(1)='wfoptalg' ; cond_values(1)=0
1455      call chkint_eq(1,1,cond_string,cond_values,ierr,'nbdblock',dt%nbdblock,1,(/1/),iout)
1456    end if
1457 !  When wfoptalg==2, nbdblock must be 1
1458    if(dt%wfoptalg==2)then
1459      cond_string(1)='wfoptalg' ; cond_values(1)=2
1460      call chkint_eq(1,1,cond_string,cond_values,ierr,'nbdblock',dt%nbdblock,1,(/1/),iout)
1461    end if
1462 !  When wfoptalg==3, nbdblock must be 1, and iscf must be -2
1463    if(dt%wfoptalg==3)then
1464      cond_string(1)='wfoptalg' ; cond_values(1)=3
1465      call chkint_eq(1,1,cond_string,cond_values,ierr,'nbdblock',dt%nbdblock,1,(/1/),iout)
1466      call chkint_eq(1,1,cond_string,cond_values,ierr,'iscf',dt%iscf,1,(/-2/),iout)
1467    end if
1468 !  When wfoptalg==4, nbdblock must be a divisor of nband
1469    if(mod(dt%wfoptalg,10)==4.and.dt%optdriver==RUNL_GSTATE)then
1470      do isppol=1,nsppol
1471        do ikpt=1,nkpt
1472          if(mod(dt%nband(ikpt+(isppol-1)*nkpt),dt%nbdblock)/=0) then
1473            write(message, '(5a)' )&
1474 &           'For the moment, when wfoptalg=4,',ch10,&
1475 &           'nband must be a multiple of nbdblock.',ch10,&
1476 &           'Action: check the value of the input variable nbdblock.'
1477            MSG_ERROR_NOSTOP(message,ierr)
1478          end if
1479        end do
1480      end do
1481    end if
1482 
1483 !  nberry
1484 !  must be between 0 and 20
1485    if(dt%berryopt/=0)then
1486      call chkint_ge(0,0,cond_string,cond_values,ierr,'nberry',dt%nberry,0,iout)
1487      call chkint_le(0,0,cond_string,cond_values,ierr,'nberry',dt%nberry,20,iout)
1488      if(xmpi_paral==1)then
1489 !      MPI Parallel case
1490        if (dt%nberry/=0.and.dt%berryopt>0.and.&
1491 &       dt%berryopt/= 4.and.dt%berryopt/= 5.and.dt%berryopt/= 6.and.dt%berryopt/= 7.and.&
1492 &       dt%berryopt/=14.and.dt%berryopt/=15.and.dt%berryopt/=16.and.dt%berryopt/=17) then
1493          write(message,'(a,a,a,a,a,i4,a,a,a)')&
1494 &         'Berry phase calculation of polarisation with positive berryopt is not',ch10,&
1495 &         'allowed in the parallel version of ABINIT.',ch10,&
1496 &         'So, the value of nberry=',dt%nberry,' is not allowed,',ch10,&
1497 &         'Action: change berryopt to negative values or change nberry, or use the sequential version.'
1498          MSG_ERROR_NOSTOP(message,ierr)
1499        end if
1500      end if
1501    end if
1502 
1503    if (dt%optcell /=0 .and. dt%berryopt == 4)  then
1504      write(message,'(a,a,a,a,a,a,a,a,a,a,a,a,a)') ch10,&
1505 &     ' chkinp : WARNING -',ch10,&
1506 &     '  Constant unreduced E calculation with relaxation of cell parameters is allowed.',ch10,&
1507 &     '  But we strongly recommend users to use reduced ebar calculation (berryopt=14)',ch10,&
1508 &     '  with the relaxation of cell parameters, for internal consistency purpose.',ch10, &
1509 &     '  For more information, please refer to "M. Stengel, N.A. Spaldin and D.Vanderbilt,', ch10, &
1510 &     '  Nat. Phys., 5, 304,(2009)" and its supplementary notes.', ch10
1511      call wrtout(ab_out,message,'COLL')
1512      call wrtout(std_out,message,'COLL')
1513    end if
1514 
1515    if (dt%optcell /=0 .and. (dt%berryopt == 6 ))  then
1516      write(message,'(a,a,a,a,a,a,a,a,a,a,a,a,a)') ch10,&
1517 &     ' chkinp : WARNING -',ch10,&
1518 &     '  Constant unreduced D calculation with relaxation of cell parameters is allowed.',ch10,&
1519 &     '  But we strongly recommend users to use reduced d calculation (berryopt=16)',ch10,&
1520 &     '  with the relaxation of cell parameters, for internal consistency purpose.',ch10, &
1521 &     '  For more information, please refer to "M. Stengel, N.A. Spaldin and D.Vanderbilt,', ch10, &
1522 &     '  Nat. Phys., 5, 304,(2009)" and its supplementary notes.', ch10
1523      call wrtout(ab_out,message,'COLL')
1524      call wrtout(std_out,message,'COLL')
1525    end if
1526 
1527 !  ndynimage
1528 !  Must be greater or equal to 1
1529    call chkint_ge(0,0,cond_string,cond_values,ierr,'ndynimage',dt%ndynimage,1,iout)
1530 
1531 !  neb_algo
1532    call chkint_eq(0,0,cond_string,cond_values,ierr,'neb_algo',dt%neb_algo,4,(/0,1,2,3/),iout)
1533 
1534 !  nfft and nfftdg
1535 !  Must have nfft<=nfftdg
1536    if (usepaw==1) then
1537      nfft  =dt%ngfft(1)  *dt%ngfft(2)  *dt%ngfft(3)
1538      nfftdg=dt%ngfftdg(1)*dt%ngfftdg(2)*dt%ngfftdg(3)
1539      cond_string(1)='nfft' ; cond_values(1)=nfft
1540      call chkint(1,1,cond_string,cond_values,ierr,'nfftdg',nfftdg,1,(/0/),1,nfft,iout) ! Must be 0 or nfft
1541    end if
1542 
1543 !  diismemory
1544 !  Must be greater or equal to 1
1545    call chkint_ge(0,0,cond_string,cond_values,ierr,'diismemory',dt%diismemory,1,iout)
1546 
1547 !  nimage
1548 !  Must be greater or equal to 1
1549    call chkint_ge(0,0,cond_string,cond_values,ierr,'nimage',dt%nimage,1,iout)
1550    if (usewvl==1) then
1551      cond_string(1)='usewvl' ; cond_values(1)=usewvl
1552      call chkint_eq(1,1,cond_string,cond_values,ierr,'nimage',dt%nimage,1,(/1/),iout)
1553    end if
1554    if (optdriver/=RUNL_GSTATE) then
1555      cond_string(1)='optdriver' ; cond_values(1)=optdriver
1556      call chkint_eq(1,1,cond_string,cond_values,ierr,'nimage',dt%nimage,1,(/1/),iout)
1557    end if
1558    if (dt%tfkinfunc==2) then
1559      cond_string(1)='tfkinfunc' ; cond_values(1)=dt%tfkinfunc
1560      call chkint_eq(1,1,cond_string,cond_values,ierr,'nimage',dt%nimage,1,(/1/),iout)
1561    end if
1562    if (dt%prtxml==1) then
1563      cond_string(1)='prtxml' ; cond_values(1)=dt%prtxml
1564      call chkint_eq(1,1,cond_string,cond_values,ierr,'nimage',dt%nimage,1,(/1/),iout)
1565    end if
1566    if (dt%imgmov==9.or.dt%imgmov==13) then
1567      if (dt%pitransform==1.and.(mod(dt%nimage,2)/=0)) then
1568        write(message,'(6a)')ch10,&
1569 &       'Path-Integral Molecular Dynamics (imgmov=9,13)',ch10,&
1570 &       'in normal mode tranformation (pitransform=1).',ch10,&
1571 &       'requires nimage to be even!'
1572        MSG_ERROR_NOSTOP(message,ierr)
1573      end if
1574    end if
1575    if (dt%imgmov==10.and.dt%pitransform>0) then
1576      write(message,'(4a)')ch10,&
1577 &     'Path-Integral Molecular Dynamics (imgmov=10) with QTB',ch10,&
1578 &     'requires primitive coordinates (pitransform=0).'
1579      MSG_ERROR_NOSTOP(message,ierr)
1580    end if
1581 
1582 !  nkpt
1583 !  Must be greater or equal to 1
1584    call chkint_ge(0,0,cond_string,cond_values,ierr,'nkpt',nkpt,1,iout)
1585 !  If prtdos>=2, nkpt must be greater or equal to 2
1586    if(dt%prtdos>=2)then
1587      cond_string(1)='prtdos' ; cond_values(1)=dt%prtdos
1588      call chkint_ge(1,1,cond_string,cond_values,ierr,'nkpt',nkpt,2,iout)
1589    end if
1590 !  Must be smaller than 50 if iscf=-2 (band structure)
1591 !  while prteig=0 and prtvol<2, except if kptopt>0
1592    if(dt%iscf==-2 .and. dt%prteig==0 .and. dt%prtvol<2 .and. dt%kptopt<=0)then
1593      cond_string(1)='iscf'   ; cond_values(1)=dt%iscf
1594      cond_string(2)='prteig' ; cond_values(2)=dt%prteig
1595      cond_string(3)='prtvol' ; cond_values(3)=dt%prtvol
1596      call chkint_le(1,3,cond_string,cond_values,ierr,'nkpt',nkpt,50,iout)
1597    end if
1598 
1599 !  nloalg(1)= nloc_alg
1600 !  Must be 2, 3, 4
1601    call chkint_eq(0,0,cond_string,cond_values,ierr,'nloc_alg',dt%nloalg(1),3,(/2,3,4/),iout)
1602 
1603 !  nloc_mem= nloalg(2)*(nloalg(3)+1)
1604 !  nloalg(2) must be -1 or 1 ; nloalg(3) is 0 or 1.
1605    nloc_mem=dt%nloalg(2)*(dt%nloalg(3)+1)
1606    call chkint_eq(0,0,cond_string,cond_values,ierr,'nloc_mem',nloc_mem,4,(/-2,-1,1,2/),iout)
1607 
1608 !  npband
1609 !  Must be greater or equal to 1
1610    call chkint_ge(0,0,cond_string,cond_values,ierr,'npband',dt%npband,1,iout)
1611 
1612 !  npfft
1613 !  Must be greater or equal to 1
1614    call chkint_ge(0,0,cond_string,cond_values,ierr,'npfft',dt%npfft,1,iout)
1615 !  If usepaw==1 and pawmixdg==0, npfft must be equal to 1
1616    if(usepaw==1 .and. dt%pawmixdg==0)then
1617      cond_string(1)='usepaw  ' ; cond_values(1)=usepaw
1618      cond_string(2)='pawmixdg' ; cond_values(2)=dt%pawmixdg
1619      call chkint_eq(1,2,cond_string,cond_values,ierr,'npfft',dt%npfft,1,(/1/),iout)
1620    end if
1621 #ifdef HAVE_OPENMP
1622    if (dt%wfoptalg==114) then
1623      if ( xomp_get_num_threads(.true.) > 1 .and. dt%npfft > 1 ) then
1624        write(message,'(4a,i4,a,i4,a)') "When compilied with OpenMP, the FFT parallelization is not ",&
1625 &       "compatible with multiple threads.",ch10,"Please set npfft to 1 (currently npfft=",&
1626 &       dt%npfft, ") or export OMP_NUM_THREADS=1 (currently ",xomp_get_num_threads(.true.),")"
1627        MSG_ERROR_NOSTOP(message, ierr)
1628      end if
1629    end if
1630 #endif
1631 
1632 !  npimage
1633 !  Must be greater or equal to 1
1634    call chkint_ge(0,0,cond_string,cond_values,ierr,'npimage',dt%npimage,1,iout)
1635 !  At present, parallelism over images is not coded ...
1636 !  call chkint_eq(0,0,cond_string,cond_values,ierr,'npimage',dt%npimage,1,(/1/),iout)
1637 
1638 !  npkpt
1639 !  Must be greater or equal to 1
1640    call chkint_ge(0,0,cond_string,cond_values,ierr,'npkpt',dt%npkpt,1,iout)
1641 
1642 !  nppert
1643    cond_string(1)='paral_rf' ; cond_values(1)=1
1644    call chkint_ge(1,1,cond_string,cond_values,ierr,'nppert',dt%nppert,1,iout)
1645 
1646 !  nproc
1647    if (response==1.and.nsppol==2.and.nproc>1.and.modulo(nproc,2)>0) then
1648      write(message,'(8a)' ) &
1649 &     'For DFPT parallel calculations on spin-polarized systems (nsppol=2),',ch10,&
1650 &     'the number of processors must be even !'
1651      MSG_ERROR_NOSTOP(message,ierr)
1652    end if
1653 
1654 !  nproj
1655 !  If there is more than one projector for some angular momentum
1656 !  channel of some pseudopotential
1657    do ilang=0,3
1658 !    nprojmax(ilang)=maxval(pspheads(1:npsp)%nproj(ilang)) ! Likely problems with HP compiler
1659      nprojmax(ilang)=pspheads(1)%nproj(ilang)
1660      if(npsp>=2)then
1661 
1662        do ii=2,npsp
1663          nprojmax(ilang)=max(pspheads(ii)%nproj(ilang),nprojmax(ilang))
1664        end do
1665      end if
1666    end do
1667 
1668 !  npspinor
1669 !  Must be equal to 1 or 2
1670    call chkint_eq(0,0,cond_string,cond_values,ierr,'npspinor',dt%npspinor,2,(/1,2/),iout)
1671 !  If nspinor==1, npspinor must be equal to 1
1672    if(dt%nspinor==1 )then
1673      cond_string(1)='nspinor' ; cond_values(1)=dt%nspinor
1674      call chkint_eq(0,1,cond_string,cond_values,ierr,'npspinor',dt%npspinor,1,(/1/),iout)
1675    end if
1676 
1677 !  npimage
1678 
1679 !  npvel (must be positive)
1680    call chkint_ge(0,0,cond_string,cond_values,ierr,'npvel',dt%npvel,0,iout)
1681 
1682 !  npwkss
1683 !  Must be greater or equal to -1
1684    call chkint_ge(0,0,cond_string,cond_values,ierr,'npwkss',dt%npwkss,-1,iout)
1685 
1686 !  np_slk
1687    call chkint_ge(0,0,cond_string,cond_values,ierr,'np_slk',dt%np_slk,0,iout)
1688    if (dt%np_slk>0) then
1689      if(dt%np_slk <= dt%npfft*dt%npband*dt%npspinor .and. MOD(dt%npfft*dt%npband*dt%npspinor, dt%np_slk) /= 0) then
1690        MSG_ERROR_NOSTOP('np_slk must divide npfft*npband*npspinor.',ierr)
1691      end if
1692    end if
1693 
1694 !  nqpt
1695    call chkint_eq(0,0,cond_string,cond_values,ierr,'nqpt',dt%nqpt,2,(/0,1/),iout)
1696 
1697 !  nscforder
1698    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)
1699 
1700 !  nspden
1701    call chkint_eq(0,0,cond_string,cond_values,ierr,'nspden',nspden,3,(/1,2,4/),iout)
1702 
1703    if(nsppol==2)then  !  When nsppol=2, nspden must be 2
1704      cond_string(1)='nsppol' ; cond_values(1)=2
1705      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspden',nspden,1,(/2/),iout)
1706    end if
1707    if(nspden==2 .and. nsppol==1 .and. response==1)then
1708      write(message,'(13a)')&
1709 &     'nspden==2 together with nsppol==1 is not allowed',ch10,&
1710 &     'for response function calculations.',ch10,&
1711 &     'For antiferromagnetic materials, use nspden==2 and nsppol=2.',ch10,&
1712 &     'In this case, Shubnikov symmetries will be used to decrease',ch10,&
1713 &     'the number of perturbations. In a future version, it will also be',ch10,&
1714 &     'used to decrease the number of spin components (to be coded).',ch10,&
1715 &     'Action: change nsppol to 1, or check nspden.'
1716      MSG_ERROR_NOSTOP(message,ierr)
1717    end if
1718    if(nspden==4.and.response==1)then
1719      write(message,'(3a)')&
1720 &     'nspden==4 allowed in response formalism.',ch10,&
1721 &     'BUT Non collinear magnetism under development in perturbative treatment.'
1722      MSG_WARNING(message)
1723    end if
1724 !  TR symmetry not allowed for NC magnetism, in the present version
1725 !  (to be investigated further)
1726    if (nspden==4.and.(dt%kptopt==1.or.dt%kptopt==2)) then
1727      write(message, '(8a)' ) ch10,&
1728 &     'When non-collinear magnetism is activated (nspden=4),',ch10,&
1729 &     'time-reversal symmetry cannot be used in the present',ch10,&
1730 &     'state of the code (to be checked and validated).',ch10,&
1731 &     'Action: choose kptopt different from 1 or 2.'
1732      MSG_ERROR_NOSTOP(message, ierr)
1733    end if
1734 !  When densfor_pred<0 or 3, nspden must be 1 or 2
1735    if(dt%densfor_pred<0.or.dt%densfor_pred==3)then
1736      cond_string(1)='densfor_pred' ; cond_values(1)=dt%densfor_pred
1737      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspden',nspden,2,(/1,2/),iout)
1738    end if
1739 !  When ionmov=4 and iscf>10, nspden must be 1 or 2
1740    if(dt%ionmov==4.and.dt%iscf>10)then
1741      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
1742      cond_string(1)='iscf' ; cond_values(1)=dt%iscf
1743      call chkint_eq(1,2,cond_string,cond_values,ierr,'nspden',nspden,2,(/1,2/),iout)
1744    end if
1745 !  When iprcel>49, nspden must be 1 or 2
1746    if(mod(dt%iprcel,100)>49)then
1747      cond_string(1)='iprcel' ; cond_values(1)=dt%iprcel
1748      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspden',nspden,2,(/1,2/),iout)
1749    end if
1750    if(mgga==1.and.nspden==4)then
1751      write(message, '(3a)' )&
1752 &     'The meta-GGA XC kernel is not yet implemented for non-colinear magnetism case',ch10, &
1753 &     'Please use "nspden=1 or 2".'
1754      MSG_ERROR(message)
1755    end if
1756 
1757 !  nspinor
1758    call chkint_eq(0,0,cond_string,cond_values,ierr,'nspinor',nspinor,2,(/1,2/),iout)
1759    if(nspden==2)then !  When nspden=2, nspinor must be 1
1760      cond_string(1)='nspden' ; cond_values(1)=2
1761      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/1/),iout)
1762    end if
1763 
1764    if(nspden==4)then  !  When nspden=4, nspinor must be 2
1765      cond_string(1)='nspden' ; cond_values(1)=4
1766      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/2/),iout)
1767    end if
1768 !  When iscf=-1, nspinor must be 1
1769    if(dt%iscf==-1)then
1770      cond_string(1)='iscf' ; cond_values(1)=-1
1771 !    Make sure that nsppol is 1
1772      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/1/),iout)
1773    end if
1774 !  spin-orbit is not implemented for the strain perturbation
1775    if(dt%rfstrs/=0)then
1776      cond_string(1)='rfstrs' ; cond_values(1)=dt%rfstrs
1777      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/1/),iout)
1778    end if
1779 !  When usepawu=2, nspinor must be 1
1780    if(dt%usepawu==2)then
1781      cond_string(1)='usepawu' ; cond_values(1)=2
1782 !    Make sure that nspinor is 1
1783      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',nspinor,1,(/1/),iout)
1784    end if
1785 
1786 !  nsppol
1787    call chkint_eq(0,0,cond_string,cond_values,ierr,'nsppol',nsppol,2,(/1,2/),iout)
1788 
1789 !  nsym
1790    call chkint_ge(0,0,cond_string,cond_values,ierr,'nsym',dt%nsym,1,iout)
1791 !  check if nsym=1 in phonon calculation in finite electric field
1792    if (response==1.and.&
1793 &   (dt%berryopt== 4.or.dt%berryopt== 6.or.dt%berryopt== 7.or.&
1794 &   dt%berryopt==14.or.dt%berryopt==16.or.dt%berryopt==17)) then
1795      cond_string(1)='response' ; cond_values(1)=1
1796      cond_string(2)='berryopt' ; cond_values(2)=4
1797      call chkint_eq(1,2,cond_string,cond_values,ierr,'nsym',dt%nsym,1,(/1/),iout)
1798    end if
1799 
1800 !  ntime
1801    call chkint_ge(0,0,cond_string,cond_values,ierr,'ntime',dt%ntime,0,iout)
1802 
1803 !  ntimimage
1804    call chkint_ge(0,0,cond_string,cond_values,ierr,'ntimimage',dt%ntimimage,1,iout)
1805 
1806 !  ntypalch
1807    if (usepaw==1) then
1808      cond_string(1)='pspcod' ; cond_values(1)=7;cond_values(2)=17
1809      call chkint_eq(1,2,cond_string,cond_values,ierr,'ntypalch',dt%ntypalch,1,(/0/),iout)
1810    end if
1811 
1812 !  nucdipmom
1813 
1814    if (any(abs(dt%nucdipmom)>0)) then
1815 
1816 !    nucdipmom requires PAW
1817      if(usepaw/=1)then
1818        write(message, '(3a)' )&
1819 &       ' Nuclear dipole moments (variable nucdipmom) input as nonzero but PAW not activated => stop',ch10,&
1820 &       'Action: re-run with PAW '
1821        MSG_ERROR_NOSTOP(message,ierr)
1822      end if
1823 
1824 !    nucdipmom requires complex rhoij
1825      if(dt%pawcpxocc/=2)then
1826        write(message, '(3a)' )&
1827 &       ' Nuclear dipole moments (variable nucdipmom) require complex rhoij => stop',ch10,&
1828 &       'Action: re-run with pawcpxocc = 2 '
1829        MSG_ERROR_NOSTOP(message,ierr)
1830      end if
1831 
1832 !    nucdipmom requires no force or stress calculation
1833      if(dt%optforces/=0 .OR. dt%optstress/=0)then
1834        write(message, '(3a)' )&
1835 &       ' Nuclear dipole moments (variable nucdipmom) cannot be used with force or stress calculations => stop',ch10,&
1836 &       'Action: re-run with optforces = 0 and optstress = 0 '
1837        MSG_ERROR_NOSTOP(message,ierr)
1838      end if
1839 
1840 !    nucdipmom requires kptopt > 2
1841      if(dt%kptopt<=2) then
1842        write(message, '(a,i4,a,a,a)' )&
1843 &       ' Nuclear dipole moments (variable nucdipmom) break time reveral symmetry but kptopt = ',dt%kptopt,&
1844 &       ' => stop ',ch10,&
1845 &       'Action: re-run with kptopt greater than 2 '
1846        MSG_ERROR_NOSTOP(message,ierr)
1847      end if
1848 
1849    end if
1850 
1851 !  nzchempot
1852    call chkint_ge(0,0,cond_string,cond_values,ierr,'nzchempot',dt%nzchempot,0,iout)
1853 !  Cannot be used with response functions at present
1854    if (response==1) then
1855      cond_string(1)='response' ; cond_values(1)=1
1856      call chkint_eq(1,1,cond_string,cond_values,ierr,'nzchempot',dt%nzchempot,1,(/0/),iout)
1857    end if
1858    if(dt%nzchempot>0)then
1859      do itypat=1,dt%ntypat
1860        do iz=2,dt%nzchempot
1861          dz=dt%chempot(1,iz,itypat)-dt%chempot(1,iz-1,itypat)
1862          if(dz<-tol12)then
1863            write(message, '(a,2i6,a,a,d17.10,a,a, a,d17.10,a,a, a,a,a)' )&
1864 &           ' For izchempot,itypat=',iz,itypat,ch10,&
1865 &           ' chempot(1,izchempot-1,itypat) = ',dt%chempot(1,iz-1,itypat),' and', ch10,&
1866 &           ' chempot(1,izchempot  ,itypat) = ',dt%chempot(1,iz  ,itypat),',',ch10,&
1867 &           ' while they should be ordered in increasing values =>stop',ch10,&
1868 &           'Action: correct chempot(1,*,itypat) in input file.'
1869            MSG_ERROR_NOSTOP(message,ierr)
1870          end if
1871        end do
1872        dz=dt%chempot(1,dt%nzchempot,itypat)-dt%chempot(1,1,itypat)
1873        if(dz>one)then
1874          write(message, '(a,2i6,a,a,d17.10,a,a, a,d17.10,a,a, a,a,a)' )&
1875 &         ' For nzchempot,itypat=',dt%nzchempot,itypat,ch10,&
1876 &         ' chempot(1,1,itypat) = ',dt%chempot(1,1,itypat),' and', ch10,&
1877 &         ' chempot(1,nzchempot  ,itypat) = ',dt%chempot(1,dt%nzchempot,itypat),'.',ch10,&
1878 &         ' However, the latter should, at most, be one more than the former =>stop',ch10,&
1879 &         'Action: correct chempot(1,nzchempot,itypat) in input file.'
1880          MSG_ERROR_NOSTOP(message,ierr)
1881        end if
1882      end do
1883    end if
1884 
1885 !  occ
1886 !  Do following tests only for occopt==0 or 2, when occupation numbers are needed
1887    if ((dt%iscf>0.or.dt%iscf==-1.or.dt%iscf==-3) .and. (dt%occopt==0 .or. dt%occopt==2) ) then
1888 !    make sure occupation numbers (occ(n)) were defined:
1889      sumocc=zero
1890      bantot=0
1891      do isppol=1,nsppol
1892        do ikpt=1,nkpt
1893          do iband=1,dt%nband(ikpt+(isppol-1)*nkpt)
1894            bantot=bantot+1
1895            sumocc=sumocc+dt%occ_orig(bantot)
1896            if (dt%occ_orig(bantot)<zero) then
1897              write(message, '(a,2i6,a,e20.10,a,a,a)' )&
1898 &             'iband,ikpt=',iband,ikpt,' has negative occ=',dt%occ_orig(bantot),' =>stop',ch10,&
1899 &             'Action: correct this occupation number in input file.'
1900              MSG_ERROR_NOSTOP(message,ierr)
1901            end if
1902          end do
1903        end do
1904      end do
1905      if (sumocc<=1.0d-8) then
1906        write(message, '(a,1p,e20.10,a,a,a)')&
1907 &       'Sum of occ=',sumocc, ' =>occ not defined => stop',ch10,&
1908 &       'Action: correct the array occ in input file.'
1909        MSG_ERROR_NOSTOP(message, ierr)
1910      end if
1911    end if
1912 
1913 !  occopt
1914    call chkint_eq(0,0,cond_string,cond_values,ierr,'occopt',dt%occopt,9,(/0,1,2,3,4,5,6,7,8/),iout)
1915 !  When prtdos==1 or 4, occopt must be between 3 and 8
1916    if(dt%prtdos==1.or.dt%prtdos==4)then
1917      write(cond_string(1), "(A)") 'prtdos'
1918      cond_values(1)=dt%prtdos
1919 !    Make sure that occopt is 3,4,5,6,7, or 8
1920      call chkint_eq(1,1,cond_string,cond_values,ierr,'occopt',dt%occopt,6,(/3,4,5,6,7,8/),iout)
1921    end if
1922 !  When nsppol==2 and spinmagntarget is the default value (-99.99d0), occopt cannot be 1.
1923    if(nsppol==2.and.dt%occopt==1.and.abs(dt%spinmagntarget+99.99d0)<tol8)then
1924      if(natom/=1 .or. abs(dt%znucl(dt%typat(1))-one)>tol8)then
1925        write(message,'(a,i3,2a,i3,4a,f7.2,7a)' )&
1926 &       'This is a calculation with spin-up and spin-down wavefunctions,         ... nsppol=',nsppol,ch10,&
1927 &       'in which the occupation numbers are to be determined automatically.     ... occopt=',dt%occopt,ch10,&
1928 &       'However, in this case, the target total spin magnetization',ch10,&
1929 &       'must be specified, while the default value is observed.                 ... spinmagntarget=',dt%spinmagntarget,ch10,&
1930 &       'Action: if you are doing an antiferromagnetic calculation, please use nsppol=1 with nspden=2 ;',ch10,&
1931 &       'on the other hand, if you are doing a ferromagnetic calculation, either specify your own spinmagntarget,',ch10,&
1932 &       'or let the code determine the total spin-polarization, by using a metallic value for occopt (e.g. 7 or 4 ...).'
1933        MSG_ERROR_NOSTOP(message, ierr)
1934      end if
1935    end if
1936 
1937 !  optcell
1938    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)
1939 !  With dt%berryopt=4, one must have optcell==0
1940 !  if(dt%berryopt==4)then
1941 !  cond_string(1)='berryopt' ; cond_values(1)=dt%berryopt
1942 !  call chkint_eq(1,1,cond_string,cond_values,ierr,'optcell',dt%optcell,1,(/0/),iout)
1943 !  end if
1944 
1945 !  optdriver
1946    call chkint_eq(0,0,cond_string,cond_values,ierr,'optdriver',optdriver,9,&
1947 &   [RUNL_GSTATE,RUNL_RESPFN,RUNL_SCREENING,RUNL_SIGMA,RUNL_NONLINEAR,RUNL_BSE, RUNL_GWLS, RUNL_WFK,RUNL_EPH],iout)
1948    if (response==1.and.dt%optdriver/=1) then
1949      write(message,'(a,i3,3a,7(a,i3),4a)' )&
1950 &     'The input variable optdriver=',dt%optdriver,ch10,&
1951 &     'This is in conflict with the values of the other input variables,',ch10,&
1952 &     'rfphon=',dt%rfphon,'  rfddk=',dt%rfddk,'  rf2_dkdk=',dt%rf2_dkdk,'  rf2_dkde=',dt%rf2_dkde,&
1953 &     '  rfelfd=',dt%rfelfd,'  rfmagn=',dt%rfelfd,'rfstrs=',dt%rfstrs,'  rfuser=',dt%rfuser,ch10,&
1954 &     'Action: check the values of optdriver, rfphon, rfddk, rf2dkdk, rf2dkde, rfelfd, rfmagn, rfstrs',ch10,&
1955 &     'and rfuser in your input file.'
1956      MSG_ERROR_NOSTOP(message, ierr)
1957    end if
1958    if(usepaw==1)then
1959      ! Is optdriver compatible with PAW?
1960      cond_string(1)='usepaw' ; cond_values(1)=usepaw
1961      call chkint_eq(1,1,cond_string,cond_values,ierr,&
1962 &     'optdriver',optdriver,6,[RUNL_GSTATE,RUNL_RESPFN,RUNL_SCREENING,RUNL_SIGMA,RUNL_BSE, RUNL_WFK],iout)
1963    end if
1964 
1965 !  Linear and Non-linear response calculations
1966    if(nspinor/=1)then
1967      cond_string(1)='nspinor' ; cond_values(1)=nspinor
1968      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_NONLINEAR/),iout)
1969    end if
1970    if(dt%occopt/=1 .and. dt%occopt/=2)then
1971      cond_string(1)='occopt' ; cond_values(1)=dt%occopt
1972      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_NONLINEAR/),iout)
1973    end if
1974    if(dt%mkmem==0)then
1975      cond_string(1)='mkmem' ; cond_values(1)=dt%mkmem
1976      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_NONLINEAR/),iout)
1977    end if
1978    if(dt%kptopt==1 .or. dt%kptopt==4) then
1979      cond_string(1)='kptopt' ; cond_values(1)=dt%kptopt
1980      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,2,(/RUNL_RESPFN,RUNL_NONLINEAR/),iout)
1981    end if
1982    allow=(dt%ixc > 0).and.(dt%ixc /= 3).and.(dt%ixc /= 7).and.(dt%ixc /= 8)
1983    if(.not.allow)then
1984      allow=(dt%ixc < 0).and.(libxc_functionals_isgga().or.libxc_functionals_ismgga())
1985    end if
1986    if(allow)then
1987      cond_string(1)='ixc' ; cond_values(1)=dt%ixc
1988      call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',dt%optdriver,1,(/RUNL_NONLINEAR/),iout)
1989    end if
1990 
1991 !  optforces
1992 !  When ionmov>0, optforces must be >0
1993    if(dt%ionmov>0)then
1994      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
1995      call chkint_eq(1,1,cond_string,cond_values,ierr,'optforces',dt%optforces,2,(/1,2/),iout)
1996    end if
1997 !  When imgmov>0, optforces must be >0
1998    if(dt%imgmov>0)then
1999      cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
2000      call chkint_eq(1,1,cond_string,cond_values,ierr,'optforces',dt%optforces,2,(/1,2/),iout)
2001    end if
2002 !  When iscf=22, optforces must be 0 or 2
2003    if(dt%iscf==22)then
2004      cond_string(1)='iscf' ; cond_values(1)=dt%iscf
2005      call chkint_eq(1,1,cond_string,cond_values,ierr,'optforces',dt%optforces,2,(/0,2/),iout)
2006    end if
2007 
2008 !  optstress
2009 !  When optcell>0, optstress must be >0
2010    if(dt%optcell>0)then
2011      cond_string(1)='optcell' ; cond_values(1)=dt%optcell
2012      call chkint_eq(1,1,cond_string,cond_values,ierr,'optstress',dt%optstress,1,(/1/),iout)
2013    end if
2014 
2015   !  orbmag
2016   ! only values of 0 (default) and 1 are allowed
2017    call chkint_eq(0,0,cond_string,cond_values,ierr,'orbmag',dt%orbmag,2,(/0,1/),iout)
2018   ! when orbmag /= 0, symmorphi must be 0 (no tnons)
2019    if(dt%orbmag .NE. 0) then
2020      cond_string(1)='orbmag';cond_values(1)=dt%orbmag
2021      call chkint_eq(1,1,cond_string,cond_values,ierr,'symmorphi',dt%symmorphi,1,(/0/),iout)
2022    end if
2023   ! only kptopt 4 and 3 are allowed
2024    if(dt%orbmag .NE. 0) then
2025      cond_string(1)='orbmag';cond_values(1)=dt%orbmag
2026      call chkint_eq(1,1,cond_string,cond_values,ierr,'kptopt',dt%kptopt,2,(/3,4/),iout)
2027    end if
2028   ! only nproc 1 for now
2029    if(dt%orbmag .NE. 0) then
2030      cond_string(1)='orbmag';cond_values(1)=dt%orbmag
2031      call chkint_eq(1,1,cond_string,cond_values,ierr,'nproc',nproc,1,(/1/),iout)
2032    end if
2033 
2034 
2035 !  paral_atom
2036    call chkint_eq(0,0,cond_string,cond_values,ierr,'paral_atom',dt%paral_atom,2,(/0,1/),iout)
2037    if (dt%paral_atom/=0) then
2038      if (dt%optdriver/=RUNL_GSTATE.and.dt%optdriver/=RUNL_RESPFN) then
2039        write(message, '(5a)' )&
2040 &       'Parallelisation over atoms is only compatible with',ch10,&
2041 &       'ground-state or response function calculations !',ch10,&
2042 &       'Action: change paral_atom in input file.'
2043        MSG_ERROR_NOSTOP(message, ierr)
2044      end if
2045      if (dt%usedmft==1) then
2046        cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
2047        call chkint_eq(1,1,cond_string,cond_values,ierr,'paral_atom',dt%paral_atom,1,(/0/),iout)
2048      end if
2049      if (dt%prtden>1.and.dt%paral_kgb==0) then
2050        cond_string(1)='paral_kgb' ; cond_values(1)=dt%paral_kgb
2051        cond_string(2)='prtden' ; cond_values(2)=dt%prtden-1
2052        call chkint_eq(1,2,cond_string,cond_values,ierr,'paral_atom',dt%paral_atom,1,(/0/),iout)
2053      end if
2054    end if
2055 
2056 !  paral_kgb
2057    call chkint_eq(0,0,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,2,(/0,1/),iout)
2058 !  Warning
2059    if(dt%paral_kgb==1.and.dt%iomode/=IO_MODE_MPI) then
2060      write(message,'(11a)' )&
2061 &     'When k-points/bands/FFT parallelism is activated',ch10,&
2062 &     '(paral_kgb=1), only MPI-IO input/output is allowed !',ch10,&
2063 &     'iomode/=1 in your input file',ch10,&
2064 &     'You will not be able to perform input/output !'
2065      MSG_WARNING(message)
2066    end if
2067    if(dt%paral_kgb==1.and.dt%nstep==0) then
2068      message='When k-points/bands/FFT parallelism is activated, nstep=0 is not allowed!'
2069      MSG_ERROR_NOSTOP(message,ierr)
2070    end if
2071    if(dt%paral_kgb==1.and.dt%usefock>0) then
2072      message='Hartree-Fock or Hybrid Functionals are not compatible with bands/FFT parallelism!'
2073      MSG_ERROR_NOSTOP(message,ierr)
2074    end if
2075 
2076 !  paral_rf
2077    if ((response==0).and.(dt%paral_rf/=0)) then
2078      write(message,'(a,i3,3a,7(i3,a),4a)' )&
2079 &     'The input variable paral_rf=',dt%paral_rf,ch10,&
2080 &     'This is in conflict with the values of the other input variables,',ch10,&
2081 &     'rfphon=',dt%rfphon,'  rfddk=',dt%rfddk,'  rf2_dkdk=',dt%rf2_dkdk,'  rf2_dkde=',dt%rf2_dkde,&
2082 &     '  rfelfd=',dt%rfelfd,'  rfmagn=',dt%rfmagn,'rfstrs=',dt%rfstrs,'  rfuser=',dt%rfuser,ch10,&
2083 &     'Action: check the values of paral_rf, rfphon, rfddk, rf2dkdk, rf2dkde, rfelfd, rfmagn, rfstrs',ch10,&
2084 &     '        and rfuser in your input file.'
2085      MSG_ERROR_NOSTOP(message, ierr)
2086    end if
2087 
2088 !  pawcpxocc
2089    if (usepaw==1) then
2090      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawcpxocc',dt%pawcpxocc,2,(/1,2/),iout)
2091      if (dt%usepawu>=1.and.nspinor==2.and.dt%pawcpxocc==1) then
2092        write(message, '(5a)' )&
2093 &       'When non-collinear magnetism is activated ,',ch10,&
2094 &       'and LDA+U activated ',ch10,&
2095 &       'PAW occupancies must be complex !'
2096        MSG_ERROR_NOSTOP(message, ierr)
2097      else if (dt%pawspnorb==1.and.(dt%kptopt==0.or.dt%kptopt>=3).and.dt%pawcpxocc==1) then
2098        if (optdriver==RUNL_GSTATE.and.dt%iscf<10) then
2099          write(message, '(11a)' )&
2100 &         'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2101 &         'and time-reversal symmetry is broken (kptopt/=1 and kptopt/=2)',ch10,&
2102 &         'PAW occupancies are complex !',ch10,&
2103 &         'Their imaginary part is used to evaluate total energy by direct',ch10,&
2104 &         'scheme, needed here because SCF potential mixing has been chosen (iscf<10).',ch10,&
2105 &         'Action: put pawcpxocc=2 in input file, or choose SCF density mixing (iscf>=10).'
2106          MSG_ERROR_NOSTOP(message, ierr)
2107        else if (optdriver==RUNL_GSTATE.and.dt%iscf>=10) then
2108          write(message, '(11a)' )&
2109 &         'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2110 &         'and time-reversal symmetry is broken (kptopt/=1 and kptopt/=2)',ch10,&
2111 &         'PAW occupancies are complex !',ch10,&
2112 &         'By setting pawcpxocc=1 in input file, their imaginary part',ch10,&
2113 &         'is not computed. As a consequence, total energy computed',ch10,&
2114 &         'is not available. Put pawcpxocc=2 in input file if you want it.'
2115          MSG_WARNING(message)
2116        else
2117          write(message, '(11a)' )&
2118 &         'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2119 &         'and time-reversal symmetry is broken (kptopt/=1 and kptopt/=2)',ch10,&
2120 &         'PAW occupancies are complex !',ch10,&
2121 &         'Action: put pawcpxocc=2 in input file to compute their imaginary part.'
2122          MSG_ERROR_NOSTOP(message, ierr)
2123        end if
2124      end if
2125      if (dt%pawspnorb==1.and.dt%kptopt==0) then
2126        write(message, '(7a)' )&
2127 &       'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2128 &       'time-reversal symmetry might be broken.',ch10,&
2129 &       'Using kptopt=0 might be risky: if (kx,ky,kz) is present in k-points list,',ch10,&
2130 &       '(-kx,-ky,-kz) (or equivalent) should also be present.'
2131        MSG_WARNING(message)
2132      end if
2133    end if
2134 
2135 !  pawcross
2136    if (usepaw==1) then
2137      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawcross',dt%pawcross,2,(/0,1/),iout)
2138    end if
2139 
2140 !  pawfatbnd
2141    call chkint_eq(0,0,cond_string,cond_values,ierr,'pawfatbnd',dt%pawfatbnd,3,(/0,1,2/),iout)
2142    if(usepaw/=1.and.dt%pawfatbnd>1) then
2143      message = 'pawfatbnd without PAW is not possible'
2144      MSG_ERROR_NOSTOP(message,ierr)
2145    end if
2146    if(dt%prtdosm==1.and.dt%pawfatbnd>0)then
2147      message = 'pawfatbnd>0  and prtdosm=1 are not compatible '
2148      MSG_ERROR_NOSTOP(message,ierr)
2149    end if
2150 !  for the moment pawfatbnd is not compatible with fft or band parallelization
2151    !if (dt%pawfatbnd > 0 .and. (dt%npfft > 1 .or. dt%npband > 1)) then
2152    !  message = 'pawfatbnd and FFT or band parallelization are not compatible yet. Set pawfatbnd to 0  '
2153    !  MSG_ERROR_NOSTOP(message,ierr)
2154    !end if
2155 
2156 !  pawlcutd
2157    if (usepaw==1) then
2158      call chkint_ge(0,0,cond_string,cond_values,ierr,'pawlcutd',dt%pawlcutd,0,iout)
2159    end if
2160 
2161 !  pawlmix
2162    if (usepaw==1) then
2163      call chkint_ge(0,0,cond_string,cond_values,ierr,'pawlmix',dt%pawlmix,0,iout)
2164    end if
2165 
2166 !  pawmixdg
2167    if (usepaw==1) then
2168      if(dt%ionmov==4)then
2169        cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
2170        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawmixdg',dt%pawmixdg,1,(/1/),iout)
2171      end if
2172      if(dt%iscf==5.or.dt%iscf==6.or.dt%iscf==15.or.dt%iscf==16)then
2173        cond_string(1)='iscf' ; cond_values(1)=dt%iscf
2174        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawmixdg',dt%pawmixdg,1,(/1/),iout)
2175      end if
2176      if(usewvl==1)then
2177        cond_string(1)='usewvl' ; cond_values(1)=1
2178        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawmixdg',dt%pawmixdg,1,(/1/),iout)
2179      end if
2180    end if
2181 
2182 !  pawnhatxc
2183    if (usepaw==1) then
2184      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawnhatxc',dt%pawnhatxc,2,(/0,1/),iout)
2185    end if
2186 
2187 !  pawnzlm
2188    if (usepaw==1) then
2189      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawnzlm',dt%pawnzlm,2,(/0,1/),iout)
2190    end if
2191 
2192 !  pawoptmix
2193    if (usepaw==1) then
2194      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawoptmix',dt%pawoptmix,2,(/0,1/),iout)
2195    end if
2196 
2197 !  pawprtdos
2198    if (usepaw==1) then
2199      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawprtdos',dt%pawprtdos,3,(/0,1,2/),iout)
2200    end if
2201 
2202 !  pawprtvol
2203    if (usepaw==1) then
2204      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawprtvol',dt%pawprtvol,7,(/-3,-2,-1,0,1,2,3/),iout)
2205    end if
2206 
2207 !  pawspnorb
2208    if (usepaw==1) then
2209      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawspnorb',dt%pawspnorb,2,(/0,1/),iout)
2210      if (dt%pawspnorb==1.and.(dt%kptopt==1.or.dt%kptopt==2)) then
2211        write(message, '(7a)' )&
2212 &       'When spin-orbit coupling is activated (pawspnorb=1),',ch10,&
2213 &       'time-reversal symmetry is broken; k-points cannot',ch10,&
2214 &       'be generated using TR-symmetry.',ch10,&
2215 &       'Action: choose kptopt different from 1 or 2.'
2216        MSG_ERROR_NOSTOP(message, ierr)
2217      end if
2218    end if
2219 
2220 !  pawstgylm, pawsushat
2221    if (usepaw==1) then
2222      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawstgylm',dt%pawstgylm,2,(/0,1/),iout)
2223      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawsushat',dt%pawstgylm,2,(/0,1/),iout)
2224    end if
2225 
2226 !  pawusecp
2227    if (usepaw==1) then
2228      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawusecp',dt%pawusecp,2,(/0,1/),iout)
2229 !      if (dt%mkmem/=0)then
2230 !        cond_string(1)='mkmem' ; cond_values(1)=dt%mkmem
2231 !        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawusecp',dt%pawusecp,1,(/1/),iout)
2232 !      end if
2233 !      if (dt%mk1mem/=0)then
2234 !        cond_string(1)='mk1mem' ; cond_values(1)=dt%mk1mem
2235 !        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawusecp',dt%pawusecp,1,(/1/),iout)
2236 !      end if
2237 !      if (dt%mkqmem/=0)then
2238 !        cond_string(1)='mkqmem' ; cond_values(1)=dt%mkqmem
2239 !        call chkint_eq(1,1,cond_string,cond_values,ierr,'pawusecp',dt%pawusecp,1,(/1/),iout)
2240 !      end if
2241    end if
2242 
2243 !  pawxcdev
2244    if (usepaw==1) then
2245      call chkint_eq(0,0,cond_string,cond_values,ierr,'pawxcdev',dt%pawxcdev,3,(/0,1,2/),iout)
2246    end if
2247 
2248 !  pimass
2249 !  Check that masses are > 0 if imgmov = 9 or 13
2250    if (dt%imgmov==9.or.dt%imgmov==13) then
2251      do itypat=1,dt%ntypat
2252        cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
2253        write(input_name,'(a4,i1,a1)')'pimass(',itypat,')'
2254        call chkdpr(1,1,cond_string,cond_values,ierr,input_name,dt%pimass(itypat),1,tol8,iout)
2255      end do
2256    end if
2257 
2258 !  pimd_constraint
2259    call chkint_eq(0,0,cond_string,cond_values,ierr,'pimd_constraint',dt%pimd_constraint,2,(/0,1/),iout)
2260    if(dt%pimd_constraint==1.and.dt%nconeq>1 )then
2261      cond_string(1)='pimd_constraint' ; cond_values(1)=dt%pimd_constraint
2262 !    Make sure that nconeq=1
2263      call chkint_eq(1,1,cond_string,cond_values,ierr,'nconeq',dt%nconeq,1,(/1/),iout)
2264    end if
2265 
2266 !  pitransform
2267    call chkint_eq(0,0,cond_string,cond_values,ierr,'pitransform',dt%pitransform,3,(/0,1,2/),iout)
2268 !  When imgmov is not one of 9 or 13, pitransform must be 0
2269    if(dt%imgmov/=9 .and. dt%imgmov/=13 )then
2270      cond_string(1)='imgmov' ; cond_values(1)=dt%imgmov
2271 !    Make sure that pitransform=0
2272      call chkint_eq(1,1,cond_string,cond_values,ierr,'pitransform',dt%pitransform,1,(/0/),iout)
2273    end if
2274    if(dt%pimd_constraint/=0 )then
2275      cond_string(1)='pimd_constraint' ; cond_values(1)=dt%pimd_constraint
2276 !    Make sure that pitransform=0
2277      call chkint_eq(1,1,cond_string,cond_values,ierr,'pitransform',dt%pitransform,1,(/0/),iout)
2278    end if
2279 
2280 !  plowan_compute
2281    cond_string(1)='usepaw' ; cond_values(1)=1
2282    call chkint_eq(1,1,cond_string,cond_values,ierr,'plowan_compute',dt%plowan_compute,3,(/0,1,2/),iout)
2283    if(dt%plowan_compute>0) then
2284 !    plowan_bandi/plowan_bandf
2285      call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_bandi',dt%plowan_bandi,              1,iout)
2286      call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_bandf',dt%plowan_bandf,dt%plowan_bandi,iout)
2287 
2288      call chkint_le(0,0,cond_string,cond_values,ierr,'plowan_bandi',dt%plowan_bandi,dt%plowan_bandf,iout)
2289      call chkint_le(0,0,cond_string,cond_values,ierr,'plowan_bandi',dt%plowan_bandf,dt%mband       ,iout)
2290 
2291      call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_natom',dt%plowan_natom,              0,iout)
2292 
2293      maxplowan_iatom=maxval(dt%plowan_iatom(1:dt%plowan_natom))
2294      minplowan_iatom=minval(dt%plowan_iatom(1:dt%plowan_natom))
2295      call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_iatom',minplowan_iatom,              1,iout)
2296      call chkint_le(0,0,cond_string,cond_values,ierr,'plowan_iatom',maxplowan_iatom,          natom,iout)
2297 
2298      kk=0
2299      do jj = 1, dt%plowan_natom
2300        do ii = 1, dt%plowan_nbl(jj)
2301          kk=kk+1
2302          cond_string(1)='usepaw' ; cond_values(1)=1
2303          call chkint_eq(1,1,cond_string,cond_values,ierr,'plowan_lcalc',dt%plowan_lcalc(kk),4,(/0,1,2,3/),iout)
2304        end do
2305      end do
2306 
2307      call chkint_ge(0,0,cond_string,cond_values,ierr,'plowan_nt'   ,dt%plowan_nt,                 0,iout)
2308      cond_string(1)='usepaw' ; cond_values(1)=1
2309      call chkint_eq(1,1,cond_string,cond_values,ierr,'plowan_realspace',dt%plowan_realspace,3,(/0,1,2/),iout)
2310    end if
2311 
2312 !  posdoppler
2313    call chkint_eq(0,0,cond_string,cond_values,ierr,'posdoppler',dt%posdoppler,2,(/0,1/),iout)
2314 
2315 !  positron
2316    call chkint_eq(0,0,cond_string,cond_values,ierr,'positron',dt%positron,7,(/-20,-10,-2,-1,0,1,2/),iout)
2317    if ((dt%positron==2.or.dt%positron<0).and.(dt%ixcpositron==3.or.dt%ixcpositron==31)) then
2318      if ((dt%ixc<11.or.dt%ixc>17).and.dt%ixc/=23.and.dt%ixc/=26.and.dt%ixc/=27) then
2319        write(message, '(7a)' )&
2320 &       'For the electronic ground-state calculation in presence of a positron,',ch10,&
2321 &       'when GGA is selected for electron-positron correlation (ixcpositron=3 or 31),',ch10,&
2322 &       'electron-electron XC must also be GGA !',ch10,&
2323 &       'Action: choose another psp file.'
2324        MSG_ERROR_NOSTOP(message, ierr)
2325      end if
2326    end if
2327    if (dt%positron/=0.and.dt%ionmov==5) then
2328      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
2329      call chkint_eq(1,1,cond_string,cond_values,ierr,'positron',dt%positron,1,(/0/),iout)
2330    end if
2331    if (dt%positron<0.and.usepaw==0) then
2332      write(message, '(5a)' )&
2333 &     'You cannot use positron<0 (automatic two-component DFT)',ch10,&
2334 &     'with norm-conserving pseudopotentials !',ch10,&
2335 &     'Action: choose PAW.'
2336      MSG_ERROR_NOSTOP(message, ierr)
2337    end if
2338    if ((dt%positron==1.or.dt%positron<0).and.dt%iscf<10.and.dt%tolvrs>tiny(one)) then
2339      write(message, '(7a)' )&
2340 &     'You cannot perform a positronic ground-state calculation (positron=1 or <0)',ch10,&
2341 &     'using SCF potential mixing (iscf<10) and tolvrs !',ch10,&
2342 &     '(in that case, the potential is constant)',ch10,&
2343 &     'Action: change iscf or select another convergence criterion.'
2344      MSG_ERROR_NOSTOP(message, ierr)
2345    end if
2346 
2347 !  posocc
2348    call chkdpr(0,0,cond_string,cond_values,ierr,'posocc',dt%posocc,-1,one,iout)
2349 
2350 !  postoldfe, postoldff
2351    call chkdpr(0,0,cond_string,cond_values,ierr,'postoldff',dt%postoldff,1,zero,iout)
2352    if (dt%positron<0) then
2353      if ( (abs(dt%postoldfe)> tiny(0.0_dp).and.abs(dt%postoldff)> tiny(0.0_dp)).or.&
2354 &     (abs(dt%postoldfe)<=tiny(0.0_dp).and.abs(dt%postoldff)<=tiny(0.0_dp))) then
2355        write(message,'(5a)' )&
2356 &       'One and only one of the input tolerance criteria postoldfe or postoldff',ch10,&
2357 &       'must differ from zero !',ch10,&
2358 &       'Action: change postoldfe or postldff in input file.'
2359        MSG_ERROR_NOSTOP(message, ierr)
2360      end if
2361      if (abs(dt%postoldff)>tiny(0.0_dp).and.dt%optforces/=1)then
2362        write(message,'(3a)' )&
2363 &       'When postoldff is set to a non-zero value, optforces must be set to 1 !',ch10,&
2364 &       'Action: change your input file.'
2365        MSG_ERROR_NOSTOP(message, ierr)
2366      end if
2367    end if
2368 
2369 !  prepanl
2370 !  Must have prtden=1 to prepare a nonlinear calculation
2371    if (dt%prtden /= 1) then
2372      cond_string(1)='prtden' ; cond_values(1)=dt%prtden
2373      call chkint_ne(1,1,cond_string,cond_values,ierr,'prepanl',dt%prepanl,1,(/1/),iout)
2374    end if
2375 
2376 !  prtbbb
2377 !  Not allowed for PAW
2378    if(usepaw==1.and.dt%prtbbb==1)then
2379      cond_string(1)='usepaw' ; cond_values(1)=usepaw
2380      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtbbb',dt%prtbbb,1,(/0/),iout)
2381    end if
2382 
2383 !  prtden
2384    if (usepaw==1) then
2385      call chkint_le(0,0,cond_string,cond_values,ierr,'prtden',dt%prtden,7,iout)
2386    else
2387      call chkint_le(0,0,cond_string,cond_values,ierr,'prtden',dt%prtden,1,iout)
2388    end if
2389 
2390 !  prtdensph
2391    if (usepaw==1) then
2392      call chkint_eq(0,0,cond_string,cond_values,ierr,'prtdensph',dt%prtdensph,2,(/0,1/),iout)
2393    end if
2394 
2395 !  prtdos
2396    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtdos',dt%prtdos,6,(/0,1,2,3,4,5/),iout)
2397 
2398 ! for the moment prtdos 3,4,5 are not compatible with fft or band parallelization
2399    if (dt%prtdos > 3 .and. (dt%npfft > 1 .or. dt%npband > 1)) then
2400      message = 'prtdos>3 and FFT or band parallelization are not compatible yet. Set prtdos <= 2'
2401      MSG_ERROR_NOSTOP(message, ierr)
2402    end if
2403 
2404 ! prtdos 5 only makes sense for nspinor == 2. Otherwise reset to prtdos 2
2405    if (dt%prtdos == 5 .and. dt%nspinor /= 2) then
2406      dt%prtdos = 2
2407      MSG_WARNING('prtdos==5 is only useful for nspinor 2. Has been reset to 2')
2408    end if
2409    if (dt%prtdos == 5 .and. dt%npspinor /= 1) then
2410      MSG_ERROR_NOSTOP('prtdos==5 not available with npspinor==2', ierr)
2411    end if
2412    ! Consistency check for prtdos 5 with PAW
2413    if (dt%prtdos == 5 .and. dt%usepaw == 1) then
2414      if (dt%pawprtdos == 2) then
2415        MSG_ERROR_NOSTOP('prtdos==5 is not compatible with pawprtdos 2', ierr)
2416      end if
2417      MSG_ERROR_NOSTOP('prtdos==5 is not available with PAW', ierr)
2418    end if
2419 
2420 !  prtdosm
2421    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtdosm',dt%prtdosm,3,(/0,1,2/),iout)
2422    if(usepaw==1.and.dt%pawprtdos==1)then
2423      cond_string(1)='pawprtdos' ; cond_values(1)=dt%pawprtdos
2424      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtdosm',dt%prtdosm,1,(/0/),iout)
2425    end if
2426    if(usepaw==1.and.dt%prtdosm>=1)then
2427      cond_string(1)='prtdosm' ; cond_values(1)=dt%prtdosm
2428      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtdos',dt%prtdos,1,(/3/),iout)
2429    end if
2430    if(dt%prtdosm==2.and.dt%pawprtdos/=2)then
2431      message = ' pawprtdos/=2  and prtdosm=2 are not compatible '
2432      MSG_ERROR(message)
2433    end if
2434 
2435 !  prtelf
2436    call chkint_ge(0,0,cond_string,cond_values,ierr,'prtelf',dt%prtkden,0,iout)
2437    if(optdriver/=RUNL_GSTATE)then
2438      cond_string(1)='optdriver' ; cond_values(1)=optdriver
2439      call chkint_eq(0,1,cond_string,cond_values,ierr,'prtelf',dt%prtelf,1,(/0/),iout)
2440    end if
2441    if(usepaw/=0)then
2442      cond_string(1)='usepaw' ; cond_values(1)=usepaw
2443      call chkint_eq(0,1,cond_string,cond_values,ierr,'prtelf',dt%prtelf,1,(/0/),iout)
2444    end if
2445 
2446 !  prtfsurf only one shift allowed (gamma)
2447    if (dt%prtfsurf == 1) then
2448 
2449      if (abs(dt%kptrlatt(1,2))+abs(dt%kptrlatt(1,3))+abs(dt%kptrlatt(2,3))+&
2450 &     abs(dt%kptrlatt(2,1))+abs(dt%kptrlatt(3,1))+abs(dt%kptrlatt(3,2)) /= 0 ) then
2451        write(message,'(4a)')ch10,&
2452 &       'prtfsurf does not work with non-diagonal kptrlatt ', ch10,&
2453 &       'Action: set nshift 1 and shiftk 0 0 0'
2454        MSG_ERROR_NOSTOP(message, ierr)
2455      end if
2456      if (dt%nshiftk > 1) then
2457        write(message,'(4a)') ch10,&
2458 &       'prtfsurf does not work with multiple kpt shifts ', ch10, &
2459 &       'Action: set nshift 1 and shiftk 0 0 0'
2460        MSG_ERROR_NOSTOP(message, ierr)
2461      end if
2462      if (sum(abs(dt%shiftk(:,1:dt%nshiftk))) > tol8) then
2463        write(message,'(4a)')ch10,&
2464 &       'prtfsurf does not work with non-zero kpt shift ',ch10,&
2465 &       'Action: set nshift 1 and shiftk 0 0 0'
2466        MSG_ERROR_NOSTOP(message, ierr)
2467      end if
2468 
2469 !    Occcupations, Fermi level and k weights have to be calculated correctly.
2470      if (.not.(dt%iscf>1.or.dt%iscf==-3)) then
2471        write(message,'(4a)')ch10,&
2472 &       'prtfsurf==1 requires either iscf>1 or iscf==-3 ',ch10,&
2473 &       'Action: change iscf in the input file. '
2474        MSG_ERROR_NOSTOP(message, ierr)
2475      end if
2476 
2477 !    Make sure all nband are equal (well it is always enforced for metals)
2478      if (any(dt%nband(1:nkpt*nsppol) /= maxval(dt%nband(1:nkpt*nsppol)) )) then
2479        write(message,'(3a)')&
2480 &       'The number of bands has to be constant for the output of the Fermi surface.',ch10,&
2481 &       'Action: set all the nbands to the same value in your input file'
2482        MSG_ERROR_NOSTOP(message,ierr)
2483      end if
2484    end if ! prtfsurf==1
2485 
2486 !  prtgden
2487    call chkint(0,0,cond_string,cond_values,ierr,&
2488 &   'prtgden',dt%prtgden,1,(/0/),1,0,iout)
2489    if(optdriver/=RUNL_GSTATE)then
2490      cond_string(1)='optdriver' ; cond_values(1)=optdriver
2491      call chkint(0,1,cond_string,cond_values,ierr,&
2492 &     'prtgden',dt%prtgden,1,(/0/),0,0,iout)
2493    end if
2494    if(usepaw/=0)then
2495      cond_string(1)='usepaw' ; cond_values(1)=usepaw
2496      call chkint(0,1,cond_string,cond_values,ierr,&
2497 &     'prtgden',dt%prtgden,1,(/0/),0,0,iout)
2498    end if
2499 
2500 !  prtkden
2501    call chkint_ge(0,0,cond_string,cond_values,ierr,'prtkden',dt%prtkden,0,iout)
2502    if(optdriver/=RUNL_GSTATE)then
2503      cond_string(1)='optdriver' ; cond_values(1)=optdriver
2504      call chkint_eq(0,1,cond_string,cond_values,ierr,'prtkden',dt%prtkden,1,(/0/),iout)
2505    end if
2506    if(usepaw/=0)then
2507      cond_string(1)='usepaw' ; cond_values(1)=usepaw
2508      call chkint_eq(0,1,cond_string,cond_values,ierr,'prtkden',dt%prtkden,1,(/0/),iout)
2509    end if
2510 
2511 !  prtlden
2512    call chkint(0,0,cond_string,cond_values,ierr,&
2513 &   'prtlden',dt%prtlden,1,(/0/),1,0,iout)
2514    if(optdriver/=RUNL_GSTATE)then
2515      cond_string(1)='optdriver' ; cond_values(1)=optdriver
2516      call chkint(0,1,cond_string,cond_values,ierr,&
2517 &     'prtlden',dt%prtlden,1,(/0/),0,0,iout)
2518    end if
2519    if(usepaw/=0)then
2520      cond_string(1)='usepaw' ; cond_values(1)=usepaw
2521      call chkint(0,1,cond_string,cond_values,ierr,&
2522 &     'prtlden',dt%prtlden,1,(/0/),0,0,iout)
2523    end if
2524 
2525 !  prtstm
2526    call chkint_ge(0,0,cond_string,cond_values,ierr,'prtstm',dt%prtstm,0,iout)
2527    if(optdriver/=RUNL_GSTATE)then
2528      cond_string(1)='optdriver' ; cond_values(1)=optdriver
2529      call chkint_eq(0,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2530    end if
2531    if(dt%occopt/=7)then
2532      cond_string(1)='occopt' ; cond_values(1)=dt%occopt
2533      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2534    end if
2535    if(dt%nstep/=1)then
2536      cond_string(1)='nstep' ; cond_values(1)=dt%nstep
2537      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2538    end if
2539    if(dt%ionmov/=0)then
2540      cond_string(1)='ionmov' ; cond_values(1)=dt%ionmov
2541      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2542    end if
2543 !  tolwfr must be 0 to make a problem (another tol variable is used). Here, check that it is very very small.
2544    if(abs(dt%tolwfr)<tol16*tol16)then
2545      cond_string(1)='tolwfr' ; cond_values(1)=0
2546      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2547    end if
2548    if(dt%prtden/=0)then
2549      cond_string(1)='prtden' ; cond_values(1)=dt%prtden
2550      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2551    end if
2552    if(dt%prtnabla>0)then
2553      cond_string(1)='prtnabla' ; cond_values(1)=dt%prtnabla
2554      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2555    end if
2556    if(dt%prtvxc>0)then
2557      cond_string(1)='prtvxc' ; cond_values(1)=dt%prtvxc
2558      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2559    end if
2560    if(dt%prtvha>0)then
2561      cond_string(1)='prtvha' ; cond_values(1)=dt%prtvha
2562      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2563    end if
2564    if(dt%prtvhxc>0)then
2565      cond_string(1)='prtvhxc' ; cond_values(1)=dt%prtvhxc
2566      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtstm',dt%prtstm,1,(/0/),iout)
2567    end if
2568 
2569 !  prtvclmb - needs prtvha as well
2570    if(dt%prtvclmb > 0)then
2571      cond_string(1)='prtvclmb' ; cond_values(1)=dt%prtvclmb
2572      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtvha',dt%prtvha,1,(/1/),iout)
2573    end if
2574 
2575 !  prtvolimg
2576    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtvolimg',dt%prtvolimg,3,(/0,1,2/),iout)
2577 
2578 !  prtwant
2579    if (dt%prtwant/=0) then
2580      cond_string(1)='prtwant' ; cond_values(1)=dt%prtwant
2581      call chkint_eq(0,0,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,1,(/0/),iout)
2582    end if
2583 #if !defined HAVE_WANNIER90
2584    if(dt%prtwant==2) then
2585      write(message, '(a,a,a)' )&
2586 &     ' prtwant==2 is only relevant if wannier90 library is linked',ch10,&
2587 &     ' Action: check compilation options'
2588      MSG_ERROR_NOSTOP(message,ierr)
2589    end if
2590 #endif
2591 
2592 !  prtwf
2593    call chkint_eq(0,0,cond_string,cond_values,ierr,'prtwf',dt%prtwf,5,[-1,0,1,2,3],iout)
2594 
2595 
2596 !  random_atpos
2597    call chkint_eq(0,0,cond_string,cond_values,ierr,'random_atpos',dt%random_atpos,5,(/0,1,2,3,4/),iout)
2598 
2599 !  ratsph
2600 !  If PAW and (prtdos==3 or dt%prtdensph==1), must be greater than PAW radius
2601    if(usepaw==1.and.(dt%prtdos==3.or.dt%prtdensph==1))then
2602      do itypat=1,dt%ntypat
2603        if (pspheads(itypat)%pawheader%rpaw>dt%ratsph(itypat)) then
2604          write(message, '(7a,i2,a,f15.12,3a)' )&
2605 &         'Projected DOS/density is required in the framework of PAW !',ch10,&
2606 &         'The radius of spheres in which DOS/density has to be projected',ch10,&
2607 &         'must be greater or equal than the (max.) PAW radius !',ch10,&
2608 &         'Rpaw(atom_type ',itypat,')= ',pspheads(itypat)%pawheader%rpaw,' au',ch10,&
2609 &         'Action: modify value of ratsph in input file.'
2610          MSG_ERROR_NOSTOP(message, ierr)
2611        end if
2612      end do
2613    end if
2614 
2615 
2616 !  recgratio
2617    if (dt%tfkinfunc==2) then
2618      write(message, '(a,a)' ) ch10,&
2619 &     '=== RECURSION METHOD ==========================================================='
2620      call wrtout(ab_out,message,'COLL')
2621      cond_string(1)='tfkinfunc' ; cond_values(1)=2
2622      call chkint_ge(0,1,cond_string,cond_values,ierr,'recgratio',dt%recgratio,1,iout)
2623      if(dt%recgratio>1) then
2624        write(message, '(a,a)' )&
2625 &       '=== Coarse Grid is used in recursion ==========================================='
2626        call wrtout(ab_out,message,'COLL')
2627        write(message, '(a,i3,a,a,i3,a,i3,a,i3)' ) 'grid ratio =',dt%recgratio,&
2628 &       ch10,'fine grid =   ',dt%ngfft(1),' ',dt%ngfft(2),' ',dt%ngfft(3)
2629        call wrtout(ab_out,message,'COLL')
2630        write(message, '(a,i2,a,i2,a,i2)' ) 'coarse grid = ',&
2631 &       dt%ngfft(1)/dt%recgratio,' ',dt%ngfft(2)/dt%recgratio,' ',dt%ngfft(3)/dt%recgratio
2632        call wrtout(ab_out,message,'COLL')
2633      else
2634        write(message, '(a,i2,a,i2,a,i2)' ) 'fine grid =   ',dt%ngfft(1),' ',dt%ngfft(2),' ',dt%ngfft(3)
2635        call wrtout(ab_out,message,'COLL')
2636 
2637      end if
2638    end if
2639 
2640 
2641 !  rfatpol
2642    call chkint_ge(0,0,cond_string,cond_values,ierr,'rfatpol(1)',dt%rfatpol(1),1,iout)
2643    cond_string(1)='natom' ; cond_values(1)=natom
2644    call chkint_le(1,1,cond_string,cond_values,ierr,'rfatpol(2)',dt%rfatpol(2),natom,iout)
2645 
2646 !  rprimd
2647 !  With optcell beyond 4, one has constraints on rprimd.
2648    if(dt%optcell==4 .or. dt%optcell==7 )then
2649      cond_string(1)='optcell' ; cond_values(1)=4
2650      if(dt%optcell==7)cond_values(1)=7
2651      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(1,2)',rprimd(1,2),0,0.0_dp,iout)
2652      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(1,3)',rprimd(1,3),0,0.0_dp,iout)
2653      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(2,1)',rprimd(2,1),0,0.0_dp,iout)
2654      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(3,1)',rprimd(3,1),0,0.0_dp,iout)
2655    else if(dt%optcell==5 .or. dt%optcell==8 )then
2656      cond_string(1)='optcell' ; cond_values(1)=5
2657      if(dt%optcell==8)cond_values(1)=8
2658      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(2,1)',rprimd(2,1),0,0.0_dp,iout)
2659      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(2,3)',rprimd(2,3),0,0.0_dp,iout)
2660      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(1,2)',rprimd(1,2),0,0.0_dp,iout)
2661      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(3,2)',rprimd(3,2),0,0.0_dp,iout)
2662    else if(dt%optcell==6 .or. dt%optcell==9 )then
2663      cond_string(1)='optcell' ; cond_values(1)=6
2664      if(dt%optcell==9)cond_values(1)=9
2665      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(3,1)',rprimd(3,1),0,0.0_dp,iout)
2666      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(3,2)',rprimd(3,2),0,0.0_dp,iout)
2667      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(1,3)',rprimd(1,3),0,0.0_dp,iout)
2668      call chkdpr(1,1,cond_string,cond_values,ierr,'rprimd(2,3)',rprimd(2,3),0,0.0_dp,iout)
2669    end if
2670 
2671 !  so_psp
2672    if(usepaw==0)then
2673      do ipsp=1,npsp
2674 !      Check that so_psp is between 0 and 3
2675        if ( dt%so_psp(ipsp)<0 .or. dt%so_psp(ipsp)>3 ) then
2676          write(message, '(a,i3,a,i3,a,a,a,a,a)' )&
2677 &         'so_psp(',ipsp,' ) was input as',dt%so_psp(ipsp),' .',ch10,&
2678 &         'Input value must be 0, 1, 2, or 3.',ch10,&
2679 &         'Action: modify value of so_psp (old name : so_typat) in input file.'
2680          MSG_ERROR_NOSTOP(message, ierr)
2681        end if
2682 !      If nspinor=1, the spin-orbit contribution cannot be taken into account
2683        if ( nspinor==1 .and. (dt%so_psp(ipsp)==2 .or. dt%so_psp(ipsp)==3) ) then
2684          write(message, '(a,i2,a,i3,a,a,a,a,a)' )&
2685 &         'so_psp(',ipsp,') was input as',dt%so_psp(ipsp),', with nspinor=1 and usepaw=0.',ch10,&
2686 &         'When nspinor=1, so_psp cannot be required to be 2 or 3.',ch10,&
2687 &         'Action: modify value of so_psp (old name : so_typat) or nspinor in input file.'
2688          MSG_ERROR_NOSTOP(message, ierr)
2689        end if
2690 !      If nspinor=2, the spin-orbit contribution should be present in the pseudopotentials,
2691 !      unless the user explicitly allows not to treat it.
2692        if ( nspinor==2 .and. dt%so_psp(ipsp)/=0 .and. pspheads(ipsp)%pspso==0 ) then
2693          write(message, '(a,i2,a,i3,9a)' )&
2694 &         'so_psp(',ipsp,') was input as',dt%so_psp(ipsp),', with nspinor=2 and usepaw=0.',ch10,&
2695 &         'This requires a treatment of the spin-orbit interaction. However, it has been detected ',ch10,&
2696 &         'that the pseudopotential that you want to use does not specify the spin-orbit coupling.',ch10,&
2697 &         'Action: choose a pseudopotential that contains information about the spin-orbit interaction,',ch10,&
2698 &         ' or deliberately switch off the spin-orbit interaction by setting so_psp=0 for that pseudopotential in the input file.'
2699          MSG_ERROR_NOSTOP(message, ierr)
2700        end if
2701      end do ! ipsp
2702    end if ! usepaw==0
2703 
2704 !  spinmagntarget
2705    if(abs(dt%spinmagntarget+99.99d0)>tol8 .and. abs(dt%spinmagntarget)>tol8)then
2706      if(nsppol==1)then
2707        write(message, '(a,f8.2,4a)' )&
2708 &       'spinmagntarget was input as',dt%spinmagntarget,ch10,&
2709 &       'When nsppol=1, spinmagntarget is required to be 0.0d0 or the default value.',ch10,&
2710 &       'Action: modify value spinmagntarget or nsppol in input file.'
2711        MSG_ERROR_NOSTOP(message, ierr)
2712      end if
2713      if(optdriver==RUNL_RESPFN)then
2714        write(message, '(a,f8.2,4a)' )&
2715 &       'spinmagntarget was input as',dt%spinmagntarget,ch10,&
2716 &       'For a response function run, spinmagntarget is required to be 0.0d0 or the default value.',ch10,&
2717 &       'Action: modify value spinmagntarget or nsppol in input file.'
2718        MSG_ERROR_NOSTOP(message, ierr)
2719      end if
2720      if(dt%prtdos==1)then
2721        write(message, '(a,f8.2,4a)' )&
2722 &       'spinmagntarget was input as',dt%spinmagntarget,ch10,&
2723 &       'When prtdos==1, spinmagntarget is required to be 0.0d0 or the default value.',ch10,&
2724 &       'Action: modify value spinmagntarget or nsppol in input file.'
2725        MSG_ERROR_NOSTOP(message, ierr)
2726      end if
2727    end if
2728 !  If nsppol==2 and spinmagntarget==0.0 , suggest to use anti-ferromagnetic capability of ABINIT.
2729    if(nsppol==2.and.abs(dt%spinmagntarget)<tol8)then
2730      write(message,'(a,i3,2a,f7.2,6a)' )&
2731 &     ' This is a calculation with spin-up and spin-down wavefunctions,         ... nsppol=',nsppol,ch10,&
2732 &     ' in which the target spin-polarization is zero.                  ... spinmagntarget=',dt%spinmagntarget,ch10,&
2733 &     ' Tip ... It might be possible that the ground state is either non-spin-polarized, or antiferromagnetic.',ch10,&
2734 &     ' In the former case, it is advantageous to use nsppol=1 and nspden=1,',ch10,&
2735 &     ' while in the latter  case, it is advantageous to use nsppol=1 and nspden=2.'
2736      call wrtout(iout,message,'COLL')
2737    end if
2738 
2739 !  stmbias
2740    cond_string(1)='prtstm' ; cond_values(1)=dt%prtstm
2741    if(dt%prtstm/=0)then
2742 !    If non-zero prtstm, stmbias cannot be zero : test is positive or zero
2743      if(dt%stmbias>-tol10)then
2744 !      Then, enforce positive
2745        call chkdpr(1,1,cond_string,cond_values,ierr,'stmbias',dt%stmbias,1,2*tol10,iout)
2746      end if
2747    else
2748      call chkdpr(1,1,cond_string,cond_values,ierr,'stmbias',dt%stmbias,0,zero,iout)
2749    end if
2750 
2751 !  string_algo
2752    call chkint_eq(0,0,cond_string,cond_values,ierr,'string_algo',dt%string_algo,2,(/1,2/),iout)
2753 
2754 !  symafm
2755    if(nsppol==1 .and. nspden==2)then
2756 !    At least one of the symmetry operations must be antiferromagnetic
2757      if(minval(dt%symafm(1:dt%nsym))/=-1)then
2758        write(message, '(5a)' )&
2759 &       'When nsppol==1 and nspden==2, at least one of the symmetry operations',ch10,&
2760 &       'must be anti-ferromagnetic (symafm=-1), in order to deduce the spin-down density',ch10,&
2761 &       'from the spin-up density.'
2762        call wrtout(iout,message,'COLL')
2763        call wrtout(std_out,  message,'COLL')
2764        write(message, '(7a)' ) &
2765 &       'However, it is observed that none of the symmetry operations is anti-ferromagnetic.',ch10,&
2766 &       'Action: Check the atomic positions, the input variables spinat, symrel, tnons, symafm.',ch10,&
2767 &       '        In case your system is not antiferromagnetic (it might be ferrimagnetic ...),',ch10,&
2768 &       '        you must use nsppol=2 with nspden=2 (the latter being the default when nsppol=2).'
2769        MSG_ERROR_NOSTOP(message,ierr)
2770      end if
2771    end if
2772 
2773 !  symrel and tnons
2774 !  Check the point group closure (TODO should check the spatial group closure !!)
2775    call chkgrp(dt%nsym,dt%symafm,dt%symrel,ierrgrp)
2776    if (ierrgrp==1) ierr=ierr+1
2777 
2778 !  Check the orthogonality of the symmetry operations
2779 !  (lengths and absolute values of scalar products should be preserved)
2780    iexit=0
2781 
2782    call chkorthsy(gprimd,iexit,dt%nsym,rmet,rprimd,dt%symrel)
2783 
2784 !  symchi
2785    if (all(dt%symchi /= [0, 1])) then
2786      write(message, '(a,i0,2a)' )'symchi  was input as ',dt%symchi,ch10,'Input value must be 0, 1.'
2787      MSG_ERROR_NOSTOP(message, ierr)
2788    end if
2789 
2790 !  symsigma
2791    if (dt%symsigma/=0.and.dt%symsigma/=1.and.dt%symsigma/=2) then
2792      write(message, '(a,i0,a,a,a,a)' )&
2793 &     'symsigma  was input as',dt%symsigma,ch10,&
2794 &     'Input value must be 0, 1, or 2.',ch10,&
2795 &     'Action: modify value of symsigma in input file.'
2796      MSG_ERROR_NOSTOP(message, ierr)
2797    end if
2798 
2799 !  MG now it is possible to perform a GW calculation with non-symmorphic operations if required by the user
2800 !  tnons
2801    if (dt%symmorphi==0) then
2802      if(dt%nbandkss/=0)then
2803        do isym=1,dt%nsym
2804          if(sum(dt%tnons(:,isym)**2)>tol6)then
2805            write(message, '(3a,i3,a,3f8.4,3a)' )&
2806 &           'When nbandkss/=0, all the components of tnons must be zero.',ch10,&
2807 &           'However, for the symmetry operation number ',isym,', tnons =',dt%tnons(:,isym),'.',ch10,&
2808 &           'Action: use the symmetry finder (nsym=0) with symmorphi==0.'
2809            MSG_ERROR_NOSTOP(message,ierr)
2810          end if
2811        end do
2812      end if
2813      if (ANY(optdriver ==[RUNL_SCREENING,RUNL_SIGMA])) then
2814        do isym=1,dt%nsym
2815          if (sum(dt%tnons(:,isym)**2)>tol6) then
2816            write(message,'(3a,i3,a,3f8.4,3a)')&
2817 &           'When optdriver==RUNL_SCREENING or RUNL_SIGMA, all the components of tnons must be zero.',ch10,&
2818 &           'However, for the symmetry operation number ',isym,', tnons =',dt%tnons(:,isym),'.',ch10,&
2819 &           'Action: use the symmetry finder (nsym=0) with symmorphi==0.'
2820            MSG_ERROR_NOSTOP(message, ierr)
2821          end if
2822        end do
2823      end if
2824    end if !of symmorphi
2825 
2826 !  tfwkinfunc
2827    call chkint_eq(0,0,cond_string,cond_values,ierr,'tfwkinfunc',dt%tfkinfunc,5,(/0,1,2,11,12/),iout)
2828    if(dt%ionmov==4)then
2829      cond_string(1)='ionmov' ; cond_values(1)=4
2830      call chkint_eq(1,1,cond_string,cond_values,ierr,'tkinfunc',dt%tfkinfunc,1,(/0/),iout)
2831    end if
2832 
2833 !  tolmxde
2834    call chkdpr(0,0,cond_string,cond_values,ierr,'tolmxde',dt%tolmxde,1,zero,iout)
2835 
2836 !  toldff
2837    call chkdpr(0,0,cond_string,cond_values,ierr,'toldff',dt%toldff,1,zero,iout)
2838 
2839 !  tolimg
2840    call chkdpr(0,0,cond_string,cond_values,ierr,'tolimg',dt%tolimg,1,zero,iout)
2841 
2842 !  tolrde
2843    call chkdpr(0,0,cond_string,cond_values,ierr,'tolrde',dt%tolrde,1,zero,iout)
2844 
2845 !  tolrff
2846    call chkdpr(0,0,cond_string,cond_values,ierr,'tolrff',dt%tolrff,1,zero,iout)
2847 
2848 !  tolwfr
2849    call chkdpr(0,0,cond_string,cond_values,ierr,'tolwfr',dt%tolwfr,1,zero,iout)
2850 
2851 !  tsmear
2852    call chkdpr(0,0,cond_string,cond_values,ierr,'tsmear',dt%tsmear,1,zero,iout)
2853 !  Check that tsmear is non-zero positive for metallic occupation functions
2854    if(3<=dt%occopt .and. dt%occopt<=8)then
2855      cond_string(1)='occopt' ; cond_values(1)=dt%occopt
2856      call chkdpr(1,1,cond_string,cond_values,ierr,'tsmear',dt%tsmear,1,tol8,iout)
2857    end if
2858 
2859 !  ucrpa
2860    call chkint_eq(0,0,cond_string,cond_values,ierr,'ucrpa',dt%ucrpa,5,(/0,1,2,3,4/),iout)
2861    if (dt%ucrpa>=1) then
2862      cond_string(1)='ucrpa' ; cond_values(1)=dt%ucrpa
2863      call chkint_eq(1,1,cond_string,cond_values,ierr,'nspinor',dt%nspinor,1,(/1/),iout)
2864    end if
2865 
2866 !  usedmatpu
2867    if (usepaw==1.and.dt%usepawu==1) then
2868 !    abs(dt%usedmatpu)<=nstep
2869      cond_string(1)='nstep' ; cond_values(1)=dt%nstep
2870      call chkint_le(1,1,cond_string,cond_values,ierr,'abs(usedmatpu)',abs(dt%usedmatpu),dt%nstep,iout)
2871 !    lpawu must be constant or -1
2872      if (dt%usedmatpu/=0) then
2873        do itypat=1,dt%ntypat
2874          if (dt%lpawu(itypat)/=-1.and.dt%lpawu(itypat)/=maxval(dt%lpawu(:))) then
2875            write(message, '(3a)' )&
2876 &           'When usedmatpu/=0 (use of an initial density matrix for LDA+U),',ch10,&
2877 &           'lpawu must be equal for all types of atoms on which +U is applied !'
2878            MSG_ERROR_NOSTOP(message,ierr)
2879          end if
2880        end do
2881      end if
2882    end if
2883 
2884 !  usedmft
2885    if (dt%usedmft>0) then
2886      cond_string(1)='usedmft' ; cond_values(1)=1
2887      call chkint_eq(0,1,cond_string,cond_values,ierr,'usedmft',dt%usedmft,2,(/0,1/),iout)
2888      if (dt%paral_kgb>0) then
2889        cond_string(1)='usedmft' ; cond_values(1)=dt%usedmft
2890        call chkint_eq(1,1,cond_string,cond_values,ierr,'npspinor',dt%npspinor,1,(/1/),iout)
2891      end if
2892 !    call chkint_eq(1,1,cond_string,cond_values,ierr,'paral_kgb',dt%paral_kgb,1,(/0/),iout)
2893    end if
2894 
2895 !  useexexch and lexexch
2896 !  Local exact-exchange and restrictions
2897    if(dt%useexexch/=0)then
2898      cond_string(1)='useexexch' ; cond_values(1)=dt%useexexch
2899      call chkint_eq(1,1,cond_string,cond_values,ierr,'useexexch',dt%useexexch,1,(/1/),iout)
2900      cond_string(1)='useexexch' ; cond_values(1)=dt%useexexch
2901      call chkint_eq(1,1,cond_string,cond_values,ierr,'usepaw',usepaw,1,(/1/),iout)
2902      cond_string(1)='useexexch' ; cond_values(1)=dt%useexexch
2903      call chkint_eq(1,1,cond_string,cond_values,ierr,'pawxcdev',dt%pawxcdev,2,(/1,2/),iout)
2904      cond_string(1)='useexexch' ; cond_values(1)=dt%useexexch
2905      call chkint_eq(1,1,cond_string,cond_values,ierr,'ixc',dt%ixc,2,(/11,23/),iout)
2906      do itypat=1,dt%ntypat
2907        cond_string(1)='lexexch' ; cond_values(1)=dt%lexexch(itypat)
2908        call chkint_eq(1,1,cond_string,cond_values,ierr,'lexexch',dt%lexexch(itypat),5,(/-1,0,1,2,3/),iout)
2909      end do
2910    end if
2911 
2912 !  usekden
2913    call chkint_eq(0,0,cond_string,cond_values,ierr,'usekden',dt%usekden,2,(/0,1/),iout)
2914    if(dt%usekden==0)then
2915      cond_string(1)='usekden' ; cond_values(1)=dt%usekden
2916      call chkint_eq(1,1,cond_string,cond_values,ierr,'prtkden',dt%prtkden,1,(/0/),iout)
2917      if(mgga==1)then
2918        write(message, '(3a)' )&
2919 &       'The functional is a MGGA, but the kinetic energy density',ch10, &
2920 &       'is not present. Please set "usekden 1" in the input file.'
2921        MSG_ERROR(message)
2922      end if
2923    else if(dt%usekden/=0)then
2924      cond_string(1)='usekden' ; cond_values(1)=dt%usekden
2925      call chkint_eq(1,1,cond_string,cond_values,ierr,'usewvl',usewvl,1,(/0/),iout)
2926      cond_string(1)='usekden' ; cond_values(1)=dt%usekden
2927      call chkint_eq(1,1,cond_string,cond_values,ierr,'usepaw',usepaw,1,(/0/),iout)
2928      cond_string(1)='usekden' ; cond_values(1)=dt%usekden
2929      call chkint_eq(1,1,cond_string,cond_values,ierr,'intxc',dt%intxc,1,(/0/),iout)
2930      do ipsp=1,npsp
2931 !      Check that xccc is zero (metaGGAs cannot be used at present with non-linear core corrections)
2932        if ( pspheads(ipsp)%xccc/=0 ) then
2933          write(message, '(3a,i0,3a)' )&
2934 &         'When usekden is non-zero, it is not possible to use pseudopotentials with a non-linear core correction.',ch10,&
2935 &         'However, for pseudopotential number ',ipsp,', there is such a core correction.',ch10,&
2936 &         'Action: either set usekden=0 in input file, or change this pseudopotential file.'
2937          MSG_ERROR_NOSTOP(message, ierr)
2938        end if
2939      end do
2940    end if
2941 
2942 !  usepawu and lpawu
2943 !  PAW+U and restrictions
2944    call chkint_eq(0,0,cond_string,cond_values,ierr,'usepawu',dt%usepawu,7,(/0,1,2,3,4,10,14/),iout)
2945    if(dt%usepawu/=0)then
2946      cond_string(1)='usepawu' ; cond_values(1)=dt%usepawu
2947      call chkint_eq(1,1,cond_string,cond_values,ierr,'usepaw',usepaw,1,(/1/),iout)
2948      do itypat=1,dt%ntypat
2949        cond_string(1)='lpawu' ; cond_values(1)=dt%lpawu(itypat)
2950        call chkint_eq(1,1,cond_string,cond_values,ierr,'lpawu',dt%lpawu(itypat),5,(/-1,0,1,2,3/),iout)
2951      end do
2952      if(dt%pawspnorb>0) then
2953        write(message,'(3a)' ) &
2954 &       '  LDA+U+SpinOrbit is still on test ',ch10,&
2955 &       '  (not yet in production)'
2956        MSG_WARNING(message)
2957      end if
2958    end if
2959 
2960 !  useexexch AND usepawu
2961 !  Restriction when use together
2962    if(dt%useexexch>0.and.dt%usepawu>0)then
2963      do itypat=1,dt%ntypat
2964        if (dt%lpawu(itypat)/=dt%lexexch(itypat).and.&
2965 &       dt%lpawu(itypat)/=-1.and.dt%lexexch(itypat)/=-1) then
2966          write(message, '(5a,i2,3a)' )&
2967 &         'When PAW+U (usepawu>0) and local exact-exchange (useexexch>0)',ch10,&
2968 &         'are selected together, they must apply on the same',ch10,&
2969 &         'angular momentum (lpawu/=lexexch forbidden, here for typat=',itypat,') !',ch10,&
2970 &         'Action: correct your input file.'
2971          MSG_ERROR_NOSTOP(message,ierr)
2972        end if
2973      end do
2974    end if
2975 
2976 !  usedmft/usepawu and lpawu
2977 !  Restriction when use together
2978    if(dt%usedmft>0.or.dt%usepawu>0)then
2979      nlpawu=0
2980      do itypat=1,dt%ntypat
2981        if (dt%lpawu(itypat)/=-1) then
2982          nlpawu=nlpawu+1
2983        end if
2984      end do
2985      if(nlpawu==0) then
2986        write(message, '(6a)' )&
2987 &       'When DFT+U or DFT+DMFT is used',ch10,&
2988 &       'at least one value of lpawu should be different from -1',ch10,&
2989 &       'Action: correct your input file.'
2990        MSG_ERROR(message)
2991      end if
2992    end if
2993 
2994 !  usepotzero
2995    if(dt%usepotzero/=0)then
2996      if(dt%iscf<10) then
2997        write(message, '(3a)' )&
2998 &       'usepotzero can only be used with density mixing (not implemented yet)',ch10,&
2999 &       'Action: choose iscf > 10 '
3000        MSG_ERROR_NOSTOP(message,ierr)
3001      end if
3002    end if
3003 
3004 !  usexcnhat
3005    call chkint_eq(0,0,cond_string,cond_values,ierr,'usexcnhat',dt%usexcnhat_orig,3,(/-1,0,1/),iout)
3006 
3007 !  useylm
3008    call chkint_eq(0,0,cond_string,cond_values,ierr,'useylm',dt%useylm,2,(/0,1/),iout)
3009    if (usepaw==1) then
3010      if(usewvl==0) then
3011        write(cond_string(1), "(A)") 'pspcod'
3012        cond_values(1)=7;cond_values(2)=17
3013        call chkint_eq(1,2,cond_string,cond_values,ierr,'useylm',dt%useylm,1,(/1/),iout)
3014      else
3015        write(cond_string(1), "(A)") 'usewvl'
3016        cond_values(1)=1
3017        call chkint_eq(1,1,cond_string,cond_values,ierr,'useylm',dt%useylm,1,(/0/),iout)
3018      end if
3019    end if
3020 
3021 !  use_gpu_cuda
3022    call chkint_eq(0,0,cond_string,cond_values,ierr,'use_gpu_cuda',dt%use_gpu_cuda,2,(/0,1/),iout)
3023    if (dt%use_gpu_cuda==1) then
3024      if (dt%nspinor==2) then
3025        write(message,'(3a)')&
3026 &       'Use of GPU is not allowed when nspinor==2 !',ch10,&
3027 &       'Action: impose use_gpu_cuda=0 in your input file.'
3028        MSG_ERROR_NOSTOP(message, ierr)
3029      end if
3030 !    if (dt%optdriver==RUNL_GSTATE.and.mod(dt%wfoptalg,10)/=4) then
3031 !    write(message,'(6a)') ch10,&
3032 !    &       ' chkinp : ERROR -',ch10,&
3033 !    &       '  When GPU is in use (use_gpu_cuda=1), wfoptalg must be 4 or 14 !',ch10,&
3034 !    &       '  Action: change wfoptalg in your input file.'
3035 !    call wrtout(std_out,message,'COLL')
3036 !    ierr=ierr+1
3037 !    end if
3038      if (dt%useylm==0) then
3039        write(message,'(3a)')&
3040 &       'Use of GPU is not allowed when useylm==0 !',ch10,&
3041 &       'Action: impose uselym=1 in your input file.'
3042        MSG_ERROR_NOSTOP(message, ierr)
3043      end if
3044      if (dt%tfkinfunc>0) then
3045        write(message,'(5a)')&
3046 &       'use_gpu_cuda=1 is not allowed when tfkinfunc>0 !',ch10,&
3047 &       'Action: suppress use_gpu_cuda=0 from your input file',ch10,&
3048 &       '        (GPU will be used but with another mechanism)'
3049        MSG_ERROR_NOSTOP(message, ierr)
3050      end if
3051      if (dt%ngfft(4)/=dt%ngfft(1).or.dt%ngfft(5)/=dt%ngfft(2).or.dt%ngfft(6)/=dt%ngfft(3)) then
3052        write(message,'(3a)')&
3053 &       'When GPU is in use (use_gpu_cuda=1), ngfft(4:6) must be equal to ngfft(1:3) !',ch10,&
3054 &       'Action: suppress ngfft in input file or change it.'
3055        MSG_ERROR_NOSTOP(message, ierr)
3056      end if
3057 #ifndef HAVE_GPU_CUDA
3058      write(message,'(6a)') ch10,&
3059 &     ' invars0: ERROR -',ch10,&
3060 &     '   Input variables use_gpu_cuda is on but abinit hasn''t been built with gpu mode enabled !',ch10,&
3061 &     '   Action: change the input variable use_gpu_cuda or re-compile ABINIT with Cuda enabled.'
3062      call wrtout(std_out,message,'COLL')
3063      ierr=ierr+1
3064 #endif
3065 #ifndef HAVE_GPU_CUDA_DP
3066      write(message,'(10a)') ch10,&
3067 &     ' invars0: ERROR -',ch10,&
3068 &     '   Input variables use_gpu_cuda is on but abinit hasn''t been built',ch10,&
3069 &     '   with gpu mode in DOUBLE PRECISION enabled !',ch10,&
3070 &     '   Action: change the input variable use_gpu_cuda',ch10,&
3071 &     '   or re-compile ABINIT with double precision Cuda enabled.'
3072      call wrtout(std_out,message,'COLL')
3073      ierr=ierr+1
3074 #endif
3075    end if
3076 
3077 !  use_slk
3078    if (dt%paral_kgb==1) then
3079      call chkint_eq(0,0,cond_string,cond_values,ierr,'use_slk',dt%use_slk,2,(/0,1/),iout)
3080    end if
3081 
3082 !  vdw_xc
3083    call chkint_eq(0,1,cond_string,cond_values,ierr,'vdw_xc',dt%vdw_xc,9,(/0,1,2,5,6,7,10,11,14/),iout)
3084    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
3085      write(message,'(a,i2,a)')&
3086 &     'vdw_xc=',dt%vdw_xc,' is not yet available with Projector Augmented-Wave (PAW) formalism!'
3087      MSG_ERROR_NOSTOP(message, ierr)
3088    end if
3089 !  vdw DFT-D2
3090    if (dt%vdw_xc==5.or.dt%vdw_xc==6.or.dt%vdw_xc==7) then
3091 !    Only for GS or RF calculations
3092      if(optdriver/=RUNL_GSTATE.and.optdriver/=RUNL_RESPFN) then
3093        cond_string(1)='vdw_xc' ; cond_values(1)=dt%vdw_xc
3094        call chkint_ne(1,1,cond_string,cond_values,ierr,'optdriver',optdriver,2,(/RUNL_GSTATE,RUNL_RESPFN/),iout)
3095      end if
3096 !    Restriction for DFT-D2
3097      if (dt%vdw_xc==5) then
3098 !    Only with PBE, BP86  or BLYP GGA XC
3099        if(dt%ixc/=11.and.dt%ixc/=-101130.and.dt%ixc/=-130101.and. &
3100 &       dt%ixc/=18.and.dt%ixc/=-106131.and.dt%ixc/=-131106.and. &
3101 &       dt%ixc/=19.and.dt%ixc/=-106132.and.dt%ixc/=-132106.and. &
3102 &       dt%ixc/=-202231.and.dt%ixc/=-231202) then
3103          write(message,'(8a)') ch10,&
3104 &         ' chkinp : ERROR -',ch10,&
3105 &         '  Van der Waals DFT-D2 correction (vdw_xc=5) only available for the following XC functionals:',ch10,&
3106 &         '      GGA-PBE, GGA-BLYP, GGA-BP86, mGGA-TPSS',ch10,&
3107 &         '  Action: change your pseudopotential file.'
3108          call wrtout(std_out,message,'COLL')
3109          ierr=ierr+1
3110        end if
3111 !       Only for the first 5 lines of the periodic table
3112        do itypat=1,dt%ntypat
3113          if (dt%znucl(itypat)<0.or.dt%znucl(itypat)>54) then
3114            write(message,'(4a,f5.1,a)') ch10,&
3115 &           ' chkinp : ERROR -',ch10,&
3116 &           '  Van der Waals DFT-D2 correction (vdw_xc=5) not available for atom type Z=',dt%znucl(itypat),' !'
3117            call wrtout(std_out,message,'COLL')
3118            ierr=ierr+1
3119          end if
3120        end do
3121      end if
3122 !    Restriction for DFT-D3/DFT-D3(BJ)
3123      if (dt%vdw_xc==6.or.dt%vdw_xc==7) then
3124 !    Only with PBE, BP86  or BLYP GGA XC
3125        if(dt%ixc/=11.and.dt%ixc/=-101130.and.dt%ixc/=-130101.and. &
3126 &       dt%ixc/=18.and.dt%ixc/=-106131.and.dt%ixc/=-131106.and. &
3127 &       dt%ixc/=19.and.dt%ixc/=-106132.and.dt%ixc/=-132106.and. &
3128 &       dt%ixc/=-202231.and.dt%ixc/=-231202.and.&
3129 &       dt%ixc/=14.and.dt%ixc/=-102130.and.dt%ixc/=-130102.and. &
3130 &       dt%ixc/=-170.and.dt%ixc/=41.and.dt%ixc/=-406) then
3131          write(message,'(4a,i2,5a)') ch10,&
3132 &         ' chkinp : ERROR -',ch10,&
3133 &         '  Van der Waals DFT-D correction (vdw_xc=',dt%vdw_xc,') only available for the following XC functionals:',ch10,&
3134 &         '      GGA-PBE, GGA-BLYP, GGA-BP86, mGGA-TPSS, GGA-RevPBE, PBE0',ch10,&
3135 &         '  Action: change your pseudopotential file.'
3136          call wrtout(std_out,message,'COLL')
3137          ierr=ierr+1
3138        end if
3139 !       Only up to chemical species 96
3140        do itypat=1,dt%ntypat
3141          if (dt%znucl(itypat)<0.or.dt%znucl(itypat)>96) then
3142            write(message,'(4a,i2,1a,f5.1,a)') ch10,&
3143 &           ' chkinp : ERROR -',ch10,&
3144 &           '  Van der Waals DFT-D correction (vdw_xc=',dt%vdw_xc,') not available for atom type Z=',dt%znucl(itypat),' !'
3145            call wrtout(std_out,message,'COLL')
3146            ierr=ierr+1
3147          end if
3148        end do
3149      end if
3150    end if
3151 
3152 !  wfoptalg
3153 !  Must be greater or equal to 0
3154    call chkint_ge(0,0,cond_string,cond_values,ierr,'wfoptalg',dt%wfoptalg,0,iout)
3155 !  wfoptalg==0,1,4,10 or 14 if PAW
3156    if (usepaw==1) then
3157      write(cond_string(1), "(A)") 'usepaw'
3158      cond_values(1)=1
3159      call chkint_eq(0,1,cond_string,cond_values,ierr,'wfoptalg',dt%wfoptalg,6,(/0,1,4,10,14,114/),iout)
3160    end if
3161 
3162    ! Check if FFT library supports MPI-FFT.
3163    if (dt%npfft > 1 .and..not. fftalg_has_mpi(fftalg)) then
3164      write(message,"(a,i0,a)")"fftalg: ",fftalg," cannot be used in MPI-FFT mode (npfft > 1)"
3165      MSG_ERROR_NOSTOP(message,ierr)
3166    end if
3167 
3168    ! Chebyshev
3169    if(dt%wfoptalg == 1) then
3170      if(dt%nspinor > 1) then
3171        message='Nspinor > 1 not yet compatible with wfoptalg 1'
3172        MSG_ERROR_NOSTOP(message, ierr)
3173      end if
3174      !! TODO obsolete?
3175      if(dt%usefock > 0) then
3176        message='Fock not yet compatible with wfoptalg 1 (use Fock-level parallelism)'
3177        MSG_ERROR_NOSTOP(message, ierr)
3178      end if
3179      if(maxval(abs(dt%istwfk(1:nkpt))) > 2) then
3180        message='Istwfk > 2 not compatible with wfoptalg 1'
3181        MSG_ERROR_NOSTOP(message, ierr)
3182      end if
3183      if(dt%ecutsm > 0) then
3184        message='Ecutsm > 0 not yet compatible with wfoptalg 1'
3185        MSG_ERROR_NOSTOP(message, ierr)
3186      end if
3187      !! TODO check bandpp instead of overwriting it
3188    end if
3189 
3190 !  wtk
3191 !  Check that no k point weight is < 0:
3192    do ikpt=1,nkpt
3193      if (dt%wtk(ikpt)< -tiny(0.0_dp) ) then
3194        write(message, '(a,i5,a,1p,e12.4,a,a,a)' )&
3195 &       'At k point number',ikpt,'  wtk=',dt%wtk(ikpt),' <0.',ch10,&
3196 &       'Action: check wtk in input file. Each wtk must be >=0.'
3197        MSG_ERROR_NOSTOP(message,ierr)
3198      end if
3199    end do
3200 
3201 !  xc_denpos
3202    call chkdpr(0,0,cond_string,cond_values,ierr,'xc_denpos',dt%xc_denpos,1,tiny(one),iout)
3203 
3204 !  xc_tb09_c
3205    call chkdpr(0,0,cond_string,cond_values,ierr,'xc_tb09_c',dt%xc_tb09_c,1,0.0_dp,iout)
3206 
3207 !  xred
3208 !  Check that two atoms are not on top of each other
3209    do iimage=1,dt%nimage
3210      if(natom>1)then
3211        ABI_ALLOCATE(frac,(3,natom))
3212        do ia=1,natom
3213 !        Map reduced coordinate xred(mu,ia) into [0,1)
3214          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))
3215          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))
3216          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))
3217        end do
3218        do ia=1,natom-1
3219          do ib=ia+1,natom
3220            if( abs(frac(1,ia)-frac(1,ib))<1.0d-6 .and. &
3221 &           abs(frac(2,ia)-frac(2,ib))<1.0d-6 .and. &
3222 &           abs(frac(3,ia)-frac(3,ib))<1.0d-6         ) then
3223              if(iimage>1)then
3224                write(message,'(2a,i5)') ch10,' The following was observed for image=',iimage
3225                call wrtout(iout,message,'COLL')
3226                call wrtout(std_out,message,'COLL')
3227              end if
3228              write(message, '(a,i4,a,i4,a,a,a,a,a,a)' )&
3229 &             'Atoms number',ia,' and',ib,' are located at the same point',' of the unit cell',ch10,&
3230 &             '(periodic images are taken into account).',ch10,&
3231 &             'Action: change the coordinate of one of these atoms in the input file.'
3232              MSG_ERROR_NOSTOP(message,ierr)
3233            end if
3234          end do
3235        end do
3236        ABI_DEALLOCATE(frac)
3237      end if
3238    end do
3239 
3240 !  znucl
3241 !  Check that znucl and znuclpsp agree
3242    do ipsp=1,npsp
3243      if (abs(dt%znucl(ipsp)-pspheads(ipsp)%znuclpsp)> tol12 ) then
3244        write(message, '(a,i0,a,es12.4,a,a,es12.4,2a)' )&
3245 &       'For pseudopotential ',ipsp,'  znucl from user input file= ',dt%znucl(ipsp),ch10,&
3246 &       'while znucl from pseudopotential file=',pspheads(ipsp)%znuclpsp,ch10,&
3247 &       'Action: check znucl in input file, or check psp file. They must agree.'
3248        MSG_ERROR_NOSTOP(message,ierr)
3249      end if
3250    end do
3251 
3252 !  bandFFT
3253    if(dt%paral_kgb==1.and.dt%optdriver==RUNL_GSTATE) then
3254      if (mod(dt%wfoptalg,10) /= 4 .and. dt%wfoptalg /= 1) then
3255        write(message,'(a,i0,a,a,a,a)')&
3256 &       'The value of wfoptalg is found to be ',dt%wfoptalg,ch10,&
3257 &       'This is not allowed in the case of band-FFT parallelization.',ch10,&
3258 &       'Action: put wfoptalg = 4, 14 or 114 in your input file'
3259        MSG_ERROR_NOSTOP(message,ierr)
3260      end if
3261 !    Make sure all nband are equal
3262      if (any(dt%nband(1:nkpt*nsppol) /= maxval(dt%nband(1:nkpt*nsppol)) )) then
3263        write(message,'(a,a,a)')&
3264 &       'The number of bands have to remain constant in the case of band-FFT parallelization.',ch10,&
3265 &       'Action: set all the nbands to the same value in your input file'
3266        MSG_ERROR_NOSTOP(message,ierr)
3267      end if
3268      if(maxval(abs(dt%istwfk(1:nkpt)-1)) > 1)then
3269        write(message,'(5a)' )&
3270 &       'One of the components of istwfk is not equal to 1 or 2.',ch10,&
3271 &       'Time-reversal symmetry is not yet programmed in the case of band-FFT parallelization.',ch10,&
3272 &       'Action: set istwfk to 1 or 2 for all k-points'
3273        MSG_ERROR_NOSTOP(message,ierr)
3274      end if
3275      if (dt%mkmem == 0) then
3276        write(message,'(a,i0,a,a,a,a)')&
3277 &       'The value of mkmem is found to be ',dt%mkmem,ch10,&
3278 &       'An out-of-core solution can''t be used in the case of band-FFT parallelization.',ch10,&
3279 &       'Action: put mkmem = nkpt in your input file'
3280        MSG_ERROR_NOSTOP(message,ierr)
3281      end if
3282    end if
3283 
3284 !  WVL - wavelets checks and limitations
3285    if(dt%usewvl == 1) then
3286      if (dt%wvl_hgrid <= 0) then
3287        write(message,'(a,i0,a,a,a,a)')&
3288 &       'The value of wvl_hgrid is found to be ',dt%wvl_hgrid,ch10,&
3289 &       'This value is mandatory and must be positive.',ch10,&
3290 &       'Action: put wvl_hgrid to a positive value in your input file'
3291        MSG_ERROR_NOSTOP(message,ierr)
3292      end if
3293      if (dt%nsym /= 1 .and. dt%icoulomb == 1) then
3294        write(message,'(a,i0,a,a,a,a)')&
3295 &       'The value of nsym is found to be ',dt%nsym,ch10,&
3296 &       'No symetry operations are allowed for isolated systems.',ch10,&
3297 &       'Action: put nsym = 1 in your input file'
3298        MSG_ERROR_NOSTOP(message,ierr)
3299      end if
3300      if (dt%optstress > 0) then
3301        write(message,'(a,i0,a,a,a,a)')&
3302 &       'The value of optstress is found to be ', dt%optstress, ch10,&
3303 &       'There is no stress computation available with the wavelet code.',ch10,&
3304 &       'Action: put optstress = 0 in your input file'
3305        MSG_ERROR_NOSTOP(message,ierr)
3306      end if
3307      if (usepaw == 1) then
3308        MSG_WARNING('WVL+PAW is under development')
3309      end if
3310      if (dt%nspden > 2) then
3311        write(message,'(a,i0,a,a,a,a)')&
3312 &       'The value of nspden is found to be ', dt%nspden, ch10, &
3313 &       'The wavelet computation is not allowed with non-colinear spin.',ch10,&
3314 &       'Action: put nspden = 1 or 2 in your input file'
3315        MSG_ERROR_NOSTOP(message,ierr)
3316      end if
3317      if (dt%nspden /= dt%nsppol) then
3318        write(message,'(a,i0,a,a,i0,a,a)')&
3319 &       'The value of nspden is found to be ', dt%nspden, ch10, &
3320 &       'and the one of nsppol is found to be ', dt%nsppol, ch10, &
3321 &       'In wavelet computation, nspden and nsppol must be equal.'
3322        MSG_ERROR_NOSTOP(message,ierr)
3323      end if
3324 !    We check the consistency of occupation, empty bands are not allowed.
3325      if (dt%nsppol == 2) then
3326        mband = dt%nelect
3327      else
3328        mband = dt%mband
3329      end if
3330      do ii = 1, mband, 1
3331        if (dt%occ_orig(ii) < tol8 .and. dt%iscf == 0) then
3332          write(message,'(a,f7.4,a,a,a,a,a,a)')&
3333 &         'One value of occ is found to be ', dt%occ_orig(ii), ch10, &
3334 &         'The direct minimization is not allowed with empty bands.',ch10,&
3335 &         'Action: use occopt = 1 for automatic band filling or', ch10, &
3336 &         'change occ value in your input file'
3337          MSG_ERROR_NOSTOP(message,ierr)
3338        end if
3339      end do
3340      if (npsp /= dt%ntypat) then
3341        write(message, '(a,a,a,a,I0,a,I0,a,a,a)' ) ch10,&
3342 &       'wvl_wfs_set:  consistency checks failed,', ch10, &
3343 &       'dtset%npsp (', npsp, ') /= dtset%ntypat (', dt%ntypat, ').', ch10, &
3344 &       'No alchemy pseudo are allowed with wavelets.'
3345        MSG_ERROR_NOSTOP(message,ierr)
3346      end if
3347    end if
3348 
3349    ! Test on tolerances (similar tests are performed in scprqt, so keep the two versions in synch)
3350    if (any(optdriver == [RUNL_GSTATE, RUNL_RESPFN])) then
3351      ttolwfr=0 ; ttoldff=0 ; ttoldfe=0 ; ttolvrs=0; ttolrff=0
3352      if(abs(dt%tolwfr)>tiny(zero))ttolwfr=1
3353      if(abs(dt%toldff)>tiny(zero))ttoldff=1
3354      if(abs(dt%tolrff)>tiny(zero))ttolrff=1
3355      if(abs(dt%toldfe)>tiny(zero))ttoldfe=1
3356      if(abs(dt%tolvrs)>tiny(zero))ttolvrs=1
3357 
3358      ! If non-scf calculations, tolwfr must be defined
3359      if(ttolwfr /= 1 .and. ((dt%iscf<0 .and. dt%iscf/=-3) .or. dt%rf2_dkdk/=0 .or. dt%rf2_dkde/=0))then
3360        write(message,'(a,a,a,es14.6,a,a)')&
3361 &       'when iscf <0 and /= -3, or when rf2_dkdk/=0 or rf2_dkde/=0, tolwfr must be strictly',ch10,&
3362 &       'positive, while it is ',dt%tolwfr,ch10,&
3363 &       'Action: change tolwfr in your input file and resubmit the job.'
3364        MSG_ERROR_NOSTOP(message, ierr)
3365      end if
3366      !  toldff only allowed when prtfor==1
3367      !if((ttoldff == 1 .or. ttolrff == 1) .and. dt%prtfor==0 )then
3368      !  MSG_ERROR_NOSTOP('toldff only allowed when prtfor=1!', ierr)
3369      !end if
3370 
3371      ! If SCF calculations, one and only one of these can differ from zero
3372      ! FIXME: this test should be done on input, not during calculation
3373      if(ttolwfr+ttoldff+ttoldfe+ttolvrs+ttolrff /= 1 .and. (dt%iscf>0 .or. dt%iscf==-3))then
3374        write(message,'(6a,es14.6,a,es14.6,a,es14.6,a,es14.6,a,a,es14.6,a,a,a)' )&
3375 &       'For the SCF case, one and only one of the input tolerance criteria ',ch10,&
3376 &       'tolwfr, toldff, tolrff, toldfe or tolvrs ','must differ from zero, while they are',ch10,&
3377 &       'tolwfr=',dt%tolwfr,', toldff=',dt%toldff,', tolrff=',dt%tolrff,', toldfe=',dt%toldfe,ch10,&
3378 &       'and tolvrs=',dt%tolvrs,' .',ch10,&
3379 &       'Action: change your input file and resubmit the job.'
3380        MSG_ERROR_NOSTOP(message, ierr)
3381      end if
3382    end if
3383 
3384 
3385 !  If molecular dynamics or structural optimization is being done
3386 !  (dt%ionmov>0), make sure not all atoms are fixed
3387 !  if (dt%ionmov > 0) then
3388 !  if (natfix == natom) then
3389 !  write(message, '(a,a,a,a,i4,a,i5,a,a,i5,a,a,a,a,a,a)' ) ch10,&
3390 !  &   ' setup1: ERROR -',ch10,&
3391 !  &   '  ionmov is ',dt%ionmov,' and number of fixed atoms is ',natfix,ch10,&
3392 !  &   '  while number of atoms natom is ',natom,'.',ch10,&
3393 !  &   '  Thus all atoms are fixed and option ionmov to move atoms',&
3394 !  &           ' is inconsistent.',ch10,&
3395 !  &   '  Action: change ionmov or natfix and iatfix in input file and resubmit.'
3396 !  call wrtout(std_out,message,"COLL")
3397 !  ierr = ierr + 1
3398 !  end if
3399 !  end if
3400 
3401 !  Should check that the symmetry operations are consistent with iatfixx,
3402 !  iatfixy and iatfixz (diagonal symmetry operations)
3403 
3404 !  Should check values of fftalg
3405 
3406 !  rfasr=2 possible only when electric field response is computed.
3407 
3408 !  Must have nqpt=1 for rfphon=1
3409 
3410 !  ** Here ends the checking section **************************************
3411 
3412    call dtset_free(dt)
3413    ierr_dtset(idtset)=ierr
3414 
3415  end do !  End do loop on idtset
3416 
3417  if (maxval(dtsets(:)%usewvl) > 0) then
3418    write(message,'(4a)') ch10,&
3419 &   ' Comparison between wvl_hgrid and ecut',ch10,&
3420 &   '  real-space mesh | eq. Ec around atoms | eq. Ec further from atoms'
3421    MSG_COMMENT(message)
3422    wvl_hgrid = zero
3423    twvl = .false.
3424    do idtset=1,ndtset_alloc
3425 !    Give an indication to the equivalent ecut corresponding to
3426 !    given hgrid.
3427      if (dtsets(idtset)%usewvl == 1 .and. &
3428 &     wvl_hgrid /= dtsets(idtset)%wvl_hgrid) then
3429        write(message,'(F11.3,A,F16.1,A,F16.1,A)') &
3430 &       dtsets(idtset)%wvl_hgrid, " bohr  |", &
3431 &       two * pi * pi / (dtsets(idtset)%wvl_hgrid ** 2), " Ht  | ", &
3432 &       half * pi * pi / (dtsets(idtset)%wvl_hgrid ** 2), " Ht"
3433        call wrtout(std_out,message,'COLL')
3434        wvl_hgrid = dtsets(idtset)%wvl_hgrid
3435      end if
3436      twvl = twvl .or. (dtsets(idtset)%usewvl == 1 .and. dtsets(idtset)%iomode /= IO_MODE_ETSF)
3437    end do
3438    if (twvl) then
3439      write(message,'(5a)') &
3440 &     'Restart files from wavelets in non ETSF format does not follow', ch10, &
3441 &     'the ABINIT standards.', ch10, &
3442 &     'Put iomode to 3 to use ETSF retart files.'
3443      MSG_WARNING(message)
3444    end if
3445  end if
3446 
3447 !If there was a problem, then stop.
3448  call xmpi_sum(ierr_dtset,xmpi_world,mpierr)
3449  ierr=sum(ierr_dtset(1:ndtset_alloc)/mpi_enregs(1:ndtset_alloc)%nproc)
3450 
3451  if (ierr==1) then
3452    write(message,'(a,i0,3a)')&
3453 &   'Checking consistency of input data against itself gave ',ierr,' inconsistency.',ch10,&
3454 &   'The details of the problem can be found above.'
3455    MSG_ERROR(message)
3456  end if
3457  if (ierr>1) then
3458    write(message,'(a,i0,3a)')&
3459 &   'Checking consistency of input data against itself gave ',ierr,' inconsistencies.',ch10,&
3460 &   'The details of the problems can be found above.'
3461    MSG_ERROR(message)
3462  end if
3463 
3464  ABI_DEALLOCATE(ierr_dtset)
3465 
3466  if (ndtset_alloc /= 1 .and. get_timelimit() > zero) then
3467    MSG_ERROR("--timelimit option cannot be used when ndtset > 1")
3468  end if
3469 
3470  DBG_EXIT("COLL")
3471 
3472 end subroutine chkinp