! ! Copyright (C) 2015-2017 M. Govoni ! This file is distributed under the terms of the ! GNU General Public License. See the file `License' ! in the root directory of the present distribution, ! or http://www.gnu.org/copyleft/gpl.txt . ! ! This file is part of WEST. ! ! Contributors to this file: ! Marco Govoni ! !----------------------------------------------------------------------- SUBROUTINE fetch_input( num_drivers, driver, verbose ) !----------------------------------------------------------------------- ! USE json_module, ONLY : json_file USE westcom USE io_files, ONLY : tmp_dir, prefix USE io_global, ONLY : stdout USE mp, ONLY : mp_bcast USE mp_world, ONLY : mpime,root,world_comm USE mp_global, ONLY : nimage USE io_push, ONLY : io_push_title,io_push_value,io_push_bar,io_push_es0,io_push_c512 USE gvect, ONLY : ecutrho USE start_k, ONLY : nk1, nk2, nk3 USE control_flags, ONLY : gamma_only ! IMPLICIT NONE ! ! I/O ! INTEGER, INTENT(IN) :: num_drivers INTEGER, INTENT(IN) :: driver(num_drivers) LOGICAL, INTENT(IN) :: verbose ! ! Workspace ! TYPE(json_file) :: json INTEGER :: i INTEGER :: iiarg, nargs INTEGER :: numsp LOGICAL :: found CHARACTER (LEN=512) :: input_file CHARACTER(LEN=512), EXTERNAL :: trimcheck CHARACTER(LEN=:),ALLOCATABLE :: cval REAL(DP) :: rval INTEGER :: ival INTEGER,ALLOCATABLE :: ivec(:) REAL(DP),ALLOCATABLE :: rvec(:) LOGICAL :: lval INTEGER :: iunit ! CALL start_clock('fetch_input') ! ! PRESETS ! ! ** input_west ** IF ( ANY(driver(:)==1) ) THEN qe_prefix = 'pwscf' west_prefix = 'west' CALL get_environment_variable( 'ESPRESSO_TMPDIR', outdir ) IF ( trim( outdir ) == ' ' ) outdir = './' ENDIF ! ! ** wstat_control ** IF ( ANY(driver(:)==2) ) THEN ! ! ** WARNING ** : In order to properly initialize these variables, this driver ! can be called only after: ! - fetch_input( driver 1 ) ! - read_pwout() ! wstat_calculation = 'S' n_pdep_eigen = 1 n_pdep_times = 4 n_pdep_maxiter = 100 n_dfpt_maxiter = 250 n_pdep_read_from_file = 0 trev_pdep = 1.d-3 trev_pdep_rel = 1.d-1 tr2_dfpt = 1.d-12 l_kinetic_only = .FALSE. l_minimize_exx_if_active = .FALSE. l_use_ecutrho = .FALSE. IF( ALLOCATED(qlist) ) DEALLOCATE(qlist) IF ( gamma_only ) THEN ALLOCATE( qlist(1) ) qlist(1) = 1 ELSE ALLOCATE(qlist(nk1*nk2*nk3)) qlist = (/ (i, i=1,nk1*nk2*nk3,1) /) ENDIF ENDIF ! ! ** wfreq_control ** IF ( ANY(driver(:)==3) ) THEN ! ! ** WARNING ** : In order to properly initialize these variables, this driver ! can be called only after: ! - fetch_input( driver 1 ) ! - read_pwout() ! wfreq_calculation = 'XWGQ' n_pdep_eigen_to_use = 2 qp_bandrange = (/ 1, 2 /) macropol_calculation = 'N' n_lanczos = 20 n_imfreq = 128 n_refreq = 10 ecut_imfreq = ecutrho ecut_refreq = 2._DP wfreq_eta = 0.003675_DP n_secant_maxiter = 1 trev_secant = 0.003675_DP l_enable_lanczos = .TRUE. l_enable_gwetot = .FALSE. o_restart_time = 0._DP ecut_spectralf = (/ -2._DP, 2._DP /) n_spectralf = 10 ENDIF ! ! ** westpp_control ** IF ( ANY(driver(:)==4) ) THEN westpp_calculation = 'r' westpp_range = (/ 1, 2 /) westpp_format = 'C' westpp_sign = .FALSE. westpp_n_pdep_eigen_to_use = 1 westpp_r0 = (/ 0.d0, 0.d0, 0.d0 /) westpp_nr = 100 westpp_rmax = 1.d0 westpp_epsinfty = 1.d0 ENDIF ! ! READ the input ! IF ( mpime==root ) THEN ! ! CALL json%initialize() CALL json%load_file( filename = main_input_file ) ! IF ( ANY(driver(:)==1) ) THEN CALL json%get('input_west.qe_prefix', cval, found) IF( found ) qe_prefix = cval CALL json%get('input_west.west_prefix', cval, found) IF( found ) west_prefix = cval CALL json%get('input_west.outdir', cval, found) IF( found ) outdir = cval ENDIF ! IF ( ANY(driver(:)==2) ) THEN CALL json%get('wstat_control.wstat_calculation', cval, found) IF( found ) wstat_calculation = cval CALL json%get('wstat_control.n_pdep_eigen', ival, found) IF( found ) n_pdep_eigen = ival CALL json%get('wstat_control.n_pdep_times', ival, found) IF( found ) n_pdep_times = ival CALL json%get('wstat_control.n_pdep_maxiter', ival, found) IF( found ) n_pdep_maxiter = ival CALL json%get('wstat_control.n_dfpt_maxiter', ival, found) IF( found ) n_dfpt_maxiter = ival CALL json%get('wstat_control.n_pdep_read_from_file', ival, found) IF( found ) n_pdep_read_from_file = ival CALL json%get('wstat_control.trev_pdep', rval, found) IF( found ) trev_pdep = rval CALL json%get('wstat_control.trev_pdep_rel', rval, found) IF( found ) trev_pdep_rel = rval CALL json%get('wstat_control.tr2_dfpt', rval, found) IF( found ) tr2_dfpt = rval CALL json%get('wstat_control.l_kinetic_only', lval, found) IF( found ) l_kinetic_only = lval CALL json%get('wstat_control.l_minimize_exx_if_active', lval, found) IF( found ) l_minimize_exx_if_active = lval CALL json%get('wstat_control.l_use_ecutrho', lval, found) IF( found ) l_use_ecutrho = lval !CALL json%get('wstat_control.nq', ivec, found) !IF( found ) nq(1:3) = ivec(:) CALL json%get('wstat_control.qlist', ivec, found) IF( found ) THEN IF( ALLOCATED(qlist) ) DEALLOCATE(qlist) ALLOCATE(qlist(SIZE(ivec))) qlist(1:SIZE(ivec)) = ivec(1:SIZE(ivec)) ENDIF ENDIF ! IF ( ANY(driver(:)==3) ) THEN CALL json%get('wfreq_control.wfreq_calculation', cval, found) IF( found ) wfreq_calculation = cval CALL json%get('wfreq_control.n_pdep_eigen_to_use', ival, found) IF( found ) n_pdep_eigen_to_use = ival CALL json%get('wfreq_control.qp_bandrange', ivec, found) IF( found ) qp_bandrange(1:2) = ivec(:) ! CALL json%get('wfreq_control.qp_bandrange(2)', rval, found) ! IF( found ) qp_bandrange(2) = rval CALL json%get('wfreq_control.macropol_calculation', cval, found) IF( found ) macropol_calculation = cval CALL json%get('wfreq_control.n_lanczos', ival, found) IF( found ) n_lanczos = ival CALL json%get('wfreq_control.n_imfreq', ival, found) IF( found ) n_imfreq = ival CALL json%get('wfreq_control.n_refreq', ival, found) IF( found ) n_refreq = ival CALL json%get('wfreq_control.ecut_imfreq', rval, found) IF( found ) ecut_imfreq = rval CALL json%get('wfreq_control.ecut_refreq', rval, found) IF( found ) ecut_refreq = rval CALL json%get('wfreq_control.wfreq_eta', rval, found) IF( found ) wfreq_eta = rval CALL json%get('wfreq_control.n_secant_maxiter', ival, found) IF( found ) n_secant_maxiter = ival CALL json%get('wfreq_control.trev_secant', rval, found) IF( found ) trev_secant = rval CALL json%get('wfreq_control.l_enable_lanczos', lval, found) IF( found ) l_enable_lanczos = lval CALL json%get('wfreq_control.l_enable_gwetot', lval, found) IF( found ) l_enable_gwetot = lval CALL json%get('wfreq_control.o_restart_time', rval, found) IF( found ) o_restart_time = rval CALL json%get('wfreq_control.ecut_spectralf', rvec, found) IF( found ) ecut_spectralf(1:2) = rvec(1:2) ! CALL json%get('wfreq_control.ecut_spectralf(2)', rval, found) ! IF( found ) ecut_spectralf(2) = rval CALL json%get('wfreq_control.n_spectralf', ival, found) IF( found ) n_spectralf = ival ENDIF ! IF ( ANY(driver(:)==4) ) THEN CALL json%get('westpp_control.westpp_calculation', cval, found) IF( found ) westpp_calculation = cval CALL json%get('westpp_control.westpp_range', rvec, found) IF( found ) westpp_range(1:2) = rvec(1:2) ! CALL json%get('westpp_control.westpp_range(2)', rval, found) ! IF( found ) westpp_range(2) = rval CALL json%get('westpp_control.westpp_format', cval, found) IF( found ) westpp_format = cval CALL json%get('westpp_control.westpp_sign', lval, found) IF( found ) westpp_sign = lval CALL json%get('westpp_control.westpp_n_pdep_eigen_to_use', ival, found) IF( found ) westpp_n_pdep_eigen_to_use = ival CALL json%get('westpp_control.westpp_r0', rvec, found) IF( found ) westpp_r0(1:3) = rvec(1:3) ! CALL json%get('westpp_control.westpp_r0(2)', rval, found) ! IF( found ) westpp_r0(2) = rval ! CALL json%get('westpp_control.westpp_r0(3)', rval, found) ! IF( found ) westpp_r0(3) = rval CALL json%get('westpp_control.westpp_nr', ival, found) IF( found ) westpp_nr = ival CALL json%get('westpp_control.westpp_rmax', rval, found) IF( found ) westpp_rmax = rval CALL json%get('westpp_control.westpp_epsinfty', rval, found) IF( found ) westpp_epsinfty = rval ENDIF ! CALL json%destroy() ! ENDIF ! ! BCAST & CHECKS ! IF ( ANY(driver(:)==1) ) THEN ! CALL mp_bcast(qe_prefix,root,world_comm) prefix=qe_prefix CALL mp_bcast(west_prefix,root,world_comm) tmp_dir = trimcheck (outdir) CALL mp_bcast(tmp_dir,root,world_comm) ! ENDIF ! IF ( ANY(driver(:)==2) ) THEN ! CALL mp_bcast(wstat_calculation,root,world_comm) CALL mp_bcast(n_pdep_eigen,root,world_comm) CALL mp_bcast(n_pdep_times,root,world_comm) CALL mp_bcast(n_pdep_maxiter,root,world_comm) CALL mp_bcast(n_dfpt_maxiter,root,world_comm) CALL mp_bcast(n_pdep_read_from_file,root,world_comm) CALL mp_bcast(trev_pdep,root,world_comm) CALL mp_bcast(trev_pdep_rel,root,world_comm) CALL mp_bcast(tr2_dfpt,root,world_comm) CALL mp_bcast(l_kinetic_only,root,world_comm) CALL mp_bcast(l_minimize_exx_if_active,root,world_comm) CALL mp_bcast(l_use_ecutrho,root,world_comm) !CALL mp_bcast(nq,root,world_comm) CALL mp_bcast(qlist,root,world_comm) ! ! CHECKS ! SELECT CASE(wstat_calculation) CASE('r','R','s','S') CASE DEFAULT CALL errore('fetch_input','Err: wstat_calculation /= S or R',1) END SELECT ! IF( n_pdep_times < 2 ) CALL errore('fetch_input','Err: n_pdep_times<2',1) IF( n_pdep_eigen < 1 ) CALL errore('fetch_input','Err: n_pdep_eigen<1',1) IF( n_pdep_eigen*n_pdep_times < nimage ) CALL errore('fetch_input','Err: n_pdep_eigen*n_pdep_times n_pdep_eigen ) CALL errore('fetch_input','Err: n_pdep_read_from_file>n_pdep_eigen',1) IF(tr2_dfpt<=0._DP) CALL errore('fetch_input','Err: tr2_dfpt<0.',1) IF(trev_pdep<=0._DP) CALL errore('fetch_input','Err: trev_pdep<0.',1) IF(trev_pdep_rel<=0._DP) CALL errore('fetch_input','Err: trev_pdep_rel<0.',1) IF(gamma_only) THEN IF (SIZE(qlist)/=1) CALL errore('fetch_input','Err: SIZE(qlist)/=1.',1) ELSE IF (SIZE(qlist)>nk1*nk2*nk3) CALL errore('fetch_input','Err: SIZE(qlist)>nk1*nk2*nk3.',1) ENDIF ! ENDIF ! IF ( ANY(driver(:)==3) ) THEN ! CALL mp_bcast(wfreq_calculation,root,world_comm) CALL mp_bcast(n_pdep_eigen_to_use,root,world_comm) CALL mp_bcast(qp_bandrange,root,world_comm) CALL mp_bcast(macropol_calculation,root,world_comm) CALL mp_bcast(n_lanczos,root,world_comm) CALL mp_bcast(n_imfreq,root,world_comm) CALL mp_bcast(n_refreq,root,world_comm) CALL mp_bcast(ecut_imfreq,root,world_comm) CALL mp_bcast(ecut_refreq,root,world_comm) CALL mp_bcast(wfreq_eta,root,world_comm) CALL mp_bcast(n_secant_maxiter,root,world_comm) CALL mp_bcast(trev_secant,root,world_comm) CALL mp_bcast(l_enable_lanczos,root,world_comm) CALL mp_bcast(l_enable_gwetot,root,world_comm) CALL mp_bcast(o_restart_time,root,world_comm) CALL mp_bcast(ecut_spectralf,root,world_comm) CALL mp_bcast(n_spectralf,root,world_comm) ! ! CHECKS ! IF( n_lanczos < 2 ) CALL errore('fetch_input','Err: n_lanczos<2',1) IF( n_pdep_eigen_to_use < 1 ) CALL errore('fetch_input','Err: n_pdep_eigen_to_use<1',1) IF( n_pdep_eigen_to_use > n_pdep_eigen ) CALL errore('fetch_input','Err: n_pdep_eigen_to_use>n_pdep_eigen',1) IF( n_imfreq < 1 ) CALL errore('fetch_input','Err: n_imfreq<1',1) IF( n_refreq < 1 ) CALL errore('fetch_input','Err: n_refreq<1',1) IF( n_spectralf < 2 ) CALL errore('fetch_input','Err: n_spectralf<1',1) IF( qp_bandrange(1) < 1 ) CALL errore('fetch_input','Err: qp_bandrange(1)<1',1) IF( qp_bandrange(2) < 1 ) CALL errore('fetch_input','Err: qp_bandrange(2)<1',1) IF( qp_bandrange(2) < qp_bandrange(1) ) CALL errore('fetch_input','Err: qp_bandrange(2)