1!
2! Copyright (C) 2001-2008 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!----------------------------------------------------------------------------
9PROGRAM q2r
10  !----------------------------------------------------------------------------
11  !
12  !  q2r.x:
13  !     reads force constant matrices C(q) produced by the phonon code
14  !     for a grid of q-points, calculates the corresponding set of
15  !     interatomic force constants (IFC), C(R)
16  !
17  !  Input data: Namelist "input"
18  !     fildyn     :  input file name (character, must be specified)
19  !                   "fildyn"0 contains information on the q-point grid
20  !                   "fildyn"1-N contain force constants C_n = C(q_n)
21  !                   for n=1,...N, where N is the number of q-points
22  !                   in the irreducible brillouin zone
23  !                   Normally this should be the same as specified
24  !                   on input to the phonon code
25  !                   In the non collinear/spin-orbit case the files
26  !                   produced by ph.x are in .xml format. In this case
27  !                   fildyn is the same as in the phonon code + the .xml
28  !                   extension.
29  !     flfrc      :  output file containing the IFC in real space
30  !                   (character, must be specified)
31  !     zasr       :  Indicates type of Acoustic Sum Rules used for the Born
32  !                   effective charges (character):
33  !                   - 'no': no Acoustic Sum Rules imposed (default)
34  !                   - 'simple':  previous implementation of the asr used
35  !                     (3 translational asr imposed by correction of
36  !                     the diagonal elements of the force-constants matrix)
37  !                   - 'crystal': 3 translational asr imposed by optimized
38  !                      correction of the IFC (projection).
39  !                   - 'one-dim': 3 translational asr + 1 rotational asr
40  !                     imposed by optimized correction of the IFC (the
41  !                     rotation axis is the direction of periodicity; it
42  !                     will work only if this axis considered is one of
43  !                     the cartesian axis).
44  !                   - 'zero-dim': 3 translational asr + 3 rotational asr
45  !                     imposed by optimized correction of the IFC.
46  !                   Note that in certain cases, not all the rotational asr
47  !                   can be applied (e.g. if there are only 2 atoms in a
48  !                   molecule or if all the atoms are aligned, etc.).
49  !                   In these cases the supplementary asr are cancelled
50  !                   during the orthonormalization procedure (see below).
51  !     loto_2d    :  set to .true. to activate two-dimensional treatment of LO-TO splitting.
52  !
53  !  If a file "fildyn"0 is not found, the code will ignore variable "fildyn"
54  !  and will try to read from the following cards the missing information
55  !  on the q-point grid and file names:
56  !     nr1,nr2,nr3:  dimensions of the FFT grid formed by the q-point grid
57  !     nfile      :  number of files containing C(q_n), n=1,nfile
58  !  followed by nfile cards:
59  !     filin      :  name of file containing C(q_n)
60  !  The name and order of files is not important as long as q=0 is the first
61  !
62  USE kinds,       ONLY : DP
63  USE mp,          ONLY : mp_bcast
64  USE mp_world,    ONLY : world_comm
65  USE mp_global,   ONLY : mp_startup, mp_global_end
66  USE io_global,   ONLY : ionode_id, ionode, stdout
67  USE environment, ONLY : environment_start, environment_end
68  USE el_phon,     ONLY : el_ph_nsigma
69  !
70  IMPLICIT NONE
71  !
72  CHARACTER(len=256) :: fildyn, filin, flfrc, prefix
73  CHARACTER (LEN=10) :: zasr
74  LOGICAL            :: la2F, loto_2d
75  INTEGER            :: ios
76  !
77  NAMELIST / input / fildyn, flfrc, prefix, zasr, la2F, loto_2d, el_ph_nsigma
78  !
79  CALL mp_startup()
80  CALL environment_start('Q2R')
81  !
82  IF (ionode) CALL input_from_file ( )
83     !
84  fildyn = ' '
85  flfrc = ' '
86  prefix = ' '
87  loto_2d=.false.
88  zasr = 'no'
89     !
90  la2F=.false.
91  el_ph_nsigma=10
92     !
93     !
94  IF (ionode)  READ ( 5, input, IOSTAT =ios )
95
96  CALL mp_bcast(ios, ionode_id, world_comm)
97  CALL errore('q2r','error reading input namelist', abs(ios))
98
99  CALL mp_bcast(fildyn, ionode_id, world_comm)
100  CALL mp_bcast(flfrc, ionode_id, world_comm)
101  CALL mp_bcast(prefix, ionode_id, world_comm)
102  CALL mp_bcast(zasr, ionode_id, world_comm)
103  CALL mp_bcast(loto_2d, ionode_id, world_comm)
104  CALL mp_bcast(la2F, ionode_id, world_comm)
105  CALL mp_bcast(el_ph_nsigma, ionode_id, world_comm)
106  !
107  CALL do_q2r(fildyn, flfrc, prefix, zasr, la2F, loto_2d)
108  !
109  CALL environment_end('Q2R')
110
111  CALL mp_global_end()
112  !
113END PROGRAM q2r
114!
115!----------------------------------------------------------------------------
116