134      SUBROUTINE slatm1( MODE, COND, IRSIGN, IDIST, ISEED, D, N,
 
  142      INTEGER            IDIST, INFO, IRSIGN, MODE, N
 
  154      parameter( one = 1.0e0 )
 
  156      parameter( half = 0.5e0 )
 
  170      INTRINSIC          abs, exp, log, real
 
  185      IF( mode.LT.-6 .OR. mode.GT.6 ) 
THEN 
  187      ELSE IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
 
  188     $         ( irsign.NE.0 .AND. irsign.NE.1 ) ) 
THEN 
  190      ELSE IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
 
  193      ELSE IF( ( mode.EQ.6 .OR. mode.EQ.-6 ) .AND.
 
  194     $         ( idist.LT.1 .OR. idist.GT.3 ) ) 
THEN 
  196      ELSE IF( n.LT.0 ) 
THEN 
  201         CALL xerbla( 
'SLATM1', -info )
 
  208         GO TO ( 10, 30, 50, 70, 90, 110 )abs( mode )
 
  233            alpha = cond**( -one / real( n-1 ) )
 
  235               d( i ) = alpha**( i-1 )
 
  246            alpha = ( one-temp ) / real( n-1 )
 
  248               d( i ) = real( n-i )*alpha + temp
 
  256         alpha = log( one / cond )
 
  258            d( i ) = exp( alpha*slaran( iseed ) )
 
  265         CALL slarnv( idist, iseed, n, d )
 
  272         IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
 
  275               temp = slaran( iseed )
 
 
subroutine slarnv(idist, iseed, n, x)
SLARNV returns a vector of random numbers from a uniform or normal distribution.
subroutine slatm1(mode, cond, irsign, idist, iseed, d, n, info)
SLATM1