File: fd_gradient.f90

package info (click to toggle)
espresso 6.7-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 311,068 kB
  • sloc: f90: 447,429; ansic: 52,566; sh: 40,631; xml: 37,561; tcl: 20,077; lisp: 5,923; makefile: 4,503; python: 4,379; perl: 1,219; cpp: 761; fortran: 618; java: 568; awk: 128
file content (270 lines) | stat: -rw-r--r-- 7,319 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
!
! Copyright (C) 2006-2010 Quantum ESPRESSO 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 .
!
!
!
!----------------------------------------------------------------------
! Module to compute finite differences gradients on dense real space grid
! Written by Oliviero Andreussi
!----------------------------------------------------------------------
!
!=----------------------------------------------------------------------=!
   MODULE fd_gradient
!=----------------------------------------------------------------------=!

      USE kinds, ONLY: DP

      IMPLICIT NONE

  CONTAINS
!=----------------------------------------------------------------------=!
SUBROUTINE calc_fd_gradient( nfdpoint, icfd, ncfd, nnr, f, grad )
!=----------------------------------------------------------------------=!
  USE kinds,         ONLY : DP
  USE cell_base,     ONLY : at, bg, alat
  USE fft_base,      ONLY : dfftp
  USE fft_types,     ONLY : fft_index_to_3d
  USE scatter_mod,   ONLY : scatter_grid
  USE mp,            ONLY : mp_sum
  USE mp_bands,      ONLY : me_bgrp, intra_bgrp_comm

  IMPLICIT NONE
  !
  INTEGER, INTENT(IN)  :: nfdpoint
  INTEGER, INTENT(IN)  :: ncfd
  INTEGER, INTENT(IN)  :: icfd(-nfdpoint:nfdpoint)
  INTEGER, INTENT(IN)  :: nnr
  REAL( DP ), DIMENSION( nnr ), INTENT(IN) :: f
  REAL( DP ), DIMENSION( 3, nnr ), INTENT(OUT) :: grad

  INTEGER :: i, ir, ir_end, ipol, in
  INTEGER :: ix(-nfdpoint:nfdpoint),iy(-nfdpoint:nfdpoint),iz(-nfdpoint:nfdpoint)
  INTEGER :: ixc, iyc, izc, ixp, ixm, iyp, iym, izp, izm
  REAL( DP ), DIMENSION( :, : ), ALLOCATABLE :: gradtmp, gradaux
  LOGICAL  :: offrange
  !
  grad = 0.D0
  !
  ALLOCATE( gradtmp( dfftp%nr1x*dfftp%nr2x*dfftp%nr3x, 3 ) )
  gradtmp = 0.D0
  !
#if defined (__MPI)
  ir_end = MIN(nnr,dfftp%nr1x*dfftp%my_nr2p*dfftp%my_nr3p)
#else
  ir_end = nnr
#endif
  !
  DO ir = 1, ir_end
    !
    CALL fft_index_to_3d (ir, dfftp, ix(0), iy(0), iz(0), offrange)
    IF ( offrange ) CYCLE
    !
    DO in = 1, nfdpoint
      ix(in) = ix(in-1) + 1
      IF( ix(in) .GT. dfftp%nr1-1 ) ix(in) = 0
      ix(-in) = ix(-in+1) - 1
      IF( ix(-in) .LT. 0 ) ix(-in) = dfftp%nr1-1
      iy(in) = iy(in-1) + 1
      IF( iy(in) .GT. dfftp%nr2-1 ) iy(in) = 0
      iy(-in) = iy(-in+1) - 1
      IF( iy(-in) .LT. 0 ) iy(-in) = dfftp%nr2-1
      iz(in) = iz(in-1) + 1
      IF( iz(in) .GT. dfftp%nr3-1 ) iz(in) = 0
      iz(-in) = iz(-in+1) - 1
      IF( iz(-in) .LT. 0 ) iz(-in) = dfftp%nr3-1
    ENDDO
    !
    DO in = -nfdpoint, nfdpoint
      i = ix(in) + iy(0) * dfftp%nr1x + iz(0) * dfftp%nr1x * dfftp%nr2x + 1
      gradtmp(i,1) = gradtmp(i,1) - icfd(in)*f(ir)*dfftp%nr1
      i = ix(0) + iy(in) * dfftp%nr1x + iz(0) * dfftp%nr1x * dfftp%nr2x + 1
      gradtmp(i,2) = gradtmp(i,2) - icfd(in)*f(ir)*dfftp%nr2
      i = ix(0) + iy(0) * dfftp%nr1x + iz(in) * dfftp%nr1x * dfftp%nr2x + 1
      gradtmp(i,3) = gradtmp(i,3) - icfd(in)*f(ir)*dfftp%nr3
    ENDDO
    !
  ENDDO
  !
  ALLOCATE( gradaux(nnr,3) )
#if defined (__MPI)
  DO ipol = 1, 3
    CALL mp_sum( gradtmp(:,ipol), intra_bgrp_comm )
    CALL scatter_grid ( dfftp, gradtmp(:,ipol), gradaux(:,ipol) )
  ENDDO
#else
  gradaux(1:nnr,:) = gradtmp(1:nnr,:)
#endif
  !
  DEALLOCATE( gradtmp )
  !
  DO ir = 1,nnr
    grad(:,ir) = MATMUL( bg, gradaux(ir,:) )
  ENDDO
  DEALLOCATE( gradaux )
  !
  grad = grad / DBLE(ncfd) / alat
  !
  RETURN

END SUBROUTINE calc_fd_gradient

