source: LMDZ6/trunk/libf/misc/sort.f90 @ 5301

Last change on this file since 5301 was 5246, checked in by abarral, 11 days ago

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 573 bytes
Line 
1!
2! $Header$
3!
4!
5!
6SUBROUTINE sort(n,d)
7  !
8  ! P.Le Van
9  !
10  !...  cette routine met le tableau d  dans l'ordre croissant  ....
11  !c   ( pour avoir l'ordre decroissant,il suffit de remplacer l'instruc
12  !  tion  situee + bas  IF(d(j).LE.p)  THEN     par
13  !                       IF(d(j).GE.p)  THEN
14  !
15
16  INTEGER :: n
17  REAL :: d(n) , p
18  INTEGER :: i,j,k
19
20  DO i=1,n-1
21    k=i
22    p=d(i)
23    DO j=i+1,n
24     IF(d(j).LE.p) THEN
25       k=j
26       p=d(j)
27     ENDIF
28    ENDDO
29
30   IF(k.ne.i) THEN
31     d(k)=d(i)
32     d(i)=p
33   ENDIF
34  ENDDO
35
36   RETURN
37END SUBROUTINE sort
Note: See TracBrowser for help on using the repository browser.