Many comment fix for allowing C Wrapper to work on MATGEN
authorjulie <julielangou@users.noreply.github.com>
Tue, 13 Apr 2010 19:09:55 +0000 (19:09 +0000)
committerjulie <julielangou@users.noreply.github.com>
Tue, 13 Apr 2010 19:09:55 +0000 (19:09 +0000)
35 files changed:
TESTING/MATGEN/clahilb.f
TESTING/MATGEN/claror.f
TESTING/MATGEN/clatm1.f
TESTING/MATGEN/clatm2.f
TESTING/MATGEN/clatm3.f
TESTING/MATGEN/clatm6.f
TESTING/MATGEN/clatme.f
TESTING/MATGEN/clatmr.f
TESTING/MATGEN/clatms.f
TESTING/MATGEN/clatmt.f
TESTING/MATGEN/dlahilb.f
TESTING/MATGEN/dlatm1.f
TESTING/MATGEN/dlatm2.f
TESTING/MATGEN/dlatm3.f
TESTING/MATGEN/dlatme.f
TESTING/MATGEN/dlatmr.f
TESTING/MATGEN/dlatms.f
TESTING/MATGEN/dlatmt.f
TESTING/MATGEN/slahilb.f
TESTING/MATGEN/slatm1.f
TESTING/MATGEN/slatm2.f
TESTING/MATGEN/slatm3.f
TESTING/MATGEN/slatme.f
TESTING/MATGEN/slatmr.f
TESTING/MATGEN/slatms.f
TESTING/MATGEN/slatmt.f
TESTING/MATGEN/zlahilb.f
TESTING/MATGEN/zlaror.f
TESTING/MATGEN/zlatm1.f
TESTING/MATGEN/zlatm2.f
TESTING/MATGEN/zlatm3.f
TESTING/MATGEN/zlatme.f
TESTING/MATGEN/zlatmr.f
TESTING/MATGEN/zlatms.f
TESTING/MATGEN/zlatmt.f