SUBROUTINE init_fd_gradient( ifdtype, nfdpoint, ncfd, icfd )

  USE kinds,         ONLY : DP

  IMPLICIT NONE
  !
  INTEGER, INTENT(IN)  :: ifdtype, nfdpoint
  INTEGER, INTENT(OUT) :: ncfd
  INTEGER, INTENT(OUT) :: icfd(-nfdpoint:nfdpoint)
  !
  INTEGER :: in
  !
  ncfd = 0
  icfd = 0
  !
  SELECT CASE ( ifdtype )
    !
  CASE ( 1 )
    ! (2N+1)-point Central Differences
    IF ( nfdpoint .EQ. 1 ) THEN
      ncfd = 2
      icfd(  1 ) =   1
    ELSE IF ( nfdpoint .EQ. 2 ) THEN
      ncfd = 12
      icfd(  2 ) =  -1
      icfd(  1 ) =   8
    ELSE IF ( nfdpoint .EQ. 3 ) THEN
      ncfd = 60
      icfd(  3 ) =   1
      icfd(  2 ) =  -9
      icfd(  1 ) =  45
    ELSE IF ( nfdpoint .EQ. 4 ) THEN
      ncfd = 840
      icfd(  4 ) =  -3
      icfd(  3 ) =  32
      icfd(  2 ) =-168
      icfd(  1 ) = 672
    ELSE
      WRITE(*,*)'ERROR: wrong number of points',nfdpoint,&
               &' for finite difference type ',ifdtype
      STOP
    ENDIF
    !
  CASE ( 2 )
    ! Low-Noise Lanczos Differentiators ( M = 2 )
    IF ( nfdpoint .GE. 2 ) THEN
      ncfd = (nfdpoint)*(nfdpoint+1)*(2*nfdpoint+1)/3
      DO in = 1,nfdpoint
        icfd( in ) = in
      ENDDO
    ELSE
      WRITE(*,*)'ERROR: wrong number of points',nfdpoint,&
               &' for finite difference type ',ifdtype
      STOP
    END IF
    !
  CASE ( 3 )
    ! Super Lanczos Low-Noise Differentiators ( M = 4 )
    IF ( nfdpoint .EQ. 3 ) THEN
      ncfd = 252
      icfd(  3 ) = -22
      icfd(  2 ) =  67
      icfd(  1 ) =  58
    ELSE IF ( nfdpoint .EQ. 4 ) THEN
      ncfd = 1188
      icfd(  4 ) = -86
      icfd(  3 ) = 142
      icfd(  2 ) = 193
      icfd(  1 ) = 126
    ELSE IF ( nfdpoint .EQ. 5 ) THEN
      ncfd = 5148
      icfd(  5 ) =-300
      icfd(  4 ) = 294
      icfd(  3 ) = 532
      icfd(  2 ) = 503
      icfd(  1 ) = 296
    ELSE
      WRITE(*,*)'ERROR: wrong number of points',nfdpoint,&
               &' for finite difference type ',ifdtype
      STOP
    ENDIF
    !
  CASE ( 4 )
    ! Smooth Noise-Robust Differentiators  ( n = 2 )
    IF ( nfdpoint .EQ. 2 ) THEN
      ncfd = 8
      icfd(  2 ) =   1
      icfd(  1 ) =   2
    ELSE IF ( nfdpoint .EQ. 3 ) THEN
      ncfd = 32
      icfd(  3 ) =   1
      icfd(  2 ) =   4
      icfd(  1 ) =   5
    ELSE IF ( nfdpoint .EQ. 4 ) THEN
      ncfd = 128
      icfd(  4 ) =   1
      icfd(  3 ) =   6
      icfd(  2 ) =  14
      icfd(  1 ) =  14
    ELSE IF ( nfdpoint .EQ. 5 ) THEN
      ncfd = 512
      icfd(  5 ) =   1
      icfd(  4 ) =   8
      icfd(  3 ) =  27
      icfd(  2 ) =  48
      icfd(  1 ) =  42
    ELSE
      WRITE(*,*)'ERROR: wrong number of points',nfdpoint,&
               &' for finite difference type ',ifdtype
      STOP
    ENDIF
    !
  CASE ( 5 )
    ! Smooth Noise-Robust Differentiators  ( n = 4 )
    IF ( nfdpoint .EQ. 3 ) THEN
      ncfd = 96
      icfd(  3 ) =  -5
      icfd(  2 ) =  12
      icfd(  1 ) =  39
    ELSE IF ( nfdpoint .EQ. 4 ) THEN
      ncfd = 96
      icfd(  4 ) =  -2
      icfd(  3 ) =  -1
      icfd(  2 ) =  16
      icfd(  1 ) =  27
    ELSE IF ( nfdpoint .EQ. 5 ) THEN
      ncfd = 1536
      icfd(  5 ) = -11
      icfd(  4 ) = -32
      icfd(  3 ) =  39
      icfd(  2 ) = 256
      icfd(  1 ) = 322
    ELSE
      WRITE(*,*)'ERROR: wrong number of points',nfdpoint,&
               &' for finite difference type ',ifdtype
      STOP
    ENDIF
    !
  CASE DEFAULT
    !
    WRITE(*,*)'ERROR: finite difference type unknown, ifdtype=',ifdtype
    STOP
    !
  END SELECT
  !
  DO in = 1,nfdpoint
    icfd( -in ) = - icfd( in )
  ENDDO
  !
  RETURN
  !
END SUBROUTINE init_fd_gradient

!=----------------------------------------------------------------------=!
   END MODULE fd_gradient
!=----------------------------------------------------------------------=!