~ubuntu-branches/ubuntu/hoary/scilab/hoary

« back to all changes in this revision

Viewing changes to routines/slicot/mb01sd.f

  • Committer: Bazaar Package Importer
  • Author(s): Torsten Werner
  • Date: 2005-01-09 22:58:21 UTC
  • mfrom: (1.1.1 upstream)
  • Revision ID: james.westby@ubuntu.com-20050109225821-473xr8vhgugxxx5j
Tags: 3.0-12
changed configure.in to build scilab's own malloc.o, closes: #255869

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
      SUBROUTINE MB01SD( JOBS, M, N, A, LDA, R, C )
 
2
C
 
3
C     RELEASE 3.0, WGS COPYRIGHT 1998.
 
4
C
 
5
C     PURPOSE
 
6
C
 
7
C     To scale a general M-by-N matrix A using the row and column
 
8
C     scaling factors in the vectors R and C.
 
9
C
 
10
C     ARGUMENTS
 
11
C
 
12
C     Mode Parameters
 
13
C
 
14
C     JOBS    CHARACTER*1
 
15
C             Specifies the scaling operation to be done, as follows:
 
16
C             = 'R':  row scaling, i.e., A will be premultiplied  
 
17
C                     by diag(R);
 
18
C             = 'C':  column scaling, i.e., A will be postmultiplied
 
19
C                     by diag(C);
 
20
C             = 'B':  both row and column scaling, i.e., A will be
 
21
C                     replaced by diag(R) * A * diag(C).
 
22
C
 
23
C     Input/Output Parameters
 
24
C
 
25
C     M       (input) INTEGER
 
26
C             The number of rows of the matrix A.  M >= 0.
 
27
C
 
28
C     N       (input) INTEGER
 
29
C             The number of columns of the matrix A.  N >= 0.
 
30
C
 
31
C     A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
 
32
C             On entry, the M-by-N matrix A. 
 
33
C             On exit, the scaled matrix.  See JOBS for the form of the
 
34
C             scaled matrix.
 
35
C
 
36
C     LDA     INTEGER
 
37
C             The leading dimension of the array A.  LDA >= max(1,M).
 
38
C
 
39
C     R       (input) DOUBLE PRECISION array, dimension (M)
 
40
C             The row scale factors for A. 
 
41
C             R is not referenced if JOBS = 'C'.
 
42
C
 
43
C     C       (input) DOUBLE PRECISION array, dimension (N)
 
44
C             The column scale factors for A.
 
45
C             C is not referenced if JOBS = 'R'.
 
46
C
 
47
C
 
48
C     CONTRIBUTOR
 
49
C
 
50
C     A. Varga, German Aerospace Center,
 
51
C     DLR Oberpfaffenhofen, April 1998.
 
52
C     Based on the RASP routine DMSCAL.
 
53
C
 
54
C    ******************************************************************
 
55
C
 
56
C     .. Scalar Arguments ..
 
57
      CHARACTER          JOBS
 
58
      INTEGER            LDA, M, N
 
59
C     .. Array Arguments ..
 
60
      DOUBLE PRECISION   A(LDA,*), C(*), R(*)
 
61
C     .. Local Scalars ..
 
62
      INTEGER            I, J
 
63
      DOUBLE PRECISION   CJ
 
64
C     .. External Functions ..
 
65
      LOGICAL            LSAME
 
66
      EXTERNAL           LSAME
 
67
C     .. Executable Statements ..
 
68
C
 
69
C     Quick return if possible.
 
70
C
 
71
      IF( M.EQ.0 .OR. N.EQ.0 )
 
72
     $   RETURN
 
73
C
 
74
      IF( LSAME( JOBS, 'C' ) ) THEN
 
75
C
 
76
C        Column scaling, no row scaling.
 
77
C
 
78
         DO 20 J = 1, N
 
79
            CJ = C(J)
 
80
            DO 10 I = 1, M
 
81
               A(I,J) = CJ*A(I,J)
 
82
   10       CONTINUE
 
83
   20    CONTINUE
 
84
      ELSE IF( LSAME( JOBS, 'R' ) ) THEN
 
85
C
 
86
C        Row scaling, no column scaling.
 
87
C
 
88
         DO 40 J = 1, N
 
89
            DO 30 I = 1, M
 
90
               A(I,J) = R(I)*A(I,J)
 
91
   30       CONTINUE
 
92
   40    CONTINUE
 
93
      ELSE IF( LSAME( JOBS, 'B' ) ) THEN
 
94
C
 
95
C        Row and column scaling.
 
96
C
 
97
         DO 60 J = 1, N
 
98
            CJ = C(J)
 
99
            DO 50 I = 1, M
 
100
               A(I,J) = CJ*R(I)*A(I,J)
 
101
   50       CONTINUE
 
102
   60    CONTINUE
 
103
      END IF
 
104
C
 
105
      RETURN
 
106
C *** Last line of MB01SD ***
 
107
      END