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