! ! Copyright (C) 2002 FPMD group ! This file is distributed under the terms of the ! GNU General Public License. See the file `License' ! in the root directory of the present distribution, ! or http://www.gnu.org/copyleft/gpl.txt . ! SUBROUTINE ngnr_set( alat, a1, a2, a3, gcut, qk, ng, nr1, nr2, nr3 ) ! this routine calculates the storage required for G vectors arrays ! ---------------------------------------------- ! END manual ! ... declare modules USE kinds, ONLY: dbl USE mp, ONLY: mp_max, mp_min, mp_sum USE mp_global, ONLY: mpime, nproc, group IMPLICIT NONE INTEGER, INTENT(OUT) :: nr1, nr2, nr3, ng REAL(dbl), INTENT(IN) :: alat, a1(3), a2(3), a3(3), gcut, qk(3) ! ... declare other variables INTEGER :: i, j, k INTEGER :: nr1x, nr2x, nr3x INTEGER :: nr1tab, nr2tab, nr3tab, nr INTEGER :: nb(3) REAL(dbl) :: gsq, sqgc REAL(dbl) :: c(3), g(3) REAL(dbl) :: b1(3), b2(3), b3(3) LOGICAL :: tqk ! ... end of declarations ! ---------------------------------------------- ! ... mpime = processor number, starting from 0 ! ... evaluate cutoffs in reciprocal space and the required mesh size sqgc = sqrt(gcut) nr = int(sqgc) + 2 ! nr = mesh size parameter ! ... reciprocal lattice generators call recips(a1, a2, a3, b1, b2, b3) b1 = b1 * alat b2 = b2 * alat b3 = b3 * alat ! ... verify that, for G