1!
2! Copyright (C) 2001-2018 Quantum ESPRESSO group
3! This file is distributed under the terms of the
4! GNU General Public License. See the file `License'
5! in the root directory of the present distribution,
6! or http://www.gnu.org/copyleft/gpl.txt .
7!
8!
9!-----------------------------------------------------------------------
10SUBROUTINE hp_summary_q
11  !-----------------------------------------------------------------------
12  !
13  ! This routine writes on output the quantities which have been read
14  ! from the punch file, and the quantities computed in hp_setup_q.
15  ! If iverbosity = 1 only a partial summary is done.
16  !
17  USE kinds,         ONLY : DP
18  USE io_global,     ONLY : stdout
19  USE cell_base,     ONLY : at
20  USE klist,         ONLY : lgauss, smearing, degauss, nkstot, xk, wk
21  USE fft_base,      ONLY : dfftp
22  USE gvect,         ONLY : gcutm, ngm
23  USE gvecs,         ONLY : doublegrid, dual, gcutms, ngms
24  USE gvecw,         ONLY : ecutwfc
25  USE fft_base,      ONLY : dffts
26  USE symm_base,     ONLY : s, sr, ft, sname
27  USE funct,         ONLY : write_dft_name
28  USE control_flags, ONLY : iverbosity
29  USE lr_symm_base,  ONLY : irotmq, minus_q, nsymq
30  USE ldaU_hp,       ONLY : conv_thr_chi
31
32  IMPLICIT NONE
33  !
34  INTEGER :: i, ipol, apol, na, nt, isymq, isym, ik, nsymtot
35  ! generic counter
36  ! counter on polarizations
37  ! counter on polarizations
38  ! counter on atoms
39  ! counter on atomic types
40  ! counter on symmetries
41  ! counter on symmetries
42  ! counter on k points
43  !
44  REAL(DP) :: ft1, ft2, ft3, xkg(3)
45  ! fractionary translations
46  ! k point in crystal coordinates
47  !
48  WRITE( stdout, '(/,19x,"WRITING LINEAR-RESPONSE SUMMARY:",/)')
49  !
50  ! Now print the information specific for every q point
51  !
52  ! Description of symmetries for a given q point
53  !
54  IF (nsymq.le.1.and..not.minus_q) THEN
55     WRITE( stdout, '(5x,"No symmetry (except the identity)!")')
56  ELSE
57     WRITE( stdout, '(/5x,"Number of symmetries in the small group of q, nsymq = ",i2)') nsymq
58     IF (minus_q) WRITE( stdout, '(5x," + the symmetry q -> -q+G ")')
59  ENDIF
60  !
61  ! Description of the symmetry matrices (and vectors of fractional
62  ! translations if f/=0) of the small group of q
63  !
64  IF (iverbosity > 1) THEN
65     !
66     WRITE( stdout, '(/5x,"Symmetry matrices (and vectors of fractional translations if f/=0):")')
67     !
68     IF (minus_q) THEN
69        nsymtot = nsymq + 1
70     ELSE
71        nsymtot = nsymq
72     ENDIF
73     !
74     DO isymq = 1, nsymtot
75        !
76        IF (isymq.GT.nsymq) THEN
77           isym = irotmq
78           WRITE( stdout, '(/5x,"This transformation sends q -> -q+G")')
79        ELSE
80           isym = isymq
81        ENDIF
82        !
83        WRITE( stdout, '(/5x,"isym = ",i2,5x,a45/)') isymq, sname (isym)
84        !
85        IF ( ft(1,isym)**2 + ft(2,isym)**2 + ft(3,isym)**2 > 1.0d-8 ) THEN
86           !
87           ft1 = at (1, 1) * ft(1, isym) + &
88                 at (1, 2) * ft(2, isym) + &
89                 at (1, 3) * ft(3, isym)
90           ft2 = at (2, 1) * ft(1, isym) + &
91                 at (2, 2) * ft(2, isym) + &
92                 at (2, 3) * ft(3, isym)
93           ft3 = at (3, 1) * ft(1, isym) + &
94                 at (3, 2) * ft(2, isym) + &
95                 at (3, 3) * ft(3, isym)
96           !
97           WRITE( stdout, '(5x,"cryst.",3x,"s(",i2,") = (",3(i6,5x)," )    f =( ",f10.7," )")') &
98                & isymq, (s(1,ipol,isym), ipol=1,3), ft(1,isym)
99           WRITE( stdout, '(21x," (",3(i6,5x), " )       ( ",f10.7," )")')  &
100                &        (s(2,ipol,isym), ipol=1,3), ft(2,isym)
101           WRITE( stdout, '(21x," (",3(i6,5x)," )       ( ",f10.7," )"/)')  &
102                &        (s(3,ipol,isym), ipol=1,3), ft(3,isym)
103           WRITE( stdout, '(5x,"cart.",4x,"s(",i2,") = (",3f11.7, " )    f =( ",f10.7," )")') &
104                & isymq, (sr(1,ipol,isym), ipol=1,3), ft1
105           WRITE( stdout, '(21x," (",3f11.7, " )       ( ",f10.7," )")')    &
106                &        (sr(2,ipol,isym), ipol=1,3), ft2
107           WRITE( stdout, '(21x," (",3f11.7, " )       ( ",f10.7," )"/)')   &
108                &        (sr(3,ipol,isym), ipol=1,3), ft3
109           !
110        ELSE
111           !
112           WRITE( stdout, '(5x,"cryst.",3x,"s(",i2,") = (",3(i6,5x), " )")') &
113                & isymq,  (s(1,ipol,isym), ipol=1,3)
114           WRITE( stdout, '(21x," (",3(i6,5x)," )")')  &
115                &         (s (2,ipol,isym), ipol=1,3)
116           WRITE( stdout, '(21x," (",3(i6,5x)," )"/)') &
117                &         (s(3,ipol,isym), ipol=1,3)
118           WRITE( stdout, '(5x,"cart.",4x,"s(",i2,") = (",3f11.7, " )")')    &
119               & isymq,   (sr(1,ipol,isym), ipol=1,3)
120           WRITE( stdout, '(21x," (",3f11.7," )")')    &
121               &          (sr(2,ipol,isym), ipol=1,3)
122           WRITE( stdout, '(21x," (",3f11.7," )"/)')   &
123               &          (sr(3,ipol,isym), ipol=1,3)
124           !
125        ENDIF
126        !
127     ENDDO ! isymq
128     !
129  ENDIF
130  !
131  ! Description of the G cutoff and the FFT grid
132  !
133  WRITE( stdout, '(/5x,"G cutoff =",f10.4,"  (",i7," G-vectors)", &
134                 & "     FFT grid: (",i3,",",i3,",",i3,")")')     &
135                 & gcutm, ngm, dfftp%nr1, dfftp%nr2, dfftp%nr3
136  !
137  IF (doublegrid) &
138  WRITE( stdout, '(5x,"G cutoff =",f10.4,"  (", i7," G-vectors)", &
139                & "  smooth grid: (",i3, ",",i3,",",i3,")")')     &
140                & gcutms, ngms, dffts%nr1, dffts%nr2, dffts%nr3
141  !
142  ! Number of k (and k+q if q/=0) points
143  !
144  IF (.NOT.lgauss) THEN
145     WRITE( stdout, '(/5x,"Number of k (and k+q if q/=0) points =",i6,/)') nkstot
146  ELSE
147     WRITE( stdout, '(/5x,"Number of k (and k+q if q/=0) points =", i6, 2x, &
148                   & a," smearing, width (Ry) =",f8.4,/)') &
149                   & nkstot, TRIM(smearing), degauss
150  ENDIF
151  !
152  ! Coordinates of the k (and k+q if q/=0) points
153  !
154  IF ( iverbosity > 1 .OR. (nkstot<100) ) THEN
155     !
156     ! cartesian coordinates
157     !
158     WRITE( stdout, '(23x,"cart. coord. (in units 2pi/alat)")')
159     DO ik = 1, nkstot
160        WRITE( stdout, '(8x,"k (",i5,") = (",3f12.7,"), wk =",f10.7)') &
161             & ik, (xk(ipol,ik), ipol=1,3), wk(ik)
162     ENDDO
163     !
164     ! crystal coordinates
165     !
166     WRITE( stdout, '(/23x,"cryst. coord.")')
167     DO ik = 1, nkstot
168        DO ipol = 1, 3
169           xkg (ipol) = at (1, ipol) * xk (1, ik) + &
170                        at (2, ipol) * xk (2, ik) + &
171                        at (3, ipol) * xk (3, ik)
172        ENDDO
173        WRITE( stdout, '(8x,"k (",i5,") = (",3f12.7,"), wk =",f10.7)') &
174             & ik, (xkg(ipol), ipol=1,3), wk(ik)
175     ENDDO
176     !
177  ENDIF
178  !
179  RETURN
180  !
181END SUBROUTINE hp_summary_q
182