Statistiques
| Révision :

root / src / lapack / double / dlamrg.f @ 2

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

1
      SUBROUTINE DLAMRG( N1, N2, A, DTRD1, DTRD2, INDEX )
2
*
3
*  -- LAPACK routine (version 3.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
*     November 2006
7
*
8
*     .. Scalar Arguments ..
9
      INTEGER            DTRD1, DTRD2, N1, N2
10
*     ..
11
*     .. Array Arguments ..
12
      INTEGER            INDEX( * )
13
      DOUBLE PRECISION   A( * )
14
*     ..
15
*
16
*  Purpose
17
*  =======
18
*
19
*  DLAMRG will create a permutation list which will merge the elements
20
*  of A (which is composed of two independently sorted sets) into a
21
*  single set which is sorted in ascending order.
22
*
23
*  Arguments
24
*  =========
25
*
26
*  N1     (input) INTEGER
27
*  N2     (input) INTEGER
28
*         These arguements contain the respective lengths of the two
29
*         sorted lists to be merged.
30
*
31
*  A      (input) DOUBLE PRECISION array, dimension (N1+N2)
32
*         The first N1 elements of A contain a list of numbers which
33
*         are sorted in either ascending or descending order.  Likewise
34
*         for the final N2 elements.
35
*
36
*  DTRD1  (input) INTEGER
37
*  DTRD2  (input) INTEGER
38
*         These are the strides to be taken through the array A.
39
*         Allowable strides are 1 and -1.  They indicate whether a
40
*         subset of A is sorted in ascending (DTRDx = 1) or descending
41
*         (DTRDx = -1) order.
42
*
43
*  INDEX  (output) INTEGER array, dimension (N1+N2)
44
*         On exit this array will contain a permutation such that
45
*         if B( I ) = A( INDEX( I ) ) for I=1,N1+N2, then B will be
46
*         sorted in ascending order.
47
*
48
*  =====================================================================
49
*
50
*     .. Local Scalars ..
51
      INTEGER            I, IND1, IND2, N1SV, N2SV
52
*     ..
53
*     .. Executable Statements ..
54
*
55
      N1SV = N1
56
      N2SV = N2
57
      IF( DTRD1.GT.0 ) THEN
58
         IND1 = 1
59
      ELSE
60
         IND1 = N1
61
      END IF
62
      IF( DTRD2.GT.0 ) THEN
63
         IND2 = 1 + N1
64
      ELSE
65
         IND2 = N1 + N2
66
      END IF
67
      I = 1
68
*     while ( (N1SV > 0) & (N2SV > 0) )
69
   10 CONTINUE
70
      IF( N1SV.GT.0 .AND. N2SV.GT.0 ) THEN
71
         IF( A( IND1 ).LE.A( IND2 ) ) THEN
72
            INDEX( I ) = IND1
73
            I = I + 1
74
            IND1 = IND1 + DTRD1
75
            N1SV = N1SV - 1
76
         ELSE
77
            INDEX( I ) = IND2
78
            I = I + 1
79
            IND2 = IND2 + DTRD2
80
            N2SV = N2SV - 1
81
         END IF
82
         GO TO 10
83
      END IF
84
*     end while
85
      IF( N1SV.EQ.0 ) THEN
86
         DO 20 N1SV = 1, N2SV
87
            INDEX( I ) = IND2
88
            I = I + 1
89
            IND2 = IND2 + DTRD2
90
   20    CONTINUE
91
      ELSE
92
*     N2SV .EQ. 0
93
         DO 30 N2SV = 1, N1SV
94
            INDEX( I ) = IND1
95
            I = I + 1
96
            IND1 = IND1 + DTRD1
97
   30    CONTINUE
98
      END IF
99
*
100
      RETURN
101
*
102
*     End of DLAMRG
103
*
104
      END