Small cleanup. Misleading error messages.

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@9536 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
dalcorso 2012-10-15 15:05:43 +00:00
parent f651c58175
commit 0bcf7f7214
8 changed files with 20 additions and 20 deletions

View File

@ -242,7 +242,7 @@ CONTAINS
lm = l**2 + m
n_starting_wfc = n_starting_wfc + 1
IF (n_starting_wfc + 2*l + 1 > natomwfc) CALL errore &
('atomic_wfc_nc', 'internal error: too many wfcs', 1)
('atomic_wfc_nc_z', 'internal error: too many wfcs', 1)
DO ig=1,npw
aux(ig) = sk(ig)*ylm(ig,lm)*chiq(ig,nb,nt)
ENDDO

View File

@ -210,7 +210,7 @@ PROGRAM average
DEALLOCATE (ityps)
DEALLOCATE (taus)
!
IF (nats>nat) CALL errore ('chdens', 'wrong file order? ', 1)
IF (nats>nat) CALL errore ('average', 'wrong file order? ', 1)
IF (dfftp%nr1x/=nr1sxa.or.dfftp%nr2x/=nr2sxa) &
CALL errore ('average', 'incompatible nr1x or nr2x', 1)
IF (dfftp%nr1/=nr1sa.or.dfftp%nr2/=nr2sa.or.dfftp%nr3/=nr3sa) &
@ -220,7 +220,7 @@ PROGRAM average
CALL errore ('average', 'incompatible gcutm or dual or ecut', 1)
DO i = 1, 6
IF (abs( celldm (i)-celldms (i) ) > 1.0d-7 ) &
CALL errore ('chdens', 'incompatible celldm', 1)
CALL errore ('average', 'incompatible celldm', 1)
ENDDO
DO ir = 1, dfftp%nnr
psic (ir) = psic (ir) + weight(ifile) * cmplx(rho%of_r(ir, 1),0.d0,kind=DP)

View File

@ -367,7 +367,7 @@ SUBROUTINE chdens (filplot,plot_num)
&" not implemented for Gamma only!",/, &
&"SOLUTION: restart this calculation with", &
&" emtpy namelist &inputpp")')
CALL errore ('punch_plot','Not implemented, please read above',1)
CALL errore ('chdens','Not implemented, please read above',1)
ENDIF
!
ENDIF

View File

@ -122,7 +122,7 @@ SUBROUTINE do_initial_state (excite)
!
! ... The Hubbard contribution
!
IF ( lda_plus_u ) CALL errore('initial_state','LDA+U not implemented',1)
IF ( lda_plus_u ) CALL errore('do_initial_state','LDA+U not implemented',1)
!
! change atomic type and recompute needed quantities

View File

@ -235,7 +235,7 @@ PROGRAM PAWplot
ENDIF
CALL mp_bcast (ios, ionode_id)
IF ( ios /= 0) &
CALL errore ('postproc', 'reading inputpp namelist', abs(ios))
CALL errore ('pawplot', 'reading inputpp namelist', abs(ios))
!
! ... Broadcast variables
!
@ -281,7 +281,7 @@ PROGRAM PAWplot
!
! One-dimensional plot
!
IF (nx <= 0 ) CALL errore ('chdens', 'wrong nx', 1)
IF (nx <= 0 ) CALL errore ('pawplot', 'wrong nx', 1)
ALLOCATE ( rhoplot(nx) )
IF ( okpaw ) THEN
WRITE (stdout, '(5x,"Reconstructing all-electron charge (PAW)")')
@ -317,10 +317,10 @@ PROGRAM PAWplot
ELSEIF ( twodim ) THEN
IF ( abs(e1(1)*e2(1) + e1(2)*e2(2) + e1(3)*e2(3)) > 1d-6) &
CALL errore ('pawplot', 'e1 and e2 are not orthogonal', 1)
IF ( nx <= 0 .or. ny <= 0 ) CALL errore ('chdens', 'wrong nx or ny', 1)
IF ( nx <= 0 .or. ny <= 0 ) CALL errore ('pawplot', 'wrong nx or ny', 1)
ELSEIF (tredim) THEN
IF ( nx <= 0 .or. ny <= 0 .or. nz <=0 ) &
CALL errore ('chdens', 'wrong nx or ny or nz', 1)
CALL errore ('pawplot', 'wrong nx or ny or nz', 1)
ENDIF
!
DEALLOCATE (rhog)

View File

