LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dlaord.f
Go to the documentation of this file.
1 *> \brief \b DLAORD
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE DLAORD( JOB, N, X, INCX )
12 *
13 * .. Scalar Arguments ..
14 * CHARACTER JOB
15 * INTEGER INCX, N
16 * ..
17 * .. Array Arguments ..
18 * DOUBLE PRECISION X( * )
19 * ..
20 *
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> DLAORD sorts the elements of a vector x in increasing or decreasing
28 *> order.
29 *> \endverbatim
30 *
31 * Arguments:
32 * ==========
33 *
34 *> \param[in] JOB
35 *> \verbatim
36 *> JOB is CHARACTER
37 *> = 'I': Sort in increasing order
38 *> = 'D': Sort in decreasing order
39 *> \endverbatim
40 *>
41 *> \param[in] N
42 *> \verbatim
43 *> N is INTEGER
44 *> The length of the vector X.
45 *> \endverbatim
46 *>
47 *> \param[in,out] X
48 *> \verbatim
49 *> X is DOUBLE PRECISION array, dimension
50 *> (1+(N-1)*INCX)
51 *> On entry, the vector of length n to be sorted.
52 *> On exit, the vector x is sorted in the prescribed order.
53 *> \endverbatim
54 *>
55 *> \param[in] INCX
56 *> \verbatim
57 *> INCX is INTEGER
58 *> The spacing between successive elements of X. INCX >= 0.
59 *> \endverbatim
60 *
61 * Authors:
62 * ========
63 *
64 *> \author Univ. of Tennessee
65 *> \author Univ. of California Berkeley
66 *> \author Univ. of Colorado Denver
67 *> \author NAG Ltd.
68 *
69 *> \date November 2011
70 *
71 *> \ingroup double_lin
72 *
73 * =====================================================================
74  SUBROUTINE dlaord( JOB, N, X, INCX )
75 *
76 * -- LAPACK test routine (version 3.4.0) --
77 * -- LAPACK is a software package provided by Univ. of Tennessee, --
78 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
79 * November 2011
80 *
81 * .. Scalar Arguments ..
82  CHARACTER JOB
83  INTEGER INCX, N
84 * ..
85 * .. Array Arguments ..
86  DOUBLE PRECISION X( * )
87 * ..
88 *
89 * =====================================================================
90 *
91 * .. Local Scalars ..
92  INTEGER I, INC, IX, IXNEXT
93  DOUBLE PRECISION TEMP
94 * ..
95 * .. External Functions ..
96  LOGICAL LSAME
97  EXTERNAL lsame
98 * ..
99 * .. Intrinsic Functions ..
100  INTRINSIC abs
101 * ..
102 * .. Executable Statements ..
103 *
104  inc = abs( incx )
105  IF( lsame( job, 'I' ) ) THEN
106 *
107 * Sort in increasing order
108 *
109  DO 20 i = 2, n
110  ix = 1 + ( i-1 )*inc
111  10 CONTINUE
112  IF( ix.EQ.1 )
113  $ GO TO 20
114  ixnext = ix - inc
115  IF( x( ix ).GT.x( ixnext ) ) THEN
116  GO TO 20
117  ELSE
118  temp = x( ix )
119  x( ix ) = x( ixnext )
120  x( ixnext ) = temp
121  END IF
122  ix = ixnext
123  GO TO 10
124  20 CONTINUE
125 *
126  ELSE IF( lsame( job, 'D' ) ) THEN
127 *
128 * Sort in decreasing order
129 *
130  DO 40 i = 2, n
131  ix = 1 + ( i-1 )*inc
132  30 CONTINUE
133  IF( ix.EQ.1 )
134  $ GO TO 40
135  ixnext = ix - inc
136  IF( x( ix ).LT.x( ixnext ) ) THEN
137  GO TO 40
138  ELSE
139  temp = x( ix )
140  x( ix ) = x( ixnext )
141  x( ixnext ) = temp
142  END IF
143  ix = ixnext
144  GO TO 30
145  40 CONTINUE
146  END IF
147  RETURN
148 *
149 * End of DLAORD
150 *
151  END
subroutine dlaord(JOB, N, X, INCX)
DLAORD
Definition: dlaord.f:75