Statistiques
| Révision :

root / src / lapack / double / dlasdt.f @ 10

Historique | Voir | Annoter | Télécharger (2,88 ko)

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