index 692eae0..cc0d319 100644 (file)
@@ -1,4 +1,4 @@
-      SUBROUTINE CLAHILB(N, NRHS, A, LDA, X, LDX, B, LDB, WORK, 
+      SUBROUTINE CLAHILB( N, NRHS, A, LDA, X, LDX, B, LDB, WORK, 
      $     INFO, PATH)
 !
 !  -- LAPACK auxiliary test routine (version 3.0) --
@@ -48,7 +48,7 @@
 !  N       (input) INTEGER
 !          The dimension of the matrix A.
 !
-!  NRHS    (input) NRHS
+!  NRHS    (input) INTEGER
 !          The requested number of right-hand sides.
 !
 !  A       (output) COMPLEX array, dimension (LDA, N)
index edf81ad..cea544a 100644 (file)
@@ -26,7 +26,7 @@
 *  Arguments
 *  =========
 *
-*  SIDE   - CHARACTER*1
+*  SIDE     (input) CHARACTER*1
 *           SIDE specifies whether A is multiplied on the left or right
 *           by U.
 *       SIDE = 'L'   Multiply A on the left (premultiply) by U
@@ -35,7 +35,7 @@
 *       SIDE = 'T'   Multiply A on the left by U and the right by U'
 *           Not modified.
 *
-*  INIT   - CHARACTER*1
+*  INIT     (input) CHARACTER*1
 *           INIT specifies whether or not A should be initialized to
 *           the identity matrix.
 *              INIT = 'I'   Initialize A to (a section of) the
 *
 *           Not modified.
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of A. Not modified.
 *
-*  A      - COMPLEX array, dimension ( LDA, N )
+*  A        (input/output) COMPLEX array, dimension ( LDA, N )
 *           Input and output array. Overwritten by U A ( if SIDE = 'L' )
 *           or by A U ( if SIDE = 'R' )
 *           or by U A U* ( if SIDE = 'C')
 *           or by U A U' ( if SIDE = 'T') on exit.
 *
-*  LDA    - INTEGER
+*  LDA       (input) INTEGER
 *           Leading dimension of A. Must be at least MAX ( 1, M ).
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. The array elements should be between 0 and 4095;
 *           if not they will be reduced mod 4096.  Also, ISEED(4) must
 *           sequence.
 *           Modified.
 *
-*  X      - COMPLEX array, dimension ( 3*MAX( M, N ) )
+*  X        (workspace) COMPLEX array, dimension ( 3*MAX( M, N ) )
 *           Workspace. Of length:
 *               2*M + N if SIDE = 'L',
 *               2*N + M if SIDE = 'R',
 *               3*N     if SIDE = 'C' or 'T'.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           An error flag.  It is set to:
 *            0  if no error.
 *            1  if CLARND returned a bad random number (installation
index a4ad3e6..daac84e 100644 (file)
@@ -24,7 +24,7 @@
 *  Arguments
 *  =========
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry describes how D is to be computed:
 *           MODE = 0 means do not change D.
 *           MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
 *              1 to 1/COND, if negative, from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  IRSIGN - INTEGER
+*  IRSIGN   (input) INTEGER
 *           On entry, if MODE neither -6, 0 nor 6, determines sign of
 *           entries of D
 *           0 => leave entries of D unchanged
 *           1 => multiply each entry of D by random complex number
 *                uniformly distributed with absolute value 1
 *
-*  IDIST  - CHARACTER*1
+*  IDIST    (input) CHARACTER*1
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => real and imaginary parts each UNIFORM( 0, 1 )
@@ -62,7 +62,7 @@
 *           4 => complex number uniform in DISK( 0, 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. The random number generator uses a
 *           linear congruential sequence limited to small
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  D      - COMPLEX array, dimension ( MIN( M , N ) )
+*  D        (input/output) COMPLEX array, dimension ( MIN( M , N ) )
 *           Array to be computed according to MODE, COND and IRSIGN.
 *           May be changed on exit if MODE is nonzero.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of entries of D. Not modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *            0  => normal termination
 *           -1  => if MODE not in range -6 to 6
 *           -2  => if MODE neither -6, 0 nor 6, and
index 690a26e..4becfa7 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of matrix. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of matrix. Not modified.
 *
-*  I      - INTEGER
+*  I        (input) INTEGER
 *           Row of entry to be returned. Not modified.
 *
-*  J      - INTEGER
+*  J        (input) INTEGER
 *           Column of entry to be returned. Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           Lower bandwidth. Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           Upper bandwidth. Not modified.
 *
-*  IDIST  - INTEGER
+*  IDIST    (input) INTEGER
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => real and imaginary parts each UNIFORM( 0, 1 )
 *           4 => complex number uniform in DISK( 0 , 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER            array of dimension ( 4 )
+*  ISEED    (input/output) INTEGER array of dimension ( 4 )
 *           Seed for random number generator.
 *           Changed on exit.
 *
-*  D      - COMPLEX            array of dimension ( MIN( I , J ) )
+*  D        (input) COMPLEX array of dimension ( MIN( I , J ) )
 *           Diagonal entries of matrix. Not modified.
 *
-*  IGRADE - INTEGER
+*  IGRADE   (input) INTEGER
 *           Specifies grading of matrix as follows:
 *           0  => no grading
 *           1  => matrix premultiplied by diag( DL )
 *                         postmultiplied by diag( DL )
 *           Not modified.
 *
-*  DL     - COMPLEX            array ( I or J, as appropriate )
+*  DL       (input) COMPLEX array ( I or J, as appropriate )
 *           Left scale factors for grading matrix.  Not modified.
 *
-*  DR     - COMPLEX            array ( I or J, as appropriate )
+*  DR       (input) COMPLEX array ( I or J, as appropriate )
 *           Right scale factors for grading matrix.  Not modified.
 *
-*  IPVTNG - INTEGER
+*  IPVTNG   (input) INTEGER
 *           On entry specifies pivoting permutations as follows:
 *           0 => none.
 *           1 => row pivoting.
 *           3 => full pivoting, i.e., on both sides.
 *           Not modified.
 *
-*  IWORK  - INTEGER            array ( I or J, as appropriate )
+*  IWORK    (workspace) INTEGER array ( I or J, as appropriate )
 *           This array specifies the permutation used. The
 *           row (or column) in position K was originally in
 *           position IWORK( K ).
 *           This differs from IWORK for CLATM3. Not modified.
 *
-*  SPARSE - REAL               between 0. and 1.
+*  SPARSE   (input) REAL 
+*           Value between 0. and 1.
 *           On entry specifies the sparsity of the matrix
 *           if sparse matix is to be generated.
 *           SPARSE should lie between 0 and 1.
index e9c032e..040b62e 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of matrix. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of matrix. Not modified.
 *
-*  I      - INTEGER
+*  I        (input) INTEGER
 *           Row of unpivoted entry to be returned. Not modified.
 *
-*  J      - INTEGER
+*  J        (input) INTEGER
 *           Column of unpivoted entry to be returned. Not modified.
 *
-*  ISUB   - INTEGER
+*  ISUB    (input/output) INTEGER
 *           Row of pivoted entry to be returned. Changed on exit.
 *
-*  JSUB   - INTEGER
+*  JSUB     (input/output) INTEGER
 *           Column of pivoted entry to be returned. Changed on exit.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           Lower bandwidth. Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           Upper bandwidth. Not modified.
 *
-*  IDIST  - INTEGER
+*  IDIST    (input) INTEGER
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => real and imaginary parts each UNIFORM( 0, 1 )
 *           4 => complex number uniform in DISK( 0 , 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER            array of dimension ( 4 )
+*  ISEED    (input/output) INTEGER array of dimension ( 4 )
 *           Seed for random number generator.
 *           Changed on exit.
 *
-*  D      - COMPLEX            array of dimension ( MIN( I , J ) )
+*  D        (input) COMPLEX array of dimension ( MIN( I , J ) )
 *           Diagonal entries of matrix. Not modified.
 *
-*  IGRADE - INTEGER
+*  IGRADE   (input) INTEGER
 *           Specifies grading of matrix as follows:
 *           0  => no grading
 *           1  => matrix premultiplied by diag( DL )
 *                         postmultiplied by diag( DL )
 *           Not modified.
 *
-*  DL     - COMPLEX            array ( I or J, as appropriate )
+*  DL       (input) COMPLEX array ( I or J, as appropriate )
 *           Left scale factors for grading matrix.  Not modified.
 *
-*  DR     - COMPLEX            array ( I or J, as appropriate )
+*  DR       (input) COMPLEX array ( I or J, as appropriate )
 *           Right scale factors for grading matrix.  Not modified.
 *
-*  IPVTNG - INTEGER
+*  IPVTNG   (input) INTEGER
 *           On entry specifies pivoting permutations as follows:
 *           0 => none.
 *           1 => row pivoting.
 *           3 => full pivoting, i.e., on both sides.
 *           Not modified.
 *
-*  IWORK  - INTEGER            array ( I or J, as appropriate )
+*  IWORK    (input) INTEGER array ( I or J, as appropriate )
 *           This array specifies the permutation used. The
 *           row (or column) originally in position K is in
 *           position IWORK( K ) after pivoting.
 *           This differs from IWORK for CLATM2. Not modified.
 *
-*  SPARSE - REAL               between 0. and 1.
+*  SPARSE   (input) REAL between 0. and 1.
 *           On entry specifies the sparsity of the matrix
 *           if sparse matix is to be generated.
 *           SPARSE should lie between 0 and 1.
index 174ee62..3b57854 100644 (file)
@@ -86,6 +86,7 @@
 *          The leading dimension of Y.
 *
 *  ALPHA   (input) COMPLEX
+*
 *  BETA    (input) COMPLEX
 *          Weighting constants for matrix A.
 *
index 1a97dad..a2063db 100644 (file)
@@ -1,5 +1,7 @@
-      SUBROUTINE CLATME( N, DIST, ISEED, D, MODE, COND, DMAX, EI, RSIGN,
-     $                   UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, A,
+      SUBROUTINE CLATME( N, DIST, ISEED, D, MODE, COND, DMAX, EI, 
+     $  RSIGN, 
+     $                   UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, 
+     $  A, 
      $                   LDA, WORK, INFO )
 *
 *  -- LAPACK test routine (version 3.1) --
 *  Arguments
 *  =========
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns (or rows) of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values, and on the
 *           upper triangle (see UPPER).
@@ -64,7 +66,7 @@
 *           'D' => uniform on the complex disc |z| < 1.
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  D      - COMPLEX array, dimension ( N )
+*  D        (input/output) COMPLEX array, dimension ( N )
 *           This array is used to specify the eigenvalues of A.  If
 *           MODE=0, then D is assumed to contain the eigenvalues
 *           otherwise they will be computed according to MODE, COND,
 *           DMAX, and RSIGN and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              ranging from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - COMPLEX
+*  DMAX     (input) COMPLEX
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))).  Note that DMAX need not be
 *           equal to DMAX.
 *           Not modified.
 *
-*  EI     - CHARACTER*1 (ignored)
+*  EI       (input) CHARACTER*1 array, dimension ( N )
+*           (ignored)
 *           Not modified.
 *
-*  RSIGN  - CHARACTER*1
+*  RSIGN    (input) CHARACTER*1
 *           If MODE is not 0, 6, or -6, and RSIGN='T', then the
 *           elements of D, as computed according to MODE and COND, will
 *           be multiplied by a random complex number from the unit
 *           only have the values 'T' or 'F'.
 *           Not modified.
 *
-*  UPPER  - CHARACTER*1
+*  UPPER    (input) CHARACTER*1
 *           If UPPER='T', then the elements of A above the diagonal
 *           will be set to random numbers out of DIST.  If UPPER='F',
 *           they will not.  UPPER may only have the values 'T' or 'F'.
 *           Not modified.
 *
-*  SIM    - CHARACTER*1
+*  SIM      (input) CHARACTER*1
 *           If SIM='T', then A will be operated on by a "similarity
 *           transform", i.e., multiplied on the left by a matrix X and
 *           on the right by X inverse.  X = U S V, where U and V are
 *           SIM='F', then A will not be transformed.
 *           Not modified.
 *
-*  DS     - REAL array, dimension ( N )
+*  DS       (input/output) REAL array, dimension ( N )
 *           This array is used to specify the singular values of X,
 *           in the same way that D specifies the eigenvalues of A.
 *           If MODE=0, the DS contains the singular values, which
 *           may not be zero.
 *           Modified if MODE is nonzero.
 *
-*  MODES  - INTEGER
-*  CONDS  - REAL
+*  MODES    (input) INTEGER
+*
+*  CONDS    (input) REAL
 *           Similar to MODE and COND, but for specifying the diagonal
 *           of S.  MODES=-6 and +6 are not allowed (since they would
 *           result in randomly ill-conditioned eigenvalues.)
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix.  KL=1
 *           specifies upper Hessenberg form.  If KL is at least N-1,
 *           then A will have full lower bandwidth.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix.  KU=1
 *           specifies lower Hessenberg form.  If KU is at least N-1,
 *           then A will have full upper bandwidth; if KU and KL
 *           KU and KL may be less than N-1.
 *           Not modified.
 *
-*  ANORM  - REAL
+*  ANORM    (input) REAL
 *           If ANORM is not negative, then A will be scaled by a non-
 *           negative real number to make the maximum-element-norm of A
 *           to be ANORM.
 *           Not modified.
 *
-*  A      - COMPLEX array, dimension ( LDA, N )
+*  A        (output) COMPLEX array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  LDA must be at least M.
 *           Not modified.
 *
-*  WORK   - COMPLEX array, dimension ( 3*N )
+*  WORK     (workspace) COMPLEX array, dimension ( 3*N )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index cb8d3ca..6558141 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate a random matrix .
 *           'U' => real and imaginary parts are independent
@@ -98,7 +98,7 @@
 *           'D' => uniform on interior of unit disk ( 'D' for disk )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension (4)
+*  ISEED    (input/output) INTEGER array, dimension (4)
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='S', generated matrix is symmetric.
 *           If SYM='H', generated matrix is Hermitian.
 *           If SYM='N', generated matrix is nonsymmetric.
 *           Not modified.
 *
-*  D      - COMPLEX array, dimension (min(M,N))
+*  D        (input/output) COMPLEX array, dimension (min(M,N))
 *           On entry this array specifies the diagonal entries
 *           of the diagonal of A.  D may either be specified
 *           on entry, or set according to MODE and COND as described
 *           below. If the matrix is Hermitian, the real part of D
 *           will be taken. May be changed on exit if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry describes how D is to be used:
 *           MODE = 0 means use D as input
 *           MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
 *              1 to 1/COND, if negative, from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - COMPLEX
+*  DMAX     (input) COMPLEX
 *           If MODE neither -6, 0 nor 6, the diagonal is scaled by
 *           DMAX / max(abs(D(i))), so that maximum absolute entry
 *           of diagonal is abs(DMAX). If DMAX is complex (or zero),
 *           diagonal will be scaled by a complex number (or zero).
 *
-*  RSIGN  - CHARACTER*1
+*  RSIGN    (input) CHARACTER*1
 *           If MODE neither -6, 0 nor 6, specifies sign of diagonal
 *           as follows:
 *           'T' => diagonal entries are multiplied by a random complex
 *           'F' => diagonal unchanged
 *           Not modified.
 *
-*  GRADE  - CHARACTER*1
+*  GRADE    (input) CHARACTER*1
 *           Specifies grading of matrix as follows:
 *           'N'  => no grading
 *           'L'  => matrix premultiplied by diag( DL )
 *                   Note: if GRADE='S', then M must equal N.
 *           Not modified.
 *
-*  DL     - COMPLEX array, dimension (M)
+*  DL       (input/output) COMPLEX array, dimension (M)
 *           If MODEL=0, then on entry this array specifies the diagonal
 *           entries of a diagonal matrix used as described under GRADE
 *           above. If MODEL is not zero, then DL will be set according
 *           If GRADE='E', then DL cannot have zero entries.
 *           Not referenced if GRADE = 'N' or 'R'. Changed on exit.
 *
-*  MODEL  - INTEGER
+*  MODEL    (input) INTEGER
 *           This specifies how the diagonal array DL is to be computed,
 *           just as MODE specifies how D is to be computed.
 *           Not modified.
 *
-*  CONDL  - REAL
+*  CONDL    (input) REAL
 *           When MODEL is not zero, this specifies the condition number
 *           of the computed DL.  Not modified.
 *
-*  DR     - COMPLEX array, dimension (N)
+*  DR       (input/output) COMPLEX array, dimension (N)
 *           If MODER=0, then on entry this array specifies the diagonal
 *           entries of a diagonal matrix used as described under GRADE
 *           above. If MODER is not zero, then DR will be set according
 *           Not referenced if GRADE = 'N', 'L', 'H' or 'S'.
 *           Changed on exit.
 *
-*  MODER  - INTEGER
+*  MODER    (input) INTEGER
 *           This specifies how the diagonal array DR is to be computed,
 *           just as MODE specifies how D is to be computed.
 *           Not modified.
 *
-*  CONDR  - REAL
+*  CONDR    (input) REAL
 *           When MODER is not zero, this specifies the condition number
 *           of the computed DR.  Not modified.
 *
-*  PIVTNG - CHARACTER*1
+*  PIVTNG   (input) CHARACTER*1
 *           On entry specifies pivoting permutations as follows:
 *           'N' or ' ' => none.
 *           'L' => left or row pivoting (matrix must be nonsymmetric).
 *           contain the same data. This consistency cannot be
 *           maintained with less than full bandwidth.
 *
-*  IPIVOT - INTEGER array, dimension (N or M)
+*  IPIVOT   (input) INTEGER array, dimension (N or M)
 *           This array specifies the permutation used.  After the
 *           basic matrix is generated, the rows, columns, or both
 *           are permuted.   If, say, row pivoting is selected, CLATMR
 *           result in a pivot vector identical to IPIVOT.
 *           Not referenced if PIVTNG = 'N'. Not modified.
 *
-*  SPARSE - REAL
+*  SPARSE   (input) REAL
 *           On entry specifies the sparsity of the matrix if a sparse
 *           matrix is to be generated. SPARSE should lie between
 *           0 and 1. To generate a sparse matrix, for each matrix entry
 *           entries will be set to zero.
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           On entry specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL at least M-1 implies the matrix is not
 *           banded. Must equal KU if matrix is symmetric or Hermitian.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           On entry specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU at least N-1 implies the matrix is not
 *           banded. Must equal KL if matrix is symmetric or Hermitian.
 *           Not modified.
 *
-*  ANORM  - REAL
+*  ANORM    (input) REAL
 *           On entry specifies maximum entry of output matrix
 *           (output matrix will by multiplied by a constant so that
 *           its largest absolute entry equal ANORM)
 *           if ANORM is nonnegative. If ANORM is negative no scaling
 *           is done. Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           On entry specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - COMPLEX array, dimension (LDA,N)
+*  A        (input/output) COMPLEX array, dimension (LDA,N)
 *           On exit A is the desired test matrix. Only those
 *           entries of A which are significant on output
 *           will be referenced (even if A is in packed or band
 *           storage format). The 'unoccupied corners' of A in
 *           band format will be zeroed out.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           on entry LDA specifies the first dimension of A as
 *           declared in the calling program.
 *           If PACK='N', 'U' or 'L', LDA must be at least max ( 1, M ).
 *           KUU = MIN ( KU, N-1 ) and KLL = MIN ( KL, N-1 )
 *           Not modified.
 *
-*  IWORK  - INTEGER array, dimension (N or M)
+*  IWORK    (workspace) INTEGER array, dimension (N or M)
 *           Workspace. Not referenced if PIVTNG = 'N'. Changed on exit.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error parameter on exit:
 *             0 => normal return
 *            -1 => M negative or unequal to N and SYM='S' or 'H'
index 0d4361c..fb54f8a 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           The number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns of A. N must equal M if the matrix
 *           is symmetric or hermitian (i.e., if SYM is not 'N')
 *           Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values.
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -93,7 +93,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='H', the generated matrix is hermitian, with
 *             eigenvalues specified by D, COND, MODE, and DMAX; they
 *             may be positive, negative, or zero.
 *             DMAX; they will not be negative.
 *           Not modified.
 *
-*  D      - REAL array, dimension ( MIN( M, N ) )
+*  D        (input/output) REAL array, dimension ( MIN( M, N ) )
 *           This array is used to specify the singular values or
 *           eigenvalues of A (see SYM, above.)  If MODE=0, then D is
 *           assumed to contain the singular/eigenvalues, otherwise
 *           and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the singular/eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              sign (i.e., +1 or -1.)
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - REAL
+*  DMAX     (input) REAL
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or
 *           (or zero), D will be scaled by a negative number (or zero).
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL being at least M-1 means that the matrix
 *           is symmetric or hermitian.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU being at least N-1 means that the matrix
 *           is symmetric or hermitian.
 *           Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           This specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - COMPLEX array, dimension ( LDA, N )
+*  A        (input/output) COMPLEX array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.  A is first generated
 *           in full (unpacked) form, and then packed, if so specified
 *           by PACK.  Thus, the first M elements of the first N
 *           matrix are set to zero.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  If PACK='N', 'U', 'L', 'C', or 'R', then
 *           LDA must be at least M.  If PACK='B' or 'Q', then LDA must
 *           array: MIN( KU, N-1) + MIN( KL, M-1) + 1.
 *           Not modified.
 *
-*  WORK   - COMPLEX array, dimension ( 3*MAX( N, M ) )
+*  WORK     (workspace) COMPLEX array, dimension ( 3*MAX( N, M ) )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index a1b8e37..1d7a13c 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           The number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns of A. N must equal M if the matrix
 *           is symmetric or hermitian (i.e., if SYM is not 'N')
 *           Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values.
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -93,7 +93,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='H', the generated matrix is hermitian, with
 *             eigenvalues specified by D, COND, MODE, and DMAX; they
 *             may be positive, negative, or zero.
 *             DMAX; they will not be negative.
 *           Not modified.
 *
-*  D      - REAL array, dimension ( MIN( M, N ) )
+*  D        (input/output) REAL array, dimension ( MIN( M, N ) )
 *           This array is used to specify the singular values or
 *           eigenvalues of A (see SYM, above.)  If MODE=0, then D is
 *           assumed to contain the singular/eigenvalues, otherwise
 *           and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the singular/eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              sign (i.e., +1 or -1.)
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - REAL
+*  DMAX     (input) REAL
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or
 *           (or zero), D will be scaled by a negative number (or zero).
 *           Not modified.
 *
-*  RANK   - INTEGER
+*  RANK     (input) INTEGER
 *           The rank of matrix to be generated for modes 1,2,3 only.
 *           D( RANK+1:N ) = 0.
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL being at least M-1 means that the matrix
 *           is symmetric or hermitian.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU being at least N-1 means that the matrix
 *           is symmetric or hermitian.
 *           Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           This specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - COMPLEX array, dimension ( LDA, N )
+*  A        (input/output) COMPLEX array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.  A is first generated
 *           in full (unpacked) form, and then packed, if so specified
 *           by PACK.  Thus, the first M elements of the first N
 *           matrix are set to zero.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  If PACK='N', 'U', 'L', 'C', or 'R', then
 *           LDA must be at least M.  If PACK='B' or 'Q', then LDA must
 *           array: MIN( KU, N-1) + MIN( KL, M-1) + 1.
 *           Not modified.
 *
-*  WORK   - COMPLEX array, dimension ( 3*MAX( N, M ) )
+*  WORK     (workspace) COMPLEX array, dimension ( 3*MAX( N, M ) )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index ebc4d55..5440d46 100644 (file)
@@ -1,4 +1,4 @@
-      SUBROUTINE DLAHILB(N, NRHS, A, LDA, X, LDX, B, LDB, WORK, INFO)
+      SUBROUTINE DLAHILB( N, NRHS, A, LDA, X, LDX, B, LDB, WORK, INFO)
 !
 !  -- LAPACK auxiliary test routine (version 3.0) --
 !     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
@@ -45,7 +45,7 @@
 !  N       (input) INTEGER
 !          The dimension of the matrix A.
 !      
-!  NRHS    (input) NRHS
+!  NRHS    (input) INTEGER
 !          The requested number of right-hand sides.
 !
 !  A       (output) DOUBLE PRECISION array, dimension (LDA, N)
index 3c4be6d..6bf103a 100644 (file)
@@ -24,7 +24,7 @@
 *  Arguments
 *  =========
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry describes how D is to be computed:
 *           MODE = 0 means do not change D.
 *           MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
 *              1 to 1/COND, if negative, from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  IRSIGN - INTEGER
+*  IRSIGN   (input) INTEGER
 *           On entry, if MODE neither -6, 0 nor 6, determines sign of
 *           entries of D
 *           0 => leave entries of D unchanged
 *           1 => multiply each entry of D by 1 or -1 with probability .5
 *
-*  IDIST  - CHARACTER*1
+*  IDIST    (input) CHARACTER*1
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => UNIFORM( 0, 1 )
@@ -60,7 +60,7 @@
 *           3 => NORMAL( 0, 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. The random number generator uses a
 *           linear congruential sequence limited to small
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  D      - DOUBLE PRECISION array, dimension ( MIN( M , N ) )
+*  D        (input/output) DOUBLE PRECISION array, dimension ( MIN( M , N ) )
 *           Array to be computed according to MODE, COND and IRSIGN.
 *           May be changed on exit if MODE is nonzero.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of entries of D. Not modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *            0  => normal termination
 *           -1  => if MODE not in range -6 to 6
 *           -2  => if MODE neither -6, 0 nor 6, and
index 86282ee..5397589 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of matrix. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of matrix. Not modified.
 *
-*  I      - INTEGER
+*  I        (input) INTEGER
 *           Row of entry to be returned. Not modified.
 *
-*  J      - INTEGER
+*  J        (input) INTEGER
 *           Column of entry to be returned. Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           Lower bandwidth. Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           Upper bandwidth. Not modified.
 *
-*  IDIST  - INTEGER
+*  IDIST    (input) INTEGER
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => UNIFORM( 0, 1 )
 *           3 => NORMAL( 0, 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER array of dimension ( 4 )
+*  ISEED    (input/output) INTEGER array of dimension ( 4 )
 *           Seed for random number generator.
 *           Changed on exit.
 *
-*  D      - DOUBLE PRECISION array of dimension ( MIN( I , J ) )
+*  D        (input) DOUBLE PRECISION array of dimension ( MIN( I , J ) )
 *           Diagonal entries of matrix. Not modified.
 *
-*  IGRADE - INTEGER
+*  IGRADE   (input) INTEGER
 *           Specifies grading of matrix as follows:
 *           0  => no grading
 *           1  => matrix premultiplied by diag( DL )
 *                         postmultiplied by diag( DL )
 *           Not modified.
 *
-*  DL     - DOUBLE PRECISION array ( I or J, as appropriate )
+*  DL       (input) DOUBLE PRECISION array ( I or J, as appropriate )
 *           Left scale factors for grading matrix.  Not modified.
 *
-*  DR     - DOUBLE PRECISION array ( I or J, as appropriate )
+*  DR       (input) DOUBLE PRECISION array ( I or J, as appropriate )
 *           Right scale factors for grading matrix.  Not modified.
 *
-*  IPVTNG - INTEGER
+*  IPVTNG   (input) INTEGER
 *           On entry specifies pivoting permutations as follows:
 *           0 => none.
 *           1 => row pivoting.
 *           3 => full pivoting, i.e., on both sides.
 *           Not modified.
 *
-*  IWORK  - INTEGER array ( I or J, as appropriate )
+*  IWORK    (workspace) INTEGER array ( I or J, as appropriate )
 *           This array specifies the permutation used. The
 *           row (or column) in position K was originally in
 *           position IWORK( K ).
 *           This differs from IWORK for DLATM3. Not modified.
 *
-*  SPARSE - DOUBLE PRECISION    between 0. and 1.
+*  SPARSE   (input) DOUBLE PRECISION    between 0. and 1.
 *           On entry specifies the sparsity of the matrix
 *           if sparse matix is to be generated.
 *           SPARSE should lie between 0 and 1.
index 159c044..ac3b5e8 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of matrix. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of matrix. Not modified.
 *
-*  I      - INTEGER
+*  I       (input) INTEGER
 *           Row of unpivoted entry to be returned. Not modified.
 *
-*  J      - INTEGER
+*  J        (input) INTEGER
 *           Column of unpivoted entry to be returned. Not modified.
 *
-*  ISUB   - INTEGER
+*  ISUB    (input/output) INTEGER
 *           Row of pivoted entry to be returned. Changed on exit.
 *
-*  JSUB   - INTEGER
+*  JSUB     (input/output) INTEGER
 *           Column of pivoted entry to be returned. Changed on exit.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           Lower bandwidth. Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           Upper bandwidth. Not modified.
 *
-*  IDIST  - INTEGER
+*  IDIST    (input) INTEGER
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => UNIFORM( 0, 1 )
 *           3 => NORMAL( 0, 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER array of dimension ( 4 )
+*  ISEED    (input/output) INTEGER array of dimension ( 4 )
 *           Seed for random number generator.
 *           Changed on exit.
 *
-*  D      - DOUBLE PRECISION array of dimension ( MIN( I , J ) )
+*  D        (input) DOUBLE PRECISION array of dimension ( MIN( I , J ) )
 *           Diagonal entries of matrix. Not modified.
 *
-*  IGRADE - INTEGER
+*  IGRADE   (input) INTEGER
 *           Specifies grading of matrix as follows:
 *           0  => no grading
 *           1  => matrix premultiplied by diag( DL )
 *                         postmultiplied by diag( DL )
 *           Not modified.
 *
-*  DL     - DOUBLE PRECISION array ( I or J, as appropriate )
+*  DL       (input) DOUBLE PRECISION array ( I or J, as appropriate )
 *           Left scale factors for grading matrix.  Not modified.
 *
-*  DR     - DOUBLE PRECISION array ( I or J, as appropriate )
+*  DR       (input) DOUBLE PRECISION array ( I or J, as appropriate )
 *           Right scale factors for grading matrix.  Not modified.
 *
-*  IPVTNG - INTEGER
+*  IPVTNG   (input) INTEGER
 *           On entry specifies pivoting permutations as follows:
 *           0 => none.
 *           1 => row pivoting.
 *           3 => full pivoting, i.e., on both sides.
 *           Not modified.
 *
-*  IWORK  - INTEGER array ( I or J, as appropriate )
+*  IWORK    (input) INTEGER array ( I or J, as appropriate )
 *           This array specifies the permutation used. The
 *           row (or column) originally in position K is in
 *           position IWORK( K ) after pivoting.
 *           This differs from IWORK for DLATM2. Not modified.
 *
-*  SPARSE - DOUBLE PRECISION between 0. and 1.
+*  SPARSE   (input) DOUBLE PRECISION between 0. and 1.
 *           On entry specifies the sparsity of the matrix
 *           if sparse matix is to be generated.
 *           SPARSE should lie between 0 and 1.
index 70c20fa..834b1c6 100644 (file)
@@ -1,5 +1,7 @@
-      SUBROUTINE DLATME( N, DIST, ISEED, D, MODE, COND, DMAX, EI, RSIGN,
-     $                   UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, A,
+      SUBROUTINE DLATME( N, DIST, ISEED, D, MODE, COND, DMAX, EI, 
+     $  RSIGN, 
+     $                   UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, 
+     $  A, 
      $                   LDA, WORK, INFO )
 *
 *  -- LAPACK test routine (version 3.1) --
 *  Arguments
 *  =========
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns (or rows) of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values, and for the
 *           upper triangle (see UPPER).
@@ -68,7 +70,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
@@ -79,7 +81,7 @@
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  D      - DOUBLE PRECISION array, dimension ( N )
+*  D        (input/output) DOUBLE PRECISION array, dimension ( N )
 *           This array is used to specify the eigenvalues of A.  If
 *           MODE=0, then D is assumed to contain the eigenvalues (but
 *           see the description of EI), otherwise they will be
@@ -87,7 +89,7 @@
 *           placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D (with EI) as input
 *              ranging from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - DOUBLE PRECISION
+*  DMAX     (input) DOUBLE PRECISION
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))).  Note that DMAX need not be
 *           scaled by a negative number (or zero).
 *           Not modified.
 *
-*  EI     - CHARACTER*1 array, dimension ( N )
+*  EI       (input) CHARACTER*1 array, dimension ( N )
 *           If MODE is 0, and EI(1) is not ' ' (space character),
 *           this array specifies which elements of D (on input) are
 *           real eigenvalues and which are the real and imaginary parts
 *           EI(1)=' ', then the eigenvalues will all be real.
 *           Not modified.
 *
-*  RSIGN  - CHARACTER*1
+*  RSIGN    (input) CHARACTER*1
 *           If MODE is not 0, 6, or -6, and RSIGN='T', then the
 *           elements of D, as computed according to MODE and COND, will
 *           be multiplied by a random sign (+1 or -1).  If RSIGN='F',
 *           'F'.
 *           Not modified.
 *
-*  UPPER  - CHARACTER*1
+*  UPPER    (input) CHARACTER*1
 *           If UPPER='T', then the elements of A above the diagonal
 *           (and above the 2x2 diagonal blocks, if A has complex
 *           eigenvalues) will be set to random numbers out of DIST.
 *           values 'T' or 'F'.
 *           Not modified.
 *
-*  SIM    - CHARACTER*1
+*  SIM      (input) CHARACTER*1
 *           If SIM='T', then A will be operated on by a "similarity
 *           transform", i.e., multiplied on the left by a matrix X and
 *           on the right by X inverse.  X = U S V, where U and V are
 *           SIM='F', then A will not be transformed.
 *           Not modified.
 *
-*  DS     - DOUBLE PRECISION array, dimension ( N )
+*  DS       (input/output) DOUBLE PRECISION array, dimension ( N )
 *           This array is used to specify the singular values of X,
 *           in the same way that D specifies the eigenvalues of A.
 *           If MODE=0, the DS contains the singular values, which
 *           may not be zero.
 *           Modified if MODE is nonzero.
 *
-*  MODES  - INTEGER
-*  CONDS  - DOUBLE PRECISION
+*  MODES    (input) INTEGER
+*
+*  CONDS    (input) DOUBLE PRECISION
 *           Same as MODE and COND, but for specifying the diagonal
 *           of S.  MODES=-6 and +6 are not allowed (since they would
 *           result in randomly ill-conditioned eigenvalues.)
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix.  KL=1
 *           specifies upper Hessenberg form.  If KL is at least N-1,
 *           then A will have full lower bandwidth.  KL must be at
 *           least 1.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix.  KU=1
 *           specifies lower Hessenberg form.  If KU is at least N-1,
 *           then A will have full upper bandwidth; if KU and KL
 *           KU and KL may be less than N-1.  KU must be at least 1.
 *           Not modified.
 *
-*  ANORM  - DOUBLE PRECISION
+*  ANORM    (input) DOUBLE PRECISION
 *           If ANORM is not negative, then A will be scaled by a non-
 *           negative real number to make the maximum-element-norm of A
 *           to be ANORM.
 *           Not modified.
 *
-*  A      - DOUBLE PRECISION array, dimension ( LDA, N )
+*  A        (output) DOUBLE PRECISION array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  LDA must be at least N.
 *           Not modified.
 *
-*  WORK   - DOUBLE PRECISION array, dimension ( 3*N )
+*  WORK     (workspace) DOUBLE PRECISION array, dimension ( 3*N )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index deb3db6..ea38486 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate a random matrix .
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -90,7 +90,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension (4)
+*  ISEED    (input/output) INTEGER array, dimension (4)
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='S' or 'H', generated matrix is symmetric.
 *           If SYM='N', generated matrix is nonsymmetric.
 *           Not modified.
 *
-*  D      - DOUBLE PRECISION array, dimension (min(M,N))
+*  D        (input/output) DOUBLE PRECISION array, dimension (min(M,N))
 *           On entry this array specifies the diagonal entries
 *           of the diagonal of A.  D may either be specified
 *           on entry, or set according to MODE and COND as described
 *           below. May be changed on exit if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry describes how D is to be used:
 *           MODE = 0 means use D as input
 *           MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
 *              1 to 1/COND, if negative, from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - DOUBLE PRECISION
+*  DMAX     (input) DOUBLE PRECISION
 *           If MODE neither -6, 0 nor 6, the diagonal is scaled by
 *           DMAX / max(abs(D(i))), so that maximum absolute entry
 *           of diagonal is abs(DMAX). If DMAX is negative (or zero),
 *           diagonal will be scaled by a negative number (or zero).
 *
-*  RSIGN  - CHARACTER*1
+*  RSIGN    (input) CHARACTER*1
 *           If MODE neither -6, 0 nor 6, specifies sign of diagonal
 *           as follows:
 *           'T' => diagonal entries are multiplied by 1 or -1
 *           'F' => diagonal unchanged
 *           Not modified.
 *
-*  GRADE  - CHARACTER*1
+*  GRADE    (input) CHARACTER*1
 *           Specifies grading of matrix as follows:
 *           'N'  => no grading
 *           'L'  => matrix premultiplied by diag( DL )
 *                   Note: if GRADE='E', then M must equal N.
 *           Not modified.
 *
-*  DL     - DOUBLE PRECISION array, dimension (M)
+*  DL       (input/output) DOUBLE PRECISION array, dimension (M)
 *           If MODEL=0, then on entry this array specifies the diagonal
 *           entries of a diagonal matrix used as described under GRADE
 *           above. If MODEL is not zero, then DL will be set according
 *           If GRADE='E', then DL cannot have zero entries.
 *           Not referenced if GRADE = 'N' or 'R'. Changed on exit.
 *
-*  MODEL  - INTEGER
+*  MODEL    (input) INTEGER
 *           This specifies how the diagonal array DL is to be computed,
 *           just as MODE specifies how D is to be computed.
 *           Not modified.
 *
-*  CONDL  - DOUBLE PRECISION
+*  CONDL    (input) DOUBLE PRECISION
 *           When MODEL is not zero, this specifies the condition number
 *           of the computed DL.  Not modified.
 *
-*  DR     - DOUBLE PRECISION array, dimension (N)
+*  DR       (input/output) DOUBLE PRECISION array, dimension (N)
 *           If MODER=0, then on entry this array specifies the diagonal
 *           entries of a diagonal matrix used as described under GRADE
 *           above. If MODER is not zero, then DR will be set according
 *           Not referenced if GRADE = 'N', 'L', 'H', 'S' or 'E'.
 *           Changed on exit.
 *
-*  MODER  - INTEGER
+*  MODER    (input) INTEGER
 *           This specifies how the diagonal array DR is to be computed,
 *           just as MODE specifies how D is to be computed.
 *           Not modified.
 *
-*  CONDR  - DOUBLE PRECISION
+*  CONDR    (input) DOUBLE PRECISION
 *           When MODER is not zero, this specifies the condition number
 *           of the computed DR.  Not modified.
 *
-*  PIVTNG - CHARACTER*1
+*  PIVTNG   (input) CHARACTER*1
 *           On entry specifies pivoting permutations as follows:
 *           'N' or ' ' => none.
 *           'L' => left or row pivoting (matrix must be nonsymmetric).
 *           contain the same data. This consistency cannot be
 *           maintained with less than full bandwidth.
 *
-*  IPIVOT - INTEGER array, dimension (N or M)
+*  IPIVOT   (input) INTEGER array, dimension (N or M)
 *           This array specifies the permutation used.  After the
 *           basic matrix is generated, the rows, columns, or both
 *           are permuted.   If, say, row pivoting is selected, DLATMR
 *           result in a pivot vector identical to IPIVOT.
 *           Not referenced if PIVTNG = 'N'. Not modified.
 *
-*  SPARSE - DOUBLE PRECISION
+*  SPARSE   (input) DOUBLE PRECISION
 *           On entry specifies the sparsity of the matrix if a sparse
 *           matrix is to be generated. SPARSE should lie between
 *           0 and 1. To generate a sparse matrix, for each matrix entry
 *           entries will be set to zero.
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           On entry specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL at least M-1 implies the matrix is not
 *           banded. Must equal KU if matrix is symmetric.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           On entry specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU at least N-1 implies the matrix is not
 *           banded. Must equal KL if matrix is symmetric.
 *           Not modified.
 *
-*  ANORM  - DOUBLE PRECISION
+*  ANORM    (input) DOUBLE PRECISION
 *           On entry specifies maximum entry of output matrix
 *           (output matrix will by multiplied by a constant so that
 *           its largest absolute entry equal ANORM)
 *           if ANORM is nonnegative. If ANORM is negative no scaling
 *           is done. Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           On entry specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric)
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - DOUBLE PRECISION array, dimension (LDA,N)
+*  A        (output) DOUBLE PRECISION array, dimension (LDA,N)
 *           On exit A is the desired test matrix. Only those
 *           entries of A which are significant on output
 *           will be referenced (even if A is in packed or band
 *           storage format). The 'unoccupied corners' of A in
 *           band format will be zeroed out.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           on entry LDA specifies the first dimension of A as
 *           declared in the calling program.
 *           If PACK='N', 'U' or 'L', LDA must be at least max ( 1, M ).
 *           KUU = MIN ( KU, N-1 ) and KLL = MIN ( KL, N-1 )
 *           Not modified.
 *
-*  IWORK  - INTEGER array, dimension ( N or M)
+*  IWORK    (workspace) INTEGER array, dimension ( N or M)
 *           Workspace. Not referenced if PIVTNG = 'N'. Changed on exit.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error parameter on exit:
 *             0 => normal return
 *            -1 => M negative or unequal to N and SYM='S' or 'H'
index 9949681..25e68bf 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           The number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values.
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -90,7 +90,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='S' or 'H', the generated matrix is symmetric, with
 *             eigenvalues specified by D, COND, MODE, and DMAX; they
 *             may be positive, negative, or zero.
 *             they will not be negative.
 *           Not modified.
 *
-*  D      - DOUBLE PRECISION array, dimension ( MIN( M , N ) )
+*  D        (input/output) DOUBLE PRECISION array, dimension ( MIN( M , N ) )
 *           This array is used to specify the singular values or
 *           eigenvalues of A (see SYM, above.)  If MODE=0, then D is
 *           assumed to contain the singular/eigenvalues, otherwise
 *           and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the singular/eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              sign (i.e., +1 or -1.)
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - DOUBLE PRECISION
+*  DMAX     (input) DOUBLE PRECISION
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or
 *           (or zero), D will be scaled by a negative number (or zero).
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL being at least M-1 means that the matrix
 *           is symmetric.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU being at least N-1 means that the matrix
 *           is symmetric.
 *           Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           This specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric)
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - DOUBLE PRECISION array, dimension ( LDA, N )
+*  A        (input/output) DOUBLE PRECISION array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.  A is first generated
 *           in full (unpacked) form, and then packed, if so specified
 *           by PACK.  Thus, the first M elements of the first N
 *           matrix are set to zero.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  If PACK='N', 'U', 'L', 'C', or 'R', then
 *           LDA must be at least M.  If PACK='B' or 'Q', then LDA must
 *           array: MIN( KU, N-1) + MIN( KL, M-1) + 1.
 *           Not modified.
 *
-*  WORK   - DOUBLE PRECISION array, dimension ( 3*MAX( N , M ) )
+*  WORK     (workspace) DOUBLE PRECISION array, dimension ( 3*MAX( N , M ) )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index 2ff3255..90a0001 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           The number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values.
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -90,7 +90,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='S' or 'H', the generated matrix is symmetric, with
 *             eigenvalues specified by D, COND, MODE, and DMAX; they
 *             may be positive, negative, or zero.
 *             they will not be negative.
 *           Not modified.
 *
-*  D      - DOUBLE PRECISION array, dimension ( MIN( M , N ) )
+*  D        (input/output) DOUBLE PRECISION array, dimension ( MIN( M , N ) )
 *           This array is used to specify the singular values or
 *           eigenvalues of A (see SYM, above.)  If MODE=0, then D is
 *           assumed to contain the singular/eigenvalues, otherwise
 *           and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the singular/eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              sign (i.e., +1 or -1.)
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - DOUBLE PRECISION
+*  DMAX     (input) DOUBLE PRECISION
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or
 *           (or zero), D will be scaled by a negative number (or zero).
 *           Not modified.
 *
-*  RANK   - INTEGER
+*  RANK     (input) INTEGER
 *           The rank of matrix to be generated for modes 1,2,3 only.
 *           D( RANK+1:N ) = 0.
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL being at least M-1 means that the matrix
 *           is symmetric.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU being at least N-1 means that the matrix
 *           is symmetric.
 *           Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           This specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric)
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - DOUBLE PRECISION array, dimension ( LDA, N )
+*  A        (input/output) DOUBLE PRECISION array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.  A is first generated
 *           in full (unpacked) form, and then packed, if so specified
 *           by PACK.  Thus, the first M elements of the first N
 *           matrix are set to zero.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  If PACK='N', 'U', 'L', 'C', or 'R', then
 *           LDA must be at least M.  If PACK='B' or 'Q', then LDA must
 *           array: MIN( KU, N-1) + MIN( KL, M-1) + 1.
 *           Not modified.
 *
-*  WORK   - DOUBLE PRECISION array, dimension ( 3*MAX( N , M ) )
+*  WORK     (workspace) DOUBLE PRECISION array, dimension ( 3*MAX( N , M ) )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index afdc420..f030772 100644 (file)
@@ -1,4 +1,4 @@
-      SUBROUTINE SLAHILB(N, NRHS, A, LDA, X, LDX, B, LDB, WORK, INFO)
+      SUBROUTINE SLAHILB( N, NRHS, A, LDA, X, LDX, B, LDB, WORK, INFO)
 !
 !  -- LAPACK auxiliary test routine (version 3.0) --
 !     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
@@ -45,7 +45,7 @@
 !  N       (input) INTEGER
 !          The dimension of the matrix A.
 !      
-!  NRHS    (input) NRHS
+!  NRHS    (input) INTEGER
 !          The requested number of right-hand sides.
 !
 !  A       (output) REAL array, dimension (LDA, N)
index c4033f9..c88c049 100644 (file)
@@ -24,7 +24,7 @@
 *  Arguments
 *  =========
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry describes how D is to be computed:
 *           MODE = 0 means do not change D.
 *           MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
 *              1 to 1/COND, if negative, from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  IRSIGN - INTEGER
+*  IRSIGN   (input) INTEGER
 *           On entry, if MODE neither -6, 0 nor 6, determines sign of
 *           entries of D
 *           0 => leave entries of D unchanged
 *           1 => multiply each entry of D by 1 or -1 with probability .5
 *
-*  IDIST  - CHARACTER*1
+*  IDIST    (input) CHARACTER*1
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => UNIFORM( 0, 1 )
@@ -60,7 +60,7 @@
 *           3 => NORMAL( 0, 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. The random number generator uses a
 *           linear congruential sequence limited to small
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  D      - REAL array, dimension ( MIN( M , N ) )
+*  D        (input/output) REAL array, dimension ( MIN( M , N ) )
 *           Array to be computed according to MODE, COND and IRSIGN.
 *           May be changed on exit if MODE is nonzero.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of entries of D. Not modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *            0  => normal termination
 *           -1  => if MODE not in range -6 to 6
 *           -2  => if MODE neither -6, 0 nor 6, and
index d51a28d..0017973 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of matrix. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of matrix. Not modified.
 *
-*  I      - INTEGER
+*  I        (input) INTEGER
 *           Row of entry to be returned. Not modified.
 *
-*  J      - INTEGER
+*  J        (input) INTEGER
 *           Column of entry to be returned. Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           Lower bandwidth. Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           Upper bandwidth. Not modified.
 *
-*  IDIST  - INTEGER
+*  IDIST    (input) INTEGER
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => UNIFORM( 0, 1 )
 *           3 => NORMAL( 0, 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER array of dimension ( 4 )
+*  ISEED    (input/output) INTEGER array of dimension ( 4 )
 *           Seed for random number generator.
 *           Changed on exit.
 *
-*  D      - REAL array of dimension ( MIN( I , J ) )
+*  D        (input) REAL array of dimension ( MIN( I , J ) )
 *           Diagonal entries of matrix. Not modified.
 *
-*  IGRADE - INTEGER
+*  IGRADE   (input) INTEGER
 *           Specifies grading of matrix as follows:
 *           0  => no grading
 *           1  => matrix premultiplied by diag( DL )
 *                         postmultiplied by diag( DL )
 *           Not modified.
 *
-*  DL     - REAL array ( I or J, as appropriate )
+*  DL       (input) REAL array ( I or J, as appropriate )
 *           Left scale factors for grading matrix.  Not modified.
 *
-*  DR     - REAL array ( I or J, as appropriate )
+*  DR       (input) REAL array ( I or J, as appropriate )
 *           Right scale factors for grading matrix.  Not modified.
 *
-*  IPVTNG - INTEGER
+*  IPVTNG   (input) INTEGER
 *           On entry specifies pivoting permutations as follows:
 *           0 => none.
 *           1 => row pivoting.
 *           3 => full pivoting, i.e., on both sides.
 *           Not modified.
 *
-*  IWORK  - INTEGER array ( I or J, as appropriate )
+*  IWORK    (workspace) INTEGER array ( I or J, as appropriate )
 *           This array specifies the permutation used. The
 *           row (or column) in position K was originally in
 *           position IWORK( K ).
 *           This differs from IWORK for SLATM3. Not modified.
 *
-*  SPARSE - REAL    between 0. and 1.
+*  SPARSE   (input) REAL    between 0. and 1.
 *           On entry specifies the sparsity of the matrix
 *           if sparse matix is to be generated.
 *           SPARSE should lie between 0 and 1.
index f199e26..7d003d9 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of matrix. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of matrix. Not modified.
 *
-*  I      - INTEGER
+*  I        (input) INTEGER
 *           Row of unpivoted entry to be returned. Not modified.
 *
-*  J      - INTEGER
+*  J        (input) INTEGER
 *           Column of unpivoted entry to be returned. Not modified.
 *
-*  ISUB   - INTEGER
+*  ISUB     (input/output) INTEGER
 *           Row of pivoted entry to be returned. Changed on exit.
 *
-*  JSUB   - INTEGER
+*  JSUB     (input/output) INTEGER
 *           Column of pivoted entry to be returned. Changed on exit.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           Lower bandwidth. Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           Upper bandwidth. Not modified.
 *
-*  IDIST  - INTEGER
+*  IDIST    (input) INTEGER
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => UNIFORM( 0, 1 )
 *           3 => NORMAL( 0, 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER array of dimension ( 4 )
+*  ISEED    (input/output) INTEGER array of dimension ( 4 )
 *           Seed for random number generator.
 *           Changed on exit.
 *
-*  D      - REAL array of dimension ( MIN( I , J ) )
+*  D        (input) REAL array of dimension ( MIN( I , J ) )
 *           Diagonal entries of matrix. Not modified.
 *
-*  IGRADE - INTEGER
+*  IGRADE   (input) INTEGER
 *           Specifies grading of matrix as follows:
 *           0  => no grading
 *           1  => matrix premultiplied by diag( DL )
 *                         postmultiplied by diag( DL )
 *           Not modified.
 *
-*  DL     - REAL array ( I or J, as appropriate )
+*  DL       (input) REAL array ( I or J, as appropriate )
 *           Left scale factors for grading matrix.  Not modified.
 *
-*  DR     - REAL array ( I or J, as appropriate )
+*  DR       (input) REAL array ( I or J, as appropriate )
 *           Right scale factors for grading matrix.  Not modified.
 *
-*  IPVTNG - INTEGER
+*  IPVTNG   (input) INTEGER
 *           On entry specifies pivoting permutations as follows:
 *           0 => none.
 *           1 => row pivoting.
 *           3 => full pivoting, i.e., on both sides.
 *           Not modified.
 *
-*  IWORK  - INTEGER array ( I or J, as appropriate )
+*  IWORK    (input) INTEGER array ( I or J, as appropriate )
 *           This array specifies the permutation used. The
 *           row (or column) originally in position K is in
 *           position IWORK( K ) after pivoting.
 *           This differs from IWORK for SLATM2. Not modified.
 *
-*  SPARSE - REAL between 0. and 1.
+*  SPARSE   (input) REAL between 0. and 1.
 *           On entry specifies the sparsity of the matrix
 *           if sparse matix is to be generated.
 *           SPARSE should lie between 0 and 1.
index 319527d..9db211c 100644 (file)
@@ -1,5 +1,7 @@
-      SUBROUTINE SLATME( N, DIST, ISEED, D, MODE, COND, DMAX, EI, RSIGN,
-     $                   UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, A,
+      SUBROUTINE SLATME( N, DIST, ISEED, D, MODE, COND, DMAX, EI, 
+     $  RSIGN, 
+     $                   UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, 
+     $  A, 
      $                   LDA, WORK, INFO )
 *
 *  -- LAPACK test routine (version 3.1) --
 *  Arguments
 *  =========
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns (or rows) of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values, and for the
 *           upper triangle (see UPPER).
@@ -68,7 +70,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
@@ -79,7 +81,7 @@
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  D      - REAL array, dimension ( N )
+*  D        (input/output) REAL array, dimension ( N )
 *           This array is used to specify the eigenvalues of A.  If
 *           MODE=0, then D is assumed to contain the eigenvalues (but
 *           see the description of EI), otherwise they will be
@@ -87,7 +89,7 @@
 *           placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D (with EI) as input
 *              ranging from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - REAL
+*  DMAX     (input) REAL
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))).  Note that DMAX need not be
 *           scaled by a negative number (or zero).
 *           Not modified.
 *
-*  EI     - CHARACTER*1 array, dimension ( N )
+*  EI       (input) CHARACTER*1 array, dimension ( N )
 *           If MODE is 0, and EI(1) is not ' ' (space character),
 *           this array specifies which elements of D (on input) are
 *           real eigenvalues and which are the real and imaginary parts
 *           EI(1)=' ', then the eigenvalues will all be real.
 *           Not modified.
 *
-*  RSIGN  - CHARACTER*1
+*  RSIGN    (input) CHARACTER*1
 *           If MODE is not 0, 6, or -6, and RSIGN='T', then the
 *           elements of D, as computed according to MODE and COND, will
 *           be multiplied by a random sign (+1 or -1).  If RSIGN='F',
 *           'F'.
 *           Not modified.
 *
-*  UPPER  - CHARACTER*1
+*  UPPER    (input) CHARACTER*1
 *           If UPPER='T', then the elements of A above the diagonal
 *           (and above the 2x2 diagonal blocks, if A has complex
 *           eigenvalues) will be set to random numbers out of DIST.
 *           values 'T' or 'F'.
 *           Not modified.
 *
-*  SIM    - CHARACTER*1
+*  SIM      (input) CHARACTER*1
 *           If SIM='T', then A will be operated on by a "similarity
 *           transform", i.e., multiplied on the left by a matrix X and
 *           on the right by X inverse.  X = U S V, where U and V are
 *           SIM='F', then A will not be transformed.
 *           Not modified.
 *
-*  DS     - REAL array, dimension ( N )
+*  DS       (input/output) REAL array, dimension ( N )
 *           This array is used to specify the singular values of X,
 *           in the same way that D specifies the eigenvalues of A.
 *           If MODE=0, the DS contains the singular values, which
 *           may not be zero.
 *           Modified if MODE is nonzero.
 *
-*  MODES  - INTEGER
-*  CONDS  - REAL
+*  MODES    (input) INTEGER
+*
+*  CONDS    (input) REAL
 *           Same as MODE and COND, but for specifying the diagonal
 *           of S.  MODES=-6 and +6 are not allowed (since they would
 *           result in randomly ill-conditioned eigenvalues.)
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix.  KL=1
 *           specifies upper Hessenberg form.  If KL is at least N-1,
 *           then A will have full lower bandwidth.  KL must be at
 *           least 1.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix.  KU=1
 *           specifies lower Hessenberg form.  If KU is at least N-1,
 *           then A will have full upper bandwidth; if KU and KL
 *           KU and KL may be less than N-1.  KU must be at least 1.
 *           Not modified.
 *
-*  ANORM  - REAL
+*  ANORM    (input) REAL
 *           If ANORM is not negative, then A will be scaled by a non-
 *           negative real number to make the maximum-element-norm of A
 *           to be ANORM.
 *           Not modified.
 *
-*  A      - REAL array, dimension ( LDA, N )
+*  A        (output) REAL array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  LDA must be at least N.
 *           Not modified.
 *
-*  WORK   - REAL array, dimension ( 3*N )
+*  WORK     (workspace) REAL array, dimension ( 3*N )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index 424a17b..4d753c7 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate a random matrix .
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -90,7 +90,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension (4)
+*  ISEED    (input/output) INTEGER array, dimension (4)
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='S' or 'H', generated matrix is symmetric.
 *           If SYM='N', generated matrix is nonsymmetric.
 *           Not modified.
 *
-*  D      - REAL array, dimension (min(M,N))
+*  D        (input) REAL array, dimension (min(M,N))
 *           On entry this array specifies the diagonal entries
 *           of the diagonal of A.  D may either be specified
 *           on entry, or set according to MODE and COND as described
 *           below. May be changed on exit if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry describes how D is to be used:
 *           MODE = 0 means use D as input
 *           MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
 *              1 to 1/COND, if negative, from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - REAL
+*  DMAX     (input) REAL
 *           If MODE neither -6, 0 nor 6, the diagonal is scaled by
 *           DMAX / max(abs(D(i))), so that maximum absolute entry
 *           of diagonal is abs(DMAX). If DMAX is negative (or zero),
 *           diagonal will be scaled by a negative number (or zero).
 *
-*  RSIGN  - CHARACTER*1
+*  RSIGN    (input) CHARACTER*1
 *           If MODE neither -6, 0 nor 6, specifies sign of diagonal
 *           as follows:
 *           'T' => diagonal entries are multiplied by 1 or -1
 *           'F' => diagonal unchanged
 *           Not modified.
 *
-*  GRADE  - CHARACTER*1
+*  GRADE    (input) CHARACTER*1
 *           Specifies grading of matrix as follows:
 *           'N'  => no grading
 *           'L'  => matrix premultiplied by diag( DL )
 *                   Note: if GRADE='E', then M must equal N.
 *           Not modified.
 *
-*  DL     - REAL array, dimension (M)
+*  DL       (input/output) REAL array, dimension (M)
 *           If MODEL=0, then on entry this array specifies the diagonal
 *           entries of a diagonal matrix used as described under GRADE
 *           above. If MODEL is not zero, then DL will be set according
 *           If GRADE='E', then DL cannot have zero entries.
 *           Not referenced if GRADE = 'N' or 'R'. Changed on exit.
 *
-*  MODEL  - INTEGER
+*  MODEL    (input) INTEGER
 *           This specifies how the diagonal array DL is to be computed,
 *           just as MODE specifies how D is to be computed.
 *           Not modified.
 *
-*  CONDL  - REAL
+*  CONDL    (input) REAL
 *           When MODEL is not zero, this specifies the condition number
 *           of the computed DL.  Not modified.
 *
-*  DR     - REAL array, dimension (N)
+*  DR       (input/output) REAL array, dimension (N)
 *           If MODER=0, then on entry this array specifies the diagonal
 *           entries of a diagonal matrix used as described under GRADE
 *           above. If MODER is not zero, then DR will be set according
 *           Not referenced if GRADE = 'N', 'L', 'H', 'S' or 'E'.
 *           Changed on exit.
 *
-*  MODER  - INTEGER
+*  MODER    (input) INTEGER
 *           This specifies how the diagonal array DR is to be computed,
 *           just as MODE specifies how D is to be computed.
 *           Not modified.
 *
-*  CONDR  - REAL
+*  CONDR    (input) REAL
 *           When MODER is not zero, this specifies the condition number
 *           of the computed DR.  Not modified.
 *
-*  PIVTNG - CHARACTER*1
+*  PIVTNG   (input) CHARACTER*1
 *           On entry specifies pivoting permutations as follows:
 *           'N' or ' ' => none.
 *           'L' => left or row pivoting (matrix must be nonsymmetric).
 *           contain the same data. This consistency cannot be
 *           maintained with less than full bandwidth.
 *
-*  IPIVOT - INTEGER array, dimension (N or M)
+*  IPIVOT   (input) INTEGER array, dimension (N or M)
 *           This array specifies the permutation used.  After the
 *           basic matrix is generated, the rows, columns, or both
 *           are permuted.   If, say, row pivoting is selected, SLATMR
 *           result in a pivot vector identical to IPIVOT.
 *           Not referenced if PIVTNG = 'N'. Not modified.
 *
-*  SPARSE - REAL
+*  SPARSE   (input) REAL
 *           On entry specifies the sparsity of the matrix if a sparse
 *           matrix is to be generated. SPARSE should lie between
 *           0 and 1. To generate a sparse matrix, for each matrix entry
 *           entries will be set to zero.
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           On entry specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL at least M-1 implies the matrix is not
 *           banded. Must equal KU if matrix is symmetric.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           On entry specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU at least N-1 implies the matrix is not
 *           banded. Must equal KL if matrix is symmetric.
 *           Not modified.
 *
-*  ANORM  - REAL
+*  ANORM    (input) REAL
 *           On entry specifies maximum entry of output matrix
 *           (output matrix will by multiplied by a constant so that
 *           its largest absolute entry equal ANORM)
 *           if ANORM is nonnegative. If ANORM is negative no scaling
 *           is done. Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           On entry specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric)
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - REAL array, dimension (LDA,N)
+*  A        (input/output) REAL array, dimension (LDA,N)
 *           On exit A is the desired test matrix. Only those
 *           entries of A which are significant on output
 *           will be referenced (even if A is in packed or band
 *           storage format). The 'unoccupied corners' of A in
 *           band format will be zeroed out.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           on entry LDA specifies the first dimension of A as
 *           declared in the calling program.
 *           If PACK='N', 'U' or 'L', LDA must be at least max ( 1, M ).
 *           KUU = MIN ( KU, N-1 ) and KLL = MIN ( KL, N-1 )
 *           Not modified.
 *
-*  IWORK  - INTEGER array, dimension ( N or M)
+*  IWORK    (workspace) INTEGER array, dimension ( N or M)
 *           Workspace. Not referenced if PIVTNG = 'N'. Changed on exit.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error parameter on exit:
 *             0 => normal return
 *            -1 => M negative or unequal to N and SYM='S' or 'H'
index 3f70d13..1eec944 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           The number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values.
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -90,7 +90,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='S' or 'H', the generated matrix is symmetric, with
 *             eigenvalues specified by D, COND, MODE, and DMAX; they
 *             may be positive, negative, or zero.
 *             they will not be negative.
 *           Not modified.
 *
-*  D      - REAL array, dimension ( MIN( M , N ) )
+*  D        (input/output) REAL array, dimension ( MIN( M , N ) )
 *           This array is used to specify the singular values or
 *           eigenvalues of A (see SYM, above.)  If MODE=0, then D is
 *           assumed to contain the singular/eigenvalues, otherwise
 *           and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the singular/eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              sign (i.e., +1 or -1.)
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - REAL
+*  DMAX     (input) REAL
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or
 *           (or zero), D will be scaled by a negative number (or zero).
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL being at least M-1 means that the matrix
 *           is symmetric.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU being at least N-1 means that the matrix
 *           is symmetric.
 *           Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           This specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric)
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - REAL array, dimension ( LDA, N )
+*  A        (input/output) REAL array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.  A is first generated
 *           in full (unpacked) form, and then packed, if so specified
 *           by PACK.  Thus, the first M elements of the first N
 *           matrix are set to zero.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  If PACK='N', 'U', 'L', 'C', or 'R', then
 *           LDA must be at least M.  If PACK='B' or 'Q', then LDA must
 *           array: MIN( KU, N-1) + MIN( KL, M-1) + 1.
 *           Not modified.
 *
