File: bdlaapp.f

package info (click to toggle)
scalapack 2.1.0-4
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 36,184 kB
  • sloc: fortran: 338,772; ansic: 75,298; makefile: 1,392; sh: 56
file content (167 lines) | stat: -rw-r--r-- 4,899 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
      SUBROUTINE BDLAAPP( ISIDE, M, N, NB, A, LDA, NITRAF, ITRAF,
     $                    DTRAF, WORK )
      IMPLICIT NONE
*
*     .. Scalar Arguments ..
      INTEGER            ISIDE, LDA, M, N, NB, NITRAF
*     ..
*     .. Array Arguments ..
      INTEGER            ITRAF( * )
      DOUBLE PRECISION   A( LDA, * ), DTRAF( * ), WORK( * )
*
*
*  Purpose
*  =======
*
*  BDLAAPP computes
*
*          B = Q**T * A       or       B = A * Q,
*
*  where A is an M-by-N matrix and Q is an orthogonal matrix represented
*  by the parameters in the arrays ITRAF and DTRAF as described in
*  BDTREXC.
*
*  This is an auxiliary routine called by BDTRSEN.
*
*  Arguments
*  =========
*
*  ISIDE   (input) INTEGER
*          Specifies whether Q multiplies A from the left or right as
*          follows:
*          = 0: compute B = Q**T * A;
*          = 1: compute B = A * Q.
*
*  M       (input) INTEGER
*          The number of rows of A.
*
*  N       (input) INTEGER
*          The number of columns of A.
*
*  NB      (input) INTEGER
*          If ISIDE = 0, the Q is applied block column-wise to the rows
*          of A and NB specifies the maximal width of the block columns.
*          If ISIDE = 1, this variable is not referenced.
*
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
*          On entry, the matrix A.
*          On exit, A is overwritten by B.
*
*  LDA     (input) INTEGER
*          The leading dimension of the array A. LDA >= max(1,N).
*
*  NITRAF  (input) INTEGER
*          Length of the array ITRAF. NITRAF >= 0.
*
*  ITRAF   (input) INTEGER array, length NITRAF
*          List of parameters for representing the transformation
*          matrix Q, see BDTREXC.
*
*  DTRAF   (output) DOUBLE PRECISION array, length k, where
*          List of parameters for representing the transformation
*          matrix Q, see BDTREXC.
*
*  WORK    (workspace) DOUBLE PRECISION array, dimension (N)
*
*  =====================================================================
*

*     .. Parameters ..
      DOUBLE PRECISION   ZERO, ONE
      PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
*     ..
*     .. Local Scalars ..
      INTEGER            I, IT, J, NNB, PD
      DOUBLE PRECISION   TAU
*     ..
*     .. External Subroutines ..
      EXTERNAL           DLARFX, DROT
*     .. Intrinsic Functions ..
      INTRINSIC          MIN
*     ..
*     .. Executable Statements ..
*
*     Quick return if possible.
*
      IF( M.LE.0 .OR. N.LE.0 )
     $   RETURN
*
      IF( ISIDE.EQ.0 ) THEN
*
*        Apply Q from left.
*
         DO 20 J = 1, N, NB
            PD = 1
            NNB = MIN( NB, N - J + 1 )
            DO 10 I = 1, NITRAF
               IT = ITRAF(I)
               IF( IT.LE.M ) THEN
*
*                 Apply Givens rotation.
*
                  CALL DROT( NNB, A(IT,J), LDA, A(IT+1,J), LDA,
     $                       DTRAF(PD), DTRAF(PD+1) )
                  PD = PD + 2
               ELSE IF( IT.LE.2*M ) THEN
*
*                 Apply Householder reflector of first kind.
*
                  TAU = DTRAF(PD)
                  DTRAF(PD) = ONE
                  CALL DLARFX( 'Left', 3, NNB, DTRAF(PD), TAU,
     $                         A(IT-M,J), LDA, WORK )
                  DTRAF(PD) = TAU
                  PD = PD + 3
               ELSE
*
*                 Apply Householder reflector of second kind.
*
                  TAU = DTRAF(PD+2)
                  DTRAF(PD+2) = ONE
                  CALL DLARFX( 'Left', 3, NNB, DTRAF(PD), TAU,
     $                         A(IT-2*M,J), LDA, WORK )
                  DTRAF(PD+2) = TAU
                  PD = PD + 3
               END IF
   10       CONTINUE
   20    CONTINUE
      ELSE
         PD = 1
         DO 30 I = 1, NITRAF
            IT = ITRAF(I)
            IF( IT.LE.N ) THEN
*
*              Apply Givens rotation.
*
               CALL DROT( M, A(1,IT), 1, A(1,IT+1), 1, DTRAF(PD),
     $                    DTRAF(PD+1) )
               PD = PD + 2
            ELSE IF( IT.LE.2*N ) THEN
*
*              Apply Householder reflector of first kind.
*
               TAU = DTRAF(PD)
               DTRAF(PD) = ONE
               CALL DLARFX( 'Right', M, 3, DTRAF(PD), TAU, A(1,IT-N),
     $                      LDA, WORK )
               DTRAF(PD) = TAU
               PD = PD + 3
            ELSE
*
*              Apply Householder reflector of second kind.
*
               TAU = DTRAF(PD+2)
               DTRAF(PD+2) = ONE
               CALL DLARFX( 'Right', M, 3, DTRAF(PD), TAU, A(1,IT-2*N),
     $                      LDA, WORK )
               DTRAF(PD+2) = TAU
               PD = PD + 3
            END IF
   30    CONTINUE
      END IF
*
      RETURN
*
*     End of BDLAAPP
*
      END