diff --git a/FFTXlib/fft_types.f90 b/FFTXlib/fft_types.f90 index bc25672c2..409ec407a 100644 --- a/FFTXlib/fft_types.f90 +++ b/FFTXlib/fft_types.f90 @@ -170,11 +170,6 @@ MODULE fft_types INTEGER, ALLOCATABLE :: srh(:,:) ! Isend/recv handles by subbatch #endif COMPLEX(DP), ALLOCATABLE, DIMENSION(:) :: aux -#if defined(_OPENMP) - INTEGER, ALLOCATABLE :: comm2s(:) ! multiple communicator for the fft group along the second direction - INTEGER, ALLOCATABLE :: comm3s(:) ! multiple communicator for the fft group along the third direction -#endif - END TYPE REAL(DP) :: fft_dual = 4.0d0 @@ -245,14 +240,6 @@ CONTAINS CALL MPI_COMM_SPLIT( comm, color, key, desc%comm3, ierr ) CALL MPI_COMM_RANK( desc%comm3, desc%mype3, ierr ) CALL MPI_COMM_SIZE( desc%comm3, desc%nproc3, ierr ) -#if defined(_OPENMP) - ALLOCATE( desc%comm2s( OMP_GET_MAX_THREADS() )) - ALLOCATE( desc%comm3s( OMP_GET_MAX_THREADS() )) - DO i=1, OMP_GET_MAX_THREADS() - CALL MPI_COMM_DUP(desc%comm2, desc%comm2s(i), ierr) - CALL MPI_COMM_DUP(desc%comm3, desc%comm3s(i), ierr) - ENDDO -#endif #else desc%comm2 = desc%comm ; desc%mype2 = desc%mype ; desc%nproc2 = desc%nproc desc%comm3 = desc%comm ; desc%mype3 = desc%mype ; desc%nproc3 = desc%nproc @@ -446,14 +433,6 @@ CONTAINS #if defined(__MPI) IF (desc%comm2 /= MPI_COMM_NULL) CALL MPI_COMM_FREE( desc%comm2, ierr ) IF (desc%comm3 /= MPI_COMM_NULL) CALL MPI_COMM_FREE( desc%comm3, ierr ) -#if defined(_OPENMP) - DO i=1, SIZE(desc%comm2s) - IF (desc%comm2s(i) /= MPI_COMM_NULL) CALL MPI_COMM_FREE( desc%comm2s(i), ierr ) - IF (desc%comm3s(i) /= MPI_COMM_NULL) CALL MPI_COMM_FREE( desc%comm3s(i), ierr ) - ENDDO - DEALLOCATE( desc%comm2s ) - DEALLOCATE( desc%comm3s ) -#endif #else desc%comm2 = MPI_COMM_NULL desc%comm3 = MPI_COMM_NULL @@ -493,24 +472,6 @@ CONTAINS INTEGER :: ierr !write (6,*) ' inside fft_type_set' ; FLUSH(6) ! -#if defined(__MPI) -#if defined(_OPENMP) - IF (nmany > OMP_GET_MAX_THREADS()) THEN - DO i=1, SIZE(desc%comm2s) - IF (desc%comm2s(i) /= MPI_COMM_NULL) CALL MPI_COMM_FREE( desc%comm2s(i), ierr ) - IF (desc%comm3s(i) /= MPI_COMM_NULL) CALL MPI_COMM_FREE( desc%comm3s(i), ierr ) - ENDDO - DEALLOCATE( desc%comm2s ) - DEALLOCATE( desc%comm3s ) - ALLOCATE( desc%comm2s( nmany )) - ALLOCATE( desc%comm3s( nmany )) - DO i=1, nmany - CALL MPI_COMM_DUP(desc%comm2, desc%comm2s(i), ierr) - CALL MPI_COMM_DUP(desc%comm3, desc%comm3s(i), ierr) - ENDDO - ENDIF -#endif -#endif ! IF (.NOT. ALLOCATED( desc%nsp ) ) & CALL fftx_error__(' fft_type_set ', ' fft arrays not yet allocated ', 1 ) diff --git a/HP/src/hp_postproc.f90 b/HP/src/hp_postproc.f90 index 9e0dab2d3..72b620e92 100644 --- a/HP/src/hp_postproc.f90 +++ b/HP/src/hp_postproc.f90 @@ -61,7 +61,7 @@ SUBROUTINE hp_postproc eps3 = 1.d-4 ! the same threshold for the comparison of distances ! as in PW/src/inter_V.f90 DFT+U+V ! - CHARACTER(len=50) :: filenameU + CHARACTER(len=256) :: filenameU INTEGER, EXTERNAL :: find_free_unit ! CALL start_clock('hp_calc_U') diff --git a/PHonon/PH/elphon.f90 b/PHonon/PH/elphon.f90 index aef34d5be..4b9ba0d55 100644 --- a/PHonon/PH/elphon.f90 +++ b/PHonon/PH/elphon.f90 @@ -13,7 +13,7 @@ SUBROUTINE elphon() ! Electron-phonon calculation from data saved in fildvscf ! USE kinds, ONLY : DP - USE constants, ONLY : amu_ry + USE constants, ONLY : amu_ry, RY_TO_THZ, RY_TO_CMM1 USE cell_base, ONLY : celldm, omega, ibrav, at, bg USE ions_base, ONLY : nat, ntyp => nsp, ityp, tau, amass USE gvecs, ONLY: doublegrid @@ -50,7 +50,7 @@ SUBROUTINE elphon() COMPLEX(DP), allocatable :: phip (:, :, :, :) INTEGER :: ntyp_, nat_, ibrav_, nspin_mag_, mu, nu, na, nb, nta, ntb, nqs_ - REAL(DP) :: celldm_(6) + REAL(DP) :: celldm_(6), w1 CHARACTER(LEN=3) :: atm(ntyp) CALL start_clock ('elphon') @@ -165,9 +165,27 @@ SUBROUTINE elphon() deallocate( phip ) ENDIF - ENDIF + ! + ! Write phonon frequency to stdout + ! + WRITE( stdout, 8000) (xq (i), i = 1, 3) + ! + DO nu = 1, 3 * nat + w1 = SQRT( ABS( w2(nu) ) ) + if (w2(nu) < 0.d0) w1 = - w1 + WRITE( stdout, 8010) nu, w1 * RY_TO_THZ, w1 * RY_TO_CMM1 + ENDDO + ! + WRITE( stdout, '(1x,74("*"))') + ! + ENDIF ! .NOT. trans ! CALL stop_clock ('elphon') + ! +8000 FORMAT(/,5x,'Diagonalizing the dynamical matrix', & + & //,5x,'q = ( ',3f14.9,' ) ',//,1x,74('*')) +8010 FORMAT (5x,'freq (',i5,') =',f15.6,' [THz] =',f15.6,' [cm-1]') + ! RETURN END SUBROUTINE elphon ! diff --git a/PHonon/PH/openfilq.f90 b/PHonon/PH/openfilq.f90 index 74df0a55a..e6795f59e 100644 --- a/PHonon/PH/openfilq.f90 +++ b/PHonon/PH/openfilq.f90 @@ -83,16 +83,17 @@ SUBROUTINE openfilq() ELSE ! this is the standard treatment IF (lgamma.AND.modenum==0.AND..NOT.newgrid ) tmp_dir=tmp_dir_save - IF ((noncolin.AND.domag).OR.lsda) tmp_dir=tmp_dir_phq + ! FIXME: why this case? + IF ( noncolin.AND.domag ) tmp_dir=tmp_dir_phq ENDIF !!!!!!!!!!!!!!!!!!!!!!!! END OF ACFDT TEST !!!!!!!!!!!!!!!! iuwfc = 20 lrwfc = nbnd * npwx * npol CALL open_buffer (iuwfc, 'wfc', lrwfc, io_level, exst_mem, exst, tmp_dir) IF (.NOT.exst.AND..NOT.exst_mem.and..not.all_done) THEN - tmp_dir = tmp_dir_phq - !FIXME Dirty fix for obscure case, likely obsolete? CALL close_buffer(iuwfc, 'delete') + !FIXME Dirty fix for obscure case + tmp_dir = tmp_dir_phq CALL open_buffer (iuwfc, 'wfc', lrwfc, io_level, exst_mem, exst, tmp_dir) IF (.NOT.exst.AND..NOT.exst_mem) CALL errore ('openfilq', 'file '//trim(prefix)//'.wfc not found', 1) END IF diff --git a/PHonon/examples/README b/PHonon/examples/README index 69d157777..0d1a7340e 100644 --- a/PHonon/examples/README +++ b/PHonon/examples/README @@ -89,8 +89,8 @@ example05: tensor for AlAs. example06 - This example shows how to use ph.x to calculate - the phonon frequencies at Gamma and X of fcc-Pt. + This example shows how to use ph.x to calculate the phonon frequencies + at Gamma and X and the dispersion for fcc-Pt with spin-orbit interactions. example07: This example tests pw.x and ph.x in several cases that require the @@ -120,7 +120,7 @@ example12: modes of a molecule (SiH4) at Gamma. example13: - Deleted + Full dispersions for spin-polarized phonons (Ni) example14: This example shows how to use ph.x to calculate the phonon frequencies diff --git a/PHonon/examples/example06/README b/PHonon/examples/example06/README index 00bd0ebd4..664851eb4 100644 --- a/PHonon/examples/example06/README +++ b/PHonon/examples/example06/README @@ -10,3 +10,5 @@ The calculation proceeds as follows: output=pt.ph.out). 3) make a phonon calculation at X (input=pt.phX.in, output=pt.phX.out). + +4) make a phonon dispersion calculation (input=pt.ph.in, output=pt.ph.out). diff --git a/PHonon/examples/example06/reference/pt.ph.out b/PHonon/examples/example06/reference/pt.ph.out index a8c7374df..c2b84f21a 100644 --- a/PHonon/examples/example06/reference/pt.ph.out +++ b/PHonon/examples/example06/reference/pt.ph.out @@ -1,42 +1,60 @@ - Program PHONON v.6.0 (svn rev. 13188M) starts on 7Dec2016 at 13:11:59 + Program PHONON v.6.5 starts on 19Mar2020 at 21:11:48 This program is part of the open-source Quantum ESPRESSO suite for quantum simulation of materials; please cite "P. Giannozzi et al., J. Phys.:Condens. Matter 21 395502 (2009); + "P. Giannozzi et al., J. Phys.:Condens. Matter 29 465901 (2017); URL http://www.quantum-espresso.org", in publications or presentations arising from this work. More details at http://www.quantum-espresso.org/quote Parallel version (MPI), running on 4 processors + + MPI processes distributed on 1 nodes R & G space division: proc/nbgrp/npool/nimage = 4 + Fft bands division: nmany = 1 - Reading data from directory: - /home/pietro/espresso-svn/tempdir/platinum.save + Reading xml data from directory: - Info: using nr1, nr2, nr3 values from input - - Info: using nr1, nr2, nr3 values from input + /home/giannozz/q-e-mio/tempdir/platinum.save/ + Message from routine qexsd_readschema : + input info not found or not readable in xml file IMPORTANT: XC functional enforced from input : - Exchange-correlation = SLA PZ NOGX NOGC ( 1 1 0 0 0 0) + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) Any further DFT definition will be discarded Please, verify this is what you really want - + Parallelization info -------------------- sticks: dense smooth PW G-vecs: dense smooth PW Min 118 55 18 1712 556 102 Max 119 56 19 1715 558 104 Sum 475 223 73 6855 2229 411 + + + Check: negative core charge= -0.000004 + Reading collected, re-writing distributed wavefunctions - Check: negative/imaginary core charge= -0.000004 0.000000 + Dynamical matrices for ( 4, 4, 4) uniform grid of q-points + ( 8 q-points): + N xq(1) xq(2) xq(3) + 1 0.000000000 0.000000000 0.000000000 + 2 -0.250000000 0.250000000 -0.250000000 + 3 0.500000000 -0.500000000 0.500000000 + 4 0.000000000 0.500000000 0.000000000 + 5 0.750000000 -0.250000000 0.750000000 + 6 0.500000000 0.000000000 0.500000000 + 7 0.000000000 -1.000000000 0.000000000 + 8 -0.500000000 -1.000000000 0.000000000 Calculation of q = 0.0000000 0.0000000 0.0000000 - phonons of Pt at Gamma + phonon dispersions of Pt bravais-lattice index = 2 lattice parameter (alat) = 7.4200 a.u. @@ -48,7 +66,8 @@ convergence threshold = 1.0E-16 beta = 0.7000 number of iterations used = 4 - Exchange-correlation = SLA PZ NOGX NOGC ( 1 1 0 0 0 0) + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) Non magnetic calculation with spin-orbit celldm(1)= 7.42000 celldm(2)= 0.00000 celldm(3)= 0.00000 @@ -74,7 +93,7 @@ Computing dynamical matrix for q = ( 0.0000000 0.0000000 0.0000000 ) - + 49 Sym.Ops. (with q -> -q+G ) @@ -82,13 +101,10 @@ G cutoff = 167.3514 ( 557 G-vectors) smooth grid: ( 20, 20, 20) number of k points= 2 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 - cart. coord. in units 2pi/alat - k( 1) = ( -0.2500000 0.2500000 0.2500000), wk = 0.2500000 - k( 2) = ( 0.2500000 -0.2500000 0.7500000), wk = 0.7500000 PseudoPot. # 1 for Pt read from file: - ./Pt.rel-pz-n-rrkjus.UPF - MD5 check sum: 4baafe8ec1942611396c7a5466f52249 + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e Pseudo is Ultrasoft + core correction, Zval = 10.0 Generated by new atomic code, or converted to UPF format Using radial grid of 1277 points, 6 beta functions with: @@ -112,60 +128,60 @@ Alpha used in Ewald sum = 2.6000 - PHONON : 0.95s CPU 1.11s WALL + PHONON : 0.56s CPU 0.57s WALL Representation # 1 modes # 1 2 3 Self-consistent Calculation + + Pert. # 1: Fermi energy shift (Ry) = 4.1359E-25 -7.8366E-38 + Pert. # 2: Fermi energy shift (Ry) = 3.1019E-25 -1.2539E-37 + Pert. # 3: Fermi energy shift (Ry) = -4.1359E-25 -1.9592E-37 - Pert. # 1: Fermi energy shift (Ry) = 0.0000E+00 0.0000E+00 - Pert. # 2: Fermi energy shift (Ry) = 1.0340E-25 -3.1347E-38 - Pert. # 3: Fermi energy shift (Ry) = 1.7233E-25 0.0000E+00 - - iter # 1 total cpu time : 1.5 secs av.it.: 6.3 + iter # 1 total cpu time : 0.8 secs av.it.: 6.3 thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 5.745E-07 + + Pert. # 1: Fermi energy shift (Ry) = -6.8932E-25 7.3468E-40 + Pert. # 2: Fermi energy shift (Ry) = -2.4126E-25 3.6734E-40 + Pert. # 3: Fermi energy shift (Ry) = -3.7912E-25 -2.7551E-39 - Pert. # 1: Fermi energy shift (Ry) = -6.8932E-26 0.0000E+00 - Pert. # 2: Fermi energy shift (Ry) = 3.4466E-26 -4.8979E-40 - Pert. # 3: Fermi energy shift (Ry) = -6.8932E-26 6.1224E-41 + iter # 2 total cpu time : 1.1 secs av.it.: 12.3 + thresh= 7.580E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.682E-08 + + Pert. # 1: Fermi energy shift (Ry) = 1.3786E-25 7.3468E-40 + Pert. # 2: Fermi energy shift (Ry) = 5.1699E-25 6.1224E-40 + Pert. # 3: Fermi energy shift (Ry) = -6.8932E-25 1.1632E-39 - iter # 2 total cpu time : 2.0 secs av.it.: 12.3 - thresh= 7.579E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.681E-08 + iter # 3 total cpu time : 1.3 secs av.it.: 11.3 + thresh= 1.297E-05 alpha_mix = 0.700 |ddv_scf|^2 = 6.466E-10 + + Pert. # 1: Fermi energy shift (Ry) = 4.1359E-25 -3.6734E-40 + Pert. # 2: Fermi energy shift (Ry) = -3.7912E-25 9.1835E-41 + Pert. # 3: Fermi energy shift (Ry) = -4.4806E-25 1.4541E-40 - Pert. # 1: Fermi energy shift (Ry) = 2.0680E-25 6.1224E-41 - Pert. # 2: Fermi energy shift (Ry) = 3.4466E-26 3.0612E-41 - Pert. # 3: Fermi energy shift (Ry) = -1.7233E-25 0.0000E+00 + iter # 4 total cpu time : 1.6 secs av.it.: 10.2 + thresh= 2.543E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.836E-13 + + Pert. # 1: Fermi energy shift (Ry) = -2.7573E-25 -1.5306E-40 + Pert. # 2: Fermi energy shift (Ry) = 3.1019E-25 -3.0612E-40 + Pert. # 3: Fermi energy shift (Ry) = 5.1699E-25 0.0000E+00 - iter # 3 total cpu time : 2.4 secs av.it.: 11.3 - thresh= 1.297E-05 alpha_mix = 0.700 |ddv_scf|^2 = 6.464E-10 + iter # 5 total cpu time : 1.8 secs av.it.: 11.5 + thresh= 4.285E-08 alpha_mix = 0.700 |ddv_scf|^2 = 2.768E-15 + + Pert. # 1: Fermi energy shift (Ry) = 6.8932E-25 -1.5306E-40 + Pert. # 2: Fermi energy shift (Ry) = 1.3786E-25 -3.0612E-40 + Pert. # 3: Fermi energy shift (Ry) = -2.7573E-25 0.0000E+00 - Pert. # 1: Fermi energy shift (Ry) = -2.0680E-25 -3.0612E-41 - Pert. # 2: Fermi energy shift (Ry) = -1.7233E-25 0.0000E+00 - Pert. # 3: Fermi energy shift (Ry) = -1.7233E-25 3.0612E-41 - - iter # 4 total cpu time : 2.9 secs av.it.: 10.2 - thresh= 2.543E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.837E-13 - - Pert. # 1: Fermi energy shift (Ry) = 6.8932E-26 3.0612E-41 - Pert. # 2: Fermi energy shift (Ry) = -6.8932E-26 -1.5306E-41 - Pert. # 3: Fermi energy shift (Ry) = -3.4466E-26 3.0612E-41 - - iter # 5 total cpu time : 3.3 secs av.it.: 11.5 - thresh= 4.287E-08 alpha_mix = 0.700 |ddv_scf|^2 = 2.773E-15 - - Pert. # 1: Fermi energy shift (Ry) = 0.0000E+00 0.0000E+00 - Pert. # 2: Fermi energy shift (Ry) = -1.3786E-25 4.5918E-41 - Pert. # 3: Fermi energy shift (Ry) = -3.4466E-26 1.5306E-41 - - iter # 6 total cpu time : 3.7 secs av.it.: 10.3 - thresh= 5.266E-09 alpha_mix = 0.700 |ddv_scf|^2 = 3.185E-17 + iter # 6 total cpu time : 2.0 secs av.it.: 10.3 + thresh= 5.261E-09 alpha_mix = 0.700 |ddv_scf|^2 = 3.184E-17 End of self-consistent calculation Convergence has been achieved - + Number of q in the star = 1 List of q in the star: 1 0.000000000 0.000000000 0.000000000 @@ -175,95 +191,3037 @@ q = ( 0.000000000 0.000000000 0.000000000 ) ************************************************************************** - freq ( 1) = 0.178931 [THz] = 5.968504 [cm-1] - freq ( 2) = 0.178931 [THz] = 5.968504 [cm-1] - freq ( 3) = 0.178931 [THz] = 5.968504 [cm-1] + freq ( 1) = 0.178889 [THz] = 5.967080 [cm-1] + freq ( 2) = 0.178889 [THz] = 5.967080 [cm-1] + freq ( 3) = 0.178889 [THz] = 5.967080 [cm-1] ************************************************************************** Mode symmetry, O_h (m-3m) point group: freq ( 1 - 3) = 6.0 [cm-1] --> T_1u G_15 G_4- I - PHONON : 3.25s CPU 3.77s WALL + Calculation of q = -0.2500000 0.2500000 -0.2500000 + + Subspace diagonalization in iterative solution of the eigenvalue problem: + a serial algorithm will be used + + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 118 55 21 1712 556 132 + Max 119 56 22 1715 558 135 + Sum 475 223 85 6855 2229 531 + + + Title: + phonon dispersions of Pt + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 18 + kinetic-energy cutoff = 30.0000 Ry + charge density cutoff = 250.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + + celldm(1)= 7.420000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Pt 10.00 195.07800 Pt( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Pt tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 20 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.2500000 0.2500000 0.2500000), wk = 0.0937500 + k( 2) = ( -0.5000000 0.5000000 0.0000000), wk = 0.0000000 + k( 3) = ( 0.2500000 -0.2500000 0.7500000), wk = 0.0937500 + k( 4) = ( 0.0000000 0.0000000 0.5000000), wk = 0.0000000 + k( 5) = ( 0.2500000 0.2500000 0.2500000), wk = 0.0937500 + k( 6) = ( 0.0000000 0.5000000 0.0000000), wk = 0.0000000 + k( 7) = ( 0.2500000 -0.2500000 0.2500000), wk = 0.0312500 + k( 8) = ( 0.0000000 0.0000000 0.0000000), wk = 0.0000000 + k( 9) = ( -0.2500000 0.2500000 -0.2500000), wk = 0.0312500 + k( 10) = ( -0.5000000 0.5000000 -0.5000000), wk = 0.0000000 + k( 11) = ( -0.2500000 0.7500000 0.2500000), wk = 0.1875000 + k( 12) = ( -0.5000000 1.0000000 0.0000000), wk = 0.0000000 + k( 13) = ( -0.2500000 0.7500000 -0.2500000), wk = 0.0937500 + k( 14) = ( -0.5000000 1.0000000 -0.5000000), wk = 0.0000000 + k( 15) = ( -0.2500000 0.2500000 0.7500000), wk = 0.0937500 + k( 16) = ( -0.5000000 0.5000000 0.5000000), wk = 0.0000000 + k( 17) = ( 0.7500000 0.2500000 0.2500000), wk = 0.1875000 + k( 18) = ( 0.5000000 0.5000000 0.0000000), wk = 0.0000000 + k( 19) = ( 0.2500000 -0.2500000 -0.7500000), wk = 0.0937500 + k( 20) = ( 0.0000000 0.0000000 -1.0000000), wk = 0.0000000 + + Dense grid: 6855 G-vectors FFT dimensions: ( 27, 27, 27) + + Smooth grid: 2229 G-vectors FFT dimensions: ( 20, 20, 20) + + Estimated max dynamical RAM per process > 12.24 MB + + Estimated total dynamical RAM > 48.97 MB + + Check: negative core charge= -0.000004 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/charge-density + + Starting wfcs are 12 atomic + 6 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 15.4 + + total cpu time spent up to now is 0.9 secs + + End of band structure calculation + + k =-0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k =-0.5000 0.5000 0.0000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k = 0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.0000 0.0000 0.5000 ( 290 PWs) bands (ev): + + 10.0187 10.0187 12.1665 12.1665 14.1806 14.1806 15.6749 15.6749 + 15.7566 15.7566 17.0173 17.0173 33.8083 33.8083 35.8441 35.8441 + 36.2252 36.2252 + + k = 0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.0000 0.5000 0.0000 ( 290 PWs) bands (ev): + + 10.0187 10.0187 12.1665 12.1665 14.1806 14.1806 15.6749 15.6749 + 15.7566 15.7566 17.0173 17.0173 33.8083 33.8083 35.8441 35.8441 + 36.2252 36.2252 + + k = 0.2500-0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.0000 0.0000 0.0000 ( 283 PWs) bands (ev): + + 7.2727 7.2727 13.3946 13.3946 13.3946 13.3946 14.3825 14.3825 + 16.2214 16.2214 16.2214 16.2214 34.8330 34.8330 38.3520 38.3520 + 39.6350 39.6350 + + k =-0.2500 0.2500-0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k =-0.5000 0.5000-0.5000 ( 272 PWs) bands (ev): + + 10.2248 10.2248 13.2340 13.2340 14.2435 14.2435 16.8898 16.8898 + 17.4171 17.4171 18.0789 18.0789 23.4362 23.4362 33.8541 33.8541 + 36.9667 36.9667 + + k =-0.2500 0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.5000 1.0000 0.0000 ( 280 PWs) bands (ev): + + 11.8705 11.8705 12.8375 12.8375 13.0920 13.0920 15.7990 15.7990 + 18.2074 18.2074 24.7578 24.7578 25.1486 25.1486 26.5186 26.5186 + 29.7304 29.7304 + + k =-0.2500 0.7500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.5000 1.0000-0.5000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k =-0.2500 0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.5000 0.5000 0.5000 ( 272 PWs) bands (ev): + + 10.2248 10.2248 13.2340 13.2340 14.2435 14.2435 16.8898 16.8898 + 17.4171 17.4171 18.0789 18.0789 23.4362 23.4362 33.8541 33.8541 + 36.9667 36.9667 + + k = 0.7500 0.2500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.5000 0.5000 0.0000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k = 0.2500-0.2500-0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.0000 0.0000-1.0000 ( 286 PWs) bands (ev): + + 10.4903 10.4903 10.9472 10.9472 17.4906 17.4906 17.8002 17.8002 + 18.7797 18.7797 19.1008 19.1008 26.3323 26.3323 28.7371 28.7371 + 30.2769 30.2769 + + the Fermi energy is 17.9731 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/ + + phonon dispersions of Pt + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 30.0000 Ry + charge density cut-off = 250.0000 Ry + convergence threshold = 1.0E-16 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + celldm(1)= 7.42000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Pt 195.0780 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( -0.2500000 0.2500000 -0.2500000 ) + + 6 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 348.6487 ( 1715 G-vectors) FFT grid: ( 27, 27, 27) + G cutoff = 167.3514 ( 557 G-vectors) smooth grid: ( 20, 20, 20) + + number of k points= 20 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, C_3v (3m) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_1 L_1 To be done + + Representation 2 2 modes -E L_3 To be done + + + + Alpha used in Ewald sum = 2.6000 + PHONON : 3.29s CPU 3.45s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 3.7 secs av.it.: 8.4 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.689E-01 + + iter # 2 total cpu time : 3.9 secs av.it.: 11.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 3.427E+02 + + iter # 3 total cpu time : 4.1 secs av.it.: 11.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 8.890E-02 + + iter # 4 total cpu time : 4.3 secs av.it.: 7.9 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 5.599E-02 + + iter # 5 total cpu time : 4.5 secs av.it.: 7.5 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 3.019E-04 + + iter # 6 total cpu time : 4.7 secs av.it.: 6.4 + thresh= 1.738E-03 alpha_mix = 0.700 |ddv_scf|^2 = 5.833E-07 + + iter # 7 total cpu time : 4.8 secs av.it.: 7.2 + thresh= 7.638E-05 alpha_mix = 0.700 |ddv_scf|^2 = 5.345E-06 + + iter # 8 total cpu time : 5.0 secs av.it.: 5.9 + thresh= 2.312E-04 alpha_mix = 0.700 |ddv_scf|^2 = 6.904E-09 + + iter # 9 total cpu time : 5.2 secs av.it.: 7.0 + thresh= 8.309E-06 alpha_mix = 0.700 |ddv_scf|^2 = 8.120E-11 + + iter # 10 total cpu time : 5.3 secs av.it.: 7.8 + thresh= 9.011E-07 alpha_mix = 0.700 |ddv_scf|^2 = 5.477E-11 + + iter # 11 total cpu time : 5.6 secs av.it.: 6.5 + thresh= 7.401E-07 alpha_mix = 0.700 |ddv_scf|^2 = 3.609E-13 + + iter # 12 total cpu time : 5.8 secs av.it.: 7.2 + thresh= 6.008E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.519E-13 + + iter # 13 total cpu time : 6.0 secs av.it.: 6.3 + thresh= 3.897E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.584E-15 + + iter # 14 total cpu time : 6.1 secs av.it.: 7.0 + thresh= 3.980E-09 alpha_mix = 0.700 |ddv_scf|^2 = 5.387E-16 + + iter # 15 total cpu time : 6.3 secs av.it.: 6.6 + thresh= 2.321E-09 alpha_mix = 0.700 |ddv_scf|^2 = 3.347E-18 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 6.8 secs av.it.: 6.6 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.790E-06 + + iter # 2 total cpu time : 7.3 secs av.it.: 10.9 + thresh= 1.338E-04 alpha_mix = 0.700 |ddv_scf|^2 = 6.946E-08 + + iter # 3 total cpu time : 7.7 secs av.it.: 10.5 + thresh= 2.636E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.863E-09 + + iter # 4 total cpu time : 8.1 secs av.it.: 10.3 + thresh= 4.316E-06 alpha_mix = 0.700 |ddv_scf|^2 = 8.509E-11 + + iter # 5 total cpu time : 8.6 secs av.it.: 10.5 + thresh= 9.224E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.864E-13 + + iter # 6 total cpu time : 9.1 secs av.it.: 10.4 + thresh= 4.317E-08 alpha_mix = 0.700 |ddv_scf|^2 = 2.828E-15 + + iter # 7 total cpu time : 9.5 secs av.it.: 10.3 + thresh= 5.318E-09 alpha_mix = 0.700 |ddv_scf|^2 = 7.288E-17 + + iter # 8 total cpu time : 10.0 secs av.it.: 10.2 + thresh= 8.537E-10 alpha_mix = 0.700 |ddv_scf|^2 = 2.084E-18 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 8 + List of q in the star: + 1 -0.250000000 0.250000000 -0.250000000 + 2 0.250000000 -0.250000000 -0.250000000 + 3 0.250000000 -0.250000000 0.250000000 + 4 0.250000000 0.250000000 0.250000000 + 5 -0.250000000 -0.250000000 -0.250000000 + 6 -0.250000000 -0.250000000 0.250000000 + 7 -0.250000000 0.250000000 0.250000000 + 8 0.250000000 0.250000000 -0.250000000 + + Diagonalizing the dynamical matrix + + q = ( -0.250000000 0.250000000 -0.250000000 ) + + ************************************************************************** + freq ( 1) = 2.294374 [THz] = 76.532090 [cm-1] + freq ( 2) = 2.294374 [THz] = 76.532090 [cm-1] + freq ( 3) = 4.560518 [THz] = 152.122522 [cm-1] + ************************************************************************** + + Mode symmetry, C_3v (3m) point group: + + freq ( 1 - 2) = 76.5 [cm-1] --> E L_3 + freq ( 3 - 3) = 152.1 [cm-1] --> A_1 L_1 + + Calculation of q = 0.5000000 -0.5000000 0.5000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 118 55 21 1712 556 133 + Max 119 56 22 1715 558 136 + Sum 475 223 85 6855 2229 537 + + + Title: + phonon dispersions of Pt + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 18 + kinetic-energy cutoff = 30.0000 Ry + charge density cutoff = 250.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + + celldm(1)= 7.420000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Pt 10.00 195.07800 Pt( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Pt tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 10 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.2500000 0.2500000 0.2500000), wk = 0.1875000 + k( 2) = ( 0.2500000 -0.2500000 0.7500000), wk = 0.0000000 + k( 3) = ( 0.2500000 -0.2500000 0.7500000), wk = 0.1875000 + k( 4) = ( 0.7500000 -0.7500000 1.2500000), wk = 0.0000000 + k( 5) = ( 0.2500000 -0.2500000 0.2500000), wk = 0.0625000 + k( 6) = ( 0.7500000 -0.7500000 0.7500000), wk = 0.0000000 + k( 7) = ( 0.2500000 0.2500000 0.7500000), wk = 0.3750000 + k( 8) = ( 0.7500000 -0.2500000 1.2500000), wk = 0.0000000 + k( 9) = ( 0.7500000 0.2500000 -0.2500000), wk = 0.1875000 + k( 10) = ( 1.2500000 -0.2500000 0.2500000), wk = 0.0000000 + + Dense grid: 6855 G-vectors FFT dimensions: ( 27, 27, 27) + + Smooth grid: 2229 G-vectors FFT dimensions: ( 20, 20, 20) + + Estimated max dynamical RAM per process > 12.27 MB + + Estimated total dynamical RAM > 49.09 MB + + Check: negative core charge= -0.000004 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/charge-density + + Starting wfcs are 12 atomic + 6 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 15.6 + + total cpu time spent up to now is 1.4 secs + + End of band structure calculation + + k =-0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.7500-0.7500 1.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.2500-0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.7500-0.7500 0.7500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.2500 0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.7500-0.2500 1.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.7500 0.2500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 1.2500-0.2500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + the Fermi energy is 17.9731 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/ + + phonon dispersions of Pt + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 30.0000 Ry + charge density cut-off = 250.0000 Ry + convergence threshold = 1.0E-16 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + celldm(1)= 7.42000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Pt 195.0780 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.5000000 -0.5000000 0.5000000 ) + + 13 Sym.Ops. (with q -> -q+G ) + + + G cutoff = 348.6487 ( 1715 G-vectors) FFT grid: ( 27, 27, 27) + G cutoff = 167.3514 ( 557 G-vectors) smooth grid: ( 20, 20, 20) + + number of k points= 10 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, D_3d (-3m) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_2u L_2' To be done + + Representation 2 2 modes -E_u L_3' To be done + + + + Alpha used in Ewald sum = 2.6000 + PHONON : 10.12s CPU 10.94s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 11.1 secs av.it.: 8.4 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.240E-03 + + iter # 2 total cpu time : 11.2 secs av.it.: 9.8 + thresh= 3.522E-03 alpha_mix = 0.700 |ddv_scf|^2 = 2.517E-03 + + iter # 3 total cpu time : 11.4 secs av.it.: 9.0 + thresh= 5.017E-03 alpha_mix = 0.700 |ddv_scf|^2 = 2.884E-08 + + iter # 4 total cpu time : 11.5 secs av.it.: 10.4 + thresh= 1.698E-05 alpha_mix = 0.700 |ddv_scf|^2 = 7.874E-10 + + iter # 5 total cpu time : 11.7 secs av.it.: 9.6 + thresh= 2.806E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.922E-11 + + iter # 6 total cpu time : 11.8 secs av.it.: 9.0 + thresh= 4.384E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.128E-13 + + iter # 7 total cpu time : 11.9 secs av.it.: 9.6 + thresh= 3.359E-08 alpha_mix = 0.700 |ddv_scf|^2 = 2.350E-15 + + iter # 8 total cpu time : 12.0 secs av.it.: 9.0 + thresh= 4.848E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.366E-17 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 12.3 secs av.it.: 7.1 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 2.254E-06 + + iter # 2 total cpu time : 12.6 secs av.it.: 11.8 + thresh= 1.501E-04 alpha_mix = 0.700 |ddv_scf|^2 = 9.858E-08 + + iter # 3 total cpu time : 12.9 secs av.it.: 11.5 + thresh= 3.140E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.741E-09 + + iter # 4 total cpu time : 13.2 secs av.it.: 10.3 + thresh= 4.172E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.334E-12 + + iter # 5 total cpu time : 13.5 secs av.it.: 11.6 + thresh= 1.155E-07 alpha_mix = 0.700 |ddv_scf|^2 = 9.583E-15 + + iter # 6 total cpu time : 13.8 secs av.it.: 10.2 + thresh= 9.789E-09 alpha_mix = 0.700 |ddv_scf|^2 = 3.091E-16 + + iter # 7 total cpu time : 14.1 secs av.it.: 10.5 + thresh= 1.758E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.754E-19 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 4 + List of q in the star: + 1 0.500000000 -0.500000000 0.500000000 + 2 0.500000000 0.500000000 0.500000000 + 3 -0.500000000 0.500000000 0.500000000 + 4 0.500000000 0.500000000 -0.500000000 + + Diagonalizing the dynamical matrix + + q = ( 0.500000000 -0.500000000 0.500000000 ) + + ************************************************************************** + freq ( 1) = 2.699668 [THz] = 90.051225 [cm-1] + freq ( 2) = 2.699668 [THz] = 90.051225 [cm-1] + freq ( 3) = 6.043301 [THz] = 201.582832 [cm-1] + ************************************************************************** + + Mode symmetry, D_3d (-3m) point group: + + freq ( 1 - 2) = 90.1 [cm-1] --> E_u L_3' + freq ( 3 - 3) = 201.6 [cm-1] --> A_2u L_2' + + Calculation of q = 0.0000000 0.5000000 0.0000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 118 55 21 1712 556 132 + Max 119 56 22 1715 558 135 + Sum 475 223 85 6855 2229 531 + + + Title: + phonon dispersions of Pt + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 18 + kinetic-energy cutoff = 30.0000 Ry + charge density cutoff = 250.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + + celldm(1)= 7.420000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Pt 10.00 195.07800 Pt( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Pt tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 12 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.2500000 0.2500000 0.2500000), wk = 0.1250000 + k( 2) = ( -0.2500000 0.7500000 0.2500000), wk = 0.0000000 + k( 3) = ( 0.2500000 -0.2500000 0.7500000), wk = 0.2500000 + k( 4) = ( 0.2500000 0.2500000 0.7500000), wk = 0.0000000 + k( 5) = ( -0.2500000 -0.2500000 0.2500000), wk = 0.1250000 + k( 6) = ( -0.2500000 0.2500000 0.2500000), wk = 0.0000000 + k( 7) = ( -0.7500000 0.2500000 -0.2500000), wk = 0.2500000 + k( 8) = ( -0.7500000 0.7500000 -0.2500000), wk = 0.0000000 + k( 9) = ( -0.2500000 0.7500000 -0.2500000), wk = 0.1250000 + k( 10) = ( -0.2500000 1.2500000 -0.2500000), wk = 0.0000000 + k( 11) = ( -0.2500000 -0.7500000 -0.2500000), wk = 0.1250000 + k( 12) = ( -0.2500000 -0.2500000 -0.2500000), wk = 0.0000000 + + Dense grid: 6855 G-vectors FFT dimensions: ( 27, 27, 27) + + Smooth grid: 2229 G-vectors FFT dimensions: ( 20, 20, 20) + + Estimated max dynamical RAM per process > 12.25 MB + + Estimated total dynamical RAM > 48.99 MB + + Check: negative core charge= -0.000004 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/charge-density + + Starting wfcs are 12 atomic + 6 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 15.3 + + total cpu time spent up to now is 2.0 secs + + End of band structure calculation + + k =-0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k =-0.2500 0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500 0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500-0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k =-0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k =-0.7500 0.2500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.7500 0.7500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500 0.7500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500 1.2500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500-0.7500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500-0.2500-0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + the Fermi energy is 17.9731 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/ + + phonon dispersions of Pt + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 30.0000 Ry + charge density cut-off = 250.0000 Ry + convergence threshold = 1.0E-16 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + celldm(1)= 7.42000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Pt 195.0780 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.0000000 0.5000000 0.0000000 ) + + 8 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 348.6487 ( 1715 G-vectors) FFT grid: ( 27, 27, 27) + G cutoff = 167.3514 ( 557 G-vectors) smooth grid: ( 20, 20, 20) + + number of k points= 12 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, C_4v (4mm) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_1 G_1 D_1 To be done + + Representation 2 2 modes -E G_5 D_5 To be done + + + + Alpha used in Ewald sum = 2.6000 + PHONON : 14.04s CPU 15.11s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 15.3 secs av.it.: 9.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.103E-01 + + iter # 2 total cpu time : 15.5 secs av.it.: 12.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 2.606E+01 + + iter # 3 total cpu time : 15.6 secs av.it.: 12.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.667E-02 + + iter # 4 total cpu time : 15.8 secs av.it.: 8.7 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.212E-02 + + iter # 5 total cpu time : 15.9 secs av.it.: 7.7 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 6.353E-06 + + iter # 6 total cpu time : 16.0 secs av.it.: 7.8 + thresh= 2.521E-04 alpha_mix = 0.700 |ddv_scf|^2 = 7.445E-09 + + iter # 7 total cpu time : 16.2 secs av.it.: 9.2 + thresh= 8.628E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.958E-08 + + iter # 8 total cpu time : 16.3 secs av.it.: 7.3 + thresh= 1.399E-05 alpha_mix = 0.700 |ddv_scf|^2 = 8.377E-09 + + iter # 9 total cpu time : 16.4 secs av.it.: 7.5 + thresh= 9.152E-06 alpha_mix = 0.700 |ddv_scf|^2 = 6.908E-11 + + iter # 10 total cpu time : 16.6 secs av.it.: 7.3 + thresh= 8.311E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.090E-12 + + iter # 11 total cpu time : 16.7 secs av.it.: 7.8 + thresh= 1.044E-07 alpha_mix = 0.700 |ddv_scf|^2 = 4.176E-14 + + iter # 12 total cpu time : 16.9 secs av.it.: 8.0 + thresh= 2.044E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.209E-14 + + iter # 13 total cpu time : 17.0 secs av.it.: 7.0 + thresh= 1.099E-08 alpha_mix = 0.700 |ddv_scf|^2 = 3.603E-15 + + iter # 14 total cpu time : 17.1 secs av.it.: 7.7 + thresh= 6.002E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.044E-16 + + iter # 15 total cpu time : 17.3 secs av.it.: 7.8 + thresh= 1.430E-09 alpha_mix = 0.700 |ddv_scf|^2 = 3.764E-18 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 17.6 secs av.it.: 7.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 3.873E-06 + + iter # 2 total cpu time : 17.9 secs av.it.: 12.1 + thresh= 1.968E-04 alpha_mix = 0.700 |ddv_scf|^2 = 2.934E-07 + + iter # 3 total cpu time : 18.3 secs av.it.: 11.3 + thresh= 5.417E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.052E-09 + + iter # 4 total cpu time : 18.6 secs av.it.: 10.8 + thresh= 4.530E-06 alpha_mix = 0.700 |ddv_scf|^2 = 3.370E-12 + + iter # 5 total cpu time : 19.0 secs av.it.: 11.4 + thresh= 1.836E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.522E-13 + + iter # 6 total cpu time : 19.3 secs av.it.: 11.5 + thresh= 3.901E-08 alpha_mix = 0.700 |ddv_scf|^2 = 7.025E-16 + + iter # 7 total cpu time : 19.6 secs av.it.: 10.8 + thresh= 2.650E-09 alpha_mix = 0.700 |ddv_scf|^2 = 3.608E-17 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 6 + List of q in the star: + 1 0.000000000 0.500000000 0.000000000 + 2 0.000000000 -0.500000000 0.000000000 + 3 0.500000000 0.000000000 0.000000000 + 4 0.000000000 0.000000000 0.500000000 + 5 0.000000000 0.000000000 -0.500000000 + 6 -0.500000000 0.000000000 0.000000000 + + Diagonalizing the dynamical matrix + + q = ( 0.000000000 0.500000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 2.781800 [THz] = 92.790863 [cm-1] + freq ( 2) = 2.781800 [THz] = 92.790863 [cm-1] + freq ( 3) = 4.119507 [THz] = 137.411975 [cm-1] + ************************************************************************** + + Mode symmetry, C_4v (4mm) point group: + + freq ( 1 - 2) = 92.8 [cm-1] --> E G_5 D_5 + freq ( 3 - 3) = 137.4 [cm-1] --> A_1 G_1 D_1 + + Calculation of q = 0.7500000 -0.2500000 0.7500000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 118 55 22 1712 556 152 + Max 119 56 23 1715 558 153 + Sum 475 223 91 6855 2229 609 + + + Title: + phonon dispersions of Pt + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 18 + kinetic-energy cutoff = 30.0000 Ry + charge density cutoff = 250.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + + celldm(1)= 7.420000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Pt 10.00 195.07800 Pt( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Pt tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 40 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.2500000 0.2500000 0.2500000), wk = 0.0625000 + k( 2) = ( 0.5000000 0.0000000 1.0000000), wk = 0.0000000 + k( 3) = ( 0.2500000 -0.2500000 0.7500000), wk = 0.0625000 + k( 4) = ( 1.0000000 -0.5000000 1.5000000), wk = 0.0000000 + k( 5) = ( -0.2500000 0.2500000 -0.2500000), wk = 0.0312500 + k( 6) = ( 0.5000000 0.0000000 0.5000000), wk = 0.0000000 + k( 7) = ( 0.2500000 0.2500000 0.2500000), wk = 0.0312500 + k( 8) = ( 1.0000000 0.0000000 1.0000000), wk = 0.0000000 + k( 9) = ( -0.2500000 -0.2500000 0.2500000), wk = 0.0625000 + k( 10) = ( 0.5000000 -0.5000000 1.0000000), wk = 0.0000000 + k( 11) = ( -0.2500000 -0.2500000 -0.2500000), wk = 0.0312500 + k( 12) = ( 0.5000000 -0.5000000 0.5000000), wk = 0.0000000 + k( 13) = ( 0.2500000 -0.2500000 0.2500000), wk = 0.0312500 + k( 14) = ( 1.0000000 -0.5000000 1.0000000), wk = 0.0000000 + k( 15) = ( 0.2500000 -0.2500000 -0.7500000), wk = 0.0625000 + k( 16) = ( 1.0000000 -0.5000000 0.0000000), wk = 0.0000000 + k( 17) = ( -0.2500000 -0.2500000 -0.7500000), wk = 0.0625000 + k( 18) = ( 0.5000000 -0.5000000 0.0000000), wk = 0.0000000 + k( 19) = ( -0.2500000 -0.2500000 0.7500000), wk = 0.0625000 + k( 20) = ( 0.5000000 -0.5000000 1.5000000), wk = 0.0000000 + k( 21) = ( -0.7500000 0.2500000 -0.2500000), wk = 0.0625000 + k( 22) = ( 0.0000000 0.0000000 0.5000000), wk = 0.0000000 + k( 23) = ( -0.2500000 0.7500000 -0.2500000), wk = 0.0312500 + k( 24) = ( 0.5000000 0.5000000 0.5000000), wk = 0.0000000 + k( 25) = ( 0.2500000 0.2500000 0.7500000), wk = 0.0625000 + k( 26) = ( 1.0000000 0.0000000 1.5000000), wk = 0.0000000 + k( 27) = ( -0.7500000 0.2500000 0.2500000), wk = 0.0625000 + k( 28) = ( 0.0000000 0.0000000 1.0000000), wk = 0.0000000 + k( 29) = ( 0.7500000 0.2500000 -0.2500000), wk = 0.0625000 + k( 30) = ( 1.5000000 0.0000000 0.5000000), wk = 0.0000000 + k( 31) = ( -0.2500000 0.7500000 0.2500000), wk = 0.0625000 + k( 32) = ( 0.5000000 0.5000000 1.0000000), wk = 0.0000000 + k( 33) = ( -0.2500000 -0.7500000 -0.2500000), wk = 0.0312500 + k( 34) = ( 0.5000000 -1.0000000 0.5000000), wk = 0.0000000 + k( 35) = ( -0.2500000 -0.7500000 0.2500000), wk = 0.0625000 + k( 36) = ( 0.5000000 -1.0000000 1.0000000), wk = 0.0000000 + k( 37) = ( 0.2500000 -0.7500000 0.2500000), wk = 0.0312500 + k( 38) = ( 1.0000000 -1.0000000 1.0000000), wk = 0.0000000 + k( 39) = ( 0.2500000 0.7500000 0.2500000), wk = 0.0312500 + k( 40) = ( 1.0000000 0.5000000 1.0000000), wk = 0.0000000 + + Dense grid: 6855 G-vectors FFT dimensions: ( 27, 27, 27) + + Smooth grid: 2229 G-vectors FFT dimensions: ( 20, 20, 20) + + Estimated max dynamical RAM per process > 12.29 MB + + Estimated total dynamical RAM > 49.15 MB + + Check: negative core charge= -0.000004 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/charge-density + + Starting wfcs are 12 atomic + 6 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 15.1 + + total cpu time spent up to now is 3.7 secs + + End of band structure calculation + + k =-0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.5000 0.0000 1.0000 ( 280 PWs) bands (ev): + + 11.8705 11.8705 12.8375 12.8375 13.0920 13.0920 15.7990 15.7990 + 18.2074 18.2074 24.7578 24.7578 25.1486 25.1486 26.5186 26.5186 + 29.7304 29.7304 + + k = 0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 1.0000-0.5000 1.5000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k =-0.2500 0.2500-0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.5000 0.0000 0.5000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k = 0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 1.0000 0.0000 1.0000 ( 286 PWs) bands (ev): + + 10.4903 10.4903 10.9472 10.9472 17.4906 17.4906 17.8002 17.8002 + 18.7797 18.7797 19.1008 19.1008 26.3323 26.3323 28.7371 28.7371 + 30.2769 30.2769 + + k =-0.2500-0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.5000-0.5000 1.0000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k =-0.2500-0.2500-0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.5000-0.5000 0.5000 ( 272 PWs) bands (ev): + + 10.2248 10.2248 13.2340 13.2340 14.2435 14.2435 16.8898 16.8898 + 17.4171 17.4171 18.0789 18.0789 23.4362 23.4362 33.8541 33.8541 + 36.9667 36.9667 + + k = 0.2500-0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 1.0000-0.5000 1.0000 ( 290 PWs) bands (ev): + + 10.0187 10.0187 12.1665 12.1665 14.1806 14.1806 15.6749 15.6749 + 15.7566 15.7566 17.0173 17.0173 33.8083 33.8083 35.8441 35.8441 + 36.2252 36.2252 + + k = 0.2500-0.2500-0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 1.0000-0.5000 0.0000 ( 280 PWs) bands (ev): + + 11.8705 11.8705 12.8375 12.8375 13.0920 13.0920 15.7990 15.7990 + 18.2074 18.2074 24.7578 24.7578 25.1486 25.1486 26.5186 26.5186 + 29.7304 29.7304 + + k =-0.2500-0.2500-0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.5000-0.5000 0.0000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k =-0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.5000-0.5000 1.5000 ( 272 PWs) bands (ev): + + 10.2248 10.2248 13.2340 13.2340 14.2435 14.2435 16.8898 16.8898 + 17.4171 17.4171 18.0789 18.0789 23.4362 23.4362 33.8541 33.8541 + 36.9667 36.9667 + + k =-0.7500 0.2500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.0000 0.0000 0.5000 ( 290 PWs) bands (ev): + + 10.0187 10.0187 12.1665 12.1665 14.1806 14.1806 15.6749 15.6749 + 15.7566 15.7566 17.0173 17.0173 33.8083 33.8083 35.8441 35.8441 + 36.2252 36.2252 + + k =-0.2500 0.7500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.5000 0.5000 0.5000 ( 272 PWs) bands (ev): + + 10.2248 10.2248 13.2340 13.2340 14.2435 14.2435 16.8898 16.8898 + 17.4171 17.4171 18.0789 18.0789 23.4362 23.4362 33.8541 33.8541 + 36.9667 36.9667 + + k = 0.2500 0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 1.0000 0.0000 1.5000 ( 280 PWs) bands (ev): + + 11.8705 11.8705 12.8375 12.8375 13.0920 13.0920 15.7990 15.7990 + 18.2074 18.2074 24.7578 24.7578 25.1486 25.1486 26.5186 26.5186 + 29.7304 29.7304 + + k =-0.7500 0.2500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.0000 0.0000 1.0000 ( 286 PWs) bands (ev): + + 10.4903 10.4903 10.9472 10.9472 17.4906 17.4906 17.8002 17.8002 + 18.7797 18.7797 19.1008 19.1008 26.3323 26.3323 28.7371 28.7371 + 30.2769 30.2769 + + k = 0.7500 0.2500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 1.5000 0.0000 0.5000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k =-0.2500 0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.5000 0.5000 1.0000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k =-0.2500-0.7500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.5000-1.0000 0.5000 ( 283 PWs) bands (ev): + + 11.6660 11.6660 12.8195 12.8195 13.2912 13.2912 15.1036 15.1036 + 16.1317 16.1317 19.5736 19.5736 28.3422 28.3422 30.4772 30.4772 + 36.8897 36.8897 + + k =-0.2500-0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.5000-1.0000 1.0000 ( 290 PWs) bands (ev): + + 10.0187 10.0187 12.1665 12.1665 14.1806 14.1806 15.6749 15.6749 + 15.7566 15.7566 17.0173 17.0173 33.8083 33.8083 35.8441 35.8441 + 36.2252 36.2252 + + k = 0.2500-0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 1.0000-1.0000 1.0000 ( 283 PWs) bands (ev): + + 7.2727 7.2727 13.3946 13.3946 13.3946 13.3946 14.3825 14.3825 + 16.2214 16.2214 16.2214 16.2214 34.8330 34.8330 38.3520 38.3520 + 39.6350 39.6350 + + k = 0.2500 0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 1.0000 0.5000 1.0000 ( 290 PWs) bands (ev): + + 10.0187 10.0187 12.1665 12.1665 14.1806 14.1806 15.6749 15.6749 + 15.7566 15.7566 17.0173 17.0173 33.8083 33.8083 35.8441 35.8441 + 36.2252 36.2252 + + the Fermi energy is 17.9731 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/ + + phonon dispersions of Pt + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 30.0000 Ry + charge density cut-off = 250.0000 Ry + convergence threshold = 1.0E-16 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + celldm(1)= 7.42000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Pt 195.0780 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.7500000 -0.2500000 0.7500000 ) + + 2 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 348.6487 ( 1715 G-vectors) FFT grid: ( 27, 27, 27) + G cutoff = 167.3514 ( 557 G-vectors) smooth grid: ( 20, 20, 20) + + number of k points= 40 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, C_s (m) point group: + + + Atomic displacements: + There are 3 irreducible representations + + Representation 1 1 modes -A' To be done + + Representation 2 1 modes -A' To be done + + Representation 3 1 modes -A'' To be done + + + + Alpha used in Ewald sum = 2.6000 + PHONON : 20.81s CPU 22.24s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 22.7 secs av.it.: 8.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.271E-03 + + iter # 2 total cpu time : 23.2 secs av.it.: 10.3 + thresh= 3.565E-03 alpha_mix = 0.700 |ddv_scf|^2 = 2.189E-02 + + iter # 3 total cpu time : 23.6 secs av.it.: 9.0 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.728E-03 + + iter # 4 total cpu time : 24.0 secs av.it.: 8.8 + thresh= 4.157E-03 alpha_mix = 0.700 |ddv_scf|^2 = 7.986E-07 + + iter # 5 total cpu time : 24.4 secs av.it.: 9.2 + thresh= 8.936E-05 alpha_mix = 0.700 |ddv_scf|^2 = 3.481E-08 + + iter # 6 total cpu time : 24.8 secs av.it.: 9.2 + thresh= 1.866E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.396E-09 + + iter # 7 total cpu time : 25.2 secs av.it.: 9.2 + thresh= 3.736E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.962E-11 + + iter # 8 total cpu time : 25.6 secs av.it.: 9.9 + thresh= 4.429E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.306E-10 + + iter # 9 total cpu time : 26.0 secs av.it.: 8.3 + thresh= 1.143E-06 alpha_mix = 0.700 |ddv_scf|^2 = 2.505E-12 + + iter # 10 total cpu time : 26.5 secs av.it.: 9.4 + thresh= 1.583E-07 alpha_mix = 0.700 |ddv_scf|^2 = 8.072E-13 + + iter # 11 total cpu time : 26.9 secs av.it.: 8.8 + thresh= 8.984E-08 alpha_mix = 0.700 |ddv_scf|^2 = 7.932E-15 + + iter # 12 total cpu time : 27.3 secs av.it.: 9.6 + thresh= 8.906E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.739E-15 + + iter # 13 total cpu time : 27.7 secs av.it.: 9.6 + thresh= 5.234E-09 alpha_mix = 0.700 |ddv_scf|^2 = 4.502E-15 + + iter # 14 total cpu time : 28.0 secs av.it.: 8.8 + thresh= 6.710E-09 alpha_mix = 0.700 |ddv_scf|^2 = 1.968E-16 + + iter # 15 total cpu time : 28.5 secs av.it.: 8.9 + thresh= 1.403E-09 alpha_mix = 0.700 |ddv_scf|^2 = 1.292E-16 + + iter # 16 total cpu time : 28.9 secs av.it.: 8.7 + thresh= 1.137E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.967E-19 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 mode # 2 + + Self-consistent Calculation + + iter # 1 total cpu time : 29.3 secs av.it.: 7.9 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 3.770E-04 + + iter # 2 total cpu time : 29.8 secs av.it.: 10.2 + thresh= 1.942E-03 alpha_mix = 0.700 |ddv_scf|^2 = 9.150E-03 + + iter # 3 total cpu time : 30.2 secs av.it.: 8.2 + thresh= 9.566E-03 alpha_mix = 0.700 |ddv_scf|^2 = 2.030E-04 + + iter # 4 total cpu time : 30.6 secs av.it.: 8.9 + thresh= 1.425E-03 alpha_mix = 0.700 |ddv_scf|^2 = 1.707E-06 + + iter # 5 total cpu time : 31.0 secs av.it.: 9.2 + thresh= 1.306E-04 alpha_mix = 0.700 |ddv_scf|^2 = 3.458E-08 + + iter # 6 total cpu time : 31.4 secs av.it.: 9.3 + thresh= 1.859E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.843E-10 + + iter # 7 total cpu time : 31.8 secs av.it.: 10.1 + thresh= 1.686E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.132E-10 + + iter # 8 total cpu time : 32.2 secs av.it.: 10.1 + thresh= 1.064E-06 alpha_mix = 0.700 |ddv_scf|^2 = 9.924E-10 + + iter # 9 total cpu time : 32.6 secs av.it.: 8.2 + thresh= 3.150E-06 alpha_mix = 0.700 |ddv_scf|^2 = 4.919E-12 + + iter # 10 total cpu time : 33.0 secs av.it.: 10.1 + thresh= 2.218E-07 alpha_mix = 0.700 |ddv_scf|^2 = 5.659E-11 + + iter # 11 total cpu time : 33.4 secs av.it.: 8.2 + thresh= 7.523E-07 alpha_mix = 0.700 |ddv_scf|^2 = 2.581E-14 + + iter # 12 total cpu time : 33.9 secs av.it.: 10.1 + thresh= 1.607E-08 alpha_mix = 0.700 |ddv_scf|^2 = 9.909E-15 + + iter # 13 total cpu time : 34.3 secs av.it.: 9.2 + thresh= 9.954E-09 alpha_mix = 0.700 |ddv_scf|^2 = 3.735E-16 + + iter # 14 total cpu time : 34.7 secs av.it.: 9.9 + thresh= 1.933E-09 alpha_mix = 0.700 |ddv_scf|^2 = 5.520E-16 + + iter # 15 total cpu time : 35.1 secs av.it.: 9.4 + thresh= 2.350E-09 alpha_mix = 0.700 |ddv_scf|^2 = 1.750E-15 + + iter # 16 total cpu time : 35.5 secs av.it.: 8.2 + thresh= 4.184E-09 alpha_mix = 0.700 |ddv_scf|^2 = 8.292E-17 + + iter # 17 total cpu time : 35.9 secs av.it.: 8.6 + thresh= 9.106E-10 alpha_mix = 0.700 |ddv_scf|^2 = 6.919E-18 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 3 mode # 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 36.2 secs av.it.: 7.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.838E-05 + + iter # 2 total cpu time : 36.7 secs av.it.: 10.1 + thresh= 4.288E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.568E-06 + + iter # 3 total cpu time : 37.1 secs av.it.: 9.8 + thresh= 1.252E-04 alpha_mix = 0.700 |ddv_scf|^2 = 8.831E-09 + + iter # 4 total cpu time : 37.5 secs av.it.: 9.3 + thresh= 9.397E-06 alpha_mix = 0.700 |ddv_scf|^2 = 3.992E-11 + + iter # 5 total cpu time : 38.0 secs av.it.: 10.1 + thresh= 6.318E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.097E-12 + + iter # 6 total cpu time : 38.4 secs av.it.: 9.8 + thresh= 1.047E-07 alpha_mix = 0.700 |ddv_scf|^2 = 4.650E-15 + + iter # 7 total cpu time : 38.8 secs av.it.: 9.3 + thresh= 6.819E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.854E-16 + + iter # 8 total cpu time : 39.3 secs av.it.: 9.6 + thresh= 1.689E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.462E-19 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 24 + List of q in the star: + 1 0.750000000 -0.250000000 0.750000000 + 2 0.750000000 -0.250000000 -0.750000000 + 3 -0.750000000 -0.250000000 -0.750000000 + 4 -0.750000000 -0.250000000 0.750000000 + 5 -0.750000000 0.250000000 -0.750000000 + 6 -0.250000000 0.750000000 -0.750000000 + 7 -0.750000000 0.750000000 -0.250000000 + 8 0.750000000 0.250000000 0.750000000 + 9 -0.750000000 0.250000000 0.750000000 + 10 0.750000000 0.250000000 -0.750000000 + 11 -0.750000000 0.750000000 0.250000000 + 12 -0.250000000 0.750000000 0.750000000 + 13 0.250000000 0.750000000 -0.750000000 + 14 -0.250000000 -0.750000000 -0.750000000 + 15 0.750000000 0.750000000 -0.250000000 + 16 0.750000000 -0.750000000 0.250000000 + 17 -0.750000000 -0.750000000 -0.250000000 + 18 0.250000000 -0.750000000 0.750000000 + 19 -0.750000000 -0.750000000 0.250000000 + 20 0.250000000 0.750000000 0.750000000 + 21 -0.250000000 -0.750000000 0.750000000 + 22 0.750000000 0.750000000 0.250000000 + 23 0.250000000 -0.750000000 -0.750000000 + 24 0.750000000 -0.750000000 -0.250000000 + + Diagonalizing the dynamical matrix + + q = ( 0.750000000 -0.250000000 0.750000000 ) + + ************************************************************************** + freq ( 1) = 3.513283 [THz] = 117.190506 [cm-1] + freq ( 2) = 4.155681 [THz] = 138.618586 [cm-1] + freq ( 3) = 5.871175 [THz] = 195.841313 [cm-1] + ************************************************************************** + + Mode symmetry, C_s (m) point group: + + freq ( 1 - 1) = 117.2 [cm-1] --> A'' + freq ( 2 - 2) = 138.6 [cm-1] --> A' + freq ( 3 - 3) = 195.8 [cm-1] --> A' + + Calculation of q = 0.5000000 0.0000000 0.5000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 118 55 21 1712 556 132 + Max 119 56 22 1715 558 135 + Sum 475 223 85 6855 2229 531 + + + Title: + phonon dispersions of Pt + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 18 + kinetic-energy cutoff = 30.0000 Ry + charge density cutoff = 250.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + + celldm(1)= 7.420000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Pt 10.00 195.07800 Pt( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Pt tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 20 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.2500000 0.2500000 0.2500000), wk = 0.1250000 + k( 2) = ( 0.2500000 0.2500000 0.7500000), wk = 0.0000000 + k( 3) = ( 0.2500000 -0.2500000 0.7500000), wk = 0.1250000 + k( 4) = ( 0.7500000 -0.2500000 1.2500000), wk = 0.0000000 + k( 5) = ( 0.2500000 0.2500000 0.2500000), wk = 0.0625000 + k( 6) = ( 0.7500000 0.2500000 0.7500000), wk = 0.0000000 + k( 7) = ( -0.2500000 0.2500000 -0.2500000), wk = 0.0625000 + k( 8) = ( 0.2500000 0.2500000 0.2500000), wk = 0.0000000 + k( 9) = ( -0.2500000 -0.2500000 0.7500000), wk = 0.1250000 + k( 10) = ( 0.2500000 -0.2500000 1.2500000), wk = 0.0000000 + k( 11) = ( -0.7500000 -0.2500000 -0.2500000), wk = 0.1250000 + k( 12) = ( -0.2500000 -0.2500000 0.2500000), wk = 0.0000000 + k( 13) = ( -0.7500000 -0.2500000 0.2500000), wk = 0.1250000 + k( 14) = ( -0.2500000 -0.2500000 0.7500000), wk = 0.0000000 + k( 15) = ( -0.2500000 0.7500000 -0.2500000), wk = 0.0625000 + k( 16) = ( 0.2500000 0.7500000 0.2500000), wk = 0.0000000 + k( 17) = ( -0.2500000 0.7500000 0.2500000), wk = 0.1250000 + k( 18) = ( 0.2500000 0.7500000 0.7500000), wk = 0.0000000 + k( 19) = ( 0.2500000 -0.7500000 0.2500000), wk = 0.0625000 + k( 20) = ( 0.7500000 -0.7500000 0.7500000), wk = 0.0000000 + + Dense grid: 6855 G-vectors FFT dimensions: ( 27, 27, 27) + + Smooth grid: 2229 G-vectors FFT dimensions: ( 20, 20, 20) + + Estimated max dynamical RAM per process > 12.26 MB + + Estimated total dynamical RAM > 49.05 MB + + Check: negative core charge= -0.000004 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/charge-density + + Starting wfcs are 12 atomic + 6 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 15.2 + + total cpu time spent up to now is 4.6 secs + + End of band structure calculation + + k =-0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.2500 0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.7500-0.2500 1.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.7500 0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500 0.2500-0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k = 0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k =-0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500-0.2500 1.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.7500-0.2500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500-0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k =-0.7500-0.2500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500 0.7500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500 0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500 0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500 0.7500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500-0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.7500-0.7500 0.7500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + the Fermi energy is 17.9731 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/ + + phonon dispersions of Pt + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 30.0000 Ry + charge density cut-off = 250.0000 Ry + convergence threshold = 1.0E-16 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + celldm(1)= 7.42000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Pt 195.0780 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.5000000 0.0000000 0.5000000 ) + + 4 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 348.6487 ( 1715 G-vectors) FFT grid: ( 27, 27, 27) + G cutoff = 167.3514 ( 557 G-vectors) smooth grid: ( 20, 20, 20) + + number of k points= 20 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, C_2v (mm2) point group: + + + Atomic displacements: + There are 3 irreducible representations + + Representation 1 1 modes -A_1 D_1 S_1 To be done + + Representation 2 1 modes -B_1 D_3 S_3 To be done + + Representation 3 1 modes -B_2 D_4 S_4 To be done + + + + Alpha used in Ewald sum = 2.6000 + PHONON : 37.65s CPU 40.61s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 40.9 secs av.it.: 9.0 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 6.304E-03 + + iter # 2 total cpu time : 41.1 secs av.it.: 10.8 + thresh= 7.940E-03 alpha_mix = 0.700 |ddv_scf|^2 = 2.663E-01 + + iter # 3 total cpu time : 41.4 secs av.it.: 10.6 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 2.898E-03 + + iter # 4 total cpu time : 41.6 secs av.it.: 8.8 + thresh= 5.383E-03 alpha_mix = 0.700 |ddv_scf|^2 = 2.474E-05 + + iter # 5 total cpu time : 41.8 secs av.it.: 8.8 + thresh= 4.974E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.082E-09 + + iter # 6 total cpu time : 42.1 secs av.it.: 10.7 + thresh= 3.289E-06 alpha_mix = 0.700 |ddv_scf|^2 = 4.058E-11 + + iter # 7 total cpu time : 42.4 secs av.it.: 10.8 + thresh= 6.370E-07 alpha_mix = 0.700 |ddv_scf|^2 = 5.150E-12 + + iter # 8 total cpu time : 42.6 secs av.it.: 11.1 + thresh= 2.269E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.105E-10 + + iter # 9 total cpu time : 42.9 secs av.it.: 8.2 + thresh= 1.051E-06 alpha_mix = 0.700 |ddv_scf|^2 = 3.130E-12 + + iter # 10 total cpu time : 43.1 secs av.it.: 9.2 + thresh= 1.769E-07 alpha_mix = 0.700 |ddv_scf|^2 = 2.355E-12 + + iter # 11 total cpu time : 43.3 secs av.it.: 8.9 + thresh= 1.535E-07 alpha_mix = 0.700 |ddv_scf|^2 = 4.723E-13 + + iter # 12 total cpu time : 43.6 secs av.it.: 9.3 + thresh= 6.872E-08 alpha_mix = 0.700 |ddv_scf|^2 = 4.333E-15 + + iter # 13 total cpu time : 43.8 secs av.it.: 9.3 + thresh= 6.583E-09 alpha_mix = 0.700 |ddv_scf|^2 = 6.814E-16 + + iter # 14 total cpu time : 44.0 secs av.it.: 10.0 + thresh= 2.610E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.604E-15 + + iter # 15 total cpu time : 44.2 secs av.it.: 8.3 + thresh= 5.103E-09 alpha_mix = 0.700 |ddv_scf|^2 = 1.966E-16 + + iter # 16 total cpu time : 44.4 secs av.it.: 9.1 + thresh= 1.402E-09 alpha_mix = 0.700 |ddv_scf|^2 = 8.903E-19 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 mode # 2 + + Self-consistent Calculation + + iter # 1 total cpu time : 44.6 secs av.it.: 7.4 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 9.916E-06 + + iter # 2 total cpu time : 44.9 secs av.it.: 11.2 + thresh= 3.149E-04 alpha_mix = 0.700 |ddv_scf|^2 = 5.557E-07 + + iter # 3 total cpu time : 45.1 secs av.it.: 10.4 + thresh= 7.454E-05 alpha_mix = 0.700 |ddv_scf|^2 = 8.866E-09 + + iter # 4 total cpu time : 45.4 secs av.it.: 10.7 + thresh= 9.416E-06 alpha_mix = 0.700 |ddv_scf|^2 = 3.598E-10 + + iter # 5 total cpu time : 45.6 secs av.it.: 10.9 + thresh= 1.897E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.025E-12 + + iter # 6 total cpu time : 45.9 secs av.it.: 10.5 + thresh= 1.012E-07 alpha_mix = 0.700 |ddv_scf|^2 = 5.579E-15 + + iter # 7 total cpu time : 46.1 secs av.it.: 9.7 + thresh= 7.469E-09 alpha_mix = 0.700 |ddv_scf|^2 = 3.382E-16 + + iter # 8 total cpu time : 46.4 secs av.it.: 10.5 + thresh= 1.839E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.651E-19 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 3 mode # 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 46.6 secs av.it.: 8.0 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 6.790E-05 + + iter # 2 total cpu time : 46.9 secs av.it.: 11.0 + thresh= 8.240E-04 alpha_mix = 0.700 |ddv_scf|^2 = 2.014E-05 + + iter # 3 total cpu time : 47.1 secs av.it.: 10.3 + thresh= 4.488E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.386E-08 + + iter # 4 total cpu time : 47.4 secs av.it.: 10.6 + thresh= 1.177E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.761E-10 + + iter # 5 total cpu time : 47.6 secs av.it.: 10.5 + thresh= 1.327E-06 alpha_mix = 0.700 |ddv_scf|^2 = 3.119E-12 + + iter # 6 total cpu time : 47.8 secs av.it.: 10.5 + thresh= 1.766E-07 alpha_mix = 0.700 |ddv_scf|^2 = 2.049E-14 + + iter # 7 total cpu time : 48.1 secs av.it.: 10.6 + thresh= 1.431E-08 alpha_mix = 0.700 |ddv_scf|^2 = 4.656E-16 + + iter # 8 total cpu time : 48.3 secs av.it.: 10.3 + thresh= 2.158E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.117E-18 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 12 + List of q in the star: + 1 0.500000000 0.000000000 0.500000000 + 2 -0.500000000 0.000000000 0.500000000 + 3 -0.500000000 0.000000000 -0.500000000 + 4 0.500000000 0.000000000 -0.500000000 + 5 0.000000000 0.500000000 -0.500000000 + 6 -0.500000000 0.500000000 0.000000000 + 7 0.000000000 0.500000000 0.500000000 + 8 0.000000000 -0.500000000 -0.500000000 + 9 0.500000000 0.500000000 0.000000000 + 10 0.500000000 -0.500000000 0.000000000 + 11 -0.500000000 -0.500000000 0.000000000 + 12 0.000000000 -0.500000000 0.500000000 + + Diagonalizing the dynamical matrix + + q = ( 0.500000000 0.000000000 0.500000000 ) + + ************************************************************************** + freq ( 1) = 2.856569 [THz] = 95.284896 [cm-1] + freq ( 2) = 4.035108 [THz] = 134.596701 [cm-1] + freq ( 3) = 5.304844 [THz] = 176.950549 [cm-1] + ************************************************************************** + + Mode symmetry, C_2v (mm2) point group: + + freq ( 1 - 1) = 95.3 [cm-1] --> B_1 D_3 S_3 + freq ( 2 - 2) = 134.6 [cm-1] --> B_2 D_4 S_4 + freq ( 3 - 3) = 177.0 [cm-1] --> A_1 D_1 S_1 + + Calculation of q = 0.0000000 -1.0000000 0.0000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 118 55 21 1712 556 132 + Max 119 56 22 1715 558 135 + Sum 475 223 85 6855 2229 531 + + + Title: + phonon dispersions of Pt + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 18 + kinetic-energy cutoff = 30.0000 Ry + charge density cutoff = 250.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + + celldm(1)= 7.420000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Pt 10.00 195.07800 Pt( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Pt tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 6 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.2500000 0.2500000 0.2500000), wk = 0.2500000 + k( 2) = ( -0.2500000 -0.7500000 0.2500000), wk = 0.0000000 + k( 3) = ( 0.2500000 -0.2500000 0.7500000), wk = 0.5000000 + k( 4) = ( 0.2500000 -1.2500000 0.7500000), wk = 0.0000000 + k( 5) = ( -0.2500000 0.7500000 0.2500000), wk = 0.2500000 + k( 6) = ( -0.2500000 -0.2500000 0.2500000), wk = 0.0000000 + + Dense grid: 6855 G-vectors FFT dimensions: ( 27, 27, 27) + + Smooth grid: 2229 G-vectors FFT dimensions: ( 20, 20, 20) + + Estimated max dynamical RAM per process > 12.28 MB + + Estimated total dynamical RAM > 49.13 MB + + Check: negative core charge= -0.000004 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/charge-density + + Starting wfcs are 12 atomic + 6 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 15.7 + + total cpu time spent up to now is 5.0 secs + + End of band structure calculation + + k =-0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k =-0.2500-0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500-1.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500 0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500-0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + the Fermi energy is 17.9731 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/ + + phonon dispersions of Pt + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 30.0000 Ry + charge density cut-off = 250.0000 Ry + convergence threshold = 1.0E-16 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + celldm(1)= 7.42000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Pt 195.0780 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.0000000 -1.0000000 0.0000000 ) + + 17 Sym.Ops. (with q -> -q+G ) + + + G cutoff = 348.6487 ( 1715 G-vectors) FFT grid: ( 27, 27, 27) + G cutoff = 167.3514 ( 557 G-vectors) smooth grid: ( 20, 20, 20) + + number of k points= 6 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, D_4h(4/mmm) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_2u X_4' M_4' To be done + + Representation 2 2 modes -E_u X_5' M_5' To be done + + + + Alpha used in Ewald sum = 2.6000 + PHONON : 45.46s CPU 49.02s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 49.1 secs av.it.: 8.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.837E-04 + + iter # 2 total cpu time : 49.3 secs av.it.: 10.7 + thresh= 2.199E-03 alpha_mix = 0.700 |ddv_scf|^2 = 5.208E-04 + + iter # 3 total cpu time : 49.4 secs av.it.: 9.3 + thresh= 2.282E-03 alpha_mix = 0.700 |ddv_scf|^2 = 2.226E-08 + + iter # 4 total cpu time : 49.5 secs av.it.: 10.7 + thresh= 1.492E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.950E-10 + + iter # 5 total cpu time : 49.6 secs av.it.: 9.7 + thresh= 1.396E-06 alpha_mix = 0.700 |ddv_scf|^2 = 4.734E-12 + + iter # 6 total cpu time : 49.7 secs av.it.: 10.3 + thresh= 2.176E-07 alpha_mix = 0.700 |ddv_scf|^2 = 6.745E-15 + + iter # 7 total cpu time : 49.8 secs av.it.: 10.7 + thresh= 8.213E-09 alpha_mix = 0.700 |ddv_scf|^2 = 2.979E-16 + + iter # 8 total cpu time : 49.9 secs av.it.: 10.0 + thresh= 1.726E-09 alpha_mix = 0.700 |ddv_scf|^2 = 1.378E-18 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 50.1 secs av.it.: 7.5 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 7.680E-06 + + iter # 2 total cpu time : 50.3 secs av.it.: 11.5 + thresh= 2.771E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.049E-06 + + iter # 3 total cpu time : 50.5 secs av.it.: 11.2 + thresh= 1.024E-04 alpha_mix = 0.700 |ddv_scf|^2 = 2.459E-09 + + iter # 4 total cpu time : 50.8 secs av.it.: 11.0 + thresh= 4.959E-06 alpha_mix = 0.700 |ddv_scf|^2 = 4.604E-12 + + iter # 5 total cpu time : 51.0 secs av.it.: 11.0 + thresh= 2.146E-07 alpha_mix = 0.700 |ddv_scf|^2 = 4.660E-14 + + iter # 6 total cpu time : 51.2 secs av.it.: 11.0 + thresh= 2.159E-08 alpha_mix = 0.700 |ddv_scf|^2 = 7.099E-16 + + iter # 7 total cpu time : 51.4 secs av.it.: 10.5 + thresh= 2.664E-09 alpha_mix = 0.700 |ddv_scf|^2 = 5.043E-19 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 3 + List of q in the star: + 1 0.000000000 -1.000000000 0.000000000 + 2 -1.000000000 0.000000000 0.000000000 + 3 0.000000000 0.000000000 -1.000000000 + + Diagonalizing the dynamical matrix + + q = ( 0.000000000 -1.000000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 3.691552 [THz] = 123.136927 [cm-1] + freq ( 2) = 3.691552 [THz] = 123.136927 [cm-1] + freq ( 3) = 5.815222 [THz] = 193.974936 [cm-1] + ************************************************************************** + + Mode symmetry, D_4h(4/mmm) point group: + + freq ( 1 - 2) = 123.1 [cm-1] --> E_u X_5' M_5' + freq ( 3 - 3) = 194.0 [cm-1] --> A_2u X_4' M_4' + + Calculation of q = -0.5000000 -1.0000000 0.0000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 118 55 21 1712 556 132 + Max 119 56 22 1715 558 135 + Sum 475 223 85 6855 2229 531 + + + Title: + phonon dispersions of Pt + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 18 + kinetic-energy cutoff = 30.0000 Ry + charge density cutoff = 250.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + + celldm(1)= 7.420000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Pt 10.00 195.07800 Pt( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Pt tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 8 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.2500000 0.2500000 0.2500000), wk = 0.2500000 + k( 2) = ( -0.7500000 -0.7500000 0.2500000), wk = 0.0000000 + k( 3) = ( 0.2500000 -0.2500000 0.7500000), wk = 0.2500000 + k( 4) = ( -0.2500000 -1.2500000 0.7500000), wk = 0.0000000 + k( 5) = ( -0.7500000 0.2500000 -0.2500000), wk = 0.2500000 + k( 6) = ( -1.2500000 -0.7500000 -0.2500000), wk = 0.0000000 + k( 7) = ( -0.2500000 0.2500000 0.7500000), wk = 0.2500000 + k( 8) = ( -0.7500000 -0.7500000 0.7500000), wk = 0.0000000 + + Dense grid: 6855 G-vectors FFT dimensions: ( 27, 27, 27) + + Smooth grid: 2229 G-vectors FFT dimensions: ( 20, 20, 20) + + Estimated max dynamical RAM per process > 12.29 MB + + Estimated total dynamical RAM > 49.16 MB + + Check: negative core charge= -0.000004 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/charge-density + + Starting wfcs are 12 atomic + 6 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 15.2 + + total cpu time spent up to now is 5.4 secs + + End of band structure calculation + + k =-0.2500 0.2500 0.2500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + k =-0.7500-0.7500 0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k = 0.2500-0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500-1.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.7500 0.2500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-1.2500-0.7500-0.2500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.2500 0.2500 0.7500 ( 283 PWs) bands (ev): + + 11.2910 11.2910 12.4161 12.4161 13.9359 13.9359 15.5889 15.5889 + 17.8747 17.8747 20.6641 20.6641 25.0087 25.0087 31.6343 31.6343 + 33.8373 33.8373 + + k =-0.7500-0.7500 0.7500 ( 289 PWs) bands (ev): + + 9.3170 9.3170 13.3107 13.3107 13.5800 13.5800 14.7744 14.7744 + 16.0692 16.0692 16.6624 16.6624 31.1506 31.1506 35.9701 35.9701 + 39.8081 39.8081 + + the Fermi energy is 17.9731 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/platinum.save/ + + phonon dispersions of Pt + + bravais-lattice index = 2 + lattice parameter (alat) = 7.4200 a.u. + unit-cell volume = 102.1296 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 30.0000 Ry + charge density cut-off = 250.0000 Ry + convergence threshold = 1.0E-16 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Non magnetic calculation with spin-orbit + + celldm(1)= 7.42000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Pt 195.0780 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( -0.5000000 -1.0000000 0.0000000 ) + + 8 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 348.6487 ( 1715 G-vectors) FFT grid: ( 27, 27, 27) + G cutoff = 167.3514 ( 557 G-vectors) smooth grid: ( 20, 20, 20) + + number of k points= 8 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Pt read from file: + /home/giannozz/q-e-mio/pseudo/Pt.rel-pz-n-rrkjus.UPF + MD5 check sum: 29bb1080eaf7d3d26ad87326ed34c38e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1277 points, 6 beta functions with: + l(1) = 2 + l(2) = 2 + l(3) = 2 + l(4) = 2 + l(5) = 1 + l(6) = 1 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, D_2d (-42m) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -B_2 X_3 W_2 To be done + + Representation 2 2 modes -E X_5 W_3 To be done + + + + Alpha used in Ewald sum = 2.6000 + PHONON : 48.38s CPU 52.12s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 52.2 secs av.it.: 8.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 8.097E-05 + + iter # 2 total cpu time : 52.4 secs av.it.: 11.2 + thresh= 8.999E-04 alpha_mix = 0.700 |ddv_scf|^2 = 3.784E-05 + + iter # 3 total cpu time : 52.5 secs av.it.: 10.5 + thresh= 6.152E-04 alpha_mix = 0.700 |ddv_scf|^2 = 5.954E-08 + + iter # 4 total cpu time : 52.6 secs av.it.: 11.0 + thresh= 2.440E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.609E-09 + + iter # 5 total cpu time : 52.8 secs av.it.: 10.5 + thresh= 5.108E-06 alpha_mix = 0.700 |ddv_scf|^2 = 9.594E-12 + + iter # 6 total cpu time : 52.9 secs av.it.: 10.5 + thresh= 3.097E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.636E-13 + + iter # 7 total cpu time : 53.0 secs av.it.: 10.5 + thresh= 4.045E-08 alpha_mix = 0.700 |ddv_scf|^2 = 2.303E-15 + + iter # 8 total cpu time : 53.2 secs av.it.: 10.5 + thresh= 4.799E-09 alpha_mix = 0.700 |ddv_scf|^2 = 1.015E-17 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 53.4 secs av.it.: 8.4 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.172E-05 + + iter # 2 total cpu time : 53.7 secs av.it.: 12.1 + thresh= 6.459E-04 alpha_mix = 0.700 |ddv_scf|^2 = 2.270E-05 + + iter # 3 total cpu time : 53.9 secs av.it.: 11.2 + thresh= 4.764E-04 alpha_mix = 0.700 |ddv_scf|^2 = 4.116E-09 + + iter # 4 total cpu time : 54.2 secs av.it.: 11.8 + thresh= 6.416E-06 alpha_mix = 0.700 |ddv_scf|^2 = 5.272E-11 + + iter # 5 total cpu time : 54.4 secs av.it.: 11.8 + thresh= 7.261E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.132E-12 + + iter # 6 total cpu time : 54.6 secs av.it.: 11.5 + thresh= 1.064E-07 alpha_mix = 0.700 |ddv_scf|^2 = 2.022E-14 + + iter # 7 total cpu time : 54.9 secs av.it.: 11.5 + thresh= 1.422E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.195E-16 + + iter # 8 total cpu time : 55.1 secs av.it.: 11.6 + thresh= 1.093E-09 alpha_mix = 0.700 |ddv_scf|^2 = 1.024E-18 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 6 + List of q in the star: + 1 -0.500000000 -1.000000000 0.000000000 + 2 0.000000000 1.000000000 0.500000000 + 3 0.000000000 -1.000000000 -0.500000000 + 4 0.500000000 1.000000000 0.000000000 + 5 -1.000000000 -0.500000000 0.000000000 + 6 0.000000000 -0.500000000 -1.000000000 + + Diagonalizing the dynamical matrix + + q = ( -0.500000000 -1.000000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 3.975390 [THz] = 132.604721 [cm-1] + freq ( 2) = 5.105603 [THz] = 170.304590 [cm-1] + freq ( 3) = 5.105603 [THz] = 170.304590 [cm-1] + ************************************************************************** + + Mode symmetry, D_2d (-42m) point group: + + freq ( 1 - 1) = 132.6 [cm-1] --> B_2 X_3 W_2 + freq ( 2 - 3) = 170.3 [cm-1] --> E X_5 W_3 + + init_run : 0.72s CPU 0.75s WALL ( 7 calls) + electrons : 4.40s CPU 4.63s WALL ( 7 calls) + + Called by init_run: + wfcinit : 0.00s CPU 0.00s WALL ( 7 calls) + potinit : 0.01s CPU 0.01s WALL ( 7 calls) + hinit0 : 0.64s CPU 0.64s WALL ( 7 calls) + + Called by electrons: + c_bands : 4.39s CPU 4.63s WALL ( 7 calls) + v_of_rho : 0.00s CPU 0.00s WALL ( 8 calls) + newd : 0.06s CPU 0.09s WALL ( 8 calls) + + Called by c_bands: + init_us_2 : 0.05s CPU 0.05s WALL ( 2202 calls) + cegterg : 4.06s CPU 4.28s WALL ( 118 calls) + + Called by sum_band: + + Called by *egterg: + cdiaghg : 1.23s CPU 1.27s WALL ( 1887 calls) + h_psi : 26.17s CPU 28.57s WALL ( 26641 calls) + s_psi : 1.85s CPU 2.03s WALL ( 53209 calls) + g_psi : 0.01s CPU 0.01s WALL ( 1771 calls) + + Called by h_psi: + h_psi:calbec : 1.46s CPU 1.60s WALL ( 26641 calls) + vloc_psi : 23.64s CPU 25.80s WALL ( 26641 calls) + add_vuspsi : 0.93s CPU 1.02s WALL ( 26641 calls) + + General routines + calbec : 2.59s CPU 2.82s WALL ( 56875 calls) + fft : 1.33s CPU 1.34s WALL ( 2082 calls) + ffts : 0.04s CPU 0.05s WALL ( 822 calls) + fftw : 24.50s CPU 26.82s WALL ( 1084512 calls) + interpolate : 0.08s CPU 0.09s WALL ( 523 calls) + davcio : 0.19s CPU 0.31s WALL ( 11424 calls) + + Parallel routines + fft_scatt_xy : 2.84s CPU 3.09s WALL ( 1087416 calls) + fft_scatt_yz : 12.20s CPU 13.24s WALL ( 1087416 calls) + + PHONON : 51.22s CPU 55.15s WALL INITIALIZATION: - phq_setup : 0.01s CPU 0.01s WALL ( 1 calls) - phq_init : 0.49s CPU 0.53s WALL ( 1 calls) - - phq_init : 0.49s CPU 0.53s WALL ( 1 calls) - set_drhoc : 0.14s CPU 0.15s WALL ( 3 calls) - init_vloc : 0.00s CPU 0.01s WALL ( 1 calls) - init_us_1 : 0.24s CPU 0.33s WALL ( 1 calls) - newd : 0.03s CPU 0.03s WALL ( 1 calls) - dvanqq : 0.11s CPU 0.12s WALL ( 1 calls) - drho : 0.15s CPU 0.16s WALL ( 1 calls) - + phq_setup : 0.02s CPU 0.03s WALL ( 8 calls) + phq_init : 3.38s CPU 3.42s WALL ( 8 calls) + + phq_init : 3.38s CPU 3.42s WALL ( 8 calls) + set_drhoc : 0.32s CPU 0.33s WALL ( 24 calls) + init_vloc : 0.01s CPU 0.01s WALL ( 8 calls) + init_us_1 : 0.66s CPU 0.67s WALL ( 8 calls) + newd : 0.06s CPU 0.09s WALL ( 8 calls) + dvanqq : 0.40s CPU 0.41s WALL ( 8 calls) + drho : 2.07s CPU 2.09s WALL ( 8 calls) + DYNAMICAL MATRIX: - dynmat0 : 0.13s CPU 0.14s WALL ( 1 calls) - phqscf : 2.29s CPU 2.64s WALL ( 1 calls) - dynmatrix : 0.01s CPU 0.01s WALL ( 1 calls) - - phqscf : 2.29s CPU 2.64s WALL ( 1 calls) - solve_linter : 2.28s CPU 2.63s WALL ( 1 calls) - drhodv : 0.01s CPU 0.01s WALL ( 1 calls) - - dynmat0 : 0.13s CPU 0.14s WALL ( 1 calls) - dynmat_us : 0.03s CPU 0.03s WALL ( 1 calls) - d2ionq : 0.00s CPU 0.00s WALL ( 1 calls) - dynmatcc : 0.10s CPU 0.10s WALL ( 1 calls) - - dynmat_us : 0.03s CPU 0.03s WALL ( 1 calls) - addusdynmat : 0.01s CPU 0.01s WALL ( 1 calls) - - phqscf : 2.29s CPU 2.64s WALL ( 1 calls) - solve_linter : 2.28s CPU 2.63s WALL ( 1 calls) - - solve_linter : 2.28s CPU 2.63s WALL ( 1 calls) - dvqpsi_us : 0.05s CPU 0.06s WALL ( 6 calls) - ortho : 0.03s CPU 0.04s WALL ( 36 calls) - cgsolve : 0.86s CPU 1.04s WALL ( 36 calls) - incdrhoscf : 0.05s CPU 0.05s WALL ( 36 calls) - addusddens : 0.16s CPU 0.18s WALL ( 7 calls) - vpsifft : 0.03s CPU 0.03s WALL ( 30 calls) - dv_of_drho : 0.01s CPU 0.01s WALL ( 18 calls) - mix_pot : 0.01s CPU 0.01s WALL ( 6 calls) - ef_shift : 0.01s CPU 0.01s WALL ( 7 calls) - localdos : 0.02s CPU 0.02s WALL ( 1 calls) - psymdvscf : 0.70s CPU 0.73s WALL ( 6 calls) - newdq : 0.31s CPU 0.33s WALL ( 6 calls) - adddvscf : 0.02s CPU 0.02s WALL ( 30 calls) - drhodvus : 0.00s CPU 0.00s WALL ( 1 calls) - - dvqpsi_us : 0.05s CPU 0.06s WALL ( 6 calls) - dvqpsi_us_on : 0.05s CPU 0.05s WALL ( 6 calls) - - cgsolve : 0.86s CPU 1.04s WALL ( 36 calls) - ch_psi : 0.82s CPU 0.99s WALL ( 512 calls) - - ch_psi : 0.82s CPU 0.99s WALL ( 512 calls) - h_psi : 0.52s CPU 0.66s WALL ( 512 calls) - last : 0.23s CPU 0.24s WALL ( 512 calls) - - h_psi : 0.52s CPU 0.66s WALL ( 512 calls) - add_vuspsi : 0.06s CPU 0.08s WALL ( 512 calls) - - incdrhoscf : 0.05s CPU 0.05s WALL ( 36 calls) - - drhodvus : 0.00s CPU 0.00s WALL ( 1 calls) - + dynmat0 : 0.66s CPU 0.67s WALL ( 8 calls) + phqscf : 42.26s CPU 45.85s WALL ( 8 calls) + dynmatrix : 0.01s CPU 0.01s WALL ( 8 calls) + + phqscf : 42.26s CPU 45.85s WALL ( 8 calls) + solve_linter : 42.10s CPU 45.68s WALL ( 17 calls) + drhodv : 0.14s CPU 0.15s WALL ( 17 calls) + + dynmat0 : 0.66s CPU 0.67s WALL ( 8 calls) + dynmat_us : 0.35s CPU 0.36s WALL ( 8 calls) + d2ionq : 0.03s CPU 0.03s WALL ( 8 calls) + dynmatcc : 0.25s CPU 0.25s WALL ( 8 calls) + + dynmat_us : 0.35s CPU 0.36s WALL ( 8 calls) + addusdynmat : 0.05s CPU 0.05s WALL ( 8 calls) + + phqscf : 42.26s CPU 45.85s WALL ( 8 calls) + solve_linter : 42.10s CPU 45.68s WALL ( 17 calls) + + solve_linter : 42.10s CPU 45.68s WALL ( 17 calls) + dvqpsi_us : 0.73s CPU 0.80s WALL ( 180 calls) + ortho : 0.60s CPU 0.64s WALL ( 1932 calls) + cgsolve : 27.91s CPU 30.56s WALL ( 1932 calls) + incdrhoscf : 2.36s CPU 2.62s WALL ( 1932 calls) + addusddens : 2.85s CPU 2.87s WALL ( 187 calls) + vpsifft : 1.98s CPU 2.18s WALL ( 1752 calls) + dv_of_drho : 0.07s CPU 0.07s WALL ( 219 calls) + mix_pot : 0.09s CPU 0.10s WALL ( 170 calls) + ef_shift : 0.00s CPU 0.00s WALL ( 7 calls) + localdos : 0.01s CPU 0.01s WALL ( 1 calls) + psymdvscf : 1.31s CPU 1.32s WALL ( 170 calls) + newdq : 3.22s CPU 3.29s WALL ( 170 calls) + adddvscf : 0.28s CPU 0.31s WALL ( 1752 calls) + drhodvus : 0.00s CPU 0.00s WALL ( 17 calls) + + dvqpsi_us : 0.73s CPU 0.80s WALL ( 180 calls) + dvqpsi_us_on : 0.40s CPU 0.43s WALL ( 180 calls) + + cgsolve : 27.91s CPU 30.56s WALL ( 1932 calls) + ch_psi : 27.25s CPU 29.84s WALL ( 24636 calls) + + ch_psi : 27.25s CPU 29.84s WALL ( 24636 calls) + h_psi : 26.17s CPU 28.57s WALL ( 26641 calls) + last : 2.55s CPU 2.79s WALL ( 24636 calls) + + h_psi : 26.17s CPU 28.57s WALL ( 26641 calls) + add_vuspsi : 0.93s CPU 1.02s WALL ( 26641 calls) + + incdrhoscf : 2.36s CPU 2.62s WALL ( 1932 calls) + + drhodvus : 0.00s CPU 0.00s WALL ( 17 calls) + General routines - calbec : 0.16s CPU 0.18s WALL ( 1148 calls) - fft : 0.07s CPU 0.13s WALL ( 215 calls) - ffts : 0.00s CPU 0.00s WALL ( 100 calls) - fftw : 0.37s CPU 0.45s WALL ( 20636 calls) - davcio : 0.01s CPU 0.01s WALL ( 204 calls) - write_rec : 0.01s CPU 0.01s WALL ( 7 calls) + calbec : 2.59s CPU 2.82s WALL ( 56875 calls) + fft : 1.33s CPU 1.34s WALL ( 2082 calls) + ffts : 0.04s CPU 0.05s WALL ( 822 calls) + fftw : 24.50s CPU 26.82s WALL ( 1084512 calls) + davcio : 0.19s CPU 0.31s WALL ( 11424 calls) + write_rec : 0.19s CPU 0.26s WALL ( 187 calls) + + + PHONON : 51.22s CPU 55.15s WALL - - PHONON : 3.25s CPU 3.77s WALL - - - This run was terminated on: 13:12: 3 7Dec2016 + + This run was terminated on: 21:12:43 19Mar2020 =------------------------------------------------------------------------------= JOB DONE. diff --git a/PHonon/examples/example06/run_example b/PHonon/examples/example06/run_example index 7270b2c7b..8be3f3672 100755 --- a/PHonon/examples/example06/run_example +++ b/PHonon/examples/example06/run_example @@ -157,5 +157,22 @@ $PH_COMMAND < pt.phX.in > pt.phX.out check_failure $? $ECHO " done" +cat > pt.ph.in << EOF +phonon dispersions of Pt + &inputph + amass(1)=195.078, + prefix='platinum', + outdir='$TMP_DIR' + fildyn='ptdyn', + tr2_ph=1.0d-16, + ldisp=.true., nq1=4,nq2=4,nq3=4 + / +EOF +$ECHO " running the phonon dispersions calculation for Pt with spin-orbit coupling...\c" +$PH_COMMAND < pt.ph.in > pt.ph.out +check_failure $? +$ECHO " done" + $ECHO $ECHO "$EXAMPLE_DIR: done" + diff --git a/PHonon/examples/example10/README b/PHonon/examples/example10/README index e99093d91..c15b98f4f 100644 --- a/PHonon/examples/example10/README +++ b/PHonon/examples/example10/README @@ -29,6 +29,6 @@ The calculation proceeds as follows: insulator with noncollinear magnetization. (input=o2_nc.scf.in, output=o2_nc.scf.out) -8) make a self-consistent calculation for the O2 molecule treated as an - insulator with noncollinear magnetization. +8) make a phonon calculatio at the Gamma point for the O2 molecule + treated as an insulator with noncollinear magnetization. (input=o2_nc.phG.in, output=o2_nc.phG.out) diff --git a/PHonon/examples/example13/reference/ni.ph.out b/PHonon/examples/example13/reference/ni.ph.out new file mode 100644 index 000000000..c0ebe447c --- /dev/null +++ b/PHonon/examples/example13/reference/ni.ph.out @@ -0,0 +1,3089 @@ + + Program PHONON v.6.5 starts on 19Mar2020 at 9:46:11 + + This program is part of the open-source Quantum ESPRESSO suite + for quantum simulation of materials; please cite + "P. Giannozzi et al., J. Phys.:Condens. Matter 21 395502 (2009); + "P. Giannozzi et al., J. Phys.:Condens. Matter 29 465901 (2017); + URL http://www.quantum-espresso.org", + in publications or presentations arising from this work. More details at + http://www.quantum-espresso.org/quote + + Parallel version (MPI & OpenMP), running on 4 processor cores + Number of MPI processes: 4 + Threads/MPI process: 1 + + MPI processes distributed on 1 nodes + R & G space division: proc/nbgrp/npool/nimage = 4 + + Reading xml data from directory: + + /home/giannozz/q-e-mio/tempdir/nickel.save/ + Message from routine qexsd_readschema : + input info not found or not readable in xml file + + IMPORTANT: XC functional enforced from input : + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + Any further DFT definition will be discarded + Please, verify this is what you really want + + file Ni.pbe-nd-rrkjus.UPF: wavefunction(s) 4S renormalized + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 112 40 15 1604 351 82 + Max 113 41 16 1607 354 83 + Sum 451 163 61 6423 1411 331 + + Generating pointlists ... + new r_m : 0.2917 (alat units) 1.9397 (a.u.) for type 1 + + Check: negative core charge= -0.000021 + Reading collected, re-writing distributed wavefunctions + + + Dynamical matrices for ( 4, 4, 4) uniform grid of q-points + ( 8 q-points): + N xq(1) xq(2) xq(3) + 1 0.000000000 0.000000000 0.000000000 + 2 -0.250000000 0.250000000 -0.250000000 + 3 0.500000000 -0.500000000 0.500000000 + 4 0.000000000 0.500000000 0.000000000 + 5 0.750000000 -0.250000000 0.750000000 + 6 0.500000000 0.000000000 0.500000000 + 7 0.000000000 -1.000000000 0.000000000 + 8 -0.500000000 -1.000000000 0.000000000 + + Calculation of q = 0.0000000 0.0000000 0.0000000 + + phonons of Ni + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 27.0000 Ry + charge density cut-off = 300.0000 Ry + convergence threshold = 1.0E-14 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + + celldm(1)= 6.65000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Ni 58.6934 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.0000000 0.0000000 0.0000000 ) + + 49 Sym.Ops. (with q -> -q+G ) + + + G cutoff = 336.0507 ( 1607 G-vectors) FFT grid: ( 25, 25, 25) + G cutoff = 120.9783 ( 354 G-vectors) smooth grid: ( 15, 15, 15) + + number of k points= 20 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, O_h (m-3m) point group: + + + Atomic displacements: + There are 1 irreducible representations + + Representation 1 3 modes -T_1u G_15 G_4- To be done + + + + Alpha used in Ewald sum = 2.8000 + PHONON : 0.50s CPU 0.53s WALL + + + + Representation # 1 modes # 1 2 3 + + Self-consistent Calculation + + Pert. # 1: Fermi energy shift (Ry) = -7.7548E-26 -2.6645E-37 + Pert. # 2: Fermi energy shift (Ry) = -3.4466E-26 2.5077E-37 + Pert. # 3: Fermi energy shift (Ry) = -1.8095E-25 -2.5077E-37 + + iter # 1 total cpu time : 0.8 secs av.it.: 3.9 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 2.545E-06 + + Pert. # 1: Fermi energy shift (Ry) = -3.1019E-25 -1.4204E-38 + Pert. # 2: Fermi energy shift (Ry) = 0.0000E+00 -1.9592E-39 + Pert. # 3: Fermi energy shift (Ry) = -1.2063E-25 6.3673E-39 + + iter # 2 total cpu time : 1.1 secs av.it.: 7.8 + thresh= 1.595E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.111E-08 + + Pert. # 1: Fermi energy shift (Ry) = -1.2063E-25 2.2194E-40 + Pert. # 2: Fermi energy shift (Ry) = -8.6165E-26 3.0612E-41 + Pert. # 3: Fermi energy shift (Ry) = 2.2403E-25 -9.9488E-41 + + iter # 3 total cpu time : 1.4 secs av.it.: 6.9 + thresh= 1.054E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.035E-09 + + Pert. # 1: Fermi energy shift (Ry) = -1.7233E-26 -3.6734E-40 + Pert. # 2: Fermi energy shift (Ry) = -1.7233E-26 3.0229E-40 + Pert. # 3: Fermi energy shift (Ry) = 3.2743E-25 5.7397E-41 + + iter # 4 total cpu time : 1.7 secs av.it.: 6.8 + thresh= 3.216E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.632E-12 + + Pert. # 1: Fermi energy shift (Ry) = -1.7233E-25 4.2091E-41 + Pert. # 2: Fermi energy shift (Ry) = 0.0000E+00 -6.1224E-41 + Pert. # 3: Fermi energy shift (Ry) = -1.7233E-26 0.0000E+00 + + iter # 5 total cpu time : 2.0 secs av.it.: 7.4 + thresh= 1.278E-07 alpha_mix = 0.700 |ddv_scf|^2 = 2.131E-14 + + Pert. # 1: Fermi energy shift (Ry) = 9.4781E-26 4.2091E-41 + Pert. # 2: Fermi energy shift (Ry) = -8.6165E-26 -6.1224E-41 + Pert. # 3: Fermi energy shift (Ry) = 4.3082E-26 0.0000E+00 + + iter # 6 total cpu time : 2.3 secs av.it.: 7.6 + thresh= 1.460E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.239E-15 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 1 + List of q in the star: + 1 0.000000000 0.000000000 0.000000000 + + Diagonalizing the dynamical matrix + + q = ( 0.000000000 0.000000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 0.939837 [THz] = 31.349593 [cm-1] + freq ( 2) = 0.939837 [THz] = 31.349593 [cm-1] + freq ( 3) = 0.939837 [THz] = 31.349593 [cm-1] + ************************************************************************** + + Mode symmetry, O_h (m-3m) point group: + + freq ( 1 - 3) = 31.3 [cm-1] --> T_1u G_15 G_4- I + + Calculation of q = -0.2500000 0.2500000 -0.2500000 + + Subspace diagonalization in iterative solution of the eigenvalue problem: + a serial algorithm will be used + + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 112 40 15 1604 351 84 + Max 113 41 16 1607 354 87 + Sum 451 163 61 6423 1411 339 + + + Title: + phonons of Ni + + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 9 + kinetic-energy cutoff = 27.0000 Ry + charge density cutoff = 300.0000 Ry + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + celldm(1)= 6.650000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Ni 10.00 58.69340 Ni( 1.00) + + Starting magnetic structure + atomic species magnetization + Ni 0.000 + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Ni tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 120 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 6423 G-vectors FFT dimensions: ( 25, 25, 25) + + Smooth grid: 1411 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 6.85 MB + + Estimated total dynamical RAM > 27.40 MB + Generating pointlists ... + + Check: negative core charge= -0.000021 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/charge-density + + Starting wfcs are 6 atomic + 3 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 14.4 + + total cpu time spent up to now is 2.0 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 14.2874 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/ + + phonons of Ni + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 27.0000 Ry + charge density cut-off = 300.0000 Ry + convergence threshold = 1.0E-14 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + + celldm(1)= 6.65000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Ni 58.6934 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( -0.2500000 0.2500000 -0.2500000 ) + + 6 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 336.0507 ( 1607 G-vectors) FFT grid: ( 25, 25, 25) + G cutoff = 120.9783 ( 354 G-vectors) smooth grid: ( 15, 15, 15) + + number of k points= 240 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, C_3v (3m) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_1 L_1 To be done + + Representation 2 2 modes -E L_3 To be done + + + + Alpha used in Ewald sum = 2.8000 + PHONON : 4.19s CPU 4.63s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 5.0 secs av.it.: 5.6 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.643E-01 + + iter # 2 total cpu time : 5.4 secs av.it.: 8.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.985E+02 + + iter # 3 total cpu time : 5.8 secs av.it.: 8.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.375E-01 + + iter # 4 total cpu time : 6.2 secs av.it.: 6.4 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 6.421E-01 + + iter # 5 total cpu time : 6.5 secs av.it.: 6.0 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.578E-02 + + iter # 6 total cpu time : 6.8 secs av.it.: 4.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.113E-04 + + iter # 7 total cpu time : 7.1 secs av.it.: 4.2 + thresh= 1.055E-03 alpha_mix = 0.700 |ddv_scf|^2 = 5.219E-05 + + iter # 8 total cpu time : 7.4 secs av.it.: 3.8 + thresh= 7.225E-04 alpha_mix = 0.700 |ddv_scf|^2 = 6.883E-08 + + iter # 9 total cpu time : 7.7 secs av.it.: 4.9 + thresh= 2.623E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.578E-10 + + iter # 10 total cpu time : 8.0 secs av.it.: 5.8 + thresh= 1.606E-06 alpha_mix = 0.700 |ddv_scf|^2 = 4.847E-10 + + iter # 11 total cpu time : 8.3 secs av.it.: 5.0 + thresh= 2.202E-06 alpha_mix = 0.700 |ddv_scf|^2 = 4.210E-10 + + iter # 12 total cpu time : 8.6 secs av.it.: 4.0 + thresh= 2.052E-06 alpha_mix = 0.700 |ddv_scf|^2 = 6.373E-11 + + iter # 13 total cpu time : 8.9 secs av.it.: 4.7 + thresh= 7.983E-07 alpha_mix = 0.700 |ddv_scf|^2 = 3.323E-11 + + iter # 14 total cpu time : 9.1 secs av.it.: 4.4 + thresh= 5.765E-07 alpha_mix = 0.700 |ddv_scf|^2 = 3.540E-14 + + iter # 15 total cpu time : 9.5 secs av.it.: 6.2 + thresh= 1.881E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.680E-14 + + iter # 16 total cpu time : 9.8 secs av.it.: 6.0 + thresh= 1.296E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.954E-14 + + iter # 17 total cpu time : 10.1 secs av.it.: 4.0 + thresh= 1.398E-08 alpha_mix = 0.700 |ddv_scf|^2 = 6.509E-16 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 10.7 secs av.it.: 4.1 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 6.528E-06 + + iter # 2 total cpu time : 11.5 secs av.it.: 7.3 + thresh= 2.555E-04 alpha_mix = 0.700 |ddv_scf|^2 = 3.474E-08 + + iter # 3 total cpu time : 12.2 secs av.it.: 7.2 + thresh= 1.864E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.428E-09 + + iter # 4 total cpu time : 13.0 secs av.it.: 7.3 + thresh= 4.928E-06 alpha_mix = 0.700 |ddv_scf|^2 = 4.703E-11 + + iter # 5 total cpu time : 13.8 secs av.it.: 7.8 + thresh= 6.858E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.486E-12 + + iter # 6 total cpu time : 14.6 secs av.it.: 7.8 + thresh= 1.219E-07 alpha_mix = 0.700 |ddv_scf|^2 = 5.024E-14 + + iter # 7 total cpu time : 15.4 secs av.it.: 7.9 + thresh= 2.241E-08 alpha_mix = 0.700 |ddv_scf|^2 = 7.397E-15 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 8 + List of q in the star: + 1 -0.250000000 0.250000000 -0.250000000 + 2 0.250000000 -0.250000000 -0.250000000 + 3 0.250000000 -0.250000000 0.250000000 + 4 0.250000000 0.250000000 0.250000000 + 5 -0.250000000 -0.250000000 -0.250000000 + 6 -0.250000000 -0.250000000 0.250000000 + 7 -0.250000000 0.250000000 0.250000000 + 8 0.250000000 0.250000000 -0.250000000 + + Diagonalizing the dynamical matrix + + q = ( -0.250000000 0.250000000 -0.250000000 ) + + ************************************************************************** + freq ( 1) = 3.289586 [THz] = 109.728781 [cm-1] + freq ( 2) = 3.289586 [THz] = 109.728781 [cm-1] + freq ( 3) = 6.783202 [THz] = 226.263254 [cm-1] + ************************************************************************** + + Mode symmetry, C_3v (3m) point group: + + freq ( 1 - 2) = 109.7 [cm-1] --> E L_3 + freq ( 3 - 3) = 226.3 [cm-1] --> A_1 L_1 + + Calculation of q = 0.5000000 -0.5000000 0.5000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 112 40 20 1604 351 114 + Max 113 41 22 1607 354 115 + Sum 451 163 85 6423 1411 459 + + + Title: + phonons of Ni + + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 9 + kinetic-energy cutoff = 27.0000 Ry + charge density cutoff = 300.0000 Ry + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + celldm(1)= 6.650000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Ni 10.00 58.69340 Ni( 1.00) + + Starting magnetic structure + atomic species magnetization + Ni 0.000 + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Ni tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 60 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.1250000 0.1250000 0.1250000), wk = 0.0234375 + k( 2) = ( 0.3750000 -0.3750000 0.6250000), wk = 0.0000000 + k( 3) = ( -0.3750000 0.3750000 -0.1250000), wk = 0.0234375 + k( 4) = ( 0.1250000 -0.1250000 0.3750000), wk = 0.0000000 + k( 5) = ( 0.3750000 -0.3750000 0.6250000), wk = 0.0234375 + k( 6) = ( 0.8750000 -0.8750000 1.1250000), wk = 0.0000000 + k( 7) = ( 0.1250000 -0.1250000 0.3750000), wk = 0.0234375 + k( 8) = ( 0.6250000 -0.6250000 0.8750000), wk = 0.0000000 + k( 9) = ( -0.1250000 0.6250000 0.1250000), wk = 0.0468750 + k( 10) = ( 0.3750000 0.1250000 0.6250000), wk = 0.0000000 + k( 11) = ( 0.6250000 -0.1250000 0.8750000), wk = 0.0468750 + k( 12) = ( 1.1250000 -0.6250000 1.3750000), wk = 0.0000000 + k( 13) = ( 0.3750000 0.1250000 0.6250000), wk = 0.0468750 + k( 14) = ( 0.8750000 -0.3750000 1.1250000), wk = 0.0000000 + k( 15) = ( -0.1250000 -0.8750000 0.1250000), wk = 0.0468750 + k( 16) = ( 0.3750000 -1.3750000 0.6250000), wk = 0.0000000 + k( 17) = ( -0.3750000 0.3750000 0.3750000), wk = 0.0234375 + k( 18) = ( 0.1250000 -0.1250000 0.8750000), wk = 0.0000000 + k( 19) = ( 0.3750000 -0.3750000 1.1250000), wk = 0.0234375 + k( 20) = ( 0.8750000 -0.8750000 1.6250000), wk = 0.0000000 + k( 21) = ( 0.1250000 -0.1250000 0.1250000), wk = 0.0078125 + k( 22) = ( 0.6250000 -0.6250000 0.6250000), wk = 0.0000000 + k( 23) = ( -0.3750000 -0.3750000 -0.1250000), wk = 0.0468750 + k( 24) = ( 0.1250000 -0.8750000 0.3750000), wk = 0.0000000 + k( 25) = ( -0.1250000 -0.3750000 0.3750000), wk = 0.0234375 + k( 26) = ( 0.3750000 -0.8750000 0.8750000), wk = 0.0000000 + k( 27) = ( 0.3750000 0.3750000 0.6250000), wk = 0.0468750 + k( 28) = ( 0.8750000 -0.1250000 1.1250000), wk = 0.0000000 + k( 29) = ( 0.6250000 0.3750000 -0.3750000), wk = 0.0234375 + k( 30) = ( 1.1250000 -0.1250000 0.1250000), wk = 0.0000000 + k( 31) = ( 0.1250000 0.1250000 0.3750000), wk = 0.0468750 + k( 32) = ( 0.6250000 -0.3750000 0.8750000), wk = 0.0000000 + k( 33) = ( 0.3750000 0.1250000 -0.1250000), wk = 0.0234375 + k( 34) = ( 0.8750000 -0.3750000 0.3750000), wk = 0.0000000 + k( 35) = ( -0.1250000 -0.6250000 -0.1250000), wk = 0.0234375 + k( 36) = ( 0.3750000 -1.1250000 0.3750000), wk = 0.0000000 + k( 37) = ( 0.1250000 -0.6250000 0.1250000), wk = 0.0234375 + k( 38) = ( 0.6250000 -1.1250000 0.6250000), wk = 0.0000000 + k( 39) = ( 0.6250000 0.1250000 0.8750000), wk = 0.0468750 + k( 40) = ( 1.1250000 -0.3750000 1.3750000), wk = 0.0000000 + k( 41) = ( -0.8750000 0.1250000 0.6250000), wk = 0.0468750 + k( 42) = ( -0.3750000 -0.3750000 1.1250000), wk = 0.0000000 + k( 43) = ( 0.8750000 0.1250000 -0.6250000), wk = 0.0468750 + k( 44) = ( 1.3750000 -0.3750000 -0.1250000), wk = 0.0000000 + k( 45) = ( 0.3750000 -0.1250000 0.6250000), wk = 0.0468750 + k( 46) = ( 0.8750000 -0.6250000 1.1250000), wk = 0.0000000 + k( 47) = ( -0.6250000 -0.1250000 0.3750000), wk = 0.0468750 + k( 48) = ( -0.1250000 -0.6250000 0.8750000), wk = 0.0000000 + k( 49) = ( 0.6250000 -0.1250000 -0.3750000), wk = 0.0468750 + k( 50) = ( 1.1250000 -0.6250000 0.1250000), wk = 0.0000000 + k( 51) = ( -0.1250000 0.8750000 -0.1250000), wk = 0.0234375 + k( 52) = ( 0.3750000 0.3750000 0.3750000), wk = 0.0000000 + k( 53) = ( 0.1250000 0.8750000 0.1250000), wk = 0.0234375 + k( 54) = ( 0.6250000 0.3750000 0.6250000), wk = 0.0000000 + k( 55) = ( 0.3750000 -0.3750000 0.3750000), wk = 0.0078125 + k( 56) = ( 0.8750000 -0.8750000 0.8750000), wk = 0.0000000 + k( 57) = ( 0.3750000 0.3750000 1.1250000), wk = 0.0468750 + k( 58) = ( 0.8750000 -0.1250000 1.6250000), wk = 0.0000000 + k( 59) = ( 1.1250000 0.3750000 -0.3750000), wk = 0.0234375 + k( 60) = ( 1.6250000 -0.1250000 0.1250000), wk = 0.0000000 + + Dense grid: 6423 G-vectors FFT dimensions: ( 25, 25, 25) + + Smooth grid: 1411 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 6.88 MB + + Estimated total dynamical RAM > 27.54 MB + Generating pointlists ... + + Check: negative core charge= -0.000021 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/charge-density + + Starting wfcs are 6 atomic + 3 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 14.3 + + total cpu time spent up to now is 3.1 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 14.2874 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/ + + phonons of Ni + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 27.0000 Ry + charge density cut-off = 300.0000 Ry + convergence threshold = 1.0E-14 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + + celldm(1)= 6.65000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Ni 58.6934 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.5000000 -0.5000000 0.5000000 ) + + 13 Sym.Ops. (with q -> -q+G ) + + + G cutoff = 336.0507 ( 1607 G-vectors) FFT grid: ( 25, 25, 25) + G cutoff = 120.9783 ( 353 G-vectors) smooth grid: ( 15, 15, 15) + + number of k points= 120 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, D_3d (-3m) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_2u L_2' To be done + + Representation 2 2 modes -E_u L_3' To be done + + + + Alpha used in Ewald sum = 2.8000 + PHONON : 14.91s CPU 16.74s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 16.9 secs av.it.: 5.0 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.046E-03 + + iter # 2 total cpu time : 17.2 secs av.it.: 6.6 + thresh= 3.234E-03 alpha_mix = 0.700 |ddv_scf|^2 = 1.173E-03 + + iter # 3 total cpu time : 17.4 secs av.it.: 6.0 + thresh= 3.425E-03 alpha_mix = 0.700 |ddv_scf|^2 = 9.551E-08 + + iter # 4 total cpu time : 17.6 secs av.it.: 6.3 + thresh= 3.090E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.337E-09 + + iter # 5 total cpu time : 17.8 secs av.it.: 5.7 + thresh= 3.656E-06 alpha_mix = 0.700 |ddv_scf|^2 = 2.764E-11 + + iter # 6 total cpu time : 18.0 secs av.it.: 6.1 + thresh= 5.258E-07 alpha_mix = 0.700 |ddv_scf|^2 = 9.147E-14 + + iter # 7 total cpu time : 18.2 secs av.it.: 6.3 + thresh= 3.024E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.742E-15 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 18.6 secs av.it.: 4.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 7.299E-06 + + iter # 2 total cpu time : 19.0 secs av.it.: 7.4 + thresh= 2.702E-04 alpha_mix = 0.700 |ddv_scf|^2 = 4.440E-08 + + iter # 3 total cpu time : 19.5 secs av.it.: 7.2 + thresh= 2.107E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.349E-09 + + iter # 4 total cpu time : 19.9 secs av.it.: 6.5 + thresh= 4.847E-06 alpha_mix = 0.700 |ddv_scf|^2 = 3.630E-12 + + iter # 5 total cpu time : 20.3 secs av.it.: 7.3 + thresh= 1.905E-07 alpha_mix = 0.700 |ddv_scf|^2 = 6.672E-14 + + iter # 6 total cpu time : 20.8 secs av.it.: 7.4 + thresh= 2.583E-08 alpha_mix = 0.700 |ddv_scf|^2 = 5.951E-15 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 4 + List of q in the star: + 1 0.500000000 -0.500000000 0.500000000 + 2 0.500000000 0.500000000 0.500000000 + 3 -0.500000000 0.500000000 0.500000000 + 4 0.500000000 0.500000000 -0.500000000 + + Diagonalizing the dynamical matrix + + q = ( 0.500000000 -0.500000000 0.500000000 ) + + ************************************************************************** + freq ( 1) = 4.762448 [THz] = 158.858162 [cm-1] + freq ( 2) = 4.762448 [THz] = 158.858162 [cm-1] + freq ( 3) = 9.096135 [THz] = 303.414413 [cm-1] + ************************************************************************** + + Mode symmetry, D_3d (-3m) point group: + + freq ( 1 - 2) = 158.9 [cm-1] --> E_u L_3' + freq ( 3 - 3) = 303.4 [cm-1] --> A_2u L_2' + + Calculation of q = 0.0000000 0.5000000 0.0000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 112 40 17 1604 351 96 + Max 113 41 19 1607 354 97 + Sum 451 163 73 6423 1411 387 + + + Title: + phonons of Ni + + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 9 + kinetic-energy cutoff = 27.0000 Ry + charge density cutoff = 300.0000 Ry + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + celldm(1)= 6.650000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Ni 10.00 58.69340 Ni( 1.00) + + Starting magnetic structure + atomic species magnetization + Ni 0.000 + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Ni tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 80 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.1250000 0.1250000 0.1250000), wk = 0.0156250 + k( 2) = ( -0.1250000 0.6250000 0.1250000), wk = 0.0000000 + k( 3) = ( -0.3750000 0.3750000 -0.1250000), wk = 0.0312500 + k( 4) = ( -0.3750000 0.8750000 -0.1250000), wk = 0.0000000 + k( 5) = ( 0.3750000 -0.3750000 0.6250000), wk = 0.0312500 + k( 6) = ( 0.3750000 0.1250000 0.6250000), wk = 0.0000000 + k( 7) = ( 0.1250000 -0.1250000 0.3750000), wk = 0.0312500 + k( 8) = ( 0.1250000 0.3750000 0.3750000), wk = 0.0000000 + k( 9) = ( -0.1250000 0.6250000 0.1250000), wk = 0.0156250 + k( 10) = ( -0.1250000 1.1250000 0.1250000), wk = 0.0000000 + k( 11) = ( 0.6250000 -0.1250000 0.8750000), wk = 0.0312500 + k( 12) = ( 0.6250000 0.3750000 0.8750000), wk = 0.0000000 + k( 13) = ( 0.3750000 0.1250000 0.6250000), wk = 0.0312500 + k( 14) = ( 0.3750000 0.6250000 0.6250000), wk = 0.0000000 + k( 15) = ( -0.1250000 -0.8750000 0.1250000), wk = 0.0156250 + k( 16) = ( -0.1250000 -0.3750000 0.1250000), wk = 0.0000000 + k( 17) = ( -0.3750000 0.3750000 0.3750000), wk = 0.0156250 + k( 18) = ( -0.3750000 0.8750000 0.3750000), wk = 0.0000000 + k( 19) = ( 0.3750000 -0.3750000 1.1250000), wk = 0.0312500 + k( 20) = ( 0.3750000 0.1250000 1.1250000), wk = 0.0000000 + k( 21) = ( -0.1250000 -0.1250000 0.1250000), wk = 0.0156250 + k( 22) = ( -0.1250000 0.3750000 0.1250000), wk = 0.0000000 + k( 23) = ( 0.1250000 -0.3750000 0.3750000), wk = 0.0312500 + k( 24) = ( 0.1250000 0.1250000 0.3750000), wk = 0.0000000 + k( 25) = ( 0.3750000 -0.1250000 0.3750000), wk = 0.0156250 + k( 26) = ( 0.3750000 0.3750000 0.3750000), wk = 0.0000000 + k( 27) = ( 0.3750000 0.1250000 0.3750000), wk = 0.0156250 + k( 28) = ( 0.3750000 0.6250000 0.3750000), wk = 0.0000000 + k( 29) = ( -0.6250000 0.3750000 -0.3750000), wk = 0.0312500 + k( 30) = ( -0.6250000 0.8750000 -0.3750000), wk = 0.0000000 + k( 31) = ( -0.3750000 0.6250000 -0.3750000), wk = 0.0156250 + k( 32) = ( -0.3750000 1.1250000 -0.3750000), wk = 0.0000000 + k( 33) = ( -0.3750000 -0.6250000 -0.3750000), wk = 0.0156250 + k( 34) = ( -0.3750000 -0.1250000 -0.3750000), wk = 0.0000000 + k( 35) = ( -0.3750000 0.1250000 -0.1250000), wk = 0.0312500 + k( 36) = ( -0.3750000 0.6250000 -0.1250000), wk = 0.0000000 + k( 37) = ( -0.1250000 0.3750000 -0.1250000), wk = 0.0156250 + k( 38) = ( -0.1250000 0.8750000 -0.1250000), wk = 0.0000000 + k( 39) = ( -0.1250000 -0.3750000 -0.1250000), wk = 0.0156250 + k( 40) = ( -0.1250000 0.1250000 -0.1250000), wk = 0.0000000 + k( 41) = ( -0.1250000 -0.6250000 0.1250000), wk = 0.0156250 + k( 42) = ( -0.1250000 -0.1250000 0.1250000), wk = 0.0000000 + k( 43) = ( 0.6250000 -0.1250000 -0.1250000), wk = 0.0312500 + k( 44) = ( 0.6250000 0.3750000 -0.1250000), wk = 0.0000000 + k( 45) = ( 0.6250000 0.1250000 0.1250000), wk = 0.0312500 + k( 46) = ( 0.6250000 0.6250000 0.1250000), wk = 0.0000000 + k( 47) = ( -0.8750000 0.1250000 -0.6250000), wk = 0.0312500 + k( 48) = ( -0.8750000 0.6250000 -0.6250000), wk = 0.0000000 + k( 49) = ( -0.1250000 0.6250000 -0.8750000), wk = 0.0312500 + k( 50) = ( -0.1250000 1.1250000 -0.8750000), wk = 0.0000000 + k( 51) = ( -0.1250000 0.8750000 -0.6250000), wk = 0.0312500 + k( 52) = ( -0.1250000 1.3750000 -0.6250000), wk = 0.0000000 + k( 53) = ( -0.1250000 -0.8750000 -0.6250000), wk = 0.0312500 + k( 54) = ( -0.1250000 -0.3750000 -0.6250000), wk = 0.0000000 + k( 55) = ( 0.8750000 -0.6250000 0.1250000), wk = 0.0312500 + k( 56) = ( 0.8750000 -0.1250000 0.1250000), wk = 0.0000000 + k( 57) = ( -0.6250000 -0.1250000 -0.3750000), wk = 0.0312500 + k( 58) = ( -0.6250000 0.3750000 -0.3750000), wk = 0.0000000 + k( 59) = ( 0.1250000 0.3750000 -0.6250000), wk = 0.0312500 + k( 60) = ( 0.1250000 0.8750000 -0.6250000), wk = 0.0000000 + k( 61) = ( 0.1250000 0.6250000 -0.3750000), wk = 0.0312500 + k( 62) = ( 0.1250000 1.1250000 -0.3750000), wk = 0.0000000 + k( 63) = ( 0.1250000 -0.6250000 -0.3750000), wk = 0.0312500 + k( 64) = ( 0.1250000 -0.1250000 -0.3750000), wk = 0.0000000 + k( 65) = ( 0.6250000 -0.3750000 -0.1250000), wk = 0.0312500 + k( 66) = ( 0.6250000 0.1250000 -0.1250000), wk = 0.0000000 + k( 67) = ( -0.1250000 0.8750000 0.1250000), wk = 0.0156250 + k( 68) = ( -0.1250000 1.3750000 0.1250000), wk = 0.0000000 + k( 69) = ( -0.8750000 -0.1250000 -0.1250000), wk = 0.0312500 + k( 70) = ( -0.8750000 0.3750000 -0.1250000), wk = 0.0000000 + k( 71) = ( -0.8750000 0.1250000 0.1250000), wk = 0.0312500 + k( 72) = ( -0.8750000 0.6250000 0.1250000), wk = 0.0000000 + k( 73) = ( -0.3750000 -0.3750000 0.3750000), wk = 0.0156250 + k( 74) = ( -0.3750000 0.1250000 0.3750000), wk = 0.0000000 + k( 75) = ( -1.1250000 0.3750000 -0.3750000), wk = 0.0312500 + k( 76) = ( -1.1250000 0.8750000 -0.3750000), wk = 0.0000000 + k( 77) = ( -0.3750000 1.1250000 -0.3750000), wk = 0.0156250 + k( 78) = ( -0.3750000 1.6250000 -0.3750000), wk = 0.0000000 + k( 79) = ( -0.3750000 -1.1250000 -0.3750000), wk = 0.0156250 + k( 80) = ( -0.3750000 -0.6250000 -0.3750000), wk = 0.0000000 + + Dense grid: 6423 G-vectors FFT dimensions: ( 25, 25, 25) + + Smooth grid: 1411 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 6.86 MB + + Estimated total dynamical RAM > 27.42 MB + Generating pointlists ... + + Check: negative core charge= -0.000021 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/charge-density + + Starting wfcs are 6 atomic + 3 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 14.2 + + total cpu time spent up to now is 4.4 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 14.2874 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/ + + phonons of Ni + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 27.0000 Ry + charge density cut-off = 300.0000 Ry + convergence threshold = 1.0E-14 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + + celldm(1)= 6.65000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Ni 58.6934 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.0000000 0.5000000 0.0000000 ) + + 8 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 336.0507 ( 1607 G-vectors) FFT grid: ( 25, 25, 25) + G cutoff = 120.9783 ( 353 G-vectors) smooth grid: ( 15, 15, 15) + + number of k points= 160 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, C_4v (4mm) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_1 G_1 D_1 To be done + + Representation 2 2 modes -E G_5 D_5 To be done + + + + Alpha used in Ewald sum = 2.8000 + PHONON : 19.95s CPU 22.39s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 22.7 secs av.it.: 5.7 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.675E-01 + + iter # 2 total cpu time : 23.0 secs av.it.: 8.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.042E+02 + + iter # 3 total cpu time : 23.3 secs av.it.: 8.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 2.075E-01 + + iter # 4 total cpu time : 23.5 secs av.it.: 6.6 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 2.941E-01 + + iter # 5 total cpu time : 23.8 secs av.it.: 6.1 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 2.038E-03 + + iter # 6 total cpu time : 24.0 secs av.it.: 4.6 + thresh= 4.514E-03 alpha_mix = 0.700 |ddv_scf|^2 = 4.347E-06 + + iter # 7 total cpu time : 24.2 secs av.it.: 4.9 + thresh= 2.085E-04 alpha_mix = 0.700 |ddv_scf|^2 = 2.032E-06 + + iter # 8 total cpu time : 24.4 secs av.it.: 4.3 + thresh= 1.425E-04 alpha_mix = 0.700 |ddv_scf|^2 = 5.394E-09 + + iter # 9 total cpu time : 24.6 secs av.it.: 5.4 + thresh= 7.344E-06 alpha_mix = 0.700 |ddv_scf|^2 = 4.535E-10 + + iter # 10 total cpu time : 24.9 secs av.it.: 5.5 + thresh= 2.130E-06 alpha_mix = 0.700 |ddv_scf|^2 = 3.511E-10 + + iter # 11 total cpu time : 25.1 secs av.it.: 4.6 + thresh= 1.874E-06 alpha_mix = 0.700 |ddv_scf|^2 = 7.217E-11 + + iter # 12 total cpu time : 25.3 secs av.it.: 4.7 + thresh= 8.495E-07 alpha_mix = 0.700 |ddv_scf|^2 = 4.225E-11 + + iter # 13 total cpu time : 25.5 secs av.it.: 4.7 + thresh= 6.500E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.322E-13 + + iter # 14 total cpu time : 25.7 secs av.it.: 5.7 + thresh= 3.636E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.381E-13 + + iter # 15 total cpu time : 25.9 secs av.it.: 4.6 + thresh= 3.716E-08 alpha_mix = 0.700 |ddv_scf|^2 = 4.161E-14 + + iter # 16 total cpu time : 26.1 secs av.it.: 4.9 + thresh= 2.040E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.833E-16 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 26.6 secs av.it.: 4.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 9.403E-06 + + iter # 2 total cpu time : 27.2 secs av.it.: 7.7 + thresh= 3.066E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.494E-07 + + iter # 3 total cpu time : 27.7 secs av.it.: 7.8 + thresh= 3.865E-05 alpha_mix = 0.700 |ddv_scf|^2 = 3.012E-09 + + iter # 4 total cpu time : 28.3 secs av.it.: 7.9 + thresh= 5.488E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.352E-10 + + iter # 5 total cpu time : 28.9 secs av.it.: 8.1 + thresh= 1.163E-06 alpha_mix = 0.700 |ddv_scf|^2 = 2.365E-12 + + iter # 6 total cpu time : 29.5 secs av.it.: 8.2 + thresh= 1.538E-07 alpha_mix = 0.700 |ddv_scf|^2 = 9.283E-14 + + iter # 7 total cpu time : 30.1 secs av.it.: 8.1 + thresh= 3.047E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.483E-14 + + iter # 8 total cpu time : 30.7 secs av.it.: 8.5 + thresh= 1.218E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.154E-16 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 6 + List of q in the star: + 1 0.000000000 0.500000000 0.000000000 + 2 0.000000000 -0.500000000 0.000000000 + 3 0.500000000 0.000000000 0.000000000 + 4 0.000000000 0.000000000 0.500000000 + 5 0.000000000 0.000000000 -0.500000000 + 6 -0.500000000 0.000000000 0.000000000 + + Diagonalizing the dynamical matrix + + q = ( 0.000000000 0.500000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 4.718207 [THz] = 157.382454 [cm-1] + freq ( 2) = 4.718207 [THz] = 157.382454 [cm-1] + freq ( 3) = 6.916715 [THz] = 230.716772 [cm-1] + ************************************************************************** + + Mode symmetry, C_4v (4mm) point group: + + freq ( 1 - 2) = 157.4 [cm-1] --> E G_5 D_5 + freq ( 3 - 3) = 230.7 [cm-1] --> A_1 G_1 D_1 + + Calculation of q = 0.7500000 -0.2500000 0.7500000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 112 40 21 1604 351 132 + Max 113 41 22 1607 354 135 + Sum 451 163 85 6423 1411 531 + + + Title: + phonons of Ni + + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 9 + kinetic-energy cutoff = 27.0000 Ry + charge density cutoff = 300.0000 Ry + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + celldm(1)= 6.650000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Ni 10.00 58.69340 Ni( 1.00) + + Starting magnetic structure + atomic species magnetization + Ni 0.000 + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Ni tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 288 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 6423 G-vectors FFT dimensions: ( 25, 25, 25) + + Smooth grid: 1411 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 6.90 MB + + Estimated total dynamical RAM > 27.61 MB + Generating pointlists ... + + Check: negative core charge= -0.000021 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/charge-density + + Starting wfcs are 6 atomic + 3 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 13.9 + + total cpu time spent up to now is 9.2 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 14.2874 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/ + + phonons of Ni + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 27.0000 Ry + charge density cut-off = 300.0000 Ry + convergence threshold = 1.0E-14 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + + celldm(1)= 6.65000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Ni 58.6934 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.7500000 -0.2500000 0.7500000 ) + + 2 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 336.0507 ( 1607 G-vectors) FFT grid: ( 25, 25, 25) + G cutoff = 120.9783 ( 354 G-vectors) smooth grid: ( 15, 15, 15) + + number of k points= 576 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, C_s (m) point group: + + + Atomic displacements: + There are 3 irreducible representations + + Representation 1 1 modes -A' To be done + + Representation 2 1 modes -A' To be done + + Representation 3 1 modes -A'' To be done + + + + Alpha used in Ewald sum = 2.8000 + PHONON : 32.36s CPU 36.08s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 37.0 secs av.it.: 5.2 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.750E-03 + + iter # 2 total cpu time : 38.0 secs av.it.: 7.6 + thresh= 4.183E-03 alpha_mix = 0.700 |ddv_scf|^2 = 1.436E-01 + + iter # 3 total cpu time : 38.9 secs av.it.: 7.0 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.000E-02 + + iter # 4 total cpu time : 39.8 secs av.it.: 5.9 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 8.505E-05 + + iter # 5 total cpu time : 40.6 secs av.it.: 5.8 + thresh= 9.222E-04 alpha_mix = 0.700 |ddv_scf|^2 = 7.423E-07 + + iter # 6 total cpu time : 41.4 secs av.it.: 6.0 + thresh= 8.616E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.668E-08 + + iter # 7 total cpu time : 42.3 secs av.it.: 6.6 + thresh= 1.291E-05 alpha_mix = 0.700 |ddv_scf|^2 = 6.577E-08 + + iter # 8 total cpu time : 43.2 secs av.it.: 5.7 + thresh= 2.565E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.775E-09 + + iter # 9 total cpu time : 44.0 secs av.it.: 5.9 + thresh= 5.267E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.086E-12 + + iter # 10 total cpu time : 45.0 secs av.it.: 7.3 + thresh= 1.042E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.173E-12 + + iter # 11 total cpu time : 45.9 secs av.it.: 6.6 + thresh= 1.083E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.921E-13 + + iter # 12 total cpu time : 46.8 secs av.it.: 6.9 + thresh= 4.382E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.522E-14 + + iter # 13 total cpu time : 47.8 secs av.it.: 7.4 + thresh= 1.234E-08 alpha_mix = 0.700 |ddv_scf|^2 = 6.227E-13 + + iter # 14 total cpu time : 48.7 secs av.it.: 5.8 + thresh= 7.891E-08 alpha_mix = 0.700 |ddv_scf|^2 = 7.049E-15 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 mode # 2 + + Self-consistent Calculation + + iter # 1 total cpu time : 49.5 secs av.it.: 4.7 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 6.089E-04 + + iter # 2 total cpu time : 50.5 secs av.it.: 7.7 + thresh= 2.468E-03 alpha_mix = 0.700 |ddv_scf|^2 = 6.417E-02 + + iter # 3 total cpu time : 51.4 secs av.it.: 6.6 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.877E-03 + + iter # 4 total cpu time : 52.3 secs av.it.: 5.9 + thresh= 4.332E-03 alpha_mix = 0.700 |ddv_scf|^2 = 9.011E-05 + + iter # 5 total cpu time : 53.1 secs av.it.: 5.7 + thresh= 9.492E-04 alpha_mix = 0.700 |ddv_scf|^2 = 4.034E-07 + + iter # 6 total cpu time : 53.9 secs av.it.: 6.1 + thresh= 6.352E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.342E-09 + + iter # 7 total cpu time : 54.9 secs av.it.: 7.5 + thresh= 4.840E-06 alpha_mix = 0.700 |ddv_scf|^2 = 6.337E-08 + + iter # 8 total cpu time : 55.7 secs av.it.: 5.7 + thresh= 2.517E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.187E-09 + + iter # 9 total cpu time : 56.6 secs av.it.: 6.1 + thresh= 4.677E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.502E-11 + + iter # 10 total cpu time : 57.6 secs av.it.: 7.1 + thresh= 3.876E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.655E-11 + + iter # 11 total cpu time : 58.4 secs av.it.: 6.1 + thresh= 4.068E-07 alpha_mix = 0.700 |ddv_scf|^2 = 2.883E-13 + + iter # 12 total cpu time : 59.4 secs av.it.: 7.3 + thresh= 5.369E-08 alpha_mix = 0.700 |ddv_scf|^2 = 4.286E-13 + + iter # 13 total cpu time : 60.3 secs av.it.: 6.5 + thresh= 6.547E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.247E-13 + + iter # 14 total cpu time : 61.2 secs av.it.: 7.0 + thresh= 3.532E-08 alpha_mix = 0.700 |ddv_scf|^2 = 5.947E-13 + + iter # 15 total cpu time : 62.0 secs av.it.: 5.8 + thresh= 7.711E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.002E-14 + + iter # 16 total cpu time : 63.0 secs av.it.: 6.7 + thresh= 1.001E-08 alpha_mix = 0.700 |ddv_scf|^2 = 6.475E-15 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 3 mode # 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 63.8 secs av.it.: 4.4 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.210E-05 + + iter # 2 total cpu time : 64.8 secs av.it.: 6.9 + thresh= 6.489E-04 alpha_mix = 0.700 |ddv_scf|^2 = 8.418E-07 + + iter # 3 total cpu time : 65.7 secs av.it.: 7.0 + thresh= 9.175E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.138E-08 + + iter # 4 total cpu time : 66.6 secs av.it.: 6.9 + thresh= 1.067E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.285E-10 + + iter # 5 total cpu time : 67.6 secs av.it.: 7.4 + thresh= 1.512E-06 alpha_mix = 0.700 |ddv_scf|^2 = 6.926E-12 + + iter # 6 total cpu time : 68.6 secs av.it.: 7.3 + thresh= 2.632E-07 alpha_mix = 0.700 |ddv_scf|^2 = 2.211E-13 + + iter # 7 total cpu time : 69.5 secs av.it.: 7.4 + thresh= 4.703E-08 alpha_mix = 0.700 |ddv_scf|^2 = 3.685E-14 + + iter # 8 total cpu time : 70.6 secs av.it.: 7.7 + thresh= 1.920E-08 alpha_mix = 0.700 |ddv_scf|^2 = 6.265E-16 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 24 + List of q in the star: + 1 0.750000000 -0.250000000 0.750000000 + 2 0.750000000 -0.250000000 -0.750000000 + 3 -0.750000000 -0.250000000 -0.750000000 + 4 -0.750000000 -0.250000000 0.750000000 + 5 -0.750000000 0.250000000 -0.750000000 + 6 -0.250000000 0.750000000 -0.750000000 + 7 -0.750000000 0.750000000 -0.250000000 + 8 0.750000000 0.250000000 0.750000000 + 9 -0.750000000 0.250000000 0.750000000 + 10 0.750000000 0.250000000 -0.750000000 + 11 -0.750000000 0.750000000 0.250000000 + 12 -0.250000000 0.750000000 0.750000000 + 13 0.250000000 0.750000000 -0.750000000 + 14 -0.250000000 -0.750000000 -0.750000000 + 15 0.750000000 0.750000000 -0.250000000 + 16 0.750000000 -0.750000000 0.250000000 + 17 -0.750000000 -0.750000000 -0.250000000 + 18 0.250000000 -0.750000000 0.750000000 + 19 -0.750000000 -0.750000000 0.250000000 + 20 0.250000000 0.750000000 0.750000000 + 21 -0.250000000 -0.750000000 0.750000000 + 22 0.750000000 0.750000000 0.250000000 + 23 0.250000000 -0.750000000 -0.750000000 + 24 0.750000000 -0.750000000 -0.250000000 + + Diagonalizing the dynamical matrix + + q = ( 0.750000000 -0.250000000 0.750000000 ) + + ************************************************************************** + freq ( 1) = 5.947125 [THz] = 198.374737 [cm-1] + freq ( 2) = 6.614021 [THz] = 220.619992 [cm-1] + freq ( 3) = 8.586984 [THz] = 286.430952 [cm-1] + ************************************************************************** + + Mode symmetry, C_s (m) point group: + + freq ( 1 - 1) = 198.4 [cm-1] --> A'' + freq ( 2 - 2) = 220.6 [cm-1] --> A' + freq ( 3 - 3) = 286.4 [cm-1] --> A' + + Calculation of q = 0.5000000 0.0000000 0.5000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 112 40 18 1604 351 102 + Max 113 41 19 1607 354 104 + Sum 451 163 73 6423 1411 411 + + + Title: + phonons of Ni + + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 9 + kinetic-energy cutoff = 27.0000 Ry + charge density cutoff = 300.0000 Ry + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + celldm(1)= 6.650000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Ni 10.00 58.69340 Ni( 1.00) + + Starting magnetic structure + atomic species magnetization + Ni 0.000 + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Ni tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 144 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 6423 G-vectors FFT dimensions: ( 25, 25, 25) + + Smooth grid: 1411 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 6.87 MB + + Estimated total dynamical RAM > 27.49 MB + Generating pointlists ... + + Check: negative core charge= -0.000021 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/charge-density + + Starting wfcs are 6 atomic + 3 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 14.0 + + total cpu time spent up to now is 11.7 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 14.2874 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/ + + phonons of Ni + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 27.0000 Ry + charge density cut-off = 300.0000 Ry + convergence threshold = 1.0E-14 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + + celldm(1)= 6.65000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Ni 58.6934 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.5000000 0.0000000 0.5000000 ) + + 4 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 336.0507 ( 1607 G-vectors) FFT grid: ( 25, 25, 25) + G cutoff = 120.9783 ( 354 G-vectors) smooth grid: ( 15, 15, 15) + + number of k points= 288 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, C_2v (mm2) point group: + + + Atomic displacements: + There are 3 irreducible representations + + Representation 1 1 modes -A_1 D_1 S_1 To be done + + Representation 2 1 modes -B_1 D_3 S_3 To be done + + Representation 3 1 modes -B_2 D_4 S_4 To be done + + + + Alpha used in Ewald sum = 2.8000 + PHONON : 1m 5.60s CPU 1m13.35s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 73.8 secs av.it.: 5.5 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.042E-02 + + iter # 2 total cpu time : 74.3 secs av.it.: 7.6 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.946E+00 + + iter # 3 total cpu time : 74.8 secs av.it.: 7.7 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 3.768E-02 + + iter # 4 total cpu time : 75.2 secs av.it.: 6.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.141E-03 + + iter # 5 total cpu time : 75.6 secs av.it.: 5.4 + thresh= 6.435E-03 alpha_mix = 0.700 |ddv_scf|^2 = 2.206E-07 + + iter # 6 total cpu time : 76.1 secs av.it.: 6.8 + thresh= 4.696E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.179E-06 + + iter # 7 total cpu time : 76.5 secs av.it.: 5.3 + thresh= 1.086E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.243E-09 + + iter # 8 total cpu time : 76.9 secs av.it.: 6.6 + thresh= 3.525E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.920E-09 + + iter # 9 total cpu time : 77.3 secs av.it.: 5.6 + thresh= 4.382E-06 alpha_mix = 0.700 |ddv_scf|^2 = 5.120E-12 + + iter # 10 total cpu time : 77.8 secs av.it.: 6.6 + thresh= 2.263E-07 alpha_mix = 0.700 |ddv_scf|^2 = 8.968E-13 + + iter # 11 total cpu time : 78.2 secs av.it.: 6.3 + thresh= 9.470E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.357E-13 + + iter # 12 total cpu time : 78.7 secs av.it.: 7.1 + thresh= 3.684E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.374E-13 + + iter # 13 total cpu time : 79.1 secs av.it.: 5.6 + thresh= 3.706E-08 alpha_mix = 0.700 |ddv_scf|^2 = 2.633E-13 + + iter # 14 total cpu time : 79.5 secs av.it.: 5.8 + thresh= 5.132E-08 alpha_mix = 0.700 |ddv_scf|^2 = 7.774E-15 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 mode # 2 + + Self-consistent Calculation + + iter # 1 total cpu time : 79.9 secs av.it.: 4.3 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 3.014E-05 + + iter # 2 total cpu time : 80.4 secs av.it.: 6.8 + thresh= 5.490E-04 alpha_mix = 0.700 |ddv_scf|^2 = 2.386E-07 + + iter # 3 total cpu time : 80.8 secs av.it.: 7.0 + thresh= 4.885E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.026E-08 + + iter # 4 total cpu time : 81.3 secs av.it.: 6.9 + thresh= 1.013E-05 alpha_mix = 0.700 |ddv_scf|^2 = 1.849E-10 + + iter # 5 total cpu time : 81.8 secs av.it.: 7.3 + thresh= 1.360E-06 alpha_mix = 0.700 |ddv_scf|^2 = 8.785E-12 + + iter # 6 total cpu time : 82.3 secs av.it.: 7.4 + thresh= 2.964E-07 alpha_mix = 0.700 |ddv_scf|^2 = 3.783E-13 + + iter # 7 total cpu time : 82.8 secs av.it.: 7.4 + thresh= 6.151E-08 alpha_mix = 0.700 |ddv_scf|^2 = 5.140E-14 + + iter # 8 total cpu time : 83.3 secs av.it.: 7.7 + thresh= 2.267E-08 alpha_mix = 0.700 |ddv_scf|^2 = 4.235E-16 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 3 mode # 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 83.7 secs av.it.: 4.6 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 9.482E-05 + + iter # 2 total cpu time : 84.2 secs av.it.: 7.0 + thresh= 9.737E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.103E-05 + + iter # 3 total cpu time : 84.6 secs av.it.: 6.9 + thresh= 3.321E-04 alpha_mix = 0.700 |ddv_scf|^2 = 2.126E-08 + + iter # 4 total cpu time : 85.1 secs av.it.: 7.4 + thresh= 1.458E-05 alpha_mix = 0.700 |ddv_scf|^2 = 2.768E-09 + + iter # 5 total cpu time : 85.6 secs av.it.: 7.2 + thresh= 5.261E-06 alpha_mix = 0.700 |ddv_scf|^2 = 5.199E-11 + + iter # 6 total cpu time : 86.0 secs av.it.: 7.2 + thresh= 7.210E-07 alpha_mix = 0.700 |ddv_scf|^2 = 6.732E-13 + + iter # 7 total cpu time : 86.5 secs av.it.: 7.3 + thresh= 8.205E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.367E-13 + + iter # 8 total cpu time : 87.0 secs av.it.: 7.8 + thresh= 3.697E-08 alpha_mix = 0.700 |ddv_scf|^2 = 2.930E-15 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 12 + List of q in the star: + 1 0.500000000 0.000000000 0.500000000 + 2 -0.500000000 0.000000000 0.500000000 + 3 -0.500000000 0.000000000 -0.500000000 + 4 0.500000000 0.000000000 -0.500000000 + 5 0.000000000 0.500000000 -0.500000000 + 6 -0.500000000 0.500000000 0.000000000 + 7 0.000000000 0.500000000 0.500000000 + 8 0.000000000 -0.500000000 -0.500000000 + 9 0.500000000 0.500000000 0.000000000 + 10 0.500000000 -0.500000000 0.000000000 + 11 -0.500000000 -0.500000000 0.000000000 + 12 0.000000000 -0.500000000 0.500000000 + + Diagonalizing the dynamical matrix + + q = ( 0.500000000 0.000000000 0.500000000 ) + + ************************************************************************** + freq ( 1) = 4.720919 [THz] = 157.472923 [cm-1] + freq ( 2) = 6.185773 [THz] = 206.335188 [cm-1] + freq ( 3) = 8.089659 [THz] = 269.841966 [cm-1] + ************************************************************************** + + Mode symmetry, C_2v (mm2) point group: + + freq ( 1 - 1) = 157.5 [cm-1] --> B_1 D_3 S_3 + freq ( 2 - 2) = 206.3 [cm-1] --> B_2 D_4 S_4 + freq ( 3 - 3) = 269.8 [cm-1] --> A_1 D_1 S_1 + + Calculation of q = 0.0000000 -1.0000000 0.0000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 112 40 18 1604 351 102 + Max 113 41 19 1607 354 104 + Sum 451 163 73 6423 1411 411 + + + Title: + phonons of Ni + + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 9 + kinetic-energy cutoff = 27.0000 Ry + charge density cutoff = 300.0000 Ry + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + celldm(1)= 6.650000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Ni 10.00 58.69340 Ni( 1.00) + + Starting magnetic structure + atomic species magnetization + Ni 0.000 + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Ni tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 40 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.1250000 0.1250000 0.1250000), wk = 0.0312500 + k( 2) = ( -0.1250000 -0.8750000 0.1250000), wk = 0.0000000 + k( 3) = ( -0.3750000 0.3750000 -0.1250000), wk = 0.0625000 + k( 4) = ( -0.3750000 -0.6250000 -0.1250000), wk = 0.0000000 + k( 5) = ( 0.3750000 -0.3750000 0.6250000), wk = 0.0625000 + k( 6) = ( 0.3750000 -1.3750000 0.6250000), wk = 0.0000000 + k( 7) = ( 0.1250000 -0.1250000 0.3750000), wk = 0.0625000 + k( 8) = ( 0.1250000 -1.1250000 0.3750000), wk = 0.0000000 + k( 9) = ( -0.1250000 0.6250000 0.1250000), wk = 0.0312500 + k( 10) = ( -0.1250000 -0.3750000 0.1250000), wk = 0.0000000 + k( 11) = ( 0.6250000 -0.1250000 0.8750000), wk = 0.0625000 + k( 12) = ( 0.6250000 -1.1250000 0.8750000), wk = 0.0000000 + k( 13) = ( 0.3750000 0.1250000 0.6250000), wk = 0.0625000 + k( 14) = ( 0.3750000 -0.8750000 0.6250000), wk = 0.0000000 + k( 15) = ( -0.1250000 -0.8750000 0.1250000), wk = 0.0312500 + k( 16) = ( -0.1250000 -1.8750000 0.1250000), wk = 0.0000000 + k( 17) = ( -0.3750000 0.3750000 0.3750000), wk = 0.0312500 + k( 18) = ( -0.3750000 -0.6250000 0.3750000), wk = 0.0000000 + k( 19) = ( 0.3750000 -0.3750000 1.1250000), wk = 0.0625000 + k( 20) = ( 0.3750000 -1.3750000 1.1250000), wk = 0.0000000 + k( 21) = ( 0.3750000 -0.1250000 -0.3750000), wk = 0.0312500 + k( 22) = ( 0.3750000 -1.1250000 -0.3750000), wk = 0.0000000 + k( 23) = ( -0.3750000 0.6250000 0.3750000), wk = 0.0312500 + k( 24) = ( -0.3750000 -0.3750000 0.3750000), wk = 0.0000000 + k( 25) = ( -0.1250000 0.3750000 0.1250000), wk = 0.0312500 + k( 26) = ( -0.1250000 -0.6250000 0.1250000), wk = 0.0000000 + k( 27) = ( 0.6250000 0.1250000 -0.1250000), wk = 0.0625000 + k( 28) = ( 0.6250000 -0.8750000 -0.1250000), wk = 0.0000000 + k( 29) = ( -0.1250000 0.8750000 0.6250000), wk = 0.0625000 + k( 30) = ( -0.1250000 -0.1250000 0.6250000), wk = 0.0000000 + k( 31) = ( -0.1250000 0.6250000 -0.8750000), wk = 0.0625000 + k( 32) = ( -0.1250000 -0.3750000 -0.8750000), wk = 0.0000000 + k( 33) = ( 0.1250000 0.6250000 0.3750000), wk = 0.0625000 + k( 34) = ( 0.1250000 -0.3750000 0.3750000), wk = 0.0000000 + k( 35) = ( 0.1250000 0.3750000 -0.6250000), wk = 0.0625000 + k( 36) = ( 0.1250000 -0.6250000 -0.6250000), wk = 0.0000000 + k( 37) = ( -0.8750000 0.1250000 -0.1250000), wk = 0.0625000 + k( 38) = ( -0.8750000 -0.8750000 -0.1250000), wk = 0.0000000 + k( 39) = ( -0.3750000 1.1250000 0.3750000), wk = 0.0312500 + k( 40) = ( -0.3750000 0.1250000 0.3750000), wk = 0.0000000 + + Dense grid: 6423 G-vectors FFT dimensions: ( 25, 25, 25) + + Smooth grid: 1411 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 6.90 MB + + Estimated total dynamical RAM > 27.58 MB + Generating pointlists ... + + Check: negative core charge= -0.000021 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/charge-density + + Starting wfcs are 6 atomic + 3 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 14.1 + + total cpu time spent up to now is 12.4 secs + + End of band structure calculation + + ------ SPIN UP ------------ + + + k =-0.1250 0.1250 0.1250 ( 172 PWs) bands (ev): + + 5.8697 11.5739 11.8319 11.8319 12.8613 12.8613 35.2151 39.1170 + 41.0563 + + k =-0.1250-0.8750 0.1250 ( 176 PWs) bands (ev): + + 9.7774 10.1644 12.8693 13.3037 13.6224 16.7880 24.9790 26.3754 + 30.0885 + + k =-0.3750 0.3750-0.1250 ( 171 PWs) bands (ev): + + 8.5750 11.2500 11.8343 12.1287 12.7521 13.6728 27.1042 32.6458 + 39.6758 + + k =-0.3750-0.6250-0.1250 ( 174 PWs) bands (ev): + + 10.0139 11.0553 11.4269 12.4907 13.2324 15.3091 24.0932 29.7562 + 32.8980 + + k = 0.3750-0.3750 0.6250 ( 172 PWs) bands (ev): + + 9.6624 11.5167 11.9827 12.1971 13.5534 15.4848 20.4983 33.7468 + 36.0279 + + k = 0.3750-1.3750 0.6250 ( 172 PWs) bands (ev): + + 9.6624 11.5167 11.9827 12.1971 13.5534 15.4848 20.4983 33.7468 + 36.0279 + + k = 0.1250-0.1250 0.3750 ( 169 PWs) bands (ev): + + 7.3631 11.1757 12.0273 12.1377 12.6935 13.1369 31.2698 36.2535 + 36.8262 + + k = 0.1250-1.1250 0.3750 ( 179 PWs) bands (ev): + + 10.3860 10.6412 11.6238 12.9147 13.5152 19.0390 22.3265 26.0101 + 28.3110 + + k =-0.1250 0.6250 0.1250 ( 178 PWs) bands (ev): + + 9.3859 10.5803 12.0474 12.7104 13.4797 13.7867 28.1568 31.5072 + 32.3294 + + k =-0.1250-0.3750 0.1250 ( 169 PWs) bands (ev): + + 7.3631 11.1757 12.0273 12.1377 12.6935 13.1369 31.2698 36.2535 + 36.8262 + + k = 0.6250-0.1250 0.8750 ( 179 PWs) bands (ev): + + 10.3860 10.6412 11.6238 12.9147 13.5152 19.0390 22.3265 26.0101 + 28.3110 + + k = 0.6250-1.1250 0.8750 ( 169 PWs) bands (ev): + + 7.3631 11.1757 12.0273 12.1377 12.6935 13.1369 31.2698 36.2535 + 36.8262 + + k = 0.3750 0.1250 0.6250 ( 174 PWs) bands (ev): + + 10.0139 11.0553 11.4269 12.4907 13.2324 15.3091 24.0932 29.7562 + 32.8980 + + k = 0.3750-0.8750 0.6250 ( 174 PWs) bands (ev): + + 10.0139 11.0553 11.4269 12.4907 13.2324 15.3091 24.0932 29.7562 + 32.8980 + + k =-0.1250-0.8750 0.1250 ( 176 PWs) bands (ev): + + 9.7774 10.1644 12.8693 13.3037 13.6224 16.7880 24.9790 26.3754 + 30.0885 + + k =-0.1250-1.8750 0.1250 ( 172 PWs) bands (ev): + + 5.8697 11.5739 11.8319 11.8319 12.8613 12.8613 35.2151 39.1170 + 41.0563 + + k =-0.3750 0.3750 0.3750 ( 174 PWs) bands (ev): + + 9.0450 11.8255 11.8255 12.3364 13.3397 13.3397 23.0016 37.0669 + 39.2790 + + k =-0.3750-0.6250 0.3750 ( 172 PWs) bands (ev): + + 9.6624 11.5167 11.9827 12.1971 13.5534 15.4848 20.4983 33.7468 + 36.0279 + + k = 0.3750-0.3750 1.1250 ( 176 PWs) bands (ev): + + 10.3654 11.0168 11.5578 12.5018 13.2687 17.7551 21.2364 27.2375 + 34.3327 + + k = 0.3750-1.3750 1.1250 ( 174 PWs) bands (ev): + + 10.0139 11.0553 11.4269 12.4907 13.2324 15.3091 24.0932 29.7562 + 32.8980 + + k = 0.3750-0.1250-0.3750 ( 171 PWs) bands (ev): + + 8.5750 11.2500 11.8343 12.1287 12.7521 13.6728 27.1042 32.6458 + 39.6758 + + k = 0.3750-1.1250-0.3750 ( 176 PWs) bands (ev): + + 10.3654 11.0168 11.5578 12.5018 13.2687 17.7551 21.2364 27.2375 + 34.3327 + + k =-0.3750 0.6250 0.3750 ( 172 PWs) bands (ev): + + 9.6624 11.5167 11.9827 12.1971 13.5534 15.4848 20.4983 33.7468 + 36.0279 + + k =-0.3750-0.3750 0.3750 ( 174 PWs) bands (ev): + + 9.0450 11.8255 11.8255 12.3364 13.3397 13.3397 23.0016 37.0669 + 39.2790 + + k =-0.1250 0.3750 0.1250 ( 169 PWs) bands (ev): + + 7.3631 11.1757 12.0273 12.1377 12.6935 13.1369 31.2698 36.2535 + 36.8262 + + k =-0.1250-0.6250 0.1250 ( 178 PWs) bands (ev): + + 9.3859 10.5803 12.0474 12.7104 13.4797 13.7867 28.1568 31.5072 + 32.3294 + + k = 0.6250 0.1250-0.1250 ( 178 PWs) bands (ev): + + 9.3859 10.5803 12.0474 12.7104 13.4797 13.7867 28.1568 31.5072 + 32.3294 + + k = 0.6250-0.8750-0.1250 ( 179 PWs) bands (ev): + + 10.3860 10.6412 11.6238 12.9147 13.5152 19.0390 22.3265 26.0101 + 28.3110 + + k =-0.1250 0.8750 0.6250 ( 179 PWs) bands (ev): + + 10.3860 10.6412 11.6238 12.9147 13.5152 19.0390 22.3265 26.0101 + 28.3110 + + k =-0.1250-0.1250 0.6250 ( 178 PWs) bands (ev): + + 9.3859 10.5803 12.0474 12.7104 13.4797 13.7867 28.1568 31.5072 + 32.3294 + + k =-0.1250 0.6250-0.8750 ( 179 PWs) bands (ev): + + 10.3860 10.6412 11.6238 12.9147 13.5152 19.0390 22.3265 26.0101 + 28.3110 + + k =-0.1250-0.3750-0.8750 ( 179 PWs) bands (ev): + + 10.3860 10.6412 11.6238 12.9147 13.5152 19.0390 22.3265 26.0101 + 28.3110 + + k = 0.1250 0.6250 0.3750 ( 174 PWs) bands (ev): + + 10.0139 11.0553 11.4269 12.4907 13.2324 15.3091 24.0932 29.7562 + 32.8980 + + k = 0.1250-0.3750 0.3750 ( 171 PWs) bands (ev): + + 8.5750 11.2500 11.8343 12.1287 12.7521 13.6728 27.1042 32.6458 + 39.6758 + + k = 0.1250 0.3750-0.6250 ( 174 PWs) bands (ev): + + 10.0139 11.0553 11.4269 12.4907 13.2324 15.3091 24.0932 29.7562 + 32.8980 + + k = 0.1250-0.6250-0.6250 ( 176 PWs) bands (ev): + + 10.3654 11.0168 11.5578 12.5018 13.2687 17.7551 21.2364 27.2375 + 34.3327 + + k =-0.8750 0.1250-0.1250 ( 176 PWs) bands (ev): + + 9.7774 10.1644 12.8693 13.3037 13.6224 16.7880 24.9790 26.3754 + 30.0885 + + k =-0.8750-0.8750-0.1250 ( 176 PWs) bands (ev): + + 9.7774 10.1644 12.8693 13.3037 13.6224 16.7880 24.9790 26.3754 + 30.0885 + + k =-0.3750 1.1250 0.3750 ( 176 PWs) bands (ev): + + 10.3654 11.0168 11.5578 12.5018 13.2687 17.7551 21.2364 27.2375 + 34.3327 + + k =-0.3750 0.1250 0.3750 ( 171 PWs) bands (ev): + + 8.5750 11.2500 11.8343 12.1287 12.7521 13.6728 27.1042 32.6458 + 39.6758 + + ------ SPIN DOWN ---------- + + + k =-0.1250 0.1250 0.1250 ( 172 PWs) bands (ev): + + 5.8235 12.4452 12.7307 12.7307 13.5994 13.5994 35.2386 38.9838 + 41.0911 + + k =-0.1250-0.8750 0.1250 ( 176 PWs) bands (ev): + + 10.2090 10.8957 13.6527 14.1097 14.5846 17.0385 25.1835 26.4722 + 30.1022 + + k =-0.3750 0.3750-0.1250 ( 171 PWs) bands (ev): + + 8.6208 11.9920 12.5953 12.9299 13.5959 14.4987 27.2785 32.7142 + 39.6076 + + k =-0.3750-0.6250-0.1250 ( 174 PWs) bands (ev): + + 10.3493 11.6766 12.1579 13.2575 14.1340 15.9186 24.3093 29.8490 + 32.9693 + + k = 0.3750-0.3750 0.6250 ( 172 PWs) bands (ev): + + 10.1825 12.1398 12.7501 12.7926 14.4701 15.8906 20.9029 33.7520 + 36.0974 + + k = 0.3750-1.3750 0.6250 ( 172 PWs) bands (ev): + + 10.1825 12.1398 12.7501 12.7926 14.4701 15.8906 20.9029 33.7520 + 36.0974 + + k = 0.1250-0.1250 0.3750 ( 169 PWs) bands (ev): + + 7.3328 11.9983 12.8358 13.0200 13.4875 13.9186 31.3755 36.3333 + 36.7643 + + k = 0.1250-1.1250 0.3750 ( 179 PWs) bands (ev): + + 10.8818 11.3221 12.3443 13.6454 14.5133 19.3212 22.5349 26.1705 + 28.4085 + + k =-0.1250 0.6250 0.1250 ( 178 PWs) bands (ev): + + 9.5396 11.3428 12.7065 13.5760 14.3301 14.5163 28.2785 31.5780 + 32.3841 + + k =-0.1250-0.3750 0.1250 ( 169 PWs) bands (ev): + + 7.3328 11.9983 12.8358 13.0200 13.4875 13.9186 31.3755 36.3333 + 36.7643 + + k = 0.6250-0.1250 0.8750 ( 179 PWs) bands (ev): + + 10.8818 11.3221 12.3443 13.6454 14.5133 19.3212 22.5349 26.1705 + 28.4085 + + k = 0.6250-1.1250 0.8750 ( 169 PWs) bands (ev): + + 7.3328 11.9983 12.8358 13.0200 13.4875 13.9186 31.3755 36.3333 + 36.7643 + + k = 0.3750 0.1250 0.6250 ( 174 PWs) bands (ev): + + 10.3493 11.6766 12.1579 13.2575 14.1340 15.9186 24.3093 29.8490 + 32.9693 + + k = 0.3750-0.8750 0.6250 ( 174 PWs) bands (ev): + + 10.3493 11.6766 12.1579 13.2575 14.1340 15.9186 24.3093 29.8490 + 32.9693 + + k =-0.1250-0.8750 0.1250 ( 176 PWs) bands (ev): + + 10.2090 10.8957 13.6527 14.1097 14.5846 17.0385 25.1835 26.4722 + 30.1022 + + k =-0.1250-1.8750 0.1250 ( 172 PWs) bands (ev): + + 5.8235 12.4452 12.7307 12.7307 13.5994 13.5994 35.2386 38.9838 + 41.0911 + + k =-0.3750 0.3750 0.3750 ( 174 PWs) bands (ev): + + 9.3305 12.6014 12.6014 12.6765 14.2265 14.2265 23.2891 36.8995 + 39.3685 + + k =-0.3750-0.6250 0.3750 ( 172 PWs) bands (ev): + + 10.1825 12.1398 12.7501 12.7926 14.4701 15.8906 20.9029 33.7520 + 36.0974 + + k = 0.3750-0.3750 1.1250 ( 176 PWs) bands (ev): + + 10.9698 11.5109 12.2800 13.2468 14.2186 18.1064 21.5401 27.3703 + 34.3959 + + k = 0.3750-1.3750 1.1250 ( 174 PWs) bands (ev): + + 10.3493 11.6766 12.1579 13.2575 14.1340 15.9186 24.3093 29.8490 + 32.9693 + + k = 0.3750-0.1250-0.3750 ( 171 PWs) bands (ev): + + 8.6208 11.9920 12.5953 12.9299 13.5959 14.4987 27.2785 32.7142 + 39.6076 + + k = 0.3750-1.1250-0.3750 ( 176 PWs) bands (ev): + + 10.9698 11.5109 12.2800 13.2468 14.2186 18.1064 21.5401 27.3703 + 34.3959 + + k =-0.3750 0.6250 0.3750 ( 172 PWs) bands (ev): + + 10.1825 12.1398 12.7501 12.7926 14.4701 15.8906 20.9029 33.7520 + 36.0974 + + k =-0.3750-0.3750 0.3750 ( 174 PWs) bands (ev): + + 9.3305 12.6014 12.6014 12.6765 14.2265 14.2265 23.2891 36.8995 + 39.3685 + + k =-0.1250 0.3750 0.1250 ( 169 PWs) bands (ev): + + 7.3328 11.9983 12.8358 13.0200 13.4875 13.9186 31.3755 36.3333 + 36.7643 + + k =-0.1250-0.6250 0.1250 ( 178 PWs) bands (ev): + + 9.5396 11.3428 12.7065 13.5760 14.3301 14.5163 28.2785 31.5780 + 32.3841 + + k = 0.6250 0.1250-0.1250 ( 178 PWs) bands (ev): + + 9.5396 11.3428 12.7065 13.5760 14.3301 14.5163 28.2785 31.5780 + 32.3841 + + k = 0.6250-0.8750-0.1250 ( 179 PWs) bands (ev): + + 10.8818 11.3221 12.3443 13.6454 14.5133 19.3212 22.5349 26.1705 + 28.4085 + + k =-0.1250 0.8750 0.6250 ( 179 PWs) bands (ev): + + 10.8818 11.3221 12.3443 13.6454 14.5133 19.3212 22.5349 26.1705 + 28.4085 + + k =-0.1250-0.1250 0.6250 ( 178 PWs) bands (ev): + + 9.5396 11.3428 12.7065 13.5760 14.3301 14.5163 28.2785 31.5780 + 32.3841 + + k =-0.1250 0.6250-0.8750 ( 179 PWs) bands (ev): + + 10.8818 11.3221 12.3443 13.6454 14.5133 19.3212 22.5349 26.1705 + 28.4085 + + k =-0.1250-0.3750-0.8750 ( 179 PWs) bands (ev): + + 10.8818 11.3221 12.3443 13.6454 14.5133 19.3212 22.5349 26.1705 + 28.4085 + + k = 0.1250 0.6250 0.3750 ( 174 PWs) bands (ev): + + 10.3493 11.6766 12.1579 13.2575 14.1340 15.9186 24.3093 29.8490 + 32.9693 + + k = 0.1250-0.3750 0.3750 ( 171 PWs) bands (ev): + + 8.6208 11.9920 12.5953 12.9299 13.5959 14.4987 27.2785 32.7142 + 39.6076 + + k = 0.1250 0.3750-0.6250 ( 174 PWs) bands (ev): + + 10.3493 11.6766 12.1579 13.2575 14.1340 15.9186 24.3093 29.8490 + 32.9693 + + k = 0.1250-0.6250-0.6250 ( 176 PWs) bands (ev): + + 10.9698 11.5109 12.2800 13.2468 14.2186 18.1064 21.5401 27.3703 + 34.3959 + + k =-0.8750 0.1250-0.1250 ( 176 PWs) bands (ev): + + 10.2090 10.8957 13.6527 14.1097 14.5846 17.0385 25.1835 26.4722 + 30.1022 + + k =-0.8750-0.8750-0.1250 ( 176 PWs) bands (ev): + + 10.2090 10.8957 13.6527 14.1097 14.5846 17.0385 25.1835 26.4722 + 30.1022 + + k =-0.3750 1.1250 0.3750 ( 176 PWs) bands (ev): + + 10.9698 11.5109 12.2800 13.2468 14.2186 18.1064 21.5401 27.3703 + 34.3959 + + k =-0.3750 0.1250 0.3750 ( 171 PWs) bands (ev): + + 8.6208 11.9920 12.5953 12.9299 13.5959 14.4987 27.2785 32.7142 + 39.6076 + + the Fermi energy is 14.2874 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/ + + phonons of Ni + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 27.0000 Ry + charge density cut-off = 300.0000 Ry + convergence threshold = 1.0E-14 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + + celldm(1)= 6.65000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Ni 58.6934 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.0000000 -1.0000000 0.0000000 ) + + 17 Sym.Ops. (with q -> -q+G ) + + + G cutoff = 336.0507 ( 1607 G-vectors) FFT grid: ( 25, 25, 25) + G cutoff = 120.9783 ( 354 G-vectors) smooth grid: ( 15, 15, 15) + + number of k points= 80 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, D_4h(4/mmm) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_2u X_4' M_4' To be done + + Representation 2 2 modes -E_u X_5' M_5' To be done + + + + Alpha used in Ewald sum = 2.8000 + PHONON : 1m18.53s CPU 1m27.96s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 88.1 secs av.it.: 5.0 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.698E-04 + + iter # 2 total cpu time : 88.3 secs av.it.: 6.8 + thresh= 2.168E-03 alpha_mix = 0.700 |ddv_scf|^2 = 2.689E-04 + + iter # 3 total cpu time : 88.4 secs av.it.: 6.3 + thresh= 1.640E-03 alpha_mix = 0.700 |ddv_scf|^2 = 3.460E-08 + + iter # 4 total cpu time : 88.6 secs av.it.: 6.6 + thresh= 1.860E-05 alpha_mix = 0.700 |ddv_scf|^2 = 3.151E-10 + + iter # 5 total cpu time : 88.7 secs av.it.: 5.8 + thresh= 1.775E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.020E-11 + + iter # 6 total cpu time : 88.9 secs av.it.: 6.1 + thresh= 3.194E-07 alpha_mix = 0.700 |ddv_scf|^2 = 5.186E-14 + + iter # 7 total cpu time : 89.0 secs av.it.: 6.6 + thresh= 2.277E-08 alpha_mix = 0.700 |ddv_scf|^2 = 9.389E-16 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 89.3 secs av.it.: 4.4 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 1.425E-05 + + iter # 2 total cpu time : 89.6 secs av.it.: 7.4 + thresh= 3.776E-04 alpha_mix = 0.700 |ddv_scf|^2 = 5.395E-07 + + iter # 3 total cpu time : 89.9 secs av.it.: 7.3 + thresh= 7.345E-05 alpha_mix = 0.700 |ddv_scf|^2 = 3.167E-09 + + iter # 4 total cpu time : 90.2 secs av.it.: 6.8 + thresh= 5.628E-06 alpha_mix = 0.700 |ddv_scf|^2 = 5.795E-12 + + iter # 5 total cpu time : 90.5 secs av.it.: 6.9 + thresh= 2.407E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.497E-13 + + iter # 6 total cpu time : 90.8 secs av.it.: 7.1 + thresh= 3.869E-08 alpha_mix = 0.700 |ddv_scf|^2 = 8.874E-15 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 3 + List of q in the star: + 1 0.000000000 -1.000000000 0.000000000 + 2 -1.000000000 0.000000000 0.000000000 + 3 0.000000000 0.000000000 -1.000000000 + + Diagonalizing the dynamical matrix + + q = ( 0.000000000 -1.000000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 6.621627 [THz] = 220.873705 [cm-1] + freq ( 2) = 6.621627 [THz] = 220.873705 [cm-1] + freq ( 3) = 8.965810 [THz] = 299.067238 [cm-1] + ************************************************************************** + + Mode symmetry, D_4h(4/mmm) point group: + + freq ( 1 - 2) = 220.9 [cm-1] --> E_u X_5' M_5' + freq ( 3 - 3) = 299.1 [cm-1] --> A_2u X_4' M_4' + + Calculation of q = -0.5000000 -1.0000000 0.0000000 + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 112 40 18 1604 351 102 + Max 113 41 19 1607 354 104 + Sum 451 163 73 6423 1411 411 + + + Title: + phonons of Ni + + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 9 + kinetic-energy cutoff = 27.0000 Ry + charge density cutoff = 300.0000 Ry + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + celldm(1)= 6.650000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Ni 10.00 58.69340 Ni( 1.00) + + Starting magnetic structure + atomic species magnetization + Ni 0.000 + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Ni tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 64 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.1250000 0.1250000 0.1250000), wk = 0.0312500 + k( 2) = ( -0.6250000 -0.8750000 0.1250000), wk = 0.0000000 + k( 3) = ( -0.3750000 0.3750000 -0.1250000), wk = 0.0312500 + k( 4) = ( -0.8750000 -0.6250000 -0.1250000), wk = 0.0000000 + k( 5) = ( 0.3750000 -0.3750000 0.6250000), wk = 0.0312500 + k( 6) = ( -0.1250000 -1.3750000 0.6250000), wk = 0.0000000 + k( 7) = ( 0.1250000 -0.1250000 0.3750000), wk = 0.0312500 + k( 8) = ( -0.3750000 -1.1250000 0.3750000), wk = 0.0000000 + k( 9) = ( -0.1250000 0.6250000 0.1250000), wk = 0.0312500 + k( 10) = ( -0.6250000 -0.3750000 0.1250000), wk = 0.0000000 + k( 11) = ( 0.6250000 -0.1250000 0.8750000), wk = 0.0312500 + k( 12) = ( 0.1250000 -1.1250000 0.8750000), wk = 0.0000000 + k( 13) = ( 0.3750000 0.1250000 0.6250000), wk = 0.0312500 + k( 14) = ( -0.1250000 -0.8750000 0.6250000), wk = 0.0000000 + k( 15) = ( -0.1250000 -0.8750000 0.1250000), wk = 0.0312500 + k( 16) = ( -0.6250000 -1.8750000 0.1250000), wk = 0.0000000 + k( 17) = ( -0.3750000 0.3750000 0.3750000), wk = 0.0312500 + k( 18) = ( -0.8750000 -0.6250000 0.3750000), wk = 0.0000000 + k( 19) = ( 0.3750000 -0.3750000 1.1250000), wk = 0.0312500 + k( 20) = ( -0.1250000 -1.3750000 1.1250000), wk = 0.0000000 + k( 21) = ( 0.1250000 -0.3750000 0.3750000), wk = 0.0312500 + k( 22) = ( -0.3750000 -1.3750000 0.3750000), wk = 0.0000000 + k( 23) = ( 0.3750000 -0.3750000 -0.1250000), wk = 0.0312500 + k( 24) = ( -0.1250000 -1.3750000 -0.1250000), wk = 0.0000000 + k( 25) = ( -0.6250000 0.3750000 -0.3750000), wk = 0.0312500 + k( 26) = ( -1.1250000 -0.6250000 -0.3750000), wk = 0.0000000 + k( 27) = ( -0.3750000 0.3750000 0.6250000), wk = 0.0312500 + k( 28) = ( -0.8750000 -0.6250000 0.6250000), wk = 0.0000000 + k( 29) = ( -0.3750000 0.1250000 -0.1250000), wk = 0.0312500 + k( 30) = ( -0.8750000 -0.8750000 -0.1250000), wk = 0.0000000 + k( 31) = ( -0.1250000 0.1250000 0.3750000), wk = 0.0312500 + k( 32) = ( -0.6250000 -0.8750000 0.3750000), wk = 0.0000000 + k( 33) = ( 0.1250000 0.6250000 -0.1250000), wk = 0.0312500 + k( 34) = ( -0.3750000 -0.3750000 -0.1250000), wk = 0.0000000 + k( 35) = ( 0.6250000 0.1250000 -0.1250000), wk = 0.0312500 + k( 36) = ( 0.1250000 -0.8750000 -0.1250000), wk = 0.0000000 + k( 37) = ( -0.8750000 0.1250000 -0.6250000), wk = 0.0312500 + k( 38) = ( -1.3750000 -0.8750000 -0.6250000), wk = 0.0000000 + k( 39) = ( 0.8750000 -0.1250000 0.6250000), wk = 0.0312500 + k( 40) = ( 0.3750000 -1.1250000 0.6250000), wk = 0.0000000 + k( 41) = ( -0.6250000 0.1250000 0.8750000), wk = 0.0312500 + k( 42) = ( -1.1250000 -0.8750000 0.8750000), wk = 0.0000000 + k( 43) = ( -0.1250000 0.8750000 0.6250000), wk = 0.0312500 + k( 44) = ( -0.6250000 -0.1250000 0.6250000), wk = 0.0000000 + k( 45) = ( 0.1250000 0.8750000 -0.6250000), wk = 0.0312500 + k( 46) = ( -0.3750000 -0.1250000 -0.6250000), wk = 0.0000000 + k( 47) = ( -0.6250000 -0.1250000 -0.3750000), wk = 0.0312500 + k( 48) = ( -1.1250000 -1.1250000 -0.3750000), wk = 0.0000000 + k( 49) = ( 0.6250000 0.1250000 0.3750000), wk = 0.0312500 + k( 50) = ( 0.1250000 -0.8750000 0.3750000), wk = 0.0000000 + k( 51) = ( -0.3750000 -0.1250000 0.6250000), wk = 0.0312500 + k( 52) = ( -0.8750000 -1.1250000 0.6250000), wk = 0.0000000 + k( 53) = ( 0.1250000 0.6250000 0.3750000), wk = 0.0312500 + k( 54) = ( -0.3750000 -0.3750000 0.3750000), wk = 0.0000000 + k( 55) = ( -0.1250000 0.6250000 -0.3750000), wk = 0.0312500 + k( 56) = ( -0.6250000 -0.3750000 -0.3750000), wk = 0.0000000 + k( 57) = ( 0.1250000 -0.8750000 -0.1250000), wk = 0.0312500 + k( 58) = ( -0.3750000 -1.8750000 -0.1250000), wk = 0.0000000 + k( 59) = ( -0.8750000 0.1250000 -0.1250000), wk = 0.0312500 + k( 60) = ( -1.3750000 -0.8750000 -0.1250000), wk = 0.0000000 + k( 61) = ( -1.1250000 0.3750000 -0.3750000), wk = 0.0312500 + k( 62) = ( -1.6250000 -0.6250000 -0.3750000), wk = 0.0000000 + k( 63) = ( -0.3750000 0.3750000 1.1250000), wk = 0.0312500 + k( 64) = ( -0.8750000 -0.6250000 1.1250000), wk = 0.0000000 + + Dense grid: 6423 G-vectors FFT dimensions: ( 25, 25, 25) + + Smooth grid: 1411 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 6.90 MB + + Estimated total dynamical RAM > 27.62 MB + Generating pointlists ... + + Check: negative core charge= -0.000021 + + The potential is recalculated from file : + /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/charge-density + + Starting wfcs are 6 atomic + 3 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 1.00E-10, avg # of iterations = 13.7 + + total cpu time spent up to now is 13.5 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 14.2874 ev + + Writing output data file /home/giannozz/q-e-mio/tempdir/_ph0/nickel.save/ + + phonons of Ni + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 27.0000 Ry + charge density cut-off = 300.0000 Ry + convergence threshold = 1.0E-14 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PBE + ( 1 4 3 4 0 0 0) + + + celldm(1)= 6.65000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Ni 58.6934 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( -0.5000000 -1.0000000 0.0000000 ) + + 8 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 336.0507 ( 1607 G-vectors) FFT grid: ( 25, 25, 25) + G cutoff = 120.9783 ( 354 G-vectors) smooth grid: ( 15, 15, 15) + + number of k points= 128 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + Mode symmetry, D_2d (-42m) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -B_2 X_3 W_2 To be done + + Representation 2 2 modes -E X_5 W_3 To be done + + + + Alpha used in Ewald sum = 2.8000 + PHONON : 1m22.30s CPU 1m32.09s WALL + + + + Representation # 1 mode # 1 + + Self-consistent Calculation + + iter # 1 total cpu time : 92.3 secs av.it.: 4.7 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 9.983E-05 + + iter # 2 total cpu time : 92.5 secs av.it.: 7.1 + thresh= 9.992E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.487E-05 + + iter # 3 total cpu time : 92.7 secs av.it.: 7.0 + thresh= 3.856E-04 alpha_mix = 0.700 |ddv_scf|^2 = 2.452E-08 + + iter # 4 total cpu time : 93.0 secs av.it.: 7.5 + thresh= 1.566E-05 alpha_mix = 0.700 |ddv_scf|^2 = 3.225E-09 + + iter # 5 total cpu time : 93.2 secs av.it.: 7.3 + thresh= 5.679E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.164E-10 + + iter # 6 total cpu time : 93.4 secs av.it.: 7.3 + thresh= 1.079E-06 alpha_mix = 0.700 |ddv_scf|^2 = 2.471E-12 + + iter # 7 total cpu time : 93.7 secs av.it.: 7.6 + thresh= 1.572E-07 alpha_mix = 0.700 |ddv_scf|^2 = 5.807E-13 + + iter # 8 total cpu time : 93.9 secs av.it.: 8.1 + thresh= 7.620E-08 alpha_mix = 0.700 |ddv_scf|^2 = 4.623E-15 + + End of self-consistent calculation + + Convergence has been achieved + + + Representation # 2 modes # 2 3 + + Self-consistent Calculation + + iter # 1 total cpu time : 94.3 secs av.it.: 4.9 + thresh= 1.000E-02 alpha_mix = 0.700 |ddv_scf|^2 = 4.800E-05 + + iter # 2 total cpu time : 94.8 secs av.it.: 7.8 + thresh= 6.929E-04 alpha_mix = 0.700 |ddv_scf|^2 = 1.231E-05 + + iter # 3 total cpu time : 95.2 secs av.it.: 7.5 + thresh= 3.509E-04 alpha_mix = 0.700 |ddv_scf|^2 = 6.062E-09 + + iter # 4 total cpu time : 95.7 secs av.it.: 8.0 + thresh= 7.786E-06 alpha_mix = 0.700 |ddv_scf|^2 = 4.462E-10 + + iter # 5 total cpu time : 96.1 secs av.it.: 7.9 + thresh= 2.112E-06 alpha_mix = 0.700 |ddv_scf|^2 = 1.139E-11 + + iter # 6 total cpu time : 96.6 secs av.it.: 7.9 + thresh= 3.375E-07 alpha_mix = 0.700 |ddv_scf|^2 = 1.252E-13 + + iter # 7 total cpu time : 97.1 secs av.it.: 7.9 + thresh= 3.538E-08 alpha_mix = 0.700 |ddv_scf|^2 = 1.503E-14 + + iter # 8 total cpu time : 97.6 secs av.it.: 8.4 + thresh= 1.226E-08 alpha_mix = 0.700 |ddv_scf|^2 = 3.651E-16 + + End of self-consistent calculation + + Convergence has been achieved + + Number of q in the star = 6 + List of q in the star: + 1 -0.500000000 -1.000000000 0.000000000 + 2 0.000000000 1.000000000 0.500000000 + 3 0.000000000 -1.000000000 -0.500000000 + 4 0.500000000 1.000000000 0.000000000 + 5 -1.000000000 -0.500000000 0.000000000 + 6 0.000000000 -0.500000000 -1.000000000 + + Diagonalizing the dynamical matrix + + q = ( -0.500000000 -1.000000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 6.767337 [THz] = 225.734076 [cm-1] + freq ( 2) = 7.847085 [THz] = 261.750565 [cm-1] + freq ( 3) = 7.847085 [THz] = 261.750565 [cm-1] + ************************************************************************** + + Mode symmetry, D_2d (-42m) point group: + + freq ( 1 - 1) = 225.7 [cm-1] --> B_2 X_3 W_2 + freq ( 2 - 3) = 261.8 [cm-1] --> E X_5 W_3 + + init_run : 0.48s CPU 0.52s WALL ( 7 calls) + electrons : 11.82s CPU 12.91s WALL ( 7 calls) + + Called by init_run: + wfcinit : 0.00s CPU 0.00s WALL ( 7 calls) + potinit : 0.03s CPU 0.04s WALL ( 7 calls) + hinit0 : 0.41s CPU 0.42s WALL ( 7 calls) + + Called by electrons: + c_bands : 11.81s CPU 12.90s WALL ( 7 calls) + v_of_rho : 0.03s CPU 0.03s WALL ( 8 calls) + newd : 0.03s CPU 0.03s WALL ( 8 calls) + + Called by c_bands: + init_us_2 : 0.40s CPU 0.44s WALL ( 29408 calls) + cegterg : 10.88s CPU 11.88s WALL ( 1593 calls) + + Called by sum_band: + + Called by *egterg: + h_psi : 47.30s CPU 53.10s WALL ( 224730 calls) + s_psi : 2.53s CPU 2.87s WALL ( 449217 calls) + g_psi : 0.05s CPU 0.06s WALL ( 22398 calls) + cdiaghg : 3.57s CPU 3.88s WALL ( 23990 calls) + + Called by h_psi: + h_psi:calbec : 2.94s CPU 3.30s WALL ( 224730 calls) + vloc_psi : 42.15s CPU 47.31s WALL ( 224730 calls) + add_vuspsi : 1.27s CPU 1.44s WALL ( 224730 calls) + + General routines + calbec : 5.49s CPU 6.18s WALL ( 498161 calls) + fft : 0.66s CPU 0.72s WALL ( 7372 calls) + ffts : 0.08s CPU 0.10s WALL ( 3557 calls) + fftw : 48.28s CPU 54.25s WALL ( 2770904 calls) + interpolate : 0.10s CPU 0.12s WALL ( 924 calls) + davcio : 0.71s CPU 1.01s WALL ( 129200 calls) + + Parallel routines + fft_scatt_xy : 7.06s CPU 7.97s WALL ( 2781833 calls) + fft_scatt_yz : 26.61s CPU 29.97s WALL ( 2781833 calls) + + PHONON : 1m27.22s CPU 1m37.60s WALL + + INITIALIZATION: + phq_setup : 0.15s CPU 0.16s WALL ( 8 calls) + phq_init : 1.92s CPU 1.99s WALL ( 8 calls) + + phq_init : 1.92s CPU 1.99s WALL ( 8 calls) + set_drhoc : 0.28s CPU 0.29s WALL ( 24 calls) + init_vloc : 0.01s CPU 0.01s WALL ( 8 calls) + init_us_1 : 0.44s CPU 0.45s WALL ( 8 calls) + newd : 0.03s CPU 0.03s WALL ( 8 calls) + dvanqq : 0.18s CPU 0.18s WALL ( 8 calls) + drho : 1.06s CPU 1.11s WALL ( 8 calls) + + DYNAMICAL MATRIX: + dynmat0 : 0.47s CPU 0.47s WALL ( 8 calls) + phqscf : 72.37s CPU 81.50s WALL ( 8 calls) + dynmatrix : 0.00s CPU 0.01s WALL ( 8 calls) + + phqscf : 72.37s CPU 81.50s WALL ( 8 calls) + solve_linter : 72.10s CPU 81.20s WALL ( 17 calls) + drhodv : 0.26s CPU 0.28s WALL ( 17 calls) + + dynmat0 : 0.47s CPU 0.47s WALL ( 8 calls) + dynmat_us : 0.24s CPU 0.24s WALL ( 8 calls) + d2ionq : 0.00s CPU 0.00s WALL ( 8 calls) + dynmatcc : 0.22s CPU 0.22s WALL ( 8 calls) + + dynmat_us : 0.24s CPU 0.24s WALL ( 8 calls) + addusdynmat : 0.00s CPU 0.00s WALL ( 8 calls) + + phqscf : 72.37s CPU 81.50s WALL ( 8 calls) + solve_linter : 72.10s CPU 81.20s WALL ( 17 calls) + + solve_linter : 72.10s CPU 81.20s WALL ( 17 calls) + dvqpsi_us : 1.33s CPU 1.50s WALL ( 2448 calls) + ortho : 1.09s CPU 1.23s WALL ( 25340 calls) + cgsolve : 52.50s CPU 59.18s WALL ( 25340 calls) + incdrhoscf : 5.90s CPU 6.66s WALL ( 25340 calls) + addusddens : 0.84s CPU 0.88s WALL ( 181 calls) + vpsifft : 5.16s CPU 5.83s WALL ( 22892 calls) + dv_of_drho : 0.63s CPU 0.65s WALL ( 211 calls) + mix_pot : 0.12s CPU 0.15s WALL ( 164 calls) + ef_shift : 0.01s CPU 0.01s WALL ( 7 calls) + localdos : 0.01s CPU 0.01s WALL ( 1 calls) + psymdvscf : 1.90s CPU 1.94s WALL ( 164 calls) + newdq : 0.80s CPU 0.90s WALL ( 164 calls) + adddvscf : 0.37s CPU 0.42s WALL ( 22892 calls) + drhodvus : 0.00s CPU 0.00s WALL ( 17 calls) + + dvqpsi_us : 1.33s CPU 1.50s WALL ( 2448 calls) + dvqpsi_us_on : 0.44s CPU 0.50s WALL ( 2448 calls) + + cgsolve : 52.50s CPU 59.18s WALL ( 25340 calls) + ch_psi : 49.53s CPU 55.81s WALL ( 199147 calls) + + ch_psi : 49.53s CPU 55.81s WALL ( 199147 calls) + h_psi : 47.30s CPU 53.10s WALL ( 224730 calls) + last : 5.91s CPU 6.66s WALL ( 199147 calls) + + h_psi : 47.30s CPU 53.10s WALL ( 224730 calls) + add_vuspsi : 1.27s CPU 1.44s WALL ( 224730 calls) + + incdrhoscf : 5.90s CPU 6.66s WALL ( 25340 calls) + addusdbec : 0.49s CPU 0.54s WALL ( 27788 calls) + + drhodvus : 0.00s CPU 0.00s WALL ( 17 calls) + + General routines + calbec : 5.49s CPU 6.18s WALL ( 498161 calls) + fft : 0.66s CPU 0.72s WALL ( 7372 calls) + ffts : 0.08s CPU 0.10s WALL ( 3557 calls) + fftw : 48.28s CPU 54.25s WALL ( 2770904 calls) + davcio : 0.71s CPU 1.01s WALL ( 129200 calls) + write_rec : 0.11s CPU 0.12s WALL ( 181 calls) + + + PHONON : 1m27.22s CPU 1m37.60s WALL + + + This run was terminated on: 9:47:49 19Mar2020 + +=------------------------------------------------------------------------------= + JOB DONE. +=------------------------------------------------------------------------------= diff --git a/PHonon/examples/example13/reference/ni.scf.out b/PHonon/examples/example13/reference/ni.scf.out new file mode 100644 index 000000000..1bc89a8a4 --- /dev/null +++ b/PHonon/examples/example13/reference/ni.scf.out @@ -0,0 +1,461 @@ + + Program PWSCF v.6.5 starts on 19Mar2020 at 9:46: 9 + + This program is part of the open-source Quantum ESPRESSO suite + for quantum simulation of materials; please cite + "P. Giannozzi et al., J. Phys.:Condens. Matter 21 395502 (2009); + "P. Giannozzi et al., J. Phys.:Condens. Matter 29 465901 (2017); + URL http://www.quantum-espresso.org", + in publications or presentations arising from this work. More details at + http://www.quantum-espresso.org/quote + + Parallel version (MPI & OpenMP), running on 4 processor cores + Number of MPI processes: 4 + Threads/MPI process: 1 + + MPI processes distributed on 1 nodes + R & G space division: proc/nbgrp/npool/nimage = 4 + Waiting for input... + Reading input from standard input + + Current dimensions of program PWSCF are: + Max number of different atomic species (ntypx) = 10 + Max number of k-points (npk) = 40000 + Max angular momentum in pseudopotentials (lmaxx) = 3 + file Ni.pbe-nd-rrkjus.UPF: wavefunction(s) 4S renormalized + + Subspace diagonalization in iterative solution of the eigenvalue problem: + a serial algorithm will be used + + + Parallelization info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Min 112 40 15 1604 351 82 + Max 113 41 16 1607 354 83 + Sum 451 163 61 6423 1411 331 + + + + bravais-lattice index = 2 + lattice parameter (alat) = 6.6500 a.u. + unit-cell volume = 73.5199 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 10.00 + number of Kohn-Sham states= 9 + kinetic-energy cutoff = 27.0000 Ry + charge density cutoff = 300.0000 Ry + convergence threshold = 1.0E-08 + mixing beta = 0.7000 + number of iterations used = 8 plain mixing + Exchange-correlation= SLA PW PBE PBE + ( 1 4 3 4 0 0 0) + + celldm(1)= 6.650000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Ni read from file: + /home/giannozz/q-e-mio/pseudo/Ni.pbe-nd-rrkjus.UPF + MD5 check sum: d71bc9c4c8adef96ad6fe9664ede368e + Pseudo is Ultrasoft + core correction, Zval = 10.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 1203 points, 6 beta functions with: + l(1) = 0 + l(2) = 0 + l(3) = 1 + l(4) = 1 + l(5) = 2 + l(6) = 2 + Q(r) pseudized with 0 coefficients + + + atomic species valence mass pseudopotential + Ni 10.00 58.69340 Ni( 1.00) + + Starting magnetic structure + atomic species magnetization + Ni 0.500 + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Ni tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 10 Marzari-Vanderbilt smearing, width (Ry)= 0.0200 + cart. coord. in units 2pi/alat + k( 1) = ( -0.1250000 0.1250000 0.1250000), wk = 0.0312500 + k( 2) = ( -0.3750000 0.3750000 -0.1250000), wk = 0.0937500 + k( 3) = ( 0.3750000 -0.3750000 0.6250000), wk = 0.0937500 + k( 4) = ( 0.1250000 -0.1250000 0.3750000), wk = 0.0937500 + k( 5) = ( -0.1250000 0.6250000 0.1250000), wk = 0.0937500 + k( 6) = ( 0.6250000 -0.1250000 0.8750000), wk = 0.1875000 + k( 7) = ( 0.3750000 0.1250000 0.6250000), wk = 0.1875000 + k( 8) = ( -0.1250000 -0.8750000 0.1250000), wk = 0.0937500 + k( 9) = ( -0.3750000 0.3750000 0.3750000), wk = 0.0312500 + k( 10) = ( 0.3750000 -0.3750000 1.1250000), wk = 0.0937500 + + Dense grid: 6423 G-vectors FFT dimensions: ( 25, 25, 25) + + Smooth grid: 1411 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 7.84 MB + + Estimated total dynamical RAM > 31.37 MB + Generating pointlists ... + new r_m : 0.2917 (alat units) 1.9397 (a.u.) for type 1 + + Check: negative core charge= -0.000021 + + Initial potential from superposition of free atoms + + starting charge 9.99954, renormalised to 10.00000 + Starting wfcs are 6 randomized atomic wfcs + 3 random wfcs + + total cpu time spent up to now is 0.4 secs + + Self-consistent Calculation + + iteration # 1 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 1.00E-02, avg # of iterations = 4.2 + + total cpu time spent up to now is 0.4 secs + + total energy = -85.61582607 Ry + Harris-Foulkes estimate = -85.78369204 Ry + estimated scf accuracy < 0.60123762 Ry + + total magnetization = 1.63 Bohr mag/cell + absolute magnetization = 1.65 Bohr mag/cell + + iteration # 2 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 6.01E-03, avg # of iterations = 2.0 + + total cpu time spent up to now is 0.5 secs + + total energy = -85.74795377 Ry + Harris-Foulkes estimate = -86.04555041 Ry + estimated scf accuracy < 0.81456890 Ry + + total magnetization = 0.70 Bohr mag/cell + absolute magnetization = 0.75 Bohr mag/cell + + iteration # 3 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 6.01E-03, avg # of iterations = 1.1 + + total cpu time spent up to now is 0.5 secs + + total energy = -85.88902499 Ry + Harris-Foulkes estimate = -85.86964512 Ry + estimated scf accuracy < 0.02587232 Ry + + total magnetization = 0.85 Bohr mag/cell + absolute magnetization = 1.00 Bohr mag/cell + + iteration # 4 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 2.59E-04, avg # of iterations = 1.6 + + total cpu time spent up to now is 0.6 secs + + total energy = -85.89672647 Ry + Harris-Foulkes estimate = -85.89651894 Ry + estimated scf accuracy < 0.00091973 Ry + + total magnetization = 0.72 Bohr mag/cell + absolute magnetization = 0.84 Bohr mag/cell + + iteration # 5 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 9.20E-06, avg # of iterations = 2.0 + + total cpu time spent up to now is 0.6 secs + + total energy = -85.89693407 Ry + Harris-Foulkes estimate = -85.89693937 Ry + estimated scf accuracy < 0.00010875 Ry + + total magnetization = 0.70 Bohr mag/cell + absolute magnetization = 0.82 Bohr mag/cell + + iteration # 6 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 1.09E-06, avg # of iterations = 1.6 + + total cpu time spent up to now is 0.7 secs + + total energy = -85.89698810 Ry + Harris-Foulkes estimate = -85.89696699 Ry + estimated scf accuracy < 0.00004828 Ry + + total magnetization = 0.71 Bohr mag/cell + absolute magnetization = 0.81 Bohr mag/cell + + iteration # 7 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 4.83E-07, avg # of iterations = 1.0 + + total cpu time spent up to now is 0.7 secs + + total energy = -85.89698843 Ry + Harris-Foulkes estimate = -85.89698777 Ry + estimated scf accuracy < 0.00000129 Ry + + total magnetization = 0.71 Bohr mag/cell + absolute magnetization = 0.81 Bohr mag/cell + + iteration # 8 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 1.29E-08, avg # of iterations = 2.1 + + total cpu time spent up to now is 0.8 secs + + total energy = -85.89698924 Ry + Harris-Foulkes estimate = -85.89698895 Ry + estimated scf accuracy < 0.00000064 Ry + + total magnetization = 0.71 Bohr mag/cell + absolute magnetization = 0.80 Bohr mag/cell + + iteration # 9 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 6.40E-09, avg # of iterations = 1.2 + + total cpu time spent up to now is 0.8 secs + + total energy = -85.89698930 Ry + Harris-Foulkes estimate = -85.89698920 Ry + estimated scf accuracy < 0.00000020 Ry + + total magnetization = 0.71 Bohr mag/cell + absolute magnetization = 0.80 Bohr mag/cell + + iteration # 10 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 2.02E-09, avg # of iterations = 1.0 + + total cpu time spent up to now is 0.9 secs + + total energy = -85.89698931 Ry + Harris-Foulkes estimate = -85.89698930 Ry + estimated scf accuracy < 0.00000002 Ry + + total magnetization = 0.71 Bohr mag/cell + absolute magnetization = 0.80 Bohr mag/cell + + iteration # 11 ecut= 27.00 Ry beta= 0.70 + Davidson diagonalization with overlap + ethr = 2.13E-10, avg # of iterations = 1.0 + + Magnetic moment per site: + atom: 1 charge: 8.7379 magn: 0.7488 constr: 0.0000 + + total cpu time spent up to now is 0.9 secs + + End of self-consistent calculation + + ------ SPIN UP ------------ + + + k =-0.1250 0.1250 0.1250 ( 172 PWs) bands (ev): + + 5.8697 11.5737 11.8317 11.8317 12.8611 12.8611 35.2150 39.1169 + 41.0563 + + k =-0.3750 0.3750-0.1250 ( 171 PWs) bands (ev): + + 8.5750 11.2499 11.8341 12.1285 12.7519 13.6726 27.1041 32.6457 + 39.6758 + + k = 0.3750-0.3750 0.6250 ( 172 PWs) bands (ev): + + 9.6622 11.5165 11.9825 12.1969 13.5532 15.4846 20.4981 33.7467 + 36.0278 + + k = 0.1250-0.1250 0.3750 ( 169 PWs) bands (ev): + + 7.3630 11.1755 12.0271 12.1374 12.6933 13.1367 31.2697 36.2534 + 36.8261 + + k =-0.1250 0.6250 0.1250 ( 178 PWs) bands (ev): + + 9.3858 10.5801 12.0472 12.7102 13.4795 13.7865 28.1567 31.5072 + 32.3294 + + k = 0.6250-0.1250 0.8750 ( 179 PWs) bands (ev): + + 10.3858 10.6410 11.6236 12.9145 13.5150 19.0389 22.3264 26.0100 + 28.3109 + + k = 0.3750 0.1250 0.6250 ( 174 PWs) bands (ev): + + 10.0138 11.0551 11.4267 12.4905 13.2322 15.3089 24.0931 29.7561 + 32.8980 + + k =-0.1250-0.8750 0.1250 ( 176 PWs) bands (ev): + + 9.7772 10.1642 12.8691 13.3034 13.6221 16.7879 24.9788 26.3753 + 30.0885 + + k =-0.3750 0.3750 0.3750 ( 174 PWs) bands (ev): + + 9.0448 11.8253 11.8253 12.3362 13.3394 13.3394 23.0015 37.0668 + 39.2789 + + k = 0.3750-0.3750 1.1250 ( 176 PWs) bands (ev): + + 10.3652 11.0167 11.5576 12.5016 13.2684 17.7549 21.2363 27.2374 + 34.3326 + + ------ SPIN DOWN ---------- + + + k =-0.1250 0.1250 0.1250 ( 172 PWs) bands (ev): + + 5.8235 12.4452 12.7306 12.7306 13.5993 13.5993 35.2386 38.9839 + 41.0911 + + k =-0.3750 0.3750-0.1250 ( 171 PWs) bands (ev): + + 8.6208 11.9920 12.5953 12.9299 13.5958 14.4987 27.2785 32.7142 + 39.6077 + + k = 0.3750-0.3750 0.6250 ( 172 PWs) bands (ev): + + 10.1825 12.1397 12.7501 12.7926 14.4701 15.8906 20.9029 33.7520 + 36.0975 + + k = 0.1250-0.1250 0.3750 ( 169 PWs) bands (ev): + + 7.3328 11.9983 12.8358 13.0200 13.4874 13.9185 31.3755 36.3333 + 36.7643 + + k =-0.1250 0.6250 0.1250 ( 178 PWs) bands (ev): + + 9.5396 11.3428 12.7065 13.5760 14.3301 14.5163 28.2785 31.5780 + 32.3842 + + k = 0.6250-0.1250 0.8750 ( 179 PWs) bands (ev): + + 10.8818 11.3220 12.3443 13.6454 14.5133 19.3212 22.5349 26.1705 + 28.4085 + + k = 0.3750 0.1250 0.6250 ( 174 PWs) bands (ev): + + 10.3493 11.6766 12.1579 13.2575 14.1339 15.9186 24.3093 29.8491 + 32.9693 + + k =-0.1250-0.8750 0.1250 ( 176 PWs) bands (ev): + + 10.2090 10.8957 13.6527 14.1097 14.5846 17.0385 25.1835 26.4722 + 30.1022 + + k =-0.3750 0.3750 0.3750 ( 174 PWs) bands (ev): + + 9.3306 12.6014 12.6014 12.6765 14.2264 14.2264 23.2891 36.8996 + 39.3685 + + k = 0.3750-0.3750 1.1250 ( 176 PWs) bands (ev): + + 10.9698 11.5109 12.2799 13.2468 14.2186 18.1064 21.5401 27.3703 + 34.3960 + + the Fermi energy is 14.2874 ev + +! total energy = -85.89698931 Ry + Harris-Foulkes estimate = -85.89698931 Ry + estimated scf accuracy < 1.3E-09 Ry + + The total energy is the sum of the following terms: + + one-electron contribution = -2.06436173 Ry + hartree contribution = 15.23370153 Ry + xc contribution = -30.12053187 Ry + ewald contribution = -68.94529435 Ry + smearing contrib. (-TS) = -0.00050289 Ry + + total magnetization = 0.71 Bohr mag/cell + absolute magnetization = 0.80 Bohr mag/cell + + convergence has been achieved in 11 iterations + + Forces acting on atoms (cartesian axes, Ry/au): + + atom 1 type 1 force = 0.00000000 0.00000000 0.00000000 + + Total force = 0.000000 Total SCF correction = 0.000000 + + Writing output data file /home/giannozz/q-e-mio/tempdir/nickel.save/ + + init_run : 0.09s CPU 0.09s WALL ( 1 calls) + electrons : 0.48s CPU 0.53s WALL ( 1 calls) + forces : 0.01s CPU 0.01s WALL ( 1 calls) + + Called by init_run: + wfcinit : 0.01s CPU 0.01s WALL ( 1 calls) + potinit : 0.01s CPU 0.01s WALL ( 1 calls) + hinit0 : 0.06s CPU 0.06s WALL ( 1 calls) + + Called by electrons: + c_bands : 0.27s CPU 0.30s WALL ( 11 calls) + sum_band : 0.13s CPU 0.13s WALL ( 11 calls) + v_of_rho : 0.05s CPU 0.05s WALL ( 12 calls) + newd : 0.03s CPU 0.04s WALL ( 12 calls) + mix_rho : 0.01s CPU 0.01s WALL ( 11 calls) + + Called by c_bands: + init_us_2 : 0.01s CPU 0.01s WALL ( 480 calls) + cegterg : 0.25s CPU 0.28s WALL ( 220 calls) + + Called by sum_band: + sum_band:bec : 0.00s CPU 0.00s WALL ( 220 calls) + addusdens : 0.08s CPU 0.08s WALL ( 11 calls) + + Called by *egterg: + h_psi : 0.18s CPU 0.20s WALL ( 617 calls) + s_psi : 0.00s CPU 0.00s WALL ( 617 calls) + g_psi : 0.00s CPU 0.00s WALL ( 377 calls) + cdiaghg : 0.05s CPU 0.05s WALL ( 597 calls) + + Called by h_psi: + h_psi:calbec : 0.01s CPU 0.01s WALL ( 617 calls) + vloc_psi : 0.16s CPU 0.18s WALL ( 617 calls) + add_vuspsi : 0.00s CPU 0.01s WALL ( 617 calls) + + General routines + calbec : 0.01s CPU 0.01s WALL ( 917 calls) + fft : 0.03s CPU 0.03s WALL ( 313 calls) + ffts : 0.00s CPU 0.00s WALL ( 46 calls) + fftw : 0.18s CPU 0.20s WALL ( 11200 calls) + interpolate : 0.00s CPU 0.00s WALL ( 24 calls) + + Parallel routines + fft_scatt_xy : 0.03s CPU 0.03s WALL ( 11559 calls) + fft_scatt_yz : 0.11s CPU 0.12s WALL ( 11559 calls) + + PWSCF : 0.84s CPU 0.93s WALL + + + This run was terminated on: 9:46:10 19Mar2020 + +=------------------------------------------------------------------------------= + JOB DONE. +=------------------------------------------------------------------------------= diff --git a/PHonon/examples/example13/run_example b/PHonon/examples/example13/run_example new file mode 100755 index 000000000..aa3ea78ba --- /dev/null +++ b/PHonon/examples/example13/run_example @@ -0,0 +1,139 @@ +#!/bin/sh + +# run from directory where this script is +cd `echo $0 | sed 's/\(.*\)\/.*/\1/'` # extract pathname +EXAMPLE_DIR=`pwd` + +# check whether ECHO has the -e option +if test "`echo -e`" = "-e" ; then ECHO=echo ; else ECHO="echo -e" ; fi + +$ECHO +$ECHO "$EXAMPLE_DIR : starting" +$ECHO +$ECHO "This example shows how to use pw.x and ph.x to calculate phonon" +$ECHO "dispersions for spin-polarized fcc-Ni." + +# set the needed environment variables +. ../../../environment_variables +# required executables and pseudopotentials +BIN_LIST="pw.x ph.x" +PSEUDO_LIST="Ni.pbe-nd-rrkjus.UPF" + +$ECHO +$ECHO " executables directory: $BIN_DIR" +$ECHO " pseudo directory: $PSEUDO_DIR" +$ECHO " temporary directory: $TMP_DIR" +$ECHO +$ECHO " checking that needed directories and files exist...\c" + +# check for directories +for DIR in "$BIN_DIR" "$PSEUDO_DIR" ; do + if test ! -d $DIR ; then + $ECHO + $ECHO "ERROR: $DIR not existent or not a directory" + $ECHO "Aborting" + exit 1 + fi +done +for DIR in "$TMP_DIR" "$EXAMPLE_DIR/results" ; do + if test ! -d $DIR ; then + mkdir $DIR + fi +done +cd $EXAMPLE_DIR/results + +# check for executables +for FILE in $BIN_LIST ; do + if test ! -x $BIN_DIR/$FILE ; then + $ECHO + $ECHO "ERROR: $BIN_DIR/$FILE not existent or not executable" + $ECHO "Aborting" + exit 1 + fi +done + +# check for pseudopotentials +for FILE in $PSEUDO_LIST ; do + if test ! -r $PSEUDO_DIR/$FILE ; then + $ECHO + $ECHO "Downloading $FILE to $PSEUDO_DIR...\c" + $WGET $PSEUDO_DIR/$FILE $NETWORK_PSEUDO/$FILE 2> /dev/null + fi + if test $? != 0; then + $ECHO + $ECHO "ERROR: $PSEUDO_DIR/$FILE not existent or not readable" + $ECHO "Aborting" + exit 1 + fi +done +$ECHO " done" + +# how to run executables +PW_COMMAND="$PARA_PREFIX $BIN_DIR/pw.x $PARA_POSTFIX" +PH_COMMAND="$PARA_PREFIX $BIN_DIR/ph.x $PARA_POSTFIX" +$ECHO +$ECHO " running pw.x as: $PW_COMMAND" +$ECHO " running ph.x as: $PH_COMMAND" +$ECHO + +# clean TMP_DIR +$ECHO " cleaning $TMP_DIR...\c" +rm -rf $TMP_DIR/nickel* +rm -rf $TMP_DIR/_ph0/nickel* +$ECHO " done" + +# self-consistent calculation for Ni with US-PP +cat > ni.scf.in << EOF + &control + calculation='scf' + restart_mode='from_scratch', + tprnfor = .true. + prefix='nickel', + pseudo_dir = '$PSEUDO_DIR/', + outdir='$TMP_DIR/' + / + &system + ibrav=2, celldm(1) =6.65, nat= 1, ntyp= 1, + nspin=2, + starting_magnetization(1)=0.5, + degauss=0.02, + smearing='mv', + occupations='smearing', + ecutwfc =27.0 + ecutrho =300.0 + / + &electrons + conv_thr = 1.0d-8 + mixing_beta = 0.7 + / +ATOMIC_SPECIES + Ni 58.6934 Ni.pbe-nd-rrkjus.UPF +ATOMIC_POSITIONS (alat) + Ni 0.00 0.00 0.00 +K_POINTS AUTOMATIC +4 4 4 1 1 1 +EOF +$ECHO " running the scf calculation for Ni...\c" +$PW_COMMAND < ni.scf.in > ni.scf.out +check_failure $? +$ECHO " done" + +# phonon dispersion calculation +cat > ni.ph.in << EOF +phonons of Ni + &inputph + tr2_ph=1.0d-14, + prefix='nickel', + amass(1)=58.6934, + fildyn='niX.dyn', + outdir='$TMP_DIR/', + ldisp=.true., nq1=4,nq2=4,nq3=4 + / +EOF +$ECHO " running the phonon dispersion calculation for Ni...\c" +$PH_COMMAND < ni.ph.in > ni.ph.out +check_failure $? +$ECHO " done" + +$ECHO +$ECHO "$EXAMPLE_DIR: done" diff --git a/PW/src/print_clock_pw.f90 b/PW/src/print_clock_pw.f90 index 9098200e3..80a6654a6 100644 --- a/PW/src/print_clock_pw.f90 +++ b/PW/src/print_clock_pw.f90 @@ -79,39 +79,96 @@ SUBROUTINE print_clock_pw() WRITE( stdout, '(/5x,"Called by c_bands:")' ) CALL print_clock( 'init_us_2' ) IF ( isolve == 0 ) THEN - IF ( gamma_only ) THEN - CALL print_clock( 'regterg' ) - ELSE - CALL print_clock( 'cegterg' ) - ENDIF + CALL print_clock( 'regterg' ) ; CALL print_clock( 'cegterg' ) ELSE IF (isolve == 1) THEN - IF ( gamma_only ) THEN - CALL print_clock( 'rcgdiagg' ) - ELSE - CALL print_clock( 'ccgdiagg' ) - ENDIF + CALL print_clock( 'rcgdiagg' ) ; CALL print_clock( 'ccgdiagg' ) CALL print_clock( 'wfcrot' ) ELSE IF (isolve == 2) THEN - IF ( gamma_only ) THEN - CALL print_clock( 'ppcg_gamma' ) - ELSE - CALL print_clock( 'ppcg_k' ) - ENDIF + CALL print_clock( 'ppcg_gamma' ) ; CALL print_clock( 'ppcg_k' ) CALL print_clock( 'wfcrot' ) + ELSE IF (isolve == 3) THEN + CALL print_clock( 'paro_gamma' ) ; CALL print_clock( 'paro_k' ) ENDIF ! !IF ( iverbosity > 0) THEN WRITE( stdout, '(/5x,"Called by sum_band:")' ) + CALL print_clock( 'sum_band:weights' ) + CALL print_clock( 'sum_band:loop' ) + CALL print_clock( 'sum_band:buffer' ) + CALL print_clock( 'sum_band:init_us_2' ) + CALL print_clock( 'sum_band:calbec' ) CALL print_clock( 'sum_band:becsum' ) CALL print_clock( 'addusdens' ) !ENDIF ! IF ( isolve == 0 ) THEN WRITE( stdout, '(/5x,"Called by *egterg:")' ) + IF ( gamma_only ) THEN + CALL print_clock( 'rdiaghg' ) + IF ( iverbosity > 0 ) THEN + CALL print_clock( 'regterg:overlap' ) + CALL print_clock( 'regterg:update' ) + CALL print_clock( 'regterg:last' ) + CALL print_clock( 'rdiaghg:choldc' ) + CALL print_clock( 'rdiaghg:inversion' ) + CALL print_clock( 'rdiaghg:paragemm' ) + ENDIF + ELSE + CALL print_clock( 'cdiaghg' ) + IF ( iverbosity > 0 ) THEN + CALL print_clock( 'cegterg:overlap' ) + CALL print_clock( 'cegterg:update' ) + CALL print_clock( 'cegterg:last' ) + CALL print_clock( 'cdiaghg:choldc' ) + CALL print_clock( 'cdiaghg:inversion' ) + CALL print_clock( 'cdiaghg:paragemm' ) + END IF + END IF ELSE IF ( isolve == 1 ) THEN WRITE( stdout, '(/5x,"Called by *cgdiagg:")' ) ELSE IF ( isolve == 2 ) THEN WRITE( stdout, '(/5x,"Called by ppcg_*:")' ) +! IF ( iverbosity > 0 ) THEN + CALL print_clock( 'ppcg:zgemm' ) ; CALL print_clock( 'ppcg:dgemm' ) + CALL print_clock( 'ppcg:hpsi' ) + CALL print_clock( 'ppcg:cholQR' ) + CALL print_clock( 'ppcg:RR' ) + CALL print_clock( 'ppcg:ZTRSM' ) ; CALL print_clock( 'ppcg:DTRSM' ) + CALL print_clock( 'ppcg:lock' ) +! END IF + ELSE IF ( isolve == 3 ) THEN + WRITE( stdout, '(/5x,"Called by paro_*:")' ) +! IF ( iverbosity > 0 ) THEN + CALL print_clock( 'paro:init' ) + CALL print_clock( 'paro:pack' ) + CALL print_clock( 'paro:zero' ) + CALL print_clock( 'paro:mp_bar' ) + CALL print_clock( 'paro:mp_sum' ) + CALL print_clock( 'pcg' ) + CALL print_clock( 'pcg:hs_1psi' ) + CALL print_clock( 'pcg:ortho' ) + CALL print_clock( 'pcg:move' ) + + CALL print_clock( 'rotHSw' ) + CALL print_clock( 'rotHSw:move' ) + CALL print_clock( 'rotHSw:hc' ) + CALL print_clock( 'rotHSw:diag' ) + CALL print_clock( 'rotHSw:evc' ) + CALL print_clock( 'rotHSw:hc:b0' ) ; + CALL print_clock( 'rotHSw:hc:s1' ) ; call print_clock('rotHSw:hc:comp') + CALL print_clock( 'rotHSw:hc:b1' ) ; + CALL print_clock( 'rotHSw:hc:s2' ) ; + CALL print_clock( 'rotHSw:hc:s3' ) ; call print_clock('rotHSw:hc:rs') + CALL print_clock( 'rotHSw:hc:b2' ) ; call print_clock('rotHSw:hc:sy') + CALL print_clock( 'rotHSw:hc:s4' ) ; CALL print_clock('rotHSw:hc:b3' ) + CALL print_clock( 'rotHSw:ev:b0' ) ; + CALL print_clock( 'rotHSw:ev:b3' ) ; call print_clock('rotHSw:ev:bc') + CALL print_clock( 'rotHSw:ev:s5' ) ; + CALL print_clock( 'rotHSw:ev:b4' ) ; call print_clock('rotHSw:ev:comp') + CALL print_clock( 'rotHSw:ev:s6' ) ; + CALL print_clock( 'rotHSw:ev:b5' ) ; call print_clock('rotHSw:ev:sum') + CALL print_clock( 'rotHSw:ev:s7' ) ; CALL print_clock('rotHSw:ev:b6' ) +! END IF END IF ! CALL print_clock( 'h_psi' ) @@ -130,37 +187,6 @@ SUBROUTINE print_clock_pw() CALL print_clock ( 'fwfft_orbital' ) CALL print_clock ( 'v_loc_psir' ) ENDIF - IF ( gamma_only ) THEN - CALL print_clock( 'rdiaghg' ) - IF ( iverbosity > 0 ) THEN - CALL print_clock( 'regterg:overlap' ) - CALL print_clock( 'regterg:update' ) - CALL print_clock( 'regterg:last' ) - CALL print_clock( 'rdiaghg:choldc' ) - CALL print_clock( 'rdiaghg:inversion' ) - CALL print_clock( 'rdiaghg:paragemm' ) - ENDIF - ELSE - CALL print_clock( 'cdiaghg' ) - IF ( iverbosity > 0 ) THEN - CALL print_clock( 'cegterg:overlap' ) - CALL print_clock( 'cegterg:update' ) - CALL print_clock( 'cegterg:last' ) - CALL print_clock( 'cdiaghg:choldc' ) - CALL print_clock( 'cdiaghg:inversion' ) - CALL print_clock( 'cdiaghg:paragemm' ) - END IF - END IF - IF ( isolve == 2 ) THEN -! IF ( iverbosity > 0 ) THEN - CALL print_clock( 'ppcg:zgemm' ) ; CALL print_clock( 'ppcg:dgemm' ) - CALL print_clock( 'ppcg:hpsi' ) - CALL print_clock( 'ppcg:cholQR' ) - CALL print_clock( 'ppcg:RR' ) - CALL print_clock( 'ppcg:ZTRSM' ) ; CALL print_clock( 'ppcg:DTRSM' ) - CALL print_clock( 'ppcg:lock' ) -! END IF - END IF ! WRITE( stdout, '(/5x,"Called by h_psi:")' ) CALL print_clock( 'h_psi:calbec' ) diff --git a/PW/src/sum_band.f90 b/PW/src/sum_band.f90 index a5c679ca6..5f98af1b7 100644 --- a/PW/src/sum_band.f90 +++ b/PW/src/sum_band.f90 @@ -78,7 +78,9 @@ SUBROUTINE sum_band() ! ! ... calculates weights of Kohn-Sham orbitals used in calculation of rho ! + CALL start_clock( 'sum_band:weights' ) CALL weights ( ) + CALL stop_clock( 'sum_band:weights' ) ! IF (one_atom_occupations) CALL new_evc() ! @@ -122,6 +124,7 @@ SUBROUTINE sum_band() ! eband = 0.D0 ! + CALL start_clock( 'sum_band:loop' ) IF ( gamma_only ) THEN ! CALL sum_band_gamma() @@ -131,6 +134,7 @@ SUBROUTINE sum_band() CALL sum_band_k() ! END IF + CALL stop_clock( 'sum_band:loop' ) CALL mp_sum( eband, inter_pool_comm ) CALL mp_sum( eband, inter_bgrp_comm ) ! @@ -185,6 +189,7 @@ SUBROUTINE sum_band() ! ! ... symmetrize rho(G) ! + CALL start_clock( 'sum_band:sym_rho' ) CALL sym_rho ( nspin_mag, rho%of_g ) ! ! ... synchronize rho%of_r to the calculated rho%of_g (use psic as work array) @@ -222,6 +227,7 @@ SUBROUTINE sum_band() END DO ! END IF + CALL stop_clock( 'sum_band:sym_rho' ) ! ! ... if LSDA rho%of_r and rho%of_g are converted from (up,dw) to ! ... (up+dw,up-dw) format. @@ -286,13 +292,21 @@ SUBROUTINE sum_band() ! npw = ngk(ik) ! + CALL start_clock( 'sum_band:buffer' ) IF ( nks > 1 ) & CALL get_buffer ( evc, nwordwfc, iunwfc, ik ) + IF ( nks > 1 ) CALL using_evc(1) ! get_buffer(evc, ...) evc is updated (intent out) + + CALL stop_clock( 'sum_band:buffer' ) + ! + CALL start_clock( 'sum_band:init_us_2' ) ! IF ( nkb > 0 ) CALL using_vkb(1) + ! IF ( nkb > 0 ) & CALL init_us_2( npw, igk_k(1,ik), xk(1,ik), vkb ) + CALL stop_clock( 'sum_band:init_us_2' ) ! ! ... here we compute the band energy: the sum of the eigenvalues ! @@ -548,13 +562,20 @@ SUBROUTINE sum_band() IF ( lsda ) current_spin = isk(ik) npw = ngk (ik) ! + CALL start_clock( 'sum_band:buffer' ) IF ( nks > 1 ) & CALL get_buffer ( evc, nwordwfc, iunwfc, ik ) IF ( nks > 1 ) CALL using_evc(1) + + CALL stop_clock( 'sum_band:buffer' ) + ! + CALL start_clock( 'sum_band:init_us_2' ) ! IF ( nkb > 0 ) CALL using_vkb(1) + IF ( nkb > 0 ) & CALL init_us_2( npw, igk_k(1,ik), xk(1,ik), vkb ) + CALL stop_clock( 'sum_band:init_us_2' ) ! ! ... here we compute the band energy: the sum of the eigenvalues ! @@ -926,6 +947,7 @@ SUBROUTINE sum_bec ( ik, current_spin, ibnd_start, ibnd_end, this_bgrp_nbnd ) CALL using_indv_ijkb0(0) CALL using_becp_auto(2) ! + CALL start_clock( 'sum_band:calbec' ) npw = ngk(ik) IF ( .NOT. real_space ) THEN ! calbec computes becp = @@ -947,6 +969,7 @@ SUBROUTINE sum_bec ( ik, current_spin, ibnd_start, ibnd_end, this_bgrp_nbnd ) call mp_sum(becp%k,inter_bgrp_comm) endif ENDIF + CALL stop_clock( 'sum_band:calbec' ) ! ! In the EXX case with ultrasoft or PAW, a copy of becp will be ! saved in a global variable to be rotated later diff --git a/PW/src/sum_band_gpu.f90 b/PW/src/sum_band_gpu.f90 index 618dd81e2..705dea755 100644 --- a/PW/src/sum_band_gpu.f90 +++ b/PW/src/sum_band_gpu.f90 @@ -84,7 +84,9 @@ SUBROUTINE sum_band_gpu() ! ! ... calculates weights of Kohn-Sham orbitals used in calculation of rho ! + CALL start_clock_gpu( 'sum_band:weights' ) CALL weights ( ) + CALL stop_clock_gpu( 'sum_band:weights' ) ! IF (one_atom_occupations) CALL new_evc() ! @@ -128,6 +130,7 @@ SUBROUTINE sum_band_gpu() ! eband = 0.D0 ! + CALL start_clock_gpu( 'sum_band:loop' ) IF ( gamma_only ) THEN ! CALL sum_band_gamma_gpu() @@ -137,6 +140,7 @@ SUBROUTINE sum_band_gpu() CALL sum_band_k_gpu() ! END IF + CALL stop_clock_gpu( 'sum_band:loop' ) CALL mp_sum( eband, inter_pool_comm ) CALL mp_sum( eband, inter_bgrp_comm ) ! @@ -193,6 +197,7 @@ SUBROUTINE sum_band_gpu() ! ! ... symmetrize rho(G) ! + CALL start_clock_gpu( 'sum_band:sym_rho' ) CALL sym_rho ( nspin_mag, rho%of_g ) ! ! ... synchronize rho%of_r to the calculated rho%of_g (use psic as work array) @@ -230,6 +235,7 @@ SUBROUTINE sum_band_gpu() END DO ! END IF + CALL stop_clock_gpu( 'sum_band:sym_rho' ) ! ! ... if LSDA rho%of_r and rho%of_g are converted from (up,dw) to ! ... (up+dw,up-dw) format. @@ -247,8 +253,7 @@ SUBROUTINE sum_band_gpu() !----------------------------------------------------------------------- SUBROUTINE sum_band_gamma_gpu() !----------------------------------------------------------------------- - ! - ! ... gamma version + !! \(\texttt{sum_band}\) - part for gamma version. ! USE becmod, ONLY : becp USE mp_bands, ONLY : me_bgrp @@ -309,13 +314,19 @@ SUBROUTINE sum_band_gpu() ! npw = ngk(ik) ! + CALL start_clock_gpu( 'sum_band:buffer' ) IF ( nks > 1 ) & CALL get_buffer ( evc, nwordwfc, iunwfc, ik ) IF ( nks > 1 ) CALL using_evc(2) ! get_buffer(evc, ...) evc is updated (intent out) IF ( nks > 1 ) CALL using_evc_d(0) ! sync on the GPU ! + CALL stop_clock_gpu( 'sum_band:buffer' ) + ! + CALL start_clock_gpu( 'sum_band:init_us_2' ) + IF ( nkb > 0 ) CALL using_vkb_d(2) IF ( nkb > 0 ) CALL init_us_2_gpu( npw, igk_k_d(1,ik), xk(1,ik), vkb_d ) + CALL stop_clock_gpu( 'sum_band:init_us_2' ) ! ! ... here we compute the band energy: the sum of the eigenvalues ! @@ -523,8 +534,7 @@ SUBROUTINE sum_band_gpu() !----------------------------------------------------------------------- SUBROUTINE sum_band_k_gpu() !----------------------------------------------------------------------- - ! - ! ... k-points version + !! \(\texttt{sum_band}\) - part for k-points version ! USE wavefunctions_gpum, ONLY : psic_nc_d USE mp_bands, ONLY : me_bgrp @@ -611,14 +621,18 @@ SUBROUTINE sum_band_gpu() IF ( lsda ) current_spin = isk(ik) npw = ngk (ik) ! + CALL start_clock_gpu( 'sum_band:buffer' ) IF ( nks > 1 ) & CALL get_buffer ( evc, nwordwfc, iunwfc, ik ) IF ( nks > 1 ) CALL using_evc(2) IF ( nks > 1 ) CALL using_evc_d(0) ! sync evc on GPU, OPTIMIZE (use async here) + CALL stop_clock_gpu( 'sum_band:buffer' ) ! + CALL start_clock_gpu( 'sum_band:init_us_2' ) IF ( nkb > 0 ) CALL using_vkb_d(2) IF ( nkb > 0 ) & CALL init_us_2_gpu( npw, igk_k_d(1,ik), xk(1,ik), vkb_d ) + CALL stop_clock_gpu( 'sum_band:init_us_2' ) ! ! ... here we compute the band energy: the sum of the eigenvalues ! @@ -996,13 +1010,15 @@ END SUBROUTINE sum_band_gpu SUBROUTINE sum_bec_gpu ( ik, current_spin, ibnd_start, ibnd_end, this_bgrp_nbnd ) !---------------------------------------------------------------------------- ! - ! This routine computes the sum over bands - ! \sum_i <\psi_i|\beta_l>w_i<\beta_m|\psi_i> - ! for point "ik" and, for LSDA, spin "current_spin" - ! Calls calbec to compute "becp"= - ! Output is accumulated (unsymmetrized) into "becsum", module "uspp" + !! This routine computes the sum over bands: ! - ! Routine used in sum_band (if okvan) and in compute_becsum, called by hinit1 (if okpaw) + !! \[ \sum_i \langle\psi_i|\beta_l\rangle w_i \langle\beta_m|\psi_i\rangle \] + ! + !! for point "ik" and, for LSDA, spin "current_spin". + !! Calls calbec to compute \(\text{"becp"}=\langle \beta_m|\psi_i \rangle\). + !! Output is accumulated (unsymmetrized) into "becsum", module "uspp". + ! + !! Routine used in sum_band (if okvan) and in compute_becsum, called by hinit1 (if okpaw). ! #if defined(__CUDA) USE cudafor @@ -1064,6 +1080,7 @@ SUBROUTINE sum_bec_gpu ( ik, current_spin, ibnd_start, ibnd_end, this_bgrp_nbnd CALL using_becsum_d(1) IF (tqr) CALL using_ebecsum_d(1) ! + CALL start_clock_gpu( 'sum_band:calbec' ) npw = ngk(ik) IF ( .NOT. real_space ) THEN CALL using_evc_d(0); CALL using_vkb_d(0); CALL using_becp_d_auto(2) @@ -1087,6 +1104,7 @@ SUBROUTINE sum_bec_gpu ( ik, current_spin, ibnd_start, ibnd_end, this_bgrp_nbnd call mp_sum(becp%k,inter_bgrp_comm) endif ENDIF + CALL stop_clock_gpu( 'sum_band:calbec' ) ! ! In the EXX case with ultrasoft or PAW, a copy of becp will be ! saved in a global variable to be rotated later @@ -1277,10 +1295,9 @@ END SUBROUTINE sum_bec_gpu !---------------------------------------------------------------------------- SUBROUTINE add_becsum_nc_gpu ( na, np, becsum_nc_d, becsum_d ) !---------------------------------------------------------------------------- - ! - ! This routine multiplies becsum_nc by the identity and the Pauli matrices, - ! saves it in becsum for the calculation of augmentation charge and - ! magnetization. + !! This routine multiplies \(\text{becsum_nc}\) by the identity and the + !! Pauli matrices, saves it in \(\text{becsum}\) for the calculation of + !! augmentation charge and magnetization. ! #if defined(__CUDA) USE cudafor @@ -1340,10 +1357,9 @@ END SUBROUTINE add_becsum_nc_gpu !---------------------------------------------------------------------------- SUBROUTINE add_becsum_so_gpu( na, np, becsum_nc_d, becsum_d ) !---------------------------------------------------------------------------- - ! - ! This routine multiplies becsum_nc by the identity and the Pauli matrices, - ! rotates it as appropriate for the spin-orbit case, saves it in becsum - ! for the calculation of augmentation charge and magnetization. + !! This routine multiplies \(\text{becsum_nc}\) by the identity and the Pauli + !! matrices, rotates it as appropriate for the spin-orbit case, saves it in + !! \(\text{becsum}\) for the calculation of augmentation charge and magnetization. ! #if defined(__CUDA) USE cudafor diff --git a/UtilXlib/clocks_handler.f90 b/UtilXlib/clocks_handler.f90 index fafa33ba9..e589e09c4 100644 --- a/UtilXlib/clocks_handler.f90 +++ b/UtilXlib/clocks_handler.f90 @@ -92,9 +92,10 @@ SUBROUTINE init_clocks( go ) ! ... go = .FALSE. : only clock #1 will run ! USE util_param, ONLY : DP, stdout - USE mytime, ONLY : called, gpu_called, t0cpu, cputime, no, notrunning, maxclock, & - clock_label, walltime, t0wall, gputime, nclock, mpi_per_thread - USE mytime, ONLY : gpu_starts, gpu_stops + USE mytime, ONLY : called, t0cpu, cputime, no, notrunning, maxclock, & + clock_label, walltime, t0wall, nclock, mpi_per_thread + ! ... GPU related timers + USE mytime, ONLY : gpu_starts, gpu_stops, gpu_called, gputime #if defined (__TRACE) USE mytime, ONLY : mpime, max_print_depth, MPI_COMM_WORLD #endif @@ -373,7 +374,7 @@ SUBROUTINE stop_clock( label ) RETURN ! END SUBROUTINE stop_clock - +! SUBROUTINE stop_clock_gpu( label ) !---------------------------------------------------------------------------- ! @@ -405,6 +406,10 @@ SUBROUTINE stop_clock_gpu( label ) ! IF ( no ) RETURN ! + ! ... initialize time used in CUDA APIs if __CUDA is present. + ! + time = 0.0 + ! ! ... prevent trouble if label is longer than 12 characters ! label_ = trim ( label ) @@ -457,7 +462,7 @@ SUBROUTINE print_clock( label ) !---------------------------------------------------------------------------- ! USE util_param, ONLY : stdout - USE mytime, ONLY : nclock, clock_label + USE mytime, ONLY : nclock, clock_label, gpu_called ! IMPLICIT NONE ! @@ -465,6 +470,9 @@ SUBROUTINE print_clock( label ) ! CHARACTER(len=12) :: label_ INTEGER :: n + LOGICAL :: print_gpu + ! + print_gpu = ANY(gpu_called > 0) ! IF ( label == ' ' ) THEN ! @@ -473,7 +481,7 @@ SUBROUTINE print_clock( label ) DO n = 1, nclock ! CALL print_this_clock( n ) - CALL print_this_clock_gpu( n ) + IF(print_gpu) CALL print_this_clock_gpu( n ) ! ENDDO ! @@ -488,7 +496,7 @@ SUBROUTINE print_clock( label ) IF ( clock_label(n) == label_ ) THEN ! CALL print_this_clock( n ) - CALL print_this_clock_gpu( n ) + IF(print_gpu) CALL print_this_clock_gpu( n ) ! exit ! diff --git a/test-suite/jobconfig b/test-suite/jobconfig index a1b0392e1..23e3549c6 100644 --- a/test-suite/jobconfig +++ b/test-suite/jobconfig @@ -56,7 +56,7 @@ inputs_args = ('c.scf.in', '1'), ('c.phG.in', '2'), ('ni.scf.in', '1'), ('ni.phX [ph_metal/] program = PH -inputs_args = ('al.scf.fit.in', '1'), ('al.scf.in', '1'), ('al.elph.in', '2'), ('q2r.in', '3'), ('matdyn.in.freq', '4'), ('matdyn.in.dos', '4'), ('lambda.in', '5') +inputs_args = ('al.scf.fit.in', '1'), ('al.scf.in', '1'), ('al.elph.in', '2'), ('al.elph.notrans.in', '2'), ('q2r.in', '3'), ('matdyn.in.freq', '4'), ('matdyn.in.dos', '4'), ('lambda.in', '5') [ph_U_metal_us/] program = PH diff --git a/test-suite/not_epw_comp/elphon.f90 b/test-suite/not_epw_comp/elphon.f90 index adacbb124..72edb06a0 100644 --- a/test-suite/not_epw_comp/elphon.f90 +++ b/test-suite/not_epw_comp/elphon.f90 @@ -13,7 +13,7 @@ SUBROUTINE elphon() ! Electron-phonon calculation from data saved in fildvscf ! USE kinds, ONLY : DP - USE constants, ONLY : amu_ry + USE constants, ONLY : amu_ry, RY_TO_THZ, RY_TO_CMM1 USE cell_base, ONLY : celldm, omega, ibrav, at, bg USE ions_base, ONLY : nat, ntyp => nsp, ityp, tau, amass USE gvecs, ONLY: doublegrid @@ -51,7 +51,7 @@ SUBROUTINE elphon() COMPLEX(DP), allocatable :: phip (:, :, :, :) INTEGER :: ntyp_, nat_, ibrav_, nspin_mag_, mu, nu, na, nb, nta, ntb, nqs_ - REAL(DP) :: celldm_(6) + REAL(DP) :: celldm_(6), w1 CHARACTER(LEN=3) :: atm(ntyp) CALL start_clock ('elphon') @@ -166,9 +166,27 @@ SUBROUTINE elphon() deallocate( phip ) ENDIF - ENDIF + ! + ! Write phonon frequency to stdout + ! + WRITE( stdout, 8000) (xq (i), i = 1, 3) + ! + DO nu = 1, 3 * nat + w1 = SQRT( ABS( w2(nu) ) ) + if (w2(nu) < 0.d0) w1 = - w1 + WRITE( stdout, 8010) nu, w1 * RY_TO_THZ, w1 * RY_TO_CMM1 + ENDDO + ! + WRITE( stdout, '(1x,74("*"))') + ! + ENDIF ! .NOT. trans ! CALL stop_clock ('elphon') + ! +8000 FORMAT(/,5x,'Diagonalizing the dynamical matrix', & + & //,5x,'q = ( ',3f14.9,' ) ',//,1x,74('*')) +8010 FORMAT (5x,'freq (',i5,') =',f15.6,' [THz] =',f15.6,' [cm-1]') + ! RETURN END SUBROUTINE elphon ! diff --git a/test-suite/ph_U_metal_us/Fe.scf.in b/test-suite/ph_U_metal_us/Fe.scf.in index 6cb79807e..fd03b5e74 100644 --- a/test-suite/ph_U_metal_us/Fe.scf.in +++ b/test-suite/ph_U_metal_us/Fe.scf.in @@ -25,6 +25,7 @@ Hubbard_U(1) = 2.0 / &electrons + startingwfc = 'atomic' conv_thr = 1.d-14 mixing_beta = 0.3 / diff --git a/test-suite/ph_metal/al.elph.notrans.in b/test-suite/ph_metal/al.elph.notrans.in new file mode 100644 index 000000000..55d57e8a3 --- /dev/null +++ b/test-suite/ph_metal/al.elph.notrans.in @@ -0,0 +1,15 @@ +Electron-phonon coefficients for Al + &inputph + tr2_ph=1.0d-10, + prefix='aluminum', + fildvscf='aldv', + amass(1)=26.98, + outdir='./', + fildyn='al.dyn', + electron_phonon='interpolated', + el_ph_sigma=0.005, + el_ph_nsigma=10, + trans=.false., + ldisp=.true. + nq1=4, nq2=4, nq3=4 + / diff --git a/test-suite/ph_metal/benchmark.out.git.inp=al.elph.notrans.in.args=2 b/test-suite/ph_metal/benchmark.out.git.inp=al.elph.notrans.in.args=2 new file mode 100644 index 000000000..b2f67dc55 --- /dev/null +++ b/test-suite/ph_metal/benchmark.out.git.inp=al.elph.notrans.in.args=2 @@ -0,0 +1,1912 @@ + + Program PHONON v.6.5 starts on 20Mar2020 at 14:53:48 + + This program is part of the open-source Quantum ESPRESSO suite + for quantum simulation of materials; please cite + "P. Giannozzi et al., J. Phys.:Condens. Matter 21 395502 (2009); + "P. Giannozzi et al., J. Phys.:Condens. Matter 29 465901 (2017); + URL http://www.quantum-espresso.org", + in publications or presentations arising from this work. More details at + http://www.quantum-espresso.org/quote + + Parallel version (MPI), running on 1 processors + + MPI processes distributed on 1 nodes + + Reading xml data from directory: + + ./aluminum.save/ + Message from routine qexsd_readschema : + input info not found or not readable in xml file + + IMPORTANT: XC functional enforced from input : + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + Any further DFT definition will be discarded + Please, verify this is what you really want + + + G-vector sticks info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Sum 121 121 43 869 869 181 + + Reading collected, re-writing distributed wavefunctions + + + Dynamical matrices for ( 4, 4, 4) uniform grid of q-points + ( 8 q-points): + N xq(1) xq(2) xq(3) + 1 0.000000000 0.000000000 0.000000000 + 2 -0.250000000 0.250000000 -0.250000000 + 3 0.500000000 -0.500000000 0.500000000 + 4 0.000000000 0.500000000 0.000000000 + 5 0.750000000 -0.250000000 0.750000000 + 6 0.500000000 0.000000000 0.500000000 + 7 0.000000000 -1.000000000 0.000000000 + 8 -0.500000000 -1.000000000 0.000000000 + + Calculation of q = 0.0000000 0.0000000 0.0000000 + + Electron-phonon coefficients for Al + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 15.0000 Ry + charge density cut-off = 60.0000 Ry + convergence threshold = 1.0E-10 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + + celldm(1)= 7.50000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Al 26.9800 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.0000000 0.0000000 0.0000000 ) + + 49 Sym.Ops. (with q -> -q+G ) + + + G cutoff = 85.4897 ( 869 G-vectors) FFT grid: ( 15, 15, 15) + + number of k points= 29 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + Mode symmetry, O_h (m-3m) point group: + + + Atomic displacements: + There are 1 irreducible representations + + Representation 1 3 modes -T_1u G_15 G_4- To be done + + + PHONON : 0.15s CPU 0.16s WALL + + Reading dVscf from file aldv + Reading dynamics matrix from file al.dyn1 + + Diagonalizing the dynamical matrix + + q = ( 0.000000000 0.000000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 0.169231 [THz] = 5.644932 [cm-1] + freq ( 2) = 0.169231 [THz] = 5.644932 [cm-1] + freq ( 3) = 0.169231 [THz] = 5.644932 [cm-1] + ************************************************************************** + electron-phonon interaction ... + + Gaussian Broadening: 0.005 Ry, ngauss= 0 + DOS = 1.339210 states/spin/Ry/Unit Cell at Ef= 8.321794 eV + lambda( 1)= 0.0000 gamma= 0.00 GHz + lambda( 2)= 0.0000 gamma= 0.00 GHz + lambda( 3)= 0.0000 gamma= 0.00 GHz + Gaussian Broadening: 0.010 Ry, ngauss= 0 + DOS = 1.881761 states/spin/Ry/Unit Cell at Ef= 8.327154 eV + lambda( 1)= 0.0000 gamma= 0.00 GHz + lambda( 2)= 0.0000 gamma= 0.00 GHz + lambda( 3)= 0.0000 gamma= 0.00 GHz + Gaussian Broadening: 0.015 Ry, ngauss= 0 + DOS = 2.123229 states/spin/Ry/Unit Cell at Ef= 8.328622 eV + lambda( 1)= 0.0000 gamma= 0.00 GHz + lambda( 2)= 0.0000 gamma= 0.00 GHz + lambda( 3)= 0.0000 gamma= 0.00 GHz + Gaussian Broadening: 0.020 Ry, ngauss= 0 + DOS = 2.249739 states/spin/Ry/Unit Cell at Ef= 8.324320 eV + lambda( 1)= 0.0000 gamma= 0.03 GHz + lambda( 2)= 0.0000 gamma= 0.03 GHz + lambda( 3)= 0.0000 gamma= 0.03 GHz + Gaussian Broadening: 0.025 Ry, ngauss= 0 + DOS = 2.329803 states/spin/Ry/Unit Cell at Ef= 8.317862 eV + lambda( 1)= 0.0000 gamma= 0.09 GHz + lambda( 2)= 0.0000 gamma= 0.09 GHz + lambda( 3)= 0.0000 gamma= 0.09 GHz + Gaussian Broadening: 0.030 Ry, ngauss= 0 + DOS = 2.396029 states/spin/Ry/Unit Cell at Ef= 8.311297 eV + lambda( 1)= 0.0000 gamma= 0.17 GHz + lambda( 2)= 0.0000 gamma= 0.17 GHz + lambda( 3)= 0.0000 gamma= 0.17 GHz + Gaussian Broadening: 0.035 Ry, ngauss= 0 + DOS = 2.455226 states/spin/Ry/Unit Cell at Ef= 8.305263 eV + lambda( 1)= 0.0000 gamma= 0.26 GHz + lambda( 2)= 0.0000 gamma= 0.26 GHz + lambda( 3)= 0.0000 gamma= 0.26 GHz + Gaussian Broadening: 0.040 Ry, ngauss= 0 + DOS = 2.507873 states/spin/Ry/Unit Cell at Ef= 8.299956 eV + lambda( 1)= 0.0000 gamma= 0.37 GHz + lambda( 2)= 0.0000 gamma= 0.37 GHz + lambda( 3)= 0.0000 gamma= 0.37 GHz + Gaussian Broadening: 0.045 Ry, ngauss= 0 + DOS = 2.552966 states/spin/Ry/Unit Cell at Ef= 8.295412 eV + lambda( 1)= 0.0000 gamma= 0.49 GHz + lambda( 2)= 0.0000 gamma= 0.49 GHz + lambda( 3)= 0.0000 gamma= 0.49 GHz + Gaussian Broadening: 0.050 Ry, ngauss= 0 + DOS = 2.589582 states/spin/Ry/Unit Cell at Ef= 8.291554 eV + lambda( 1)= 0.0000 gamma= 0.63 GHz + lambda( 2)= 0.0000 gamma= 0.63 GHz + lambda( 3)= 0.0000 gamma= 0.63 GHz + + + Number of q in the star = 1 + List of q in the star: + 1 0.000000000 0.000000000 0.000000000 + + Calculation of q = -0.2500000 0.2500000 -0.2500000 + + Subspace diagonalization in iterative solution of the eigenvalue problem: + a serial algorithm will be used + + + G-vector sticks info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Sum 121 121 55 869 869 259 + + + Title: + Electron-phonon coefficients for Al + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 3.00 + number of Kohn-Sham states= 6 + kinetic-energy cutoff = 15.0000 Ry + charge density cutoff = 60.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + celldm(1)= 7.500000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + atomic species valence mass pseudopotential + Al 3.00 26.98000 Al( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Al tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 240 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 869 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 0.53 MB + + The potential is recalculated from file : + ./_ph0/aluminum.q_2/aluminum.save/charge-density + + Starting wfcs are 4 atomic + 2 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 3.33E-10, avg # of iterations = 13.6 + + total cpu time spent up to now is 2.2 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 8.1776 ev + + Writing output data file ./_ph0/aluminum.q_2/aluminum.save/ + + Electron-phonon coefficients for Al + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 15.0000 Ry + charge density cut-off = 60.0000 Ry + convergence threshold = 1.0E-10 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + + celldm(1)= 7.50000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Al 26.9800 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( -0.2500000 0.2500000 -0.2500000 ) + + 6 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 85.4897 ( 869 G-vectors) FFT grid: ( 15, 15, 15) + + number of k points= 240 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + Mode symmetry, C_3v (3m) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_1 L_1 To be done + + Representation 2 2 modes -E L_3 To be done + + + PHONON : 3.43s CPU 3.54s WALL + + Reading dVscf from file aldv + Reading dynamics matrix from file al.dyn2 + + Diagonalizing the dynamical matrix + + q = ( -0.250000000 0.250000000 -0.250000000 ) + + ************************************************************************** + freq ( 1) = 3.512865 [THz] = 117.176558 [cm-1] + freq ( 2) = 3.512865 [THz] = 117.176558 [cm-1] + freq ( 3) = 6.337242 [THz] = 211.387635 [cm-1] + ************************************************************************** + electron-phonon interaction ... + + Gaussian Broadening: 0.005 Ry, ngauss= 0 + DOS = 1.339210 states/spin/Ry/Unit Cell at Ef= 8.321794 eV + lambda( 1)= 0.0022 gamma= 0.04 GHz + lambda( 2)= 0.0023 gamma= 0.04 GHz + lambda( 3)= 0.0285 gamma= 1.47 GHz + Gaussian Broadening: 0.010 Ry, ngauss= 0 + DOS = 1.881761 states/spin/Ry/Unit Cell at Ef= 8.327154 eV + lambda( 1)= 0.0202 gamma= 0.45 GHz + lambda( 2)= 0.0209 gamma= 0.46 GHz + lambda( 3)= 0.2322 gamma= 16.75 GHz + Gaussian Broadening: 0.015 Ry, ngauss= 0 + DOS = 2.123229 states/spin/Ry/Unit Cell at Ef= 8.328622 eV + lambda( 1)= 0.0248 gamma= 0.62 GHz + lambda( 2)= 0.0253 gamma= 0.63 GHz + lambda( 3)= 0.2281 gamma= 18.57 GHz + Gaussian Broadening: 0.020 Ry, ngauss= 0 + DOS = 2.249739 states/spin/Ry/Unit Cell at Ef= 8.324320 eV + lambda( 1)= 0.0284 gamma= 0.75 GHz + lambda( 2)= 0.0282 gamma= 0.75 GHz + lambda( 3)= 0.2029 gamma= 17.50 GHz + Gaussian Broadening: 0.025 Ry, ngauss= 0 + DOS = 2.329803 states/spin/Ry/Unit Cell at Ef= 8.317862 eV + lambda( 1)= 0.0326 gamma= 0.89 GHz + lambda( 2)= 0.0321 gamma= 0.88 GHz + lambda( 3)= 0.1883 gamma= 16.82 GHz + Gaussian Broadening: 0.030 Ry, ngauss= 0 + DOS = 2.396029 states/spin/Ry/Unit Cell at Ef= 8.311297 eV + lambda( 1)= 0.0371 gamma= 1.05 GHz + lambda( 2)= 0.0366 gamma= 1.03 GHz + lambda( 3)= 0.1845 gamma= 16.96 GHz + Gaussian Broadening: 0.035 Ry, ngauss= 0 + DOS = 2.455226 states/spin/Ry/Unit Cell at Ef= 8.305263 eV + lambda( 1)= 0.0416 gamma= 1.20 GHz + lambda( 2)= 0.0410 gamma= 1.19 GHz + lambda( 3)= 0.1880 gamma= 17.70 GHz + Gaussian Broadening: 0.040 Ry, ngauss= 0 + DOS = 2.507873 states/spin/Ry/Unit Cell at Ef= 8.299956 eV + lambda( 1)= 0.0459 gamma= 1.36 GHz + lambda( 2)= 0.0452 gamma= 1.34 GHz + lambda( 3)= 0.1957 gamma= 18.82 GHz + Gaussian Broadening: 0.045 Ry, ngauss= 0 + DOS = 2.552966 states/spin/Ry/Unit Cell at Ef= 8.295412 eV + lambda( 1)= 0.0498 gamma= 1.50 GHz + lambda( 2)= 0.0489 gamma= 1.47 GHz + lambda( 3)= 0.2053 gamma= 20.10 GHz + Gaussian Broadening: 0.050 Ry, ngauss= 0 + DOS = 2.589582 states/spin/Ry/Unit Cell at Ef= 8.291554 eV + lambda( 1)= 0.0532 gamma= 1.62 GHz + lambda( 2)= 0.0521 gamma= 1.59 GHz + lambda( 3)= 0.2153 gamma= 21.39 GHz + + + Number of q in the star = 8 + List of q in the star: + 1 -0.250000000 0.250000000 -0.250000000 + 2 0.250000000 -0.250000000 -0.250000000 + 3 0.250000000 -0.250000000 0.250000000 + 4 0.250000000 0.250000000 0.250000000 + 5 -0.250000000 -0.250000000 -0.250000000 + 6 -0.250000000 -0.250000000 0.250000000 + 7 -0.250000000 0.250000000 0.250000000 + 8 0.250000000 0.250000000 -0.250000000 + + Calculation of q = 0.5000000 -0.5000000 0.5000000 + + G-vector sticks info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Sum 121 121 61 869 869 331 + + + Title: + Electron-phonon coefficients for Al + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 3.00 + number of Kohn-Sham states= 6 + kinetic-energy cutoff = 15.0000 Ry + charge density cutoff = 60.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + celldm(1)= 7.500000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + atomic species valence mass pseudopotential + Al 3.00 26.98000 Al( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Al tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 130 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 869 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 0.53 MB + + The potential is recalculated from file : + ./_ph0/aluminum.q_3/aluminum.save/charge-density + + Starting wfcs are 4 atomic + 2 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 3.33E-10, avg # of iterations = 13.8 + + total cpu time spent up to now is 3.4 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 8.1776 ev + + Writing output data file ./_ph0/aluminum.q_3/aluminum.save/ + + Electron-phonon coefficients for Al + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 15.0000 Ry + charge density cut-off = 60.0000 Ry + convergence threshold = 1.0E-10 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + + celldm(1)= 7.50000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Al 26.9800 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.5000000 -0.5000000 0.5000000 ) + + 13 Sym.Ops. (with q -> -q+G ) + + + G cutoff = 85.4897 ( 869 G-vectors) FFT grid: ( 15, 15, 15) + + number of k points= 130 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + Mode symmetry, D_3d (-3m) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_2u L_2' To be done + + Representation 2 2 modes -E_u L_3' To be done + + + PHONON : 6.13s CPU 6.30s WALL + + Reading dVscf from file aldv + Reading dynamics matrix from file al.dyn3 + + Diagonalizing the dynamical matrix + + q = ( 0.500000000 -0.500000000 0.500000000 ) + + ************************************************************************** + freq ( 1) = 4.438808 [THz] = 148.062713 [cm-1] + freq ( 2) = 4.438808 [THz] = 148.062713 [cm-1] + freq ( 3) = 9.422660 [THz] = 314.306122 [cm-1] + ************************************************************************** + electron-phonon interaction ... + + Gaussian Broadening: 0.005 Ry, ngauss= 0 + DOS = 1.339210 states/spin/Ry/Unit Cell at Ef= 8.321794 eV + lambda( 1)= 0.0000 gamma= 0.00 GHz + lambda( 2)= 0.0000 gamma= 0.00 GHz + lambda( 3)= 0.0000 gamma= 0.00 GHz + Gaussian Broadening: 0.010 Ry, ngauss= 0 + DOS = 1.881761 states/spin/Ry/Unit Cell at Ef= 8.327154 eV + lambda( 1)= 0.0293 gamma= 1.04 GHz + lambda( 2)= 0.0263 gamma= 0.93 GHz + lambda( 3)= 0.0398 gamma= 6.36 GHz + Gaussian Broadening: 0.015 Ry, ngauss= 0 + DOS = 2.123229 states/spin/Ry/Unit Cell at Ef= 8.328622 eV + lambda( 1)= 0.0674 gamma= 2.69 GHz + lambda( 2)= 0.0610 gamma= 2.44 GHz + lambda( 3)= 0.1003 gamma= 18.06 GHz + Gaussian Broadening: 0.020 Ry, ngauss= 0 + DOS = 2.249739 states/spin/Ry/Unit Cell at Ef= 8.324320 eV + lambda( 1)= 0.0786 gamma= 3.33 GHz + lambda( 2)= 0.0723 gamma= 3.06 GHz + lambda( 3)= 0.1262 gamma= 24.07 GHz + Gaussian Broadening: 0.025 Ry, ngauss= 0 + DOS = 2.329803 states/spin/Ry/Unit Cell at Ef= 8.317862 eV + lambda( 1)= 0.0833 gamma= 3.65 GHz + lambda( 2)= 0.0785 gamma= 3.44 GHz + lambda( 3)= 0.1412 gamma= 27.90 GHz + Gaussian Broadening: 0.030 Ry, ngauss= 0 + DOS = 2.396029 states/spin/Ry/Unit Cell at Ef= 8.311297 eV + lambda( 1)= 0.0860 gamma= 3.88 GHz + lambda( 2)= 0.0829 gamma= 3.74 GHz + lambda( 3)= 0.1501 gamma= 30.49 GHz + Gaussian Broadening: 0.035 Ry, ngauss= 0 + DOS = 2.455226 states/spin/Ry/Unit Cell at Ef= 8.305263 eV + lambda( 1)= 0.0876 gamma= 4.05 GHz + lambda( 2)= 0.0860 gamma= 3.97 GHz + lambda( 3)= 0.1550 gamma= 32.26 GHz + Gaussian Broadening: 0.040 Ry, ngauss= 0 + DOS = 2.507873 states/spin/Ry/Unit Cell at Ef= 8.299956 eV + lambda( 1)= 0.0888 gamma= 4.19 GHz + lambda( 2)= 0.0884 gamma= 4.17 GHz + lambda( 3)= 0.1582 gamma= 33.65 GHz + Gaussian Broadening: 0.045 Ry, ngauss= 0 + DOS = 2.552966 states/spin/Ry/Unit Cell at Ef= 8.295412 eV + lambda( 1)= 0.0898 gamma= 4.31 GHz + lambda( 2)= 0.0903 gamma= 4.34 GHz + lambda( 3)= 0.1608 gamma= 34.80 GHz + Gaussian Broadening: 0.050 Ry, ngauss= 0 + DOS = 2.589582 states/spin/Ry/Unit Cell at Ef= 8.291554 eV + lambda( 1)= 0.0904 gamma= 4.41 GHz + lambda( 2)= 0.0916 gamma= 4.46 GHz + lambda( 3)= 0.1628 gamma= 35.73 GHz + + + Number of q in the star = 4 + List of q in the star: + 1 0.500000000 -0.500000000 0.500000000 + 2 0.500000000 0.500000000 0.500000000 + 3 -0.500000000 0.500000000 0.500000000 + 4 0.500000000 0.500000000 -0.500000000 + + Calculation of q = 0.0000000 0.5000000 0.0000000 + + G-vector sticks info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Sum 121 121 55 869 869 259 + + + Title: + Electron-phonon coefficients for Al + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 3.00 + number of Kohn-Sham states= 6 + kinetic-energy cutoff = 15.0000 Ry + charge density cutoff = 60.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + celldm(1)= 7.500000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + atomic species valence mass pseudopotential + Al 3.00 26.98000 Al( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Al tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 200 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 869 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 0.53 MB + + The potential is recalculated from file : + ./_ph0/aluminum.q_4/aluminum.save/charge-density + + Starting wfcs are 4 atomic + 2 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 3.33E-10, avg # of iterations = 13.3 + + total cpu time spent up to now is 5.3 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 8.1776 ev + + Writing output data file ./_ph0/aluminum.q_4/aluminum.save/ + + Electron-phonon coefficients for Al + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 15.0000 Ry + charge density cut-off = 60.0000 Ry + convergence threshold = 1.0E-10 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + + celldm(1)= 7.50000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Al 26.9800 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.0000000 0.5000000 0.0000000 ) + + 8 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 85.4897 ( 869 G-vectors) FFT grid: ( 15, 15, 15) + + number of k points= 200 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + Mode symmetry, C_4v (4mm) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_1 G_1 D_1 To be done + + Representation 2 2 modes -E G_5 D_5 To be done + + + PHONON : 9.16s CPU 9.42s WALL + + Reading dVscf from file aldv + Reading dynamics matrix from file al.dyn4 + + Diagonalizing the dynamical matrix + + q = ( 0.000000000 0.500000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 4.200502 [THz] = 140.113680 [cm-1] + freq ( 2) = 4.200502 [THz] = 140.113680 [cm-1] + freq ( 3) = 6.475071 [THz] = 215.985116 [cm-1] + ************************************************************************** + electron-phonon interaction ... + + Gaussian Broadening: 0.005 Ry, ngauss= 0 + DOS = 1.339210 states/spin/Ry/Unit Cell at Ef= 8.321794 eV + lambda( 1)= 0.0004 gamma= 0.01 GHz + lambda( 2)= 0.0004 gamma= 0.01 GHz + lambda( 3)= 0.0021 gamma= 0.11 GHz + Gaussian Broadening: 0.010 Ry, ngauss= 0 + DOS = 1.881761 states/spin/Ry/Unit Cell at Ef= 8.327154 eV + lambda( 1)= 0.0592 gamma= 1.88 GHz + lambda( 2)= 0.0592 gamma= 1.88 GHz + lambda( 3)= 0.0611 gamma= 4.60 GHz + Gaussian Broadening: 0.015 Ry, ngauss= 0 + DOS = 2.123229 states/spin/Ry/Unit Cell at Ef= 8.328622 eV + lambda( 1)= 0.1026 gamma= 3.67 GHz + lambda( 2)= 0.1026 gamma= 3.67 GHz + lambda( 3)= 0.0896 gamma= 7.62 GHz + Gaussian Broadening: 0.020 Ry, ngauss= 0 + DOS = 2.249739 states/spin/Ry/Unit Cell at Ef= 8.324320 eV + lambda( 1)= 0.1110 gamma= 4.21 GHz + lambda( 2)= 0.1110 gamma= 4.21 GHz + lambda( 3)= 0.1116 gamma= 10.05 GHz + Gaussian Broadening: 0.025 Ry, ngauss= 0 + DOS = 2.329803 states/spin/Ry/Unit Cell at Ef= 8.317862 eV + lambda( 1)= 0.1149 gamma= 4.51 GHz + lambda( 2)= 0.1149 gamma= 4.51 GHz + lambda( 3)= 0.1428 gamma= 13.32 GHz + Gaussian Broadening: 0.030 Ry, ngauss= 0 + DOS = 2.396029 states/spin/Ry/Unit Cell at Ef= 8.311297 eV + lambda( 1)= 0.1209 gamma= 4.88 GHz + lambda( 2)= 0.1209 gamma= 4.88 GHz + lambda( 3)= 0.1730 gamma= 16.60 GHz + Gaussian Broadening: 0.035 Ry, ngauss= 0 + DOS = 2.455226 states/spin/Ry/Unit Cell at Ef= 8.305263 eV + lambda( 1)= 0.1285 gamma= 5.32 GHz + lambda( 2)= 0.1285 gamma= 5.32 GHz + lambda( 3)= 0.1968 gamma= 19.34 GHz + Gaussian Broadening: 0.040 Ry, ngauss= 0 + DOS = 2.507873 states/spin/Ry/Unit Cell at Ef= 8.299956 eV + lambda( 1)= 0.1365 gamma= 5.77 GHz + lambda( 2)= 0.1365 gamma= 5.77 GHz + lambda( 3)= 0.2146 gamma= 21.55 GHz + Gaussian Broadening: 0.045 Ry, ngauss= 0 + DOS = 2.552966 states/spin/Ry/Unit Cell at Ef= 8.295412 eV + lambda( 1)= 0.1438 gamma= 6.18 GHz + lambda( 2)= 0.1438 gamma= 6.18 GHz + lambda( 3)= 0.2282 gamma= 23.33 GHz + Gaussian Broadening: 0.050 Ry, ngauss= 0 + DOS = 2.589582 states/spin/Ry/Unit Cell at Ef= 8.291554 eV + lambda( 1)= 0.1498 gamma= 6.54 GHz + lambda( 2)= 0.1498 gamma= 6.54 GHz + lambda( 3)= 0.2386 gamma= 24.74 GHz + + + Number of q in the star = 6 + List of q in the star: + 1 0.000000000 0.500000000 0.000000000 + 2 0.000000000 -0.500000000 0.000000000 + 3 0.500000000 0.000000000 0.000000000 + 4 0.000000000 0.000000000 0.500000000 + 5 0.000000000 0.000000000 -0.500000000 + 6 -0.500000000 0.000000000 0.000000000 + + Calculation of q = 0.7500000 -0.2500000 0.7500000 + + G-vector sticks info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Sum 121 121 61 869 869 339 + + + Title: + Electron-phonon coefficients for Al + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 3.00 + number of Kohn-Sham states= 6 + kinetic-energy cutoff = 15.0000 Ry + charge density cutoff = 60.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + celldm(1)= 7.500000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + atomic species valence mass pseudopotential + Al 3.00 26.98000 Al( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Al tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 576 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 869 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 0.53 MB + + The potential is recalculated from file : + ./_ph0/aluminum.q_5/aluminum.save/charge-density + + Starting wfcs are 4 atomic + 2 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 3.33E-10, avg # of iterations = 13.4 + + total cpu time spent up to now is 10.5 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 8.1776 ev + + Writing output data file ./_ph0/aluminum.q_5/aluminum.save/ + + Electron-phonon coefficients for Al + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 15.0000 Ry + charge density cut-off = 60.0000 Ry + convergence threshold = 1.0E-10 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + + celldm(1)= 7.50000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Al 26.9800 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.7500000 -0.2500000 0.7500000 ) + + 2 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 85.4897 ( 869 G-vectors) FFT grid: ( 15, 15, 15) + + number of k points= 576 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + Mode symmetry, C_s (m) point group: + + + Atomic displacements: + There are 3 irreducible representations + + Representation 1 1 modes -A' To be done + + Representation 2 1 modes -A' To be done + + Representation 3 1 modes -A'' To be done + + + PHONON : 15.67s CPU 16.14s WALL + + Reading dVscf from file aldv + Reading dynamics matrix from file al.dyn5 + + Diagonalizing the dynamical matrix + + q = ( 0.750000000 -0.250000000 0.750000000 ) + + ************************************************************************** + freq ( 1) = 5.392366 [THz] = 179.869983 [cm-1] + freq ( 2) = 6.718298 [THz] = 224.098299 [cm-1] + freq ( 3) = 8.795520 [THz] = 293.386982 [cm-1] + ************************************************************************** + electron-phonon interaction ... + + Gaussian Broadening: 0.005 Ry, ngauss= 0 + DOS = 1.339210 states/spin/Ry/Unit Cell at Ef= 8.321794 eV + lambda( 1)= 0.0085 gamma= 0.32 GHz + lambda( 2)= 0.0210 gamma= 1.21 GHz + lambda( 3)= 0.0283 gamma= 2.80 GHz + Gaussian Broadening: 0.010 Ry, ngauss= 0 + DOS = 1.881761 states/spin/Ry/Unit Cell at Ef= 8.327154 eV + lambda( 1)= 0.0619 gamma= 3.23 GHz + lambda( 2)= 0.1348 gamma= 10.93 GHz + lambda( 3)= 0.2010 gamma= 27.94 GHz + Gaussian Broadening: 0.015 Ry, ngauss= 0 + DOS = 2.123229 states/spin/Ry/Unit Cell at Ef= 8.328622 eV + lambda( 1)= 0.0789 gamma= 4.65 GHz + lambda( 2)= 0.1335 gamma= 12.22 GHz + lambda( 3)= 0.2252 gamma= 35.33 GHz + Gaussian Broadening: 0.020 Ry, ngauss= 0 + DOS = 2.249739 states/spin/Ry/Unit Cell at Ef= 8.324320 eV + lambda( 1)= 0.0855 gamma= 5.34 GHz + lambda( 2)= 0.1171 gamma= 11.35 GHz + lambda( 3)= 0.2246 gamma= 37.33 GHz + Gaussian Broadening: 0.025 Ry, ngauss= 0 + DOS = 2.329803 states/spin/Ry/Unit Cell at Ef= 8.317862 eV + lambda( 1)= 0.0864 gamma= 5.59 GHz + lambda( 2)= 0.1046 gamma= 10.50 GHz + lambda( 3)= 0.2162 gamma= 37.21 GHz + Gaussian Broadening: 0.030 Ry, ngauss= 0 + DOS = 2.396029 states/spin/Ry/Unit Cell at Ef= 8.311297 eV + lambda( 1)= 0.0867 gamma= 5.77 GHz + lambda( 2)= 0.0976 gamma= 10.08 GHz + lambda( 3)= 0.2084 gamma= 36.88 GHz + Gaussian Broadening: 0.035 Ry, ngauss= 0 + DOS = 2.455226 states/spin/Ry/Unit Cell at Ef= 8.305263 eV + lambda( 1)= 0.0876 gamma= 5.97 GHz + lambda( 2)= 0.0945 gamma= 10.00 GHz + lambda( 3)= 0.2035 gamma= 36.92 GHz + Gaussian Broadening: 0.040 Ry, ngauss= 0 + DOS = 2.507873 states/spin/Ry/Unit Cell at Ef= 8.299956 eV + lambda( 1)= 0.0889 gamma= 6.19 GHz + lambda( 2)= 0.0938 gamma= 10.14 GHz + lambda( 3)= 0.2015 gamma= 37.33 GHz + Gaussian Broadening: 0.045 Ry, ngauss= 0 + DOS = 2.552966 states/spin/Ry/Unit Cell at Ef= 8.295412 eV + lambda( 1)= 0.0904 gamma= 6.41 GHz + lambda( 2)= 0.0943 gamma= 10.38 GHz + lambda( 3)= 0.2014 gamma= 37.98 GHz + Gaussian Broadening: 0.050 Ry, ngauss= 0 + DOS = 2.589582 states/spin/Ry/Unit Cell at Ef= 8.291554 eV + lambda( 1)= 0.0918 gamma= 6.60 GHz + lambda( 2)= 0.0955 gamma= 10.66 GHz + lambda( 3)= 0.2023 gamma= 38.70 GHz + + + Number of q in the star = 24 + List of q in the star: + 1 0.750000000 -0.250000000 0.750000000 + 2 0.750000000 -0.250000000 -0.750000000 + 3 -0.750000000 -0.250000000 -0.750000000 + 4 -0.750000000 -0.250000000 0.750000000 + 5 -0.750000000 0.250000000 -0.750000000 + 6 -0.250000000 0.750000000 -0.750000000 + 7 -0.750000000 0.750000000 -0.250000000 + 8 0.750000000 0.250000000 0.750000000 + 9 -0.750000000 0.250000000 0.750000000 + 10 0.750000000 0.250000000 -0.750000000 + 11 -0.750000000 0.750000000 0.250000000 + 12 -0.250000000 0.750000000 0.750000000 + 13 0.250000000 0.750000000 -0.750000000 + 14 -0.250000000 -0.750000000 -0.750000000 + 15 0.750000000 0.750000000 -0.250000000 + 16 0.750000000 -0.750000000 0.250000000 + 17 -0.750000000 -0.750000000 -0.250000000 + 18 0.250000000 -0.750000000 0.750000000 + 19 -0.750000000 -0.750000000 0.250000000 + 20 0.250000000 0.750000000 0.750000000 + 21 -0.250000000 -0.750000000 0.750000000 + 22 0.750000000 0.750000000 0.250000000 + 23 0.250000000 -0.750000000 -0.750000000 + 24 0.750000000 -0.750000000 -0.250000000 + + Calculation of q = 0.5000000 0.0000000 0.5000000 + + G-vector sticks info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Sum 121 121 61 869 869 307 + + + Title: + Electron-phonon coefficients for Al + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 3.00 + number of Kohn-Sham states= 6 + kinetic-energy cutoff = 15.0000 Ry + charge density cutoff = 60.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + celldm(1)= 7.500000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + atomic species valence mass pseudopotential + Al 3.00 26.98000 Al( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Al tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 328 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 869 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 0.53 MB + + The potential is recalculated from file : + ./_ph0/aluminum.q_6/aluminum.save/charge-density + + Starting wfcs are 4 atomic + 2 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 3.33E-10, avg # of iterations = 13.4 + + total cpu time spent up to now is 13.5 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 8.1776 ev + + Writing output data file ./_ph0/aluminum.q_6/aluminum.save/ + + Electron-phonon coefficients for Al + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 15.0000 Ry + charge density cut-off = 60.0000 Ry + convergence threshold = 1.0E-10 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + + celldm(1)= 7.50000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Al 26.9800 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.5000000 0.0000000 0.5000000 ) + + 4 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 85.4897 ( 869 G-vectors) FFT grid: ( 15, 15, 15) + + number of k points= 328 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + Mode symmetry, C_2v (mm2) point group: + + + Atomic displacements: + There are 3 irreducible representations + + Representation 1 1 modes -A_1 D_1 S_1 To be done + + Representation 2 1 modes -B_1 D_3 S_3 To be done + + Representation 3 1 modes -B_2 D_4 S_4 To be done + + + PHONON : 21.09s CPU 21.71s WALL + + Reading dVscf from file aldv + Reading dynamics matrix from file al.dyn6 + + Diagonalizing the dynamical matrix + + q = ( 0.500000000 0.000000000 0.500000000 ) + + ************************************************************************** + freq ( 1) = 4.864117 [THz] = 162.249465 [cm-1] + freq ( 2) = 6.528764 [THz] = 217.776128 [cm-1] + freq ( 3) = 8.467440 [THz] = 282.443411 [cm-1] + ************************************************************************** + electron-phonon interaction ... + + Gaussian Broadening: 0.005 Ry, ngauss= 0 + DOS = 1.339210 states/spin/Ry/Unit Cell at Ef= 8.321794 eV + lambda( 1)= 0.0231 gamma= 0.70 GHz + lambda( 2)= 0.0561 gamma= 3.06 GHz + lambda( 3)= 1.3275 gamma= 121.72 GHz + Gaussian Broadening: 0.010 Ry, ngauss= 0 + DOS = 1.881761 states/spin/Ry/Unit Cell at Ef= 8.327154 eV + lambda( 1)= 0.0651 gamma= 2.77 GHz + lambda( 2)= 0.0805 gamma= 6.17 GHz + lambda( 3)= 0.8798 gamma= 113.35 GHz + Gaussian Broadening: 0.015 Ry, ngauss= 0 + DOS = 2.123229 states/spin/Ry/Unit Cell at Ef= 8.328622 eV + lambda( 1)= 0.0534 gamma= 2.56 GHz + lambda( 2)= 0.1119 gamma= 9.67 GHz + lambda( 3)= 0.5477 gamma= 79.62 GHz + Gaussian Broadening: 0.020 Ry, ngauss= 0 + DOS = 2.249739 states/spin/Ry/Unit Cell at Ef= 8.324320 eV + lambda( 1)= 0.0426 gamma= 2.17 GHz + lambda( 2)= 0.1258 gamma= 11.52 GHz + lambda( 3)= 0.3882 gamma= 59.80 GHz + Gaussian Broadening: 0.025 Ry, ngauss= 0 + DOS = 2.329803 states/spin/Ry/Unit Cell at Ef= 8.317862 eV + lambda( 1)= 0.0364 gamma= 1.91 GHz + lambda( 2)= 0.1254 gamma= 11.90 GHz + lambda( 3)= 0.3071 gamma= 48.99 GHz + Gaussian Broadening: 0.030 Ry, ngauss= 0 + DOS = 2.396029 states/spin/Ry/Unit Cell at Ef= 8.311297 eV + lambda( 1)= 0.0336 gamma= 1.82 GHz + lambda( 2)= 0.1248 gamma= 12.17 GHz + lambda( 3)= 0.2649 gamma= 43.46 GHz + Gaussian Broadening: 0.035 Ry, ngauss= 0 + DOS = 2.455226 states/spin/Ry/Unit Cell at Ef= 8.305263 eV + lambda( 1)= 0.0326 gamma= 1.81 GHz + lambda( 2)= 0.1264 gamma= 12.63 GHz + lambda( 3)= 0.2426 gamma= 40.79 GHz + Gaussian Broadening: 0.040 Ry, ngauss= 0 + DOS = 2.507873 states/spin/Ry/Unit Cell at Ef= 8.299956 eV + lambda( 1)= 0.0325 gamma= 1.84 GHz + lambda( 2)= 0.1291 gamma= 13.18 GHz + lambda( 3)= 0.2302 gamma= 39.53 GHz + Gaussian Broadening: 0.045 Ry, ngauss= 0 + DOS = 2.552966 states/spin/Ry/Unit Cell at Ef= 8.295412 eV + lambda( 1)= 0.0328 gamma= 1.89 GHz + lambda( 2)= 0.1319 gamma= 13.71 GHz + lambda( 3)= 0.2225 gamma= 38.89 GHz + Gaussian Broadening: 0.050 Ry, ngauss= 0 + DOS = 2.589582 states/spin/Ry/Unit Cell at Ef= 8.291554 eV + lambda( 1)= 0.0332 gamma= 1.94 GHz + lambda( 2)= 0.1343 gamma= 14.15 GHz + lambda( 3)= 0.2170 gamma= 38.48 GHz + + + Number of q in the star = 12 + List of q in the star: + 1 0.500000000 0.000000000 0.500000000 + 2 -0.500000000 0.000000000 0.500000000 + 3 -0.500000000 0.000000000 -0.500000000 + 4 0.500000000 0.000000000 -0.500000000 + 5 0.000000000 0.500000000 -0.500000000 + 6 -0.500000000 0.500000000 0.000000000 + 7 0.000000000 0.500000000 0.500000000 + 8 0.000000000 -0.500000000 -0.500000000 + 9 0.500000000 0.500000000 0.000000000 + 10 0.500000000 -0.500000000 0.000000000 + 11 -0.500000000 -0.500000000 0.000000000 + 12 0.000000000 -0.500000000 0.500000000 + + Calculation of q = 0.0000000 -1.0000000 0.0000000 + + G-vector sticks info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Sum 121 121 61 869 869 331 + + + Title: + Electron-phonon coefficients for Al + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 3.00 + number of Kohn-Sham states= 6 + kinetic-energy cutoff = 15.0000 Ry + charge density cutoff = 60.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + celldm(1)= 7.500000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + atomic species valence mass pseudopotential + Al 3.00 26.98000 Al( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Al tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 118 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 869 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 0.53 MB + + The potential is recalculated from file : + ./_ph0/aluminum.q_7/aluminum.save/charge-density + + Starting wfcs are 4 atomic + 2 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 3.33E-10, avg # of iterations = 13.2 + + total cpu time spent up to now is 14.6 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 8.1776 ev + + Writing output data file ./_ph0/aluminum.q_7/aluminum.save/ + + Electron-phonon coefficients for Al + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 15.0000 Ry + charge density cut-off = 60.0000 Ry + convergence threshold = 1.0E-10 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + + celldm(1)= 7.50000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Al 26.9800 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( 0.0000000 -1.0000000 0.0000000 ) + + 17 Sym.Ops. (with q -> -q+G ) + + + G cutoff = 85.4897 ( 869 G-vectors) FFT grid: ( 15, 15, 15) + + number of k points= 118 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + Mode symmetry, D_4h(4/mmm) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -A_2u X_4' M_4' To be done + + Representation 2 2 modes -E_u X_5' M_5' To be done + + + PHONON : 23.91s CPU 24.60s WALL + + Reading dVscf from file aldv + Reading dynamics matrix from file al.dyn7 + + Diagonalizing the dynamical matrix + + q = ( 0.000000000 -1.000000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 6.062807 [THz] = 202.233476 [cm-1] + freq ( 2) = 6.062807 [THz] = 202.233476 [cm-1] + freq ( 3) = 9.881161 [THz] = 329.600048 [cm-1] + ************************************************************************** + electron-phonon interaction ... + + Gaussian Broadening: 0.005 Ry, ngauss= 0 + DOS = 1.339210 states/spin/Ry/Unit Cell at Ef= 8.321794 eV + lambda( 1)= 0.0244 gamma= 1.15 GHz + lambda( 2)= 0.0244 gamma= 1.15 GHz + lambda( 3)= 0.0002 gamma= 0.02 GHz + Gaussian Broadening: 0.010 Ry, ngauss= 0 + DOS = 1.881761 states/spin/Ry/Unit Cell at Ef= 8.327154 eV + lambda( 1)= 0.1841 gamma= 12.16 GHz + lambda( 2)= 0.1841 gamma= 12.16 GHz + lambda( 3)= 0.0906 gamma= 15.89 GHz + Gaussian Broadening: 0.015 Ry, ngauss= 0 + DOS = 2.123229 states/spin/Ry/Unit Cell at Ef= 8.328622 eV + lambda( 1)= 0.1730 gamma= 12.89 GHz + lambda( 2)= 0.1728 gamma= 12.88 GHz + lambda( 3)= 0.1863 gamma= 36.88 GHz + Gaussian Broadening: 0.020 Ry, ngauss= 0 + DOS = 2.249739 states/spin/Ry/Unit Cell at Ef= 8.324320 eV + lambda( 1)= 0.1524 gamma= 12.03 GHz + lambda( 2)= 0.1518 gamma= 11.99 GHz + lambda( 3)= 0.2008 gamma= 42.11 GHz + Gaussian Broadening: 0.025 Ry, ngauss= 0 + DOS = 2.329803 states/spin/Ry/Unit Cell at Ef= 8.317862 eV + lambda( 1)= 0.1402 gamma= 11.47 GHz + lambda( 2)= 0.1392 gamma= 11.38 GHz + lambda( 3)= 0.1846 gamma= 40.11 GHz + Gaussian Broadening: 0.030 Ry, ngauss= 0 + DOS = 2.396029 states/spin/Ry/Unit Cell at Ef= 8.311297 eV + lambda( 1)= 0.1319 gamma= 11.09 GHz + lambda( 2)= 0.1306 gamma= 10.98 GHz + lambda( 3)= 0.1656 gamma= 37.00 GHz + Gaussian Broadening: 0.035 Ry, ngauss= 0 + DOS = 2.455226 states/spin/Ry/Unit Cell at Ef= 8.305263 eV + lambda( 1)= 0.1255 gamma= 10.81 GHz + lambda( 2)= 0.1241 gamma= 10.69 GHz + lambda( 3)= 0.1526 gamma= 34.93 GHz + Gaussian Broadening: 0.040 Ry, ngauss= 0 + DOS = 2.507873 states/spin/Ry/Unit Cell at Ef= 8.299956 eV + lambda( 1)= 0.1206 gamma= 10.62 GHz + lambda( 2)= 0.1191 gamma= 10.48 GHz + lambda( 3)= 0.1459 gamma= 34.11 GHz + Gaussian Broadening: 0.045 Ry, ngauss= 0 + DOS = 2.552966 states/spin/Ry/Unit Cell at Ef= 8.295412 eV + lambda( 1)= 0.1171 gamma= 10.49 GHz + lambda( 2)= 0.1155 gamma= 10.35 GHz + lambda( 3)= 0.1431 gamma= 34.07 GHz + Gaussian Broadening: 0.050 Ry, ngauss= 0 + DOS = 2.589582 states/spin/Ry/Unit Cell at Ef= 8.291554 eV + lambda( 1)= 0.1147 gamma= 10.43 GHz + lambda( 2)= 0.1130 gamma= 10.27 GHz + lambda( 3)= 0.1425 gamma= 34.40 GHz + + + Number of q in the star = 3 + List of q in the star: + 1 0.000000000 -1.000000000 0.000000000 + 2 -1.000000000 0.000000000 0.000000000 + 3 0.000000000 0.000000000 -1.000000000 + + Calculation of q = -0.5000000 -1.0000000 0.0000000 + + G-vector sticks info + -------------------- + sticks: dense smooth PW G-vecs: dense smooth PW + Sum 121 121 61 869 869 331 + + + Title: + Electron-phonon coefficients for Al + + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + number of electrons = 3.00 + number of Kohn-Sham states= 6 + kinetic-energy cutoff = 15.0000 Ry + charge density cutoff = 60.0000 Ry + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + celldm(1)= 7.500000 celldm(2)= 0.000000 celldm(3)= 0.000000 + celldm(4)= 0.000000 celldm(5)= 0.000000 celldm(6)= 0.000000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.500000 0.000000 0.500000 ) + a(2) = ( 0.000000 0.500000 0.500000 ) + a(3) = ( -0.500000 0.500000 0.000000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.000000 -1.000000 1.000000 ) + b(2) = ( 1.000000 1.000000 1.000000 ) + b(3) = ( -1.000000 1.000000 -1.000000 ) + + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + atomic species valence mass pseudopotential + Al 3.00 26.98000 Al( 1.00) + + 48 Sym. Ops., with inversion, found + + + + Cartesian axes + + site n. atom positions (alat units) + 1 Al tau( 1) = ( 0.0000000 0.0000000 0.0000000 ) + + number of k points= 174 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + Number of k-points >= 100: set verbosity='high' to print them. + + Dense grid: 869 G-vectors FFT dimensions: ( 15, 15, 15) + + Estimated max dynamical RAM per process > 0.53 MB + + The potential is recalculated from file : + ./_ph0/aluminum.q_8/aluminum.save/charge-density + + Starting wfcs are 4 atomic + 2 random wfcs + + Band Structure Calculation + Davidson diagonalization with overlap + + ethr = 3.33E-10, avg # of iterations = 13.3 + + total cpu time spent up to now is 16.2 secs + + End of band structure calculation + + Number of k-points >= 100: set verbosity='high' to print the bands. + + the Fermi energy is 8.1776 ev + + Writing output data file ./_ph0/aluminum.q_8/aluminum.save/ + + Electron-phonon coefficients for Al + + bravais-lattice index = 2 + lattice parameter (alat) = 7.5000 a.u. + unit-cell volume = 105.4688 (a.u.)^3 + number of atoms/cell = 1 + number of atomic types = 1 + kinetic-energy cut-off = 15.0000 Ry + charge density cut-off = 60.0000 Ry + convergence threshold = 1.0E-10 + beta = 0.7000 + number of iterations used = 4 + Exchange-correlation= PZ + ( 1 1 0 0 0 0 0) + + + celldm(1)= 7.50000 celldm(2)= 0.00000 celldm(3)= 0.00000 + celldm(4)= 0.00000 celldm(5)= 0.00000 celldm(6)= 0.00000 + + crystal axes: (cart. coord. in units of alat) + a(1) = ( -0.5000 0.0000 0.5000 ) + a(2) = ( 0.0000 0.5000 0.5000 ) + a(3) = ( -0.5000 0.5000 0.0000 ) + + reciprocal axes: (cart. coord. in units 2 pi/alat) + b(1) = ( -1.0000 -1.0000 1.0000 ) + b(2) = ( 1.0000 1.0000 1.0000 ) + b(3) = ( -1.0000 1.0000 -1.0000 ) + + + Atoms inside the unit cell: + + Cartesian axes + + site n. atom mass positions (alat units) + 1 Al 26.9800 tau( 1) = ( 0.00000 0.00000 0.00000 ) + + Computing dynamical matrix for + q = ( -0.5000000 -1.0000000 0.0000000 ) + + 8 Sym.Ops. (no q -> -q+G ) + + + G cutoff = 85.4897 ( 869 G-vectors) FFT grid: ( 15, 15, 15) + + number of k points= 174 Marzari-Vanderbilt smearing, width (Ry)= 0.0500 + + PseudoPot. # 1 for Al read from file: + ./Al.pz-vbc.UPF + MD5 check sum: f06ceae8da0fe5c02c98e3688433298c + Pseudo is Norm-conserving, Zval = 3.0 + Generated by new atomic code, or converted to UPF format + Using radial grid of 171 points, 2 beta functions with: + l(1) = 0 + l(2) = 1 + + Mode symmetry, D_2d (-42m) point group: + + + Atomic displacements: + There are 2 irreducible representations + + Representation 1 1 modes -B_2 X_3 W_2 To be done + + Representation 2 2 modes -E X_5 W_3 To be done + + + PHONON : 26.66s CPU 27.42s WALL + + Reading dVscf from file aldv + Reading dynamics matrix from file al.dyn8 + + Diagonalizing the dynamical matrix + + q = ( -0.500000000 -1.000000000 0.000000000 ) + + ************************************************************************** + freq ( 1) = 6.453902 [THz] = 215.278984 [cm-1] + freq ( 2) = 7.608435 [THz] = 253.790089 [cm-1] + freq ( 3) = 7.608435 [THz] = 253.790089 [cm-1] + ************************************************************************** + electron-phonon interaction ... + + Gaussian Broadening: 0.005 Ry, ngauss= 0 + DOS = 1.339210 states/spin/Ry/Unit Cell at Ef= 8.321794 eV + lambda( 1)= 0.0002 gamma= 0.01 GHz + lambda( 2)= 0.0004 gamma= 0.03 GHz + lambda( 3)= 0.0004 gamma= 0.03 GHz + Gaussian Broadening: 0.010 Ry, ngauss= 0 + DOS = 1.881761 states/spin/Ry/Unit Cell at Ef= 8.327154 eV + lambda( 1)= 0.0336 gamma= 2.51 GHz + lambda( 2)= 0.0634 gamma= 6.60 GHz + lambda( 3)= 0.0634 gamma= 6.60 GHz + Gaussian Broadening: 0.015 Ry, ngauss= 0 + DOS = 2.123229 states/spin/Ry/Unit Cell at Ef= 8.328622 eV + lambda( 1)= 0.0693 gamma= 5.85 GHz + lambda( 2)= 0.1079 gamma= 12.67 GHz + lambda( 3)= 0.1080 gamma= 12.68 GHz + Gaussian Broadening: 0.020 Ry, ngauss= 0 + DOS = 2.249739 states/spin/Ry/Unit Cell at Ef= 8.324320 eV + lambda( 1)= 0.0748 gamma= 6.69 GHz + lambda( 2)= 0.1141 gamma= 14.19 GHz + lambda( 3)= 0.1147 gamma= 14.27 GHz + Gaussian Broadening: 0.025 Ry, ngauss= 0 + DOS = 2.329803 states/spin/Ry/Unit Cell at Ef= 8.317862 eV + lambda( 1)= 0.0727 gamma= 6.74 GHz + lambda( 2)= 0.1154 gamma= 14.86 GHz + lambda( 3)= 0.1166 gamma= 15.01 GHz + Gaussian Broadening: 0.030 Ry, ngauss= 0 + DOS = 2.396029 states/spin/Ry/Unit Cell at Ef= 8.311297 eV + lambda( 1)= 0.0706 gamma= 6.73 GHz + lambda( 2)= 0.1196 gamma= 15.83 GHz + lambda( 3)= 0.1210 gamma= 16.02 GHz + Gaussian Broadening: 0.035 Ry, ngauss= 0 + DOS = 2.455226 states/spin/Ry/Unit Cell at Ef= 8.305263 eV + lambda( 1)= 0.0701 gamma= 6.84 GHz + lambda( 2)= 0.1268 gamma= 17.20 GHz + lambda( 3)= 0.1282 gamma= 17.40 GHz + Gaussian Broadening: 0.040 Ry, ngauss= 0 + DOS = 2.507873 states/spin/Ry/Unit Cell at Ef= 8.299956 eV + lambda( 1)= 0.0711 gamma= 7.09 GHz + lambda( 2)= 0.1359 gamma= 18.84 GHz + lambda( 3)= 0.1374 gamma= 19.05 GHz + Gaussian Broadening: 0.045 Ry, ngauss= 0 + DOS = 2.552966 states/spin/Ry/Unit Cell at Ef= 8.295412 eV + lambda( 1)= 0.0731 gamma= 7.43 GHz + lambda( 2)= 0.1455 gamma= 20.53 GHz + lambda( 3)= 0.1469 gamma= 20.73 GHz + Gaussian Broadening: 0.050 Ry, ngauss= 0 + DOS = 2.589582 states/spin/Ry/Unit Cell at Ef= 8.291554 eV + lambda( 1)= 0.0756 gamma= 7.79 GHz + lambda( 2)= 0.1542 gamma= 22.07 GHz + lambda( 3)= 0.1556 gamma= 22.28 GHz + + + Number of q in the star = 6 + List of q in the star: + 1 -0.500000000 -1.000000000 0.000000000 + 2 0.000000000 1.000000000 0.500000000 + 3 0.000000000 -1.000000000 -0.500000000 + 4 0.500000000 1.000000000 0.000000000 + 5 -1.000000000 -0.500000000 0.000000000 + 6 0.000000000 -0.500000000 -1.000000000 + + init_run : 0.06s CPU 0.06s WALL ( 7 calls) + electrons : 15.38s CPU 15.93s WALL ( 7 calls) + + Called by init_run: + wfcinit : 0.00s CPU 0.00s WALL ( 7 calls) + potinit : 0.00s CPU 0.00s WALL ( 7 calls) + hinit0 : 0.03s CPU 0.03s WALL ( 7 calls) + + Called by electrons: + c_bands : 15.37s CPU 15.92s WALL ( 7 calls) + v_of_rho : 0.00s CPU 0.00s WALL ( 8 calls) + + Called by c_bands: + init_us_2 : 0.09s CPU 0.10s WALL ( 4925 calls) + cegterg : 14.14s CPU 14.61s WALL ( 1845 calls) + + Called by sum_band: + + Called by *egterg: + h_psi : 10.79s CPU 11.03s WALL ( 27346 calls) + g_psi : 0.13s CPU 0.16s WALL ( 23735 calls) + cdiaghg : 2.81s CPU 2.97s WALL ( 25501 calls) + + Called by h_psi: + h_psi:calbec : 0.21s CPU 0.23s WALL ( 27346 calls) + vloc_psi : 10.31s CPU 10.49s WALL ( 27346 calls) + add_vuspsi : 0.16s CPU 0.17s WALL ( 27346 calls) + + General routines + calbec : 0.19s CPU 0.19s WALL ( 30994 calls) + fft : 0.01s CPU 0.01s WALL ( 24 calls) + ffts : 0.11s CPU 0.12s WALL ( 2736 calls) + fftw : 12.09s CPU 12.11s WALL ( 297142 calls) + davcio : 0.03s CPU 0.07s WALL ( 8079 calls) + + Parallel routines + + PHONON : 28.02s CPU 28.79s WALL + + INITIALIZATION: + phq_setup : 0.03s CPU 0.03s WALL ( 8 calls) + phq_init : 0.06s CPU 0.07s WALL ( 8 calls) + + phq_init : 0.06s CPU 0.07s WALL ( 8 calls) + init_vloc : 0.00s CPU 0.00s WALL ( 8 calls) + init_us_1 : 0.02s CPU 0.02s WALL ( 8 calls) + + + + + dvqpsi_us : 1.73s CPU 1.77s WALL ( 2736 calls) + + dvqpsi_us : 1.73s CPU 1.77s WALL ( 2736 calls) + dvqpsi_us_on : 0.08s CPU 0.08s WALL ( 2736 calls) + + + h_psi : 10.79s CPU 11.03s WALL ( 27346 calls) + + h_psi : 10.79s CPU 11.03s WALL ( 27346 calls) + add_vuspsi : 0.16s CPU 0.17s WALL ( 27346 calls) + + + + General routines + calbec : 0.19s CPU 0.19s WALL ( 30994 calls) + fft : 0.01s CPU 0.01s WALL ( 24 calls) + ffts : 0.11s CPU 0.12s WALL ( 2736 calls) + fftw : 12.09s CPU 12.11s WALL ( 297142 calls) + davcio : 0.03s CPU 0.07s WALL ( 8079 calls) + + + PHONON : 28.02s CPU 28.79s WALL + + + This run was terminated on: 14:54:16 20Mar2020 + +=------------------------------------------------------------------------------= + JOB DONE. +=------------------------------------------------------------------------------=