-*  WORK   - REAL array, dimension ( 3*MAX( N , M ) )
+*  WORK     (workspace) REAL array, dimension ( 3*MAX( N , M ) )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index c0119cc..6e5007c 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           The number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values.
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -90,7 +90,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='S' or 'H', the generated matrix is symmetric, with
 *             eigenvalues specified by D, COND, MODE, and DMAX; they
 *             may be positive, negative, or zero.
 *             they will not be negative.
 *           Not modified.
 *
-*  D      - REAL array, dimension ( MIN( M , N ) )
+*  D        (input/output) REAL array, dimension ( MIN( M , N ) )
 *           This array is used to specify the singular values or
 *           eigenvalues of A (see SYM, above.)  If MODE=0, then D is
 *           assumed to contain the singular/eigenvalues, otherwise
 *           and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the singular/eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              sign (i.e., +1 or -1.)
 *           Not modified.
 *
-*  COND   - REAL
+*  COND     (input) REAL
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - REAL
+*  DMAX     (input) REAL
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or
 *           (or zero), D will be scaled by a negative number (or zero).
 *           Not modified.
 *
-*  RANK   - INTEGER
+*  RANK     (input) INTEGER
 *           The rank of matrix to be generated for modes 1,2,3 only.
 *           D( RANK+1:N ) = 0.
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL being at least M-1 means that the matrix
 *           is symmetric.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU being at least N-1 means that the matrix
 *           is symmetric.
 *           Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           This specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric)
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - REAL array, dimension ( LDA, N )
+*  A        (input/output) REAL array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.  A is first generated
 *           in full (unpacked) form, and then packed, if so specified
 *           by PACK.  Thus, the first M elements of the first N
 *           matrix are set to zero.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  If PACK='N', 'U', 'L', 'C', or 'R', then
 *           LDA must be at least M.  If PACK='B' or 'Q', then LDA must
 *           array: MIN( KU, N-1) + MIN( KL, M-1) + 1.
 *           Not modified.
 *
