source: LMDZ6/trunk/libf/filtrez/eigen_sort.f90 @ 5246

Last change on this file since 5246 was 5246, checked in by abarral, 23 hours 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: 452 bytes
Line 
1!
2! $Header$
3!
4    SUBROUTINE eigen_sort(d,v,n,np)
5      INTEGER :: n,np
6      REAL :: d(np),v(np,np)
7      INTEGER :: i,j,k
8      REAL :: p
9
10   DO i=1,n-1
11      k=i
12      p=d(i)
13    DO j=i+1,n
14       IF(d(j).ge.p) THEN
15        k=j
16        p=d(j)
17       ENDIF
18    ENDDO
19
20    IF(k.ne.i) THEN
21      d(k)=d(i)
22      d(i)=p
23     DO j=1,n
24      p=v(j,i)
25      v(j,i)=v(j,k)
26      v(j,k)=p
27     ENDDO
28    ENDIF
29   ENDDO
30
31    RETURN
32END SUBROUTINE eigen_sort
Note: See TracBrowser for help on using the repository browser.