LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
slasdt.f
Go to the documentation of this file.
1*> \brief \b SLASDT creates a tree of subproblems for bidiagonal divide and conquer. Used by sbdsdc.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download SLASDT + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slasdt.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slasdt.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slasdt.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE SLASDT( N, LVL, ND, INODE, NDIML, NDIMR, MSUB )
22*
23* .. Scalar Arguments ..
24* INTEGER LVL, MSUB, N, ND
25* ..
26* .. Array Arguments ..
27* INTEGER INODE( * ), NDIML( * ), NDIMR( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> SLASDT creates a tree of subproblems for bidiagonal divide and
37*> conquer.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] N
44*> \verbatim
45*> N is INTEGER
46*> On entry, the number of diagonal elements of the
47*> bidiagonal matrix.
48*> \endverbatim
49*>
50*> \param[out] LVL
51*> \verbatim
52*> LVL is INTEGER
53*> On exit, the number of levels on the computation tree.
54*> \endverbatim
55*>
56*> \param[out] ND
57*> \verbatim
58*> ND is INTEGER
59*> On exit, the number of nodes on the tree.
60*> \endverbatim
61*>
62*> \param[out] INODE
63*> \verbatim
64*> INODE is INTEGER array, dimension ( N )
65*> On exit, centers of subproblems.
66*> \endverbatim
67*>
68*> \param[out] NDIML
69*> \verbatim
70*> NDIML is INTEGER array, dimension ( N )
71*> On exit, row dimensions of left children.
72*> \endverbatim
73*>
74*> \param[out] NDIMR
75*> \verbatim
76*> NDIMR is INTEGER array, dimension ( N )
77*> On exit, row dimensions of right children.
78*> \endverbatim
79*>
80*> \param[in] MSUB
81*> \verbatim
82*> MSUB is INTEGER
83*> On entry, the maximum row dimension each subproblem at the
84*> bottom of the tree can be of.
85*> \endverbatim
86*
87* Authors:
88* ========
89*
90*> \author Univ. of Tennessee
91*> \author Univ. of California Berkeley
92*> \author Univ. of Colorado Denver
93*> \author NAG Ltd.
94*
95*> \ingroup lasdt
96*
97*> \par Contributors:
98* ==================
99*>
100*> Ming Gu and Huan Ren, Computer Science Division, University of
101*> California at Berkeley, USA
102*>
103* =====================================================================
104 SUBROUTINE slasdt( N, LVL, ND, INODE, NDIML, NDIMR, MSUB )
105*
106* -- LAPACK auxiliary routine --
107* -- LAPACK is a software package provided by Univ. of Tennessee, --
108* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
109*
110* .. Scalar Arguments ..
111 INTEGER LVL, MSUB, N, ND
112* ..
113* .. Array Arguments ..
114 INTEGER INODE( * ), NDIML( * ), NDIMR( * )
115* ..
116*
117* =====================================================================
118*
119* .. Parameters ..
120 REAL TWO
121 parameter( two = 2.0e+0 )
122* ..
123* .. Local Scalars ..
124 INTEGER I, IL, IR, LLST, MAXN, NCRNT, NLVL
125 REAL TEMP
126* ..
127* .. Intrinsic Functions ..
128 INTRINSIC int, log, max, real
129* ..
130* .. Executable Statements ..
131*
132* Find the number of levels on the tree.
133*
134 maxn = max( 1, n )
135 temp = log( real( maxn ) / real( msub+1 ) ) / log( two )
136 lvl = int( temp ) + 1
137*
138 i = n / 2
139 inode( 1 ) = i + 1
140 ndiml( 1 ) = i
141 ndimr( 1 ) = n - i - 1
142 il = 0
143 ir = 1
144 llst = 1
145 DO 20 nlvl = 1, lvl - 1
146*
147* Constructing the tree at (NLVL+1)-st level. The number of
148* nodes created on this level is LLST * 2.
149*
150 DO 10 i = 0, llst - 1
151 il = il + 2
152 ir = ir + 2
153 ncrnt = llst + i
154 ndiml( il ) = ndiml( ncrnt ) / 2
155 ndimr( il ) = ndiml( ncrnt ) - ndiml( il ) - 1
156 inode( il ) = inode( ncrnt ) - ndimr( il ) - 1
157 ndiml( ir ) = ndimr( ncrnt ) / 2
158 ndimr( ir ) = ndimr( ncrnt ) - ndiml( ir ) - 1
159 inode( ir ) = inode( ncrnt ) + ndiml( ir ) + 1
160 10 CONTINUE
161 llst = llst*2
162 20 CONTINUE
163 nd = llst*2 - 1
164*
165 RETURN
166*
167* End of SLASDT
168*
169 END
subroutine slasdt(n, lvl, nd, inode, ndiml, ndimr, msub)
SLASDT creates a tree of subproblems for bidiagonal divide and conquer. Used by sbdsdc.
Definition slasdt.f:105