XClib - output unit fix

This commit is contained in:
fabrizio22 2021-02-15 20:23:10 +01:00
parent caa4803e24
commit a03d63f8e6
7 changed files with 40 additions and 32 deletions

View File

@ -13,7 +13,7 @@ set(sources_xclib
qe_funct_mgga.f90
qe_kind.f90
xclib_error.f90
xclib_para_m.f90
xclib_utils_and_para.f90
xc_beef_interface.f90
xc_input_params_mod.f90
xc_lib.f90

View File

@ -3,7 +3,7 @@
include ../make.inc
XCL = \
xclib_para_m.o \
xclib_utils_and_para.o \
xclib_error.o \
qe_kind.o \
qe_constants.o \

View File

@ -10,6 +10,7 @@ MODULE dft_mod
!--------------------------------------------------------------------------
!! Routines to set and/or recover DFT names, parameters and flags.
!
USE xclib_utils_and_para, ONLY: stdout
#if defined(__LIBXC)
#include "xc_version.h"
USE xc_f03_lib_m
@ -336,24 +337,24 @@ CONTAINS
ENDDO
!
IF ( n_ext_params /= 0 ) THEN
WRITE( *, '(/5X,"WARNING: libxc functional with ID ",I4," depends",&
&/5X," on external parameters: the correct operation in",&
&/5X," QE is not guaranteed with default values.")' ) id_vec(ii)
WRITE(stdout,'(/5X,"WARNING: libxc functional with ID ",I4," depends",&
&/5X," on external parameters: the correct operation in",&
&/5X," QE is not guaranteed with default values.")' ) id_vec(ii)
ENDIF
IF ( flag_v(1) == 0 ) THEN
WRITE( *, '(/5X,"WARNING: libxc functional with ID ",I4," does not ",&
&/5X,"provide Exc: its correct operation in QE is not ",&
&/5X,"guaranteed.")' ) id_vec(ii)
WRITE(stdout,'(/5X,"WARNING: libxc functional with ID ",I4," does not ",&
&/5X,"provide Exc: its correct operation in QE is not ",&
&/5X,"guaranteed.")' ) id_vec(ii)
ENDIF
IF ( flag_v(2) == 0 ) THEN
WRITE( *, '(/5X,"WARNING: libxc functional with ID ",I4," does not ",&
&/5X,"provide Vxc: its correct operation in QE is not ",&
&/5X,"guaranteed.")' ) id_vec(ii)
WRITE(stdout,'(/5X,"WARNING: libxc functional with ID ",I4," does not ",&
&/5X,"provide Vxc: its correct operation in QE is not ",&
&/5X,"guaranteed.")' ) id_vec(ii)
ENDIF
IF (dftout(1:3) .EQ. 'XC-' .AND. flag_v(3) == 0 ) THEN
WRITE( *, '(/5X,"WARNING: libxc functional with ID ",I4," does not ",&
&/5X,"provide Vxc derivative: its correct operation in QE is",&
&/5X," not guaranteed when derivative is needed.")' ) id_vec(ii)
WRITE(stdout,'(/5X,"WARNING: libxc functional with ID ",I4," does not ",&
&/5X,"provide Vxc derivative: its correct operation in QE is",&
&/5X," not guaranteed when derivative is needed.")' ) id_vec(ii)
ENDIF
CALL xc_f03_func_end( xc_func03 )
ENDIF
@ -386,27 +387,27 @@ CONTAINS
! check dft has not been previously set differently
!
IF (save_iexch /= notset .AND. save_iexch /= iexch) THEN
WRITE(*,*) iexch, save_iexch
WRITE(stdout,*) iexch, save_iexch
CALL xclib_error( 'set_dft_from_name', ' conflicting values for iexch', 1 )
ENDIF
IF (save_icorr /= notset .AND. save_icorr /= icorr) THEN
WRITE(*,*) icorr, save_icorr
WRITE(stdout,*) icorr, save_icorr
CALL xclib_error( 'set_dft_from_name', ' conflicting values for icorr', 1 )
ENDIF
IF (save_igcx /= notset .AND. save_igcx /= igcx) THEN
WRITE(*,*) igcx, save_igcx
WRITE(stdout,*) igcx, save_igcx
CALL xclib_error( 'set_dft_from_name', ' conflicting values for igcx', 1 )
ENDIF
IF (save_igcc /= notset .AND. save_igcc /= igcc) THEN
WRITE (*,*) igcc, save_igcc
WRITE(stdout,*) igcc, save_igcc
CALL xclib_error( 'set_dft_from_name', ' conflicting values for igcc', 1 )
ENDIF
IF (save_meta /= notset .AND. save_meta /= imeta) THEN
WRITE (*,*) imeta, save_meta
WRITE(stdout,*) imeta, save_meta
CALL xclib_error( 'set_dft_from_name', ' conflicting values for imeta', 1 )
ENDIF
IF (save_metac /= notset .AND. save_metac /= imetac) THEN
WRITE (*,*) imetac, save_metac
WRITE(stdout,*) imetac, save_metac
CALL xclib_error( 'set_dft_from_name', ' conflicting values for imetac', 1 )
ENDIF
!
@ -473,7 +474,7 @@ CONTAINS
!WRITE(*, '("matches",i2,2X,A,2X,A)') i, name(i), TRIM(dft)
matching = i
ELSE
WRITE(*, '(2(2X,i2,2X,A))') i, TRIM(name(i)), &
WRITE(stdout, '(2(2X,i2,2X,A))') i, TRIM(name(i)), &
matching, TRIM(name(matching))
CALL xclib_error( 'set_dft', 'two conflicting matching values', 1 )
ENDIF
@ -826,7 +827,7 @@ CONTAINS
REAL(DP), INTENT(IN) :: exx_fraction_
!! Imposed value of exact exchange fraction
exx_fraction = exx_fraction_
WRITE( *,'(5x,a,f6.2)') 'EXX fraction changed: ', exx_fraction
WRITE( stdout,'(5x,a,f6.2)') 'EXX fraction changed: ', exx_fraction
RETURN
END SUBROUTINE xclib_set_exx_fraction
!-----------------------------------------------------------------------
@ -878,7 +879,7 @@ CONTAINS
REAL(DP):: scrparm_
!! Value to impose as screening parameter
screening_parameter = scrparm_
WRITE( *,'(5x,a,f12.7)') 'EXX Screening parameter changed: ', &
WRITE(stdout,'(5x,a,f12.7)') 'EXX Screening parameter changed: ', &
& screening_parameter
END SUBROUTINE set_screening_parameter
!-----------------------------------------------------------------------
@ -900,7 +901,7 @@ CONTAINS
REAL(DP):: gauparm_
!! Value to impose as gau parameter
gau_parameter = gauparm_
WRITE( *,'(5x,a,f12.7)') 'EXX Gau parameter changed: ', &
WRITE(stdout,'(5x,a,f12.7)') 'EXX Gau parameter changed: ', &
& gau_parameter
END SUBROUTINE set_gau_parameter
!-----------------------------------------------------------------------

View File

@ -1,5 +1,6 @@
dft_mod.o : qe_kind.o
dft_mod.o : xc_input_params_mod.o
dft_mod.o : xclib_utils_and_para.o
qe_constants.o : qe_kind.o
qe_drivers_d_gga.o : qe_drivers_gga.o
qe_drivers_d_gga.o : qe_kind.o
@ -54,11 +55,11 @@ xc_wrapper_mgga.o : dft_mod.o
xc_wrapper_mgga.o : qe_drivers_mgga.o
xc_wrapper_mgga.o : qe_kind.o
xc_wrapper_mgga.o : xc_input_params_mod.o
xclib_error.o : xclib_para_m.o
xclib_error.o : xclib_utils_and_para.o
xclib_test.o : qe_constants.o
xclib_test.o : qe_kind.o
xclib_test.o : xc_input_params_mod.o
xclib_test.o : xc_lib.o
xclib_test.o : xclib_para_m.o
xclib_test.o : xclib_utils_and_para.o
beefun.o : beefleg.h
beefun.o : pbecor.h

View File

@ -12,7 +12,8 @@ SUBROUTINE xclib_error( calling_routine, message, ierr )
!! This is a simple routine which writes an error message to output (copied
!! from laxlib).
!
USE xclib_parallel_include
USE xclib_utils_and_para
!
IMPLICIT NONE
!
CHARACTER(LEN=*), INTENT(IN) :: calling_routine
@ -57,6 +58,8 @@ SUBROUTINE xclib_infomsg( calling_routine, message )
!----------------------------------------------------------------------------
!! This is a simple routine which writes an info/warning message to output.
!
USE xclib_utils_and_para, ONLY: stdout
!
IMPLICIT NONE
!
CHARACTER (LEN=*), INTENT(IN) :: calling_routine
@ -64,8 +67,8 @@ SUBROUTINE xclib_infomsg( calling_routine, message )
CHARACTER (LEN=*), INTENT(IN) :: message
!! the output message
!
WRITE( UNIT = * , FMT = '(5X,"Message from routine ",A,":")' ) calling_routine
WRITE( UNIT = * , FMT = '(5X,A)' ) message
WRITE( UNIT=stdout ,FMT = '(5X,"Message from routine ",A,":")' ) calling_routine
WRITE( UNIT=stdout ,FMT = '(5X,A)' ) message
!
RETURN
!

View File

@ -31,7 +31,7 @@ PROGRAM xclib_test
xclib_get_ID, xclib_reset_dft, xc_gcx, &
xclib_dft_is_libxc, xclib_init_libxc, &
xclib_finalize_libxc
USE xclib_parallel_include
USE xclib_utils and_para
#if defined(__LIBXC)
#include "xc_version.h"
USE xc_f03_lib_m

View File

@ -7,7 +7,7 @@
! or http://www.gnu.org/copyleft/gpl.txt .
!
!-----------------------------------------------------
MODULE xclib_parallel_include
MODULE xclib_utils_and_para
!-----------------------------------------------------
!! MPI stuff
!
@ -26,4 +26,7 @@ MODULE xclib_parallel_include
INTEGER, PARAMETER :: MPI_COMM_NULL = -1
INTEGER, PARAMETER :: MPI_COMM_SELF = -2
#endif
END MODULE xclib_parallel_include
! standard output unit
INTEGER, PARAMETER :: stdout = 6
!
END MODULE xclib_utils_and_para