Statistiques
| Révision :

root / src / ConvGrad_Cart2Int.f90 @ 2

Historique | Voir | Annoter | Télécharger (4,35 ko)

1
      SUBROUTINE ConvGrad_Cart2Int(n,BMat,indzmat,GradCart,GradInt)
2

    
3
        use Io_module
4
        use Path_module, only : atome
5

    
6
        IMPLICIT NONE
7

    
8
!
9
        INTEGER(KINT), INTENT(IN) ::  n, indzmat(n,5)
10
        REAL(KREAL), INTENT(IN)  :: BMat(3,n,3,n), GradCart(3,n)
11
        REAL(KREAL), INTENT(INOUT)  :: GradInt(3,n)
12

    
13

    
14
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
15
!
16
! This routines converts a gradient in cartesian coordinates into
17
! the gradient in internal coordinates (either Zmat, Mixed or Baker)
18
!
19
! It uses a LAPACK subroutine (dgelsd) which purpose is:
20

    
21
! *  DGELSD computes the minimum-norm solution to a real linear least
22
! *  squares problem:
23
! *      minimize 2-norm(| b - A*x |)
24
! *  using the singular value decomposition (SVD) of A. A is an M-by-N
25
! *  matrix which may be rank-deficient.
26

    
27
! Variables:
28
! input  : n, number of atoms
29
!          BMat: the dZ/dx matrix
30
!          GradCart: Gradient in cartesian coordinates
31
!
32
! output : GradInt: Gradient in internal coordintaes
33
!
34
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
35

    
36
      logical    debug, init
37
      REAL(KREAL), parameter :: zero = 0d0, tol = 1d-8,  eps = 1d-12
38
 
39
      REAL(KREAL) , ALLOCATABLE :: AEigVec(:,:), AEigVal(:),ATA(:)
40
      INTEGER(KINT) :: n3, iat, k
41
      INTEGER(KINT) :: i
42
!
43
      save  debug, init
44
      data  init /.false./
45

    
46
!     .. Local Arrays  for LAPACK
47
      INTEGER(KINT) :: Info, LWork, Rank
48
      REAL(KREAL), ALLOCATABLE :: S(:), Work(:), GradCTmp(:,:)
49

    
50
!     IWORK dimension should be at least 3*MIN(M,N)*NLVL + 11*MIN(M,N),
51
!     where NLVL = MAX( 0, INT( LOG_2( MIN(M,N)/(SMLSIZ+1) ) )+1 )
52
!     and SMLSIZ = 25 
53
      INTEGER(KINT) :: LIWork, NLVL, SMLSIZ=12 ! We take smaller value just to be sure
54
      INTEGER(KINT), ALLOCATABLE :: IWork(:) ! IWork
55

    
56

    
57
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
58
!
59

    
60
  INTERFACE
61
     function valid(string) result (isValid)
62
       CHARACTER(*), intent(in) :: string
63
       logical                  :: isValid
64
     END function VALID
65

    
66
     SUBROUTINE DGELSD( M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, &
67
                        WORK, LWORK, IWORK, INFO )
68
! *
69
! *  -- LAPACK driver routine (version 3.2.2) --
70
! *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
71
! *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
72
! *     June 2010
73
! *
74
! *     .. Scalar Arguments ..
75
      INTEGER            INFO, LDA, LDB, LWORK, M, N, NRHS, RANK
76
      DOUBLE PRECISION   RCOND
77
!*     ..
78
!*     .. Array Arguments ..
79
      INTEGER            IWORK( * )
80
      DOUBLE PRECISION   A( LDA, * ), B( LDB, * ), S( * ), WORK( * )
81

    
82
    END SUBROUTINE DGELSD
83

    
84

    
85

    
86
     
87
  END INTERFACE
88

    
89
!
90
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
91

    
92

    
93
      if (.not.init) then
94
        init = .true.
95
        debug = valid ('GEOSTEP').OR.valid('ConvGrad')
96
      endif
97

    
98
!
99
      Allocate(GradCTmp(3,n))
100

    
101
      if (debug) WRITE(*,*) "================ Entering ConvGrad_Cart2Int ============="
102
!
103
      n3 = 3 * n
104
!
105
      
106
      NLVL= MAX( 0, INT( LOG( n3*1.d0/(SMLSIZ+1))/LOG(2.d0) ) +1 )
107
      LIWork=Max(1,3*n3*NLVL + 11*n3+1)
108

    
109
      Allocate(IWork(LIWork),WOrk(1))
110

    
111
      LWork=-1
112
      GradInt=0.d0
113

    
114
        call DGELSD( n3, n3, 1, BMat, n3, GradCart, n3, GradInt, Tol, RANK, &
115
                        WORK, LWORK, IWORK, INFO )
116

    
117
        LWork=Work(1)
118
        if (debug) WRITE(*,*) "DEBUG CONVGRAD_CART2INT LWORK,N3=",LWORK,N3
119

    
120
        DEALLOCATE(Work)
121
        ALLOCATE(Work(LWork))
122

    
123
        call DGELSD( n3, n3, 1, BMat, n3, GradCart, n3, GradInt, Tol, RANK, &
124
                        WORK, LWORK, IWORK, INFO )
125

    
126
        GradInt=GradCart
127
      if (debug) then
128
         WRITE(*,*) "DEBUG CONVGRAD_CART2INT -- GradInt after DGELSD"
129
         WRITE(*,*) "INFO=",INFO
130
         DO I=1,N
131
            WRITE(*,'(1X,I5,3(1X,F13.6))') I, GradInt(1:3,I)
132
         END DO
133
      END IF
134

    
135

    
136
! In case we used a Zmat, we might have dummy atoms.
137
! We are extra cautious and put their gradient components to 0
138

    
139
      do iat = 1, n
140
        do k = 1, 3
141
          if (atome(indzmat(iat,1)) == 0) then
142
            GradInt(k,iat) = zero
143
          endif
144
        end do
145
      end do
146

    
147
      where (abs(GradInt)<=eps) GradInt=zero
148

    
149
      if (debug) write (*,*) "DBG ConvGrad_Cart2Int GradInt=",GradInt
150

    
151
      DEALLOCATE(IWork,Work,GradCTmp)
152
!
153
!
154
      if (debug) WRITE(*,*) "================  ConvGrad_Cart2Int Over ============="
155
      return
156
! ======================================================================
157

    
158
    end SUBROUTINE ConvGrad_Cart2Int