LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dlahilb ( integer  N,
integer  NRHS,
double precision, dimension(lda, n)  A,
integer  LDA,
double precision, dimension(ldx, nrhs)  X,
integer  LDX,
double precision, dimension(ldb, nrhs)  B,
integer  LDB,
double precision, dimension(n)  WORK,
integer  INFO 
)

DLAHILB

Purpose:
 DLAHILB generates an N by N scaled Hilbert matrix in A along with
 NRHS right-hand sides in B and solutions in X such that A*X=B.

 The Hilbert matrix is scaled by M = LCM(1, 2, ..., 2*N-1) so that all
 entries are integers.  The right-hand sides are the first NRHS 
 columns of M * the identity matrix, and the solutions are the 
 first NRHS columns of the inverse Hilbert matrix.

 The condition number of the Hilbert matrix grows exponentially with
 its size, roughly as O(e ** (3.5*N)).  Additionally, the inverse
 Hilbert matrices beyond a relatively small dimension cannot be
 generated exactly without extra precision.  Precision is exhausted
 when the largest entry in the inverse Hilbert matrix is greater than
 2 to the power of the number of bits in the fraction of the data type
 used plus one, which is 24 for single precision.  

 In single, the generated solution is exact for N <= 6 and has
 small componentwise error for 7 <= N <= 11.
Parameters
[in]N
          N is INTEGER
          The dimension of the matrix A.
[in]NRHS
          NRHS is NRHS
          The requested number of right-hand sides.
[out]A
          A is DOUBLE PRECISION array, dimension (LDA, N)
          The generated scaled Hilbert matrix.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= N.
[out]X
          X is DOUBLE PRECISION array, dimension (LDX, NRHS)
          The generated exact solutions.  Currently, the first NRHS
          columns of the inverse Hilbert matrix.
[in]LDX
          LDX is INTEGER
          The leading dimension of the array X.  LDX >= N.
[out]B
          B is DOUBLE PRECISION array, dimension (LDB, NRHS)
          The generated right-hand sides.  Currently, the first NRHS
          columns of LCM(1, 2, ..., 2*N-1) * the identity matrix.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  LDB >= N.
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (N)
[out]INFO
          INFO is INTEGER
          = 0: successful exit
          = 1: N is too large; the data is still generated but may not
               be not exact.
          < 0: if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 126 of file dlahilb.f.

126 *
127 * -- LAPACK test routine (version 3.4.0) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * November 2011
131 *
132 * .. Scalar Arguments ..
133  INTEGER n, nrhs, lda, ldx, ldb, info
134 * .. Array Arguments ..
135  DOUBLE PRECISION a(lda, n), x(ldx, nrhs), b(ldb, nrhs), work(n)
136 * ..
137 *
138 * =====================================================================
139 * .. Local Scalars ..
140  INTEGER tm, ti, r
141  INTEGER m
142  INTEGER i, j
143  COMPLEX*16 tmp
144 * ..
145 * .. Parameters ..
146 * NMAX_EXACT the largest dimension where the generated data is
147 * exact.
148 * NMAX_APPROX the largest dimension where the generated data has
149 * a small componentwise relative error.
150  INTEGER nmax_exact, nmax_approx
151  parameter(nmax_exact = 6, nmax_approx = 11)
152 
153 * ..
154 * .. External Functions
155  EXTERNAL dlaset
156  INTRINSIC dble
157 * ..
158 * .. Executable Statements ..
159 *
160 * Test the input arguments
161 *
162  info = 0
163  IF (n .LT. 0 .OR. n .GT. nmax_approx) THEN
164  info = -1
165  ELSE IF (nrhs .LT. 0) THEN
166  info = -2
167  ELSE IF (lda .LT. n) THEN
168  info = -4
169  ELSE IF (ldx .LT. n) THEN
170  info = -6
171  ELSE IF (ldb .LT. n) THEN
172  info = -8
173  END IF
174  IF (info .LT. 0) THEN
175  CALL xerbla('DLAHILB', -info)
176  RETURN
177  END IF
178  IF (n .GT. nmax_exact) THEN
179  info = 1
180  END IF
181 *
182 * Compute M = the LCM of the integers [1, 2*N-1]. The largest
183 * reasonable N is small enough that integers suffice (up to N = 11).
184  m = 1
185  DO i = 2, (2*n-1)
186  tm = m
187  ti = i
188  r = mod(tm, ti)
189  DO WHILE (r .NE. 0)
190  tm = ti
191  ti = r
192  r = mod(tm, ti)
193  END DO
194  m = (m / ti) * i
195  END DO
196 *
197 * Generate the scaled Hilbert matrix in A
198  DO j = 1, n
199  DO i = 1, n
200  a(i, j) = dble(m) / (i + j - 1)
201  END DO
202  END DO
203 *
204 * Generate matrix B as simply the first NRHS columns of M * the
205 * identity.
206  tmp = dble(m)
207  CALL dlaset('Full', n, nrhs, 0.0d+0, tmp, b, ldb)
208 *
209 * Generate the true solutions in X. Because B = the first NRHS
210 * columns of M*I, the true solutions are just the first NRHS columns
211 * of the inverse Hilbert matrix.
212  work(1) = n
213  DO j = 2, n
214  work(j) = ( ( (work(j-1)/(j-1)) * (j-1 - n) ) /(j-1) )
215  $ * (n +j -1)
216  END DO
217 *
218  DO j = 1, nrhs
219  DO i = 1, n
220  x(i, j) = (work(i)*work(j)) / (i + j - 1)
221  END DO
222  END DO
223 *
subroutine dlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: dlaset.f:112
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62

Here is the call graph for this function:

Here is the caller graph for this function: