1!
2! Copyright (C) 2002-2020 Quantum ESPRESSO group
3! This file is distributed under the terms of the
4! GNU General Public License. See the file `License'
5! in the root directory of the present distribution,
6! or http://www.gnu.org/copyleft/gpl.txt .
7!
8!---------------------------------------------
9! TB
10! included gate related stuff, search 'TB'
11!---------------------------------------------
12!
13!----------------------------------------------------------------------------
14MODULE read_namelists_module
15  !----------------------------------------------------------------------------
16  !
17  !  ... this module handles the reading of input namelists
18  !  ... written by Carlo Cavazzoni, with many additions
19  !  --------------------------------------------------
20  !
21  USE kinds,     ONLY : DP
22  USE input_parameters
23  !
24  IMPLICIT NONE
25  !
26  SAVE
27  !
28  PRIVATE
29  !
30  REAL(DP), PARAMETER :: sm_not_set = -20.0_DP
31  !
32  PUBLIC :: read_namelists, sm_not_set
33  PUBLIC :: check_namelist_read ! made public upon request of A.Jay
34  ! FIXME: should the following ones be public?
35  PUBLIC :: control_defaults, system_defaults, &
36       electrons_defaults, wannier_ac_defaults, ions_defaults, &
37       cell_defaults, press_ai_defaults, wannier_defaults, control_bcast,&
38       system_bcast, electrons_bcast, ions_bcast, cell_bcast, &
39       press_ai_bcast, wannier_bcast, wannier_ac_bcast, control_checkin, &
40       system_checkin, electrons_checkin, ions_checkin, cell_checkin, &
41       wannier_checkin, wannier_ac_checkin, fixval
42  !
43  !  ... end of module-scope declarations
44  !
45  !  ----------------------------------------------
46  !
47  CONTAINS
48     !
49     !=-----------------------------------------------------------------------=!
50     !
51     !  Variables initialization for Namelist CONTROL
52     !
53     !=-----------------------------------------------------------------------=!
54     !
55     !-----------------------------------------------------------------------
56     SUBROUTINE control_defaults( prog )
57       !-----------------------------------------------------------------------
58       !
59       IMPLICIT NONE
60       !
61       CHARACTER(LEN=2) :: prog   ! ... specify the calling program
62       CHARACTER(LEN=20) ::    temp_string
63       !
64       !
65       IF ( prog == 'PW' ) THEN
66          title = ' '
67          calculation = 'scf'
68       ELSE
69          title = 'MD Simulation'
70          calculation = 'cp'
71       END IF
72
73       verbosity = 'default'
74       IF( prog == 'PW' ) restart_mode = 'from_scratch'
75       IF( prog == 'CP' ) restart_mode = 'restart'
76       nstep  = 50
77       IF( prog == 'PW' ) iprint = 100000
78       IF( prog == 'CP' ) iprint = 10
79       IF( prog == 'PW' ) isave = 0
80       IF( prog == 'CP' ) isave = 100
81       !
82       tstress = .FALSE.
83       tprnfor = .FALSE.
84       tabps = .FALSE.
85       !
86       IF( prog == 'PW' ) dt  = 20.0_DP
87       IF( prog == 'CP' ) dt  =  1.0_DP
88       !
89       ndr = 50
90       ndw = 50
91       !
92       ! ... use the path specified as outdir and the filename prefix
93       ! ... to store output data
94       !
95       CALL get_environment_variable( 'ESPRESSO_TMPDIR', outdir )
96       IF ( TRIM( outdir ) == ' ' ) outdir = './'
97       IF( prog == 'PW' ) prefix = 'pwscf'
98       IF( prog == 'CP' ) prefix = 'cp'
99       !
100       ! ... directory containing the pseudopotentials
101       !
102       CALL get_environment_variable( 'ESPRESSO_PSEUDO', pseudo_dir )
103       IF ( TRIM( pseudo_dir ) == ' ') THEN
104          CALL get_environment_variable( 'HOME', pseudo_dir )
105          pseudo_dir = TRIM( pseudo_dir ) // '/espresso/pseudo/'
106       END IF
107       !
108       ! ... max number of md steps added to the xml file. Needs to be limited for very long
109       !     md simulations
110       CALL get_environment_variable('MAX_XML_STEPS', temp_string)
111            IF ( TRIM(temp_string) .NE.  ' ')  READ(temp_string, *) max_xml_steps
112       refg          = 0.05_DP
113       max_seconds   = 1.E+7_DP
114       ekin_conv_thr = 1.E-6_DP
115       etot_conv_thr = 1.E-4_DP
116       forc_conv_thr = 1.E-3_DP
117       disk_io  = 'default'
118       dipfield = .FALSE.
119       gate     = .FALSE. !TB
120       lberry   = .FALSE.
121       gdir     = 0
122       nppstr   = 0
123       wf_collect = .TRUE.
124       lelfield = .FALSE.
125       lorbm = .FALSE.
126       nberrycyc  = 1
127       lecrpa   = .FALSE.
128       tqmmm = .FALSE.
129       !
130       saverho = .TRUE.
131       memory = 'default'
132       !
133       lfcpopt = .FALSE.
134       lfcpdyn = .FALSE.
135       !
136       CALL get_environment_variable( 'QEXML', input_xml_schema_file )
137       !
138       RETURN
139       !
140     END SUBROUTINE
141     !
142     !=----------------------------------------------------------------------=!
143     !
144     !  Variables initialization for Namelist SYSTEM
145     !
146     !=----------------------------------------------------------------------=!
147     !
148     !-----------------------------------------------------------------------
149     SUBROUTINE system_defaults( prog )
150       !-----------------------------------------------------------------------
151       !
152       IMPLICIT NONE
153       !
154       CHARACTER(LEN=2) :: prog   ! ... specify the calling program
155       !
156       !
157       ibrav  = -1
158       celldm = (/ 0.0_DP, 0.0_DP, 0.0_DP, 0.0_DP, 0.0_DP, 0.0_DP /)
159       a = 0.0_DP
160       b = 0.0_DP
161       c = 0.0_DP
162       cosab = 0.0_DP
163       cosac = 0.0_DP
164       cosbc = 0.0_DP
165       nat    = 0
166       ntyp   = 0
167       nbnd   = 0
168       tot_charge = 0.0_DP
169       tot_magnetization = -1
170       ecutwfc = 0.0_DP
171       ecutrho = 0.0_DP
172       nr1  = 0
173       nr2  = 0
174       nr3  = 0
175       nr1s = 0
176       nr2s = 0
177       nr3s = 0
178       nr1b = 0
179       nr2b = 0
180       nr3b = 0
181       occupations = 'fixed'
182       smearing = 'gaussian'
183       degauss = 0.0_DP
184       nspin = 1
185       nosym = .FALSE.
186       nosym_evc = .FALSE.
187       force_symmorphic = .FALSE.
188       use_all_frac = .FALSE.
189       noinv = .FALSE.
190       ecfixed = 0.0_DP
191       qcutz   = 0.0_DP
192       q2sigma = 0.01_DP
193       input_dft = 'none'
194       ecutfock  = -1.0_DP
195       starting_charge = 0.0_DP
196!
197! ... set starting_magnetization to an invalid value:
198! ... in PW starting_magnetization MUST be set for at least one atomic type
199! ... (unless the magnetization is set in other ways)
200! ... in CP starting_magnetization MUST REMAIN UNSET
201!
202       starting_magnetization = sm_not_set
203
204       IF ( prog == 'PW' ) THEN
205          starting_ns_eigenvalue = -1.0_DP
206          U_projection_type = 'atomic'
207       END IF
208       !
209       ! .. DFT + U and its extensions
210       !
211       lda_plus_U = .FALSE.
212       lda_plus_u_kind = 0
213       Hubbard_U = 0.0_DP
214       Hubbard_U_back = 0.0_DP
215       Hubbard_V = 0.0_DP
216       Hubbard_J0 = 0.0_DP
217       Hubbard_J = 0.0_DP
218       Hubbard_alpha = 0.0_DP
219       Hubbard_alpha_back = 0.0_DP
220       Hubbard_beta = 0.0_DP
221       Hubbard_parameters = 'input'
222       reserv = .false.
223       reserv_back = .false.
224       backall = .false.
225       lback = -1
226       l1back = -1
227       hub_pot_fix = .false.
228       step_pen=.false.
229       A_pen=0.0_DP
230       sigma_pen=0.01_DP
231       alpha_pen=0.0_DP
232       !
233       ! ... EXX
234       !
235       ace=.TRUE.
236       n_proj = 0
237       localization_thr = 0.0_dp
238       scdm=.FALSE.
239       scdmden=1.0d0
240       scdmgrd=1.0d0
241       nscdm=1
242       !
243       ! ... electric fields
244       !
245       edir = 1
246       emaxpos = 0.5_DP
247       eopreg = 0.1_DP
248       eamp = 0.0_DP
249       ! TB gate related variables
250       zgate = 0.5
251       relaxz = .false.
252       block = .false.
253       block_1 = 0.45
254       block_2 = 0.55
255       block_height = 0.0
256       !
257       !  ... postprocessing of DOS & phonons & el-ph
258       !
259       la2F = .FALSE.
260       !
261       ! ... non collinear program variables
262       !
263       lspinorb = .FALSE.
264       lforcet = .FALSE.
265       starting_spin_angle=.FALSE.
266       noncolin = .FALSE.
267       lambda = 1.0_DP
268       constrained_magnetization= 'none'
269       fixed_magnetization = 0.0_DP
270       B_field = 0.0_DP
271       angle1 = 0.0_DP
272       angle2 = 0.0_DP
273       report =-1
274       !
275       no_t_rev = .FALSE.
276       !
277       assume_isolated = 'none'
278       !
279       one_atom_occupations=.FALSE.
280       !
281       spline_ps = .false.
282       !
283       real_space = .false.
284       !
285       ! ... DFT-D, Tkatchenko-Scheffler, XDM
286       !
287       vdw_corr    = 'none'
288       london      = .false.
289       london_s6   = 0.75_DP
290       london_rcut = 200.00_DP
291       london_c6   = -1.0_DP
292       london_rvdw = -1.0_DP
293       ts_vdw          = .FALSE.
294       ts_vdw_isolated = .FALSE.
295       ts_vdw_econv_thr = 1.E-6_DP
296       xdm = .FALSE.
297       xdm_a1 = 0.0_DP
298       xdm_a2 = 0.0_DP
299       dftd3_version = 3
300       dftd3_threebody = .TRUE.
301       !
302       ! ... ESM
303       !
304       esm_bc='pbc'
305       esm_efield=0.0_DP
306       esm_w=0.0_DP
307       esm_a=0.0_DP
308       esm_zb=-2.0_DP
309       esm_nfit=4
310       esm_debug=.FALSE.
311       esm_debug_gpmax=0
312       !
313       ! ... FCP
314       !
315       fcp_mu          = 0.0_DP
316       fcp_mass        = 10000.0_DP
317       fcp_tempw       = 0.0_DP
318       fcp_relax       = 'lm'
319       fcp_relax_step  = 0.5_DP
320       fcp_relax_crit  = 0.001_DP
321       fcp_mdiis_size  = 4
322       fcp_mdiis_step  = 0.2_DP
323       !
324       ! ... Wyckoff
325       !
326       space_group=0
327       uniqueb = .FALSE.
328       origin_choice = 1
329       rhombohedral = .TRUE.
330       !
331       RETURN
332       !
333     END SUBROUTINE
334     !
335     !=----------------------------------------------------------------------=!
336     !
337     !  Variables initialization for Namelist ELECTRONS
338     !
339     !=----------------------------------------------------------------------=!
340     !
341     !-----------------------------------------------------------------------
342     SUBROUTINE electrons_defaults( prog )
343       !-----------------------------------------------------------------------
344       !
345       IMPLICIT NONE
346       !
347       CHARACTER(LEN=2) :: prog   ! ... specify the calling program
348       !
349       !
350       emass = 400.0_DP
351       emass_cutoff = 2.5_DP
352       orthogonalization = 'ortho'
353       ortho_eps = 1.E-9_DP
354       ortho_max = 300
355       electron_maxstep = 100
356       scf_must_converge = .true.
357       !
358       ! ... ( 'sd' | 'cg' | 'damp' | 'verlet' | 'none' | 'diis' | 'cp-bo' )
359       !
360       electron_dynamics = 'none'
361       electron_damping = 0.1_DP
362       !
363       ! ... ( 'zero' | 'default' )
364       !
365       electron_velocities = 'default'
366       !
367       ! ... ( 'nose' | 'not_controlled' | 'rescaling')
368       !
369       electron_temperature = 'not_controlled'
370       ekincw = 0.001_DP
371       fnosee = 1.0_DP
372       ampre  = 0.0_DP
373       grease = 1.0_DP
374       conv_thr = 1.E-6_DP
375       diis_size = 4
376       diis_nreset = 3
377       diis_hcut = 1.0_DP
378       diis_wthr = 0.0_DP
379       diis_delt = 0.0_DP
380       diis_maxstep = 100
381       diis_rot = .FALSE.
382       diis_fthr = 0.0_DP
383       diis_temp = 0.0_DP
384       diis_achmix = 0.0_DP
385       diis_g0chmix = 0.0_DP
386       diis_g1chmix = 0.0_DP
387       diis_nchmix = 3
388       diis_nrot = 3
389       diis_rothr  = 0.0_DP
390       diis_ethr   = 0.0_DP
391       diis_chguess = .FALSE.
392       mixing_mode = 'plain'
393       mixing_fixed_ns = 0
394       mixing_beta = 0.7_DP
395       mixing_ndim = 8
396       diagonalization = 'david'
397       diago_thr_init = 0.0_DP
398       diago_cg_maxiter = 20
399       diago_ppcg_maxiter = 20
400       diago_david_ndim = 2
401       diago_full_acc = .FALSE.
402       !
403       sic = 'none'
404       sic_epsilon = 0.0_DP
405       sic_alpha = 0.0_DP
406       force_pairing = .false.
407       !
408       fermi_energy = 0.0_DP
409       n_inner = 2
410       niter_cold_restart=1
411       lambda_cold=0.03_DP
412       rotation_dynamics = "line-minimization"
413       occupation_dynamics = "line-minimization"
414       rotmass = 0.0_DP
415       occmass = 0.0_DP
416       rotation_damping = 0.0_DP
417       occupation_damping = 0.0_DP
418       !
419       tcg     = .FALSE.
420       maxiter = 100
421       passop  = 0.3_DP
422       niter_cg_restart = 20
423       etresh  = 1.E-6_DP
424       !
425       epol   = 3
426       efield = 0.0_DP
427       epol2  = 3
428       efield2 = 0.0_DP
429       efield_cart(1)=0.d0
430       efield_cart(2)=0.d0
431       efield_cart(3)=0.d0
432       efield_phase='none'
433       !
434       occupation_constraints = .false.
435       !
436       adaptive_thr   =  .false.
437       conv_thr_init  =  0.1E-2_DP
438       conv_thr_multi =  0.1_DP
439       !
440       ! ... CP-BO ...
441       tcpbo = .false.
442       emass_emin = 200.0_DP
443       emass_cutoff_emin = 6.0_DP
444       electron_damping_emin = 0.35_DP
445       dt_emin = 4.0_DP
446       !
447       RETURN
448       !
449     END SUBROUTINE
450     !
451     !=----------------------------------------------------------------------=!
452     !
453     !  Variables initialization for Namelist WANNIER_AC
454     !
455     !----------------------------------------------------------------------
456     SUBROUTINE wannier_ac_defaults( prog )
457       !----------------------------------------------------------------------
458       !
459       IMPLICIT NONE
460       !
461       CHARACTER(LEN=2) :: prog   ! ... specify the calling program
462       !
463       !
464       plot_wannier = .FALSE.
465       use_energy_int = .FALSE.
466       print_wannier_coeff = .FALSE.
467       nwan = 0
468       constrain_pot = 0.d0
469       plot_wan_num = 0
470       plot_wan_spin = 1
471       !
472       RETURN
473       !
474     END SUBROUTINE
475
476     !=----------------------------------------------------------------------=!
477     !
478     !  Variables initialization for Namelist IONS
479     !
480     !=----------------------------------------------------------------------=!
481     !
482     !-----------------------------------------------------------------------
483     SUBROUTINE ions_defaults( prog )
484       !-----------------------------------------------------------------------
485       !
486       IMPLICIT NONE
487       !
488       CHARACTER(LEN=2) :: prog   ! ... specify the calling program
489       !
490       ! ... ( 'sd' | 'cg' | 'damp' | 'verlet' | 'none' | 'bfgs' | 'beeman' )
491       !
492       ion_dynamics = 'none'
493       ion_radius   = 0.5_DP
494       ion_damping  = 0.1_DP
495       !
496       ! ... ( 'default' | 'from_input' )
497       !
498       ion_positions = 'default'
499       !
500       ! ... ( 'zero' | 'default' | 'from_input' )
501       !
502       ion_velocities = 'default'
503       !
504       ! ... ( 'nose' | 'not_controlled' | 'rescaling' | 'berendsen' |
505       !       'andersen' | 'initial' )
506       !
507       ion_temperature = 'not_controlled'
508       !
509       tempw       = 300.0_DP
510       fnosep      = -1.0_DP
511       fnosep(1)   = 1.0_DP
512       nhpcl       = 0
513       nhptyp      = 0
514       ndega       = 0
515       tranp       = .FALSE.
516       amprp       = 0.0_DP
517       greasp      = 1.0_DP
518       tolp        = 100.0_DP
519       ion_nstepe  = 1
520       ion_maxstep = 100
521       delta_t     = 1.0_DP
522       nraise      = 1
523       !
524       refold_pos       = .FALSE.
525       remove_rigid_rot = .FALSE.
526       !
527       upscale           = 100.0_DP
528       pot_extrapolation = 'atomic'
529       wfc_extrapolation = 'none'
530       !
531       ! ... BFGS defaults
532       !
533       bfgs_ndim        = 1
534       trust_radius_max = 0.8_DP   ! bohr
535       trust_radius_min = 1.E-4_DP ! bohr
536       trust_radius_ini = 0.5_DP   ! bohr
537       w_1              = 0.01_DP
538       w_2              = 0.50_DP
539       !
540       l_mplathe=.false.
541       n_muller=0
542       np_muller=1
543       l_exit_muller=.false.
544
545
546       RETURN
547       !
548     END SUBROUTINE
549     !
550     !
551     !=----------------------------------------------------------------------=!
552     !
553     !  Variables initialization for Namelist CELL
554     !
555     !=----------------------------------------------------------------------=!
556     !
557     !-----------------------------------------------------------------------
558     SUBROUTINE cell_defaults( prog )
559       !-----------------------------------------------------------------------
560       !
561       IMPLICIT NONE
562       !
563       CHARACTER(LEN=2) :: prog   ! ... specify the calling program
564       !
565       !
566       cell_parameters = 'default'
567       !
568       ! ... ( 'sd' | 'pr' | 'none' | 'w' | 'damp-pr' | 'damp-w' | 'bfgs' )
569       !
570       cell_dynamics = 'none'
571       !
572       ! ... ( 'zero' | 'default' )
573       !
574       cell_velocities = 'default'
575       press = 0.0_DP
576       wmass = 0.0_DP
577       !
578       ! ... ( 'nose' | 'not_controlled' | 'rescaling' )
579       !
580       cell_temperature = 'not_controlled'
581       temph = 0.0_DP
582       fnoseh = 1.0_DP
583       greash = 1.0_DP
584       !
585       ! ... ('all'* | 'volume' | 'x' | 'y' | 'z' | 'xy' | 'xz' | 'yz' | 'xyz' )
586       !
587       cell_dofree = 'all'
588       cell_factor = 0.0_DP
589       cell_nstepe = 1
590       cell_damping = 0.1_DP
591       press_conv_thr = 0.5_DP
592       treinit_gvecs = .FALSE.
593       !
594       RETURN
595       !
596     END SUBROUTINE
597     !
598     !
599     !=----------------------------------------------------------------------=!
600     !
601     !  Variables initialization for Namelist PRESS_AI
602     !
603     !=----------------------------------------------------------------------=!
604     !
605     !----------------------------------------------------------------------
606     SUBROUTINE press_ai_defaults( prog )
607     !
608       IMPLICIT NONE
609       !
610       CHARACTER(LEN=2) :: prog   ! ... specify the calling program
611       !
612       abivol = .false.
613       abisur = .false.
614       pvar = .false.
615       fill_vac = .false.
616       cntr = .false.
617       scale_at = .false.
618       t_gauss = .false.
619       jellium = .false.
620
621       P_ext = 0.0_DP
622       P_in = 0.0_DP
623       P_fin = 0.0_DP
624       Surf_t = 0.0_DP
625       rho_thr = 0.0_DP
626       dthr = 0.0_DP
627       step_rad = 0.0_DP
628       delta_eps = 0.0_DP
629       delta_sigma = 0.0_DP
630       R_j = 0.0_DP
631       h_j = 0.0_DP
632
633       n_cntr = 0
634       axis = 3
635       !
636       RETURN
637       !
638     END SUBROUTINE
639     !
640     !=----------------------------------------------------------------------=!
641     !
642     !  Variables initialization for Namelist WANNIER
643     !
644     !-----------------------------------------------------------------------
645     SUBROUTINE wannier_defaults( prog )
646       !-----------------------------------------------------------------------
647       !
648       IMPLICIT NONE
649       !
650       CHARACTER(LEN=2) :: prog   ! ... specify the calling program
651       !
652       !
653       wf_efield = .FALSE.
654       wf_switch = .FALSE.
655       !
656       sw_len = 1
657       !
658       efx0 = 0.0_DP
659       efy0 = 0.0_DP
660       efz0 = 0.0_DP
661       efx1 = 0.0_DP
662       efy1 = 0.0_DP
663       efz1 = 0.0_DP
664       !
665       wfsd = 1
666       !
667       wfdt        = 5.0_DP
668       maxwfdt     = 0.30_DP
669       wf_q        = 1500.0_DP
670       wf_friction = 0.3_DP
671!=======================================================================
672!exx_wf related
673       exx_neigh        =  60
674       vnbsp            =  0
675       exx_poisson_eps  =  1.E-6_DP
676       exx_dis_cutoff   =  8.0_DP
677       exx_ps_rcut_self =  6.0_DP
678       exx_ps_rcut_pair =  5.0_DP
679       exx_me_rcut_self = 10.0_DP
680       exx_me_rcut_pair =  7.0_DP
681       exx_use_cube_domain = .false.
682!=======================================================================
683       !
684       nit    = 10
685       nsd    = 10
686       nsteps = 20
687       !
688       tolw = 1.E-8_DP
689       !
690       adapt = .TRUE.
691       !
692       calwf  = 3
693       nwf    = 0
694       wffort = 40
695       !
696       writev = .FALSE.
697       !
698       RETURN
699       !
700     END SUBROUTINE
701     !
702     !=----------------------------------------------------------------------=!
703     !
704     !  Broadcast variables values for Namelist CONTROL
705     !
706     !=----------------------------------------------------------------------=!
707     !
708     !-----------------------------------------------------------------------
709     SUBROUTINE control_bcast()
710       !-----------------------------------------------------------------------
711       !
712       USE io_global, ONLY : ionode_id
713       USE mp,        ONLY : mp_bcast
714       USE mp_images, ONLY : intra_image_comm
715       !
716       IMPLICIT NONE
717       !
718       CALL mp_bcast( title,         ionode_id, intra_image_comm )
719       CALL mp_bcast( calculation,   ionode_id, intra_image_comm )
720       CALL mp_bcast( verbosity,     ionode_id, intra_image_comm )
721       CALL mp_bcast( restart_mode,  ionode_id, intra_image_comm )
722       CALL mp_bcast( nstep,         ionode_id, intra_image_comm )
723       CALL mp_bcast( iprint,        ionode_id, intra_image_comm )
724       CALL mp_bcast( isave,         ionode_id, intra_image_comm )
725       CALL mp_bcast( tstress,       ionode_id, intra_image_comm )
726       CALL mp_bcast( tprnfor,       ionode_id, intra_image_comm )
727       CALL mp_bcast( tabps,         ionode_id, intra_image_comm )
728       CALL mp_bcast( dt,            ionode_id, intra_image_comm )
729       CALL mp_bcast( ndr,           ionode_id, intra_image_comm )
730       CALL mp_bcast( ndw,           ionode_id, intra_image_comm )
731       CALL mp_bcast( outdir,        ionode_id, intra_image_comm )
732       CALL mp_bcast( wfcdir,        ionode_id, intra_image_comm )
733       CALL mp_bcast( prefix,        ionode_id, intra_image_comm )
734       CALL mp_bcast( max_seconds,   ionode_id, intra_image_comm )
735       CALL mp_bcast( ekin_conv_thr, ionode_id, intra_image_comm )
736       CALL mp_bcast( etot_conv_thr, ionode_id, intra_image_comm )
737       CALL mp_bcast( forc_conv_thr, ionode_id, intra_image_comm )
738       CALL mp_bcast( pseudo_dir,    ionode_id, intra_image_comm )
739       CALL mp_bcast( refg,          ionode_id, intra_image_comm )
740       CALL mp_bcast( disk_io,       ionode_id, intra_image_comm )
741       CALL mp_bcast( tefield,       ionode_id, intra_image_comm )
742       CALL mp_bcast( tefield2,      ionode_id, intra_image_comm )
743       CALL mp_bcast( dipfield,      ionode_id, intra_image_comm )
744       CALL mp_bcast( lberry,        ionode_id, intra_image_comm )
745       CALL mp_bcast( gdir,          ionode_id, intra_image_comm )
746       CALL mp_bcast( nppstr,        ionode_id, intra_image_comm )
747       CALL mp_bcast( point_label_type,   ionode_id, intra_image_comm )
748       CALL mp_bcast( wf_collect,    ionode_id, intra_image_comm )
749       CALL mp_bcast( lelfield,      ionode_id, intra_image_comm )
750       CALL mp_bcast( lorbm,         ionode_id, intra_image_comm )
751       CALL mp_bcast( nberrycyc,     ionode_id, intra_image_comm )
752       CALL mp_bcast( saverho,       ionode_id, intra_image_comm )
753       CALL mp_bcast( lecrpa,        ionode_id, intra_image_comm )
754       CALL mp_bcast( tqmmm,         ionode_id, intra_image_comm )
755       CALL mp_bcast( vdw_table_name,ionode_id, intra_image_comm )
756       CALL mp_bcast( memory,        ionode_id, intra_image_comm )
757       CALL mp_bcast( lfcpopt,       ionode_id, intra_image_comm )
758       CALL mp_bcast( lfcpdyn,       ionode_id, intra_image_comm )
759       CALL mp_bcast( input_xml_schema_file, ionode_id, intra_image_comm )
760       CALL mp_bcast( gate,          ionode_id, intra_image_comm ) !TB
761       !
762       RETURN
763       !
764     END SUBROUTINE
765     !
766     !=----------------------------------------------------------------------=!
767     !
768     !  Broadcast variables values for Namelist SYSTEM
769     !
770     !=----------------------------------------------------------------------=!
771     !
772     !-----------------------------------------------------------------------
773     SUBROUTINE system_bcast()
774       !-----------------------------------------------------------------------
775       !
776       USE io_global, ONLY : ionode_id
777       USE mp,        ONLY : mp_bcast
778       USE mp_images, ONLY : intra_image_comm
779       !
780       IMPLICIT NONE
781       !
782       CALL mp_bcast( ibrav,             ionode_id, intra_image_comm )
783       CALL mp_bcast( celldm,            ionode_id, intra_image_comm )
784       CALL mp_bcast( a,                 ionode_id, intra_image_comm )
785       CALL mp_bcast( b,                 ionode_id, intra_image_comm )
786       CALL mp_bcast( c,                 ionode_id, intra_image_comm )
787       CALL mp_bcast( cosab,             ionode_id, intra_image_comm )
788       CALL mp_bcast( cosac,             ionode_id, intra_image_comm )
789       CALL mp_bcast( cosbc,             ionode_id, intra_image_comm )
790       CALL mp_bcast( nat,               ionode_id, intra_image_comm )
791       CALL mp_bcast( ntyp,              ionode_id, intra_image_comm )
792       CALL mp_bcast( nbnd,              ionode_id, intra_image_comm )
793       CALL mp_bcast( tot_charge,        ionode_id, intra_image_comm )
794       CALL mp_bcast( tot_magnetization, ionode_id, intra_image_comm )
795       CALL mp_bcast( ecutwfc,           ionode_id, intra_image_comm )
796       CALL mp_bcast( ecutrho,           ionode_id, intra_image_comm )
797       CALL mp_bcast( nr1,               ionode_id, intra_image_comm )
798       CALL mp_bcast( nr2,               ionode_id, intra_image_comm )
799       CALL mp_bcast( nr3,               ionode_id, intra_image_comm )
800       CALL mp_bcast( nr1s,              ionode_id, intra_image_comm )
801       CALL mp_bcast( nr2s,              ionode_id, intra_image_comm )
802       CALL mp_bcast( nr3s,              ionode_id, intra_image_comm )
803       CALL mp_bcast( nr1b,              ionode_id, intra_image_comm )
804       CALL mp_bcast( nr2b,              ionode_id, intra_image_comm )
805       CALL mp_bcast( nr3b,              ionode_id, intra_image_comm )
806       CALL mp_bcast( occupations,       ionode_id, intra_image_comm )
807       CALL mp_bcast( smearing,          ionode_id, intra_image_comm )
808       CALL mp_bcast( degauss,           ionode_id, intra_image_comm )
809       CALL mp_bcast( nspin,             ionode_id, intra_image_comm )
810       CALL mp_bcast( nosym,             ionode_id, intra_image_comm )
811       CALL mp_bcast( nosym_evc,         ionode_id, intra_image_comm )
812       CALL mp_bcast( noinv,             ionode_id, intra_image_comm )
813       CALL mp_bcast( force_symmorphic,  ionode_id, intra_image_comm )
814       CALL mp_bcast( use_all_frac,      ionode_id, intra_image_comm )
815       CALL mp_bcast( ecfixed,           ionode_id, intra_image_comm )
816       CALL mp_bcast( qcutz,             ionode_id, intra_image_comm )
817       CALL mp_bcast( q2sigma,           ionode_id, intra_image_comm )
818       CALL mp_bcast( input_dft,         ionode_id, intra_image_comm )
819
820       ! ... EXX
821
822       CALL mp_bcast( ace,                 ionode_id, intra_image_comm )
823       CALL mp_bcast( localization_thr,    ionode_id, intra_image_comm )
824       CALL mp_bcast( scdm,                ionode_id, intra_image_comm )
825       CALL mp_bcast( scdmden,             ionode_id, intra_image_comm )
826       CALL mp_bcast( scdmgrd,             ionode_id, intra_image_comm )
827       CALL mp_bcast( nscdm,               ionode_id, intra_image_comm )
828       CALL mp_bcast( n_proj,              ionode_id, intra_image_comm )
829       CALL mp_bcast( nqx1,                   ionode_id, intra_image_comm )
830       CALL mp_bcast( nqx2,                   ionode_id, intra_image_comm )
831       CALL mp_bcast( nqx3,                   ionode_id, intra_image_comm )
832       CALL mp_bcast( exx_fraction,           ionode_id, intra_image_comm )
833       CALL mp_bcast( screening_parameter,    ionode_id, intra_image_comm )
834       CALL mp_bcast( gau_parameter,          ionode_id, intra_image_comm )
835       CALL mp_bcast( exxdiv_treatment,       ionode_id, intra_image_comm )
836       CALL mp_bcast( x_gamma_extrapolation,  ionode_id, intra_image_comm )
837       CALL mp_bcast( yukawa,                 ionode_id, intra_image_comm )
838       CALL mp_bcast( ecutvcut,               ionode_id, intra_image_comm )
839       CALL mp_bcast( ecutfock,               ionode_id, intra_image_comm )
840       !
841       CALL mp_bcast( starting_charge,        ionode_id, intra_image_comm )
842       CALL mp_bcast( starting_magnetization, ionode_id, intra_image_comm )
843       CALL mp_bcast( starting_ns_eigenvalue, ionode_id, intra_image_comm )
844       CALL mp_bcast( U_projection_type,      ionode_id, intra_image_comm )
845       CALL mp_bcast( lda_plus_U,             ionode_id, intra_image_comm )
846       CALL mp_bcast( lda_plus_u_kind,        ionode_id, intra_image_comm )
847       CALL mp_bcast( Hubbard_U,              ionode_id, intra_image_comm )
848       CALL mp_bcast( Hubbard_U_back,         ionode_id, intra_image_comm )
849       CALL mp_bcast( Hubbard_J0,             ionode_id, intra_image_comm )
850       CALL mp_bcast( Hubbard_J,              ionode_id, intra_image_comm )
851       CALL mp_bcast( Hubbard_V,              ionode_id, intra_image_comm )
852       CALL mp_bcast( Hubbard_alpha,          ionode_id, intra_image_comm )
853       CALL mp_bcast( Hubbard_alpha_back,     ionode_id, intra_image_comm )
854       CALL mp_bcast( Hubbard_beta,           ionode_id, intra_image_comm )
855       CALL mp_bcast( hub_pot_fix,            ionode_id,intra_image_comm )
856       CALL mp_bcast( Hubbard_parameters,     ionode_id,intra_image_comm )
857       CALL mp_bcast( reserv,                 ionode_id,intra_image_comm )
858       CALL mp_bcast( reserv_back,            ionode_id,intra_image_comm )
859       CALL mp_bcast( backall,                ionode_id,intra_image_comm )
860       CALL mp_bcast( lback,                  ionode_id,intra_image_comm )
861       CALL mp_bcast( l1back,                 ionode_id,intra_image_comm )
862       CALL mp_bcast( step_pen,               ionode_id, intra_image_comm )
863       CALL mp_bcast( A_pen,                  ionode_id, intra_image_comm )
864       CALL mp_bcast( sigma_pen,              ionode_id, intra_image_comm )
865       CALL mp_bcast( alpha_pen,              ionode_id, intra_image_comm )
866       CALL mp_bcast( edir,                   ionode_id, intra_image_comm )
867       CALL mp_bcast( emaxpos,                ionode_id, intra_image_comm )
868       CALL mp_bcast( eopreg,                 ionode_id, intra_image_comm )
869       CALL mp_bcast( eamp,                   ionode_id, intra_image_comm )
870       CALL mp_bcast( la2F,                   ionode_id, intra_image_comm )
871       !
872       ! ... non collinear broadcast
873       !
874       CALL mp_bcast( lspinorb,                  ionode_id, intra_image_comm )
875       CALL mp_bcast( lforcet,                   ionode_id, intra_image_comm )
876       CALL mp_bcast( starting_spin_angle,       ionode_id, intra_image_comm )
877       CALL mp_bcast( noncolin,                  ionode_id, intra_image_comm )
878       CALL mp_bcast( angle1,                    ionode_id, intra_image_comm )
879       CALL mp_bcast( angle2,                    ionode_id, intra_image_comm )
880       CALL mp_bcast( report,                    ionode_id, intra_image_comm )
881       CALL mp_bcast( constrained_magnetization, ionode_id, intra_image_comm )
882       CALL mp_bcast( B_field,                   ionode_id, intra_image_comm )
883       CALL mp_bcast( fixed_magnetization,       ionode_id, intra_image_comm )
884       CALL mp_bcast( lambda,                    ionode_id, intra_image_comm )
885       !
886       CALL mp_bcast( assume_isolated,           ionode_id, intra_image_comm )
887       CALL mp_bcast( one_atom_occupations,      ionode_id, intra_image_comm )
888       CALL mp_bcast( spline_ps,                 ionode_id, intra_image_comm )
889       !
890       CALL mp_bcast( vdw_corr,                  ionode_id, intra_image_comm )
891       CALL mp_bcast( ts_vdw,                    ionode_id, intra_image_comm )
892       CALL mp_bcast( ts_vdw_isolated,           ionode_id, intra_image_comm )
893       CALL mp_bcast( ts_vdw_econv_thr,          ionode_id, intra_image_comm )
894       CALL mp_bcast( london,                    ionode_id, intra_image_comm )
895       CALL mp_bcast( london_s6,                 ionode_id, intra_image_comm )
896       CALL mp_bcast( london_rcut,               ionode_id, intra_image_comm )
897       CALL mp_bcast( london_c6,                 ionode_id, intra_image_comm )
898       CALL mp_bcast( london_rvdw,               ionode_id, intra_image_comm )
899       CALL mp_bcast( xdm,                       ionode_id, intra_image_comm )
900       CALL mp_bcast( xdm_a1,                    ionode_id, intra_image_comm )
901       CALL mp_bcast( xdm_a2,                    ionode_id, intra_image_comm )
902       !
903       CALL mp_bcast( no_t_rev,                  ionode_id, intra_image_comm )
904       !
905       ! ... ESM method broadcast
906       !
907       CALL mp_bcast( esm_bc,             ionode_id, intra_image_comm )
908       CALL mp_bcast( esm_efield,         ionode_id, intra_image_comm )
909       CALL mp_bcast( esm_w,              ionode_id, intra_image_comm )
910       CALL mp_bcast( esm_a,              ionode_id, intra_image_comm )
911       CALL mp_bcast( esm_zb,             ionode_id, intra_image_comm )
912       CALL mp_bcast( esm_nfit,           ionode_id, intra_image_comm )
913       CALL mp_bcast( esm_debug,          ionode_id, intra_image_comm )
914       CALL mp_bcast( esm_debug_gpmax,    ionode_id, intra_image_comm )
915       !
916       ! ... FCP
917       !
918       CALL mp_bcast( fcp_mu,          ionode_id, intra_image_comm )
919       CALL mp_bcast( fcp_mass,        ionode_id, intra_image_comm )
920       CALL mp_bcast( fcp_tempw,       ionode_id, intra_image_comm )
921       CALL mp_bcast( fcp_relax,       ionode_id, intra_image_comm )
922       CALL mp_bcast( fcp_relax_step,  ionode_id, intra_image_comm )
923       CALL mp_bcast( fcp_relax_crit,  ionode_id, intra_image_comm )
924       CALL mp_bcast( fcp_mdiis_size,  ionode_id, intra_image_comm )
925       CALL mp_bcast( fcp_mdiis_step,  ionode_id, intra_image_comm )
926       !
927       !
928       ! ... space group information
929       !
930       CALL mp_bcast( space_group,        ionode_id, intra_image_comm )
931       CALL mp_bcast( uniqueb,            ionode_id, intra_image_comm )
932       CALL mp_bcast( origin_choice,      ionode_id, intra_image_comm )
933       CALL mp_bcast( rhombohedral,       ionode_id, intra_image_comm )
934       !
935       ! TB - gate broadcast
936       !
937       CALL mp_bcast( zgate,              ionode_id, intra_image_comm )
938       CALL mp_bcast( relaxz,             ionode_id, intra_image_comm )
939       CALL mp_bcast( block,              ionode_id, intra_image_comm )
940       CALL mp_bcast( block_1,            ionode_id, intra_image_comm )
941       CALL mp_bcast( block_2,            ionode_id, intra_image_comm )
942       CALL mp_bcast( block_height,       ionode_id, intra_image_comm )
943
944       RETURN
945       !
946     END SUBROUTINE
947     !
948     !=----------------------------------------------------------------------=!
949     !
950     !  Broadcast variables values for Namelist ELECTRONS
951     !
952     !=----------------------------------------------------------------------=!
953     !
954     !-----------------------------------------------------------------------
955     SUBROUTINE electrons_bcast()
956       !-----------------------------------------------------------------------
957       !
958       USE io_global, ONLY : ionode_id
959       USE mp,        ONLY : mp_bcast
960       USE mp_images, ONLY : intra_image_comm
961       !
962       IMPLICIT NONE
963       !
964       CALL mp_bcast( emass,                ionode_id, intra_image_comm )
965       CALL mp_bcast( emass_cutoff,         ionode_id, intra_image_comm )
966       CALL mp_bcast( orthogonalization,    ionode_id, intra_image_comm )
967       CALL mp_bcast( electron_maxstep,     ionode_id, intra_image_comm )
968       CALL mp_bcast( scf_must_converge,    ionode_id, intra_image_comm )
969       CALL mp_bcast( ortho_eps,            ionode_id, intra_image_comm )
970       CALL mp_bcast( ortho_max,            ionode_id, intra_image_comm )
971       CALL mp_bcast( electron_dynamics,    ionode_id, intra_image_comm )
972       CALL mp_bcast( electron_damping,     ionode_id, intra_image_comm )
973       CALL mp_bcast( electron_velocities,  ionode_id, intra_image_comm )
974       CALL mp_bcast( electron_temperature, ionode_id, intra_image_comm )
975       CALL mp_bcast( conv_thr,             ionode_id, intra_image_comm )
976       CALL mp_bcast( ekincw,               ionode_id, intra_image_comm )
977       CALL mp_bcast( fnosee,               ionode_id, intra_image_comm )
978       CALL mp_bcast( startingwfc,          ionode_id, intra_image_comm )
979       CALL mp_bcast( ampre,                ionode_id, intra_image_comm )
980       CALL mp_bcast( grease,               ionode_id, intra_image_comm )
981       CALL mp_bcast( startingpot,          ionode_id, intra_image_comm )
982       CALL mp_bcast( diis_size,            ionode_id, intra_image_comm )
983       CALL mp_bcast( diis_nreset,          ionode_id, intra_image_comm )
984       CALL mp_bcast( diis_hcut,            ionode_id, intra_image_comm )
985       CALL mp_bcast( diis_wthr,            ionode_id, intra_image_comm )
986       CALL mp_bcast( diis_delt,            ionode_id, intra_image_comm )
987       CALL mp_bcast( diis_maxstep,         ionode_id, intra_image_comm )
988       CALL mp_bcast( diis_rot,             ionode_id, intra_image_comm )
989       CALL mp_bcast( diis_fthr,            ionode_id, intra_image_comm )
990       CALL mp_bcast( diis_temp,            ionode_id, intra_image_comm )
991       CALL mp_bcast( diis_achmix,          ionode_id, intra_image_comm )
992       CALL mp_bcast( diis_g0chmix,         ionode_id, intra_image_comm )
993       CALL mp_bcast( diis_g1chmix,         ionode_id, intra_image_comm )
994       CALL mp_bcast( diis_nchmix,          ionode_id, intra_image_comm )
995       CALL mp_bcast( diis_nrot,            ionode_id, intra_image_comm )
996       CALL mp_bcast( diis_rothr,           ionode_id, intra_image_comm )
997       CALL mp_bcast( diis_ethr,            ionode_id, intra_image_comm )
998       CALL mp_bcast( diis_chguess,         ionode_id, intra_image_comm )
999       CALL mp_bcast( mixing_fixed_ns,      ionode_id, intra_image_comm )
1000       CALL mp_bcast( mixing_mode,          ionode_id, intra_image_comm )
1001       CALL mp_bcast( mixing_beta,          ionode_id, intra_image_comm )
1002       CALL mp_bcast( mixing_ndim,          ionode_id, intra_image_comm )
1003       CALL mp_bcast( tqr,                  ionode_id, intra_image_comm )
1004       CALL mp_bcast( tq_smoothing,         ionode_id, intra_image_comm )
1005       CALL mp_bcast( tbeta_smoothing,      ionode_id, intra_image_comm )
1006       CALL mp_bcast( diagonalization,      ionode_id, intra_image_comm )
1007       CALL mp_bcast( diago_thr_init,       ionode_id, intra_image_comm )
1008       CALL mp_bcast( diago_cg_maxiter,     ionode_id, intra_image_comm )
1009       CALL mp_bcast( diago_ppcg_maxiter,   ionode_id, intra_image_comm )
1010       CALL mp_bcast( diago_david_ndim,     ionode_id, intra_image_comm )
1011       CALL mp_bcast( diago_full_acc,       ionode_id, intra_image_comm )
1012       CALL mp_bcast( sic,                  ionode_id, intra_image_comm )
1013       CALL mp_bcast( sic_epsilon ,         ionode_id, intra_image_comm )
1014       CALL mp_bcast( sic_alpha   ,         ionode_id, intra_image_comm )
1015       CALL mp_bcast( force_pairing ,       ionode_id, intra_image_comm )
1016       !
1017       ! ... ensemble-DFT
1018       !
1019       CALL mp_bcast( fermi_energy,       ionode_id, intra_image_comm )
1020       CALL mp_bcast( n_inner,            ionode_id, intra_image_comm )
1021       CALL mp_bcast( niter_cold_restart, ionode_id, intra_image_comm )
1022       CALL mp_bcast( lambda_cold,        ionode_id, intra_image_comm )
1023       CALL mp_bcast( rotation_dynamics,  ionode_id, intra_image_comm )
1024       CALL mp_bcast( occupation_dynamics,ionode_id, intra_image_comm )
1025       CALL mp_bcast( rotmass,            ionode_id, intra_image_comm )
1026       CALL mp_bcast( occmass,            ionode_id, intra_image_comm )
1027       CALL mp_bcast( rotation_damping,   ionode_id, intra_image_comm )
1028       CALL mp_bcast( occupation_damping, ionode_id, intra_image_comm )
1029       !
1030       ! ... conjugate gradient
1031       !
1032       CALL mp_bcast( tcg,     ionode_id, intra_image_comm )
1033       CALL mp_bcast( maxiter, ionode_id, intra_image_comm )
1034       CALL mp_bcast( etresh,  ionode_id, intra_image_comm )
1035       CALL mp_bcast( passop,  ionode_id, intra_image_comm )
1036       CALL mp_bcast( niter_cg_restart, ionode_id, intra_image_comm )
1037       !
1038       ! ... electric field
1039       !
1040       CALL mp_bcast( epol,   ionode_id, intra_image_comm )
1041       CALL mp_bcast( efield, ionode_id, intra_image_comm )
1042       !
1043       CALL mp_bcast( epol2,   ionode_id, intra_image_comm )
1044       CALL mp_bcast( efield2, ionode_id, intra_image_comm )
1045       CALL mp_bcast( efield_cart,   ionode_id, intra_image_comm )
1046       CALL mp_bcast( efield_phase,   ionode_id, intra_image_comm )
1047       !
1048       ! ... occupation constraints ...
1049       !
1050       CALL mp_bcast( occupation_constraints, ionode_id, intra_image_comm )
1051       !
1052       ! ... real space ...
1053       CALL mp_bcast( real_space,         ionode_id, intra_image_comm )
1054       CALL mp_bcast( adaptive_thr,       ionode_id, intra_image_comm )
1055       CALL mp_bcast( conv_thr_init,      ionode_id, intra_image_comm )
1056       CALL mp_bcast( conv_thr_multi,     ionode_id, intra_image_comm )
1057       !
1058       ! ... CP-BO ...
1059       CALL mp_bcast( tcpbo,                 ionode_id, intra_image_comm )
1060       CALL mp_bcast( emass_emin,            ionode_id, intra_image_comm )
1061       CALL mp_bcast( emass_cutoff_emin,     ionode_id, intra_image_comm )
1062       CALL mp_bcast( electron_damping_emin, ionode_id, intra_image_comm )
1063       CALL mp_bcast( dt_emin,               ionode_id, intra_image_comm )
1064       !
1065       RETURN
1066       !
1067     END SUBROUTINE
1068     !
1069     !
1070     !=----------------------------------------------------------------------=!
1071     !
1072     !  Broadcast variables values for Namelist IONS
1073     !
1074     !=----------------------------------------------------------------------=!
1075     !
1076     !-----------------------------------------------------------------------
1077     SUBROUTINE ions_bcast()
1078       !-----------------------------------------------------------------------
1079       !
1080       USE io_global, ONLY: ionode_id
1081       USE mp,        ONLY: mp_bcast
1082       USE mp_images, ONLY : intra_image_comm
1083       !
1084       IMPLICIT NONE
1085       !
1086       CALL mp_bcast( ion_dynamics,      ionode_id, intra_image_comm )
1087       CALL mp_bcast( ion_radius,        ionode_id, intra_image_comm )
1088       CALL mp_bcast( ion_damping,       ionode_id, intra_image_comm )
1089       CALL mp_bcast( ion_positions,     ionode_id, intra_image_comm )
1090       CALL mp_bcast( ion_velocities,    ionode_id, intra_image_comm )
1091       CALL mp_bcast( ion_temperature,   ionode_id, intra_image_comm )
1092       CALL mp_bcast( tempw,             ionode_id, intra_image_comm )
1093       CALL mp_bcast( fnosep,            ionode_id, intra_image_comm )
1094       CALL mp_bcast( nhgrp,             ionode_id, intra_image_comm )
1095       CALL mp_bcast( fnhscl,            ionode_id, intra_image_comm )
1096       CALL mp_bcast( nhpcl,             ionode_id, intra_image_comm )
1097       CALL mp_bcast( nhptyp,            ionode_id, intra_image_comm )
1098       CALL mp_bcast( ndega,             ionode_id, intra_image_comm )
1099       CALL mp_bcast( tranp,             ionode_id, intra_image_comm )
1100       CALL mp_bcast( amprp,             ionode_id, intra_image_comm )
1101       CALL mp_bcast( greasp,            ionode_id, intra_image_comm )
1102       CALL mp_bcast( tolp,              ionode_id, intra_image_comm )
1103       CALL mp_bcast( ion_nstepe,        ionode_id, intra_image_comm )
1104       CALL mp_bcast( ion_maxstep,       ionode_id, intra_image_comm )
1105       CALL mp_bcast( delta_t,           ionode_id, intra_image_comm )
1106       CALL mp_bcast( nraise,            ionode_id, intra_image_comm )
1107       CALL mp_bcast( refold_pos,        ionode_id, intra_image_comm )
1108       CALL mp_bcast( remove_rigid_rot,  ionode_id, intra_image_comm )
1109       CALL mp_bcast( upscale,           ionode_id, intra_image_comm )
1110       CALL mp_bcast( pot_extrapolation, ionode_id, intra_image_comm )
1111       CALL mp_bcast( wfc_extrapolation, ionode_id, intra_image_comm )
1112       !
1113       ! ... BFGS
1114       !
1115       CALL mp_bcast( bfgs_ndim,        ionode_id, intra_image_comm )
1116       CALL mp_bcast( trust_radius_max, ionode_id, intra_image_comm )
1117       CALL mp_bcast( trust_radius_min, ionode_id, intra_image_comm )
1118       CALL mp_bcast( trust_radius_ini, ionode_id, intra_image_comm )
1119       CALL mp_bcast( w_1,              ionode_id, intra_image_comm )
1120       CALL mp_bcast( w_2,              ionode_id, intra_image_comm )
1121       !
1122       CALL mp_bcast(l_mplathe,         ionode_id, intra_image_comm )
1123       CALL mp_bcast(n_muller,          ionode_id, intra_image_comm )
1124       CALL mp_bcast(np_muller,         ionode_id, intra_image_comm )
1125       CALL mp_bcast(l_exit_muller,     ionode_id, intra_image_comm )
1126
1127
1128       RETURN
1129       !
1130     END SUBROUTINE
1131     !
1132     !=----------------------------------------------------------------------=!
1133     !
1134     !  Broadcast variables values for Namelist CELL
1135     !
1136     !=----------------------------------------------------------------------=!
1137     !
1138     !-----------------------------------------------------------------------
1139     SUBROUTINE cell_bcast()
1140       !-----------------------------------------------------------------------
1141       !
1142       USE io_global, ONLY: ionode_id
1143       USE mp, ONLY: mp_bcast
1144       USE mp_images, ONLY : intra_image_comm
1145       !
1146       IMPLICIT NONE
1147       !
1148       CALL mp_bcast( cell_parameters,  ionode_id, intra_image_comm )
1149       CALL mp_bcast( cell_dynamics,    ionode_id, intra_image_comm )
1150       CALL mp_bcast( cell_velocities,  ionode_id, intra_image_comm )
1151       CALL mp_bcast( cell_dofree,      ionode_id, intra_image_comm )
1152       CALL mp_bcast( press,            ionode_id, intra_image_comm )
1153       CALL mp_bcast( wmass,            ionode_id, intra_image_comm )
1154       CALL mp_bcast( cell_temperature, ionode_id, intra_image_comm )
1155       CALL mp_bcast( temph,            ionode_id, intra_image_comm )
1156       CALL mp_bcast( fnoseh,           ionode_id, intra_image_comm )
1157       CALL mp_bcast( greash,           ionode_id, intra_image_comm )
1158       CALL mp_bcast( cell_factor,      ionode_id, intra_image_comm )
1159       CALL mp_bcast( cell_nstepe,      ionode_id, intra_image_comm )
1160       CALL mp_bcast( cell_damping,     ionode_id, intra_image_comm )
1161       CALL mp_bcast( press_conv_thr,   ionode_id, intra_image_comm )
1162       CALL mp_bcast( treinit_gvecs,    ionode_id, intra_image_comm )
1163       !
1164       RETURN
1165       !
1166     END SUBROUTINE
1167     !
1168     !=----------------------------------------------------------------------=!
1169     !
1170     !  Broadcast variables values for Namelist PRESS_AI
1171     !
1172     !=----------------------------------------------------------------------=!
1173     !
1174     !----------------------------------------------------------------------
1175     SUBROUTINE press_ai_bcast()
1176       !----------------------------------------------------------------------
1177       !
1178       USE io_global, ONLY: ionode_id
1179       USE mp,        ONLY: mp_bcast
1180       USE mp_images, ONLY : intra_image_comm
1181       !
1182       IMPLICIT NONE
1183       !
1184       !
1185       CALL mp_bcast( abivol, ionode_id, intra_image_comm )
1186       CALL mp_bcast( abisur, ionode_id, intra_image_comm )
1187       CALL mp_bcast( t_gauss, ionode_id, intra_image_comm )
1188       CALL mp_bcast( cntr, ionode_id, intra_image_comm )
1189       CALL mp_bcast( P_ext, ionode_id, intra_image_comm )
1190       CALL mp_bcast( Surf_t, ionode_id, intra_image_comm )
1191       CALL mp_bcast( pvar, ionode_id, intra_image_comm )
1192       CALL mp_bcast( P_in, ionode_id, intra_image_comm )
1193       CALL mp_bcast( P_fin, ionode_id, intra_image_comm )
1194       CALL mp_bcast( delta_eps, ionode_id, intra_image_comm )
1195       CALL mp_bcast( delta_sigma, ionode_id, intra_image_comm )
1196       CALL mp_bcast( fill_vac, ionode_id, intra_image_comm )
1197       CALL mp_bcast( scale_at, ionode_id, intra_image_comm )
1198       CALL mp_bcast( n_cntr, ionode_id, intra_image_comm )
1199       CALL mp_bcast( axis, ionode_id, intra_image_comm )
1200       CALL mp_bcast( rho_thr, ionode_id, intra_image_comm )
1201       CALL mp_bcast( dthr, ionode_id, intra_image_comm )
1202       CALL mp_bcast( step_rad, ionode_id, intra_image_comm )
1203       CALL mp_bcast( jellium, ionode_id, intra_image_comm )
1204       CALL mp_bcast( R_j, ionode_id, intra_image_comm )
1205       CALL mp_bcast( h_j, ionode_id, intra_image_comm )
1206       !
1207       RETURN
1208       !
1209     END SUBROUTINE
1210     !
1211     !=----------------------------------------------------------------------------=!
1212     !
1213     !  Broadcast variables values for Namelist WANNIER
1214     !
1215     !=----------------------------------------------------------------------=!
1216     !
1217     !-----------------------------------------------------------------------
1218     SUBROUTINE wannier_bcast()
1219       !-----------------------------------------------------------------------
1220       !
1221       USE io_global, ONLY: ionode_id
1222       USE mp,        ONLY: mp_bcast
1223       USE mp_images, ONLY : intra_image_comm
1224       !
1225       IMPLICIT NONE
1226       !
1227       CALL mp_bcast( wf_efield,   ionode_id, intra_image_comm )
1228       CALL mp_bcast( wf_switch,   ionode_id, intra_image_comm )
1229       CALL mp_bcast( sw_len,      ionode_id, intra_image_comm )
1230       CALL mp_bcast( efx0,        ionode_id, intra_image_comm )
1231       CALL mp_bcast( efy0,        ionode_id, intra_image_comm )
1232       CALL mp_bcast( efz0,        ionode_id, intra_image_comm )
1233       CALL mp_bcast( efx1,        ionode_id, intra_image_comm )
1234       CALL mp_bcast( efy1,        ionode_id, intra_image_comm )
1235       CALL mp_bcast( efz1,        ionode_id, intra_image_comm )
1236       CALL mp_bcast( wfsd,        ionode_id, intra_image_comm )
1237       CALL mp_bcast( wfdt,        ionode_id, intra_image_comm )
1238       CALL mp_bcast( maxwfdt,     ionode_id, intra_image_comm )
1239       CALL mp_bcast( wf_q,        ionode_id, intra_image_comm )
1240       CALL mp_bcast( wf_friction, ionode_id, intra_image_comm )
1241       CALL mp_bcast( nit,         ionode_id, intra_image_comm )
1242       CALL mp_bcast( nsd,         ionode_id, intra_image_comm )
1243       CALL mp_bcast( nsteps,      ionode_id, intra_image_comm )
1244       CALL mp_bcast( tolw,        ionode_id, intra_image_comm )
1245       CALL mp_bcast( adapt,       ionode_id, intra_image_comm )
1246       CALL mp_bcast( calwf,       ionode_id, intra_image_comm )
1247       CALL mp_bcast( nwf,         ionode_id, intra_image_comm )
1248       CALL mp_bcast( wffort,      ionode_id, intra_image_comm )
1249       CALL mp_bcast( writev,      ionode_id, intra_image_comm )
1250!=================================================================
1251!exx_wf related
1252       CALL mp_bcast( exx_neigh,       ionode_id, intra_image_comm )
1253       CALL mp_bcast( exx_poisson_eps, ionode_id, intra_image_comm )
1254       CALL mp_bcast( exx_dis_cutoff,  ionode_id, intra_image_comm )
1255       CALL mp_bcast( exx_ps_rcut_self, ionode_id, intra_image_comm )
1256       CALL mp_bcast( exx_ps_rcut_pair, ionode_id, intra_image_comm )
1257       CALL mp_bcast( exx_me_rcut_self, ionode_id, intra_image_comm )
1258       CALL mp_bcast( exx_me_rcut_pair, ionode_id, intra_image_comm )
1259       CALL mp_bcast( exx_use_cube_domain, ionode_id, intra_image_comm )
1260       CALL mp_bcast( vnbsp,       ionode_id, intra_image_comm )
1261       !
1262       RETURN
1263       !
1264     END SUBROUTINE
1265     !
1266     !=----------------------------------------------------------------------------=!
1267     !
1268     !  Broadcast variables values for Namelist WANNIER_NEW
1269     !
1270     !=----------------------------------------------------------------------------=!
1271     !
1272     !----------------------------------------------------------------------
1273     SUBROUTINE wannier_ac_bcast()
1274       !----------------------------------------------------------------------
1275       !
1276       USE io_global, ONLY: ionode_id
1277       USE mp,        ONLY: mp_bcast
1278       USE mp_images, ONLY : intra_image_comm
1279       !
1280       IMPLICIT NONE
1281       !
1282       !
1283       CALL mp_bcast( plot_wannier,ionode_id, intra_image_comm )
1284       CALL mp_bcast( use_energy_int,ionode_id, intra_image_comm )
1285       CALL mp_bcast( print_wannier_coeff,ionode_id, intra_image_comm )
1286       CALL mp_bcast( nwan,        ionode_id, intra_image_comm )
1287       CALL mp_bcast( plot_wan_num,ionode_id, intra_image_comm )
1288       CALL mp_bcast( plot_wan_spin,ionode_id, intra_image_comm )
1289!       CALL mp_bcast( wan_data,ionode_id, intra_image_comm )
1290       CALL mp_bcast( constrain_pot,   ionode_id, intra_image_comm )
1291       RETURN
1292       !
1293     END SUBROUTINE
1294
1295     !
1296     !=----------------------------------------------------------------------=!
1297     !
1298     !  Check input values for Namelist CONTROL
1299     !
1300     !=----------------------------------------------------------------------=!
1301     !
1302     !-----------------------------------------------------------------------
1303     SUBROUTINE control_checkin( prog )
1304       !-----------------------------------------------------------------------
1305       !
1306       IMPLICIT NONE
1307       !
1308       CHARACTER(LEN=2)  :: prog   ! ... specify the calling program
1309       CHARACTER(LEN=20) :: sub_name = ' control_checkin '
1310       INTEGER           :: i
1311       LOGICAL           :: allowed = .FALSE.
1312       !
1313       !
1314       DO i = 1, SIZE( calculation_allowed )
1315          IF( TRIM(calculation) == calculation_allowed(i) ) allowed = .TRUE.
1316       END DO
1317       IF( .NOT. allowed ) &
1318          CALL errore( sub_name, ' calculation "'// &
1319                       & TRIM(calculation)//'" not allowed ',1)
1320       IF( ndr < 50 ) &
1321          CALL errore( sub_name,' ndr out of range ', 1 )
1322       IF( ndw > 0 .AND. ndw < 50 ) &
1323          CALL errore( sub_name,' ndw out of range ', 1 )
1324       IF( nstep < 0 ) &
1325          CALL errore( sub_name,' nstep out of range ', 1 )
1326       IF( iprint < 1 ) &
1327          CALL errore( sub_name,' iprint out of range ', 1 )
1328
1329       IF( prog == 'PW' ) THEN
1330         IF( isave > 0 ) &
1331           CALL infomsg( sub_name,' isave not used in PW ' )
1332       ELSE
1333         IF( isave < 1 ) &
1334           CALL errore( sub_name,' isave out of range ', 1 )
1335       END IF
1336
1337       IF( dt < 0.0_DP ) &
1338          CALL errore( sub_name,' dt out of range ', 1 )
1339       IF( max_seconds < 0.0_DP ) &
1340          CALL errore( sub_name,' max_seconds out of range ', 1 )
1341
1342       IF( ekin_conv_thr < 0.0_DP ) THEN
1343          IF( prog == 'PW' ) THEN
1344            CALL infomsg( sub_name,' ekin_conv_thr not used in PW ')
1345          ELSE
1346            CALL errore( sub_name,' ekin_conv_thr out of range ', 1 )
1347          END IF
1348       END IF
1349
1350       IF( etot_conv_thr < 0.0_DP ) &
1351          CALL errore( sub_name,' etot_conv_thr out of range ', 1 )
1352       IF( forc_conv_thr < 0.0_DP ) &
1353          CALL errore( sub_name,' forc_conv_thr out of range ', 1 )
1354       IF( prog == 'CP' ) THEN
1355          IF( dipfield ) &
1356             CALL infomsg( sub_name,' dipfield not yet implemented ')
1357          IF( lberry ) &
1358             CALL infomsg( sub_name,' lberry not implemented yet ')
1359          IF( gdir /= 0 ) &
1360             CALL infomsg( sub_name,' gdir not used ')
1361          IF( nppstr /= 0 ) &
1362             CALL infomsg( sub_name,' nppstr not used ')
1363       END IF
1364       !
1365       IF( prog == 'PW' .AND. TRIM( restart_mode ) == 'reset_counters' ) THEN
1366         CALL infomsg ( sub_name, ' restart_mode == reset_counters' // &
1367                    & ' not implemented in PW ' )
1368       END IF
1369       !
1370       IF( refg < 0 ) &
1371         CALL errore( sub_name, ' wrong table interval refg ', 1 )
1372       !
1373       IF( ( prog == 'CP' ) .AND. ( TRIM(memory) == 'small' ) .AND. wf_collect ) &
1374         CALL errore( sub_name, ' wf_collect = .true. is not allowed with memory = small ', 1 )
1375
1376       allowed = .FALSE.
1377       DO i = 1, SIZE( memory_allowed )
1378          IF( TRIM(memory) == memory_allowed(i) ) allowed = .TRUE.
1379       END DO
1380       IF( .NOT. allowed ) &
1381          CALL errore(sub_name, ' memory "' // TRIM(memory)//'" not allowed',1)
1382       ! TB
1383       IF ( gate .and. tefield .and. (.not. dipfield) ) &
1384          CALL errore(sub_name, ' gate cannot be used with tefield if dipole correction is not active', 1)
1385       IF ( gate .and. dipfield .and. (.not. tefield) ) &
1386          CALL errore(sub_name, ' dipole correction is not active if tefield = .false.', 1)
1387
1388       RETURN
1389       !
1390     END SUBROUTINE
1391     !
1392     !=----------------------------------------------------------------------=!
1393     !
1394     !  Check input values for Namelist SYSTEM
1395     !
1396     !=----------------------------------------------------------------------=!
1397     !
1398     !-----------------------------------------------------------------------
1399     SUBROUTINE system_checkin( prog )
1400       !-----------------------------------------------------------------------
1401       !
1402       IMPLICIT NONE
1403       !
1404       CHARACTER(LEN=2)  :: prog   ! ... specify the calling program
1405       CHARACTER(LEN=20) :: sub_name = ' system_checkin '
1406       INTEGER           :: i
1407       LOGICAL           :: allowed
1408       !
1409       !
1410       IF( ( ibrav /= 0 ) .AND. (celldm(1) == 0.0_DP) .AND. ( a == 0.0_DP ) ) &
1411           CALL errore( ' iosys ', &
1412                      & ' invalid lattice parameters ( celldm or a )', 1 )
1413       !
1414       IF( nat < 0 ) &
1415          CALL errore( sub_name ,' nat less than zero ', MAX( nat, 1) )
1416       !
1417       IF( ntyp < 0 ) &
1418          CALL errore( sub_name ,' ntyp less than zero ', MAX( ntyp, 1) )
1419       IF( ntyp < 0 .OR. ntyp > nsx ) &
1420          CALL errore( sub_name , &
1421                       & ' ntyp too large, increase NSX ', MAX( ntyp, 1) )
1422       !
1423       IF( nspin < 1 .OR. nspin > 4 .OR. nspin == 3 ) &
1424          CALL errore( sub_name ,' nspin out of range ', MAX(nspin, 1 ) )
1425       !
1426       IF( ecutwfc < 0.0_DP ) &
1427          CALL errore( sub_name ,' ecutwfc out of range ',1)
1428       IF( ecutrho < 0.0_DP ) &
1429          CALL errore( sub_name ,' ecutrho out of range ',1)
1430       !
1431       IF( prog == 'CP' ) THEN
1432          IF( degauss /= 0.0_DP ) &
1433             CALL infomsg( sub_name ,' degauss is not used in CP ')
1434       END IF
1435       !
1436       IF( ecfixed < 0.0_DP ) &
1437          CALL errore( sub_name ,' ecfixed out of range ',1)
1438       IF( qcutz < 0.0_DP ) &
1439          CALL errore( sub_name ,' qcutz out of range ',1)
1440       IF( q2sigma < 0.0_DP ) &
1441          CALL errore( sub_name ,' q2sigma out of range ',1)
1442       IF( prog == 'CP' ) THEN
1443          IF( ANY(starting_magnetization /= SM_NOT_SET ) ) &
1444             CALL infomsg( sub_name ,&
1445                          & ' starting_magnetization is not used in CP ')
1446          IF( la2F ) &
1447             CALL infomsg( sub_name ,' la2F is not used in CP ')
1448          IF( ANY(Hubbard_alpha /= 0.0_DP) ) &
1449             CALL infomsg( sub_name ,' Hubbard_alpha is not used in CP ')
1450          IF( nosym ) &
1451             CALL infomsg( sub_name ,' nosym not implemented in CP ')
1452          IF( nosym_evc ) &
1453             CALL infomsg( sub_name ,' nosym_evc not implemented in CP ')
1454          IF( noinv ) &
1455             CALL infomsg( sub_name ,' noinv not implemented in CP ')
1456       END IF
1457       !
1458       ! ... control on SIC variables
1459       !
1460       IF ( sic /= 'none' ) THEN
1461          !
1462          IF (sic_epsilon > 1.0_DP )  &
1463             CALL errore( sub_name, &
1464                        & ' invalid sic_epsilon, greater than 1.',1 )
1465          IF (sic_epsilon < 0.0_DP )  &
1466             CALL errore( sub_name, &
1467                        & ' invalid sic_epsilon, less than 0 ',1 )
1468          IF (sic_alpha > 1.0_DP )  &
1469             CALL errore( sub_name, &
1470                        & ' invalid sic_alpha, greater than 1.',1 )
1471          IF (sic_alpha < 0.0_DP )  &
1472             CALL errore( sub_name, &
1473                        & ' invalid sic_alpha, less than 0 ',1 )
1474          !
1475          IF ( .NOT. force_pairing ) &
1476             CALL errore( sub_name, &
1477                        & ' invalid force_pairing with sic activated', 1 )
1478          IF ( nspin /= 2 ) &
1479             CALL errore( sub_name, &
1480                        & ' invalid nspin with sic activated', 1 )
1481          IF ( tot_magnetization /= 1._DP )  &
1482             CALL errore( sub_name, &
1483                  & ' invalid tot_magnetization_ with sic activated', 1 )
1484          !
1485       ENDIF
1486       !
1487       ! ... control on EXX variables
1488       !
1489       DO i = 1, SIZE( exxdiv_treatment_allowed )
1490          IF( TRIM(exxdiv_treatment) == exxdiv_treatment_allowed(i) ) allowed = .TRUE.
1491       END DO
1492       IF( .NOT. allowed ) CALL errore(sub_name, &
1493           ' invalid exxdiv_treatment: '//TRIM(exxdiv_treatment), 1 )
1494       !
1495       IF ( TRIM(exxdiv_treatment) == "yukawa" .AND. yukawa <= 0.0 ) &
1496          CALL errore(sub_name, ' invalid value for yukawa', 1 )
1497       !
1498       IF ( TRIM(exxdiv_treatment) == "vcut_ws" .AND. ecutvcut <= 0.0 ) &
1499          CALL errore(sub_name, ' invalid value for ecutvcut', 1 )
1500       !
1501       IF ( x_gamma_extrapolation .AND. ( TRIM(exxdiv_treatment) == "vcut_ws" .OR. &
1502                                          TRIM(exxdiv_treatment) == "vcut_spherical" ) ) &
1503          CALL errore(sub_name, ' x_gamma_extrapolation cannot be used with vcut', 1 )
1504       !
1505       ! TB - gate check
1506       !
1507       IF ( gate .and. tot_charge == 0 ) &
1508          CALL errore(sub_name, ' charged plane (gate) to compensate tot_charge of 0', 1)
1509       RETURN
1510       !
1511       ! ... control on FCP variables
1512       !
1513       allowed = .FALSE.
1514       DO i = 1, SIZE(fcp_relax_allowed)
1515          IF( TRIM(fcp_relax) == fcp_relax_allowed(i) ) allowed = .TRUE.
1516       END DO
1517       IF( .NOT. allowed ) &
1518          CALL errore(sub_name, ' fcp_relax '''//TRIM(fcp_relax)//''' not allowed ', 1)
1519       !
1520     END SUBROUTINE
1521     !
1522     !=----------------------------------------------------------------------=!
1523     !
1524     !  Check input values for Namelist ELECTRONS
1525     !
1526     !=----------------------------------------------------------------------=!
1527     !
1528     !-----------------------------------------------------------------------
1529     SUBROUTINE electrons_checkin( prog )
1530       !-----------------------------------------------------------------------
1531       !
1532       IMPLICIT NONE
1533       !
1534       CHARACTER(LEN=2)  :: prog   ! ... specify the calling program
1535       CHARACTER(LEN=20) :: sub_name = ' electrons_checkin '
1536       INTEGER           :: i
1537       LOGICAL           :: allowed = .FALSE.
1538       !
1539       !
1540       DO i = 1, SIZE(electron_dynamics_allowed)
1541          IF( TRIM(electron_dynamics) == &
1542              electron_dynamics_allowed(i) ) allowed = .TRUE.
1543       END DO
1544       IF( .NOT. allowed ) &
1545          CALL errore( sub_name, ' electron_dynamics "'//&
1546                       & TRIM(electron_dynamics)//'" not allowed ',1)
1547       IF( emass <= 0.0_DP ) &
1548          CALL errore( sub_name, ' emass less or equal 0 ',1)
1549       IF( emass_cutoff <= 0.0_DP ) &
1550          CALL errore( sub_name, ' emass_cutoff less or equal 0 ',1)
1551       IF( ortho_eps <= 0.0_DP ) &
1552          CALL errore( sub_name, ' ortho_eps less or equal 0 ',1)
1553       IF( ortho_max < 1 ) &
1554          CALL errore( sub_name, ' ortho_max less than 1 ',1)
1555       IF( fnosee <= 0.0_DP ) &
1556          CALL errore( sub_name, ' fnosee less or equal 0 ',1)
1557       IF( ekincw <= 0.0_DP ) &
1558          CALL errore( sub_name, ' ekincw less or equal 0 ',1)
1559       IF( occupation_constraints ) &
1560          CALL errore( sub_name, ' occupation_constraints not yet implemented ',1)
1561
1562!
1563       RETURN
1564     END SUBROUTINE
1565     !
1566     !=----------------------------------------------------------------------=!
1567     !
1568     !  Check input values for Namelist IONS
1569     !
1570     !=----------------------------------------------------------------------=!
1571     !
1572     !-----------------------------------------------------------------------
1573     SUBROUTINE ions_checkin( prog )
1574       !-----------------------------------------------------------------------
1575       !
1576       IMPLICIT NONE
1577       !
1578       CHARACTER(LEN=2)  :: prog   ! ... specify the calling program
1579       CHARACTER(LEN=20) :: sub_name = ' ions_checkin '
1580       INTEGER           :: i
1581       LOGICAL           :: allowed = .FALSE.
1582       !
1583       !
1584       allowed = .FALSE.
1585       DO i = 1, SIZE(ion_dynamics_allowed)
1586          IF( TRIM(ion_dynamics) == ion_dynamics_allowed(i) ) allowed = .TRUE.
1587       END DO
1588       IF( .NOT. allowed ) &
1589          CALL errore( sub_name, ' ion_dynamics "'// &
1590                       & TRIM(ion_dynamics)//'" not allowed ',1)
1591       IF( tempw <= 0.0_DP ) &
1592          CALL errore( sub_name,' tempw out of range ',1)
1593       IF( fnosep( 1 ) <= 0.0_DP ) &
1594          CALL errore( sub_name,' fnosep out of range ',1)
1595       IF( nhpcl > nhclm ) &
1596          CALL infomsg ( sub_name,' nhpcl should be less than nhclm')
1597       IF( nhpcl < 0 ) &
1598          CALL infomsg ( sub_name,' nhpcl out of range ')
1599       IF( ion_nstepe <= 0 ) &
1600          CALL errore( sub_name,' ion_nstepe out of range ',1)
1601       IF( ion_maxstep < 0 ) &
1602          CALL errore( sub_name,' ion_maxstep out of range ',1)
1603       !
1604       RETURN
1605       !
1606     END SUBROUTINE
1607     !
1608     !=----------------------------------------------------------------------=!
1609     !
1610     !  Check input values for Namelist CELL
1611     !
1612     !=----------------------------------------------------------------------=!
1613     !
1614     !=----------------------------------------------------------------------=!
1615     !
1616     !-----------------------------------------------------------------------
1617     SUBROUTINE cell_checkin( prog )
1618       !-----------------------------------------------------------------------
1619       !
1620       IMPLICIT NONE
1621       !
1622       CHARACTER(LEN=2)  :: prog   ! ... specify the calling program
1623       CHARACTER(LEN=20) :: sub_name = ' cell_checkin '
1624       INTEGER           :: i
1625       LOGICAL           :: allowed = .FALSE.
1626       !
1627       !
1628       DO i = 1, SIZE(cell_dynamics_allowed)
1629          IF( TRIM(cell_dynamics) == &
1630              cell_dynamics_allowed(i) ) allowed = .TRUE.
1631       END DO
1632       IF( .NOT. allowed ) &
1633          CALL errore( sub_name, ' cell_dynamics "'// &
1634                       TRIM(cell_dynamics)//'" not allowed ',1)
1635       IF( wmass < 0.0_DP ) &
1636          CALL errore( sub_name,' wmass out of range ',1)
1637       IF( prog == 'CP' ) THEN
1638          IF( cell_factor /= 0.0_DP ) &
1639             CALL infomsg( sub_name,' cell_factor not used in CP ')
1640       END IF
1641       IF( cell_nstepe <= 0 ) &
1642          CALL errore( sub_name,' cell_nstepe out of range ',1)
1643       !
1644       RETURN
1645       !
1646     END SUBROUTINE
1647     !
1648     !=----------------------------------------------------------------------=!
1649     !
1650     !  Check input values for Namelist WANNIER
1651     !
1652     !=----------------------------------------------------------------------=!
1653     !
1654     !-----------------------------------------------------------------------
1655     SUBROUTINE wannier_checkin( prog )
1656       !-----------------------------------------------------------------------
1657       !
1658       IMPLICIT NONE
1659       !
1660       CHARACTER(LEN=2)  :: prog   ! ... specify the calling program
1661       CHARACTER(LEN=20) :: sub_name = 'wannier_checkin'
1662       !
1663       IF ( calwf < 1 .OR. calwf > 5 ) &
1664          CALL errore( sub_name, ' calwf out of range ', 1 )
1665       !
1666       IF ( wfsd < 1 .OR. wfsd > 3 ) &
1667          CALL errore( sub_name, ' wfsd out of range ', 1 )      !
1668       !
1669       RETURN
1670       !
1671     END SUBROUTINE
1672     !
1673     !=----------------------------------------------------------------------=!
1674     !
1675     !  Check input values for Namelist WANNIER_NEW
1676     !
1677     !=----------------------------------------------------------------------=!
1678     !
1679     !----------------------------------------------------------------------
1680     SUBROUTINE wannier_ac_checkin( prog )
1681       !--------------------------------------------------------------------
1682       !
1683       IMPLICIT NONE
1684       !
1685       CHARACTER(LEN=2)  :: prog   ! ... specify the calling program
1686       CHARACTER(LEN=20) :: sub_name = 'wannier_new_checkin'
1687       !
1688       !
1689       IF ( nwan > nwanx ) &
1690          CALL errore( sub_name, ' nwan out of range ', 1 )
1691
1692       IF ( plot_wan_num < 0 .OR. plot_wan_num > nwan ) &
1693          CALL errore( sub_name, ' plot_wan_num out of range ', 1 )
1694
1695       IF ( plot_wan_spin < 0 .OR. plot_wan_spin > 2 ) &
1696          CALL errore( sub_name, ' plot_wan_spin out of range ', 1 )
1697       !
1698       RETURN
1699       !
1700     END SUBROUTINE
1701     !
1702     !=----------------------------------------------------------------------=!
1703     !
1704     !  Set values according to the "calculation" variable
1705     !
1706     !=----------------------------------------------------------------------=!
1707     !
1708     !-----------------------------------------------------------------------
1709     SUBROUTINE fixval( prog )
1710       !-----------------------------------------------------------------------
1711       !
1712       USE constants, ONLY : e2
1713       !
1714       IMPLICIT NONE
1715       !
1716       CHARACTER(LEN=2)  :: prog   ! ... specify the calling program
1717       CHARACTER(LEN=20) :: sub_name = ' fixval '
1718       !
1719       !
1720       SELECT CASE( TRIM( calculation ) )
1721          CASE ('scf', 'ensemble')
1722             IF( prog == 'CP' ) THEN
1723                 electron_dynamics = 'damp'
1724                 ion_dynamics      = 'none'
1725                 cell_dynamics     = 'none'
1726             END IF
1727          CASE ('nscf', 'bands')
1728             IF( prog == 'CP' ) occupations = 'bogus'
1729             IF( prog == 'CP' ) electron_dynamics = 'damp'
1730          CASE ( 'cp-wf' )
1731             IF( prog == 'CP' ) THEN
1732                electron_dynamics = 'damp'
1733                ion_dynamics      = 'damp'
1734             END IF
1735             IF ( prog == 'PW' ) &
1736                CALL errore( sub_name, ' calculation ' // &
1737                           & TRIM( calculation ) // ' not implemented ', 1 )
1738          CASE ( 'vc-cp-wf' )
1739             IF( prog == 'CP' ) THEN
1740                electron_dynamics = 'verlet'
1741                ion_dynamics      = 'verlet'
1742                cell_dynamics     = 'pr'
1743             ELSE IF( prog == 'PW' ) THEN
1744                CALL errore( sub_name, ' calculation ' // &
1745                           & TRIM( calculation ) // ' not implemented ', 1 )
1746             END IF
1747             !
1748!=========================================================================
1749!Lingzhu Kong
1750          CASE ( 'cp-wf-nscf' )
1751             IF( prog == 'CP' ) THEN
1752                occupations       = 'fixed'
1753                electron_dynamics = 'damp'
1754                ion_dynamics      = 'damp'
1755             END IF
1756             IF ( prog == 'PW' ) &
1757                CALL errore( sub_name, ' calculation ' // &
1758                           & TRIM( calculation ) // ' not implemented ', 1 )
1759!=========================================================================
1760          CASE ('relax')
1761             IF( prog == 'CP' ) THEN
1762                electron_dynamics = 'damp'
1763                ion_dynamics      = 'damp'
1764             ELSE IF( prog == 'PW' ) THEN
1765                ion_dynamics = 'bfgs'
1766             END IF
1767          CASE ( 'md', 'cp' )
1768             IF( prog == 'CP' ) THEN
1769                electron_dynamics = 'verlet'
1770                ion_dynamics      = 'verlet'
1771             ELSE IF( prog == 'PW' ) THEN
1772                ion_dynamics = 'verlet'
1773             END IF
1774          CASE ('vc-relax')
1775             IF( prog == 'CP' ) THEN
1776                electron_dynamics = 'damp'
1777                ion_dynamics      = 'damp'
1778                cell_dynamics     = 'damp-pr'
1779             ELSE IF( prog == 'PW' ) THEN
1780                ion_dynamics = 'bfgs'
1781                cell_dynamics= 'bfgs'
1782             END IF
1783          CASE ( 'vc-md', 'vc-cp' )
1784             IF( prog == 'CP' ) THEN
1785                electron_dynamics = 'verlet'
1786                ion_dynamics      = 'verlet'
1787                cell_dynamics     = 'pr'
1788             ELSE IF( prog == 'PW' ) THEN
1789                ion_dynamics = 'beeman'
1790             END IF
1791             !
1792          CASE DEFAULT
1793             !
1794             CALL errore( sub_name,' calculation '// &
1795                        & TRIM(calculation)//' not implemented ', 1 )
1796             !
1797       END SELECT
1798       !
1799       IF ( prog == 'PW' ) THEN
1800          !
1801          IF ( calculation == 'nscf' .OR. calculation == 'bands'  ) THEN
1802             !
1803             startingpot = 'file'
1804             startingwfc = 'atomic+random'
1805             !
1806          ELSE IF ( restart_mode == "from_scratch" ) THEN
1807             !
1808             startingwfc = 'atomic+random'
1809             startingpot = 'atomic'
1810             !
1811          ELSE
1812             !
1813             startingwfc = 'file'
1814             startingpot = 'file'
1815             !
1816          END IF
1817          !
1818       ELSE IF ( prog == 'CP' ) THEN
1819          !
1820          startingwfc = 'random'
1821          startingpot = ' '
1822          !
1823       END IF
1824       !
1825       IF ( TRIM( sic ) /= 'none' ) THEN
1826         force_pairing = ( nspin == 2 .AND. ( tot_magnetization==0._dp .OR. &
1827                                              tot_magnetization==1._dp ) )
1828       END IF
1829       !
1830       RETURN
1831       !
1832     END SUBROUTINE
1833     !
1834     !=----------------------------------------------------------------------=!
1835     !
1836     !  Namelist parsing main routine
1837     !
1838     !=----------------------------------------------------------------------=!
1839     !
1840     !-----------------------------------------------------------------------
1841     SUBROUTINE read_namelists( prog_, unit )
1842       !-----------------------------------------------------------------------
1843       !
1844       !  this routine reads data from standard input and puts them into
1845       !  module-scope variables (accessible from other routines by including
1846       !  this module, or the one that contains them)
1847       !  ----------------------------------------------
1848       !
1849       ! ... declare modules
1850       !
1851       USE io_global, ONLY : ionode, ionode_id
1852       USE mp,        ONLY : mp_bcast
1853       USE mp_images, ONLY : intra_image_comm
1854       !
1855       IMPLICIT NONE
1856       !
1857       ! ... declare variables
1858       !
1859       CHARACTER(LEN=*) :: prog_  ! specifies the calling program, allowed:
1860                                  !     prog = 'PW'     pwscf
1861                                  !     prog = 'CP'     cp
1862                                  !     prog = 'PW+iPi' pwscf + i-Pi
1863       !
1864       INTEGER, INTENT(IN), optional :: unit
1865       !
1866       ! ... declare other variables
1867       !
1868       CHARACTER(LEN=2) :: prog
1869       INTEGER :: ios
1870       INTEGER :: unit_loc=5
1871       !
1872       ! ... end of declarations
1873       !
1874       !  ----------------------------------------------
1875       !
1876       IF(PRESENT(unit)) unit_loc = unit
1877       !
1878       prog = prog_(1:2) ! Allowed: 'PW' or 'CP'
1879       IF( prog /= 'PW' .AND. prog /= 'CP' ) &
1880          CALL errore( ' read_namelists ', ' unknown calling program ', 1 )
1881       !
1882       ! ... default settings for all namelists
1883       !
1884       CALL control_defaults( prog )
1885       CALL system_defaults( prog )
1886       CALL electrons_defaults( prog )
1887       CALL ions_defaults( prog )
1888       CALL cell_defaults( prog )
1889       !
1890       ! ... Here start reading standard input file
1891       !
1892       !
1893       ! ... CONTROL namelist
1894       !
1895       ios = 0
1896       IF( ionode ) THEN
1897          READ( unit_loc, control, iostat = ios )
1898       END IF
1899       CALL check_namelist_read(ios, unit_loc, "control")
1900       !
1901       CALL control_bcast( )
1902       CALL control_checkin( prog )
1903       !
1904       ! ... fixval changes some default values according to the value
1905       ! ... of "calculation" read in CONTROL namelist
1906       !
1907       CALL fixval( prog )
1908       !
1909       ! ... SYSTEM namelist
1910       !
1911       ios = 0
1912       IF( ionode ) THEN
1913          READ( unit_loc, system, iostat = ios )
1914       END IF
1915       CALL check_namelist_read(ios, unit_loc, "system")
1916       !
1917       CALL system_bcast( )
1918       !
1919       CALL system_checkin( prog )
1920       !
1921       ! ... ELECTRONS namelist
1922       !
1923       ios = 0
1924       IF( ionode ) THEN
1925          READ( unit_loc, electrons, iostat = ios )
1926       END IF
1927       CALL check_namelist_read(ios, unit_loc, "electrons")
1928       !
1929       CALL electrons_bcast( )
1930       CALL electrons_checkin( prog )
1931       !
1932       ! ... IONS namelist - must be read only if ionic motion is expected,
1933       ! ...                 or if code called by i-Pi via run_driver
1934       !
1935       ios = 0
1936       IF ( ionode ) THEN
1937          IF ( ( TRIM( calculation ) /= 'nscf'  .AND. &
1938                 TRIM( calculation ) /= 'bands' ) .OR. &
1939               ( TRIM( prog_ ) == 'PW+iPi' ) ) THEN
1940             READ( unit_loc, ions, iostat = ios )
1941          END IF
1942          !
1943          ! SCF might (optionally) have &ions :: ion_positions = 'from_file'
1944          !
1945          IF ( (ios /= 0) .AND. TRIM( calculation ) == 'scf' ) THEN
1946             ! presumably, not found: rewind the file pointer to the location
1947             ! of the previous present section, in this case electrons
1948             REWIND( unit_loc )
1949             READ( unit_loc, electrons, iostat = ios )
1950          END IF
1951          !
1952       END IF
1953       !
1954       CALL check_namelist_read(ios, unit_loc, "ions")
1955       !
1956       CALL ions_bcast( )
1957       CALL ions_checkin( prog )
1958       !
1959       ! ... CELL namelist
1960       !
1961       ios = 0
1962       IF( ionode ) THEN
1963          IF( TRIM( calculation ) == 'vc-relax' .OR. &
1964              TRIM( calculation ) == 'vc-cp'    .OR. &
1965              TRIM( calculation ) == 'vc-md'    .OR. &
1966              TRIM( calculation ) == 'vc-md'    .OR. &
1967              TRIM( calculation ) == 'vc-cp-wf') THEN
1968             READ( unit_loc, cell, iostat = ios )
1969          END IF
1970       END IF
1971       CALL check_namelist_read(ios, unit_loc, "cell")
1972       !
1973       CALL cell_bcast()
1974       CALL cell_checkin( prog )
1975       !
1976       ios = 0
1977       IF( ionode ) THEN
1978          if (tabps) then
1979             READ( unit_loc, press_ai, iostat = ios )
1980          end if
1981       END IF
1982       CALL check_namelist_read(ios, unit_loc, "press_ai")
1983       !
1984       CALL press_ai_bcast()
1985       !
1986       ! ... WANNIER NAMELIST
1987       !
1988       CALL wannier_defaults( prog )
1989       ios = 0
1990       IF( ionode ) THEN
1991          IF( TRIM( calculation ) == 'cp-wf'       .OR. &
1992              TRIM( calculation ) == 'vc-cp-wf'    .OR. &
1993              TRIM( calculation ) == 'cp-wf-nscf') THEN
1994             READ( unit_loc, wannier, iostat = ios )
1995          END IF
1996       END IF
1997       CALL check_namelist_read(ios, unit_loc, "wannier")
1998       !
1999       CALL wannier_bcast()
2000       CALL wannier_checkin( prog )
2001       !
2002       ! ... WANNIER_NEW NAMELIST
2003       !
2004       CALL wannier_ac_defaults( prog )
2005       ios = 0
2006       IF( ionode ) THEN
2007          IF( use_wannier ) THEN
2008             READ( unit_loc, wannier_ac, iostat = ios )
2009          END IF
2010       END IF
2011       CALL check_namelist_read(ios, unit_loc, "wannier_ac")
2012       !
2013       CALL wannier_ac_bcast()
2014       CALL wannier_ac_checkin( prog )
2015       !
2016       RETURN
2017       !
2018     END SUBROUTINE read_namelists
2019     !
2020     SUBROUTINE check_namelist_read(ios, unit_loc, nl_name)
2021       USE io_global, ONLY : ionode, ionode_id
2022       USE mp,        ONLY : mp_bcast
2023       USE mp_images, ONLY : intra_image_comm
2024       !
2025       IMPLICIT NONE
2026       INTEGER,INTENT(in) :: ios, unit_loc
2027       CHARACTER(LEN=*) :: nl_name
2028       CHARACTER(len=512) :: line
2029       INTEGER :: ios2
2030       !
2031       IF( ionode ) THEN
2032         ios2=0
2033         IF (ios /=0) THEN
2034           BACKSPACE(unit_loc)
2035           READ(unit_loc,'(A512)', iostat=ios2) line
2036         END IF
2037       END IF
2038
2039       CALL mp_bcast( ios2, ionode_id, intra_image_comm )
2040       IF( ios2 /= 0 ) THEN
2041          CALL errore( ' read_namelists ', ' could not find namelist &'//TRIM(nl_name), 2)
2042       ENDIF
2043       !
2044       CALL mp_bcast( ios, ionode_id, intra_image_comm )
2045       CALL mp_bcast( line, ionode_id, intra_image_comm )
2046       IF( ios /= 0 ) THEN
2047          CALL errore( ' read_namelists ', &
2048                       ' bad line in namelist &'//TRIM(nl_name)//&
2049                       ': "'//TRIM(line)//'" (error could be in the previous line)',&
2050                       1 )
2051       END IF
2052       !
2053     END SUBROUTINE check_namelist_read
2054     !
2055END MODULE read_namelists_module
2056