LAPACK  3.9.0
LAPACK: Linear Algebra PACKage

◆ slahilb()

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 2017

Definition at line 126 of file slahilb.f.

126 *
127 * -- LAPACK test routine (version 3.8.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 2017
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 * .. External Subroutines ..
153  EXTERNAL xerbla
154 * ..
155 * .. External Functions
156  EXTERNAL slaset
157  INTRINSIC real
158 * ..
159 * .. Executable Statements ..
160 *
161 * Test the input arguments
162 *
163  info = 0
164  IF (n .LT. 0 .OR. n .GT. nmax_approx) THEN
165  info = -1
166  ELSE IF (nrhs .LT. 0) THEN
167  info = -2
168  ELSE IF (lda .LT. n) THEN
169  info = -4
170  ELSE IF (ldx .LT. n) THEN
171  info = -6
172  ELSE IF (ldb .LT. n) THEN
173  info = -8
174  END IF
175  IF (info .LT. 0) THEN
176  CALL xerbla('SLAHILB', -info)
177  RETURN
178  END IF
179  IF (n .GT. nmax_exact) THEN
180  info = 1
181  END IF
182 *
183 * Compute M = the LCM of the integers [1, 2*N-1]. The largest
184 * reasonable N is small enough that integers suffice (up to N = 11).
185  m = 1
186  DO i = 2, (2*n-1)
187  tm = m
188  ti = i
189  r = mod(tm, ti)
190  DO WHILE (r .NE. 0)
191  tm = ti
192  ti = r
193  r = mod(tm, ti)
194  END DO
195  m = (m / ti) * i
196  END DO
197 *
198 * Generate the scaled Hilbert matrix in A
199  DO j = 1, n
200  DO i = 1, n
201  a(i, j) = real(m) / (i + j - 1)
202  END DO
203  END DO
204 *
205 * Generate matrix B as simply the first NRHS columns of M * the
206 * identity.
207  CALL slaset('Full', n, nrhs, 0.0, real(m), 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 *
Here is the call graph for this function:
xerbla
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
slaset
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