File: MB02UV.f

package info (click to toggle)
dynare 4.3.0-2
  • links: PTS, VCS
  • area: main
  • in suites: wheezy
  • size: 40,640 kB
  • sloc: fortran: 82,231; cpp: 72,734; ansic: 28,874; pascal: 13,241; sh: 4,300; objc: 3,281; yacc: 2,833; makefile: 1,288; lex: 1,162; python: 162; lisp: 54; xml: 8
file content (195 lines) | stat: -rw-r--r-- 6,043 bytes parent folder | download
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
      SUBROUTINE MB02UV( N, A, LDA, IPIV, JPIV, INFO )
C
C     SLICOT RELEASE 5.0.
C
C     Copyright (c) 2002-2009 NICONET e.V.
C
C     This program is free software: you can redistribute it and/or
C     modify it under the terms of the GNU General Public License as
C     published by the Free Software Foundation, either version 2 of
C     the License, or (at your option) any later version.
C
C     This program is distributed in the hope that it will be useful,
C     but WITHOUT ANY WARRANTY; without even the implied warranty of
C     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
C     GNU General Public License for more details.
C
C     You should have received a copy of the GNU General Public License
C     along with this program.  If not, see
C     <http://www.gnu.org/licenses/>.
C
C     PURPOSE
C
C     To compute an LU factorization, using complete pivoting, of the
C     N-by-N matrix A. The factorization has the form A = P * L * U * Q,
C     where P and Q are permutation matrices, L is lower triangular with
C     unit diagonal elements and U is upper triangular.
C
C     ARGUMENTS
C
C     Input/Output Parameters
C
C     N       (input) INTEGER
C             The order of the matrix A.
C
C     A       (input/output) DOUBLE PRECISION array, dimension (LDA, N)
C             On entry, the leading N-by-N part of this array must
C             contain the matrix A to be factored.
C             On exit, the leading N-by-N part of this array contains
C             the factors L and U from the factorization A = P*L*U*Q;
C             the unit diagonal elements of L are not stored. If U(k, k)
C             appears to be less than SMIN, U(k, k) is given the value
C             of SMIN, giving a nonsingular perturbed system.
C
C     LDA     INTEGER
C             The leading dimension of the array A.  LDA >= max(1, N).
C
C     IPIV    (output) INTEGER array, dimension (N)
C             The pivot indices; for 1 <= i <= N, row i of the
C             matrix has been interchanged with row IPIV(i).
C
C     JPIV    (output) INTEGER array, dimension (N)
C             The pivot indices; for 1 <= j <= N, column j of the
C             matrix has been interchanged with column JPIV(j).
C
C     Error indicator
C
C     INFO    INTEGER
C             = 0:  successful exit;
C             = k:  U(k, k) is likely to produce owerflow if one tries
C                   to solve for x in Ax = b. So U is perturbed to get
C                   a nonsingular system. This is a warning.
C
C     FURTHER COMMENTS
C
C     In the interests of speed, this routine does not check the input
C     for errors. It should only be used to factorize matrices A of
C     very small order.
C
C     CONTRIBUTOR
C
C     Bo Kagstrom and Peter Poromaa, Univ. of Umea, Sweden, Nov. 1993.
C
C     REVISIONS
C
C     April 1998 (T. Penzl).
C     Sep. 1998 (V. Sima).
C     March 1999 (V. Sima).
C     March 2004 (V. Sima).
C
C     ******************************************************************
C
C     .. Parameters ..
      DOUBLE PRECISION   ZERO, ONE
      PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
C     .. Scalar Arguments ..
      INTEGER            INFO, LDA, N
C     .. Array Arguments ..
      INTEGER            IPIV( * ), JPIV( * )
      DOUBLE PRECISION   A( LDA, * )
C     .. Local Scalars ..
      INTEGER            I, IP, IPV, JP, JPV
      DOUBLE PRECISION   BIGNUM, EPS, SMIN, SMLNUM, XMAX
C     .. External Functions ..
      DOUBLE PRECISION   DLAMCH
      EXTERNAL           DLAMCH
C     .. External Subroutines ..
      EXTERNAL           DGER, DLABAD, DSCAL, DSWAP
C     .. Intrinsic Functions ..
      INTRINSIC          ABS, MAX
C     .. Executable Statements ..
C
C     Set constants to control owerflow.

      INFO = 0
      EPS    = DLAMCH( 'Precision' )
      SMLNUM = DLAMCH( 'Safe minimum' ) / EPS
      BIGNUM = ONE / SMLNUM
      CALL DLABAD( SMLNUM, BIGNUM )
C
C     Find max element in matrix A.
C
      IPV = 1
      JPV = 1
      XMAX = ZERO
      DO 40 JP = 1, N
         DO 20 IP = 1, N
            IF ( ABS( A(IP, JP) ) .GT. XMAX ) THEN
               XMAX = ABS( A(IP, JP) )
               IPV  = IP
               JPV  = JP
            ENDIF
   20    CONTINUE
   40 CONTINUE
      SMIN =  MAX( EPS * XMAX, SMLNUM )
C
C     Swap rows.
C
      IF ( IPV .NE. 1 ) CALL DSWAP( N, A(IPV, 1), LDA, A(1, 1), LDA )
      IPIV(1) = IPV
C
C     Swap columns.
C
      IF ( JPV .NE. 1 ) CALL DSWAP( N, A(1, JPV), 1, A(1, 1), 1 )
      JPIV(1) = JPV
C
C     Check for singularity.
C
      IF ( ABS( A(1, 1) ) .LT. SMIN ) THEN
         INFO = 1
         A(1, 1) = SMIN
      ENDIF
      IF ( N.GT.1 ) THEN
         CALL DSCAL( N - 1, ONE / A(1, 1), A(2, 1), 1 )
         CALL DGER( N - 1, N - 1, -ONE, A(2, 1), 1, A(1, 2), LDA,
     $              A(2, 2), LDA )
      ENDIF
C
C     Factorize the rest of A with complete pivoting.
C     Set pivots less than SMIN to SMIN.
C
      DO 100 I = 2, N - 1
C
C        Find max element in remaining matrix.
C
         IPV = I
         JPV = I
         XMAX = ZERO
         DO 80 JP = I, N
            DO 60 IP = I, N
               IF ( ABS( A(IP, JP) ) .GT. XMAX ) THEN
                  XMAX = ABS( A(IP, JP) )
                  IPV = IP
                  JPV = JP
               ENDIF
   60       CONTINUE
   80    CONTINUE
C
C        Swap rows.
C
         IF ( IPV .NE. I ) CALL DSWAP( N, A(IPV, 1), LDA, A(I, 1), LDA )
         IPIV(I) = IPV
C
C        Swap columns.
C
         IF ( JPV .NE. I ) CALL DSWAP( N, A(1, JPV), 1, A(1, I), 1 )
         JPIV(I) = JPV
C
C        Check for almost singularity.
C
         IF ( ABS( A(I, I) ) .LT. SMIN ) THEN
            INFO = I
            A(I, I) = SMIN
         ENDIF
         CALL DSCAL( N - I, ONE / A(I, I), A(I + 1, I), 1 )
         CALL DGER( N - I, N - I, -ONE, A(I + 1, I), 1, A(I, I + 1),
     $              LDA, A(I + 1, I + 1), LDA )
  100 CONTINUE
      IF ( ABS( A(N, N) ) .LT. SMIN ) THEN
         INFO = N
         A(N, N) = SMIN
      ENDIF
C
      RETURN
C *** Last line of MB02UV ***
      END