UD01DD

Reading a sparse real matrix

[Specification] [Arguments] [Method] [References] [Comments] [Example]

Purpose

  To read the elements of a sparse matrix.

Specification
      SUBROUTINE UD01DD( M, N, NIN, A, LDA, INFO )
C     .. Scalar Arguments ..
      INTEGER           INFO, LDA, M, N, NIN
C     .. Array Arguments ..
      DOUBLE PRECISION  A(LDA,*)

Arguments

Input/Output Parameters

  M       (input) INTEGER
          The number of rows of the matrix A.  M >= 0.

  N       (input) INTEGER
          The number of columns of the matrix A.  N >= 0.

  NIN     (input) INTEGER
          The input channel from which the elements of A are read.
          NIN >= 0.

  A       (output) DOUBLE PRECISION array, dimension (LDA,N)
          The leading M-by-N part of this array contains the sparse
          matrix A. The not assigned elements are set to zero.

  LDA     INTEGER
          The leading dimension of array A.  LDA >= MAX(1,M).

Error Indicator
  INFO    INTEGER
          = 0:  successful exit;
          < 0:  if INFO = -i, the i-th argument had an illegal
                value;
          = 1 : if a row index i is read with i < 1 or i > M or
                a column index j is read with j < 1 or j > N.
                This is a warning.

Method
  First, the elements A(i,j) with 1 <= i <= M and 1 <= j <= N are
  set to zero. Next the nonzero elements are read from the input
  file NIN. Each line of NIN must contain consecutively the values
  i, j, A(i,j). The routine terminates after the last line has been
  read.

References
  None.

Numerical Aspects
  None.

Further Comments
  None
Example

Program Text

*     UD01DD EXAMPLE PROGRAM TEXT
*     Copyright (c) 2002-2017 NICONET e.V.
*
*     .. Parameters ..
      INTEGER          NIN, NOUT
      PARAMETER        ( NIN = 5, NOUT = 6 )
      INTEGER          MMAX, NMAX
      PARAMETER        ( MMAX = 10, NMAX = 10 )
      INTEGER          LDA
      PARAMETER        ( LDA = NMAX )
*     .. Local Scalars ..
      INTEGER          INFO, INFO1, M, N
*     .. Local Arrays ..
      DOUBLE PRECISION A(LDA,NMAX)
*     .. External Subroutines ..
      EXTERNAL         UD01DD, UD01MD
*     .. Executable Statements ..
*
      WRITE ( NOUT, FMT = 99999 )
*     Skip the heading in the data file and read the data.
      READ ( NIN, FMT = '()' )
      READ ( NIN, FMT = * ) M, N
      IF ( M.LT.0 .OR. M.GT.MMAX ) THEN
         WRITE ( NOUT, FMT = 99994 ) M
      ELSE IF ( N.LT.0 .OR. N.GT.NMAX ) THEN
         WRITE ( NOUT, FMT = 99995 ) N
      ELSE
*        Read the coefficients of the matrix polynomial P(s).
         CALL UD01DD( M, N, NIN, A, LDA, INFO )
         IF ( INFO.GE.0 ) THEN
*           Write the matrix A.
            CALL UD01MD( M, N, 5, NOUT, A, LDA, ' Matrix A', INFO1 )
            IF ( INFO1.NE.0 )
     $         WRITE ( NOUT, FMT = 99998 ) INFO1
         END IF
         IF ( INFO.NE.0 )
     $      WRITE ( NOUT, FMT = 99997 ) INFO
      END IF
      STOP
*
99999 FORMAT (' UD01DD EXAMPLE PROGRAM RESULTS', /1X)
99998 FORMAT (' INFO on exit from UD01MD = ',I2)
99997 FORMAT (' INFO on exit from UD01DD = ',I2)
99995 FORMAT (/' N is out of range.',/' N = ',I5)
99994 FORMAT (/' M is out of range.',/' M = ',I5)
      END
Program Data
UD01DD EXAMPLE PROGRAM DATA
6  5
1   1   -1.1
6   1    1.5
2   2   -2.2
6   2    2.5
3   3   -3.3
6   3    3.5
4   4   -4.4
6   4    4.5
5   5   -5.5
6   5    5.5
Program Results
 UD01DD EXAMPLE PROGRAM RESULTS

  Matrix A ( 6X 5)

            1              2              3              4              5
  1   -0.1100000D+01  0.0000000D+00  0.0000000D+00  0.0000000D+00  0.0000000D+00
  2    0.0000000D+00 -0.2200000D+01  0.0000000D+00  0.0000000D+00  0.0000000D+00
  3    0.0000000D+00  0.0000000D+00 -0.3300000D+01  0.0000000D+00  0.0000000D+00
  4    0.0000000D+00  0.0000000D+00  0.0000000D+00 -0.4400000D+01  0.0000000D+00
  5    0.0000000D+00  0.0000000D+00  0.0000000D+00  0.0000000D+00 -0.5500000D+01
  6    0.1500000D+01  0.2500000D+01  0.3500000D+01  0.4500000D+01  0.5500000D+01
 

Return to index