-*  WORK   - REAL array, dimension ( 3*MAX( N , M ) )
+*  WORK     (workspace) REAL array, dimension ( 3*MAX( N , M ) )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index ace37e0..df7cf9e 100644 (file)
@@ -1,4 +1,4 @@
-      SUBROUTINE ZLAHILB(N, NRHS, A, LDA, X, LDX, B, LDB, WORK,
+      SUBROUTINE ZLAHILB( N, NRHS, A, LDA, X, LDX, B, LDB, WORK,
      $     INFO, PATH)
 !
 !  -- LAPACK auxiliary test routine (version 3.0) --
@@ -48,7 +48,7 @@
 !  N       (input) INTEGER
 !          The dimension of the matrix A.
 !
-!  NRHS    (input) NRHS
+!  NRHS    (input) INTEGER
 !          The requested number of right-hand sides.
 !
 !  A       (output) COMPLEX array, dimension (LDA, N)
index e58d808..56ceca4 100644 (file)
@@ -26,7 +26,7 @@
 *  Arguments
 *  =========
 *
-*  SIDE   - CHARACTER*1
+*  SIDE     (input) CHARACTER*1
 *           SIDE specifies whether A is multiplied on the left or right
 *           by U.
 *       SIDE = 'L'   Multiply A on the left (premultiply) by U
@@ -35,7 +35,7 @@
 *       SIDE = 'T'   Multiply A on the left by U and the right by U'
 *           Not modified.
 *
-*  INIT   - CHARACTER*1
+*  INIT     (input) CHARACTER*1
 *           INIT specifies whether or not A should be initialized to
 *           the identity matrix.
 *              INIT = 'I'   Initialize A to (a section of) the
 *           columns will be orthogonal, the remaining columns being
 *           zero.
 *           For matrices where M > N, just use the previous
-*           explaination, interchanging 'L' and 'R' and "rows" and
+*           explanation, interchanging 'L' and 'R' and "rows" and
 *           "columns".
 *
 *           Not modified.
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of A. Not modified.
 *
-*  A      - COMPLEX*16 array, dimension ( LDA, N )
+*  A        COMPLEX*16 array, dimension ( LDA, N )
 *           Input and output array. Overwritten by U A ( if SIDE = 'L' )
 *           or by A U ( if SIDE = 'R' )
 *           or by U A U* ( if SIDE = 'C')
 *           or by U A U' ( if SIDE = 'T') on exit.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           Leading dimension of A. Must be at least MAX ( 1, M ).
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. The array elements should be between 0 and 4095;
 *           if not they will be reduced mod 4096.  Also, ISEED(4) must
 *           sequence.
 *           Modified.
 *
-*  X      - COMPLEX*16 array, dimension ( 3*MAX( M, N ) )
+*  X       (workspace) COMPLEX*16 array, dimension ( 3*MAX( M, N ) )
 *           Workspace. Of length:
 *               2*M + N if SIDE = 'L',
 *               2*N + M if SIDE = 'R',
 *               3*N     if SIDE = 'C' or 'T'.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO    (output) INTEGER
 *           An error flag.  It is set to:
 *            0  if no error.
 *            1  if ZLARND returned a bad random number (installation
index 0991e17..153ed0f 100644 (file)
@@ -24,7 +24,7 @@
 *  Arguments
 *  =========
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry describes how D is to be computed:
 *           MODE = 0 means do not change D.
 *           MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
 *              1 to 1/COND, if negative, from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  IRSIGN - INTEGER
+*  IRSIGN   (input) INTEGER
 *           On entry, if MODE neither -6, 0 nor 6, determines sign of
 *           entries of D
 *           0 => leave entries of D unchanged
 *           1 => multiply each entry of D by random complex number
 *                uniformly distributed with absolute value 1
 *
-*  IDIST  - CHARACTER*1
+*  IDIST    (input) CHARACTER*1
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => real and imaginary parts each UNIFORM( 0, 1 )
@@ -62,7 +62,7 @@
 *           4 => complex number uniform in DISK( 0, 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. The random number generator uses a
 *           linear congruential sequence limited to small
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  D      - COMPLEX*16 array, dimension ( MIN( M , N ) )
+*  D        (input/output) COMPLEX*16 array, dimension ( MIN( M , N ) )
 *           Array to be computed according to MODE, COND and IRSIGN.
 *           May be changed on exit if MODE is nonzero.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of entries of D. Not modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *            0  => normal termination
 *           -1  => if MODE not in range -6 to 6
 *           -2  => if MODE neither -6, 0 nor 6, and
index da10ed9..a1db344 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of matrix. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of matrix. Not modified.
 *
-*  I      - INTEGER
+*  I        (input) INTEGER
 *           Row of entry to be returned. Not modified.
 *
-*  J      - INTEGER
+*  J        (input) INTEGER
 *           Column of entry to be returned. Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           Lower bandwidth. Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           Upper bandwidth. Not modified.
 *
-*  IDIST  - INTEGER
+*  IDIST    (input) INTEGER
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => real and imaginary parts each UNIFORM( 0, 1 )
 *           4 => complex number uniform in DISK( 0 , 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER            array of dimension ( 4 )
+*  ISEED    (input/output) INTEGER array of dimension ( 4 )
 *           Seed for random number generator.
 *           Changed on exit.
 *
-*  D      - COMPLEX*16            array of dimension ( MIN( I , J ) )
+*  D        (input) COMPLEX*16 array of dimension ( MIN( I , J ) )
 *           Diagonal entries of matrix. Not modified.
 *
-*  IGRADE - INTEGER
+*  IGRADE   (input) INTEGER
 *           Specifies grading of matrix as follows:
 *           0  => no grading
 *           1  => matrix premultiplied by diag( DL )
 *                         postmultiplied by diag( DL )
 *           Not modified.
 *
-*  DL     - COMPLEX*16            array ( I or J, as appropriate )
+*  DL       (input) COMPLEX*16 array ( I or J, as appropriate )
 *           Left scale factors for grading matrix.  Not modified.
 *
-*  DR     - COMPLEX*16            array ( I or J, as appropriate )
+*  DR       (input) COMPLEX*16 array ( I or J, as appropriate )
 *           Right scale factors for grading matrix.  Not modified.
 *
-*  IPVTNG - INTEGER
+*  IPVTNG   (input) INTEGER
 *           On entry specifies pivoting permutations as follows:
 *           0 => none.
 *           1 => row pivoting.
 *           3 => full pivoting, i.e., on both sides.
 *           Not modified.
 *
-*  IWORK  - INTEGER            array ( I or J, as appropriate )
+*  IWORK    (workspace) INTEGER array ( I or J, as appropriate )
 *           This array specifies the permutation used. The
 *           row (or column) in position K was originally in
 *           position IWORK( K ).
 *           This differs from IWORK for ZLATM3. Not modified.
 *
-*  SPARSE - DOUBLE PRECISION               between 0. and 1.
+*  SPARSE   (input) DOUBLE PRECISION between 0. and 1.
 *           On entry specifies the sparsity of the matrix
 *           if sparse matix is to be generated.
 *           SPARSE should lie between 0 and 1.
index 2e81cf7..5c220b8 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of matrix. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of matrix. Not modified.
 *
-*  I      - INTEGER
+*  I        (input) INTEGER
 *           Row of unpivoted entry to be returned. Not modified.
 *
-*  J      - INTEGER
+*  J        (input) INTEGER
 *           Column of unpivoted entry to be returned. Not modified.
 *
-*  ISUB   - INTEGER
+*  ISUB     (input/output) INTEGER
 *           Row of pivoted entry to be returned. Changed on exit.
 *
-*  JSUB   - INTEGER
+*  JSUB     (input/output) INTEGER
 *           Column of pivoted entry to be returned. Changed on exit.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           Lower bandwidth. Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           Upper bandwidth. Not modified.
 *
-*  IDIST  - INTEGER
+*  IDIST    (input) INTEGER
 *           On entry, IDIST specifies the type of distribution to be
 *           used to generate a random matrix .
 *           1 => real and imaginary parts each UNIFORM( 0, 1 )
 *           4 => complex number uniform in DISK( 0 , 1 )
 *           Not modified.
 *
-*  ISEED  - INTEGER            array of dimension ( 4 )
+*  ISEED    (input/output) INTEGER array of dimension ( 4 )
 *           Seed for random number generator.
 *           Changed on exit.
 *
-*  D      - COMPLEX*16            array of dimension ( MIN( I , J ) )
+*  D        (input) COMPLEX*16 array of dimension ( MIN( I , J ) )
 *           Diagonal entries of matrix. Not modified.
 *
-*  IGRADE - INTEGER
+*  IGRADE   (input) INTEGER
 *           Specifies grading of matrix as follows:
 *           0  => no grading
 *           1  => matrix premultiplied by diag( DL )
 *                         postmultiplied by diag( DL )
 *           Not modified.
 *
-*  DL     - COMPLEX*16            array ( I or J, as appropriate )
+*  DL       (input) COMPLEX*16 array ( I or J, as appropriate )
 *           Left scale factors for grading matrix.  Not modified.
 *
-*  DR     - COMPLEX*16            array ( I or J, as appropriate )
+*  DR       (input) COMPLEX*16 array ( I or J, as appropriate )
 *           Right scale factors for grading matrix.  Not modified.
 *
-*  IPVTNG - INTEGER
+*  IPVTNG   (input) INTEGER
 *           On entry specifies pivoting permutations as follows:
 *           0 => none.
 *           1 => row pivoting.
 *           3 => full pivoting, i.e., on both sides.
 *           Not modified.
 *
-*  IWORK  - INTEGER            array ( I or J, as appropriate )
+*  IWORK    (input) INTEGER array ( I or J, as appropriate )
 *           This array specifies the permutation used. The
 *           row (or column) originally in position K is in
 *           position IWORK( K ) after pivoting.
 *           This differs from IWORK for ZLATM2. Not modified.
 *
-*  SPARSE - DOUBLE PRECISION               between 0. and 1.
+*  SPARSE   (input) DOUBLE PRECISION between 0. and 1.
 *           On entry specifies the sparsity of the matrix
 *           if sparse matix is to be generated.
 *           SPARSE should lie between 0 and 1.
index 18a17df..30da313 100644 (file)
@@ -1,5 +1,7 @@
-      SUBROUTINE ZLATME( N, DIST, ISEED, D, MODE, COND, DMAX, EI, RSIGN,
-     $                   UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, A,
+      SUBROUTINE ZLATME( N, DIST, ISEED, D, MODE, COND, DMAX, EI, 
+     $  RSIGN, 
+     $                   UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, 
+     $  A, 
      $                   LDA, WORK, INFO )
 *
 *  -- LAPACK test routine (version 3.1) --
 *  Arguments
 *  =========
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns (or rows) of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values, and on the
 *           upper triangle (see UPPER).
@@ -64,7 +66,7 @@
 *           'D' => uniform on the complex disc |z| < 1.
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  D      - COMPLEX*16 array, dimension ( N )
+*  D        (input/output) COMPLEX*16 array, dimension ( N )
 *           This array is used to specify the eigenvalues of A.  If
 *           MODE=0, then D is assumed to contain the eigenvalues
 *           otherwise they will be computed according to MODE, COND,
 *           DMAX, and RSIGN and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              ranging from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - COMPLEX*16
+*  DMAX     (input) COMPLEX*16
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))).  Note that DMAX need not be
 *           equal to DMAX.
 *           Not modified.
 *
-*  EI     - CHARACTER*1 (ignored)
+*  EI       (input) CHARACTER*1 array, dimension ( N )
+*           (ignored)
 *           Not modified.
 *
-*  RSIGN  - CHARACTER*1
+*  RSIGN    (input) CHARACTER*1
 *           If MODE is not 0, 6, or -6, and RSIGN='T', then the
 *           elements of D, as computed according to MODE and COND, will
 *           be multiplied by a random complex number from the unit
 *           only have the values 'T' or 'F'.
 *           Not modified.
 *
-*  UPPER  - CHARACTER*1
+*  UPPER    (input) CHARACTER*1
 *           If UPPER='T', then the elements of A above the diagonal
 *           will be set to random numbers out of DIST.  If UPPER='F',
 *           they will not.  UPPER may only have the values 'T' or 'F'.
 *           Not modified.
 *
-*  SIM    - CHARACTER*1
+*  SIM      (input) CHARACTER*1
 *           If SIM='T', then A will be operated on by a "similarity
 *           transform", i.e., multiplied on the left by a matrix X and
 *           on the right by X inverse.  X = U S V, where U and V are
 *           SIM='F', then A will not be transformed.
 *           Not modified.
 *
-*  DS     - DOUBLE PRECISION array, dimension ( N )
+*  DS       (input/output) DOUBLE PRECISION array, dimension ( N )
 *           This array is used to specify the singular values of X,
 *           in the same way that D specifies the eigenvalues of A.
 *           If MODE=0, the DS contains the singular values, which
 *           may not be zero.
 *           Modified if MODE is nonzero.
 *
-*  MODES  - INTEGER
-*  CONDS  - DOUBLE PRECISION
+*  MODES    (input) INTEGER
+*
+*  CONDS    (input) DOUBLE PRECISION
 *           Similar to MODE and COND, but for specifying the diagonal
 *           of S.  MODES=-6 and +6 are not allowed (since they would
 *           result in randomly ill-conditioned eigenvalues.)
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix.  KL=1
 *           specifies upper Hessenberg form.  If KL is at least N-1,
 *           then A will have full lower bandwidth.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix.  KU=1
 *           specifies lower Hessenberg form.  If KU is at least N-1,
 *           then A will have full upper bandwidth; if KU and KL
 *           KU and KL may be less than N-1.
 *           Not modified.
 *
-*  ANORM  - DOUBLE PRECISION
+*  ANORM    (input) DOUBLE PRECISION
 *           If ANORM is not negative, then A will be scaled by a non-
 *           negative real number to make the maximum-element-norm of A
 *           to be ANORM.
 *           Not modified.
 *
-*  A      - COMPLEX*16 array, dimension ( LDA, N )
+*  A        (output) COMPLEX*16 array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  LDA must be at least M.
 *           Not modified.
 *
-*  WORK   - COMPLEX*16 array, dimension ( 3*N )
+*  WORK     (workspace) COMPLEX*16 array, dimension ( 3*N )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index 5e4e608..b416a7a 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           Number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           Number of columns of A. Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate a random matrix .
 *           'U' => real and imaginary parts are independent
@@ -98,7 +98,7 @@
 *           'D' => uniform on interior of unit disk ( 'D' for disk )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension (4)
+*  ISEED    (input/output) INTEGER array, dimension (4)
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='S', generated matrix is symmetric.
 *           If SYM='H', generated matrix is Hermitian.
 *           If SYM='N', generated matrix is nonsymmetric.
 *           Not modified.
 *
-*  D      - COMPLEX*16 array, dimension (min(M,N))
+*  D        (input/output) COMPLEX*16 array, dimension (min(M,N))
 *           On entry this array specifies the diagonal entries
 *           of the diagonal of A.  D may either be specified
 *           on entry, or set according to MODE and COND as described
 *           below. If the matrix is Hermitian, the real part of D
 *           will be taken. May be changed on exit if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry describes how D is to be used:
 *           MODE = 0 means use D as input
 *           MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
 *              1 to 1/COND, if negative, from 1/COND to 1,
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - COMPLEX*16
+*  DMAX     (input) COMPLEX*16
 *           If MODE neither -6, 0 nor 6, the diagonal is scaled by
 *           DMAX / max(abs(D(i))), so that maximum absolute entry
 *           of diagonal is abs(DMAX). If DMAX is complex (or zero),
 *           diagonal will be scaled by a complex number (or zero).
 *
-*  RSIGN  - CHARACTER*1
+*  RSIGN    (input) CHARACTER*1
 *           If MODE neither -6, 0 nor 6, specifies sign of diagonal
 *           as follows:
 *           'T' => diagonal entries are multiplied by a random complex
 *           'F' => diagonal unchanged
 *           Not modified.
 *
-*  GRADE  - CHARACTER*1
+*  GRADE    (input) CHARACTER*1
 *           Specifies grading of matrix as follows:
 *           'N'  => no grading
 *           'L'  => matrix premultiplied by diag( DL )
 *                   Note: if GRADE='S', then M must equal N.
 *           Not modified.
 *
-*  DL     - COMPLEX*16 array, dimension (M)
+*  DL       (input/output) COMPLEX*16 array, dimension (M)
 *           If MODEL=0, then on entry this array specifies the diagonal
 *           entries of a diagonal matrix used as described under GRADE
 *           above. If MODEL is not zero, then DL will be set according
 *           If GRADE='E', then DL cannot have zero entries.
 *           Not referenced if GRADE = 'N' or 'R'. Changed on exit.
 *
-*  MODEL  - INTEGER
+*  MODEL    (input) INTEGER
 *           This specifies how the diagonal array DL is to be computed,
 *           just as MODE specifies how D is to be computed.
 *           Not modified.
 *
-*  CONDL  - DOUBLE PRECISION
+*  CONDL    (input) DOUBLE PRECISION
 *           When MODEL is not zero, this specifies the condition number
 *           of the computed DL.  Not modified.
 *
-*  DR     - COMPLEX*16 array, dimension (N)
+*  DR       (input/output) COMPLEX*16 array, dimension (N)
 *           If MODER=0, then on entry this array specifies the diagonal
 *           entries of a diagonal matrix used as described under GRADE
 *           above. If MODER is not zero, then DR will be set according
 *           Not referenced if GRADE = 'N', 'L', 'H' or 'S'.
 *           Changed on exit.
 *
-*  MODER  - INTEGER
+*  MODER    (input) INTEGER
 *           This specifies how the diagonal array DR is to be computed,
 *           just as MODE specifies how D is to be computed.
 *           Not modified.
 *
-*  CONDR  - DOUBLE PRECISION
+*  CONDR    (input) DOUBLE PRECISION
 *           When MODER is not zero, this specifies the condition number
 *           of the computed DR.  Not modified.
 *
-*  PIVTNG - CHARACTER*1
+*  PIVTNG   (input) CHARACTER*1
 *           On entry specifies pivoting permutations as follows:
 *           'N' or ' ' => none.
 *           'L' => left or row pivoting (matrix must be nonsymmetric).
 *           contain the same data. This consistency cannot be
 *           maintained with less than full bandwidth.
 *
-*  IPIVOT - INTEGER array, dimension (N or M)
+*  IPIVOT   (input) INTEGER array, dimension (N or M)
 *           This array specifies the permutation used.  After the
 *           basic matrix is generated, the rows, columns, or both
 *           are permuted.   If, say, row pivoting is selected, ZLATMR
 *           result in a pivot vector identical to IPIVOT.
 *           Not referenced if PIVTNG = 'N'. Not modified.
 *
-*  SPARSE - DOUBLE PRECISION
+*  SPARSE   (input) DOUBLE PRECISION
 *           On entry specifies the sparsity of the matrix if a sparse
 *           matrix is to be generated. SPARSE should lie between
 *           0 and 1. To generate a sparse matrix, for each matrix entry
 *           entries will be set to zero.
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           On entry specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL at least M-1 implies the matrix is not
 *           banded. Must equal KU if matrix is symmetric or Hermitian.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           On entry specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU at least N-1 implies the matrix is not
 *           banded. Must equal KL if matrix is symmetric or Hermitian.
 *           Not modified.
 *
-*  ANORM  - DOUBLE PRECISION
+*  ANORM    (input) DOUBLE PRECISION
 *           On entry specifies maximum entry of output matrix
 *           (output matrix will by multiplied by a constant so that
 *           its largest absolute entry equal ANORM)
 *           if ANORM is nonnegative. If ANORM is negative no scaling
 *           is done. Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           On entry specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - COMPLEX*16 array, dimension (LDA,N)
+*  A        (input/output) COMPLEX*16 array, dimension (LDA,N)
 *           On exit A is the desired test matrix. Only those
 *           entries of A which are significant on output
 *           will be referenced (even if A is in packed or band
 *           storage format). The 'unoccupied corners' of A in
 *           band format will be zeroed out.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           on entry LDA specifies the first dimension of A as
 *           declared in the calling program.
 *           If PACK='N', 'U' or 'L', LDA must be at least max ( 1, M ).
 *           KUU = MIN ( KU, N-1 ) and KLL = MIN ( KL, N-1 )
 *           Not modified.
 *
-*  IWORK  - INTEGER array, dimension (N or M)
+*  IWORK    (workspace) INTEGER array, dimension (N or M)
 *           Workspace. Not referenced if PIVTNG = 'N'. Changed on exit.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error parameter on exit:
 *             0 => normal return
 *            -1 => M negative or unequal to N and SYM='S' or 'H'
index 7ab7046..72bff19 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           The number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns of A. N must equal M if the matrix
 *           is symmetric or hermitian (i.e., if SYM is not 'N')
 *           Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values.
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -93,7 +93,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='H', the generated matrix is hermitian, with
 *             eigenvalues specified by D, COND, MODE, and DMAX; they
 *             may be positive, negative, or zero.
 *             DMAX; they will not be negative.
 *           Not modified.
 *
-*  D      - DOUBLE PRECISION array, dimension ( MIN( M, N ) )
+*  D        (input/output) DOUBLE PRECISION array, dimension ( MIN( M, N ) )
 *           This array is used to specify the singular values or
 *           eigenvalues of A (see SYM, above.)  If MODE=0, then D is
 *           assumed to contain the singular/eigenvalues, otherwise
 *           and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the singular/eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              sign (i.e., +1 or -1.)
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - DOUBLE PRECISION
+*  DMAX     (input) DOUBLE PRECISION
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or
 *           (or zero), D will be scaled by a negative number (or zero).
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL being at least M-1 means that the matrix
 *           is symmetric or hermitian.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU being at least N-1 means that the matrix
 *           is symmetric or hermitian.
 *           Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           This specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - COMPLEX*16 array, dimension ( LDA, N )
+*  A        (input/output) COMPLEX*16 array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.  A is first generated
 *           in full (unpacked) form, and then packed, if so specified
 *           by PACK.  Thus, the first M elements of the first N
 *           matrix are set to zero.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  If PACK='N', 'U', 'L', 'C', or 'R', then
 *           LDA must be at least M.  If PACK='B' or 'Q', then LDA must
 *           array: MIN( KU, N-1) + MIN( KL, M-1) + 1.
 *           Not modified.
 *
-*  WORK   - COMPLEX*16 array, dimension ( 3*MAX( N, M ) )
+*  WORK     (workspace) COMPLEX*16 array, dimension ( 3*MAX( N, M ) )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return
index 69d6228..b584030 100644 (file)
 *  Arguments
 *  =========
 *
-*  M      - INTEGER
+*  M        (input) INTEGER
 *           The number of rows of A. Not modified.
 *
-*  N      - INTEGER
+*  N        (input) INTEGER
 *           The number of columns of A. N must equal M if the matrix
 *           is symmetric or hermitian (i.e., if SYM is not 'N')
 *           Not modified.
 *
-*  DIST   - CHARACTER*1
+*  DIST     (input) CHARACTER*1
 *           On entry, DIST specifies the type of distribution to be used
 *           to generate the random eigen-/singular values.
 *           'U' => UNIFORM( 0, 1 )  ( 'U' for uniform )
@@ -93,7 +93,7 @@
 *           'N' => NORMAL( 0, 1 )   ( 'N' for normal )
 *           Not modified.
 *
-*  ISEED  - INTEGER array, dimension ( 4 )
+*  ISEED    (input/output) INTEGER array, dimension ( 4 )
 *           On entry ISEED specifies the seed of the random number
 *           generator. They should lie between 0 and 4095 inclusive,
 *           and ISEED(4) should be odd. The random number generator
 *           to continue the same random number sequence.
 *           Changed on exit.
 *
-*  SYM    - CHARACTER*1
+*  SYM      (input) CHARACTER*1
 *           If SYM='H', the generated matrix is hermitian, with
 *             eigenvalues specified by D, COND, MODE, and DMAX; they
 *             may be positive, negative, or zero.
 *             DMAX; they will not be negative.
 *           Not modified.
 *
-*  D      - DOUBLE PRECISION array, dimension ( MIN( M, N ) )
+*  D        (input/output) DOUBLE PRECISION array, dimension ( MIN( M, N ) )
 *           This array is used to specify the singular values or
 *           eigenvalues of A (see SYM, above.)  If MODE=0, then D is
 *           assumed to contain the singular/eigenvalues, otherwise
 *           and placed in D.
 *           Modified if MODE is nonzero.
 *
-*  MODE   - INTEGER
+*  MODE     (input) INTEGER
 *           On entry this describes how the singular/eigenvalues are to
 *           be specified:
 *           MODE = 0 means use D as input
 *              sign (i.e., +1 or -1.)
 *           Not modified.
 *
-*  COND   - DOUBLE PRECISION
+*  COND     (input) DOUBLE PRECISION
 *           On entry, this is used as described under MODE above.
 *           If used, it must be >= 1. Not modified.
 *
-*  DMAX   - DOUBLE PRECISION
+*  DMAX     (input) DOUBLE PRECISION
 *           If MODE is neither -6, 0 nor 6, the contents of D, as
 *           computed according to MODE and COND, will be scaled by
 *           DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or
 *           (or zero), D will be scaled by a negative number (or zero).
 *           Not modified.
 *
-*  RANK   - INTEGER
+*  RANK     (input) INTEGER
 *           The rank of matrix to be generated for modes 1,2,3 only.
 *           D( RANK+1:N ) = 0.
 *           Not modified.
 *
-*  KL     - INTEGER
+*  KL       (input) INTEGER
 *           This specifies the lower bandwidth of the  matrix. For
 *           example, KL=0 implies upper triangular, KL=1 implies upper
 *           Hessenberg, and KL being at least M-1 means that the matrix
 *           is symmetric or hermitian.
 *           Not modified.
 *
-*  KU     - INTEGER
+*  KU       (input) INTEGER
 *           This specifies the upper bandwidth of the  matrix. For
 *           example, KU=0 implies lower triangular, KU=1 implies lower
 *           Hessenberg, and KU being at least N-1 means that the matrix
 *           is symmetric or hermitian.
 *           Not modified.
 *
-*  PACK   - CHARACTER*1
+*  PACK     (input) CHARACTER*1
 *           This specifies packing of matrix as follows:
 *           'N' => no packing
 *           'U' => zero out all subdiagonal entries (if symmetric
 *           they will generate mathematically equivalent matrices.
 *           Not modified.
 *
-*  A      - COMPLEX*16 array, dimension ( LDA, N )
+*  A        (input/output) COMPLEX*16 array, dimension ( LDA, N )
 *           On exit A is the desired test matrix.  A is first generated
 *           in full (unpacked) form, and then packed, if so specified
 *           by PACK.  Thus, the first M elements of the first N
 *           matrix are set to zero.
 *           Modified.
 *
-*  LDA    - INTEGER
+*  LDA      (input) INTEGER
 *           LDA specifies the first dimension of A as declared in the
 *           calling program.  If PACK='N', 'U', 'L', 'C', or 'R', then
 *           LDA must be at least M.  If PACK='B' or 'Q', then LDA must
 *           array: MIN( KU, N-1) + MIN( KL, M-1) + 1.
 *           Not modified.
 *
-*  WORK   - COMPLEX*16 array, dimension ( 3*MAX( N, M ) )
+*  WORK     (workspace) COMPLEX*16 array, dimension ( 3*MAX( N, M ) )
 *           Workspace.
 *           Modified.
 *
-*  INFO   - INTEGER
+*  INFO     (output) INTEGER
 *           Error code.  On exit, INFO will be set to one of the
 *           following values:
 *             0 => normal return