Lots of trailing whitespaces in the files of Syd. Cleaning this. No big deal.
[platform/upstream/lapack.git] / SRC / dlasdt.f
1 *> \brief \b DLASDT 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 DLASDT + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlasdt.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlasdt.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasdt.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE DLASDT( 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 *> DLASDT 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 *> \date September 2012
96 *
97 *> \ingroup OTHERauxiliary
98 *
99 *> \par Contributors:
100 *  ==================
101 *>
102 *>     Ming Gu and Huan Ren, Computer Science Division, University of
103 *>     California at Berkeley, USA
104 *>
105 *  =====================================================================
106       SUBROUTINE DLASDT( N, LVL, ND, INODE, NDIML, NDIMR, MSUB )
107 *
108 *  -- LAPACK auxiliary routine (version 3.4.2) --
109 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
110 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
111 *     September 2012
112 *
113 *     .. Scalar Arguments ..
114       INTEGER            LVL, MSUB, N, ND
115 *     ..
116 *     .. Array Arguments ..
117       INTEGER            INODE( * ), NDIML( * ), NDIMR( * )
118 *     ..
119 *
120 *  =====================================================================
121 *
122 *     .. Parameters ..
123       DOUBLE PRECISION   TWO
124       PARAMETER          ( TWO = 2.0D+0 )
125 *     ..
126 *     .. Local Scalars ..
127       INTEGER            I, IL, IR, LLST, MAXN, NCRNT, NLVL
128       DOUBLE PRECISION   TEMP
129 *     ..
130 *     .. Intrinsic Functions ..
131       INTRINSIC          DBLE, INT, LOG, MAX
132 *     ..
133 *     .. Executable Statements ..
134 *
135 *     Find the number of levels on the tree.
136 *
137       MAXN = MAX( 1, N )
138       TEMP = LOG( DBLE( MAXN ) / DBLE( MSUB+1 ) ) / LOG( TWO )
139       LVL = INT( TEMP ) + 1
140 *
141       I = N / 2
142       INODE( 1 ) = I + 1
143       NDIML( 1 ) = I
144       NDIMR( 1 ) = N - I - 1
145       IL = 0
146       IR = 1
147       LLST = 1
148       DO 20 NLVL = 1, LVL - 1
149 *
150 *        Constructing the tree at (NLVL+1)-st level. The number of
151 *        nodes created on this level is LLST * 2.
152 *
153          DO 10 I = 0, LLST - 1
154             IL = IL + 2
155             IR = IR + 2
156             NCRNT = LLST + I
157             NDIML( IL ) = NDIML( NCRNT ) / 2
158             NDIMR( IL ) = NDIML( NCRNT ) - NDIML( IL ) - 1
159             INODE( IL ) = INODE( NCRNT ) - NDIMR( IL ) - 1
160             NDIML( IR ) = NDIMR( NCRNT ) / 2
161             NDIMR( IR ) = NDIMR( NCRNT ) - NDIML( IR ) - 1
162             INODE( IR ) = INODE( NCRNT ) + NDIML( IR ) + 1
163    10    CONTINUE
164          LLST = LLST*2
165    20 CONTINUE
166       ND = LLST*2 - 1
167 *
168       RETURN
169 *
170 *     End of DLASDT
171 *
172       END