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

SLAHILB

Purpose:
 SLAHILB 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 INTEGER
          The requested number of right-hand sides.
[out]A
          A is REAL 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 REAL 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 REAL 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 REAL 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 2015

Definition at line 126 of file slahilb.f.

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

Here is the call graph for this function: