Statistiques
| Révision :

root / src / minv.f90

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

1
      SUBROUTINE MINV(A,N,D)
2

    
3

    
4
!----------------------------------------------------------------------
5
! This routine was adapted from the public domain mopac6 diis.f 
6
!  source file (c) 2009, Stewart Computational Chemistry.
7
!  <http://www.openmopac.net/Downloads/Downloads.html>
8
!
9
!----------------------------------------------------------------------
10
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
11
!  Centre National de la Recherche Scientifique,
12
!  Université Claude Bernard Lyon 1. All rights reserved.
13
!
14
!  This work is registered with the Agency for the Protection of Programs 
15
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
16
!
17
!  Authors: P. Fleurat-Lessard, P. Dayal
18
!  Contact: optnpath@gmail.com
19
!
20
! This file is part of "Opt'n Path".
21
!
22
!  "Opt'n Path" is free software: you can redistribute it and/or modify
23
!  it under the terms of the GNU Affero General Public License as
24
!  published by the Free Software Foundation, either version 3 of the License,
25
!  or (at your option) any later version.
26
!
27
!  "Opt'n Path" is distributed in the hope that it will be useful,
28
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
29
!
30
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
31
!  GNU Affero General Public License for more details.
32
!
33
!  You should have received a copy of the GNU Affero General Public License
34
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
35
!
36
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
37
! for commercial licensing opportunities.
38
!----------------------------------------------------------------------
39
 
40

    
41
      IMPLICIT NONE
42
      integer, parameter :: KINT = kind(1)
43
      integer, parameter :: KREAL = kind(1.0d0)
44

    
45
      INTEGER(KINT), INTENT(IN) :: N
46
      REAL(KREAL), INTENT(INOUT) :: A(N*N)
47
      REAL(KREAL), INTENT(OUT) :: D
48

    
49
 
50
!**********************************************************************
51
!*
52
!*     INVERT A MATRIX USING GAUSS-JORDAN METHOD.  PART OF DIIS
53
!*     A - INPUT MATRIX (MUST BE A GENERAL MATRIX), DESTROYED IN
54
!*        COMPUTATION AND REPLACED BY RESULTANT INVERSE.
55
!*     N - ORDER OF MATRIX A
56
!*     D - RESULTANT DETERMINANT
57
!*
58
!**********************************************************************
59
      INTEGER(KINT), ALLOCATABLE :: L(:), M(:)
60
      INTEGER(KINT) :: I,J,K,NK,KK,KI,KJ,IZ,IJ,JP,JK,IK,JR,JQ,JI
61

    
62
      REAL(KREAL) :: BigA,Hold
63

    
64
      ALLOCATE(L(N),M(N))
65
!
66
!     SEARCH FOR LARGEST ELEMENT
67
!
68
      D=1.0D0
69
      NK=-N
70
      DO 180 K=1,N
71
         NK=NK+N
72
         L(K)=K
73
         M(K)=K
74
         KK=NK+K
75
         BIGA=A(KK)
76
         DO 20 J=K,N
77
            IZ=N*(J-1)
78
            DO 20 I=K,N
79
               IJ=IZ+I
80
               IF (ABS(BIGA).LT.ABS(A(IJ)))THEN
81
                  BIGA=A(IJ)
82
                  L(K)=I
83
                  M(K)=J
84
               ENDIF
85
20          CONTINUE
86
!
87
!     INTERCHANGE ROWS
88
!
89
         J=L(K)
90
         IF (J-K) 50,50,30
91
   30    KI=K-N
92
         DO 40 I=1,N
93
            KI=KI+N
94
            HOLD=-A(KI)
95
            JI=KI-K+J
96
            A(KI)=A(JI)
97
   40    A(JI)=HOLD
98
!
99
!     INTERCHANGE COLUMNS
100
!
101
   50    I=M(K)
102
         IF (I-K) 80,80,60
103
   60    JP=N*(I-1)
104
         DO 70 J=1,N
105
            JK=NK+J
106
            JI=JP+J
107
            HOLD=-A(JK)
108
            A(JK)=A(JI)
109
   70    A(JI)=HOLD
110
!C
111
!C     DIVIDE COLUMN BY MINUS PIVOT (VALUE OF PIVOT ELEMENT IS
112
!C     CONTAINED IN BIGA)
113
!C
114
   80    IF (BIGA) 100,90,100
115
   90    D=0.0
116
         RETURN
117
  100    DO 120 I=1,N
118
            IF (I-K) 110,120,110
119
  110       IK=NK+I
120
            A(IK)=A(IK)/(-BIGA)
121
  120    CONTINUE
122
!C  REDUCE MATRIX
123
         DO 150 I=1,N
124
            IK=NK+I
125
            HOLD=A(IK)
126
            IJ=I-N
127
            DO 150 J=1,N
128
               IJ=IJ+N
129
               IF (I-K) 130,150,130
130
  130          IF (J-K) 140,150,140
131
  140          KJ=IJ-I+K
132
               A(IJ)=HOLD*A(KJ)+A(IJ)
133
  150    CONTINUE
134
!C
135
!C     DIVIDE ROW BY PIVOT
136
!C
137
         KJ=K-N
138
         DO 170 J=1,N
139
            KJ=KJ+N
140
            IF (J-K) 160,170,160
141
  160       A(KJ)=A(KJ)/BIGA
142
  170    CONTINUE
143
!C
144
!C     PRODUCT OF PIVOTS
145
!C
146
         D=MAX(-1.D25,MIN(1.D25,D))
147
         D=D*BIGA
148
!C
149
!C     REPLACE PIVOT BY RECIPROCAL
150
!C
151
         A(KK)=1.0/BIGA
152
  180 CONTINUE
153
!C
154
!C     FINAL ROW AND COLUMN INTERCHANGE
155
!C
156
      K=N
157
  190 K=(K-1)
158
      IF (K) 260,260,200
159
  200 I=L(K)
160
      IF (I-K) 230,230,210
161
  210 JQ=N*(K-1)
162
      JR=N*(I-1)
163
      DO 220 J=1,N
164
         JK=JQ+J
165
         HOLD=A(JK)
166
         JI=JR+J
167
         A(JK)=-A(JI)
168
  220 A(JI)=HOLD
169
  230 J=M(K)
170
      IF (J-K) 190,190,240
171
  240 KI=K-N
172
      DO 250 I=1,N
173
         KI=KI+N
174
         HOLD=A(KI)
175
         JI=KI-K+J
176
         A(KI)=-A(JI)
177
  250 A(JI) =HOLD
178
      GO TO 190
179
  260 RETURN
180
      END