@ -102,7 +102,7 @@ PROGRAM do_projwfc
!
IF (ios /= 0) WRITE (stdout, &
'("*** namelist &inputpp no longer valid: please use &projwfc instead")')
IF (ios /= 0) CALL errore ('projwfc', 'reading projwfc namelist', abs (ios) )
IF (ios /= 0) CALL errore ('do_projwfc', 'reading projwfc namelist', abs (ios) )
!
! ... Broadcast variables
!
@ -154,7 +154,7 @@ PROGRAM do_projwfc
!
IF ( tdosinboxes ) THEN
IF( nproc_ortho > 1 ) THEN
CALL errore ('projwfc', 'nproc_ortho > 1 not yet implemented', 1)
CALL errore ('do_projwfc', 'nproc_ortho > 1 not yet implemented', 1)
ELSE
CALL projwave_boxes (filpdos, filproj, n_proj_boxes, irmin, irmax, plotboxes)
ENDIF
@ -682,7 +682,7 @@ SUBROUTINE projwave( filproj, lsym, lgww, lwrite_ovp, lbinary )
ELSEIF ( nspin == 2 ) THEN
current_spin = isk ( ik )
ELSE
CALL errore ('projwfc_nc',' called in the wrong case ',1)
CALL errore ('projave',' called in the wrong case ',1)
ENDIF
DO ibnd = 1, nbnd
DO nwfc = 1, natomwfc
@ -1880,7 +1880,7 @@ SUBROUTINE write_io_header(filplot, iunplot, title, nr1x, nr2x, nr3x, &
OPEN (UNIT = iunplot, FILE = filplot, FORM = 'formatted', &
STATUS = 'unknown', ERR = 101, IOSTAT = ios)
101 CALL errore ('write_io_h', 'opening file '//trim(filplot), abs (ios) )
101 CALL errore ('write_io_header', 'opening file '//trim(filplot), abs (ios) )
WRITE (iunplot, '(a)') title
WRITE (iunplot, '(8i8)') nr1x, nr2x, nr3x, nr1, nr2, nr3, nat, ntyp
WRITE (iunplot, '(i6,6f12.8)') ibrav, celldm
@ -2214,8 +2214,8 @@ SUBROUTINE pprojwave( filproj, lsym, lwrite_ovp, lbinary )
ENDDO
ENDDO
!
IF (lmax_wfc > 3) CALL errore ('projwave', 'l > 3 not yet implemented', 1)
IF (nwfc /= natomwfc) CALL errore ('projwave', 'wrong # of atomic wfcs?', 1)
IF (lmax_wfc > 3) CALL errore ('pprojwave', 'l > 3 not yet implemented', 1)
IF (nwfc /= natomwfc) CALL errore ('pprojwave', 'wrong # of atomic wfcs?', 1)
!
!
IF( ionode ) THEN
@ -2395,7 +2395,7 @@ SUBROUTINE pprojwave( filproj, lsym, lwrite_ovp, lbinary )
nlmchi(nwfc1)%l == nlmchi(nwfc)%l .and. &
nlmchi(nwfc1)%m == 1 ) GOTO 10
ENDDO
CALL errore('projwave','cannot symmetrize',1)
CALL errore('pprojwave','cannot symmetrize',1)
10 nwfc1=nwfc1-1
!
! nwfc1 is the first rotated atomic wfc corresponding to nwfc
@ -2629,7 +2629,7 @@ SUBROUTINE pprojwave( filproj, lsym, lwrite_ovp, lbinary )
ELSEIF ( nspin == 2 ) THEN
current_spin = isk ( ik )
ELSE
CALL errore ('projwfc_nc',' called in the wrong case ',1)
CALL errore ('pprojwave',' called in the wrong case ',1)
ENDIF
DO ibnd = 1, nbnd
DO nwfc = 1, natomwfc

View File

@ -54,9 +54,9 @@ SUBROUTINE sym_band(filband, spin_component, firstk, lastk)
CHARACTER (len=256) :: filband, namefile
!
IF (spin_component/=1.and.nspin/=2) &
CALL errore('punch_bands','incorrect spin_component',1)
CALL errore('sym_band','incorrect spin_component',1)
IF (spin_component<1.or.spin_component>2) &
CALL errore('punch_bands','incorrect lsda spin_component',1)
CALL errore('sym_band','incorrect lsda spin_component',1)
ALLOCATE(rap_et(nbnd,nkstot))
ALLOCATE(code_group_k(nkstot))

View File

@ -44,7 +44,7 @@ SUBROUTINE xk_et_collect( xk_collect, et_collect, xk, et, nkstot, nks, nbnd )
IF ( ( my_pool_id + 1 ) <= rest ) nks1 = nks1 + kunit
!
IF (nks1.ne.nks) &
call errore('xk_wk_collect','problems with nks1',1)
call errore('xk_et_collect','problems with nks1',1)
!
! ... calculates nbase = the position in the list of the first point that
! ... belong to this npool - 1