1 SUBROUTINE DLASDT( N, LVL, ND, INODE, NDIML, NDIMR, MSUB )
2 *
3 * -- LAPACK auxiliary routine (version 3.2.2) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * June 2010
7 *
8 * .. Scalar Arguments ..
9 INTEGER LVL, MSUB, N, ND
10 * ..
11 * .. Array Arguments ..
12 INTEGER INODE( * ), NDIML( * ), NDIMR( * )
13 * ..
14 *
15 * Purpose
16 * =======
17 *
18 * DLASDT creates a tree of subproblems for bidiagonal divide and
19 * conquer.
20 *
21 * Arguments
22 * =========
23 *
24 * N (input) INTEGER
25 * On entry, the number of diagonal elements of the
26 * bidiagonal matrix.
27 *
28 * LVL (output) INTEGER
29 * On exit, the number of levels on the computation tree.
30 *
31 * ND (output) INTEGER
32 * On exit, the number of nodes on the tree.
33 *
34 * INODE (output) INTEGER array, dimension ( N )
35 * On exit, centers of subproblems.
36 *
37 * NDIML (output) INTEGER array, dimension ( N )
38 * On exit, row dimensions of left children.
39 *
40 * NDIMR (output) INTEGER array, dimension ( N )
41 * On exit, row dimensions of right children.
42 *
43 * MSUB (input) INTEGER
44 * On entry, the maximum row dimension each subproblem at the
45 * bottom of the tree can be of.
46 *
47 * Further Details
48 * ===============
49 *
50 * Based on contributions by
51 * Ming Gu and Huan Ren, Computer Science Division, University of
52 * California at Berkeley, USA
53 *
54 * =====================================================================
55 *
56 * .. Parameters ..
57 DOUBLE PRECISION TWO
58 PARAMETER ( TWO = 2.0D+0 )
59 * ..
60 * .. Local Scalars ..
61 INTEGER I, IL, IR, LLST, MAXN, NCRNT, NLVL
62 DOUBLE PRECISION TEMP
63 * ..
64 * .. Intrinsic Functions ..
65 INTRINSIC DBLE, INT, LOG, MAX
66 * ..
67 * .. Executable Statements ..
68 *
69 * Find the number of levels on the tree.
70 *
71 MAXN = MAX( 1, N )
72 TEMP = LOG( DBLE( MAXN ) / DBLE( MSUB+1 ) ) / LOG( TWO )
73 LVL = INT( TEMP ) + 1
74 *
75 I = N / 2
76 INODE( 1 ) = I + 1
77 NDIML( 1 ) = I
78 NDIMR( 1 ) = N - I - 1
79 IL = 0
80 IR = 1
81 LLST = 1
82 DO 20 NLVL = 1, LVL - 1
83 *
84 * Constructing the tree at (NLVL+1)-st level. The number of
85 * nodes created on this level is LLST * 2.
86 *
87 DO 10 I = 0, LLST - 1
88 IL = IL + 2
89 IR = IR + 2
90 NCRNT = LLST + I
91 NDIML( IL ) = NDIML( NCRNT ) / 2
92 NDIMR( IL ) = NDIML( NCRNT ) - NDIML( IL ) - 1
93 INODE( IL ) = INODE( NCRNT ) - NDIMR( IL ) - 1
94 NDIML( IR ) = NDIMR( NCRNT ) / 2
95 NDIMR( IR ) = NDIMR( NCRNT ) - NDIML( IR ) - 1
96 INODE( IR ) = INODE( NCRNT ) + NDIML( IR ) + 1
97 10 CONTINUE
98 LLST = LLST*2
99 20 CONTINUE
100 ND = LLST*2 - 1
101 *
102 RETURN
103 *
104 * End of DLASDT
105 *
106 END
2 *
3 * -- LAPACK auxiliary routine (version 3.2.2) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * June 2010
7 *
8 * .. Scalar Arguments ..
9 INTEGER LVL, MSUB, N, ND
10 * ..
11 * .. Array Arguments ..
12 INTEGER INODE( * ), NDIML( * ), NDIMR( * )
13 * ..
14 *
15 * Purpose
16 * =======
17 *
18 * DLASDT creates a tree of subproblems for bidiagonal divide and
19 * conquer.
20 *
21 * Arguments
22 * =========
23 *
24 * N (input) INTEGER
25 * On entry, the number of diagonal elements of the
26 * bidiagonal matrix.
27 *
28 * LVL (output) INTEGER
29 * On exit, the number of levels on the computation tree.
30 *
31 * ND (output) INTEGER
32 * On exit, the number of nodes on the tree.
33 *
34 * INODE (output) INTEGER array, dimension ( N )
35 * On exit, centers of subproblems.
36 *
37 * NDIML (output) INTEGER array, dimension ( N )
38 * On exit, row dimensions of left children.
39 *
40 * NDIMR (output) INTEGER array, dimension ( N )
41 * On exit, row dimensions of right children.
42 *
43 * MSUB (input) INTEGER
44 * On entry, the maximum row dimension each subproblem at the
45 * bottom of the tree can be of.
46 *
47 * Further Details
48 * ===============
49 *
50 * Based on contributions by
51 * Ming Gu and Huan Ren, Computer Science Division, University of
52 * California at Berkeley, USA
53 *
54 * =====================================================================
55 *
56 * .. Parameters ..
57 DOUBLE PRECISION TWO
58 PARAMETER ( TWO = 2.0D+0 )
59 * ..
60 * .. Local Scalars ..
61 INTEGER I, IL, IR, LLST, MAXN, NCRNT, NLVL
62 DOUBLE PRECISION TEMP
63 * ..
64 * .. Intrinsic Functions ..
65 INTRINSIC DBLE, INT, LOG, MAX
66 * ..
67 * .. Executable Statements ..
68 *
69 * Find the number of levels on the tree.
70 *
71 MAXN = MAX( 1, N )
72 TEMP = LOG( DBLE( MAXN ) / DBLE( MSUB+1 ) ) / LOG( TWO )
73 LVL = INT( TEMP ) + 1
74 *
75 I = N / 2
76 INODE( 1 ) = I + 1
77 NDIML( 1 ) = I
78 NDIMR( 1 ) = N - I - 1
79 IL = 0
80 IR = 1
81 LLST = 1
82 DO 20 NLVL = 1, LVL - 1
83 *
84 * Constructing the tree at (NLVL+1)-st level. The number of
85 * nodes created on this level is LLST * 2.
86 *
87 DO 10 I = 0, LLST - 1
88 IL = IL + 2
89 IR = IR + 2
90 NCRNT = LLST + I
91 NDIML( IL ) = NDIML( NCRNT ) / 2
92 NDIMR( IL ) = NDIML( NCRNT ) - NDIML( IL ) - 1
93 INODE( IL ) = INODE( NCRNT ) - NDIMR( IL ) - 1
94 NDIML( IR ) = NDIMR( NCRNT ) / 2
95 NDIMR( IR ) = NDIMR( NCRNT ) - NDIML( IR ) - 1
96 INODE( IR ) = INODE( NCRNT ) + NDIML( IR ) + 1
97 10 CONTINUE
98 LLST = LLST*2
99 20 CONTINUE
100 ND = LLST*2 - 1
101 *
102 RETURN
103 *
104 * End of DLASDT
105 *
106 END